1! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s 2 3! Test that IO item list are lowered and passed correctly 4 5! CHECK-LABEL: func @_QPpass_assumed_len_char_unformatted_io 6subroutine pass_assumed_len_char_unformatted_io(c) 7 character(*) :: c 8 ! CHECK: %[[unbox:.*]]:2 = fir.unboxchar %arg0 : (!fir.boxchar<1>) -> (!fir.ref<!fir.char<1,?>>, index) 9 write(1, rec=1) c 10 ! CHECK: %[[box:.*]] = fir.embox %[[unbox]]#0 typeparams %[[unbox]]#1 : (!fir.ref<!fir.char<1,?>>, index) -> !fir.box<!fir.char<1,?>> 11 ! CHECK: %[[castedBox:.*]] = fir.convert %[[box]] : (!fir.box<!fir.char<1,?>>) -> !fir.box<none> 12 ! CHECK: fir.call @_FortranAioOutputDescriptor(%{{.*}}, %[[castedBox]]) {{.*}}: (!fir.ref<i8>, !fir.box<none>) -> i1 13end 14 15! CHECK-LABEL: func @_QPpass_assumed_len_char_array 16subroutine pass_assumed_len_char_array(carray) 17 character(*) :: carray(2, 3) 18 ! CHECK-DAG: %[[unboxed:.*]]:2 = fir.unboxchar %arg0 : (!fir.boxchar<1>) -> (!fir.ref<!fir.char<1,?>>, index) 19 ! CHECK-DAG: %[[buffer:.*]] = fir.convert %[[unboxed]]#0 : (!fir.ref<!fir.char<1,?>>) -> !fir.ref<!fir.array<2x3x!fir.char<1,?>>> 20 ! CHECK-DAG: %[[c2:.*]] = arith.constant 2 : index 21 ! CHECK-DAG: %[[c3:.*]] = arith.constant 3 : index 22 ! CHECK-DAG: %[[shape:.*]] = fir.shape %[[c2]], %[[c3]] : (index, index) -> !fir.shape<2> 23 ! CHECK: %[[box:.*]] = fir.embox %[[buffer]](%[[shape]]) typeparams %[[unboxed]]#1 : (!fir.ref<!fir.array<2x3x!fir.char<1,?>>>, !fir.shape<2>, index) -> !fir.box<!fir.array<2x3x!fir.char<1,?>>> 24 ! CHECK: %[[descriptor:.*]] = fir.convert %[[box]] : (!fir.box<!fir.array<2x3x!fir.char<1,?>>>) -> !fir.box<none> 25 ! CHECK: fir.call @_FortranAioOutputDescriptor(%{{.*}}, %[[descriptor]]) {{.*}}: (!fir.ref<i8>, !fir.box<none>) -> i1 26 print *, carray 27end 28 29! CHECK-LABEL: func @_QPpass_array_slice_read( 30! CHECK-SAME: %[[VAL_0:.*]]: !fir.box<!fir.array<?xf32>>{{.*}}) { 31! CHECK: %[[VAL_1:.*]] = arith.constant 5 : i32 32! CHECK: %[[VAL_2:.*]] = fir.address_of(@_QQclX{{.*}}) : !fir.ref<!fir.char<1, 33! CHECK: %[[VAL_3:.*]] = fir.convert %[[VAL_2]] : (!fir.ref<!fir.char<1,{{[0-9]+}}>>) -> !fir.ref<i8> 34! CHECK: %[[VAL_4:.*]] = arith.constant {{[0-9]+}} : i32 35! CHECK: %[[VAL_5:.*]] = fir.call @_FortranAioBeginExternalListInput(%[[VAL_1]], %[[VAL_3]], %[[VAL_4]]) {{.*}}: (i32, !fir.ref<i8>, i32) -> !fir.ref<i8> 36! CHECK: %[[VAL_6:.*]] = arith.constant 101 : i64 37! CHECK: %[[VAL_7:.*]] = fir.convert %[[VAL_6]] : (i64) -> index 38! CHECK: %[[VAL_8:.*]] = arith.constant 2 : i64 39! CHECK: %[[VAL_9:.*]] = fir.convert %[[VAL_8]] : (i64) -> index 40! CHECK: %[[VAL_10:.*]] = arith.constant 200 : i64 41! CHECK: %[[VAL_11:.*]] = fir.convert %[[VAL_10]] : (i64) -> index 42! CHECK: %[[VAL_12:.*]] = fir.slice %[[VAL_7]], %[[VAL_11]], %[[VAL_9]] : (index, index, index) -> !fir.slice<1> 43! CHECK: %[[VAL_13:.*]] = fir.rebox %[[VAL_0]] {{\[}}%[[VAL_12]]] : (!fir.box<!fir.array<?xf32>>, !fir.slice<1>) -> !fir.box<!fir.array<50xf32>> 44! CHECK: %[[VAL_14:.*]] = fir.convert %[[VAL_13]] : (!fir.box<!fir.array<50xf32>>) -> !fir.box<none> 45! CHECK: %[[VAL_15:.*]] = fir.call @_FortranAioInputDescriptor(%[[VAL_5]], %[[VAL_14]]) {{.*}}: (!fir.ref<i8>, !fir.box<none>) -> i1 46! CHECK: %[[VAL_16:.*]] = fir.call @_FortranAioEndIoStatement(%[[VAL_5]]) {{.*}}: (!fir.ref<i8>) -> i32 47! CHECK: return 48! CHECK: } 49 50subroutine pass_array_slice_read(x) 51 real :: x(:) 52 read(5, *) x(101:200:2) 53end 54 55! CHECK-LABEL: func @_QPpass_array_slice_write( 56! CHECK-SAME: %[[VAL_0:.*]]: !fir.box<!fir.array<?xf32>>{{.*}}) { 57! CHECK: %[[VAL_1:.*]] = arith.constant 1 : i32 58! CHECK: %[[VAL_2:.*]] = fir.address_of(@_QQclX{{.*}}) : !fir.ref<!fir.char<1, 59! CHECK: %[[VAL_3:.*]] = fir.convert %[[VAL_2]] : (!fir.ref<!fir.char<1,{{[0-9]+}}>>) -> !fir.ref<i8> 60! CHECK: %[[VAL_4:.*]] = arith.constant {{[0-9]+}} : i32 61! CHECK: %[[VAL_5:.*]] = fir.call @_FortranAioBeginUnformattedOutput(%[[VAL_1]], %[[VAL_3]], %[[VAL_4]]) {{.*}}: (i32, !fir.ref<i8>, i32) -> !fir.ref<i8> 62! CHECK: %[[VAL_6:.*]] = arith.constant 1 : i32 63! CHECK: %[[VAL_7:.*]] = fir.convert %[[VAL_6]] : (i32) -> i64 64! CHECK: %[[VAL_8:.*]] = fir.call @_FortranAioSetRec(%[[VAL_5]], %[[VAL_7]]) {{.*}}: (!fir.ref<i8>, i64) -> i1 65! CHECK: %[[VAL_9:.*]] = arith.constant 101 : i64 66! CHECK: %[[VAL_10:.*]] = fir.convert %[[VAL_9]] : (i64) -> index 67! CHECK: %[[VAL_11:.*]] = arith.constant 2 : i64 68! CHECK: %[[VAL_12:.*]] = fir.convert %[[VAL_11]] : (i64) -> index 69! CHECK: %[[VAL_13:.*]] = arith.constant 200 : i64 70! CHECK: %[[VAL_14:.*]] = fir.convert %[[VAL_13]] : (i64) -> index 71! CHECK: %[[VAL_15:.*]] = fir.slice %[[VAL_10]], %[[VAL_14]], %[[VAL_12]] : (index, index, index) -> !fir.slice<1> 72! CHECK: %[[VAL_16:.*]] = fir.rebox %[[VAL_0]] {{\[}}%[[VAL_15]]] : (!fir.box<!fir.array<?xf32>>, !fir.slice<1>) -> !fir.box<!fir.array<50xf32>> 73! CHECK: %[[VAL_17:.*]] = fir.convert %[[VAL_16]] : (!fir.box<!fir.array<50xf32>>) -> !fir.box<none> 74! CHECK: %[[VAL_18:.*]] = fir.call @_FortranAioOutputDescriptor(%[[VAL_5]], %[[VAL_17]]) {{.*}}: (!fir.ref<i8>, !fir.box<none>) -> i1 75! CHECK: %[[VAL_19:.*]] = fir.call @_FortranAioEndIoStatement(%[[VAL_5]]) {{.*}}: (!fir.ref<i8>) -> i32 76! CHECK: return 77! CHECK: } 78 79subroutine pass_array_slice_write(x) 80 real :: x(:) 81 write(1, rec=1) x(101:200:2) 82end 83 84 85! CHECK-LABEL: func @_QPpass_vector_subscript_write( 86! CHECK-SAME: %[[x:.*]]: !fir.ref<!fir.array<100xf32>>{{.*}}, %[[j:.*]]: !fir.ref<!fir.array<10xi32>>{{.*}}) 87subroutine pass_vector_subscript_write(x, j) 88 ! Check that a temp is made for array with vector subscript in output IO. 89 integer :: j(10) 90 real :: x(100) 91 ! CHECK: %[[jload:.*]] = fir.array_load %[[j]](%{{.*}}) : (!fir.ref<!fir.array<10xi32>>, !fir.shape<1>) -> !fir.array<10xi32> 92 ! CHECK: %[[xload:.*]] = fir.array_load %[[x]](%{{.*}}) : (!fir.ref<!fir.array<100xf32>>, !fir.shape<1>) -> !fir.array<100xf32> 93 ! CHECK: %[[temp:.*]] = fir.allocmem !fir.array<10xf32> 94 ! CHECK: %[[tempload:.*]] = fir.array_load %[[temp]](%{{.*}}) : (!fir.heap<!fir.array<10xf32>>, !fir.shape<1>) -> !fir.array<10xf32> 95 ! CHECK: %[[copy:.*]] = fir.do_loop 96 ! CHECK: %[[jfetch:.*]] = fir.array_fetch %[[jload]], %{{.*}} : (!fir.array<10xi32>, index) -> i32 97 ! CHECK: %[[jcast:.*]] = fir.convert %[[jfetch]] : (i32) -> index 98 ! CHECK: %[[jindex:.*]] = arith.subi %[[jcast]], %c1{{.*}} : index 99 ! CHECK: %[[xfetch:.*]] = fir.array_fetch %[[xload]], %[[jindex]] : (!fir.array<100xf32>, index) -> f32 100 ! CHECK: %[[update:.*]] = fir.array_update %{{.*}}, %[[xfetch]], %{{.*}} : (!fir.array<10xf32>, f32, index) -> !fir.array<10xf32> 101 ! CHECK: fir.result %[[update]] : !fir.array<10xf32> 102 ! CHECK: } 103 ! CHECK: fir.array_merge_store %[[tempload]], %[[copy]] to %[[temp]] : !fir.array<10xf32>, !fir.array<10xf32>, !fir.heap<!fir.array<10xf32>> 104 ! CHECK: %[[embox:.*]] = fir.embox %[[temp]](%{{.*}}) : (!fir.heap<!fir.array<10xf32>>, !fir.shape<1>) -> !fir.box<!fir.array<10xf32>> 105 ! CHECK: %[[boxCast:.*]] = fir.convert %[[embox]] : (!fir.box<!fir.array<10xf32>>) -> !fir.box<none> 106 ! CHECK: fir.call @_FortranAioOutputDescriptor(%{{.*}}, %[[boxCast]]) {{.*}}: (!fir.ref<i8>, !fir.box<none>) -> i1 107 ! CHECK: fir.freemem %[[temp]] : !fir.heap<!fir.array<10xf32>> 108 write(1, rec=1) x(j) 109end 110