Skip to content

Commit 90b3f5b

Browse files
committed
Enable the assertion checking that a BoxValue has an address and resides
in memory. The remaining issues were problems with the lowering of CHARACTER variables and values. This patch attempts to clean up some of that, passing CharBoxValue and Value where appropriate, etc. Use llvm::dbgs() consistently. Some clean up of other small TODOs and FIXMEs.
1 parent b76112e commit 90b3f5b

File tree

9 files changed

+216
-142
lines changed

9 files changed

+216
-142
lines changed

flang/include/flang/Lower/CharacterExpr.h

Lines changed: 19 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,7 @@ class CharacterExprHelper {
5353

5454
/// Lower \p lhs = \p rhs where \p lhs and \p rhs are scalar characters.
5555
/// It handles cases where \p lhs and \p rhs may overlap.
56-
void createAssign(mlir::Value lhs, mlir::Value rhs);
56+
void createAssign(mlir::Value lhs, const fir::ExtendedValue &rhs);
5757

5858
/// Lower an assignment where the buffer and LEN parameter are known and do
5959
/// not need to be unboxed.
@@ -101,7 +101,7 @@ class CharacterExprHelper {
101101
materializeCharacterOrSequence(mlir::Value str);
102102

103103
/// Return true if \p type is a character literal type (is
104-
/// fir.array<len x fir.char<kind>>).;
104+
/// `fir.array<len x fir.char<kind>>`).;
105105
static bool isCharacterLiteral(mlir::Type type);
106106

107107
/// Return true if \p type is one of the following type
@@ -119,6 +119,7 @@ class CharacterExprHelper {
119119
/// Determine the base character type
120120
static fir::CharacterType getCharacterType(mlir::Type type);
121121
static fir::CharacterType getCharacterType(const fir::CharBoxValue &box);
122+
static fir::CharacterType getCharacterType(mlir::Value str);
122123

123124
/// Return the integer type that must be used to manipulate
124125
/// Character lengths. TODO: move this to FirOpBuilder?
@@ -130,10 +131,12 @@ class CharacterExprHelper {
130131
/// - fir.array<len x fir.char<kind>>
131132
/// - fir.char<kind>
132133
/// - fir.ref<char<kind>>
133-
/// If the no length is passed, it is attempted to be extracted from \p
134-
/// character (or its type). This will crash if this is not possible.
135-
/// The returned value is a CharBoxValue if \p character is a scalar,
136-
/// otherwise it is a CharArrayBoxValue.
134+
///
135+
/// Does the heavy lifting of converting the value \p character (along with an
136+
/// optional \p len value) to an extended value. If \p len is null, a length
137+
/// value is extracted from \p character (or its type). This will produce an
138+
/// error if it's not possible. The returned value is a CharBoxValue if \p
139+
/// character is a scalar, otherwise it is a CharArrayBoxValue.
137140
fir::ExtendedValue toExtendedValue(mlir::Value character,
138141
mlir::Value len = {});
139142

@@ -143,17 +146,23 @@ class CharacterExprHelper {
143146
/// - !fir.array<dim x !fir.char<kind, len>>
144147
/// - !fir.ref<T> where T is either of the first two cases
145148
/// - !fir.box<T> where T is either of the first two cases
149+
///
150+
/// In certain contexts, Fortran allows an array of CHARACTERs to be treated
151+
/// as if it were one longer CHARACTER scalar, each element append to the
152+
/// previous.
146153
static bool isArray(mlir::Type type);
147154

148155
private:
149-
fir::CharBoxValue materializeValue(const fir::CharBoxValue &str);
156+
fir::CharBoxValue materializeValue(mlir::Value str);
150157
fir::CharBoxValue toDataLengthPair(mlir::Value character);
151158
mlir::Type getReferenceType(const fir::CharBoxValue &c) const;
159+
mlir::Type getReferenceType(mlir::Value str) const;
152160
mlir::Type getSeqTy(const fir::CharBoxValue &c) const;
161+
mlir::Type getSeqTy(mlir::Value str) const;
162+
mlir::Value getCharBoxBuffer(const fir::CharBoxValue &box);
153163
mlir::Value createEmbox(const fir::CharBoxValue &str);
154-
mlir::Value createLoadCharAt(const fir::CharBoxValue &str, mlir::Value index);
155-
void createStoreCharAt(const fir::CharBoxValue &str, mlir::Value index,
156-
mlir::Value c);
164+
mlir::Value createLoadCharAt(mlir::Value buff, mlir::Value index);
165+
void createStoreCharAt(mlir::Value str, mlir::Value index, mlir::Value c);
157166
void createCopy(const fir::CharBoxValue &dest, const fir::CharBoxValue &src,
158167
mlir::Value count);
159168
void createPadding(const fir::CharBoxValue &str, mlir::Value lower,

flang/include/flang/Lower/Support/BoxValue.h

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -54,8 +54,8 @@ class AbstractBox {
5454
public:
5555
AbstractBox() = delete;
5656
AbstractBox(mlir::Value addr) : addr{addr} {
57-
//assert(isa_passbyref_type(addr.getType()) &&
58-
// "box values must be references");
57+
assert(isa_passbyref_type(addr.getType()) &&
58+
"box values must be references");
5959
}
6060

6161
/// An abstract box always contains a memory reference to a value.
@@ -225,7 +225,11 @@ class ExtendedValue : public details::matcher<ExtendedValue> {
225225
using VT = std::variant<UnboxedValue, CharBoxValue, ArrayBoxValue,
226226
CharArrayBoxValue, BoxValue, ProcBoxValue>;
227227

228-
template <typename A>
228+
ExtendedValue() : box{UnboxedValue{}} {}
229+
ExtendedValue(const ExtendedValue &) = default;
230+
ExtendedValue(ExtendedValue &&) = default;
231+
template <typename A, typename = std::enable_if_t<
232+
!std::is_same_v<std::decay_t<A>, ExtendedValue>>>
229233
constexpr ExtendedValue(A &&box) : box{std::forward<A>(box)} {}
230234

231235
template <typename A>

flang/lib/Lower/Bridge.cpp

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1484,8 +1484,10 @@ class FirConverter : public Fortran::lower::AbstractConverter {
14841484
if (isCharacterCategory(lhsType->category())) {
14851485
// Fortran 2018 10.2.1.3 p10 and p11
14861486
// Generating value for lhs to get fir.boxchar.
1487+
Fortran::lower::ExpressionContext context;
14871488
auto lhs = genExprAddr(assign.lhs);
1488-
auto rhs = genExprValue(assign.rhs);
1489+
auto rhs = createSomeExtendedExpression(
1490+
toLocation(), *this, assign.rhs, localSymbols, context);
14891491
Fortran::lower::CharacterExprHelper{*builder, loc}.createAssign(
14901492
lhs, rhs);
14911493
return;
@@ -1798,11 +1800,11 @@ class FirConverter : public Fortran::lower::AbstractConverter {
17981800
// Assume that the members of the COMMON block will appear in an order
17991801
// that is sorted by offset.
18001802
[[maybe_unused]] std::int64_t lastByteOff = -1;
1801-
LLVM_DEBUG(llvm::errs() << "block {\n");
1803+
LLVM_DEBUG(llvm::dbgs() << "block {\n");
18021804
for (const auto &obj : details->objects()) {
18031805
assert(lastByteOff < static_cast<std::int64_t>(obj->offset()));
18041806
lastByteOff = static_cast<std::int64_t>(obj->offset());
1805-
LLVM_DEBUG(llvm::errs() << "offset: " << obj->offset() << '\n');
1807+
LLVM_DEBUG(llvm::dbgs() << "offset: " << obj->offset() << '\n');
18061808
if (const auto *objDet =
18071809
obj->detailsIf<Fortran::semantics::ObjectEntityDetails>())
18081810
if (objDet->init()) {
@@ -1814,7 +1816,7 @@ class FirConverter : public Fortran::lower::AbstractConverter {
18141816
castVal, off);
18151817
}
18161818
}
1817-
LLVM_DEBUG(llvm::errs() << "}\n");
1819+
LLVM_DEBUG(llvm::dbgs() << "}\n");
18181820
builder.create<fir::HasValueOp>(loc, cb);
18191821
};
18201822
global = builder->createGlobal(loc, commonTy, globalName,

0 commit comments

Comments
 (0)