xref: /llvm-project/flang/test/Semantics/OpenMP/atomic04.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! Update assignment must be 'var = var op expr' or 'var = expr op var'
8
9program OmpAtomic
10   use omp_lib
11   real x
12   integer y
13   logical m, n, l
14   x = 5.73
15   y = 3
16   m = .TRUE.
17   n = .FALSE.
18!$omp atomic
19   x = x + 1
20!$omp atomic
21   x = 1 + x
22!$omp atomic
23   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
24   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
25   x = y + 1
26!$omp atomic
27   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
28   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
29   x = 1 + y
30
31!$omp atomic
32   x = x - 1
33!$omp atomic
34   x = 1 - x
35!$omp atomic
36   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
37   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
38   x = y - 1
39!$omp atomic
40   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
41   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
42   x = 1 - y
43
44!$omp atomic
45   x = x*1
46!$omp atomic
47   x = 1*x
48!$omp atomic
49   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
50   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
51   x = y*1
52!$omp atomic
53   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
54   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
55   x = 1*y
56
57!$omp atomic
58   x = x/1
59!$omp atomic
60   x = 1/x
61!$omp atomic
62   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
63   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
64   x = y/1
65!$omp atomic
66   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
67   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
68   x = 1/y
69
70!$omp atomic
71   m = m .AND. n
72!$omp atomic
73   m = n .AND. m
74!$omp atomic
75   !ERROR: Atomic update statement should be of form `m = m operator expr` OR `m = expr operator m`
76   !ERROR: Exactly one occurence of 'm' expected on the RHS of atomic update assignment statement
77   m = n .AND. l
78
79!$omp atomic
80   m = m .OR. n
81!$omp atomic
82   m = n .OR. m
83!$omp atomic
84   !ERROR: Atomic update statement should be of form `m = m operator expr` OR `m = expr operator m`
85   !ERROR: Exactly one occurence of 'm' expected on the RHS of atomic update assignment statement
86   m = n .OR. l
87
88!$omp atomic
89   m = m .EQV. n
90!$omp atomic
91   m = n .EQV. m
92!$omp atomic
93   !ERROR: Atomic update statement should be of form `m = m operator expr` OR `m = expr operator m`
94   !ERROR: Exactly one occurence of 'm' expected on the RHS of atomic update assignment statement
95   m = n .EQV. l
96
97!$omp atomic
98   m = m .NEQV. n
99!$omp atomic
100   m = n .NEQV. m
101!$omp atomic
102   !ERROR: Atomic update statement should be of form `m = m operator expr` OR `m = expr operator m`
103   !ERROR: Exactly one occurence of 'm' expected on the RHS of atomic update assignment statement
104   m = n .NEQV. l
105
106!$omp atomic update
107   x = x + 1
108!$omp atomic update
109   x = 1 + x
110!$omp atomic update
111   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
112   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
113   x = y + 1
114!$omp atomic update
115   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
116   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
117   x = 1 + y
118
119!$omp atomic update
120   x = x - 1
121!$omp atomic update
122   x = 1 - x
123!$omp atomic update
124   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
125   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
126   x = y - 1
127!$omp atomic update
128   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
129   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
130   x = 1 - y
131
132!$omp atomic update
133   x = x*1
134!$omp atomic update
135   x = 1*x
136!$omp atomic update
137   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
138   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
139   x = y*1
140!$omp atomic update
141   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
142   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
143   x = 1*y
144
145!$omp atomic update
146   x = x/1
147!$omp atomic update
148   x = 1/x
149!$omp atomic update
150   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
151   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
152   x = y/1
153!$omp atomic update
154   !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
155   !ERROR: Exactly one occurence of 'x' expected on the RHS of atomic update assignment statement
156   x = 1/y
157
158!$omp atomic update
159   m = m .AND. n
160!$omp atomic update
161   m = n .AND. m
162!$omp atomic update
163   !ERROR: Atomic update statement should be of form `m = m operator expr` OR `m = expr operator m`
164   !ERROR: Exactly one occurence of 'm' expected on the RHS of atomic update assignment statement
165   m = n .AND. l
166
167!$omp atomic update
168   m = m .OR. n
169!$omp atomic update
170   m = n .OR. m
171!$omp atomic update
172   !ERROR: Atomic update statement should be of form `m = m operator expr` OR `m = expr operator m`
173   !ERROR: Exactly one occurence of 'm' expected on the RHS of atomic update assignment statement
174   m = n .OR. l
175
176!$omp atomic update
177   m = m .EQV. n
178!$omp atomic update
179   m = n .EQV. m
180!$omp atomic update
181   !ERROR: Atomic update statement should be of form `m = m operator expr` OR `m = expr operator m`
182   !ERROR: Exactly one occurence of 'm' expected on the RHS of atomic update assignment statement
183   m = n .EQV. l
184
185!$omp atomic update
186   m = m .NEQV. n
187!$omp atomic update
188   m = n .NEQV. m
189!$omp atomic update
190   !ERROR: Atomic update statement should be of form `m = m operator expr` OR `m = expr operator m`
191   !ERROR: Exactly one occurence of 'm' expected on the RHS of atomic update assignment statement
192   m = n .NEQV. l
193
194end program OmpAtomic
195
196subroutine more_invalid_atomic_update_stmts()
197    integer :: a, b, c
198    integer :: d(10)
199    real :: x, y, z(10)
200    type some_type
201        real :: m
202        real :: n(10)
203    end type
204    type(some_type) p
205
206    !$omp atomic
207    !ERROR: Invalid or missing operator in atomic update statement
208        x = x
209
210    !$omp atomic update
211    !ERROR: Invalid or missing operator in atomic update statement
212        x = 1
213
214    !$omp atomic update
215    !ERROR: Exactly one occurence of 'a' expected on the RHS of atomic update assignment statement
216        a = a * b + a
217
218    !$omp atomic
219    !ERROR: Atomic update statement should be of form `a = a operator expr` OR `a = expr operator a`
220        a = b * (a + 9)
221
222    !$omp atomic update
223    !ERROR: Exactly one occurence of 'a' expected on the RHS of atomic update assignment statement
224        a = a * (a + b)
225
226    !$omp atomic
227    !ERROR: Exactly one occurence of 'a' expected on the RHS of atomic update assignment statement
228        a = (b + a) * a
229
230    !$omp atomic
231    !ERROR: Atomic update statement should be of form `a = a operator expr` OR `a = expr operator a`
232        a = a * b + c
233
234    !$omp atomic update
235    !ERROR: Atomic update statement should be of form `a = a operator expr` OR `a = expr operator a`
236        a = a + b + c
237
238    !$omp atomic
239        a = b * c + a
240
241    !$omp atomic update
242        a = c + b + a
243
244    !$omp atomic
245    !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches scalar INTEGER(4) and rank 1 array of INTEGER(4)
246    !ERROR: Expected scalar expression on the RHS of atomic update assignment statement
247        a = a + d
248
249    !$omp atomic update
250    !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches scalar REAL(4) and rank 1 array of REAL(4)
251    !ERROR: Atomic update statement should be of form `x = x operator expr` OR `x = expr operator x`
252    !ERROR: Expected scalar expression on the RHS of atomic update assignment statement
253        x = x * y / z
254
255    !$omp atomic
256    !ERROR: Atomic update statement should be of form `p%m = p%m operator expr` OR `p%m = expr operator p%m`
257    !ERROR: Exactly one occurence of 'p%m' expected on the RHS of atomic update assignment statement
258        p%m = x + y
259
260    !$omp atomic update
261    !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches scalar REAL(4) and rank 1 array of REAL(4)
262    !ERROR: Expected scalar expression on the RHS of atomic update assignment statement
263    !ERROR: Exactly one occurence of 'p%m' expected on the RHS of atomic update assignment statement
264        p%m = p%m + p%n
265end subroutine
266