Skip to content

Commit eac8473

Browse files
authored
Merge pull request #1045 from schweitzpgi/ch-m1a
Fix fir.coordinate_of op use with char<kind,?> types.
2 parents d3c498a + 735c474 commit eac8473

File tree

3 files changed

+28
-15
lines changed

3 files changed

+28
-15
lines changed

flang/lib/Lower/ConvertExpr.cpp

Lines changed: 15 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1481,8 +1481,22 @@ class ScalarExprLowering {
14811481
delta = builder.create<mlir::MulIOp>(loc, delta, ext);
14821482
++dim;
14831483
}
1484-
return builder.create<fir::CoordinateOp>(
1484+
auto origRefTy = refTy;
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+
auto coor = builder.create<fir::CoordinateOp>(
14851497
loc, refTy, base, llvm::ArrayRef<mlir::Value>{total});
1498+
// Convert to expected, original type after address arithmetic.
1499+
return builder.createConvert(loc, origRefTy, coor);
14861500
};
14871501
return array.match(
14881502
[&](const fir::ArrayBoxValue &arr) -> ExtValue {

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)