[lldb] Add ability to hide the root name of a value
[llvm-project.git] / flang / lib / Semantics / check-do-forall.cpp
blob65b2986139b4d7c0764e43cabb07b764c790d8dc
1 //===-- lib/Semantics/check-do-forall.cpp ---------------------------------===//
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 //===----------------------------------------------------------------------===//
9 #include "check-do-forall.h"
10 #include "definable.h"
11 #include "flang/Common/template.h"
12 #include "flang/Evaluate/call.h"
13 #include "flang/Evaluate/expression.h"
14 #include "flang/Evaluate/tools.h"
15 #include "flang/Parser/message.h"
16 #include "flang/Parser/parse-tree-visitor.h"
17 #include "flang/Parser/tools.h"
18 #include "flang/Semantics/attr.h"
19 #include "flang/Semantics/scope.h"
20 #include "flang/Semantics/semantics.h"
21 #include "flang/Semantics/symbol.h"
22 #include "flang/Semantics/tools.h"
23 #include "flang/Semantics/type.h"
25 namespace Fortran::evaluate {
26 using ActualArgumentRef = common::Reference<const ActualArgument>;
28 inline bool operator<(ActualArgumentRef x, ActualArgumentRef y) {
29 return &*x < &*y;
31 } // namespace Fortran::evaluate
33 namespace Fortran::semantics {
35 using namespace parser::literals;
37 using Bounds = parser::LoopControl::Bounds;
38 using IndexVarKind = SemanticsContext::IndexVarKind;
40 static const parser::ConcurrentHeader &GetConcurrentHeader(
41 const parser::LoopControl &loopControl) {
42 const auto &concurrent{
43 std::get<parser::LoopControl::Concurrent>(loopControl.u)};
44 return std::get<parser::ConcurrentHeader>(concurrent.t);
46 static const parser::ConcurrentHeader &GetConcurrentHeader(
47 const parser::ForallConstruct &construct) {
48 const auto &stmt{
49 std::get<parser::Statement<parser::ForallConstructStmt>>(construct.t)};
50 return std::get<common::Indirection<parser::ConcurrentHeader>>(
51 stmt.statement.t)
52 .value();
54 static const parser::ConcurrentHeader &GetConcurrentHeader(
55 const parser::ForallStmt &stmt) {
56 return std::get<common::Indirection<parser::ConcurrentHeader>>(stmt.t)
57 .value();
59 template <typename T>
60 static const std::list<parser::ConcurrentControl> &GetControls(const T &x) {
61 return std::get<std::list<parser::ConcurrentControl>>(
62 GetConcurrentHeader(x).t);
65 static const Bounds &GetBounds(const parser::DoConstruct &doConstruct) {
66 auto &loopControl{doConstruct.GetLoopControl().value()};
67 return std::get<Bounds>(loopControl.u);
70 static const parser::Name &GetDoVariable(
71 const parser::DoConstruct &doConstruct) {
72 const Bounds &bounds{GetBounds(doConstruct)};
73 return bounds.name.thing;
76 static parser::MessageFixedText GetEnclosingDoMsg() {
77 return "Enclosing DO CONCURRENT statement"_en_US;
80 static void SayWithDo(SemanticsContext &context, parser::CharBlock stmtLocation,
81 parser::MessageFixedText &&message, parser::CharBlock doLocation) {
82 context.Say(stmtLocation, message).Attach(doLocation, GetEnclosingDoMsg());
85 // 11.1.7.5 - enforce semantics constraints on a DO CONCURRENT loop body
86 class DoConcurrentBodyEnforce {
87 public:
88 DoConcurrentBodyEnforce(
89 SemanticsContext &context, parser::CharBlock doConcurrentSourcePosition)
90 : context_{context}, doConcurrentSourcePosition_{
91 doConcurrentSourcePosition} {}
92 std::set<parser::Label> labels() { return labels_; }
93 template <typename T> bool Pre(const T &) { return true; }
94 template <typename T> void Post(const T &) {}
96 template <typename T> bool Pre(const parser::Statement<T> &statement) {
97 currentStatementSourcePosition_ = statement.source;
98 if (statement.label.has_value()) {
99 labels_.insert(*statement.label);
101 return true;
104 template <typename T> bool Pre(const parser::UnlabeledStatement<T> &stmt) {
105 currentStatementSourcePosition_ = stmt.source;
106 return true;
109 // C1140 -- Can't deallocate a polymorphic entity in a DO CONCURRENT.
110 // Deallocation can be caused by exiting a block that declares an allocatable
111 // entity, assignment to an allocatable variable, or an actual DEALLOCATE
112 // statement
114 // Note also that the deallocation of a derived type entity might cause the
115 // invocation of an IMPURE final subroutine. (C1139)
118 // Only to be called for symbols with ObjectEntityDetails
119 static bool HasImpureFinal(const Symbol &original) {
120 const Symbol &symbol{ResolveAssociations(original)};
121 if (symbol.has<ObjectEntityDetails>()) {
122 if (const DeclTypeSpec * symType{symbol.GetType()}) {
123 if (const DerivedTypeSpec * derived{symType->AsDerived()}) {
124 return semantics::HasImpureFinal(*derived);
128 return false;
131 // Predicate for deallocations caused by block exit and direct deallocation
132 static bool DeallocateAll(const Symbol &) { return true; }
134 // Predicate for deallocations caused by intrinsic assignment
135 static bool DeallocateNonCoarray(const Symbol &component) {
136 return !evaluate::IsCoarray(component);
139 static bool WillDeallocatePolymorphic(const Symbol &entity,
140 const std::function<bool(const Symbol &)> &WillDeallocate) {
141 return WillDeallocate(entity) && IsPolymorphicAllocatable(entity);
144 // Is it possible that we will we deallocate a polymorphic entity or one
145 // of its components?
146 static bool MightDeallocatePolymorphic(const Symbol &original,
147 const std::function<bool(const Symbol &)> &WillDeallocate) {
148 const Symbol &symbol{ResolveAssociations(original)};
149 // Check the entity itself, no coarray exception here
150 if (IsPolymorphicAllocatable(symbol)) {
151 return true;
153 // Check the components
154 if (const auto *details{symbol.detailsIf<ObjectEntityDetails>()}) {
155 if (const DeclTypeSpec * entityType{details->type()}) {
156 if (const DerivedTypeSpec * derivedType{entityType->AsDerived()}) {
157 UltimateComponentIterator ultimates{*derivedType};
158 for (const auto &ultimate : ultimates) {
159 if (WillDeallocatePolymorphic(ultimate, WillDeallocate)) {
160 return true;
166 return false;
169 void SayDeallocateWithImpureFinal(const Symbol &entity, const char *reason) {
170 context_.SayWithDecl(entity, currentStatementSourcePosition_,
171 "Deallocation of an entity with an IMPURE FINAL procedure"
172 " caused by %s not allowed in DO CONCURRENT"_err_en_US,
173 reason);
176 void SayDeallocateOfPolymorph(
177 parser::CharBlock location, const Symbol &entity, const char *reason) {
178 context_.SayWithDecl(entity, location,
179 "Deallocation of a polymorphic entity caused by %s"
180 " not allowed in DO CONCURRENT"_err_en_US,
181 reason);
184 // Deallocation caused by block exit
185 // Allocatable entities and all of their allocatable subcomponents will be
186 // deallocated. This test is different from the other two because it does
187 // not deallocate in cases where the entity itself is not allocatable but
188 // has allocatable polymorphic components
189 void Post(const parser::BlockConstruct &blockConstruct) {
190 const auto &endBlockStmt{
191 std::get<parser::Statement<parser::EndBlockStmt>>(blockConstruct.t)};
192 const Scope &blockScope{context_.FindScope(endBlockStmt.source)};
193 const Scope &doScope{context_.FindScope(doConcurrentSourcePosition_)};
194 if (DoesScopeContain(&doScope, blockScope)) {
195 const char *reason{"block exit"};
196 for (auto &pair : blockScope) {
197 const Symbol &entity{*pair.second};
198 if (IsAllocatable(entity) && !IsSaved(entity) &&
199 MightDeallocatePolymorphic(entity, DeallocateAll)) {
200 SayDeallocateOfPolymorph(endBlockStmt.source, entity, reason);
202 if (HasImpureFinal(entity)) {
203 SayDeallocateWithImpureFinal(entity, reason);
209 // Deallocation caused by assignment
210 // Note that this case does not cause deallocation of coarray components
211 void Post(const parser::AssignmentStmt &stmt) {
212 const auto &variable{std::get<parser::Variable>(stmt.t)};
213 if (const Symbol * entity{GetLastName(variable).symbol}) {
214 const char *reason{"assignment"};
215 if (MightDeallocatePolymorphic(*entity, DeallocateNonCoarray)) {
216 SayDeallocateOfPolymorph(variable.GetSource(), *entity, reason);
218 if (HasImpureFinal(*entity)) {
219 SayDeallocateWithImpureFinal(*entity, reason);
224 // Deallocation from a DEALLOCATE statement
225 // This case is different because DEALLOCATE statements deallocate both
226 // ALLOCATABLE and POINTER entities
227 void Post(const parser::DeallocateStmt &stmt) {
228 const auto &allocateObjectList{
229 std::get<std::list<parser::AllocateObject>>(stmt.t)};
230 for (const auto &allocateObject : allocateObjectList) {
231 const parser::Name &name{GetLastName(allocateObject)};
232 const char *reason{"a DEALLOCATE statement"};
233 if (name.symbol) {
234 const Symbol &entity{*name.symbol};
235 const DeclTypeSpec *entityType{entity.GetType()};
236 if ((entityType && entityType->IsPolymorphic()) || // POINTER case
237 MightDeallocatePolymorphic(entity, DeallocateAll)) {
238 SayDeallocateOfPolymorph(
239 currentStatementSourcePosition_, entity, reason);
241 if (HasImpureFinal(entity)) {
242 SayDeallocateWithImpureFinal(entity, reason);
248 // C1137 -- No image control statements in a DO CONCURRENT
249 void Post(const parser::ExecutableConstruct &construct) {
250 if (IsImageControlStmt(construct)) {
251 const parser::CharBlock statementLocation{
252 GetImageControlStmtLocation(construct)};
253 auto &msg{context_.Say(statementLocation,
254 "An image control statement is not allowed in DO"
255 " CONCURRENT"_err_en_US)};
256 if (auto coarrayMsg{GetImageControlStmtCoarrayMsg(construct)}) {
257 msg.Attach(statementLocation, *coarrayMsg);
259 msg.Attach(doConcurrentSourcePosition_, GetEnclosingDoMsg());
263 // C1136 -- No RETURN statements in a DO CONCURRENT
264 void Post(const parser::ReturnStmt &) {
265 context_
266 .Say(currentStatementSourcePosition_,
267 "RETURN is not allowed in DO CONCURRENT"_err_en_US)
268 .Attach(doConcurrentSourcePosition_, GetEnclosingDoMsg());
271 // C1139: call to impure procedure and ...
272 // C1141: cannot call ieee_get_flag, ieee_[gs]et_halting_mode
273 // It's not necessary to check the ieee_get* procedures because they're
274 // not pure, and impure procedures are caught by checks for constraint C1139
275 void Post(const parser::ProcedureDesignator &procedureDesignator) {
276 if (auto *name{std::get_if<parser::Name>(&procedureDesignator.u)}) {
277 if (name->symbol && !IsPureProcedure(*name->symbol)) {
278 SayWithDo(context_, currentStatementSourcePosition_,
279 "Call to an impure procedure is not allowed in DO"
280 " CONCURRENT"_err_en_US,
281 doConcurrentSourcePosition_);
283 if (name->symbol &&
284 fromScope(*name->symbol, "__fortran_ieee_exceptions"s)) {
285 if (name->source == "ieee_set_halting_mode") {
286 SayWithDo(context_, currentStatementSourcePosition_,
287 "IEEE_SET_HALTING_MODE is not allowed in DO "
288 "CONCURRENT"_err_en_US,
289 doConcurrentSourcePosition_);
292 } else {
293 // C1139: this a procedure component
294 auto &component{std::get<parser::ProcComponentRef>(procedureDesignator.u)
295 .v.thing.component};
296 if (component.symbol && !IsPureProcedure(*component.symbol)) {
297 SayWithDo(context_, currentStatementSourcePosition_,
298 "Call to an impure procedure component is not allowed"
299 " in DO CONCURRENT"_err_en_US,
300 doConcurrentSourcePosition_);
305 // 11.1.7.5, paragraph 5, no ADVANCE specifier in a DO CONCURRENT
306 void Post(const parser::IoControlSpec &ioControlSpec) {
307 if (auto *charExpr{
308 std::get_if<parser::IoControlSpec::CharExpr>(&ioControlSpec.u)}) {
309 if (std::get<parser::IoControlSpec::CharExpr::Kind>(charExpr->t) ==
310 parser::IoControlSpec::CharExpr::Kind::Advance) {
311 SayWithDo(context_, currentStatementSourcePosition_,
312 "ADVANCE specifier is not allowed in DO"
313 " CONCURRENT"_err_en_US,
314 doConcurrentSourcePosition_);
319 private:
320 bool fromScope(const Symbol &symbol, const std::string &moduleName) {
321 if (symbol.GetUltimate().owner().IsModule() &&
322 symbol.GetUltimate().owner().GetName().value().ToString() ==
323 moduleName) {
324 return true;
326 return false;
329 std::set<parser::Label> labels_;
330 parser::CharBlock currentStatementSourcePosition_;
331 SemanticsContext &context_;
332 parser::CharBlock doConcurrentSourcePosition_;
333 }; // class DoConcurrentBodyEnforce
335 // Class for enforcing C1130 -- in a DO CONCURRENT with DEFAULT(NONE),
336 // variables from enclosing scopes must have their locality specified
337 class DoConcurrentVariableEnforce {
338 public:
339 DoConcurrentVariableEnforce(
340 SemanticsContext &context, parser::CharBlock doConcurrentSourcePosition)
341 : context_{context},
342 doConcurrentSourcePosition_{doConcurrentSourcePosition},
343 blockScope_{context.FindScope(doConcurrentSourcePosition_)} {}
345 template <typename T> bool Pre(const T &) { return true; }
346 template <typename T> void Post(const T &) {}
348 // Check to see if the name is a variable from an enclosing scope
349 void Post(const parser::Name &name) {
350 if (const Symbol * symbol{name.symbol}) {
351 if (IsVariableName(*symbol)) {
352 const Scope &variableScope{symbol->owner()};
353 if (DoesScopeContain(&variableScope, blockScope_)) {
354 context_.SayWithDecl(*symbol, name.source,
355 "Variable '%s' from an enclosing scope referenced in DO "
356 "CONCURRENT with DEFAULT(NONE) must appear in a "
357 "locality-spec"_err_en_US,
358 symbol->name());
364 private:
365 SemanticsContext &context_;
366 parser::CharBlock doConcurrentSourcePosition_;
367 const Scope &blockScope_;
368 }; // class DoConcurrentVariableEnforce
370 // Find a DO or FORALL and enforce semantics checks on its body
371 class DoContext {
372 public:
373 DoContext(SemanticsContext &context, IndexVarKind kind)
374 : context_{context}, kind_{kind} {}
376 // Mark this DO construct as a point of definition for the DO variables
377 // or index-names it contains. If they're already defined, emit an error
378 // message. We need to remember both the variable and the source location of
379 // the variable in the DO construct so that we can remove it when we leave
380 // the DO construct and use its location in error messages.
381 void DefineDoVariables(const parser::DoConstruct &doConstruct) {
382 if (doConstruct.IsDoNormal()) {
383 context_.ActivateIndexVar(GetDoVariable(doConstruct), IndexVarKind::DO);
384 } else if (doConstruct.IsDoConcurrent()) {
385 if (const auto &loopControl{doConstruct.GetLoopControl()}) {
386 ActivateIndexVars(GetControls(*loopControl));
391 // Called at the end of a DO construct to deactivate the DO construct
392 void ResetDoVariables(const parser::DoConstruct &doConstruct) {
393 if (doConstruct.IsDoNormal()) {
394 context_.DeactivateIndexVar(GetDoVariable(doConstruct));
395 } else if (doConstruct.IsDoConcurrent()) {
396 if (const auto &loopControl{doConstruct.GetLoopControl()}) {
397 DeactivateIndexVars(GetControls(*loopControl));
402 void ActivateIndexVars(const std::list<parser::ConcurrentControl> &controls) {
403 for (const auto &control : controls) {
404 context_.ActivateIndexVar(std::get<parser::Name>(control.t), kind_);
407 void DeactivateIndexVars(
408 const std::list<parser::ConcurrentControl> &controls) {
409 for (const auto &control : controls) {
410 context_.DeactivateIndexVar(std::get<parser::Name>(control.t));
414 void Check(const parser::DoConstruct &doConstruct) {
415 if (doConstruct.IsDoConcurrent()) {
416 CheckDoConcurrent(doConstruct);
417 return;
419 if (doConstruct.IsDoNormal()) {
420 CheckDoNormal(doConstruct);
421 return;
423 // TODO: handle the other cases
426 void Check(const parser::ForallStmt &stmt) {
427 CheckConcurrentHeader(GetConcurrentHeader(stmt));
429 void Check(const parser::ForallConstruct &construct) {
430 CheckConcurrentHeader(GetConcurrentHeader(construct));
433 void Check(const parser::ForallAssignmentStmt &stmt) {
434 const evaluate::Assignment *assignment{common::visit(
435 common::visitors{[&](const auto &x) { return GetAssignment(x); }},
436 stmt.u)};
437 if (assignment) {
438 CheckForallIndexesUsed(*assignment);
439 CheckForImpureCall(assignment->lhs);
440 CheckForImpureCall(assignment->rhs);
441 if (const auto *proc{
442 std::get_if<evaluate::ProcedureRef>(&assignment->u)}) {
443 CheckForImpureCall(*proc);
445 common::visit(
446 common::visitors{
447 [](const evaluate::Assignment::Intrinsic &) {},
448 [&](const evaluate::ProcedureRef &proc) {
449 CheckForImpureCall(proc);
451 [&](const evaluate::Assignment::BoundsSpec &bounds) {
452 for (const auto &bound : bounds) {
453 CheckForImpureCall(SomeExpr{bound});
456 [&](const evaluate::Assignment::BoundsRemapping &bounds) {
457 for (const auto &bound : bounds) {
458 CheckForImpureCall(SomeExpr{bound.first});
459 CheckForImpureCall(SomeExpr{bound.second});
463 assignment->u);
467 private:
468 void SayBadDoControl(parser::CharBlock sourceLocation) {
469 context_.Say(sourceLocation, "DO controls should be INTEGER"_err_en_US);
472 void CheckDoControl(const parser::CharBlock &sourceLocation, bool isReal) {
473 const bool warn{context_.warnOnNonstandardUsage() ||
474 context_.ShouldWarn(common::LanguageFeature::RealDoControls)};
475 if (isReal && !warn) {
476 // No messages for the default case
477 } else if (isReal && warn) {
478 context_.Say(sourceLocation, "DO controls should be INTEGER"_port_en_US);
479 } else {
480 SayBadDoControl(sourceLocation);
484 void CheckDoVariable(const parser::ScalarName &scalarName) {
485 const parser::CharBlock &sourceLocation{scalarName.thing.source};
486 if (const Symbol * symbol{scalarName.thing.symbol}) {
487 if (!IsVariableName(*symbol)) {
488 context_.Say(
489 sourceLocation, "DO control must be an INTEGER variable"_err_en_US);
490 } else if (auto why{WhyNotDefinable(sourceLocation,
491 context_.FindScope(sourceLocation), DefinabilityFlags{},
492 *symbol)}) {
493 context_
494 .Say(sourceLocation,
495 "'%s' may not be used as a DO variable"_err_en_US,
496 symbol->name())
497 .Attach(std::move(*why));
498 } else {
499 const DeclTypeSpec *symType{symbol->GetType()};
500 if (!symType) {
501 SayBadDoControl(sourceLocation);
502 } else {
503 if (!symType->IsNumeric(TypeCategory::Integer)) {
504 CheckDoControl(
505 sourceLocation, symType->IsNumeric(TypeCategory::Real));
508 } // No messages for INTEGER
512 // Semantic checks for the limit and step expressions
513 void CheckDoExpression(const parser::ScalarExpr &scalarExpression) {
514 if (const SomeExpr * expr{GetExpr(context_, scalarExpression)}) {
515 if (!ExprHasTypeCategory(*expr, TypeCategory::Integer)) {
516 // No warnings or errors for type INTEGER
517 const parser::CharBlock &loc{scalarExpression.thing.value().source};
518 CheckDoControl(loc, ExprHasTypeCategory(*expr, TypeCategory::Real));
523 void CheckDoNormal(const parser::DoConstruct &doConstruct) {
524 // C1120 -- types of DO variables must be INTEGER, extended by allowing
525 // REAL and DOUBLE PRECISION
526 const Bounds &bounds{GetBounds(doConstruct)};
527 CheckDoVariable(bounds.name);
528 CheckDoExpression(bounds.lower);
529 CheckDoExpression(bounds.upper);
530 if (bounds.step) {
531 CheckDoExpression(*bounds.step);
532 if (IsZero(*bounds.step)) {
533 context_.Say(bounds.step->thing.value().source,
534 "DO step expression should not be zero"_warn_en_US);
539 void CheckDoConcurrent(const parser::DoConstruct &doConstruct) {
540 auto &doStmt{
541 std::get<parser::Statement<parser::NonLabelDoStmt>>(doConstruct.t)};
542 currentStatementSourcePosition_ = doStmt.source;
544 const parser::Block &block{std::get<parser::Block>(doConstruct.t)};
545 DoConcurrentBodyEnforce doConcurrentBodyEnforce{context_, doStmt.source};
546 parser::Walk(block, doConcurrentBodyEnforce);
548 LabelEnforce doConcurrentLabelEnforce{context_,
549 doConcurrentBodyEnforce.labels(), currentStatementSourcePosition_,
550 "DO CONCURRENT"};
551 parser::Walk(block, doConcurrentLabelEnforce);
553 const auto &loopControl{doConstruct.GetLoopControl()};
554 CheckConcurrentLoopControl(*loopControl);
555 CheckLocalitySpecs(*loopControl, block);
558 // Return a set of symbols whose names are in a Local locality-spec. Look
559 // the names up in the scope that encloses the DO construct to avoid getting
560 // the local versions of them. Then follow the host-, use-, and
561 // construct-associations to get the root symbols
562 UnorderedSymbolSet GatherLocals(
563 const std::list<parser::LocalitySpec> &localitySpecs) const {
564 UnorderedSymbolSet symbols;
565 const Scope &parentScope{
566 context_.FindScope(currentStatementSourcePosition_).parent()};
567 // Loop through the LocalitySpec::Local locality-specs
568 for (const auto &ls : localitySpecs) {
569 if (const auto *names{std::get_if<parser::LocalitySpec::Local>(&ls.u)}) {
570 // Loop through the names in the Local locality-spec getting their
571 // symbols
572 for (const parser::Name &name : names->v) {
573 if (const Symbol * symbol{parentScope.FindSymbol(name.source)}) {
574 symbols.insert(ResolveAssociations(*symbol));
579 return symbols;
582 UnorderedSymbolSet GatherSymbolsFromExpression(
583 const parser::Expr &expression) const {
584 UnorderedSymbolSet result;
585 if (const auto *expr{GetExpr(context_, expression)}) {
586 for (const Symbol &symbol : evaluate::CollectSymbols(*expr)) {
587 result.insert(ResolveAssociations(symbol));
590 return result;
593 // C1121 - procedures in mask must be pure
594 void CheckMaskIsPure(const parser::ScalarLogicalExpr &mask) const {
595 UnorderedSymbolSet references{
596 GatherSymbolsFromExpression(mask.thing.thing.value())};
597 for (const Symbol &ref : OrderBySourcePosition(references)) {
598 if (IsProcedure(ref) && !IsPureProcedure(ref)) {
599 context_.SayWithDecl(ref, parser::Unwrap<parser::Expr>(mask)->source,
600 "%s mask expression may not reference impure procedure '%s'"_err_en_US,
601 LoopKindName(), ref.name());
602 return;
607 void CheckNoCollisions(const UnorderedSymbolSet &refs,
608 const UnorderedSymbolSet &uses, parser::MessageFixedText &&errorMessage,
609 const parser::CharBlock &refPosition) const {
610 for (const Symbol &ref : OrderBySourcePosition(refs)) {
611 if (uses.find(ref) != uses.end()) {
612 context_.SayWithDecl(ref, refPosition, std::move(errorMessage),
613 LoopKindName(), ref.name());
614 return;
619 void HasNoReferences(const UnorderedSymbolSet &indexNames,
620 const parser::ScalarIntExpr &expr) const {
621 CheckNoCollisions(GatherSymbolsFromExpression(expr.thing.thing.value()),
622 indexNames,
623 "%s limit expression may not reference index variable '%s'"_err_en_US,
624 expr.thing.thing.value().source);
627 // C1129, names in local locality-specs can't be in mask expressions
628 void CheckMaskDoesNotReferenceLocal(const parser::ScalarLogicalExpr &mask,
629 const UnorderedSymbolSet &localVars) const {
630 CheckNoCollisions(GatherSymbolsFromExpression(mask.thing.thing.value()),
631 localVars,
632 "%s mask expression references variable '%s'"
633 " in LOCAL locality-spec"_err_en_US,
634 mask.thing.thing.value().source);
637 // C1129, names in local locality-specs can't be in limit or step
638 // expressions
639 void CheckExprDoesNotReferenceLocal(const parser::ScalarIntExpr &expr,
640 const UnorderedSymbolSet &localVars) const {
641 CheckNoCollisions(GatherSymbolsFromExpression(expr.thing.thing.value()),
642 localVars,
643 "%s expression references variable '%s'"
644 " in LOCAL locality-spec"_err_en_US,
645 expr.thing.thing.value().source);
648 // C1130, DEFAULT(NONE) locality requires names to be in locality-specs to
649 // be used in the body of the DO loop
650 void CheckDefaultNoneImpliesExplicitLocality(
651 const std::list<parser::LocalitySpec> &localitySpecs,
652 const parser::Block &block) const {
653 bool hasDefaultNone{false};
654 for (auto &ls : localitySpecs) {
655 if (std::holds_alternative<parser::LocalitySpec::DefaultNone>(ls.u)) {
656 if (hasDefaultNone) {
657 // C1127, you can only have one DEFAULT(NONE)
658 context_.Say(currentStatementSourcePosition_,
659 "Only one DEFAULT(NONE) may appear"_port_en_US);
660 break;
662 hasDefaultNone = true;
665 if (hasDefaultNone) {
666 DoConcurrentVariableEnforce doConcurrentVariableEnforce{
667 context_, currentStatementSourcePosition_};
668 parser::Walk(block, doConcurrentVariableEnforce);
672 // C1123, concurrent limit or step expressions can't reference index-names
673 void CheckConcurrentHeader(const parser::ConcurrentHeader &header) const {
674 if (const auto &mask{
675 std::get<std::optional<parser::ScalarLogicalExpr>>(header.t)}) {
676 CheckMaskIsPure(*mask);
678 auto &controls{std::get<std::list<parser::ConcurrentControl>>(header.t)};
679 UnorderedSymbolSet indexNames;
680 for (const parser::ConcurrentControl &control : controls) {
681 const auto &indexName{std::get<parser::Name>(control.t)};
682 if (indexName.symbol) {
683 indexNames.insert(*indexName.symbol);
686 if (!indexNames.empty()) {
687 for (const parser::ConcurrentControl &control : controls) {
688 HasNoReferences(indexNames, std::get<1>(control.t));
689 HasNoReferences(indexNames, std::get<2>(control.t));
690 if (const auto &intExpr{
691 std::get<std::optional<parser::ScalarIntExpr>>(control.t)}) {
692 const parser::Expr &expr{intExpr->thing.thing.value()};
693 CheckNoCollisions(GatherSymbolsFromExpression(expr), indexNames,
694 "%s step expression may not reference index variable '%s'"_err_en_US,
695 expr.source);
696 if (IsZero(expr)) {
697 context_.Say(expr.source,
698 "%s step expression may not be zero"_err_en_US, LoopKindName());
705 void CheckLocalitySpecs(
706 const parser::LoopControl &control, const parser::Block &block) const {
707 const auto &concurrent{
708 std::get<parser::LoopControl::Concurrent>(control.u)};
709 const auto &header{std::get<parser::ConcurrentHeader>(concurrent.t)};
710 const auto &localitySpecs{
711 std::get<std::list<parser::LocalitySpec>>(concurrent.t)};
712 if (!localitySpecs.empty()) {
713 const UnorderedSymbolSet &localVars{GatherLocals(localitySpecs)};
714 for (const auto &c : GetControls(control)) {
715 CheckExprDoesNotReferenceLocal(std::get<1>(c.t), localVars);
716 CheckExprDoesNotReferenceLocal(std::get<2>(c.t), localVars);
717 if (const auto &expr{
718 std::get<std::optional<parser::ScalarIntExpr>>(c.t)}) {
719 CheckExprDoesNotReferenceLocal(*expr, localVars);
722 if (const auto &mask{
723 std::get<std::optional<parser::ScalarLogicalExpr>>(header.t)}) {
724 CheckMaskDoesNotReferenceLocal(*mask, localVars);
726 CheckDefaultNoneImpliesExplicitLocality(localitySpecs, block);
730 // check constraints [C1121 .. C1130]
731 void CheckConcurrentLoopControl(const parser::LoopControl &control) const {
732 const auto &concurrent{
733 std::get<parser::LoopControl::Concurrent>(control.u)};
734 CheckConcurrentHeader(std::get<parser::ConcurrentHeader>(concurrent.t));
737 template <typename T> void CheckForImpureCall(const T &x) {
738 if (auto bad{FindImpureCall(context_.foldingContext(), x)}) {
739 context_.Say(
740 "Impure procedure '%s' may not be referenced in a %s"_err_en_US, *bad,
741 LoopKindName());
745 // Each index should be used on the LHS of each assignment in a FORALL
746 void CheckForallIndexesUsed(const evaluate::Assignment &assignment) {
747 SymbolVector indexVars{context_.GetIndexVars(IndexVarKind::FORALL)};
748 if (!indexVars.empty()) {
749 UnorderedSymbolSet symbols{evaluate::CollectSymbols(assignment.lhs)};
750 common::visit(
751 common::visitors{
752 [&](const evaluate::Assignment::BoundsSpec &spec) {
753 for (const auto &bound : spec) {
754 // TODO: this is working around missing std::set::merge in some versions of
755 // clang that we are building with
756 #ifdef __clang__
757 auto boundSymbols{evaluate::CollectSymbols(bound)};
758 symbols.insert(boundSymbols.begin(), boundSymbols.end());
759 #else
760 symbols.merge(evaluate::CollectSymbols(bound));
761 #endif
764 [&](const evaluate::Assignment::BoundsRemapping &remapping) {
765 for (const auto &bounds : remapping) {
766 #ifdef __clang__
767 auto lbSymbols{evaluate::CollectSymbols(bounds.first)};
768 symbols.insert(lbSymbols.begin(), lbSymbols.end());
769 auto ubSymbols{evaluate::CollectSymbols(bounds.second)};
770 symbols.insert(ubSymbols.begin(), ubSymbols.end());
771 #else
772 symbols.merge(evaluate::CollectSymbols(bounds.first));
773 symbols.merge(evaluate::CollectSymbols(bounds.second));
774 #endif
777 [](const auto &) {},
779 assignment.u);
780 for (const Symbol &index : indexVars) {
781 if (symbols.count(index) == 0) {
782 context_.Say("FORALL index variable '%s' not used on left-hand side"
783 " of assignment"_warn_en_US,
784 index.name());
790 // For messages where the DO loop must be DO CONCURRENT, make that explicit.
791 const char *LoopKindName() const {
792 return kind_ == IndexVarKind::DO ? "DO CONCURRENT" : "FORALL";
795 SemanticsContext &context_;
796 const IndexVarKind kind_;
797 parser::CharBlock currentStatementSourcePosition_;
798 }; // class DoContext
800 void DoForallChecker::Enter(const parser::DoConstruct &doConstruct) {
801 DoContext doContext{context_, IndexVarKind::DO};
802 doContext.DefineDoVariables(doConstruct);
805 void DoForallChecker::Leave(const parser::DoConstruct &doConstruct) {
806 DoContext doContext{context_, IndexVarKind::DO};
807 doContext.Check(doConstruct);
808 doContext.ResetDoVariables(doConstruct);
811 void DoForallChecker::Enter(const parser::ForallConstruct &construct) {
812 DoContext doContext{context_, IndexVarKind::FORALL};
813 doContext.ActivateIndexVars(GetControls(construct));
815 void DoForallChecker::Leave(const parser::ForallConstruct &construct) {
816 DoContext doContext{context_, IndexVarKind::FORALL};
817 doContext.Check(construct);
818 doContext.DeactivateIndexVars(GetControls(construct));
821 void DoForallChecker::Enter(const parser::ForallStmt &stmt) {
822 DoContext doContext{context_, IndexVarKind::FORALL};
823 doContext.ActivateIndexVars(GetControls(stmt));
825 void DoForallChecker::Leave(const parser::ForallStmt &stmt) {
826 DoContext doContext{context_, IndexVarKind::FORALL};
827 doContext.Check(stmt);
828 doContext.DeactivateIndexVars(GetControls(stmt));
830 void DoForallChecker::Leave(const parser::ForallAssignmentStmt &stmt) {
831 DoContext doContext{context_, IndexVarKind::FORALL};
832 doContext.Check(stmt);
835 template <typename A>
836 static parser::CharBlock GetConstructPosition(const A &a) {
837 return std::get<0>(a.t).source;
840 static parser::CharBlock GetNodePosition(const ConstructNode &construct) {
841 return common::visit(
842 [&](const auto &x) { return GetConstructPosition(*x); }, construct);
845 void DoForallChecker::SayBadLeave(StmtType stmtType,
846 const char *enclosingStmtName, const ConstructNode &construct) const {
847 context_
848 .Say("%s must not leave a %s statement"_err_en_US, EnumToString(stmtType),
849 enclosingStmtName)
850 .Attach(GetNodePosition(construct), "The construct that was left"_en_US);
853 static const parser::DoConstruct *MaybeGetDoConstruct(
854 const ConstructNode &construct) {
855 if (const auto *doNode{
856 std::get_if<const parser::DoConstruct *>(&construct)}) {
857 return *doNode;
858 } else {
859 return nullptr;
863 static bool ConstructIsDoConcurrent(const ConstructNode &construct) {
864 const parser::DoConstruct *doConstruct{MaybeGetDoConstruct(construct)};
865 return doConstruct && doConstruct->IsDoConcurrent();
868 // Check that CYCLE and EXIT statements do not cause flow of control to
869 // leave DO CONCURRENT, CRITICAL, or CHANGE TEAM constructs.
870 void DoForallChecker::CheckForBadLeave(
871 StmtType stmtType, const ConstructNode &construct) const {
872 common::visit(common::visitors{
873 [&](const parser::DoConstruct *doConstructPtr) {
874 if (doConstructPtr->IsDoConcurrent()) {
875 // C1135 and C1167 -- CYCLE and EXIT statements can't
876 // leave a DO CONCURRENT
877 SayBadLeave(stmtType, "DO CONCURRENT", construct);
880 [&](const parser::CriticalConstruct *) {
881 // C1135 and C1168 -- similarly, for CRITICAL
882 SayBadLeave(stmtType, "CRITICAL", construct);
884 [&](const parser::ChangeTeamConstruct *) {
885 // C1135 and C1168 -- similarly, for CHANGE TEAM
886 SayBadLeave(stmtType, "CHANGE TEAM", construct);
888 [](const auto *) {},
890 construct);
893 static bool StmtMatchesConstruct(const parser::Name *stmtName,
894 StmtType stmtType, const std::optional<parser::Name> &constructName,
895 const ConstructNode &construct) {
896 bool inDoConstruct{MaybeGetDoConstruct(construct) != nullptr};
897 if (!stmtName) {
898 return inDoConstruct; // Unlabeled statements match all DO constructs
899 } else if (constructName && constructName->source == stmtName->source) {
900 return stmtType == StmtType::EXIT || inDoConstruct;
901 } else {
902 return false;
906 // C1167 Can't EXIT from a DO CONCURRENT
907 void DoForallChecker::CheckDoConcurrentExit(
908 StmtType stmtType, const ConstructNode &construct) const {
909 if (stmtType == StmtType::EXIT && ConstructIsDoConcurrent(construct)) {
910 SayBadLeave(StmtType::EXIT, "DO CONCURRENT", construct);
914 // Check nesting violations for a CYCLE or EXIT statement. Loop up the
915 // nesting levels looking for a construct that matches the CYCLE or EXIT
916 // statment. At every construct, check for a violation. If we find a match
917 // without finding a violation, the check is complete.
918 void DoForallChecker::CheckNesting(
919 StmtType stmtType, const parser::Name *stmtName) const {
920 const ConstructStack &stack{context_.constructStack()};
921 for (auto iter{stack.cend()}; iter-- != stack.cbegin();) {
922 const ConstructNode &construct{*iter};
923 const std::optional<parser::Name> &constructName{
924 MaybeGetNodeName(construct)};
925 if (StmtMatchesConstruct(stmtName, stmtType, constructName, construct)) {
926 CheckDoConcurrentExit(stmtType, construct);
927 return; // We got a match, so we're finished checking
929 CheckForBadLeave(stmtType, construct);
932 // We haven't found a match in the enclosing constructs
933 if (stmtType == StmtType::EXIT) {
934 context_.Say("No matching construct for EXIT statement"_err_en_US);
935 } else {
936 context_.Say("No matching DO construct for CYCLE statement"_err_en_US);
940 // C1135 -- Nesting for CYCLE statements
941 void DoForallChecker::Enter(const parser::CycleStmt &cycleStmt) {
942 CheckNesting(StmtType::CYCLE, common::GetPtrFromOptional(cycleStmt.v));
945 // C1167 and C1168 -- Nesting for EXIT statements
946 void DoForallChecker::Enter(const parser::ExitStmt &exitStmt) {
947 CheckNesting(StmtType::EXIT, common::GetPtrFromOptional(exitStmt.v));
950 void DoForallChecker::Leave(const parser::AssignmentStmt &stmt) {
951 const auto &variable{std::get<parser::Variable>(stmt.t)};
952 context_.CheckIndexVarRedefine(variable);
955 static void CheckIfArgIsDoVar(const evaluate::ActualArgument &arg,
956 const parser::CharBlock location, SemanticsContext &context) {
957 common::Intent intent{arg.dummyIntent()};
958 if (intent == common::Intent::Out || intent == common::Intent::InOut) {
959 if (const SomeExpr * argExpr{arg.UnwrapExpr()}) {
960 if (const Symbol * var{evaluate::UnwrapWholeSymbolDataRef(*argExpr)}) {
961 if (intent == common::Intent::Out) {
962 context.CheckIndexVarRedefine(location, *var);
963 } else {
964 context.WarnIndexVarRedefine(location, *var); // INTENT(INOUT)
971 // Check to see if a DO variable is being passed as an actual argument to a
972 // dummy argument whose intent is OUT or INOUT. To do this, we need to find
973 // the expressions for actual arguments which contain DO variables. We get the
974 // intents of the dummy arguments from the ProcedureRef in the "typedCall"
975 // field of the CallStmt which was filled in during expression checking. At
976 // the same time, we need to iterate over the parser::Expr versions of the
977 // actual arguments to get their source locations of the arguments for the
978 // messages.
979 void DoForallChecker::Leave(const parser::CallStmt &callStmt) {
980 if (const auto &typedCall{callStmt.typedCall}) {
981 const auto &parsedArgs{
982 std::get<std::list<parser::ActualArgSpec>>(callStmt.v.t)};
983 auto parsedArgIter{parsedArgs.begin()};
984 const evaluate::ActualArguments &checkedArgs{typedCall->arguments()};
985 for (const auto &checkedOptionalArg : checkedArgs) {
986 if (parsedArgIter == parsedArgs.end()) {
987 break; // No more parsed arguments, we're done.
989 const auto &parsedArg{std::get<parser::ActualArg>(parsedArgIter->t)};
990 ++parsedArgIter;
991 if (checkedOptionalArg) {
992 const evaluate::ActualArgument &checkedArg{*checkedOptionalArg};
993 if (const auto *parsedExpr{
994 std::get_if<common::Indirection<parser::Expr>>(&parsedArg.u)}) {
995 CheckIfArgIsDoVar(checkedArg, parsedExpr->value().source, context_);
1002 void DoForallChecker::Leave(const parser::ConnectSpec &connectSpec) {
1003 const auto *newunit{
1004 std::get_if<parser::ConnectSpec::Newunit>(&connectSpec.u)};
1005 if (newunit) {
1006 context_.CheckIndexVarRedefine(newunit->v.thing.thing);
1010 using ActualArgumentSet = std::set<evaluate::ActualArgumentRef>;
1012 struct CollectActualArgumentsHelper
1013 : public evaluate::SetTraverse<CollectActualArgumentsHelper,
1014 ActualArgumentSet> {
1015 using Base = SetTraverse<CollectActualArgumentsHelper, ActualArgumentSet>;
1016 CollectActualArgumentsHelper() : Base{*this} {}
1017 using Base::operator();
1018 ActualArgumentSet operator()(const evaluate::ActualArgument &arg) const {
1019 return Combine(ActualArgumentSet{arg},
1020 CollectActualArgumentsHelper{}(arg.UnwrapExpr()));
1024 template <typename A> ActualArgumentSet CollectActualArguments(const A &x) {
1025 return CollectActualArgumentsHelper{}(x);
1028 template ActualArgumentSet CollectActualArguments(const SomeExpr &);
1030 void DoForallChecker::Enter(const parser::Expr &parsedExpr) { ++exprDepth_; }
1032 void DoForallChecker::Leave(const parser::Expr &parsedExpr) {
1033 CHECK(exprDepth_ > 0);
1034 if (--exprDepth_ == 0) { // Only check top level expressions
1035 if (const SomeExpr * expr{GetExpr(context_, parsedExpr)}) {
1036 ActualArgumentSet argSet{CollectActualArguments(*expr)};
1037 for (const evaluate::ActualArgumentRef &argRef : argSet) {
1038 CheckIfArgIsDoVar(*argRef, parsedExpr.source, context_);
1044 void DoForallChecker::Leave(const parser::InquireSpec &inquireSpec) {
1045 const auto *intVar{std::get_if<parser::InquireSpec::IntVar>(&inquireSpec.u)};
1046 if (intVar) {
1047 const auto &scalar{std::get<parser::ScalarIntVariable>(intVar->t)};
1048 context_.CheckIndexVarRedefine(scalar.thing.thing);
1052 void DoForallChecker::Leave(const parser::IoControlSpec &ioControlSpec) {
1053 const auto *size{std::get_if<parser::IoControlSpec::Size>(&ioControlSpec.u)};
1054 if (size) {
1055 context_.CheckIndexVarRedefine(size->v.thing.thing);
1059 void DoForallChecker::Leave(const parser::OutputImpliedDo &outputImpliedDo) {
1060 const auto &control{std::get<parser::IoImpliedDoControl>(outputImpliedDo.t)};
1061 const parser::Name &name{control.name.thing.thing};
1062 context_.CheckIndexVarRedefine(name.source, *name.symbol);
1065 void DoForallChecker::Leave(const parser::StatVariable &statVariable) {
1066 context_.CheckIndexVarRedefine(statVariable.v.thing.thing);
1069 } // namespace Fortran::semantics