! RUN: bbc -polymorphic-type -emit-hlfir %s -o - | FileCheck %s module poly type p1 integer :: a integer :: b contains procedure, nopass :: proc1 => proc1_p1 end type type, extends(p1) :: p2 integer :: c contains procedure, nopass :: proc1 => proc1_p2 end type contains subroutine proc1_p1() print*, 'call proc1_p1' end subroutine subroutine proc1_p2() print*, 'call proc1_p2' end subroutine subroutine test_nullify() class(p1), pointer :: c allocate(p2::c) call c%proc1() nullify(c) ! c dynamic type must be reset to p1 call c%proc1() end subroutine end module program test use poly call test_nullify() end ! CHECK-LABEL: func.func @_QMpolyPtest_nullify() ! CHECK: %[[C_DESC:.*]] = fir.alloca !fir.class>> {bindc_name = "c", uniq_name = "_QMpolyFtest_nullifyEc"} ! CHECK: %[[C_DESC_DECL:.*]]:2 = hlfir.declare %28 {fortran_attrs = #fir.var_attrs, uniq_name = "_QMpolyFtest_nullifyEc"} : (!fir.ref>>>) -> (!fir.ref>>>, !fir.ref>>>) ! CHECK: %{{.*}} = fir.call @_FortranAPointerAllocate(%{{.*}}, %{{.*}}, %{{.*}}, %{{.*}}, %{{.*}}) {{.*}}: (!fir.ref>, i1, !fir.box, !fir.ref, i32) -> i32 ! CHECK: %[[DECLARED_TYPE_DESC:.*]] = fir.type_desc !fir.type<_QMpolyTp1{a:i32,b:i32}> ! CHECK: %[[C_DESC_CAST:.*]] = fir.convert %[[C_DESC_DECL]]#1 : (!fir.ref>>>) -> !fir.ref> ! CHECK: %[[TYPE_DESC_CAST:.*]] = fir.convert %[[DECLARED_TYPE_DESC]] : (!fir.tdesc>) -> !fir.ref ! CHECK: %[[RANK:.*]] = arith.constant 0 : i32 ! CHECK: %[[CORANK:.*]] = arith.constant 0 : i32 ! CHECK: %{{.*}} = fir.call @_FortranAPointerNullifyDerived(%[[C_DESC_CAST]], %[[TYPE_DESC_CAST]], %[[RANK]], %[[CORANK]]) {{.*}}: (!fir.ref>, !fir.ref, i32, i32) -> none