Skip to content

Commit

Permalink
Handling the name resolution for select rank
Browse files Browse the repository at this point in the history
0. Added a new field in AssocEntityDetails which is a std::optonal<int> field holding the rank of a symbol, this field is explicitely set when an AssocEntityDetails is created w.r.t SelectRank, not tested with other assocEntityDetails related symbols(like select type or Associations).
1. Added getters and setters for setting the above variable.
2. Changes to getters and setters for retrieving the values from std::optional
3. Changes to the printing of symbol to adapt to adding 'rank: ' field for AssocEntityDetails based symbols, Also the Rank API in class Symbol is changed to handle the above change.
4. Added scope creation rules for selectRankCaseStmt, i.e inside each selectRankCaseStmt a scope::Kind::Block is created.
5. Setting the type, attributes and rank of a symbol which is newly created in the block scope also first setting the Details of the newly created symbol.
6.Remove the unnecessary changes in 'setRankFromParserNode' in resolve-names.cpp, as seems to be unnecessary as of now.

7. Change 'getAssocRank' to 'associationRank' based on C++17 guidelines
8. Did minor changes before pushing

Clang formatted code
  • Loading branch information
Sameeranjoshi committed Mar 23, 2020
1 parent 12f5860 commit 6966342
Show file tree
Hide file tree
Showing 3 changed files with 79 additions and 8 deletions.
17 changes: 16 additions & 1 deletion include/flang/Semantics/symbol.h
Original file line number Diff line number Diff line change
Expand Up @@ -139,8 +139,18 @@ class AssocEntityDetails : public EntityDetails {
AssocEntityDetails &operator=(AssocEntityDetails &&) = default;
const MaybeExpr &expr() const { return expr_; }

void set_rank(int rank);
std::optional<int> associationRank() const {
if (associationRank_.has_value()) {
return associationRank_.value();
} else {
return {};
}
}

private:
MaybeExpr expr_;
std::optional<int> associationRank_;
};

// An entity known to be an object.
Expand Down Expand Up @@ -565,6 +575,7 @@ class Symbol {
}

void SetType(const DeclTypeSpec &);
void SetRank(const int rank);

bool IsDummy() const;
bool IsFuncResult() const;
Expand Down Expand Up @@ -616,7 +627,11 @@ class Symbol {
[](const ObjectEntityDetails &oed) { return oed.shape().Rank(); },
[](const AssocEntityDetails &aed) {
if (const auto &expr{aed.expr()}) {
return expr->Rank();
if (aed.associationRank().has_value()) {
return aed.associationRank().value();
} else {
return expr->Rank();
}
} else {
return 0;
}
Expand Down
58 changes: 51 additions & 7 deletions lib/Semantics/resolve-names.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -966,12 +966,18 @@ class ConstructVisitor : public virtual DeclarationVisitor {
void Post(const parser::EndAssociateStmt &);
void Post(const parser::Association &);
void Post(const parser::SelectTypeStmt &);

void Post(const parser::SelectRankStmt &);
bool Pre(const parser::SelectTypeConstruct &);
void Post(const parser::SelectTypeConstruct &);
bool Pre(const parser::SelectTypeConstruct::TypeCase &);
void Post(const parser::SelectTypeConstruct::TypeCase &);
// gives blank scopes
bool Pre(const parser::SelectRankConstruct::RankCase &);
void Post(const parser::SelectRankConstruct::RankCase &);
void Post(const parser::TypeGuardStmt::Guard &);
void Post(const parser::SelectRankCaseStmt::Rank &);

bool Pre(const parser::ChangeTeamStmt &);
void Post(const parser::EndChangeTeamStmt &);
void Post(const parser::CoarrayAssociation &);
Expand Down Expand Up @@ -1044,6 +1050,7 @@ class ConstructVisitor : public virtual DeclarationVisitor {
Symbol *MakeAssocEntity();
void SetTypeFromAssociation(Symbol &);
void SetAttrsFromAssociation(Symbol &);
void SetRankFromParserNode(Symbol &, int actualRank);
Selector ResolveSelector(const parser::Selector &);
void ResolveIndexName(const parser::ConcurrentControl &control);
Association &GetCurrentAssociation();
Expand Down Expand Up @@ -4806,13 +4813,7 @@ bool ConstructVisitor::Pre(const parser::SelectTypeConstruct &) {
void ConstructVisitor::Post(const parser::SelectTypeConstruct &) {
PopAssociation();
}
void ConstructVisitor::Post(const parser::SelectRankStmt &x) {
auto &association{GetCurrentAssociation()};
if (const std::optional<parser::Name> &name{std::get<1>(x.t)}) {
MakePlaceholder(*name, MiscDetails::Kind::SelectRankAssociateName);
association.name = &*name;
}
}

void ConstructVisitor::Post(const parser::SelectTypeStmt &x) {
auto &association{GetCurrentAssociation()};
if (const std::optional<parser::Name> &name{std::get<1>(x.t)}) {
Expand All @@ -4836,6 +4837,15 @@ void ConstructVisitor::Post(const parser::SelectTypeStmt &x) {
}
}

void ConstructVisitor::Post(const parser::SelectRankStmt &x) {
auto &association{GetCurrentAssociation()};
if (const std::optional<parser::Name> &name{std::get<1>(x.t)}) {
// This isn't a name in the current scope, it is in each SelectRankCaseStmt
MakePlaceholder(*name, MiscDetails::Kind::SelectRankAssociateName);
association.name = &*name;
}
}

bool ConstructVisitor::Pre(const parser::SelectTypeConstruct::TypeCase &) {
PushScope(Scope::Kind::Block, nullptr);
return true;
Expand All @@ -4844,6 +4854,14 @@ void ConstructVisitor::Post(const parser::SelectTypeConstruct::TypeCase &) {
PopScope();
}

bool ConstructVisitor::Pre(const parser::SelectRankConstruct::RankCase &) {
PushScope(Scope::Kind::Block, nullptr);
return true;
}
void ConstructVisitor::Post(const parser::SelectRankConstruct::RankCase &) {
PopScope();
}

void ConstructVisitor::Post(const parser::TypeGuardStmt::Guard &x) {
if (auto *symbol{MakeAssocEntity()}) {
if (std::holds_alternative<parser::Default>(x.u)) {
Expand All @@ -4855,6 +4873,25 @@ void ConstructVisitor::Post(const parser::TypeGuardStmt::Guard &x) {
}
}

void ConstructVisitor::Post(const parser::SelectRankCaseStmt::Rank &x) {
if (auto *symbol{MakeAssocEntity()}) {
SetTypeFromAssociation(*symbol);
SetAttrsFromAssociation(*symbol);
std::visit(
common::visitors{
[&](const parser::ScalarIntConstantExpr &init) {
Walk(init);
MaybeIntExpr expr{EvaluateIntExpr(init)};
if (auto val{evaluate::ToInt64(expr)}) {
SetRankFromParserNode(*symbol, *val);
}
},
[&](const auto &) {},
},
x.u);
}
}

bool ConstructVisitor::Pre(const parser::SelectRankConstruct &) {
PushAssociation();
return true;
Expand Down Expand Up @@ -4930,6 +4967,13 @@ void ConstructVisitor::SetTypeFromAssociation(Symbol &symbol) {
}
}

// Set the rank of symbol based on the current rankCase value extracted from
// evaluating the parser node.
void ConstructVisitor::SetRankFromParserNode(Symbol &symbol, int actualRank) {
const int dummyRank{actualRank};
symbol.SetRank(dummyRank);
}

// If current selector is a variable, set some of its attributes on symbol.
void ConstructVisitor::SetAttrsFromAssociation(Symbol &symbol) {
Attrs attrs{evaluate::GetAttrs(GetCurrentAssociation().selector.expr)};
Expand Down
12 changes: 12 additions & 0 deletions lib/Semantics/symbol.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -113,6 +113,7 @@ void EntityDetails::set_type(const DeclTypeSpec &type) {
type_ = &type;
}

void AssocEntityDetails::set_rank(const int rank) { associationRank_ = rank; }
void EntityDetails::ReplaceType(const DeclTypeSpec &type) { type_ = &type; }

void ObjectEntityDetails::set_shape(const ArraySpec &shape) {
Expand Down Expand Up @@ -281,6 +282,14 @@ void Symbol::SetType(const DeclTypeSpec &type) {
details_);
}

void Symbol::SetRank(const int rank) {
std::visit(
common::visitors{
[&](AssocEntityDetails &x) { x.set_rank(rank); },
[](auto &) {},
},
details_);
}
bool Symbol::IsDummy() const {
return std::visit(
common::visitors{[](const EntityDetails &x) { return x.isDummy(); },
Expand Down Expand Up @@ -357,6 +366,9 @@ llvm::raw_ostream &operator<<(
llvm::raw_ostream &operator<<(
llvm::raw_ostream &os, const AssocEntityDetails &x) {
os << *static_cast<const EntityDetails *>(&x);
if (x.associationRank().has_value()) {
os << " rank: " << x.associationRank().value();
}
DumpExpr(os, "expr", x.expr());
return os;
}
Expand Down

0 comments on commit 6966342

Please sign in to comment.