xref: /llvm-project/flang/test/Lower/variable-inquiries.f90 (revision f35f863a88f83332bef9605ef4cfe4f05c066efb)
1! Test property inquiries on variables
2! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
3
4module inquired
5  real(8), allocatable :: a(:)
6end module
7
8! CHECK-LABEL: @_QPissue844()
9subroutine issue844()
10  use inquired
11  ! Verify that evaluate::DescriptorInquiry are made using the symbol mapped
12  ! in lowering (the use associated one, and not directly the ultimate
13  ! symbol).
14
15  ! CHECK: %[[a:.*]] = fir.address_of(@_QMinquiredEa) : !fir.ref<!fir.box<!fir.heap<!fir.array<?xf64>>>>
16  ! CHECK: %[[box_load:.*]] = fir.load %[[a]] : !fir.ref<!fir.box<!fir.heap<!fir.array<?xf64>>>>
17  ! CHECK: %[[dim:.*]]:3 = fir.box_dims %[[box_load]], %c0{{.*}} : (!fir.box<!fir.heap<!fir.array<?xf64>>>, index) -> (index, index, index)
18  ! CHECK: %[[cast:.*]] = fir.convert %[[dim]]#1 : (index) -> i64
19  ! CHECK: fir.call @_FortranAioOutputInteger64(%{{.*}}, %[[cast]]) {{.*}}: (!fir.ref<i8>, i64) -> i1
20  print *, size(a, kind=8)
21end subroutine
22