Compiler was rewriting SIZE(PACK(x, MASK)) to COUNT(MASK). It was wrapping the COUNT call without a KIND argument (leading to INTEGER(4) result in the characteristics) in an Expr<ExtentType> (implying INTEGER(8) result), this lead to inconsistencies that later hit verifier errors in lowering. Set the KIND argument to the KIND of ExtentType to ensure the built expression is consistent. This requires giving access to some safe place where the "kind" name can be saved and turned into a CharBlock (count has a DIM argument that require using the KIND keyword here). For the FoldingContext that belong to SemanticsContext, this is the same string set as the one used by SemanticsContext for similar purposes.
9 lines
263 B
Fortran
9 lines
263 B
Fortran
! RUN: %flang_fc1 -fdebug-unparse %s 2>&1 | FileCheck %s
|
|
|
|
subroutine test_pack_size_rewrite(x, mask)
|
|
real :: x(:)
|
|
logical, intent(in) :: mask(:)
|
|
! CHECK: CALL test(count(mask,kind=8_8))
|
|
call test(size(pack(x, mask), dim=1, kind=8))
|
|
end subroutine
|