xref: /llvm-project/flang/test/Semantics/dosemantics12.f90 (revision 90828d67ea35c86b76fc8f3dec5da03f645eadaf)
1! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
2! Copyright (c) 2019, NVIDIA CORPORATION.  All rights reserved.
3!
4! Licensed under the Apache License, Version 2.0 (the "License");
5! you may not use this file except in compliance with the License.
6! You may obtain a copy of the License at
7!
8!     http://www.apache.org/licenses/LICENSE-2.0
9!
10! Unless required by applicable law or agreed to in writing, software
11! distributed under the License is distributed on an "AS IS" BASIS,
12! WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
13! See the License for the specific language governing permissions and
14! limitations under the License.
15!
16!Section 11.1.7.4.3, paragraph 2 states:
17!  Except for the incrementation of the DO variable that occurs in step (3),
18!  the DO variable shall neither be redefined nor become undefined while the
19!  DO construct is active.
20
21subroutine s1()
22
23  ! Redefinition via intrinsic assignment (section 19.6.5, case (1))
24  do ivar = 1,20
25    print *, "hello"
26!ERROR: Cannot redefine DO variable 'ivar'
27    ivar = 99
28  end do
29
30  ! Redefinition in the presence of a construct association
31  associate (avar => ivar)
32    do ivar = 1,20
33      print *, "hello"
34!ERROR: Cannot redefine DO variable 'ivar'
35      avar = 99
36    end do
37  end associate
38
39  ivar = 99
40
41  ! Redefinition via intrinsic assignment (section 19.6.5, case (1))
42  do concurrent (ivar = 1:10)
43    print *, "hello"
44!ERROR: Cannot redefine DO variable 'ivar'
45    ivar = 99
46  end do
47
48  ivar = 99
49
50end subroutine s1
51
52subroutine s2()
53
54  integer :: ivar
55
56  read '(I10)', ivar
57
58  ! Redefinition via an input statement (section 19.6.5, case (3))
59  do ivar = 1,20
60    print *, "hello"
61!ERROR: Cannot redefine DO variable 'ivar'
62    read '(I10)', ivar
63  end do
64
65  ! Redefinition via an input statement (section 19.6.5, case (3))
66  do concurrent (ivar = 1:10)
67    print *, "hello"
68!ERROR: Cannot redefine DO variable 'ivar'
69    read '(I10)', ivar
70  end do
71
72end subroutine s2
73
74subroutine s3()
75
76  integer :: ivar
77
78  ! Redefinition via use as a DO variable (section 19.6.5, case (4))
79  do ivar = 1,10
80!ERROR: Cannot redefine DO variable 'ivar'
81    do ivar = 1,20
82!ERROR: Cannot redefine DO variable 'ivar'
83      do ivar = 1,30
84        print *, "hello"
85      end do
86    end do
87  end do
88
89  ! This one's OK, even though we used ivar previously as a DO variable
90  ! since it's not a redefinition
91  do ivar = 1,40
92    print *, "hello"
93  end do
94
95  ! Redefinition via use as a DO variable (section 19.6.5, case (4))
96  do concurrent (ivar = 1:10)
97!ERROR: Cannot redefine DO variable 'ivar'
98    do ivar = 1,20
99      print *, "hello"
100    end do
101  end do
102
103end subroutine s3
104
105subroutine s4()
106
107  integer :: ivar
108  real :: x(10)
109
110  print '(f10.5)', (x(ivar), ivar = 1, 10)
111
112  ! Redefinition via use as a DO variable (section 19.6.5, case (5))
113  do ivar = 1,20
114!ERROR: Cannot redefine DO variable 'ivar'
115    print '(f10.5)', (x(ivar), ivar = 1, 10)
116  end do
117
118  ! Redefinition via use as a DO variable (section 19.6.5, case (5))
119  do concurrent (ivar = 1:10)
120!ERROR: Cannot redefine DO variable 'ivar'
121    print '(f10.5)', (x(ivar), ivar = 1, 10)
122  end do
123
124end subroutine s4
125
126subroutine s5()
127
128  integer :: ivar
129  real :: x
130
131  read (3, '(f10.5)', iostat = ivar) x
132
133  ! Redefinition via use in IOSTAT specifier (section 19.6.5, case (7))
134  do ivar = 1,20
135    print *, "hello"
136!ERROR: Cannot redefine DO variable 'ivar'
137    read (3, '(f10.5)', iostat = ivar) x
138  end do
139
140  ! Redefinition via use in IOSTAT specifier (section 19.6.5, case (7))
141  do concurrent (ivar = 1:10)
142    print *, "hello"
143!ERROR: Cannot redefine DO variable 'ivar'
144    read (3, '(f10.5)', iostat = ivar) x
145  end do
146
147end subroutine s5
148
149subroutine s6()
150
151  character (len=3) :: key
152  integer :: chars
153  integer :: ivar
154  real :: x
155
156  read (3, '(a3)', advance='no', size = chars) key
157
158  ! Redefinition via use in SIZE specifier (section 19.6.5, case (9))
159  do ivar = 1,20
160!ERROR: Cannot redefine DO variable 'ivar'
161    read (3, '(a3)', advance='no', size = ivar) key
162    print *, "hello"
163  end do
164
165  ! Redefinition via use in SIZE specifier (section 19.6.5, case (9))
166  do concurrent (ivar = 1:10)
167!ERROR: ADVANCE specifier is not allowed in DO CONCURRENT
168!ERROR: Cannot redefine DO variable 'ivar'
169    read (3, '(a3)', advance='no', size = ivar) key
170    print *, "hello"
171  end do
172
173end subroutine s6
174
175subroutine s7()
176
177  integer :: iostatVar, nextrecVar, numberVar, posVar, reclVar, sizeVar
178
179  inquire(3, iostat=iostatVar, nextrec=nextrecVar, number=numberVar, &
180    pos=posVar, recl=reclVar, size=sizeVar)
181
182  ! Redefinition via use in IOSTAT specifier (section 19.6.5, case (10))
183  do iostatVar = 1,20
184    print *, "hello"
185!ERROR: Cannot redefine DO variable 'iostatvar'
186    inquire(3, iostat=iostatVar, nextrec=nextrecVar, number=numberVar, &
187      pos=posVar, recl=reclVar, size=sizeVar)
188  end do
189
190  ! Redefinition via use in IOSTAT specifier (section 19.6.5, case (10))
191  do concurrent (iostatVar = 1:10)
192    print *, "hello"
193!ERROR: Cannot redefine DO variable 'iostatvar'
194    inquire(3, iostat=iostatVar, nextrec=nextrecVar, number=numberVar, &
195      pos=posVar, recl=reclVar, size=sizeVar)
196  end do
197
198  ! Redefinition via use in NEXTREC specifier (section 19.6.5, case (10))
199  do nextrecVar = 1,20
200    print *, "hello"
201!ERROR: Cannot redefine DO variable 'nextrecvar'
202    inquire(3, iostat=iostatVar, nextrec=nextrecVar, number=numberVar, &
203      pos=posVar, recl=reclVar, size=sizeVar)
204  end do
205
206  ! Redefinition via use in NEXTREC specifier (section 19.6.5, case (10))
207  do concurrent (nextrecVar = 1:10)
208    print *, "hello"
209!ERROR: Cannot redefine DO variable 'nextrecvar'
210    inquire(3, iostat=iostatVar, nextrec=nextrecVar, number=numberVar, &
211      pos=posVar, recl=reclVar, size=sizeVar)
212  end do
213
214  ! Redefinition via use in NUMBER specifier (section 19.6.5, case (10))
215  do numberVar = 1,20
216    print *, "hello"
217!ERROR: Cannot redefine DO variable 'numbervar'
218    inquire(3, iostat=iostatVar, nextrec=nextrecVar, number=numberVar, &
219      pos=posVar, recl=reclVar, size=sizeVar)
220  end do
221
222  ! Redefinition via use in NUMBER specifier (section 19.6.5, case (10))
223  do concurrent (numberVar = 1:10)
224    print *, "hello"
225!ERROR: Cannot redefine DO variable 'numbervar'
226    inquire(3, iostat=iostatVar, nextrec=nextrecVar, number=numberVar, &
227      pos=posVar, recl=reclVar, size=sizeVar)
228  end do
229
230  ! Redefinition via use in RECL specifier (section 19.6.5, case (10))
231  do reclVar = 1,20
232    print *, "hello"
233    inquire(3, iostat=iostatVar, nextrec=nextrecVar, number=numberVar, &
234!ERROR: Cannot redefine DO variable 'reclvar'
235      pos=posVar, recl=reclVar, size=sizeVar)
236  end do
237
238  ! Redefinition via use in RECL specifier (section 19.6.5, case (10))
239  do concurrent (reclVar = 1:10)
240    print *, "hello"
241    inquire(3, iostat=iostatVar, nextrec=nextrecVar, number=numberVar, &
242!ERROR: Cannot redefine DO variable 'reclvar'
243      pos=posVar, recl=reclVar, size=sizeVar)
244  end do
245
246  ! Redefinition via use in POS specifier (section 19.6.5, case (10))
247  do posVar = 1,20
248    print *, "hello"
249    inquire(3, iostat=iostatVar, nextrec=nextrecVar, number=numberVar, &
250!ERROR: Cannot redefine DO variable 'posvar'
251      pos=posVar, recl=reclVar, size=sizeVar)
252  end do
253
254  ! Redefinition via use in POS specifier (section 19.6.5, case (10))
255  do concurrent (posVar = 1:10)
256    print *, "hello"
257    inquire(3, iostat=iostatVar, nextrec=nextrecVar, number=numberVar, &
258!ERROR: Cannot redefine DO variable 'posvar'
259      pos=posVar, recl=reclVar, size=sizeVar)
260  end do
261
262  ! Redefinition via use in SIZE specifier (section 19.6.5, case (10))
263  do sizeVar = 1,20
264    print *, "hello"
265    inquire(3, iostat=iostatVar, nextrec=nextrecVar, number=numberVar, &
266!ERROR: Cannot redefine DO variable 'sizevar'
267      pos=posVar, recl=reclVar, size=sizeVar)
268  end do
269
270  ! Redefinition via use in SIZE specifier (section 19.6.5, case (10))
271  do concurrent (sizeVar = 1:10)
272    print *, "hello"
273    inquire(3, iostat=iostatVar, nextrec=nextrecVar, number=numberVar, &
274!ERROR: Cannot redefine DO variable 'sizevar'
275      pos=posVar, recl=reclVar, size=sizeVar)
276  end do
277
278end subroutine s7
279
280subroutine s8()
281
282  Integer :: ivar
283  integer, pointer :: ip
284
285  allocate(ip, stat = ivar)
286
287  ! Redefinition via a STAT= specifier (section 19.6.5, case (16))
288  do ivar = 1,20
289!ERROR: Cannot redefine DO variable 'ivar'
290    allocate(ip, stat = ivar)
291    print *, "hello"
292  end do
293
294  ! Redefinition via a STAT= specifier (section 19.6.5, case (16))
295  do concurrent (ivar = 1:10)
296!ERROR: Cannot redefine DO variable 'ivar'
297    allocate(ip, stat = ivar)
298    print *, "hello"
299  end do
300
301end subroutine s8
302
303subroutine s9()
304
305  Integer :: ivar
306
307  ! OK since the DO CONCURRENT index-name exists only in the scope of the
308  ! DO CONCURRENT construct
309  do ivar = 1,20
310    print *, "hello"
311    do concurrent (ivar = 1:10)
312      print *, "hello"
313    end do
314  end do
315
316  ! Technically non-conformant (F'2023 19.4 p8)
317  do concurrent (ivar = 1:10)
318    print *, "hello"
319    !PORTABILITY: Index variable 'ivar' should not also be an index in an enclosing FORALL or DO CONCURRENT
320    do concurrent (ivar = 1:10)
321      print *, "hello"
322    end do
323  end do
324
325end subroutine s9
326
327subroutine s10()
328
329  Integer :: ivar
330  open(file="abc", newunit=ivar)
331
332  ! Redefinition via NEWUNIT specifier (section 19.6.5, case (29))
333  do ivar = 1,20
334    print *, "hello"
335!ERROR: Cannot redefine DO variable 'ivar'
336    open(file="abc", newunit=ivar)
337  end do
338
339  ! Redefinition via NEWUNIT specifier (section 19.6.5, case (29))
340  do concurrent (ivar = 1:10)
341    print *, "hello"
342!ERROR: Cannot redefine DO variable 'ivar'
343    open(file="abc", newunit=ivar)
344  end do
345
346end subroutine s10
347
348subroutine s11()
349
350  Integer, allocatable :: ivar
351
352  allocate(ivar)
353
354  ! This look is OK
355  do ivar = 1,20
356    print *, "hello"
357  end do
358
359  ! Redefinition via deallocation (section 19.6.6, case (10))
360  do ivar = 1,20
361    print *, "hello"
362!ERROR: Cannot redefine DO variable 'ivar'
363    deallocate(ivar)
364  end do
365
366  ! This case is not applicable since the version of "ivar" that's inside the
367  ! DO CONCURRENT has the scope of the DO CONCURRENT construct.  Within that
368  ! scope, it does not have the "allocatable" attribute, so the following test
369  ! fails because you can only deallocate a variable that's allocatable.
370  do concurrent (ivar = 1:10)
371    print *, "hello"
372!ERROR: Name in DEALLOCATE statement must have the ALLOCATABLE or POINTER attribute
373    deallocate(ivar)
374  end do
375
376end subroutine s11
377
378subroutine s12()
379
380  Integer :: ivar, jvar
381
382  call intentInSub(jvar, ivar)
383  do ivar = 1,10
384    call intentInSub(jvar, ivar)
385  end do
386
387  call intentOutSub(jvar, ivar)
388  do ivar = 1,10
389!ERROR: Cannot redefine DO variable 'ivar'
390    call intentOutSub(jvar, ivar)
391  end do
392
393  call intentInOutSub(jvar, ivar)
394  do ivar = 1,10
395    !WARNING: Possible redefinition of DO variable 'ivar'
396    call intentInOutSub(jvar, ivar)
397  end do
398
399contains
400  subroutine intentInSub(arg1, arg2)
401    integer, intent(in) :: arg1
402    integer, intent(in) :: arg2
403  end subroutine intentInSub
404
405  subroutine intentOutSub(arg1, arg2)
406    integer, intent(in) :: arg1
407    integer, intent(out) :: arg2
408  end subroutine intentOutSub
409
410  subroutine intentInOutSub(arg1, arg2)
411    integer, intent(in) :: arg1
412    integer, intent(inout) :: arg2
413  end subroutine intentInOutSub
414
415end subroutine s12
416
417subroutine s13()
418
419  Integer :: ivar, jvar
420
421  ! This one is OK
422  do ivar = 1, 10
423    jvar = intentInFunc(ivar)
424  end do
425
426  ! Error for passing a DO variable to an INTENT(OUT) dummy
427  do ivar = 1, 10
428!ERROR: Cannot redefine DO variable 'ivar'
429    jvar = intentOutFunc(ivar)
430  end do
431
432  ! Error for passing a DO variable to an INTENT(OUT) dummy, more complex
433  ! expression
434  do ivar = 1, 10
435!ERROR: Cannot redefine DO variable 'ivar'
436    jvar = 83 + intentInFunc(intentOutFunc(ivar))
437  end do
438
439  do ivar = 1, 10
440    !WARNING: Possible redefinition of DO variable 'ivar'
441    jvar = intentInOutFunc(ivar)
442  end do
443
444contains
445  function intentInFunc(dummyArg)
446    integer, intent(in) :: dummyArg
447    integer  :: intentInFunc
448
449    intentInFunc = 343
450  end function intentInFunc
451
452  function intentOutFunc(dummyArg)
453    integer, intent(out) :: dummyArg
454    integer  :: intentOutFunc
455
456    dummyArg = 216
457    intentOutFunc = 343
458  end function intentOutFunc
459
460  function intentInOutFunc(dummyArg)
461    integer, intent(inout) :: dummyArg
462    integer  :: intentInOutFunc
463
464    dummyArg = 216
465    intentInOutFunc = 343
466  end function intentInOutFunc
467
468end subroutine s13
469