llvm-project/flang/test/Lower/OpenACC/acc-host-data.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

54 lines
2.2 KiB
Fortran

! This test checks lowering of OpenACC host_data directive.
! RUN: bbc -fopenacc -emit-hlfir %s -o - | FileCheck %s
subroutine acc_host_data()
real, dimension(10) :: a
logical :: ifCondition = .TRUE.
! CHECK: %[[A:.*]] = fir.alloca !fir.array<10xf32> {bindc_name = "a", uniq_name = "_QFacc_host_dataEa"}
! CHECK: %[[DECLA:.*]]:2 = hlfir.declare %[[A]]
! CHECK: %[[IFCOND:.*]] = fir.address_of(@_QFacc_host_dataEifcondition) : !fir.ref<!fir.logical<4>>
! CHECK: %[[DECLIFCOND:.*]]:2 = hlfir.declare %[[IFCOND]]
!$acc host_data use_device(a)
!$acc end host_data
! CHECK: %[[DA:.*]] = acc.use_device varPtr(%[[DECLA]]#0 : !fir.ref<!fir.array<10xf32>>) -> !fir.ref<!fir.array<10xf32>> {name = "a"}
! CHECK: acc.host_data dataOperands(%[[DA]] : !fir.ref<!fir.array<10xf32>>)
!$acc host_data use_device(a) if_present
!$acc end host_data
! CHECK: %[[DA:.*]] = acc.use_device varPtr(%[[DECLA]]#0 : !fir.ref<!fir.array<10xf32>>) -> !fir.ref<!fir.array<10xf32>> {name = "a"}
! CHECK: acc.host_data dataOperands(%[[DA]] : !fir.ref<!fir.array<10xf32>>) {
! CHECK: } attributes {ifPresent}
!$acc host_data use_device(a) if_present if_present
!$acc end host_data
! CHECK: acc.host_data dataOperands(%{{.*}} : !fir.ref<!fir.array<10xf32>>) {
! CHECK: } attributes {ifPresent}
!$acc host_data use_device(a) if(ifCondition)
!$acc end host_data
! CHECK: %[[DA:.*]] = acc.use_device varPtr(%[[DECLA]]#0 : !fir.ref<!fir.array<10xf32>>) -> !fir.ref<!fir.array<10xf32>> {name = "a"}
! CHECK: %[[LOAD_IFCOND:.*]] = fir.load %[[DECLIFCOND]]#0 : !fir.ref<!fir.logical<4>>
! CHECK: %[[IFCOND_I1:.*]] = fir.convert %[[LOAD_IFCOND]] : (!fir.logical<4>) -> i1
! CHECK: acc.host_data if(%[[IFCOND_I1]]) dataOperands(%[[DA]] : !fir.ref<!fir.array<10xf32>>)
!$acc host_data use_device(a) if(.true.)
!$acc end host_data
! CHECK: %[[DA:.*]] = acc.use_device varPtr(%[[DECLA]]#0 : !fir.ref<!fir.array<10xf32>>) -> !fir.ref<!fir.array<10xf32>> {name = "a"}
! CHECK: acc.host_data dataOperands(%[[DA]] : !fir.ref<!fir.array<10xf32>>)
!$acc host_data use_device(a) if(.false.)
a = 1.0
!$acc end host_data
! CHECK-NOT: acc.host_data
! CHECK: hlfir.assign %{{.*}} to %[[DECLA]]#0
end subroutine