Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / forall01.f90
blob5a493d45c6540689503944ef5ec4634c826e7e59
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 subroutine 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 !ERROR: 'j' is already declared in this scoping unit
14 !ERROR: Cannot redefine FORALL variable 'j'
15 forall (j=1:9)
16 end forall
17 end forall
18 end
20 subroutine forall2
21 integer, pointer :: a(:)
22 integer, target :: b(10,10)
23 forall (i=1:10)
24 !ERROR: Impure procedure 'f_impure' may not be referenced in a FORALL
25 a(f_impure(i):) => b(i,:)
26 end forall
27 !ERROR: FORALL mask expression may not reference impure procedure 'f_impure'
28 forall (j=1:10, f_impure(1)>2)
29 end forall
30 contains
31 impure integer function f_impure(i)
32 f_impure = i
33 end
34 end
36 subroutine forall3
37 real :: x
38 forall(i=1:10)
39 !ERROR: Cannot redefine FORALL variable 'i'
40 i = 1
41 end forall
42 forall(i=1:10)
43 forall(j=1:10)
44 !ERROR: Cannot redefine FORALL variable 'i'
45 !WARNING: FORALL index variable 'j' not used on left-hand side of assignment
46 i = 1
47 end forall
48 end forall
49 !ERROR: Cannot redefine FORALL variable 'i'
50 forall(i=1:10) i = 1
51 end
53 subroutine forall4
54 integer, parameter :: zero = 0
55 integer :: a(10)
57 !ERROR: FORALL limit expression may not reference index variable 'i'
58 forall(i=1:i)
59 a(i) = i
60 end forall
61 !ERROR: FORALL step expression may not reference index variable 'i'
62 forall(i=1:10:i)
63 a(i) = i
64 end forall
65 !ERROR: FORALL step expression may not be zero
66 forall(i=1:10:zero)
67 a(i) = i
68 end forall
70 !ERROR: FORALL limit expression may not reference index variable 'i'
71 forall(i=1:i) a(i) = i
72 !ERROR: FORALL step expression may not reference index variable 'i'
73 forall(i=1:10:i) a(i) = i
74 !ERROR: FORALL step expression may not be zero
75 forall(i=1:10:zero) a(i) = i
76 end
78 ! Note: this gets warnings but not errors
79 subroutine forall5
80 real, target :: x(10), y(10)
81 forall(i=1:10)
82 x(i) = y(i)
83 end forall
84 forall(i=1:10)
85 !WARNING: FORALL index variable 'i' not used on left-hand side of assignment
86 x = y
87 forall(j=1:10)
88 !WARNING: FORALL index variable 'j' not used on left-hand side of assignment
89 x(i) = y(i)
90 !WARNING: FORALL index variable 'i' not used on left-hand side of assignment
91 x(j) = y(j)
92 endforall
93 endforall
94 do concurrent(i=1:10)
95 x = y
96 !WARNING: FORALL index variable 'i' not used on left-hand side of assignment
97 forall(i=1:10) x = y
98 end do
99 end
101 subroutine 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
114 subroutine forall7(x)
115 integer :: iarr(1)
116 real :: a(10)
117 class(*) :: x
118 associate (j => iarr(1))
119 forall (j=1:size(a))
120 a(j) = a(j) + 1
121 end forall
122 end associate
123 associate (j => iarr(1) + 1)
124 forall (j=1:size(a))
125 a(j) = a(j) + 1
126 end forall
127 end associate
128 select type (j => x)
129 type is (integer)
130 forall (j=1:size(a))
131 a(j) = a(j) + 1
132 end forall
133 end select
134 end subroutine