[LLVM] Fix Maintainers.md formatting (NFC)
[llvm-project.git] / flang / test / Semantics / OpenMP / clause-validity01.f90
blob406d30b38948eae5702baebbdaa1ca7b3b677862
1 ! REQUIRES: openmp_runtime
3 ! RUN: %python %S/../test_errors.py %s %flang_fc1 %openmp_flags %openmp_module_flag -fopenmp-version=50
4 use omp_lib
5 ! Check OpenMP clause validity for the following directives:
7 ! 2.5 PARALLEL construct
8 ! 2.7.1 Loop construct
9 ! ...
11 use iso_c_binding
12 integer :: b = 128
13 integer, allocatable :: allc
14 type(C_PTR) :: cpt
15 integer :: z, c = 32
16 integer, parameter :: num = 16
17 real(8) :: arrayA(256), arrayB(512)
19 integer(omp_memspace_handle_kind) :: xy_memspace = omp_default_mem_space
20 type(omp_alloctrait) :: xy_traits(1) = [omp_alloctrait(omp_atk_alignment,64)]
21 integer(omp_allocator_handle_kind) :: xy_alloc
22 xy_alloc = omp_init_allocator(xy_memspace, 1, xy_traits)
24 arrayA = 1.414
25 arrayB = 3.14
26 N = 1024
28 ! 2.5 parallel-clause -> if-clause |
29 ! num-threads-clause |
30 ! default-clause |
31 ! private-clause |
32 ! firstprivate-clause |
33 ! shared-clause |
34 ! copyin-clause |
35 ! reduction-clause |
36 ! proc-bind-clause |
37 ! allocate-clause
39 !$omp parallel
40 do i = 1, N
41 a = 3.14
42 enddo
43 !$omp end parallel
45 !$omp parallel private(b) allocate(b)
46 do i = 1, N
47 a = 3.14
48 enddo
49 !$omp end parallel
51 !$omp parallel private(c, b) allocate(omp_default_mem_space : b, c)
52 do i = 1, N
53 a = 3.14
54 enddo
55 !$omp end parallel
57 !$omp parallel allocate(b) allocate(c) private(b, c)
58 do i = 1, N
59 a = 3.14
60 enddo
61 !$omp end parallel
63 !$omp parallel allocate(xy_alloc :b) private(b)
64 do i = 1, N
65 a = 3.14
66 enddo
67 !$omp end parallel
69 !$omp task private(b) allocate(b)
70 do i = 1, N
71 z = 2
72 end do
73 !$omp end task
75 !$omp teams private(b) allocate(b)
76 do i = 1, N
77 z = 2
78 end do
79 !$omp end teams
81 !$omp target private(b) allocate(b)
82 do i = 1, N
83 z = 2
84 end do
85 !$omp end target
87 !ERROR: ALLOCATE clause is not allowed on the TARGET DATA directive
88 !$omp target data map(from: b) allocate(b)
89 do i = 1, N
90 z = 2
91 enddo
92 !$omp end target data
94 !ERROR: SCHEDULE clause is not allowed on the PARALLEL directive
95 !$omp parallel schedule(static)
96 do i = 1, N
97 a = 3.14
98 enddo
99 !$omp end parallel
101 !ERROR: COLLAPSE clause is not allowed on the PARALLEL directive
102 !$omp parallel collapse(2)
103 do i = 1, N
104 do j = 1, N
105 a = 3.14
106 enddo
107 enddo
108 !$omp end parallel
110 !ERROR: The parameter of the COLLAPSE clause must be a constant positive integer expression
111 !$omp do collapse(-1)
112 do i = 1, N
113 do j = 1, N
114 a = 3.14
115 enddo
116 enddo
117 !$omp end do
119 a = 1.0
120 !$omp parallel firstprivate(a)
121 do i = 1, N
122 a = 3.14
123 enddo
124 !ERROR: NUM_THREADS clause is not allowed on the END PARALLEL directive
125 !$omp end parallel num_threads(4)
127 !ERROR: LASTPRIVATE clause is not allowed on the PARALLEL directive
128 !ERROR: NUM_TASKS clause is not allowed on the PARALLEL directive
129 !ERROR: INBRANCH clause is not allowed on the PARALLEL directive
130 !$omp parallel lastprivate(a) NUM_TASKS(4) inbranch
131 do i = 1, N
132 a = 3.14
133 enddo
134 !$omp end parallel
136 !ERROR: At most one NUM_THREADS clause can appear on the PARALLEL directive
137 !$omp parallel num_threads(2) num_threads(4)
138 do i = 1, N
139 a = 3.14
140 enddo
141 !$omp end parallel
143 !ERROR: The parameter of the NUM_THREADS clause must be a positive integer expression
144 !$omp parallel num_threads(1-4)
145 do i = 1, N
146 a = 3.14
147 enddo
148 !ERROR: NOWAIT clause is not allowed on the END PARALLEL directive
149 !$omp end parallel nowait
151 !$omp parallel num_threads(num-10)
152 do i = 1, N
153 a = 3.14
154 enddo
155 !$omp end parallel
157 !$omp parallel num_threads(b+1)
158 do i = 1, N
159 a = 3.14
160 enddo
161 !$omp end parallel
163 !$omp parallel
164 do i = 1, N
165 enddo
166 !ERROR: Unmatched END TARGET directive
167 !$omp end target
169 ! OMP 5.0 - 2.6 Restriction point 1
170 outofparallel: do k =1, 10
171 !$omp parallel
172 !$omp do
173 outer: do i=0, 10
174 inner: do j=1, 10
175 exit
176 !ERROR: EXIT statement terminates associated loop of an OpenMP DO construct
177 exit outer
178 !ERROR: EXIT to construct 'outofparallel' outside of PARALLEL construct is not allowed
179 !ERROR: EXIT to construct 'outofparallel' outside of DO construct is not allowed
180 exit outofparallel
181 end do inner
182 end do outer
183 !$omp end do
184 !$omp end parallel
185 end do outofparallel
187 ! 2.7.1 do-clause -> private-clause |
188 ! firstprivate-clause |
189 ! lastprivate-clause |
190 ! linear-clause |
191 ! reduction-clause |
192 ! schedule-clause |
193 ! collapse-clause |
194 ! ordered-clause
196 !ERROR: When SCHEDULE clause has AUTO specified, it must not have chunk size specified
197 !ERROR: At most one SCHEDULE clause can appear on the DO directive
198 !ERROR: When SCHEDULE clause has RUNTIME specified, it must not have chunk size specified
199 !$omp do schedule(auto, 2) schedule(runtime, 2)
200 do i = 1, N
201 a = 3.14
202 enddo
204 !ERROR: A modifier may not be specified in a LINEAR clause on the DO directive
205 !$omp do linear(ref(b))
206 do i = 1, N
207 a = 3.14
208 enddo
210 !ERROR: The NONMONOTONIC modifier can only be specified with SCHEDULE(DYNAMIC) or SCHEDULE(GUIDED)
211 !ERROR: The NONMONOTONIC modifier cannot be specified if an ORDERED clause is specified
212 !$omp do schedule(NONMONOTONIC:static) ordered
213 do i = 1, N
214 a = 3.14
215 enddo
217 !$omp do schedule(simd, monotonic:dynamic)
218 do i = 1, N
219 a = 3.14
220 enddo
222 !ERROR: Clause LINEAR is not allowed if clause ORDERED appears on the DO directive
223 !ERROR: The parameter of the ORDERED clause must be a constant positive integer expression
224 !$omp do ordered(1-1) private(b) linear(b) linear(a)
225 do i = 1, N
226 a = 3.14
227 enddo
229 !ERROR: The parameter of the ORDERED clause must be greater than or equal to the parameter of the COLLAPSE clause
230 !$omp do collapse(num-14) ordered(1)
231 do i = 1, N
232 do j = 1, N
233 do k = 1, N
234 a = 3.14
235 enddo
236 enddo
237 enddo
239 !$omp parallel do simd if(parallel:a>1.)
240 do i = 1, N
241 enddo
242 !$omp end parallel do simd
244 !ERROR: Unmatched directive name modifier TARGET on the IF clause
245 !$omp parallel do if(target:a>1.)
246 do i = 1, N
247 enddo
248 !ERROR: Unmatched END SIMD directive
249 !$omp end simd
251 ! 2.7.2 sections-clause -> private-clause |
252 ! firstprivate-clause |
253 ! lastprivate-clause |
254 ! reduction-clause
256 !$omp parallel
257 !$omp sections
258 !$omp section
259 a = 0.0
260 !$omp section
261 b = 1
262 !$omp end sections nowait
263 !$omp end parallel
265 !$omp parallel
266 !$omp sections
267 !$omp section
268 a = 0.0
269 !ERROR: Unmatched END PARALLEL SECTIONS directive
270 !$omp end parallel sections
271 !$omp end parallel
273 !$omp parallel
274 !$omp sections
275 a = 0.0
276 b = 1
277 !$omp section
278 c = 1
279 d = 2
280 !ERROR: NUM_THREADS clause is not allowed on the END SECTIONS directive
281 !$omp end sections num_threads(4)
283 !$omp parallel
284 !$omp sections
285 b = 1
286 !$omp section
287 c = 1
288 d = 2
289 !ERROR: At most one NOWAIT clause can appear on the END SECTIONS directive
290 !$omp end sections nowait nowait
291 !$omp end parallel
293 !$omp end parallel
295 ! 2.11.2 parallel-sections-clause -> parallel-clause |
296 ! sections-clause
298 !$omp parallel sections num_threads(4) private(b) lastprivate(d)
299 a = 0.0
300 !$omp section
301 b = 1
302 c = 2
303 !$omp section
304 d = 3
305 !$omp end parallel sections
307 !ERROR: At most one NUM_THREADS clause can appear on the PARALLEL SECTIONS directive
308 !$omp parallel sections num_threads(1) num_threads(4)
309 a = 0.0
310 !ERROR: Unmatched END SECTIONS directive
311 !$omp end sections
313 !$omp parallel sections
314 !ERROR: NOWAIT clause is not allowed on the END PARALLEL SECTIONS directive
315 !$omp end parallel sections nowait
317 ! 2.7.3 single-clause -> private-clause |
318 ! firstprivate-clause
319 ! end-single-clause -> copyprivate-clause |
320 ! nowait-clause
322 !$omp parallel
323 b = 1
324 !ERROR: LASTPRIVATE clause is not allowed on the SINGLE directive
325 !ERROR: NOWAIT clause is not allowed on the OMP SINGLE directive, use it on OMP END SINGLE directive
326 !$omp single private(a) lastprivate(c) nowait
327 a = 3.14
328 !ERROR: Clause NOWAIT is not allowed if clause COPYPRIVATE appears on the END SINGLE directive
329 !ERROR: COPYPRIVATE variable 'a' may not appear on a PRIVATE or FIRSTPRIVATE clause on a SINGLE construct
330 !ERROR: At most one NOWAIT clause can appear on the END SINGLE directive
331 !$omp end single copyprivate(a) nowait nowait
332 c = 2
333 !$omp end parallel
335 ! 2.7.4 workshare
337 !$omp parallel
338 !$omp workshare
339 a = 1.0
340 !$omp end workshare nowait
341 !ERROR: NUM_THREADS clause is not allowed on the WORKSHARE directive
342 !$omp workshare num_threads(4)
343 a = 1.0
344 !ERROR: COPYPRIVATE clause is not allowed on the END WORKSHARE directive
345 !$omp end workshare nowait copyprivate(a)
346 !ERROR: NOWAIT clause is not allowed on the OMP WORKSHARE directive, use it on OMP END WORKSHARE directive
347 !$omp workshare nowait
348 !$omp end workshare
349 !$omp end parallel
351 ! 2.8.1 simd-clause -> safelen-clause |
352 ! simdlen-clause |
353 ! linear-clause |
354 ! aligned-clause |
355 ! private-clause |
356 ! lastprivate-clause |
357 ! reduction-clause |
358 ! collapse-clause
360 a = 0.0
361 !ERROR: TASK_REDUCTION clause is not allowed on the SIMD directive
362 !$omp simd private(b) reduction(+:a) task_reduction(+:a)
363 do i = 1, N
364 a = a + b + 3.14
365 enddo
367 !ERROR: At most one SAFELEN clause can appear on the SIMD directive
368 !$omp simd safelen(1) safelen(2)
369 do i = 1, N
370 a = 3.14
371 enddo
373 !ERROR: The parameter of the SIMDLEN clause must be a constant positive integer expression
374 !$omp simd simdlen(-1)
375 do i = 1, N
376 a = 3.14
377 enddo
379 !ERROR: The parameter of the ALIGNED clause must be a constant positive integer expression
380 !$omp simd aligned(cpt:-2)
381 do i = 1, N
382 a = 3.14
383 enddo
385 !$omp parallel
386 !ERROR: The parameter of the SIMDLEN clause must be less than or equal to the parameter of the SAFELEN clause
387 !$omp simd safelen(1+1) simdlen(1+2)
388 do i = 1, N
389 a = 3.14
390 enddo
391 !$omp end parallel
393 !ERROR: The `SAFELEN` clause cannot appear in the `SIMD` directive with `ORDER(CONCURRENT)` clause
394 !$omp simd order(concurrent) safelen(1+2)
395 do i = 1, N
396 a = 3.14
397 enddo
399 ! 2.11.1 parallel-do-clause -> parallel-clause |
400 ! do-clause
402 !ERROR: At most one PROC_BIND clause can appear on the PARALLEL DO directive
403 !ERROR: A modifier may not be specified in a LINEAR clause on the PARALLEL DO directive
404 !$omp parallel do proc_bind(master) proc_bind(close) linear(val(b))
405 do i = 1, N
406 a = 3.14
407 enddo
409 ! 2.8.3 do-simd-clause -> do-clause |
410 ! simd-clause
412 !$omp parallel
413 !ERROR: No ORDERED clause with a parameter can be specified on the DO SIMD directive
414 !ERROR: NOGROUP clause is not allowed on the DO SIMD directive
415 !ERROR: NOWAIT clause is not allowed on the OMP DO SIMD directive, use it on OMP END DO SIMD directive
416 !$omp do simd ordered(2) NOGROUP nowait
417 do i = 1, N
418 do j = 1, N
419 a = 3.14
420 enddo
421 enddo
422 !omp end do nowait
423 !$omp end parallel
425 ! 2.11.4 parallel-do-simd-clause -> parallel-clause |
426 ! do-simd-clause
428 !$omp parallel do simd collapse(2) safelen(2) &
429 !$omp & simdlen(1) private(c) firstprivate(a) proc_bind(spread)
430 do i = 1, N
431 do j = 1, N
432 a = 3.14
433 enddo
434 enddo
436 ! 2.9.2 taskloop -> TASKLOOP [taskloop-clause[ [,] taskloop-clause]...]
437 ! taskloop-clause -> if-clause |
438 ! shared-clause |
439 ! private-clause |
440 ! firstprivate-clause |
441 ! lastprivate-clause |
442 ! default-clause |
443 ! grainsize-clause |
444 ! num-tasks-clause |
445 ! collapse-clause |
446 ! final-clause |
447 ! priority-clause |
448 ! untied-clause |
449 ! mergeable-clause |
450 ! nogroup-clause
452 !$omp taskloop
453 do i = 1, N
454 a = 3.14
455 enddo
457 !ERROR: SCHEDULE clause is not allowed on the TASKLOOP directive
458 !$omp taskloop schedule(static)
459 do i = 1, N
460 a = 3.14
461 enddo
463 !ERROR: GRAINSIZE and NUM_TASKS clauses are mutually exclusive and may not appear on the same TASKLOOP directive
464 !$omp taskloop num_tasks(3) grainsize(2)
465 do i = 1,N
466 a = 3.14
467 enddo
469 !ERROR: At most one NUM_TASKS clause can appear on the TASKLOOP directive
470 !ERROR: TASK_REDUCTION clause is not allowed on the TASKLOOP directive
471 !$omp taskloop num_tasks(3) num_tasks(2) task_reduction(*:a)
472 do i = 1,N
473 a = 3.14
474 enddo
476 ! 2.13.1 master
478 !$omp parallel
479 !WARNING: OpenMP directive MASTER has been deprecated, please use MASKED instead.
480 !$omp master
481 a=3.14
482 !$omp end master
483 !$omp end parallel
485 !$omp parallel
486 !WARNING: OpenMP directive MASTER has been deprecated, please use MASKED instead.
487 !ERROR: NUM_THREADS clause is not allowed on the MASTER directive
488 !$omp master num_threads(4)
489 a=3.14
490 !$omp end master
491 !$omp end parallel
493 ! Standalone Directives (basic)
495 !$omp taskyield
496 !$omp barrier
497 !$omp taskwait
498 !ERROR: The SINK and SOURCE dependence types can only be used with the ORDERED directive, used here in the TASKWAIT construct
499 !$omp taskwait depend(source)
500 ! !$omp taskwait depend(sink:i-1)
501 ! !$omp target enter data map(to:arrayA) map(alloc:arrayB)
502 ! !$omp target update from(arrayA) to(arrayB)
503 ! !$omp target exit data map(from:arrayA) map(delete:arrayB)
504 !$omp flush (c)
505 !$omp flush acq_rel
506 !$omp flush release
507 !$omp flush acquire
508 !ERROR: If memory-order-clause is RELEASE, ACQUIRE, or ACQ_REL, list items must not be specified on the FLUSH directive
509 !$omp flush release (c)
510 !ERROR: SEQ_CST clause is not allowed on the FLUSH directive
511 !$omp flush seq_cst
512 !ERROR: RELAXED clause is not allowed on the FLUSH directive
513 !$omp flush relaxed
515 ! 2.13.2 critical Construct
517 ! !$omp critical (first)
518 a = 3.14
519 ! !$omp end critical (first)
521 ! 2.9.1 task-clause -> if-clause |
522 ! final-clause |
523 ! untied-clause |
524 ! default-clause |
525 ! mergeable-clause |
526 ! private-clause |
527 ! firstprivate-clause |
528 ! shared-clause |
529 ! depend-clause |
530 ! priority-clause
532 !$omp task shared(a) default(none) if(task:a > 1.)
533 a = 1.
534 !$omp end task
536 !ERROR: Unmatched directive name modifier TASKLOOP on the IF clause
537 !$omp task private(a) if(taskloop:a.eq.1)
538 a = 1.
539 !$omp end task
541 !ERROR: LASTPRIVATE clause is not allowed on the TASK directive
542 !ERROR: At most one FINAL clause can appear on the TASK directive
543 !$omp task lastprivate(b) final(a.GE.1) final(.false.)
544 b = 1
545 !$omp end task
547 !ERROR: The parameter of the PRIORITY clause must be a positive integer expression
548 !$omp task priority(-1) firstprivate(a) mergeable
549 a = 3.14
550 !$omp end task
552 ! 2.9.3 taskloop-simd-clause -> taskloop-clause |
553 ! simd-clause
555 !$omp taskloop simd
556 do i = 1, N
557 a = 3.14
558 enddo
559 !$omp end taskloop simd
561 !$omp taskloop simd reduction(+:a)
562 do i = 1, N
563 a = a + 3.14
564 enddo
565 !ERROR: Unmatched END TASKLOOP directive
566 !$omp end taskloop
568 !ERROR: GRAINSIZE and NUM_TASKS clauses are mutually exclusive and may not appear on the same TASKLOOP SIMD directive
569 !$omp taskloop simd num_tasks(3) grainsize(2)
570 do i = 1,N
571 a = 3.14
572 enddo
574 allocate(allc)
575 !ERROR: The parameter of the SIMDLEN clause must be a constant positive integer expression
576 !ERROR: The parameter of the ALIGNED clause must be a constant positive integer expression
577 !$omp taskloop simd simdlen(-1) aligned(allc:-2)
578 do i = 1, N
579 allc = 3.14
580 enddo
582 !$omp target enter data map(alloc:A) device(0)
583 !$omp target exit data map(delete:A) device(0)
585 end program