Lines Matching defs:p

6 !     Test p => NULL()
11 ! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<f32>>>{{.*}})
12 subroutine test_scalar(p)
13 real, pointer :: p
16 ! CHECK: fir.store %[[box]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<f32>>>
17 p => NULL()
21 ! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<!fir.char<1,?>>>>{{.*}})
22 subroutine test_scalar_char(p)
23 character(:), pointer :: p
26 ! CHECK: fir.store %[[box]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<!fir.char<1,?>>>>
27 p => NULL()
31 ! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>{{.*}})
32 subroutine test_array(p)
33 real, pointer :: p(:)
37 ! CHECK: fir.store %[[box]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>
38 p => NULL()
41 ! Test p(lb, ub) => NULL() which is none sens but is not illegal.
43 ! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>{{.*}})
44 subroutine test_array_remap(p)
45 real, pointer :: p(:)
49 ! CHECK: fir.store %[[box]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>
50 p(10:20) => NULL()
54 ! Test p => NULL(MOLD)
58 ! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<f32>>>{{[^,]*}},
59 subroutine test_scalar_mold(p, x)
60 real, pointer :: p, x
68 ! CHECK: fir.store %[[VAL_5]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<f32>>>
69 p => NULL(x)
73 ! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<!fir.char<1,?>>>>{{[^,]*}},
74 subroutine test_scalar_char_mold(p, x)
75 character(:), pointer :: p, x
85 ! CHECK: fir.store %[[VAL_14]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<!fir.char<1,?>>>>
86 p => NULL(x)
90 ! CHECK-SAME: %[[p:.*]]: !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>{{[^,]*}},
91 subroutine test_array_mold(p, x)
92 real, pointer :: p(:), x(:)
104 ! CHECK: fir.store %[[VAL_9]] to %[[p]] : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>
105 p => NULL(x)
108 subroutine test_polymorphic_null(p)
111 class(t), pointer :: p(:)
112 p => null()
123 subroutine test_unlimited_polymorphic_null(p)
124 class(*), pointer :: p(:)
125 p => null()