xref: /llvm-project/flang/test/Semantics/forall01.f90 (revision 38763be6ab706e5661e94b68c3aa2069f4c736d8)
1! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
2subroutine forall1
3  real :: a(9)
4  !ERROR: 'i' is already declared in this scoping unit
5  !ERROR: Cannot redefine FORALL variable 'i'
6  forall (i=1:8, i=1:9)  a(i) = i
7  !ERROR: 'i' is already declared in this scoping unit
8  !ERROR: Cannot redefine FORALL variable 'i'
9  forall (i=1:8, i=1:9)
10    a(i) = i
11  end forall
12  forall (j=1:8)
13    !PORTABILITY: Index variable 'j' should not also be an index in an enclosing FORALL or DO CONCURRENT
14    forall (j=1:9)
15    end forall
16  end forall
17end
18
19subroutine forall2
20  integer, pointer :: a(:)
21  integer, target :: b(10,10)
22  forall (i=1:10)
23    !ERROR: Impure procedure 'f_impure' may not be referenced in a FORALL
24    a(f_impure(i):) => b(i,:)
25  end forall
26  !ERROR: FORALL mask expression may not reference impure procedure 'f_impure'
27  forall (j=1:10, f_impure(1)>2)
28  end forall
29contains
30  impure integer function f_impure(i)
31    f_impure = i
32  end
33end
34
35subroutine forall3
36  real :: x
37  forall(i=1:10)
38    !ERROR: Cannot redefine FORALL variable 'i'
39    i = 1
40  end forall
41  forall(i=1:10)
42    forall(j=1:10)
43      !ERROR: Cannot redefine FORALL variable 'i'
44      !WARNING: FORALL index variable 'j' not used on left-hand side of assignment
45      i = 1
46    end forall
47  end forall
48  !ERROR: Cannot redefine FORALL variable 'i'
49  forall(i=1:10) i = 1
50end
51
52subroutine forall4
53  integer, parameter :: zero = 0
54  integer :: a(10)
55
56  !ERROR: FORALL limit expression may not reference index variable 'i'
57  forall(i=1:i)
58    a(i) = i
59  end forall
60  !ERROR: FORALL step expression may not reference index variable 'i'
61  forall(i=1:10:i)
62    a(i) = i
63  end forall
64  !ERROR: FORALL step expression may not be zero
65  forall(i=1:10:zero)
66    a(i) = i
67  end forall
68
69  !ERROR: FORALL limit expression may not reference index variable 'i'
70  forall(i=1:i) a(i) = i
71  !ERROR: FORALL step expression may not reference index variable 'i'
72  forall(i=1:10:i) a(i) = i
73  !ERROR: FORALL step expression may not be zero
74  forall(i=1:10:zero) a(i) = i
75end
76
77subroutine forall5
78  real, target :: x(10), y(10)
79  forall(i=1:10)
80    x(i) = y(i)
81  end forall
82  forall(i=1:10)
83    !WARNING: FORALL index variable 'i' not used on left-hand side of assignment
84    x = y
85    forall(j=1:10)
86      !WARNING: FORALL index variable 'j' not used on left-hand side of assignment
87      x(i) = y(i)
88      !WARNING: FORALL index variable 'i' not used on left-hand side of assignment
89      x(j) = y(j)
90    endforall
91  endforall
92  do concurrent(i=1:10)
93    x = y
94    !Odd rule from F'2023 19.4 p8
95    !PORTABILITY: Index variable 'i' should not also be an index in an enclosing FORALL or DO CONCURRENT
96    !WARNING: FORALL index variable 'i' not used on left-hand side of assignment
97    forall(i=1:10) x = y
98  end do
99end
100
101subroutine forall6
102  type t
103    real, pointer :: p
104  end type
105  type(t) :: a(10)
106  real, target :: b(10)
107  forall(i=1:10)
108    a(i)%p => b(i)
109    !WARNING: FORALL index variable 'i' not used on left-hand side of assignment
110    a(1)%p => b(i)
111  end forall
112end
113
114subroutine forall7(x)
115  integer :: iarr(1)
116  real :: a(10)
117  class(*) :: x
118  associate (j => iarr(1))
119    !PORTABILITY: Index variable 'j' should be a scalar object or common block if it is present in the enclosing scope
120    forall (j=1:size(a))
121      a(j) = a(j) + 1
122    end forall
123  end associate
124  associate (j => iarr(1) + 1)
125    !PORTABILITY: Index variable 'j' should be a scalar object or common block if it is present in the enclosing scope
126    forall (j=1:size(a))
127      a(j) = a(j) + 1
128    end forall
129  end associate
130  select type (j => x)
131  type is (integer)
132    !PORTABILITY: Index variable 'j' should be a scalar object or common block if it is present in the enclosing scope
133    forall (j=1:size(a))
134      a(j) = a(j) + 1
135    end forall
136  end select
137end subroutine
138
139subroutine forall8(x)
140  real :: x(10)
141  real, external :: foo
142  !ERROR: Impure procedure 'foo' may not be referenced in a FORALL
143  forall(i=1:10) x(i) = foo() + i
144  !OK
145  associate(y => foo())
146    forall (i=1:10) x(i) = y + i
147  end associate
148end subroutine
149