|
| 1 | +! RUN: bbc -emit-fir %s -o - | FileCheck %s |
| 2 | + |
| 3 | +! CHECK-LABEL: eoshift_test1 |
| 4 | +subroutine eoshift_test1(arr, shift) |
| 5 | + logical, dimension(3) :: arr, res |
| 6 | + integer :: shift |
| 7 | +! CHECK: %[[resBox:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<?x!fir.logical<4>>>> {uniq_name = ""} |
| 8 | +! CHECK: %[[res:.*]] = fir.alloca !fir.array<3x!fir.logical<4>> {bindc_name = "res", uniq_name = "_QFeoshift_test1Eres"} |
| 9 | +! CHECK: %[[resLoad:.*]] = fir.array_load %[[res]]({{.*}}) : (!fir.ref<!fir.array<3x!fir.logical<4>>>, !fir.shape<1>) -> !fir.array<3x!fir.logical<4>> |
| 10 | +! CHECK: %[[arr:.*]] = fir.embox %arg0({{.*}}) : (!fir.ref<!fir.array<3x!fir.logical<4>>>, !fir.shape<1>) -> !fir.box<!fir.array<3x!fir.logical<4>>> |
| 11 | +! CHECK: %[[bits:.*]] = fir.zero_bits !fir.heap<!fir.array<?x!fir.logical<4>>> |
| 12 | +! CHECK: %[[init:.*]] = fir.embox %[[bits]]({{.*}}) : (!fir.heap<!fir.array<?x!fir.logical<4>>>, !fir.shape<1>) -> !fir.box<!fir.heap<!fir.array<?x!fir.logical<4>>>> |
| 13 | +! CHECK: fir.store %[[init]] to %[[resBox]] : !fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.logical<4>>>>> |
| 14 | +! CHECK: %[[boundBox:.*]] = fir.absent !fir.box<none> |
| 15 | +! CHECK: %[[shift:.*]] = fir.load %arg1 : !fir.ref<i32> |
| 16 | + |
| 17 | + res = eoshift(arr, shift) |
| 18 | + |
| 19 | +! CHECK: %[[resIRBox:.*]] = fir.convert %[[resBox]] : (!fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.logical<4>>>>>) -> !fir.ref<!fir.box<none>> |
| 20 | +! CHECK: %[[arrBox:.*]] = fir.convert %[[arr]] : (!fir.box<!fir.array<3x!fir.logical<4>>>) -> !fir.box<none> |
| 21 | +! CHECK: %[[shiftBox:.*]] = fir.convert %[[shift]] : (i32) -> i64 |
| 22 | +! CHECK: %[[tmp:.*]] = fir.call @_FortranAEoshiftVector(%[[resIRBox]], %[[arrBox]], %[[shiftBox]], %[[boundBox]], {{.*}}, {{.*}}) : (!fir.ref<!fir.box<none>>, !fir.box<none>, i64, !fir.box<none>, !fir.ref<i8>, i32) -> none |
| 23 | +! CHECK: fir.array_merge_store %[[resLoad]], {{.*}} to %[[res]] : !fir.array<3x!fir.logical<4>>, !fir.array<3x!fir.logical<4>>, !fir.ref<!fir.array<3x!fir.logical<4>>> |
| 24 | +end subroutine eoshift_test1 |
| 25 | + |
| 26 | +! CHECK-LABEL: eoshift_test2 |
| 27 | +subroutine eoshift_test2(arr, shift, bound, dim) |
| 28 | + integer, dimension(3,3) :: arr, res |
| 29 | + integer, dimension(3) :: shift |
| 30 | + integer :: bound, dim |
| 31 | +! CHECK: %[[resBox:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<?x?xi32>>> {uniq_name = ""} |
| 32 | +! CHECK: %[[res:.*]] = fir.alloca !fir.array<3x3xi32> {bindc_name = "res", uniq_name = "_QFeoshift_test2Eres"} |
| 33 | +!CHECK: %[[resLoad:.*]] = fir.array_load %[[res]]({{.*}}) : (!fir.ref<!fir.array<3x3xi32>>, !fir.shape<2>) -> !fir.array<3x3xi32> |
| 34 | +! CHECK: %[[dim:.*]] = fir.load %arg3 : !fir.ref<i32> |
| 35 | + |
| 36 | + res = eoshift(arr, shift, bound, dim) |
| 37 | + |
| 38 | +! CHECK: %[[arr:.*]] = fir.embox %arg0({{.*}}) : (!fir.ref<!fir.array<3x3xi32>>, !fir.shape<2>) -> !fir.box<!fir.array<3x3xi32>> |
| 39 | +! CHECK: %[[boundBox:.*]] = fir.embox %arg2 : (!fir.ref<i32>) -> !fir.box<i32> |
| 40 | +! CHECK: %[[shiftBox:.*]] = fir.embox %arg1({{.*}}) : (!fir.ref<!fir.array<3xi32>>, !fir.shape<1>) -> !fir.box<!fir.array<3xi32>> |
| 41 | +! CHECK: %[[resIRBox:.*]] = fir.convert %[[resBox]] : (!fir.ref<!fir.box<!fir.heap<!fir.array<?x?xi32>>>>) -> !fir.ref<!fir.box<none>> |
| 42 | +! CHECK: %[[arrBox:.*]] = fir.convert %[[arr]] : (!fir.box<!fir.array<3x3xi32>>) -> !fir.box<none> |
| 43 | +! CHECK: %[[shiftBoxNone:.*]] = fir.convert %[[shiftBox]] : (!fir.box<!fir.array<3xi32>>) -> !fir.box<none> |
| 44 | +! CHECK: %[[boundBoxNone:.*]] = fir.convert %[[boundBox]] : (!fir.box<i32>) -> !fir.box<none> |
| 45 | + |
| 46 | +! CHECK: %[[tmp:.*]] = fir.call @_FortranAEoshift(%[[resIRBox]], %[[arrBox]], %[[shiftBoxNone]], %[[boundBoxNone]], %[[dim]], {{.*}}, {{.*}}) : (!fir.ref<!fir.box<none>>, !fir.box<none>, !fir.box<none>, !fir.box<none>, i32, !fir.ref<i8>, i32) -> none |
| 47 | +! CHECK: fir.array_merge_store %[[resLoad]], {{.*}} to %[[res]] : !fir.array<3x3xi32>, !fir.array<3x3xi32>, !fir.ref<!fir.array<3x3xi32>> |
| 48 | +end subroutine eoshift_test2 |
| 49 | + |
| 50 | +! CHECK-LABEL: eoshift_test3 |
| 51 | +subroutine eoshift_test3(arr, shift, dim) |
| 52 | + character(4), dimension(3,3) :: arr, res |
| 53 | + integer :: shift, dim |
| 54 | + |
| 55 | +! CHECK: %[[resBox:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<?x?x!fir.char<1,?>>>> {uniq_name = ""} |
| 56 | +! CHECK: %[[arr:.*]]:2 = fir.unboxchar %arg0 : (!fir.boxchar<1>) -> (!fir.ref<!fir.char<1,?>>, index) |
| 57 | +! CHECK: %[[array:.*]] = fir.convert %[[arr]]#0 : (!fir.ref<!fir.char<1,?>>) -> !fir.ref<!fir.array<3x3x!fir.char<1,4>>> |
| 58 | +! CHECK: %[[res:.*]] = fir.alloca !fir.array<3x3x!fir.char<1,4>> {bindc_name = "res", uniq_name = "_QFeoshift_test3Eres"} |
| 59 | +! CHECK: %[[resLoad:.*]] = fir.array_load %[[res]]({{.*}}) : (!fir.ref<!fir.array<3x3x!fir.char<1,4>>>, !fir.shape<2>) -> !fir.array<3x3x!fir.char<1,4>> |
| 60 | +! CHECK: %[[dim:.*]] = fir.load %arg2 : !fir.ref<i32> |
| 61 | +! CHECK: %[[arrayBox:.*]] = fir.embox %[[array]]({{.*}}) : (!fir.ref<!fir.array<3x3x!fir.char<1,4>>>, !fir.shape<2>) -> !fir.box<!fir.array<3x3x!fir.char<1,4>>> |
| 62 | + |
| 63 | + res = eoshift(arr, SHIFT=shift, DIM=dim) |
| 64 | + |
| 65 | +! CHECK: %[[boundBox:.*]] = fir.absent !fir.box<none> |
| 66 | +! CHECK: %[[shiftBox:.*]] = fir.embox %arg1 : (!fir.ref<i32>) -> !fir.box<i32> |
| 67 | +! CHECK: %[[resIRBox:.*]] = fir.convert %[[resBox]] : (!fir.ref<!fir.box<!fir.heap<!fir.array<?x?x!fir.char<1,?>>>>>) -> !fir.ref<!fir.box<none>> |
| 68 | +! CHECK: %[[arrayBoxNone:.*]] = fir.convert %[[arrayBox]] : (!fir.box<!fir.array<3x3x!fir.char<1,4>>>) -> !fir.box<none> |
| 69 | +! CHECK: %[[shiftBoxNone:.*]] = fir.convert %[[shiftBox]] : (!fir.box<i32>) -> !fir.box<none> |
| 70 | +! CHECK: %[[tmp:.*]] = fir.call @_FortranAEoshift(%[[resIRBox]], %[[arrayBoxNone]], %[[shiftBoxNone]], %[[boundBox]], %[[dim]], {{.*}}, {{.*}}) : (!fir.ref<!fir.box<none>>, !fir.box<none>, !fir.box<none>, !fir.box<none>, i32, !fir.ref<i8>, i32) -> none |
| 71 | +! CHECK: fir.array_merge_store %[[resLoad]], {{.*}} to %[[res]] : !fir.array<3x3x!fir.char<1,4>>, !fir.array<3x3x!fir.char<1,4>>, !fir.ref<!fir.array<3x3x!fir.char<1,4>>> |
| 72 | +end subroutine eoshift_test3 |
0 commit comments