! This test checks lowering of OpenACC reduction clause. ! RUN: bbc -fopenacc -emit-hlfir %s -o - | FileCheck %s --check-prefixes=CHECK ! CHECK-LABEL: acc.reduction.recipe @reduction_max_ref_UxUxf32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: index, %[[ARG2:.*]]: index): ! CHECK: %[[CST:.*]] = arith.constant -1.401300e-45 : f32 ! CHECK: %[[SHAPE:.*]] = fir.shape %arg1, %arg2 : (index, index) -> !fir.shape<2> ! CHECK: %[[TEMP:.*]] = fir.alloca !fir.array, %arg1, %arg2 ! CHECK: %[[DECL:.*]]:2 = hlfir.declare %[[TEMP]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref>, !fir.shape<2>) -> (!fir.box>, !fir.ref>) ! CHECK: hlfir.assign %[[CST]] to %[[DECL]]#0 : f32, !fir.box> ! CHECK: acc.yield %[[DECL]]#0 : !fir.box> ! CHECK: } combiner { ! CHECK: ^bb0(%[[V1:.*]]: !fir.ref>, %[[V2:.*]]: !fir.ref>, %[[LB0:.*]]: index, %[[UB0:.*]]: index, %[[STEP0:.*]]: index, %[[LB1:.*]]: index, %[[UB1:.*]]: index, %[[STEP1:.*]]: index): ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}}, %{{.*}} : (index, index) -> !fir.shape<2> ! CHECK: %[[DECL_V1:.*]]:2 = hlfir.declare %[[V1]](%[[SHAPE]]) {uniq_name = ""} : (!fir.ref>, !fir.shape<2>) -> (!fir.box>, !fir.ref>) ! CHECK: %[[DECL_V2:.*]]:2 = hlfir.declare %[[V2]](%[[SHAPE]]) {uniq_name = ""} : (!fir.ref>, !fir.shape<2>) -> (!fir.box>, !fir.ref>) ! CHECK: %[[DES_V1:.*]] = hlfir.designate %[[DECL_V1]]#0 (%arg2:%arg3:%arg4, %arg5:%arg6:%arg7) shape %10 : (!fir.box>, index, index, index, index, index, index, !fir.shape<2>) -> !fir.box> ! CHECK: %[[DES_V2:.*]] = hlfir.designate %[[DECL_V2]]#0 (%arg2:%arg3:%arg4, %arg5:%arg6:%arg7) shape %10 : (!fir.box>, index, index, index, index, index, index, !fir.shape<2>) -> !fir.box> ! CHECK: %[[ELEMENTAL:.*]] = hlfir.elemental %[[SHAPE]] unordered : (!fir.shape<2>) -> !hlfir.expr { ! CHECK: ^bb0(%[[ARG0:.*]]: index, %[[ARG1:.*]]: index): ! CHECK: %[[D1:.*]] = hlfir.designate %13 (%[[ARG0]], %[[ARG1]]) : (!fir.box>, index, index) -> !fir.ref ! CHECK: %[[D2:.*]] = hlfir.designate %14 (%[[ARG0]], %[[ARG1]]) : (!fir.box>, index, index) -> !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[D1]] : !fir.ref ! CHECK: %[[LOAD2:.*]] = fir.load %[[D2]] : !fir.ref ! CHECK: %[[CMP:.*]] = arith.cmpf ogt, %[[LOAD1]], %[[LOAD2]] {{.*}} : f32 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD1]], %[[LOAD2]] : f32 ! CHECK: hlfir.yield_element %[[SELECT]] : f32 ! CHECK: } ! CHECK: hlfir.assign %[[ELEMENTAL]] to %[[DECL_V1]]#0 : !hlfir.expr, !fir.box> ! CHECK: acc.yield %[[V1]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_max_box_ptr_Uxf32 : !fir.box>> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.box>>): ! CHECK: } combiner { ! CHECK: ^bb0(%{{.*}}: !fir.box>>, %{{.*}}: !fir.box>>, %{{.*}}: index, %{{.*}}: index, %{{.*}}: index): ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_max_box_heap_Uxf32 : !fir.box>> reduction_operator init { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box>>): ! CHECK: %[[CST:.*]] = arith.constant -1.401300e-45 : f32 ! CHECK: %[[C0:.*]] = arith.constant 0 : index ! CHECK: %[[BOX_DIMS:.*]]:3 = fir.box_dims %[[ARG0]], %[[C0]] : (!fir.box>>, index) -> (index, index, index) ! CHECK: %[[SHAPE:.*]] = fir.shape %[[BOX_DIMS]]#1 : (index) -> !fir.shape<1> ! CHECK: %[[TEMP:.*]] = fir.allocmem !fir.array, %[[BOX_DIMS]]#1 {bindc_name = ".tmp", uniq_name = ""} ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %2(%1) {uniq_name = ".tmp"} : (!fir.heap>, !fir.shape<1>) -> (!fir.box>, !fir.heap>) ! CHECK: hlfir.assign %[[CST]] to %[[DECLARE]]#0 : f32, !fir.box> ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.box> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box>>, %[[ARG1:.*]]: !fir.box>>, %[[ARG2:.*]]: index, %[[ARG3:.*]]: index, %[[ARG4:.*]]: index): ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1> ! CHECK: %[[DES_V1:.*]] = hlfir.designate %[[ARG0]] (%[[ARG2]]:%[[ARG3]]:%[[ARG4]]) shape %[[SHAPE]] : (!fir.box>>, index, index, index, !fir.shape<1>) -> !fir.box>> ! CHECK: %[[DES_V2:.*]] = hlfir.designate %[[ARG1]] (%[[ARG2]]:%[[ARG3]]:%[[ARG4]]) shape %[[SHAPE]] : (!fir.box>>, index, index, index, !fir.shape<1>) -> !fir.box>> ! CHECK: %[[ELEMENTAL:.*]] = hlfir.elemental %[[SHAPE]] unordered : (!fir.shape<1>) -> !hlfir.expr { ! CHECK: ^bb0(%[[IV:.*]]: index): ! CHECK: %[[V1:.*]] = hlfir.designate %[[DES_V1]] (%[[IV]]) : (!fir.box>>, index) -> !fir.ref ! CHECK: %[[V2:.*]] = hlfir.designate %[[DES_V2]] (%[[IV]]) : (!fir.box>>, index) -> !fir.ref ! CHECK: %[[LOAD_V1:.*]] = fir.load %[[V1]] : !fir.ref ! CHECK: %[[LOAD_V2:.*]] = fir.load %[[V2]] : !fir.ref ! CHECK: %[[CMP:.*]] = arith.cmpf ogt, %[[LOAD_V1]], %[[LOAD_V2]] {{.*}} : f32 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD_V1]], %[[LOAD_V2]] : f32 ! CHECK: hlfir.yield_element %[[SELECT]] : f32 ! CHECK: } ! CHECK: hlfir.assign %[[ELEMENTAL]] to %[[ARG0]] : !hlfir.expr, !fir.box>> ! CHECK: acc.yield %[[ARG0]] : !fir.box>> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_add_section_lb1.ub3_box_Uxi32 : !fir.box> reduction_operator init { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box>): ! CHECK: %[[BOX_DIMS:.*]]:3 = fir.box_dims %[[ARG0]], %c0{{.*}} : (!fir.box>, index) -> (index, index, index) ! CHECK: %[[SHAPE:.*]] = fir.shape %[[BOX_DIMS]]#1 : (index) -> !fir.shape<1> ! CHECK: %[[TEMP:.*]] = fir.allocmem !fir.array, %0#1 {bindc_name = ".tmp", uniq_name = ""} ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[TEMP]](%[[SHAPE]]) {uniq_name = ".tmp"} : (!fir.heap>, !fir.shape<1>) -> (!fir.box>, !fir.heap>) ! CHECK: hlfir.assign %c0{{.*}} to %[[DECLARE]]#0 : i32, !fir.box> ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.box> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box>, %[[ARG1:.*]]: !fir.box>): ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1> ! CHECK: %[[DES1:.*]] = hlfir.designate %[[ARG0]] shape %[[SHAPE]] : (!fir.box>, !fir.shape<1>) -> !fir.box> ! CHECK: %[[DES2:.*]] = hlfir.designate %[[ARG1]] shape %[[SHAPE]] : (!fir.box>, !fir.shape<1>) -> !fir.box> ! CHECK: %[[ELEMENTAL:.*]] = hlfir.elemental %[[SHAPE]] unordered : (!fir.shape<1>) -> !hlfir.expr { ! CHECK: ^bb0(%[[IV:.*]]: index): ! CHECK: %[[DES_V1:.*]] = hlfir.designate %[[DES1]] (%[[IV]]) : (!fir.box>, index) -> !fir.ref ! CHECK: %[[DES_V2:.*]] = hlfir.designate %[[DES2]] (%[[IV]]) : (!fir.box>, index) -> !fir.ref ! CHECK: %[[LOAD_V1:.*]] = fir.load %[[DES_V1]] : !fir.ref ! CHECK: %[[LOAD_V2:.*]] = fir.load %[[DES_V2]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.addi %[[LOAD_V1]], %[[LOAD_V2]] : i32 ! CHECK: hlfir.yield_element %[[COMBINED]] : i32 ! CHECK: } ! CHECK: hlfir.assign %[[ELEMENTAL]] to %[[ARG0]] : !hlfir.expr, !fir.box> ! CHECK: acc.yield %[[ARG0]] : !fir.box> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_max_box_Uxf32 : !fir.box> reduction_operator init { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box>): ! CHECK: %[[INIT_VALUE:.*]] = arith.constant -1.401300e-45 : f32 ! CHECK: %[[C0:.*]] = arith.constant 0 : index ! CHECK: %[[BOX_DIMS:.*]]:3 = fir.box_dims %[[ARG0]], %[[C0]] : (!fir.box>, index) -> (index, index, index) ! CHECK: %[[SHAPE:.*]] = fir.shape %[[BOX_DIMS]]#1 : (index) -> !fir.shape<1> ! CHECK: %[[TEMP:.*]] = fir.allocmem !fir.array, %0#1 {bindc_name = ".tmp", uniq_name = ""} ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[TEMP]](%[[SHAPE]]) {uniq_name = ".tmp"} : (!fir.heap>, !fir.shape<1>) -> (!fir.box>, !fir.heap>) ! CHECK: hlfir.assign %[[INIT_VALUE]] to %[[DECLARE]]#0 : f32, !fir.box> ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.box> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box>, %[[ARG1:.*]]: !fir.box> ! CHECK: %[[LEFT:.*]] = hlfir.designate %[[ARG0]] (%{{.*}}:%{{.*}}:%{{.*}}) shape %{{.*}} : (!fir.box>, index, index, index, !fir.shape<1>) -> !fir.box> ! CHECK: %[[RIGHT:.*]] = hlfir.designate %[[ARG1]] (%{{.*}}:%{{.*}}:%{{.*}}) shape %{{.*}} : (!fir.box>, index, index, index, !fir.shape<1>) -> !fir.box> ! CHECK: %[[ELEMENTAL:.*]] = hlfir.elemental %{{.*}} unordered : (!fir.shape<1>) -> !hlfir.expr { ! CHECK: ^bb0(%{{.*}}: index): ! CHECK: %[[DES_V1:.*]] = hlfir.designate %[[LEFT]] (%{{.*}}) : (!fir.box>, index) -> !fir.ref ! CHECK: %[[DES_V2:.*]] = hlfir.designate %[[RIGHT]] (%{{.*}}) : (!fir.box>, index) -> !fir.ref ! CHECK: %[[LOAD_V1:.*]] = fir.load %[[DES_V1]] : !fir.ref ! CHECK: %[[LOAD_V2:.*]] = fir.load %[[DES_V2]] : !fir.ref ! CHECK: %[[CMPF:.*]] = arith.cmpf ogt, %[[LOAD_V1]], %[[LOAD_V2]] {{.*}} : f32 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMPF]], %[[LOAD_V1]], %[[LOAD_V2]] : f32 ! CHECK: hlfir.yield_element %[[SELECT]] : f32 ! CHECK: } ! CHECK: hlfir.assign %[[ELEMENTAL]] to %[[ARG0]] : !hlfir.expr, !fir.box> ! CHECK: acc.yield %[[ARG0]] : !fir.box> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_add_box_Uxi32 : !fir.box> reduction_operator init { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box>): ! CHECK: %[[INIT_VALUE:.*]] = arith.constant 0 : i32 ! CHECK: %[[C0:.*]] = arith.constant 0 : index ! CHECK: %[[BOX_DIMS:.*]]:3 = fir.box_dims %[[ARG0]], %[[C0]] : (!fir.box>, index) -> (index, index, index) ! CHECK: %[[SHAPE:.*]] = fir.shape %[[BOX_DIMS]]#1 : (index) -> !fir.shape<1> ! CHECK: %[[TEMP:.*]] = fir.allocmem !fir.array, %[[BOX_DIMS]]#1 {bindc_name = ".tmp", uniq_name = ""} ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[TEMP]](%[[SHAPE]]) {uniq_name = ".tmp"} : (!fir.heap>, !fir.shape<1>) -> (!fir.box>, !fir.heap>) ! CHECK: hlfir.assign %[[INIT_VALUE]] to %[[DECLARE]]#0 : i32, !fir.box> ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.box> ! CHECK: } combiner { ! CHECK: ^bb0(%[[V1:.*]]: !fir.box>, %[[V2:.*]]: !fir.box> ! CHECK: %[[LEFT:.*]] = hlfir.designate %[[ARG0]] (%{{.*}}:%{{.*}}:%{{.*}}) shape %{{.*}} : (!fir.box>, index, index, index, !fir.shape<1>) -> !fir.box> ! CHECK: %[[RIGHT:.*]] = hlfir.designate %[[ARG1]] (%{{.*}}:%{{.*}}:%{{.*}}) shape %{{.*}} : (!fir.box>, index, index, index, !fir.shape<1>) -> !fir.box> ! CHECK: %[[ELEMENTAL:.*]] = hlfir.elemental %{{.*}} unordered : (!fir.shape<1>) -> !hlfir.expr { ! CHECK: ^bb0(%{{.*}}: index): ! CHECK: %[[DES_V1:.*]] = hlfir.designate %[[LEFT]] (%{{.*}}) : (!fir.box>, index) -> !fir.ref ! CHECK: %[[DES_V2:.*]] = hlfir.designate %[[RIGHT]] (%{{.*}}) : (!fir.box>, index) -> !fir.ref ! CHECK: %[[LOAD_V1:.*]] = fir.load %[[DES_V1]] : !fir.ref ! CHECK: %[[LOAD_V2:.*]] = fir.load %[[DES_V2]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.addi %[[LOAD_V1]], %[[LOAD_V2]] : i32 ! CHECK: hlfir.yield_element %[[COMBINED]] : i32 ! CHECK: } ! CHECK: hlfir.assign %[[ELEMENTAL]] to %[[V1]] : !hlfir.expr, !fir.box> ! CHECK: acc.yield %arg0 : !fir.box> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_mul_ref_z32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[REAL:.*]] = arith.constant 1.000000e+00 : f32 ! CHECK: %[[IMAG:.*]] = arith.constant 0.000000e+00 : f32 ! CHECK: %[[UNDEF:.*]] = fir.undefined !fir.complex<4> ! CHECK: %[[UNDEF1:.*]] = fir.insert_value %[[UNDEF]], %[[REAL]], [0 : index] : (!fir.complex<4>, f32) -> !fir.complex<4> ! CHECK: %[[UNDEF2:.*]] = fir.insert_value %[[UNDEF1]], %[[IMAG]], [1 : index] : (!fir.complex<4>, f32) -> !fir.complex<4> ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.complex<4> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref>) -> (!fir.ref>, !fir.ref>) ! CHECK: fir.store %[[UNDEF2]] to %[[DECLARE]]#0 : !fir.ref> ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref> ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref> ! CHECK: %[[COMBINED:.*]] = fir.mulc %[[LOAD0]], %[[LOAD1]] {fastmath = #arith.fastmath} : !fir.complex<4> ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref> ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_add_ref_z32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[REAL:.*]] = arith.constant 0.000000e+00 : f32 ! CHECK: %[[IMAG:.*]] = arith.constant 0.000000e+00 : f32 ! CHECK: %[[UNDEF:.*]] = fir.undefined !fir.complex<4> ! CHECK: %[[UNDEF1:.*]] = fir.insert_value %[[UNDEF]], %[[REAL]], [0 : index] : (!fir.complex<4>, f32) -> !fir.complex<4> ! CHECK: %[[UNDEF2:.*]] = fir.insert_value %[[UNDEF1]], %[[IMAG]], [1 : index] : (!fir.complex<4>, f32) -> !fir.complex<4> ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.complex<4> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref>) -> (!fir.ref>, !fir.ref>) ! CHECK: fir.store %[[UNDEF2]] to %[[DECLARE]]#0 : !fir.ref> ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref> ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref> ! CHECK: %[[COMBINED:.*]] = fir.addc %[[LOAD0]], %[[LOAD1]] {fastmath = #arith.fastmath} : !fir.complex<4> ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref> ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_neqv_ref_l32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[CST:.*]] = arith.constant false ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.logical<4> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref>) -> (!fir.ref>, !fir.ref>) ! CHECK: %[[CONVERT:.*]] = fir.convert %[[CST]] : (i1) -> !fir.logical<4> ! CHECK: fir.store %[[CONVERT]] to %[[DECLARE]]#0 : !fir.ref> ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref> ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref> ! CHECK: %[[CONV0:.*]] = fir.convert %[[LOAD0]] : (!fir.logical<4>) -> i1 ! CHECK: %[[CONV1:.*]] = fir.convert %[[LOAD1]] : (!fir.logical<4>) -> i1 ! CHECK: %[[CMP:.*]] = arith.cmpi ne, %[[CONV0]], %[[CONV1]] : i1 ! CHECK: %[[CMP_CONV:.*]] = fir.convert %[[CMP]] : (i1) -> !fir.logical<4> ! CHECK: fir.store %[[CMP_CONV]] to %[[ARG0]] : !fir.ref> ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_eqv_ref_l32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[CST:.*]] = arith.constant true ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.logical<4> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref>) -> (!fir.ref>, !fir.ref>) ! CHECK: %[[CONVERT:.*]] = fir.convert %[[CST]] : (i1) -> !fir.logical<4> ! CHECK: fir.store %[[CONVERT]] to %[[DECLARE]]#0 : !fir.ref> ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref> ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref> ! CHECK: %[[CONV0:.*]] = fir.convert %[[LOAD0]] : (!fir.logical<4>) -> i1 ! CHECK: %[[CONV1:.*]] = fir.convert %[[LOAD1]] : (!fir.logical<4>) -> i1 ! CHECK: %[[CMP:.*]] = arith.cmpi eq, %[[CONV0]], %[[CONV1]] : i1 ! CHECK: %[[CMP_CONV:.*]] = fir.convert %[[CMP]] : (i1) -> !fir.logical<4> ! CHECK: fir.store %[[CMP_CONV]] to %[[ARG0]] : !fir.ref> ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_lor_ref_l32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[CST:.*]] = arith.constant false ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.logical<4> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref>) -> (!fir.ref>, !fir.ref>) ! CHECK: %[[CONVERT:.*]] = fir.convert %[[CST]] : (i1) -> !fir.logical<4> ! CHECK: fir.store %[[CONVERT]] to %[[DECLARE]]#0 : !fir.ref> ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref> ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref> ! CHECK: %[[CONV0:.*]] = fir.convert %[[LOAD0]] : (!fir.logical<4>) -> i1 ! CHECK: %[[CONV1:.*]] = fir.convert %[[LOAD1]] : (!fir.logical<4>) -> i1 ! CHECK: %[[CMP:.*]] = arith.ori %[[CONV0]], %[[CONV1]] : i1 ! CHECK: %[[CMP_CONV:.*]] = fir.convert %[[CMP]] : (i1) -> !fir.logical<4> ! CHECK: fir.store %[[CMP_CONV]] to %[[ARG0]] : !fir.ref> ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_land_ref_l32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[CST:.*]] = arith.constant true ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.logical<4> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref>) -> (!fir.ref>, !fir.ref>) ! CHECK: %[[CONVERT:.*]] = fir.convert %[[CST]] : (i1) -> !fir.logical<4> ! CHECK: fir.store %[[CONVERT]] to %[[DECLARE]]#0 : !fir.ref> ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref> ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref> ! CHECK: %[[CONV0:.*]] = fir.convert %[[LOAD0]] : (!fir.logical<4>) -> i1 ! CHECK: %[[CONV1:.*]] = fir.convert %[[LOAD1]] : (!fir.logical<4>) -> i1 ! CHECK: %[[CMP:.*]] = arith.andi %[[CONV0]], %[[CONV1]] : i1 ! CHECK: %[[CMP_CONV:.*]] = fir.convert %[[CMP]] : (i1) -> !fir.logical<4> ! CHECK: fir.store %[[CMP_CONV]] to %[[ARG0]] : !fir.ref> ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_xor_ref_i32 : !fir.ref reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref): ! CHECK: %[[CST:.*]] = arith.constant 0 : i32 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32 ! CHECK: %[[DECLARE]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref) -> (!fir.ref, !fir.ref) ! CHECK: fir.store %[[CST]] to %[[DECLARE]]#0 : !fir.ref ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref, %[[ARG1:.*]]: !fir.ref): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.xori %[[LOAD0]], %[[LOAD1]] : i32 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref ! CHECK: acc.yield %[[ARG0]] : !fir.ref ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_ior_ref_i32 : !fir.ref reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref): ! CHECK: %[[CST:.*]] = arith.constant 0 : i32 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref) -> (!fir.ref, !fir.ref) ! CHECK: fir.store %[[CST]] to %[[DECLARE:.*]]#0 : !fir.ref ! CHECK: acc.yield %[[DECLARE:.*]]#0 : !fir.ref ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref, %[[ARG1:.*]]: !fir.ref): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.ori %[[LOAD0]], %[[LOAD1]] : i32 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref ! CHECK: acc.yield %[[ARG0]] : !fir.ref ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_iand_ref_i32 : !fir.ref reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref): ! CHECK: %[[CST:.*]] = arith.constant -1 : i32 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref) -> (!fir.ref, !fir.ref) ! CHECK: fir.store %[[CST]] to %[[DECLARE]]#0 : !fir.ref ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref, %[[ARG1:.*]]: !fir.ref): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.andi %[[LOAD0]], %[[LOAD1]] : i32 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref ! CHECK: acc.yield %[[ARG0]] : !fir.ref ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_max_section_ext100_ref_100xf32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[INIT:.*]] = arith.constant -1.401300e-45 : f32 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1> ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100xf32> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref>, !fir.shape<1>) -> (!fir.ref>, !fir.ref>) ! CHECK: %[[LB:.*]] = arith.constant 0 : index ! CHECK: %[[UB:.*]] = arith.constant 99 : index ! CHECK: %[[STEP:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV:.*]] = %[[LB]] to %[[UB]] step %[[STEP]] { ! CHECK: %[[COORD:.*]] = fir.coordinate_of %[[DECLARE]]#0, %[[IV]] : (!fir.ref>, index) -> !fir.ref ! CHECK: fir.store %[[INIT]] to %[[COORD]] : !fir.ref ! CHECK: } ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LB0:.*]] = arith.constant 0 : index ! CHECK: %[[UB0:.*]] = arith.constant 99 : index ! CHECK: %[[STEP0:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV0:.*]] = %[[LB0]] to %[[UB0]] step %[[STEP0]] { ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV0]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV0]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref ! CHECK: %[[CMP:.*]] = arith.cmpf ogt, %[[LOAD1]], %[[LOAD2]] {{.*}} : f32 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD1]], %[[LOAD2]] : f32 ! CHECK: fir.store %[[SELECT]] to %[[COORD1]] : !fir.ref ! CHECK: } ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_max_ref_f32 : !fir.ref reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref): ! CHECK: %[[INIT:.*]] = arith.constant -1.401300e-45 : f32 ! CHECK: %[[ALLOCA:.*]] = fir.alloca f32 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %0 {uniq_name = "acc.reduction.init"} : (!fir.ref) -> (!fir.ref, !fir.ref) ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref, %[[ARG1:.*]]: !fir.ref): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref ! CHECK: %[[CMP:.*]] = arith.cmpf ogt, %[[LOAD0]], %[[LOAD1]] {{.*}} : f32 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD0]], %[[LOAD1]] : f32 ! CHECK: fir.store %[[SELECT]] to %[[ARG0]] : !fir.ref ! CHECK: acc.yield %[[ARG0]] : !fir.ref ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_max_section_ext100xext10_ref_100x10xi32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%arg0: !fir.ref>): ! CHECK: %[[INIT:.*]] = arith.constant -2147483648 : i32 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}}, %{{.*}} : (index, index) -> !fir.shape<2> ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100x10xi32> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref>, !fir.shape<2>) -> (!fir.ref>, !fir.ref>) ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LB0:.*]] = arith.constant 0 : index ! CHECK: %[[UB0:.*]] = arith.constant 9 : index ! CHECK: %[[STEP0:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV0:.*]] = %[[LB0]] to %[[UB0]] step %[[STEP0]] { ! CHECK: %[[LB1:.*]] = arith.constant 0 : index ! CHECK: %[[UB1:.*]] = arith.constant 99 : index ! CHECK: %[[STEP1:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV1:.*]] = %[[LB1]] to %[[UB1]] step %[[STEP1]] { ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0:.*]], %[[IV0]], %[[IV1]] : (!fir.ref>, index, index) -> !fir.ref ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1:.*]], %[[IV0]], %[[IV1]] : (!fir.ref>, index, index) -> !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref ! CHECK: %[[CMP:.*]] = arith.cmpi sgt, %[[LOAD1]], %[[LOAD2]] : i32 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD1]], %[[LOAD2]] : i32 ! CHECK: fir.store %[[SELECT]] to %[[COORD1]] : !fir.ref ! CHECK: } ! CHECK: } ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_max_ref_i32 : !fir.ref reduction_operator init { ! CHECK: ^bb0(%arg0: !fir.ref): ! CHECK: %[[INIT:.*]] = arith.constant -2147483648 : i32 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref) -> (!fir.ref, !fir.ref) ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref, %[[ARG1:.*]]: !fir.ref): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref ! CHECK: %[[CMP:.*]] = arith.cmpi sgt, %[[LOAD0]], %[[LOAD1]] : i32 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD0]], %[[LOAD1]] : i32 ! CHECK: fir.store %[[SELECT]] to %[[ARG0]] : !fir.ref ! CHECK: acc.yield %[[ARG0]] : !fir.ref ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_min_section_ext100xext10_ref_100x10xf32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[INIT:.*]] = arith.constant 3.40282347E+38 : f32 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}}, %{{.*}} : (index, index) -> !fir.shape<2> ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100x10xf32> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref>, !fir.shape<2>) -> (!fir.ref>, !fir.ref>) ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LB0:.*]] = arith.constant 0 : index ! CHECK: %[[UB0:.*]] = arith.constant 9 : index ! CHECK: %[[STEP0:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV0:.*]] = %[[LB0]] to %[[UB0]] step %[[STEP0]] { ! CHECK: %[[LB1:.*]] = arith.constant 0 : index ! CHECK: %[[UB1:.*]] = arith.constant 99 : index ! CHECK: %[[STEP1:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV1:.*]] = %[[LB1]] to %[[UB1]] step %[[STEP1]] { ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV0]], %[[IV1]] : (!fir.ref>, index, index) -> !fir.ref ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV0]], %[[IV1]] : (!fir.ref>, index, index) -> !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref ! CHECK: %[[CMP:.*]] = arith.cmpf olt, %[[LOAD1]], %[[LOAD2]] {{.*}} : f32 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD1]], %[[LOAD2]] : f32 ! CHECK: fir.store %[[SELECT]] to %[[COORD1]] : !fir.ref ! CHECK: } ! CHECK: } ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_min_ref_f32 : !fir.ref reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref): ! CHECK: %[[INIT:.*]] = arith.constant 3.40282347E+38 : f32 ! CHECK: %[[ALLOCA:.*]] = fir.alloca f32 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref) -> (!fir.ref, !fir.ref) ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref, %[[ARG1:.*]]: !fir.ref): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref ! CHECK: %[[CMP:.*]] = arith.cmpf olt, %[[LOAD0]], %[[LOAD1]] {{.*}} : f32 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD0]], %[[LOAD1]] : f32 ! CHECK: fir.store %[[SELECT]] to %[[ARG0]] : !fir.ref ! CHECK: acc.yield %[[ARG0]] : !fir.ref ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_min_section_ext100_ref_100xi32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[INIT:.*]] = arith.constant 2147483647 : i32 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1> ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100xi32> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref>, !fir.shape<1>) -> (!fir.ref>, !fir.ref>) ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LB0:.*]] = arith.constant 0 : index ! CHECK: %[[UB0:.*]] = arith.constant 99 : index ! CHECK: %[[STEP0:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV0:.*]] = %[[LB0]] to %[[UB0]] step %[[STEP0]] { ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV0]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV0]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref ! CHECK: %[[CMP:.*]] = arith.cmpi slt, %[[LOAD1]], %[[LOAD2]] : i32 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD1]], %[[LOAD2]] : i32 ! CHECK: fir.store %[[SELECT]] to %[[COORD1]] : !fir.ref ! CHECK: } ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_min_ref_i32 : !fir.ref reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref): ! CHECK: %[[INIT:.*]] = arith.constant 2147483647 : i32 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref) -> (!fir.ref, !fir.ref) ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref, %[[ARG1:.*]]: !fir.ref): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref ! CHECK: %[[CMP:.*]] = arith.cmpi slt, %[[LOAD0]], %[[LOAD1]] : i32 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD0]], %[[LOAD1]] : i32 ! CHECK: fir.store %[[SELECT]] to %[[ARG0]] : !fir.ref ! CHECK: acc.yield %[[ARG0]] : !fir.ref ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_mul_ref_f32 : !fir.ref reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref): ! CHECK: %[[INIT:.*]] = arith.constant 1.000000e+00 : f32 ! CHECK: %[[ALLOCA:.*]] = fir.alloca f32 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref) -> (!fir.ref, !fir.ref) ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref, %[[ARG1:.*]]: !fir.ref): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.mulf %[[LOAD0]], %[[LOAD1]] fastmath : f32 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref ! CHECK: acc.yield %[[ARG0]] : !fir.ref ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_mul_section_ext100_ref_100xi32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[INIT:.*]] = arith.constant 1 : i32 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1> ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100xi32> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref>, !fir.shape<1>) -> (!fir.ref>, !fir.ref>) ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LB:.*]] = arith.constant 0 : index ! CHECK: %[[UB:.*]] = arith.constant 99 : index ! CHECK: %[[STEP:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV:.*]] = %[[LB]] to %[[UB]] step %[[STEP]] { ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.muli %[[LOAD1]], %[[LOAD2]] : i32 ! CHECK: fir.store %[[COMBINED]] to %[[COORD1]] : !fir.ref ! CHECK: } ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_mul_ref_i32 : !fir.ref reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref): ! CHECK: %[[INIT:.*]] = arith.constant 1 : i32 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref) -> (!fir.ref, !fir.ref) ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref, %[[ARG1:.*]]: !fir.ref): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.muli %[[LOAD0]], %[[LOAD1]] : i32 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref ! CHECK: acc.yield %[[ARG0]] : !fir.ref ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_add_section_ext100_ref_100xf32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[INIT:.*]] = arith.constant 0.000000e+00 : f32 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1> ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100xf32> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref>, !fir.shape<1>) -> (!fir.ref>, !fir.ref>) ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LB:.*]] = arith.constant 0 : index ! CHECK: %[[UB:.*]] = arith.constant 99 : index ! CHECK: %[[STEP:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV:.*]] = %[[LB]] to %[[UB]] step %[[STEP]] { ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.addf %[[LOAD1]], %[[LOAD2]] fastmath : f32 ! CHECK: fir.store %[[COMBINED]] to %[[COORD1]] : !fir.ref ! CHECK: } ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_add_ref_f32 : !fir.ref reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref): ! CHECK: %[[INIT:.*]] = arith.constant 0.000000e+00 : f32 ! CHECK: %[[ALLOCA:.*]] = fir.alloca f32 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref) -> (!fir.ref, !fir.ref) ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref, %[[ARG1:.*]]: !fir.ref): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.addf %[[LOAD0]], %[[LOAD1]] fastmath : f32 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref ! CHECK: acc.yield %[[ARG0]] : !fir.ref ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_add_section_ext100xext10xext2_ref_100x10x2xi32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[INIT:.*]] = arith.constant 0 : i32 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}}, %{{.*}}, %{{.*}} : (index, index, index) -> !fir.shape<3> ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100x10x2xi32> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref>, !fir.shape<3>) -> (!fir.ref>, !fir.ref>) ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LB0:.*]] = arith.constant 0 : index ! CHECK: %[[UB0:.*]] = arith.constant 1 : index ! CHECK: %[[STEP0:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV0:.*]] = %[[LB0]] to %[[UB0]] step %[[STEP0]] { ! CHECK: %[[LB1:.*]] = arith.constant 0 : index ! CHECK: %[[UB1:.*]] = arith.constant 9 : index ! CHECK: %[[STEP1:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV1:.*]] = %[[LB1]] to %[[UB1]] step %[[STEP1]] { ! CHECK: %[[LB2:.*]] = arith.constant 0 : index ! CHECK: %[[UB2:.*]] = arith.constant 99 : index ! CHECK: %[[STEP2:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV2:.*]] = %[[LB2]] to %[[UB2]] step %[[STEP2]] { ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV0]], %[[IV1]], %[[IV2]] : (!fir.ref>, index, index, index) -> !fir.ref ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV0]], %[[IV1]], %[[IV2]] : (!fir.ref>, index, index, index) -> !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.addi %[[LOAD1]], %[[LOAD2]] : i32 ! CHECK: fir.store %[[COMBINED]] to %[[COORD1]] : !fir.ref ! CHECK: } ! CHECK: } ! CHECK: } ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_add_section_ext100xext10_ref_100x10xi32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[INIT:.*]] = arith.constant 0 : i32 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}}, %{{.*}} : (index, index) -> !fir.shape<2> ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100x10xi32> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref>, !fir.shape<2>) -> (!fir.ref>, !fir.ref>) ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LB0:.*]] = arith.constant 0 : index ! CHECK: %[[UB0:.*]] = arith.constant 9 : index ! CHECK: %[[STEP0:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV0:.*]] = %[[LB0]] to %[[UB0]] step %[[STEP0]] { ! CHECK: %[[LB1:.*]] = arith.constant 0 : index ! CHECK: %[[UB1:.*]] = arith.constant 99 : index ! CHECK: %[[STEP1:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV1:.*]] = %[[LB1]] to %[[UB1]] step %[[STEP1]] { ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV0]], %[[IV1]] : (!fir.ref>, index, index) -> !fir.ref ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV0]], %[[IV1]] : (!fir.ref>, index, index) -> !fir.ref ! CHECK: %[[LOAD1]] = fir.load %[[COORD1]] : !fir.ref ! CHECK: %[[LOAD2]] = fir.load %[[COORD2]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.addi %[[LOAD1]], %[[LOAD2]] : i32 ! CHECK: fir.store %[[COMBINED]] to %[[COORD1]] : !fir.ref ! CHECK: } ! CHECK: } ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_add_section_ext100_ref_100xi32 : !fir.ref> reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref>): ! CHECK: %[[INIT:.*]] = arith.constant 0 : i32 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1> ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100xi32> ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref>, !fir.shape<1>) -> (!fir.ref>, !fir.ref>) ! HFLIR: acc.yield %[[DECLARE]]#0 : !fir.ref> ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref>, %[[ARG1:.*]]: !fir.ref>): ! CHECK: %[[LB:.*]] = arith.constant 0 : index ! CHECK: %[[UB:.*]] = arith.constant 99 : index ! CHECK: %[[STEP:.*]] = arith.constant 1 : index ! CHECK: fir.do_loop %[[IV:.*]] = %[[LB]] to %[[UB]] step %[[STEP]] { ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV]] : (!fir.ref>, index) -> !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.addi %[[LOAD1]], %[[LOAD2]] : i32 ! CHECK: fir.store %[[COMBINED]] to %[[COORD1]] : !fir.ref ! CHECK: } ! CHECK: acc.yield %[[ARG0]] : !fir.ref> ! CHECK: } ! CHECK-LABEL: acc.reduction.recipe @reduction_add_ref_i32 : !fir.ref reduction_operator init { ! CHECK: ^bb0(%{{.*}}: !fir.ref): ! CHECK: %[[INIT:.*]] = arith.constant 0 : i32 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref) -> (!fir.ref, !fir.ref) ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref ! CHECK: } combiner { ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref, %[[ARG1:.*]]: !fir.ref): ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref ! CHECK: %[[COMBINED:.*]] = arith.addi %[[LOAD0]], %[[LOAD1]] : i32 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref ! CHECK: acc.yield %[[ARG0]] : !fir.ref ! CHECK: } subroutine acc_reduction_add_int(a, b) integer :: a(100) integer :: i, b !$acc loop reduction(+:b) do i = 1, 100 b = b + a(i) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_int( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref {fir.bindc_name = "b"}) ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]] ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#1 : !fir.ref) -> !fir.ref {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_add_ref_i32 -> %[[RED_B]] : !fir.ref) subroutine acc_reduction_add_int_array_1d(a, b) integer :: a(100) integer :: i, b(100) !$acc loop reduction(+:b) do i = 1, 100 b(i) = b(i) + a(i) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_int_array_1d( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref> {fir.bindc_name = "b"}) ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]] ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#1 : !fir.ref>) bounds(%{{.*}}) -> !fir.ref> {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_add_section_ext100_ref_100xi32 -> %[[RED_B]] : !fir.ref>) subroutine acc_reduction_add_int_array_2d(a, b) integer :: a(100, 10), b(100, 10) integer :: i, j !$acc loop collapse(2) reduction(+:b) do i = 1, 100 do j = 1, 10 b(i, j) = b(i, j) + a(i, j) end do end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_int_array_2d( ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref> {fir.bindc_name = "a"}, %[[ARG1:.*]]: !fir.ref> {fir.bindc_name = "b"}) { ! CHECK: %[[DECLARG1:.*]]:2 = hlfir.declare %[[ARG1]] ! CHECK: %[[RED_ARG1:.*]] = acc.reduction varPtr(%[[DECLARG1]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_add_section_ext100xext10_ref_100x10xi32 -> %[[RED_ARG1]] : !fir.ref>) ! CHECK: } attributes {collapse = [2]{{.*}} subroutine acc_reduction_add_int_array_3d(a, b) integer :: a(100, 10, 2), b(100, 10, 2) integer :: i, j, k !$acc loop collapse(3) reduction(+:b) do i = 1, 100 do j = 1, 10 do k = 1, 2 b(i, j, k) = b(i, j, k) + a(i, j, k) end do end do end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_int_array_3d( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[ARG1:.*]]: !fir.ref> {fir.bindc_name = "b"}) ! CHECK: %[[DECLARG1:.*]]:2 = hlfir.declare %[[ARG1]] ! CHECK: %[[RED_ARG1:.*]] = acc.reduction varPtr(%[[DECLARG1]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}, %{{.*}}) -> !fir.ref> {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_add_section_ext100xext10xext2_ref_100x10x2xi32 -> %[[RED_ARG1]] : !fir.ref>) ! CHECK: } attributes {collapse = [3]{{.*}} subroutine acc_reduction_add_float(a, b) real :: a(100), b integer :: i !$acc loop reduction(+:b) do i = 1, 100 b = b + a(i) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_float( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref {fir.bindc_name = "b"}) ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]] ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#1 : !fir.ref) -> !fir.ref {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_add_ref_f32 -> %[[RED_B]] : !fir.ref) subroutine acc_reduction_add_float_array_1d(a, b) real :: a(100), b(100) integer :: i !$acc loop reduction(+:b) do i = 1, 100 b(i) = b(i) + a(i) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_float_array_1d( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref> {fir.bindc_name = "b"}) ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]] ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#1 : !fir.ref>) bounds(%{{.*}}) -> !fir.ref> {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_add_section_ext100_ref_100xf32 -> %[[RED_B]] : !fir.ref>) subroutine acc_reduction_mul_int(a, b) integer :: a(100) integer :: i, b !$acc loop reduction(*:b) do i = 1, 100 b = b * a(i) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_mul_int( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref {fir.bindc_name = "b"}) ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]] ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#1 : !fir.ref) -> !fir.ref {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_mul_ref_i32 -> %[[RED_B]] : !fir.ref) subroutine acc_reduction_mul_int_array_1d(a, b) integer :: a(100) integer :: i, b(100) !$acc loop reduction(*:b) do i = 1, 100 b(i) = b(i) * a(i) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_mul_int_array_1d( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref> {fir.bindc_name = "b"}) ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]] ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#1 : !fir.ref>) bounds(%{{.*}}) -> !fir.ref> {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_mul_section_ext100_ref_100xi32 -> %[[RED_B]] : !fir.ref>) subroutine acc_reduction_mul_float(a, b) real :: a(100), b integer :: i !$acc loop reduction(*:b) do i = 1, 100 b = b * a(i) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_mul_float( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref {fir.bindc_name = "b"}) ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]] ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#1 : !fir.ref) -> !fir.ref {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_mul_ref_f32 -> %[[RED_B]] : !fir.ref) subroutine acc_reduction_mul_float_array_1d(a, b) real :: a(100), b(100) integer :: i !$acc loop reduction(*:b) do i = 1, 100 b(i) = b(i) * a(i) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_mul_float_array_1d( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref> {fir.bindc_name = "b"}) ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]] ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#1 : !fir.ref>) bounds(%{{.*}}) -> !fir.ref> {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_mul_section_ext100_ref_100xf32 -> %[[RED_B]] : !fir.ref>) subroutine acc_reduction_min_int(a, b) integer :: a(100) integer :: i, b !$acc loop reduction(min:b) do i = 1, 100 b = min(b, a(i)) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_min_int( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref {fir.bindc_name = "b"}) ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]] ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#1 : !fir.ref) -> !fir.ref {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_min_ref_i32 -> %[[RED_B]] : !fir.ref) subroutine acc_reduction_min_int_array_1d(a, b) integer :: a(100), b(100) integer :: i !$acc loop reduction(min:b) do i = 1, 100 b(i) = min(b(i), a(i)) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_min_int_array_1d( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[ARG1:.*]]: !fir.ref> {fir.bindc_name = "b"}) ! CHECK: %[[DECLARG1:.*]]:2 = hlfir.declare %[[ARG1]] ! CHECK: %[[RED_ARG1:.*]] = acc.reduction varPtr(%[[DECLARG1]]#1 : !fir.ref>) bounds(%{{.*}}) -> !fir.ref> {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_min_section_ext100_ref_100xi32 -> %[[RED_ARG1]] : !fir.ref>) subroutine acc_reduction_min_float(a, b) real :: a(100), b integer :: i !$acc loop reduction(min:b) do i = 1, 100 b = min(b, a(i)) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_min_float( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref {fir.bindc_name = "b"}) ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]] ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#1 : !fir.ref) -> !fir.ref {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_min_ref_f32 -> %[[RED_B]] : !fir.ref) subroutine acc_reduction_min_float_array2d(a, b) real :: a(100, 10), b(100, 10) integer :: i, j !$acc loop reduction(min:b) collapse(2) do i = 1, 100 do j = 1, 10 b(i, j) = min(b(i, j), a(i, j)) end do end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_min_float_array2d( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[ARG1:.*]]: !fir.ref> {fir.bindc_name = "b"}) ! CHECK: %[[DECLARG1:.*]]:2 = hlfir.declare %[[ARG1]] ! CHECK: %[[RED_ARG1:.*]] = acc.reduction varPtr(%[[DECLARG1]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_min_section_ext100xext10_ref_100x10xf32 -> %[[RED_ARG1]] : !fir.ref>) ! CHECK: attributes {collapse = [2]{{.*}} subroutine acc_reduction_max_int(a, b) integer :: a(100) integer :: i, b !$acc loop reduction(max:b) do i = 1, 100 b = max(b, a(i)) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_max_int( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref {fir.bindc_name = "b"}) ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]] ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#1 : !fir.ref) -> !fir.ref {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_max_ref_i32 -> %[[RED_B]] : !fir.ref) subroutine acc_reduction_max_int_array2d(a, b) integer :: a(100, 10), b(100, 10) integer :: i, j !$acc loop reduction(max:b) collapse(2) do i = 1, 100 do j = 1, 10 b(i, j) = max(b(i, j), a(i, j)) end do end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_max_int_array2d( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[ARG1:.*]]: !fir.ref> {fir.bindc_name = "b"}) ! CHECK: %[[DECLARG1:.*]]:2 = hlfir.declare %[[ARG1]] ! CHECK: %[[RED_ARG1:.*]] = acc.reduction varPtr(%[[DECLARG1]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_max_section_ext100xext10_ref_100x10xi32 -> %[[RED_ARG1]] : !fir.ref>) subroutine acc_reduction_max_float(a, b) real :: a(100), b integer :: i !$acc loop reduction(max:b) do i = 1, 100 b = max(b, a(i)) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_max_float( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref {fir.bindc_name = "b"}) ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]] ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#1 : !fir.ref) -> !fir.ref {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_max_ref_f32 -> %[[RED_B]] : !fir.ref) subroutine acc_reduction_max_float_array1d(a, b) real :: a(100), b(100) integer :: i !$acc loop reduction(max:b) do i = 1, 100 b(i) = max(b(i), a(i)) end do end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_max_float_array1d( ! CHECK-SAME: %{{.*}}: !fir.ref> {fir.bindc_name = "a"}, %[[ARG1:.*]]: !fir.ref> {fir.bindc_name = "b"}) ! CHECK: %[[DECLARG1:.*]]:2 = hlfir.declare %[[ARG1]] ! CHECK: %[[RED_ARG1:.*]] = acc.reduction varPtr(%[[DECLARG1]]#1 : !fir.ref>) bounds(%{{.*}}) -> !fir.ref> {name = "b"} ! CHECK: acc.loop {{.*}} reduction(@reduction_max_section_ext100_ref_100xf32 -> %[[RED_ARG1]] : !fir.ref>) subroutine acc_reduction_iand() integer :: i !$acc parallel reduction(iand:i) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_iand() ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref) -> !fir.ref {name = "i"} ! CHECK: acc.parallel reduction(@reduction_iand_ref_i32 -> %[[RED]] : !fir.ref) subroutine acc_reduction_ior() integer :: i !$acc parallel reduction(ior:i) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_ior() ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref) -> !fir.ref {name = "i"} ! CHECK: acc.parallel reduction(@reduction_ior_ref_i32 -> %[[RED]] : !fir.ref) subroutine acc_reduction_ieor() integer :: i !$acc parallel reduction(ieor:i) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_ieor() ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref) -> !fir.ref {name = "i"} ! CHECK: acc.parallel reduction(@reduction_xor_ref_i32 -> %[[RED]] : !fir.ref) subroutine acc_reduction_and() logical :: l !$acc parallel reduction(.and.:l) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_and() ! CHECK: %[[L:.*]] = fir.alloca !fir.logical<4> {bindc_name = "l", uniq_name = "_QFacc_reduction_andEl"} ! CHECK: %[[DECLL:.*]]:2 = hlfir.declare %[[L]] ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[DECLL]]#1 : !fir.ref>) -> !fir.ref> {name = "l"} ! CHECK: acc.parallel reduction(@reduction_land_ref_l32 -> %[[RED]] : !fir.ref>) subroutine acc_reduction_or() logical :: l !$acc parallel reduction(.or.:l) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_or() ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref>) -> !fir.ref> {name = "l"} ! CHECK: acc.parallel reduction(@reduction_lor_ref_l32 -> %[[RED]] : !fir.ref>) subroutine acc_reduction_eqv() logical :: l !$acc parallel reduction(.eqv.:l) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_eqv() ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref>) -> !fir.ref> {name = "l"} ! CHECK: acc.parallel reduction(@reduction_eqv_ref_l32 -> %[[RED]] : !fir.ref>) subroutine acc_reduction_neqv() logical :: l !$acc parallel reduction(.neqv.:l) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_neqv() ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref>) -> !fir.ref> {name = "l"} ! CHECK: acc.parallel reduction(@reduction_neqv_ref_l32 -> %[[RED]] : !fir.ref>) subroutine acc_reduction_add_cmplx() complex :: c !$acc parallel reduction(+:c) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_cmplx() ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref>) -> !fir.ref> {name = "c"} ! CHECK: acc.parallel reduction(@reduction_add_ref_z32 -> %[[RED]] : !fir.ref>) subroutine acc_reduction_mul_cmplx() complex :: c !$acc parallel reduction(*:c) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_mul_cmplx() ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref>) -> !fir.ref> {name = "c"} ! CHECK: acc.parallel reduction(@reduction_mul_ref_z32 -> %[[RED]] : !fir.ref>) subroutine acc_reduction_add_alloc() integer, allocatable :: i allocate(i) !$acc parallel reduction(+:i) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_alloc() ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.box> {bindc_name = "i", uniq_name = "_QFacc_reduction_add_allocEi"} ! CHECK: %[[DECL:.*]]:2 = hlfir.declare %[[ALLOCA]] ! CHECK: %[[LOAD:.*]] = fir.load %[[DECL]]#1 : !fir.ref>> ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[LOAD]] : (!fir.box>) -> !fir.heap ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[BOX_ADDR]] : !fir.heap) -> !fir.heap {name = "i"} ! CHECK: acc.parallel reduction(@reduction_add_heap_i32 -> %[[RED]] : !fir.heap) subroutine acc_reduction_add_pointer(i) integer, pointer :: i !$acc parallel reduction(+:i) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_pointer( ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref>> {fir.bindc_name = "i"}) ! CHECK: %[[DECLARG0:.*]]:2 = hlfir.declare %[[ARG0]] ! CHECK: %[[LOAD:.*]] = fir.load %[[DECLARG0]]#1 : !fir.ref>> ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[LOAD]] : (!fir.box>) -> !fir.ptr ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[BOX_ADDR]] : !fir.ptr) -> !fir.ptr {name = "i"} ! CHECK: acc.parallel reduction(@reduction_add_ptr_i32 -> %[[RED]] : !fir.ptr) subroutine acc_reduction_add_static_slice(a) integer :: a(100) !$acc parallel reduction(+:a(11:20)) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_static_slice( ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref> {fir.bindc_name = "a"}) ! CHECK: %[[C100:.*]] = arith.constant 100 : index ! CHECK: %[[DECLARG0:.*]]:2 = hlfir.declare %[[ARG0]] ! CHECK: %[[C1:.*]] = arith.constant 1 : index ! CHECK: %[[LB:.*]] = arith.constant 10 : index ! CHECK: %[[UB:.*]] = arith.constant 19 : index ! CHECK: %[[BOUND:.*]] = acc.bounds lowerbound(%[[LB]] : index) upperbound(%[[UB]] : index) extent(%[[C100]] : index) stride(%[[C1]] : index) startIdx(%[[C1]] : index) ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[DECLARG0]]#1 : !fir.ref>) bounds(%[[BOUND]]) -> !fir.ref> {name = "a(11:20)"} ! CHECK: acc.parallel reduction(@reduction_add_section_lb10.ub19_ref_100xi32 -> %[[RED]] : !fir.ref>) subroutine acc_reduction_add_dynamic_extent_add(a) integer :: a(:) !$acc parallel reduction(+:a) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_dynamic_extent_add( ! CHECK-SAME: %[[ARG0:.*]]: !fir.box> {fir.bindc_name = "a"}) ! CHECK: %[[DECLARG0:.*]]:2 = hlfir.declare %[[ARG0]] ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref>) bounds(%{{.*}}) -> !fir.ref> {name = "a"} ! CHECK: acc.parallel reduction(@reduction_add_box_Uxi32 -> %[[RED:.*]] : !fir.ref>) subroutine acc_reduction_add_assumed_shape_max(a) real :: a(:) !$acc parallel reduction(max:a) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_assumed_shape_max( ! CHECK-SAME: %[[ARG0:.*]]: !fir.box> {fir.bindc_name = "a"}) ! CHECK: %[[DECLARG0:.*]]:2 = hlfir.declare %[[ARG0]] ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref>) bounds(%{{.*}}) -> !fir.ref> {name = "a"} ! CHECK: acc.parallel reduction(@reduction_max_box_Uxf32 -> %[[RED]] : !fir.ref>) { subroutine acc_reduction_add_dynamic_extent_add_with_section(a) integer :: a(:) !$acc parallel reduction(+:a(2:4)) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_dynamic_extent_add_with_section( ! CHECK-SAME: %[[ARG0:.*]]: !fir.box> {fir.bindc_name = "a"}) ! CHECK: %[[DECL:.*]]:2 = hlfir.declare %[[ARG0]] {uniq_name = "_QFacc_reduction_add_dynamic_extent_add_with_sectionEa"} : (!fir.box>) -> (!fir.box>, !fir.box>) ! CHECK: %[[BOUND:.*]] = acc.bounds lowerbound(%c1{{.*}} : index) upperbound(%c3{{.*}} : index) extent(%{{.*}}#1 : index) stride(%{{.*}}#2 : index) startIdx(%{{.*}} : index) {strideInBytes = true} ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[DECL]]#1 : (!fir.box>) -> !fir.ref> ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[BOX_ADDR]] : !fir.ref>) bounds(%[[BOUND]]) -> !fir.ref> {name = "a(2:4)"} ! CHECK: acc.parallel reduction(@reduction_add_section_lb1.ub3_box_Uxi32 -> %[[RED]] : !fir.ref>) subroutine acc_reduction_add_allocatable(a) real, allocatable :: a(:) !$acc parallel reduction(max:a) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_allocatable( ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref>>> {fir.bindc_name = "a"}) ! CHECK: %[[DECL:.*]]:2 = hlfir.declare %[[ARG0]] {fortran_attrs = #fir.var_attrs, uniq_name = "_QFacc_reduction_add_allocatableEa"} : (!fir.ref>>>) -> (!fir.ref>>>, !fir.ref>>>) ! CHECK: %[[BOX:.*]] = fir.load %[[DECL]]#1 : !fir.ref>>> ! CHECK: %[[BOUND:.*]] = acc.bounds lowerbound(%c0{{.*}} : index) upperbound(%{{.*}} : index) extent(%{{.*}}#1 : index) stride(%{{.*}}#2 : index) startIdx(%{{.*}}#0 : index) {strideInBytes = true} ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[BOX]] : (!fir.box>>) -> !fir.heap> ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[BOX_ADDR]] : !fir.heap>) bounds(%6) -> !fir.heap> {name = "a"} ! CHECK: acc.parallel reduction(@reduction_max_box_heap_Uxf32 -> %[[RED]] : !fir.heap>) subroutine acc_reduction_add_pointer_array(a) real, pointer :: a(:) !$acc parallel reduction(max:a) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_add_pointer_array( ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref>>> {fir.bindc_name = "a"}) ! CHECK: %[[DECL:.*]]:2 = hlfir.declare %[[ARG0]] {fortran_attrs = #fir.var_attrs, uniq_name = "_QFacc_reduction_add_pointer_arrayEa"} : (!fir.ref>>>) -> (!fir.ref>>>, !fir.ref>>>) ! CHECK: %[[BOX:.*]] = fir.load %[[DECL]]#1 : !fir.ref>>> ! CHECK: %[[BOUND:.*]] = acc.bounds lowerbound(%c0{{.*}} : index) upperbound(%{{.*}} : index) extent(%{{.*}}#1 : index) stride(%{{.*}}#2 : index) startIdx(%{{.*}}#0 : index) {strideInBytes = true} ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[BOX]] : (!fir.box>>) -> !fir.ptr> ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[BOX_ADDR]] : !fir.ptr>) bounds(%[[BOUND]]) -> !fir.ptr> {name = "a"} ! CHECK: acc.parallel reduction(@reduction_max_box_ptr_Uxf32 -> %[[RED]] : !fir.ptr>) subroutine acc_reduction_max_dynamic_extent_max(a, n) integer :: n real :: a(n, n) !$acc parallel reduction(max:a) !$acc end parallel end subroutine ! CHECK-LABEL: func.func @_QPacc_reduction_max_dynamic_extent_max( ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref> {fir.bindc_name = "a"}, %{{.*}}: !fir.ref {fir.bindc_name = "n"}) ! CHECK: %[[DECL_A:.*]]:2 = hlfir.declare %[[ARG0]](%{{.*}}) {uniq_name = "_QFacc_reduction_max_dynamic_extent_maxEa"} : (!fir.ref>, !fir.shape<2>) -> (!fir.box>, !fir.ref>) ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[DECL_A]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {name = "a"} ! CHECK: acc.parallel reduction(@reduction_max_ref_UxUxf32 -> %[[RED]] : !fir.ref>)