Skip to content

Commit 753aef9

Browse files
committed
Lower IO input with vector subscripts
Define a VectorSubscriptBox class that allow representing and working with a lowered Designator containing vector subscripts while ensuring all the subscripts expression are only lowered once. It's a bit of a super ExtendedValue (but is is not added as such because it is heavy and its use case is only restricted to IO input so far). The key point of this class is that it has members functions `loopOverElements` and `loopOverElementsWhile` that allow creating loops over each element of the designator, and call a provided callback with the address of the element. This class is used in input IO to create an IO runtime call for each element of the designator, since it is not possible to build a descriptor for it. The `loopOverElementsWhile` version is required when error recovery is enabled in IO. A hidden VectorSubscriptBoxBuilder is in charge of making a custom Designator<T> visit and create the VectorSubscriptBox. Once this is done, the VectorSubscriptBox does not equire any front-end data structures to work with. The motivation for creating such tool is that the current lowering array lowering infrastructure is centered around assignment (to a variable or temporary), and could not be used here to created the loops over the IO runtime calls without some non trivial modification to it. Adding complexity to the array expression lowering framework to cover a corner case did not appear a good idea. The option of creating a temp, passing it to the runtime, and copying it back was explored, but it was not possible to guarantee that the subscript would be evaluated only once given there was no way to "keep the lowered representation" of the designator between the temp creation and the copy back (the temp creation requires evaluating the susbcripts to compute the shape in general). However, note that with the added VectorSubscriptBox, it would actually now also be possible to deploy a temp + copy back mechanism. This can be done later if it appeared beneficial in real world program. The only cases left TODOs are the cases when one of the Components is a parent type reference (not yet handled properly in the general case), the coarray case, and the PDT case (not sure exactly how type params will be threaded in fir.field_index). All other cases are covered, and I tried to add exhaustive tests since I do not expect real world program to be very harsh on this utility (most will just do READ(*, *) x(y)).
1 parent ff9e169 commit 753aef9

File tree

9 files changed

+1354
-83
lines changed

9 files changed

+1354
-83
lines changed

flang/include/flang/Lower/Support/Utils.h

Lines changed: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -45,4 +45,25 @@ toEvExpr(const A &x) {
4545
return Fortran::evaluate::AsGenericExpr(Fortran::common::Clone(x));
4646
}
4747

48+
template <Fortran::common::TypeCategory FROM>
49+
static Fortran::evaluate::Expr<Fortran::evaluate::SomeType> ignoreEvConvert(
50+
const Fortran::evaluate::Convert<
51+
Fortran::evaluate::Type<Fortran::common::TypeCategory::Integer, 8>,
52+
FROM> &x) {
53+
return toEvExpr(x.left());
54+
}
55+
template <typename A>
56+
static Fortran::evaluate::Expr<Fortran::evaluate::SomeType>
57+
ignoreEvConvert(const A &x) {
58+
return toEvExpr(x);
59+
}
60+
/// A vector subscript expression may be wrapped with a cast to INTEGER*8.
61+
/// Get rid of it here so the vector can be loaded. Add it back when
62+
/// generating the elemental evaluation (inside the loop nest).
63+
inline Fortran::evaluate::Expr<Fortran::evaluate::SomeType>
64+
ignoreEvConvert(const Fortran::evaluate::Expr<Fortran::evaluate::Type<
65+
Fortran::common::TypeCategory::Integer, 8>> &x) {
66+
return std::visit([](const auto &v) { return ignoreEvConvert(v); }, x.u);
67+
}
68+
4869
#endif // FORTRAN_LOWER_SUPPORT_UTILS_H
Lines changed: 152 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,152 @@
1+
//===-- VectorSubscripts.h -- vector subscripts tools -----------*- C++ -*-===//
2+
//
3+
// Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4+
// See https://llvm.org/LICENSE.txt for license information.
5+
// SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6+
//
7+
//===----------------------------------------------------------------------===//
8+
///
9+
/// \file
10+
/// \brief Defines a compiler internal representation for lowered designators
11+
/// containing vector subscripts. This representation allows working on such
12+
/// designators in custom ways while ensuring the designator subscripts are
13+
/// only evaluated once. It is mainly intended for cases that do not fit in
14+
/// the array expression lowering framework like input IO in presence of
15+
/// vector subscripts.
16+
///
17+
//===----------------------------------------------------------------------===//
18+
19+
#ifndef FORTRAN_LOWER_VECTORSUBSCRIPTS_H
20+
#define FORTRAN_LOWER_VECTORSUBSCRIPTS_H
21+
22+
#include "flang/Optimizer/Builder/BoxValue.h"
23+
24+
namespace fir {
25+
class FirOpBuilder;
26+
}
27+
28+
namespace Fortran {
29+
30+
namespace evaluate {
31+
template <typename>
32+
class Expr;
33+
struct SomeType;
34+
} // namespace evaluate
35+
36+
namespace lower {
37+
38+
class AbstractConverter;
39+
class StatementContext;
40+
41+
/// VectorSubscriptBox is a lowered representation for any Designator<T> that
42+
/// contain at least one vector subscript.
43+
///
44+
/// A designator `x%a(i,j)%b(1:foo():1, vector, k)%c%d(m)%e1
45+
/// Is lowered into:
46+
/// - an ExtendedValue for ranked base (x%a(i,j)%b)
47+
/// - mlir:Values and ExtendedValues for the triplet, vector subscript and
48+
/// scalar subscripts of the ranked array reference (1:foo():1, vector, k)
49+
/// - a list of fir.field_index and scalar integers mlir::Value for the
50+
/// component
51+
/// path at the right of the ranked array ref (%c%d(m)%e).
52+
///
53+
/// This representation allows later creating loops over the designator elements
54+
/// and fir.array_coor to get the element addresses without re-evaluating any
55+
/// sub-expressions.
56+
class VectorSubscriptBox {
57+
public:
58+
/// Type of the callbacks that can be passed to work with the element
59+
/// addresses.
60+
using ElementalGenerator = std::function<void(const fir::ExtendedValue &)>;
61+
using ElementalGeneratorWithBoolReturn =
62+
std::function<mlir::Value(const fir::ExtendedValue &)>;
63+
struct LoweredVectorSubscript {
64+
fir::ExtendedValue vector;
65+
// Vector size, guaranteed to be of indexType.
66+
mlir::Value size;
67+
};
68+
struct LoweredTriplet {
69+
// Triplets value, guaranteed to be of indexType.
70+
mlir::Value lb;
71+
mlir::Value ub;
72+
mlir::Value stride;
73+
};
74+
using LoweredSubscript =
75+
std::variant<mlir::Value, LoweredTriplet, LoweredVectorSubscript>;
76+
using MaybeSubstring = llvm::SmallVector<mlir::Value, 2>;
77+
VectorSubscriptBox(
78+
fir::ExtendedValue &&loweredBase,
79+
llvm::SmallVector<LoweredSubscript, 16> &&loweredSubscripts,
80+
llvm::SmallVector<mlir::Value> &&componentPath,
81+
MaybeSubstring substringBounds, mlir::Type elementType)
82+
: loweredBase{std::move(loweredBase)}, loweredSubscripts{std::move(
83+
loweredSubscripts)},
84+
componentPath{std::move(componentPath)},
85+
substringBounds{substringBounds}, elementType{elementType} {};
86+
87+
/// Loop over the elements described by the VectorSubscriptBox, and call
88+
/// \p elementalGenerator inside the loops with the element addresses.
89+
void loopOverElements(fir::FirOpBuilder &builder, mlir::Location loc,
90+
const ElementalGenerator &elementalGenerator);
91+
92+
/// Loop over the elements described by the VectorSubscriptBox while a
93+
/// condition is true, and call \p elementalGenerator inside the loops with
94+
/// the element addresses. The initial condition value is \p initialCondition,
95+
/// and then it is the result of \p elementalGenerator. The value of the
96+
/// condition after the loops is returned.
97+
mlir::Value loopOverElementsWhile(
98+
fir::FirOpBuilder &builder, mlir::Location loc,
99+
const ElementalGeneratorWithBoolReturn &elementalGenerator,
100+
mlir::Value initialCondition);
101+
102+
/// Return the type of the elements of the array section.
103+
mlir::Type getElementType() { return elementType; }
104+
105+
private:
106+
/// Common implementation for DoLoop and IterWhile loop creations.
107+
template <typename LoopType, typename Generator>
108+
mlir::Value loopOverElementsBase(fir::FirOpBuilder &builder,
109+
mlir::Location loc,
110+
const Generator &elementalGenerator,
111+
mlir::Value initialCondition);
112+
/// Create sliceOp for the designator.
113+
mlir::Value createSlice(fir::FirOpBuilder &builder, mlir::Location loc);
114+
115+
/// Create ExtendedValue the element inside the loop.
116+
fir::ExtendedValue getElementAt(fir::FirOpBuilder &builder,
117+
mlir::Location loc, mlir::Value shape,
118+
mlir::Value slice,
119+
mlir::ValueRange inductionVariables);
120+
121+
/// Generate the [lb, ub, step] to loop over the section (in loop order, not
122+
/// Fortran dimension order).
123+
llvm::SmallVector<std::tuple<mlir::Value, mlir::Value, mlir::Value>>
124+
genLoopBounds(fir::FirOpBuilder &builder, mlir::Location loc);
125+
126+
/// Lowered base of the ranked array ref.
127+
fir::ExtendedValue loweredBase;
128+
/// Subscripts values of the rank arrayRef part.
129+
llvm::SmallVector<LoweredSubscript, 16> loweredSubscripts;
130+
/// Scalar subscripts and components at the right of the ranked
131+
/// array ref part of any.
132+
llvm::SmallVector<mlir::Value> componentPath;
133+
/// List of substring bounds if this is a substring (only the lower bound if
134+
/// the upper is implicit).
135+
MaybeSubstring substringBounds;
136+
/// Type of the elements described by this array section.
137+
mlir::Type elementType;
138+
};
139+
140+
/// Lower \p expr, that must be an designator containing vector subscripts, to a
141+
/// VectorSubscriptBox representation. This causes evaluation of all the
142+
/// subscripts. Any required clean-ups from subscript expression are added to \p
143+
/// stmtCtx.
144+
VectorSubscriptBox genVectorSubscriptBox(
145+
mlir::Location loc, Fortran::lower::AbstractConverter &converter,
146+
Fortran::lower::StatementContext &stmtCtx,
147+
const Fortran::evaluate::Expr<Fortran::evaluate::SomeType> &expr);
148+
149+
} // namespace lower
150+
} // namespace Fortran
151+
152+
#endif // FORTRAN_LOWER_VECTORSUBSCRIPTS_H

flang/include/flang/Optimizer/Builder/FIRBuilder.h

Lines changed: 26 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -336,7 +336,7 @@ class FirOpBuilder : public mlir::OpBuilder {
336336

337337
/// Generate code testing \p addr is not a null address.
338338
mlir::Value genIsNotNull(mlir::Location loc, mlir::Value addr);
339-
339+
340340
/// Generate code testing \p addr is a null address.
341341
mlir::Value genIsNull(mlir::Location loc, mlir::Value addr);
342342

@@ -428,12 +428,37 @@ fir::ExtendedValue componentToExtendedValue(fir::FirOpBuilder &builder,
428428
mlir::Location loc,
429429
mlir::Value component);
430430

431+
/// Given the address of an array element and the ExtendedValue describing the
432+
/// array, returns the ExtendedValue describing the array element. The purpose
433+
/// is to propagate the length parameters of the array to the element.
434+
/// This can be used for elements of `array` or `array(i:j:k)`. If \p element
435+
/// belongs to an array section `array%x` whose base is \p array,
436+
/// arraySectionElementToExtendedValue must be used instead.
437+
fir::ExtendedValue arrayElementToExtendedValue(fir::FirOpBuilder &builder,
438+
mlir::Location loc,
439+
const fir::ExtendedValue &array,
440+
mlir::Value element);
441+
442+
/// Build the ExtendedValue for \p element that is an element of an array or
443+
/// array section with \p array base (`array` or `array(i:j:k)%x%y`).
444+
/// If it is an array section, \p slice must be provided and be a fir::SliceOp
445+
/// that describes the section.
446+
fir::ExtendedValue arraySectionElementToExtendedValue(
447+
fir::FirOpBuilder &builder, mlir::Location loc,
448+
const fir::ExtendedValue &array, mlir::Value element, mlir::Value slice);
449+
431450
/// Assign \p rhs to \p lhs. Both \p rhs and \p lhs must be scalar derived
432451
/// types. The assignment follows Fortran intrinsic assignment semantic for
433452
/// derived types (10.2.1.3 point 13).
434453
void genRecordAssignment(fir::FirOpBuilder &builder, mlir::Location loc,
435454
const fir::ExtendedValue &lhs,
436455
const fir::ExtendedValue &rhs);
456+
457+
/// Compute the extent of (lb:ub:step) as max((ub-lb+step)/step, 0). See Fortran
458+
/// 2018 9.5.3.3.2 section for more details.
459+
mlir::Value computeTripletExtent(fir::FirOpBuilder &builder, mlir::Location loc,
460+
mlir::Value lb, mlir::Value ub,
461+
mlir::Value step, mlir::Type type);
437462
} // namespace fir::factory
438463

439464
#endif // FORTRAN_OPTIMIZER_BUILDER_FIRBUILDER_H

flang/lib/Lower/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ add_flang_library(FortranLower
1919
PFTBuilder.cpp
2020
Runtime.cpp
2121
SymbolMap.cpp
22+
VectorSubscripts.cpp
2223

2324
DEPENDS
2425
FIRBuilder

flang/lib/Lower/ConvertExpr.cpp

Lines changed: 9 additions & 56 deletions
Original file line numberDiff line numberDiff line change
@@ -207,54 +207,6 @@ static bool isAllocatableOrPointer(const Fortran::lower::SomeExpr &expr) {
207207
return sym && Fortran::semantics::IsAllocatableOrPointer(*sym);
208208
}
209209

210-
/// Given the address of an array element and the ExtendedValue describing the
211-
/// array, returns the ExtendedValue describing the array element. The purpose
212-
/// is to propagate the length parameters of the array to the element.
213-
/// This can be used for elements of `array` or `array(i:j:k)`. If \p element
214-
/// belongs to an array section `array%x` whose base is \p array,
215-
/// arraySectionElementToExtendedValue must be used instead.
216-
static fir::ExtendedValue
217-
arrayElementToExtendedValue(fir::FirOpBuilder &builder, mlir::Location loc,
218-
const fir::ExtendedValue &array,
219-
mlir::Value element) {
220-
return array.match(
221-
[&](const fir::CharBoxValue &cb) -> fir::ExtendedValue {
222-
return cb.clone(element);
223-
},
224-
[&](const fir::CharArrayBoxValue &bv) -> fir::ExtendedValue {
225-
return bv.cloneElement(element);
226-
},
227-
[&](const fir::BoxValue &box) -> fir::ExtendedValue {
228-
if (box.isCharacter()) {
229-
auto len = fir::factory::readCharLen(builder, loc, box);
230-
return fir::CharBoxValue{element, len};
231-
}
232-
if (box.isDerivedWithLengthParameters())
233-
TODO(loc, "get length parameters from derived type BoxValue");
234-
return element;
235-
},
236-
[&](const auto &) -> fir::ExtendedValue { return element; });
237-
}
238-
239-
/// Build the ExtendedValue for \p element that is an element of an array or
240-
/// array section with \p array base (`array` or `array(i:j:k)%x%y`).
241-
/// If it is an array section, \p slice must be provided and be a fir::SliceOp
242-
/// that describes the section.
243-
static fir::ExtendedValue arraySectionElementToExtendedValue(
244-
fir::FirOpBuilder &builder, mlir::Location loc,
245-
const fir::ExtendedValue &array, mlir::Value element, mlir::Value slice) {
246-
if (!slice)
247-
return arrayElementToExtendedValue(builder, loc, array, element);
248-
auto sliceOp = mlir::dyn_cast_or_null<fir::SliceOp>(slice.getDefiningOp());
249-
assert(sliceOp && "slice must be a sliceOp");
250-
if (sliceOp.fields().empty())
251-
return arrayElementToExtendedValue(builder, loc, array, element);
252-
// For F95, using componentToExtendedValue will work, but when PDTs are
253-
// lowered. It will be required to go down the slice to propagate the length
254-
// parameters.
255-
return fir::factory::componentToExtendedValue(builder, loc, element);
256-
}
257-
258210
/// Convert the array_load, `load`, to an extended value. If `path` is not
259211
/// empty, then traverse through the components designated. The base value is
260212
/// `newBase`. This does not accept an array_load with a slice operand.
@@ -1442,7 +1394,7 @@ class ScalarExprLowering {
14421394
assert(args.size() == seqTy.getDimension());
14431395
auto ty = builder.getRefType(seqTy.getEleTy());
14441396
auto addr = builder.create<fir::CoordinateOp>(loc, ty, base, args);
1445-
return arrayElementToExtendedValue(builder, loc, array, addr);
1397+
return fir::factory::arrayElementToExtendedValue(builder, loc, array, addr);
14461398
}
14471399

14481400
/// Lower an ArrayRef to a fir.coordinate_of using an element offset instead
@@ -1552,7 +1504,8 @@ class ScalarExprLowering {
15521504
auto elementAddr = builder.create<fir::ArrayCoorOp>(
15531505
loc, refTy, addr, shape, /*slice=*/mlir::Value{}, arrayCoorArgs,
15541506
fir::getTypeParams(exv));
1555-
return arrayElementToExtendedValue(builder, loc, exv, elementAddr);
1507+
return fir::factory::arrayElementToExtendedValue(builder, loc, exv,
1508+
elementAddr);
15561509
}
15571510

15581511
/// Return the coordinate of the array reference.
@@ -4842,8 +4795,8 @@ class ArrayExprLowering {
48424795
mlir::Value coor = builder.create<fir::ArrayCoorOp>(
48434796
loc, refEleTy, memref, shape, slice, indices,
48444797
fir::getTypeParams(extMemref));
4845-
return arraySectionElementToExtendedValue(builder, loc, extMemref, coor,
4846-
slice);
4798+
return fir::factory::arraySectionElementToExtendedValue(
4799+
builder, loc, extMemref, coor, slice);
48474800
};
48484801
}
48494802
auto arrLoad = builder.create<fir::ArrayLoadOp>(
@@ -4893,8 +4846,8 @@ class ArrayExprLowering {
48934846
llvm::ArrayRef<mlir::NamedAttribute>{
48944847
Fortran::lower::getAdaptToByRefAttr(builder)});
48954848
builder.create<fir::StoreOp>(loc, base, temp);
4896-
return arraySectionElementToExtendedValue(builder, loc, extMemref, temp,
4897-
slice);
4849+
return fir::factory::arraySectionElementToExtendedValue(
4850+
builder, loc, extMemref, temp, slice);
48984851
};
48994852
}
49004853
// In the default case, the array reference forwards an `array_fetch` Op
@@ -4903,8 +4856,8 @@ class ArrayExprLowering {
49034856
auto arrFetch = builder.create<fir::ArrayFetchOp>(
49044857
loc, adjustedArraySubtype(arrTy, iters.iterVec()), arrLd,
49054858
iters.iterVec(), arrLdTypeParams);
4906-
return arraySectionElementToExtendedValue(builder, loc, extMemref,
4907-
arrFetch, slice);
4859+
return fir::factory::arraySectionElementToExtendedValue(
4860+
builder, loc, extMemref, arrFetch, slice);
49084861
};
49094862
}
49104863

0 commit comments

Comments
 (0)