[clangd] Re-land "support outgoing calls in call hierarchy" (#117673)
[llvm-project.git] / flang / test / Semantics / OpenMP / nested-simd.f90
blobc9fb90cdeceb252cc408dbba818d8395b94686c6
1 ! RUN: %python %S/../test_errors.py %s %flang_fc1 -fopenmp
2 ! OpenMP Version 4.5
3 ! Various checks with the nesting of SIMD construct
5 SUBROUTINE NESTED_GOOD(N)
6 INTEGER N, I, J, K, A(10), B(10)
7 !$OMP SIMD
8 DO I = 1,N
9 !$OMP ATOMIC
10 K = K + 1
11 IF (I <= 10) THEN
12 !$OMP ORDERED SIMD
13 DO J = 1,N
14 A(J) = J
15 END DO
16 !$OMP END ORDERED
17 ENDIF
18 END DO
19 !$OMP END SIMD
21 !$OMP SIMD
22 DO I = 1,N
23 IF (I <= 10) THEN
24 !$OMP SIMD
25 DO J = 1,N
26 A(J) = J
27 END DO
28 !$OMP END SIMD
29 ENDIF
30 END DO
31 !$OMP END SIMD
32 END SUBROUTINE NESTED_GOOD
34 SUBROUTINE NESTED_BAD(N)
35 INTEGER N, I, J, K, A(10), B(10)
37 !$OMP SIMD
38 DO I = 1,N
39 IF (I <= 10) THEN
40 !$OMP ORDERED SIMD
41 DO J = 1,N
42 print *, "Hi"
43 !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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
44 !ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
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, the `SCAN` 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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
68 !$omp target
69 do J = 1, N
70 K = 2
71 end do
72 !$omp end target
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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
74 !$OMP DO
75 DO J = 1,N
76 A(J) = J
77 END DO
78 !$OMP END DO
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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
80 !$OMP PARALLEL DO
81 DO J = 1,N
82 A(J) = J
83 END DO
84 !$OMP END PARALLEL DO
85 ENDIF
86 END DO
87 !$OMP END SIMD
89 !$OMP DO SIMD
90 DO I = 1,N
91 !$OMP ATOMIC
92 K = K + 1
93 IF (I <= 10) THEN
94 !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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
95 !$omp task
96 do J = 1, N
97 K = 2
98 end do
99 !$omp end task
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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
101 !$omp target
102 do J = 1, N
103 K = 2
104 end do
105 !$omp end target
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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
107 !ERROR: A worksharing region may not be closely nested inside a worksharing, explicit task, taskloop, critical, ordered, atomic, or master region
108 !$OMP DO
109 DO J = 1,N
110 A(J) = J
111 END DO
112 !$OMP END DO
113 !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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
114 !$OMP PARALLEL DO
115 DO J = 1,N
116 A(J) = J
117 END DO
118 !$OMP END PARALLEL DO
119 ENDIF
120 END DO
121 !$OMP END DO SIMD
123 !$OMP PARALLEL DO SIMD
124 DO I = 1,N
125 !$OMP ATOMIC
126 K = K + 1
127 IF (I <= 10) THEN
128 !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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
129 !$omp task
130 do J = 1, N
131 K = 2
132 end do
133 !$omp end task
134 !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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
135 !$omp target
136 do J = 1, N
137 K = 2
138 end do
139 !$omp end target
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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
141 !ERROR: A worksharing region may not be closely nested inside a worksharing, explicit task, taskloop, critical, ordered, atomic, or master region
142 !$OMP DO
143 DO J = 1,N
144 A(J) = J
145 END DO
146 !$OMP END DO
147 !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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
148 !$OMP PARALLEL DO
149 DO J = 1,N
150 A(J) = J
151 END DO
152 !$OMP END PARALLEL DO
153 ENDIF
154 END DO
155 !$OMP END PARALLEL DO SIMD
157 !$OMP TARGET SIMD
158 DO I = 1,N
159 !$OMP ATOMIC
160 K = K + 1
161 IF (I <= 10) THEN
162 !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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
163 !$omp task
164 do J = 1, N
165 K = 2
166 end do
167 !$omp end task
168 !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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
169 !$omp target
170 do J = 1, N
171 K = 2
172 end do
173 !$omp end target
174 !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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
175 !$OMP DO
176 DO J = 1,N
177 A(J) = J
178 END DO
179 !$OMP END DO
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, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
181 !$OMP PARALLEL DO
182 DO J = 1,N
183 A(J) = J
184 END DO
185 !$OMP END PARALLEL DO
186 ENDIF
187 END DO
188 !$OMP END TARGET SIMD
191 END SUBROUTINE NESTED_BAD