[LoopReroll] Add an extra defensive check to avoid SCEV assertion.
[llvm-project.git] / flang / test / Semantics / omp-nested-simd.f90
blob1b5bb9c5cceeb9c5535f387e19fa460625b7b9fb
1 ! RUN: %S/test_errors.sh %s %t %flang_fc1 -fopenmp
2 ! REQUIRES: shell
3 ! OpenMP Version 4.5
4 ! Various checks with the nesting of SIMD construct
6 SUBROUTINE NESTED_GOOD(N)
7 INTEGER N, I, J, K, A(10), B(10)
8 !$OMP SIMD
9 DO I = 1,N
10 !$OMP ATOMIC
11 K = K + 1
12 IF (I <= 10) THEN
13 !$OMP ORDERED SIMD
14 DO J = 1,N
15 A(J) = J
16 END DO
17 !$OMP END ORDERED
18 ENDIF
19 END DO
20 !$OMP END SIMD
22 !$OMP SIMD
23 DO I = 1,N
24 IF (I <= 10) THEN
25 !$OMP SIMD
26 DO J = 1,N
27 A(J) = J
28 END DO
29 !$OMP END SIMD
30 ENDIF
31 END DO
32 !$OMP END SIMD
33 END SUBROUTINE NESTED_GOOD
35 SUBROUTINE NESTED_BAD(N)
36 INTEGER N, I, J, K, A(10), B(10)
38 !$OMP SIMD
39 DO I = 1,N
40 IF (I <= 10) THEN
41 !$OMP ORDERED SIMD
42 DO J = 1,N
43 print *, "Hi"
44 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
45 !$omp teams
46 DO K = 1,N
47 print *, 'Hello'
48 END DO
49 !$omp end teams
50 END DO
51 !$OMP END ORDERED
52 ENDIF
53 END DO
54 !$OMP END SIMD
56 !$OMP SIMD
57 DO I = 1,N
58 !$OMP ATOMIC
59 K = K + 1
60 IF (I <= 10) THEN
61 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
62 !$omp task
63 do J = 1, N
64 K = 2
65 end do
66 !$omp end task
67 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
68 !$omp teams
69 do J = 1, N
70 K = 2
71 end do
72 !$omp end teams
73 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
74 !$omp target
75 do J = 1, N
76 K = 2
77 end do
78 !$omp end target
79 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
80 !$OMP DO
81 DO J = 1,N
82 A(J) = J
83 END DO
84 !$OMP END DO
85 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
86 !$OMP PARALLEL DO
87 DO J = 1,N
88 A(J) = J
89 END DO
90 !$OMP END PARALLEL DO
91 ENDIF
92 END DO
93 !$OMP END SIMD
95 !$OMP DO SIMD
96 DO I = 1,N
97 !$OMP ATOMIC
98 K = K + 1
99 IF (I <= 10) THEN
100 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
101 !$omp task
102 do J = 1, N
103 K = 2
104 end do
105 !$omp end task
106 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
107 !$omp teams
108 do J = 1, N
109 K = 2
110 end do
111 !$omp end teams
112 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
113 !$omp target
114 do J = 1, N
115 K = 2
116 end do
117 !$omp end target
118 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
119 !ERROR: A worksharing region may not be closely nested inside a worksharing, explicit task, taskloop, critical, ordered, atomic, or master region
120 !$OMP DO
121 DO J = 1,N
122 A(J) = J
123 END DO
124 !$OMP END DO
125 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
126 !$OMP PARALLEL DO
127 DO J = 1,N
128 A(J) = J
129 END DO
130 !$OMP END PARALLEL DO
131 ENDIF
132 END DO
133 !$OMP END DO SIMD
135 !$OMP PARALLEL DO SIMD
136 DO I = 1,N
137 !$OMP ATOMIC
138 K = K + 1
139 IF (I <= 10) THEN
140 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
141 !$omp task
142 do J = 1, N
143 K = 2
144 end do
145 !$omp end task
146 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
147 !$omp teams
148 do J = 1, N
149 K = 2
150 end do
151 !$omp end teams
152 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
153 !$omp target
154 do J = 1, N
155 K = 2
156 end do
157 !$omp end target
158 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
159 !ERROR: A worksharing region may not be closely nested inside a worksharing, explicit task, taskloop, critical, ordered, atomic, or master region
160 !$OMP DO
161 DO J = 1,N
162 A(J) = J
163 END DO
164 !$OMP END DO
165 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
166 !$OMP PARALLEL DO
167 DO J = 1,N
168 A(J) = J
169 END DO
170 !$OMP END PARALLEL DO
171 ENDIF
172 END DO
173 !$OMP END PARALLEL DO SIMD
175 !$OMP TARGET SIMD
176 DO I = 1,N
177 !$OMP ATOMIC
178 K = K + 1
179 IF (I <= 10) THEN
180 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
181 !$omp task
182 do J = 1, N
183 K = 2
184 end do
185 !$omp end task
186 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
187 !$omp teams
188 do J = 1, N
189 K = 2
190 end do
191 !$omp end teams
192 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
193 !$omp target
194 do J = 1, N
195 K = 2
196 end do
197 !$omp end target
198 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
199 !$OMP DO
200 DO J = 1,N
201 A(J) = J
202 END DO
203 !$OMP END DO
204 !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct and the `ORDERED` construct with the `SIMD` clause.
205 !$OMP PARALLEL DO
206 DO J = 1,N
207 A(J) = J
208 END DO
209 !$OMP END PARALLEL DO
210 ENDIF
211 END DO
212 !$OMP END TARGET SIMD
215 END SUBROUTINE NESTED_BAD