Skip to content

Commit 4b4021a

Browse files
committed
Fix fir.coordinate_of op use with char<kind,?> types.
The coordinate_of op requires a constant sized type, so it will not work correctly if used with fir.char with unknown length. The code was already computing the correct offsets from runtime values, but the type was not being converted resulting in internal errors in code gen.
1 parent d471d6f commit 4b4021a

File tree

3 files changed

+26
-14
lines changed

3 files changed

+26
-14
lines changed

flang/lib/Lower/ConvertExpr.cpp

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1481,6 +1481,19 @@ class ScalarExprLowering {
14811481
delta = builder.create<mlir::MulIOp>(loc, delta, ext);
14821482
++dim;
14831483
}
1484+
#if 1
1485+
if (fir::factory::CharacterExprHelper::isCharacterScalar(refTy)) {
1486+
auto chTy = fir::factory::CharacterExprHelper::getCharacterType(refTy);
1487+
if (fir::characterWithDynamicLen(chTy)) {
1488+
auto ctx = builder.getContext();
1489+
auto kind = fir::factory::CharacterExprHelper::getCharacterKind(chTy);
1490+
auto singleTy = fir::CharacterType::getSingleton(ctx, kind);
1491+
refTy = builder.getRefType(singleTy);
1492+
auto seqRefTy = builder.getRefType(builder.getVarLenSeqTy(singleTy));
1493+
base = builder.createConvert(loc, seqRefTy, base);
1494+
}
1495+
}
1496+
#endif
14841497
return builder.create<fir::CoordinateOp>(
14851498
loc, refTy, base, llvm::ArrayRef<mlir::Value>{total});
14861499
};

flang/lib/Optimizer/Builder/Character.cpp

Lines changed: 5 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -26,9 +26,8 @@ static fir::CharacterType recoverCharacterType(mlir::Type type) {
2626
if (auto boxType = type.dyn_cast<fir::BoxCharType>())
2727
return boxType.getEleTy();
2828
while (true) {
29-
if (auto pointedType = fir::dyn_cast_ptrEleTy(type))
30-
type = pointedType;
31-
else if (auto boxTy = type.dyn_cast<fir::BoxType>())
29+
type = fir::unwrapRefType(type);
30+
if (auto boxTy = type.dyn_cast<fir::BoxType>())
3231
type = boxTy.getEleTy();
3332
else
3433
break;
@@ -643,15 +642,11 @@ bool fir::factory::CharacterExprHelper::isCharacterLiteral(mlir::Type type) {
643642
bool fir::factory::CharacterExprHelper::isCharacterScalar(mlir::Type type) {
644643
if (type.isa<fir::BoxCharType>())
645644
return true;
646-
if (auto pointedType = fir::dyn_cast_ptrEleTy(type))
647-
type = pointedType;
645+
type = fir::unwrapRefType(type);
648646
if (auto boxTy = type.dyn_cast<fir::BoxType>())
649647
type = boxTy.getEleTy();
650-
if (auto pointedType = fir::dyn_cast_ptrEleTy(type))
651-
type = pointedType;
652-
if (auto seqType = type.dyn_cast<fir::SequenceType>())
653-
return false;
654-
return fir::isa_char(type);
648+
type = fir::unwrapRefType(type);
649+
return !type.isa<fir::SequenceType>() && fir::isa_char(type);
655650
}
656651

657652
fir::KindTy

flang/test/Lower/derived-allocatable-components.f90

Lines changed: 8 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -249,8 +249,10 @@ subroutine ref_scalar_def_char_a(a0_0, a1_0, a0_1, a1_1)
249249
! CHECK: %[[sub:.*]] = subi %[[c7]], %[[dims]]#0 : index
250250
! CHECK: %[[mul:.*]] = muli %[[len]], %[[sub]] : index
251251
! CHECK: %[[offset:.*]] = addi %[[mul]], %c0{{.*}} : index
252-
! CHECK: %[[addr:.*]] = fir.coordinate_of %[[cast]], %[[offset]]
253-
! CHECK: %[[boxchar:.*]] = fir.emboxchar %[[addr]], %[[len]]
252+
! CHECK: %[[cnvt:.*]] = fir.convert %[[cast]]
253+
! CHECK: %[[addr:.*]] = fir.coordinate_of %[[cnvt]], %[[offset]]
254+
! CHECK: %[[cnvt:.*]] = fir.convert %[[addr]]
255+
! CHECK: %[[boxchar:.*]] = fir.emboxchar %[[cnvt]], %[[len]]
254256
! CHECK: fir.call @_QPtakes_char_scalar(%[[boxchar]])
255257
call takes_char_scalar(a1_0%p(7))
256258

@@ -267,8 +269,10 @@ subroutine ref_scalar_def_char_a(a0_0, a1_0, a0_1, a1_1)
267269
! CHECK: %[[sub:.*]] = subi %[[c7]], %[[dims]]#0 : index
268270
! CHECK: %[[mul:.*]] = muli %[[len]], %[[sub]] : index
269271
! CHECK: %[[offset:.*]] = addi %[[mul]], %c0{{.*}} : index
270-
! CHECK: %[[addr:.*]] = fir.coordinate_of %[[cast]], %[[offset]]
271-
! CHECK: %[[boxchar:.*]] = fir.emboxchar %[[addr]], %[[len]]
272+
! CHECK: %[[cnvt:.*]] = fir.convert %[[cast]]
273+
! CHECK: %[[addr:.*]] = fir.coordinate_of %[[cnvt]], %[[offset]]
274+
! CHECK: %[[cnvt:.*]] = fir.convert %[[addr]]
275+
! CHECK: %[[boxchar:.*]] = fir.emboxchar %[[cnvt]], %[[len]]
272276
! CHECK: fir.call @_QPtakes_char_scalar(%[[boxchar]])
273277
call takes_char_scalar(a1_1(5)%p(7))
274278

0 commit comments

Comments
 (0)