Skip to content

Commit 7aeb24a

Browse files
authored
Merge pull request #671 from flang-compiler/jp-boxvalue-clean-up
[NFC] Remove old BoxValue class and rename IrBoxValue to BoxValue
2 parents 97c463d + 67cfbeb commit 7aeb24a

File tree

9 files changed

+92
-211
lines changed

9 files changed

+92
-211
lines changed

flang/include/flang/Lower/FIRBuilder.h

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@
2828
namespace fir {
2929
class AbstractArrayBox;
3030
class ExtendedValue;
31-
class IrBoxValue;
31+
class BoxValue;
3232
} // namespace fir
3333

3434
namespace Fortran::lower {
@@ -278,8 +278,8 @@ mlir::Value readLowerBound(FirOpBuilder &, mlir::Location,
278278
const fir::ExtendedValue &, unsigned dim,
279279
mlir::Value defaultValue);
280280

281-
/// Read extents from an IrBoxValue into \p result.
282-
void readExtents(FirOpBuilder &, mlir::Location, const fir::IrBoxValue &,
281+
/// Read extents from an BoxValue into \p result.
282+
void readExtents(FirOpBuilder &, mlir::Location, const fir::BoxValue &,
283283
llvm::SmallVectorImpl<mlir::Value> &result);
284284

285285
//===--------------------------------------------------------------------===//

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

Lines changed: 32 additions & 76 deletions
Original file line numberDiff line numberDiff line change
@@ -27,18 +27,16 @@ namespace fir {
2727
class CharBoxValue;
2828
class ArrayBoxValue;
2929
class CharArrayBoxValue;
30-
class BoxValue;
3130
class ProcBoxValue;
3231
class MutableBoxValue;
33-
class IrBoxValue;
32+
class BoxValue;
3433

3534
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const CharBoxValue &);
3635
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const ArrayBoxValue &);
3736
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const CharArrayBoxValue &);
38-
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const BoxValue &);
3937
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const ProcBoxValue &);
4038
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const MutableBoxValue &);
41-
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const IrBoxValue &);
39+
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const BoxValue &);
4240

4341
//===----------------------------------------------------------------------===//
4442
//
@@ -184,47 +182,13 @@ class ProcBoxValue : public AbstractBox {
184182
mlir::Value hostContext;
185183
};
186184

187-
/// In the generalized form, a boxed value can have a dynamic size, be an array
188-
/// with dynamic extents and lbounds, and take dynamic type parameters.
189-
class BoxValue : public AbstractBox, public AbstractArrayBox {
190-
public:
191-
BoxValue(mlir::Value addr) : AbstractBox{addr}, AbstractArrayBox{} {}
192-
BoxValue(mlir::Value addr, mlir::Value len)
193-
: AbstractBox{addr}, AbstractArrayBox{}, len{len} {}
194-
BoxValue(mlir::Value addr, llvm::ArrayRef<mlir::Value> extents,
195-
llvm::ArrayRef<mlir::Value> lbounds = {})
196-
: AbstractBox{addr}, AbstractArrayBox{extents, lbounds} {}
197-
BoxValue(mlir::Value addr, mlir::Value len,
198-
llvm::ArrayRef<mlir::Value> params,
199-
llvm::ArrayRef<mlir::Value> extents,
200-
llvm::ArrayRef<mlir::Value> lbounds = {})
201-
: AbstractBox{addr}, AbstractArrayBox{extents, lbounds}, len{len},
202-
params{params.begin(), params.end()} {}
203-
204-
BoxValue clone(mlir::Value newBase) const {
205-
return {newBase, len, params, extents, lbounds};
206-
}
207-
208-
BoxValue cloneElement(mlir::Value newBase) const {
209-
return {newBase, len, params, {}, {}};
210-
}
211-
212-
mlir::Value getLen() const { return len; }
213-
214-
llvm::ArrayRef<mlir::Value> getLenTypeParams() const { return params; }
215-
216-
friend llvm::raw_ostream &operator<<(llvm::raw_ostream &, const BoxValue &);
217-
LLVM_DUMP_METHOD void dump() const { llvm::errs() << *this; }
218-
219-
protected:
220-
mlir::Value len; // box is CHARACTER
221-
llvm::SmallVector<mlir::Value, 2> params; // LENs, box is derived type
222-
};
223-
224185
/// Base class for values associated to a fir.box or fir.ref<fir.box>.
225-
class AbstractIrBox : public AbstractBox {
186+
class AbstractIrBox : public AbstractBox, public AbstractArrayBox {
226187
public:
227188
AbstractIrBox(mlir::Value addr) : AbstractBox{addr} {}
189+
AbstractIrBox(mlir::Value addr, llvm::ArrayRef<mlir::Value> lbounds,
190+
llvm::ArrayRef<mlir::Value> extents)
191+
: AbstractBox{addr}, AbstractArrayBox(extents, lbounds) {}
228192
/// Get the fir.box<type> part of the address type.
229193
fir::BoxType getBoxTy() const {
230194
auto type = getAddr().getType();
@@ -255,8 +219,7 @@ class AbstractIrBox : public AbstractBox {
255219
/// Returns the rank of the entity. Beware that zero will be returned for
256220
/// both scalars and assumed rank.
257221
unsigned rank() const {
258-
auto seqTy = getBaseTy().dyn_cast<fir::SequenceType>();
259-
if (seqTy)
222+
if (auto seqTy = getBaseTy().dyn_cast<fir::SequenceType>())
260223
return seqTy.getDimension();
261224
return 0;
262225
}
@@ -271,61 +234,52 @@ class AbstractIrBox : public AbstractBox {
271234
};
272235

273236
/// An entity described by a fir.box value that cannot be read into
274-
/// another BoxValue category, either because the fir.box may be an
237+
/// another ExtendedValue category, either because the fir.box may be an
275238
/// absent optional and we need to wait until the user is referencing it
276239
/// to read it, or because it contains important information that cannot
277240
/// be exposed in FIR (e.g. non contiguous byte stride).
278241
/// It may also store explicit bounds or length parameters that were specified
279242
/// for the entity.
280-
class IrBoxValue : public AbstractIrBox {
243+
class BoxValue : public AbstractIrBox {
281244
public:
282-
IrBoxValue(mlir::Value addr) : AbstractIrBox{addr} { assert(verify()); }
283-
IrBoxValue(mlir::Value addr, llvm::ArrayRef<mlir::Value> lbounds,
284-
llvm::ArrayRef<mlir::Value> explicitParams,
285-
llvm::ArrayRef<mlir::Value> explicitExtents = {})
286-
: AbstractIrBox{addr}, lbounds{lbounds.begin(), lbounds.end()},
287-
explicitParams{explicitParams.begin(), explicitParams.end()},
288-
explicitExtents{explicitExtents.begin(), explicitExtents.end()} {
245+
BoxValue(mlir::Value addr) : AbstractIrBox{addr} { assert(verify()); }
246+
BoxValue(mlir::Value addr, llvm::ArrayRef<mlir::Value> lbounds,
247+
llvm::ArrayRef<mlir::Value> explicitParams,
248+
llvm::ArrayRef<mlir::Value> explicitExtents = {})
249+
: AbstractIrBox{addr, lbounds, explicitExtents},
250+
explicitParams{explicitParams.begin(), explicitParams.end()} {
289251
assert(verify());
290252
}
291253
// TODO: check contiguous attribute of addr
292254
bool isContiguous() const { return false; }
293255

294-
friend llvm::raw_ostream &operator<<(llvm::raw_ostream &, const IrBoxValue &);
256+
friend llvm::raw_ostream &operator<<(llvm::raw_ostream &, const BoxValue &);
295257
LLVM_DUMP_METHOD void dump() const { llvm::errs() << *this; }
296258

297259
llvm::ArrayRef<mlir::Value> getLBounds() const { return lbounds; }
298-
llvm::ArrayRef<mlir::Value> getExplicitExtents() const {
299-
return explicitExtents;
300-
}
260+
261+
// The extents member is not guaranteed to be field for arrays. It is only
262+
// guaranteed to be field for explicit shape arrays. In general,
263+
// explicit-shape will not come as descriptors, so this field will be empty in
264+
// most cases. The exception are derived types with length parameters and
265+
// polymorphic dummy argument arrays. It may be possible for the explicit
266+
// extents to conflict with the shape information that is in the box according
267+
// to 15.5.2.11 sequence association rules.
268+
llvm::ArrayRef<mlir::Value> getExplicitExtents() const { return extents; }
269+
301270
llvm::ArrayRef<mlir::Value> getExplicitParameters() const {
302271
return explicitParams;
303272
}
304273

305274
protected:
306275
// Verify constructor invariants.
307276
bool verify() const;
308-
// Always field when the IrBoxValue has lower bounds other than one.
309-
llvm::SmallVector<mlir::Value, 4> lbounds;
310277

311-
// Only field when the IrBoxValue has explicit length parameters.
278+
// Only field when the BoxValue has explicit length parameters.
312279
// Otherwise, the length parameters are in the fir.box.
313280
llvm::SmallVector<mlir::Value, 2> explicitParams;
314-
315-
// Only field with the explicit length parameters
316-
// Otherwise, the extents are in the fir.box.
317-
llvm::SmallVector<mlir::Value, 4> explicitExtents;
318-
// Note about explicitExtents: In general, explicit-shape will not come as
319-
// descriptors, so this field will be empty in most cases. The exception are
320-
// derived types with length parameters and polymorphic dummy argument arrays.
321-
// It may be possible for the explicit extents to conflict with
322-
// the shape information that is in the box according to 15.5.2.11
323-
// sequence association rules.
324281
};
325282

326-
/// Used for triple notation (array slices)
327-
using RangeBoxValue = std::tuple<mlir::Value, mlir::Value, mlir::Value>;
328-
329283
/// Set of variables (addresses) holding the allocatable properties. These may
330284
/// be empty in case it is not deemed safe to duplicate the descriptor
331285
/// information locally (For instance, a volatile allocatable will always be
@@ -404,6 +358,9 @@ class MutableBoxValue : public AbstractIrBox {
404358
MutableProperties mutableProperties;
405359
};
406360

361+
/// Used for triple notation (array slices)
362+
using RangeBoxValue = std::tuple<mlir::Value, mlir::Value, mlir::Value>;
363+
407364
class ExtendedValue;
408365

409366
mlir::Value getBase(const ExtendedValue &exv);
@@ -419,9 +376,8 @@ bool isArray(const ExtendedValue &exv);
419376
/// indices if it is an array entity.
420377
class ExtendedValue : public details::matcher<ExtendedValue> {
421378
public:
422-
using VT =
423-
std::variant<UnboxedValue, CharBoxValue, ArrayBoxValue, CharArrayBoxValue,
424-
BoxValue, ProcBoxValue, IrBoxValue>;
379+
using VT = std::variant<UnboxedValue, CharBoxValue, ArrayBoxValue,
380+
CharArrayBoxValue, ProcBoxValue, BoxValue>;
425381

426382
ExtendedValue() : box{UnboxedValue{}} {}
427383
ExtendedValue(const ExtendedValue &) = default;

flang/lib/Lower/Allocatable.cpp

Lines changed: 5 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -954,9 +954,9 @@ Fortran::lower::createTempMutableBox(Fortran::lower::FirOpBuilder &builder,
954954
// MutableBoxValue reading interface implementation
955955
//===----------------------------------------------------------------------===//
956956

957-
/// Helper to decide if a MutableBoxValue must be read to an IrBoxValue or
957+
/// Helper to decide if a MutableBoxValue must be read to an BoxValue or
958958
/// can be read to a reified box value.
959-
static bool readToIrBoxValue(const fir::MutableBoxValue &box) {
959+
static bool readToBoxValue(const fir::MutableBoxValue &box) {
960960
// If this is described by a set of local variables, the value
961961
// should not be tracked as a fir.box.
962962
if (box.isDescribedByVariables())
@@ -984,11 +984,11 @@ Fortran::lower::genMutableBoxRead(Fortran::lower::FirOpBuilder &builder,
984984
llvm::SmallVector<mlir::Value, 2> lbounds;
985985
llvm::SmallVector<mlir::Value, 2> extents;
986986
llvm::SmallVector<mlir::Value, 2> lengths;
987-
if (readToIrBoxValue(box)) {
987+
if (readToBoxValue(box)) {
988988
auto reader = MutablePropertyReader(builder, loc, box);
989989
reader.getLowerBounds(lbounds);
990-
return fir::IrBoxValue{reader.getIrBox(), lbounds,
991-
box.nonDeferredLenParams()};
990+
return fir::BoxValue{reader.getIrBox(), lbounds,
991+
box.nonDeferredLenParams()};
992992
}
993993
// Contiguous intrinsic type entity: all the data can be extracted from the
994994
// fir.box.
@@ -1046,11 +1046,6 @@ void Fortran::lower::associateMutableBoxWithShift(
10461046
arr.getExtents(), {arr.getLen()});
10471047
},
10481048
[&](const fir::BoxValue &arr) {
1049-
writer.updateMutableBox(arr.getAddr(),
1050-
lbounds.empty() ? arr.getLBounds() : lbounds,
1051-
arr.getExtents(), arr.getLenTypeParams());
1052-
},
1053-
[&](const fir::IrBoxValue &arr) {
10541049
// Rebox array fir.box to the pointer type and apply potential new lower
10551050
// bounds.
10561051
mlir::Value shift;
@@ -1129,10 +1124,6 @@ void Fortran::lower::associateMutableBoxWithRemap(
11291124
{arr.getLen()});
11301125
},
11311126
[&](const fir::BoxValue &arr) {
1132-
writer.updateMutableBox(cast(arr.getAddr()), lbounds, extents,
1133-
arr.getLenTypeParams());
1134-
},
1135-
[&](const fir::IrBoxValue &arr) {
11361127
// Rebox right-hand side fir.box with a new shape and type.
11371128
auto shapeType =
11381129
fir::ShapeShiftType::get(builder.getContext(), extents.size());

flang/lib/Lower/Bridge.cpp

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1250,8 +1250,11 @@ class FirConverter : public Fortran::lower::AbstractConverter {
12501250
sym, value.getAddr(), value.getLen(),
12511251
value.getExtents(), value.getLBounds());
12521252
},
1253-
[&](const fir::BoxValue &) {
1254-
TODO(toLocation(), "association selector of derived type");
1253+
[&](const fir::BoxValue &value) {
1254+
localSymbols.addBoxSymbol(sym, value.getAddr(),
1255+
value.getLBounds(),
1256+
value.getExplicitParameters(),
1257+
value.getExplicitExtents());
12551258
},
12561259
[&](const auto &) {
12571260
mlir::emitError(toLocation(),

flang/lib/Lower/ConvertExpr.cpp

Lines changed: 6 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -182,16 +182,13 @@ arrayElementToExtendedValue(Fortran::lower::FirOpBuilder &builder,
182182
[&](const fir::CharArrayBoxValue &bv) -> fir::ExtendedValue {
183183
return bv.cloneElement(element);
184184
},
185-
[&](const fir::BoxValue &bv) -> fir::ExtendedValue {
186-
return bv.cloneElement(element);
187-
},
188-
[&](const fir::IrBoxValue &box) -> fir::ExtendedValue {
185+
[&](const fir::BoxValue &box) -> fir::ExtendedValue {
189186
if (box.isCharacter()) {
190187
auto len = Fortran::lower::readCharLen(builder, loc, box);
191188
return fir::CharBoxValue{element, len};
192189
}
193190
if (box.isDerived())
194-
TODO(loc, "get length parameters from IrBox");
191+
TODO(loc, "get length parameters from derived type BoxValue");
195192
return element;
196193
},
197194
[&](const auto &) -> fir::ExtendedValue { return element; });
@@ -1188,16 +1185,12 @@ class ScalarExprLowering {
11881185
delta = one;
11891186
return fir::CharBoxValue(genFullDim(arr, delta), arr.getLen());
11901187
},
1191-
[&](const Fortran::lower::SymbolBox::Derived &arr)
1192-
-> fir::ExtendedValue {
1193-
TODO(loc, "array ref of derived type with length parameters");
1194-
},
1195-
[&](const Fortran::lower::SymbolBox::IrBox &arr) -> fir::ExtendedValue {
1196-
// CoordinateOp for IrBoxValue is not generated here. The dimensions
1188+
[&](const Fortran::lower::SymbolBox::Box &arr) -> fir::ExtendedValue {
1189+
// CoordinateOp for BoxValue is not generated here. The dimensions
11971190
// must be kept in the fir.coordinate_op so that potential fir.box
11981191
// strides can be applied by codegen.
11991192
fir::emitFatalError(
1200-
loc, "internal: IrBoxValue in dim-collapsed fir.coordinate_of");
1193+
loc, "internal: BoxValue in dim-collapsed fir.coordinate_of");
12011194
},
12021195
[&](const auto &) -> fir::ExtendedValue {
12031196
fir::emitFatalError(loc, "internal: array lowering failed");
@@ -1235,10 +1228,6 @@ class ScalarExprLowering {
12351228
lengthParams.emplace_back(arr.getLen());
12361229
},
12371230
[&](const fir::BoxValue &arr) {
1238-
auto lengths = arr.getLenTypeParams();
1239-
lengthParams.append(lengths.begin(), lengths.end());
1240-
},
1241-
[&](const fir::IrBoxValue &arr) {
12421231
auto lengths = arr.getExplicitParameters();
12431232
lengthParams.append(lengths.begin(), lengths.end());
12441233
},
@@ -2468,7 +2457,7 @@ class ArrayExprLowering {
24682457
TODO(loc, "use fir.rebox for array section of fir.box");
24692458
mlir::Value embox = builder.create<fir::EmboxOp>(
24702459
loc, boxTy, memref, shape, slice, /*lenParams=*/llvm::None);
2471-
return [=](IterSpace) -> ExtValue { return fir::IrBoxValue(embox); };
2460+
return [=](IterSpace) -> ExtValue { return fir::BoxValue(embox); };
24722461
}
24732462
mlir::Value arrLd = builder.create<fir::ArrayLoadOp>(
24742463
loc, arrTy, memref, shape, slice, /*lenParams=*/llvm::None);

flang/lib/Lower/ConvertVariable.cpp

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -681,13 +681,13 @@ static void instantiateCommon(Fortran::lower::AbstractConverter &converter,
681681
// Lower Variables specification expressions and attributes
682682
//===--------------------------------------------------------------===//
683683

684-
/// Helper to decide if a dummy argument must be tracked in an IrBox.
685-
static bool lowerToIrBox(const Fortran::semantics::Symbol &sym,
686-
mlir::Value dummyArg) {
687-
// Only dummy arguments coming as fir.box can be tracked in an IrBox.
684+
/// Helper to decide if a dummy argument must be tracked in an BoxValue.
685+
static bool lowerToBoxValue(const Fortran::semantics::Symbol &sym,
686+
mlir::Value dummyArg) {
687+
// Only dummy arguments coming as fir.box can be tracked in an BoxValue.
688688
if (!dummyArg || !dummyArg.getType().isa<fir::BoxType>())
689689
return false;
690-
// Non contiguous arrays must be tracked in an IrBox.
690+
// Non contiguous arrays must be tracked in an BoxValue.
691691
if (sym.Rank() > 0 && !sym.attrs().test(Fortran::semantics::Attr::CONTIGUOUS))
692692
return true;
693693
// Assumed rank and optional fir.box cannot yet be read while lowering the
@@ -855,7 +855,7 @@ void Fortran::lower::mapSymbolAttributes(
855855

856856
if (isDummy) {
857857
auto dummyArg = symMap.lookupSymbol(sym).getAddr();
858-
if (lowerToIrBox(sym, dummyArg)) {
858+
if (lowerToBoxValue(sym, dummyArg)) {
859859
llvm::SmallVector<mlir::Value, 4> lbounds;
860860
llvm::SmallVector<mlir::Value, 4> extents;
861861
llvm::SmallVector<mlir::Value, 2> explicitParams;
@@ -869,8 +869,8 @@ void Fortran::lower::mapSymbolAttributes(
869869
lowerExplicitLowerBounds(converter, loc, sba, lbounds, symMap, stmtCtx);
870870
lowerExplicitExtents(converter, loc, sba, lbounds, extents, symMap,
871871
stmtCtx);
872-
symMap.addIrBoxSymbol(sym, dummyArg, lbounds, explicitParams, extents,
873-
replace);
872+
symMap.addBoxSymbol(sym, dummyArg, lbounds, explicitParams, extents,
873+
replace);
874874
return;
875875
}
876876
}

0 commit comments

Comments
 (0)