make designMode property available from js
[kdelibs.git] / kate / tests / highlight.f90
blobe2008c20a28700a71e5eadbf85da9875ea2bb410
1 ! This file is an example to test the syntax highlighting file F.xml
2 ! (for fortran 90 and F)
4 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
5 ! THIS IS AN EXAMPLE OF A MODULE !
6 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
7 module module_example
9 ! use 'implicit none' when you want all variables to be declared
10 implicit none
12 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
13 ! PUBLICS AND PRIVATES
15 ! In fortran 90 you can define your own operator
16 public :: operator(.norm.)
17 public :: operator(+) ! <-- you can also overload the usual operators
18 public :: factorial
19 public :: example_fn
21 private :: point3d_add
22 private :: point3d_norm
24 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
25 ! USER-DEFINED TYPES...
27 ! This is a definition to use in declarations of real variables,
28 ! parameters, etc.
29 integer, parameter, public :: kr = selected_real_kind(10)
31 ! This is a user-defined type
32 type, public :: point3d
33 real(kind=kr) :: x, y, z
34 end type point3d
36 ! This type is useless: it is only an example of type definition!
37 type, public :: example_type
38 complex(kind=kr) :: c ! <-- a complex number (two reals of kind kr)!
39 real, dimension(-10:10) :: & ! <-- this line does not end here!
40 r1, r2 ! <-- this is the final part of the previous line
41 real, pointer, dimension(:) :: pointer_to_array_of_real
42 real, dimension(:), pointer :: array_of_pointer_to_real
43 end type example_type
45 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
46 ! INTERFACES...
48 ! Interface for the norm of a 3-D vector
49 interface operator(.norm.)
50 module procedure point3d_norm
51 end interface
53 ! Interface for the operator '+'
54 interface operator(+)
55 module procedure point3d_add
56 end interface
58 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
59 ! SOME DECLARATIONS...
61 ! A real number can be declared with the following line:
62 real(kind=kr) :: real_var1
63 ! But if you are not interested on the precision of floating point numbers,
64 ! you can use simply:
65 real :: real_var2
67 ! An array can be declared in two ways:
68 real(kind=kr), dimension(1:10, -4:5), private :: a, b, c
69 real(kind=kr), private :: d(1:10, -4:5)
71 ! This is a string with fixed lenght
72 character(len=10) :: str_var
74 ! This is an allocatable array, which can be a target of a pointer
75 type(example_type), private, dimension(:), allocatable, target :: &
76 many_examples
78 ! Fortran 90 hasn't got its own preprocessor, it uses the C preprocessor!
79 #ifdef XXX
80 c <-- this is a comment in the old fortran 77 style (fixed form)
81 c This is a free form file, so we shouldn't use this kind of comments!
82 c But fortran 90 still understands fixed form, when parsing sources with
83 c the *.f extension.
84 c ! <-- this 'c' shouldn't be highlighted as a comment!
85 #endif
87 contains
90 ! The sum of two points
91 pure function point3d_add(a, b) result(rs)
92 type(point3d) :: rs
93 type(point3d), intent(in) :: a, b
94 rs%x = a%x + b%x
95 rs%y = a%y + b%y
96 rs%z = a%z + b%z
97 end function point3d_add
100 ! The norm of a point
101 pure function point3d_norm(a) result(rs)
102 real(kind=kr) :: rs
103 type(point3d), intent(in) :: a
104 rs = sqrt(a%x * a%x + a%y * a%y + a%z * a%z)
105 end function point3d_norm
108 ! A simple recursive function
109 recursive function factorial(i) result (rs)
110 integer :: rs
111 integer, intent(in) :: i
112 if ( i <= 1 ) then
113 rs = 1
114 else
115 rs = i * factorial(i - 1)
116 end if
117 end function factorial
120 ! This is a useless function
121 subroutine example_fn(int_arg, real_arg, str_arg)
122 integer, intent(in) :: int_arg
123 real(kind=kr), intent(out) :: real_arg
124 character(len=*), intent(in) :: str_arg
126 type(example_type), pointer :: p
127 integer :: n, i, j
128 logical :: flag
130 flag = .true. ! .true. is not an operator!
131 if ( flag .and. flag ) then ! .and. is a pre-defined operator
132 print *, "blabla"
133 end if
135 ! Examples of inquiry functions: allocated, lbound, ubound.
136 if ( .not. allocated(many_examples) ) then
137 allocate( many_examples(10) )
138 end if
139 print *, "Lower bound = ", lbound(many_examples, 1)
140 print *, "Upper bound = ", ubound(many_examples, 1)
142 p => many_examples(5) ! <-- p is a pointer
144 ! A strange way to calculate i*i: add the first i odd numbers
145 i = 6
146 j = 0
147 do n = 1, i
148 j = j + (2*n - 1)
149 end do
150 print *, "i*i = ", i*i, j
152 real_arg = real(j) ! <-- here the highlighting is not very good:
153 ! it is unable to distinguish between this and a definition like:
154 ! real(kind=kr) :: a
155 deallocate( many_examples )
156 end subroutine example_fn
158 end module module_example
161 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
162 ! THIS IS THE MAIN PROGRAM !
163 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
164 program example
165 use module_example
167 ! this is another example of use of the 'implicit' keyword
168 implicit double precision (a-h,o-z)
170 real(kind=kr) :: var_out
172 type(point3d) :: &
173 a = point3d(0.0_kr, 1.0_kr, 2.0_kr), &
174 b = point3d(4.0_kr, 5.0_kr, 6.0_kr)
176 print *, "a + b = ", .norm. (a + b)
177 print *, "factorial of 5 = ", factorial(5)
179 call example_fn(1, var_out, "hello!")
181 end program example