
Prevent hlfir.declare output to be fir.box/class values with the heap/pointer attribute to ensure the runtime descriptor attributes are in line with the Fortran attributes for the entities being declared (only fir.ref<box/class> can be ALLOCATABLE/POINTERS). This fixes a bug where an associated entity inside a SELECT TYPE was being unexpectedly reallocated inside assign runtime because the selector was allocatable and this attribute was not properly removed when creating the descriptor for the associated entity (that does not inherit the ALLOCATABLE/POINTER attribute according to Fortran 2023 section 11.1.3.3).
33 lines
2.4 KiB
Fortran
33 lines
2.4 KiB
Fortran
! RUN: bbc -emit-hlfir -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.heap<!fir.array<?x!fir.type<_QMpolymorphic_expressions_typesTt{c:i32}>>>>, !fir.shift<1>) -> (!fir.class<!fir.array<?x!fir.type<_QMpolymorphic_expressions_typesTt{c:i32}>>>, !fir.class<!fir.array<?x!fir.type<_QMpolymorphic_expressions_typesTt{c:i32}>>>)
|
|
! CHECK: %[[VAL_22:.*]] = arith.constant true
|
|
! CHECK: %[[VAL_23:.*]] = hlfir.as_expr %[[VAL_21]]#0 move %[[VAL_22]] : (!fir.class<!fir.array<?x!fir.type<_QMpolymorphic_expressions_typesTt{c:i32}>>>, i1) -> !hlfir.expr<?x!fir.type<_QMpolymorphic_expressions_typesTt{c:i32}>?>
|
|
! CHECK: %[[VAL_24:.*]] = arith.constant 0 : index
|
|
! CHECK: %[[VAL_25:.*]]:3 = fir.box_dims %[[VAL_21]]#0, %[[VAL_24]] : (!fir.class<!fir.array<?x!fir.type<_QMpolymorphic_expressions_typesTt{c:i32}>>>, 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<?x!fir.type<_QMpolymorphic_expressions_typesTt{c:i32}>?>, !fir.shape<1>) -> (!fir.class<!fir.array<?x!fir.type<_QMpolymorphic_expressions_typesTt{c:i32}>>>, !fir.class<!fir.array<?x!fir.type<_QMpolymorphic_expressions_typesTt{c:i32}>>>, i1)
|
|
! CHECK: fir.call @_QPcallee(%[[VAL_27]]#0) fastmath<contract> : (!fir.class<!fir.array<?x!fir.type<_QMpolymorphic_expressions_typesTt{c:i32}>>>) -> ()
|
|
! CHECK: hlfir.end_associate %[[VAL_27]]#0, %[[VAL_27]]#2 : !fir.class<!fir.array<?x!fir.type<_QMpolymorphic_expressions_typesTt{c:i32}>>>, i1
|
|
! CHECK: hlfir.destroy %[[VAL_23]] : !hlfir.expr<?x!fir.type<_QMpolymorphic_expressions_typesTt{c:i32}>?>
|