[flang] Accept polymorphic component element in storage_size
[llvm-project.git] / flang / test / Lower / Intrinsics / ubound01.f90
blob797accb0ac689d158a09f82ca413937645203c04
1 ! RUN: bbc -emit-fir %s -o - | FileCheck %s
3 ! Check that assumed shape lower bounds are applied before passing the
4 ! descriptor to the runtime call.
6 real, target :: a(10:20,99:100)
7 call s2(a,17,-100)
8 contains
9 subroutine show(bounds)
10 integer(8) :: bounds(:)
11 print *, bounds
12 end subroutine
13 subroutine s2(a,n,n2)
14 Real a(n:,n2:)
15 call show(ubound(a, kind=8))
16 End Subroutine
17 end
19 ! CHECK-LABEL: func.func @_QFPs2
20 ! CHECK-SAME: %[[ARG0:.*]]: !fir.box<!fir.array<?x?xf32>>
21 ! CHECK: %[[BOX:.*]] = fir.rebox %[[ARG0]](%{{.*}}) : (!fir.box<!fir.array<?x?xf32>>, !fir.shift<2>) -> !fir.box<!fir.array<?x?xf32>>
22 ! CHECK: %[[BOX_NONE:.*]] = fir.convert %[[BOX]] : (!fir.box<!fir.array<?x?xf32>>) -> !fir.box<none>
23 ! CHECK: %{{.*}} = fir.call @_FortranAUbound(%{{.*}}, %[[BOX_NONE]], %{{.*}}, %{{.*}}, %{{.*}}) {{.*}}: (!fir.ref<!fir.box<none>>, !fir.box<none>, i32, !fir.ref<i8>, i32) -> none