lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / value_1.f90
blobab0d40952209533ec96b35b6b088f4b3eb92ed44
1 ! { dg-do run }
2 ! { dg-options "-std=f2003 " }
3 ! Tests the functionality of the patch for PR29642, which requested the
4 ! implementation of the F2003 VALUE attribute for gfortran.
6 ! Contributed by Paul Thomas <pault@gcc.gnu.org>
8 module global
9 type :: mytype
10 real(4) :: x
11 character(4) :: c
12 end type mytype
13 contains
14 subroutine typhoo (dt)
15 type(mytype), value :: dt
16 if (dtne (dt, mytype (42.0, "lmno"))) STOP 1
17 dt = mytype (21.0, "wxyz")
18 if (dtne (dt, mytype (21.0, "wxyz"))) STOP 2
19 end subroutine typhoo
21 logical function dtne (a, b)
22 type(mytype) :: a, b
23 dtne = .FALSE.
24 if ((a%x /= b%x) .or. (a%c /= b%c)) dtne = .TRUE.
25 end function dtne
26 end module global
28 program test_value
29 use global
30 integer(8) :: i = 42
31 real(8) :: r = 42.0
32 character(2) :: c = "ab"
33 complex(8) :: z = (-99.0, 199.0)
34 type(mytype) :: dt = mytype (42.0, "lmno")
36 call foo (c)
37 if (c /= "ab") STOP 3
39 call bar (i)
40 if (i /= 42) STOP 4
42 call foobar (r)
43 if (r /= 42.0) STOP 5
45 call complex_foo (z)
46 if (z /= (-99.0, 199.0)) STOP 6
48 call typhoo (dt)
49 if (dtne (dt, mytype (42.0, "lmno"))) STOP 7
51 r = 20.0
52 call foobar (r*2.0 + 2.0)
54 contains
55 subroutine foo (c)
56 character(2), value :: c
57 if (c /= "ab") STOP 8
58 c = "cd"
59 if (c /= "cd") STOP 9
60 end subroutine foo
62 subroutine bar (i)
63 integer(8), value :: i
64 if (i /= 42) STOP 10
65 i = 99
66 if (i /= 99) STOP 11
67 end subroutine bar
69 subroutine foobar (r)
70 real(8), value :: r
71 if (r /= 42.0) STOP 12
72 r = 99.0
73 if (r /= 99.0) STOP 13
74 end subroutine foobar
76 subroutine complex_foo (z)
77 COMPLEX(8), value :: z
78 if (z /= (-99.0, 199.0)) STOP 14
79 z = (77.0, -42.0)
80 if (z /= (77.0, -42.0)) STOP 15
81 end subroutine complex_foo
83 end program test_value