! RUN: bbc --use-desc-for-alloc=false -emit-fir -hlfir=false %s -o - | FileCheck %s ! RUN: %flang_fc1 -mllvm --use-desc-for-alloc=false -emit-fir -flang-deprecated-no-hlfir %s -o - | FileCheck %s ! CHECK-LABEL: to_from_only subroutine to_from_only ! CHECK: %[[a1:.*]] = fir.alloca !fir.box>> ! CHECK: %[[b1:.*]] = fir.alloca !fir.box>> integer, allocatable :: from(:), to(:) allocate(from(20)) ! CHECK: %[[errMsg:.*]] = fir.absent !fir.box ! CHECK: %[[false:.*]] = arith.constant false ! CHECK-DAG: %[[a2:.*]] = fir.convert %[[a1]] : (!fir.ref>>>) -> !fir.ref> ! CHECK-DAG: %[[b2:.*]] = fir.convert %[[b1]] : (!fir.ref>>>) -> !fir.ref> call move_alloc(from, to) ! CHECK: fir.call @_FortranAMoveAlloc(%[[b2]], %[[a2]], %{{.*}}, %[[false]], %[[errMsg]], %{{.*}}, %{{.*}}) fastmath : (!fir.ref>, !fir.ref>, !fir.ref, i1, !fir.box, !fir.ref, i32) -> i32 ! CHECK-DAG: %[[a3:.*]] = fir.load %[[a1:.*]] : !fir.ref>>> ! CHECK-DAG: %[[a4:.*]] = fir.box_addr %[[a3]] : (!fir.box>>) -> !fir.heap> ! CHECK-DAG: %[[b3:.*]] = fir.load %[[b1]] : !fir.ref>>> ! CHECK-DAG: %[[b4:.*]] = fir.box_addr %[[b3:.*]] : (!fir.box>>) -> !fir.heap> end subroutine to_from_only ! CHECK-LABEL: to_from_stat subroutine to_from_stat ! CHECK-DAG: %[[a1:.*]] = fir.alloca !fir.box>> ! CHECK-DAG: %[[b1:.*]] = fir.alloca !fir.box>> integer, allocatable :: from(:), to(:) ! CHECK-DAG: %[[stat1:.*]] = fir.alloca i32 integer :: stat allocate(from(20)) ! CHECK: %[[errMsg:.*]] = fir.absent !fir.box ! CHECK: %[[true:.*]] = arith.constant true ! CHECK-DAG: %[[a2:.*]] = fir.convert %[[a1]] : (!fir.ref>>>) -> !fir.ref> ! CHECK-DAG: %[[b2:.*]] = fir.convert %[[b1]] : (!fir.ref>>>) -> !fir.ref> call move_alloc(from, to, stat) ! CHECK: %[[stat:.*]] = fir.call @_FortranAMoveAlloc(%[[b2]], %[[a2]], %{{.*}}, %[[true]], %[[errMsg]], %{{.*}}, %{{.*}}) fastmath : (!fir.ref>, !fir.ref>, !fir.ref, i1, !fir.box, !fir.ref, i32) -> i32 ! CHECK-DAG: %[[a3:.*]] = fir.load %[[a1:.*]] : !fir.ref>>> ! CHECK-DAG: %[[a4:.*]] = fir.box_addr %[[a3]] : (!fir.box>>) -> !fir.heap> ! CHECK-DAG: %[[b3:.*]] = fir.load %[[b1]] : !fir.ref>>> ! CHECK-DAG: %[[b4:.*]] = fir.box_addr %[[b3:.*]] : (!fir.box>>) -> !fir.heap> end subroutine to_from_stat ! CHECK-LABEL: to_from_stat_errmsg subroutine to_from_stat_errmsg ! CHECK-DAG: %[[errMsg1:.*]] = fir.alloca !fir.char<1,64> ! CHECK-DAG: %[[a1:.*]] = fir.alloca !fir.box>> ! CHECK-DAG: %[[b1:.*]] = fir.alloca !fir.box>> integer, allocatable :: from(:), to(:) ! CHECK-DAG: %[[stat1:.*]] = fir.alloca i32 integer :: stat character :: errMsg*64 allocate(from(20)) ! CHECK: %[[errMsg2:.*]] = fir.embox %[[errMsg1]] : (!fir.ref>) -> !fir.box> ! CHECK: %[[true:.*]] = arith.constant true ! CHECK-DAG: %[[errMsg3:.*]] = fir.convert %[[errMsg2]] : (!fir.box>) -> !fir.box ! CHECK-DAG: %[[a2:.*]] = fir.convert %[[a1]] : (!fir.ref>>>) -> !fir.ref> ! CHECK-DAG: %[[b2:.*]] = fir.convert %[[b1]] : (!fir.ref>>>) -> !fir.ref> call move_alloc(from, to, stat, errMsg) ! CHECK: %[[stat:.*]] = fir.call @_FortranAMoveAlloc(%[[b2]], %[[a2]], %{{.*}}, %[[true]], %[[errMsg3]], %{{.*}}, %{{.*}}) fastmath : (!fir.ref>, !fir.ref>, !fir.ref, i1, !fir.box, !fir.ref, i32) -> i32 ! CHECK-DAG: %[[a3:.*]] = fir.load %[[a1:.*]] : !fir.ref>>> ! CHECK-DAG: %[[a4:.*]] = fir.box_addr %[[a3]] : (!fir.box>>) -> !fir.heap> ! CHECK-DAG: %[[b3:.*]] = fir.load %[[b1]] : !fir.ref>>> ! CHECK-DAG: %[[b4:.*]] = fir.box_addr %[[b3:.*]] : (!fir.box>>) -> !fir.heap> end subroutine to_from_stat_errmsg