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