xref: /llvm-project/flang/test/Lower/allocatable-return.f90 (revision d0829fbdeda0a2faa8cf684e1396e579691bdfa2)
1! RUN: bbc -emit-fir -hlfir=false -I nowhere %s -o - | FileCheck %s
2
3! Test allocatable return.
4! Allocatable arrays must have default runtime lbounds after the return.
5
6function test_alloc_return_scalar
7  real, allocatable :: test_alloc_return_scalar
8  allocate(test_alloc_return_scalar)
9end function test_alloc_return_scalar
10! CHECK-LABEL:   func.func @_QPtest_alloc_return_scalar() -> !fir.box<!fir.heap<f32>> {
11! CHECK:           %[[VAL_0:.*]] = fir.alloca !fir.box<!fir.heap<f32>> {bindc_name = "test_alloc_return_scalar", uniq_name = "_QFtest_alloc_return_scalarEtest_alloc_return_scalar"}
12! CHECK:           %[[VAL_5:.*]] = fir.load %[[VAL_0]] : !fir.ref<!fir.box<!fir.heap<f32>>>
13! CHECK:           return %[[VAL_5]] : !fir.box<!fir.heap<f32>>
14! CHECK:         }
15
16function test_alloc_return_array
17  real, allocatable :: test_alloc_return_array(:)
18  allocate(test_alloc_return_array(7:8))
19end function test_alloc_return_array
20! CHECK-LABEL:   func.func @_QPtest_alloc_return_array() -> !fir.box<!fir.heap<!fir.array<?xf32>>> {
21! CHECK:           %[[VAL_0:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<?xf32>>> {bindc_name = "test_alloc_return_array", uniq_name = "_QFtest_alloc_return_arrayEtest_alloc_return_array"}
22! CHECK:           %[[VAL_18:.*]] = fir.load %[[VAL_0]] : !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>
23! CHECK:           %[[VAL_19:.*]] = arith.constant 1 : index
24! CHECK:           %[[VAL_20:.*]] = fir.shift %[[VAL_19]] : (index) -> !fir.shift<1>
25! CHECK:           %[[VAL_21:.*]] = fir.rebox %[[VAL_18]](%[[VAL_20]]) : (!fir.box<!fir.heap<!fir.array<?xf32>>>, !fir.shift<1>) -> !fir.box<!fir.heap<!fir.array<?xf32>>>
26! CHECK:           return %[[VAL_21]] : !fir.box<!fir.heap<!fir.array<?xf32>>>
27! CHECK:         }
28
29function test_alloc_return_char_scalar
30  character(3), allocatable :: test_alloc_return_char_scalar
31  allocate(test_alloc_return_char_scalar)
32end function test_alloc_return_char_scalar
33! CHECK-LABEL:   func.func @_QPtest_alloc_return_char_scalar() -> !fir.box<!fir.heap<!fir.char<1,3>>> {
34! CHECK:           %[[VAL_0:.*]] = fir.alloca !fir.box<!fir.heap<!fir.char<1,3>>> {bindc_name = "test_alloc_return_char_scalar", uniq_name = "_QFtest_alloc_return_char_scalarEtest_alloc_return_char_scalar"}
35! CHECK:           %[[VAL_5:.*]] = fir.load %[[VAL_0]] : !fir.ref<!fir.box<!fir.heap<!fir.char<1,3>>>>
36! CHECK:           return %[[VAL_5]] : !fir.box<!fir.heap<!fir.char<1,3>>>
37! CHECK:         }
38
39function test_alloc_return_char_array
40  character(3), allocatable :: test_alloc_return_char_array(:)
41  allocate(test_alloc_return_char_array(7:8))
42end function test_alloc_return_char_array
43! CHECK-LABEL:   func.func @_QPtest_alloc_return_char_array() -> !fir.box<!fir.heap<!fir.array<?x!fir.char<1,3>>>> {
44! CHECK:           %[[VAL_0:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<?x!fir.char<1,3>>>> {bindc_name = "test_alloc_return_char_array", uniq_name = "_QFtest_alloc_return_char_arrayEtest_alloc_return_char_array"}
45! CHECK:           %[[VAL_18:.*]] = fir.load %[[VAL_0]] : !fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.char<1,3>>>>>
46! CHECK:           %[[VAL_19:.*]] = arith.constant 1 : index
47! CHECK:           %[[VAL_20:.*]] = fir.shift %[[VAL_19]] : (index) -> !fir.shift<1>
48! CHECK:           %[[VAL_21:.*]] = fir.rebox %[[VAL_18]](%[[VAL_20]]) : (!fir.box<!fir.heap<!fir.array<?x!fir.char<1,3>>>>, !fir.shift<1>) -> !fir.box<!fir.heap<!fir.array<?x!fir.char<1,3>>>>
49! CHECK:           return %[[VAL_21]] : !fir.box<!fir.heap<!fir.array<?x!fir.char<1,3>>>>
50! CHECK:         }
51
52function test_alloc_return_poly_scalar
53  type t
54  end type t
55  class(*), allocatable :: test_alloc_return_poly_scalar
56  allocate(t :: test_alloc_return_poly_scalar)
57end function test_alloc_return_poly_scalar
58! CHECK-LABEL:   func.func @_QPtest_alloc_return_poly_scalar() -> !fir.class<!fir.heap<none>> {
59! CHECK:           %[[VAL_0:.*]] = fir.alloca !fir.class<!fir.heap<none>> {bindc_name = "test_alloc_return_poly_scalar", uniq_name = "_QFtest_alloc_return_poly_scalarEtest_alloc_return_poly_scalar"}
60! CHECK:           %[[VAL_16:.*]] = fir.load %[[VAL_0]] : !fir.ref<!fir.class<!fir.heap<none>>>
61! CHECK:           return %[[VAL_16]] : !fir.class<!fir.heap<none>>
62! CHECK:         }
63
64function test_alloc_return_poly_array
65  type t
66  end type t
67  class(*), allocatable :: test_alloc_return_poly_array(:)
68  allocate(t :: test_alloc_return_poly_array(7:8))
69end function test_alloc_return_poly_array
70! CHECK-LABEL:   func.func @_QPtest_alloc_return_poly_array() -> !fir.class<!fir.heap<!fir.array<?xnone>>> {
71! CHECK:           %[[VAL_0:.*]] = fir.alloca !fir.class<!fir.heap<!fir.array<?xnone>>> {bindc_name = "test_alloc_return_poly_array", uniq_name = "_QFtest_alloc_return_poly_arrayEtest_alloc_return_poly_array"}
72! CHECK:           %[[VAL_25:.*]] = fir.load %[[VAL_0]] : !fir.ref<!fir.class<!fir.heap<!fir.array<?xnone>>>>
73! CHECK:           %[[VAL_26:.*]] = arith.constant 1 : index
74! CHECK:           %[[VAL_27:.*]] = fir.shift %[[VAL_26]] : (index) -> !fir.shift<1>
75! CHECK:           %[[VAL_28:.*]] = fir.rebox %[[VAL_25]](%[[VAL_27]]) : (!fir.class<!fir.heap<!fir.array<?xnone>>>, !fir.shift<1>) -> !fir.class<!fir.heap<!fir.array<?xnone>>>
76! CHECK:           return %[[VAL_28]] : !fir.class<!fir.heap<!fir.array<?xnone>>>
77! CHECK:         }
78