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