Files
clang-p2996/flang/test/Semantics/OpenMP/interop-construct.f90
Leandro Lupori 76fee8f4ed [flang][OpenMP][NFC] Don't use special chars in error messages (#134686)
Some error messages were using a special char for `fi`, in the
word `specified`, probably due to a typo.

This caused an error on Windows: #134625
2025-04-07 16:22:51 -03:00

31 lines
1018 B
Fortran

! REQUIRES: openmp_runtime
! RUN: %python %S/../test_errors.py %s %flang %openmp_flags -fopenmp-version=52
! OpenMP Version 5.2
! 14.1 Interop construct
! To check various semantic errors for inteorp construct.
SUBROUTINE test_interop_01()
USE omp_lib
INTEGER(OMP_INTEROP_KIND) :: obj
!ERROR: Each interop-var may be specified for at most one action-clause of each INTEROP construct.
!$OMP INTEROP INIT(TARGETSYNC,TARGET: obj) USE(obj)
PRINT *, 'pass'
END SUBROUTINE test_interop_01
SUBROUTINE test_interop_02()
USE omp_lib
INTEGER(OMP_INTEROP_KIND) :: obj
!ERROR: Each interop-type may be specified at most once.
!$OMP INTEROP INIT(TARGETSYNC,TARGET,TARGETSYNC: obj)
PRINT *, 'pass'
END SUBROUTINE test_interop_02
SUBROUTINE test_interop_03()
USE omp_lib
INTEGER(OMP_INTEROP_KIND) :: obj
!ERROR: A DEPEND clause can only appear on the directive if the interop-type includes TARGETSYNC
!$OMP INTEROP INIT(TARGET: obj) DEPEND(INOUT: obj)
PRINT *, 'pass'
END SUBROUTINE test_interop_03