RISC-V: Regenerate opt urls.
[official-gcc.git] / gcc / testsuite / gfortran.dg / namelist_69.f90
blob1c3f3d7c09fb5e5986df1b09e743c0326f4eb97b
1 ! { dg-do run }
3 ! PR fortran/47339
4 ! PR fortran/43062
6 ! Run-time test for Fortran 2003 NAMELISTS
7 ! Version for non-strings
9 program nml_test
10 implicit none
12 character(len=1000) :: str
14 integer, allocatable :: a(:)
15 integer, allocatable :: b
16 integer, pointer :: ap(:)
17 integer, pointer :: bp
18 integer :: c
19 integer :: d(3)
21 type t
22 integer :: c1
23 integer :: c2(3)
24 end type t
25 type(t) :: e,f(2)
26 type(t),allocatable :: g,h(:)
27 type(t),pointer :: i,j(:)
29 namelist /nml/ a, b, c, d, ap, bp,e,f,g,h,i,j
31 a = [1,2]
32 allocate(b,ap(2),bp)
33 ap = [98, 99]
34 b = 7
35 bp = 101
36 c = 8
37 d = [-1, -2, -3]
39 e%c1 = -701
40 e%c2 = [-702,-703,-704]
41 f(1)%c1 = 33001
42 f(2)%c1 = 33002
43 f(1)%c2 = [44001,44002,44003]
44 f(2)%c2 = [44011,44012,44013]
46 allocate(g,h(2),i,j(2))
48 g%c1 = -601
49 g%c2 = [-602,6703,-604]
50 h(1)%c1 = 35001
51 h(2)%c1 = 35002
52 h(1)%c2 = [45001,45002,45003]
53 h(2)%c2 = [45011,45012,45013]
55 i%c1 = -501
56 i%c2 = [-502,-503,-504]
57 j(1)%c1 = 36001
58 j(2)%c1 = 36002
59 j(1)%c2 = [46001,46002,46003]
60 j(2)%c2 = [46011,46012,46013]
62 ! SAVE NAMELIST
63 str = repeat('X', len(str))
64 write(str,nml=nml)
66 ! RESET NAMELIST
67 a = [-1,-1]
68 ap = [-1, -1]
69 b = -1
70 bp = -1
71 c = -1
72 d = [-1, -1, -1]
74 e%c1 = -1
75 e%c2 = [-1,-1,-1]
76 f(1)%c1 = -1
77 f(2)%c1 = -1
78 f(1)%c2 = [-1,-1,-1]
79 f(2)%c2 = [-1,-1,-1]
81 g%c1 = -1
82 g%c2 = [-1,-1,-1]
83 h(1)%c1 = -1
84 h(2)%c1 = -1
85 h(1)%c2 = [-1,-1,-1]
86 h(2)%c2 = [-1,-1,-1]
88 i%c1 = -1
89 i%c2 = [-1,-1,-1]
90 j(1)%c1 = -1
91 j(2)%c1 = -1
92 j(1)%c2 = [-1,-1,-1]
93 j(2)%c2 = [-1,-1,-1]
95 ! Read back
96 read(str,nml=nml)
98 ! Check result
99 if (any (a /= [1,2])) STOP 1
100 if (any (ap /= [98, 99])) STOP 2
101 if (b /= 7) STOP 3
102 if (bp /= 101) STOP 4
103 if (c /= 8) STOP 5
104 if (any (d /= [-1, -2, -3])) STOP 6
106 if (e%c1 /= -701) STOP 7
107 if (any (e%c2 /= [-702,-703,-704])) STOP 8
108 if (f(1)%c1 /= 33001) STOP 9
109 if (f(2)%c1 /= 33002) STOP 10
110 if (any (f(1)%c2 /= [44001,44002,44003])) STOP 11
111 if (any (f(2)%c2 /= [44011,44012,44013])) STOP 12
113 if (g%c1 /= -601) STOP 13
114 if (any(g%c2 /= [-602,6703,-604])) STOP 14
115 if (h(1)%c1 /= 35001) STOP 15
116 if (h(2)%c1 /= 35002) STOP 16
117 if (any (h(1)%c2 /= [45001,45002,45003])) STOP 17
118 if (any (h(2)%c2 /= [45011,45012,45013])) STOP 18
120 if (i%c1 /= -501) STOP 19
121 if (any (i%c2 /= [-502,-503,-504])) STOP 20
122 if (j(1)%c1 /= 36001) STOP 21
123 if (j(2)%c1 /= 36002) STOP 22
124 if (any (j(1)%c2 /= [46001,46002,46003])) STOP 23
125 if (any (j(2)%c2 /= [46011,46012,46013])) STOP 24
127 ! Check argument passing (dummy processing)
128 call test2(a,b,c,d,ap,bp,e,f,g,h,i,j,2)
130 contains
131 subroutine test2(x1,x2,x3,x4,x1p,x2p,x6,x7,x8,x9,x10,x11,n)
132 integer, allocatable :: x1(:)
133 integer, allocatable :: x2
134 integer, pointer :: x1p(:)
135 integer, pointer :: x2p
136 integer :: x3
137 integer :: x4(3)
138 integer :: n
139 integer :: x5(n)
140 type(t) :: x6,x7(2)
141 type(t),allocatable :: x8,x9(:)
142 type(t),pointer :: x10,x11(:)
143 type(t) :: x12(n)
145 namelist /nml2/ x1, x2, x3, x4,x5,x1p,x2p,x6,x7,x8,x9,x10,x11,x12
147 x5 = [ 42, 53 ]
149 x12(1)%c1 = 37001
150 x12(2)%c1 = 37002
151 x12(1)%c2 = [47001,47002,47003]
152 x12(2)%c2 = [47011,47012,47013]
154 ! SAVE NAMELIST
155 str = repeat('X', len(str))
156 write(str,nml=nml2)
158 ! RESET NAMELIST
159 x1 = [-1,-1]
160 x1p = [-1, -1]
161 x2 = -1
162 x2p = -1
163 x3 = -1
164 x4 = [-1, -1, -1]
166 x6%c1 = -1
167 x6%c2 = [-1,-1,-1]
168 x7(1)%c1 = -1
169 x7(2)%c1 = -1
170 x7(1)%c2 = [-1,-1,-1]
171 x7(2)%c2 = [-1,-1,-1]
173 x8%c1 = -1
174 x8%c2 = [-1,-1,-1]
175 x9(1)%c1 = -1
176 x9(2)%c1 = -1
177 x9(1)%c2 = [-1,-1,-1]
178 x9(2)%c2 = [-1,-1,-1]
180 x10%c1 = -1
181 x10%c2 = [-1,-1,-1]
182 x11(1)%c1 = -1
183 x11(2)%c1 = -1
184 x11(1)%c2 = [-1,-1,-1]
185 x11(2)%c2 = [-1,-1,-1]
187 x5 = [ -1, -1 ]
189 x12(1)%c1 = -1
190 x12(2)%c1 = -1
191 x12(1)%c2 = [-1,-1,-1]
192 x12(2)%c2 = [-1,-1,-1]
194 ! Read back
195 read(str,nml=nml2)
197 ! Check result
198 if (any (x1 /= [1,2])) STOP 25
199 if (any (x1p /= [98, 99])) STOP 26
200 if (x2 /= 7) STOP 27
201 if (x2p /= 101) STOP 28
202 if (x3 /= 8) STOP 29
203 if (any (x4 /= [-1, -2, -3])) STOP 30
205 if (x6%c1 /= -701) STOP 31
206 if (any (x6%c2 /= [-702,-703,-704])) STOP 32
207 if (x7(1)%c1 /= 33001) STOP 33
208 if (x7(2)%c1 /= 33002) STOP 34
209 if (any (x7(1)%c2 /= [44001,44002,44003])) STOP 35
210 if (any (x7(2)%c2 /= [44011,44012,44013])) STOP 36
212 if (x8%c1 /= -601) STOP 37
213 if (any(x8%c2 /= [-602,6703,-604])) STOP 38
214 if (x9(1)%c1 /= 35001) STOP 39
215 if (x9(2)%c1 /= 35002) STOP 40
216 if (any (x9(1)%c2 /= [45001,45002,45003])) STOP 41
217 if (any (x9(2)%c2 /= [45011,45012,45013])) STOP 42
219 if (x10%c1 /= -501) STOP 43
220 if (any (x10%c2 /= [-502,-503,-504])) STOP 44
221 if (x11(1)%c1 /= 36001) STOP 45
222 if (x11(2)%c1 /= 36002) STOP 46
223 if (any (x11(1)%c2 /= [46001,46002,46003])) STOP 47
224 if (any (x11(2)%c2 /= [46011,46012,46013])) STOP 48
226 if (any (x5 /= [ 42, 53 ])) STOP 49
228 if (x12(1)%c1 /= 37001) STOP 50
229 if (x12(2)%c1 /= 37002) STOP 51
230 if (any (x12(1)%c2 /= [47001,47002,47003])) STOP 52
231 if (any (x12(2)%c2 /= [47011,47012,47013])) STOP 53
232 end subroutine test2
233 end program nml_test