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.
84 lines
2.5 KiB
Fortran
84 lines
2.5 KiB
Fortran
! REQUIRES: openmp_runtime
|
|
! RUN: %python %S/../test_errors.py %s %flang_fc1 %openmp_flags -fopenmp-version=51
|
|
use omp_lib
|
|
implicit none
|
|
! Check atomic compare. This combines elements from multiple other "atomic*.f90", as
|
|
! to avoid having several files with just a few lines in them. atomic compare needs
|
|
! higher openmp version than the others, so need a separate file.
|
|
|
|
|
|
real a, b, c
|
|
a = 1.0
|
|
b = 2.0
|
|
c = 3.0
|
|
!$omp parallel num_threads(4)
|
|
! First a few things that should compile without error.
|
|
!$omp atomic seq_cst, compare
|
|
if (b .eq. a) then
|
|
b = c
|
|
end if
|
|
|
|
!$omp atomic seq_cst compare
|
|
if (a .eq. b) a = c
|
|
!$omp end atomic
|
|
|
|
!$omp atomic compare acquire hint(OMP_LOCK_HINT_CONTENDED)
|
|
if (b .eq. a) b = c
|
|
|
|
!$omp atomic release hint(OMP_LOCK_HINT_UNCONTENDED) compare
|
|
if (b .eq. a) b = c
|
|
|
|
!$omp atomic compare seq_cst
|
|
if (b .eq. c) b = a
|
|
|
|
!$omp atomic hint(1) acq_rel compare
|
|
if (b .eq. a) b = c
|
|
!$omp end atomic
|
|
|
|
!$omp atomic hint(1) acq_rel compare fail(release)
|
|
if (c .eq. a) a = b
|
|
!$omp end atomic
|
|
|
|
!$omp atomic compare fail(release)
|
|
if (c .eq. a) a = b
|
|
!$omp end atomic
|
|
|
|
! Check for error conditions:
|
|
!ERROR: At most one SEQ_CST clause can appear on the ATOMIC directive
|
|
!$omp atomic seq_cst seq_cst compare
|
|
if (b .eq. c) b = a
|
|
!ERROR: At most one SEQ_CST clause can appear on the ATOMIC directive
|
|
!$omp atomic compare seq_cst seq_cst
|
|
if (b .eq. c) b = a
|
|
!ERROR: At most one SEQ_CST clause can appear on the ATOMIC directive
|
|
!$omp atomic seq_cst compare seq_cst
|
|
if (b .eq. c) b = a
|
|
|
|
!ERROR: At most one ACQUIRE clause can appear on the ATOMIC directive
|
|
!$omp atomic acquire acquire compare
|
|
if (b .eq. c) b = a
|
|
!ERROR: At most one ACQUIRE clause can appear on the ATOMIC directive
|
|
!$omp atomic compare acquire acquire
|
|
if (b .eq. c) b = a
|
|
!ERROR: At most one ACQUIRE clause can appear on the ATOMIC directive
|
|
!$omp atomic acquire compare acquire
|
|
if (b .eq. c) b = a
|
|
|
|
!ERROR: At most one RELAXED clause can appear on the ATOMIC directive
|
|
!$omp atomic relaxed relaxed compare
|
|
if (b .eq. c) b = a
|
|
!ERROR: At most one RELAXED clause can appear on the ATOMIC directive
|
|
!$omp atomic compare relaxed relaxed
|
|
if (b .eq. c) b = a
|
|
!ERROR: At most one RELAXED clause can appear on the ATOMIC directive
|
|
!$omp atomic relaxed compare relaxed
|
|
if (b .eq. c) b = a
|
|
|
|
!ERROR: At most one FAIL clause can appear on the ATOMIC directive
|
|
!$omp atomic fail(release) compare fail(release)
|
|
if (c .eq. a) a = b
|
|
!$omp end atomic
|
|
|
|
!$omp end parallel
|
|
end
|