! RUN: bbc -emit-hlfir --polymorphic-type -o - %s -I nowhere | FileCheck %s module polymorphic_expressions_types type t integer c end type t end module polymorphic_expressions_types ! Test that proper polymorphic type used for hlfir.as_expr, ! and that hlfir.association has polymorphic result type. subroutine test1(a) use polymorphic_expressions_types interface subroutine callee(x) use polymorphic_expressions_types class(t) :: x(:) end subroutine callee end interface class(t), allocatable :: a call callee(spread(a, 1, 2)) end subroutine test1 ! CHECK-LABEL: func.func @_QPtest1( ! CHECK: %[[VAL_21:.*]]:2 = hlfir.declare %{{.*}}(%{{.*}}) {uniq_name = ".tmp.intrinsic_result"} : (!fir.class>>>, !fir.shift<1>) -> (!fir.class>>>, !fir.class>>>) ! CHECK: %[[VAL_22:.*]] = arith.constant true ! CHECK: %[[VAL_23:.*]] = hlfir.as_expr %[[VAL_21]]#0 move %[[VAL_22]] : (!fir.class>>>, i1) -> !hlfir.expr?> ! CHECK: %[[VAL_24:.*]] = arith.constant 0 : index ! CHECK: %[[VAL_25:.*]]:3 = fir.box_dims %[[VAL_21]]#0, %[[VAL_24]] : (!fir.class>>>, index) -> (index, index, index) ! CHECK: %[[VAL_26:.*]] = fir.shape %[[VAL_25]]#1 : (index) -> !fir.shape<1> ! CHECK: %[[VAL_27:.*]]:3 = hlfir.associate %[[VAL_23]](%[[VAL_26]]) {adapt.valuebyref} : (!hlfir.expr?>, !fir.shape<1>) -> (!fir.class>>>, !fir.class>>>, i1) ! CHECK: %[[VAL_28:.*]] = fir.rebox %[[VAL_27]]#0 : (!fir.class>>>) -> !fir.class>> ! CHECK: fir.call @_QPcallee(%[[VAL_28]]) fastmath : (!fir.class>>) -> () ! CHECK: hlfir.end_associate %[[VAL_27]]#0, %[[VAL_27]]#2 : !fir.class>>>, i1 ! CHECK: hlfir.destroy %[[VAL_23]] : !hlfir.expr?>