tree-optimization/113385 - wrong loop father with early exit vectorization
[official-gcc.git] / gcc / testsuite / gfortran.dg / gomp / clauses-1.f90
blob92801852984d8af6dee844f7a44582093a84972e
1 ! { dg-do compile }
3 module m
4 use iso_c_binding, only: c_intptr_t
5 implicit none (external, type)
7 integer(c_intptr_t), parameter :: &
8 omp_null_allocator = 0, &
9 omp_default_mem_alloc = 1, &
10 omp_large_cap_mem_alloc = 2, &
11 omp_const_mem_alloc = 3, &
12 omp_high_bw_mem_alloc = 4, &
13 omp_low_lat_mem_alloc = 5, &
14 omp_cgroup_mem_alloc = 6, &
15 omp_pteam_mem_alloc = 7, &
16 omp_thread_mem_alloc = 8
18 integer, parameter :: &
19 omp_allocator_handle_kind = c_intptr_t
21 integer :: t
22 !$omp threadprivate (t)
24 integer :: f, l, ll, r, r2
25 !$omp declare target (f, l, ll, r, r2)
27 contains
29 subroutine foo (d, m, i1, i2, i3, p, idp, s, nte, tl, nth, g, nta, fi, pp, q, dd, ntm)
30 !$omp declare target (foo)
31 integer :: d, m, p, idp, s, nte, tl, nth, g, nta, pp, q, dd, ntm
32 logical :: i1, i2, i3, fi
33 pointer :: q
34 integer :: i
36 !$omp distribute parallel do &
37 !$omp& private (p) firstprivate (f) collapse(1) dist_schedule(static, 16) &
38 !$omp& if (parallel: i2) default(shared) shared(s) reduction(+:r) num_threads (nth) proc_bind(spread) &
39 !$omp& lastprivate (l) schedule(static, 4) order(concurrent) &
40 !$omp& allocate (omp_default_mem_alloc:f)
41 do i = 1, 64
42 ll = ll +1
43 end do
45 !$omp distribute parallel do simd &
46 !$omp& private (p) firstprivate (f) collapse(1) dist_schedule(static, 16) &
47 !$omp& if (parallel: i2) if(simd: i1) default(shared) shared(s) reduction(+:r) num_threads (nth) proc_bind(spread) &
48 !$omp& lastprivate (l) schedule(static, 4) nontemporal(ntm) &
49 !$omp& safelen(8) simdlen(4) aligned(q: 32) order(concurrent) &
50 !$omp& allocate (omp_default_mem_alloc:f)
51 do i = 1, 64
52 ll = ll +1
53 end do
55 !$omp distribute simd &
56 !$omp& private (p) firstprivate (f) collapse(1) dist_schedule(static, 16) &
57 !$omp& safelen(8) simdlen(4) aligned(q: 32) reduction(+:r) if(i1) nontemporal(ntm) &
58 !$omp& order(concurrent) &
59 !$omp& allocate (omp_default_mem_alloc:f)
60 do i = 1, 64
61 ll = ll +1
62 end do
63 end
65 subroutine qux (p)
66 !$omp declare target (qux)
67 integer, value :: p
69 !$omp loop bind(teams) order(concurrent) &
70 !$omp& private (p) lastprivate (l) collapse(1) reduction(+:r)
71 do l = 1, 64
72 ll = ll + 1
73 end do
74 end
76 subroutine baz (d, m, i1, i2, i3, p, idp, s, nte, tl, nth, g, nta, fi, pp, q, dd, ntm)
77 integer :: d, m, p, idp, s, nte, tl, nth, g, nta, pp, q, dd, ntm
78 logical :: i1, i2, i3, fi
79 pointer :: q
80 integer :: i
81 !$omp distribute parallel do &
82 !$omp& private (p) firstprivate (f) collapse(1) dist_schedule(static, 16) &
83 !$omp& if (parallel: i2) default(shared) shared(s) reduction(+:r) num_threads (nth) proc_bind(spread) &
84 !$omp& lastprivate (l) schedule(static, 4) copyin(t) &
85 !$omp& allocate (p)
86 do i = 1, 64
87 ll = ll +1
88 end do
90 !$omp distribute parallel do &
91 !$omp& private (p) firstprivate (f) collapse(1) dist_schedule(static, 16) &
92 !$omp& if (parallel: i2) default(shared) shared(s) reduction(+:r) num_threads (nth) proc_bind(spread) &
93 !$omp& lastprivate (l) schedule(static, 4) order(concurrent) &
94 !$omp& allocate (p)
95 do i = 1, 64
96 ll = ll +1
97 end do
99 !$omp distribute parallel do simd &
100 !$omp& private (p) firstprivate (f) collapse(1) dist_schedule(static, 16) &
101 !$omp& if (parallel: i2) if(simd: i1) default(shared) shared(s) reduction(+:r) num_threads (nth) proc_bind(spread) &
102 !$omp& lastprivate (l) schedule(static, 4) nontemporal(ntm) &
103 !$omp& safelen(8) simdlen(4) aligned(q: 32) copyin(t) &
104 !$omp& allocate (f)
105 do i = 1, 64
106 ll = ll + 1
107 end do
109 !$omp distribute parallel do simd &
110 !$omp& private (p) firstprivate (f) collapse(1) dist_schedule(static, 16) &
111 !$omp& if (parallel: i2) if(simd: i1) default(shared) shared(s) reduction(+:r) num_threads (nth) proc_bind(spread) &
112 !$omp& lastprivate (l) schedule(static, 4) nontemporal(ntm) &
113 !$omp& safelen(8) simdlen(4) aligned(q: 32) order(concurrent) &
114 !$omp& allocate (f)
115 do i = 1, 64
116 ll = ll + 1
117 end do
119 !$omp distribute simd &
120 !$omp& private (p) firstprivate (f) collapse(1) dist_schedule(static, 16) &
121 !$omp& safelen(8) simdlen(4) aligned(q: 32) reduction(+:r) if(i1) nontemporal(ntm) &
122 !$omp& order(concurrent) &
123 !$omp& allocate (f)
124 do i = 1, 64
125 ll = ll + 1
126 end do
128 !$omp loop bind(parallel) order(concurrent) &
129 !$omp& private (p) lastprivate (l) collapse(1) reduction(+:r)
130 do l = 1, 64
131 ll = ll + 1
132 end do
135 subroutine bar (d, m, i1, i2, i3, p, idp, s, nte, tl, nth, g, nta, fi, pp, q, dd, ntm)
136 integer :: d, m, p, idp, s, nte, tl, nth, g, nta, pp, q, dd(0:5), ntm
137 logical :: i1, i2, i3, fi
138 pointer :: q
139 integer :: i
141 !$omp do simd &
142 !$omp& private (p) firstprivate (f) lastprivate (l) linear (ll:1) reduction(+:r) schedule(static, 4) collapse(1) &
143 !$omp& safelen(8) simdlen(4) aligned(q: 32) nontemporal(ntm) if(i1) order(concurrent) &
144 !$omp& allocate (f)
145 do i = 1, 64
146 ll = ll + 1
147 end do
148 !$omp end do simd nowait
150 !$omp parallel do &
151 !$omp& private (p) firstprivate (f) if (parallel: i2) default(shared) shared(s) copyin(t) reduction(+:r) num_threads (nth) &
152 !$omp& proc_bind(spread) lastprivate (l) linear (ll:1) ordered schedule(static, 4) collapse(1) &
153 !$omp& allocate (f)
154 do i = 1, 64
155 ll = ll + 1
156 end do
158 !$omp parallel do &
159 !$omp& private (p) firstprivate (f) if (parallel: i2) default(shared) shared(s) copyin(t) reduction(+:r) num_threads (nth) &
160 !$omp& proc_bind(spread) lastprivate (l) linear (ll:1) schedule(static, 4) collapse(1) order(concurrent) &
161 !$omp& allocate (f)
162 do i = 1, 64
163 ll = ll + 1
164 end do
166 !$omp parallel do simd &
167 !$omp& private (p) firstprivate (f) if (i2) default(shared) shared(s) copyin(t) reduction(+:r) num_threads (nth) &
168 !$omp& proc_bind(spread) lastprivate (l) linear (ll:1) schedule(static, 4) collapse(1) &
169 !$omp& safelen(8) simdlen(4) aligned(q: 32) nontemporal(ntm) order(concurrent) &
170 !$omp& allocate (f)
171 do i = 1, 64
172 ll = ll + 1
173 end do
175 !$omp parallel sections &
176 !$omp& private (p) firstprivate (f) if (parallel: i2) default(shared) shared(s) copyin(t) reduction(+:r) num_threads (nth) &
177 !$omp& proc_bind(spread) lastprivate (l) &
178 !$omp& allocate (f)
179 !$omp section
180 block; end block
181 !$omp section
182 block; end block
183 !$omp end parallel sections
185 !$omp target parallel &
186 !$omp& device(d) map (tofrom: m) if (target: i1) private (p) firstprivate (f) defaultmap(tofrom: scalar) is_device_ptr (idp) &
187 !$omp& if (parallel: i2) default(shared) shared(s) reduction(+:r) num_threads (nth) proc_bind(spread) &
188 !$omp& depend(inout: dd(0)) in_reduction(+:r2) &
189 !$omp& allocate (omp_default_mem_alloc:f)
190 !$omp end target parallel nowait
192 !$omp target parallel do &
193 !$omp& device(d) map (tofrom: m) if (target: i1) private (p) firstprivate (f) defaultmap(tofrom: scalar) is_device_ptr (idp) &
194 !$omp& if (parallel: i2) default(shared) shared(s) reduction(+:r) num_threads (nth) proc_bind(spread) &
195 !$omp& lastprivate (l) linear (ll:1) ordered schedule(static, 4) collapse(1) depend(inout: dd(0)) &
196 !$omp& in_reduction(+:r2) &
197 !$omp& allocate (omp_default_mem_alloc:f)
198 do i = 1, 64
199 ll = ll + 1
200 end do
201 !$omp end target parallel do nowait
203 !$omp target parallel do &
204 !$omp& device(d) map (tofrom: m) if (target: i1) private (p) firstprivate (f) defaultmap(tofrom: scalar) is_device_ptr (idp) &
205 !$omp& if (parallel: i2) default(shared) shared(s) reduction(+:r) num_threads (nth) proc_bind(spread) &
206 !$omp& lastprivate (l) linear (ll:1) schedule(static, 4) collapse(1) depend(inout: dd(0)) order(concurrent) &
207 !$omp& in_reduction(+:r2) &
208 !$omp& allocate (omp_default_mem_alloc:f)
209 do i = 1, 64
210 ll = ll + 1
211 end do
212 !$omp end target parallel do nowait
214 !$omp target parallel do simd &
215 !$omp& device(d) map (tofrom: m) if (target: i1) private (p) firstprivate (f) defaultmap(tofrom: scalar) is_device_ptr (idp) &
216 !$omp& if (parallel: i2) default(shared) shared(s) reduction(+:r) num_threads (nth) proc_bind(spread) &
217 !$omp& lastprivate (l) linear (ll:1) schedule(static, 4) collapse(1) &
218 !$omp& safelen(8) simdlen(4) aligned(q: 32) depend(inout: dd(0)) nontemporal(ntm) if (simd: i3) order(concurrent) &
219 !$omp& in_reduction(+:r2) &
220 !$omp& allocate (omp_default_mem_alloc:f)
221 do i = 1, 64
222 ll = ll + 1
223 end do
224 !$omp end target parallel do simd nowait
226 !$omp target teams &
227 !$omp& device(d) map (tofrom: m) if (target: i1) private (p) firstprivate (f) defaultmap(tofrom: scalar) is_device_ptr (idp) &
228 !$omp& shared(s) default(shared) reduction(+:r) num_teams(nte - 1:nte) thread_limit(tl) depend(inout: dd(0)) &
229 !$omp& in_reduction(+:r2) &
230 !$omp& allocate (omp_default_mem_alloc:f)
231 !$omp end target teams nowait
233 !$omp target teams distribute &
234 !$omp& device(d) map (tofrom: m) if (target: i1) private (p) firstprivate (f) defaultmap(tofrom: scalar) is_device_ptr (idp) &
235 !$omp& shared(s) default(shared) reduction(+:r) num_teams(nte) thread_limit(tl) order(concurrent) &
236 !$omp& collapse(1) dist_schedule(static, 16) depend(inout: dd(0)) in_reduction(+:r2) &
237 !$omp& allocate (omp_default_mem_alloc:f)
238 do i = 1, 64
239 end do
240 !$omp end target teams distribute nowait
242 !$omp target teams distribute parallel do &
243 !$omp& device(d) map (tofrom: m) if (target: i1) private (p) firstprivate (f) defaultmap(tofrom: scalar) is_device_ptr (idp) &
244 !$omp& shared(s) default(shared) reduction(+:r) num_teams(nte-1:nte) thread_limit(tl) &
245 !$omp& collapse(1) dist_schedule(static, 16) &
246 !$omp& if (parallel: i2) num_threads (nth) proc_bind(spread) &
247 !$omp& lastprivate (l) schedule(static, 4) depend(inout: dd(0)) order(concurrent) &
248 !$omp& in_reduction(+:r2) &
249 !$omp& allocate (omp_default_mem_alloc:f)
250 do i = 1, 64
251 ll = ll + 1
252 end do
253 !$omp end target teams distribute parallel do nowait
255 !$omp target teams distribute parallel do simd &
256 !$omp& device(d) map (tofrom: m) if (target: i1) private (p) firstprivate (f) defaultmap(tofrom: scalar) is_device_ptr (idp) &
257 !$omp& shared(s) default(shared) reduction(+:r) num_teams(nte) thread_limit(tl) &
258 !$omp& collapse(1) dist_schedule(static, 16) &
259 !$omp& if (parallel: i2) num_threads (nth) proc_bind(spread) &
260 !$omp& lastprivate (l) schedule(static, 4) order(concurrent) &
261 !$omp& safelen(8) simdlen(4) aligned(q: 32) depend(inout: dd(0)) nontemporal(ntm) if (simd: i3) &
262 !$omp& in_reduction(+:r2) &
263 !$omp& allocate (omp_default_mem_alloc:f)
264 do i = 1, 64
265 ll = ll + 1
266 end do
267 !$omp end target teams distribute parallel do simd nowait
269 !$omp target teams distribute simd &
270 !$omp& device(d) map (tofrom: m) if (i1) private (p) firstprivate (f) defaultmap(tofrom: scalar) is_device_ptr (idp) &
271 !$omp& shared(s) default(shared) reduction(+:r) num_teams(nte-1:nte) thread_limit(tl) &
272 !$omp& collapse(1) dist_schedule(static, 16) order(concurrent) &
273 !$omp& safelen(8) simdlen(4) aligned(q: 32) depend(inout: dd(0)) nontemporal(ntm) &
274 !$omp& in_reduction(+:r2) &
275 !$omp& allocate (omp_default_mem_alloc:f)
276 do i = 1, 64
277 ll = ll + 1
278 end do
279 !$omp end target teams distribute simd nowait
281 !$omp target simd &
282 !$omp& device(d) map (tofrom: m) if (target: i1) private (p) firstprivate (f) defaultmap(tofrom: scalar) is_device_ptr (idp) &
283 !$omp& safelen(8) simdlen(4) lastprivate (l) linear(ll: 1) aligned(q: 32) reduction(+:r) &
284 !$omp& depend(inout: dd(0)) nontemporal(ntm) if(simd:i3) order(concurrent) &
285 !$omp& in_reduction(+:r2) &
286 !$omp& allocate (omp_default_mem_alloc:f)
287 do i = 1, 64
288 ll = ll + 1
289 end do
290 !$omp end target simd nowait
292 !$omp taskgroup task_reduction(+:r2) &
293 !$omp& allocate (r2)
294 !$omp taskloop simd &
295 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) collapse(1) untied &
296 !$omp& if(taskloop: i1) if(simd: i2) final(fi) mergeable priority (pp) &
297 !$omp& safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) in_reduction(+:r2) nontemporal(ntm) &
298 !$omp& order(concurrent) &
299 !$omp& allocate (f)
300 do i = 1, 64
301 ll = ll + 1
302 end do
303 !$omp end taskgroup
305 !$omp taskgroup task_reduction(+:r) &
306 !$omp& allocate (r)
307 !$omp taskloop simd &
308 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) collapse(1) untied if(i1) &
309 !$omp& final(fi) mergeable nogroup priority (pp) &
310 !$omp& safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) in_reduction(+:r) nontemporal(ntm) &
311 !$omp& order(concurrent) &
312 !$omp& allocate (f)
313 do i = 1, 64
314 ll = ll + 1
315 end do
316 !$omp end taskgroup
318 !$omp taskwait
319 !$omp taskloop simd &
320 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) collapse(1) if(taskloop: i1) &
321 !$omp& final(fi) priority (pp) safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(+:r) if (simd: i3) nontemporal(ntm) &
322 !$omp& order(concurrent) &
323 !$omp& allocate (f)
324 do i = 1, 64
325 ll = ll + 1
326 end do
328 !$omp target depend(inout: dd(0)) in_reduction(+:r2)
329 !$omp teams distribute &
330 !$omp& private(p) firstprivate (f) shared(s) default(shared) reduction(+:r) num_teams(nte) thread_limit(tl) &
331 !$omp& collapse(1) dist_schedule(static, 16) order(concurrent) &
332 !$omp& allocate (omp_default_mem_alloc: f)
333 do i = 1, 64
334 end do
335 !$omp end target nowait
337 !$omp target
338 !$omp teams distribute parallel do &
339 !$omp& private(p) firstprivate (f) shared(s) default(shared) reduction(+:r) num_teams(nte-1:nte) thread_limit(tl) &
340 !$omp& collapse(1) dist_schedule(static, 16) &
341 !$omp& if (parallel: i2) num_threads (nth) proc_bind(spread) &
342 !$omp& lastprivate (l) schedule(static, 4) order(concurrent) &
343 !$omp& allocate (omp_default_mem_alloc: f)
344 do i = 1, 64
345 ll = ll +1
346 end do
347 !$omp end target
349 !$omp target
350 !$omp teams distribute parallel do simd &
351 !$omp& private(p) firstprivate (f) shared(s) default(shared) reduction(+:r) num_teams(nte) thread_limit(tl) &
352 !$omp& collapse(1) dist_schedule(static, 16) &
353 !$omp& if (parallel: i2) num_threads (nth) proc_bind(spread) &
354 !$omp& lastprivate (l) schedule(static, 4) order(concurrent) &
355 !$omp& safelen(8) simdlen(4) aligned(q: 32) if (simd: i3) nontemporal(ntm) &
356 !$omp& allocate (omp_default_mem_alloc: f)
357 do i = 1, 64
358 ll = ll +1
359 end do
360 !$omp end target
362 !$omp target
363 !$omp teams distribute simd &
364 !$omp& private(p) firstprivate (f) shared(s) default(shared) reduction(+:r) num_teams(nte-1:nte) thread_limit(tl) &
365 !$omp& collapse(1) dist_schedule(static, 16) order(concurrent) &
366 !$omp& safelen(8) simdlen(4) aligned(q: 32) if(i3) nontemporal(ntm) &
367 !$omp& allocate (omp_default_mem_alloc: f)
368 do i = 1, 64
369 ll = ll +1
370 end do
371 !$omp end target
373 !$omp teams distribute parallel do &
374 !$omp& private(p) firstprivate (f) shared(s) default(shared) reduction(+:r) num_teams(nte) thread_limit(tl) &
375 !$omp& collapse(1) dist_schedule(static, 16) &
376 !$omp& if (parallel: i2) num_threads (nth) proc_bind(spread) &
377 !$omp& lastprivate (l) schedule(static, 4) copyin(t) &
378 !$omp& allocate (f)
379 do i = 1, 64
380 ll = ll +1
381 end do
383 !$omp teams distribute parallel do &
384 !$omp& private(p) firstprivate (f) shared(s) default(shared) reduction(+:r) num_teams(nte-1:nte) thread_limit(tl) &
385 !$omp& collapse(1) dist_schedule(static, 16) order(concurrent) &
386 !$omp& if (parallel: i2) num_threads (nth) proc_bind(spread) &
387 !$omp& lastprivate (l) schedule(static, 4) &
388 !$omp& allocate (f)
389 do i = 1, 64
390 ll = ll +1
391 end do
393 !$omp teams distribute parallel do simd &
394 !$omp& private(p) firstprivate (f) shared(s) default(shared) reduction(+:r) num_teams(nte) thread_limit(tl) &
395 !$omp& collapse(1) dist_schedule(static, 16) &
396 !$omp& if (parallel: i2) num_threads (nth) proc_bind(spread) &
397 !$omp& lastprivate (l) schedule(static, 4) &
398 !$omp& safelen(8) simdlen(4) aligned(q: 32) if (simd: i3) nontemporal(ntm) copyin(t) &
399 !$omp& allocate (f)
400 do i = 1, 64
401 ll = ll +1
402 end do
404 !$omp teams distribute parallel do simd &
405 !$omp& private(p) firstprivate (f) shared(s) default(shared) reduction(+:r) num_teams(nte-1:nte) thread_limit(tl) &
406 !$omp& collapse(1) dist_schedule(static, 16) &
407 !$omp& if (parallel: i2) num_threads (nth) proc_bind(spread) &
408 !$omp& lastprivate (l) schedule(static, 4) order(concurrent) &
409 !$omp& safelen(8) simdlen(4) aligned(q: 32) if (simd: i3) nontemporal(ntm) &
410 !$omp& allocate (f)
411 do i = 1, 64
412 ll = ll +1
413 end do
415 !$omp teams distribute simd &
416 !$omp& private(p) firstprivate (f) shared(s) default(shared) reduction(+:r) num_teams(nte) thread_limit(tl) &
417 !$omp& collapse(1) dist_schedule(static, 16) order(concurrent) &
418 !$omp& safelen(8) simdlen(4) aligned(q: 32) if(i3) nontemporal(ntm) &
419 !$omp& allocate(f)
420 do i = 1, 64
421 ll = ll +1
422 end do
424 !$omp parallel master &
425 !$omp& private (p) firstprivate (f) if (parallel: i2) default(shared) shared(s) reduction(+:r) &
426 !$omp& num_threads (nth) proc_bind(spread) copyin(t) &
427 !$omp& allocate (f)
428 !$omp end parallel master
430 !$omp parallel masked &
431 !$omp& private (p) firstprivate (f) if (parallel: i2) default(shared) shared(s) reduction(+:r) &
432 !$omp& num_threads (nth) proc_bind(spread) copyin(t) filter (d) &
433 !$omp& allocate (f)
434 !$omp end parallel masked
436 !$omp taskgroup task_reduction (+:r2) &
437 !$omp& allocate (r2)
438 !$omp master taskloop &
439 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) collapse(1) untied &
440 !$omp& if(taskloop: i1) final(fi) mergeable priority (pp) &
441 !$omp& reduction(default, +:r) in_reduction(+:r2) &
442 !$omp& allocate (f)
443 do i = 1, 64
444 ll = ll +1
445 end do
446 !$omp end taskgroup
448 !$omp taskgroup task_reduction (+:r2) &
449 !$omp& allocate (r2)
450 !$omp masked taskloop &
451 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) collapse(1) untied &
452 !$omp& if(taskloop: i1) final(fi) mergeable priority (pp) reduction(default, +:r) in_reduction(+:r2) filter (d) &
453 !$omp& allocate (f)
454 do i = 1, 64
455 ll = ll +1
456 end do
457 !$omp end taskgroup
459 !$omp taskgroup task_reduction (+:r2) &
460 !$omp& allocate (r2)
461 !$omp master taskloop simd &
462 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) collapse(1) untied &
463 !$omp& if(taskloop: i1) if(simd: i2) final(fi) mergeable priority (pp) &
464 !$omp& safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) in_reduction(+:r2) nontemporal(ntm) &
465 !$omp& order(concurrent) &
466 !$omp& allocate (f)
467 do i = 1, 64
468 ll = ll +1
469 end do
470 !$omp end taskgroup
472 !$omp taskgroup task_reduction (+:r2) &
473 !$omp& allocate (r2)
474 !$omp masked taskloop simd &
475 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) collapse(1) untied &
476 !$omp& if(taskloop: i1) if(simd: i2) final(fi) mergeable priority (pp) &
477 !$omp& safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) in_reduction(+:r2) nontemporal(ntm) &
478 !$omp& order(concurrent) filter (d) &
479 !$omp& allocate (f)
480 do i = 1, 64
481 ll = ll +1
482 end do
483 !$omp end taskgroup
485 !$omp parallel master taskloop &
486 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) collapse(1) untied &
487 !$omp& if(taskloop: i1) final(fi) mergeable priority (pp) &
488 !$omp& reduction(default, +:r) if (parallel: i2) num_threads (nth) proc_bind(spread) copyin(t) &
489 !$omp& allocate (f)
490 do i = 1, 64
491 ll = ll +1
492 end do
494 !$omp parallel masked taskloop &
495 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) collapse(1) untied &
496 !$omp& if(taskloop: i1) final(fi) mergeable priority (pp) &
497 !$omp& reduction(default, +:r) if (parallel: i2) num_threads (nth) proc_bind(spread) copyin(t) filter (d) &
498 !$omp& allocate (f)
499 do i = 1, 64
500 ll = ll +1
501 end do
503 !$omp parallel master taskloop simd &
504 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) collapse(1) untied &
505 !$omp& if(taskloop: i1) if(simd: i2) final(fi) mergeable priority (pp) &
506 !$omp& safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) nontemporal(ntm) if (parallel: i2) &
507 !$omp& num_threads (nth) proc_bind(spread) copyin(t) order(concurrent) &
508 !$omp& allocate (f)
509 do i = 1, 64
510 ll = ll +1
511 end do
513 !$omp parallel masked taskloop simd &
514 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) grainsize (g) collapse(1) untied &
515 !$omp& if(taskloop: i1) if(simd: i2) final(fi) mergeable priority (pp) &
516 !$omp& safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) nontemporal(ntm) if (parallel: i2) &
517 !$omp& num_threads (nth) proc_bind(spread) copyin(t) order(concurrent) filter (d) &
518 !$omp& allocate (f)
519 do i = 1, 64
520 ll = ll +1
521 end do
523 !$omp taskgroup task_reduction (+:r2) &
524 !$omp& allocate (r2)
525 !$omp master taskloop &
526 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) collapse(1) &
527 !$omp& untied if(i1) final(fi) mergeable priority (pp) reduction(default, +:r) in_reduction(+:r2)
528 do i = 1, 64
529 ll = ll +1
530 end do
531 !$omp end taskgroup
533 !$omp taskgroup task_reduction (+:r2) &
534 !$omp& allocate (r2)
535 !$omp masked taskloop &
536 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) collapse(1) &
537 !$omp& untied if(i1) final(fi) mergeable priority (pp) reduction(default, +:r) in_reduction(+:r2) filter (d)
538 do i = 1, 64
539 ll = ll +1
540 end do
541 !$omp end taskgroup
543 !$omp taskgroup task_reduction (+:r2) &
544 !$omp& allocate (r2)
545 !$omp master taskloop simd &
546 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) collapse(1) untied if(i1) &
547 !$omp& final(fi) mergeable priority (pp) safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) &
548 !$omp& in_reduction(+:r2) nontemporal(ntm) order(concurrent) &
549 !$omp& allocate (f)
550 do i = 1, 64
551 ll = ll +1
552 end do
553 !$omp end taskgroup
555 !$omp taskgroup task_reduction (+:r2) &
556 !$omp& allocate (r2)
557 !$omp masked taskloop simd &
558 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) collapse(1) untied &
559 !$omp& if(i1) final(fi) mergeable priority (pp) safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) &
560 !$omp& in_reduction(+:r2) nontemporal(ntm) order(concurrent) filter (d) &
561 !$omp& allocate (f)
562 do i = 1, 64
563 ll = ll +1
564 end do
565 !$omp end taskgroup
567 !$omp parallel master taskloop &
568 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) collapse(1) untied &
569 !$omp& if(i1) final(fi) mergeable priority (pp) reduction(default, +:r) num_threads (nth) proc_bind(spread) copyin(t) &
570 !$omp& allocate (f)
571 do i = 1, 64
572 ll = ll +1
573 end do
575 !$omp parallel masked taskloop &
576 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) collapse(1) untied &
577 !$omp& if(i1) final(fi) mergeable priority (pp) reduction(default, +:r) num_threads (nth) proc_bind(spread) &
578 !$omp& copyin(t) filter (d) &
579 !$omp& allocate (f)
580 do i = 1, 64
581 ll = ll +1
582 end do
584 !$omp parallel master taskloop simd &
585 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) collapse(1) untied &
586 !$omp& if(i1) final(fi) mergeable priority (pp) safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) &
587 !$omp& nontemporal(ntm) num_threads (nth) proc_bind(spread)copyin(t) order(concurrent) &
588 !$omp& allocate (f)
589 do i = 1, 64
590 ll = ll +1
591 end do
593 !$omp parallel masked taskloop simd &
594 !$omp& private (p) firstprivate (f) lastprivate (l) shared (s) default(shared) num_tasks (nta) collapse(1) untied if(i1) &
595 !$omp& final(fi) mergeable priority (pp) safelen(8) simdlen(4) linear(ll: 1) aligned(q: 32) reduction(default, +:r) &
596 !$omp& nontemporal(ntm) num_threads (nth) proc_bind(spread) copyin(t) order(concurrent) filter (d) &
597 !$omp& allocate (f)
598 do i = 1, 64
599 ll = ll +1
600 end do
602 !$omp loop bind(thread) order(concurrent) &
603 !$omp& private (p) lastprivate (l) collapse(1) reduction(+:r)
604 do l = 1, 64
605 ll = ll + 1
606 end do
608 !$omp parallel loop &
609 !$omp& private (p) firstprivate (f) default(shared) shared(s) copyin(t) reduction(+:r) num_threads (nth) &
610 !$omp& proc_bind(spread) lastprivate (l) collapse(1) bind(parallel) order(concurrent) if (parallel: i2) &
611 !$omp& allocate (f)
612 do l = 1, 64
613 ll = ll + 1
614 end do
616 !$omp parallel loop &
617 !$omp& private (p) firstprivate (f) default(shared) shared(s) copyin(t) reduction(+:r) num_threads (nth) &
618 !$omp& proc_bind(spread) lastprivate (l) collapse(1) if (parallel: i2) &
619 !$omp& allocate (f)
620 do l = 1, 64
621 ll = ll + 1
622 end do
624 !$omp teams loop &
625 !$omp& private(p) firstprivate (f) shared(s) default(shared) reduction(+:r) num_teams(nte-1:nte) thread_limit(tl) &
626 !$omp& collapse(1) lastprivate (l) bind(teams) &
627 !$omp& allocate (f)
628 do l = 1, 64
629 end do
631 !$omp teams loop &
632 !$omp& private(p) firstprivate (f) shared(s) default(shared) reduction(+:r) num_teams(nte) thread_limit(tl) &
633 !$omp& collapse(1) lastprivate (l) order(concurrent) &
634 !$omp& allocate (f)
635 do l = 1, 64
636 end do
638 !$omp target parallel loop &
639 !$omp& device(d) map (tofrom: m) private (p) firstprivate (f) defaultmap(tofrom: scalar) is_device_ptr (idp) &
640 !$omp& default(shared) shared(s) reduction(+:r) num_threads (nth) proc_bind(spread) &
641 !$omp& depend(inout: dd(0)) lastprivate (l) order(concurrent) collapse(1) in_reduction(+:r2) &
642 !$omp& if (target: i1) if (parallel: i2) &
643 !$omp& allocate (omp_default_mem_alloc: f)
644 do l = 1, 64
645 end do
646 !$omp end target parallel loop nowait
648 !$omp target teams loop &
649 !$omp& device(d) map (tofrom: m) private (p) firstprivate (f) defaultmap(tofrom: scalar) is_device_ptr (idp) &
650 !$omp& shared(s) default(shared) reduction(+:r) num_teams(nte-1:nte) thread_limit(tl) depend(inout: dd(0)) &
651 !$omp& lastprivate (l) bind(teams) collapse(1) in_reduction(+:r2) if (target: i1) &
652 !$omp& allocate (omp_default_mem_alloc: f)
653 do l = 1, 64
654 end do
655 !$omp end target teams loop nowait
657 !$omp target teams loop &
658 !$omp& device(d) map (tofrom: m) private (p) firstprivate (f) defaultmap(tofrom: scalar) is_device_ptr (idp) &
659 !$omp& shared(s) default(shared) reduction(+:r) num_teams(nte) thread_limit(tl) depend(inout: dd(0)) &
660 !$omp& lastprivate (l) order(concurrent) collapse(1) in_reduction(+:r2) if (target: i1) &
661 !$omp& allocate (omp_default_mem_alloc: f)
662 do l = 1, 64
663 end do
664 !$omp end target teams loop nowait
667 end module