xref: /llvm-project/flang/test/Lower/HLFIR/function-return-as-expr.f90 (revision 12ba74e181bd6641b532e271f3bfabf53066b1c0)
1! RUN: bbc -emit-hlfir -o - %s -I nowhere 2>&1 | FileCheck %s
2
3module types
4  type t1
5  end type t1
6end module types
7
8subroutine test1
9  integer :: i
10  i = inner() + 1
11contains
12  function inner()
13    integer, allocatable ::  inner
14  end function inner
15end subroutine test1
16! CHECK-LABEL:   func.func @_QPtest1() {
17! CHECK:           %[[VAL_0:.*]] = fir.alloca !fir.box<!fir.heap<i32>> {bindc_name = ".result"}
18! CHECK:           %[[VAL_4:.*]]:2 = hlfir.declare %[[VAL_0]] {uniq_name = ".tmp.func_result"} : (!fir.ref<!fir.box<!fir.heap<i32>>>) -> (!fir.ref<!fir.box<!fir.heap<i32>>>, !fir.ref<!fir.box<!fir.heap<i32>>>)
19! CHECK:           %[[VAL_5:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<!fir.box<!fir.heap<i32>>>
20! CHECK:           %[[VAL_6:.*]] = fir.box_addr %[[VAL_5]] : (!fir.box<!fir.heap<i32>>) -> !fir.heap<i32>
21! CHECK:           %[[VAL_7:.*]] = fir.load %[[VAL_6]] : !fir.heap<i32>
22! CHECK:           %[[VAL_8:.*]] = arith.constant 1 : i32
23! CHECK:           %[[VAL_9:.*]] = arith.addi %[[VAL_7]], %[[VAL_8]] : i32
24
25subroutine test2
26  character(len=:), allocatable :: c
27  c = inner()
28contains
29  function inner()
30    character(len=:), allocatable ::  inner
31  end function inner
32end subroutine test2
33! CHECK-LABEL:   func.func @_QPtest2() {
34! CHECK:           %[[VAL_7:.*]]:2 = hlfir.declare %{{.*}} {uniq_name = ".tmp.func_result"} : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>) -> (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>, !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>)
35! CHECK:           %[[VAL_8:.*]] = fir.load %[[VAL_7]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>
36! CHECK:           %[[VAL_9:.*]] = fir.box_addr %[[VAL_8]] : (!fir.box<!fir.heap<!fir.char<1,?>>>) -> !fir.heap<!fir.char<1,?>>
37! CHECK:           %[[VAL_10:.*]] = fir.load %[[VAL_7]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>
38! CHECK:           %[[VAL_11:.*]] = fir.box_elesize %[[VAL_10]] : (!fir.box<!fir.heap<!fir.char<1,?>>>) -> index
39! CHECK:           %[[VAL_12:.*]] = fir.emboxchar %[[VAL_9]], %[[VAL_11]] : (!fir.heap<!fir.char<1,?>>, index) -> !fir.boxchar<1>
40! CHECK:           %[[VAL_13:.*]] = arith.constant false
41! CHECK:           %[[VAL_14:.*]] = hlfir.as_expr %[[VAL_12]] move %[[VAL_13]] : (!fir.boxchar<1>, i1) -> !hlfir.expr<!fir.char<1,?>>
42! CHECK:           hlfir.assign %[[VAL_14]] to %{{.*}}#0 realloc : !hlfir.expr<!fir.char<1,?>>, !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>
43
44subroutine test3
45  character(len=:), allocatable :: c
46  c = inner()
47contains
48  function inner()
49    character(len=3), allocatable ::  inner
50  end function inner
51end subroutine test3
52! CHECK-LABEL:   func.func @_QPtest3() {
53! CHECK:           %[[VAL_13:.*]]:2 = hlfir.declare %{{.*}} typeparams %{{.*}} {uniq_name = ".tmp.func_result"} : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,3>>>>, index) -> (!fir.ref<!fir.box<!fir.heap<!fir.char<1,3>>>>, !fir.ref<!fir.box<!fir.heap<!fir.char<1,3>>>>)
54! CHECK:           %[[VAL_14:.*]] = fir.load %[[VAL_13]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.char<1,3>>>>
55! CHECK:           %[[VAL_15:.*]] = fir.box_addr %[[VAL_14]] : (!fir.box<!fir.heap<!fir.char<1,3>>>) -> !fir.heap<!fir.char<1,3>>
56! CHECK:           %[[VAL_16:.*]] = arith.constant false
57! CHECK:           %[[VAL_17:.*]] = hlfir.as_expr %[[VAL_15]] move %[[VAL_16]] : (!fir.heap<!fir.char<1,3>>, i1) -> !hlfir.expr<!fir.char<1,3>>
58! CHECK:           hlfir.assign %[[VAL_17]] to %{{.*}}#0 realloc : !hlfir.expr<!fir.char<1,3>>, !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>
59
60subroutine test4
61  class(*), allocatable :: p
62  p = inner()
63contains
64  function inner()
65    class(*), allocatable :: inner
66  end function inner
67end subroutine test4
68! CHECK-LABEL:   func.func @_QPtest4() {
69! CHECK:           %[[VAL_6:.*]] = fir.load %[[VAL_0:.*]] : !fir.ref<!fir.class<!fir.heap<none>>>
70! CHECK:           %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_6]] {uniq_name = ".tmp.func_result"} : (!fir.class<!fir.heap<none>>) -> (!fir.class<!fir.heap<none>>, !fir.class<!fir.heap<none>>)
71! CHECK:           hlfir.assign %[[VAL_7]]#0 to %{{.*}}#0 realloc : !fir.class<!fir.heap<none>>, !fir.ref<!fir.class<!fir.heap<none>>>
72! CHECK:           %[[VAL_10:.*]] = fir.convert %[[VAL_0]] : (!fir.ref<!fir.class<!fir.heap<none>>>) -> !fir.box<none>
73! CHECK:           fir.call @_FortranADestroy(%[[VAL_10]]) fastmath<contract> : (!fir.box<none>) -> ()
74
75subroutine test4b
76  class(*), allocatable :: p(:, :)
77  p = inner()
78contains
79  function inner()
80    class(*), allocatable :: inner(:, :)
81  end function inner
82end subroutine test4b
83! CHECK-LABEL:   func.func @_QPtest4b() {
84! CHECK:           %[[VAL_6:.*]] = fir.load %[[VAL_0:.*]] : !fir.ref<!fir.class<!fir.heap<!fir.array<?x?xnone>>>>
85! CHECK:           %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_6]] {uniq_name = ".tmp.func_result"} : (!fir.class<!fir.heap<!fir.array<?x?xnone>>>) -> (!fir.class<!fir.heap<!fir.array<?x?xnone>>>, !fir.class<!fir.heap<!fir.array<?x?xnone>>>)
86! CHECK:           hlfir.assign %[[VAL_7]]#0 to %{{.*}}#0 realloc : !fir.class<!fir.heap<!fir.array<?x?xnone>>>, !fir.ref<!fir.class<!fir.heap<!fir.array<?x?xnone>>>>
87! CHECK:           %[[VAL_10:.*]] = fir.convert %[[VAL_0]] : (!fir.ref<!fir.class<!fir.heap<!fir.array<?x?xnone>>>>) -> !fir.box<none>
88! CHECK:           fir.call @_FortranADestroy(%[[VAL_10]]) fastmath<contract> : (!fir.box<none>) -> ()
89
90subroutine test5
91  use types
92  type(t1) :: r
93  r = inner()
94contains
95  function inner()
96    type(t1) :: inner
97  end function inner
98end subroutine test5
99! CHECK-LABEL:   func.func @_QPtest5() {
100! CHECK:           %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}} {uniq_name = ".tmp.func_result"} : (!fir.ref<!fir.type<_QMtypesTt1>>) -> (!fir.ref<!fir.type<_QMtypesTt1>>, !fir.ref<!fir.type<_QMtypesTt1>>)
101! CHECK:           %[[VAL_5:.*]] = arith.constant false
102! CHECK:           %[[VAL_6:.*]] = hlfir.as_expr %[[VAL_4]]#0 move %[[VAL_5]] : (!fir.ref<!fir.type<_QMtypesTt1>>, i1) -> !hlfir.expr<!fir.type<_QMtypesTt1>>
103! CHECK:           hlfir.assign %[[VAL_6]] to %{{.*}}#0 : !hlfir.expr<!fir.type<_QMtypesTt1>>, !fir.ref<!fir.type<_QMtypesTt1>>
104
105subroutine test6(x)
106  character(len=:), allocatable :: c(:)
107  integer :: x(:)
108  c = inner(x)
109contains
110  elemental function inner(x)
111    integer, intent(in) ::  x
112    character(len=3) ::  inner
113  end function inner
114end subroutine test6
115! CHECK-LABEL:   func.func @_QPtest6(
116! CHECK:           %[[VAL_14:.*]] = hlfir.elemental
117! CHECK:             %[[VAL_24:.*]]:2 = hlfir.declare %{{.*}} typeparams %{{.*}} {uniq_name = ".tmp.func_result"} : (!fir.ref<!fir.char<1,3>>, index) -> (!fir.ref<!fir.char<1,3>>, !fir.ref<!fir.char<1,3>>)
118! CHECK:             %[[VAL_25:.*]] = arith.constant false
119! CHECK:             %[[VAL_26:.*]] = hlfir.as_expr %[[VAL_24]]#0 move %[[VAL_25]] : (!fir.ref<!fir.char<1,3>>, i1) -> !hlfir.expr<!fir.char<1,3>>
120! CHECK:             hlfir.yield_element %[[VAL_26]] : !hlfir.expr<!fir.char<1,3>>
121
122subroutine test7(x)
123  use types
124  integer :: x(:)
125  class(*), allocatable :: p(:)
126  p = inner(x)
127contains
128  elemental function inner(x)
129    integer, intent(in) :: x
130    type(t1) :: inner
131  end function inner
132end subroutine test7
133! CHECK-LABEL:   func.func @_QPtest7(
134! CHECK:           %[[VAL_12:.*]] = hlfir.elemental
135! CHECK:             %[[VAL_16:.*]]:2 = hlfir.declare %{{.*}} {uniq_name = ".tmp.func_result"} : (!fir.ref<!fir.type<_QMtypesTt1>>) -> (!fir.ref<!fir.type<_QMtypesTt1>>, !fir.ref<!fir.type<_QMtypesTt1>>)
136! CHECK:             %[[VAL_17:.*]] = arith.constant false
137! CHECK:             %[[VAL_18:.*]] = hlfir.as_expr %[[VAL_16]]#0 move %[[VAL_17]] : (!fir.ref<!fir.type<_QMtypesTt1>>, i1) -> !hlfir.expr<!fir.type<_QMtypesTt1>>
138! CHECK:             hlfir.yield_element %[[VAL_18]] : !hlfir.expr<!fir.type<_QMtypesTt1>>
139
140subroutine test8
141  if (associated(inner())) STOP 1
142contains
143  function inner()
144    real, pointer :: inner
145  end function inner
146end subroutine test8
147! CHECK-LABEL:   func.func @_QPtest8() {
148! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %{{.*}} {uniq_name = ".tmp.func_result"} : (!fir.ref<!fir.box<!fir.ptr<f32>>>) -> (!fir.ref<!fir.box<!fir.ptr<f32>>>, !fir.ref<!fir.box<!fir.ptr<f32>>>)
149! CHECK:           %[[VAL_3:.*]] = fir.load %[[VAL_2]]#1 : !fir.ref<!fir.box<!fir.ptr<f32>>>
150! CHECK:           %[[VAL_4:.*]] = fir.box_addr %[[VAL_3]] : (!fir.box<!fir.ptr<f32>>) -> !fir.ptr<f32>
151