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