mirror of
https://github.com/llvm/llvm-project.git
synced 2025-04-17 03:26:48 +00:00

The lowering produces fir.dummy_scope operation if the current function has dummy arguments. Each hlfir.declare generated for a dummy argument is then using the result of fir.dummy_scope as its dummy_scope operand. This is only done for HLFIR. I was not able to find a reliable way to identify dummy symbols in `genDeclareSymbol`, so I added a set of registered dummy symbols that is alive during the variables instantiation for the current function. The set is initialized during the mapping of the dummy argument symbols to their MLIR values. It is reset right after all variables are instantiated - this is done to avoid generating hlfir.declare operations with dummy_scope for the clones of the dummy symbols (e.g. this happens with OpenMP privatization). If this can be done in a cleaner way, please advise.
33 lines
2.9 KiB
Fortran
33 lines
2.9 KiB
Fortran
! RUN: bbc -emit-hlfir %s -o - | FileCheck %s
|
|
|
|
subroutine test_c1_to_c4(c4, c1)
|
|
character(len=*, kind=4) :: c4
|
|
character(len=*, kind=1) :: c1
|
|
c4 = c1
|
|
end subroutine
|
|
|
|
subroutine test_c4_to_c1(c4, c1)
|
|
character(len=*, kind=4) :: c4
|
|
character(len=*, kind=1) :: c1
|
|
c1 = c4
|
|
end subroutine
|
|
|
|
! CHECK: func.func @_QPtest_c1_to_c4(%[[ARG0:.*]]: !fir.boxchar<4> {fir.bindc_name = "c4"}, %[[ARG1:.*]]: !fir.boxchar<1> {fir.bindc_name = "c1"}) {
|
|
! CHECK: %[[VAL_0:.*]]:2 = fir.unboxchar %[[ARG1]] : (!fir.boxchar<1>) -> (!fir.ref<!fir.char<1,?>>, index)
|
|
! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]]#0 typeparams %[[VAL_0]]#1 dummy_scope %{{[0-9]+}} {uniq_name = "_QFtest_c1_to_c4Ec1"} : (!fir.ref<!fir.char<1,?>>, index, !fir.dscope) -> (!fir.boxchar<1>, !fir.ref<!fir.char<1,?>>)
|
|
! CHECK: %[[VAL_2:.*]]:2 = fir.unboxchar %[[ARG0]] : (!fir.boxchar<4>) -> (!fir.ref<!fir.char<4,?>>, index)
|
|
! CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %[[VAL_2]]#0 typeparams %[[VAL_2]]#1 dummy_scope %{{[0-9]+}} {uniq_name = "_QFtest_c1_to_c4Ec4"} : (!fir.ref<!fir.char<4,?>>, index, !fir.dscope) -> (!fir.boxchar<4>, !fir.ref<!fir.char<4,?>>)
|
|
! CHECK: %[[VAL_4:.*]] = fir.alloca !fir.char<4,?>(%[[VAL_0]]#1 : index)
|
|
! CHECK: fir.char_convert %[[VAL_1]]#1 for %[[VAL_0]]#1 to %[[VAL_4:.*]] : !fir.ref<!fir.char<1,?>>, index, !fir.ref<!fir.char<4,?>>
|
|
|
|
! CHECK: func.func @_QPtest_c4_to_c1(%[[ARG0:.*]]: !fir.boxchar<4> {fir.bindc_name = "c4"}, %[[ARG1:.*]]: !fir.boxchar<1> {fir.bindc_name = "c1"}) {
|
|
! CHECK: %[[VAL_0:.*]]:2 = fir.unboxchar %[[ARG1]] : (!fir.boxchar<1>) -> (!fir.ref<!fir.char<1,?>>, index)
|
|
! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]]#0 typeparams %[[VAL_0]]#1 dummy_scope %{{[0-9]+}} {uniq_name = "_QFtest_c4_to_c1Ec1"} : (!fir.ref<!fir.char<1,?>>, index, !fir.dscope) -> (!fir.boxchar<1>, !fir.ref<!fir.char<1,?>>)
|
|
! CHECK: %[[VAL_2:.*]]:2 = fir.unboxchar %[[ARG0]] : (!fir.boxchar<4>) -> (!fir.ref<!fir.char<4,?>>, index)
|
|
! CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %[[VAL_2]]#0 typeparams %[[VAL_2]]#1 dummy_scope %{{[0-9]+}} {uniq_name = "_QFtest_c4_to_c1Ec4"} : (!fir.ref<!fir.char<4,?>>, index, !fir.dscope) -> (!fir.boxchar<4>, !fir.ref<!fir.char<4,?>>)
|
|
! CHECK: %[[C4:.*]] = arith.constant 4 : index
|
|
! CHECK: %[[VAL_4:.*]] = arith.muli %[[VAL_2]]#1, %[[C4]] : index
|
|
! CHECK: %[[VAL_5:.*]] = fir.alloca !fir.char<1,?>(%[[VAL_4]] : index)
|
|
! CHECK: fir.char_convert %[[VAL_3]]#1 for %[[VAL_2]]#1 to %[[VAL_5:.*]] : !fir.ref<!fir.char<4,?>>, index, !fir.ref<!fir.char<1,?>>
|
|
! CHECK: %[[VAL_6:.*]]:2 = hlfir.declare %[[VAL_5]] typeparams %[[VAL_2]]#1 {uniq_name = ".temp.kindconvert"} : (!fir.ref<!fir.char<1,?>>, index) -> (!fir.boxchar<1>, !fir.ref<!fir.char<1,?>>)
|