[Clang] Make OpenMP offloading consistently use the bound architecture (#125135)
[llvm-project.git] / flang / test / Lower / HLFIR / issue80884.f90
blob725ed1982975bc97b3027963dc08b76b2b22c6f0
1 ! Test lowering of pointer remapping with component ref in the RHS.
2 ! RUN: bbc -emit-hlfir -o - %s -I nw | FileCheck %s
4 subroutine issue80884(p, targ)
5 type t0
6 real :: array(10, 10)
7 end type
8 type, extends(t0) :: t
9 end type
10 type(t), target :: targ
11 real, pointer :: p(:)
12 p(1:100) => targ%array
13 end subroutine
14 ! CHECK-LABEL: func.func @_QPissue80884(
15 ! CHECK: %[[VAL_2:.*]]:2 = hlfir.declare %{{.*}} {fortran_attrs = #fir.var_attrs<pointer>, uniq_name = "_QFissue80884Ep"} : (!fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>, !fir.dscope) -> (!fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>, !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>)
16 ! CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %{{.*}} {fortran_attrs = #fir.var_attrs<target>, uniq_name = "_QFissue80884Etarg"} : (!fir.ref<!fir.type<_QFissue80884Tt{t0:!fir.type<_QFissue80884Tt0{array:!fir.array<10x10xf32>}>}>>, !fir.dscope) -> (!fir.ref<!fir.type<_QFissue80884Tt{t0:!fir.type<_QFissue80884Tt0{array:!fir.array<10x10xf32>}>}>>, !fir.ref<!fir.type<_QFissue80884Tt{t0:!fir.type<_QFissue80884Tt0{array:!fir.array<10x10xf32>}>}>>)
17 ! CHECK: %[[VAL_4:.*]] = arith.constant 1 : i64
18 ! CHECK: %[[VAL_5:.*]] = arith.constant 100 : i64
19 ! CHECK: %[[VAL_6:.*]] = hlfir.designate %[[VAL_3]]#0{"t0"} : (!fir.ref<!fir.type<_QFissue80884Tt{t0:!fir.type<_QFissue80884Tt0{array:!fir.array<10x10xf32>}>}>>) -> !fir.ref<!fir.type<_QFissue80884Tt0{array:!fir.array<10x10xf32>}>>
20 ! CHECK: %[[VAL_7:.*]] = arith.constant 10 : index
21 ! CHECK: %[[VAL_8:.*]] = arith.constant 10 : index
22 ! CHECK: %[[VAL_9:.*]] = fir.shape %[[VAL_7]], %[[VAL_8]] : (index, index) -> !fir.shape<2>
23 ! CHECK: %[[VAL_10:.*]] = hlfir.designate %[[VAL_6]]{"array"} shape %[[VAL_9]] : (!fir.ref<!fir.type<_QFissue80884Tt0{array:!fir.array<10x10xf32>}>>, !fir.shape<2>) -> !fir.ref<!fir.array<10x10xf32>>
24 ! CHECK: %[[VAL_11:.*]] = arith.constant 1 : index
25 ! CHECK: %[[VAL_12:.*]] = fir.convert %[[VAL_4]] : (i64) -> index
26 ! CHECK: %[[VAL_13:.*]] = fir.convert %[[VAL_5]] : (i64) -> index
27 ! CHECK: %[[VAL_14:.*]] = arith.subi %[[VAL_13]], %[[VAL_12]] : index
28 ! CHECK: %[[VAL_15:.*]] = arith.addi %[[VAL_14]], %[[VAL_11]] : index
29 ! CHECK: %[[VAL_16:.*]] = fir.convert %[[VAL_10]] : (!fir.ref<!fir.array<10x10xf32>>) -> !fir.ref<!fir.array<?xf32>>
30 ! CHECK: %[[VAL_17:.*]] = fir.shape_shift %[[VAL_4]], %[[VAL_15]] : (i64, index) -> !fir.shapeshift<1>
31 ! CHECK: %[[VAL_18:.*]] = fir.embox %[[VAL_16]](%[[VAL_17]]) : (!fir.ref<!fir.array<?xf32>>, !fir.shapeshift<1>) -> !fir.box<!fir.ptr<!fir.array<?xf32>>>
32 ! CHECK: fir.store %[[VAL_18]] to %[[VAL_2]]#1 : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>