1! Test lowering of character array constructors to HLFIR. 2! RUN: bbc -emit-hlfir -o - %s | FileCheck %s 3 4module chararrayctor 5 character(3), target :: ctarg1 = "abc" 6 character(3), target :: ctarg2 = "def" 7contains 8 9 subroutine test_pre_computed_length(c1, c2) 10 character(*) :: c1, c2 11 call takes_char([character(3):: c1, c2]) 12 end subroutine 13! CHECK-LABEL: func.func @_QMchararrayctorPtest_pre_computed_length( 14! CHECK: %[[VAL_9:.*]]:2 = hlfir.declare %{{.*}}Ec1" 15! CHECK: %[[VAL_11:.*]]:2 = hlfir.declare %{{.*}}Ec2" 16! CHECK: %[[VAL_12:.*]] = arith.constant 2 : index 17! CHECK: %[[VAL_13:.*]] = arith.constant 3 : i64 18! CHECK: %[[VAL_14:.*]] = fir.convert %[[VAL_13]] : (i64) -> index 19! CHECK: %[[VAL_15:.*]] = arith.constant 1 : index 20! CHECK: %[[VAL_15B:.*]] = arith.constant 1 : index 21! CHECK: %[[VAL_16:.*]] = fir.allocmem !fir.array<2x!fir.char<1,3>> {bindc_name = ".tmp.arrayctor", uniq_name = ""} 22! CHECK: %[[VAL_17:.*]] = fir.shape %[[VAL_12]] : (index) -> !fir.shape<1> 23! CHECK: %[[VAL_18:.*]]:2 = hlfir.declare %[[VAL_16]](%[[VAL_17]]) typeparams %[[VAL_14]] {uniq_name = ".tmp.arrayctor"} : (!fir.heap<!fir.array<2x!fir.char<1,3>>>, !fir.shape<1>, index) -> (!fir.heap<!fir.array<2x!fir.char<1,3>>>, !fir.heap<!fir.array<2x!fir.char<1,3>>>) 24! CHECK: %[[VAL_19:.*]] = arith.constant 3 : i64 25! CHECK: %[[VAL_20:.*]] = hlfir.set_length %[[VAL_9]]#0 len %[[VAL_19]] : (!fir.boxchar<1>, i64) -> !hlfir.expr<!fir.char<1,3>> 26! CHECK: %[[VAL_21:.*]] = arith.addi %[[VAL_15]], %[[VAL_15B]] : index 27! CHECK: %[[VAL_22:.*]] = hlfir.designate %[[VAL_18]]#0 (%[[VAL_15]]) typeparams %[[VAL_14]] : (!fir.heap<!fir.array<2x!fir.char<1,3>>>, index, index) -> !fir.ref<!fir.char<1,3>> 28! CHECK: hlfir.assign %[[VAL_20]] to %[[VAL_22]] : !hlfir.expr<!fir.char<1,3>>, !fir.ref<!fir.char<1,3>> 29! CHECK: %[[VAL_23:.*]] = arith.constant 3 : i64 30! CHECK: %[[VAL_24:.*]] = hlfir.set_length %[[VAL_11]]#0 len %[[VAL_23]] : (!fir.boxchar<1>, i64) -> !hlfir.expr<!fir.char<1,3>> 31! CHECK: %[[VAL_25:.*]] = hlfir.designate %[[VAL_18]]#0 (%[[VAL_21]]) typeparams %[[VAL_14]] : (!fir.heap<!fir.array<2x!fir.char<1,3>>>, index, index) -> !fir.ref<!fir.char<1,3>> 32! CHECK: hlfir.assign %[[VAL_24]] to %[[VAL_25]] : !hlfir.expr<!fir.char<1,3>>, !fir.ref<!fir.char<1,3>> 33! CHECK: %[[VAL_26:.*]] = arith.constant true 34! CHECK: %[[VAL_27:.*]] = hlfir.as_expr %[[VAL_18]]#0 move %[[VAL_26]] : (!fir.heap<!fir.array<2x!fir.char<1,3>>>, i1) -> !hlfir.expr<2x!fir.char<1,3>> 35! CHECK: fir.call @_QMchararrayctorPtakes_char 36! CHECK: hlfir.destroy %[[VAL_27]] : !hlfir.expr<2x!fir.char<1,3>> 37 38 subroutine test_dynamic_length() 39 call takes_char([char_pointer(1), char_pointer(2)]) 40 end subroutine 41! CHECK-LABEL: func.func @_QMchararrayctorPtest_dynamic_length() { 42! CHECK: %[[VAL_0:.*]] = fir.alloca !fir.box<!fir.ptr<!fir.char<1,?>>> {bindc_name = ".result"} 43! CHECK: %[[VAL_1:.*]] = fir.alloca !fir.box<!fir.ptr<!fir.char<1,?>>> {bindc_name = ".result"} 44! CHECK: %[[VAL_2:.*]] = fir.alloca !fir.array<10xi64> {bindc_name = ".rt.arrayctor.vector"} 45! CHECK: %[[VAL_3:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<2x!fir.char<1,?>>>> {bindc_name = ".tmp.arrayctor"} 46! CHECK: %[[VAL_10:.*]] = arith.constant 2 : index 47! CHECK: %[[VAL_11:.*]] = arith.constant 0 : index 48! CHECK: %[[VAL_12:.*]] = fir.zero_bits !fir.heap<!fir.array<2x!fir.char<1,?>>> 49! CHECK: %[[VAL_13:.*]] = fir.shape %[[VAL_10]] : (index) -> !fir.shape<1> 50! CHECK: %[[VAL_14:.*]] = fir.embox %[[VAL_12]](%[[VAL_13]]) typeparams %[[VAL_11]] : (!fir.heap<!fir.array<2x!fir.char<1,?>>>, !fir.shape<1>, index) -> !fir.box<!fir.heap<!fir.array<2x!fir.char<1,?>>>> 51! CHECK: fir.store %[[VAL_14]] to %[[VAL_3]] : !fir.ref<!fir.box<!fir.heap<!fir.array<2x!fir.char<1,?>>>>> 52! CHECK: %[[VAL_15:.*]] = arith.constant true 53! CHECK: %[[VAL_16:.*]] = fir.convert %[[VAL_2]] : (!fir.ref<!fir.array<10xi64>>) -> !fir.llvm_ptr<i8> 54! CHECK: %[[VAL_20:.*]] = fir.convert %[[VAL_3]] : (!fir.ref<!fir.box<!fir.heap<!fir.array<2x!fir.char<1,?>>>>>) -> !fir.ref<!fir.box<none>> 55! CHECK: fir.call @_FortranAInitArrayConstructorVector(%[[VAL_16]], %[[VAL_20]], %[[VAL_15]], %{{.*}}, %{{.*}}) {{.*}}: (!fir.llvm_ptr<i8>, !fir.ref<!fir.box<none>>, i1, !fir.ref<i8>, i32) -> () 56! CHECK: fir.call @_QMchararrayctorPchar_pointer( 57! CHECK: fir.call @_FortranAPushArrayConstructorValue(%[[VAL_16]], %{{.*}}) {{.*}}: (!fir.llvm_ptr<i8>, !fir.box<none>) -> () 58! CHECK: fir.call @_QMchararrayctorPchar_pointer( 59! CHECK: fir.call @_FortranAPushArrayConstructorValue(%[[VAL_16]], %{{.*}}) {{.*}}: (!fir.llvm_ptr<i8>, !fir.box<none>) -> () 60! CHECK: %[[VAL_45:.*]] = arith.constant true 61! CHECK: %[[VAL_46:.*]] = fir.load %[[VAL_3]] : !fir.ref<!fir.box<!fir.heap<!fir.array<2x!fir.char<1,?>>>>> 62! CHECK: %[[VAL_47:.*]] = hlfir.as_expr %[[VAL_46]] move %[[VAL_45]] : (!fir.box<!fir.heap<!fir.array<2x!fir.char<1,?>>>>, i1) -> !hlfir.expr<2x!fir.char<1,?>> 63! CHECK: fir.call @_QMchararrayctorPtakes_char( 64! CHECK: hlfir.destroy %[[VAL_47]] : !hlfir.expr<2x!fir.char<1,?>> 65 66 67! Code below is only relevant for end-to-end test validation purpose. 68 function char_pointer(i) 69 integer :: i 70 character(:), pointer :: char_pointer 71 if (i.eq.1) then 72 char_pointer => ctarg1 73 else 74 char_pointer => ctarg2 75 end if 76 end function 77 subroutine takes_char(c) 78 character(*) :: c(:) 79 print *, "got : ", c 80 end subroutine 81end module 82 83 use chararrayctor 84 print *, "expect: ab cde" 85 call test_pre_computed_length("ab", "cdefg") 86 print *, "expect: abcdef" 87 call test_dynamic_length() 88end 89 90subroutine test_set_length_sanitize(i, c1) 91 integer(8) :: i 92 character(*) :: c1 93 call takes_char([character(len=i):: c1]) 94end subroutine 95! CHECK-LABEL: func.func @_QPtest_set_length_sanitize( 96! CHECK: %[[VAL_2:.*]]:2 = hlfir.declare {{.*}}Ec1 97! CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %arg0 98! CHECK: %[[VAL_4:.*]] = fir.load %[[VAL_3]]#0 : !fir.ref<i64> 99! CHECK: %[[VAL_25:.*]] = fir.load %[[VAL_3]]#0 : !fir.ref<i64> 100! CHECK: %[[VAL_26:.*]] = arith.constant 0 : i64 101! CHECK: %[[VAL_27:.*]] = arith.cmpi sgt, %[[VAL_25]], %[[VAL_26]] : i64 102! CHECK: %[[VAL_28:.*]] = arith.select %[[VAL_27]], %[[VAL_25]], %[[VAL_26]] : i64 103! CHECK: %[[VAL_29:.*]] = hlfir.set_length %[[VAL_2]]#0 len %[[VAL_28]] : (!fir.boxchar<1>, i64) -> !hlfir.expr<!fir.char<1,?>> 104