[flang] Accept polymorphic component element in storage_size
[llvm-project.git] / flang / test / Lower / nullify-polymorphic.f90
blob4c905b8b9e519073938cdca012b99a5957745c5f
1 ! RUN: bbc -polymorphic-type -emit-fir %s -o - | FileCheck %s
3 module poly
4 type p1
5 integer :: a
6 integer :: b
7 contains
8 procedure, nopass :: proc1 => proc1_p1
9 end type
11 type, extends(p1) :: p2
12 integer :: c
13 contains
14 procedure, nopass :: proc1 => proc1_p2
15 end type
17 contains
19 subroutine proc1_p1()
20 print*, 'call proc1_p1'
21 end subroutine
23 subroutine proc1_p2()
24 print*, 'call proc1_p2'
25 end subroutine
27 subroutine test_nullify()
28 class(p1), pointer :: c
30 allocate(p2::c)
31 call c%proc1()
33 nullify(c) ! c dynamic type must be reset to p1
35 call c%proc1()
36 end subroutine
37 end module
39 program test
40 use poly
41 call test_nullify()
42 end
44 ! CHECK-LABEL: func.func @_QMpolyPtest_nullify()
45 ! CHECK: %[[C_DESC:.*]] = fir.alloca !fir.class<!fir.ptr<!fir.type<_QMpolyTp1{a:i32,b:i32}>>> {bindc_name = "c", uniq_name = "_QMpolyFtest_nullifyEc"}
46 ! CHECK: %{{.*}} = fir.call @_FortranAPointerAllocate(%{{.*}}, %{{.*}}, %{{.*}}, %{{.*}}, %{{.*}}) {{.*}}: (!fir.ref<!fir.box<none>>, i1, !fir.box<none>, !fir.ref<i8>, i32) -> i32
47 ! CHECK: %[[DECLARED_TYPE:.*]] = fir.address_of(@_QMpolyE.dt.p1) : !fir.ref<!fir.type<{{.*}}>>
48 ! CHECK: %[[C_DESC_CAST:.*]] = fir.convert %[[C_DESC]] : (!fir.ref<!fir.class<!fir.ptr<!fir.type<_QMpolyTp1{a:i32,b:i32}>>>>) -> !fir.ref<!fir.box<none>>
49 ! CHECK: %[[TYPE_DESC_CAST:.*]] = fir.convert %[[DECLARED_TYPE]] : (!fir.ref<!fir.type<{{.*}}>>) -> !fir.ref<none>
50 ! CHECK: %[[RANK:.*]] = arith.constant 0 : i32
51 ! CHECK: %[[CORANK:.*]] = arith.constant 0 : i32
52 ! CHECK: %{{.*}} = fir.call @_FortranAPointerNullifyDerived(%[[C_DESC_CAST]], %[[TYPE_DESC_CAST]], %[[RANK]], %[[CORANK]]) {{.*}}: (!fir.ref<!fir.box<none>>, !fir.ref<none>, i32, i32) -> none