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