! This test checks lowering of OpenACC data bounds operation. ! RUN: bbc -fopenacc -emit-hlfir %s -o - | FileCheck %s module openacc_bounds type t1 integer, pointer, dimension(:) :: array_comp end type type t2 integer, dimension(10) :: array_comp end type type t3 integer, allocatable, dimension(:) :: array_comp end type contains subroutine acc_derived_type_component_pointer_array() type(t1) :: d !$acc enter data create(d%array_comp) end subroutine ! CHECK-LABEL: func.func @_QMopenacc_boundsPacc_derived_type_component_pointer_array() { ! CHECK: %[[D:.*]] = fir.alloca !fir.type<_QMopenacc_boundsTt1{array_comp:!fir.box>>}> {bindc_name = "d", uniq_name = "_QMopenacc_boundsFacc_derived_type_component_pointer_arrayEd"} ! CHECK: %[[DECL_D:.*]]:2 = hlfir.declare %[[D]] {uniq_name = "_QMopenacc_boundsFacc_derived_type_component_pointer_arrayEd"} : (!fir.ref>>}>>) -> (!fir.ref>>}>>, !fir.ref>>}>>) ! CHECK: %[[COORD:.*]] = hlfir.designate %[[DECL_D]]#0{"array_comp"} {fortran_attrs = #fir.var_attrs} : (!fir.ref>>}>>) -> !fir.ref>>> ! CHECK: %[[LOAD:.*]] = fir.load %[[COORD]] : !fir.ref>>> ! CHECK: %[[BOX_DIMS0:.*]]:3 = fir.box_dims %[[LOAD]], %c0{{.*}} : (!fir.box>>, index) -> (index, index, index) ! CHECK: %[[C1:.*]] = arith.constant 1 : index ! CHECK: %[[BOX_DIMS1:.*]]:3 = fir.box_dims %[[LOAD]], %c0{{.*}} : (!fir.box>>, index) -> (index, index, index) ! CHECK: %[[UB:.*]] = arith.subi %[[BOX_DIMS1]]#1, %[[C1]] : index ! CHECK: %[[BOUND:.*]] = acc.bounds lowerbound(%c0{{.*}} : index) upperbound(%[[UB]] : index) extent(%[[BOX_DIMS1]]#1 : index) stride(%[[BOX_DIMS1]]#2 : index) startIdx(%[[BOX_DIMS0]]#0 : index) {strideInBytes = true} ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[LOAD]] : (!fir.box>>) -> !fir.ptr> ! CHECK: %[[CREATE:.*]] = acc.create varPtr(%[[BOX_ADDR]] : !fir.ptr>) bounds(%[[BOUND]]) -> !fir.ptr> {name = "d%array_comp", structured = false} ! CHECK: acc.enter_data dataOperands(%[[CREATE]] : !fir.ptr>) ! CHECK: return ! CHECK: } subroutine acc_derived_type_component_array() type(t2) :: d !$acc enter data create(d%array_comp) end subroutine ! CHECK-LABEL: func.func @_QMopenacc_boundsPacc_derived_type_component_array() ! CHECK: %[[D:.*]] = fir.alloca !fir.type<_QMopenacc_boundsTt2{array_comp:!fir.array<10xi32>}> {bindc_name = "d", uniq_name = "_QMopenacc_boundsFacc_derived_type_component_arrayEd"} ! CHECK: %[[DECL_D:.*]]:2 = hlfir.declare %[[D]] {uniq_name = "_QMopenacc_boundsFacc_derived_type_component_arrayEd"} : (!fir.ref}>>) -> (!fir.ref}>>, !fir.ref}>>) ! CHECK: %[[C10:.*]] = arith.constant 10 : index ! CHECK: %[[SHAPE:.*]] = fir.shape %[[C10]] : (index) -> !fir.shape<1> ! CHECK: %[[COORD:.*]] = hlfir.designate %[[DECL_D]]#0{"array_comp"} shape %[[SHAPE]] : (!fir.ref}>>, !fir.shape<1>) -> !fir.ref> ! CHECK: %[[C1:.*]] = arith.constant 1 : index ! CHECK: %[[C0:.*]] = arith.constant 0 : index ! CHECK: %[[UB:.*]] = arith.subi %[[C10]], %[[C1]] : index ! CHECK: %[[BOUND:.*]] = acc.bounds lowerbound(%[[C0]] : index) upperbound(%[[UB]] : index) extent(%[[C10]] : index) stride(%[[C1]] : index) startIdx(%[[C1]] : index) ! CHECK: %[[CREATE:.*]] = acc.create varPtr(%[[COORD]] : !fir.ref>) bounds(%[[BOUND]]) -> !fir.ref> {name = "d%array_comp", structured = false} ! CHECK: acc.enter_data dataOperands(%[[CREATE]] : !fir.ref>) ! CHECK: return ! CHECK: } subroutine acc_derived_type_component_allocatable_array() type(t3) :: d !$acc enter data create(d%array_comp) end subroutine ! CHECK-LABEL: func.func @_QMopenacc_boundsPacc_derived_type_component_allocatable_array() { ! CHECK: %[[D:.*]] = fir.alloca !fir.type<_QMopenacc_boundsTt3{array_comp:!fir.box>>}> {bindc_name = "d", uniq_name = "_QMopenacc_boundsFacc_derived_type_component_allocatable_arrayEd"} ! CHECK: %[[DECL_D:.*]]:2 = hlfir.declare %[[D]] {uniq_name = "_QMopenacc_boundsFacc_derived_type_component_allocatable_arrayEd"} : (!fir.ref>>}>>) -> (!fir.ref>>}>>, !fir.ref>>}>>) ! CHECK: %[[COORD:.*]] = hlfir.designate %[[DECL_D]]#0{"array_comp"} {fortran_attrs = #fir.var_attrs} : (!fir.ref>>}>>) -> !fir.ref>>> ! CHECK: %[[LOAD:.*]] = fir.load %[[COORD]] : !fir.ref>>> ! CHECK: %[[BOX_DIMS0:.*]]:3 = fir.box_dims %[[LOAD]], %c0{{.*}} : (!fir.box>>, index) -> (index, index, index) ! CHECK: %[[C1:.*]] = arith.constant 1 : index ! CHECK: %[[BOX_DIMS1:.*]]:3 = fir.box_dims %[[LOAD]], %c0{{.*}} : (!fir.box>>, index) -> (index, index, index) ! CHECK: %[[UB:.*]] = arith.subi %[[BOX_DIMS1]]#1, %[[C1]] : index ! CHECK: %[[BOUND:.*]] = acc.bounds lowerbound(%c0{{.*}} : index) upperbound(%[[UB]] : index) extent(%[[BOX_DIMS1]]#1 : index) stride(%[[BOX_DIMS1]]#2 : index) startIdx(%[[BOX_DIMS0]]#0 : index) {strideInBytes = true} ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[LOAD]] : (!fir.box>>) -> !fir.heap> ! CHECK: %[[CREATE:.*]] = acc.create varPtr(%[[BOX_ADDR]] : !fir.heap>) bounds(%[[BOUND]]) -> !fir.heap> {name = "d%array_comp", structured = false} ! CHECK: acc.enter_data dataOperands(%[[CREATE]] : !fir.heap>) ! CHECK: return ! CHECK: } subroutine acc_undefined_extent(a) real, dimension(1:*) :: a !$acc kernels present(a) !$acc end kernels end subroutine ! CHECK-LABEL: func.func @_QMopenacc_boundsPacc_undefined_extent( ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref> {fir.bindc_name = "a"}) { ! CHECK: %[[DECL_ARG0:.*]]:2 = hlfir.declare %[[ARG0]](%{{.*}}) {uniq_name = "_QMopenacc_boundsFacc_undefined_extentEa"} : (!fir.ref>, !fir.shape<1>) -> (!fir.box>, !fir.ref>) ! CHECK: %[[ONE:.*]] = arith.constant 1 : index ! CHECK: %[[ZERO:.*]] = arith.constant 0 : index ! CHECK: %[[BOUND:.*]] = acc.bounds lowerbound(%[[ZERO]] : index) upperbound(%[[ZERO]] : index) extent(%[[ZERO]] : index) stride(%[[ONE]] : index) startIdx(%[[ONE]] : index) ! CHECK: %[[PRESENT:.*]] = acc.present varPtr(%[[DECL_ARG0]]#1 : !fir.ref>) bounds(%[[BOUND]]) -> !fir.ref> {name = "a"} ! CHECK: acc.kernels dataOperands(%[[PRESENT]] : !fir.ref>) subroutine acc_multi_strides(a) real, dimension(:,:,:) :: a !$acc kernels present(a) !$acc end kernels end subroutine ! CHECK-LABEL: func.func @_QMopenacc_boundsPacc_multi_strides( ! CHECK-SAME: %[[ARG0:.*]]: !fir.box> {fir.bindc_name = "a"}) ! CHECK: %[[DECL_ARG0:.*]]:2 = hlfir.declare %[[ARG0]] {uniq_name = "_QMopenacc_boundsFacc_multi_stridesEa"} : (!fir.box>) -> (!fir.box>, !fir.box>) ! CHECK: %[[BOX_DIMS0:.*]]:3 = fir.box_dims %[[DECL_ARG0]]#1, %c0{{.*}} : (!fir.box>, index) -> (index, index, index) ! CHECK: %[[BOUNDS0:.*]] = acc.bounds lowerbound(%{{.*}} : index) upperbound(%{{.*}} : index) extent(%[[BOX_DIMS0]]#1 : index) stride(%[[BOX_DIMS0]]#2 : index) startIdx(%{{.*}} : index) {strideInBytes = true} ! CHECK: %[[STRIDE1:.*]] = arith.muli %[[BOX_DIMS0]]#2, %[[BOX_DIMS0]]#1 : index ! CHECK: %[[BOX_DIMS1:.*]]:3 = fir.box_dims %[[DECL_ARG0]]#1, %c1{{.*}} : (!fir.box>, index) -> (index, index, index) ! CHECK: %[[BOUNDS1:.*]] = acc.bounds lowerbound(%{{.*}} : index) upperbound(%{{.*}} : index) extent(%[[BOX_DIMS1]]#1 : index) stride(%[[STRIDE1]] : index) startIdx(%{{.*}} : index) {strideInBytes = true} ! CHECK: %[[STRIDE2:.*]] = arith.muli %[[STRIDE1]], %[[BOX_DIMS1]]#1 : index ! CHECK: %[[BOX_DIMS2:.*]]:3 = fir.box_dims %[[DECL_ARG0]]#1, %c2{{.*}} : (!fir.box>, index) -> (index, index, index) ! CHECK: %[[BOUNDS2:.*]] = acc.bounds lowerbound(%{{.*}} : index) upperbound(%{{.*}} : index) extent(%[[BOX_DIMS2]]#1 : index) stride(%[[STRIDE2]] : index) startIdx(%{{.*}} : index) {strideInBytes = true} ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[DECL_ARG0]]#1 : (!fir.box>) -> !fir.ref> ! CHECK: %[[PRESENT:.*]] = acc.present varPtr(%[[BOX_ADDR]] : !fir.ref>) bounds(%29, %33, %37) -> !fir.ref> {name = "a"} ! CHECK: acc.kernels dataOperands(%[[PRESENT]] : !fir.ref>) { subroutine acc_optional_data(a) real, pointer, optional :: a(:) !$acc data attach(a) !$acc end data end subroutine ! CHECK-LABEL: func.func @_QMopenacc_boundsPacc_optional_data( ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref>>> {fir.bindc_name = "a", fir.optional}) { ! CHECK: %[[ARG0_DECL:.*]]:2 = hlfir.declare %arg0 {fortran_attrs = #fir.var_attrs, uniq_name = "_QMopenacc_boundsFacc_optional_dataEa"} : (!fir.ref>>>) -> (!fir.ref>>>, !fir.ref>>>) ! CHECK: %[[IS_PRESENT:.*]] = fir.is_present %[[ARG0_DECL]]#1 : (!fir.ref>>>) -> i1 ! CHECK: %[[BOX:.*]] = fir.if %[[IS_PRESENT]] -> (!fir.box>>) { ! CHECK: %[[LOAD:.*]] = fir.load %[[ARG0_DECL]]#1 : !fir.ref>>> ! CHECK: fir.result %[[LOAD]] : !fir.box>> ! CHECK: } else { ! CHECK: %[[ABSENT:.*]] = fir.absent !fir.box>> ! CHECK: fir.result %[[ABSENT]] : !fir.box>> ! CHECK: } ! CHECK: %[[RES:.*]]:5 = fir.if %[[IS_PRESENT]] -> (index, index, index, index, index) { ! CHECK: fir.result %{{.*}}, %{{.*}}, %{{.*}}, %{{.*}}, %{{.*}} : index, index, index, index, index ! CHECK: } else { ! CHECK: %[[C0:.*]] = arith.constant 0 : index ! CHECK: %[[CM1:.*]] = arith.constant -1 : index ! CHECK: fir.result %[[C0]], %[[CM1]], %[[C0]], %[[C0]], %[[C0]] : index, index, index, index, index ! CHECK: } ! CHECK: %[[BOUND:.*]] = acc.bounds lowerbound(%[[RES]]#0 : index) upperbound(%[[RES]]#1 : index) extent(%[[RES]]#2 : index) stride(%[[RES]]#3 : index) startIdx(%[[RES]]#4 : index) {strideInBytes = true} ! CHECK: %[[BOX_ADDR:.*]] = fir.if %[[IS_PRESENT]] -> (!fir.ptr>) { ! CHECK: %[[ADDR:.*]] = fir.box_addr %[[BOX]] : (!fir.box>>) -> !fir.ptr> ! CHECK: fir.result %[[ADDR]] : !fir.ptr> ! CHECK: } else { ! CHECK: %[[ABSENT:.*]] = fir.absent !fir.ptr> ! CHECK: fir.result %[[ABSENT]] : !fir.ptr> ! CHECK: } ! CHECK: %[[ATTACH:.*]] = acc.attach varPtr(%[[BOX_ADDR]] : !fir.ptr>) bounds(%[[BOUND]]) -> !fir.ptr> {name = "a"} ! CHECK: acc.data dataOperands(%[[ATTACH]] : !fir.ptr>) end module