16a7da2e3SjeanPerier! RUN: bbc -emit-hlfir %s -o - | FileCheck %s 26a7da2e3SjeanPerier! Test lowering of extension of SOURCE allocation (non deferred length 36a7da2e3SjeanPerier! of character allocate-object need not to match the SOURCE length, truncation 46a7da2e3SjeanPerier! and padding are performed instead as in assignments). 56a7da2e3SjeanPerier 66a7da2e3SjeanPeriersubroutine test() 76a7da2e3SjeanPerier! CHECK-LABEL: func.func @_QPtest() { 86a7da2e3SjeanPerier! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}} {{.*}}Ec_deferred 96a7da2e3SjeanPerier! CHECK: %[[VAL_9:.*]]:2 = hlfir.declare %{{.*}} typeparams %[[VAL_6:.*]] {{.*}}Ec_longer 106a7da2e3SjeanPerier! CHECK: %[[VAL_14:.*]]:2 = hlfir.declare %{{.*}} typeparams %[[VAL_11:.*]] {{.*}}Ec_shorter 116a7da2e3SjeanPerier! CHECK: %[[VAL_17:.*]]:2 = hlfir.declare %{{.*}} typeparams %[[VAL_16:.*]] {{{.*}}Ec_source 126a7da2e3SjeanPerier character(5) :: c_source = "hello" 136a7da2e3SjeanPerier character(2), allocatable :: c_shorter 146a7da2e3SjeanPerier character(:), allocatable :: c_deferred 156a7da2e3SjeanPerier character(7), allocatable :: c_longer 166a7da2e3SjeanPerier! CHECK: %[[VAL_18:.*]] = arith.constant false 176a7da2e3SjeanPerier! CHECK: %[[VAL_22:.*]] = fir.embox %[[VAL_17]]#1 : (!fir.ref<!fir.char<1,5>>) -> !fir.box<!fir.char<1,5>> 186a7da2e3SjeanPerier 196a7da2e3SjeanPerier! CHECK: %[[VAL_23:.*]] = fir.convert %[[VAL_14]]#1 : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,2>>>>) -> !fir.ref<!fir.box<none>> 206a7da2e3SjeanPerier! CHECK: %[[VAL_24:.*]] = fir.convert %[[VAL_22]] : (!fir.box<!fir.char<1,5>>) -> !fir.box<none> 216a7da2e3SjeanPerier! CHECK: %[[VAL_26:.*]] = fir.call @_FortranAAllocatableAllocateSource(%[[VAL_23]], %[[VAL_24]], %[[VAL_18]] 226a7da2e3SjeanPerier 236a7da2e3SjeanPerier! CHECK: %[[VAL_27:.*]] = fir.convert %[[VAL_4]]#1 : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>) -> !fir.ref<!fir.box<none>> 246a7da2e3SjeanPerier! CHECK: %[[VAL_28:.*]] = fir.convert %[[VAL_16]] : (index) -> i64 256a7da2e3SjeanPerier! CHECK: %[[VAL_29:.*]] = arith.constant 1 : i32 266a7da2e3SjeanPerier! CHECK: %[[VAL_30:.*]] = arith.constant 0 : i32 276a7da2e3SjeanPerier! CHECK: %[[VAL_31:.*]] = arith.constant 0 : i32 28*12ba74e1SValentin Clement (バレンタイン クレメン)! CHECK: fir.call @_FortranAAllocatableInitCharacterForAllocate(%[[VAL_27]], %[[VAL_28]], %[[VAL_29]], %[[VAL_30]], %[[VAL_31]] 296a7da2e3SjeanPerier! CHECK: %[[VAL_33:.*]] = fir.convert %[[VAL_4]]#1 : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>) -> !fir.ref<!fir.box<none>> 306a7da2e3SjeanPerier! CHECK: %[[VAL_34:.*]] = fir.convert %[[VAL_22]] : (!fir.box<!fir.char<1,5>>) -> !fir.box<none> 316a7da2e3SjeanPerier! CHECK: %[[VAL_36:.*]] = fir.call @_FortranAAllocatableAllocateSource(%[[VAL_33]], %[[VAL_34]], %[[VAL_18]], 326a7da2e3SjeanPerier 336a7da2e3SjeanPerier! CHECK-NOT: AllocatableInitCharacterForAllocate 346a7da2e3SjeanPerier! CHECK: %[[VAL_37:.*]] = fir.convert %[[VAL_9]]#1 : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,7>>>>) -> !fir.ref<!fir.box<none>> 356a7da2e3SjeanPerier! CHECK: %[[VAL_38:.*]] = fir.convert %[[VAL_22]] : (!fir.box<!fir.char<1,5>>) -> !fir.box<none> 366a7da2e3SjeanPerier! CHECK: %[[VAL_40:.*]] = fir.call @_FortranAAllocatableAllocateSource(%[[VAL_37]], %[[VAL_38]], %[[VAL_18]], 376a7da2e3SjeanPerier allocate(c_shorter, c_deferred, c_longer, source=c_source) 386a7da2e3SjeanPerier 396a7da2e3SjeanPerier! Expect at runtime: 406a7da2e3SjeanPerier! ZZheZZ 416a7da2e3SjeanPerier! ZZhelloZZ 426a7da2e3SjeanPerier! ZZhello ZZ 436a7da2e3SjeanPerier write(*,"('ZZ',A,'ZZ')") c_shorter 446a7da2e3SjeanPerier write(*,"('ZZ',A,'ZZ')") c_deferred 456a7da2e3SjeanPerier write(*,"('ZZ',A,'ZZ')") c_longer 466a7da2e3SjeanPerierend subroutine 476a7da2e3SjeanPerier 486a7da2e3SjeanPerier call test() 496a7da2e3SjeanPerierend 50