1! Test lowering of pointer disassociation 2! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s 3 4 5! ----------------------------------------------------------------------------- 6! Test p => NULL() 7! ----------------------------------------------------------------------------- 8 9 10! CHECK-LABEL: func @_QPtest_scalar( 11! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<f32>>>{{.*}}) 12subroutine test_scalar(p) 13 real, pointer :: p 14 ! CHECK: %[[null:.*]] = fir.zero_bits !fir.ptr<f32> 15 ! CHECK: %[[box:.*]] = fir.embox %[[null]] : (!fir.ptr<f32>) -> !fir.box<!fir.ptr<f32>> 16 ! CHECK: fir.store %[[box]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<f32>>> 17 p => NULL() 18end subroutine 19 20! CHECK-LABEL: func @_QPtest_scalar_char( 21! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<!fir.char<1,?>>>>{{.*}}) 22subroutine test_scalar_char(p) 23 character(:), pointer :: p 24 ! CHECK: %[[null:.*]] = fir.zero_bits !fir.ptr<!fir.char<1,?>> 25 ! CHECK: %[[box:.*]] = fir.embox %[[null]] typeparams %c0{{.*}} : (!fir.ptr<!fir.char<1,?>>, index) -> !fir.box<!fir.ptr<!fir.char<1,?>>> 26 ! CHECK: fir.store %[[box]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<!fir.char<1,?>>>> 27 p => NULL() 28end subroutine 29 30! CHECK-LABEL: func @_QPtest_array( 31! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>{{.*}}) 32subroutine test_array(p) 33 real, pointer :: p(:) 34 ! CHECK: %[[null:.*]] = fir.zero_bits !fir.ptr<!fir.array<?xf32>> 35 ! CHECK: %[[shape:.*]] = fir.shape %c0{{.*}} 36 ! CHECK: %[[box:.*]] = fir.embox %[[null]](%[[shape]]) : (!fir.ptr<!fir.array<?xf32>>, !fir.shape<1>) -> !fir.box<!fir.ptr<!fir.array<?xf32>>> 37 ! CHECK: fir.store %[[box]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>> 38 p => NULL() 39end subroutine 40 41! Test p(lb, ub) => NULL() which is none sens but is not illegal. 42! CHECK-LABEL: func @_QPtest_array_remap( 43! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>{{.*}}) 44subroutine test_array_remap(p) 45 real, pointer :: p(:) 46 ! CHECK: %[[null:.*]] = fir.zero_bits !fir.ptr<!fir.array<?xf32>> 47 ! CHECK: %[[shape:.*]] = fir.shape %c0{{.*}} 48 ! CHECK: %[[box:.*]] = fir.embox %[[null]](%[[shape]]) : (!fir.ptr<!fir.array<?xf32>>, !fir.shape<1>) -> !fir.box<!fir.ptr<!fir.array<?xf32>>> 49 ! CHECK: fir.store %[[box]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>> 50 p(10:20) => NULL() 51end subroutine 52 53! ----------------------------------------------------------------------------- 54! Test p => NULL(MOLD) 55! ----------------------------------------------------------------------------- 56 57! CHECK-LABEL: func @_QPtest_scalar_mold( 58! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<f32>>>{{[^,]*}}, 59subroutine test_scalar_mold(p, x) 60 real, pointer :: p, x 61 ! CHECK: %[[VAL_0:.*]] = fir.alloca !fir.box<!fir.ptr<f32>> 62 ! CHECK: %[[VAL_1:.*]] = fir.zero_bits !fir.ptr<f32> 63 ! CHECK: %[[VAL_2:.*]] = fir.embox %[[VAL_1]] : (!fir.ptr<f32>) -> !fir.box<!fir.ptr<f32>> 64 ! CHECK: fir.store %[[VAL_2]] to %[[VAL_0]] : !fir.ref<!fir.box<!fir.ptr<f32>>> 65 ! CHECK: %[[VAL_3:.*]] = fir.load %[[VAL_0]] : !fir.ref<!fir.box<!fir.ptr<f32>>> 66 ! CHECK: %[[VAL_4:.*]] = fir.box_addr %[[VAL_3]] : (!fir.box<!fir.ptr<f32>>) -> !fir.ptr<f32> 67 ! CHECK: %[[VAL_5:.*]] = fir.embox %[[VAL_4]] : (!fir.ptr<f32>) -> !fir.box<!fir.ptr<f32>> 68 ! CHECK: fir.store %[[VAL_5]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<f32>>> 69 p => NULL(x) 70end subroutine 71 72! CHECK-LABEL: func @_QPtest_scalar_char_mold( 73! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<!fir.char<1,?>>>>{{[^,]*}}, 74subroutine test_scalar_char_mold(p, x) 75 character(:), pointer :: p, x 76 ! CHECK: %[[VAL_7:.*]] = fir.alloca !fir.box<!fir.ptr<!fir.char<1,?>>> 77 ! CHECK: %[[VAL_8:.*]] = fir.zero_bits !fir.ptr<!fir.char<1,?>> 78 ! CHECK: %[[VAL_9:.*]] = arith.constant 0 : index 79 ! CHECK: %[[VAL_10:.*]] = fir.embox %[[VAL_8]] typeparams %[[VAL_9]] : (!fir.ptr<!fir.char<1,?>>, index) -> !fir.box<!fir.ptr<!fir.char<1,?>>> 80 ! CHECK: fir.store %[[VAL_10]] to %[[VAL_7]] : !fir.ref<!fir.box<!fir.ptr<!fir.char<1,?>>>> 81 ! CHECK: %[[VAL_11:.*]] = fir.load %[[VAL_7]] : !fir.ref<!fir.box<!fir.ptr<!fir.char<1,?>>>> 82 ! CHECK: %[[VAL_12:.*]] = fir.box_elesize %[[VAL_11]] : (!fir.box<!fir.ptr<!fir.char<1,?>>>) -> index 83 ! CHECK: %[[VAL_13:.*]] = fir.box_addr %[[VAL_11]] : (!fir.box<!fir.ptr<!fir.char<1,?>>>) -> !fir.ptr<!fir.char<1,?>> 84 ! CHECK: %[[VAL_14:.*]] = fir.embox %[[VAL_13]] typeparams %[[VAL_12]] : (!fir.ptr<!fir.char<1,?>>, index) -> !fir.box<!fir.ptr<!fir.char<1,?>>> 85 ! CHECK: fir.store %[[VAL_14]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<!fir.char<1,?>>>> 86 p => NULL(x) 87end subroutine 88 89! CHECK-LABEL: func @_QPtest_array_mold( 90! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>{{[^,]*}}, 91subroutine test_array_mold(p, x) 92 real, pointer :: p(:), x(:) 93 ! CHECK: %[[VAL_0:.*]] = fir.alloca !fir.box<!fir.ptr<!fir.array<?xf32>>> 94 ! CHECK: %[[VAL_1:.*]] = fir.zero_bits !fir.ptr<!fir.array<?xf32>> 95 ! CHECK: %[[VAL_2:.*]] = arith.constant 0 : index 96 ! CHECK: %[[VAL_3:.*]] = fir.shape %[[VAL_2]] : (index) -> !fir.shape<1> 97 ! CHECK: %[[VAL_4:.*]] = fir.embox %[[VAL_1]](%[[VAL_3]]) : (!fir.ptr<!fir.array<?xf32>>, !fir.shape<1>) -> !fir.box<!fir.ptr<!fir.array<?xf32>>> 98 ! CHECK: fir.store %[[VAL_4]] to %[[VAL_0]] : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>> 99 ! CHECK: %[[VAL_5:.*]] = fir.load %[[VAL_0]] : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>> 100 ! CHECK: %[[VAL_6:.*]] = arith.constant 0 : index 101 ! CHECK: %[[VAL_7:.*]]:3 = fir.box_dims %[[VAL_5]], %[[VAL_6]] : (!fir.box<!fir.ptr<!fir.array<?xf32>>>, index) -> (index, index, index) 102 ! CHECK: %[[VAL_8:.*]] = fir.shift %[[VAL_7]]#0 : (index) -> !fir.shift<1> 103 ! CHECK: %[[VAL_9:.*]] = fir.rebox %[[VAL_5]](%[[VAL_8]]) : (!fir.box<!fir.ptr<!fir.array<?xf32>>>, !fir.shift<1>) -> !fir.box<!fir.ptr<!fir.array<?xf32>>> 104 ! CHECK: fir.store %[[VAL_9]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>> 105 p => NULL(x) 106end subroutine 107 108subroutine test_polymorphic_null(p) 109 type t 110 end type 111 class(t), pointer :: p(:) 112 p => null() 113end subroutine 114! CHECK-LABEL: func.func @_QPtest_polymorphic_null( 115! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.class<!fir.ptr<!fir.array<?x!fir.type<_QFtest_polymorphic_nullTt>>>>> 116! CHECK: %[[VAL_1:.*]] = fir.type_desc !fir.type<_QFtest_polymorphic_nullTt> 117! CHECK: %[[VAL_2:.*]] = fir.convert %[[VAL_0]] : (!fir.ref<!fir.class<!fir.ptr<!fir.array<?x!fir.type<_QFtest_polymorphic_nullTt>>>>>) -> !fir.ref<!fir.box<none>> 118! CHECK: %[[VAL_3:.*]] = fir.convert %[[VAL_1]] : (!fir.tdesc<!fir.type<_QFtest_polymorphic_nullTt>>) -> !fir.ref<none> 119! CHECK: %[[VAL_4:.*]] = arith.constant 1 : i32 120! CHECK: %[[VAL_5:.*]] = arith.constant 0 : i32 121! CHECK: fir.call @_FortranAPointerNullifyDerived(%[[VAL_2]], %[[VAL_3]], %[[VAL_4]], %[[VAL_5]]) {{.*}}: (!fir.ref<!fir.box<none>>, !fir.ref<none>, i32, i32) -> () 122 123subroutine test_unlimited_polymorphic_null(p) 124 class(*), pointer :: p(:) 125 p => null() 126end subroutine 127! CHECK-LABEL: func.func @_QPtest_unlimited_polymorphic_null( 128! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.class<!fir.ptr<!fir.array<?xnone>>>> 129! CHECK: %[[VAL_1:.*]] = fir.zero_bits !fir.ptr<!fir.array<?xnone>> 130! CHECK: %[[VAL_2:.*]] = arith.constant 0 : index 131! CHECK: %[[VAL_3:.*]] = fir.shape %[[VAL_2]] : (index) -> !fir.shape<1> 132! CHECK: %[[VAL_4:.*]] = fir.embox %[[VAL_1]](%[[VAL_3]]) : (!fir.ptr<!fir.array<?xnone>>, !fir.shape<1>) -> !fir.class<!fir.ptr<!fir.array<?xnone>>> 133! CHECK: fir.store %[[VAL_4]] to %[[VAL_0]] : !fir.ref<!fir.class<!fir.ptr<!fir.array<?xnone>>>> 134