diff --git a/autotests/folding/highlight.f.fold b/autotests/folding/highlight.f.fold new file mode 100644 --- /dev/null +++ b/autotests/folding/highlight.f.fold @@ -0,0 +1,28 @@ +* This file is an example to test the syntax highlighting file fortran-fixed.xml +* (for fortran, fixed format) + +c <-- this is a comment in the old fortran 77 style (fixed form) +c In the free form file, so we shouldn't use this kind of comments! +c But fortran 90 still understands fixed form, when parsing sources with +c the *.f extension. + +* this 'c' shouldn't be highlighted as a comment! + c + +* Prints the values of e ** (j * i * pi / 4) for i = 0, 1, 2, ..., 7 +* where j is the imaginary number sqrt(-1) + +PROGRAM CMPLXD + IMPLICIT COMPLEX(X) + PARAMETER (PI = 3.141592653589793, XJ = (0, 1)) + DO 1, I = 0, 7 + X = EXP(XJ * I * PI / 4) + IF (AIMAG(X).LT.0) THEN + PRINT 2, 'e**(j*', I, '*pi/4) = ', REAL(X), ' - j',-AIMAG(X) + ELSE + PRINT 2, 'e**(j*', I, '*pi/4) = ', REAL(X), ' + j', AIMAG(X) + END IF + FORMAT (A, I1, A, F10.7, A, F9.7) + CONTINUE + STOP +END diff --git a/autotests/folding/highlight.f90.fold b/autotests/folding/highlight.f90.fold --- a/autotests/folding/highlight.f90.fold +++ b/autotests/folding/highlight.f90.fold @@ -1,12 +1,12 @@ -! This file is an example to test the syntax highlighting file F.xml -! (for fortran 90 and F) +! This file is an example to test the syntax highlighting file fortran-free.xml +! (for fortran, free format) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! THIS IS AN EXAMPLE OF A MODULE ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! module module_example - ! use 'implicit none' when you want all variables to be declared + ! use 'implicit none' when you want all variables to be declared implicit none !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! @@ -29,7 +29,7 @@ integer, parameter, public :: kr = selected_real_kind(10) ! This is a user-defined type - type, public :: point3d + type, public :: point3d real(kind=kr) :: x, y, z end type point3d @@ -41,7 +41,7 @@ real, pointer, dimension(:) :: pointer_to_array_of_real real, dimension(:), pointer :: array_of_pointer_to_real end type example_type - + !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! INTERFACES... @@ -77,14 +77,10 @@ ! Fortran 90 hasn't got its own preprocessor, it uses the C preprocessor! #ifdef XXX -c <-- this is a comment in the old fortran 77 style (fixed form) -c This is a free form file, so we shouldn't use this kind of comments! -c But fortran 90 still understands fixed form, when parsing sources with -c the *.f extension. - c ! <-- this 'c' shouldn't be highlighted as a comment! + #endif -contains +contains ! The sum of two points @@ -101,7 +97,7 @@ pure function point3d_norm(a) result(rs) real(kind=kr) :: rs type(point3d), intent(in) :: a - rs = sqrt(a%x * a%x + a%y * a%y + a%z * a%z) + rs = sqrt(a%x * a%x + a%y * a%y + a%z * a%z) end function point3d_norm @@ -146,7 +142,7 @@ j = 0 do n = 1, i j = j + (2*n - 1) - end do + end do print *, "i*i = ", i*i, j real_arg = real(j) ! <-- here the highlighting is not very good: diff --git a/autotests/html/highlight.f.html b/autotests/html/highlight.f.html new file mode 100644 --- /dev/null +++ b/autotests/html/highlight.f.html @@ -0,0 +1,35 @@ + + + +highlight.f + +
+* This file is an example to test the syntax highlighting file fortran-fixed.xml
+* (for fortran, fixed format)
+
+c <-- this is a comment in the old fortran 77 style (fixed form)
+c In the free form file, so we shouldn't use this kind of comments!
+c But fortran 90 still understands fixed form, when parsing sources with
+c the *.f extension.
+
+* this 'c' shouldn't be highlighted as a comment!
+ c
+
+*     Prints the values of e ** (j * i * pi / 4) for i = 0, 1, 2, ..., 7
+*         where j is the imaginary number sqrt(-1)
+
+PROGRAM CMPLXD
+    IMPLICIT COMPLEX(X)
+    PARAMETER (PI = 3.141592653589793, XJ = (0, 1))
+    DO 1, I = 0, 7
+        X = EXP(XJ * I * PI / 4)
+        IF (AIMAG(X).LT.0) THEN
+            PRINT 2, 'e**(j*', I, '*pi/4) = ', REAL(X), ' - j',-AIMAG(X)
+        ELSE
+            PRINT 2, 'e**(j*', I, '*pi/4) = ', REAL(X), ' + j', AIMAG(X)
+        END IF
+        FORMAT (A, I1, A, F10.7, A, F9.7)
+        CONTINUE
+    STOP
+END
+
diff --git a/autotests/html/highlight.f90.html b/autotests/html/highlight.f90.html --- a/autotests/html/highlight.f90.html +++ b/autotests/html/highlight.f90.html @@ -2,17 +2,17 @@ highlight.f90 - +
-! This file is an example to test the syntax highlighting file F.xml
-! (for fortran 90 and F)
+! This file is an example to test the syntax highlighting file fortran-free.xml
+! (for fortran, free format)
 
 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
 !                      THIS IS AN EXAMPLE OF A MODULE                          !
 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
 module module_example
 
-  ! use 'implicit none' when you want all variables to be declared  
+  ! use 'implicit none' when you want all variables to be declared
   implicit none
 
 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
@@ -35,19 +35,19 @@
   integer, parameter, public :: kr = selected_real_kind(10)
 
   ! This is a user-defined type
-  type, public :: point3d 
-    real(kind=kr) :: x, y, z
+  type, public :: point3d
+    real(kind=kr) :: x, y, z
   end type point3d
 
   ! This type is useless: it is only an example of type definition!
   type, public :: example_type
     complex(kind=kr)            :: c ! <-- a complex number (two reals of kind kr)!
-    real, dimension(-10:10)     :: & ! <-- this line does not end here!
+    real, dimension(-10:10)     :: & ! <-- this line does not end here!
       r1, r2 ! <-- this is the final part of the previous line
-    real, pointer, dimension(:) :: pointer_to_array_of_real
-    real, dimension(:), pointer :: array_of_pointer_to_real
+    real, pointer, dimension(:) :: pointer_to_array_of_real
+    real, dimension(:), pointer :: array_of_pointer_to_real
   end type example_type
-  
+
 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
 ! INTERFACES...
 
@@ -65,14 +65,14 @@
 ! SOME DECLARATIONS...
 
   ! A real number can be declared with the following line:
-  real(kind=kr) :: real_var1
+  real(kind=kr) :: real_var1
   ! But if you are not interested on the precision of floating point numbers,
   ! you can use simply:
-  real :: real_var2
+  real :: real_var2
 
   ! An array can be declared in two ways:
-  real(kind=kr), dimension(1:10, -4:5), private :: a, b, c
-  real(kind=kr), private :: d(1:10, -4:5)
+  real(kind=kr), dimension(1:10, -4:5), private :: a, b, c
+  real(kind=kr), private :: d(1:10, -4:5)
 
   ! This is a string with fixed lenght
   character(len=10) :: str_var
@@ -83,14 +83,10 @@
 
 ! Fortran 90 hasn't got its own preprocessor, it uses the C preprocessor!
 #ifdef XXX
-c <-- this is a comment in the old fortran 77 style (fixed form)
-c This is a free form file, so we shouldn't use this kind of comments!
-c But fortran 90 still understands fixed form, when parsing sources with
-c the *.f extension.
- c ! <-- this 'c' shouldn't be highlighted as a comment!
+
 #endif
 
-contains
+contains
 
 
   ! The sum of two points
@@ -105,17 +101,17 @@
 
   ! The norm of a point
   pure function point3d_norm(a) result(rs)
-    real(kind=kr) :: rs
+    real(kind=kr) :: rs
     type(point3d), intent(in) :: a
-    rs = sqrt(a%x * a%x + a%y * a%y + a%z * a%z)    
+    rs = sqrt(a%x * a%x + a%y * a%y + a%z * a%z)
   end function point3d_norm
 
 
   ! A simple recursive function
   recursive function factorial(i) result (rs)
     integer :: rs
     integer, intent(in) :: i
-    if ( i <= 1 ) then
+    if ( i <= 1 ) then
       rs = 1
     else
       rs = i * factorial(i - 1)
@@ -126,7 +122,7 @@
   ! This is a useless function
   subroutine example_fn(int_arg, real_arg, str_arg)
     integer, intent(in) :: int_arg
-    real(kind=kr), intent(out) :: real_arg
+    real(kind=kr), intent(out) :: real_arg
     character(len=*), intent(in) :: str_arg
 
     type(example_type), pointer :: p
@@ -152,10 +148,10 @@
     j = 0
     do n = 1, i
       j = j + (2*n - 1)
-    end do 
+    end do
     print *, "i*i = ", i*i, j
 
-    real_arg = real(j) ! <-- here the highlighting is not very good:
+    real_arg = real(j) ! <-- here the highlighting is not very good:
     ! it is unable to distinguish between this and a definition like:
     !  real(kind=kr) :: a
     deallocate( many_examples )
@@ -171,9 +167,9 @@
   use module_example
 
   ! this is another example of use of the 'implicit' keyword
-  implicit double precision (a-h,o-z)
+  implicit double precision (a-h,o-z)
 
-  real(kind=kr) :: var_out
+  real(kind=kr) :: var_out
 
   type(point3d) :: &
    a = point3d(0.0_kr, 1.0_kr, 2.0_kr), &
diff --git a/autotests/input/highlight.f b/autotests/input/highlight.f
new file mode 100644
--- /dev/null
+++ b/autotests/input/highlight.f
@@ -0,0 +1,28 @@
+* This file is an example to test the syntax highlighting file fortran-fixed.xml
+* (for fortran, fixed format)
+
+c <-- this is a comment in the old fortran 77 style (fixed form)
+c In the free form file, so we shouldn't use this kind of comments!
+c But fortran 90 still understands fixed form, when parsing sources with
+c the *.f extension.
+
+* this 'c' shouldn't be highlighted as a comment!
+ c
+
+*     Prints the values of e ** (j * i * pi / 4) for i = 0, 1, 2, ..., 7
+*         where j is the imaginary number sqrt(-1)
+
+PROGRAM CMPLXD
+    IMPLICIT COMPLEX(X)
+    PARAMETER (PI = 3.141592653589793, XJ = (0, 1))
+    DO 1, I = 0, 7
+        X = EXP(XJ * I * PI / 4)
+        IF (AIMAG(X).LT.0) THEN
+            PRINT 2, 'e**(j*', I, '*pi/4) = ', REAL(X), ' - j',-AIMAG(X)
+        ELSE
+            PRINT 2, 'e**(j*', I, '*pi/4) = ', REAL(X), ' + j', AIMAG(X)
+        END IF
+        FORMAT (A, I1, A, F10.7, A, F9.7)
+        CONTINUE
+    STOP
+END
diff --git a/autotests/input/highlight.f90 b/autotests/input/highlight.f90
--- a/autotests/input/highlight.f90
+++ b/autotests/input/highlight.f90
@@ -1,12 +1,12 @@
-! This file is an example to test the syntax highlighting file F.xml
-! (for fortran 90 and F)
+! This file is an example to test the syntax highlighting file fortran-free.xml
+! (for fortran, free format)
 
 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
 !                      THIS IS AN EXAMPLE OF A MODULE                          !
 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
 module module_example
 
-  ! use 'implicit none' when you want all variables to be declared  
+  ! use 'implicit none' when you want all variables to be declared
   implicit none
 
 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
@@ -29,7 +29,7 @@
   integer, parameter, public :: kr = selected_real_kind(10)
 
   ! This is a user-defined type
-  type, public :: point3d 
+  type, public :: point3d
     real(kind=kr) :: x, y, z
   end type point3d
 
@@ -41,7 +41,7 @@
     real, pointer, dimension(:) :: pointer_to_array_of_real
     real, dimension(:), pointer :: array_of_pointer_to_real
   end type example_type
-  
+
 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
 ! INTERFACES...
 
@@ -77,11 +77,7 @@
 
 ! Fortran 90 hasn't got its own preprocessor, it uses the C preprocessor!
 #ifdef XXX
-c <-- this is a comment in the old fortran 77 style (fixed form)
-c This is a free form file, so we shouldn't use this kind of comments!
-c But fortran 90 still understands fixed form, when parsing sources with
-c the *.f extension.
- c ! <-- this 'c' shouldn't be highlighted as a comment!
+
 #endif
 
 contains
@@ -101,7 +97,7 @@
   pure function point3d_norm(a) result(rs)
     real(kind=kr) :: rs
     type(point3d), intent(in) :: a
-    rs = sqrt(a%x * a%x + a%y * a%y + a%z * a%z)    
+    rs = sqrt(a%x * a%x + a%y * a%y + a%z * a%z)
   end function point3d_norm
 
 
@@ -146,7 +142,7 @@
     j = 0
     do n = 1, i
       j = j + (2*n - 1)
-    end do 
+    end do
     print *, "i*i = ", i*i, j
 
     real_arg = real(j) ! <-- here the highlighting is not very good:
diff --git a/autotests/reference/highlight.f.ref b/autotests/reference/highlight.f.ref
new file mode 100644
--- /dev/null
+++ b/autotests/reference/highlight.f.ref
@@ -0,0 +1,28 @@
+* This file is an example to test the syntax highlighting file fortran-fixed.xml
+* (for fortran, fixed format)
+
+c <-- this is a comment in the old fortran 77 style (fixed form)
+c In the free form file, so we shouldn't use this kind of comments!
+c But fortran 90 still understands fixed form, when parsing sources with
+c the *.f extension.
+
+* this 'c' shouldn't be highlighted as a comment!
+ c
+
+* Prints the values of e ** (j * i * pi / 4) for i = 0, 1, 2, ..., 7
+* where j is the imaginary number sqrt(-1)
+
+PROGRAM CMPLXD
+ IMPLICIT COMPLEX(X)
+ PARAMETER (PI = 3.141592653589793, XJ = (0, 1))
+ DO 1, I = 0, 7
+ X = EXP(XJ * I * PI / 4)
+ IF (AIMAG(X).LT.0) THEN
+ PRINT 2, 'e**(j*', I, '*pi/4) = ', REAL(X), ' - j',-AIMAG(X)
+ ELSE
+ PRINT 2, 'e**(j*', I, '*pi/4) = ', REAL(X), ' + j', AIMAG(X)
+ END IF
+ FORMAT (A, I1, A, F10.7, A, F9.7)
+ CONTINUE
+ STOP
+END
diff --git a/autotests/reference/highlight.f90.ref b/autotests/reference/highlight.f90.ref --- a/autotests/reference/highlight.f90.ref +++ b/autotests/reference/highlight.f90.ref @@ -1,12 +1,12 @@ -! This file is an example to test the syntax highlighting file F.xml
-! (for fortran 90 and F)
+! This file is an example to test the syntax highlighting file fortran-free.xml
+! (for fortran, free format)

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! THIS IS AN EXAMPLE OF A MODULE !
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
module module_example

- ! use 'implicit none' when you want all variables to be declared
+ ! use 'implicit none' when you want all variables to be declared
implicit none

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
@@ -29,19 +29,19 @@ integer, parameter, public :: kr = selected_real_kind(10)

! This is a user-defined type
- type, public :: point3d
- real(kind=kr) :: x, y, z
+ type, public :: point3d
+ real(kind=kr) :: x, y, z
end type point3d

! This type is useless: it is only an example of type definition!
type, public :: example_type
complex(kind=kr) :: c ! <-- a complex number (two reals of kind kr)!
- real, dimension(-10:10) :: & ! <-- this line does not end here!
+ real, dimension(-10:10) :: & ! <-- this line does not end here!
r1, r2 ! <-- this is the final part of the previous line
- real, pointer, dimension(:) :: pointer_to_array_of_real
- real, dimension(:), pointer :: array_of_pointer_to_real
+ real, pointer, dimension(:) :: pointer_to_array_of_real
+ real, dimension(:), pointer :: array_of_pointer_to_real
end type example_type
-
+
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! INTERFACES...

@@ -59,14 +59,14 @@ ! SOME DECLARATIONS...

! A real number can be declared with the following line:
- real(kind=kr) :: real_var1
+ real(kind=kr) :: real_var1
! But if you are not interested on the precision of floating point numbers,
! you can use simply:
- real :: real_var2
+ real :: real_var2

! An array can be declared in two ways:
- real(kind=kr), dimension(1:10, -4:5), private :: a, b, c
- real(kind=kr), private :: d(1:10, -4:5)
+ real(kind=kr), dimension(1:10, -4:5), private :: a, b, c
+ real(kind=kr), private :: d(1:10, -4:5)

! This is a string with fixed lenght
character(len=10) :: str_var
@@ -77,14 +77,10 @@
! Fortran 90 hasn't got its own preprocessor, it uses the C preprocessor!
#ifdef XXX
-c <-- this is a comment in the old fortran 77 style (fixed form)
-c This is a free form file, so we shouldn't use this kind of comments!
-c But fortran 90 still understands fixed form, when parsing sources with
-c the *.f extension.
- c ! <-- this 'c' shouldn't be highlighted as a comment!
+
#endif

-contains
+contains


! The sum of two points
@@ -99,17 +95,17 @@
! The norm of a point
pure function point3d_norm(a) result(rs)
- real(kind=kr) :: rs
+ real(kind=kr) :: rs
type(point3d), intent(in) :: a
- rs = sqrt(a%x * a%x + a%y * a%y + a%z * a%z)
+ rs = sqrt(a%x * a%x + a%y * a%y + a%z * a%z)
end function point3d_norm


! A simple recursive function
recursive function factorial(i) result (rs)
integer :: rs
integer, intent(in) :: i
- if ( i <= 1 ) then
+ if ( i <= 1 ) then
rs = 1
else
rs = i * factorial(i - 1)
@@ -120,7 +116,7 @@ ! This is a useless function
subroutine example_fn(int_arg, real_arg, str_arg)
integer, intent(in) :: int_arg
- real(kind=kr), intent(out) :: real_arg
+ real(kind=kr), intent(out) :: real_arg
character(len=*), intent(in) :: str_arg

type(example_type), pointer :: p
@@ -146,10 +142,10 @@ j = 0
do n = 1, i
j = j + (2*n - 1)
- end do
+ end do
print *, "i*i = ", i*i, j

- real_arg = real(j) ! <-- here the highlighting is not very good:
+ real_arg = real(j) ! <-- here the highlighting is not very good:
! it is unable to distinguish between this and a definition like:
! real(kind=kr) :: a
deallocate( many_examples )
@@ -165,9 +161,9 @@ use module_example

! this is another example of use of the 'implicit' keyword
- implicit double precision (a-h,o-z)
+ implicit double precision (a-h,o-z)

- real(kind=kr) :: var_out
+ real(kind=kr) :: var_out

type(point3d) :: &
a = point3d(0.0_kr, 1.0_kr, 2.0_kr), &
diff --git a/data/syntax/fortran.xml b/data/syntax/fortran-fixed.xml rename from data/syntax/fortran.xml rename to data/syntax/fortran-fixed.xml --- a/data/syntax/fortran.xml +++ b/data/syntax/fortran-fixed.xml @@ -1,7 +1,8 @@ - + + @@ -11,19 +12,13 @@ allocate break call - case common - continue cycle deallocate - default - forall where elsewhere - - equivalence exit external @@ -48,15 +43,15 @@ recursive result return - select - selectcase stop - to use only entry while + access @@ -128,8 +123,6 @@ pad - double - precision parameter save pointer @@ -139,6 +132,7 @@ allocatable optional sequence + + - + + + + - + + - + + + + + - + @@ -430,9 +433,7 @@ - - - + @@ -455,46 +456,43 @@ - + - - - + + - - + - + - - + + + - - - + - - - + + - - + + @@ -548,7 +546,7 @@ - + @@ -577,8 +575,8 @@ - + diff --git a/data/syntax/fortran-free.xml b/data/syntax/fortran-free.xml new file mode 100644 --- /dev/null +++ b/data/syntax/fortran-free.xml @@ -0,0 +1,311 @@ + + + + + + + + + + + + keywords##Fortran (Fixed Format) + associate + import + impure + + + io_functions##Fortran (Fixed Format) + + + + io_keywords##Fortran (Fixed Format) + + + + open_keywords##Fortran (Fixed Format) + + + + inquire_keywords##Fortran (Fixed Format) + + + types##Fortran (Fixed Format) + abstract + asynchronous + bind + contiguous + deferred + enum + enumerator + final + generic + nopass + non_overridable + protected + value + volatile + + + + + + + elemental_procs##Fortran (Fixed Format) + + acosh + asinh + atanh + bessel_j0 + bessel_j1 + bessel_jn + bessel_y0 + bessel_y1 + bessel_yn + erf + erfc + erfc_scaled + gamma + log_gamma + hypot + + + + + inquiry_fn##Fortran (Fixed Format) + + extends_type_of + same_type_as + storage_size + + lcobound + ucobound + image_index + + + + + transform_fn##Fortran (Fixed Format) + + selected_char_kind + + parity + iall + iany + iparity + + num_images + this_image + + + + + non_elem_subr##Fortran (Fixed Format) + + cpu_time + + execute_command_line + get_environment_variable + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +