llvm-project/flang/test/Lower/OpenACC/acc-host-data.f90

Ignoring revisions in .git-blame-ignore-revs. Click here to bypass and see the normal blame view.

54 lines
2.2 KiB
Fortran
Raw Normal View History

! 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
[flang][acc] Improve acc lowering around fir.box and arrays (#125600) The current implementation of OpenACC lowering includes explicit expansion of following cases: - Creation of `acc.bounds` operations for all arrays, including those whose dimensions are captured in the type (eg `!fir.array<100xf32>`) - Expansion of box types by only putting the box's address in the data clause. The address was extracted with a `fir.box_addr` operation and the bounds were filled with `fir.box_dims` operation. However, with the creation of the new type interface `MappableType`, the idea is that specific type-based semantics can now be used. This also really simplifies representation in the IR. Consider the following example: ``` subroutine sub(arr) real :: arr(:) !$acc enter data copyin(arr) end subroutine ``` Before the current PR, the relevant acc dialect IR looked like: ``` func.func @_QPsub(%arg0: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "arr"}) { ... %1:2 = hlfir.declare %arg0 dummy_scope %0 {uniq_name = "_QFsubEarr"} : (!fir.box<!fir.array<?xf32>>, !fir.dscope) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>) %c1 = arith.constant 1 : index %c0 = arith.constant 0 : index %2:3 = fir.box_dims %1#0, %c0 : (!fir.box<!fir.array<?xf32>>, index) -> (index, index, index) %c0_0 = arith.constant 0 : index %3 = arith.subi %2#1, %c1 : index %4 = acc.bounds lowerbound(%c0_0 : index) upperbound(%3 : index) extent(%2#1 : index) stride(%2#2 : index) startIdx(%c1 : index) {strideInBytes = true} %5 = fir.box_addr %1#0 : (!fir.box<!fir.array<?xf32>>) -> !fir.ref<!fir.array<?xf32>> %6 = acc.copyin varPtr(%5 : !fir.ref<!fir.array<?xf32>>) bounds(%4) -> !fir.ref<!fir.array<?xf32>> {name = "arr", structured = false} acc.enter_data dataOperands(%6 : !fir.ref<!fir.array<?xf32>>) ``` After the current change, it looks like: ``` func.func @_QPsub(%arg0: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "arr"}) { ... %1:2 = hlfir.declare %arg0 dummy_scope %0 {uniq_name = "_QFsubEarr"} : (!fir.box<!fir.array<?xf32>>, !fir.dscope) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>) %2 = acc.copyin var(%1#0 : !fir.box<!fir.array<?xf32>>) -> !fir.box<!fir.array<?xf32>> {name = "arr", structured = false} acc.enter_data dataOperands(%2 : !fir.box<!fir.array<?xf32>>) ``` Restoring the old behavior can be done with following command line options: `--openacc-unwrap-fir-box=true --openacc-generate-default-bounds=true`
2025-02-04 08:08:16 -08:00
! 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
[flang][acc] Improve acc lowering around fir.box and arrays (#125600) The current implementation of OpenACC lowering includes explicit expansion of following cases: - Creation of `acc.bounds` operations for all arrays, including those whose dimensions are captured in the type (eg `!fir.array<100xf32>`) - Expansion of box types by only putting the box's address in the data clause. The address was extracted with a `fir.box_addr` operation and the bounds were filled with `fir.box_dims` operation. However, with the creation of the new type interface `MappableType`, the idea is that specific type-based semantics can now be used. This also really simplifies representation in the IR. Consider the following example: ``` subroutine sub(arr) real :: arr(:) !$acc enter data copyin(arr) end subroutine ``` Before the current PR, the relevant acc dialect IR looked like: ``` func.func @_QPsub(%arg0: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "arr"}) { ... %1:2 = hlfir.declare %arg0 dummy_scope %0 {uniq_name = "_QFsubEarr"} : (!fir.box<!fir.array<?xf32>>, !fir.dscope) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>) %c1 = arith.constant 1 : index %c0 = arith.constant 0 : index %2:3 = fir.box_dims %1#0, %c0 : (!fir.box<!fir.array<?xf32>>, index) -> (index, index, index) %c0_0 = arith.constant 0 : index %3 = arith.subi %2#1, %c1 : index %4 = acc.bounds lowerbound(%c0_0 : index) upperbound(%3 : index) extent(%2#1 : index) stride(%2#2 : index) startIdx(%c1 : index) {strideInBytes = true} %5 = fir.box_addr %1#0 : (!fir.box<!fir.array<?xf32>>) -> !fir.ref<!fir.array<?xf32>> %6 = acc.copyin varPtr(%5 : !fir.ref<!fir.array<?xf32>>) bounds(%4) -> !fir.ref<!fir.array<?xf32>> {name = "arr", structured = false} acc.enter_data dataOperands(%6 : !fir.ref<!fir.array<?xf32>>) ``` After the current change, it looks like: ``` func.func @_QPsub(%arg0: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "arr"}) { ... %1:2 = hlfir.declare %arg0 dummy_scope %0 {uniq_name = "_QFsubEarr"} : (!fir.box<!fir.array<?xf32>>, !fir.dscope) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>) %2 = acc.copyin var(%1#0 : !fir.box<!fir.array<?xf32>>) -> !fir.box<!fir.array<?xf32>> {name = "arr", structured = false} acc.enter_data dataOperands(%2 : !fir.box<!fir.array<?xf32>>) ``` Restoring the old behavior can be done with following command line options: `--openacc-unwrap-fir-box=true --openacc-generate-default-bounds=true`
2025-02-04 08:08:16 -08:00
! 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
[flang][acc] Improve acc lowering around fir.box and arrays (#125600) The current implementation of OpenACC lowering includes explicit expansion of following cases: - Creation of `acc.bounds` operations for all arrays, including those whose dimensions are captured in the type (eg `!fir.array<100xf32>`) - Expansion of box types by only putting the box's address in the data clause. The address was extracted with a `fir.box_addr` operation and the bounds were filled with `fir.box_dims` operation. However, with the creation of the new type interface `MappableType`, the idea is that specific type-based semantics can now be used. This also really simplifies representation in the IR. Consider the following example: ``` subroutine sub(arr) real :: arr(:) !$acc enter data copyin(arr) end subroutine ``` Before the current PR, the relevant acc dialect IR looked like: ``` func.func @_QPsub(%arg0: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "arr"}) { ... %1:2 = hlfir.declare %arg0 dummy_scope %0 {uniq_name = "_QFsubEarr"} : (!fir.box<!fir.array<?xf32>>, !fir.dscope) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>) %c1 = arith.constant 1 : index %c0 = arith.constant 0 : index %2:3 = fir.box_dims %1#0, %c0 : (!fir.box<!fir.array<?xf32>>, index) -> (index, index, index) %c0_0 = arith.constant 0 : index %3 = arith.subi %2#1, %c1 : index %4 = acc.bounds lowerbound(%c0_0 : index) upperbound(%3 : index) extent(%2#1 : index) stride(%2#2 : index) startIdx(%c1 : index) {strideInBytes = true} %5 = fir.box_addr %1#0 : (!fir.box<!fir.array<?xf32>>) -> !fir.ref<!fir.array<?xf32>> %6 = acc.copyin varPtr(%5 : !fir.ref<!fir.array<?xf32>>) bounds(%4) -> !fir.ref<!fir.array<?xf32>> {name = "arr", structured = false} acc.enter_data dataOperands(%6 : !fir.ref<!fir.array<?xf32>>) ``` After the current change, it looks like: ``` func.func @_QPsub(%arg0: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "arr"}) { ... %1:2 = hlfir.declare %arg0 dummy_scope %0 {uniq_name = "_QFsubEarr"} : (!fir.box<!fir.array<?xf32>>, !fir.dscope) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>) %2 = acc.copyin var(%1#0 : !fir.box<!fir.array<?xf32>>) -> !fir.box<!fir.array<?xf32>> {name = "arr", structured = false} acc.enter_data dataOperands(%2 : !fir.box<!fir.array<?xf32>>) ``` Restoring the old behavior can be done with following command line options: `--openacc-unwrap-fir-box=true --openacc-generate-default-bounds=true`
2025-02-04 08:08:16 -08:00
! 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
[flang][acc] Improve acc lowering around fir.box and arrays (#125600) The current implementation of OpenACC lowering includes explicit expansion of following cases: - Creation of `acc.bounds` operations for all arrays, including those whose dimensions are captured in the type (eg `!fir.array<100xf32>`) - Expansion of box types by only putting the box's address in the data clause. The address was extracted with a `fir.box_addr` operation and the bounds were filled with `fir.box_dims` operation. However, with the creation of the new type interface `MappableType`, the idea is that specific type-based semantics can now be used. This also really simplifies representation in the IR. Consider the following example: ``` subroutine sub(arr) real :: arr(:) !$acc enter data copyin(arr) end subroutine ``` Before the current PR, the relevant acc dialect IR looked like: ``` func.func @_QPsub(%arg0: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "arr"}) { ... %1:2 = hlfir.declare %arg0 dummy_scope %0 {uniq_name = "_QFsubEarr"} : (!fir.box<!fir.array<?xf32>>, !fir.dscope) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>) %c1 = arith.constant 1 : index %c0 = arith.constant 0 : index %2:3 = fir.box_dims %1#0, %c0 : (!fir.box<!fir.array<?xf32>>, index) -> (index, index, index) %c0_0 = arith.constant 0 : index %3 = arith.subi %2#1, %c1 : index %4 = acc.bounds lowerbound(%c0_0 : index) upperbound(%3 : index) extent(%2#1 : index) stride(%2#2 : index) startIdx(%c1 : index) {strideInBytes = true} %5 = fir.box_addr %1#0 : (!fir.box<!fir.array<?xf32>>) -> !fir.ref<!fir.array<?xf32>> %6 = acc.copyin varPtr(%5 : !fir.ref<!fir.array<?xf32>>) bounds(%4) -> !fir.ref<!fir.array<?xf32>> {name = "arr", structured = false} acc.enter_data dataOperands(%6 : !fir.ref<!fir.array<?xf32>>) ``` After the current change, it looks like: ``` func.func @_QPsub(%arg0: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "arr"}) { ... %1:2 = hlfir.declare %arg0 dummy_scope %0 {uniq_name = "_QFsubEarr"} : (!fir.box<!fir.array<?xf32>>, !fir.dscope) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>) %2 = acc.copyin var(%1#0 : !fir.box<!fir.array<?xf32>>) -> !fir.box<!fir.array<?xf32>> {name = "arr", structured = false} acc.enter_data dataOperands(%2 : !fir.box<!fir.array<?xf32>>) ``` Restoring the old behavior can be done with following command line options: `--openacc-unwrap-fir-box=true --openacc-generate-default-bounds=true`
2025-02-04 08:08:16 -08:00
! 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