Files
clang-p2996/flang/test/Semantics/OpenMP/omp-atomic-assignment-stmt.f90
Krzysztof Parzyszek 141d390dcb [flang][OpenMP] Overhaul implementation of ATOMIC construct (#137852)
The parser will accept a wide variety of illegal attempts at forming an
ATOMIC construct, leaving it to the semantic analysis to diagnose any
issues. This consolidates the analysis into one place and allows us to
produce more informative diagnostics.

The parser's outcome will be parser::OpenMPAtomicConstruct object
holding the directive, parser::Body, and an optional end-directive. The
prior variety of OmpAtomicXyz classes, as well as OmpAtomicClause have
been removed. READ, WRITE, etc. are now proper clauses.

The semantic analysis consistently operates on "evaluation"
representations, mainly evaluate::Expr (as SomeExpr) and
evaluate::Assignment. The results of the semantic analysis are stored in
a mutable member of the OpenMPAtomicConstruct node. This follows a
precedent of having `typedExpr` member in parser::Expr, for example.
This allows the lowering code to avoid duplicated handling of AST nodes.

Using a BLOCK construct containing multiple statements for an ATOMIC
construct that requires multiple statements is now allowed. In fact, any
nesting of such BLOCK constructs is allowed.

This implementation will parse, and perform semantic checks for both
conditional-update and conditional-update-capture, although no MLIR will
be generated for those. Instead, a TODO error will be issues prior to
lowering.

The allowed forms of the ATOMIC construct were based on the OpenMP 6.0
spec.
2025-06-11 10:05:34 -05:00

155 lines
4.2 KiB
Fortran

! REQUIRES: openmp_runtime
! RUN: %python %S/../test_errors.py %s %flang_fc1 %openmp_flags -fopenmp-version=50
! Semantic checks for various assignments related to atomic constructs
program sample
use omp_lib
integer :: x, v
integer :: y(10)
integer, allocatable :: k
integer a(10)
type sample_type
integer :: y
integer :: m
endtype
type(sample_type) :: z
character :: l, r
!$omp atomic read
v = x
!$omp atomic read
!ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches scalar INTEGER(4) and rank 1 array of INTEGER(4)
!ERROR: Atomic variable y(1_8:3_8:1_8) should be a scalar
v = y(1:3)
!$omp atomic read
!ERROR: Atomic expression x*(10_4+x) should be a variable
v = x * (10 + x)
!$omp atomic read
!ERROR: Atomic expression 4_4 should be a variable
v = 4
!$omp atomic read
!ERROR: Atomic variable k cannot be ALLOCATABLE
v = k
!$omp atomic write
!ERROR: Atomic variable k cannot be ALLOCATABLE
k = x
!$omp atomic update
!ERROR: Atomic variable k cannot be ALLOCATABLE
k = k + x * (v * x)
!$omp atomic
!ERROR: Atomic variable k cannot be ALLOCATABLE
k = v * k
!$omp atomic write
!ERROR: Within atomic operation z%y and x+z%y access the same storage
z%y = x + z%y
!$omp atomic write
!ERROR: Within atomic operation x and x access the same storage
x = x
!$omp atomic write
!ERROR: Within atomic operation m and min(m,x,z%m)+k access the same storage
m = min(m, x, z%m) + k
!$omp atomic read
!ERROR: Within atomic operation x and x access the same storage
x = x
!$omp atomic read
!ERROR: Atomic expression min(m,x,z%m)+k should be a variable
m = min(m, x, z%m) + k
!$omp atomic read
!ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches scalar INTEGER(4) and rank 1 array of INTEGER(4)
!ERROR: Atomic variable a should be a scalar
x = a
!$omp atomic write
!ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches scalar INTEGER(4) and rank 1 array of INTEGER(4)
x = a
!$omp atomic write
!ERROR: Atomic variable a should be a scalar
a = x
!$omp atomic capture
v = x
x = x + 1
!$omp end atomic
!$omp atomic release capture
v = x
! This ends up being "x = b + x".
x = b + (x*1)
!$omp end atomic
!$omp atomic capture hint(0)
v = x
x = 1
!$omp end atomic
!$omp atomic capture
!ERROR: In ATOMIC UPDATE operation with CAPTURE the right-hand side of the capture assignment should read b
v = x
b = b + 1
!$omp end atomic
!$omp atomic capture
!ERROR: In ATOMIC UPDATE operation with CAPTURE the right-hand side of the capture assignment should read b
v = x
b = 10
!$omp end atomic
!$omp atomic capture
x = x + 10
!ERROR: In ATOMIC UPDATE operation with CAPTURE the right-hand side of the capture assignment should read x
v = b
!$omp end atomic
!ERROR: In ATOMIC UPDATE operation with CAPTURE neither statement could be the update or the capture
!$omp atomic capture
v = 1
x = 4
!$omp end atomic
!$omp atomic capture
!ERROR: In ATOMIC UPDATE operation with CAPTURE the right-hand side of the capture assignment should read z%m
x = z%y
z%m = z%m + 1.0
!$omp end atomic
!$omp atomic capture
z%m = z%m + 1.0
!ERROR: In ATOMIC UPDATE operation with CAPTURE the right-hand side of the capture assignment should read z%m
x = z%y
!$omp end atomic
!$omp atomic capture
!ERROR: In ATOMIC UPDATE operation with CAPTURE the right-hand side of the capture assignment should read y(1_8)
x = y(2)
y(1) = y(1) + 1
!$omp end atomic
!$omp atomic capture
y(1) = y(1) + 1
!ERROR: In ATOMIC UPDATE operation with CAPTURE the right-hand side of the capture assignment should read y(1_8)
x = y(2)
!$omp end atomic
!$omp atomic read
!ERROR: Atomic variable r cannot have CHARACTER type
l = r
!$omp atomic write
!ERROR: Atomic variable l cannot have CHARACTER type
l = r
end program