1 //===-- lib/Semantics/resolve-names.cpp -----------------------------------===//
2 // Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
3 // See https://llvm.org/LICENSE.txt for license information.
4 // SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
5 //
6 //===----------------------------------------------------------------------===//
7 
8 #include "resolve-names.h"
9 #include "assignment.h"
10 #include "mod-file.h"
11 #include "pointer-assignment.h"
12 #include "program-tree.h"
13 #include "resolve-directives.h"
14 #include "resolve-names-utils.h"
15 #include "rewrite-parse-tree.h"
16 #include "flang/Common/Fortran.h"
17 #include "flang/Common/default-kinds.h"
18 #include "flang/Common/indirection.h"
19 #include "flang/Common/restorer.h"
20 #include "flang/Evaluate/characteristics.h"
21 #include "flang/Evaluate/check-expression.h"
22 #include "flang/Evaluate/common.h"
23 #include "flang/Evaluate/fold-designator.h"
24 #include "flang/Evaluate/fold.h"
25 #include "flang/Evaluate/intrinsics.h"
26 #include "flang/Evaluate/tools.h"
27 #include "flang/Evaluate/type.h"
28 #include "flang/Parser/parse-tree-visitor.h"
29 #include "flang/Parser/parse-tree.h"
30 #include "flang/Parser/tools.h"
31 #include "flang/Semantics/attr.h"
32 #include "flang/Semantics/expression.h"
33 #include "flang/Semantics/scope.h"
34 #include "flang/Semantics/semantics.h"
35 #include "flang/Semantics/symbol.h"
36 #include "flang/Semantics/tools.h"
37 #include "flang/Semantics/type.h"
38 #include "llvm/Support/raw_ostream.h"
39 #include <list>
40 #include <map>
41 #include <set>
42 #include <stack>
43 
44 namespace Fortran::semantics {
45 
46 using namespace parser::literals;
47 
48 template <typename T> using Indirection = common::Indirection<T>;
49 using Message = parser::Message;
50 using Messages = parser::Messages;
51 using MessageFixedText = parser::MessageFixedText;
52 using MessageFormattedText = parser::MessageFormattedText;
53 
54 class ResolveNamesVisitor;
55 
56 // ImplicitRules maps initial character of identifier to the DeclTypeSpec
57 // representing the implicit type; std::nullopt if none.
58 // It also records the presence of IMPLICIT NONE statements.
59 // When inheritFromParent is set, defaults come from the parent rules.
60 class ImplicitRules {
61 public:
ImplicitRules(SemanticsContext & context,ImplicitRules * parent)62   ImplicitRules(SemanticsContext &context, ImplicitRules *parent)
63       : parent_{parent}, context_{context} {
64     inheritFromParent_ = parent != nullptr;
65   }
66   bool isImplicitNoneType() const;
67   bool isImplicitNoneExternal() const;
set_isImplicitNoneType(bool x)68   void set_isImplicitNoneType(bool x) { isImplicitNoneType_ = x; }
set_isImplicitNoneExternal(bool x)69   void set_isImplicitNoneExternal(bool x) { isImplicitNoneExternal_ = x; }
set_inheritFromParent(bool x)70   void set_inheritFromParent(bool x) { inheritFromParent_ = x; }
71   // Get the implicit type for this name. May be null.
72   const DeclTypeSpec *GetType(SourceName) const;
73   // Record the implicit type for the range of characters [fromLetter,
74   // toLetter].
75   void SetTypeMapping(const DeclTypeSpec &type, parser::Location fromLetter,
76       parser::Location toLetter);
77 
78 private:
79   static char Incr(char ch);
80 
81   ImplicitRules *parent_;
82   SemanticsContext &context_;
83   bool inheritFromParent_{false}; // look in parent if not specified here
84   bool isImplicitNoneType_{
85       context_.IsEnabled(common::LanguageFeature::ImplicitNoneTypeAlways)};
86   bool isImplicitNoneExternal_{false};
87   // map_ contains the mapping between letters and types that were defined
88   // by the IMPLICIT statements of the related scope. It does not contain
89   // the default Fortran mappings nor the mapping defined in parents.
90   std::map<char, common::Reference<const DeclTypeSpec>> map_;
91 
92   friend llvm::raw_ostream &operator<<(
93       llvm::raw_ostream &, const ImplicitRules &);
94   friend void ShowImplicitRule(
95       llvm::raw_ostream &, const ImplicitRules &, char);
96 };
97 
98 // scope -> implicit rules for that scope
99 using ImplicitRulesMap = std::map<const Scope *, ImplicitRules>;
100 
101 // Track statement source locations and save messages.
102 class MessageHandler {
103 public:
MessageHandler()104   MessageHandler() { DIE("MessageHandler: default-constructed"); }
MessageHandler(SemanticsContext & c)105   explicit MessageHandler(SemanticsContext &c) : context_{&c} {}
messages()106   Messages &messages() { return context_->messages(); };
currStmtSource()107   const std::optional<SourceName> &currStmtSource() {
108     return context_->location();
109   }
set_currStmtSource(const std::optional<SourceName> & source)110   void set_currStmtSource(const std::optional<SourceName> &source) {
111     context_->set_location(source);
112   }
113 
114   // Emit a message associated with the current statement source.
115   Message &Say(MessageFixedText &&);
116   Message &Say(MessageFormattedText &&);
117   // Emit a message about a SourceName
118   Message &Say(const SourceName &, MessageFixedText &&);
119   // Emit a formatted message associated with a source location.
120   template <typename... A>
Say(const SourceName & source,MessageFixedText && msg,A &&...args)121   Message &Say(const SourceName &source, MessageFixedText &&msg, A &&...args) {
122     return context_->Say(source, std::move(msg), std::forward<A>(args)...);
123   }
124 
125 private:
126   SemanticsContext *context_;
127 };
128 
129 // Inheritance graph for the parse tree visitation classes that follow:
130 //   BaseVisitor
131 //   + AttrsVisitor
132 //   | + DeclTypeSpecVisitor
133 //   |   + ImplicitRulesVisitor
134 //   |     + ScopeHandler -----------+--+
135 //   |       + ModuleVisitor ========|==+
136 //   |       + InterfaceVisitor      |  |
137 //   |       +-+ SubprogramVisitor ==|==+
138 //   + ArraySpecVisitor              |  |
139 //     + DeclarationVisitor <--------+  |
140 //       + ConstructVisitor             |
141 //         + ResolveNamesVisitor <------+
142 
143 class BaseVisitor {
144 public:
BaseVisitor()145   BaseVisitor() { DIE("BaseVisitor: default-constructed"); }
BaseVisitor(SemanticsContext & c,ResolveNamesVisitor & v,ImplicitRulesMap & rules)146   BaseVisitor(
147       SemanticsContext &c, ResolveNamesVisitor &v, ImplicitRulesMap &rules)
148       : implicitRulesMap_{&rules}, this_{&v}, context_{&c}, messageHandler_{c} {
149   }
150   template <typename T> void Walk(const T &);
151 
messageHandler()152   MessageHandler &messageHandler() { return messageHandler_; }
currStmtSource()153   const std::optional<SourceName> &currStmtSource() {
154     return context_->location();
155   }
context() const156   SemanticsContext &context() const { return *context_; }
GetFoldingContext() const157   evaluate::FoldingContext &GetFoldingContext() const {
158     return context_->foldingContext();
159   }
IsIntrinsic(const SourceName & name,std::optional<Symbol::Flag> flag) const160   bool IsIntrinsic(
161       const SourceName &name, std::optional<Symbol::Flag> flag) const {
162     if (!flag) {
163       return context_->intrinsics().IsIntrinsic(name.ToString());
164     } else if (flag == Symbol::Flag::Function) {
165       return context_->intrinsics().IsIntrinsicFunction(name.ToString());
166     } else if (flag == Symbol::Flag::Subroutine) {
167       return context_->intrinsics().IsIntrinsicSubroutine(name.ToString());
168     } else {
169       DIE("expected Subroutine or Function flag");
170     }
171   }
172 
173   // Make a placeholder symbol for a Name that otherwise wouldn't have one.
174   // It is not in any scope and always has MiscDetails.
175   void MakePlaceholder(const parser::Name &, MiscDetails::Kind);
176 
FoldExpr(T && expr)177   template <typename T> common::IfNoLvalue<T, T> FoldExpr(T &&expr) {
178     return evaluate::Fold(GetFoldingContext(), std::move(expr));
179   }
180 
EvaluateExpr(const T & expr)181   template <typename T> MaybeExpr EvaluateExpr(const T &expr) {
182     return FoldExpr(AnalyzeExpr(*context_, expr));
183   }
184 
185   template <typename T>
EvaluateNonPointerInitializer(const Symbol & symbol,const T & expr,parser::CharBlock source)186   MaybeExpr EvaluateNonPointerInitializer(
187       const Symbol &symbol, const T &expr, parser::CharBlock source) {
188     if (!context().HasError(symbol)) {
189       if (auto maybeExpr{AnalyzeExpr(*context_, expr)}) {
190         auto restorer{GetFoldingContext().messages().SetLocation(source)};
191         return evaluate::NonPointerInitializationExpr(
192             symbol, std::move(*maybeExpr), GetFoldingContext());
193       }
194     }
195     return std::nullopt;
196   }
197 
EvaluateIntExpr(const T & expr)198   template <typename T> MaybeIntExpr EvaluateIntExpr(const T &expr) {
199     return semantics::EvaluateIntExpr(*context_, expr);
200   }
201 
202   template <typename T>
EvaluateSubscriptIntExpr(const T & expr)203   MaybeSubscriptIntExpr EvaluateSubscriptIntExpr(const T &expr) {
204     if (MaybeIntExpr maybeIntExpr{EvaluateIntExpr(expr)}) {
205       return FoldExpr(evaluate::ConvertToType<evaluate::SubscriptInteger>(
206           std::move(*maybeIntExpr)));
207     } else {
208       return std::nullopt;
209     }
210   }
211 
Say(A &&...args)212   template <typename... A> Message &Say(A &&...args) {
213     return messageHandler_.Say(std::forward<A>(args)...);
214   }
215   template <typename... A>
Say(const parser::Name & name,MessageFixedText && text,const A &...args)216   Message &Say(
217       const parser::Name &name, MessageFixedText &&text, const A &...args) {
218     return messageHandler_.Say(name.source, std::move(text), args...);
219   }
220 
221 protected:
222   ImplicitRulesMap *implicitRulesMap_{nullptr};
223 
224 private:
225   ResolveNamesVisitor *this_;
226   SemanticsContext *context_;
227   MessageHandler messageHandler_;
228 };
229 
230 // Provide Post methods to collect attributes into a member variable.
231 class AttrsVisitor : public virtual BaseVisitor {
232 public:
233   bool BeginAttrs(); // always returns true
234   Attrs GetAttrs();
235   Attrs EndAttrs();
236   bool SetPassNameOn(Symbol &);
237   bool SetBindNameOn(Symbol &);
238   void Post(const parser::LanguageBindingSpec &);
239   bool Pre(const parser::IntentSpec &);
240   bool Pre(const parser::Pass &);
241 
242   bool CheckAndSet(Attr);
243 
244 // Simple case: encountering CLASSNAME causes ATTRNAME to be set.
245 #define HANDLE_ATTR_CLASS(CLASSNAME, ATTRNAME) \
246   bool Pre(const parser::CLASSNAME &) { \
247     CheckAndSet(Attr::ATTRNAME); \
248     return false; \
249   }
250   HANDLE_ATTR_CLASS(PrefixSpec::Elemental, ELEMENTAL)
251   HANDLE_ATTR_CLASS(PrefixSpec::Impure, IMPURE)
252   HANDLE_ATTR_CLASS(PrefixSpec::Module, MODULE)
253   HANDLE_ATTR_CLASS(PrefixSpec::Non_Recursive, NON_RECURSIVE)
254   HANDLE_ATTR_CLASS(PrefixSpec::Pure, PURE)
255   HANDLE_ATTR_CLASS(PrefixSpec::Recursive, RECURSIVE)
256   HANDLE_ATTR_CLASS(TypeAttrSpec::BindC, BIND_C)
257   HANDLE_ATTR_CLASS(BindAttr::Deferred, DEFERRED)
258   HANDLE_ATTR_CLASS(BindAttr::Non_Overridable, NON_OVERRIDABLE)
259   HANDLE_ATTR_CLASS(Abstract, ABSTRACT)
260   HANDLE_ATTR_CLASS(Allocatable, ALLOCATABLE)
261   HANDLE_ATTR_CLASS(Asynchronous, ASYNCHRONOUS)
262   HANDLE_ATTR_CLASS(Contiguous, CONTIGUOUS)
263   HANDLE_ATTR_CLASS(External, EXTERNAL)
264   HANDLE_ATTR_CLASS(Intrinsic, INTRINSIC)
265   HANDLE_ATTR_CLASS(NoPass, NOPASS)
266   HANDLE_ATTR_CLASS(Optional, OPTIONAL)
267   HANDLE_ATTR_CLASS(Parameter, PARAMETER)
268   HANDLE_ATTR_CLASS(Pointer, POINTER)
269   HANDLE_ATTR_CLASS(Protected, PROTECTED)
270   HANDLE_ATTR_CLASS(Save, SAVE)
271   HANDLE_ATTR_CLASS(Target, TARGET)
272   HANDLE_ATTR_CLASS(Value, VALUE)
273   HANDLE_ATTR_CLASS(Volatile, VOLATILE)
274 #undef HANDLE_ATTR_CLASS
275 
276 protected:
277   std::optional<Attrs> attrs_;
278 
AccessSpecToAttr(const parser::AccessSpec & x)279   Attr AccessSpecToAttr(const parser::AccessSpec &x) {
280     switch (x.v) {
281     case parser::AccessSpec::Kind::Public:
282       return Attr::PUBLIC;
283     case parser::AccessSpec::Kind::Private:
284       return Attr::PRIVATE;
285     }
286     llvm_unreachable("Switch covers all cases"); // suppress g++ warning
287   }
IntentSpecToAttr(const parser::IntentSpec & x)288   Attr IntentSpecToAttr(const parser::IntentSpec &x) {
289     switch (x.v) {
290     case parser::IntentSpec::Intent::In:
291       return Attr::INTENT_IN;
292     case parser::IntentSpec::Intent::Out:
293       return Attr::INTENT_OUT;
294     case parser::IntentSpec::Intent::InOut:
295       return Attr::INTENT_INOUT;
296     }
297     llvm_unreachable("Switch covers all cases"); // suppress g++ warning
298   }
299 
300 private:
301   bool IsDuplicateAttr(Attr);
302   bool HaveAttrConflict(Attr, Attr, Attr);
303   bool IsConflictingAttr(Attr);
304 
305   MaybeExpr bindName_; // from BIND(C, NAME="...")
306   std::optional<SourceName> passName_; // from PASS(...)
307 };
308 
309 // Find and create types from declaration-type-spec nodes.
310 class DeclTypeSpecVisitor : public AttrsVisitor {
311 public:
312   using AttrsVisitor::Post;
313   using AttrsVisitor::Pre;
314   void Post(const parser::IntrinsicTypeSpec::DoublePrecision &);
315   void Post(const parser::IntrinsicTypeSpec::DoubleComplex &);
316   void Post(const parser::DeclarationTypeSpec::ClassStar &);
317   void Post(const parser::DeclarationTypeSpec::TypeStar &);
318   bool Pre(const parser::TypeGuardStmt &);
319   void Post(const parser::TypeGuardStmt &);
320   void Post(const parser::TypeSpec &);
321 
322 protected:
323   struct State {
324     bool expectDeclTypeSpec{false}; // should see decl-type-spec only when true
325     const DeclTypeSpec *declTypeSpec{nullptr};
326     struct {
327       DerivedTypeSpec *type{nullptr};
328       DeclTypeSpec::Category category{DeclTypeSpec::TypeDerived};
329     } derived;
330     bool allowForwardReferenceToDerivedType{false};
331   };
332 
allowForwardReferenceToDerivedType() const333   bool allowForwardReferenceToDerivedType() const {
334     return state_.allowForwardReferenceToDerivedType;
335   }
set_allowForwardReferenceToDerivedType(bool yes)336   void set_allowForwardReferenceToDerivedType(bool yes) {
337     state_.allowForwardReferenceToDerivedType = yes;
338   }
339 
340   // Walk the parse tree of a type spec and return the DeclTypeSpec for it.
341   template <typename T>
ProcessTypeSpec(const T & x,bool allowForward=false)342   const DeclTypeSpec *ProcessTypeSpec(const T &x, bool allowForward = false) {
343     auto restorer{common::ScopedSet(state_, State{})};
344     set_allowForwardReferenceToDerivedType(allowForward);
345     BeginDeclTypeSpec();
346     Walk(x);
347     const auto *type{GetDeclTypeSpec()};
348     EndDeclTypeSpec();
349     return type;
350   }
351 
352   const DeclTypeSpec *GetDeclTypeSpec();
353   void BeginDeclTypeSpec();
354   void EndDeclTypeSpec();
355   void SetDeclTypeSpec(const DeclTypeSpec &);
356   void SetDeclTypeSpecCategory(DeclTypeSpec::Category);
GetDeclTypeSpecCategory() const357   DeclTypeSpec::Category GetDeclTypeSpecCategory() const {
358     return state_.derived.category;
359   }
360   KindExpr GetKindParamExpr(
361       TypeCategory, const std::optional<parser::KindSelector> &);
362   void CheckForAbstractType(const Symbol &typeSymbol);
363 
364 private:
365   State state_;
366 
367   void MakeNumericType(TypeCategory, int kind);
368 };
369 
370 // Visit ImplicitStmt and related parse tree nodes and updates implicit rules.
371 class ImplicitRulesVisitor : public DeclTypeSpecVisitor {
372 public:
373   using DeclTypeSpecVisitor::Post;
374   using DeclTypeSpecVisitor::Pre;
375   using ImplicitNoneNameSpec = parser::ImplicitStmt::ImplicitNoneNameSpec;
376 
377   void Post(const parser::ParameterStmt &);
378   bool Pre(const parser::ImplicitStmt &);
379   bool Pre(const parser::LetterSpec &);
380   bool Pre(const parser::ImplicitSpec &);
381   void Post(const parser::ImplicitSpec &);
382 
GetType(SourceName name)383   const DeclTypeSpec *GetType(SourceName name) {
384     return implicitRules_->GetType(name);
385   }
isImplicitNoneType() const386   bool isImplicitNoneType() const {
387     return implicitRules_->isImplicitNoneType();
388   }
isImplicitNoneType(const Scope & scope) const389   bool isImplicitNoneType(const Scope &scope) const {
390     return implicitRulesMap_->at(&scope).isImplicitNoneType();
391   }
isImplicitNoneExternal() const392   bool isImplicitNoneExternal() const {
393     return implicitRules_->isImplicitNoneExternal();
394   }
set_inheritFromParent(bool x)395   void set_inheritFromParent(bool x) {
396     implicitRules_->set_inheritFromParent(x);
397   }
398 
399 protected:
400   void BeginScope(const Scope &);
401   void SetScope(const Scope &);
402 
403 private:
404   // implicit rules in effect for current scope
405   ImplicitRules *implicitRules_{nullptr};
406   std::optional<SourceName> prevImplicit_;
407   std::optional<SourceName> prevImplicitNone_;
408   std::optional<SourceName> prevImplicitNoneType_;
409   std::optional<SourceName> prevParameterStmt_;
410 
411   bool HandleImplicitNone(const std::list<ImplicitNoneNameSpec> &nameSpecs);
412 };
413 
414 // Track array specifications. They can occur in AttrSpec, EntityDecl,
415 // ObjectDecl, DimensionStmt, CommonBlockObject, or BasedPointerStmt.
416 // 1. INTEGER, DIMENSION(10) :: x
417 // 2. INTEGER :: x(10)
418 // 3. ALLOCATABLE :: x(:)
419 // 4. DIMENSION :: x(10)
420 // 5. COMMON x(10)
421 // 6. BasedPointerStmt
422 class ArraySpecVisitor : public virtual BaseVisitor {
423 public:
424   void Post(const parser::ArraySpec &);
425   void Post(const parser::ComponentArraySpec &);
426   void Post(const parser::CoarraySpec &);
Post(const parser::AttrSpec &)427   void Post(const parser::AttrSpec &) { PostAttrSpec(); }
Post(const parser::ComponentAttrSpec &)428   void Post(const parser::ComponentAttrSpec &) { PostAttrSpec(); }
429 
430 protected:
431   const ArraySpec &arraySpec();
set_arraySpec(const ArraySpec arraySpec)432   void set_arraySpec(const ArraySpec arraySpec) { arraySpec_ = arraySpec; }
433   const ArraySpec &coarraySpec();
434   void BeginArraySpec();
435   void EndArraySpec();
ClearArraySpec()436   void ClearArraySpec() { arraySpec_.clear(); }
ClearCoarraySpec()437   void ClearCoarraySpec() { coarraySpec_.clear(); }
438 
439 private:
440   // arraySpec_/coarraySpec_ are populated from any ArraySpec/CoarraySpec
441   ArraySpec arraySpec_;
442   ArraySpec coarraySpec_;
443   // When an ArraySpec is under an AttrSpec or ComponentAttrSpec, it is moved
444   // into attrArraySpec_
445   ArraySpec attrArraySpec_;
446   ArraySpec attrCoarraySpec_;
447 
448   void PostAttrSpec();
449 };
450 
451 // Manage a stack of Scopes
452 class ScopeHandler : public ImplicitRulesVisitor {
453 public:
454   using ImplicitRulesVisitor::Post;
455   using ImplicitRulesVisitor::Pre;
456 
currScope()457   Scope &currScope() { return DEREF(currScope_); }
458   // The enclosing host procedure if current scope is in an internal procedure
459   Scope *GetHostProcedure();
460   // The enclosing scope, skipping blocks and derived types.
461   // TODO: Will return the scope of a FORALL or implied DO loop; is this ok?
462   // If not, should call FindProgramUnitContaining() instead.
463   Scope &InclusiveScope();
464   // The enclosing scope, skipping derived types.
465   Scope &NonDerivedTypeScope();
466 
467   // Create a new scope and push it on the scope stack.
468   void PushScope(Scope::Kind kind, Symbol *symbol);
469   void PushScope(Scope &scope);
470   void PopScope();
471   void SetScope(Scope &);
472 
Pre(const parser::Statement<T> & x)473   template <typename T> bool Pre(const parser::Statement<T> &x) {
474     messageHandler().set_currStmtSource(x.source);
475     currScope_->AddSourceRange(x.source);
476     return true;
477   }
Post(const parser::Statement<T> &)478   template <typename T> void Post(const parser::Statement<T> &) {
479     messageHandler().set_currStmtSource(std::nullopt);
480   }
481 
482   // Special messages: already declared; referencing symbol's declaration;
483   // about a type; two names & locations
484   void SayAlreadyDeclared(const parser::Name &, Symbol &);
485   void SayAlreadyDeclared(const SourceName &, Symbol &);
486   void SayAlreadyDeclared(const SourceName &, const SourceName &);
487   void SayWithReason(
488       const parser::Name &, Symbol &, MessageFixedText &&, MessageFixedText &&);
489   void SayWithDecl(const parser::Name &, Symbol &, MessageFixedText &&);
490   void SayLocalMustBeVariable(const parser::Name &, Symbol &);
491   void SayDerivedType(const SourceName &, MessageFixedText &&, const Scope &);
492   void Say2(const SourceName &, MessageFixedText &&, const SourceName &,
493       MessageFixedText &&);
494   void Say2(
495       const SourceName &, MessageFixedText &&, Symbol &, MessageFixedText &&);
496   void Say2(
497       const parser::Name &, MessageFixedText &&, Symbol &, MessageFixedText &&);
498 
499   // Search for symbol by name in current, parent derived type, and
500   // containing scopes
501   Symbol *FindSymbol(const parser::Name &);
502   Symbol *FindSymbol(const Scope &, const parser::Name &);
503   // Search for name only in scope, not in enclosing scopes.
504   Symbol *FindInScope(const Scope &, const parser::Name &);
505   Symbol *FindInScope(const Scope &, const SourceName &);
FindInScope(const T & name)506   template <typename T> Symbol *FindInScope(const T &name) {
507     return FindInScope(currScope(), name);
508   }
509   // Search for name in a derived type scope and its parents.
510   Symbol *FindInTypeOrParents(const Scope &, const parser::Name &);
511   Symbol *FindInTypeOrParents(const parser::Name &);
512   void EraseSymbol(const parser::Name &);
EraseSymbol(const Symbol & symbol)513   void EraseSymbol(const Symbol &symbol) { currScope().erase(symbol.name()); }
514   // Make a new symbol with the name and attrs of an existing one
515   Symbol &CopySymbol(const SourceName &, const Symbol &);
516 
517   // Make symbols in the current or named scope
518   Symbol &MakeSymbol(Scope &, const SourceName &, Attrs);
519   Symbol &MakeSymbol(const SourceName &, Attrs = Attrs{});
520   Symbol &MakeSymbol(const parser::Name &, Attrs = Attrs{});
521   Symbol &MakeHostAssocSymbol(const parser::Name &, const Symbol &);
522 
523   template <typename D>
MakeSymbol(const parser::Name & name,D && details)524   common::IfNoLvalue<Symbol &, D> MakeSymbol(
525       const parser::Name &name, D &&details) {
526     return MakeSymbol(name, Attrs{}, std::move(details));
527   }
528 
529   template <typename D>
MakeSymbol(const parser::Name & name,const Attrs & attrs,D && details)530   common::IfNoLvalue<Symbol &, D> MakeSymbol(
531       const parser::Name &name, const Attrs &attrs, D &&details) {
532     return Resolve(name, MakeSymbol(name.source, attrs, std::move(details)));
533   }
534 
535   template <typename D>
MakeSymbol(const SourceName & name,const Attrs & attrs,D && details)536   common::IfNoLvalue<Symbol &, D> MakeSymbol(
537       const SourceName &name, const Attrs &attrs, D &&details) {
538     // Note: don't use FindSymbol here. If this is a derived type scope,
539     // we want to detect whether the name is already declared as a component.
540     auto *symbol{FindInScope(name)};
541     if (!symbol) {
542       symbol = &MakeSymbol(name, attrs);
543       symbol->set_details(std::move(details));
544       return *symbol;
545     }
546     if constexpr (std::is_same_v<DerivedTypeDetails, D>) {
547       if (auto *d{symbol->detailsIf<GenericDetails>()}) {
548         if (!d->specific()) {
549           // derived type with same name as a generic
550           auto *derivedType{d->derivedType()};
551           if (!derivedType) {
552             derivedType =
553                 &currScope().MakeSymbol(name, attrs, std::move(details));
554             d->set_derivedType(*derivedType);
555           } else {
556             SayAlreadyDeclared(name, *derivedType);
557           }
558           return *derivedType;
559         }
560       }
561     }
562     if (symbol->CanReplaceDetails(details)) {
563       // update the existing symbol
564       symbol->attrs() |= attrs;
565       symbol->set_details(std::move(details));
566       return *symbol;
567     } else if constexpr (std::is_same_v<UnknownDetails, D>) {
568       symbol->attrs() |= attrs;
569       return *symbol;
570     } else {
571       if (!CheckPossibleBadForwardRef(*symbol)) {
572         SayAlreadyDeclared(name, *symbol);
573       }
574       // replace the old symbol with a new one with correct details
575       EraseSymbol(*symbol);
576       auto &result{MakeSymbol(name, attrs, std::move(details))};
577       context().SetError(result);
578       return result;
579     }
580   }
581 
582   void MakeExternal(Symbol &);
583 
584 protected:
585   // Apply the implicit type rules to this symbol.
586   void ApplyImplicitRules(Symbol &);
587   const DeclTypeSpec *GetImplicitType(Symbol &, const Scope &);
588   bool ConvertToObjectEntity(Symbol &);
589   bool ConvertToProcEntity(Symbol &);
590 
591   const DeclTypeSpec &MakeNumericType(
592       TypeCategory, const std::optional<parser::KindSelector> &);
593   const DeclTypeSpec &MakeLogicalType(
594       const std::optional<parser::KindSelector> &);
595   void NotePossibleBadForwardRef(const parser::Name &);
596   std::optional<SourceName> HadForwardRef(const Symbol &) const;
597   bool CheckPossibleBadForwardRef(const Symbol &);
598 
599   bool inExecutionPart_{false};
600   bool inSpecificationPart_{false};
601   bool inEquivalenceStmt_{false};
602   std::set<SourceName> specPartForwardRefs_;
603 
604 private:
605   Scope *currScope_{nullptr};
606 };
607 
608 class ModuleVisitor : public virtual ScopeHandler {
609 public:
610   bool Pre(const parser::AccessStmt &);
611   bool Pre(const parser::Only &);
612   bool Pre(const parser::Rename::Names &);
613   bool Pre(const parser::Rename::Operators &);
614   bool Pre(const parser::UseStmt &);
615   void Post(const parser::UseStmt &);
616 
617   void BeginModule(const parser::Name &, bool isSubmodule);
618   bool BeginSubmodule(const parser::Name &, const parser::ParentIdentifier &);
619   void ApplyDefaultAccess();
620   void AddGenericUse(GenericDetails &, const SourceName &, const Symbol &);
621 
622 private:
623   // The default access spec for this module.
624   Attr defaultAccess_{Attr::PUBLIC};
625   // The location of the last AccessStmt without access-ids, if any.
626   std::optional<SourceName> prevAccessStmt_;
627   // The scope of the module during a UseStmt
628   Scope *useModuleScope_{nullptr};
629 
630   Symbol &SetAccess(const SourceName &, Attr attr, Symbol * = nullptr);
631   // A rename in a USE statement: local => use
632   struct SymbolRename {
633     Symbol *local{nullptr};
634     Symbol *use{nullptr};
635   };
636   // Record a use from useModuleScope_ of use Name/Symbol as local Name/Symbol
637   SymbolRename AddUse(const SourceName &localName, const SourceName &useName);
638   SymbolRename AddUse(const SourceName &, const SourceName &, Symbol *);
639   void DoAddUse(const SourceName &, const SourceName &, Symbol &localSymbol,
640       const Symbol &useSymbol);
641   void AddUse(const GenericSpecInfo &);
642   Scope *FindModule(const parser::Name &, Scope *ancestor = nullptr);
643 };
644 
645 class InterfaceVisitor : public virtual ScopeHandler {
646 public:
647   bool Pre(const parser::InterfaceStmt &);
648   void Post(const parser::InterfaceStmt &);
649   void Post(const parser::EndInterfaceStmt &);
650   bool Pre(const parser::GenericSpec &);
651   bool Pre(const parser::ProcedureStmt &);
652   bool Pre(const parser::GenericStmt &);
653   void Post(const parser::GenericStmt &);
654 
655   bool inInterfaceBlock() const;
656   bool isGeneric() const;
657   bool isAbstract() const;
658 
659 protected:
660   GenericDetails &GetGenericDetails();
661   // Add to generic the symbol for the subprogram with the same name
662   void CheckGenericProcedures(Symbol &);
663 
664 private:
665   // A new GenericInfo is pushed for each interface block and generic stmt
666   struct GenericInfo {
GenericInfoFortran::semantics::InterfaceVisitor::GenericInfo667     GenericInfo(bool isInterface, bool isAbstract = false)
668         : isInterface{isInterface}, isAbstract{isAbstract} {}
669     bool isInterface; // in interface block
670     bool isAbstract; // in abstract interface block
671     Symbol *symbol{nullptr}; // the generic symbol being defined
672   };
673   std::stack<GenericInfo> genericInfo_;
GetGenericInfo() const674   const GenericInfo &GetGenericInfo() const { return genericInfo_.top(); }
SetGenericSymbol(Symbol & symbol)675   void SetGenericSymbol(Symbol &symbol) { genericInfo_.top().symbol = &symbol; }
676 
677   using ProcedureKind = parser::ProcedureStmt::Kind;
678   // mapping of generic to its specific proc names and kinds
679   std::multimap<Symbol *, std::pair<const parser::Name *, ProcedureKind>>
680       specificProcs_;
681 
682   void AddSpecificProcs(const std::list<parser::Name> &, ProcedureKind);
683   void ResolveSpecificsInGeneric(Symbol &generic);
684 };
685 
686 class SubprogramVisitor : public virtual ScopeHandler, public InterfaceVisitor {
687 public:
688   bool HandleStmtFunction(const parser::StmtFunctionStmt &);
689   bool Pre(const parser::SubroutineStmt &);
690   void Post(const parser::SubroutineStmt &);
691   bool Pre(const parser::FunctionStmt &);
692   void Post(const parser::FunctionStmt &);
693   bool Pre(const parser::EntryStmt &);
694   void Post(const parser::EntryStmt &);
695   bool Pre(const parser::InterfaceBody::Subroutine &);
696   void Post(const parser::InterfaceBody::Subroutine &);
697   bool Pre(const parser::InterfaceBody::Function &);
698   void Post(const parser::InterfaceBody::Function &);
699   bool Pre(const parser::Suffix &);
700   bool Pre(const parser::PrefixSpec &);
701   void Post(const parser::ImplicitPart &);
702 
703   bool BeginSubprogram(
704       const parser::Name &, Symbol::Flag, bool hasModulePrefix = false);
705   bool BeginMpSubprogram(const parser::Name &);
706   void PushBlockDataScope(const parser::Name &);
707   void EndSubprogram();
708 
709 protected:
710   // Set when we see a stmt function that is really an array element assignment
711   bool badStmtFuncFound_{false};
712 
713 private:
714   // Info about the current function: parse tree of the type in the PrefixSpec;
715   // name and symbol of the function result from the Suffix; source location.
716   struct {
717     const parser::DeclarationTypeSpec *parsedType{nullptr};
718     const parser::Name *resultName{nullptr};
719     Symbol *resultSymbol{nullptr};
720     std::optional<SourceName> source;
721   } funcInfo_;
722 
723   // Create a subprogram symbol in the current scope and push a new scope.
724   void CheckExtantExternal(const parser::Name &, Symbol::Flag);
725   Symbol &PushSubprogramScope(const parser::Name &, Symbol::Flag);
726   Symbol *GetSpecificFromGeneric(const parser::Name &);
727   SubprogramDetails &PostSubprogramStmt(const parser::Name &);
728 };
729 
730 class DeclarationVisitor : public ArraySpecVisitor,
731                            public virtual ScopeHandler {
732 public:
733   using ArraySpecVisitor::Post;
734   using ScopeHandler::Post;
735   using ScopeHandler::Pre;
736 
737   bool Pre(const parser::Initialization &);
738   void Post(const parser::EntityDecl &);
739   void Post(const parser::ObjectDecl &);
740   void Post(const parser::PointerDecl &);
Pre(const parser::BindStmt &)741   bool Pre(const parser::BindStmt &) { return BeginAttrs(); }
Post(const parser::BindStmt &)742   void Post(const parser::BindStmt &) { EndAttrs(); }
743   bool Pre(const parser::BindEntity &);
744   bool Pre(const parser::NamedConstantDef &);
745   bool Pre(const parser::NamedConstant &);
746   void Post(const parser::EnumDef &);
747   bool Pre(const parser::Enumerator &);
748   bool Pre(const parser::AccessSpec &);
749   bool Pre(const parser::AsynchronousStmt &);
750   bool Pre(const parser::ContiguousStmt &);
751   bool Pre(const parser::ExternalStmt &);
752   bool Pre(const parser::IntentStmt &);
753   bool Pre(const parser::IntrinsicStmt &);
754   bool Pre(const parser::OptionalStmt &);
755   bool Pre(const parser::ProtectedStmt &);
756   bool Pre(const parser::ValueStmt &);
757   bool Pre(const parser::VolatileStmt &);
Pre(const parser::AllocatableStmt &)758   bool Pre(const parser::AllocatableStmt &) {
759     objectDeclAttr_ = Attr::ALLOCATABLE;
760     return true;
761   }
Post(const parser::AllocatableStmt &)762   void Post(const parser::AllocatableStmt &) { objectDeclAttr_ = std::nullopt; }
Pre(const parser::TargetStmt &)763   bool Pre(const parser::TargetStmt &) {
764     objectDeclAttr_ = Attr::TARGET;
765     return true;
766   }
Post(const parser::TargetStmt &)767   void Post(const parser::TargetStmt &) { objectDeclAttr_ = std::nullopt; }
768   void Post(const parser::DimensionStmt::Declaration &);
769   void Post(const parser::CodimensionDecl &);
Pre(const parser::TypeDeclarationStmt &)770   bool Pre(const parser::TypeDeclarationStmt &) { return BeginDecl(); }
771   void Post(const parser::TypeDeclarationStmt &);
772   void Post(const parser::IntegerTypeSpec &);
773   void Post(const parser::IntrinsicTypeSpec::Real &);
774   void Post(const parser::IntrinsicTypeSpec::Complex &);
775   void Post(const parser::IntrinsicTypeSpec::Logical &);
776   void Post(const parser::IntrinsicTypeSpec::Character &);
777   void Post(const parser::CharSelector::LengthAndKind &);
778   void Post(const parser::CharLength &);
779   void Post(const parser::LengthSelector &);
780   bool Pre(const parser::KindParam &);
781   bool Pre(const parser::DeclarationTypeSpec::Type &);
782   void Post(const parser::DeclarationTypeSpec::Type &);
783   bool Pre(const parser::DeclarationTypeSpec::Class &);
784   void Post(const parser::DeclarationTypeSpec::Class &);
785   bool Pre(const parser::DeclarationTypeSpec::Record &);
786   void Post(const parser::DerivedTypeSpec &);
787   bool Pre(const parser::DerivedTypeDef &);
788   bool Pre(const parser::DerivedTypeStmt &);
789   void Post(const parser::DerivedTypeStmt &);
Pre(const parser::TypeParamDefStmt &)790   bool Pre(const parser::TypeParamDefStmt &) { return BeginDecl(); }
791   void Post(const parser::TypeParamDefStmt &);
792   bool Pre(const parser::TypeAttrSpec::Extends &);
793   bool Pre(const parser::PrivateStmt &);
794   bool Pre(const parser::SequenceStmt &);
Pre(const parser::ComponentDefStmt &)795   bool Pre(const parser::ComponentDefStmt &) { return BeginDecl(); }
Post(const parser::ComponentDefStmt &)796   void Post(const parser::ComponentDefStmt &) { EndDecl(); }
797   void Post(const parser::ComponentDecl &);
798   bool Pre(const parser::ProcedureDeclarationStmt &);
799   void Post(const parser::ProcedureDeclarationStmt &);
800   bool Pre(const parser::DataComponentDefStmt &); // returns false
801   bool Pre(const parser::ProcComponentDefStmt &);
802   void Post(const parser::ProcComponentDefStmt &);
803   bool Pre(const parser::ProcPointerInit &);
804   void Post(const parser::ProcInterface &);
805   void Post(const parser::ProcDecl &);
806   bool Pre(const parser::TypeBoundProcedurePart &);
807   void Post(const parser::TypeBoundProcedurePart &);
808   void Post(const parser::ContainsStmt &);
Pre(const parser::TypeBoundProcBinding &)809   bool Pre(const parser::TypeBoundProcBinding &) { return BeginAttrs(); }
Post(const parser::TypeBoundProcBinding &)810   void Post(const parser::TypeBoundProcBinding &) { EndAttrs(); }
811   void Post(const parser::TypeBoundProcedureStmt::WithoutInterface &);
812   void Post(const parser::TypeBoundProcedureStmt::WithInterface &);
813   void Post(const parser::FinalProcedureStmt &);
814   bool Pre(const parser::TypeBoundGenericStmt &);
815   bool Pre(const parser::AllocateStmt &);
816   void Post(const parser::AllocateStmt &);
817   bool Pre(const parser::StructureConstructor &);
818   bool Pre(const parser::NamelistStmt::Group &);
819   bool Pre(const parser::IoControlSpec &);
820   bool Pre(const parser::CommonStmt::Block &);
821   bool Pre(const parser::CommonBlockObject &);
822   void Post(const parser::CommonBlockObject &);
823   bool Pre(const parser::EquivalenceStmt &);
824   bool Pre(const parser::SaveStmt &);
825   bool Pre(const parser::BasedPointerStmt &);
826 
827   void PointerInitialization(
828       const parser::Name &, const parser::InitialDataTarget &);
829   void PointerInitialization(
830       const parser::Name &, const parser::ProcPointerInit &);
831   void NonPointerInitialization(
832       const parser::Name &, const parser::ConstantExpr &);
833   void CheckExplicitInterface(const parser::Name &);
834   void CheckBindings(const parser::TypeBoundProcedureStmt::WithoutInterface &);
835 
836   const parser::Name *ResolveDesignator(const parser::Designator &);
837 
838 protected:
839   bool BeginDecl();
840   void EndDecl();
841   Symbol &DeclareObjectEntity(const parser::Name &, Attrs = Attrs{});
842   // Make sure that there's an entity in an enclosing scope called Name
843   Symbol &FindOrDeclareEnclosingEntity(const parser::Name &);
844   // Declare a LOCAL/LOCAL_INIT entity. If there isn't a type specified
845   // it comes from the entity in the containing scope, or implicit rules.
846   // Return pointer to the new symbol, or nullptr on error.
847   Symbol *DeclareLocalEntity(const parser::Name &);
848   // Declare a statement entity (e.g., an implied DO loop index).
849   // If there isn't a type specified, implicit rules apply.
850   // Return pointer to the new symbol, or nullptr on error.
851   Symbol *DeclareStatementEntity(
852       const parser::Name &, const std::optional<parser::IntegerTypeSpec> &);
853   Symbol &MakeCommonBlockSymbol(const parser::Name &);
854   Symbol &MakeCommonBlockSymbol(const std::optional<parser::Name> &);
855   bool CheckUseError(const parser::Name &);
856   void CheckAccessibility(const SourceName &, bool, Symbol &);
857   void CheckCommonBlocks();
858   void CheckSaveStmts();
859   void CheckEquivalenceSets();
860   bool CheckNotInBlock(const char *);
861   bool NameIsKnownOrIntrinsic(const parser::Name &);
862 
863   // Each of these returns a pointer to a resolved Name (i.e. with symbol)
864   // or nullptr in case of error.
865   const parser::Name *ResolveStructureComponent(
866       const parser::StructureComponent &);
867   const parser::Name *ResolveDataRef(const parser::DataRef &);
868   const parser::Name *ResolveName(const parser::Name &);
869   bool PassesSharedLocalityChecks(const parser::Name &name, Symbol &symbol);
870   Symbol *NoteInterfaceName(const parser::Name &);
871 
872 private:
873   // The attribute corresponding to the statement containing an ObjectDecl
874   std::optional<Attr> objectDeclAttr_;
875   // Info about current character type while walking DeclTypeSpec.
876   // Also captures any "*length" specifier on an individual declaration.
877   struct {
878     std::optional<ParamValue> length;
879     std::optional<KindExpr> kind;
880   } charInfo_;
881   // Info about current derived type while walking DerivedTypeDef
882   struct {
883     const parser::Name *extends{nullptr}; // EXTENDS(name)
884     bool privateComps{false}; // components are private by default
885     bool privateBindings{false}; // bindings are private by default
886     bool sawContains{false}; // currently processing bindings
887     bool sequence{false}; // is a sequence type
888     const Symbol *type{nullptr}; // derived type being defined
889   } derivedTypeInfo_;
890   // Collect equivalence sets and process at end of specification part
891   std::vector<const std::list<parser::EquivalenceObject> *> equivalenceSets_;
892   // Names of all common block objects in the scope
893   std::set<SourceName> commonBlockObjects_;
894   // Info about about SAVE statements and attributes in current scope
895   struct {
896     std::optional<SourceName> saveAll; // "SAVE" without entity list
897     std::set<SourceName> entities; // names of entities with save attr
898     std::set<SourceName> commons; // names of common blocks with save attr
899   } saveInfo_;
900   // In a ProcedureDeclarationStmt or ProcComponentDefStmt, this is
901   // the interface name, if any.
902   const parser::Name *interfaceName_{nullptr};
903   // Map type-bound generic to binding names of its specific bindings
904   std::multimap<Symbol *, const parser::Name *> genericBindings_;
905   // Info about current ENUM
906   struct EnumeratorState {
907     // Enum value must hold inside a C_INT (7.6.2).
908     std::optional<int> value{0};
909   } enumerationState_;
910 
911   bool HandleAttributeStmt(Attr, const std::list<parser::Name> &);
912   Symbol &HandleAttributeStmt(Attr, const parser::Name &);
913   Symbol &DeclareUnknownEntity(const parser::Name &, Attrs);
914   Symbol &DeclareProcEntity(const parser::Name &, Attrs, const ProcInterface &);
915   void SetType(const parser::Name &, const DeclTypeSpec &);
916   std::optional<DerivedTypeSpec> ResolveDerivedType(const parser::Name &);
917   std::optional<DerivedTypeSpec> ResolveExtendsType(
918       const parser::Name &, const parser::Name *);
919   Symbol *MakeTypeSymbol(const SourceName &, Details &&);
920   Symbol *MakeTypeSymbol(const parser::Name &, Details &&);
921   bool OkToAddComponent(const parser::Name &, const Symbol * = nullptr);
922   ParamValue GetParamValue(
923       const parser::TypeParamValue &, common::TypeParamAttr attr);
924   void CheckCommonBlockDerivedType(const SourceName &, const Symbol &);
925   std::optional<MessageFixedText> CheckSaveAttr(const Symbol &);
926   Attrs HandleSaveName(const SourceName &, Attrs);
927   void AddSaveName(std::set<SourceName> &, const SourceName &);
928   void SetSaveAttr(Symbol &);
929   bool HandleUnrestrictedSpecificIntrinsicFunction(const parser::Name &);
930   bool IsUplevelReference(const Symbol &);
931   const parser::Name *FindComponent(const parser::Name *, const parser::Name &);
932   void Initialization(const parser::Name &, const parser::Initialization &,
933       bool inComponentDecl);
934   bool PassesLocalityChecks(const parser::Name &name, Symbol &symbol);
935   bool CheckForHostAssociatedImplicit(const parser::Name &);
936 
937   // Declare an object or procedure entity.
938   // T is one of: EntityDetails, ObjectEntityDetails, ProcEntityDetails
939   template <typename T>
DeclareEntity(const parser::Name & name,Attrs attrs)940   Symbol &DeclareEntity(const parser::Name &name, Attrs attrs) {
941     Symbol &symbol{MakeSymbol(name, attrs)};
942     if (context().HasError(symbol) || symbol.has<T>()) {
943       return symbol; // OK or error already reported
944     } else if (symbol.has<UnknownDetails>()) {
945       symbol.set_details(T{});
946       return symbol;
947     } else if (auto *details{symbol.detailsIf<EntityDetails>()}) {
948       symbol.set_details(T{std::move(*details)});
949       return symbol;
950     } else if (std::is_same_v<EntityDetails, T> &&
951         (symbol.has<ObjectEntityDetails>() ||
952             symbol.has<ProcEntityDetails>())) {
953       return symbol; // OK
954     } else if (auto *details{symbol.detailsIf<UseDetails>()}) {
955       Say(name.source,
956           "'%s' is use-associated from module '%s' and cannot be re-declared"_err_en_US,
957           name.source, GetUsedModule(*details).name());
958     } else if (auto *details{symbol.detailsIf<SubprogramNameDetails>()}) {
959       if (details->kind() == SubprogramKind::Module) {
960         Say2(name,
961             "Declaration of '%s' conflicts with its use as module procedure"_err_en_US,
962             symbol, "Module procedure definition"_en_US);
963       } else if (details->kind() == SubprogramKind::Internal) {
964         Say2(name,
965             "Declaration of '%s' conflicts with its use as internal procedure"_err_en_US,
966             symbol, "Internal procedure definition"_en_US);
967       } else {
968         DIE("unexpected kind");
969       }
970     } else if (std::is_same_v<ObjectEntityDetails, T> &&
971         symbol.has<ProcEntityDetails>()) {
972       SayWithDecl(
973           name, symbol, "'%s' is already declared as a procedure"_err_en_US);
974     } else if (std::is_same_v<ProcEntityDetails, T> &&
975         symbol.has<ObjectEntityDetails>()) {
976       if (InCommonBlock(symbol)) {
977         SayWithDecl(name, symbol,
978             "'%s' may not be a procedure as it is in a COMMON block"_err_en_US);
979       } else {
980         SayWithDecl(
981             name, symbol, "'%s' is already declared as an object"_err_en_US);
982       }
983     } else if (!CheckPossibleBadForwardRef(symbol)) {
984       SayAlreadyDeclared(name, symbol);
985     }
986     context().SetError(symbol);
987     return symbol;
988   }
989 };
990 
991 // Resolve construct entities and statement entities.
992 // Check that construct names don't conflict with other names.
993 class ConstructVisitor : public virtual DeclarationVisitor {
994 public:
995   bool Pre(const parser::ConcurrentHeader &);
996   bool Pre(const parser::LocalitySpec::Local &);
997   bool Pre(const parser::LocalitySpec::LocalInit &);
998   bool Pre(const parser::LocalitySpec::Shared &);
999   bool Pre(const parser::AcSpec &);
1000   bool Pre(const parser::AcImpliedDo &);
1001   bool Pre(const parser::DataImpliedDo &);
1002   bool Pre(const parser::DataIDoObject &);
1003   bool Pre(const parser::DataStmtObject &);
1004   bool Pre(const parser::DataStmtValue &);
1005   bool Pre(const parser::DoConstruct &);
1006   void Post(const parser::DoConstruct &);
1007   bool Pre(const parser::ForallConstruct &);
1008   void Post(const parser::ForallConstruct &);
1009   bool Pre(const parser::ForallStmt &);
1010   void Post(const parser::ForallStmt &);
1011   bool Pre(const parser::BlockStmt &);
1012   bool Pre(const parser::EndBlockStmt &);
1013   void Post(const parser::Selector &);
1014   void Post(const parser::AssociateStmt &);
1015   void Post(const parser::EndAssociateStmt &);
1016   bool Pre(const parser::Association &);
1017   void Post(const parser::SelectTypeStmt &);
1018   void Post(const parser::SelectRankStmt &);
1019   bool Pre(const parser::SelectTypeConstruct &);
1020   void Post(const parser::SelectTypeConstruct &);
1021   bool Pre(const parser::SelectTypeConstruct::TypeCase &);
1022   void Post(const parser::SelectTypeConstruct::TypeCase &);
1023   // Creates Block scopes with neither symbol name nor symbol details.
1024   bool Pre(const parser::SelectRankConstruct::RankCase &);
1025   void Post(const parser::SelectRankConstruct::RankCase &);
1026   void Post(const parser::TypeGuardStmt::Guard &);
1027   void Post(const parser::SelectRankCaseStmt::Rank &);
1028   bool Pre(const parser::ChangeTeamStmt &);
1029   void Post(const parser::EndChangeTeamStmt &);
1030   void Post(const parser::CoarrayAssociation &);
1031 
1032   // Definitions of construct names
Pre(const parser::WhereConstructStmt & x)1033   bool Pre(const parser::WhereConstructStmt &x) { return CheckDef(x.t); }
Pre(const parser::ForallConstructStmt & x)1034   bool Pre(const parser::ForallConstructStmt &x) { return CheckDef(x.t); }
Pre(const parser::CriticalStmt & x)1035   bool Pre(const parser::CriticalStmt &x) { return CheckDef(x.t); }
Pre(const parser::LabelDoStmt &)1036   bool Pre(const parser::LabelDoStmt &) {
1037     return false; // error recovery
1038   }
Pre(const parser::NonLabelDoStmt & x)1039   bool Pre(const parser::NonLabelDoStmt &x) { return CheckDef(x.t); }
Pre(const parser::IfThenStmt & x)1040   bool Pre(const parser::IfThenStmt &x) { return CheckDef(x.t); }
Pre(const parser::SelectCaseStmt & x)1041   bool Pre(const parser::SelectCaseStmt &x) { return CheckDef(x.t); }
1042   bool Pre(const parser::SelectRankConstruct &);
1043   void Post(const parser::SelectRankConstruct &);
Pre(const parser::SelectRankStmt & x)1044   bool Pre(const parser::SelectRankStmt &x) {
1045     return CheckDef(std::get<0>(x.t));
1046   }
Pre(const parser::SelectTypeStmt & x)1047   bool Pre(const parser::SelectTypeStmt &x) {
1048     return CheckDef(std::get<0>(x.t));
1049   }
1050 
1051   // References to construct names
Post(const parser::MaskedElsewhereStmt & x)1052   void Post(const parser::MaskedElsewhereStmt &x) { CheckRef(x.t); }
Post(const parser::ElsewhereStmt & x)1053   void Post(const parser::ElsewhereStmt &x) { CheckRef(x.v); }
Post(const parser::EndWhereStmt & x)1054   void Post(const parser::EndWhereStmt &x) { CheckRef(x.v); }
Post(const parser::EndForallStmt & x)1055   void Post(const parser::EndForallStmt &x) { CheckRef(x.v); }
Post(const parser::EndCriticalStmt & x)1056   void Post(const parser::EndCriticalStmt &x) { CheckRef(x.v); }
Post(const parser::EndDoStmt & x)1057   void Post(const parser::EndDoStmt &x) { CheckRef(x.v); }
Post(const parser::ElseIfStmt & x)1058   void Post(const parser::ElseIfStmt &x) { CheckRef(x.t); }
Post(const parser::ElseStmt & x)1059   void Post(const parser::ElseStmt &x) { CheckRef(x.v); }
Post(const parser::EndIfStmt & x)1060   void Post(const parser::EndIfStmt &x) { CheckRef(x.v); }
Post(const parser::CaseStmt & x)1061   void Post(const parser::CaseStmt &x) { CheckRef(x.t); }
Post(const parser::EndSelectStmt & x)1062   void Post(const parser::EndSelectStmt &x) { CheckRef(x.v); }
Post(const parser::SelectRankCaseStmt & x)1063   void Post(const parser::SelectRankCaseStmt &x) { CheckRef(x.t); }
Post(const parser::TypeGuardStmt & x)1064   void Post(const parser::TypeGuardStmt &x) { CheckRef(x.t); }
Post(const parser::CycleStmt & x)1065   void Post(const parser::CycleStmt &x) { CheckRef(x.v); }
Post(const parser::ExitStmt & x)1066   void Post(const parser::ExitStmt &x) { CheckRef(x.v); }
1067 
1068 private:
1069   // R1105 selector -> expr | variable
1070   // expr is set in either case unless there were errors
1071   struct Selector {
SelectorFortran::semantics::ConstructVisitor::Selector1072     Selector() {}
SelectorFortran::semantics::ConstructVisitor::Selector1073     Selector(const SourceName &source, MaybeExpr &&expr)
1074         : source{source}, expr{std::move(expr)} {}
operator boolFortran::semantics::ConstructVisitor::Selector1075     operator bool() const { return expr.has_value(); }
1076     parser::CharBlock source;
1077     MaybeExpr expr;
1078   };
1079   // association -> [associate-name =>] selector
1080   struct Association {
1081     const parser::Name *name{nullptr};
1082     Selector selector;
1083   };
1084   std::vector<Association> associationStack_;
1085   Association *currentAssociation_{nullptr};
1086 
CheckDef(const T & t)1087   template <typename T> bool CheckDef(const T &t) {
1088     return CheckDef(std::get<std::optional<parser::Name>>(t));
1089   }
CheckRef(const T & t)1090   template <typename T> void CheckRef(const T &t) {
1091     CheckRef(std::get<std::optional<parser::Name>>(t));
1092   }
1093   bool CheckDef(const std::optional<parser::Name> &);
1094   void CheckRef(const std::optional<parser::Name> &);
1095   const DeclTypeSpec &ToDeclTypeSpec(evaluate::DynamicType &&);
1096   const DeclTypeSpec &ToDeclTypeSpec(
1097       evaluate::DynamicType &&, MaybeSubscriptIntExpr &&length);
1098   Symbol *MakeAssocEntity();
1099   void SetTypeFromAssociation(Symbol &);
1100   void SetAttrsFromAssociation(Symbol &);
1101   Selector ResolveSelector(const parser::Selector &);
1102   void ResolveIndexName(const parser::ConcurrentControl &control);
1103   void SetCurrentAssociation(std::size_t n);
1104   Association &GetCurrentAssociation();
1105   void PushAssociation();
1106   void PopAssociation(std::size_t count = 1);
1107 };
1108 
1109 // Create scopes for OpenACC constructs
1110 class AccVisitor : public virtual DeclarationVisitor {
1111 public:
1112   void AddAccSourceRange(const parser::CharBlock &);
1113 
1114   static bool NeedsScope(const parser::OpenACCBlockConstruct &);
1115 
1116   bool Pre(const parser::OpenACCBlockConstruct &);
1117   void Post(const parser::OpenACCBlockConstruct &);
Pre(const parser::AccBeginBlockDirective & x)1118   bool Pre(const parser::AccBeginBlockDirective &x) {
1119     AddAccSourceRange(x.source);
1120     return true;
1121   }
Post(const parser::AccBeginBlockDirective &)1122   void Post(const parser::AccBeginBlockDirective &) {
1123     messageHandler().set_currStmtSource(std::nullopt);
1124   }
Pre(const parser::AccEndBlockDirective & x)1125   bool Pre(const parser::AccEndBlockDirective &x) {
1126     AddAccSourceRange(x.source);
1127     return true;
1128   }
Post(const parser::AccEndBlockDirective &)1129   void Post(const parser::AccEndBlockDirective &) {
1130     messageHandler().set_currStmtSource(std::nullopt);
1131   }
Pre(const parser::AccBeginLoopDirective & x)1132   bool Pre(const parser::AccBeginLoopDirective &x) {
1133     AddAccSourceRange(x.source);
1134     return true;
1135   }
Post(const parser::AccBeginLoopDirective & x)1136   void Post(const parser::AccBeginLoopDirective &x) {
1137     messageHandler().set_currStmtSource(std::nullopt);
1138   }
1139 };
1140 
NeedsScope(const parser::OpenACCBlockConstruct & x)1141 bool AccVisitor::NeedsScope(const parser::OpenACCBlockConstruct &x) {
1142   const auto &beginBlockDir{std::get<parser::AccBeginBlockDirective>(x.t)};
1143   const auto &beginDir{std::get<parser::AccBlockDirective>(beginBlockDir.t)};
1144   switch (beginDir.v) {
1145   case llvm::acc::Directive::ACCD_data:
1146   case llvm::acc::Directive::ACCD_host_data:
1147   case llvm::acc::Directive::ACCD_kernels:
1148   case llvm::acc::Directive::ACCD_parallel:
1149   case llvm::acc::Directive::ACCD_serial:
1150     return true;
1151   default:
1152     return false;
1153   }
1154 }
1155 
AddAccSourceRange(const parser::CharBlock & source)1156 void AccVisitor::AddAccSourceRange(const parser::CharBlock &source) {
1157   messageHandler().set_currStmtSource(source);
1158   currScope().AddSourceRange(source);
1159 }
1160 
Pre(const parser::OpenACCBlockConstruct & x)1161 bool AccVisitor::Pre(const parser::OpenACCBlockConstruct &x) {
1162   if (NeedsScope(x)) {
1163     PushScope(Scope::Kind::Block, nullptr);
1164   }
1165   return true;
1166 }
1167 
Post(const parser::OpenACCBlockConstruct & x)1168 void AccVisitor::Post(const parser::OpenACCBlockConstruct &x) {
1169   if (NeedsScope(x)) {
1170     PopScope();
1171   }
1172 }
1173 
1174 // Create scopes for OpenMP constructs
1175 class OmpVisitor : public virtual DeclarationVisitor {
1176 public:
1177   void AddOmpSourceRange(const parser::CharBlock &);
1178 
1179   static bool NeedsScope(const parser::OpenMPBlockConstruct &);
1180 
1181   bool Pre(const parser::OpenMPBlockConstruct &);
1182   void Post(const parser::OpenMPBlockConstruct &);
Pre(const parser::OmpBeginBlockDirective & x)1183   bool Pre(const parser::OmpBeginBlockDirective &x) {
1184     AddOmpSourceRange(x.source);
1185     return true;
1186   }
Post(const parser::OmpBeginBlockDirective &)1187   void Post(const parser::OmpBeginBlockDirective &) {
1188     messageHandler().set_currStmtSource(std::nullopt);
1189   }
Pre(const parser::OmpEndBlockDirective & x)1190   bool Pre(const parser::OmpEndBlockDirective &x) {
1191     AddOmpSourceRange(x.source);
1192     return true;
1193   }
Post(const parser::OmpEndBlockDirective &)1194   void Post(const parser::OmpEndBlockDirective &) {
1195     messageHandler().set_currStmtSource(std::nullopt);
1196   }
1197 
Pre(const parser::OpenMPLoopConstruct &)1198   bool Pre(const parser::OpenMPLoopConstruct &) {
1199     PushScope(Scope::Kind::Block, nullptr);
1200     return true;
1201   }
Post(const parser::OpenMPLoopConstruct &)1202   void Post(const parser::OpenMPLoopConstruct &) { PopScope(); }
Pre(const parser::OmpBeginLoopDirective & x)1203   bool Pre(const parser::OmpBeginLoopDirective &x) {
1204     AddOmpSourceRange(x.source);
1205     return true;
1206   }
Post(const parser::OmpBeginLoopDirective &)1207   void Post(const parser::OmpBeginLoopDirective &) {
1208     messageHandler().set_currStmtSource(std::nullopt);
1209   }
Pre(const parser::OmpEndLoopDirective & x)1210   bool Pre(const parser::OmpEndLoopDirective &x) {
1211     AddOmpSourceRange(x.source);
1212     return true;
1213   }
Post(const parser::OmpEndLoopDirective &)1214   void Post(const parser::OmpEndLoopDirective &) {
1215     messageHandler().set_currStmtSource(std::nullopt);
1216   }
1217 
Pre(const parser::OpenMPSectionsConstruct &)1218   bool Pre(const parser::OpenMPSectionsConstruct &) {
1219     PushScope(Scope::Kind::Block, nullptr);
1220     return true;
1221   }
Post(const parser::OpenMPSectionsConstruct &)1222   void Post(const parser::OpenMPSectionsConstruct &) { PopScope(); }
Pre(const parser::OmpBeginSectionsDirective & x)1223   bool Pre(const parser::OmpBeginSectionsDirective &x) {
1224     AddOmpSourceRange(x.source);
1225     return true;
1226   }
Post(const parser::OmpBeginSectionsDirective &)1227   void Post(const parser::OmpBeginSectionsDirective &) {
1228     messageHandler().set_currStmtSource(std::nullopt);
1229   }
Pre(const parser::OmpEndSectionsDirective & x)1230   bool Pre(const parser::OmpEndSectionsDirective &x) {
1231     AddOmpSourceRange(x.source);
1232     return true;
1233   }
Post(const parser::OmpEndSectionsDirective &)1234   void Post(const parser::OmpEndSectionsDirective &) {
1235     messageHandler().set_currStmtSource(std::nullopt);
1236   }
1237 };
1238 
NeedsScope(const parser::OpenMPBlockConstruct & x)1239 bool OmpVisitor::NeedsScope(const parser::OpenMPBlockConstruct &x) {
1240   const auto &beginBlockDir{std::get<parser::OmpBeginBlockDirective>(x.t)};
1241   const auto &beginDir{std::get<parser::OmpBlockDirective>(beginBlockDir.t)};
1242   switch (beginDir.v) {
1243   case llvm::omp::Directive::OMPD_target_data:
1244   case llvm::omp::Directive::OMPD_master:
1245   case llvm::omp::Directive::OMPD_ordered:
1246     return false;
1247   default:
1248     return true;
1249   }
1250 }
1251 
AddOmpSourceRange(const parser::CharBlock & source)1252 void OmpVisitor::AddOmpSourceRange(const parser::CharBlock &source) {
1253   messageHandler().set_currStmtSource(source);
1254   currScope().AddSourceRange(source);
1255 }
1256 
Pre(const parser::OpenMPBlockConstruct & x)1257 bool OmpVisitor::Pre(const parser::OpenMPBlockConstruct &x) {
1258   if (NeedsScope(x)) {
1259     PushScope(Scope::Kind::Block, nullptr);
1260   }
1261   return true;
1262 }
1263 
Post(const parser::OpenMPBlockConstruct & x)1264 void OmpVisitor::Post(const parser::OpenMPBlockConstruct &x) {
1265   if (NeedsScope(x)) {
1266     PopScope();
1267   }
1268 }
1269 
1270 // Walk the parse tree and resolve names to symbols.
1271 class ResolveNamesVisitor : public virtual ScopeHandler,
1272                             public ModuleVisitor,
1273                             public SubprogramVisitor,
1274                             public ConstructVisitor,
1275                             public OmpVisitor,
1276                             public AccVisitor {
1277 public:
1278   using AccVisitor::Post;
1279   using AccVisitor::Pre;
1280   using ArraySpecVisitor::Post;
1281   using ConstructVisitor::Post;
1282   using ConstructVisitor::Pre;
1283   using DeclarationVisitor::Post;
1284   using DeclarationVisitor::Pre;
1285   using ImplicitRulesVisitor::Post;
1286   using ImplicitRulesVisitor::Pre;
1287   using InterfaceVisitor::Post;
1288   using InterfaceVisitor::Pre;
1289   using ModuleVisitor::Post;
1290   using ModuleVisitor::Pre;
1291   using OmpVisitor::Post;
1292   using OmpVisitor::Pre;
1293   using ScopeHandler::Post;
1294   using ScopeHandler::Pre;
1295   using SubprogramVisitor::Post;
1296   using SubprogramVisitor::Pre;
1297 
ResolveNamesVisitor(SemanticsContext & context,ImplicitRulesMap & rules)1298   ResolveNamesVisitor(SemanticsContext &context, ImplicitRulesMap &rules)
1299       : BaseVisitor{context, *this, rules} {
1300     PushScope(context.globalScope());
1301   }
1302 
1303   // Default action for a parse tree node is to visit children.
Pre(const T &)1304   template <typename T> bool Pre(const T &) { return true; }
Post(const T &)1305   template <typename T> void Post(const T &) {}
1306 
1307   bool Pre(const parser::SpecificationPart &);
1308   void Post(const parser::Program &);
1309   bool Pre(const parser::ImplicitStmt &);
1310   void Post(const parser::PointerObject &);
1311   void Post(const parser::AllocateObject &);
1312   bool Pre(const parser::PointerAssignmentStmt &);
1313   void Post(const parser::Designator &);
1314   template <typename A, typename B>
Post(const parser::LoopBounds<A,B> & x)1315   void Post(const parser::LoopBounds<A, B> &x) {
1316     ResolveName(*parser::Unwrap<parser::Name>(x.name));
1317   }
1318   void Post(const parser::ProcComponentRef &);
1319   bool Pre(const parser::FunctionReference &);
1320   bool Pre(const parser::CallStmt &);
1321   bool Pre(const parser::ImportStmt &);
1322   void Post(const parser::TypeGuardStmt &);
1323   bool Pre(const parser::StmtFunctionStmt &);
1324   bool Pre(const parser::DefinedOpName &);
1325   bool Pre(const parser::ProgramUnit &);
1326   void Post(const parser::AssignStmt &);
1327   void Post(const parser::AssignedGotoStmt &);
1328 
1329   // These nodes should never be reached: they are handled in ProgramUnit
Pre(const parser::MainProgram &)1330   bool Pre(const parser::MainProgram &) {
1331     llvm_unreachable("This node is handled in ProgramUnit");
1332   }
Pre(const parser::FunctionSubprogram &)1333   bool Pre(const parser::FunctionSubprogram &) {
1334     llvm_unreachable("This node is handled in ProgramUnit");
1335   }
Pre(const parser::SubroutineSubprogram &)1336   bool Pre(const parser::SubroutineSubprogram &) {
1337     llvm_unreachable("This node is handled in ProgramUnit");
1338   }
Pre(const parser::SeparateModuleSubprogram &)1339   bool Pre(const parser::SeparateModuleSubprogram &) {
1340     llvm_unreachable("This node is handled in ProgramUnit");
1341   }
Pre(const parser::Module &)1342   bool Pre(const parser::Module &) {
1343     llvm_unreachable("This node is handled in ProgramUnit");
1344   }
Pre(const parser::Submodule &)1345   bool Pre(const parser::Submodule &) {
1346     llvm_unreachable("This node is handled in ProgramUnit");
1347   }
Pre(const parser::BlockData &)1348   bool Pre(const parser::BlockData &) {
1349     llvm_unreachable("This node is handled in ProgramUnit");
1350   }
1351 
1352   void NoteExecutablePartCall(Symbol::Flag, const parser::Call &);
1353 
1354   friend void ResolveSpecificationParts(SemanticsContext &, const Symbol &);
1355 
1356 private:
1357   // Kind of procedure we are expecting to see in a ProcedureDesignator
1358   std::optional<Symbol::Flag> expectedProcFlag_;
1359   std::optional<SourceName> prevImportStmt_;
1360 
1361   void PreSpecificationConstruct(const parser::SpecificationConstruct &);
1362   void CreateCommonBlockSymbols(const parser::CommonStmt &);
1363   void CreateGeneric(const parser::GenericSpec &);
1364   void FinishSpecificationPart(const std::list<parser::DeclarationConstruct> &);
1365   void AnalyzeStmtFunctionStmt(const parser::StmtFunctionStmt &);
1366   void CheckImports();
1367   void CheckImport(const SourceName &, const SourceName &);
1368   void HandleCall(Symbol::Flag, const parser::Call &);
1369   void HandleProcedureName(Symbol::Flag, const parser::Name &);
1370   bool CheckImplicitNoneExternal(const SourceName &, const Symbol &);
1371   bool SetProcFlag(const parser::Name &, Symbol &, Symbol::Flag);
1372   void ResolveSpecificationParts(ProgramTree &);
1373   void AddSubpNames(ProgramTree &);
1374   bool BeginScopeForNode(const ProgramTree &);
1375   void FinishSpecificationParts(const ProgramTree &);
1376   void FinishDerivedTypeInstantiation(Scope &);
1377   void ResolveExecutionParts(const ProgramTree &);
1378 };
1379 
1380 // ImplicitRules implementation
1381 
isImplicitNoneType() const1382 bool ImplicitRules::isImplicitNoneType() const {
1383   if (isImplicitNoneType_) {
1384     return true;
1385   } else if (map_.empty() && inheritFromParent_) {
1386     return parent_->isImplicitNoneType();
1387   } else {
1388     return false; // default if not specified
1389   }
1390 }
1391 
isImplicitNoneExternal() const1392 bool ImplicitRules::isImplicitNoneExternal() const {
1393   if (isImplicitNoneExternal_) {
1394     return true;
1395   } else if (inheritFromParent_) {
1396     return parent_->isImplicitNoneExternal();
1397   } else {
1398     return false; // default if not specified
1399   }
1400 }
1401 
GetType(SourceName name) const1402 const DeclTypeSpec *ImplicitRules::GetType(SourceName name) const {
1403   char ch{name.begin()[0]};
1404   if (isImplicitNoneType_) {
1405     return nullptr;
1406   } else if (auto it{map_.find(ch)}; it != map_.end()) {
1407     return &*it->second;
1408   } else if (inheritFromParent_) {
1409     return parent_->GetType(name);
1410   } else if (ch >= 'i' && ch <= 'n') {
1411     return &context_.MakeNumericType(TypeCategory::Integer);
1412   } else if (ch >= 'a' && ch <= 'z') {
1413     return &context_.MakeNumericType(TypeCategory::Real);
1414   } else {
1415     return nullptr;
1416   }
1417 }
1418 
SetTypeMapping(const DeclTypeSpec & type,parser::Location fromLetter,parser::Location toLetter)1419 void ImplicitRules::SetTypeMapping(const DeclTypeSpec &type,
1420     parser::Location fromLetter, parser::Location toLetter) {
1421   for (char ch = *fromLetter; ch; ch = ImplicitRules::Incr(ch)) {
1422     auto res{map_.emplace(ch, type)};
1423     if (!res.second) {
1424       context_.Say(parser::CharBlock{fromLetter},
1425           "More than one implicit type specified for '%c'"_err_en_US, ch);
1426     }
1427     if (ch == *toLetter) {
1428       break;
1429     }
1430   }
1431 }
1432 
1433 // Return the next char after ch in a way that works for ASCII or EBCDIC.
1434 // Return '\0' for the char after 'z'.
Incr(char ch)1435 char ImplicitRules::Incr(char ch) {
1436   switch (ch) {
1437   case 'i':
1438     return 'j';
1439   case 'r':
1440     return 's';
1441   case 'z':
1442     return '\0';
1443   default:
1444     return ch + 1;
1445   }
1446 }
1447 
operator <<(llvm::raw_ostream & o,const ImplicitRules & implicitRules)1448 llvm::raw_ostream &operator<<(
1449     llvm::raw_ostream &o, const ImplicitRules &implicitRules) {
1450   o << "ImplicitRules:\n";
1451   for (char ch = 'a'; ch; ch = ImplicitRules::Incr(ch)) {
1452     ShowImplicitRule(o, implicitRules, ch);
1453   }
1454   ShowImplicitRule(o, implicitRules, '_');
1455   ShowImplicitRule(o, implicitRules, '$');
1456   ShowImplicitRule(o, implicitRules, '@');
1457   return o;
1458 }
ShowImplicitRule(llvm::raw_ostream & o,const ImplicitRules & implicitRules,char ch)1459 void ShowImplicitRule(
1460     llvm::raw_ostream &o, const ImplicitRules &implicitRules, char ch) {
1461   auto it{implicitRules.map_.find(ch)};
1462   if (it != implicitRules.map_.end()) {
1463     o << "  " << ch << ": " << *it->second << '\n';
1464   }
1465 }
1466 
Walk(const T & x)1467 template <typename T> void BaseVisitor::Walk(const T &x) {
1468   parser::Walk(x, *this_);
1469 }
1470 
MakePlaceholder(const parser::Name & name,MiscDetails::Kind kind)1471 void BaseVisitor::MakePlaceholder(
1472     const parser::Name &name, MiscDetails::Kind kind) {
1473   if (!name.symbol) {
1474     name.symbol = &context_->globalScope().MakeSymbol(
1475         name.source, Attrs{}, MiscDetails{kind});
1476   }
1477 }
1478 
1479 // AttrsVisitor implementation
1480 
BeginAttrs()1481 bool AttrsVisitor::BeginAttrs() {
1482   CHECK(!attrs_);
1483   attrs_ = std::make_optional<Attrs>();
1484   return true;
1485 }
GetAttrs()1486 Attrs AttrsVisitor::GetAttrs() {
1487   CHECK(attrs_);
1488   return *attrs_;
1489 }
EndAttrs()1490 Attrs AttrsVisitor::EndAttrs() {
1491   Attrs result{GetAttrs()};
1492   attrs_.reset();
1493   passName_ = std::nullopt;
1494   bindName_.reset();
1495   return result;
1496 }
1497 
SetPassNameOn(Symbol & symbol)1498 bool AttrsVisitor::SetPassNameOn(Symbol &symbol) {
1499   if (!passName_) {
1500     return false;
1501   }
1502   std::visit(common::visitors{
1503                  [&](ProcEntityDetails &x) { x.set_passName(*passName_); },
1504                  [&](ProcBindingDetails &x) { x.set_passName(*passName_); },
1505                  [](auto &) { common::die("unexpected pass name"); },
1506              },
1507       symbol.details());
1508   return true;
1509 }
1510 
SetBindNameOn(Symbol & symbol)1511 bool AttrsVisitor::SetBindNameOn(Symbol &symbol) {
1512   if (!bindName_) {
1513     return false;
1514   }
1515   std::visit(
1516       common::visitors{
1517           [&](EntityDetails &x) { x.set_bindName(std::move(bindName_)); },
1518           [&](ObjectEntityDetails &x) { x.set_bindName(std::move(bindName_)); },
1519           [&](ProcEntityDetails &x) { x.set_bindName(std::move(bindName_)); },
1520           [&](SubprogramDetails &x) { x.set_bindName(std::move(bindName_)); },
1521           [&](CommonBlockDetails &x) { x.set_bindName(std::move(bindName_)); },
1522           [](auto &) { common::die("unexpected bind name"); },
1523       },
1524       symbol.details());
1525   return true;
1526 }
1527 
Post(const parser::LanguageBindingSpec & x)1528 void AttrsVisitor::Post(const parser::LanguageBindingSpec &x) {
1529   CHECK(attrs_);
1530   if (CheckAndSet(Attr::BIND_C)) {
1531     if (x.v) {
1532       bindName_ = EvaluateExpr(*x.v);
1533     }
1534   }
1535 }
Pre(const parser::IntentSpec & x)1536 bool AttrsVisitor::Pre(const parser::IntentSpec &x) {
1537   CHECK(attrs_);
1538   CheckAndSet(IntentSpecToAttr(x));
1539   return false;
1540 }
Pre(const parser::Pass & x)1541 bool AttrsVisitor::Pre(const parser::Pass &x) {
1542   if (CheckAndSet(Attr::PASS)) {
1543     if (x.v) {
1544       passName_ = x.v->source;
1545       MakePlaceholder(*x.v, MiscDetails::Kind::PassName);
1546     }
1547   }
1548   return false;
1549 }
1550 
1551 // C730, C743, C755, C778, C1543 say no attribute or prefix repetitions
IsDuplicateAttr(Attr attrName)1552 bool AttrsVisitor::IsDuplicateAttr(Attr attrName) {
1553   if (attrs_->test(attrName)) {
1554     Say(currStmtSource().value(),
1555         "Attribute '%s' cannot be used more than once"_en_US,
1556         AttrToString(attrName));
1557     return true;
1558   }
1559   return false;
1560 }
1561 
1562 // See if attrName violates a constraint cause by a conflict.  attr1 and attr2
1563 // name attributes that cannot be used on the same declaration
HaveAttrConflict(Attr attrName,Attr attr1,Attr attr2)1564 bool AttrsVisitor::HaveAttrConflict(Attr attrName, Attr attr1, Attr attr2) {
1565   if ((attrName == attr1 && attrs_->test(attr2)) ||
1566       (attrName == attr2 && attrs_->test(attr1))) {
1567     Say(currStmtSource().value(),
1568         "Attributes '%s' and '%s' conflict with each other"_err_en_US,
1569         AttrToString(attr1), AttrToString(attr2));
1570     return true;
1571   }
1572   return false;
1573 }
1574 // C759, C1543
IsConflictingAttr(Attr attrName)1575 bool AttrsVisitor::IsConflictingAttr(Attr attrName) {
1576   return HaveAttrConflict(attrName, Attr::INTENT_IN, Attr::INTENT_INOUT) ||
1577       HaveAttrConflict(attrName, Attr::INTENT_IN, Attr::INTENT_OUT) ||
1578       HaveAttrConflict(attrName, Attr::INTENT_INOUT, Attr::INTENT_OUT) ||
1579       HaveAttrConflict(attrName, Attr::PASS, Attr::NOPASS) || // C781
1580       HaveAttrConflict(attrName, Attr::PURE, Attr::IMPURE) ||
1581       HaveAttrConflict(attrName, Attr::PUBLIC, Attr::PRIVATE) ||
1582       HaveAttrConflict(attrName, Attr::RECURSIVE, Attr::NON_RECURSIVE);
1583 }
CheckAndSet(Attr attrName)1584 bool AttrsVisitor::CheckAndSet(Attr attrName) {
1585   CHECK(attrs_);
1586   if (IsConflictingAttr(attrName) || IsDuplicateAttr(attrName)) {
1587     return false;
1588   }
1589   attrs_->set(attrName);
1590   return true;
1591 }
1592 
1593 // DeclTypeSpecVisitor implementation
1594 
GetDeclTypeSpec()1595 const DeclTypeSpec *DeclTypeSpecVisitor::GetDeclTypeSpec() {
1596   return state_.declTypeSpec;
1597 }
1598 
BeginDeclTypeSpec()1599 void DeclTypeSpecVisitor::BeginDeclTypeSpec() {
1600   CHECK(!state_.expectDeclTypeSpec);
1601   CHECK(!state_.declTypeSpec);
1602   state_.expectDeclTypeSpec = true;
1603 }
EndDeclTypeSpec()1604 void DeclTypeSpecVisitor::EndDeclTypeSpec() {
1605   CHECK(state_.expectDeclTypeSpec);
1606   state_ = {};
1607 }
1608 
SetDeclTypeSpecCategory(DeclTypeSpec::Category category)1609 void DeclTypeSpecVisitor::SetDeclTypeSpecCategory(
1610     DeclTypeSpec::Category category) {
1611   CHECK(state_.expectDeclTypeSpec);
1612   state_.derived.category = category;
1613 }
1614 
Pre(const parser::TypeGuardStmt &)1615 bool DeclTypeSpecVisitor::Pre(const parser::TypeGuardStmt &) {
1616   BeginDeclTypeSpec();
1617   return true;
1618 }
Post(const parser::TypeGuardStmt &)1619 void DeclTypeSpecVisitor::Post(const parser::TypeGuardStmt &) {
1620   EndDeclTypeSpec();
1621 }
1622 
Post(const parser::TypeSpec & typeSpec)1623 void DeclTypeSpecVisitor::Post(const parser::TypeSpec &typeSpec) {
1624   // Record the resolved DeclTypeSpec in the parse tree for use by
1625   // expression semantics if the DeclTypeSpec is a valid TypeSpec.
1626   // The grammar ensures that it's an intrinsic or derived type spec,
1627   // not TYPE(*) or CLASS(*) or CLASS(T).
1628   if (const DeclTypeSpec * spec{state_.declTypeSpec}) {
1629     switch (spec->category()) {
1630     case DeclTypeSpec::Numeric:
1631     case DeclTypeSpec::Logical:
1632     case DeclTypeSpec::Character:
1633       typeSpec.declTypeSpec = spec;
1634       break;
1635     case DeclTypeSpec::TypeDerived:
1636       if (const DerivedTypeSpec * derived{spec->AsDerived()}) {
1637         CheckForAbstractType(derived->typeSymbol()); // C703
1638         typeSpec.declTypeSpec = spec;
1639       }
1640       break;
1641     default:
1642       CRASH_NO_CASE;
1643     }
1644   }
1645 }
1646 
Post(const parser::IntrinsicTypeSpec::DoublePrecision &)1647 void DeclTypeSpecVisitor::Post(
1648     const parser::IntrinsicTypeSpec::DoublePrecision &) {
1649   MakeNumericType(TypeCategory::Real, context().doublePrecisionKind());
1650 }
Post(const parser::IntrinsicTypeSpec::DoubleComplex &)1651 void DeclTypeSpecVisitor::Post(
1652     const parser::IntrinsicTypeSpec::DoubleComplex &) {
1653   MakeNumericType(TypeCategory::Complex, context().doublePrecisionKind());
1654 }
MakeNumericType(TypeCategory category,int kind)1655 void DeclTypeSpecVisitor::MakeNumericType(TypeCategory category, int kind) {
1656   SetDeclTypeSpec(context().MakeNumericType(category, kind));
1657 }
1658 
CheckForAbstractType(const Symbol & typeSymbol)1659 void DeclTypeSpecVisitor::CheckForAbstractType(const Symbol &typeSymbol) {
1660   if (typeSymbol.attrs().test(Attr::ABSTRACT)) {
1661     Say("ABSTRACT derived type may not be used here"_err_en_US);
1662   }
1663 }
1664 
Post(const parser::DeclarationTypeSpec::ClassStar &)1665 void DeclTypeSpecVisitor::Post(const parser::DeclarationTypeSpec::ClassStar &) {
1666   SetDeclTypeSpec(context().globalScope().MakeClassStarType());
1667 }
Post(const parser::DeclarationTypeSpec::TypeStar &)1668 void DeclTypeSpecVisitor::Post(const parser::DeclarationTypeSpec::TypeStar &) {
1669   SetDeclTypeSpec(context().globalScope().MakeTypeStarType());
1670 }
1671 
1672 // Check that we're expecting to see a DeclTypeSpec (and haven't seen one yet)
1673 // and save it in state_.declTypeSpec.
SetDeclTypeSpec(const DeclTypeSpec & declTypeSpec)1674 void DeclTypeSpecVisitor::SetDeclTypeSpec(const DeclTypeSpec &declTypeSpec) {
1675   CHECK(state_.expectDeclTypeSpec);
1676   CHECK(!state_.declTypeSpec);
1677   state_.declTypeSpec = &declTypeSpec;
1678 }
1679 
GetKindParamExpr(TypeCategory category,const std::optional<parser::KindSelector> & kind)1680 KindExpr DeclTypeSpecVisitor::GetKindParamExpr(
1681     TypeCategory category, const std::optional<parser::KindSelector> &kind) {
1682   return AnalyzeKindSelector(context(), category, kind);
1683 }
1684 
1685 // MessageHandler implementation
1686 
Say(MessageFixedText && msg)1687 Message &MessageHandler::Say(MessageFixedText &&msg) {
1688   return context_->Say(currStmtSource().value(), std::move(msg));
1689 }
Say(MessageFormattedText && msg)1690 Message &MessageHandler::Say(MessageFormattedText &&msg) {
1691   return context_->Say(currStmtSource().value(), std::move(msg));
1692 }
Say(const SourceName & name,MessageFixedText && msg)1693 Message &MessageHandler::Say(const SourceName &name, MessageFixedText &&msg) {
1694   return Say(name, std::move(msg), name);
1695 }
1696 
1697 // ImplicitRulesVisitor implementation
1698 
Post(const parser::ParameterStmt &)1699 void ImplicitRulesVisitor::Post(const parser::ParameterStmt &) {
1700   prevParameterStmt_ = currStmtSource();
1701 }
1702 
Pre(const parser::ImplicitStmt & x)1703 bool ImplicitRulesVisitor::Pre(const parser::ImplicitStmt &x) {
1704   bool result{
1705       std::visit(common::visitors{
1706                      [&](const std::list<ImplicitNoneNameSpec> &y) {
1707                        return HandleImplicitNone(y);
1708                      },
1709                      [&](const std::list<parser::ImplicitSpec> &) {
1710                        if (prevImplicitNoneType_) {
1711                          Say("IMPLICIT statement after IMPLICIT NONE or "
1712                              "IMPLICIT NONE(TYPE) statement"_err_en_US);
1713                          return false;
1714                        }
1715                        implicitRules_->set_isImplicitNoneType(false);
1716                        return true;
1717                      },
1718                  },
1719           x.u)};
1720   prevImplicit_ = currStmtSource();
1721   return result;
1722 }
1723 
Pre(const parser::LetterSpec & x)1724 bool ImplicitRulesVisitor::Pre(const parser::LetterSpec &x) {
1725   auto loLoc{std::get<parser::Location>(x.t)};
1726   auto hiLoc{loLoc};
1727   if (auto hiLocOpt{std::get<std::optional<parser::Location>>(x.t)}) {
1728     hiLoc = *hiLocOpt;
1729     if (*hiLoc < *loLoc) {
1730       Say(hiLoc, "'%s' does not follow '%s' alphabetically"_err_en_US,
1731           std::string(hiLoc, 1), std::string(loLoc, 1));
1732       return false;
1733     }
1734   }
1735   implicitRules_->SetTypeMapping(*GetDeclTypeSpec(), loLoc, hiLoc);
1736   return false;
1737 }
1738 
Pre(const parser::ImplicitSpec &)1739 bool ImplicitRulesVisitor::Pre(const parser::ImplicitSpec &) {
1740   BeginDeclTypeSpec();
1741   set_allowForwardReferenceToDerivedType(true);
1742   return true;
1743 }
1744 
Post(const parser::ImplicitSpec &)1745 void ImplicitRulesVisitor::Post(const parser::ImplicitSpec &) {
1746   EndDeclTypeSpec();
1747 }
1748 
SetScope(const Scope & scope)1749 void ImplicitRulesVisitor::SetScope(const Scope &scope) {
1750   implicitRules_ = &DEREF(implicitRulesMap_).at(&scope);
1751   prevImplicit_ = std::nullopt;
1752   prevImplicitNone_ = std::nullopt;
1753   prevImplicitNoneType_ = std::nullopt;
1754   prevParameterStmt_ = std::nullopt;
1755 }
BeginScope(const Scope & scope)1756 void ImplicitRulesVisitor::BeginScope(const Scope &scope) {
1757   // find or create implicit rules for this scope
1758   DEREF(implicitRulesMap_).try_emplace(&scope, context(), implicitRules_);
1759   SetScope(scope);
1760 }
1761 
1762 // TODO: for all of these errors, reference previous statement too
HandleImplicitNone(const std::list<ImplicitNoneNameSpec> & nameSpecs)1763 bool ImplicitRulesVisitor::HandleImplicitNone(
1764     const std::list<ImplicitNoneNameSpec> &nameSpecs) {
1765   if (prevImplicitNone_) {
1766     Say("More than one IMPLICIT NONE statement"_err_en_US);
1767     Say(*prevImplicitNone_, "Previous IMPLICIT NONE statement"_en_US);
1768     return false;
1769   }
1770   if (prevParameterStmt_) {
1771     Say("IMPLICIT NONE statement after PARAMETER statement"_err_en_US);
1772     return false;
1773   }
1774   prevImplicitNone_ = currStmtSource();
1775   bool implicitNoneTypeNever{
1776       context().IsEnabled(common::LanguageFeature::ImplicitNoneTypeNever)};
1777   if (nameSpecs.empty()) {
1778     if (!implicitNoneTypeNever) {
1779       prevImplicitNoneType_ = currStmtSource();
1780       implicitRules_->set_isImplicitNoneType(true);
1781       if (prevImplicit_) {
1782         Say("IMPLICIT NONE statement after IMPLICIT statement"_err_en_US);
1783         return false;
1784       }
1785     }
1786   } else {
1787     int sawType{0};
1788     int sawExternal{0};
1789     for (const auto noneSpec : nameSpecs) {
1790       switch (noneSpec) {
1791       case ImplicitNoneNameSpec::External:
1792         implicitRules_->set_isImplicitNoneExternal(true);
1793         ++sawExternal;
1794         break;
1795       case ImplicitNoneNameSpec::Type:
1796         if (!implicitNoneTypeNever) {
1797           prevImplicitNoneType_ = currStmtSource();
1798           implicitRules_->set_isImplicitNoneType(true);
1799           if (prevImplicit_) {
1800             Say("IMPLICIT NONE(TYPE) after IMPLICIT statement"_err_en_US);
1801             return false;
1802           }
1803           ++sawType;
1804         }
1805         break;
1806       }
1807     }
1808     if (sawType > 1) {
1809       Say("TYPE specified more than once in IMPLICIT NONE statement"_err_en_US);
1810       return false;
1811     }
1812     if (sawExternal > 1) {
1813       Say("EXTERNAL specified more than once in IMPLICIT NONE statement"_err_en_US);
1814       return false;
1815     }
1816   }
1817   return true;
1818 }
1819 
1820 // ArraySpecVisitor implementation
1821 
Post(const parser::ArraySpec & x)1822 void ArraySpecVisitor::Post(const parser::ArraySpec &x) {
1823   CHECK(arraySpec_.empty());
1824   arraySpec_ = AnalyzeArraySpec(context(), x);
1825 }
Post(const parser::ComponentArraySpec & x)1826 void ArraySpecVisitor::Post(const parser::ComponentArraySpec &x) {
1827   CHECK(arraySpec_.empty());
1828   arraySpec_ = AnalyzeArraySpec(context(), x);
1829 }
Post(const parser::CoarraySpec & x)1830 void ArraySpecVisitor::Post(const parser::CoarraySpec &x) {
1831   CHECK(coarraySpec_.empty());
1832   coarraySpec_ = AnalyzeCoarraySpec(context(), x);
1833 }
1834 
arraySpec()1835 const ArraySpec &ArraySpecVisitor::arraySpec() {
1836   return !arraySpec_.empty() ? arraySpec_ : attrArraySpec_;
1837 }
coarraySpec()1838 const ArraySpec &ArraySpecVisitor::coarraySpec() {
1839   return !coarraySpec_.empty() ? coarraySpec_ : attrCoarraySpec_;
1840 }
BeginArraySpec()1841 void ArraySpecVisitor::BeginArraySpec() {
1842   CHECK(arraySpec_.empty());
1843   CHECK(coarraySpec_.empty());
1844   CHECK(attrArraySpec_.empty());
1845   CHECK(attrCoarraySpec_.empty());
1846 }
EndArraySpec()1847 void ArraySpecVisitor::EndArraySpec() {
1848   CHECK(arraySpec_.empty());
1849   CHECK(coarraySpec_.empty());
1850   attrArraySpec_.clear();
1851   attrCoarraySpec_.clear();
1852 }
PostAttrSpec()1853 void ArraySpecVisitor::PostAttrSpec() {
1854   // Save dimension/codimension from attrs so we can process array/coarray-spec
1855   // on the entity-decl
1856   if (!arraySpec_.empty()) {
1857     if (attrArraySpec_.empty()) {
1858       attrArraySpec_ = arraySpec_;
1859       arraySpec_.clear();
1860     } else {
1861       Say(currStmtSource().value(),
1862           "Attribute 'DIMENSION' cannot be used more than once"_err_en_US);
1863     }
1864   }
1865   if (!coarraySpec_.empty()) {
1866     if (attrCoarraySpec_.empty()) {
1867       attrCoarraySpec_ = coarraySpec_;
1868       coarraySpec_.clear();
1869     } else {
1870       Say(currStmtSource().value(),
1871           "Attribute 'CODIMENSION' cannot be used more than once"_err_en_US);
1872     }
1873   }
1874 }
1875 
1876 // ScopeHandler implementation
1877 
SayAlreadyDeclared(const parser::Name & name,Symbol & prev)1878 void ScopeHandler::SayAlreadyDeclared(const parser::Name &name, Symbol &prev) {
1879   SayAlreadyDeclared(name.source, prev);
1880 }
SayAlreadyDeclared(const SourceName & name,Symbol & prev)1881 void ScopeHandler::SayAlreadyDeclared(const SourceName &name, Symbol &prev) {
1882   if (context().HasError(prev)) {
1883     // don't report another error about prev
1884   } else {
1885     if (const auto *details{prev.detailsIf<UseDetails>()}) {
1886       Say(name, "'%s' is already declared in this scoping unit"_err_en_US)
1887           .Attach(details->location(),
1888               "It is use-associated with '%s' in module '%s'"_err_en_US,
1889               details->symbol().name(), GetUsedModule(*details).name());
1890     } else {
1891       SayAlreadyDeclared(name, prev.name());
1892     }
1893     context().SetError(prev);
1894   }
1895 }
SayAlreadyDeclared(const SourceName & name1,const SourceName & name2)1896 void ScopeHandler::SayAlreadyDeclared(
1897     const SourceName &name1, const SourceName &name2) {
1898   if (name1.begin() < name2.begin()) {
1899     SayAlreadyDeclared(name2, name1);
1900   } else {
1901     Say(name1, "'%s' is already declared in this scoping unit"_err_en_US)
1902         .Attach(name2, "Previous declaration of '%s'"_en_US, name2);
1903   }
1904 }
1905 
SayWithReason(const parser::Name & name,Symbol & symbol,MessageFixedText && msg1,MessageFixedText && msg2)1906 void ScopeHandler::SayWithReason(const parser::Name &name, Symbol &symbol,
1907     MessageFixedText &&msg1, MessageFixedText &&msg2) {
1908   Say2(name, std::move(msg1), symbol, std::move(msg2));
1909   context().SetError(symbol, msg1.isFatal());
1910 }
1911 
SayWithDecl(const parser::Name & name,Symbol & symbol,MessageFixedText && msg)1912 void ScopeHandler::SayWithDecl(
1913     const parser::Name &name, Symbol &symbol, MessageFixedText &&msg) {
1914   SayWithReason(name, symbol, std::move(msg),
1915       symbol.test(Symbol::Flag::Implicit) ? "Implicit declaration of '%s'"_en_US
1916                                           : "Declaration of '%s'"_en_US);
1917 }
1918 
SayLocalMustBeVariable(const parser::Name & name,Symbol & symbol)1919 void ScopeHandler::SayLocalMustBeVariable(
1920     const parser::Name &name, Symbol &symbol) {
1921   SayWithDecl(name, symbol,
1922       "The name '%s' must be a variable to appear"
1923       " in a locality-spec"_err_en_US);
1924 }
1925 
SayDerivedType(const SourceName & name,MessageFixedText && msg,const Scope & type)1926 void ScopeHandler::SayDerivedType(
1927     const SourceName &name, MessageFixedText &&msg, const Scope &type) {
1928   const Symbol &typeSymbol{DEREF(type.GetSymbol())};
1929   Say(name, std::move(msg), name, typeSymbol.name())
1930       .Attach(typeSymbol.name(), "Declaration of derived type '%s'"_en_US,
1931           typeSymbol.name());
1932 }
Say2(const SourceName & name1,MessageFixedText && msg1,const SourceName & name2,MessageFixedText && msg2)1933 void ScopeHandler::Say2(const SourceName &name1, MessageFixedText &&msg1,
1934     const SourceName &name2, MessageFixedText &&msg2) {
1935   Say(name1, std::move(msg1)).Attach(name2, std::move(msg2), name2);
1936 }
Say2(const SourceName & name,MessageFixedText && msg1,Symbol & symbol,MessageFixedText && msg2)1937 void ScopeHandler::Say2(const SourceName &name, MessageFixedText &&msg1,
1938     Symbol &symbol, MessageFixedText &&msg2) {
1939   Say2(name, std::move(msg1), symbol.name(), std::move(msg2));
1940   context().SetError(symbol, msg1.isFatal());
1941 }
Say2(const parser::Name & name,MessageFixedText && msg1,Symbol & symbol,MessageFixedText && msg2)1942 void ScopeHandler::Say2(const parser::Name &name, MessageFixedText &&msg1,
1943     Symbol &symbol, MessageFixedText &&msg2) {
1944   Say2(name.source, std::move(msg1), symbol.name(), std::move(msg2));
1945   context().SetError(symbol, msg1.isFatal());
1946 }
1947 
1948 // T may be `Scope` or `const Scope`
GetInclusiveScope(T & scope)1949 template <typename T> static T &GetInclusiveScope(T &scope) {
1950   for (T *s{&scope}; !s->IsGlobal(); s = &s->parent()) {
1951     if (s->kind() != Scope::Kind::Block && !s->IsDerivedType() &&
1952         !s->IsStmtFunction()) {
1953       return *s;
1954     }
1955   }
1956   return scope;
1957 }
1958 
InclusiveScope()1959 Scope &ScopeHandler::InclusiveScope() { return GetInclusiveScope(currScope()); }
1960 
GetHostProcedure()1961 Scope *ScopeHandler::GetHostProcedure() {
1962   Scope &parent{InclusiveScope().parent()};
1963   return parent.kind() == Scope::Kind::Subprogram ? &parent : nullptr;
1964 }
1965 
NonDerivedTypeScope()1966 Scope &ScopeHandler::NonDerivedTypeScope() {
1967   return currScope_->IsDerivedType() ? currScope_->parent() : *currScope_;
1968 }
1969 
PushScope(Scope::Kind kind,Symbol * symbol)1970 void ScopeHandler::PushScope(Scope::Kind kind, Symbol *symbol) {
1971   PushScope(currScope().MakeScope(kind, symbol));
1972 }
PushScope(Scope & scope)1973 void ScopeHandler::PushScope(Scope &scope) {
1974   currScope_ = &scope;
1975   auto kind{currScope_->kind()};
1976   if (kind != Scope::Kind::Block) {
1977     BeginScope(scope);
1978   }
1979   // The name of a module or submodule cannot be "used" in its scope,
1980   // as we read 19.3.1(2), so we allow the name to be used as a local
1981   // identifier in the module or submodule too.  Same with programs
1982   // (14.1(3)) and BLOCK DATA.
1983   if (!currScope_->IsDerivedType() && kind != Scope::Kind::Module &&
1984       kind != Scope::Kind::MainProgram && kind != Scope::Kind::BlockData) {
1985     if (auto *symbol{scope.symbol()}) {
1986       // Create a dummy symbol so we can't create another one with the same
1987       // name. It might already be there if we previously pushed the scope.
1988       if (!FindInScope(scope, symbol->name())) {
1989         auto &newSymbol{MakeSymbol(symbol->name())};
1990         if (kind == Scope::Kind::Subprogram) {
1991           // Allow for recursive references.  If this symbol is a function
1992           // without an explicit RESULT(), this new symbol will be discarded
1993           // and replaced with an object of the same name.
1994           newSymbol.set_details(HostAssocDetails{*symbol});
1995         } else {
1996           newSymbol.set_details(MiscDetails{MiscDetails::Kind::ScopeName});
1997         }
1998       }
1999     }
2000   }
2001 }
PopScope()2002 void ScopeHandler::PopScope() {
2003   // Entities that are not yet classified as objects or procedures are now
2004   // assumed to be objects.
2005   // TODO: Statement functions
2006   for (auto &pair : currScope()) {
2007     ConvertToObjectEntity(*pair.second);
2008   }
2009   SetScope(currScope_->parent());
2010 }
SetScope(Scope & scope)2011 void ScopeHandler::SetScope(Scope &scope) {
2012   currScope_ = &scope;
2013   ImplicitRulesVisitor::SetScope(InclusiveScope());
2014 }
2015 
FindSymbol(const parser::Name & name)2016 Symbol *ScopeHandler::FindSymbol(const parser::Name &name) {
2017   return FindSymbol(currScope(), name);
2018 }
FindSymbol(const Scope & scope,const parser::Name & name)2019 Symbol *ScopeHandler::FindSymbol(const Scope &scope, const parser::Name &name) {
2020   if (scope.IsDerivedType()) {
2021     if (Symbol * symbol{scope.FindComponent(name.source)}) {
2022       if (!symbol->has<ProcBindingDetails>() &&
2023           !symbol->test(Symbol::Flag::ParentComp)) {
2024         return Resolve(name, symbol);
2025       }
2026     }
2027     return FindSymbol(scope.parent(), name);
2028   } else {
2029     // In EQUIVALENCE statements only resolve names in the local scope, see
2030     // 19.5.1.4, paragraph 2, item (10)
2031     return Resolve(name,
2032         inEquivalenceStmt_ ? FindInScope(scope, name)
2033                            : scope.FindSymbol(name.source));
2034   }
2035 }
2036 
MakeSymbol(Scope & scope,const SourceName & name,Attrs attrs)2037 Symbol &ScopeHandler::MakeSymbol(
2038     Scope &scope, const SourceName &name, Attrs attrs) {
2039   if (Symbol * symbol{FindInScope(scope, name)}) {
2040     symbol->attrs() |= attrs;
2041     return *symbol;
2042   } else {
2043     const auto pair{scope.try_emplace(name, attrs, UnknownDetails{})};
2044     CHECK(pair.second); // name was not found, so must be able to add
2045     return *pair.first->second;
2046   }
2047 }
MakeSymbol(const SourceName & name,Attrs attrs)2048 Symbol &ScopeHandler::MakeSymbol(const SourceName &name, Attrs attrs) {
2049   return MakeSymbol(currScope(), name, attrs);
2050 }
MakeSymbol(const parser::Name & name,Attrs attrs)2051 Symbol &ScopeHandler::MakeSymbol(const parser::Name &name, Attrs attrs) {
2052   return Resolve(name, MakeSymbol(name.source, attrs));
2053 }
MakeHostAssocSymbol(const parser::Name & name,const Symbol & hostSymbol)2054 Symbol &ScopeHandler::MakeHostAssocSymbol(
2055     const parser::Name &name, const Symbol &hostSymbol) {
2056   Symbol &symbol{*NonDerivedTypeScope()
2057                       .try_emplace(name.source, HostAssocDetails{hostSymbol})
2058                       .first->second};
2059   name.symbol = &symbol;
2060   symbol.attrs() = hostSymbol.attrs(); // TODO: except PRIVATE, PUBLIC?
2061   symbol.flags() = hostSymbol.flags();
2062   return symbol;
2063 }
CopySymbol(const SourceName & name,const Symbol & symbol)2064 Symbol &ScopeHandler::CopySymbol(const SourceName &name, const Symbol &symbol) {
2065   CHECK(!FindInScope(name));
2066   return MakeSymbol(currScope(), name, symbol.attrs());
2067 }
2068 
2069 // Look for name only in scope, not in enclosing scopes.
FindInScope(const Scope & scope,const parser::Name & name)2070 Symbol *ScopeHandler::FindInScope(
2071     const Scope &scope, const parser::Name &name) {
2072   return Resolve(name, FindInScope(scope, name.source));
2073 }
FindInScope(const Scope & scope,const SourceName & name)2074 Symbol *ScopeHandler::FindInScope(const Scope &scope, const SourceName &name) {
2075   // all variants of names, e.g. "operator(.ne.)" for "operator(/=)"
2076   for (const std::string &n : GetAllNames(context(), name)) {
2077     auto it{scope.find(SourceName{n})};
2078     if (it != scope.end()) {
2079       return &*it->second;
2080     }
2081   }
2082   return nullptr;
2083 }
2084 
2085 // Find a component or type parameter by name in a derived type or its parents.
FindInTypeOrParents(const Scope & scope,const parser::Name & name)2086 Symbol *ScopeHandler::FindInTypeOrParents(
2087     const Scope &scope, const parser::Name &name) {
2088   return Resolve(name, scope.FindComponent(name.source));
2089 }
FindInTypeOrParents(const parser::Name & name)2090 Symbol *ScopeHandler::FindInTypeOrParents(const parser::Name &name) {
2091   return FindInTypeOrParents(currScope(), name);
2092 }
2093 
EraseSymbol(const parser::Name & name)2094 void ScopeHandler::EraseSymbol(const parser::Name &name) {
2095   currScope().erase(name.source);
2096   name.symbol = nullptr;
2097 }
2098 
NeedsType(const Symbol & symbol)2099 static bool NeedsType(const Symbol &symbol) {
2100   return !symbol.GetType() &&
2101       std::visit(common::visitors{
2102                      [](const EntityDetails &) { return true; },
2103                      [](const ObjectEntityDetails &) { return true; },
2104                      [](const AssocEntityDetails &) { return true; },
2105                      [&](const ProcEntityDetails &p) {
2106                        return symbol.test(Symbol::Flag::Function) &&
2107                            !symbol.attrs().test(Attr::INTRINSIC) &&
2108                            !p.interface().type() && !p.interface().symbol();
2109                      },
2110                      [](const auto &) { return false; },
2111                  },
2112           symbol.details());
2113 }
2114 
ApplyImplicitRules(Symbol & symbol)2115 void ScopeHandler::ApplyImplicitRules(Symbol &symbol) {
2116   if (NeedsType(symbol)) {
2117     const Scope *scope{&symbol.owner()};
2118     if (scope->IsGlobal()) {
2119       scope = &currScope();
2120     }
2121     if (const DeclTypeSpec *
2122         type{GetImplicitType(symbol, GetInclusiveScope(*scope))}) {
2123       symbol.set(Symbol::Flag::Implicit);
2124       symbol.SetType(*type);
2125       return;
2126     }
2127     if (symbol.has<ProcEntityDetails>() &&
2128         !symbol.attrs().test(Attr::EXTERNAL)) {
2129       std::optional<Symbol::Flag> functionOrSubroutineFlag;
2130       if (symbol.test(Symbol::Flag::Function)) {
2131         functionOrSubroutineFlag = Symbol::Flag::Function;
2132       } else if (symbol.test(Symbol::Flag::Subroutine)) {
2133         functionOrSubroutineFlag = Symbol::Flag::Subroutine;
2134       }
2135       if (IsIntrinsic(symbol.name(), functionOrSubroutineFlag)) {
2136         // type will be determined in expression semantics
2137         symbol.attrs().set(Attr::INTRINSIC);
2138         return;
2139       }
2140     }
2141     if (!context().HasError(symbol)) {
2142       Say(symbol.name(), "No explicit type declared for '%s'"_err_en_US);
2143       context().SetError(symbol);
2144     }
2145   }
2146 }
2147 
GetImplicitType(Symbol & symbol,const Scope & scope)2148 const DeclTypeSpec *ScopeHandler::GetImplicitType(
2149     Symbol &symbol, const Scope &scope) {
2150   const auto *type{implicitRulesMap_->at(&scope).GetType(symbol.name())};
2151   if (type) {
2152     if (const DerivedTypeSpec * derived{type->AsDerived()}) {
2153       // Resolve any forward-referenced derived type; a quick no-op else.
2154       auto &instantiatable{*const_cast<DerivedTypeSpec *>(derived)};
2155       instantiatable.Instantiate(currScope(), context());
2156     }
2157   }
2158   return type;
2159 }
2160 
2161 // Convert symbol to be a ObjectEntity or return false if it can't be.
ConvertToObjectEntity(Symbol & symbol)2162 bool ScopeHandler::ConvertToObjectEntity(Symbol &symbol) {
2163   if (symbol.has<ObjectEntityDetails>()) {
2164     // nothing to do
2165   } else if (symbol.has<UnknownDetails>()) {
2166     symbol.set_details(ObjectEntityDetails{});
2167   } else if (auto *details{symbol.detailsIf<EntityDetails>()}) {
2168     symbol.set_details(ObjectEntityDetails{std::move(*details)});
2169   } else if (auto *useDetails{symbol.detailsIf<UseDetails>()}) {
2170     return useDetails->symbol().has<ObjectEntityDetails>();
2171   } else {
2172     return false;
2173   }
2174   return true;
2175 }
2176 // Convert symbol to be a ProcEntity or return false if it can't be.
ConvertToProcEntity(Symbol & symbol)2177 bool ScopeHandler::ConvertToProcEntity(Symbol &symbol) {
2178   if (symbol.has<ProcEntityDetails>()) {
2179     // nothing to do
2180   } else if (symbol.has<UnknownDetails>()) {
2181     symbol.set_details(ProcEntityDetails{});
2182   } else if (auto *details{symbol.detailsIf<EntityDetails>()}) {
2183     symbol.set_details(ProcEntityDetails{std::move(*details)});
2184     if (symbol.GetType() && !symbol.test(Symbol::Flag::Implicit)) {
2185       CHECK(!symbol.test(Symbol::Flag::Subroutine));
2186       symbol.set(Symbol::Flag::Function);
2187     }
2188   } else {
2189     return false;
2190   }
2191   return true;
2192 }
2193 
MakeNumericType(TypeCategory category,const std::optional<parser::KindSelector> & kind)2194 const DeclTypeSpec &ScopeHandler::MakeNumericType(
2195     TypeCategory category, const std::optional<parser::KindSelector> &kind) {
2196   KindExpr value{GetKindParamExpr(category, kind)};
2197   if (auto known{evaluate::ToInt64(value)}) {
2198     return context().MakeNumericType(category, static_cast<int>(*known));
2199   } else {
2200     return currScope_->MakeNumericType(category, std::move(value));
2201   }
2202 }
2203 
MakeLogicalType(const std::optional<parser::KindSelector> & kind)2204 const DeclTypeSpec &ScopeHandler::MakeLogicalType(
2205     const std::optional<parser::KindSelector> &kind) {
2206   KindExpr value{GetKindParamExpr(TypeCategory::Logical, kind)};
2207   if (auto known{evaluate::ToInt64(value)}) {
2208     return context().MakeLogicalType(static_cast<int>(*known));
2209   } else {
2210     return currScope_->MakeLogicalType(std::move(value));
2211   }
2212 }
2213 
NotePossibleBadForwardRef(const parser::Name & name)2214 void ScopeHandler::NotePossibleBadForwardRef(const parser::Name &name) {
2215   if (inSpecificationPart_ && name.symbol) {
2216     auto kind{currScope().kind()};
2217     if ((kind == Scope::Kind::Subprogram && !currScope().IsStmtFunction()) ||
2218         kind == Scope::Kind::Block) {
2219       bool isHostAssociated{&name.symbol->owner() == &currScope()
2220               ? name.symbol->has<HostAssocDetails>()
2221               : name.symbol->owner().Contains(currScope())};
2222       if (isHostAssociated) {
2223         specPartForwardRefs_.insert(name.source);
2224       }
2225     }
2226   }
2227 }
2228 
HadForwardRef(const Symbol & symbol) const2229 std::optional<SourceName> ScopeHandler::HadForwardRef(
2230     const Symbol &symbol) const {
2231   auto iter{specPartForwardRefs_.find(symbol.name())};
2232   if (iter != specPartForwardRefs_.end()) {
2233     return *iter;
2234   }
2235   return std::nullopt;
2236 }
2237 
CheckPossibleBadForwardRef(const Symbol & symbol)2238 bool ScopeHandler::CheckPossibleBadForwardRef(const Symbol &symbol) {
2239   if (!context().HasError(symbol)) {
2240     if (auto fwdRef{HadForwardRef(symbol)}) {
2241       const Symbol *outer{symbol.owner().FindSymbol(symbol.name())};
2242       if (outer && symbol.has<UseDetails>() &&
2243           &symbol.GetUltimate() == &outer->GetUltimate()) {
2244         // e.g. IMPORT of host's USE association
2245         return false;
2246       }
2247       Say(*fwdRef,
2248           "Forward reference to '%s' is not allowed in the same specification part"_err_en_US,
2249           *fwdRef)
2250           .Attach(symbol.name(), "Later declaration of '%s'"_en_US, *fwdRef);
2251       context().SetError(symbol);
2252       return true;
2253     }
2254   }
2255   return false;
2256 }
2257 
MakeExternal(Symbol & symbol)2258 void ScopeHandler::MakeExternal(Symbol &symbol) {
2259   if (!symbol.attrs().test(Attr::EXTERNAL)) {
2260     symbol.attrs().set(Attr::EXTERNAL);
2261     if (symbol.attrs().test(Attr::INTRINSIC)) { // C840
2262       Say(symbol.name(),
2263           "Symbol '%s' cannot have both EXTERNAL and INTRINSIC attributes"_err_en_US,
2264           symbol.name());
2265     }
2266   }
2267 }
2268 
2269 // ModuleVisitor implementation
2270 
Pre(const parser::Only & x)2271 bool ModuleVisitor::Pre(const parser::Only &x) {
2272   std::visit(common::visitors{
2273                  [&](const Indirection<parser::GenericSpec> &generic) {
2274                    AddUse(GenericSpecInfo{generic.value()});
2275                  },
2276                  [&](const parser::Name &name) {
2277                    Resolve(name, AddUse(name.source, name.source).use);
2278                  },
2279                  [&](const parser::Rename &rename) { Walk(rename); },
2280              },
2281       x.u);
2282   return false;
2283 }
2284 
Pre(const parser::Rename::Names & x)2285 bool ModuleVisitor::Pre(const parser::Rename::Names &x) {
2286   const auto &localName{std::get<0>(x.t)};
2287   const auto &useName{std::get<1>(x.t)};
2288   SymbolRename rename{AddUse(localName.source, useName.source)};
2289   Resolve(useName, rename.use);
2290   Resolve(localName, rename.local);
2291   return false;
2292 }
Pre(const parser::Rename::Operators & x)2293 bool ModuleVisitor::Pre(const parser::Rename::Operators &x) {
2294   const parser::DefinedOpName &local{std::get<0>(x.t)};
2295   const parser::DefinedOpName &use{std::get<1>(x.t)};
2296   GenericSpecInfo localInfo{local};
2297   GenericSpecInfo useInfo{use};
2298   if (IsIntrinsicOperator(context(), local.v.source)) {
2299     Say(local.v,
2300         "Intrinsic operator '%s' may not be used as a defined operator"_err_en_US);
2301   } else if (IsLogicalConstant(context(), local.v.source)) {
2302     Say(local.v,
2303         "Logical constant '%s' may not be used as a defined operator"_err_en_US);
2304   } else {
2305     SymbolRename rename{AddUse(localInfo.symbolName(), useInfo.symbolName())};
2306     useInfo.Resolve(rename.use);
2307     localInfo.Resolve(rename.local);
2308   }
2309   return false;
2310 }
2311 
2312 // Set useModuleScope_ to the Scope of the module being used.
Pre(const parser::UseStmt & x)2313 bool ModuleVisitor::Pre(const parser::UseStmt &x) {
2314   useModuleScope_ = FindModule(x.moduleName);
2315   if (!useModuleScope_) {
2316     return false;
2317   }
2318   // use the name from this source file
2319   useModuleScope_->symbol()->ReplaceName(x.moduleName.source);
2320   return true;
2321 }
2322 
Post(const parser::UseStmt & x)2323 void ModuleVisitor::Post(const parser::UseStmt &x) {
2324   if (const auto *list{std::get_if<std::list<parser::Rename>>(&x.u)}) {
2325     // Not a use-only: collect the names that were used in renames,
2326     // then add a use for each public name that was not renamed.
2327     std::set<SourceName> useNames;
2328     for (const auto &rename : *list) {
2329       std::visit(common::visitors{
2330                      [&](const parser::Rename::Names &names) {
2331                        useNames.insert(std::get<1>(names.t).source);
2332                      },
2333                      [&](const parser::Rename::Operators &ops) {
2334                        useNames.insert(std::get<1>(ops.t).v.source);
2335                      },
2336                  },
2337           rename.u);
2338     }
2339     for (const auto &[name, symbol] : *useModuleScope_) {
2340       if (symbol->attrs().test(Attr::PUBLIC) &&
2341           (!symbol->attrs().test(Attr::INTRINSIC) ||
2342               symbol->has<UseDetails>()) &&
2343           !symbol->has<MiscDetails>() && useNames.count(name) == 0) {
2344         SourceName location{x.moduleName.source};
2345         if (auto *localSymbol{FindInScope(name)}) {
2346           DoAddUse(location, localSymbol->name(), *localSymbol, *symbol);
2347         } else {
2348           DoAddUse(location, location, CopySymbol(name, *symbol), *symbol);
2349         }
2350       }
2351     }
2352   }
2353   useModuleScope_ = nullptr;
2354 }
2355 
AddUse(const SourceName & localName,const SourceName & useName)2356 ModuleVisitor::SymbolRename ModuleVisitor::AddUse(
2357     const SourceName &localName, const SourceName &useName) {
2358   return AddUse(localName, useName, FindInScope(*useModuleScope_, useName));
2359 }
2360 
AddUse(const SourceName & localName,const SourceName & useName,Symbol * useSymbol)2361 ModuleVisitor::SymbolRename ModuleVisitor::AddUse(
2362     const SourceName &localName, const SourceName &useName, Symbol *useSymbol) {
2363   if (!useModuleScope_) {
2364     return {}; // error occurred finding module
2365   }
2366   if (!useSymbol) {
2367     Say(useName, "'%s' not found in module '%s'"_err_en_US, MakeOpName(useName),
2368         useModuleScope_->GetName().value());
2369     return {};
2370   }
2371   if (useSymbol->attrs().test(Attr::PRIVATE) &&
2372       !FindModuleFileContaining(currScope())) {
2373     // Privacy is not enforced in module files so that generic interfaces
2374     // can be resolved to private specific procedures in specification
2375     // expressions.
2376     Say(useName, "'%s' is PRIVATE in '%s'"_err_en_US, MakeOpName(useName),
2377         useModuleScope_->GetName().value());
2378     return {};
2379   }
2380   auto &localSymbol{MakeSymbol(localName)};
2381   DoAddUse(useName, localName, localSymbol, *useSymbol);
2382   return {&localSymbol, useSymbol};
2383 }
2384 
2385 // symbol must be either a Use or a Generic formed by merging two uses.
2386 // Convert it to a UseError with this additional location.
ConvertToUseError(Symbol & symbol,const SourceName & location,const Scope & module)2387 static void ConvertToUseError(
2388     Symbol &symbol, const SourceName &location, const Scope &module) {
2389   const auto *useDetails{symbol.detailsIf<UseDetails>()};
2390   if (!useDetails) {
2391     auto &genericDetails{symbol.get<GenericDetails>()};
2392     useDetails = &genericDetails.uses().at(0)->get<UseDetails>();
2393   }
2394   symbol.set_details(
2395       UseErrorDetails{*useDetails}.add_occurrence(location, module));
2396 }
2397 
DoAddUse(const SourceName & location,const SourceName & localName,Symbol & localSymbol,const Symbol & useSymbol)2398 void ModuleVisitor::DoAddUse(const SourceName &location,
2399     const SourceName &localName, Symbol &localSymbol, const Symbol &useSymbol) {
2400   localSymbol.attrs() = useSymbol.attrs() & ~Attrs{Attr::PUBLIC, Attr::PRIVATE};
2401   localSymbol.flags() = useSymbol.flags();
2402   const Symbol &useUltimate{useSymbol.GetUltimate()};
2403   if (auto *useDetails{localSymbol.detailsIf<UseDetails>()}) {
2404     const Symbol &localUltimate{localSymbol.GetUltimate()};
2405     if (localUltimate == useUltimate) {
2406       // use-associating the same symbol again -- ok
2407     } else if (localUltimate.has<GenericDetails>() &&
2408         useUltimate.has<GenericDetails>()) {
2409       // use-associating generics with the same names: merge them into a
2410       // new generic in this scope
2411       auto generic1{localUltimate.get<GenericDetails>()};
2412       AddGenericUse(generic1, localName, useUltimate);
2413       generic1.AddUse(localSymbol);
2414       // useSymbol has specific g and so does generic1
2415       auto &generic2{useUltimate.get<GenericDetails>()};
2416       if (generic1.derivedType() && generic2.derivedType() &&
2417           generic1.derivedType() != generic2.derivedType()) {
2418         Say(location,
2419             "Generic interface '%s' has ambiguous derived types"
2420             " from modules '%s' and '%s'"_err_en_US,
2421             localSymbol.name(), GetUsedModule(*useDetails).name(),
2422             useUltimate.owner().GetName().value());
2423         context().SetError(localSymbol);
2424       } else {
2425         generic1.CopyFrom(generic2);
2426       }
2427       EraseSymbol(localSymbol);
2428       MakeSymbol(localSymbol.name(), localSymbol.attrs(), std::move(generic1));
2429     } else {
2430       ConvertToUseError(localSymbol, location, *useModuleScope_);
2431     }
2432   } else if (auto *genericDetails{localSymbol.detailsIf<GenericDetails>()}) {
2433     if (const auto *useDetails{useUltimate.detailsIf<GenericDetails>()}) {
2434       AddGenericUse(*genericDetails, localName, useUltimate);
2435       if (genericDetails->derivedType() && useDetails->derivedType() &&
2436           genericDetails->derivedType() != useDetails->derivedType()) {
2437         Say(location,
2438             "Generic interface '%s' has ambiguous derived types"
2439             " from modules '%s' and '%s'"_err_en_US,
2440             localSymbol.name(),
2441             genericDetails->derivedType()->owner().GetName().value(),
2442             useDetails->derivedType()->owner().GetName().value());
2443       } else {
2444         genericDetails->CopyFrom(*useDetails);
2445       }
2446     } else {
2447       ConvertToUseError(localSymbol, location, *useModuleScope_);
2448     }
2449   } else if (auto *details{localSymbol.detailsIf<UseErrorDetails>()}) {
2450     details->add_occurrence(location, *useModuleScope_);
2451   } else if (!localSymbol.has<UnknownDetails>()) {
2452     Say(location,
2453         "Cannot use-associate '%s'; it is already declared in this scope"_err_en_US,
2454         localName)
2455         .Attach(localSymbol.name(), "Previous declaration of '%s'"_en_US,
2456             localName);
2457   } else {
2458     localSymbol.set_details(UseDetails{localName, useSymbol});
2459   }
2460 }
2461 
AddUse(const GenericSpecInfo & info)2462 void ModuleVisitor::AddUse(const GenericSpecInfo &info) {
2463   if (useModuleScope_) {
2464     const auto &name{info.symbolName()};
2465     auto rename{AddUse(name, name, FindInScope(*useModuleScope_, name))};
2466     info.Resolve(rename.use);
2467   }
2468 }
2469 
2470 // Create a UseDetails symbol for this USE and add it to generic
AddGenericUse(GenericDetails & generic,const SourceName & name,const Symbol & useSymbol)2471 void ModuleVisitor::AddGenericUse(
2472     GenericDetails &generic, const SourceName &name, const Symbol &useSymbol) {
2473   generic.AddUse(currScope().MakeSymbol(name, {}, UseDetails{name, useSymbol}));
2474 }
2475 
BeginSubmodule(const parser::Name & name,const parser::ParentIdentifier & parentId)2476 bool ModuleVisitor::BeginSubmodule(
2477     const parser::Name &name, const parser::ParentIdentifier &parentId) {
2478   auto &ancestorName{std::get<parser::Name>(parentId.t)};
2479   auto &parentName{std::get<std::optional<parser::Name>>(parentId.t)};
2480   Scope *ancestor{FindModule(ancestorName)};
2481   if (!ancestor) {
2482     return false;
2483   }
2484   Scope *parentScope{parentName ? FindModule(*parentName, ancestor) : ancestor};
2485   if (!parentScope) {
2486     return false;
2487   }
2488   PushScope(*parentScope); // submodule is hosted in parent
2489   BeginModule(name, true);
2490   if (!ancestor->AddSubmodule(name.source, currScope())) {
2491     Say(name, "Module '%s' already has a submodule named '%s'"_err_en_US,
2492         ancestorName.source, name.source);
2493   }
2494   return true;
2495 }
2496 
BeginModule(const parser::Name & name,bool isSubmodule)2497 void ModuleVisitor::BeginModule(const parser::Name &name, bool isSubmodule) {
2498   auto &symbol{MakeSymbol(name, ModuleDetails{isSubmodule})};
2499   auto &details{symbol.get<ModuleDetails>()};
2500   PushScope(Scope::Kind::Module, &symbol);
2501   details.set_scope(&currScope());
2502   defaultAccess_ = Attr::PUBLIC;
2503   prevAccessStmt_ = std::nullopt;
2504 }
2505 
2506 // Find a module or submodule by name and return its scope.
2507 // If ancestor is present, look for a submodule of that ancestor module.
2508 // May have to read a .mod file to find it.
2509 // If an error occurs, report it and return nullptr.
FindModule(const parser::Name & name,Scope * ancestor)2510 Scope *ModuleVisitor::FindModule(const parser::Name &name, Scope *ancestor) {
2511   ModFileReader reader{context()};
2512   Scope *scope{reader.Read(name.source, ancestor)};
2513   if (!scope) {
2514     return nullptr;
2515   }
2516   if (scope->kind() != Scope::Kind::Module) {
2517     Say(name, "'%s' is not a module"_err_en_US);
2518     return nullptr;
2519   }
2520   if (DoesScopeContain(scope, currScope())) { // 14.2.2(1)
2521     Say(name, "Module '%s' cannot USE itself"_err_en_US);
2522   }
2523   Resolve(name, scope->symbol());
2524   return scope;
2525 }
2526 
ApplyDefaultAccess()2527 void ModuleVisitor::ApplyDefaultAccess() {
2528   for (auto &pair : currScope()) {
2529     Symbol &symbol = *pair.second;
2530     if (!symbol.attrs().HasAny({Attr::PUBLIC, Attr::PRIVATE})) {
2531       symbol.attrs().set(defaultAccess_);
2532     }
2533   }
2534 }
2535 
2536 // InterfaceVistor implementation
2537 
Pre(const parser::InterfaceStmt & x)2538 bool InterfaceVisitor::Pre(const parser::InterfaceStmt &x) {
2539   bool isAbstract{std::holds_alternative<parser::Abstract>(x.u)};
2540   genericInfo_.emplace(/*isInterface*/ true, isAbstract);
2541   return BeginAttrs();
2542 }
2543 
Post(const parser::InterfaceStmt &)2544 void InterfaceVisitor::Post(const parser::InterfaceStmt &) { EndAttrs(); }
2545 
Post(const parser::EndInterfaceStmt &)2546 void InterfaceVisitor::Post(const parser::EndInterfaceStmt &) {
2547   genericInfo_.pop();
2548 }
2549 
2550 // Create a symbol in genericSymbol_ for this GenericSpec.
Pre(const parser::GenericSpec & x)2551 bool InterfaceVisitor::Pre(const parser::GenericSpec &x) {
2552   if (auto *symbol{FindInScope(GenericSpecInfo{x}.symbolName())}) {
2553     SetGenericSymbol(*symbol);
2554   }
2555   return false;
2556 }
2557 
Pre(const parser::ProcedureStmt & x)2558 bool InterfaceVisitor::Pre(const parser::ProcedureStmt &x) {
2559   if (!isGeneric()) {
2560     Say("A PROCEDURE statement is only allowed in a generic interface block"_err_en_US);
2561     return false;
2562   }
2563   auto kind{std::get<parser::ProcedureStmt::Kind>(x.t)};
2564   const auto &names{std::get<std::list<parser::Name>>(x.t)};
2565   AddSpecificProcs(names, kind);
2566   return false;
2567 }
2568 
Pre(const parser::GenericStmt &)2569 bool InterfaceVisitor::Pre(const parser::GenericStmt &) {
2570   genericInfo_.emplace(/*isInterface*/ false);
2571   return true;
2572 }
Post(const parser::GenericStmt & x)2573 void InterfaceVisitor::Post(const parser::GenericStmt &x) {
2574   if (auto &accessSpec{std::get<std::optional<parser::AccessSpec>>(x.t)}) {
2575     GetGenericInfo().symbol->attrs().set(AccessSpecToAttr(*accessSpec));
2576   }
2577   const auto &names{std::get<std::list<parser::Name>>(x.t)};
2578   AddSpecificProcs(names, ProcedureKind::Procedure);
2579   genericInfo_.pop();
2580 }
2581 
inInterfaceBlock() const2582 bool InterfaceVisitor::inInterfaceBlock() const {
2583   return !genericInfo_.empty() && GetGenericInfo().isInterface;
2584 }
isGeneric() const2585 bool InterfaceVisitor::isGeneric() const {
2586   return !genericInfo_.empty() && GetGenericInfo().symbol;
2587 }
isAbstract() const2588 bool InterfaceVisitor::isAbstract() const {
2589   return !genericInfo_.empty() && GetGenericInfo().isAbstract;
2590 }
GetGenericDetails()2591 GenericDetails &InterfaceVisitor::GetGenericDetails() {
2592   return GetGenericInfo().symbol->get<GenericDetails>();
2593 }
2594 
AddSpecificProcs(const std::list<parser::Name> & names,ProcedureKind kind)2595 void InterfaceVisitor::AddSpecificProcs(
2596     const std::list<parser::Name> &names, ProcedureKind kind) {
2597   for (const auto &name : names) {
2598     specificProcs_.emplace(
2599         GetGenericInfo().symbol, std::make_pair(&name, kind));
2600   }
2601 }
2602 
2603 // By now we should have seen all specific procedures referenced by name in
2604 // this generic interface. Resolve those names to symbols.
ResolveSpecificsInGeneric(Symbol & generic)2605 void InterfaceVisitor::ResolveSpecificsInGeneric(Symbol &generic) {
2606   auto &details{generic.get<GenericDetails>()};
2607   SymbolSet symbolsSeen;
2608   for (const Symbol &symbol : details.specificProcs()) {
2609     symbolsSeen.insert(symbol);
2610   }
2611   auto range{specificProcs_.equal_range(&generic)};
2612   for (auto it{range.first}; it != range.second; ++it) {
2613     auto *name{it->second.first};
2614     auto kind{it->second.second};
2615     const auto *symbol{FindSymbol(*name)};
2616     if (!symbol) {
2617       Say(*name, "Procedure '%s' not found"_err_en_US);
2618       continue;
2619     }
2620     if (symbol == &generic) {
2621       if (auto *specific{generic.get<GenericDetails>().specific()}) {
2622         symbol = specific;
2623       }
2624     }
2625     const Symbol &ultimate{symbol->GetUltimate()};
2626     if (!ultimate.has<SubprogramDetails>() &&
2627         !ultimate.has<SubprogramNameDetails>()) {
2628       Say(*name, "'%s' is not a subprogram"_err_en_US);
2629       continue;
2630     }
2631     if (kind == ProcedureKind::ModuleProcedure) {
2632       if (const auto *nd{ultimate.detailsIf<SubprogramNameDetails>()}) {
2633         if (nd->kind() != SubprogramKind::Module) {
2634           Say(*name, "'%s' is not a module procedure"_err_en_US);
2635         }
2636       } else {
2637         // USE-associated procedure
2638         const auto *sd{ultimate.detailsIf<SubprogramDetails>()};
2639         CHECK(sd);
2640         if (ultimate.owner().kind() != Scope::Kind::Module ||
2641             sd->isInterface()) {
2642           Say(*name, "'%s' is not a module procedure"_err_en_US);
2643         }
2644       }
2645     }
2646     if (!symbolsSeen.insert(ultimate).second) {
2647       if (symbol == &ultimate) {
2648         Say(name->source,
2649             "Procedure '%s' is already specified in generic '%s'"_err_en_US,
2650             name->source, MakeOpName(generic.name()));
2651       } else {
2652         Say(name->source,
2653             "Procedure '%s' from module '%s' is already specified in generic '%s'"_err_en_US,
2654             ultimate.name(), ultimate.owner().GetName().value(),
2655             MakeOpName(generic.name()));
2656       }
2657       continue;
2658     }
2659     details.AddSpecificProc(*symbol, name->source);
2660   }
2661   specificProcs_.erase(range.first, range.second);
2662 }
2663 
2664 // Check that the specific procedures are all functions or all subroutines.
2665 // If there is a derived type with the same name they must be functions.
2666 // Set the corresponding flag on generic.
CheckGenericProcedures(Symbol & generic)2667 void InterfaceVisitor::CheckGenericProcedures(Symbol &generic) {
2668   ResolveSpecificsInGeneric(generic);
2669   auto &details{generic.get<GenericDetails>()};
2670   if (auto *proc{details.CheckSpecific()}) {
2671     auto msg{
2672         "'%s' may not be the name of both a generic interface and a"
2673         " procedure unless it is a specific procedure of the generic"_err_en_US};
2674     if (proc->name().begin() > generic.name().begin()) {
2675       Say(proc->name(), std::move(msg));
2676     } else {
2677       Say(generic.name(), std::move(msg));
2678     }
2679   }
2680   auto &specifics{details.specificProcs()};
2681   if (specifics.empty()) {
2682     if (details.derivedType()) {
2683       generic.set(Symbol::Flag::Function);
2684     }
2685     return;
2686   }
2687   const Symbol &firstSpecific{specifics.front()};
2688   bool isFunction{firstSpecific.test(Symbol::Flag::Function)};
2689   for (const Symbol &specific : specifics) {
2690     if (isFunction != specific.test(Symbol::Flag::Function)) { // C1514
2691       auto &msg{Say(generic.name(),
2692           "Generic interface '%s' has both a function and a subroutine"_err_en_US)};
2693       if (isFunction) {
2694         msg.Attach(firstSpecific.name(), "Function declaration"_en_US);
2695         msg.Attach(specific.name(), "Subroutine declaration"_en_US);
2696       } else {
2697         msg.Attach(firstSpecific.name(), "Subroutine declaration"_en_US);
2698         msg.Attach(specific.name(), "Function declaration"_en_US);
2699       }
2700     }
2701   }
2702   if (!isFunction && details.derivedType()) {
2703     SayDerivedType(generic.name(),
2704         "Generic interface '%s' may only contain functions due to derived type"
2705         " with same name"_err_en_US,
2706         *details.derivedType()->scope());
2707   }
2708   generic.set(isFunction ? Symbol::Flag::Function : Symbol::Flag::Subroutine);
2709 }
2710 
2711 // SubprogramVisitor implementation
2712 
2713 // Return false if it is actually an assignment statement.
HandleStmtFunction(const parser::StmtFunctionStmt & x)2714 bool SubprogramVisitor::HandleStmtFunction(const parser::StmtFunctionStmt &x) {
2715   const auto &name{std::get<parser::Name>(x.t)};
2716   const DeclTypeSpec *resultType{nullptr};
2717   // Look up name: provides return type or tells us if it's an array
2718   if (auto *symbol{FindSymbol(name)}) {
2719     auto *details{symbol->detailsIf<EntityDetails>()};
2720     if (!details) {
2721       badStmtFuncFound_ = true;
2722       return false;
2723     }
2724     // TODO: check that attrs are compatible with stmt func
2725     resultType = details->type();
2726     symbol->details() = UnknownDetails{}; // will be replaced below
2727   }
2728   if (badStmtFuncFound_) {
2729     Say(name, "'%s' has not been declared as an array"_err_en_US);
2730     return true;
2731   }
2732   auto &symbol{PushSubprogramScope(name, Symbol::Flag::Function)};
2733   symbol.set(Symbol::Flag::StmtFunction);
2734   EraseSymbol(symbol); // removes symbol added by PushSubprogramScope
2735   auto &details{symbol.get<SubprogramDetails>()};
2736   for (const auto &dummyName : std::get<std::list<parser::Name>>(x.t)) {
2737     ObjectEntityDetails dummyDetails{true};
2738     if (auto *dummySymbol{FindInScope(currScope().parent(), dummyName)}) {
2739       if (auto *d{dummySymbol->detailsIf<EntityDetails>()}) {
2740         if (d->type()) {
2741           dummyDetails.set_type(*d->type());
2742         }
2743       }
2744     }
2745     Symbol &dummy{MakeSymbol(dummyName, std::move(dummyDetails))};
2746     ApplyImplicitRules(dummy);
2747     details.add_dummyArg(dummy);
2748   }
2749   ObjectEntityDetails resultDetails;
2750   if (resultType) {
2751     resultDetails.set_type(*resultType);
2752   }
2753   resultDetails.set_funcResult(true);
2754   Symbol &result{MakeSymbol(name, std::move(resultDetails))};
2755   ApplyImplicitRules(result);
2756   details.set_result(result);
2757   const auto &parsedExpr{std::get<parser::Scalar<parser::Expr>>(x.t)};
2758   Walk(parsedExpr);
2759   // The analysis of the expression that constitutes the body of the
2760   // statement function is deferred to FinishSpecificationPart() so that
2761   // all declarations and implicit typing are complete.
2762   PopScope();
2763   return true;
2764 }
2765 
Pre(const parser::Suffix & suffix)2766 bool SubprogramVisitor::Pre(const parser::Suffix &suffix) {
2767   if (suffix.resultName) {
2768     funcInfo_.resultName = &suffix.resultName.value();
2769   }
2770   return true;
2771 }
2772 
Pre(const parser::PrefixSpec & x)2773 bool SubprogramVisitor::Pre(const parser::PrefixSpec &x) {
2774   // Save this to process after UseStmt and ImplicitPart
2775   if (const auto *parsedType{std::get_if<parser::DeclarationTypeSpec>(&x.u)}) {
2776     if (funcInfo_.parsedType) { // C1543
2777       Say(currStmtSource().value(),
2778           "FUNCTION prefix cannot specify the type more than once"_err_en_US);
2779       return false;
2780     } else {
2781       funcInfo_.parsedType = parsedType;
2782       funcInfo_.source = currStmtSource();
2783       return false;
2784     }
2785   } else {
2786     return true;
2787   }
2788 }
2789 
Post(const parser::ImplicitPart &)2790 void SubprogramVisitor::Post(const parser::ImplicitPart &) {
2791   // If the function has a type in the prefix, process it now
2792   if (funcInfo_.parsedType) {
2793     messageHandler().set_currStmtSource(funcInfo_.source);
2794     if (const auto *type{ProcessTypeSpec(*funcInfo_.parsedType, true)}) {
2795       funcInfo_.resultSymbol->SetType(*type);
2796     }
2797   }
2798   funcInfo_ = {};
2799 }
2800 
Pre(const parser::InterfaceBody::Subroutine & x)2801 bool SubprogramVisitor::Pre(const parser::InterfaceBody::Subroutine &x) {
2802   const auto &name{std::get<parser::Name>(
2803       std::get<parser::Statement<parser::SubroutineStmt>>(x.t).statement.t)};
2804   return BeginSubprogram(name, Symbol::Flag::Subroutine);
2805 }
Post(const parser::InterfaceBody::Subroutine &)2806 void SubprogramVisitor::Post(const parser::InterfaceBody::Subroutine &) {
2807   EndSubprogram();
2808 }
Pre(const parser::InterfaceBody::Function & x)2809 bool SubprogramVisitor::Pre(const parser::InterfaceBody::Function &x) {
2810   const auto &name{std::get<parser::Name>(
2811       std::get<parser::Statement<parser::FunctionStmt>>(x.t).statement.t)};
2812   return BeginSubprogram(name, Symbol::Flag::Function);
2813 }
Post(const parser::InterfaceBody::Function &)2814 void SubprogramVisitor::Post(const parser::InterfaceBody::Function &) {
2815   EndSubprogram();
2816 }
2817 
Pre(const parser::SubroutineStmt &)2818 bool SubprogramVisitor::Pre(const parser::SubroutineStmt &) {
2819   return BeginAttrs();
2820 }
Pre(const parser::FunctionStmt &)2821 bool SubprogramVisitor::Pre(const parser::FunctionStmt &) {
2822   return BeginAttrs();
2823 }
Pre(const parser::EntryStmt &)2824 bool SubprogramVisitor::Pre(const parser::EntryStmt &) { return BeginAttrs(); }
2825 
Post(const parser::SubroutineStmt & stmt)2826 void SubprogramVisitor::Post(const parser::SubroutineStmt &stmt) {
2827   const auto &name{std::get<parser::Name>(stmt.t)};
2828   auto &details{PostSubprogramStmt(name)};
2829   for (const auto &dummyArg : std::get<std::list<parser::DummyArg>>(stmt.t)) {
2830     if (const auto *dummyName{std::get_if<parser::Name>(&dummyArg.u)}) {
2831       Symbol &dummy{MakeSymbol(*dummyName, EntityDetails(true))};
2832       details.add_dummyArg(dummy);
2833     } else {
2834       details.add_alternateReturn();
2835     }
2836   }
2837 }
2838 
Post(const parser::FunctionStmt & stmt)2839 void SubprogramVisitor::Post(const parser::FunctionStmt &stmt) {
2840   const auto &name{std::get<parser::Name>(stmt.t)};
2841   auto &details{PostSubprogramStmt(name)};
2842   for (const auto &dummyName : std::get<std::list<parser::Name>>(stmt.t)) {
2843     Symbol &dummy{MakeSymbol(dummyName, EntityDetails(true))};
2844     details.add_dummyArg(dummy);
2845   }
2846   const parser::Name *funcResultName;
2847   if (funcInfo_.resultName && funcInfo_.resultName->source != name.source) {
2848     // Note that RESULT is ignored if it has the same name as the function.
2849     funcResultName = funcInfo_.resultName;
2850   } else {
2851     EraseSymbol(name); // was added by PushSubprogramScope
2852     funcResultName = &name;
2853   }
2854   // add function result to function scope
2855   EntityDetails funcResultDetails;
2856   funcResultDetails.set_funcResult(true);
2857   funcInfo_.resultSymbol =
2858       &MakeSymbol(*funcResultName, std::move(funcResultDetails));
2859   details.set_result(*funcInfo_.resultSymbol);
2860 
2861   // C1560.
2862   if (funcInfo_.resultName && funcInfo_.resultName->source == name.source) {
2863     Say(funcInfo_.resultName->source,
2864         "The function name should not appear in RESULT, references to '%s' "
2865         "inside"
2866         " the function will be considered as references to the result only"_en_US,
2867         name.source);
2868     // RESULT name was ignored above, the only side effect from doing so will be
2869     // the inability to make recursive calls. The related parser::Name is still
2870     // resolved to the created function result symbol because every parser::Name
2871     // should be resolved to avoid internal errors.
2872     Resolve(*funcInfo_.resultName, funcInfo_.resultSymbol);
2873   }
2874   name.symbol = currScope().symbol(); // must not be function result symbol
2875   // Clear the RESULT() name now in case an ENTRY statement in the implicit-part
2876   // has a RESULT() suffix.
2877   funcInfo_.resultName = nullptr;
2878 }
2879 
PostSubprogramStmt(const parser::Name & name)2880 SubprogramDetails &SubprogramVisitor::PostSubprogramStmt(
2881     const parser::Name &name) {
2882   Symbol &symbol{*currScope().symbol()};
2883   CHECK(name.source == symbol.name());
2884   SetBindNameOn(symbol);
2885   symbol.attrs() |= EndAttrs();
2886   if (symbol.attrs().test(Attr::MODULE)) {
2887     symbol.attrs().set(Attr::EXTERNAL, false);
2888   }
2889   return symbol.get<SubprogramDetails>();
2890 }
2891 
Post(const parser::EntryStmt & stmt)2892 void SubprogramVisitor::Post(const parser::EntryStmt &stmt) {
2893   auto attrs{EndAttrs()}; // needs to be called even if early return
2894   Scope &inclusiveScope{InclusiveScope()};
2895   const Symbol *subprogram{inclusiveScope.symbol()};
2896   if (!subprogram) {
2897     CHECK(context().AnyFatalError());
2898     return;
2899   }
2900   const auto &name{std::get<parser::Name>(stmt.t)};
2901   const auto *parentDetails{subprogram->detailsIf<SubprogramDetails>()};
2902   bool inFunction{parentDetails && parentDetails->isFunction()};
2903   const parser::Name *resultName{funcInfo_.resultName};
2904   if (resultName) { // RESULT(result) is present
2905     funcInfo_.resultName = nullptr;
2906     if (!inFunction) {
2907       Say2(resultName->source,
2908           "RESULT(%s) may appear only in a function"_err_en_US,
2909           subprogram->name(), "Containing subprogram"_en_US);
2910     } else if (resultName->source == subprogram->name()) { // C1574
2911       Say2(resultName->source,
2912           "RESULT(%s) may not have the same name as the function"_err_en_US,
2913           subprogram->name(), "Containing function"_en_US);
2914     } else if (const Symbol *
2915         symbol{FindSymbol(inclusiveScope.parent(), *resultName)}) { // C1574
2916       if (const auto *details{symbol->detailsIf<SubprogramDetails>()}) {
2917         if (details->entryScope() == &inclusiveScope) {
2918           Say2(resultName->source,
2919               "RESULT(%s) may not have the same name as an ENTRY in the function"_err_en_US,
2920               symbol->name(), "Conflicting ENTRY"_en_US);
2921         }
2922       }
2923     }
2924     if (Symbol * symbol{FindSymbol(name)}) { // C1570
2925       // When RESULT() appears, ENTRY name can't have been already declared
2926       if (inclusiveScope.Contains(symbol->owner())) {
2927         Say2(name,
2928             "ENTRY name '%s' may not be declared when RESULT() is present"_err_en_US,
2929             *symbol, "Previous declaration of '%s'"_en_US);
2930       }
2931     }
2932     if (resultName->source == name.source) {
2933       // ignore RESULT() hereafter when it's the same name as the ENTRY
2934       resultName = nullptr;
2935     }
2936   }
2937   SubprogramDetails entryDetails;
2938   entryDetails.set_entryScope(inclusiveScope);
2939   if (inFunction) {
2940     // Create the entity to hold the function result, if necessary.
2941     Symbol *resultSymbol{nullptr};
2942     auto &effectiveResultName{*(resultName ? resultName : &name)};
2943     resultSymbol = FindInScope(currScope(), effectiveResultName);
2944     if (resultSymbol) { // C1574
2945       std::visit(
2946           common::visitors{[](EntityDetails &x) { x.set_funcResult(true); },
2947               [](ObjectEntityDetails &x) { x.set_funcResult(true); },
2948               [](ProcEntityDetails &x) { x.set_funcResult(true); },
2949               [&](const auto &) {
2950                 Say2(effectiveResultName.source,
2951                     "'%s' was previously declared as an item that may not be used as a function result"_err_en_US,
2952                     resultSymbol->name(), "Previous declaration of '%s'"_en_US);
2953               }},
2954           resultSymbol->details());
2955     } else if (inExecutionPart_) {
2956       ObjectEntityDetails entity;
2957       entity.set_funcResult(true);
2958       resultSymbol = &MakeSymbol(effectiveResultName, std::move(entity));
2959       ApplyImplicitRules(*resultSymbol);
2960     } else {
2961       EntityDetails entity;
2962       entity.set_funcResult(true);
2963       resultSymbol = &MakeSymbol(effectiveResultName, std::move(entity));
2964     }
2965     if (!resultName) {
2966       name.symbol = nullptr; // symbol will be used for entry point below
2967     }
2968     entryDetails.set_result(*resultSymbol);
2969   }
2970 
2971   for (const auto &dummyArg : std::get<std::list<parser::DummyArg>>(stmt.t)) {
2972     if (const auto *dummyName{std::get_if<parser::Name>(&dummyArg.u)}) {
2973       Symbol *dummy{FindSymbol(*dummyName)};
2974       if (dummy) {
2975         std::visit(
2976             common::visitors{[](EntityDetails &x) { x.set_isDummy(); },
2977                 [](ObjectEntityDetails &x) { x.set_isDummy(); },
2978                 [](ProcEntityDetails &x) { x.set_isDummy(); },
2979                 [&](const auto &) {
2980                   Say2(dummyName->source,
2981                       "ENTRY dummy argument '%s' is previously declared as an item that may not be used as a dummy argument"_err_en_US,
2982                       dummy->name(), "Previous declaration of '%s'"_en_US);
2983                 }},
2984             dummy->details());
2985       } else {
2986         dummy = &MakeSymbol(*dummyName, EntityDetails(true));
2987       }
2988       entryDetails.add_dummyArg(*dummy);
2989     } else {
2990       if (inFunction) { // C1573
2991         Say(name,
2992             "ENTRY in a function may not have an alternate return dummy argument"_err_en_US);
2993         break;
2994       }
2995       entryDetails.add_alternateReturn();
2996     }
2997   }
2998 
2999   Symbol::Flag subpFlag{
3000       inFunction ? Symbol::Flag::Function : Symbol::Flag::Subroutine};
3001   CheckExtantExternal(name, subpFlag);
3002   Scope &outer{inclusiveScope.parent()}; // global or module scope
3003   if (Symbol * extant{FindSymbol(outer, name)}) {
3004     if (extant->has<ProcEntityDetails>()) {
3005       if (!extant->test(subpFlag)) {
3006         Say2(name,
3007             subpFlag == Symbol::Flag::Function
3008                 ? "'%s' was previously called as a subroutine"_err_en_US
3009                 : "'%s' was previously called as a function"_err_en_US,
3010             *extant, "Previous call of '%s'"_en_US);
3011       }
3012       if (extant->attrs().test(Attr::PRIVATE)) {
3013         attrs.set(Attr::PRIVATE);
3014       }
3015       outer.erase(extant->name());
3016     } else {
3017       if (outer.IsGlobal()) {
3018         Say2(name, "'%s' is already defined as a global identifier"_err_en_US,
3019             *extant, "Previous definition of '%s'"_en_US);
3020       } else {
3021         SayAlreadyDeclared(name, *extant);
3022       }
3023       return;
3024     }
3025   }
3026   if (outer.IsModule() && !attrs.test(Attr::PRIVATE)) {
3027     attrs.set(Attr::PUBLIC);
3028   }
3029   Symbol &entrySymbol{MakeSymbol(outer, name.source, attrs)};
3030   entrySymbol.set_details(std::move(entryDetails));
3031   if (outer.IsGlobal()) {
3032     MakeExternal(entrySymbol);
3033   }
3034   SetBindNameOn(entrySymbol);
3035   entrySymbol.set(subpFlag);
3036   Resolve(name, entrySymbol);
3037 }
3038 
3039 // A subprogram declared with MODULE PROCEDURE
BeginMpSubprogram(const parser::Name & name)3040 bool SubprogramVisitor::BeginMpSubprogram(const parser::Name &name) {
3041   auto *symbol{FindSymbol(name)};
3042   if (symbol && symbol->has<SubprogramNameDetails>()) {
3043     symbol = FindSymbol(currScope().parent(), name);
3044   }
3045   if (!IsSeparateModuleProcedureInterface(symbol)) {
3046     Say(name, "'%s' was not declared a separate module procedure"_err_en_US);
3047     return false;
3048   }
3049   if (symbol->owner() == currScope()) {
3050     PushScope(Scope::Kind::Subprogram, symbol);
3051   } else {
3052     Symbol &newSymbol{MakeSymbol(name, SubprogramDetails{})};
3053     PushScope(Scope::Kind::Subprogram, &newSymbol);
3054     const auto &details{symbol->get<SubprogramDetails>()};
3055     auto &newDetails{newSymbol.get<SubprogramDetails>()};
3056     for (const Symbol *dummyArg : details.dummyArgs()) {
3057       if (!dummyArg) {
3058         newDetails.add_alternateReturn();
3059       } else if (Symbol * copy{currScope().CopySymbol(*dummyArg)}) {
3060         newDetails.add_dummyArg(*copy);
3061       }
3062     }
3063     if (details.isFunction()) {
3064       currScope().erase(symbol->name());
3065       newDetails.set_result(*currScope().CopySymbol(details.result()));
3066     }
3067   }
3068   return true;
3069 }
3070 
3071 // A subprogram declared with SUBROUTINE or FUNCTION
BeginSubprogram(const parser::Name & name,Symbol::Flag subpFlag,bool hasModulePrefix)3072 bool SubprogramVisitor::BeginSubprogram(
3073     const parser::Name &name, Symbol::Flag subpFlag, bool hasModulePrefix) {
3074   if (hasModulePrefix && !inInterfaceBlock() &&
3075       !IsSeparateModuleProcedureInterface(
3076           FindSymbol(currScope().parent(), name))) {
3077     Say(name, "'%s' was not declared a separate module procedure"_err_en_US);
3078     return false;
3079   }
3080   PushSubprogramScope(name, subpFlag);
3081   return true;
3082 }
3083 
EndSubprogram()3084 void SubprogramVisitor::EndSubprogram() { PopScope(); }
3085 
CheckExtantExternal(const parser::Name & name,Symbol::Flag subpFlag)3086 void SubprogramVisitor::CheckExtantExternal(
3087     const parser::Name &name, Symbol::Flag subpFlag) {
3088   if (auto *prev{FindSymbol(name)}) {
3089     if (prev->attrs().test(Attr::EXTERNAL) && prev->has<ProcEntityDetails>()) {
3090       // this subprogram was previously called, now being declared
3091       if (!prev->test(subpFlag)) {
3092         Say2(name,
3093             subpFlag == Symbol::Flag::Function
3094                 ? "'%s' was previously called as a subroutine"_err_en_US
3095                 : "'%s' was previously called as a function"_err_en_US,
3096             *prev, "Previous call of '%s'"_en_US);
3097       }
3098       EraseSymbol(name);
3099     }
3100   }
3101 }
3102 
PushSubprogramScope(const parser::Name & name,Symbol::Flag subpFlag)3103 Symbol &SubprogramVisitor::PushSubprogramScope(
3104     const parser::Name &name, Symbol::Flag subpFlag) {
3105   auto *symbol{GetSpecificFromGeneric(name)};
3106   if (!symbol) {
3107     CheckExtantExternal(name, subpFlag);
3108     symbol = &MakeSymbol(name, SubprogramDetails{});
3109   }
3110   symbol->set(subpFlag);
3111   symbol->ReplaceName(name.source);
3112   PushScope(Scope::Kind::Subprogram, symbol);
3113   auto &details{symbol->get<SubprogramDetails>()};
3114   if (inInterfaceBlock()) {
3115     details.set_isInterface();
3116     if (isAbstract()) {
3117       symbol->attrs().set(Attr::ABSTRACT);
3118     } else {
3119       MakeExternal(*symbol);
3120     }
3121     if (isGeneric()) {
3122       GetGenericDetails().AddSpecificProc(*symbol, name.source);
3123     }
3124     set_inheritFromParent(false);
3125   }
3126   FindSymbol(name)->set(subpFlag); // PushScope() created symbol
3127   return *symbol;
3128 }
3129 
PushBlockDataScope(const parser::Name & name)3130 void SubprogramVisitor::PushBlockDataScope(const parser::Name &name) {
3131   if (auto *prev{FindSymbol(name)}) {
3132     if (prev->attrs().test(Attr::EXTERNAL) && prev->has<ProcEntityDetails>()) {
3133       if (prev->test(Symbol::Flag::Subroutine) ||
3134           prev->test(Symbol::Flag::Function)) {
3135         Say2(name, "BLOCK DATA '%s' has been called"_err_en_US, *prev,
3136             "Previous call of '%s'"_en_US);
3137       }
3138       EraseSymbol(name);
3139     }
3140   }
3141   if (name.source.empty()) {
3142     // Don't let unnamed BLOCK DATA conflict with unnamed PROGRAM
3143     PushScope(Scope::Kind::BlockData, nullptr);
3144   } else {
3145     PushScope(Scope::Kind::BlockData, &MakeSymbol(name, SubprogramDetails{}));
3146   }
3147 }
3148 
3149 // If name is a generic, return specific subprogram with the same name.
GetSpecificFromGeneric(const parser::Name & name)3150 Symbol *SubprogramVisitor::GetSpecificFromGeneric(const parser::Name &name) {
3151   if (auto *symbol{FindSymbol(name)}) {
3152     if (auto *details{symbol->detailsIf<GenericDetails>()}) {
3153       // found generic, want subprogram
3154       auto *specific{details->specific()};
3155       if (!specific) {
3156         specific =
3157             &currScope().MakeSymbol(name.source, Attrs{}, SubprogramDetails{});
3158         details->set_specific(Resolve(name, *specific));
3159       } else if (isGeneric()) {
3160         SayAlreadyDeclared(name, *specific);
3161       }
3162       if (!specific->has<SubprogramDetails>()) {
3163         specific->set_details(SubprogramDetails{});
3164       }
3165       return specific;
3166     }
3167   }
3168   return nullptr;
3169 }
3170 
3171 // DeclarationVisitor implementation
3172 
BeginDecl()3173 bool DeclarationVisitor::BeginDecl() {
3174   BeginDeclTypeSpec();
3175   BeginArraySpec();
3176   return BeginAttrs();
3177 }
EndDecl()3178 void DeclarationVisitor::EndDecl() {
3179   EndDeclTypeSpec();
3180   EndArraySpec();
3181   EndAttrs();
3182 }
3183 
CheckUseError(const parser::Name & name)3184 bool DeclarationVisitor::CheckUseError(const parser::Name &name) {
3185   const auto *details{name.symbol->detailsIf<UseErrorDetails>()};
3186   if (!details) {
3187     return false;
3188   }
3189   Message &msg{Say(name, "Reference to '%s' is ambiguous"_err_en_US)};
3190   for (const auto &[location, module] : details->occurrences()) {
3191     msg.Attach(location, "'%s' was use-associated from module '%s'"_en_US,
3192         name.source, module->GetName().value());
3193   }
3194   return true;
3195 }
3196 
3197 // Report error if accessibility of symbol doesn't match isPrivate.
CheckAccessibility(const SourceName & name,bool isPrivate,Symbol & symbol)3198 void DeclarationVisitor::CheckAccessibility(
3199     const SourceName &name, bool isPrivate, Symbol &symbol) {
3200   if (symbol.attrs().test(Attr::PRIVATE) != isPrivate) {
3201     Say2(name,
3202         "'%s' does not have the same accessibility as its previous declaration"_err_en_US,
3203         symbol, "Previous declaration of '%s'"_en_US);
3204   }
3205 }
3206 
Post(const parser::TypeDeclarationStmt &)3207 void DeclarationVisitor::Post(const parser::TypeDeclarationStmt &) {
3208   if (!GetAttrs().HasAny({Attr::POINTER, Attr::ALLOCATABLE})) { // C702
3209     if (const auto *typeSpec{GetDeclTypeSpec()}) {
3210       if (typeSpec->category() == DeclTypeSpec::Character) {
3211         if (typeSpec->characterTypeSpec().length().isDeferred()) {
3212           Say("The type parameter LEN cannot be deferred without"
3213               " the POINTER or ALLOCATABLE attribute"_err_en_US);
3214         }
3215       } else if (const DerivedTypeSpec * derivedSpec{typeSpec->AsDerived()}) {
3216         for (const auto &pair : derivedSpec->parameters()) {
3217           if (pair.second.isDeferred()) {
3218             Say(currStmtSource().value(),
3219                 "The value of type parameter '%s' cannot be deferred"
3220                 " without the POINTER or ALLOCATABLE attribute"_err_en_US,
3221                 pair.first);
3222           }
3223         }
3224       }
3225     }
3226   }
3227   EndDecl();
3228 }
3229 
Post(const parser::DimensionStmt::Declaration & x)3230 void DeclarationVisitor::Post(const parser::DimensionStmt::Declaration &x) {
3231   DeclareObjectEntity(std::get<parser::Name>(x.t));
3232 }
Post(const parser::CodimensionDecl & x)3233 void DeclarationVisitor::Post(const parser::CodimensionDecl &x) {
3234   DeclareObjectEntity(std::get<parser::Name>(x.t));
3235 }
3236 
Pre(const parser::Initialization &)3237 bool DeclarationVisitor::Pre(const parser::Initialization &) {
3238   // Defer inspection of initializers to Initialization() so that the
3239   // symbol being initialized will be available within the initialization
3240   // expression.
3241   return false;
3242 }
3243 
Post(const parser::EntityDecl & x)3244 void DeclarationVisitor::Post(const parser::EntityDecl &x) {
3245   // TODO: may be under StructureStmt
3246   const auto &name{std::get<parser::ObjectName>(x.t)};
3247   Attrs attrs{attrs_ ? HandleSaveName(name.source, *attrs_) : Attrs{}};
3248   Symbol &symbol{DeclareUnknownEntity(name, attrs)};
3249   symbol.ReplaceName(name.source);
3250   if (auto &init{std::get<std::optional<parser::Initialization>>(x.t)}) {
3251     if (ConvertToObjectEntity(symbol)) {
3252       Initialization(name, *init, false);
3253     }
3254   } else if (attrs.test(Attr::PARAMETER)) { // C882, C883
3255     Say(name, "Missing initialization for parameter '%s'"_err_en_US);
3256   }
3257 }
3258 
Post(const parser::PointerDecl & x)3259 void DeclarationVisitor::Post(const parser::PointerDecl &x) {
3260   const auto &name{std::get<parser::Name>(x.t)};
3261   if (const auto &deferredShapeSpecs{
3262           std::get<std::optional<parser::DeferredShapeSpecList>>(x.t)}) {
3263     CHECK(arraySpec().empty());
3264     BeginArraySpec();
3265     set_arraySpec(AnalyzeDeferredShapeSpecList(context(), *deferredShapeSpecs));
3266     Symbol &symbol{DeclareObjectEntity(name, Attrs{Attr::POINTER})};
3267     symbol.ReplaceName(name.source);
3268     EndArraySpec();
3269   } else {
3270     Symbol &symbol{DeclareUnknownEntity(name, Attrs{Attr::POINTER})};
3271     symbol.ReplaceName(name.source);
3272   }
3273 }
3274 
Pre(const parser::BindEntity & x)3275 bool DeclarationVisitor::Pre(const parser::BindEntity &x) {
3276   auto kind{std::get<parser::BindEntity::Kind>(x.t)};
3277   auto &name{std::get<parser::Name>(x.t)};
3278   Symbol *symbol;
3279   if (kind == parser::BindEntity::Kind::Object) {
3280     symbol = &HandleAttributeStmt(Attr::BIND_C, name);
3281   } else {
3282     symbol = &MakeCommonBlockSymbol(name);
3283     symbol->attrs().set(Attr::BIND_C);
3284   }
3285   SetBindNameOn(*symbol);
3286   return false;
3287 }
Pre(const parser::NamedConstantDef & x)3288 bool DeclarationVisitor::Pre(const parser::NamedConstantDef &x) {
3289   auto &name{std::get<parser::NamedConstant>(x.t).v};
3290   auto &symbol{HandleAttributeStmt(Attr::PARAMETER, name)};
3291   if (!ConvertToObjectEntity(symbol) ||
3292       symbol.test(Symbol::Flag::CrayPointer) ||
3293       symbol.test(Symbol::Flag::CrayPointee)) {
3294     SayWithDecl(
3295         name, symbol, "PARAMETER attribute not allowed on '%s'"_err_en_US);
3296     return false;
3297   }
3298   const auto &expr{std::get<parser::ConstantExpr>(x.t)};
3299   ApplyImplicitRules(symbol);
3300   Walk(expr);
3301   if (auto converted{EvaluateNonPointerInitializer(
3302           symbol, expr, expr.thing.value().source)}) {
3303     symbol.get<ObjectEntityDetails>().set_init(std::move(*converted));
3304   }
3305   return false;
3306 }
Pre(const parser::NamedConstant & x)3307 bool DeclarationVisitor::Pre(const parser::NamedConstant &x) {
3308   const parser::Name &name{x.v};
3309   if (!FindSymbol(name)) {
3310     Say(name, "Named constant '%s' not found"_err_en_US);
3311   } else {
3312     CheckUseError(name);
3313   }
3314   return false;
3315 }
3316 
Pre(const parser::Enumerator & enumerator)3317 bool DeclarationVisitor::Pre(const parser::Enumerator &enumerator) {
3318   const parser::Name &name{std::get<parser::NamedConstant>(enumerator.t).v};
3319   Symbol *symbol{FindSymbol(name)};
3320   if (symbol && !symbol->has<UnknownDetails>()) {
3321     // Contrary to named constants appearing in a PARAMETER statement,
3322     // enumerator names should not have their type, dimension or any other
3323     // attributes defined before they are declared in the enumerator statement,
3324     // with the exception of accessibility.
3325     // This is not explicitly forbidden by the standard, but they are scalars
3326     // which type is left for the compiler to chose, so do not let users try to
3327     // tamper with that.
3328     SayAlreadyDeclared(name, *symbol);
3329     symbol = nullptr;
3330   } else {
3331     // Enumerators are treated as PARAMETER (section 7.6 paragraph (4))
3332     symbol = &MakeSymbol(name, Attrs{Attr::PARAMETER}, ObjectEntityDetails{});
3333     symbol->SetType(context().MakeNumericType(
3334         TypeCategory::Integer, evaluate::CInteger::kind));
3335   }
3336 
3337   if (auto &init{std::get<std::optional<parser::ScalarIntConstantExpr>>(
3338           enumerator.t)}) {
3339     Walk(*init); // Resolve names in expression before evaluation.
3340     if (auto value{EvaluateInt64(context(), *init)}) {
3341       // Cast all init expressions to C_INT so that they can then be
3342       // safely incremented (see 7.6 Note 2).
3343       enumerationState_.value = static_cast<int>(*value);
3344     } else {
3345       Say(name,
3346           "Enumerator value could not be computed "
3347           "from the given expression"_err_en_US);
3348       // Prevent resolution of next enumerators value
3349       enumerationState_.value = std::nullopt;
3350     }
3351   }
3352 
3353   if (symbol) {
3354     if (enumerationState_.value) {
3355       symbol->get<ObjectEntityDetails>().set_init(SomeExpr{
3356           evaluate::Expr<evaluate::CInteger>{*enumerationState_.value}});
3357     } else {
3358       context().SetError(*symbol);
3359     }
3360   }
3361 
3362   if (enumerationState_.value) {
3363     (*enumerationState_.value)++;
3364   }
3365   return false;
3366 }
3367 
Post(const parser::EnumDef &)3368 void DeclarationVisitor::Post(const parser::EnumDef &) {
3369   enumerationState_ = EnumeratorState{};
3370 }
3371 
Pre(const parser::AccessSpec & x)3372 bool DeclarationVisitor::Pre(const parser::AccessSpec &x) {
3373   Attr attr{AccessSpecToAttr(x)};
3374   if (!NonDerivedTypeScope().IsModule()) { // C817
3375     Say(currStmtSource().value(),
3376         "%s attribute may only appear in the specification part of a module"_err_en_US,
3377         EnumToString(attr));
3378   }
3379   CheckAndSet(attr);
3380   return false;
3381 }
3382 
Pre(const parser::AsynchronousStmt & x)3383 bool DeclarationVisitor::Pre(const parser::AsynchronousStmt &x) {
3384   return HandleAttributeStmt(Attr::ASYNCHRONOUS, x.v);
3385 }
Pre(const parser::ContiguousStmt & x)3386 bool DeclarationVisitor::Pre(const parser::ContiguousStmt &x) {
3387   return HandleAttributeStmt(Attr::CONTIGUOUS, x.v);
3388 }
Pre(const parser::ExternalStmt & x)3389 bool DeclarationVisitor::Pre(const parser::ExternalStmt &x) {
3390   HandleAttributeStmt(Attr::EXTERNAL, x.v);
3391   for (const auto &name : x.v) {
3392     auto *symbol{FindSymbol(name)};
3393     if (!ConvertToProcEntity(*symbol)) {
3394       SayWithDecl(
3395           name, *symbol, "EXTERNAL attribute not allowed on '%s'"_err_en_US);
3396     } else if (symbol->attrs().test(Attr::INTRINSIC)) { // C840
3397       Say(symbol->name(),
3398           "Symbol '%s' cannot have both INTRINSIC and EXTERNAL attributes"_err_en_US,
3399           symbol->name());
3400     }
3401   }
3402   return false;
3403 }
Pre(const parser::IntentStmt & x)3404 bool DeclarationVisitor::Pre(const parser::IntentStmt &x) {
3405   auto &intentSpec{std::get<parser::IntentSpec>(x.t)};
3406   auto &names{std::get<std::list<parser::Name>>(x.t)};
3407   return CheckNotInBlock("INTENT") && // C1107
3408       HandleAttributeStmt(IntentSpecToAttr(intentSpec), names);
3409 }
Pre(const parser::IntrinsicStmt & x)3410 bool DeclarationVisitor::Pre(const parser::IntrinsicStmt &x) {
3411   HandleAttributeStmt(Attr::INTRINSIC, x.v);
3412   for (const auto &name : x.v) {
3413     auto *symbol{FindSymbol(name)};
3414     if (!ConvertToProcEntity(*symbol)) {
3415       SayWithDecl(
3416           name, *symbol, "INTRINSIC attribute not allowed on '%s'"_err_en_US);
3417     } else if (symbol->attrs().test(Attr::EXTERNAL)) { // C840
3418       Say(symbol->name(),
3419           "Symbol '%s' cannot have both EXTERNAL and INTRINSIC attributes"_err_en_US,
3420           symbol->name());
3421     }
3422   }
3423   return false;
3424 }
Pre(const parser::OptionalStmt & x)3425 bool DeclarationVisitor::Pre(const parser::OptionalStmt &x) {
3426   return CheckNotInBlock("OPTIONAL") && // C1107
3427       HandleAttributeStmt(Attr::OPTIONAL, x.v);
3428 }
Pre(const parser::ProtectedStmt & x)3429 bool DeclarationVisitor::Pre(const parser::ProtectedStmt &x) {
3430   return HandleAttributeStmt(Attr::PROTECTED, x.v);
3431 }
Pre(const parser::ValueStmt & x)3432 bool DeclarationVisitor::Pre(const parser::ValueStmt &x) {
3433   return CheckNotInBlock("VALUE") && // C1107
3434       HandleAttributeStmt(Attr::VALUE, x.v);
3435 }
Pre(const parser::VolatileStmt & x)3436 bool DeclarationVisitor::Pre(const parser::VolatileStmt &x) {
3437   return HandleAttributeStmt(Attr::VOLATILE, x.v);
3438 }
3439 // Handle a statement that sets an attribute on a list of names.
HandleAttributeStmt(Attr attr,const std::list<parser::Name> & names)3440 bool DeclarationVisitor::HandleAttributeStmt(
3441     Attr attr, const std::list<parser::Name> &names) {
3442   for (const auto &name : names) {
3443     HandleAttributeStmt(attr, name);
3444   }
3445   return false;
3446 }
HandleAttributeStmt(Attr attr,const parser::Name & name)3447 Symbol &DeclarationVisitor::HandleAttributeStmt(
3448     Attr attr, const parser::Name &name) {
3449   if (attr == Attr::INTRINSIC && !IsIntrinsic(name.source, std::nullopt)) {
3450     Say(name.source, "'%s' is not a known intrinsic procedure"_err_en_US);
3451   }
3452   auto *symbol{FindInScope(name)};
3453   if (attr == Attr::ASYNCHRONOUS || attr == Attr::VOLATILE) {
3454     // these can be set on a symbol that is host-assoc or use-assoc
3455     if (!symbol &&
3456         (currScope().kind() == Scope::Kind::Subprogram ||
3457             currScope().kind() == Scope::Kind::Block)) {
3458       if (auto *hostSymbol{FindSymbol(name)}) {
3459         symbol = &MakeHostAssocSymbol(name, *hostSymbol);
3460       }
3461     }
3462   } else if (symbol && symbol->has<UseDetails>()) {
3463     Say(currStmtSource().value(),
3464         "Cannot change %s attribute on use-associated '%s'"_err_en_US,
3465         EnumToString(attr), name.source);
3466     return *symbol;
3467   }
3468   if (!symbol) {
3469     symbol = &MakeSymbol(name, EntityDetails{});
3470   }
3471   symbol->attrs().set(attr);
3472   symbol->attrs() = HandleSaveName(name.source, symbol->attrs());
3473   return *symbol;
3474 }
3475 // C1107
CheckNotInBlock(const char * stmt)3476 bool DeclarationVisitor::CheckNotInBlock(const char *stmt) {
3477   if (currScope().kind() == Scope::Kind::Block) {
3478     Say(MessageFormattedText{
3479         "%s statement is not allowed in a BLOCK construct"_err_en_US, stmt});
3480     return false;
3481   } else {
3482     return true;
3483   }
3484 }
3485 
Post(const parser::ObjectDecl & x)3486 void DeclarationVisitor::Post(const parser::ObjectDecl &x) {
3487   CHECK(objectDeclAttr_);
3488   const auto &name{std::get<parser::ObjectName>(x.t)};
3489   DeclareObjectEntity(name, Attrs{*objectDeclAttr_});
3490 }
3491 
3492 // Declare an entity not yet known to be an object or proc.
DeclareUnknownEntity(const parser::Name & name,Attrs attrs)3493 Symbol &DeclarationVisitor::DeclareUnknownEntity(
3494     const parser::Name &name, Attrs attrs) {
3495   if (!arraySpec().empty() || !coarraySpec().empty()) {
3496     return DeclareObjectEntity(name, attrs);
3497   } else {
3498     Symbol &symbol{DeclareEntity<EntityDetails>(name, attrs)};
3499     if (auto *type{GetDeclTypeSpec()}) {
3500       SetType(name, *type);
3501     }
3502     charInfo_.length.reset();
3503     SetBindNameOn(symbol);
3504     if (symbol.attrs().test(Attr::EXTERNAL)) {
3505       ConvertToProcEntity(symbol);
3506     }
3507     return symbol;
3508   }
3509 }
3510 
DeclareProcEntity(const parser::Name & name,Attrs attrs,const ProcInterface & interface)3511 Symbol &DeclarationVisitor::DeclareProcEntity(
3512     const parser::Name &name, Attrs attrs, const ProcInterface &interface) {
3513   Symbol &symbol{DeclareEntity<ProcEntityDetails>(name, attrs)};
3514   if (auto *details{symbol.detailsIf<ProcEntityDetails>()}) {
3515     if (details->IsInterfaceSet()) {
3516       SayWithDecl(name, symbol,
3517           "The interface for procedure '%s' has already been "
3518           "declared"_err_en_US);
3519       context().SetError(symbol);
3520     } else {
3521       if (interface.type()) {
3522         symbol.set(Symbol::Flag::Function);
3523       } else if (interface.symbol()) {
3524         if (interface.symbol()->test(Symbol::Flag::Function)) {
3525           symbol.set(Symbol::Flag::Function);
3526         } else if (interface.symbol()->test(Symbol::Flag::Subroutine)) {
3527           symbol.set(Symbol::Flag::Subroutine);
3528         }
3529       }
3530       details->set_interface(interface);
3531       SetBindNameOn(symbol);
3532       SetPassNameOn(symbol);
3533     }
3534   }
3535   return symbol;
3536 }
3537 
DeclareObjectEntity(const parser::Name & name,Attrs attrs)3538 Symbol &DeclarationVisitor::DeclareObjectEntity(
3539     const parser::Name &name, Attrs attrs) {
3540   Symbol &symbol{DeclareEntity<ObjectEntityDetails>(name, attrs)};
3541   if (auto *details{symbol.detailsIf<ObjectEntityDetails>()}) {
3542     if (auto *type{GetDeclTypeSpec()}) {
3543       SetType(name, *type);
3544     }
3545     if (!arraySpec().empty()) {
3546       if (details->IsArray()) {
3547         if (!context().HasError(symbol)) {
3548           Say(name,
3549               "The dimensions of '%s' have already been declared"_err_en_US);
3550           context().SetError(symbol);
3551         }
3552       } else {
3553         details->set_shape(arraySpec());
3554       }
3555     }
3556     if (!coarraySpec().empty()) {
3557       if (details->IsCoarray()) {
3558         if (!context().HasError(symbol)) {
3559           Say(name,
3560               "The codimensions of '%s' have already been declared"_err_en_US);
3561           context().SetError(symbol);
3562         }
3563       } else {
3564         details->set_coshape(coarraySpec());
3565       }
3566     }
3567     SetBindNameOn(symbol);
3568   }
3569   ClearArraySpec();
3570   ClearCoarraySpec();
3571   charInfo_.length.reset();
3572   return symbol;
3573 }
3574 
Post(const parser::IntegerTypeSpec & x)3575 void DeclarationVisitor::Post(const parser::IntegerTypeSpec &x) {
3576   SetDeclTypeSpec(MakeNumericType(TypeCategory::Integer, x.v));
3577 }
Post(const parser::IntrinsicTypeSpec::Real & x)3578 void DeclarationVisitor::Post(const parser::IntrinsicTypeSpec::Real &x) {
3579   SetDeclTypeSpec(MakeNumericType(TypeCategory::Real, x.kind));
3580 }
Post(const parser::IntrinsicTypeSpec::Complex & x)3581 void DeclarationVisitor::Post(const parser::IntrinsicTypeSpec::Complex &x) {
3582   SetDeclTypeSpec(MakeNumericType(TypeCategory::Complex, x.kind));
3583 }
Post(const parser::IntrinsicTypeSpec::Logical & x)3584 void DeclarationVisitor::Post(const parser::IntrinsicTypeSpec::Logical &x) {
3585   SetDeclTypeSpec(MakeLogicalType(x.kind));
3586 }
Post(const parser::IntrinsicTypeSpec::Character &)3587 void DeclarationVisitor::Post(const parser::IntrinsicTypeSpec::Character &) {
3588   if (!charInfo_.length) {
3589     charInfo_.length = ParamValue{1, common::TypeParamAttr::Len};
3590   }
3591   if (!charInfo_.kind) {
3592     charInfo_.kind =
3593         KindExpr{context().GetDefaultKind(TypeCategory::Character)};
3594   }
3595   SetDeclTypeSpec(currScope().MakeCharacterType(
3596       std::move(*charInfo_.length), std::move(*charInfo_.kind)));
3597   charInfo_ = {};
3598 }
Post(const parser::CharSelector::LengthAndKind & x)3599 void DeclarationVisitor::Post(const parser::CharSelector::LengthAndKind &x) {
3600   charInfo_.kind = EvaluateSubscriptIntExpr(x.kind);
3601   std::optional<std::int64_t> intKind{ToInt64(charInfo_.kind)};
3602   if (intKind &&
3603       !evaluate::IsValidKindOfIntrinsicType(
3604           TypeCategory::Character, *intKind)) { // C715, C719
3605     Say(currStmtSource().value(),
3606         "KIND value (%jd) not valid for CHARACTER"_err_en_US, *intKind);
3607     charInfo_.kind = std::nullopt; // prevent further errors
3608   }
3609   if (x.length) {
3610     charInfo_.length = GetParamValue(*x.length, common::TypeParamAttr::Len);
3611   }
3612 }
Post(const parser::CharLength & x)3613 void DeclarationVisitor::Post(const parser::CharLength &x) {
3614   if (const auto *length{std::get_if<std::uint64_t>(&x.u)}) {
3615     charInfo_.length = ParamValue{
3616         static_cast<ConstantSubscript>(*length), common::TypeParamAttr::Len};
3617   } else {
3618     charInfo_.length = GetParamValue(
3619         std::get<parser::TypeParamValue>(x.u), common::TypeParamAttr::Len);
3620   }
3621 }
Post(const parser::LengthSelector & x)3622 void DeclarationVisitor::Post(const parser::LengthSelector &x) {
3623   if (const auto *param{std::get_if<parser::TypeParamValue>(&x.u)}) {
3624     charInfo_.length = GetParamValue(*param, common::TypeParamAttr::Len);
3625   }
3626 }
3627 
Pre(const parser::KindParam & x)3628 bool DeclarationVisitor::Pre(const parser::KindParam &x) {
3629   if (const auto *kind{std::get_if<
3630           parser::Scalar<parser::Integer<parser::Constant<parser::Name>>>>(
3631           &x.u)}) {
3632     const parser::Name &name{kind->thing.thing.thing};
3633     if (!FindSymbol(name)) {
3634       Say(name, "Parameter '%s' not found"_err_en_US);
3635     }
3636   }
3637   return false;
3638 }
3639 
Pre(const parser::DeclarationTypeSpec::Type &)3640 bool DeclarationVisitor::Pre(const parser::DeclarationTypeSpec::Type &) {
3641   CHECK(GetDeclTypeSpecCategory() == DeclTypeSpec::Category::TypeDerived);
3642   return true;
3643 }
3644 
Post(const parser::DeclarationTypeSpec::Type & type)3645 void DeclarationVisitor::Post(const parser::DeclarationTypeSpec::Type &type) {
3646   const parser::Name &derivedName{std::get<parser::Name>(type.derived.t)};
3647   if (const Symbol * derivedSymbol{derivedName.symbol}) {
3648     CheckForAbstractType(*derivedSymbol); // C706
3649   }
3650 }
3651 
Pre(const parser::DeclarationTypeSpec::Class &)3652 bool DeclarationVisitor::Pre(const parser::DeclarationTypeSpec::Class &) {
3653   SetDeclTypeSpecCategory(DeclTypeSpec::Category::ClassDerived);
3654   return true;
3655 }
3656 
Post(const parser::DeclarationTypeSpec::Class & parsedClass)3657 void DeclarationVisitor::Post(
3658     const parser::DeclarationTypeSpec::Class &parsedClass) {
3659   const auto &typeName{std::get<parser::Name>(parsedClass.derived.t)};
3660   if (auto spec{ResolveDerivedType(typeName)};
3661       spec && !IsExtensibleType(&*spec)) { // C705
3662     SayWithDecl(typeName, *typeName.symbol,
3663         "Non-extensible derived type '%s' may not be used with CLASS"
3664         " keyword"_err_en_US);
3665   }
3666 }
3667 
Pre(const parser::DeclarationTypeSpec::Record &)3668 bool DeclarationVisitor::Pre(const parser::DeclarationTypeSpec::Record &) {
3669   // TODO
3670   return true;
3671 }
3672 
Post(const parser::DerivedTypeSpec & x)3673 void DeclarationVisitor::Post(const parser::DerivedTypeSpec &x) {
3674   const auto &typeName{std::get<parser::Name>(x.t)};
3675   auto spec{ResolveDerivedType(typeName)};
3676   if (!spec) {
3677     return;
3678   }
3679   bool seenAnyName{false};
3680   for (const auto &typeParamSpec :
3681       std::get<std::list<parser::TypeParamSpec>>(x.t)) {
3682     const auto &optKeyword{
3683         std::get<std::optional<parser::Keyword>>(typeParamSpec.t)};
3684     std::optional<SourceName> name;
3685     if (optKeyword) {
3686       seenAnyName = true;
3687       name = optKeyword->v.source;
3688     } else if (seenAnyName) {
3689       Say(typeName.source, "Type parameter value must have a name"_err_en_US);
3690       continue;
3691     }
3692     const auto &value{std::get<parser::TypeParamValue>(typeParamSpec.t)};
3693     // The expressions in a derived type specifier whose values define
3694     // non-defaulted type parameters are evaluated (folded) in the enclosing
3695     // scope.  The KIND/LEN distinction is resolved later in
3696     // DerivedTypeSpec::CookParameters().
3697     ParamValue param{GetParamValue(value, common::TypeParamAttr::Kind)};
3698     if (!param.isExplicit() || param.GetExplicit()) {
3699       spec->AddRawParamValue(optKeyword, std::move(param));
3700     }
3701   }
3702 
3703   // The DerivedTypeSpec *spec is used initially as a search key.
3704   // If it turns out to have the same name and actual parameter
3705   // value expressions as another DerivedTypeSpec in the current
3706   // scope does, then we'll use that extant spec; otherwise, when this
3707   // spec is distinct from all derived types previously instantiated
3708   // in the current scope, this spec will be moved into that collection.
3709   const auto &dtDetails{spec->typeSymbol().get<DerivedTypeDetails>()};
3710   auto category{GetDeclTypeSpecCategory()};
3711   if (dtDetails.isForwardReferenced()) {
3712     DeclTypeSpec &type{currScope().MakeDerivedType(category, std::move(*spec))};
3713     SetDeclTypeSpec(type);
3714     return;
3715   }
3716   // Normalize parameters to produce a better search key.
3717   spec->CookParameters(GetFoldingContext());
3718   if (!spec->MightBeParameterized()) {
3719     spec->EvaluateParameters(context());
3720   }
3721   if (const DeclTypeSpec *
3722       extant{currScope().FindInstantiatedDerivedType(*spec, category)}) {
3723     // This derived type and parameter expressions (if any) are already present
3724     // in this scope.
3725     SetDeclTypeSpec(*extant);
3726   } else {
3727     DeclTypeSpec &type{currScope().MakeDerivedType(category, std::move(*spec))};
3728     DerivedTypeSpec &derived{type.derivedTypeSpec()};
3729     if (derived.MightBeParameterized() &&
3730         currScope().IsParameterizedDerivedType()) {
3731       // Defer instantiation; use the derived type's definition's scope.
3732       derived.set_scope(DEREF(spec->typeSymbol().scope()));
3733     } else {
3734       auto restorer{
3735           GetFoldingContext().messages().SetLocation(currStmtSource().value())};
3736       derived.Instantiate(currScope(), context());
3737     }
3738     SetDeclTypeSpec(type);
3739   }
3740   // Capture the DerivedTypeSpec in the parse tree for use in building
3741   // structure constructor expressions.
3742   x.derivedTypeSpec = &GetDeclTypeSpec()->derivedTypeSpec();
3743 }
3744 
3745 // The descendents of DerivedTypeDef in the parse tree are visited directly
3746 // in this Pre() routine so that recursive use of the derived type can be
3747 // supported in the components.
Pre(const parser::DerivedTypeDef & x)3748 bool DeclarationVisitor::Pre(const parser::DerivedTypeDef &x) {
3749   auto &stmt{std::get<parser::Statement<parser::DerivedTypeStmt>>(x.t)};
3750   Walk(stmt);
3751   Walk(std::get<std::list<parser::Statement<parser::TypeParamDefStmt>>>(x.t));
3752   auto &scope{currScope()};
3753   CHECK(scope.symbol());
3754   CHECK(scope.symbol()->scope() == &scope);
3755   auto &details{scope.symbol()->get<DerivedTypeDetails>()};
3756   std::set<SourceName> paramNames;
3757   for (auto &paramName : std::get<std::list<parser::Name>>(stmt.statement.t)) {
3758     details.add_paramName(paramName.source);
3759     auto *symbol{FindInScope(scope, paramName)};
3760     if (!symbol) {
3761       Say(paramName,
3762           "No definition found for type parameter '%s'"_err_en_US); // C742
3763       // No symbol for a type param.  Create one and mark it as containing an
3764       // error to improve subsequent semantic processing
3765       BeginAttrs();
3766       Symbol *typeParam{MakeTypeSymbol(
3767           paramName, TypeParamDetails{common::TypeParamAttr::Len})};
3768       context().SetError(*typeParam);
3769       EndAttrs();
3770     } else if (!symbol->has<TypeParamDetails>()) {
3771       Say2(paramName, "'%s' is not defined as a type parameter"_err_en_US,
3772           *symbol, "Definition of '%s'"_en_US); // C741
3773     }
3774     if (!paramNames.insert(paramName.source).second) {
3775       Say(paramName,
3776           "Duplicate type parameter name: '%s'"_err_en_US); // C731
3777     }
3778   }
3779   for (const auto &[name, symbol] : currScope()) {
3780     if (symbol->has<TypeParamDetails>() && !paramNames.count(name)) {
3781       SayDerivedType(name,
3782           "'%s' is not a type parameter of this derived type"_err_en_US,
3783           currScope()); // C741
3784     }
3785   }
3786   Walk(std::get<std::list<parser::Statement<parser::PrivateOrSequence>>>(x.t));
3787   const auto &componentDefs{
3788       std::get<std::list<parser::Statement<parser::ComponentDefStmt>>>(x.t)};
3789   Walk(componentDefs);
3790   if (derivedTypeInfo_.sequence) {
3791     details.set_sequence(true);
3792     if (componentDefs.empty()) { // C740
3793       Say(stmt.source,
3794           "A sequence type must have at least one component"_err_en_US);
3795     }
3796     if (!details.paramNames().empty()) { // C740
3797       Say(stmt.source,
3798           "A sequence type may not have type parameters"_err_en_US);
3799     }
3800     if (derivedTypeInfo_.extends) { // C735
3801       Say(stmt.source,
3802           "A sequence type may not have the EXTENDS attribute"_err_en_US);
3803     } else {
3804       for (const auto &componentName : details.componentNames()) {
3805         const Symbol *componentSymbol{scope.FindComponent(componentName)};
3806         if (componentSymbol && componentSymbol->has<ObjectEntityDetails>()) {
3807           const auto &componentDetails{
3808               componentSymbol->get<ObjectEntityDetails>()};
3809           const DeclTypeSpec *componentType{componentDetails.type()};
3810           if (componentType && // C740
3811               !componentType->AsIntrinsic() &&
3812               !componentType->IsSequenceType()) {
3813             Say(componentSymbol->name(),
3814                 "A sequence type data component must either be of an"
3815                 " intrinsic type or a derived sequence type"_err_en_US);
3816           }
3817         }
3818       }
3819     }
3820   }
3821   Walk(std::get<std::optional<parser::TypeBoundProcedurePart>>(x.t));
3822   Walk(std::get<parser::Statement<parser::EndTypeStmt>>(x.t));
3823   derivedTypeInfo_ = {};
3824   PopScope();
3825   return false;
3826 }
Pre(const parser::DerivedTypeStmt &)3827 bool DeclarationVisitor::Pre(const parser::DerivedTypeStmt &) {
3828   return BeginAttrs();
3829 }
Post(const parser::DerivedTypeStmt & x)3830 void DeclarationVisitor::Post(const parser::DerivedTypeStmt &x) {
3831   auto &name{std::get<parser::Name>(x.t)};
3832   // Resolve the EXTENDS() clause before creating the derived
3833   // type's symbol to foil attempts to recursively extend a type.
3834   auto *extendsName{derivedTypeInfo_.extends};
3835   std::optional<DerivedTypeSpec> extendsType{
3836       ResolveExtendsType(name, extendsName)};
3837   auto &symbol{MakeSymbol(name, GetAttrs(), DerivedTypeDetails{})};
3838   symbol.ReplaceName(name.source);
3839   derivedTypeInfo_.type = &symbol;
3840   PushScope(Scope::Kind::DerivedType, &symbol);
3841   if (extendsType) {
3842     // Declare the "parent component"; private if the type is.
3843     // Any symbol stored in the EXTENDS() clause is temporarily
3844     // hidden so that a new symbol can be created for the parent
3845     // component without producing spurious errors about already
3846     // existing.
3847     const Symbol &extendsSymbol{extendsType->typeSymbol()};
3848     auto restorer{common::ScopedSet(extendsName->symbol, nullptr)};
3849     if (OkToAddComponent(*extendsName, &extendsSymbol)) {
3850       auto &comp{DeclareEntity<ObjectEntityDetails>(*extendsName, Attrs{})};
3851       comp.attrs().set(
3852           Attr::PRIVATE, extendsSymbol.attrs().test(Attr::PRIVATE));
3853       comp.set(Symbol::Flag::ParentComp);
3854       DeclTypeSpec &type{currScope().MakeDerivedType(
3855           DeclTypeSpec::TypeDerived, std::move(*extendsType))};
3856       type.derivedTypeSpec().set_scope(*extendsSymbol.scope());
3857       comp.SetType(type);
3858       DerivedTypeDetails &details{symbol.get<DerivedTypeDetails>()};
3859       details.add_component(comp);
3860     }
3861   }
3862   EndAttrs();
3863 }
3864 
Post(const parser::TypeParamDefStmt & x)3865 void DeclarationVisitor::Post(const parser::TypeParamDefStmt &x) {
3866   auto *type{GetDeclTypeSpec()};
3867   auto attr{std::get<common::TypeParamAttr>(x.t)};
3868   for (auto &decl : std::get<std::list<parser::TypeParamDecl>>(x.t)) {
3869     auto &name{std::get<parser::Name>(decl.t)};
3870     if (Symbol * symbol{MakeTypeSymbol(name, TypeParamDetails{attr})}) {
3871       SetType(name, *type);
3872       if (auto &init{
3873               std::get<std::optional<parser::ScalarIntConstantExpr>>(decl.t)}) {
3874         if (auto maybeExpr{EvaluateNonPointerInitializer(
3875                 *symbol, *init, init->thing.thing.thing.value().source)}) {
3876           if (auto *intExpr{std::get_if<SomeIntExpr>(&maybeExpr->u)}) {
3877             symbol->get<TypeParamDetails>().set_init(std::move(*intExpr));
3878           }
3879         }
3880       }
3881     }
3882   }
3883   EndDecl();
3884 }
Pre(const parser::TypeAttrSpec::Extends & x)3885 bool DeclarationVisitor::Pre(const parser::TypeAttrSpec::Extends &x) {
3886   if (derivedTypeInfo_.extends) {
3887     Say(currStmtSource().value(),
3888         "Attribute 'EXTENDS' cannot be used more than once"_err_en_US);
3889   } else {
3890     derivedTypeInfo_.extends = &x.v;
3891   }
3892   return false;
3893 }
3894 
Pre(const parser::PrivateStmt &)3895 bool DeclarationVisitor::Pre(const parser::PrivateStmt &) {
3896   if (!currScope().parent().IsModule()) {
3897     Say("PRIVATE is only allowed in a derived type that is"
3898         " in a module"_err_en_US); // C766
3899   } else if (derivedTypeInfo_.sawContains) {
3900     derivedTypeInfo_.privateBindings = true;
3901   } else if (!derivedTypeInfo_.privateComps) {
3902     derivedTypeInfo_.privateComps = true;
3903   } else {
3904     Say("PRIVATE may not appear more than once in"
3905         " derived type components"_en_US); // C738
3906   }
3907   return false;
3908 }
Pre(const parser::SequenceStmt &)3909 bool DeclarationVisitor::Pre(const parser::SequenceStmt &) {
3910   if (derivedTypeInfo_.sequence) {
3911     Say("SEQUENCE may not appear more than once in"
3912         " derived type components"_en_US); // C738
3913   }
3914   derivedTypeInfo_.sequence = true;
3915   return false;
3916 }
Post(const parser::ComponentDecl & x)3917 void DeclarationVisitor::Post(const parser::ComponentDecl &x) {
3918   const auto &name{std::get<parser::Name>(x.t)};
3919   auto attrs{GetAttrs()};
3920   if (derivedTypeInfo_.privateComps &&
3921       !attrs.HasAny({Attr::PUBLIC, Attr::PRIVATE})) {
3922     attrs.set(Attr::PRIVATE);
3923   }
3924   if (const auto *declType{GetDeclTypeSpec()}) {
3925     if (const auto *derived{declType->AsDerived()}) {
3926       if (!attrs.HasAny({Attr::POINTER, Attr::ALLOCATABLE})) {
3927         if (derivedTypeInfo_.type == &derived->typeSymbol()) { // C744
3928           Say("Recursive use of the derived type requires "
3929               "POINTER or ALLOCATABLE"_err_en_US);
3930         }
3931       }
3932       if (!coarraySpec().empty()) { // C747
3933         if (IsTeamType(derived)) {
3934           Say("A coarray component may not be of type TEAM_TYPE from "
3935               "ISO_FORTRAN_ENV"_err_en_US);
3936         } else {
3937           if (IsIsoCType(derived)) {
3938             Say("A coarray component may not be of type C_PTR or C_FUNPTR from "
3939                 "ISO_C_BINDING"_err_en_US);
3940           }
3941         }
3942       }
3943       if (auto it{FindCoarrayUltimateComponent(*derived)}) { // C748
3944         std::string ultimateName{it.BuildResultDesignatorName()};
3945         // Strip off the leading "%"
3946         if (ultimateName.length() > 1) {
3947           ultimateName.erase(0, 1);
3948           if (attrs.HasAny({Attr::POINTER, Attr::ALLOCATABLE})) {
3949             evaluate::AttachDeclaration(
3950                 Say(name.source,
3951                     "A component with a POINTER or ALLOCATABLE attribute may "
3952                     "not "
3953                     "be of a type with a coarray ultimate component (named "
3954                     "'%s')"_err_en_US,
3955                     ultimateName),
3956                 derived->typeSymbol());
3957           }
3958           if (!arraySpec().empty() || !coarraySpec().empty()) {
3959             evaluate::AttachDeclaration(
3960                 Say(name.source,
3961                     "An array or coarray component may not be of a type with a "
3962                     "coarray ultimate component (named '%s')"_err_en_US,
3963                     ultimateName),
3964                 derived->typeSymbol());
3965           }
3966         }
3967       }
3968     }
3969   }
3970   if (OkToAddComponent(name)) {
3971     auto &symbol{DeclareObjectEntity(name, attrs)};
3972     if (symbol.has<ObjectEntityDetails>()) {
3973       if (auto &init{std::get<std::optional<parser::Initialization>>(x.t)}) {
3974         Initialization(name, *init, true);
3975       }
3976     }
3977     currScope().symbol()->get<DerivedTypeDetails>().add_component(symbol);
3978   }
3979   ClearArraySpec();
3980   ClearCoarraySpec();
3981 }
Pre(const parser::ProcedureDeclarationStmt &)3982 bool DeclarationVisitor::Pre(const parser::ProcedureDeclarationStmt &) {
3983   CHECK(!interfaceName_);
3984   return BeginDecl();
3985 }
Post(const parser::ProcedureDeclarationStmt &)3986 void DeclarationVisitor::Post(const parser::ProcedureDeclarationStmt &) {
3987   interfaceName_ = nullptr;
3988   EndDecl();
3989 }
Pre(const parser::DataComponentDefStmt & x)3990 bool DeclarationVisitor::Pre(const parser::DataComponentDefStmt &x) {
3991   // Overrides parse tree traversal so as to handle attributes first,
3992   // so POINTER & ALLOCATABLE enable forward references to derived types.
3993   Walk(std::get<std::list<parser::ComponentAttrSpec>>(x.t));
3994   set_allowForwardReferenceToDerivedType(
3995       GetAttrs().HasAny({Attr::POINTER, Attr::ALLOCATABLE}));
3996   Walk(std::get<parser::DeclarationTypeSpec>(x.t));
3997   set_allowForwardReferenceToDerivedType(false);
3998   Walk(std::get<std::list<parser::ComponentDecl>>(x.t));
3999   return false;
4000 }
Pre(const parser::ProcComponentDefStmt &)4001 bool DeclarationVisitor::Pre(const parser::ProcComponentDefStmt &) {
4002   CHECK(!interfaceName_);
4003   return true;
4004 }
Post(const parser::ProcComponentDefStmt &)4005 void DeclarationVisitor::Post(const parser::ProcComponentDefStmt &) {
4006   interfaceName_ = nullptr;
4007 }
Pre(const parser::ProcPointerInit & x)4008 bool DeclarationVisitor::Pre(const parser::ProcPointerInit &x) {
4009   if (auto *name{std::get_if<parser::Name>(&x.u)}) {
4010     return !NameIsKnownOrIntrinsic(*name);
4011   }
4012   return true;
4013 }
Post(const parser::ProcInterface & x)4014 void DeclarationVisitor::Post(const parser::ProcInterface &x) {
4015   if (auto *name{std::get_if<parser::Name>(&x.u)}) {
4016     interfaceName_ = name;
4017     NoteInterfaceName(*name);
4018   }
4019 }
4020 
Post(const parser::ProcDecl & x)4021 void DeclarationVisitor::Post(const parser::ProcDecl &x) {
4022   const auto &name{std::get<parser::Name>(x.t)};
4023   ProcInterface interface;
4024   if (interfaceName_) {
4025     interface.set_symbol(*interfaceName_->symbol);
4026   } else if (auto *type{GetDeclTypeSpec()}) {
4027     interface.set_type(*type);
4028   }
4029   auto attrs{HandleSaveName(name.source, GetAttrs())};
4030   DerivedTypeDetails *dtDetails{nullptr};
4031   if (Symbol * symbol{currScope().symbol()}) {
4032     dtDetails = symbol->detailsIf<DerivedTypeDetails>();
4033   }
4034   if (!dtDetails) {
4035     attrs.set(Attr::EXTERNAL);
4036   }
4037   Symbol &symbol{DeclareProcEntity(name, attrs, interface)};
4038   symbol.ReplaceName(name.source);
4039   if (dtDetails) {
4040     dtDetails->add_component(symbol);
4041   }
4042 }
4043 
Pre(const parser::TypeBoundProcedurePart &)4044 bool DeclarationVisitor::Pre(const parser::TypeBoundProcedurePart &) {
4045   derivedTypeInfo_.sawContains = true;
4046   return true;
4047 }
4048 
4049 // Resolve binding names from type-bound generics, saved in genericBindings_.
Post(const parser::TypeBoundProcedurePart &)4050 void DeclarationVisitor::Post(const parser::TypeBoundProcedurePart &) {
4051   // track specifics seen for the current generic to detect duplicates:
4052   const Symbol *currGeneric{nullptr};
4053   std::set<SourceName> specifics;
4054   for (const auto &[generic, bindingName] : genericBindings_) {
4055     if (generic != currGeneric) {
4056       currGeneric = generic;
4057       specifics.clear();
4058     }
4059     auto [it, inserted]{specifics.insert(bindingName->source)};
4060     if (!inserted) {
4061       Say(*bindingName, // C773
4062           "Binding name '%s' was already specified for generic '%s'"_err_en_US,
4063           bindingName->source, generic->name())
4064           .Attach(*it, "Previous specification of '%s'"_en_US, *it);
4065       continue;
4066     }
4067     auto *symbol{FindInTypeOrParents(*bindingName)};
4068     if (!symbol) {
4069       Say(*bindingName, // C772
4070           "Binding name '%s' not found in this derived type"_err_en_US);
4071     } else if (!symbol->has<ProcBindingDetails>()) {
4072       SayWithDecl(*bindingName, *symbol, // C772
4073           "'%s' is not the name of a specific binding of this type"_err_en_US);
4074     } else {
4075       generic->get<GenericDetails>().AddSpecificProc(
4076           *symbol, bindingName->source);
4077     }
4078   }
4079   genericBindings_.clear();
4080 }
4081 
Post(const parser::ContainsStmt &)4082 void DeclarationVisitor::Post(const parser::ContainsStmt &) {
4083   if (derivedTypeInfo_.sequence) {
4084     Say("A sequence type may not have a CONTAINS statement"_err_en_US); // C740
4085   }
4086 }
4087 
Post(const parser::TypeBoundProcedureStmt::WithoutInterface & x)4088 void DeclarationVisitor::Post(
4089     const parser::TypeBoundProcedureStmt::WithoutInterface &x) {
4090   if (GetAttrs().test(Attr::DEFERRED)) { // C783
4091     Say("DEFERRED is only allowed when an interface-name is provided"_err_en_US);
4092   }
4093   for (auto &declaration : x.declarations) {
4094     auto &bindingName{std::get<parser::Name>(declaration.t)};
4095     auto &optName{std::get<std::optional<parser::Name>>(declaration.t)};
4096     const parser::Name &procedureName{optName ? *optName : bindingName};
4097     Symbol *procedure{FindSymbol(procedureName)};
4098     if (!procedure) {
4099       procedure = NoteInterfaceName(procedureName);
4100     }
4101     if (auto *s{MakeTypeSymbol(bindingName, ProcBindingDetails{*procedure})}) {
4102       SetPassNameOn(*s);
4103       if (GetAttrs().test(Attr::DEFERRED)) {
4104         context().SetError(*s);
4105       }
4106     }
4107   }
4108 }
4109 
CheckBindings(const parser::TypeBoundProcedureStmt::WithoutInterface & tbps)4110 void DeclarationVisitor::CheckBindings(
4111     const parser::TypeBoundProcedureStmt::WithoutInterface &tbps) {
4112   CHECK(currScope().IsDerivedType());
4113   for (auto &declaration : tbps.declarations) {
4114     auto &bindingName{std::get<parser::Name>(declaration.t)};
4115     if (Symbol * binding{FindInScope(bindingName)}) {
4116       if (auto *details{binding->detailsIf<ProcBindingDetails>()}) {
4117         const Symbol *procedure{FindSubprogram(details->symbol())};
4118         if (!CanBeTypeBoundProc(procedure)) {
4119           if (details->symbol().name() != binding->name()) {
4120             Say(binding->name(),
4121                 "The binding of '%s' ('%s') must be either an accessible "
4122                 "module procedure or an external procedure with "
4123                 "an explicit interface"_err_en_US,
4124                 binding->name(), details->symbol().name());
4125           } else {
4126             Say(binding->name(),
4127                 "'%s' must be either an accessible module procedure "
4128                 "or an external procedure with an explicit interface"_err_en_US,
4129                 binding->name());
4130           }
4131           context().SetError(*binding);
4132         }
4133       }
4134     }
4135   }
4136 }
4137 
Post(const parser::TypeBoundProcedureStmt::WithInterface & x)4138 void DeclarationVisitor::Post(
4139     const parser::TypeBoundProcedureStmt::WithInterface &x) {
4140   if (!GetAttrs().test(Attr::DEFERRED)) { // C783
4141     Say("DEFERRED is required when an interface-name is provided"_err_en_US);
4142   }
4143   if (Symbol * interface{NoteInterfaceName(x.interfaceName)}) {
4144     for (auto &bindingName : x.bindingNames) {
4145       if (auto *s{
4146               MakeTypeSymbol(bindingName, ProcBindingDetails{*interface})}) {
4147         SetPassNameOn(*s);
4148         if (!GetAttrs().test(Attr::DEFERRED)) {
4149           context().SetError(*s);
4150         }
4151       }
4152     }
4153   }
4154 }
4155 
Post(const parser::FinalProcedureStmt & x)4156 void DeclarationVisitor::Post(const parser::FinalProcedureStmt &x) {
4157   if (currScope().IsDerivedType() && currScope().symbol()) {
4158     if (auto *details{currScope().symbol()->detailsIf<DerivedTypeDetails>()}) {
4159       for (const auto &subrName : x.v) {
4160         if (const auto *name{ResolveName(subrName)}) {
4161           auto pair{
4162               details->finals().emplace(name->source, DEREF(name->symbol))};
4163           if (!pair.second) { // C787
4164             Say(name->source,
4165                 "FINAL subroutine '%s' already appeared in this derived type"_err_en_US,
4166                 name->source)
4167                 .Attach(pair.first->first,
4168                     "earlier appearance of this FINAL subroutine"_en_US);
4169           }
4170         }
4171       }
4172     }
4173   }
4174 }
4175 
Pre(const parser::TypeBoundGenericStmt & x)4176 bool DeclarationVisitor::Pre(const parser::TypeBoundGenericStmt &x) {
4177   const auto &accessSpec{std::get<std::optional<parser::AccessSpec>>(x.t)};
4178   const auto &genericSpec{std::get<Indirection<parser::GenericSpec>>(x.t)};
4179   const auto &bindingNames{std::get<std::list<parser::Name>>(x.t)};
4180   auto info{GenericSpecInfo{genericSpec.value()}};
4181   SourceName symbolName{info.symbolName()};
4182   bool isPrivate{accessSpec ? accessSpec->v == parser::AccessSpec::Kind::Private
4183                             : derivedTypeInfo_.privateBindings};
4184   auto *genericSymbol{FindInScope(symbolName)};
4185   if (genericSymbol) {
4186     if (!genericSymbol->has<GenericDetails>()) {
4187       genericSymbol = nullptr; // MakeTypeSymbol will report the error below
4188     }
4189   } else {
4190     // look in parent types:
4191     Symbol *inheritedSymbol{nullptr};
4192     for (const auto &name : GetAllNames(context(), symbolName)) {
4193       inheritedSymbol = currScope().FindComponent(SourceName{name});
4194       if (inheritedSymbol) {
4195         break;
4196       }
4197     }
4198     if (inheritedSymbol && inheritedSymbol->has<GenericDetails>()) {
4199       CheckAccessibility(symbolName, isPrivate, *inheritedSymbol); // C771
4200     }
4201   }
4202   if (genericSymbol) {
4203     CheckAccessibility(symbolName, isPrivate, *genericSymbol); // C771
4204   } else {
4205     genericSymbol = MakeTypeSymbol(symbolName, GenericDetails{});
4206     if (!genericSymbol) {
4207       return false;
4208     }
4209     if (isPrivate) {
4210       genericSymbol->attrs().set(Attr::PRIVATE);
4211     }
4212   }
4213   for (const parser::Name &bindingName : bindingNames) {
4214     genericBindings_.emplace(genericSymbol, &bindingName);
4215   }
4216   info.Resolve(genericSymbol);
4217   return false;
4218 }
4219 
Pre(const parser::AllocateStmt &)4220 bool DeclarationVisitor::Pre(const parser::AllocateStmt &) {
4221   BeginDeclTypeSpec();
4222   return true;
4223 }
Post(const parser::AllocateStmt &)4224 void DeclarationVisitor::Post(const parser::AllocateStmt &) {
4225   EndDeclTypeSpec();
4226 }
4227 
Pre(const parser::StructureConstructor & x)4228 bool DeclarationVisitor::Pre(const parser::StructureConstructor &x) {
4229   auto &parsedType{std::get<parser::DerivedTypeSpec>(x.t)};
4230   const DeclTypeSpec *type{ProcessTypeSpec(parsedType)};
4231   if (!type) {
4232     return false;
4233   }
4234   const DerivedTypeSpec *spec{type->AsDerived()};
4235   const Scope *typeScope{spec ? spec->scope() : nullptr};
4236   if (!typeScope) {
4237     return false;
4238   }
4239 
4240   // N.B C7102 is implicitly enforced by having inaccessible types not
4241   // being found in resolution.
4242   // More constraints are enforced in expression.cpp so that they
4243   // can apply to structure constructors that have been converted
4244   // from misparsed function references.
4245   for (const auto &component :
4246       std::get<std::list<parser::ComponentSpec>>(x.t)) {
4247     // Visit the component spec expression, but not the keyword, since
4248     // we need to resolve its symbol in the scope of the derived type.
4249     Walk(std::get<parser::ComponentDataSource>(component.t));
4250     if (const auto &kw{std::get<std::optional<parser::Keyword>>(component.t)}) {
4251       FindInTypeOrParents(*typeScope, kw->v);
4252     }
4253   }
4254   return false;
4255 }
4256 
Pre(const parser::BasedPointerStmt & x)4257 bool DeclarationVisitor::Pre(const parser::BasedPointerStmt &x) {
4258   for (const parser::BasedPointer &bp : x.v) {
4259     const parser::ObjectName &pointerName{std::get<0>(bp.t)};
4260     const parser::ObjectName &pointeeName{std::get<1>(bp.t)};
4261     auto *pointer{FindSymbol(pointerName)};
4262     if (!pointer) {
4263       pointer = &MakeSymbol(pointerName, ObjectEntityDetails{});
4264     } else if (!ConvertToObjectEntity(*pointer) || IsNamedConstant(*pointer)) {
4265       SayWithDecl(pointerName, *pointer, "'%s' is not a variable"_err_en_US);
4266     } else if (pointer->Rank() > 0) {
4267       SayWithDecl(pointerName, *pointer,
4268           "Cray pointer '%s' must be a scalar"_err_en_US);
4269     } else if (pointer->test(Symbol::Flag::CrayPointee)) {
4270       Say(pointerName,
4271           "'%s' cannot be a Cray pointer as it is already a Cray pointee"_err_en_US);
4272     }
4273     pointer->set(Symbol::Flag::CrayPointer);
4274     const DeclTypeSpec &pointerType{MakeNumericType(TypeCategory::Integer,
4275         context().defaultKinds().subscriptIntegerKind())};
4276     const auto *type{pointer->GetType()};
4277     if (!type) {
4278       pointer->SetType(pointerType);
4279     } else if (*type != pointerType) {
4280       Say(pointerName.source, "Cray pointer '%s' must have type %s"_err_en_US,
4281           pointerName.source, pointerType.AsFortran());
4282     }
4283     if (ResolveName(pointeeName)) {
4284       Symbol &pointee{*pointeeName.symbol};
4285       if (pointee.has<UseDetails>()) {
4286         Say(pointeeName,
4287             "'%s' cannot be a Cray pointee as it is use-associated"_err_en_US);
4288         continue;
4289       } else if (!ConvertToObjectEntity(pointee) || IsNamedConstant(pointee)) {
4290         Say(pointeeName, "'%s' is not a variable"_err_en_US);
4291         continue;
4292       } else if (pointee.test(Symbol::Flag::CrayPointer)) {
4293         Say(pointeeName,
4294             "'%s' cannot be a Cray pointee as it is already a Cray pointer"_err_en_US);
4295       } else if (pointee.test(Symbol::Flag::CrayPointee)) {
4296         Say(pointeeName,
4297             "'%s' was already declared as a Cray pointee"_err_en_US);
4298       } else {
4299         pointee.set(Symbol::Flag::CrayPointee);
4300       }
4301       if (const auto *pointeeType{pointee.GetType()}) {
4302         if (const auto *derived{pointeeType->AsDerived()}) {
4303           if (!derived->typeSymbol().get<DerivedTypeDetails>().sequence()) {
4304             Say(pointeeName,
4305                 "Type of Cray pointee '%s' is a non-sequence derived type"_err_en_US);
4306           }
4307         }
4308       }
4309       // process the pointee array-spec, if present
4310       BeginArraySpec();
4311       Walk(std::get<std::optional<parser::ArraySpec>>(bp.t));
4312       const auto &spec{arraySpec()};
4313       if (!spec.empty()) {
4314         auto &details{pointee.get<ObjectEntityDetails>()};
4315         if (details.shape().empty()) {
4316           details.set_shape(spec);
4317         } else {
4318           SayWithDecl(pointeeName, pointee,
4319               "Array spec was already declared for '%s'"_err_en_US);
4320         }
4321       }
4322       ClearArraySpec();
4323       currScope().add_crayPointer(pointeeName.source, *pointer);
4324     }
4325   }
4326   return false;
4327 }
4328 
Pre(const parser::NamelistStmt::Group & x)4329 bool DeclarationVisitor::Pre(const parser::NamelistStmt::Group &x) {
4330   if (!CheckNotInBlock("NAMELIST")) { // C1107
4331     return false;
4332   }
4333 
4334   NamelistDetails details;
4335   for (const auto &name : std::get<std::list<parser::Name>>(x.t)) {
4336     auto *symbol{FindSymbol(name)};
4337     if (!symbol) {
4338       symbol = &MakeSymbol(name, ObjectEntityDetails{});
4339       ApplyImplicitRules(*symbol);
4340     } else if (!ConvertToObjectEntity(*symbol)) {
4341       SayWithDecl(name, *symbol, "'%s' is not a variable"_err_en_US);
4342     }
4343     symbol->GetUltimate().set(Symbol::Flag::InNamelist);
4344     details.add_object(*symbol);
4345   }
4346 
4347   const auto &groupName{std::get<parser::Name>(x.t)};
4348   auto *groupSymbol{FindInScope(groupName)};
4349   if (!groupSymbol || !groupSymbol->has<NamelistDetails>()) {
4350     groupSymbol = &MakeSymbol(groupName, std::move(details));
4351     groupSymbol->ReplaceName(groupName.source);
4352   }
4353   groupSymbol->get<NamelistDetails>().add_objects(details.objects());
4354   return false;
4355 }
4356 
Pre(const parser::IoControlSpec & x)4357 bool DeclarationVisitor::Pre(const parser::IoControlSpec &x) {
4358   if (const auto *name{std::get_if<parser::Name>(&x.u)}) {
4359     auto *symbol{FindSymbol(*name)};
4360     if (!symbol) {
4361       Say(*name, "Namelist group '%s' not found"_err_en_US);
4362     } else if (!symbol->GetUltimate().has<NamelistDetails>()) {
4363       SayWithDecl(
4364           *name, *symbol, "'%s' is not the name of a namelist group"_err_en_US);
4365     }
4366   }
4367   return true;
4368 }
4369 
Pre(const parser::CommonStmt::Block & x)4370 bool DeclarationVisitor::Pre(const parser::CommonStmt::Block &x) {
4371   CheckNotInBlock("COMMON"); // C1107
4372   return true;
4373 }
4374 
Pre(const parser::CommonBlockObject &)4375 bool DeclarationVisitor::Pre(const parser::CommonBlockObject &) {
4376   BeginArraySpec();
4377   return true;
4378 }
4379 
Post(const parser::CommonBlockObject & x)4380 void DeclarationVisitor::Post(const parser::CommonBlockObject &x) {
4381   const auto &name{std::get<parser::Name>(x.t)};
4382   DeclareObjectEntity(name);
4383   auto pair{commonBlockObjects_.insert(name.source)};
4384   if (!pair.second) {
4385     const SourceName &prev{*pair.first};
4386     Say2(name.source, "'%s' is already in a COMMON block"_err_en_US, prev,
4387         "Previous occurrence of '%s' in a COMMON block"_en_US);
4388   }
4389 }
4390 
Pre(const parser::EquivalenceStmt & x)4391 bool DeclarationVisitor::Pre(const parser::EquivalenceStmt &x) {
4392   // save equivalence sets to be processed after specification part
4393   if (CheckNotInBlock("EQUIVALENCE")) { // C1107
4394     for (const std::list<parser::EquivalenceObject> &set : x.v) {
4395       equivalenceSets_.push_back(&set);
4396     }
4397   }
4398   return false; // don't implicitly declare names yet
4399 }
4400 
CheckEquivalenceSets()4401 void DeclarationVisitor::CheckEquivalenceSets() {
4402   EquivalenceSets equivSets{context()};
4403   inEquivalenceStmt_ = true;
4404   for (const auto *set : equivalenceSets_) {
4405     const auto &source{set->front().v.value().source};
4406     if (set->size() <= 1) { // R871
4407       Say(source, "Equivalence set must have more than one object"_err_en_US);
4408     }
4409     for (const parser::EquivalenceObject &object : *set) {
4410       const auto &designator{object.v.value()};
4411       // The designator was not resolved when it was encountered so do it now.
4412       // AnalyzeExpr causes array sections to be changed to substrings as needed
4413       Walk(designator);
4414       if (AnalyzeExpr(context(), designator)) {
4415         equivSets.AddToSet(designator);
4416       }
4417     }
4418     equivSets.FinishSet(source);
4419   }
4420   inEquivalenceStmt_ = false;
4421   for (auto &set : equivSets.sets()) {
4422     if (!set.empty()) {
4423       currScope().add_equivalenceSet(std::move(set));
4424     }
4425   }
4426   equivalenceSets_.clear();
4427 }
4428 
Pre(const parser::SaveStmt & x)4429 bool DeclarationVisitor::Pre(const parser::SaveStmt &x) {
4430   if (x.v.empty()) {
4431     saveInfo_.saveAll = currStmtSource();
4432     currScope().set_hasSAVE();
4433   } else {
4434     for (const parser::SavedEntity &y : x.v) {
4435       auto kind{std::get<parser::SavedEntity::Kind>(y.t)};
4436       const auto &name{std::get<parser::Name>(y.t)};
4437       if (kind == parser::SavedEntity::Kind::Common) {
4438         MakeCommonBlockSymbol(name);
4439         AddSaveName(saveInfo_.commons, name.source);
4440       } else {
4441         HandleAttributeStmt(Attr::SAVE, name);
4442       }
4443     }
4444   }
4445   return false;
4446 }
4447 
CheckSaveStmts()4448 void DeclarationVisitor::CheckSaveStmts() {
4449   for (const SourceName &name : saveInfo_.entities) {
4450     auto *symbol{FindInScope(name)};
4451     if (!symbol) {
4452       // error was reported
4453     } else if (saveInfo_.saveAll) {
4454       // C889 - note that pgi, ifort, xlf do not enforce this constraint
4455       Say2(name,
4456           "Explicit SAVE of '%s' is redundant due to global SAVE statement"_err_en_US,
4457           *saveInfo_.saveAll, "Global SAVE statement"_en_US);
4458     } else if (auto msg{CheckSaveAttr(*symbol)}) {
4459       Say(name, std::move(*msg));
4460       context().SetError(*symbol);
4461     } else {
4462       SetSaveAttr(*symbol);
4463     }
4464   }
4465   for (const SourceName &name : saveInfo_.commons) {
4466     if (auto *symbol{currScope().FindCommonBlock(name)}) {
4467       auto &objects{symbol->get<CommonBlockDetails>().objects()};
4468       if (objects.empty()) {
4469         if (currScope().kind() != Scope::Kind::Block) {
4470           Say(name,
4471               "'%s' appears as a COMMON block in a SAVE statement but not in"
4472               " a COMMON statement"_err_en_US);
4473         } else { // C1108
4474           Say(name,
4475               "SAVE statement in BLOCK construct may not contain a"
4476               " common block name '%s'"_err_en_US);
4477         }
4478       } else {
4479         for (auto &object : symbol->get<CommonBlockDetails>().objects()) {
4480           SetSaveAttr(*object);
4481         }
4482       }
4483     }
4484   }
4485   if (saveInfo_.saveAll) {
4486     // Apply SAVE attribute to applicable symbols
4487     for (auto pair : currScope()) {
4488       auto &symbol{*pair.second};
4489       if (!CheckSaveAttr(symbol)) {
4490         SetSaveAttr(symbol);
4491       }
4492     }
4493   }
4494   saveInfo_ = {};
4495 }
4496 
4497 // If SAVE attribute can't be set on symbol, return error message.
CheckSaveAttr(const Symbol & symbol)4498 std::optional<MessageFixedText> DeclarationVisitor::CheckSaveAttr(
4499     const Symbol &symbol) {
4500   if (IsDummy(symbol)) {
4501     return "SAVE attribute may not be applied to dummy argument '%s'"_err_en_US;
4502   } else if (symbol.IsFuncResult()) {
4503     return "SAVE attribute may not be applied to function result '%s'"_err_en_US;
4504   } else if (symbol.has<ProcEntityDetails>() &&
4505       !symbol.attrs().test(Attr::POINTER)) {
4506     return "Procedure '%s' with SAVE attribute must also have POINTER attribute"_err_en_US;
4507   } else if (IsAutomatic(symbol)) {
4508     return "SAVE attribute may not be applied to automatic data object '%s'"_err_en_US;
4509   } else {
4510     return std::nullopt;
4511   }
4512 }
4513 
4514 // Record SAVEd names in saveInfo_.entities.
HandleSaveName(const SourceName & name,Attrs attrs)4515 Attrs DeclarationVisitor::HandleSaveName(const SourceName &name, Attrs attrs) {
4516   if (attrs.test(Attr::SAVE)) {
4517     AddSaveName(saveInfo_.entities, name);
4518   }
4519   return attrs;
4520 }
4521 
4522 // Record a name in a set of those to be saved.
AddSaveName(std::set<SourceName> & set,const SourceName & name)4523 void DeclarationVisitor::AddSaveName(
4524     std::set<SourceName> &set, const SourceName &name) {
4525   auto pair{set.insert(name)};
4526   if (!pair.second) {
4527     Say2(name, "SAVE attribute was already specified on '%s'"_err_en_US,
4528         *pair.first, "Previous specification of SAVE attribute"_en_US);
4529   }
4530 }
4531 
4532 // Set the SAVE attribute on symbol unless it is implicitly saved anyway.
SetSaveAttr(Symbol & symbol)4533 void DeclarationVisitor::SetSaveAttr(Symbol &symbol) {
4534   if (!IsSaved(symbol)) {
4535     symbol.attrs().set(Attr::SAVE);
4536   }
4537 }
4538 
4539 // Check types of common block objects, now that they are known.
CheckCommonBlocks()4540 void DeclarationVisitor::CheckCommonBlocks() {
4541   // check for empty common blocks
4542   for (const auto &pair : currScope().commonBlocks()) {
4543     const auto &symbol{*pair.second};
4544     if (symbol.get<CommonBlockDetails>().objects().empty() &&
4545         symbol.attrs().test(Attr::BIND_C)) {
4546       Say(symbol.name(),
4547           "'%s' appears as a COMMON block in a BIND statement but not in"
4548           " a COMMON statement"_err_en_US);
4549     }
4550   }
4551   // check objects in common blocks
4552   for (const auto &name : commonBlockObjects_) {
4553     const auto *symbol{currScope().FindSymbol(name)};
4554     if (!symbol) {
4555       continue;
4556     }
4557     const auto &attrs{symbol->attrs()};
4558     if (attrs.test(Attr::ALLOCATABLE)) {
4559       Say(name,
4560           "ALLOCATABLE object '%s' may not appear in a COMMON block"_err_en_US);
4561     } else if (attrs.test(Attr::BIND_C)) {
4562       Say(name,
4563           "Variable '%s' with BIND attribute may not appear in a COMMON block"_err_en_US);
4564     } else if (IsDummy(*symbol)) {
4565       Say(name,
4566           "Dummy argument '%s' may not appear in a COMMON block"_err_en_US);
4567     } else if (symbol->IsFuncResult()) {
4568       Say(name,
4569           "Function result '%s' may not appear in a COMMON block"_err_en_US);
4570     } else if (const DeclTypeSpec * type{symbol->GetType()}) {
4571       if (type->category() == DeclTypeSpec::ClassStar) {
4572         Say(name,
4573             "Unlimited polymorphic pointer '%s' may not appear in a COMMON block"_err_en_US);
4574       } else if (const auto *derived{type->AsDerived()}) {
4575         auto &typeSymbol{derived->typeSymbol()};
4576         if (!typeSymbol.attrs().test(Attr::BIND_C) &&
4577             !typeSymbol.get<DerivedTypeDetails>().sequence()) {
4578           Say(name,
4579               "Derived type '%s' in COMMON block must have the BIND or"
4580               " SEQUENCE attribute"_err_en_US);
4581         }
4582         CheckCommonBlockDerivedType(name, typeSymbol);
4583       }
4584     }
4585   }
4586   commonBlockObjects_ = {};
4587 }
4588 
MakeCommonBlockSymbol(const parser::Name & name)4589 Symbol &DeclarationVisitor::MakeCommonBlockSymbol(const parser::Name &name) {
4590   return Resolve(name, currScope().MakeCommonBlock(name.source));
4591 }
MakeCommonBlockSymbol(const std::optional<parser::Name> & name)4592 Symbol &DeclarationVisitor::MakeCommonBlockSymbol(
4593     const std::optional<parser::Name> &name) {
4594   if (name) {
4595     return MakeCommonBlockSymbol(*name);
4596   } else {
4597     return MakeCommonBlockSymbol(parser::Name{});
4598   }
4599 }
4600 
NameIsKnownOrIntrinsic(const parser::Name & name)4601 bool DeclarationVisitor::NameIsKnownOrIntrinsic(const parser::Name &name) {
4602   return FindSymbol(name) || HandleUnrestrictedSpecificIntrinsicFunction(name);
4603 }
4604 
4605 // Check if this derived type can be in a COMMON block.
CheckCommonBlockDerivedType(const SourceName & name,const Symbol & typeSymbol)4606 void DeclarationVisitor::CheckCommonBlockDerivedType(
4607     const SourceName &name, const Symbol &typeSymbol) {
4608   if (const auto *scope{typeSymbol.scope()}) {
4609     for (const auto &pair : *scope) {
4610       const Symbol &component{*pair.second};
4611       if (component.attrs().test(Attr::ALLOCATABLE)) {
4612         Say2(name,
4613             "Derived type variable '%s' may not appear in a COMMON block"
4614             " due to ALLOCATABLE component"_err_en_US,
4615             component.name(), "Component with ALLOCATABLE attribute"_en_US);
4616         return;
4617       }
4618       if (const auto *details{component.detailsIf<ObjectEntityDetails>()}) {
4619         if (details->init()) {
4620           Say2(name,
4621               "Derived type variable '%s' may not appear in a COMMON block"
4622               " due to component with default initialization"_err_en_US,
4623               component.name(), "Component with default initialization"_en_US);
4624           return;
4625         }
4626         if (const auto *type{details->type()}) {
4627           if (const auto *derived{type->AsDerived()}) {
4628             CheckCommonBlockDerivedType(name, derived->typeSymbol());
4629           }
4630         }
4631       }
4632     }
4633   }
4634 }
4635 
HandleUnrestrictedSpecificIntrinsicFunction(const parser::Name & name)4636 bool DeclarationVisitor::HandleUnrestrictedSpecificIntrinsicFunction(
4637     const parser::Name &name) {
4638   if (auto interface{context().intrinsics().IsSpecificIntrinsicFunction(
4639           name.source.ToString())}) {
4640     // Unrestricted specific intrinsic function names (e.g., "cos")
4641     // are acceptable as procedure interfaces.
4642     Symbol &symbol{
4643         MakeSymbol(InclusiveScope(), name.source, Attrs{Attr::INTRINSIC})};
4644     if (interface->IsElemental()) {
4645       symbol.attrs().set(Attr::ELEMENTAL);
4646     }
4647     symbol.set_details(ProcEntityDetails{});
4648     Resolve(name, symbol);
4649     return true;
4650   } else {
4651     return false;
4652   }
4653 }
4654 
4655 // Checks for all locality-specs: LOCAL, LOCAL_INIT, and SHARED
PassesSharedLocalityChecks(const parser::Name & name,Symbol & symbol)4656 bool DeclarationVisitor::PassesSharedLocalityChecks(
4657     const parser::Name &name, Symbol &symbol) {
4658   if (!IsVariableName(symbol)) {
4659     SayLocalMustBeVariable(name, symbol); // C1124
4660     return false;
4661   }
4662   if (symbol.owner() == currScope()) { // C1125 and C1126
4663     SayAlreadyDeclared(name, symbol);
4664     return false;
4665   }
4666   return true;
4667 }
4668 
4669 // Checks for locality-specs LOCAL and LOCAL_INIT
PassesLocalityChecks(const parser::Name & name,Symbol & symbol)4670 bool DeclarationVisitor::PassesLocalityChecks(
4671     const parser::Name &name, Symbol &symbol) {
4672   if (IsAllocatable(symbol)) { // C1128
4673     SayWithDecl(name, symbol,
4674         "ALLOCATABLE variable '%s' not allowed in a locality-spec"_err_en_US);
4675     return false;
4676   }
4677   if (IsOptional(symbol)) { // C1128
4678     SayWithDecl(name, symbol,
4679         "OPTIONAL argument '%s' not allowed in a locality-spec"_err_en_US);
4680     return false;
4681   }
4682   if (IsIntentIn(symbol)) { // C1128
4683     SayWithDecl(name, symbol,
4684         "INTENT IN argument '%s' not allowed in a locality-spec"_err_en_US);
4685     return false;
4686   }
4687   if (IsFinalizable(symbol)) { // C1128
4688     SayWithDecl(name, symbol,
4689         "Finalizable variable '%s' not allowed in a locality-spec"_err_en_US);
4690     return false;
4691   }
4692   if (IsCoarray(symbol)) { // C1128
4693     SayWithDecl(
4694         name, symbol, "Coarray '%s' not allowed in a locality-spec"_err_en_US);
4695     return false;
4696   }
4697   if (const DeclTypeSpec * type{symbol.GetType()}) {
4698     if (type->IsPolymorphic() && IsDummy(symbol) &&
4699         !IsPointer(symbol)) { // C1128
4700       SayWithDecl(name, symbol,
4701           "Nonpointer polymorphic argument '%s' not allowed in a "
4702           "locality-spec"_err_en_US);
4703       return false;
4704     }
4705   }
4706   if (IsAssumedSizeArray(symbol)) { // C1128
4707     SayWithDecl(name, symbol,
4708         "Assumed size array '%s' not allowed in a locality-spec"_err_en_US);
4709     return false;
4710   }
4711   if (std::optional<MessageFixedText> msg{
4712           WhyNotModifiable(symbol, currScope())}) {
4713     SayWithReason(name, symbol,
4714         "'%s' may not appear in a locality-spec because it is not "
4715         "definable"_err_en_US,
4716         std::move(*msg));
4717     return false;
4718   }
4719   return PassesSharedLocalityChecks(name, symbol);
4720 }
4721 
FindOrDeclareEnclosingEntity(const parser::Name & name)4722 Symbol &DeclarationVisitor::FindOrDeclareEnclosingEntity(
4723     const parser::Name &name) {
4724   Symbol *prev{FindSymbol(name)};
4725   if (!prev) {
4726     // Declare the name as an object in the enclosing scope so that
4727     // the name can't be repurposed there later as something else.
4728     prev = &MakeSymbol(InclusiveScope(), name.source, Attrs{});
4729     ConvertToObjectEntity(*prev);
4730     ApplyImplicitRules(*prev);
4731   }
4732   return *prev;
4733 }
4734 
DeclareLocalEntity(const parser::Name & name)4735 Symbol *DeclarationVisitor::DeclareLocalEntity(const parser::Name &name) {
4736   Symbol &prev{FindOrDeclareEnclosingEntity(name)};
4737   if (!PassesLocalityChecks(name, prev)) {
4738     return nullptr;
4739   }
4740   return &MakeHostAssocSymbol(name, prev);
4741 }
4742 
DeclareStatementEntity(const parser::Name & name,const std::optional<parser::IntegerTypeSpec> & type)4743 Symbol *DeclarationVisitor::DeclareStatementEntity(const parser::Name &name,
4744     const std::optional<parser::IntegerTypeSpec> &type) {
4745   const DeclTypeSpec *declTypeSpec{nullptr};
4746   if (auto *prev{FindSymbol(name)}) {
4747     if (prev->owner() == currScope()) {
4748       SayAlreadyDeclared(name, *prev);
4749       return nullptr;
4750     }
4751     name.symbol = nullptr;
4752     declTypeSpec = prev->GetType();
4753   }
4754   Symbol &symbol{DeclareEntity<ObjectEntityDetails>(name, {})};
4755   if (!symbol.has<ObjectEntityDetails>()) {
4756     return nullptr; // error was reported in DeclareEntity
4757   }
4758   if (type) {
4759     declTypeSpec = ProcessTypeSpec(*type);
4760   }
4761   if (declTypeSpec) {
4762     // Subtlety: Don't let a "*length" specifier (if any is pending) affect the
4763     // declaration of this implied DO loop control variable.
4764     auto restorer{
4765         common::ScopedSet(charInfo_.length, std::optional<ParamValue>{})};
4766     SetType(name, *declTypeSpec);
4767   } else {
4768     ApplyImplicitRules(symbol);
4769   }
4770   return Resolve(name, &symbol);
4771 }
4772 
4773 // Set the type of an entity or report an error.
SetType(const parser::Name & name,const DeclTypeSpec & type)4774 void DeclarationVisitor::SetType(
4775     const parser::Name &name, const DeclTypeSpec &type) {
4776   CHECK(name.symbol);
4777   auto &symbol{*name.symbol};
4778   if (charInfo_.length) { // Declaration has "*length" (R723)
4779     auto length{std::move(*charInfo_.length)};
4780     charInfo_.length.reset();
4781     if (type.category() == DeclTypeSpec::Character) {
4782       auto kind{type.characterTypeSpec().kind()};
4783       // Recurse with correct type.
4784       SetType(name,
4785           currScope().MakeCharacterType(std::move(length), std::move(kind)));
4786       return;
4787     } else { // C753
4788       Say(name,
4789           "A length specifier cannot be used to declare the non-character entity '%s'"_err_en_US);
4790     }
4791   }
4792   auto *prevType{symbol.GetType()};
4793   if (!prevType) {
4794     symbol.SetType(type);
4795   } else if (symbol.has<UseDetails>()) {
4796     // error recovery case, redeclaration of use-associated name
4797   } else if (HadForwardRef(symbol)) {
4798     // error recovery after use of host-associated name
4799   } else if (!symbol.test(Symbol::Flag::Implicit)) {
4800     SayWithDecl(
4801         name, symbol, "The type of '%s' has already been declared"_err_en_US);
4802     context().SetError(symbol);
4803   } else if (type != *prevType) {
4804     SayWithDecl(name, symbol,
4805         "The type of '%s' has already been implicitly declared"_err_en_US);
4806     context().SetError(symbol);
4807   } else {
4808     symbol.set(Symbol::Flag::Implicit, false);
4809   }
4810 }
4811 
ResolveDerivedType(const parser::Name & name)4812 std::optional<DerivedTypeSpec> DeclarationVisitor::ResolveDerivedType(
4813     const parser::Name &name) {
4814   Symbol *symbol{FindSymbol(NonDerivedTypeScope(), name)};
4815   if (!symbol || symbol->has<UnknownDetails>()) {
4816     if (allowForwardReferenceToDerivedType()) {
4817       if (!symbol) {
4818         symbol = &MakeSymbol(InclusiveScope(), name.source, Attrs{});
4819         Resolve(name, *symbol);
4820       };
4821       DerivedTypeDetails details;
4822       details.set_isForwardReferenced();
4823       symbol->set_details(std::move(details));
4824     } else { // C732
4825       Say(name, "Derived type '%s' not found"_err_en_US);
4826       return std::nullopt;
4827     }
4828   }
4829   if (CheckUseError(name)) {
4830     return std::nullopt;
4831   }
4832   symbol = &symbol->GetUltimate();
4833   if (auto *details{symbol->detailsIf<GenericDetails>()}) {
4834     if (details->derivedType()) {
4835       symbol = details->derivedType();
4836     }
4837   }
4838   if (symbol->has<DerivedTypeDetails>()) {
4839     return DerivedTypeSpec{name.source, *symbol};
4840   } else {
4841     Say(name, "'%s' is not a derived type"_err_en_US);
4842     return std::nullopt;
4843   }
4844 }
4845 
ResolveExtendsType(const parser::Name & typeName,const parser::Name * extendsName)4846 std::optional<DerivedTypeSpec> DeclarationVisitor::ResolveExtendsType(
4847     const parser::Name &typeName, const parser::Name *extendsName) {
4848   if (!extendsName) {
4849     return std::nullopt;
4850   } else if (typeName.source == extendsName->source) {
4851     Say(extendsName->source,
4852         "Derived type '%s' cannot extend itself"_err_en_US);
4853     return std::nullopt;
4854   } else {
4855     return ResolveDerivedType(*extendsName);
4856   }
4857 }
4858 
NoteInterfaceName(const parser::Name & name)4859 Symbol *DeclarationVisitor::NoteInterfaceName(const parser::Name &name) {
4860   // The symbol is checked later by CheckExplicitInterface() and
4861   // CheckBindings().  It can be a forward reference.
4862   if (!NameIsKnownOrIntrinsic(name)) {
4863     Symbol &symbol{MakeSymbol(InclusiveScope(), name.source, Attrs{})};
4864     Resolve(name, symbol);
4865   }
4866   return name.symbol;
4867 }
4868 
CheckExplicitInterface(const parser::Name & name)4869 void DeclarationVisitor::CheckExplicitInterface(const parser::Name &name) {
4870   if (const Symbol * symbol{name.symbol}) {
4871     if (!symbol->HasExplicitInterface()) {
4872       Say(name,
4873           "'%s' must be an abstract interface or a procedure with "
4874           "an explicit interface"_err_en_US,
4875           symbol->name());
4876     }
4877   }
4878 }
4879 
4880 // Create a symbol for a type parameter, component, or procedure binding in
4881 // the current derived type scope. Return false on error.
MakeTypeSymbol(const parser::Name & name,Details && details)4882 Symbol *DeclarationVisitor::MakeTypeSymbol(
4883     const parser::Name &name, Details &&details) {
4884   return Resolve(name, MakeTypeSymbol(name.source, std::move(details)));
4885 }
MakeTypeSymbol(const SourceName & name,Details && details)4886 Symbol *DeclarationVisitor::MakeTypeSymbol(
4887     const SourceName &name, Details &&details) {
4888   Scope &derivedType{currScope()};
4889   CHECK(derivedType.IsDerivedType());
4890   if (auto *symbol{FindInScope(derivedType, name)}) { // C742
4891     Say2(name,
4892         "Type parameter, component, or procedure binding '%s'"
4893         " already defined in this type"_err_en_US,
4894         *symbol, "Previous definition of '%s'"_en_US);
4895     return nullptr;
4896   } else {
4897     auto attrs{GetAttrs()};
4898     // Apply binding-private-stmt if present and this is a procedure binding
4899     if (derivedTypeInfo_.privateBindings &&
4900         !attrs.HasAny({Attr::PUBLIC, Attr::PRIVATE}) &&
4901         std::holds_alternative<ProcBindingDetails>(details)) {
4902       attrs.set(Attr::PRIVATE);
4903     }
4904     Symbol &result{MakeSymbol(name, attrs, std::move(details))};
4905     if (result.has<TypeParamDetails>()) {
4906       derivedType.symbol()->get<DerivedTypeDetails>().add_paramDecl(result);
4907     }
4908     return &result;
4909   }
4910 }
4911 
4912 // Return true if it is ok to declare this component in the current scope.
4913 // Otherwise, emit an error and return false.
OkToAddComponent(const parser::Name & name,const Symbol * extends)4914 bool DeclarationVisitor::OkToAddComponent(
4915     const parser::Name &name, const Symbol *extends) {
4916   for (const Scope *scope{&currScope()}; scope;) {
4917     CHECK(scope->IsDerivedType());
4918     if (auto *prev{FindInScope(*scope, name)}) {
4919       if (!context().HasError(*prev)) {
4920         auto msg{""_en_US};
4921         if (extends) {
4922           msg = "Type cannot be extended as it has a component named"
4923                 " '%s'"_err_en_US;
4924         } else if (prev->test(Symbol::Flag::ParentComp)) {
4925           msg = "'%s' is a parent type of this type and so cannot be"
4926                 " a component"_err_en_US;
4927         } else if (scope != &currScope()) {
4928           msg = "Component '%s' is already declared in a parent of this"
4929                 " derived type"_err_en_US;
4930         } else {
4931           msg = "Component '%s' is already declared in this"
4932                 " derived type"_err_en_US;
4933         }
4934         Say2(name, std::move(msg), *prev, "Previous declaration of '%s'"_en_US);
4935       }
4936       return false;
4937     }
4938     if (scope == &currScope() && extends) {
4939       // The parent component has not yet been added to the scope.
4940       scope = extends->scope();
4941     } else {
4942       scope = scope->GetDerivedTypeParent();
4943     }
4944   }
4945   return true;
4946 }
4947 
GetParamValue(const parser::TypeParamValue & x,common::TypeParamAttr attr)4948 ParamValue DeclarationVisitor::GetParamValue(
4949     const parser::TypeParamValue &x, common::TypeParamAttr attr) {
4950   return std::visit(
4951       common::visitors{
4952           [=](const parser::ScalarIntExpr &x) { // C704
4953             return ParamValue{EvaluateIntExpr(x), attr};
4954           },
4955           [=](const parser::Star &) { return ParamValue::Assumed(attr); },
4956           [=](const parser::TypeParamValue::Deferred &) {
4957             return ParamValue::Deferred(attr);
4958           },
4959       },
4960       x.u);
4961 }
4962 
4963 // ConstructVisitor implementation
4964 
ResolveIndexName(const parser::ConcurrentControl & control)4965 void ConstructVisitor::ResolveIndexName(
4966     const parser::ConcurrentControl &control) {
4967   const parser::Name &name{std::get<parser::Name>(control.t)};
4968   auto *prev{FindSymbol(name)};
4969   if (prev) {
4970     if (prev->owner().kind() == Scope::Kind::Forall ||
4971         prev->owner() == currScope()) {
4972       SayAlreadyDeclared(name, *prev);
4973       return;
4974     }
4975     name.symbol = nullptr;
4976   }
4977   auto &symbol{DeclareObjectEntity(name)};
4978   if (symbol.GetType()) {
4979     // type came from explicit type-spec
4980   } else if (!prev) {
4981     ApplyImplicitRules(symbol);
4982   } else {
4983     const Symbol &prevRoot{ResolveAssociations(*prev)};
4984     // prev could be host- use- or construct-associated with another symbol
4985     if (!prevRoot.has<ObjectEntityDetails>() &&
4986         !prevRoot.has<EntityDetails>()) {
4987       Say2(name, "Index name '%s' conflicts with existing identifier"_err_en_US,
4988           *prev, "Previous declaration of '%s'"_en_US);
4989       return;
4990     } else {
4991       if (const auto *type{prevRoot.GetType()}) {
4992         symbol.SetType(*type);
4993       }
4994       if (prevRoot.IsObjectArray()) {
4995         SayWithDecl(name, *prev, "Index variable '%s' is not scalar"_err_en_US);
4996         return;
4997       }
4998     }
4999   }
5000   EvaluateExpr(parser::Scalar{parser::Integer{common::Clone(name)}});
5001 }
5002 
5003 // We need to make sure that all of the index-names get declared before the
5004 // expressions in the loop control are evaluated so that references to the
5005 // index-names in the expressions are correctly detected.
Pre(const parser::ConcurrentHeader & header)5006 bool ConstructVisitor::Pre(const parser::ConcurrentHeader &header) {
5007   BeginDeclTypeSpec();
5008   Walk(std::get<std::optional<parser::IntegerTypeSpec>>(header.t));
5009   const auto &controls{
5010       std::get<std::list<parser::ConcurrentControl>>(header.t)};
5011   for (const auto &control : controls) {
5012     ResolveIndexName(control);
5013   }
5014   Walk(controls);
5015   Walk(std::get<std::optional<parser::ScalarLogicalExpr>>(header.t));
5016   EndDeclTypeSpec();
5017   return false;
5018 }
5019 
Pre(const parser::LocalitySpec::Local & x)5020 bool ConstructVisitor::Pre(const parser::LocalitySpec::Local &x) {
5021   for (auto &name : x.v) {
5022     if (auto *symbol{DeclareLocalEntity(name)}) {
5023       symbol->set(Symbol::Flag::LocalityLocal);
5024     }
5025   }
5026   return false;
5027 }
5028 
Pre(const parser::LocalitySpec::LocalInit & x)5029 bool ConstructVisitor::Pre(const parser::LocalitySpec::LocalInit &x) {
5030   for (auto &name : x.v) {
5031     if (auto *symbol{DeclareLocalEntity(name)}) {
5032       symbol->set(Symbol::Flag::LocalityLocalInit);
5033     }
5034   }
5035   return false;
5036 }
5037 
Pre(const parser::LocalitySpec::Shared & x)5038 bool ConstructVisitor::Pre(const parser::LocalitySpec::Shared &x) {
5039   for (const auto &name : x.v) {
5040     if (!FindSymbol(name)) {
5041       Say(name, "Variable '%s' with SHARED locality implicitly declared"_en_US);
5042     }
5043     Symbol &prev{FindOrDeclareEnclosingEntity(name)};
5044     if (PassesSharedLocalityChecks(name, prev)) {
5045       MakeHostAssocSymbol(name, prev).set(Symbol::Flag::LocalityShared);
5046     }
5047   }
5048   return false;
5049 }
5050 
Pre(const parser::AcSpec & x)5051 bool ConstructVisitor::Pre(const parser::AcSpec &x) {
5052   ProcessTypeSpec(x.type);
5053   PushScope(Scope::Kind::ImpliedDos, nullptr);
5054   Walk(x.values);
5055   PopScope();
5056   return false;
5057 }
5058 
5059 // Section 19.4, paragraph 5 says that each ac-do-variable has the scope of the
5060 // enclosing ac-implied-do
Pre(const parser::AcImpliedDo & x)5061 bool ConstructVisitor::Pre(const parser::AcImpliedDo &x) {
5062   auto &values{std::get<std::list<parser::AcValue>>(x.t)};
5063   auto &control{std::get<parser::AcImpliedDoControl>(x.t)};
5064   auto &type{std::get<std::optional<parser::IntegerTypeSpec>>(control.t)};
5065   auto &bounds{std::get<parser::AcImpliedDoControl::Bounds>(control.t)};
5066   PushScope(Scope::Kind::ImpliedDos, nullptr);
5067   DeclareStatementEntity(bounds.name.thing.thing, type);
5068   Walk(bounds);
5069   Walk(values);
5070   PopScope();
5071   return false;
5072 }
5073 
Pre(const parser::DataImpliedDo & x)5074 bool ConstructVisitor::Pre(const parser::DataImpliedDo &x) {
5075   auto &objects{std::get<std::list<parser::DataIDoObject>>(x.t)};
5076   auto &type{std::get<std::optional<parser::IntegerTypeSpec>>(x.t)};
5077   auto &bounds{std::get<parser::DataImpliedDo::Bounds>(x.t)};
5078   DeclareStatementEntity(bounds.name.thing.thing, type);
5079   Walk(bounds);
5080   Walk(objects);
5081   return false;
5082 }
5083 
5084 // Sets InDataStmt flag on a variable (or misidentified function) in a DATA
5085 // statement so that the predicate IsStaticallyInitialized() will be true
5086 // during semantic analysis before the symbol's initializer is constructed.
Pre(const parser::DataIDoObject & x)5087 bool ConstructVisitor::Pre(const parser::DataIDoObject &x) {
5088   std::visit(
5089       common::visitors{
5090           [&](const parser::Scalar<Indirection<parser::Designator>> &y) {
5091             Walk(y.thing.value());
5092             const parser::Name &first{parser::GetFirstName(y.thing.value())};
5093             if (first.symbol) {
5094               first.symbol->set(Symbol::Flag::InDataStmt);
5095             }
5096           },
5097           [&](const Indirection<parser::DataImpliedDo> &y) { Walk(y.value()); },
5098       },
5099       x.u);
5100   return false;
5101 }
5102 
Pre(const parser::DataStmtObject & x)5103 bool ConstructVisitor::Pre(const parser::DataStmtObject &x) {
5104   std::visit(common::visitors{
5105                  [&](const Indirection<parser::Variable> &y) {
5106                    Walk(y.value());
5107                    const parser::Name &first{parser::GetFirstName(y.value())};
5108                    if (first.symbol) {
5109                      first.symbol->set(Symbol::Flag::InDataStmt);
5110                    }
5111                  },
5112                  [&](const parser::DataImpliedDo &y) {
5113                    PushScope(Scope::Kind::ImpliedDos, nullptr);
5114                    Walk(y);
5115                    PopScope();
5116                  },
5117              },
5118       x.u);
5119   return false;
5120 }
5121 
Pre(const parser::DataStmtValue & x)5122 bool ConstructVisitor::Pre(const parser::DataStmtValue &x) {
5123   const auto &data{std::get<parser::DataStmtConstant>(x.t)};
5124   auto &mutableData{const_cast<parser::DataStmtConstant &>(data)};
5125   if (auto *elem{parser::Unwrap<parser::ArrayElement>(mutableData)}) {
5126     if (const auto *name{std::get_if<parser::Name>(&elem->base.u)}) {
5127       if (const Symbol * symbol{FindSymbol(*name)}) {
5128         const Symbol &ultimate{symbol->GetUltimate()};
5129         if (ultimate.has<DerivedTypeDetails>()) {
5130           mutableData.u = elem->ConvertToStructureConstructor(
5131               DerivedTypeSpec{name->source, ultimate});
5132         }
5133       }
5134     }
5135   }
5136   return true;
5137 }
5138 
Pre(const parser::DoConstruct & x)5139 bool ConstructVisitor::Pre(const parser::DoConstruct &x) {
5140   if (x.IsDoConcurrent()) {
5141     PushScope(Scope::Kind::Block, nullptr);
5142   }
5143   return true;
5144 }
Post(const parser::DoConstruct & x)5145 void ConstructVisitor::Post(const parser::DoConstruct &x) {
5146   if (x.IsDoConcurrent()) {
5147     PopScope();
5148   }
5149 }
5150 
Pre(const parser::ForallConstruct &)5151 bool ConstructVisitor::Pre(const parser::ForallConstruct &) {
5152   PushScope(Scope::Kind::Forall, nullptr);
5153   return true;
5154 }
Post(const parser::ForallConstruct &)5155 void ConstructVisitor::Post(const parser::ForallConstruct &) { PopScope(); }
Pre(const parser::ForallStmt &)5156 bool ConstructVisitor::Pre(const parser::ForallStmt &) {
5157   PushScope(Scope::Kind::Forall, nullptr);
5158   return true;
5159 }
Post(const parser::ForallStmt &)5160 void ConstructVisitor::Post(const parser::ForallStmt &) { PopScope(); }
5161 
Pre(const parser::BlockStmt & x)5162 bool ConstructVisitor::Pre(const parser::BlockStmt &x) {
5163   CheckDef(x.v);
5164   PushScope(Scope::Kind::Block, nullptr);
5165   return false;
5166 }
Pre(const parser::EndBlockStmt & x)5167 bool ConstructVisitor::Pre(const parser::EndBlockStmt &x) {
5168   PopScope();
5169   CheckRef(x.v);
5170   return false;
5171 }
5172 
Post(const parser::Selector & x)5173 void ConstructVisitor::Post(const parser::Selector &x) {
5174   GetCurrentAssociation().selector = ResolveSelector(x);
5175 }
5176 
Post(const parser::AssociateStmt & x)5177 void ConstructVisitor::Post(const parser::AssociateStmt &x) {
5178   CheckDef(x.t);
5179   PushScope(Scope::Kind::Block, nullptr);
5180   const auto assocCount{std::get<std::list<parser::Association>>(x.t).size()};
5181   for (auto nthLastAssoc{assocCount}; nthLastAssoc > 0; --nthLastAssoc) {
5182     SetCurrentAssociation(nthLastAssoc);
5183     if (auto *symbol{MakeAssocEntity()}) {
5184       if (ExtractCoarrayRef(GetCurrentAssociation().selector.expr)) { // C1103
5185         Say("Selector must not be a coindexed object"_err_en_US);
5186       }
5187       SetTypeFromAssociation(*symbol);
5188       SetAttrsFromAssociation(*symbol);
5189     }
5190   }
5191   PopAssociation(assocCount);
5192 }
5193 
Post(const parser::EndAssociateStmt & x)5194 void ConstructVisitor::Post(const parser::EndAssociateStmt &x) {
5195   PopScope();
5196   CheckRef(x.v);
5197 }
5198 
Pre(const parser::Association & x)5199 bool ConstructVisitor::Pre(const parser::Association &x) {
5200   PushAssociation();
5201   const auto &name{std::get<parser::Name>(x.t)};
5202   GetCurrentAssociation().name = &name;
5203   return true;
5204 }
5205 
Pre(const parser::ChangeTeamStmt & x)5206 bool ConstructVisitor::Pre(const parser::ChangeTeamStmt &x) {
5207   CheckDef(x.t);
5208   PushScope(Scope::Kind::Block, nullptr);
5209   PushAssociation();
5210   return true;
5211 }
5212 
Post(const parser::CoarrayAssociation & x)5213 void ConstructVisitor::Post(const parser::CoarrayAssociation &x) {
5214   const auto &decl{std::get<parser::CodimensionDecl>(x.t)};
5215   const auto &name{std::get<parser::Name>(decl.t)};
5216   if (auto *symbol{FindInScope(name)}) {
5217     const auto &selector{std::get<parser::Selector>(x.t)};
5218     if (auto sel{ResolveSelector(selector)}) {
5219       const Symbol *whole{UnwrapWholeSymbolDataRef(sel.expr)};
5220       if (!whole || whole->Corank() == 0) {
5221         Say(sel.source, // C1116
5222             "Selector in coarray association must name a coarray"_err_en_US);
5223       } else if (auto dynType{sel.expr->GetType()}) {
5224         if (!symbol->GetType()) {
5225           symbol->SetType(ToDeclTypeSpec(std::move(*dynType)));
5226         }
5227       }
5228     }
5229   }
5230 }
5231 
Post(const parser::EndChangeTeamStmt & x)5232 void ConstructVisitor::Post(const parser::EndChangeTeamStmt &x) {
5233   PopAssociation();
5234   PopScope();
5235   CheckRef(x.t);
5236 }
5237 
Pre(const parser::SelectTypeConstruct &)5238 bool ConstructVisitor::Pre(const parser::SelectTypeConstruct &) {
5239   PushAssociation();
5240   return true;
5241 }
5242 
Post(const parser::SelectTypeConstruct &)5243 void ConstructVisitor::Post(const parser::SelectTypeConstruct &) {
5244   PopAssociation();
5245 }
5246 
Post(const parser::SelectTypeStmt & x)5247 void ConstructVisitor::Post(const parser::SelectTypeStmt &x) {
5248   auto &association{GetCurrentAssociation()};
5249   if (const std::optional<parser::Name> &name{std::get<1>(x.t)}) {
5250     // This isn't a name in the current scope, it is in each TypeGuardStmt
5251     MakePlaceholder(*name, MiscDetails::Kind::SelectTypeAssociateName);
5252     association.name = &*name;
5253     auto exprType{association.selector.expr->GetType()};
5254     if (ExtractCoarrayRef(association.selector.expr)) { // C1103
5255       Say("Selector must not be a coindexed object"_err_en_US);
5256     }
5257     if (exprType && !exprType->IsPolymorphic()) { // C1159
5258       Say(association.selector.source,
5259           "Selector '%s' in SELECT TYPE statement must be "
5260           "polymorphic"_err_en_US);
5261     }
5262   } else {
5263     if (const Symbol *
5264         whole{UnwrapWholeSymbolDataRef(association.selector.expr)}) {
5265       ConvertToObjectEntity(const_cast<Symbol &>(*whole));
5266       if (!IsVariableName(*whole)) {
5267         Say(association.selector.source, // C901
5268             "Selector is not a variable"_err_en_US);
5269         association = {};
5270       }
5271       if (const DeclTypeSpec * type{whole->GetType()}) {
5272         if (!type->IsPolymorphic()) { // C1159
5273           Say(association.selector.source,
5274               "Selector '%s' in SELECT TYPE statement must be "
5275               "polymorphic"_err_en_US);
5276         }
5277       }
5278     } else {
5279       Say(association.selector.source, // C1157
5280           "Selector is not a named variable: 'associate-name =>' is required"_err_en_US);
5281       association = {};
5282     }
5283   }
5284 }
5285 
Post(const parser::SelectRankStmt & x)5286 void ConstructVisitor::Post(const parser::SelectRankStmt &x) {
5287   auto &association{GetCurrentAssociation()};
5288   if (const std::optional<parser::Name> &name{std::get<1>(x.t)}) {
5289     // This isn't a name in the current scope, it is in each SelectRankCaseStmt
5290     MakePlaceholder(*name, MiscDetails::Kind::SelectRankAssociateName);
5291     association.name = &*name;
5292   }
5293 }
5294 
Pre(const parser::SelectTypeConstruct::TypeCase &)5295 bool ConstructVisitor::Pre(const parser::SelectTypeConstruct::TypeCase &) {
5296   PushScope(Scope::Kind::Block, nullptr);
5297   return true;
5298 }
Post(const parser::SelectTypeConstruct::TypeCase &)5299 void ConstructVisitor::Post(const parser::SelectTypeConstruct::TypeCase &) {
5300   PopScope();
5301 }
5302 
Pre(const parser::SelectRankConstruct::RankCase &)5303 bool ConstructVisitor::Pre(const parser::SelectRankConstruct::RankCase &) {
5304   PushScope(Scope::Kind::Block, nullptr);
5305   return true;
5306 }
Post(const parser::SelectRankConstruct::RankCase &)5307 void ConstructVisitor::Post(const parser::SelectRankConstruct::RankCase &) {
5308   PopScope();
5309 }
5310 
Post(const parser::TypeGuardStmt::Guard & x)5311 void ConstructVisitor::Post(const parser::TypeGuardStmt::Guard &x) {
5312   if (auto *symbol{MakeAssocEntity()}) {
5313     if (std::holds_alternative<parser::Default>(x.u)) {
5314       SetTypeFromAssociation(*symbol);
5315     } else if (const auto *type{GetDeclTypeSpec()}) {
5316       symbol->SetType(*type);
5317     }
5318     SetAttrsFromAssociation(*symbol);
5319   }
5320 }
5321 
Post(const parser::SelectRankCaseStmt::Rank & x)5322 void ConstructVisitor::Post(const parser::SelectRankCaseStmt::Rank &x) {
5323   if (auto *symbol{MakeAssocEntity()}) {
5324     SetTypeFromAssociation(*symbol);
5325     SetAttrsFromAssociation(*symbol);
5326     if (const auto *init{std::get_if<parser::ScalarIntConstantExpr>(&x.u)}) {
5327       if (auto val{EvaluateInt64(context(), *init)}) {
5328         auto &details{symbol->get<AssocEntityDetails>()};
5329         details.set_rank(*val);
5330       }
5331     }
5332   }
5333 }
5334 
Pre(const parser::SelectRankConstruct &)5335 bool ConstructVisitor::Pre(const parser::SelectRankConstruct &) {
5336   PushAssociation();
5337   return true;
5338 }
5339 
Post(const parser::SelectRankConstruct &)5340 void ConstructVisitor::Post(const parser::SelectRankConstruct &) {
5341   PopAssociation();
5342 }
5343 
CheckDef(const std::optional<parser::Name> & x)5344 bool ConstructVisitor::CheckDef(const std::optional<parser::Name> &x) {
5345   if (x) {
5346     MakeSymbol(*x, MiscDetails{MiscDetails::Kind::ConstructName});
5347   }
5348   return true;
5349 }
5350 
CheckRef(const std::optional<parser::Name> & x)5351 void ConstructVisitor::CheckRef(const std::optional<parser::Name> &x) {
5352   if (x) {
5353     // Just add an occurrence of this name; checking is done in ValidateLabels
5354     FindSymbol(*x);
5355   }
5356 }
5357 
5358 // Make a symbol for the associating entity of the current association.
MakeAssocEntity()5359 Symbol *ConstructVisitor::MakeAssocEntity() {
5360   Symbol *symbol{nullptr};
5361   auto &association{GetCurrentAssociation()};
5362   if (association.name) {
5363     symbol = &MakeSymbol(*association.name, UnknownDetails{});
5364     if (symbol->has<AssocEntityDetails>() && symbol->owner() == currScope()) {
5365       Say(*association.name, // C1102
5366           "The associate name '%s' is already used in this associate statement"_err_en_US);
5367       return nullptr;
5368     }
5369   } else if (const Symbol *
5370       whole{UnwrapWholeSymbolDataRef(association.selector.expr)}) {
5371     symbol = &MakeSymbol(whole->name());
5372   } else {
5373     return nullptr;
5374   }
5375   if (auto &expr{association.selector.expr}) {
5376     symbol->set_details(AssocEntityDetails{common::Clone(*expr)});
5377   } else {
5378     symbol->set_details(AssocEntityDetails{});
5379   }
5380   return symbol;
5381 }
5382 
5383 // Set the type of symbol based on the current association selector.
SetTypeFromAssociation(Symbol & symbol)5384 void ConstructVisitor::SetTypeFromAssociation(Symbol &symbol) {
5385   auto &details{symbol.get<AssocEntityDetails>()};
5386   const MaybeExpr *pexpr{&details.expr()};
5387   if (!*pexpr) {
5388     pexpr = &GetCurrentAssociation().selector.expr;
5389   }
5390   if (*pexpr) {
5391     const SomeExpr &expr{**pexpr};
5392     if (std::optional<evaluate::DynamicType> type{expr.GetType()}) {
5393       if (const auto *charExpr{
5394               evaluate::UnwrapExpr<evaluate::Expr<evaluate::SomeCharacter>>(
5395                   expr)}) {
5396         symbol.SetType(ToDeclTypeSpec(std::move(*type),
5397             FoldExpr(
5398                 std::visit([](const auto &kindChar) { return kindChar.LEN(); },
5399                     charExpr->u))));
5400       } else {
5401         symbol.SetType(ToDeclTypeSpec(std::move(*type)));
5402       }
5403     } else {
5404       // BOZ literals, procedure designators, &c. are not acceptable
5405       Say(symbol.name(), "Associate name '%s' must have a type"_err_en_US);
5406     }
5407   }
5408 }
5409 
5410 // If current selector is a variable, set some of its attributes on symbol.
SetAttrsFromAssociation(Symbol & symbol)5411 void ConstructVisitor::SetAttrsFromAssociation(Symbol &symbol) {
5412   Attrs attrs{evaluate::GetAttrs(GetCurrentAssociation().selector.expr)};
5413   symbol.attrs() |= attrs &
5414       Attrs{Attr::TARGET, Attr::ASYNCHRONOUS, Attr::VOLATILE, Attr::CONTIGUOUS};
5415   if (attrs.test(Attr::POINTER)) {
5416     symbol.attrs().set(Attr::TARGET);
5417   }
5418 }
5419 
ResolveSelector(const parser::Selector & x)5420 ConstructVisitor::Selector ConstructVisitor::ResolveSelector(
5421     const parser::Selector &x) {
5422   return std::visit(common::visitors{
5423                         [&](const parser::Expr &expr) {
5424                           return Selector{expr.source, EvaluateExpr(expr)};
5425                         },
5426                         [&](const parser::Variable &var) {
5427                           return Selector{var.GetSource(), EvaluateExpr(var)};
5428                         },
5429                     },
5430       x.u);
5431 }
5432 
5433 // Set the current association to the nth to the last association on the
5434 // association stack.  The top of the stack is at n = 1.  This allows access
5435 // to the interior of a list of associations at the top of the stack.
SetCurrentAssociation(std::size_t n)5436 void ConstructVisitor::SetCurrentAssociation(std::size_t n) {
5437   CHECK(n > 0 && n <= associationStack_.size());
5438   currentAssociation_ = &associationStack_[associationStack_.size() - n];
5439 }
5440 
GetCurrentAssociation()5441 ConstructVisitor::Association &ConstructVisitor::GetCurrentAssociation() {
5442   CHECK(currentAssociation_);
5443   return *currentAssociation_;
5444 }
5445 
PushAssociation()5446 void ConstructVisitor::PushAssociation() {
5447   associationStack_.emplace_back(Association{});
5448   currentAssociation_ = &associationStack_.back();
5449 }
5450 
PopAssociation(std::size_t count)5451 void ConstructVisitor::PopAssociation(std::size_t count) {
5452   CHECK(count > 0 && count <= associationStack_.size());
5453   associationStack_.resize(associationStack_.size() - count);
5454   currentAssociation_ =
5455       associationStack_.empty() ? nullptr : &associationStack_.back();
5456 }
5457 
ToDeclTypeSpec(evaluate::DynamicType && type)5458 const DeclTypeSpec &ConstructVisitor::ToDeclTypeSpec(
5459     evaluate::DynamicType &&type) {
5460   switch (type.category()) {
5461     SWITCH_COVERS_ALL_CASES
5462   case common::TypeCategory::Integer:
5463   case common::TypeCategory::Real:
5464   case common::TypeCategory::Complex:
5465     return context().MakeNumericType(type.category(), type.kind());
5466   case common::TypeCategory::Logical:
5467     return context().MakeLogicalType(type.kind());
5468   case common::TypeCategory::Derived:
5469     if (type.IsAssumedType()) {
5470       return currScope().MakeTypeStarType();
5471     } else if (type.IsUnlimitedPolymorphic()) {
5472       return currScope().MakeClassStarType();
5473     } else {
5474       return currScope().MakeDerivedType(
5475           type.IsPolymorphic() ? DeclTypeSpec::ClassDerived
5476                                : DeclTypeSpec::TypeDerived,
5477           common::Clone(type.GetDerivedTypeSpec())
5478 
5479       );
5480     }
5481   case common::TypeCategory::Character:
5482     CRASH_NO_CASE;
5483   }
5484 }
5485 
ToDeclTypeSpec(evaluate::DynamicType && type,MaybeSubscriptIntExpr && length)5486 const DeclTypeSpec &ConstructVisitor::ToDeclTypeSpec(
5487     evaluate::DynamicType &&type, MaybeSubscriptIntExpr &&length) {
5488   CHECK(type.category() == common::TypeCategory::Character);
5489   if (length) {
5490     return currScope().MakeCharacterType(
5491         ParamValue{SomeIntExpr{*std::move(length)}, common::TypeParamAttr::Len},
5492         KindExpr{type.kind()});
5493   } else {
5494     return currScope().MakeCharacterType(
5495         ParamValue::Deferred(common::TypeParamAttr::Len),
5496         KindExpr{type.kind()});
5497   }
5498 }
5499 
5500 // ResolveNamesVisitor implementation
5501 
Pre(const parser::FunctionReference & x)5502 bool ResolveNamesVisitor::Pre(const parser::FunctionReference &x) {
5503   HandleCall(Symbol::Flag::Function, x.v);
5504   return false;
5505 }
Pre(const parser::CallStmt & x)5506 bool ResolveNamesVisitor::Pre(const parser::CallStmt &x) {
5507   HandleCall(Symbol::Flag::Subroutine, x.v);
5508   return false;
5509 }
5510 
Pre(const parser::ImportStmt & x)5511 bool ResolveNamesVisitor::Pre(const parser::ImportStmt &x) {
5512   auto &scope{currScope()};
5513   // Check C896 and C899: where IMPORT statements are allowed
5514   switch (scope.kind()) {
5515   case Scope::Kind::Module:
5516     if (scope.IsModule()) {
5517       Say("IMPORT is not allowed in a module scoping unit"_err_en_US);
5518       return false;
5519     } else if (x.kind == common::ImportKind::None) {
5520       Say("IMPORT,NONE is not allowed in a submodule scoping unit"_err_en_US);
5521       return false;
5522     }
5523     break;
5524   case Scope::Kind::MainProgram:
5525     Say("IMPORT is not allowed in a main program scoping unit"_err_en_US);
5526     return false;
5527   case Scope::Kind::Subprogram:
5528     if (scope.parent().IsGlobal()) {
5529       Say("IMPORT is not allowed in an external subprogram scoping unit"_err_en_US);
5530       return false;
5531     }
5532     break;
5533   case Scope::Kind::BlockData: // C1415 (in part)
5534     Say("IMPORT is not allowed in a BLOCK DATA subprogram"_err_en_US);
5535     return false;
5536   default:;
5537   }
5538   if (auto error{scope.SetImportKind(x.kind)}) {
5539     Say(std::move(*error));
5540   }
5541   for (auto &name : x.names) {
5542     if (FindSymbol(scope.parent(), name)) {
5543       scope.add_importName(name.source);
5544     } else {
5545       Say(name, "'%s' not found in host scope"_err_en_US);
5546     }
5547   }
5548   prevImportStmt_ = currStmtSource();
5549   return false;
5550 }
5551 
ResolveStructureComponent(const parser::StructureComponent & x)5552 const parser::Name *DeclarationVisitor::ResolveStructureComponent(
5553     const parser::StructureComponent &x) {
5554   return FindComponent(ResolveDataRef(x.base), x.component);
5555 }
5556 
ResolveDesignator(const parser::Designator & x)5557 const parser::Name *DeclarationVisitor::ResolveDesignator(
5558     const parser::Designator &x) {
5559   return std::visit(
5560       common::visitors{
5561           [&](const parser::DataRef &x) { return ResolveDataRef(x); },
5562           [&](const parser::Substring &x) {
5563             return ResolveDataRef(std::get<parser::DataRef>(x.t));
5564           },
5565       },
5566       x.u);
5567 }
5568 
ResolveDataRef(const parser::DataRef & x)5569 const parser::Name *DeclarationVisitor::ResolveDataRef(
5570     const parser::DataRef &x) {
5571   return std::visit(
5572       common::visitors{
5573           [=](const parser::Name &y) { return ResolveName(y); },
5574           [=](const Indirection<parser::StructureComponent> &y) {
5575             return ResolveStructureComponent(y.value());
5576           },
5577           [&](const Indirection<parser::ArrayElement> &y) {
5578             Walk(y.value().subscripts);
5579             const parser::Name *name{ResolveDataRef(y.value().base)};
5580             if (!name) {
5581             } else if (!name->symbol->has<ProcEntityDetails>()) {
5582               ConvertToObjectEntity(*name->symbol);
5583             } else if (!context().HasError(*name->symbol)) {
5584               SayWithDecl(*name, *name->symbol,
5585                   "Cannot reference function '%s' as data"_err_en_US);
5586             }
5587             return name;
5588           },
5589           [&](const Indirection<parser::CoindexedNamedObject> &y) {
5590             Walk(y.value().imageSelector);
5591             return ResolveDataRef(y.value().base);
5592           },
5593       },
5594       x.u);
5595 }
5596 
5597 // If implicit types are allowed, ensure name is in the symbol table.
5598 // Otherwise, report an error if it hasn't been declared.
ResolveName(const parser::Name & name)5599 const parser::Name *DeclarationVisitor::ResolveName(const parser::Name &name) {
5600   FindSymbol(name);
5601   if (CheckForHostAssociatedImplicit(name)) {
5602     NotePossibleBadForwardRef(name);
5603     return &name;
5604   }
5605   if (Symbol * symbol{name.symbol}) {
5606     if (CheckUseError(name)) {
5607       return nullptr; // reported an error
5608     }
5609     NotePossibleBadForwardRef(name);
5610     symbol->set(Symbol::Flag::ImplicitOrError, false);
5611     if (IsUplevelReference(*symbol)) {
5612       MakeHostAssocSymbol(name, *symbol);
5613     } else if (IsDummy(*symbol) ||
5614         (!symbol->GetType() && FindCommonBlockContaining(*symbol))) {
5615       ConvertToObjectEntity(*symbol);
5616       ApplyImplicitRules(*symbol);
5617     }
5618     return &name;
5619   }
5620   if (isImplicitNoneType()) {
5621     Say(name, "No explicit type declared for '%s'"_err_en_US);
5622     return nullptr;
5623   }
5624   // Create the symbol then ensure it is accessible
5625   MakeSymbol(InclusiveScope(), name.source, Attrs{});
5626   auto *symbol{FindSymbol(name)};
5627   if (!symbol) {
5628     Say(name,
5629         "'%s' from host scoping unit is not accessible due to IMPORT"_err_en_US);
5630     return nullptr;
5631   }
5632   ConvertToObjectEntity(*symbol);
5633   ApplyImplicitRules(*symbol);
5634   NotePossibleBadForwardRef(name);
5635   return &name;
5636 }
5637 
5638 // A specification expression may refer to a symbol in the host procedure that
5639 // is implicitly typed. Because specification parts are processed before
5640 // execution parts, this may be the first time we see the symbol. It can't be a
5641 // local in the current scope (because it's in a specification expression) so
5642 // either it is implicitly declared in the host procedure or it is an error.
5643 // We create a symbol in the host assuming it is the former; if that proves to
5644 // be wrong we report an error later in CheckDeclarations().
CheckForHostAssociatedImplicit(const parser::Name & name)5645 bool DeclarationVisitor::CheckForHostAssociatedImplicit(
5646     const parser::Name &name) {
5647   if (inExecutionPart_) {
5648     return false;
5649   }
5650   if (name.symbol) {
5651     ApplyImplicitRules(*name.symbol);
5652   }
5653   Symbol *hostSymbol;
5654   Scope *host{GetHostProcedure()};
5655   if (!host || isImplicitNoneType(*host)) {
5656     return false;
5657   }
5658   if (!name.symbol) {
5659     hostSymbol = &MakeSymbol(*host, name.source, Attrs{});
5660     ConvertToObjectEntity(*hostSymbol);
5661     ApplyImplicitRules(*hostSymbol);
5662     hostSymbol->set(Symbol::Flag::ImplicitOrError);
5663   } else if (name.symbol->test(Symbol::Flag::ImplicitOrError)) {
5664     hostSymbol = name.symbol;
5665   } else {
5666     return false;
5667   }
5668   Symbol &symbol{MakeHostAssocSymbol(name, *hostSymbol)};
5669   if (isImplicitNoneType()) {
5670     symbol.get<HostAssocDetails>().implicitOrExplicitTypeError = true;
5671   } else {
5672     symbol.get<HostAssocDetails>().implicitOrSpecExprError = true;
5673   }
5674   return true;
5675 }
5676 
IsUplevelReference(const Symbol & symbol)5677 bool DeclarationVisitor::IsUplevelReference(const Symbol &symbol) {
5678   const Scope &symbolUnit{GetProgramUnitContaining(symbol)};
5679   if (symbolUnit == GetProgramUnitContaining(currScope())) {
5680     return false;
5681   } else {
5682     Scope::Kind kind{symbolUnit.kind()};
5683     return kind == Scope::Kind::Subprogram || kind == Scope::Kind::MainProgram;
5684   }
5685 }
5686 
5687 // base is a part-ref of a derived type; find the named component in its type.
5688 // Also handles intrinsic type parameter inquiries (%kind, %len) and
5689 // COMPLEX component references (%re, %im).
FindComponent(const parser::Name * base,const parser::Name & component)5690 const parser::Name *DeclarationVisitor::FindComponent(
5691     const parser::Name *base, const parser::Name &component) {
5692   if (!base || !base->symbol) {
5693     return nullptr;
5694   }
5695   auto &symbol{base->symbol->GetUltimate()};
5696   if (!symbol.has<AssocEntityDetails>() && !ConvertToObjectEntity(symbol)) {
5697     SayWithDecl(*base, symbol,
5698         "'%s' is an invalid base for a component reference"_err_en_US);
5699     return nullptr;
5700   }
5701   auto *type{symbol.GetType()};
5702   if (!type) {
5703     return nullptr; // should have already reported error
5704   }
5705   if (const IntrinsicTypeSpec * intrinsic{type->AsIntrinsic()}) {
5706     auto name{component.ToString()};
5707     auto category{intrinsic->category()};
5708     MiscDetails::Kind miscKind{MiscDetails::Kind::None};
5709     if (name == "kind") {
5710       miscKind = MiscDetails::Kind::KindParamInquiry;
5711     } else if (category == TypeCategory::Character) {
5712       if (name == "len") {
5713         miscKind = MiscDetails::Kind::LenParamInquiry;
5714       }
5715     } else if (category == TypeCategory::Complex) {
5716       if (name == "re") {
5717         miscKind = MiscDetails::Kind::ComplexPartRe;
5718       } else if (name == "im") {
5719         miscKind = MiscDetails::Kind::ComplexPartIm;
5720       }
5721     }
5722     if (miscKind != MiscDetails::Kind::None) {
5723       MakePlaceholder(component, miscKind);
5724       return nullptr;
5725     }
5726   } else if (const DerivedTypeSpec * derived{type->AsDerived()}) {
5727     if (const Scope * scope{derived->scope()}) {
5728       if (Resolve(component, scope->FindComponent(component.source))) {
5729         if (auto msg{
5730                 CheckAccessibleComponent(currScope(), *component.symbol)}) {
5731           context().Say(component.source, *msg);
5732         }
5733         return &component;
5734       } else {
5735         SayDerivedType(component.source,
5736             "Component '%s' not found in derived type '%s'"_err_en_US, *scope);
5737       }
5738     }
5739     return nullptr;
5740   }
5741   if (symbol.test(Symbol::Flag::Implicit)) {
5742     Say(*base,
5743         "'%s' is not an object of derived type; it is implicitly typed"_err_en_US);
5744   } else {
5745     SayWithDecl(
5746         *base, symbol, "'%s' is not an object of derived type"_err_en_US);
5747   }
5748   return nullptr;
5749 }
5750 
Initialization(const parser::Name & name,const parser::Initialization & init,bool inComponentDecl)5751 void DeclarationVisitor::Initialization(const parser::Name &name,
5752     const parser::Initialization &init, bool inComponentDecl) {
5753   // Traversal of the initializer was deferred to here so that the
5754   // symbol being declared can be available for use in the expression, e.g.:
5755   //   real, parameter :: x = tiny(x)
5756   if (!name.symbol) {
5757     return;
5758   }
5759   Symbol &ultimate{name.symbol->GetUltimate()};
5760   if (IsAllocatable(ultimate)) {
5761     Say(name, "Allocatable object '%s' cannot be initialized"_err_en_US);
5762     return;
5763   }
5764   if (auto *object{ultimate.detailsIf<ObjectEntityDetails>()}) {
5765     // TODO: check C762 - all bounds and type parameters of component
5766     // are colons or constant expressions if component is initialized
5767     std::visit(
5768         common::visitors{
5769             [&](const parser::ConstantExpr &expr) {
5770               NonPointerInitialization(name, expr);
5771             },
5772             [&](const parser::NullInit &null) {
5773               Walk(null);
5774               if (auto nullInit{EvaluateExpr(null)}) {
5775                 if (!evaluate::IsNullPointer(*nullInit)) {
5776                   Say(name,
5777                       "Pointer initializer must be intrinsic NULL()"_err_en_US); // C813
5778                 } else if (IsPointer(ultimate)) {
5779                   object->set_init(std::move(*nullInit));
5780                 } else {
5781                   Say(name,
5782                       "Non-pointer component '%s' initialized with null pointer"_err_en_US);
5783                 }
5784               }
5785             },
5786             [&](const parser::InitialDataTarget &) {
5787               // Defer analysis to the end of the specification part
5788               // so that forward references and attribute checks like SAVE
5789               // work better.
5790             },
5791             [&](const std::list<Indirection<parser::DataStmtValue>> &) {
5792               // TODO: Need to Walk(init.u); when implementing this case
5793               if (inComponentDecl) {
5794                 Say(name,
5795                     "Component '%s' initialized with DATA statement values"_err_en_US);
5796               } else {
5797                 // TODO - DATA statements and DATA-like initialization extension
5798               }
5799             },
5800         },
5801         init.u);
5802   }
5803 }
5804 
PointerInitialization(const parser::Name & name,const parser::InitialDataTarget & target)5805 void DeclarationVisitor::PointerInitialization(
5806     const parser::Name &name, const parser::InitialDataTarget &target) {
5807   if (name.symbol) {
5808     Symbol &ultimate{name.symbol->GetUltimate()};
5809     if (!context().HasError(ultimate)) {
5810       if (IsPointer(ultimate)) {
5811         if (auto *details{ultimate.detailsIf<ObjectEntityDetails>()}) {
5812           CHECK(!details->init());
5813           Walk(target);
5814           if (MaybeExpr expr{EvaluateExpr(target)}) {
5815             // Validation is done in declaration checking.
5816             details->set_init(std::move(*expr));
5817           }
5818         }
5819       } else {
5820         Say(name,
5821             "'%s' is not a pointer but is initialized like one"_err_en_US);
5822         context().SetError(ultimate);
5823       }
5824     }
5825   }
5826 }
PointerInitialization(const parser::Name & name,const parser::ProcPointerInit & target)5827 void DeclarationVisitor::PointerInitialization(
5828     const parser::Name &name, const parser::ProcPointerInit &target) {
5829   if (name.symbol) {
5830     Symbol &ultimate{name.symbol->GetUltimate()};
5831     if (!context().HasError(ultimate)) {
5832       if (IsProcedurePointer(ultimate)) {
5833         auto &details{ultimate.get<ProcEntityDetails>()};
5834         CHECK(!details.init());
5835         Walk(target);
5836         if (const auto *targetName{std::get_if<parser::Name>(&target.u)}) {
5837           if (targetName->symbol) {
5838             // Validation is done in declaration checking.
5839             details.set_init(*targetName->symbol);
5840           }
5841         } else {
5842           details.set_init(nullptr); // explicit NULL()
5843         }
5844       } else {
5845         Say(name,
5846             "'%s' is not a procedure pointer but is initialized "
5847             "like one"_err_en_US);
5848         context().SetError(ultimate);
5849       }
5850     }
5851   }
5852 }
5853 
NonPointerInitialization(const parser::Name & name,const parser::ConstantExpr & expr)5854 void DeclarationVisitor::NonPointerInitialization(
5855     const parser::Name &name, const parser::ConstantExpr &expr) {
5856   if (name.symbol) {
5857     Symbol &ultimate{name.symbol->GetUltimate()};
5858     if (!context().HasError(ultimate)) {
5859       if (IsPointer(ultimate)) {
5860         Say(name,
5861             "'%s' is a pointer but is not initialized like one"_err_en_US);
5862       } else if (auto *details{ultimate.detailsIf<ObjectEntityDetails>()}) {
5863         CHECK(!details->init());
5864         Walk(expr);
5865         if (ultimate.owner().IsParameterizedDerivedType()) {
5866           // Can't convert to type of component, which might not yet
5867           // be known; that's done later during PDT instantiation.
5868           if (MaybeExpr value{EvaluateExpr(expr)}) {
5869             details->set_init(std::move(*value));
5870           }
5871         } else if (MaybeExpr folded{EvaluateNonPointerInitializer(
5872                        ultimate, expr, expr.thing.value().source)}) {
5873           details->set_init(std::move(*folded));
5874         }
5875       }
5876     }
5877   }
5878 }
5879 
HandleCall(Symbol::Flag procFlag,const parser::Call & call)5880 void ResolveNamesVisitor::HandleCall(
5881     Symbol::Flag procFlag, const parser::Call &call) {
5882   std::visit(
5883       common::visitors{
5884           [&](const parser::Name &x) { HandleProcedureName(procFlag, x); },
5885           [&](const parser::ProcComponentRef &x) { Walk(x); },
5886       },
5887       std::get<parser::ProcedureDesignator>(call.t).u);
5888   Walk(std::get<std::list<parser::ActualArgSpec>>(call.t));
5889 }
5890 
HandleProcedureName(Symbol::Flag flag,const parser::Name & name)5891 void ResolveNamesVisitor::HandleProcedureName(
5892     Symbol::Flag flag, const parser::Name &name) {
5893   CHECK(flag == Symbol::Flag::Function || flag == Symbol::Flag::Subroutine);
5894   auto *symbol{FindSymbol(NonDerivedTypeScope(), name)};
5895   if (!symbol) {
5896     if (IsIntrinsic(name.source, flag)) {
5897       symbol =
5898           &MakeSymbol(InclusiveScope(), name.source, Attrs{Attr::INTRINSIC});
5899     } else {
5900       symbol = &MakeSymbol(context().globalScope(), name.source, Attrs{});
5901     }
5902     Resolve(name, *symbol);
5903     if (symbol->has<ModuleDetails>()) {
5904       SayWithDecl(name, *symbol,
5905           "Use of '%s' as a procedure conflicts with its declaration"_err_en_US);
5906       return;
5907     }
5908     if (!symbol->attrs().test(Attr::INTRINSIC)) {
5909       if (!CheckImplicitNoneExternal(name.source, *symbol)) {
5910         return;
5911       }
5912       MakeExternal(*symbol);
5913     }
5914     ConvertToProcEntity(*symbol);
5915     SetProcFlag(name, *symbol, flag);
5916   } else if (CheckUseError(name)) {
5917     // error was reported
5918   } else {
5919     symbol = &Resolve(name, symbol)->GetUltimate();
5920     bool convertedToProcEntity{ConvertToProcEntity(*symbol)};
5921     if (convertedToProcEntity && !symbol->attrs().test(Attr::EXTERNAL) &&
5922         IsIntrinsic(symbol->name(), flag) && !IsDummy(*symbol)) {
5923       symbol->attrs().set(Attr::INTRINSIC);
5924       // 8.2(3): ignore type from intrinsic in type-declaration-stmt
5925       symbol->get<ProcEntityDetails>().set_interface(ProcInterface{});
5926     }
5927     if (!SetProcFlag(name, *symbol, flag)) {
5928       return; // reported error
5929     }
5930     CheckImplicitNoneExternal(name.source, *symbol);
5931     if (symbol->has<SubprogramDetails>() &&
5932         symbol->attrs().test(Attr::ABSTRACT)) {
5933       Say(name, "Abstract interface '%s' may not be called"_err_en_US);
5934     } else if (IsProcedure(*symbol) || symbol->has<DerivedTypeDetails>() ||
5935         symbol->has<ObjectEntityDetails>() ||
5936         symbol->has<AssocEntityDetails>()) {
5937       // Symbols with DerivedTypeDetails, ObjectEntityDetails and
5938       // AssocEntityDetails are accepted here as procedure-designators because
5939       // this means the related FunctionReference are mis-parsed structure
5940       // constructors or array references that will be fixed later when
5941       // analyzing expressions.
5942     } else if (symbol->test(Symbol::Flag::Implicit)) {
5943       Say(name,
5944           "Use of '%s' as a procedure conflicts with its implicit definition"_err_en_US);
5945     } else {
5946       SayWithDecl(name, *symbol,
5947           "Use of '%s' as a procedure conflicts with its declaration"_err_en_US);
5948     }
5949   }
5950 }
5951 
CheckImplicitNoneExternal(const SourceName & name,const Symbol & symbol)5952 bool ResolveNamesVisitor::CheckImplicitNoneExternal(
5953     const SourceName &name, const Symbol &symbol) {
5954   if (isImplicitNoneExternal() && !symbol.attrs().test(Attr::EXTERNAL) &&
5955       !symbol.attrs().test(Attr::INTRINSIC) && !symbol.HasExplicitInterface()) {
5956     Say(name,
5957         "'%s' is an external procedure without the EXTERNAL"
5958         " attribute in a scope with IMPLICIT NONE(EXTERNAL)"_err_en_US);
5959     return false;
5960   }
5961   return true;
5962 }
5963 
5964 // Variant of HandleProcedureName() for use while skimming the executable
5965 // part of a subprogram to catch calls to dummy procedures that are part
5966 // of the subprogram's interface, and to mark as procedures any symbols
5967 // that might otherwise have been miscategorized as objects.
NoteExecutablePartCall(Symbol::Flag flag,const parser::Call & call)5968 void ResolveNamesVisitor::NoteExecutablePartCall(
5969     Symbol::Flag flag, const parser::Call &call) {
5970   auto &designator{std::get<parser::ProcedureDesignator>(call.t)};
5971   if (const auto *name{std::get_if<parser::Name>(&designator.u)}) {
5972     // Subtlety: The symbol pointers in the parse tree are not set, because
5973     // they might end up resolving elsewhere (e.g., construct entities in
5974     // SELECT TYPE).
5975     if (Symbol * symbol{currScope().FindSymbol(name->source)}) {
5976       Symbol::Flag other{flag == Symbol::Flag::Subroutine
5977               ? Symbol::Flag::Function
5978               : Symbol::Flag::Subroutine};
5979       if (!symbol->test(other)) {
5980         ConvertToProcEntity(*symbol);
5981         if (symbol->has<ProcEntityDetails>()) {
5982           symbol->set(flag);
5983           if (IsDummy(*symbol)) {
5984             symbol->attrs().set(Attr::EXTERNAL);
5985           }
5986           ApplyImplicitRules(*symbol);
5987         }
5988       }
5989     }
5990   }
5991 }
5992 
5993 // Check and set the Function or Subroutine flag on symbol; false on error.
SetProcFlag(const parser::Name & name,Symbol & symbol,Symbol::Flag flag)5994 bool ResolveNamesVisitor::SetProcFlag(
5995     const parser::Name &name, Symbol &symbol, Symbol::Flag flag) {
5996   if (symbol.test(Symbol::Flag::Function) && flag == Symbol::Flag::Subroutine) {
5997     SayWithDecl(
5998         name, symbol, "Cannot call function '%s' like a subroutine"_err_en_US);
5999     return false;
6000   } else if (symbol.test(Symbol::Flag::Subroutine) &&
6001       flag == Symbol::Flag::Function) {
6002     SayWithDecl(
6003         name, symbol, "Cannot call subroutine '%s' like a function"_err_en_US);
6004     return false;
6005   } else if (symbol.has<ProcEntityDetails>()) {
6006     symbol.set(flag); // in case it hasn't been set yet
6007     if (flag == Symbol::Flag::Function) {
6008       ApplyImplicitRules(symbol);
6009     }
6010   } else if (symbol.GetType() && flag == Symbol::Flag::Subroutine) {
6011     SayWithDecl(
6012         name, symbol, "Cannot call function '%s' like a subroutine"_err_en_US);
6013   }
6014   return true;
6015 }
6016 
Pre(const parser::AccessStmt & x)6017 bool ModuleVisitor::Pre(const parser::AccessStmt &x) {
6018   Attr accessAttr{AccessSpecToAttr(std::get<parser::AccessSpec>(x.t))};
6019   if (!currScope().IsModule()) { // C869
6020     Say(currStmtSource().value(),
6021         "%s statement may only appear in the specification part of a module"_err_en_US,
6022         EnumToString(accessAttr));
6023     return false;
6024   }
6025   const auto &accessIds{std::get<std::list<parser::AccessId>>(x.t)};
6026   if (accessIds.empty()) {
6027     if (prevAccessStmt_) { // C869
6028       Say("The default accessibility of this module has already been declared"_err_en_US)
6029           .Attach(*prevAccessStmt_, "Previous declaration"_en_US);
6030     }
6031     prevAccessStmt_ = currStmtSource();
6032     defaultAccess_ = accessAttr;
6033   } else {
6034     for (const auto &accessId : accessIds) {
6035       std::visit(
6036           common::visitors{
6037               [=](const parser::Name &y) {
6038                 Resolve(y, SetAccess(y.source, accessAttr));
6039               },
6040               [=](const Indirection<parser::GenericSpec> &y) {
6041                 auto info{GenericSpecInfo{y.value()}};
6042                 const auto &symbolName{info.symbolName()};
6043                 if (auto *symbol{FindInScope(symbolName)}) {
6044                   info.Resolve(&SetAccess(symbolName, accessAttr, symbol));
6045                 } else if (info.kind().IsName()) {
6046                   info.Resolve(&SetAccess(symbolName, accessAttr));
6047                 } else {
6048                   Say(symbolName, "Generic spec '%s' not found"_err_en_US);
6049                 }
6050               },
6051           },
6052           accessId.u);
6053     }
6054   }
6055   return false;
6056 }
6057 
6058 // Set the access specification for this symbol.
SetAccess(const SourceName & name,Attr attr,Symbol * symbol)6059 Symbol &ModuleVisitor::SetAccess(
6060     const SourceName &name, Attr attr, Symbol *symbol) {
6061   if (!symbol) {
6062     symbol = &MakeSymbol(name);
6063   }
6064   Attrs &attrs{symbol->attrs()};
6065   if (attrs.HasAny({Attr::PUBLIC, Attr::PRIVATE})) {
6066     // PUBLIC/PRIVATE already set: make it a fatal error if it changed
6067     Attr prev = attrs.test(Attr::PUBLIC) ? Attr::PUBLIC : Attr::PRIVATE;
6068     Say(name,
6069         WithIsFatal(
6070             "The accessibility of '%s' has already been specified as %s"_en_US,
6071             attr != prev),
6072         MakeOpName(name), EnumToString(prev));
6073   } else {
6074     attrs.set(attr);
6075   }
6076   return *symbol;
6077 }
6078 
NeedsExplicitType(const Symbol & symbol)6079 static bool NeedsExplicitType(const Symbol &symbol) {
6080   if (symbol.has<UnknownDetails>()) {
6081     return true;
6082   } else if (const auto *details{symbol.detailsIf<EntityDetails>()}) {
6083     return !details->type();
6084   } else if (const auto *details{symbol.detailsIf<ObjectEntityDetails>()}) {
6085     return !details->type();
6086   } else if (const auto *details{symbol.detailsIf<ProcEntityDetails>()}) {
6087     return !details->interface().symbol() && !details->interface().type();
6088   } else {
6089     return false;
6090   }
6091 }
6092 
Pre(const parser::SpecificationPart & x)6093 bool ResolveNamesVisitor::Pre(const parser::SpecificationPart &x) {
6094   const auto &[accDecls, ompDecls, compilerDirectives, useStmts, importStmts,
6095       implicitPart, decls] = x.t;
6096   auto flagRestorer{common::ScopedSet(inSpecificationPart_, true)};
6097   Walk(accDecls);
6098   Walk(ompDecls);
6099   Walk(compilerDirectives);
6100   Walk(useStmts);
6101   Walk(importStmts);
6102   Walk(implicitPart);
6103   auto setRestorer{
6104       common::ScopedSet(specPartForwardRefs_, std::set<SourceName>{})};
6105   for (const auto &decl : decls) {
6106     if (const auto *spec{
6107             std::get_if<parser::SpecificationConstruct>(&decl.u)}) {
6108       PreSpecificationConstruct(*spec);
6109     }
6110   }
6111   Walk(decls);
6112   FinishSpecificationPart(decls);
6113   return false;
6114 }
6115 
6116 // Initial processing on specification constructs, before visiting them.
PreSpecificationConstruct(const parser::SpecificationConstruct & spec)6117 void ResolveNamesVisitor::PreSpecificationConstruct(
6118     const parser::SpecificationConstruct &spec) {
6119   std::visit(
6120       common::visitors{
6121           [&](const parser::Statement<Indirection<parser::GenericStmt>> &y) {
6122             CreateGeneric(std::get<parser::GenericSpec>(y.statement.value().t));
6123           },
6124           [&](const Indirection<parser::InterfaceBlock> &y) {
6125             const auto &stmt{std::get<parser::Statement<parser::InterfaceStmt>>(
6126                 y.value().t)};
6127             if (const auto *spec{parser::Unwrap<parser::GenericSpec>(stmt)}) {
6128               CreateGeneric(*spec);
6129             }
6130           },
6131           [&](const parser::Statement<parser::OtherSpecificationStmt> &y) {
6132             if (const auto *commonStmt{parser::Unwrap<parser::CommonStmt>(y)}) {
6133               CreateCommonBlockSymbols(*commonStmt);
6134             }
6135           },
6136           [&](const auto &) {},
6137       },
6138       spec.u);
6139 }
6140 
CreateCommonBlockSymbols(const parser::CommonStmt & commonStmt)6141 void ResolveNamesVisitor::CreateCommonBlockSymbols(
6142     const parser::CommonStmt &commonStmt) {
6143   for (const parser::CommonStmt::Block &block : commonStmt.blocks) {
6144     const auto &[name, objects] = block.t;
6145     Symbol &commonBlock{MakeCommonBlockSymbol(name)};
6146     for (const auto &object : objects) {
6147       Symbol &obj{DeclareObjectEntity(std::get<parser::Name>(object.t))};
6148       if (auto *details{obj.detailsIf<ObjectEntityDetails>()}) {
6149         details->set_commonBlock(commonBlock);
6150         commonBlock.get<CommonBlockDetails>().add_object(obj);
6151       }
6152     }
6153   }
6154 }
6155 
CreateGeneric(const parser::GenericSpec & x)6156 void ResolveNamesVisitor::CreateGeneric(const parser::GenericSpec &x) {
6157   auto info{GenericSpecInfo{x}};
6158   const SourceName &symbolName{info.symbolName()};
6159   if (IsLogicalConstant(context(), symbolName)) {
6160     Say(symbolName,
6161         "Logical constant '%s' may not be used as a defined operator"_err_en_US);
6162     return;
6163   }
6164   GenericDetails genericDetails;
6165   if (Symbol * existing{FindInScope(symbolName)}) {
6166     if (existing->has<GenericDetails>()) {
6167       info.Resolve(existing);
6168       return; // already have generic, add to it
6169     }
6170     Symbol &ultimate{existing->GetUltimate()};
6171     if (auto *ultimateDetails{ultimate.detailsIf<GenericDetails>()}) {
6172       // convert a use-associated generic into a local generic
6173       genericDetails.CopyFrom(*ultimateDetails);
6174       AddGenericUse(genericDetails, existing->name(),
6175           existing->get<UseDetails>().symbol());
6176     } else if (ultimate.has<SubprogramDetails>() ||
6177         ultimate.has<SubprogramNameDetails>()) {
6178       genericDetails.set_specific(ultimate);
6179     } else if (ultimate.has<DerivedTypeDetails>()) {
6180       genericDetails.set_derivedType(ultimate);
6181     } else {
6182       SayAlreadyDeclared(symbolName, *existing);
6183     }
6184     EraseSymbol(*existing);
6185   }
6186   info.Resolve(&MakeSymbol(symbolName, Attrs{}, std::move(genericDetails)));
6187 }
6188 
FinishSpecificationPart(const std::list<parser::DeclarationConstruct> & decls)6189 void ResolveNamesVisitor::FinishSpecificationPart(
6190     const std::list<parser::DeclarationConstruct> &decls) {
6191   badStmtFuncFound_ = false;
6192   CheckImports();
6193   bool inModule{currScope().kind() == Scope::Kind::Module};
6194   for (auto &pair : currScope()) {
6195     auto &symbol{*pair.second};
6196     if (NeedsExplicitType(symbol)) {
6197       ApplyImplicitRules(symbol);
6198     }
6199     if (symbol.has<GenericDetails>()) {
6200       CheckGenericProcedures(symbol);
6201     }
6202     if (inModule && symbol.attrs().test(Attr::EXTERNAL) &&
6203         !symbol.test(Symbol::Flag::Function) &&
6204         !symbol.test(Symbol::Flag::Subroutine)) {
6205       // in a module, external proc without return type is subroutine
6206       symbol.set(
6207           symbol.GetType() ? Symbol::Flag::Function : Symbol::Flag::Subroutine);
6208     }
6209     if (!symbol.has<HostAssocDetails>()) {
6210       CheckPossibleBadForwardRef(symbol);
6211     }
6212   }
6213   currScope().InstantiateDerivedTypes(context());
6214   for (const auto &decl : decls) {
6215     if (const auto *statement{std::get_if<
6216             parser::Statement<common::Indirection<parser::StmtFunctionStmt>>>(
6217             &decl.u)}) {
6218       AnalyzeStmtFunctionStmt(statement->statement.value());
6219     }
6220   }
6221   // TODO: what about instantiations in BLOCK?
6222   CheckSaveStmts();
6223   CheckCommonBlocks();
6224   if (!inInterfaceBlock()) {
6225     // TODO: warn for the case where the EQUIVALENCE statement is in a
6226     // procedure declaration in an interface block
6227     CheckEquivalenceSets();
6228   }
6229 }
6230 
6231 // Analyze the bodies of statement functions now that the symbols in this
6232 // specification part have been fully declared and implicitly typed.
AnalyzeStmtFunctionStmt(const parser::StmtFunctionStmt & stmtFunc)6233 void ResolveNamesVisitor::AnalyzeStmtFunctionStmt(
6234     const parser::StmtFunctionStmt &stmtFunc) {
6235   Symbol *symbol{std::get<parser::Name>(stmtFunc.t).symbol};
6236   if (!symbol || !symbol->has<SubprogramDetails>()) {
6237     return;
6238   }
6239   auto &details{symbol->get<SubprogramDetails>()};
6240   auto expr{AnalyzeExpr(
6241       context(), std::get<parser::Scalar<parser::Expr>>(stmtFunc.t))};
6242   if (!expr) {
6243     context().SetError(*symbol);
6244     return;
6245   }
6246   if (auto type{evaluate::DynamicType::From(*symbol)}) {
6247     auto converted{ConvertToType(*type, std::move(*expr))};
6248     if (!converted) {
6249       context().SetError(*symbol);
6250       return;
6251     }
6252     details.set_stmtFunction(std::move(*converted));
6253   } else {
6254     details.set_stmtFunction(std::move(*expr));
6255   }
6256 }
6257 
CheckImports()6258 void ResolveNamesVisitor::CheckImports() {
6259   auto &scope{currScope()};
6260   switch (scope.GetImportKind()) {
6261   case common::ImportKind::None:
6262     break;
6263   case common::ImportKind::All:
6264     // C8102: all entities in host must not be hidden
6265     for (const auto &pair : scope.parent()) {
6266       auto &name{pair.first};
6267       std::optional<SourceName> scopeName{scope.GetName()};
6268       if (!scopeName || name != *scopeName) {
6269         CheckImport(prevImportStmt_.value(), name);
6270       }
6271     }
6272     break;
6273   case common::ImportKind::Default:
6274   case common::ImportKind::Only:
6275     // C8102: entities named in IMPORT must not be hidden
6276     for (auto &name : scope.importNames()) {
6277       CheckImport(name, name);
6278     }
6279     break;
6280   }
6281 }
6282 
CheckImport(const SourceName & location,const SourceName & name)6283 void ResolveNamesVisitor::CheckImport(
6284     const SourceName &location, const SourceName &name) {
6285   if (auto *symbol{FindInScope(name)}) {
6286     Say(location, "'%s' from host is not accessible"_err_en_US, name)
6287         .Attach(symbol->name(), "'%s' is hidden by this entity"_en_US,
6288             symbol->name());
6289   }
6290 }
6291 
Pre(const parser::ImplicitStmt & x)6292 bool ResolveNamesVisitor::Pre(const parser::ImplicitStmt &x) {
6293   return CheckNotInBlock("IMPLICIT") && // C1107
6294       ImplicitRulesVisitor::Pre(x);
6295 }
6296 
Post(const parser::PointerObject & x)6297 void ResolveNamesVisitor::Post(const parser::PointerObject &x) {
6298   std::visit(common::visitors{
6299                  [&](const parser::Name &x) { ResolveName(x); },
6300                  [&](const parser::StructureComponent &x) {
6301                    ResolveStructureComponent(x);
6302                  },
6303              },
6304       x.u);
6305 }
Post(const parser::AllocateObject & x)6306 void ResolveNamesVisitor::Post(const parser::AllocateObject &x) {
6307   std::visit(common::visitors{
6308                  [&](const parser::Name &x) { ResolveName(x); },
6309                  [&](const parser::StructureComponent &x) {
6310                    ResolveStructureComponent(x);
6311                  },
6312              },
6313       x.u);
6314 }
6315 
Pre(const parser::PointerAssignmentStmt & x)6316 bool ResolveNamesVisitor::Pre(const parser::PointerAssignmentStmt &x) {
6317   const auto &dataRef{std::get<parser::DataRef>(x.t)};
6318   const auto &bounds{std::get<parser::PointerAssignmentStmt::Bounds>(x.t)};
6319   const auto &expr{std::get<parser::Expr>(x.t)};
6320   ResolveDataRef(dataRef);
6321   Walk(bounds);
6322   // Resolve unrestricted specific intrinsic procedures as in "p => cos".
6323   if (const parser::Name * name{parser::Unwrap<parser::Name>(expr)}) {
6324     if (NameIsKnownOrIntrinsic(*name)) {
6325       return false;
6326     }
6327   }
6328   Walk(expr);
6329   return false;
6330 }
Post(const parser::Designator & x)6331 void ResolveNamesVisitor::Post(const parser::Designator &x) {
6332   ResolveDesignator(x);
6333 }
6334 
Post(const parser::ProcComponentRef & x)6335 void ResolveNamesVisitor::Post(const parser::ProcComponentRef &x) {
6336   ResolveStructureComponent(x.v.thing);
6337 }
Post(const parser::TypeGuardStmt & x)6338 void ResolveNamesVisitor::Post(const parser::TypeGuardStmt &x) {
6339   DeclTypeSpecVisitor::Post(x);
6340   ConstructVisitor::Post(x);
6341 }
Pre(const parser::StmtFunctionStmt & x)6342 bool ResolveNamesVisitor::Pre(const parser::StmtFunctionStmt &x) {
6343   CheckNotInBlock("STATEMENT FUNCTION"); // C1107
6344   if (HandleStmtFunction(x)) {
6345     return false;
6346   } else {
6347     // This is an array element assignment: resolve names of indices
6348     const auto &names{std::get<std::list<parser::Name>>(x.t)};
6349     for (auto &name : names) {
6350       ResolveName(name);
6351     }
6352     return true;
6353   }
6354 }
6355 
Pre(const parser::DefinedOpName & x)6356 bool ResolveNamesVisitor::Pre(const parser::DefinedOpName &x) {
6357   const parser::Name &name{x.v};
6358   if (FindSymbol(name)) {
6359     // OK
6360   } else if (IsLogicalConstant(context(), name.source)) {
6361     Say(name,
6362         "Logical constant '%s' may not be used as a defined operator"_err_en_US);
6363   } else {
6364     // Resolved later in expression semantics
6365     MakePlaceholder(name, MiscDetails::Kind::TypeBoundDefinedOp);
6366   }
6367   return false;
6368 }
6369 
Post(const parser::AssignStmt & x)6370 void ResolveNamesVisitor::Post(const parser::AssignStmt &x) {
6371   if (auto *name{ResolveName(std::get<parser::Name>(x.t))}) {
6372     ConvertToObjectEntity(DEREF(name->symbol));
6373   }
6374 }
Post(const parser::AssignedGotoStmt & x)6375 void ResolveNamesVisitor::Post(const parser::AssignedGotoStmt &x) {
6376   if (auto *name{ResolveName(std::get<parser::Name>(x.t))}) {
6377     ConvertToObjectEntity(DEREF(name->symbol));
6378   }
6379 }
6380 
Pre(const parser::ProgramUnit & x)6381 bool ResolveNamesVisitor::Pre(const parser::ProgramUnit &x) {
6382   if (std::holds_alternative<common::Indirection<parser::CompilerDirective>>(
6383           x.u)) {
6384     // TODO: global directives
6385     return true;
6386   }
6387   auto root{ProgramTree::Build(x)};
6388   SetScope(context().globalScope());
6389   ResolveSpecificationParts(root);
6390   FinishSpecificationParts(root);
6391   inExecutionPart_ = true;
6392   ResolveExecutionParts(root);
6393   inExecutionPart_ = false;
6394   ResolveAccParts(context(), x);
6395   ResolveOmpParts(context(), x);
6396   return false;
6397 }
6398 
6399 // References to procedures need to record that their symbols are known
6400 // to be procedures, so that they don't get converted to objects by default.
6401 class ExecutionPartSkimmer {
6402 public:
ExecutionPartSkimmer(ResolveNamesVisitor & resolver)6403   explicit ExecutionPartSkimmer(ResolveNamesVisitor &resolver)
6404       : resolver_{resolver} {}
6405 
Walk(const parser::ExecutionPart * exec)6406   void Walk(const parser::ExecutionPart *exec) {
6407     if (exec) {
6408       parser::Walk(*exec, *this);
6409     }
6410   }
6411 
Pre(const A &)6412   template <typename A> bool Pre(const A &) { return true; }
Post(const A &)6413   template <typename A> void Post(const A &) {}
Post(const parser::FunctionReference & fr)6414   void Post(const parser::FunctionReference &fr) {
6415     resolver_.NoteExecutablePartCall(Symbol::Flag::Function, fr.v);
6416   }
Post(const parser::CallStmt & cs)6417   void Post(const parser::CallStmt &cs) {
6418     resolver_.NoteExecutablePartCall(Symbol::Flag::Subroutine, cs.v);
6419   }
6420 
6421 private:
6422   ResolveNamesVisitor &resolver_;
6423 };
6424 
6425 // Build the scope tree and resolve names in the specification parts of this
6426 // node and its children
ResolveSpecificationParts(ProgramTree & node)6427 void ResolveNamesVisitor::ResolveSpecificationParts(ProgramTree &node) {
6428   if (node.isSpecificationPartResolved()) {
6429     return; // been here already
6430   }
6431   node.set_isSpecificationPartResolved();
6432   if (!BeginScopeForNode(node)) {
6433     return; // an error prevented scope from being created
6434   }
6435   Scope &scope{currScope()};
6436   node.set_scope(scope);
6437   AddSubpNames(node);
6438   std::visit(
6439       [&](const auto *x) {
6440         if (x) {
6441           Walk(*x);
6442         }
6443       },
6444       node.stmt());
6445   Walk(node.spec());
6446   // If this is a function, convert result to an object. This is to prevent the
6447   // result from being converted later to a function symbol if it is called
6448   // inside the function.
6449   // If the result is function pointer, then ConvertToObjectEntity will not
6450   // convert the result to an object, and calling the symbol inside the function
6451   // will result in calls to the result pointer.
6452   // A function cannot be called recursively if RESULT was not used to define a
6453   // distinct result name (15.6.2.2 point 4.).
6454   if (Symbol * symbol{scope.symbol()}) {
6455     if (auto *details{symbol->detailsIf<SubprogramDetails>()}) {
6456       if (details->isFunction()) {
6457         ConvertToObjectEntity(const_cast<Symbol &>(details->result()));
6458       }
6459     }
6460   }
6461   if (node.IsModule()) {
6462     ApplyDefaultAccess();
6463   }
6464   for (auto &child : node.children()) {
6465     ResolveSpecificationParts(child);
6466   }
6467   ExecutionPartSkimmer{*this}.Walk(node.exec());
6468   PopScope();
6469   // Ensure that every object entity has a type.
6470   for (auto &pair : *node.scope()) {
6471     ApplyImplicitRules(*pair.second);
6472   }
6473 }
6474 
6475 // Add SubprogramNameDetails symbols for module and internal subprograms
AddSubpNames(ProgramTree & node)6476 void ResolveNamesVisitor::AddSubpNames(ProgramTree &node) {
6477   auto kind{
6478       node.IsModule() ? SubprogramKind::Module : SubprogramKind::Internal};
6479   for (auto &child : node.children()) {
6480     auto &symbol{MakeSymbol(child.name(), SubprogramNameDetails{kind, child})};
6481     symbol.set(child.GetSubpFlag());
6482   }
6483 }
6484 
6485 // Push a new scope for this node or return false on error.
BeginScopeForNode(const ProgramTree & node)6486 bool ResolveNamesVisitor::BeginScopeForNode(const ProgramTree &node) {
6487   switch (node.GetKind()) {
6488     SWITCH_COVERS_ALL_CASES
6489   case ProgramTree::Kind::Program:
6490     PushScope(Scope::Kind::MainProgram,
6491         &MakeSymbol(node.name(), MainProgramDetails{}));
6492     return true;
6493   case ProgramTree::Kind::Function:
6494   case ProgramTree::Kind::Subroutine:
6495     return BeginSubprogram(
6496         node.name(), node.GetSubpFlag(), node.HasModulePrefix());
6497   case ProgramTree::Kind::MpSubprogram:
6498     return BeginMpSubprogram(node.name());
6499   case ProgramTree::Kind::Module:
6500     BeginModule(node.name(), false);
6501     return true;
6502   case ProgramTree::Kind::Submodule:
6503     return BeginSubmodule(node.name(), node.GetParentId());
6504   case ProgramTree::Kind::BlockData:
6505     PushBlockDataScope(node.name());
6506     return true;
6507   }
6508 }
6509 
6510 // Some analyses and checks, such as the processing of initializers of
6511 // pointers, are deferred until all of the pertinent specification parts
6512 // have been visited.  This deferred processing enables the use of forward
6513 // references in these circumstances.
6514 class DeferredCheckVisitor {
6515 public:
DeferredCheckVisitor(ResolveNamesVisitor & resolver)6516   explicit DeferredCheckVisitor(ResolveNamesVisitor &resolver)
6517       : resolver_{resolver} {}
6518 
Walk(const A & x)6519   template <typename A> void Walk(const A &x) { parser::Walk(x, *this); }
6520 
Pre(const A &)6521   template <typename A> bool Pre(const A &) { return true; }
Post(const A &)6522   template <typename A> void Post(const A &) {}
6523 
Post(const parser::DerivedTypeStmt & x)6524   void Post(const parser::DerivedTypeStmt &x) {
6525     const auto &name{std::get<parser::Name>(x.t)};
6526     if (Symbol * symbol{name.symbol}) {
6527       if (Scope * scope{symbol->scope()}) {
6528         if (scope->IsDerivedType()) {
6529           resolver_.PushScope(*scope);
6530           pushedScope_ = true;
6531         }
6532       }
6533     }
6534   }
Post(const parser::EndTypeStmt &)6535   void Post(const parser::EndTypeStmt &) {
6536     if (pushedScope_) {
6537       resolver_.PopScope();
6538       pushedScope_ = false;
6539     }
6540   }
6541 
Post(const parser::ProcInterface & pi)6542   void Post(const parser::ProcInterface &pi) {
6543     if (const auto *name{std::get_if<parser::Name>(&pi.u)}) {
6544       resolver_.CheckExplicitInterface(*name);
6545     }
6546   }
Pre(const parser::EntityDecl & decl)6547   bool Pre(const parser::EntityDecl &decl) {
6548     Init(std::get<parser::Name>(decl.t),
6549         std::get<std::optional<parser::Initialization>>(decl.t));
6550     return false;
6551   }
Pre(const parser::ComponentDecl & decl)6552   bool Pre(const parser::ComponentDecl &decl) {
6553     Init(std::get<parser::Name>(decl.t),
6554         std::get<std::optional<parser::Initialization>>(decl.t));
6555     return false;
6556   }
Pre(const parser::ProcDecl & decl)6557   bool Pre(const parser::ProcDecl &decl) {
6558     if (const auto &init{
6559             std::get<std::optional<parser::ProcPointerInit>>(decl.t)}) {
6560       resolver_.PointerInitialization(std::get<parser::Name>(decl.t), *init);
6561     }
6562     return false;
6563   }
Post(const parser::TypeBoundProcedureStmt::WithInterface & tbps)6564   void Post(const parser::TypeBoundProcedureStmt::WithInterface &tbps) {
6565     resolver_.CheckExplicitInterface(tbps.interfaceName);
6566   }
Post(const parser::TypeBoundProcedureStmt::WithoutInterface & tbps)6567   void Post(const parser::TypeBoundProcedureStmt::WithoutInterface &tbps) {
6568     if (pushedScope_) {
6569       resolver_.CheckBindings(tbps);
6570     }
6571   }
6572 
6573 private:
Init(const parser::Name & name,const std::optional<parser::Initialization> & init)6574   void Init(const parser::Name &name,
6575       const std::optional<parser::Initialization> &init) {
6576     if (init) {
6577       if (const auto *target{
6578               std::get_if<parser::InitialDataTarget>(&init->u)}) {
6579         resolver_.PointerInitialization(name, *target);
6580       }
6581     }
6582   }
6583 
6584   ResolveNamesVisitor &resolver_;
6585   bool pushedScope_{false};
6586 };
6587 
6588 // Perform checks and completions that need to happen after all of
6589 // the specification parts but before any of the execution parts.
FinishSpecificationParts(const ProgramTree & node)6590 void ResolveNamesVisitor::FinishSpecificationParts(const ProgramTree &node) {
6591   if (!node.scope()) {
6592     return; // error occurred creating scope
6593   }
6594   SetScope(*node.scope());
6595   // The initializers of pointers, the default initializers of pointer
6596   // components, and non-deferred type-bound procedure bindings have not
6597   // yet been traversed.
6598   // We do that now, when any (formerly) forward references that appear
6599   // in those initializers will resolve to the right symbols without
6600   // incurring spurious errors with IMPLICIT NONE.
6601   DeferredCheckVisitor{*this}.Walk(node.spec());
6602   DeferredCheckVisitor{*this}.Walk(node.exec()); // for BLOCK
6603   for (Scope &childScope : currScope().children()) {
6604     if (childScope.IsParameterizedDerivedTypeInstantiation()) {
6605       FinishDerivedTypeInstantiation(childScope);
6606     }
6607   }
6608   for (const auto &child : node.children()) {
6609     FinishSpecificationParts(child);
6610   }
6611 }
6612 
6613 // Duplicate and fold component object pointer default initializer designators
6614 // using the actual type parameter values of each particular instantiation.
6615 // Validation is done later in declaration checking.
FinishDerivedTypeInstantiation(Scope & scope)6616 void ResolveNamesVisitor::FinishDerivedTypeInstantiation(Scope &scope) {
6617   CHECK(scope.IsDerivedType() && !scope.symbol());
6618   if (DerivedTypeSpec * spec{scope.derivedTypeSpec()}) {
6619     spec->Instantiate(currScope(), context());
6620     const Symbol &origTypeSymbol{spec->typeSymbol()};
6621     if (const Scope * origTypeScope{origTypeSymbol.scope()}) {
6622       CHECK(origTypeScope->IsDerivedType() &&
6623           origTypeScope->symbol() == &origTypeSymbol);
6624       auto &foldingContext{GetFoldingContext()};
6625       auto restorer{foldingContext.WithPDTInstance(*spec)};
6626       for (auto &pair : scope) {
6627         Symbol &comp{*pair.second};
6628         const Symbol &origComp{DEREF(FindInScope(*origTypeScope, comp.name()))};
6629         if (IsPointer(comp)) {
6630           if (auto *details{comp.detailsIf<ObjectEntityDetails>()}) {
6631             auto origDetails{origComp.get<ObjectEntityDetails>()};
6632             if (const MaybeExpr & init{origDetails.init()}) {
6633               SomeExpr newInit{*init};
6634               MaybeExpr folded{
6635                   evaluate::Fold(foldingContext, std::move(newInit))};
6636               details->set_init(std::move(folded));
6637             }
6638           }
6639         }
6640       }
6641     }
6642   }
6643 }
6644 
6645 // Resolve names in the execution part of this node and its children
ResolveExecutionParts(const ProgramTree & node)6646 void ResolveNamesVisitor::ResolveExecutionParts(const ProgramTree &node) {
6647   if (!node.scope()) {
6648     return; // error occurred creating scope
6649   }
6650   SetScope(*node.scope());
6651   if (const auto *exec{node.exec()}) {
6652     Walk(*exec);
6653   }
6654   PopScope(); // converts unclassified entities into objects
6655   for (const auto &child : node.children()) {
6656     ResolveExecutionParts(child);
6657   }
6658 }
6659 
Post(const parser::Program &)6660 void ResolveNamesVisitor::Post(const parser::Program &) {
6661   // ensure that all temps were deallocated
6662   CHECK(!attrs_);
6663   CHECK(!GetDeclTypeSpec());
6664 }
6665 
6666 // A singleton instance of the scope -> IMPLICIT rules mapping is
6667 // shared by all instances of ResolveNamesVisitor and accessed by this
6668 // pointer when the visitors (other than the top-level original) are
6669 // constructed.
6670 static ImplicitRulesMap *sharedImplicitRulesMap{nullptr};
6671 
ResolveNames(SemanticsContext & context,const parser::Program & program)6672 bool ResolveNames(SemanticsContext &context, const parser::Program &program) {
6673   ImplicitRulesMap implicitRulesMap;
6674   auto restorer{common::ScopedSet(sharedImplicitRulesMap, &implicitRulesMap)};
6675   ResolveNamesVisitor{context, implicitRulesMap}.Walk(program);
6676   return !context.AnyFatalError();
6677 }
6678 
6679 // Processes a module (but not internal) function when it is referenced
6680 // in a specification expression in a sibling procedure.
ResolveSpecificationParts(SemanticsContext & context,const Symbol & subprogram)6681 void ResolveSpecificationParts(
6682     SemanticsContext &context, const Symbol &subprogram) {
6683   auto originalLocation{context.location()};
6684   ResolveNamesVisitor visitor{context, DEREF(sharedImplicitRulesMap)};
6685   ProgramTree &node{subprogram.get<SubprogramNameDetails>().node()};
6686   const Scope &moduleScope{subprogram.owner()};
6687   visitor.SetScope(const_cast<Scope &>(moduleScope));
6688   visitor.ResolveSpecificationParts(node);
6689   context.set_location(std::move(originalLocation));
6690 }
6691 
6692 } // namespace Fortran::semantics
6693