Update concepts branch to revision 131834
[official-gcc.git] / gcc / testsuite / gfortran.fortran-torture / execute / st_function.f90
blobe8788025ad8bab9346ac04d7f54c56b067a057ab
1 ! Program to test STATEMENT function
2 program st_fuction
3 call simple_case
4 call with_function_call
5 call with_character_dummy
6 call with_derived_type_dummy
7 call with_pointer_dummy
8 call multiple_eval
10 contains
11 subroutine simple_case
12 integer st1, st2
13 integer c(10, 10)
14 st1 (i, j) = i + j
15 st2 (i, j) = c(i, j)
17 if (st1 (1, 2) .ne. 3) call abort
18 c = 3
19 if (st2 (1, 2) .ne. 3 .or. st2 (2, 3) .ne. 3) call abort
20 end subroutine
22 subroutine with_function_call
23 integer fun, st3
24 st3 (i, j) = fun (i) + fun (j)
26 if (st3 (fun (2), 4) .ne. 16) call abort
27 end subroutine
29 subroutine with_character_dummy
30 character (len=4) s1, s2, st4
31 character (len=10) st5, s0
32 st4 (i, j) = "0123456789"(i:j)
33 st5 (s1, s2) = s1 // s2
35 if (st4 (1, 4) .ne. "0123" ) call abort
36 if (st5 ("01", "02") .ne. "01 02 ") call abort ! { dg-warning "Character length of actual argument shorter" }
37 end subroutine
39 subroutine with_derived_type_dummy
40 type person
41 integer age
42 character (len=50) name
43 end type person
44 type (person) me, p, tom
45 type (person) st6
46 st6 (p) = p
48 me%age = 5
49 me%name = "Tom"
50 tom = st6 (me)
51 if (tom%age .ne. 5) call abort
52 if (tom%name .gt. "Tom") call abort
53 end subroutine
55 subroutine with_pointer_dummy
56 character(len=4), pointer:: p, p1
57 character(len=4), target:: i
58 character(len=6) a
59 a (p) = p // '10'
61 p1 => i
62 i = '1234'
63 if (a (p1) .ne. '123410') call abort
64 end subroutine
66 subroutine multiple_eval
67 integer st7, fun2, fun
69 st7(i) = i + fun(i)
71 if (st7(fun2(10)) .ne. 3) call abort
72 end subroutine
73 end
75 ! This functon returns the argument passed on the previous call.
76 integer function fun2 (i)
77 integer i
78 integer, save :: val = 1
80 fun2 = val
81 val = i
82 end function
84 integer function fun (i)
85 integer i
86 fun = i * 2
87 end function