Skip to content

Commit 5c8f133

Browse files
committed
Remove old BoxValue class and rename IrBoxValue to BoxValue
1 parent 9a6133f commit 5c8f133

File tree

8 files changed

+73
-188
lines changed

8 files changed

+73
-188
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: 16 additions & 56 deletions
Original file line numberDiff line numberDiff line change
@@ -26,18 +26,16 @@ namespace fir {
2626
class CharBoxValue;
2727
class ArrayBoxValue;
2828
class CharArrayBoxValue;
29-
class BoxValue;
3029
class ProcBoxValue;
3130
class MutableBoxValue;
32-
class IrBoxValue;
31+
class BoxValue;
3332

3433
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const CharBoxValue &);
3534
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const ArrayBoxValue &);
3635
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const CharArrayBoxValue &);
37-
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const BoxValue &);
3836
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const ProcBoxValue &);
3937
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const MutableBoxValue &);
40-
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const IrBoxValue &);
38+
llvm::raw_ostream &operator<<(llvm::raw_ostream &, const BoxValue &);
4139

4240
//===----------------------------------------------------------------------===//
4341
//
@@ -182,43 +180,6 @@ class ProcBoxValue : public AbstractBox {
182180
mlir::Value hostContext;
183181
};
184182

185-
/// In the generalized form, a boxed value can have a dynamic size, be an array
186-
/// with dynamic extents and lbounds, and take dynamic type parameters.
187-
class BoxValue : public AbstractBox, public AbstractArrayBox {
188-
public:
189-
BoxValue(mlir::Value addr) : AbstractBox{addr}, AbstractArrayBox{} {}
190-
BoxValue(mlir::Value addr, mlir::Value len)
191-
: AbstractBox{addr}, AbstractArrayBox{}, len{len} {}
192-
BoxValue(mlir::Value addr, llvm::ArrayRef<mlir::Value> extents,
193-
llvm::ArrayRef<mlir::Value> lbounds = {})
194-
: AbstractBox{addr}, AbstractArrayBox{extents, lbounds} {}
195-
BoxValue(mlir::Value addr, mlir::Value len,
196-
llvm::ArrayRef<mlir::Value> params,
197-
llvm::ArrayRef<mlir::Value> extents,
198-
llvm::ArrayRef<mlir::Value> lbounds = {})
199-
: AbstractBox{addr}, AbstractArrayBox{extents, lbounds}, len{len},
200-
params{params.begin(), params.end()} {}
201-
202-
BoxValue clone(mlir::Value newBase) const {
203-
return {newBase, len, params, extents, lbounds};
204-
}
205-
206-
BoxValue cloneElement(mlir::Value newBase) const {
207-
return {newBase, len, params, {}, {}};
208-
}
209-
210-
mlir::Value getLen() const { return len; }
211-
212-
llvm::ArrayRef<mlir::Value> getLenTypeParams() const { return params; }
213-
214-
friend llvm::raw_ostream &operator<<(llvm::raw_ostream &, const BoxValue &);
215-
LLVM_DUMP_METHOD void dump() const { llvm::errs() << *this; }
216-
217-
protected:
218-
mlir::Value len; // box is CHARACTER
219-
llvm::SmallVector<mlir::Value, 2> params; // LENs, box is derived type
220-
};
221-
222183
/// Base class for values associated to a fir.box or fir.ref<fir.box>.
223184
class AbstractIrBox : public AbstractBox {
224185
public:
@@ -269,18 +230,18 @@ class AbstractIrBox : public AbstractBox {
269230
};
270231

271232
/// An entity described by a fir.box value that cannot be read into
272-
/// another BoxValue category, either because the fir.box may be an
233+
/// another ExtendedValue category, either because the fir.box may be an
273234
/// absent optional and we need to wait until the user is referencing it
274235
/// to read it, or because it contains important information that cannot
275236
/// be exposed in FIR (e.g. non contiguous byte stride).
276237
/// It may also store explicit bounds or length parameters that were specified
277238
/// for the entity.
278-
class IrBoxValue : public AbstractIrBox {
239+
class BoxValue : public AbstractIrBox {
279240
public:
280-
IrBoxValue(mlir::Value addr) : AbstractIrBox{addr} { assert(verify()); }
281-
IrBoxValue(mlir::Value addr, llvm::ArrayRef<mlir::Value> lbounds,
282-
llvm::ArrayRef<mlir::Value> explicitParams,
283-
llvm::ArrayRef<mlir::Value> explicitExtents = {})
241+
BoxValue(mlir::Value addr) : AbstractIrBox{addr} { assert(verify()); }
242+
BoxValue(mlir::Value addr, llvm::ArrayRef<mlir::Value> lbounds,
243+
llvm::ArrayRef<mlir::Value> explicitParams,
244+
llvm::ArrayRef<mlir::Value> explicitExtents = {})
284245
: AbstractIrBox{addr}, lbounds{lbounds.begin(), lbounds.end()},
285246
explicitParams{explicitParams.begin(), explicitParams.end()},
286247
explicitExtents{explicitExtents.begin(), explicitExtents.end()} {
@@ -289,7 +250,7 @@ class IrBoxValue : public AbstractIrBox {
289250
// TODO: check contiguous attribute of addr
290251
bool isContiguous() const { return false; }
291252

292-
friend llvm::raw_ostream &operator<<(llvm::raw_ostream &, const IrBoxValue &);
253+
friend llvm::raw_ostream &operator<<(llvm::raw_ostream &, const BoxValue &);
293254
LLVM_DUMP_METHOD void dump() const { llvm::errs() << *this; }
294255

295256
llvm::ArrayRef<mlir::Value> getLBounds() const { return lbounds; }
@@ -303,10 +264,10 @@ class IrBoxValue : public AbstractIrBox {
303264
protected:
304265
// Verify constructor invariants.
305266
bool verify() const;
306-
// Always field when the IrBoxValue has lower bounds other than one.
267+
// Always field when the BoxValue has lower bounds other than one.
307268
llvm::SmallVector<mlir::Value, 4> lbounds;
308269

309-
// Only field when the IrBoxValue has explicit length parameters.
270+
// Only field when the BoxValue has explicit length parameters.
310271
// Otherwise, the length parameters are in the fir.box.
311272
llvm::SmallVector<mlir::Value, 2> explicitParams;
312273

@@ -321,9 +282,6 @@ class IrBoxValue : public AbstractIrBox {
321282
// sequence association rules.
322283
};
323284

324-
/// Used for triple notation (array slices)
325-
using RangeBoxValue = std::tuple<mlir::Value, mlir::Value, mlir::Value>;
326-
327285
/// Set of variables (addresses) holding the allocatable properties. These may
328286
/// be empty in case it is not deemed safe to duplicate the descriptor
329287
/// information locally (For instance, a volatile allocatable will always be
@@ -402,6 +360,9 @@ class MutableBoxValue : public AbstractIrBox {
402360
MutableProperties mutableProperties;
403361
};
404362

363+
/// Used for triple notation (array slices)
364+
using RangeBoxValue = std::tuple<mlir::Value, mlir::Value, mlir::Value>;
365+
405366
class ExtendedValue;
406367

407368
mlir::Value getBase(const ExtendedValue &exv);
@@ -417,9 +378,8 @@ bool isArray(const ExtendedValue &exv);
417378
/// indices if it is an array entity.
418379
class ExtendedValue : public details::matcher<ExtendedValue> {
419380
public:
420-
using VT =
421-
std::variant<UnboxedValue, CharBoxValue, ArrayBoxValue, CharArrayBoxValue,
422-
BoxValue, ProcBoxValue, IrBoxValue>;
381+
using VT = std::variant<UnboxedValue, CharBoxValue, ArrayBoxValue,
382+
CharArrayBoxValue, ProcBoxValue, BoxValue>;
423383

424384
ExtendedValue() : box{UnboxedValue{}} {}
425385
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: 13 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1289,8 +1289,11 @@ class FirConverter : public Fortran::lower::AbstractConverter {
12891289
sym, value.getAddr(), value.getLen(),
12901290
value.getExtents(), value.getLBounds());
12911291
},
1292-
[&](const fir::BoxValue &) {
1293-
TODO(toLocation(), "association selector of derived type");
1292+
[&](const fir::BoxValue &value) {
1293+
localSymbols.addBoxSymbol(sym, value.getAddr(),
1294+
value.getLBounds(),
1295+
value.getExplicitParameters(),
1296+
value.getExplicitExtents());
12941297
},
12951298
[&](const auto &) {
12961299
mlir::emitError(toLocation(),
@@ -2445,13 +2448,13 @@ class FirConverter : public Fortran::lower::AbstractConverter {
24452448
// Lower Variables specification expressions and attributes
24462449
//===--------------------------------------------------------------===//
24472450

2448-
/// Helper to decide if a dummy argument must be tracked in an IrBox.
2449-
static bool lowerToIrBox(const Fortran::semantics::Symbol &sym,
2450-
mlir::Value dummyArg) {
2451-
// Only dummy arguments coming as fir.box can be tracked in an IrBox.
2451+
/// Helper to decide if a dummy argument must be tracked in an fir::BoxValue.
2452+
static bool lowerToBoxValue(const Fortran::semantics::Symbol &sym,
2453+
mlir::Value dummyArg) {
2454+
// Only dummy arguments coming as fir.box can be tracked in an BoxValue.
24522455
if (!dummyArg || !dummyArg.getType().isa<fir::BoxType>())
24532456
return false;
2454-
// Non contiguous arrays must be tracked in an IrBox.
2457+
// Non contiguous arrays must be tracked in an BoxValue.
24552458
if (sym.Rank() > 0 &&
24562459
!sym.attrs().test(Fortran::semantics::Attr::CONTIGUOUS))
24572460
return true;
@@ -2607,7 +2610,7 @@ class FirConverter : public Fortran::lower::AbstractConverter {
26072610

26082611
if (isDummy) {
26092612
auto dummyArg = lookupSymbol(sym).getAddr();
2610-
if (lowerToIrBox(sym, dummyArg)) {
2613+
if (lowerToBoxValue(sym, dummyArg)) {
26112614
llvm::SmallVector<mlir::Value, 4> lbounds;
26122615
llvm::SmallVector<mlir::Value, 4> extents;
26132616
llvm::SmallVector<mlir::Value, 2> explicitParams;
@@ -2619,8 +2622,8 @@ class FirConverter : public Fortran::lower::AbstractConverter {
26192622
// TODO: derived type length parameters.
26202623
lowerExplicitLowerBounds(loc, sba, lbounds, stmtCtx);
26212624
lowerExplicitExtents(loc, sba, lbounds, extents, stmtCtx);
2622-
localSymbols.addIrBoxSymbol(sym, dummyArg, lbounds, explicitParams,
2623-
extents, replace);
2625+
localSymbols.addBoxSymbol(sym, dummyArg, lbounds, explicitParams,
2626+
extents, replace);
26242627
return;
26252628
}
26262629
}

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
},
@@ -2443,7 +2432,7 @@ class ArrayExprLowering {
24432432
TODO(loc, "use fir.rebox for array section of fir.box");
24442433
mlir::Value embox = builder.create<fir::EmboxOp>(
24452434
loc, boxTy, memref, shape, slice, /*lenParams=*/llvm::None);
2446-
return [=](IterSpace) -> ExtValue { return fir::IrBoxValue(embox); };
2435+
return [=](IterSpace) -> ExtValue { return fir::BoxValue(embox); };
24472436
}
24482437
mlir::Value arrLd = builder.create<fir::ArrayLoadOp>(
24492438
loc, arrTy, memref, shape, slice, /*lenParams=*/llvm::None);

flang/lib/Lower/FIRBuilder.cpp

Lines changed: 3 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -248,8 +248,7 @@ Fortran::lower::FirOpBuilder::createShape(mlir::Location loc,
248248
return exv.match(
249249
[&](const fir::ArrayBoxValue &box) { return consShape(loc, box); },
250250
[&](const fir::CharArrayBoxValue &box) { return consShape(loc, box); },
251-
[&](const fir::BoxValue &box) { return consShape(loc, box); },
252-
[&](const fir::IrBoxValue &box) -> mlir::Value {
251+
[&](const fir::BoxValue &box) -> mlir::Value {
253252
if (!box.getLBounds().empty()) {
254253
auto shiftType =
255254
fir::ShiftType::get(getContext(), box.getLBounds().size());
@@ -295,9 +294,6 @@ mlir::Value Fortran::lower::FirOpBuilder::createSlice(
295294
return fullShape(box.getLBounds(), box.getExtents());
296295
},
297296
[&](const fir::BoxValue &box) {
298-
return fullShape(box.getLBounds(), box.getExtents());
299-
},
300-
[&](const fir::IrBoxValue &box) {
301297
llvm::SmallVector<mlir::Value, 4> extents;
302298
Fortran::lower::readExtents(*this, loc, box, extents);
303299
return fullShape(box.getLBounds(), extents);
@@ -335,10 +331,6 @@ Fortran::lower::FirOpBuilder::createBox(mlir::Location loc,
335331
return create<fir::EmboxOp>(loc, boxTy, itemAddr, s, emptySlice,
336332
lenParams);
337333
},
338-
[&](const fir::BoxValue &box) -> mlir::Value {
339-
auto s = createShape(loc, exv);
340-
return create<fir::EmboxOp>(loc, boxTy, itemAddr, s);
341-
},
342334
[&](const fir::CharBoxValue &box) -> mlir::Value {
343335
if (Fortran::lower::CharacterExprHelper::hasConstantLengthInType(exv))
344336
return create<fir::EmboxOp>(loc, boxTy, itemAddr);
@@ -364,7 +356,7 @@ mlir::Value Fortran::lower::readCharLen(Fortran::lower::FirOpBuilder &builder,
364356
[&](const fir::CharArrayBoxValue &x) -> mlir::Value {
365357
return x.getLen();
366358
},
367-
[&](const fir::IrBoxValue &x) -> mlir::Value {
359+
[&](const fir::BoxValue &x) -> mlir::Value {
368360
assert(x.isCharacter());
369361
if (!x.getExplicitParameters().empty())
370362
return x.getExplicitParameters()[0];
@@ -390,9 +382,6 @@ mlir::Value Fortran::lower::readExtent(Fortran::lower::FirOpBuilder &builder,
390382
return x.getExtents()[dim];
391383
},
392384
[&](const fir::BoxValue &x) -> mlir::Value {
393-
return x.getExtents()[dim];
394-
},
395-
[&](const fir::IrBoxValue &x) -> mlir::Value {
396385
if (!x.getExplicitExtents().empty())
397386
return x.getExplicitExtents()[dim];
398387
auto idxTy = builder.getIndexType();
@@ -423,9 +412,6 @@ mlir::Value Fortran::lower::readLowerBound(Fortran::lower::FirOpBuilder &,
423412
[&](const fir::BoxValue &x) -> mlir::Value {
424413
return x.getLBounds().empty() ? mlir::Value{} : x.getLBounds()[dim];
425414
},
426-
[&](const fir::IrBoxValue &x) -> mlir::Value {
427-
return x.getLBounds().empty() ? mlir::Value{} : x.getLBounds()[dim];
428-
},
429415
[&](const auto &) -> mlir::Value {
430416
fir::emitFatalError(loc, "lower bound inquiry on scalar");
431417
});
@@ -435,7 +421,7 @@ mlir::Value Fortran::lower::readLowerBound(Fortran::lower::FirOpBuilder &,
435421
}
436422

437423
void Fortran::lower::readExtents(Fortran::lower::FirOpBuilder &builder,
438-
mlir::Location loc, const fir::IrBoxValue &box,
424+
mlir::Location loc, const fir::BoxValue &box,
439425
llvm::SmallVectorImpl<mlir::Value> &result) {
440426
assert(result.empty());
441427
auto explicitExtents = box.getExplicitExtents();

0 commit comments

Comments
 (0)