Skip to content

Commit 2aabe23

Browse files
committed
Use the length of the box instead of reconstructing it.
1 parent f69d30f commit 2aabe23

File tree

2 files changed

+8
-14
lines changed

2 files changed

+8
-14
lines changed

flang/lib/Lower/ConvertExpr.cpp

Lines changed: 4 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -4675,16 +4675,9 @@ class ArrayExprLowering {
46754675
static ExtValue convertAdjustedType(fir::FirOpBuilder &builder,
46764676
mlir::Location loc, mlir::Type toType,
46774677
const ExtValue &exv) {
4678-
auto lenFromBufferType = [&](mlir::Type ty) {
4679-
return builder.create<mlir::ConstantIndexOp>(
4680-
loc, fir::dyn_cast_ptrEleTy(ty).cast<fir::CharacterType>().getLen());
4681-
};
46824678
return exv.match(
46834679
[&](const fir::CharBoxValue &cb) -> ExtValue {
4684-
auto typeParams = fir::getTypeParams(exv);
4685-
auto len = typeParams.size() > 0
4686-
? typeParams[0]
4687-
: lenFromBufferType(cb.getBuffer().getType());
4680+
auto len = cb.getLen();
46884681
auto mem =
46894682
builder.create<fir::AllocaOp>(loc, toType, mlir::ValueRange{len});
46904683
fir::CharBoxValue result(mem, len);
@@ -4706,7 +4699,9 @@ class ArrayExprLowering {
47064699
return [=](IterSpace iters) -> ExtValue {
47074700
auto exv = lambda(iters);
47084701
auto val = fir::getBase(exv);
4709-
if (elementTypeWasAdjusted(val.getType()))
4702+
auto valTy = val.getType();
4703+
if (elementTypeWasAdjusted(valTy) &&
4704+
!(fir::isa_ref_type(valTy) && fir::isa_integer(ty)))
47104705
return convertAdjustedType(builder, loc, ty, exv);
47114706
return builder.createConvert(loc, ty, val);
47124707
};

flang/test/Lower/array-expression.f90

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -816,13 +816,12 @@ subroutine test19g(a,b,i)
816816
! CHECK: %[[VAL_25:.*]] = subi %[[VAL_14]], %[[VAL_23]] : index
817817
! CHECK: %[[VAL_26:.*]] = fir.do_loop %[[VAL_27:.*]] = %[[VAL_24]] to %[[VAL_25]] step %[[VAL_23]] unordered iter_args(%[[VAL_28:.*]] = %[[VAL_12]]) -> (!fir.array<70x!fir.char<4,?>>) {
818818
! CHECK: %[[VAL_29:.*]] = fir.array_access %[[VAL_20]], %[[VAL_27]] : (!fir.array<140x!fir.char<2,13>>, index) -> !fir.ref<!fir.char<2,13>>
819-
! CHECK: %[[VAL_30:.*]] = constant 13 : index
820-
! CHECK: %[[VAL_31:.*]] = fir.alloca !fir.char<4,?>(%[[VAL_30]] : index)
821-
! CHECK: %[[VAL_32:.*]] = cmpi slt, %[[VAL_30]], %[[VAL_4]] : index
822-
! CHECK: %[[VAL_33:.*]] = select %[[VAL_32]], %[[VAL_30]], %[[VAL_4]] : index
819+
! CHECK: %[[VAL_31:.*]] = fir.alloca !fir.char<4,?>(%[[VAL_4]] : index)
820+
! CHECK: %[[VAL_32:.*]] = cmpi slt, %[[VAL_4]], %[[VAL_4]] : index
821+
! CHECK: %[[VAL_33:.*]] = select %[[VAL_32]], %[[VAL_4]], %[[VAL_4]] : index
823822
! CHECK: fir.char_convert %[[VAL_29]] for %[[VAL_33]] to %[[VAL_31]] : !fir.ref<!fir.char<2,13>>, index, !fir.ref<!fir.char<4,?>>
824823
! CHECK: %[[VAL_34:.*]] = constant 1 : index
825-
! CHECK: %[[VAL_35:.*]] = subi %[[VAL_30]], %[[VAL_34]] : index
824+
! CHECK: %[[VAL_35:.*]] = subi %[[VAL_4]], %[[VAL_34]] : index
826825
! CHECK: %[[VAL_36:.*]] = constant 32 : i32
827826
! CHECK: %[[VAL_37:.*]] = fir.undefined !fir.char<4>
828827
! CHECK: %[[VAL_38:.*]] = fir.insert_value %[[VAL_37]], %[[VAL_36]], [0 : index] : (!fir.char<4>, i32) -> !fir.char<4>

0 commit comments

Comments
 (0)