Skip to content

Commit 9930973

Browse files
Ericschweitzpgi
authored andcommitted
Fix issue #504. Throw away some of the old work around code that's no longer needed. Update test to reflect the simpler fir that is now generated.
1 parent 283dfcc commit 9930973

File tree

2 files changed

+12
-36
lines changed

2 files changed

+12
-36
lines changed

flang/lib/Lower/ConvertExpr.cpp

Lines changed: 1 addition & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -276,38 +276,7 @@ class ExprLowering {
276276
fir::ExtendedValue genLoad(const fir::ExtendedValue &addr) {
277277
auto loc = getLoc();
278278
return addr.match(
279-
[&](const fir::CharBoxValue &box) -> fir::ExtendedValue {
280-
auto buffer = box.getBuffer();
281-
auto len = dyn_cast<mlir::ConstantOp>(box.getLen().getDefiningOp());
282-
if (!len) {
283-
// TODO: return an emboxchar?
284-
// Not sure an emboxchar would help, it would simply
285-
// indirects the memory reference, so it fakes the load and then
286-
// makes it harder to work with the character due to the
287-
// indirection. Solutions I see are:
288-
// 1. create a temp and returns a CharBoxValue pointing to it.
289-
// 2. create a dynamic vector fir type that can abstract 1.
290-
mlir::emitError(loc, "cannot load a variable length char");
291-
return {};
292-
}
293-
auto lenAttr = len.value().dyn_cast<mlir::IntegerAttr>();
294-
if (!lenAttr) {
295-
mlir::emitError(loc, "length must be integer");
296-
return {};
297-
}
298-
auto lenConst = lenAttr.getValue().getSExtValue();
299-
fir::SequenceType::Shape shape = {lenConst};
300-
auto baseTy =
301-
Fortran::lower::CharacterExprHelper::getCharacterType(box);
302-
auto charTy =
303-
builder.getRefType(fir::SequenceType::get(shape, baseTy));
304-
auto casted = builder.createConvert(loc, charTy, buffer);
305-
auto val = builder.create<fir::LoadOp>(loc, casted);
306-
return fir::CharBoxValue{val, box.getLen()};
307-
},
308-
[&](const fir::CharArrayBoxValue &v) -> fir::ExtendedValue {
309-
TODO("loading character array");
310-
},
279+
[](const fir::CharBoxValue &box) -> fir::ExtendedValue { return box; },
311280
[&](const fir::UnboxedValue &v) -> fir::ExtendedValue {
312281
return builder.create<fir::LoadOp>(loc, fir::getBase(v));
313282
},

flang/test/Lower/intrinsics.f90

Lines changed: 11 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -182,13 +182,20 @@ end subroutine iand_test
182182
subroutine ichar_test(c)
183183
character(1) :: c
184184
character :: str(10)
185-
! CHECK: %[[BOX:.*]] = fir.load %{{.*}} : !fir.ref<!fir.char<1>>
186-
! CHECK: %{{.*}} = fir.convert %[[BOX]] : (!fir.char<1>) -> i32
185+
! CHECK-DAG: %[[unbox:.*]]:2 = fir.unboxchar
186+
! CHECK-DAG: %[[J:.*]] = fir.alloca i32 {name = "{{.*}}Ej"}
187+
! CHECK-DAG: %[[STR:.*]] = fir.alloca !fir.array{{.*}} {name = "{{.*}}Estr"}
188+
! CHECK: %[[BOX:.*]] = fir.load %[[unbox]]#0 : !fir.ref<!fir.char<1>>
189+
! CHECK: = fir.convert %[[BOX]] : (!fir.char<1>) -> i32
187190
print *, ichar(c)
191+
! CHECK: fir.call @{{.*}}EndIoStatement
188192

189-
! CHECK: %[[ARRV:.*]] = fir.extract_value %{{.*}}, %{{.*}} : (!fir.array<1x!fir.char<1>>, i32) -> !fir.char<1>
190-
! CHECK: %{{.*}} = fir.convert %[[ARRV]] : (!fir.char<1>) -> i32
193+
! CHECK: %{{.*}} = fir.load %[[J]] : !fir.ref<i32>
194+
! CHECK: %[[ptr:.*]] = fir.coordinate_of %[[STR]], %
195+
! CHECK: %[[cast:.*]] = fir.convert %[[ptr]]
196+
! CHECK: fir.load %[[cast]] : !fir.ref<!fir.char<1>>
191197
print *, ichar(str(J))
198+
! CHECK: fir.call @{{.*}}EndIoStatement
192199
end subroutine
193200

194201
! IEOR

0 commit comments

Comments
 (0)