Skip to content

Commit 982e852

Browse files
authored
Merge pull request #1075 from flang-compiler/ch-forall
Changes to make assignments inside FORALL constructs use the array_loads
2 parents 0792de9 + 45b5779 commit 982e852

File tree

14 files changed

+1252
-750
lines changed

14 files changed

+1252
-750
lines changed

flang/include/flang/Lower/ConvertExpr.h

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -166,7 +166,6 @@ void createAllocatableArrayAssignment(
166166
/// is fully evaluated prior to being assigned back to a temporary array.
167167
fir::ExtendedValue
168168
createSomeArrayTempValue(AbstractConverter &converter,
169-
const std::optional<evaluate::Shape> &shape,
170169
const evaluate::Expr<evaluate::SomeType> &expr,
171170
SymMap &symMap, StatementContext &stmtCtx);
172171

Lines changed: 201 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,201 @@
1+
//===-- Lower/EvExprDumper.h ------------------------------------*- 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+
#ifndef FORTRAN_LOWER_EVEXPRDUMPER_H
10+
#define FORTRAN_LOWER_EVEXPRDUMPER_H
11+
12+
#include "flang/Evaluate/tools.h"
13+
#include "flang/Lower/Support/Utils.h"
14+
#include "llvm/ADT/StringRef.h"
15+
#include "llvm/ADT/Twine.h"
16+
17+
namespace Fortran::lower {
18+
19+
/// Class to dump Fortran::evaluate::Expr trees out in a user readable way.
20+
///
21+
/// FIXME: This can be improved to dump more information in some cases.
22+
class DumpEvaluateExpr {
23+
public:
24+
DumpEvaluateExpr() : outs(llvm::errs()) {}
25+
DumpEvaluateExpr(llvm::raw_ostream &str) : outs(str) {}
26+
27+
template <typename A>
28+
LLVM_DUMP_METHOD static void dump(const A &x) {
29+
DumpEvaluateExpr{}.show(x);
30+
}
31+
template <typename A>
32+
LLVM_DUMP_METHOD static void dump(llvm::raw_ostream &stream, const A &x) {
33+
DumpEvaluateExpr{stream}.show(x);
34+
}
35+
36+
private:
37+
template <typename A, bool C>
38+
LLVM_DUMP_METHOD void show(const Fortran::common::Indirection<A, C> &x) {
39+
show(x.value());
40+
}
41+
template <typename A>
42+
LLVM_DUMP_METHOD void show(const Fortran::semantics::SymbolRef x) {
43+
show(*x);
44+
}
45+
template <typename A>
46+
LLVM_DUMP_METHOD void show(const std::unique_ptr<A> &x) {
47+
show(x.get());
48+
}
49+
template <typename A>
50+
LLVM_DUMP_METHOD void show(const std::shared_ptr<A> &x) {
51+
show(x.get());
52+
}
53+
template <typename A>
54+
LLVM_DUMP_METHOD void show(const A *x) {
55+
if (x) {
56+
show(*x);
57+
return;
58+
}
59+
print("nullptr");
60+
}
61+
template <typename A>
62+
LLVM_DUMP_METHOD void show(const std::optional<A> &x) {
63+
if (x) {
64+
show(*x);
65+
return;
66+
}
67+
print("None");
68+
}
69+
template <typename... A>
70+
LLVM_DUMP_METHOD void show(const std::variant<A...> &u) {
71+
std::visit([&](const auto &v) { show(v); }, u);
72+
}
73+
template <typename A>
74+
LLVM_DUMP_METHOD void show(const std::vector<A> &x) {
75+
indent("vector");
76+
for (const auto &v : x)
77+
show(v);
78+
outdent();
79+
}
80+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::BOZLiteralConstant &);
81+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::NullPointer &);
82+
template <typename T>
83+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::Constant<T> &x) {
84+
if constexpr (T::category == Fortran::common::TypeCategory::Derived) {
85+
indent("derived constant");
86+
for (const auto &map : x.values())
87+
for (const auto &pair : map)
88+
show(pair.second.value());
89+
outdent();
90+
} else {
91+
print("constant");
92+
}
93+
}
94+
LLVM_DUMP_METHOD void show(const Fortran::semantics::Symbol &symbol);
95+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::StaticDataObject &);
96+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::ImpliedDoIndex &);
97+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::BaseObject &x);
98+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::Component &x);
99+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::NamedEntity &x);
100+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::TypeParamInquiry &x);
101+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::Triplet &x);
102+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::Subscript &x);
103+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::ArrayRef &x);
104+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::CoarrayRef &x);
105+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::DataRef &x);
106+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::Substring &x);
107+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::ComplexPart &x);
108+
template <typename T>
109+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::Designator<T> &x) {
110+
indent("designator");
111+
show(x.u);
112+
outdent();
113+
}
114+
template <typename T>
115+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::Variable<T> &x) {
116+
indent("variable");
117+
show(x.u);
118+
outdent();
119+
}
120+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::DescriptorInquiry &x);
121+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::SpecificIntrinsic &);
122+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::ProcedureDesignator &x);
123+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::ActualArgument &x);
124+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::ProcedureRef &x) {
125+
indent("procedure ref");
126+
show(x.proc());
127+
show(x.arguments());
128+
outdent();
129+
}
130+
template <typename T>
131+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::FunctionRef<T> &x) {
132+
indent("function ref");
133+
show(x.proc());
134+
show(x.arguments());
135+
outdent();
136+
}
137+
template <typename T>
138+
LLVM_DUMP_METHOD void
139+
show(const Fortran::evaluate::ArrayConstructorValue<T> &x) {
140+
show(x.u);
141+
}
142+
template <typename T>
143+
LLVM_DUMP_METHOD void
144+
show(const Fortran::evaluate::ArrayConstructorValues<T> &x) {
145+
indent("array constructor value");
146+
for (auto &v : x)
147+
show(v);
148+
outdent();
149+
}
150+
template <typename T>
151+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::ImpliedDo<T> &x) {
152+
indent("implied do");
153+
show(x.lower());
154+
show(x.upper());
155+
show(x.stride());
156+
show(x.values());
157+
outdent();
158+
}
159+
LLVM_DUMP_METHOD void show(const Fortran::semantics::ParamValue &x);
160+
LLVM_DUMP_METHOD void
161+
show(const Fortran::semantics::DerivedTypeSpec::ParameterMapType::value_type
162+
&x);
163+
LLVM_DUMP_METHOD void show(const Fortran::semantics::DerivedTypeSpec &x);
164+
LLVM_DUMP_METHOD void
165+
show(const Fortran::evaluate::StructureConstructorValues::value_type &x);
166+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::StructureConstructor &x);
167+
template <typename D, typename R, typename O>
168+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::Operation<D, R, O> &op) {
169+
indent("unary op");
170+
show(op.left());
171+
outdent();
172+
}
173+
template <typename D, typename R, typename LO, typename RO>
174+
LLVM_DUMP_METHOD void
175+
show(const Fortran::evaluate::Operation<D, R, LO, RO> &op) {
176+
indent("binary op");
177+
show(op.left());
178+
show(op.right());
179+
outdent();
180+
}
181+
LLVM_DUMP_METHOD void
182+
show(const Fortran::evaluate::Relational<Fortran::evaluate::SomeType> &x);
183+
template <typename T>
184+
LLVM_DUMP_METHOD void show(const Fortran::evaluate::Expr<T> &x) {
185+
indent("expr T");
186+
show(x.u);
187+
outdent();
188+
}
189+
190+
llvm::StringRef getIndentString() const;
191+
void print(llvm::Twine s);
192+
void indent(llvm::StringRef s);
193+
void outdent();
194+
195+
llvm::raw_ostream &outs;
196+
unsigned level = 0;
197+
};
198+
199+
} // namespace Fortran::lower
200+
201+
#endif // FORTRAN_LOWER_EVEXPRDUMPER_H

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

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -250,7 +250,7 @@ class FirOpBuilder : public mlir::OpBuilder {
250250
/// Construct one of the two forms of shape op from an array box.
251251
mlir::Value genShape(mlir::Location loc, const fir::AbstractArrayBox &arr);
252252
mlir::Value genShape(mlir::Location loc, llvm::ArrayRef<mlir::Value> shift,
253-
llvm::ArrayRef<mlir::Value> exts);
253+
llvm::ArrayRef<mlir::Value> exts);
254254
mlir::Value genShape(mlir::Location loc, llvm::ArrayRef<mlir::Value> exts);
255255

256256
/// Create one of the shape ops given an extended value. For a boxed value,
@@ -340,6 +340,12 @@ class FirOpBuilder : public mlir::OpBuilder {
340340
/// Generate code testing \p addr is a null address.
341341
mlir::Value genIsNull(mlir::Location loc, mlir::Value addr);
342342

343+
/// Compute the extent of (lb:ub:step) as max((ub-lb+step)/step, 0). See
344+
/// Fortran 2018 9.5.3.3.2 section for more details.
345+
mlir::Value genExtentFromTriplet(mlir::Location loc, mlir::Value lb,
346+
mlir::Value ub, mlir::Value step,
347+
mlir::Type type);
348+
343349
private:
344350
const KindMapping &kindMap;
345351
};
@@ -454,11 +460,6 @@ void genRecordAssignment(fir::FirOpBuilder &builder, mlir::Location loc,
454460
const fir::ExtendedValue &lhs,
455461
const fir::ExtendedValue &rhs);
456462

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);
462463
} // namespace fir::factory
463464

464465
#endif // FORTRAN_OPTIMIZER_BUILDER_FIRBUILDER_H

flang/include/flang/Optimizer/Dialect/FIRType.h

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -162,6 +162,16 @@ inline bool sequenceWithNonConstantShape(fir::SequenceType seqTy) {
162162
/// Returns true iff the type `t` does not have a constant size.
163163
bool hasDynamicSize(mlir::Type t);
164164

165+
inline unsigned getRankOfShapeType(mlir::Type t) {
166+
if (auto shTy = t.dyn_cast<fir::ShapeType>())
167+
return shTy.getRank();
168+
if (auto shTy = t.dyn_cast<fir::ShapeShiftType>())
169+
return shTy.getRank();
170+
if (auto shTy = t.dyn_cast<fir::ShiftType>())
171+
return shTy.getRank();
172+
return 0;
173+
}
174+
165175
/// If `t` is a SequenceType return its element type, otherwise return `t`.
166176
inline mlir::Type unwrapSequenceType(mlir::Type t) {
167177
if (auto seqTy = t.dyn_cast<fir::SequenceType>())

flang/lib/Lower/Bridge.cpp

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1947,6 +1947,9 @@ class FirConverter : public Fortran::lower::AbstractConverter {
19471947
: stmtCtx;
19481948
Fortran::lower::createSubroutineCall(
19491949
*this, expr, localSymbols, ctx, /*isUserDefAssignment=*/true);
1950+
if (explicitIterationSpace())
1951+
builder->create<fir::ResultOp>(
1952+
loc, explicitIterSpace.getInnerArgs());
19501953
},
19511954

19521955
// [3] Pointer assignment with possibly empty bounds-spec. R1035: a

flang/lib/Lower/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ add_flang_library(FortranLower
99
ConvertExpr.cpp
1010
ConvertType.cpp
1111
ConvertVariable.cpp
12+
EvExprDumper.cpp
1213
HostAssociations.cpp
1314
IntrinsicCall.cpp
1415
IO.cpp

0 commit comments

Comments
 (0)