llvm-project/flang/test/Semantics/OpenACC/acc-update-validity.f90
Valentin Clement (バレンタイン クレメン) 2837fd7e5a
[flang][openacc] Allow if_present multiple times on host_data and update (#135422)
Similar to #135415.

The spec has not strict restriction to allow a single `if_present`
clause on the host_data and update directives. Allowing this clause
multiple times does not change the semantic of it. This patch relax the
rules in ACC.td since there is no restriction in the standard.

The OpenACC dialect represents the `if_present` clause with a `UnitAttr`
so the attribute will be set if the is one or more `if_present` clause.
2025-04-11 14:01:03 -07:00

68 lines
1.7 KiB
Fortran

! RUN: %python %S/../test_errors.py %s %flang -fopenacc
! Check OpenACC clause validity for the following construct and directive:
! 2.14.4 Update
program openacc_update_validity
implicit none
type atype
real(8), dimension(10) :: arr
end type atype
integer :: i
integer, parameter :: N = 256
integer, dimension(N) :: c
integer :: async1
integer :: wait1, wait2
real(8), dimension(N, N) :: aa, bb, cc
logical :: ifCondition = .TRUE.
type(atype) :: t
type(atype), dimension(10) :: ta
real(8), dimension(N) :: a, f, g, h
!ERROR: At least one of DEVICE, HOST, SELF clause must appear on the UPDATE directive
!$acc update
!$acc update device(t%arr(:))
!$acc update device(ta(i)%arr(:))
!$acc update self(a, f) host(g) device(h)
!$acc update host(aa) async(1)
!$acc update device(bb) async(async1)
!ERROR: At most one ASYNC clause can appear on the UPDATE directive
!$acc update host(aa, bb) async(1) async(2)
!$acc update self(bb, cc(:,:)) wait(1)
!ERROR: SELF clause on the UPDATE directive must have a var-list
!$acc update self
!$acc update device(aa, bb, cc) wait(wait1)
!$acc update host(aa) host(bb) device(cc) wait(1,2)
!$acc update device(aa, cc) wait(wait1, wait2)
!$acc update device(aa) device_type(*) async
!$acc update host(bb) device_type(*) wait
!$acc update self(cc) device_type(host,multicore) async device_type(*) wait
!ERROR: At most one IF clause can appear on the UPDATE directive
!$acc update device(aa) if(.true.) if(ifCondition)
! OK
!$acc update device(bb) if_present if_present
!ERROR: Clause IF is not allowed after clause DEVICE_TYPE on the UPDATE directive
!$acc update device(i) device_type(*) if(.TRUE.)
end program openacc_update_validity