xref: /llvm-project/flang/test/Lower/pointer-results-as-arguments.f90 (revision f35f863a88f83332bef9605ef4cfe4f05c066efb)
1! Test passing pointers results to pointer dummy arguments
2! RUN: bbc -hlfir=false %s -o - | FileCheck %s
3
4module presults
5  interface
6    subroutine bar_scalar(x)
7      real, pointer :: x
8    end subroutine
9    subroutine bar(x)
10      real, pointer :: x(:, :)
11    end subroutine
12    function get_scalar_pointer()
13      real, pointer :: get_scalar_pointer
14    end function
15    function get_pointer()
16      real, pointer :: get_pointer(:, :)
17    end function
18  end interface
19  real, pointer :: x
20  real, pointer :: xa(:, :)
21contains
22
23! CHECK-LABEL: test_scalar_null
24subroutine test_scalar_null()
25! CHECK: %[[VAL_0:.*]] = fir.alloca !fir.box<!fir.ptr<f32>>
26! CHECK: %[[VAL_1:.*]] = fir.zero_bits !fir.ptr<f32>
27! CHECK: %[[VAL_2:.*]] = fir.embox %[[VAL_1]] : (!fir.ptr<f32>) -> !fir.box<!fir.ptr<f32>>
28! CHECK: fir.store %[[VAL_2]] to %[[VAL_0]] : !fir.ref<!fir.box<!fir.ptr<f32>>>
29! CHECK: fir.call @_QPbar_scalar(%[[VAL_0]]) {{.*}}: (!fir.ref<!fir.box<!fir.ptr<f32>>>) -> ()
30  call bar_scalar(null())
31end subroutine
32
33! CHECK-LABEL: test_scalar_null_mold
34subroutine test_scalar_null_mold()
35! CHECK: %[[VAL_3:.*]] = fir.alloca !fir.box<!fir.ptr<f32>>
36! CHECK: %[[VAL_4:.*]] = fir.zero_bits !fir.ptr<f32>
37! CHECK: %[[VAL_5:.*]] = fir.embox %[[VAL_4]] : (!fir.ptr<f32>) -> !fir.box<!fir.ptr<f32>>
38! CHECK: fir.store %[[VAL_5]] to %[[VAL_3]] : !fir.ref<!fir.box<!fir.ptr<f32>>>
39! CHECK: fir.call @_QPbar_scalar(%[[VAL_3]]) {{.*}}: (!fir.ref<!fir.box<!fir.ptr<f32>>>) -> ()
40  call bar_scalar(null(x))
41end subroutine
42
43! CHECK-LABEL: test_scalar_result
44subroutine test_scalar_result()
45! CHECK: %[[VAL_6:.*]] = fir.alloca !fir.box<!fir.ptr<f32>> {bindc_name = ".result"}
46! CHECK: %[[VAL_7:.*]] = fir.call @_QPget_scalar_pointer() {{.*}}: () -> !fir.box<!fir.ptr<f32>>
47! CHECK: fir.save_result %[[VAL_7]] to %[[VAL_6]] : !fir.box<!fir.ptr<f32>>, !fir.ref<!fir.box<!fir.ptr<f32>>>
48! CHECK: fir.call @_QPbar_scalar(%[[VAL_6]]) {{.*}}: (!fir.ref<!fir.box<!fir.ptr<f32>>>) -> ()
49  call bar_scalar(get_scalar_pointer())
50end subroutine
51
52! CHECK-LABEL: test_null
53subroutine test_null()
54! CHECK: %[[VAL_8:.*]] = arith.constant 0 : index
55! CHECK: %[[VAL_9:.*]] = fir.alloca !fir.box<!fir.ptr<!fir.array<?x?xf32>>>
56! CHECK: %[[VAL_10:.*]] = fir.zero_bits !fir.ptr<!fir.array<?x?xf32>>
57! CHECK: %[[VAL_11:.*]] = fir.shape %[[VAL_8]], %[[VAL_8]] : (index, index) -> !fir.shape<2>
58! CHECK: %[[VAL_12:.*]] = fir.embox %[[VAL_10]](%[[VAL_11]]) : (!fir.ptr<!fir.array<?x?xf32>>, !fir.shape<2>) -> !fir.box<!fir.ptr<!fir.array<?x?xf32>>>
59! CHECK: fir.store %[[VAL_12]] to %[[VAL_9]] : !fir.ref<!fir.box<!fir.ptr<!fir.array<?x?xf32>>>>
60! CHECK: fir.call @_QPbar(%[[VAL_9]]) {{.*}}: (!fir.ref<!fir.box<!fir.ptr<!fir.array<?x?xf32>>>>) -> ()
61  call bar(null())
62end subroutine
63
64! CHECK-LABEL: test_null_mold
65subroutine test_null_mold()
66! CHECK: %[[VAL_13:.*]] = arith.constant 0 : index
67! CHECK: %[[VAL_14:.*]] = fir.alloca !fir.box<!fir.ptr<!fir.array<?x?xf32>>>
68! CHECK: %[[VAL_15:.*]] = fir.zero_bits !fir.ptr<!fir.array<?x?xf32>>
69! CHECK: %[[VAL_16:.*]] = fir.shape %[[VAL_13]], %[[VAL_13]] : (index, index) -> !fir.shape<2>
70! CHECK: %[[VAL_17:.*]] = fir.embox %[[VAL_15]](%[[VAL_16]]) : (!fir.ptr<!fir.array<?x?xf32>>, !fir.shape<2>) -> !fir.box<!fir.ptr<!fir.array<?x?xf32>>>
71! CHECK: fir.store %[[VAL_17]] to %[[VAL_14]] : !fir.ref<!fir.box<!fir.ptr<!fir.array<?x?xf32>>>>
72! CHECK: fir.call @_QPbar(%[[VAL_14]]) {{.*}}: (!fir.ref<!fir.box<!fir.ptr<!fir.array<?x?xf32>>>>) -> ()
73  call bar(null(xa))
74end subroutine
75
76! CHECK-LABEL: test_result
77subroutine test_result()
78! CHECK: %[[VAL_18:.*]] = fir.alloca !fir.box<!fir.ptr<!fir.array<?x?xf32>>> {bindc_name = ".result"}
79! CHECK: %[[VAL_19:.*]] = fir.call @_QPget_pointer() {{.*}}: () -> !fir.box<!fir.ptr<!fir.array<?x?xf32>>>
80! CHECK: fir.save_result %[[VAL_19]] to %[[VAL_18]] : !fir.box<!fir.ptr<!fir.array<?x?xf32>>>, !fir.ref<!fir.box<!fir.ptr<!fir.array<?x?xf32>>>>
81! CHECK: fir.call @_QPbar(%[[VAL_18]]) {{.*}}: (!fir.ref<!fir.box<!fir.ptr<!fir.array<?x?xf32>>>>) -> ()
82  call bar(get_pointer())
83end subroutine
84
85end module
86