Skip to content

Commit

Permalink
Split a Directive Evaluation variant out from the Construct variant.
Browse files Browse the repository at this point in the history
  • Loading branch information
vdonaldson committed May 20, 2020
1 parent ba2bd44 commit 787f290
Show file tree
Hide file tree
Showing 3 changed files with 41 additions and 31 deletions.
26 changes: 18 additions & 8 deletions flang/include/flang/Lower/PFTBuilder.h
Original file line number Diff line number Diff line change
Expand Up @@ -87,8 +87,11 @@ using Constructs =
parser::CriticalConstruct, parser::DoConstruct,
parser::IfConstruct, parser::SelectRankConstruct,
parser::SelectTypeConstruct, parser::WhereConstruct,
parser::ForallConstruct, parser::CompilerDirective,
parser::OpenMPConstruct, parser::OmpEndLoopDirective>;
parser::ForallConstruct>;

using Directives =
std::tuple<parser::CompilerDirective, parser::OpenMPConstruct,
parser::OmpEndLoopDirective>;

template <typename A>
static constexpr bool isActionStmt{common::HasMember<A, ActionStmts>};
Expand All @@ -102,6 +105,9 @@ static constexpr bool isConstructStmt{common::HasMember<A, ConstructStmts>};
template <typename A>
static constexpr bool isConstruct{common::HasMember<A, Constructs>};

template <typename A>
static constexpr bool isDirective{common::HasMember<A, Directives>};

template <typename A>
static constexpr bool isIntermediateConstructStmt{common::HasMember<
A, std::tuple<parser::CaseStmt, parser::ElseIfStmt, parser::ElseStmt,
Expand Down Expand Up @@ -175,7 +181,8 @@ template <typename A>
using MakeReferenceVariant = typename MakeReferenceVariantHelper<A>::type;

using EvaluationTuple =
common::CombineTuples<ActionStmts, OtherStmts, ConstructStmts, Constructs>;
common::CombineTuples<ActionStmts, OtherStmts, ConstructStmts, Constructs,
Directives>;
/// Hide non-nullable pointers to the parse-tree node.
/// Build type std::variant<const A* const, const B* const, ...>
/// from EvaluationTuple type (std::tuple<A, B, ...>).
Expand All @@ -197,7 +204,8 @@ struct Evaluation : EvaluationVariant {
template <typename A>
Evaluation(const A &a, const ParentVariant &parentVariant)
: EvaluationVariant{a}, parentVariant{parentVariant} {
static_assert(pft::isConstruct<A>, "must be a construct");
static_assert(pft::isConstruct<A> || pft::isDirective<A>,
"must be a construct or directive");
}

/// Evaluation classification predicates.
Expand All @@ -218,10 +226,12 @@ struct Evaluation : EvaluationVariant {
return visit(common::visitors{
[](auto &r) { return pft::isConstruct<std::decay_t<decltype(r)>>; }});
}

/// For a construct with multiway control-flow semantics, return true if this
/// is one of the alternative condition statements of the construct. For
/// example, `ELSE IF` in an `IF` construct.
constexpr bool isDirective() const {
return visit(common::visitors{
[](auto &r) { return pft::isDirective<std::decay_t<decltype(r)>>; }});
}
/// Return the predicate: "This is a non-initial, non-terminal construct
/// statement." For an IfConstruct, this is ElseIfStmt and ElseStmt.
constexpr bool isIntermediateConstructStmt() const {
return visit(common::visitors{[](auto &r) {
return pft::isIntermediateConstructStmt<std::decay_t<decltype(r)>>;
Expand Down
20 changes: 9 additions & 11 deletions flang/lib/Lower/Bridge.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -773,17 +773,16 @@ class FirConverter : public Fortran::lower::AbstractConverter {
/// Generate FIR to begin a structured or unstructured increment loop.
void genFIRIncrementLoopBegin(IncrementLoopInfo &info) {
auto location = toLocation();
mlir::Type type = info.isStructured()
? mlir::IndexType::get(builder->getContext())
: info.loopVariableType;
mlir::Type type =
info.isStructured() ? builder->getIndexType() : info.loopVariableType;
auto lowerValue = genFIRLoopIndex(info.lowerExpr, type);
auto upperValue = genFIRLoopIndex(info.upperExpr, type);
info.stepValue =
info.stepExpr.has_value()
? genFIRLoopIndex(*info.stepExpr, type)
: (info.isStructured()
? builder->create<mlir::ConstantIndexOp>(location, 1)
: builder->createIntegerConstant(info.loopVariableType, 1));
: info.isStructured()
? builder->create<mlir::ConstantIndexOp>(location, 1)
: builder->createIntegerConstant(info.loopVariableType, 1);
assert(info.stepValue && "step value must be set");
info.loopVariable = createTemp(location, *info.loopVariableSym);

Expand Down Expand Up @@ -1279,7 +1278,7 @@ class FirConverter : public Fortran::lower::AbstractConverter {
auto ty = genType(*sym.symbol);
auto load = builder->create<fir::LoadOp>(
toLocation(), lookupSymbol(*sym.symbol));
auto idxTy = mlir::IndexType::get(&mlirContext);
auto idxTy = builder->getIndexType();
auto zero = builder->create<mlir::ConstantOp>(
toLocation(), idxTy, builder->getIntegerAttr(idxTy, 0));
auto cast = builder->createConvert(toLocation(), ty, zero);
Expand Down Expand Up @@ -1668,8 +1667,7 @@ class FirConverter : public Fortran::lower::AbstractConverter {
if (unstructuredContext) {
// When transitioning from unstructured to structured code,
// the structured code might be a target that starts a new block.
maybeStartBlock(eval.isConstruct() && eval.lowerAsStructured() &&
!eval.evaluationList->empty()
maybeStartBlock(eval.isConstruct() && eval.lowerAsStructured()
? eval.evaluationList->front().block
: eval.block);
}
Expand All @@ -1679,7 +1677,7 @@ class FirConverter : public Fortran::lower::AbstractConverter {
Fortran::lower::pft::Evaluation *successor{};
if (eval.isActionStmt())
successor = eval.controlSuccessor;
else if (eval.isConstruct() && !eval.evaluationList->empty() &&
else if (eval.isConstruct() &&
eval.evaluationList->back()
.lexicalSuccessor->isIntermediateConstructStmt())
successor = eval.constructExit;
Expand Down Expand Up @@ -2057,7 +2055,7 @@ class FirConverter : public Fortran::lower::AbstractConverter {
eval.block = builder->createBlock(&builder->getRegion());
for (size_t i = 0, n = eval.localBlocks.size(); i < n; ++i)
eval.localBlocks[i] = builder->createBlock(&builder->getRegion());
if (eval.isConstruct()) {
if (eval.isConstruct() || eval.isDirective()) {
if (eval.lowerAsUnstructured()) {
createEmptyBlocks(*eval.evaluationList);
} else {
Expand Down
26 changes: 14 additions & 12 deletions flang/lib/Lower/PFTBuilder.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -74,8 +74,9 @@ class PFTBuilder {
constexpr bool Pre(const A &a) {
if constexpr (lower::pft::isFunctionLike<A>) {
return enterFunction(a, semanticsContext);
} else if constexpr (lower::pft::isConstruct<A>) {
return enterConstruct(a);
} else if constexpr (lower::pft::isConstruct<A> ||
lower::pft::isDirective<A>) {
return enterConstructOrDirective(a);
} else if constexpr (UnwrapStmt<A>::isStmt) {
using T = typename UnwrapStmt<A>::Type;
// Node "a" being visited has one of the following types:
Expand All @@ -101,8 +102,9 @@ class PFTBuilder {
constexpr void Post(const A &) {
if constexpr (lower::pft::isFunctionLike<A>) {
exitFunction();
} else if constexpr (lower::pft::isConstruct<A>) {
exitConstruct();
} else if constexpr (lower::pft::isConstruct<A> ||
lower::pft::isDirective<A>) {
exitConstructOrDirective();
}
}

Expand Down Expand Up @@ -201,20 +203,20 @@ class PFTBuilder {

/// Initialize a new construct and make it the builder's focus.
template <typename A>
bool enterConstruct(const A &construct) {
bool enterConstructOrDirective(const A &construct) {
auto &eval = addEvaluation(
lower::pft::Evaluation{construct, parentVariantStack.back()});
eval.evaluationList.reset(new lower::pft::EvaluationList);
pushEvaluationList(eval.evaluationList.get());
parentVariantStack.emplace_back(eval);
constructStack.emplace_back(&eval);
constructAndDirectiveStack.emplace_back(&eval);
return true;
}

void exitConstruct() {
void exitConstructOrDirective() {
popEvaluationList();
parentVariantStack.pop_back();
constructStack.pop_back();
constructAndDirectiveStack.pop_back();
}

/// Reset functionList to an enclosing function's functionList.
Expand Down Expand Up @@ -269,8 +271,8 @@ class PFTBuilder {
lower::pft::Evaluation &addEvaluation(lower::pft::Evaluation &&eval) {
assert(functionList && "not in a function");
assert(evaluationListStack.size() > 0);
if (constructStack.size() > 0) {
eval.parentConstruct = constructStack.back();
if (constructAndDirectiveStack.size() > 0) {
eval.parentConstruct = constructAndDirectiveStack.back();
}
evaluationListStack.back()->emplace_back(std::move(eval));
lower::pft::Evaluation *p = &evaluationListStack.back()->back();
Expand Down Expand Up @@ -732,7 +734,7 @@ class PFTBuilder {
/// functionList points to the internal or module procedure function list
/// of a FunctionLikeUnit or a ModuleLikeUnit. It may be null.
std::list<lower::pft::FunctionLikeUnit> *functionList{nullptr};
std::vector<lower::pft::Evaluation *> constructStack{};
std::vector<lower::pft::Evaluation *> constructAndDirectiveStack{};
std::vector<lower::pft::Evaluation *> doConstructStack{};
/// evaluationListStack is the current nested construct evaluationList state.
std::vector<lower::pft::EvaluationList *> evaluationListStack{};
Expand Down Expand Up @@ -780,7 +782,7 @@ class PFTDumper {
for (lower::pft::Evaluation &eval : evaluationList) {
llvm::StringRef name{evaluationName(eval)};
std::string bang{eval.isUnstructured ? "!" : ""};
if (eval.isConstruct()) {
if (eval.isConstruct() || eval.isDirective()) {
outputStream << indentString << "<<" << name << bang << ">>";
if (eval.constructExit) {
outputStream << " -> " << eval.constructExit->printIndex;
Expand Down

0 comments on commit 787f290

Please sign in to comment.