! RUN: bbc -emit-fir -hlfir=false -I nowhere %s -o - | FileCheck %s ! Test allocatable return. ! Allocatable arrays must have default runtime lbounds after the return. function test_alloc_return_scalar real, allocatable :: test_alloc_return_scalar allocate(test_alloc_return_scalar) end function test_alloc_return_scalar ! CHECK-LABEL: func.func @_QPtest_alloc_return_scalar() -> !fir.box> { ! CHECK: %[[VAL_0:.*]] = fir.alloca !fir.box> {bindc_name = "test_alloc_return_scalar", uniq_name = "_QFtest_alloc_return_scalarEtest_alloc_return_scalar"} ! CHECK: %[[VAL_5:.*]] = fir.load %[[VAL_0]] : !fir.ref>> ! CHECK: return %[[VAL_5]] : !fir.box> ! CHECK: } function test_alloc_return_array real, allocatable :: test_alloc_return_array(:) allocate(test_alloc_return_array(7:8)) end function test_alloc_return_array ! CHECK-LABEL: func.func @_QPtest_alloc_return_array() -> !fir.box>> { ! CHECK: %[[VAL_0:.*]] = fir.alloca !fir.box>> {bindc_name = "test_alloc_return_array", uniq_name = "_QFtest_alloc_return_arrayEtest_alloc_return_array"} ! CHECK: %[[VAL_18:.*]] = fir.load %[[VAL_0]] : !fir.ref>>> ! CHECK: %[[VAL_19:.*]] = arith.constant 1 : index ! CHECK: %[[VAL_20:.*]] = fir.shift %[[VAL_19]] : (index) -> !fir.shift<1> ! CHECK: %[[VAL_21:.*]] = fir.rebox %[[VAL_18]](%[[VAL_20]]) : (!fir.box>>, !fir.shift<1>) -> !fir.box>> ! CHECK: return %[[VAL_21]] : !fir.box>> ! CHECK: } function test_alloc_return_char_scalar character(3), allocatable :: test_alloc_return_char_scalar allocate(test_alloc_return_char_scalar) end function test_alloc_return_char_scalar ! CHECK-LABEL: func.func @_QPtest_alloc_return_char_scalar() -> !fir.box>> { ! CHECK: %[[VAL_0:.*]] = fir.alloca !fir.box>> {bindc_name = "test_alloc_return_char_scalar", uniq_name = "_QFtest_alloc_return_char_scalarEtest_alloc_return_char_scalar"} ! CHECK: %[[VAL_5:.*]] = fir.load %[[VAL_0]] : !fir.ref>>> ! CHECK: return %[[VAL_5]] : !fir.box>> ! CHECK: } function test_alloc_return_char_array character(3), allocatable :: test_alloc_return_char_array(:) allocate(test_alloc_return_char_array(7:8)) end function test_alloc_return_char_array ! CHECK-LABEL: func.func @_QPtest_alloc_return_char_array() -> !fir.box>>> { ! CHECK: %[[VAL_0:.*]] = fir.alloca !fir.box>>> {bindc_name = "test_alloc_return_char_array", uniq_name = "_QFtest_alloc_return_char_arrayEtest_alloc_return_char_array"} ! CHECK: %[[VAL_18:.*]] = fir.load %[[VAL_0]] : !fir.ref>>>> ! CHECK: %[[VAL_19:.*]] = arith.constant 1 : index ! CHECK: %[[VAL_20:.*]] = fir.shift %[[VAL_19]] : (index) -> !fir.shift<1> ! CHECK: %[[VAL_21:.*]] = fir.rebox %[[VAL_18]](%[[VAL_20]]) : (!fir.box>>>, !fir.shift<1>) -> !fir.box>>> ! CHECK: return %[[VAL_21]] : !fir.box>>> ! CHECK: } function test_alloc_return_poly_scalar type t end type t class(*), allocatable :: test_alloc_return_poly_scalar allocate(t :: test_alloc_return_poly_scalar) end function test_alloc_return_poly_scalar ! CHECK-LABEL: func.func @_QPtest_alloc_return_poly_scalar() -> !fir.class> { ! CHECK: %[[VAL_0:.*]] = fir.alloca !fir.class> {bindc_name = "test_alloc_return_poly_scalar", uniq_name = "_QFtest_alloc_return_poly_scalarEtest_alloc_return_poly_scalar"} ! CHECK: %[[VAL_16:.*]] = fir.load %[[VAL_0]] : !fir.ref>> ! CHECK: return %[[VAL_16]] : !fir.class> ! CHECK: } function test_alloc_return_poly_array type t end type t class(*), allocatable :: test_alloc_return_poly_array(:) allocate(t :: test_alloc_return_poly_array(7:8)) end function test_alloc_return_poly_array ! CHECK-LABEL: func.func @_QPtest_alloc_return_poly_array() -> !fir.class>> { ! CHECK: %[[VAL_0:.*]] = fir.alloca !fir.class>> {bindc_name = "test_alloc_return_poly_array", uniq_name = "_QFtest_alloc_return_poly_arrayEtest_alloc_return_poly_array"} ! CHECK: %[[VAL_25:.*]] = fir.load %[[VAL_0]] : !fir.ref>>> ! CHECK: %[[VAL_26:.*]] = arith.constant 1 : index ! CHECK: %[[VAL_27:.*]] = fir.shift %[[VAL_26]] : (index) -> !fir.shift<1> ! CHECK: %[[VAL_28:.*]] = fir.rebox %[[VAL_25]](%[[VAL_27]]) : (!fir.class>>, !fir.shift<1>) -> !fir.class>> ! CHECK: return %[[VAL_28]] : !fir.class>> ! CHECK: }