xref: /llvm-project/flang/test/Semantics/OpenMP/flush02.f90 (revision 612f8ec7ac5dcddd16fb027aad64e2e353faa528)
1! REQUIRES: openmp_runtime
2
3! RUN: %python %S/../test_errors.py %s %flang_fc1 %openmp_flags -fopenmp-version=51
4
5! Check OpenMP 5.0 - 2.17.8 flush Construct
6! Restriction -
7! If memory-order-clause is release, acquire, or acq_rel, list items must not be specified on the flush directive.
8
9use omp_lib
10  implicit none
11
12  TYPE someStruct
13    REAL :: rr
14  end TYPE
15  integer :: i, a, b
16  real, DIMENSION(10) :: array
17  TYPE(someStruct) :: structObj
18
19  a = 1.0
20  !$omp parallel num_threads(4)
21  !No list flushes all.
22  if (omp_get_thread_num() == 1) THEN
23    !$omp flush
24  END IF
25
26  array = (/1, 2, 3, 4, 5, 6, 7, 8, 9, 10/)
27  !Only memory-order-clauses.
28  if (omp_get_thread_num() == 1) THEN
29    ! Not allowed clauses.
30    !$omp flush seq_cst
31    !ERROR: RELAXED clause is not allowed on the FLUSH directive
32    !$omp flush relaxed
33
34    ! Not allowed more than once.
35    !ERROR: At most one ACQ_REL clause can appear on the FLUSH directive
36    !$omp flush acq_rel acq_rel
37    !ERROR: At most one RELEASE clause can appear on the FLUSH directive
38    !$omp flush release release
39    !ERROR: At most one ACQUIRE clause can appear on the FLUSH directive
40    !$omp flush acquire acquire
41
42    ! Mix of allowed and not allowed.
43    !$omp flush seq_cst acquire
44  END IF
45
46  array = (/1, 2, 3, 4, 5, 6, 7, 8, 9, 10/)
47  ! No memory-order-clause only list-items.
48  if (omp_get_thread_num() == 2) THEN
49    !$omp flush (a)
50    !$omp flush (i, a, b)
51    !$omp flush (array, structObj%rr)
52    ! Too many flush with repeating list items.
53    !$omp flush (i, a, b, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, b, b, b, b)
54    !ERROR: No explicit type declared for 'notpresentitem'
55    !$omp flush (notPresentItem)
56  END IF
57
58  array = (/1, 2, 3, 4, 5, 6, 7, 8, 9, 10/)
59  if (omp_get_thread_num() == 3) THEN
60    !ERROR: If memory-order-clause is RELEASE, ACQUIRE, or ACQ_REL, list items must not be specified on the FLUSH directive
61    !$omp flush acq_rel (array)
62    !ERROR: If memory-order-clause is RELEASE, ACQUIRE, or ACQ_REL, list items must not be specified on the FLUSH directive
63    !$omp flush acq_rel (array, a, i)
64
65    array = (/1, 2, 3, 4, 5, 6, 7, 8, 9, 10/)
66    !ERROR: If memory-order-clause is RELEASE, ACQUIRE, or ACQ_REL, list items must not be specified on the FLUSH directive
67    !$omp flush release (array)
68    !ERROR: If memory-order-clause is RELEASE, ACQUIRE, or ACQ_REL, list items must not be specified on the FLUSH directive
69    !$omp flush release (array, a)
70
71    array = (/1, 2, 3, 4, 5, 6, 7, 8, 9, 10/)
72    !ERROR: If memory-order-clause is RELEASE, ACQUIRE, or ACQ_REL, list items must not be specified on the FLUSH directive
73    !$omp flush acquire (array)
74    !ERROR: If memory-order-clause is RELEASE, ACQUIRE, or ACQ_REL, list items must not be specified on the FLUSH directive
75    !$omp flush acquire (array, a, structObj%rr)
76  END IF
77  !$omp end parallel
78
79  !$omp parallel num_threads(4)
80    array = (/1, 2, 3, 4, 5, 6, 7, 8, 9, 10/)
81    !WARNING: OpenMP directive MASTER has been deprecated, please use MASKED instead.
82    !$omp master
83      !$omp flush (array)
84    !$omp end master
85  !$omp end parallel
86end
87
88