xref: /llvm-project/flang/test/Semantics/OpenMP/atomic03.f90 (revision 15710bbdadddbf03428fd16aed53e6be54960703)
1! REQUIRES: openmp_runtime
2
3! RUN: %python %S/../test_errors.py %s %flang_fc1 %openmp_flags
4
5! OpenMP Atomic construct
6! section 2.17.7
7! Intrinsic procedure name is one of MAX, MIN, IAND, IOR, or IEOR.
8
9program OmpAtomic
10   use omp_lib
11   real x
12   integer :: y, z, a, b, c, d
13   x = 5.73
14   y = 3
15   z = 1
16!$omp atomic
17   y = IAND(y, 4)
18!$omp atomic
19   y = IOR(y, 5)
20!$omp atomic
21   y = IEOR(y, 6)
22!$omp atomic
23   y = MAX(y, 7)
24!$omp atomic
25   y = MIN(y, 8)
26
27!$omp atomic
28   !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'z'
29   z = IAND(y, 4)
30!$omp atomic
31   !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'z'
32   z = IOR(y, 5)
33!$omp atomic
34   !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'z'
35   z = IEOR(y, 6)
36!$omp atomic
37   !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'z'
38   z = MAX(y, 7, b, c)
39!$omp atomic
40   !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'z'
41   z = MIN(y, 8, a, d)
42
43!$omp atomic
44   !ERROR: Invalid intrinsic procedure name in OpenMP ATOMIC (UPDATE) statement
45   !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'y'
46   y = FRACTION(x)
47!$omp atomic
48   !ERROR: Invalid intrinsic procedure name in OpenMP ATOMIC (UPDATE) statement
49   !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'y'
50   y = REAL(x)
51!$omp atomic update
52   y = IAND(y, 4)
53!$omp atomic update
54   y = IOR(y, 5)
55!$omp atomic update
56   y = IEOR(y, 6)
57!$omp atomic update
58   y = MAX(y, 7)
59!$omp atomic update
60   y = MIN(y, 8)
61
62!$omp atomic update
63   !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'z'
64   z = IAND(y, 4)
65!$omp atomic update
66   !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'z'
67   z = IOR(y, 5)
68!$omp atomic update
69   !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'z'
70   z = IEOR(y, 6)
71!$omp atomic update
72   !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'z'
73   z = MAX(y, 7)
74!$omp atomic update
75   !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'z'
76   z = MIN(y, 8)
77
78!$omp atomic update
79   !ERROR: Invalid intrinsic procedure name in OpenMP ATOMIC (UPDATE) statement
80   y = MOD(y, 9)
81!$omp atomic update
82   !ERROR: Invalid intrinsic procedure name in OpenMP ATOMIC (UPDATE) statement
83   x = ABS(x)
84end program OmpAtomic
85
86subroutine conflicting_types()
87    type simple
88    integer :: z
89    end type
90    real x
91    integer :: y, z
92    type(simple) ::s
93    z = 1
94    !$omp atomic
95    !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'z'
96    z = IAND(s%z, 4)
97end subroutine
98
99subroutine more_invalid_atomic_update_stmts()
100    integer :: a, b
101    integer :: k(10)
102    type some_type
103        integer :: m(10)
104    end type
105    type(some_type) :: s
106
107    !$omp atomic update
108    !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'a'
109        a = min(a, a, b)
110
111    !$omp atomic
112    !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'a'
113        a = max(b, a, b, a)
114
115    !$omp atomic
116    !ERROR: Atomic update statement should be of the form `a = intrinsic_procedure(a, expr_list)` OR `a = intrinsic_procedure(expr_list, a)`
117        a = min(b, a, b)
118
119    !$omp atomic
120    !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'a'
121        a = max(b, a, b, a, b)
122
123    !$omp atomic update
124    !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'y'
125        y = min(z, x)
126
127    !$omp atomic
128        z = max(z, y)
129
130    !$omp atomic update
131    !ERROR: Expected scalar variable on the LHS of atomic update assignment statement
132    !ERROR: Intrinsic procedure arguments in atomic update statement must have exactly one occurence of 'k'
133        k = max(x, y)
134
135    !$omp atomic
136    !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches scalar REAL(4) and rank 1 array of REAL(4)
137    !ERROR: Expected scalar expression on the RHS of atomic update assignment statement
138        x = min(x, k)
139
140    !$omp atomic
141    !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches scalar REAL(4) and rank 1 array of REAL(4)
142    !ERROR: Expected scalar expression on the RHS of atomic update assignment statement
143        z =z + s%m
144end subroutine
145