1 ! REQUIRES: openmp_runtime
3 ! RUN: %python %S/../test_errors.py %s %flang_fc1 %openmp_flags %openmp_module_flag -fopenmp-version=50
5 ! Check OpenMP clause validity for the following directives:
7 ! 2.5 PARALLEL construct
13 integer, allocatable
:: allc
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
)
28 ! 2.5 parallel-clause -> if-clause |
29 ! num-threads-clause |
32 ! firstprivate-clause |
45 !$omp parallel private(b) allocate(b)
51 !$omp parallel private(c, b) allocate(omp_default_mem_space : b, c)
57 !$omp parallel allocate(b) allocate(c) private(b, c)
63 !$omp parallel allocate(xy_alloc :b) private(b)
69 !$omp task private(b) allocate(b)
75 !$omp teams private(b) allocate(b)
81 !$omp target private(b) allocate(b)
87 !ERROR: ALLOCATE clause is not allowed on the TARGET DATA directive
88 !$omp target data map(from: b) allocate(b)
94 !ERROR: SCHEDULE clause is not allowed on the PARALLEL directive
95 !$omp parallel schedule(static)
101 !ERROR: COLLAPSE clause is not allowed on the PARALLEL directive
102 !$omp parallel collapse(2)
110 !ERROR: The parameter of the COLLAPSE clause must be a constant positive integer expression
111 !$omp do collapse(-1)
120 !$omp parallel firstprivate(a)
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
136 !ERROR: At most one NUM_THREADS clause can appear on the PARALLEL directive
137 !$omp parallel num_threads(2) num_threads(4)
143 !ERROR: The parameter of the NUM_THREADS clause must be a positive integer expression
144 !$omp parallel num_threads(1-4)
148 !ERROR: NOWAIT clause is not allowed on the END PARALLEL directive
149 !$omp end parallel nowait
151 !$omp parallel num_threads(num-10)
157 !$omp parallel num_threads(b+1)
166 !ERROR: Unmatched END TARGET directive
169 ! OMP 5.0 - 2.6 Restriction point 1
170 outofparallel
: do k
=1, 10
176 !ERROR: EXIT statement terminates associated loop of an OpenMP DO construct
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
187 ! 2.7.1 do-clause -> private-clause |
188 ! firstprivate-clause |
189 ! lastprivate-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)
204 !ERROR: A modifier may not be specified in a LINEAR clause on the DO directive
205 !$omp do linear(ref(b))
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
217 !$omp do schedule(simd, monotonic:dynamic)
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)
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)
239 !$omp parallel do simd if(parallel:a>1.)
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.)
248 !ERROR: Unmatched END SIMD directive
251 ! 2.7.2 sections-clause -> private-clause |
252 ! firstprivate-clause |
253 ! lastprivate-clause |
262 !$omp end sections nowait
269 !ERROR: Unmatched END PARALLEL SECTIONS directive
270 !$omp end parallel sections
280 !ERROR: NUM_THREADS clause is not allowed on the END SECTIONS directive
281 !$omp end sections num_threads(4)
289 !ERROR: At most one NOWAIT clause can appear on the END SECTIONS directive
290 !$omp end sections nowait nowait
295 ! 2.11.2 parallel-sections-clause -> parallel-clause |
298 !$omp parallel sections num_threads(4) private(b) lastprivate(d)
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)
310 !ERROR: Unmatched END SECTIONS directive
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 |
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
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
340 !$omp end workshare nowait
341 !ERROR: NUM_THREADS clause is not allowed on the WORKSHARE directive
342 !$omp workshare num_threads(4)
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
351 ! 2.8.1 simd-clause -> safelen-clause |
356 ! lastprivate-clause |
361 !ERROR: TASK_REDUCTION clause is not allowed on the SIMD directive
362 !$omp simd private(b) reduction(+:a) task_reduction(+:a)
367 !ERROR: At most one SAFELEN clause can appear on the SIMD directive
368 !$omp simd safelen(1) safelen(2)
373 !ERROR: The parameter of the SIMDLEN clause must be a constant positive integer expression
374 !$omp simd simdlen(-1)
379 !ERROR: The parameter of the ALIGNED clause must be a constant positive integer expression
380 !$omp simd aligned(cpt:-2)
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)
393 !ERROR: The `SAFELEN` clause cannot appear in the `SIMD` directive with `ORDER(CONCURRENT)` clause
394 !$omp simd order(concurrent) safelen(1+2)
399 ! 2.11.1 parallel-do-clause -> parallel-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))
409 ! 2.8.3 do-simd-clause -> do-clause |
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
425 ! 2.11.4 parallel-do-simd-clause -> parallel-clause |
428 !$omp parallel do simd collapse(2) safelen(2) &
429 !$omp & simdlen(1) private(c) firstprivate(a) proc_bind(spread)
436 ! 2.9.2 taskloop -> TASKLOOP [taskloop-clause[ [,] taskloop-clause]...]
437 ! taskloop-clause -> if-clause |
440 ! firstprivate-clause |
441 ! lastprivate-clause |
457 !ERROR: SCHEDULE clause is not allowed on the TASKLOOP directive
458 !$omp taskloop schedule(static)
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)
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)
479 !WARNING: OpenMP directive MASTER has been deprecated, please use MASKED instead.
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)
493 ! Standalone Directives (basic)
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)
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
512 !ERROR: RELAXED clause is not allowed on the FLUSH directive
515 ! 2.13.2 critical Construct
517 ! !$omp critical (first)
519 ! !$omp end critical (first)
521 ! 2.9.1 task-clause -> if-clause |
527 ! firstprivate-clause |
532 !$omp task shared(a) default(none) if(task:a > 1.)
536 !ERROR: Unmatched directive name modifier TASKLOOP on the IF clause
537 !$omp task private(a) if(taskloop:a.eq.1)
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.)
547 !ERROR: The parameter of the PRIORITY clause must be a positive integer expression
548 !$omp task priority(-1) firstprivate(a) mergeable
552 ! 2.9.3 taskloop-simd-clause -> taskloop-clause |
559 !$omp end taskloop simd
561 !$omp taskloop simd reduction(+:a)
565 !ERROR: Unmatched END TASKLOOP directive
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)
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)
582 !$omp target enter data map(alloc:A) device(0)
583 !$omp target exit data map(delete:A) device(0)