xref: /llvm-project/flang/lib/Semantics/resolve-names.cpp (revision 9f0f54a6290ead2e1581d75582759822a19fd885)
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 "definable.h"
11 #include "mod-file.h"
12 #include "pointer-assignment.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/Common/visit.h"
21 #include "flang/Evaluate/characteristics.h"
22 #include "flang/Evaluate/check-expression.h"
23 #include "flang/Evaluate/common.h"
24 #include "flang/Evaluate/fold-designator.h"
25 #include "flang/Evaluate/fold.h"
26 #include "flang/Evaluate/intrinsics.h"
27 #include "flang/Evaluate/tools.h"
28 #include "flang/Evaluate/type.h"
29 #include "flang/Parser/parse-tree-visitor.h"
30 #include "flang/Parser/parse-tree.h"
31 #include "flang/Parser/tools.h"
32 #include "flang/Semantics/attr.h"
33 #include "flang/Semantics/expression.h"
34 #include "flang/Semantics/openmp-modifiers.h"
35 #include "flang/Semantics/program-tree.h"
36 #include "flang/Semantics/scope.h"
37 #include "flang/Semantics/semantics.h"
38 #include "flang/Semantics/symbol.h"
39 #include "flang/Semantics/tools.h"
40 #include "flang/Semantics/type.h"
41 #include "llvm/Support/raw_ostream.h"
42 #include <list>
43 #include <map>
44 #include <set>
45 #include <stack>
46 
47 namespace Fortran::semantics {
48 
49 using namespace parser::literals;
50 
51 template <typename T> using Indirection = common::Indirection<T>;
52 using Message = parser::Message;
53 using Messages = parser::Messages;
54 using MessageFixedText = parser::MessageFixedText;
55 using MessageFormattedText = parser::MessageFormattedText;
56 
57 class ResolveNamesVisitor;
58 class ScopeHandler;
59 
60 // ImplicitRules maps initial character of identifier to the DeclTypeSpec
61 // representing the implicit type; std::nullopt if none.
62 // It also records the presence of IMPLICIT NONE statements.
63 // When inheritFromParent is set, defaults come from the parent rules.
64 class ImplicitRules {
65 public:
66   ImplicitRules(SemanticsContext &context, const ImplicitRules *parent)
67       : parent_{parent}, context_{context},
68         inheritFromParent_{parent != nullptr} {}
69   bool isImplicitNoneType() const;
70   bool isImplicitNoneExternal() const;
71   void set_isImplicitNoneType(bool x) { isImplicitNoneType_ = x; }
72   void set_isImplicitNoneExternal(bool x) { isImplicitNoneExternal_ = x; }
73   void set_inheritFromParent(bool x) { inheritFromParent_ = x; }
74   // Get the implicit type for this name. May be null.
75   const DeclTypeSpec *GetType(
76       SourceName, bool respectImplicitNone = true) const;
77   // Record the implicit type for the range of characters [fromLetter,
78   // toLetter].
79   void SetTypeMapping(const DeclTypeSpec &type, parser::Location fromLetter,
80       parser::Location toLetter);
81 
82 private:
83   static char Incr(char ch);
84 
85   const ImplicitRules *parent_;
86   SemanticsContext &context_;
87   bool inheritFromParent_{false}; // look in parent if not specified here
88   bool isImplicitNoneType_{
89       context_.IsEnabled(common::LanguageFeature::ImplicitNoneTypeAlways)};
90   bool isImplicitNoneExternal_{false};
91   // map_ contains the mapping between letters and types that were defined
92   // by the IMPLICIT statements of the related scope. It does not contain
93   // the default Fortran mappings nor the mapping defined in parents.
94   std::map<char, common::Reference<const DeclTypeSpec>> map_;
95 
96   friend llvm::raw_ostream &operator<<(
97       llvm::raw_ostream &, const ImplicitRules &);
98   friend void ShowImplicitRule(
99       llvm::raw_ostream &, const ImplicitRules &, char);
100 };
101 
102 // scope -> implicit rules for that scope
103 using ImplicitRulesMap = std::map<const Scope *, ImplicitRules>;
104 
105 // Track statement source locations and save messages.
106 class MessageHandler {
107 public:
108   MessageHandler() { DIE("MessageHandler: default-constructed"); }
109   explicit MessageHandler(SemanticsContext &c) : context_{&c} {}
110   Messages &messages() { return context_->messages(); };
111   const std::optional<SourceName> &currStmtSource() {
112     return context_->location();
113   }
114   void set_currStmtSource(const std::optional<SourceName> &source) {
115     context_->set_location(source);
116   }
117 
118   // Emit a message associated with the current statement source.
119   Message &Say(MessageFixedText &&);
120   Message &Say(MessageFormattedText &&);
121   // Emit a message about a SourceName
122   Message &Say(const SourceName &, MessageFixedText &&);
123   // Emit a formatted message associated with a source location.
124   template <typename... A>
125   Message &Say(const SourceName &source, MessageFixedText &&msg, A &&...args) {
126     return context_->Say(source, std::move(msg), std::forward<A>(args)...);
127   }
128 
129 private:
130   SemanticsContext *context_;
131 };
132 
133 // Inheritance graph for the parse tree visitation classes that follow:
134 //   BaseVisitor
135 //   + AttrsVisitor
136 //   | + DeclTypeSpecVisitor
137 //   |   + ImplicitRulesVisitor
138 //   |     + ScopeHandler ------------------+
139 //   |       + ModuleVisitor -------------+ |
140 //   |       + GenericHandler -------+    | |
141 //   |       | + InterfaceVisitor    |    | |
142 //   |       +-+ SubprogramVisitor ==|==+ | |
143 //   + ArraySpecVisitor              |  | | |
144 //     + DeclarationVisitor <--------+  | | |
145 //       + ConstructVisitor             | | |
146 //         + ResolveNamesVisitor <------+-+-+
147 
148 class BaseVisitor {
149 public:
150   BaseVisitor() { DIE("BaseVisitor: default-constructed"); }
151   BaseVisitor(
152       SemanticsContext &c, ResolveNamesVisitor &v, ImplicitRulesMap &rules)
153       : implicitRulesMap_{&rules}, this_{&v}, context_{&c}, messageHandler_{c} {
154   }
155   template <typename T> void Walk(const T &);
156 
157   MessageHandler &messageHandler() { return messageHandler_; }
158   const std::optional<SourceName> &currStmtSource() {
159     return context_->location();
160   }
161   SemanticsContext &context() const { return *context_; }
162   evaluate::FoldingContext &GetFoldingContext() const {
163     return context_->foldingContext();
164   }
165   bool IsIntrinsic(
166       const SourceName &name, std::optional<Symbol::Flag> flag) const {
167     if (!flag) {
168       return context_->intrinsics().IsIntrinsic(name.ToString());
169     } else if (flag == Symbol::Flag::Function) {
170       return context_->intrinsics().IsIntrinsicFunction(name.ToString());
171     } else if (flag == Symbol::Flag::Subroutine) {
172       return context_->intrinsics().IsIntrinsicSubroutine(name.ToString());
173     } else {
174       DIE("expected Subroutine or Function flag");
175     }
176   }
177 
178   bool InModuleFile() const {
179     return GetFoldingContext().moduleFileName().has_value();
180   }
181 
182   // Make a placeholder symbol for a Name that otherwise wouldn't have one.
183   // It is not in any scope and always has MiscDetails.
184   void MakePlaceholder(const parser::Name &, MiscDetails::Kind);
185 
186   template <typename T> common::IfNoLvalue<T, T> FoldExpr(T &&expr) {
187     return evaluate::Fold(GetFoldingContext(), std::move(expr));
188   }
189 
190   template <typename T> MaybeExpr EvaluateExpr(const T &expr) {
191     return FoldExpr(AnalyzeExpr(*context_, expr));
192   }
193 
194   template <typename T>
195   MaybeExpr EvaluateNonPointerInitializer(
196       const Symbol &symbol, const T &expr, parser::CharBlock source) {
197     if (!context().HasError(symbol)) {
198       if (auto maybeExpr{AnalyzeExpr(*context_, expr)}) {
199         auto restorer{GetFoldingContext().messages().SetLocation(source)};
200         return evaluate::NonPointerInitializationExpr(
201             symbol, std::move(*maybeExpr), GetFoldingContext());
202       }
203     }
204     return std::nullopt;
205   }
206 
207   template <typename T> MaybeIntExpr EvaluateIntExpr(const T &expr) {
208     return semantics::EvaluateIntExpr(*context_, expr);
209   }
210 
211   template <typename T>
212   MaybeSubscriptIntExpr EvaluateSubscriptIntExpr(const T &expr) {
213     if (MaybeIntExpr maybeIntExpr{EvaluateIntExpr(expr)}) {
214       return FoldExpr(evaluate::ConvertToType<evaluate::SubscriptInteger>(
215           std::move(*maybeIntExpr)));
216     } else {
217       return std::nullopt;
218     }
219   }
220 
221   template <typename... A> Message &Say(A &&...args) {
222     return messageHandler_.Say(std::forward<A>(args)...);
223   }
224   template <typename... A>
225   Message &Say(
226       const parser::Name &name, MessageFixedText &&text, const A &...args) {
227     return messageHandler_.Say(name.source, std::move(text), args...);
228   }
229 
230 protected:
231   ImplicitRulesMap *implicitRulesMap_{nullptr};
232 
233 private:
234   ResolveNamesVisitor *this_;
235   SemanticsContext *context_;
236   MessageHandler messageHandler_;
237 };
238 
239 // Provide Post methods to collect attributes into a member variable.
240 class AttrsVisitor : public virtual BaseVisitor {
241 public:
242   bool BeginAttrs(); // always returns true
243   Attrs GetAttrs();
244   std::optional<common::CUDADataAttr> cudaDataAttr() { return cudaDataAttr_; }
245   Attrs EndAttrs();
246   bool SetPassNameOn(Symbol &);
247   void SetBindNameOn(Symbol &);
248   void Post(const parser::LanguageBindingSpec &);
249   bool Pre(const parser::IntentSpec &);
250   bool Pre(const parser::Pass &);
251 
252   bool CheckAndSet(Attr);
253 
254 // Simple case: encountering CLASSNAME causes ATTRNAME to be set.
255 #define HANDLE_ATTR_CLASS(CLASSNAME, ATTRNAME) \
256   bool Pre(const parser::CLASSNAME &) { \
257     CheckAndSet(Attr::ATTRNAME); \
258     return false; \
259   }
260   HANDLE_ATTR_CLASS(PrefixSpec::Elemental, ELEMENTAL)
261   HANDLE_ATTR_CLASS(PrefixSpec::Impure, IMPURE)
262   HANDLE_ATTR_CLASS(PrefixSpec::Module, MODULE)
263   HANDLE_ATTR_CLASS(PrefixSpec::Non_Recursive, NON_RECURSIVE)
264   HANDLE_ATTR_CLASS(PrefixSpec::Pure, PURE)
265   HANDLE_ATTR_CLASS(PrefixSpec::Recursive, RECURSIVE)
266   HANDLE_ATTR_CLASS(TypeAttrSpec::BindC, BIND_C)
267   HANDLE_ATTR_CLASS(BindAttr::Deferred, DEFERRED)
268   HANDLE_ATTR_CLASS(BindAttr::Non_Overridable, NON_OVERRIDABLE)
269   HANDLE_ATTR_CLASS(Abstract, ABSTRACT)
270   HANDLE_ATTR_CLASS(Allocatable, ALLOCATABLE)
271   HANDLE_ATTR_CLASS(Asynchronous, ASYNCHRONOUS)
272   HANDLE_ATTR_CLASS(Contiguous, CONTIGUOUS)
273   HANDLE_ATTR_CLASS(External, EXTERNAL)
274   HANDLE_ATTR_CLASS(Intrinsic, INTRINSIC)
275   HANDLE_ATTR_CLASS(NoPass, NOPASS)
276   HANDLE_ATTR_CLASS(Optional, OPTIONAL)
277   HANDLE_ATTR_CLASS(Parameter, PARAMETER)
278   HANDLE_ATTR_CLASS(Pointer, POINTER)
279   HANDLE_ATTR_CLASS(Protected, PROTECTED)
280   HANDLE_ATTR_CLASS(Save, SAVE)
281   HANDLE_ATTR_CLASS(Target, TARGET)
282   HANDLE_ATTR_CLASS(Value, VALUE)
283   HANDLE_ATTR_CLASS(Volatile, VOLATILE)
284 #undef HANDLE_ATTR_CLASS
285   bool Pre(const common::CUDADataAttr);
286 
287 protected:
288   std::optional<Attrs> attrs_;
289   std::optional<common::CUDADataAttr> cudaDataAttr_;
290 
291   Attr AccessSpecToAttr(const parser::AccessSpec &x) {
292     switch (x.v) {
293     case parser::AccessSpec::Kind::Public:
294       return Attr::PUBLIC;
295     case parser::AccessSpec::Kind::Private:
296       return Attr::PRIVATE;
297     }
298     llvm_unreachable("Switch covers all cases"); // suppress g++ warning
299   }
300   Attr IntentSpecToAttr(const parser::IntentSpec &x) {
301     switch (x.v) {
302     case parser::IntentSpec::Intent::In:
303       return Attr::INTENT_IN;
304     case parser::IntentSpec::Intent::Out:
305       return Attr::INTENT_OUT;
306     case parser::IntentSpec::Intent::InOut:
307       return Attr::INTENT_INOUT;
308     }
309     llvm_unreachable("Switch covers all cases"); // suppress g++ warning
310   }
311 
312 private:
313   bool IsDuplicateAttr(Attr);
314   bool HaveAttrConflict(Attr, Attr, Attr);
315   bool IsConflictingAttr(Attr);
316 
317   MaybeExpr bindName_; // from BIND(C, NAME="...")
318   bool isCDefined_{false}; // BIND(C, NAME="...", CDEFINED) extension
319   std::optional<SourceName> passName_; // from PASS(...)
320 };
321 
322 // Find and create types from declaration-type-spec nodes.
323 class DeclTypeSpecVisitor : public AttrsVisitor {
324 public:
325   using AttrsVisitor::Post;
326   using AttrsVisitor::Pre;
327   void Post(const parser::IntrinsicTypeSpec::DoublePrecision &);
328   void Post(const parser::IntrinsicTypeSpec::DoubleComplex &);
329   void Post(const parser::DeclarationTypeSpec::ClassStar &);
330   void Post(const parser::DeclarationTypeSpec::TypeStar &);
331   bool Pre(const parser::TypeGuardStmt &);
332   void Post(const parser::TypeGuardStmt &);
333   void Post(const parser::TypeSpec &);
334 
335   // Walk the parse tree of a type spec and return the DeclTypeSpec for it.
336   template <typename T>
337   const DeclTypeSpec *ProcessTypeSpec(const T &x, bool allowForward = false) {
338     auto restorer{common::ScopedSet(state_, State{})};
339     set_allowForwardReferenceToDerivedType(allowForward);
340     BeginDeclTypeSpec();
341     Walk(x);
342     const auto *type{GetDeclTypeSpec()};
343     EndDeclTypeSpec();
344     return type;
345   }
346 
347 protected:
348   struct State {
349     bool expectDeclTypeSpec{false}; // should see decl-type-spec only when true
350     const DeclTypeSpec *declTypeSpec{nullptr};
351     struct {
352       DerivedTypeSpec *type{nullptr};
353       DeclTypeSpec::Category category{DeclTypeSpec::TypeDerived};
354     } derived;
355     bool allowForwardReferenceToDerivedType{false};
356   };
357 
358   bool allowForwardReferenceToDerivedType() const {
359     return state_.allowForwardReferenceToDerivedType;
360   }
361   void set_allowForwardReferenceToDerivedType(bool yes) {
362     state_.allowForwardReferenceToDerivedType = yes;
363   }
364 
365   const DeclTypeSpec *GetDeclTypeSpec();
366   void BeginDeclTypeSpec();
367   void EndDeclTypeSpec();
368   void SetDeclTypeSpec(const DeclTypeSpec &);
369   void SetDeclTypeSpecCategory(DeclTypeSpec::Category);
370   DeclTypeSpec::Category GetDeclTypeSpecCategory() const {
371     return state_.derived.category;
372   }
373   KindExpr GetKindParamExpr(
374       TypeCategory, const std::optional<parser::KindSelector> &);
375   void CheckForAbstractType(const Symbol &typeSymbol);
376 
377 private:
378   State state_;
379 
380   void MakeNumericType(TypeCategory, int kind);
381 };
382 
383 // Visit ImplicitStmt and related parse tree nodes and updates implicit rules.
384 class ImplicitRulesVisitor : public DeclTypeSpecVisitor {
385 public:
386   using DeclTypeSpecVisitor::Post;
387   using DeclTypeSpecVisitor::Pre;
388   using ImplicitNoneNameSpec = parser::ImplicitStmt::ImplicitNoneNameSpec;
389 
390   void Post(const parser::ParameterStmt &);
391   bool Pre(const parser::ImplicitStmt &);
392   bool Pre(const parser::LetterSpec &);
393   bool Pre(const parser::ImplicitSpec &);
394   void Post(const parser::ImplicitSpec &);
395 
396   const DeclTypeSpec *GetType(
397       SourceName name, bool respectImplicitNoneType = true) {
398     return implicitRules_->GetType(name, respectImplicitNoneType);
399   }
400   bool isImplicitNoneType() const {
401     return implicitRules_->isImplicitNoneType();
402   }
403   bool isImplicitNoneType(const Scope &scope) const {
404     return implicitRulesMap_->at(&scope).isImplicitNoneType();
405   }
406   bool isImplicitNoneExternal() const {
407     return implicitRules_->isImplicitNoneExternal();
408   }
409   void set_inheritFromParent(bool x) {
410     implicitRules_->set_inheritFromParent(x);
411   }
412 
413 protected:
414   void BeginScope(const Scope &);
415   void SetScope(const Scope &);
416 
417 private:
418   // implicit rules in effect for current scope
419   ImplicitRules *implicitRules_{nullptr};
420   std::optional<SourceName> prevImplicit_;
421   std::optional<SourceName> prevImplicitNone_;
422   std::optional<SourceName> prevImplicitNoneType_;
423   std::optional<SourceName> prevParameterStmt_;
424 
425   bool HandleImplicitNone(const std::list<ImplicitNoneNameSpec> &nameSpecs);
426 };
427 
428 // Track array specifications. They can occur in AttrSpec, EntityDecl,
429 // ObjectDecl, DimensionStmt, CommonBlockObject, BasedPointer, and
430 // ComponentDecl.
431 // 1. INTEGER, DIMENSION(10) :: x
432 // 2. INTEGER :: x(10)
433 // 3. ALLOCATABLE :: x(:)
434 // 4. DIMENSION :: x(10)
435 // 5. COMMON x(10)
436 // 6. POINTER(p,x(10))
437 class ArraySpecVisitor : public virtual BaseVisitor {
438 public:
439   void Post(const parser::ArraySpec &);
440   void Post(const parser::ComponentArraySpec &);
441   void Post(const parser::CoarraySpec &);
442   void Post(const parser::AttrSpec &) { PostAttrSpec(); }
443   void Post(const parser::ComponentAttrSpec &) { PostAttrSpec(); }
444 
445 protected:
446   const ArraySpec &arraySpec();
447   void set_arraySpec(const ArraySpec arraySpec) { arraySpec_ = arraySpec; }
448   const ArraySpec &coarraySpec();
449   void BeginArraySpec();
450   void EndArraySpec();
451   void ClearArraySpec() { arraySpec_.clear(); }
452   void ClearCoarraySpec() { coarraySpec_.clear(); }
453 
454 private:
455   // arraySpec_/coarraySpec_ are populated from any ArraySpec/CoarraySpec
456   ArraySpec arraySpec_;
457   ArraySpec coarraySpec_;
458   // When an ArraySpec is under an AttrSpec or ComponentAttrSpec, it is moved
459   // into attrArraySpec_
460   ArraySpec attrArraySpec_;
461   ArraySpec attrCoarraySpec_;
462 
463   void PostAttrSpec();
464 };
465 
466 // Manages a stack of function result information.  We defer the processing
467 // of a type specification that appears in the prefix of a FUNCTION statement
468 // until the function result variable appears in the specification part
469 // or the end of the specification part.  This allows for forward references
470 // in the type specification to resolve to local names.
471 class FuncResultStack {
472 public:
473   explicit FuncResultStack(ScopeHandler &scopeHandler)
474       : scopeHandler_{scopeHandler} {}
475   ~FuncResultStack();
476 
477   struct FuncInfo {
478     FuncInfo(const Scope &s, SourceName at) : scope{s}, source{at} {}
479     const Scope &scope;
480     SourceName source;
481     // Parse tree of the type specification in the FUNCTION prefix
482     const parser::DeclarationTypeSpec *parsedType{nullptr};
483     // Name of the function RESULT in the FUNCTION suffix, if any
484     const parser::Name *resultName{nullptr};
485     // Result symbol
486     Symbol *resultSymbol{nullptr};
487     bool inFunctionStmt{false}; // true between Pre/Post of FunctionStmt
488   };
489 
490   // Completes the definition of the top function's result.
491   void CompleteFunctionResultType();
492   // Completes the definition of a symbol if it is the top function's result.
493   void CompleteTypeIfFunctionResult(Symbol &);
494 
495   FuncInfo *Top() { return stack_.empty() ? nullptr : &stack_.back(); }
496   FuncInfo &Push(const Scope &scope, SourceName at) {
497     return stack_.emplace_back(scope, at);
498   }
499   void Pop();
500 
501 private:
502   ScopeHandler &scopeHandler_;
503   std::vector<FuncInfo> stack_;
504 };
505 
506 // Manage a stack of Scopes
507 class ScopeHandler : public ImplicitRulesVisitor {
508 public:
509   using ImplicitRulesVisitor::Post;
510   using ImplicitRulesVisitor::Pre;
511 
512   Scope &currScope() { return DEREF(currScope_); }
513   // The enclosing host procedure if current scope is in an internal procedure
514   Scope *GetHostProcedure();
515   // The innermost enclosing program unit scope, ignoring BLOCK and other
516   // construct scopes.
517   Scope &InclusiveScope();
518   // The enclosing scope, skipping derived types.
519   Scope &NonDerivedTypeScope();
520 
521   // Create a new scope and push it on the scope stack.
522   void PushScope(Scope::Kind kind, Symbol *symbol);
523   void PushScope(Scope &scope);
524   void PopScope();
525   void SetScope(Scope &);
526 
527   template <typename T> bool Pre(const parser::Statement<T> &x) {
528     messageHandler().set_currStmtSource(x.source);
529     currScope_->AddSourceRange(x.source);
530     return true;
531   }
532   template <typename T> void Post(const parser::Statement<T> &) {
533     messageHandler().set_currStmtSource(std::nullopt);
534   }
535 
536   // Special messages: already declared; referencing symbol's declaration;
537   // about a type; two names & locations
538   void SayAlreadyDeclared(const parser::Name &, Symbol &);
539   void SayAlreadyDeclared(const SourceName &, Symbol &);
540   void SayAlreadyDeclared(const SourceName &, const SourceName &);
541   void SayWithReason(
542       const parser::Name &, Symbol &, MessageFixedText &&, Message &&);
543   template <typename... A>
544   Message &SayWithDecl(
545       const parser::Name &, Symbol &, MessageFixedText &&, A &&...args);
546   void SayLocalMustBeVariable(const parser::Name &, Symbol &);
547   Message &SayDerivedType(
548       const SourceName &, MessageFixedText &&, const Scope &);
549   Message &Say2(const SourceName &, MessageFixedText &&, const SourceName &,
550       MessageFixedText &&);
551   Message &Say2(
552       const SourceName &, MessageFixedText &&, Symbol &, MessageFixedText &&);
553   Message &Say2(
554       const parser::Name &, MessageFixedText &&, Symbol &, MessageFixedText &&);
555 
556   // Search for symbol by name in current, parent derived type, and
557   // containing scopes
558   Symbol *FindSymbol(const parser::Name &);
559   Symbol *FindSymbol(const Scope &, const parser::Name &);
560   // Search for name only in scope, not in enclosing scopes.
561   Symbol *FindInScope(const Scope &, const parser::Name &);
562   Symbol *FindInScope(const Scope &, const SourceName &);
563   template <typename T> Symbol *FindInScope(const T &name) {
564     return FindInScope(currScope(), name);
565   }
566   // Search for name in a derived type scope and its parents.
567   Symbol *FindInTypeOrParents(const Scope &, const parser::Name &);
568   Symbol *FindInTypeOrParents(const parser::Name &);
569   Symbol *FindInScopeOrBlockConstructs(const Scope &, SourceName);
570   Symbol *FindSeparateModuleProcedureInterface(const parser::Name &);
571   void EraseSymbol(const parser::Name &);
572   void EraseSymbol(const Symbol &symbol) { currScope().erase(symbol.name()); }
573   // Make a new symbol with the name and attrs of an existing one
574   Symbol &CopySymbol(const SourceName &, const Symbol &);
575 
576   // Make symbols in the current or named scope
577   Symbol &MakeSymbol(Scope &, const SourceName &, Attrs);
578   Symbol &MakeSymbol(const SourceName &, Attrs = Attrs{});
579   Symbol &MakeSymbol(const parser::Name &, Attrs = Attrs{});
580   Symbol &MakeHostAssocSymbol(const parser::Name &, const Symbol &);
581 
582   template <typename D>
583   common::IfNoLvalue<Symbol &, D> MakeSymbol(
584       const parser::Name &name, D &&details) {
585     return MakeSymbol(name, Attrs{}, std::move(details));
586   }
587 
588   template <typename D>
589   common::IfNoLvalue<Symbol &, D> MakeSymbol(
590       const parser::Name &name, const Attrs &attrs, D &&details) {
591     return Resolve(name, MakeSymbol(name.source, attrs, std::move(details)));
592   }
593 
594   template <typename D>
595   common::IfNoLvalue<Symbol &, D> MakeSymbol(
596       const SourceName &name, const Attrs &attrs, D &&details) {
597     // Note: don't use FindSymbol here. If this is a derived type scope,
598     // we want to detect whether the name is already declared as a component.
599     auto *symbol{FindInScope(name)};
600     if (!symbol) {
601       symbol = &MakeSymbol(name, attrs);
602       symbol->set_details(std::move(details));
603       return *symbol;
604     }
605     if constexpr (std::is_same_v<DerivedTypeDetails, D>) {
606       if (auto *d{symbol->detailsIf<GenericDetails>()}) {
607         if (!d->specific()) {
608           // derived type with same name as a generic
609           auto *derivedType{d->derivedType()};
610           if (!derivedType) {
611             derivedType =
612                 &currScope().MakeSymbol(name, attrs, std::move(details));
613             d->set_derivedType(*derivedType);
614           } else if (derivedType->CanReplaceDetails(details)) {
615             // was forward-referenced
616             CheckDuplicatedAttrs(name, *symbol, attrs);
617             SetExplicitAttrs(*derivedType, attrs);
618             derivedType->set_details(std::move(details));
619           } else {
620             SayAlreadyDeclared(name, *derivedType);
621           }
622           return *derivedType;
623         }
624       }
625     } else if constexpr (std::is_same_v<ProcEntityDetails, D>) {
626       if (auto *d{symbol->detailsIf<GenericDetails>()}) {
627         if (!d->derivedType()) {
628           // procedure pointer with same name as a generic
629           auto *specific{d->specific()};
630           if (!specific) {
631             specific = &currScope().MakeSymbol(name, attrs, std::move(details));
632             d->set_specific(*specific);
633           } else {
634             SayAlreadyDeclared(name, *specific);
635           }
636           return *specific;
637         }
638       }
639     }
640     if (symbol->CanReplaceDetails(details)) {
641       // update the existing symbol
642       CheckDuplicatedAttrs(name, *symbol, attrs);
643       SetExplicitAttrs(*symbol, attrs);
644       if constexpr (std::is_same_v<SubprogramDetails, D>) {
645         // Dummy argument defined by explicit interface?
646         details.set_isDummy(IsDummy(*symbol));
647       }
648       symbol->set_details(std::move(details));
649       return *symbol;
650     } else if constexpr (std::is_same_v<UnknownDetails, D>) {
651       CheckDuplicatedAttrs(name, *symbol, attrs);
652       SetExplicitAttrs(*symbol, attrs);
653       return *symbol;
654     } else {
655       if (!CheckPossibleBadForwardRef(*symbol)) {
656         if (name.empty() && symbol->name().empty()) {
657           // report the error elsewhere
658           return *symbol;
659         }
660         Symbol &errSym{*symbol};
661         if (auto *d{symbol->detailsIf<GenericDetails>()}) {
662           if (d->specific()) {
663             errSym = *d->specific();
664           } else if (d->derivedType()) {
665             errSym = *d->derivedType();
666           }
667         }
668         SayAlreadyDeclared(name, errSym);
669       }
670       // replace the old symbol with a new one with correct details
671       EraseSymbol(*symbol);
672       auto &result{MakeSymbol(name, attrs, std::move(details))};
673       context().SetError(result);
674       return result;
675     }
676   }
677 
678   void MakeExternal(Symbol &);
679 
680   // C815 duplicated attribute checking; returns false on error
681   bool CheckDuplicatedAttr(SourceName, Symbol &, Attr);
682   bool CheckDuplicatedAttrs(SourceName, Symbol &, Attrs);
683 
684   void SetExplicitAttr(Symbol &symbol, Attr attr) const {
685     symbol.attrs().set(attr);
686     symbol.implicitAttrs().reset(attr);
687   }
688   void SetExplicitAttrs(Symbol &symbol, Attrs attrs) const {
689     symbol.attrs() |= attrs;
690     symbol.implicitAttrs() &= ~attrs;
691   }
692   void SetImplicitAttr(Symbol &symbol, Attr attr) const {
693     symbol.attrs().set(attr);
694     symbol.implicitAttrs().set(attr);
695   }
696   void SetCUDADataAttr(
697       SourceName, Symbol &, std::optional<common::CUDADataAttr>);
698 
699 protected:
700   FuncResultStack &funcResultStack() { return funcResultStack_; }
701 
702   // Apply the implicit type rules to this symbol.
703   void ApplyImplicitRules(Symbol &, bool allowForwardReference = false);
704   bool ImplicitlyTypeForwardRef(Symbol &);
705   void AcquireIntrinsicProcedureFlags(Symbol &);
706   const DeclTypeSpec *GetImplicitType(
707       Symbol &, bool respectImplicitNoneType = true);
708   void CheckEntryDummyUse(SourceName, Symbol *);
709   bool ConvertToObjectEntity(Symbol &);
710   bool ConvertToProcEntity(Symbol &, std::optional<SourceName> = std::nullopt);
711 
712   const DeclTypeSpec &MakeNumericType(
713       TypeCategory, const std::optional<parser::KindSelector> &);
714   const DeclTypeSpec &MakeNumericType(TypeCategory, int);
715   const DeclTypeSpec &MakeLogicalType(
716       const std::optional<parser::KindSelector> &);
717   const DeclTypeSpec &MakeLogicalType(int);
718   void NotePossibleBadForwardRef(const parser::Name &);
719   std::optional<SourceName> HadForwardRef(const Symbol &) const;
720   bool CheckPossibleBadForwardRef(const Symbol &);
721 
722   bool inSpecificationPart_{false};
723   bool deferImplicitTyping_{false};
724   bool skipImplicitTyping_{false};
725   bool inEquivalenceStmt_{false};
726 
727   // Some information is collected from a specification part for deferred
728   // processing in DeclarationPartVisitor functions (e.g., CheckSaveStmts())
729   // that are called by ResolveNamesVisitor::FinishSpecificationPart().  Since
730   // specification parts can nest (e.g., INTERFACE bodies), the collected
731   // information that is not contained in the scope needs to be packaged
732   // and restorable.
733   struct SpecificationPartState {
734     std::set<SourceName> forwardRefs;
735     // Collect equivalence sets and process at end of specification part
736     std::vector<const std::list<parser::EquivalenceObject> *> equivalenceSets;
737     // Names of all common block objects in the scope
738     std::set<SourceName> commonBlockObjects;
739     // Info about SAVE statements and attributes in current scope
740     struct {
741       std::optional<SourceName> saveAll; // "SAVE" without entity list
742       std::set<SourceName> entities; // names of entities with save attr
743       std::set<SourceName> commons; // names of common blocks with save attr
744     } saveInfo;
745   } specPartState_;
746 
747   // Some declaration processing can and should be deferred to
748   // ResolveExecutionParts() to avoid prematurely creating implicitly-typed
749   // local symbols that should be host associations.
750   struct DeferredDeclarationState {
751     // The content of each namelist group
752     std::list<const parser::NamelistStmt::Group *> namelistGroups;
753   };
754   DeferredDeclarationState *GetDeferredDeclarationState(bool add = false) {
755     if (!add && deferred_.find(&currScope()) == deferred_.end()) {
756       return nullptr;
757     } else {
758       return &deferred_.emplace(&currScope(), DeferredDeclarationState{})
759                   .first->second;
760     }
761   }
762 
763   void SkipImplicitTyping(bool skip) {
764     deferImplicitTyping_ = skipImplicitTyping_ = skip;
765   }
766 
767 private:
768   Scope *currScope_{nullptr};
769   FuncResultStack funcResultStack_{*this};
770   std::map<Scope *, DeferredDeclarationState> deferred_;
771 };
772 
773 class ModuleVisitor : public virtual ScopeHandler {
774 public:
775   bool Pre(const parser::AccessStmt &);
776   bool Pre(const parser::Only &);
777   bool Pre(const parser::Rename::Names &);
778   bool Pre(const parser::Rename::Operators &);
779   bool Pre(const parser::UseStmt &);
780   void Post(const parser::UseStmt &);
781 
782   void BeginModule(const parser::Name &, bool isSubmodule);
783   bool BeginSubmodule(const parser::Name &, const parser::ParentIdentifier &);
784   void ApplyDefaultAccess();
785   Symbol &AddGenericUse(GenericDetails &, const SourceName &, const Symbol &);
786   void AddAndCheckModuleUse(SourceName, bool isIntrinsic);
787   void CollectUseRenames(const parser::UseStmt &);
788   void ClearUseRenames() { useRenames_.clear(); }
789   void ClearUseOnly() { useOnly_.clear(); }
790   void ClearModuleUses() {
791     intrinsicUses_.clear();
792     nonIntrinsicUses_.clear();
793   }
794 
795 private:
796   // The location of the last AccessStmt without access-ids, if any.
797   std::optional<SourceName> prevAccessStmt_;
798   // The scope of the module during a UseStmt
799   Scope *useModuleScope_{nullptr};
800   // Names that have appeared in a rename clause of USE statements
801   std::set<std::pair<SourceName, SourceName>> useRenames_;
802   // Names that have appeared in an ONLY clause of a USE statement
803   std::set<std::pair<SourceName, Scope *>> useOnly_;
804   // Intrinsic and non-intrinsic (explicit or not) module names that
805   // have appeared in USE statements; used for C1406 warnings.
806   std::set<SourceName> intrinsicUses_;
807   std::set<SourceName> nonIntrinsicUses_;
808 
809   Symbol &SetAccess(const SourceName &, Attr attr, Symbol * = nullptr);
810   // A rename in a USE statement: local => use
811   struct SymbolRename {
812     Symbol *local{nullptr};
813     Symbol *use{nullptr};
814   };
815   // Record a use from useModuleScope_ of use Name/Symbol as local Name/Symbol
816   SymbolRename AddUse(const SourceName &localName, const SourceName &useName);
817   SymbolRename AddUse(const SourceName &, const SourceName &, Symbol *);
818   void DoAddUse(
819       SourceName, SourceName, Symbol &localSymbol, const Symbol &useSymbol);
820   void AddUse(const GenericSpecInfo &);
821   // Record a name appearing as the target of a USE rename clause
822   void AddUseRename(SourceName name, SourceName moduleName) {
823     useRenames_.emplace(std::make_pair(name, moduleName));
824   }
825   bool IsUseRenamed(const SourceName &name) const {
826     return useModuleScope_ && useModuleScope_->symbol() &&
827         useRenames_.find({name, useModuleScope_->symbol()->name()}) !=
828         useRenames_.end();
829   }
830   // Record a name appearing in a USE ONLY clause
831   void AddUseOnly(const SourceName &name) {
832     useOnly_.emplace(std::make_pair(name, useModuleScope_));
833   }
834   bool IsUseOnly(const SourceName &name) const {
835     return useOnly_.find({name, useModuleScope_}) != useOnly_.end();
836   }
837   Scope *FindModule(const parser::Name &, std::optional<bool> isIntrinsic,
838       Scope *ancestor = nullptr);
839 };
840 
841 class GenericHandler : public virtual ScopeHandler {
842 protected:
843   using ProcedureKind = parser::ProcedureStmt::Kind;
844   void ResolveSpecificsInGeneric(Symbol &, bool isEndOfSpecificationPart);
845   void DeclaredPossibleSpecificProc(Symbol &);
846 
847   // Mappings of generics to their as-yet specific proc names and kinds
848   using SpecificProcMapType =
849       std::multimap<Symbol *, std::pair<const parser::Name *, ProcedureKind>>;
850   SpecificProcMapType specificsForGenericProcs_;
851   // inversion of SpecificProcMapType: maps pending proc names to generics
852   using GenericProcMapType = std::multimap<SourceName, Symbol *>;
853   GenericProcMapType genericsForSpecificProcs_;
854 };
855 
856 class InterfaceVisitor : public virtual ScopeHandler,
857                          public virtual GenericHandler {
858 public:
859   bool Pre(const parser::InterfaceStmt &);
860   void Post(const parser::InterfaceStmt &);
861   void Post(const parser::EndInterfaceStmt &);
862   bool Pre(const parser::GenericSpec &);
863   bool Pre(const parser::ProcedureStmt &);
864   bool Pre(const parser::GenericStmt &);
865   void Post(const parser::GenericStmt &);
866 
867   bool inInterfaceBlock() const;
868   bool isGeneric() const;
869   bool isAbstract() const;
870 
871 protected:
872   Symbol &GetGenericSymbol() { return DEREF(genericInfo_.top().symbol); }
873   // Add to generic the symbol for the subprogram with the same name
874   void CheckGenericProcedures(Symbol &);
875 
876 private:
877   // A new GenericInfo is pushed for each interface block and generic stmt
878   struct GenericInfo {
879     GenericInfo(bool isInterface, bool isAbstract = false)
880         : isInterface{isInterface}, isAbstract{isAbstract} {}
881     bool isInterface; // in interface block
882     bool isAbstract; // in abstract interface block
883     Symbol *symbol{nullptr}; // the generic symbol being defined
884   };
885   std::stack<GenericInfo> genericInfo_;
886   const GenericInfo &GetGenericInfo() const { return genericInfo_.top(); }
887   void SetGenericSymbol(Symbol &symbol) { genericInfo_.top().symbol = &symbol; }
888   void AddSpecificProcs(const std::list<parser::Name> &, ProcedureKind);
889   void ResolveNewSpecifics();
890 };
891 
892 class SubprogramVisitor : public virtual ScopeHandler, public InterfaceVisitor {
893 public:
894   bool HandleStmtFunction(const parser::StmtFunctionStmt &);
895   bool Pre(const parser::SubroutineStmt &);
896   bool Pre(const parser::FunctionStmt &);
897   void Post(const parser::FunctionStmt &);
898   bool Pre(const parser::EntryStmt &);
899   void Post(const parser::EntryStmt &);
900   bool Pre(const parser::InterfaceBody::Subroutine &);
901   void Post(const parser::InterfaceBody::Subroutine &);
902   bool Pre(const parser::InterfaceBody::Function &);
903   void Post(const parser::InterfaceBody::Function &);
904   bool Pre(const parser::Suffix &);
905   bool Pre(const parser::PrefixSpec &);
906   bool Pre(const parser::PrefixSpec::Attributes &);
907   void Post(const parser::PrefixSpec::Launch_Bounds &);
908   void Post(const parser::PrefixSpec::Cluster_Dims &);
909 
910   bool BeginSubprogram(const parser::Name &, Symbol::Flag,
911       bool hasModulePrefix = false,
912       const parser::LanguageBindingSpec * = nullptr,
913       const ProgramTree::EntryStmtList * = nullptr);
914   bool BeginMpSubprogram(const parser::Name &);
915   void PushBlockDataScope(const parser::Name &);
916   void EndSubprogram(std::optional<parser::CharBlock> stmtSource = std::nullopt,
917       const std::optional<parser::LanguageBindingSpec> * = nullptr,
918       const ProgramTree::EntryStmtList * = nullptr);
919 
920 protected:
921   // Set when we see a stmt function that is really an array element assignment
922   bool misparsedStmtFuncFound_{false};
923 
924 private:
925   // Edits an existing symbol created for earlier calls to a subprogram or ENTRY
926   // so that it can be replaced by a later definition.
927   bool HandlePreviousCalls(const parser::Name &, Symbol &, Symbol::Flag);
928   void CheckExtantProc(const parser::Name &, Symbol::Flag);
929   // Create a subprogram symbol in the current scope and push a new scope.
930   Symbol &PushSubprogramScope(const parser::Name &, Symbol::Flag,
931       const parser::LanguageBindingSpec * = nullptr,
932       bool hasModulePrefix = false);
933   Symbol *GetSpecificFromGeneric(const parser::Name &);
934   Symbol &PostSubprogramStmt();
935   void CreateDummyArgument(SubprogramDetails &, const parser::Name &);
936   void CreateEntry(const parser::EntryStmt &stmt, Symbol &subprogram);
937   void PostEntryStmt(const parser::EntryStmt &stmt);
938   void HandleLanguageBinding(Symbol *,
939       std::optional<parser::CharBlock> stmtSource,
940       const std::optional<parser::LanguageBindingSpec> *);
941 };
942 
943 class DeclarationVisitor : public ArraySpecVisitor,
944                            public virtual GenericHandler {
945 public:
946   using ArraySpecVisitor::Post;
947   using ScopeHandler::Post;
948   using ScopeHandler::Pre;
949 
950   bool Pre(const parser::Initialization &);
951   void Post(const parser::EntityDecl &);
952   void Post(const parser::ObjectDecl &);
953   void Post(const parser::PointerDecl &);
954   bool Pre(const parser::BindStmt &) { return BeginAttrs(); }
955   void Post(const parser::BindStmt &) { EndAttrs(); }
956   bool Pre(const parser::BindEntity &);
957   bool Pre(const parser::OldParameterStmt &);
958   bool Pre(const parser::NamedConstantDef &);
959   bool Pre(const parser::NamedConstant &);
960   void Post(const parser::EnumDef &);
961   bool Pre(const parser::Enumerator &);
962   bool Pre(const parser::AccessSpec &);
963   bool Pre(const parser::AsynchronousStmt &);
964   bool Pre(const parser::ContiguousStmt &);
965   bool Pre(const parser::ExternalStmt &);
966   bool Pre(const parser::IntentStmt &);
967   bool Pre(const parser::IntrinsicStmt &);
968   bool Pre(const parser::OptionalStmt &);
969   bool Pre(const parser::ProtectedStmt &);
970   bool Pre(const parser::ValueStmt &);
971   bool Pre(const parser::VolatileStmt &);
972   bool Pre(const parser::AllocatableStmt &) {
973     objectDeclAttr_ = Attr::ALLOCATABLE;
974     return true;
975   }
976   void Post(const parser::AllocatableStmt &) { objectDeclAttr_ = std::nullopt; }
977   bool Pre(const parser::TargetStmt &) {
978     objectDeclAttr_ = Attr::TARGET;
979     return true;
980   }
981   bool Pre(const parser::CUDAAttributesStmt &);
982   void Post(const parser::TargetStmt &) { objectDeclAttr_ = std::nullopt; }
983   void Post(const parser::DimensionStmt::Declaration &);
984   void Post(const parser::CodimensionDecl &);
985   bool Pre(const parser::TypeDeclarationStmt &);
986   void Post(const parser::TypeDeclarationStmt &);
987   void Post(const parser::IntegerTypeSpec &);
988   void Post(const parser::UnsignedTypeSpec &);
989   void Post(const parser::IntrinsicTypeSpec::Real &);
990   void Post(const parser::IntrinsicTypeSpec::Complex &);
991   void Post(const parser::IntrinsicTypeSpec::Logical &);
992   void Post(const parser::IntrinsicTypeSpec::Character &);
993   void Post(const parser::CharSelector::LengthAndKind &);
994   void Post(const parser::CharLength &);
995   void Post(const parser::LengthSelector &);
996   bool Pre(const parser::KindParam &);
997   bool Pre(const parser::VectorTypeSpec &);
998   void Post(const parser::VectorTypeSpec &);
999   bool Pre(const parser::DeclarationTypeSpec::Type &);
1000   void Post(const parser::DeclarationTypeSpec::Type &);
1001   bool Pre(const parser::DeclarationTypeSpec::Class &);
1002   void Post(const parser::DeclarationTypeSpec::Class &);
1003   void Post(const parser::DeclarationTypeSpec::Record &);
1004   void Post(const parser::DerivedTypeSpec &);
1005   bool Pre(const parser::DerivedTypeDef &);
1006   bool Pre(const parser::DerivedTypeStmt &);
1007   void Post(const parser::DerivedTypeStmt &);
1008   bool Pre(const parser::TypeParamDefStmt &) { return BeginDecl(); }
1009   void Post(const parser::TypeParamDefStmt &);
1010   bool Pre(const parser::TypeAttrSpec::Extends &);
1011   bool Pre(const parser::PrivateStmt &);
1012   bool Pre(const parser::SequenceStmt &);
1013   bool Pre(const parser::ComponentDefStmt &) { return BeginDecl(); }
1014   void Post(const parser::ComponentDefStmt &) { EndDecl(); }
1015   void Post(const parser::ComponentDecl &);
1016   void Post(const parser::FillDecl &);
1017   bool Pre(const parser::ProcedureDeclarationStmt &);
1018   void Post(const parser::ProcedureDeclarationStmt &);
1019   bool Pre(const parser::DataComponentDefStmt &); // returns false
1020   bool Pre(const parser::ProcComponentDefStmt &);
1021   void Post(const parser::ProcComponentDefStmt &);
1022   bool Pre(const parser::ProcPointerInit &);
1023   void Post(const parser::ProcInterface &);
1024   void Post(const parser::ProcDecl &);
1025   bool Pre(const parser::TypeBoundProcedurePart &);
1026   void Post(const parser::TypeBoundProcedurePart &);
1027   void Post(const parser::ContainsStmt &);
1028   bool Pre(const parser::TypeBoundProcBinding &) { return BeginAttrs(); }
1029   void Post(const parser::TypeBoundProcBinding &) { EndAttrs(); }
1030   void Post(const parser::TypeBoundProcedureStmt::WithoutInterface &);
1031   void Post(const parser::TypeBoundProcedureStmt::WithInterface &);
1032   bool Pre(const parser::FinalProcedureStmt &);
1033   bool Pre(const parser::TypeBoundGenericStmt &);
1034   bool Pre(const parser::StructureDef &); // returns false
1035   bool Pre(const parser::Union::UnionStmt &);
1036   bool Pre(const parser::StructureField &);
1037   void Post(const parser::StructureField &);
1038   bool Pre(const parser::AllocateStmt &);
1039   void Post(const parser::AllocateStmt &);
1040   bool Pre(const parser::StructureConstructor &);
1041   bool Pre(const parser::NamelistStmt::Group &);
1042   bool Pre(const parser::IoControlSpec &);
1043   bool Pre(const parser::CommonStmt::Block &);
1044   bool Pre(const parser::CommonBlockObject &);
1045   void Post(const parser::CommonBlockObject &);
1046   bool Pre(const parser::EquivalenceStmt &);
1047   bool Pre(const parser::SaveStmt &);
1048   bool Pre(const parser::BasedPointer &);
1049   void Post(const parser::BasedPointer &);
1050 
1051   void PointerInitialization(
1052       const parser::Name &, const parser::InitialDataTarget &);
1053   void PointerInitialization(
1054       const parser::Name &, const parser::ProcPointerInit &);
1055   void NonPointerInitialization(
1056       const parser::Name &, const parser::ConstantExpr &);
1057   void CheckExplicitInterface(const parser::Name &);
1058   void CheckBindings(const parser::TypeBoundProcedureStmt::WithoutInterface &);
1059 
1060   const parser::Name *ResolveDesignator(const parser::Designator &);
1061   int GetVectorElementKind(
1062       TypeCategory category, const std::optional<parser::KindSelector> &kind);
1063 
1064 protected:
1065   bool BeginDecl();
1066   void EndDecl();
1067   Symbol &DeclareObjectEntity(const parser::Name &, Attrs = Attrs{});
1068   // Make sure that there's an entity in an enclosing scope called Name
1069   Symbol &FindOrDeclareEnclosingEntity(const parser::Name &);
1070   // Declare a LOCAL/LOCAL_INIT/REDUCE entity while setting a locality flag. If
1071   // there isn't a type specified it comes from the entity in the containing
1072   // scope, or implicit rules.
1073   void DeclareLocalEntity(const parser::Name &, Symbol::Flag);
1074   // Declare a statement entity (i.e., an implied DO loop index for
1075   // a DATA statement or an array constructor).  If there isn't an explict
1076   // type specified, implicit rules apply. Return pointer to the new symbol,
1077   // or nullptr on error.
1078   Symbol *DeclareStatementEntity(const parser::DoVariable &,
1079       const std::optional<parser::IntegerTypeSpec> &);
1080   Symbol &MakeCommonBlockSymbol(const parser::Name &);
1081   Symbol &MakeCommonBlockSymbol(const std::optional<parser::Name> &);
1082   bool CheckUseError(const parser::Name &);
1083   void CheckAccessibility(const SourceName &, bool, Symbol &);
1084   void CheckCommonBlocks();
1085   void CheckSaveStmts();
1086   void CheckEquivalenceSets();
1087   bool CheckNotInBlock(const char *);
1088   bool NameIsKnownOrIntrinsic(const parser::Name &);
1089   void FinishNamelists();
1090 
1091   // Each of these returns a pointer to a resolved Name (i.e. with symbol)
1092   // or nullptr in case of error.
1093   const parser::Name *ResolveStructureComponent(
1094       const parser::StructureComponent &);
1095   const parser::Name *ResolveDataRef(const parser::DataRef &);
1096   const parser::Name *ResolveName(const parser::Name &);
1097   bool PassesSharedLocalityChecks(const parser::Name &name, Symbol &symbol);
1098   Symbol *NoteInterfaceName(const parser::Name &);
1099   bool IsUplevelReference(const Symbol &);
1100 
1101   std::optional<SourceName> BeginCheckOnIndexUseInOwnBounds(
1102       const parser::DoVariable &name) {
1103     std::optional<SourceName> result{checkIndexUseInOwnBounds_};
1104     checkIndexUseInOwnBounds_ = name.thing.thing.source;
1105     return result;
1106   }
1107   void EndCheckOnIndexUseInOwnBounds(const std::optional<SourceName> &restore) {
1108     checkIndexUseInOwnBounds_ = restore;
1109   }
1110   void NoteScalarSpecificationArgument(const Symbol &symbol) {
1111     mustBeScalar_.emplace(symbol);
1112   }
1113   // Declare an object or procedure entity.
1114   // T is one of: EntityDetails, ObjectEntityDetails, ProcEntityDetails
1115   template <typename T>
1116   Symbol &DeclareEntity(const parser::Name &name, Attrs attrs) {
1117     Symbol &symbol{MakeSymbol(name, attrs)};
1118     if (context().HasError(symbol) || symbol.has<T>()) {
1119       return symbol; // OK or error already reported
1120     } else if (symbol.has<UnknownDetails>()) {
1121       symbol.set_details(T{});
1122       return symbol;
1123     } else if (auto *details{symbol.detailsIf<EntityDetails>()}) {
1124       symbol.set_details(T{std::move(*details)});
1125       return symbol;
1126     } else if (std::is_same_v<EntityDetails, T> &&
1127         (symbol.has<ObjectEntityDetails>() ||
1128             symbol.has<ProcEntityDetails>())) {
1129       return symbol; // OK
1130     } else if (auto *details{symbol.detailsIf<UseDetails>()}) {
1131       Say(name.source,
1132           "'%s' is use-associated from module '%s' and cannot be re-declared"_err_en_US,
1133           name.source, GetUsedModule(*details).name());
1134     } else if (auto *details{symbol.detailsIf<SubprogramNameDetails>()}) {
1135       if (details->kind() == SubprogramKind::Module) {
1136         Say2(name,
1137             "Declaration of '%s' conflicts with its use as module procedure"_err_en_US,
1138             symbol, "Module procedure definition"_en_US);
1139       } else if (details->kind() == SubprogramKind::Internal) {
1140         Say2(name,
1141             "Declaration of '%s' conflicts with its use as internal procedure"_err_en_US,
1142             symbol, "Internal procedure definition"_en_US);
1143       } else {
1144         DIE("unexpected kind");
1145       }
1146     } else if (std::is_same_v<ObjectEntityDetails, T> &&
1147         symbol.has<ProcEntityDetails>()) {
1148       SayWithDecl(
1149           name, symbol, "'%s' is already declared as a procedure"_err_en_US);
1150     } else if (std::is_same_v<ProcEntityDetails, T> &&
1151         symbol.has<ObjectEntityDetails>()) {
1152       if (FindCommonBlockContaining(symbol)) {
1153         SayWithDecl(name, symbol,
1154             "'%s' may not be a procedure as it is in a COMMON block"_err_en_US);
1155       } else {
1156         SayWithDecl(
1157             name, symbol, "'%s' is already declared as an object"_err_en_US);
1158       }
1159     } else if (!CheckPossibleBadForwardRef(symbol)) {
1160       SayAlreadyDeclared(name, symbol);
1161     }
1162     context().SetError(symbol);
1163     return symbol;
1164   }
1165 
1166 private:
1167   // The attribute corresponding to the statement containing an ObjectDecl
1168   std::optional<Attr> objectDeclAttr_;
1169   // Info about current character type while walking DeclTypeSpec.
1170   // Also captures any "*length" specifier on an individual declaration.
1171   struct {
1172     std::optional<ParamValue> length;
1173     std::optional<KindExpr> kind;
1174   } charInfo_;
1175   // Info about current derived type or STRUCTURE while walking
1176   // DerivedTypeDef / StructureDef
1177   struct {
1178     const parser::Name *extends{nullptr}; // EXTENDS(name)
1179     bool privateComps{false}; // components are private by default
1180     bool privateBindings{false}; // bindings are private by default
1181     bool sawContains{false}; // currently processing bindings
1182     bool sequence{false}; // is a sequence type
1183     const Symbol *type{nullptr}; // derived type being defined
1184     bool isStructure{false}; // is a DEC STRUCTURE
1185   } derivedTypeInfo_;
1186   // In a ProcedureDeclarationStmt or ProcComponentDefStmt, this is
1187   // the interface name, if any.
1188   const parser::Name *interfaceName_{nullptr};
1189   // Map type-bound generic to binding names of its specific bindings
1190   std::multimap<Symbol *, const parser::Name *> genericBindings_;
1191   // Info about current ENUM
1192   struct EnumeratorState {
1193     // Enum value must hold inside a C_INT (7.6.2).
1194     std::optional<int> value{0};
1195   } enumerationState_;
1196   // Set for OldParameterStmt processing
1197   bool inOldStyleParameterStmt_{false};
1198   // Set when walking DATA & array constructor implied DO loop bounds
1199   // to warn about use of the implied DO intex therein.
1200   std::optional<SourceName> checkIndexUseInOwnBounds_;
1201   bool isVectorType_{false};
1202   UnorderedSymbolSet mustBeScalar_;
1203 
1204   bool HandleAttributeStmt(Attr, const std::list<parser::Name> &);
1205   Symbol &HandleAttributeStmt(Attr, const parser::Name &);
1206   Symbol &DeclareUnknownEntity(const parser::Name &, Attrs);
1207   Symbol &DeclareProcEntity(
1208       const parser::Name &, Attrs, const Symbol *interface);
1209   void SetType(const parser::Name &, const DeclTypeSpec &);
1210   std::optional<DerivedTypeSpec> ResolveDerivedType(const parser::Name &);
1211   std::optional<DerivedTypeSpec> ResolveExtendsType(
1212       const parser::Name &, const parser::Name *);
1213   Symbol *MakeTypeSymbol(const SourceName &, Details &&);
1214   Symbol *MakeTypeSymbol(const parser::Name &, Details &&);
1215   bool OkToAddComponent(const parser::Name &, const Symbol *extends = nullptr);
1216   ParamValue GetParamValue(
1217       const parser::TypeParamValue &, common::TypeParamAttr attr);
1218   void CheckCommonBlockDerivedType(
1219       const SourceName &, const Symbol &, UnorderedSymbolSet &);
1220   Attrs HandleSaveName(const SourceName &, Attrs);
1221   void AddSaveName(std::set<SourceName> &, const SourceName &);
1222   bool HandleUnrestrictedSpecificIntrinsicFunction(const parser::Name &);
1223   const parser::Name *FindComponent(const parser::Name *, const parser::Name &);
1224   void Initialization(const parser::Name &, const parser::Initialization &,
1225       bool inComponentDecl);
1226   bool PassesLocalityChecks(
1227       const parser::Name &name, Symbol &symbol, Symbol::Flag flag);
1228   bool CheckForHostAssociatedImplicit(const parser::Name &);
1229   bool HasCycle(const Symbol &, const Symbol *interface);
1230   bool MustBeScalar(const Symbol &symbol) const {
1231     return mustBeScalar_.find(symbol) != mustBeScalar_.end();
1232   }
1233   void DeclareIntrinsic(const parser::Name &);
1234 };
1235 
1236 // Resolve construct entities and statement entities.
1237 // Check that construct names don't conflict with other names.
1238 class ConstructVisitor : public virtual DeclarationVisitor {
1239 public:
1240   bool Pre(const parser::ConcurrentHeader &);
1241   bool Pre(const parser::LocalitySpec::Local &);
1242   bool Pre(const parser::LocalitySpec::LocalInit &);
1243   bool Pre(const parser::LocalitySpec::Reduce &);
1244   bool Pre(const parser::LocalitySpec::Shared &);
1245   bool Pre(const parser::AcSpec &);
1246   bool Pre(const parser::AcImpliedDo &);
1247   bool Pre(const parser::DataImpliedDo &);
1248   bool Pre(const parser::DataIDoObject &);
1249   bool Pre(const parser::DataStmtObject &);
1250   bool Pre(const parser::DataStmtValue &);
1251   bool Pre(const parser::DoConstruct &);
1252   void Post(const parser::DoConstruct &);
1253   bool Pre(const parser::ForallConstruct &);
1254   void Post(const parser::ForallConstruct &);
1255   bool Pre(const parser::ForallStmt &);
1256   void Post(const parser::ForallStmt &);
1257   bool Pre(const parser::BlockConstruct &);
1258   void Post(const parser::Selector &);
1259   void Post(const parser::AssociateStmt &);
1260   void Post(const parser::EndAssociateStmt &);
1261   bool Pre(const parser::Association &);
1262   void Post(const parser::SelectTypeStmt &);
1263   void Post(const parser::SelectRankStmt &);
1264   bool Pre(const parser::SelectTypeConstruct &);
1265   void Post(const parser::SelectTypeConstruct &);
1266   bool Pre(const parser::SelectTypeConstruct::TypeCase &);
1267   void Post(const parser::SelectTypeConstruct::TypeCase &);
1268   // Creates Block scopes with neither symbol name nor symbol details.
1269   bool Pre(const parser::SelectRankConstruct::RankCase &);
1270   void Post(const parser::SelectRankConstruct::RankCase &);
1271   bool Pre(const parser::TypeGuardStmt::Guard &);
1272   void Post(const parser::TypeGuardStmt::Guard &);
1273   void Post(const parser::SelectRankCaseStmt::Rank &);
1274   bool Pre(const parser::ChangeTeamStmt &);
1275   void Post(const parser::EndChangeTeamStmt &);
1276   void Post(const parser::CoarrayAssociation &);
1277 
1278   // Definitions of construct names
1279   bool Pre(const parser::WhereConstructStmt &x) { return CheckDef(x.t); }
1280   bool Pre(const parser::ForallConstructStmt &x) { return CheckDef(x.t); }
1281   bool Pre(const parser::CriticalStmt &x) { return CheckDef(x.t); }
1282   bool Pre(const parser::LabelDoStmt &) {
1283     return false; // error recovery
1284   }
1285   bool Pre(const parser::NonLabelDoStmt &x) { return CheckDef(x.t); }
1286   bool Pre(const parser::IfThenStmt &x) { return CheckDef(x.t); }
1287   bool Pre(const parser::SelectCaseStmt &x) { return CheckDef(x.t); }
1288   bool Pre(const parser::SelectRankConstruct &);
1289   void Post(const parser::SelectRankConstruct &);
1290   bool Pre(const parser::SelectRankStmt &x) {
1291     return CheckDef(std::get<0>(x.t));
1292   }
1293   bool Pre(const parser::SelectTypeStmt &x) {
1294     return CheckDef(std::get<0>(x.t));
1295   }
1296 
1297   // References to construct names
1298   void Post(const parser::MaskedElsewhereStmt &x) { CheckRef(x.t); }
1299   void Post(const parser::ElsewhereStmt &x) { CheckRef(x.v); }
1300   void Post(const parser::EndWhereStmt &x) { CheckRef(x.v); }
1301   void Post(const parser::EndForallStmt &x) { CheckRef(x.v); }
1302   void Post(const parser::EndCriticalStmt &x) { CheckRef(x.v); }
1303   void Post(const parser::EndDoStmt &x) { CheckRef(x.v); }
1304   void Post(const parser::ElseIfStmt &x) { CheckRef(x.t); }
1305   void Post(const parser::ElseStmt &x) { CheckRef(x.v); }
1306   void Post(const parser::EndIfStmt &x) { CheckRef(x.v); }
1307   void Post(const parser::CaseStmt &x) { CheckRef(x.t); }
1308   void Post(const parser::EndSelectStmt &x) { CheckRef(x.v); }
1309   void Post(const parser::SelectRankCaseStmt &x) { CheckRef(x.t); }
1310   void Post(const parser::TypeGuardStmt &x) { CheckRef(x.t); }
1311   void Post(const parser::CycleStmt &x) { CheckRef(x.v); }
1312   void Post(const parser::ExitStmt &x) { CheckRef(x.v); }
1313 
1314   void HandleImpliedAsynchronousInScope(const parser::Block &);
1315 
1316 private:
1317   // R1105 selector -> expr | variable
1318   // expr is set in either case unless there were errors
1319   struct Selector {
1320     Selector() {}
1321     Selector(const SourceName &source, MaybeExpr &&expr)
1322         : source{source}, expr{std::move(expr)} {}
1323     operator bool() const { return expr.has_value(); }
1324     parser::CharBlock source;
1325     MaybeExpr expr;
1326   };
1327   // association -> [associate-name =>] selector
1328   struct Association {
1329     const parser::Name *name{nullptr};
1330     Selector selector;
1331   };
1332   std::vector<Association> associationStack_;
1333   Association *currentAssociation_{nullptr};
1334 
1335   template <typename T> bool CheckDef(const T &t) {
1336     return CheckDef(std::get<std::optional<parser::Name>>(t));
1337   }
1338   template <typename T> void CheckRef(const T &t) {
1339     CheckRef(std::get<std::optional<parser::Name>>(t));
1340   }
1341   bool CheckDef(const std::optional<parser::Name> &);
1342   void CheckRef(const std::optional<parser::Name> &);
1343   const DeclTypeSpec &ToDeclTypeSpec(evaluate::DynamicType &&);
1344   const DeclTypeSpec &ToDeclTypeSpec(
1345       evaluate::DynamicType &&, MaybeSubscriptIntExpr &&length);
1346   Symbol *MakeAssocEntity();
1347   void SetTypeFromAssociation(Symbol &);
1348   void SetAttrsFromAssociation(Symbol &);
1349   Selector ResolveSelector(const parser::Selector &);
1350   void ResolveIndexName(const parser::ConcurrentControl &control);
1351   void SetCurrentAssociation(std::size_t n);
1352   Association &GetCurrentAssociation();
1353   void PushAssociation();
1354   void PopAssociation(std::size_t count = 1);
1355 };
1356 
1357 // Create scopes for OpenACC constructs
1358 class AccVisitor : public virtual DeclarationVisitor {
1359 public:
1360   void AddAccSourceRange(const parser::CharBlock &);
1361 
1362   static bool NeedsScope(const parser::OpenACCBlockConstruct &);
1363 
1364   bool Pre(const parser::OpenACCBlockConstruct &);
1365   void Post(const parser::OpenACCBlockConstruct &);
1366   bool Pre(const parser::OpenACCCombinedConstruct &);
1367   void Post(const parser::OpenACCCombinedConstruct &);
1368   bool Pre(const parser::AccBeginBlockDirective &x) {
1369     AddAccSourceRange(x.source);
1370     return true;
1371   }
1372   void Post(const parser::AccBeginBlockDirective &) {
1373     messageHandler().set_currStmtSource(std::nullopt);
1374   }
1375   bool Pre(const parser::AccEndBlockDirective &x) {
1376     AddAccSourceRange(x.source);
1377     return true;
1378   }
1379   void Post(const parser::AccEndBlockDirective &) {
1380     messageHandler().set_currStmtSource(std::nullopt);
1381   }
1382   bool Pre(const parser::AccBeginLoopDirective &x) {
1383     AddAccSourceRange(x.source);
1384     return true;
1385   }
1386   void Post(const parser::AccBeginLoopDirective &x) {
1387     messageHandler().set_currStmtSource(std::nullopt);
1388   }
1389 };
1390 
1391 bool AccVisitor::NeedsScope(const parser::OpenACCBlockConstruct &x) {
1392   const auto &beginBlockDir{std::get<parser::AccBeginBlockDirective>(x.t)};
1393   const auto &beginDir{std::get<parser::AccBlockDirective>(beginBlockDir.t)};
1394   switch (beginDir.v) {
1395   case llvm::acc::Directive::ACCD_data:
1396   case llvm::acc::Directive::ACCD_host_data:
1397   case llvm::acc::Directive::ACCD_kernels:
1398   case llvm::acc::Directive::ACCD_parallel:
1399   case llvm::acc::Directive::ACCD_serial:
1400     return true;
1401   default:
1402     return false;
1403   }
1404 }
1405 
1406 void AccVisitor::AddAccSourceRange(const parser::CharBlock &source) {
1407   messageHandler().set_currStmtSource(source);
1408   currScope().AddSourceRange(source);
1409 }
1410 
1411 bool AccVisitor::Pre(const parser::OpenACCBlockConstruct &x) {
1412   if (NeedsScope(x)) {
1413     PushScope(Scope::Kind::OpenACCConstruct, nullptr);
1414   }
1415   return true;
1416 }
1417 
1418 void AccVisitor::Post(const parser::OpenACCBlockConstruct &x) {
1419   if (NeedsScope(x)) {
1420     PopScope();
1421   }
1422 }
1423 
1424 bool AccVisitor::Pre(const parser::OpenACCCombinedConstruct &x) {
1425   PushScope(Scope::Kind::OpenACCConstruct, nullptr);
1426   return true;
1427 }
1428 
1429 void AccVisitor::Post(const parser::OpenACCCombinedConstruct &x) { PopScope(); }
1430 
1431 // Create scopes for OpenMP constructs
1432 class OmpVisitor : public virtual DeclarationVisitor {
1433 public:
1434   void AddOmpSourceRange(const parser::CharBlock &);
1435 
1436   static bool NeedsScope(const parser::OpenMPBlockConstruct &);
1437   static bool NeedsScope(const parser::OmpClause &);
1438 
1439   bool Pre(const parser::OpenMPRequiresConstruct &x) {
1440     AddOmpSourceRange(x.source);
1441     return true;
1442   }
1443   bool Pre(const parser::OmpSimpleStandaloneDirective &x) {
1444     AddOmpSourceRange(x.source);
1445     return true;
1446   }
1447   bool Pre(const parser::OpenMPBlockConstruct &);
1448   void Post(const parser::OpenMPBlockConstruct &);
1449   bool Pre(const parser::OmpBeginBlockDirective &x) {
1450     AddOmpSourceRange(x.source);
1451     return true;
1452   }
1453   void Post(const parser::OmpBeginBlockDirective &) {
1454     messageHandler().set_currStmtSource(std::nullopt);
1455   }
1456   bool Pre(const parser::OmpEndBlockDirective &x) {
1457     AddOmpSourceRange(x.source);
1458     return true;
1459   }
1460   void Post(const parser::OmpEndBlockDirective &) {
1461     messageHandler().set_currStmtSource(std::nullopt);
1462   }
1463 
1464   bool Pre(const parser::OpenMPLoopConstruct &) {
1465     PushScope(Scope::Kind::OtherConstruct, nullptr);
1466     return true;
1467   }
1468   void Post(const parser::OpenMPLoopConstruct &) { PopScope(); }
1469   bool Pre(const parser::OmpBeginLoopDirective &x) {
1470     AddOmpSourceRange(x.source);
1471     return true;
1472   }
1473 
1474   bool Pre(const parser::OpenMPDeclareMapperConstruct &);
1475 
1476   bool Pre(const parser::OmpMapClause &);
1477 
1478   void Post(const parser::OmpBeginLoopDirective &) {
1479     messageHandler().set_currStmtSource(std::nullopt);
1480   }
1481   bool Pre(const parser::OmpEndLoopDirective &x) {
1482     AddOmpSourceRange(x.source);
1483     return true;
1484   }
1485   void Post(const parser::OmpEndLoopDirective &) {
1486     messageHandler().set_currStmtSource(std::nullopt);
1487   }
1488 
1489   bool Pre(const parser::OpenMPSectionsConstruct &) {
1490     PushScope(Scope::Kind::OtherConstruct, nullptr);
1491     return true;
1492   }
1493   void Post(const parser::OpenMPSectionsConstruct &) { PopScope(); }
1494   bool Pre(const parser::OmpBeginSectionsDirective &x) {
1495     AddOmpSourceRange(x.source);
1496     return true;
1497   }
1498   void Post(const parser::OmpBeginSectionsDirective &) {
1499     messageHandler().set_currStmtSource(std::nullopt);
1500   }
1501   bool Pre(const parser::OmpEndSectionsDirective &x) {
1502     AddOmpSourceRange(x.source);
1503     return true;
1504   }
1505   void Post(const parser::OmpEndSectionsDirective &) {
1506     messageHandler().set_currStmtSource(std::nullopt);
1507   }
1508   bool Pre(const parser::OmpCriticalDirective &x) {
1509     AddOmpSourceRange(x.source);
1510     return true;
1511   }
1512   void Post(const parser::OmpCriticalDirective &) {
1513     messageHandler().set_currStmtSource(std::nullopt);
1514   }
1515   bool Pre(const parser::OmpEndCriticalDirective &x) {
1516     AddOmpSourceRange(x.source);
1517     return true;
1518   }
1519   void Post(const parser::OmpEndCriticalDirective &) {
1520     messageHandler().set_currStmtSource(std::nullopt);
1521   }
1522   bool Pre(const parser::OpenMPThreadprivate &) {
1523     SkipImplicitTyping(true);
1524     return true;
1525   }
1526   void Post(const parser::OpenMPThreadprivate &) { SkipImplicitTyping(false); }
1527   bool Pre(const parser::OpenMPDeclareTargetConstruct &) {
1528     SkipImplicitTyping(true);
1529     return true;
1530   }
1531   void Post(const parser::OpenMPDeclareTargetConstruct &) {
1532     SkipImplicitTyping(false);
1533   }
1534   bool Pre(const parser::OpenMPDeclarativeAllocate &) {
1535     SkipImplicitTyping(true);
1536     return true;
1537   }
1538   void Post(const parser::OpenMPDeclarativeAllocate &) {
1539     SkipImplicitTyping(false);
1540   }
1541   bool Pre(const parser::OpenMPDeclarativeConstruct &x) {
1542     AddOmpSourceRange(x.source);
1543     return true;
1544   }
1545   void Post(const parser::OpenMPDeclarativeConstruct &) {
1546     messageHandler().set_currStmtSource(std::nullopt);
1547   }
1548   bool Pre(const parser::OpenMPDepobjConstruct &x) {
1549     AddOmpSourceRange(x.source);
1550     return true;
1551   }
1552   void Post(const parser::OpenMPDepobjConstruct &x) {
1553     messageHandler().set_currStmtSource(std::nullopt);
1554   }
1555   bool Pre(const parser::OpenMPAtomicConstruct &x) {
1556     return common::visit(common::visitors{[&](const auto &u) -> bool {
1557       AddOmpSourceRange(u.source);
1558       return true;
1559     }},
1560         x.u);
1561   }
1562   void Post(const parser::OpenMPAtomicConstruct &) {
1563     messageHandler().set_currStmtSource(std::nullopt);
1564   }
1565   bool Pre(const parser::OmpClause &x) {
1566     if (NeedsScope(x)) {
1567       PushScope(Scope::Kind::OtherClause, nullptr);
1568     }
1569     return true;
1570   }
1571   void Post(const parser::OmpClause &x) {
1572     if (NeedsScope(x)) {
1573       PopScope();
1574     }
1575   }
1576 };
1577 
1578 bool OmpVisitor::NeedsScope(const parser::OpenMPBlockConstruct &x) {
1579   const auto &beginBlockDir{std::get<parser::OmpBeginBlockDirective>(x.t)};
1580   const auto &beginDir{std::get<parser::OmpBlockDirective>(beginBlockDir.t)};
1581   switch (beginDir.v) {
1582   case llvm::omp::Directive::OMPD_master:
1583   case llvm::omp::Directive::OMPD_ordered:
1584   case llvm::omp::Directive::OMPD_taskgroup:
1585     return false;
1586   default:
1587     return true;
1588   }
1589 }
1590 
1591 bool OmpVisitor::NeedsScope(const parser::OmpClause &x) {
1592   // Iterators contain declarations, whose scope extends until the end
1593   // the clause.
1594   return llvm::omp::canHaveIterator(x.Id());
1595 }
1596 
1597 void OmpVisitor::AddOmpSourceRange(const parser::CharBlock &source) {
1598   messageHandler().set_currStmtSource(source);
1599   currScope().AddSourceRange(source);
1600 }
1601 
1602 bool OmpVisitor::Pre(const parser::OpenMPBlockConstruct &x) {
1603   if (NeedsScope(x)) {
1604     PushScope(Scope::Kind::OtherConstruct, nullptr);
1605   }
1606   return true;
1607 }
1608 
1609 void OmpVisitor::Post(const parser::OpenMPBlockConstruct &x) {
1610   if (NeedsScope(x)) {
1611     PopScope();
1612   }
1613 }
1614 
1615 // This "manually" walks the tree of the construct, because we need
1616 // to resolve the type before the map clauses are processed - when
1617 // just following the natural flow, the map clauses gets processed before
1618 // the type has been fully processed.
1619 bool OmpVisitor::Pre(const parser::OpenMPDeclareMapperConstruct &x) {
1620   AddOmpSourceRange(x.source);
1621   BeginDeclTypeSpec();
1622   const auto &spec{std::get<parser::OmpDeclareMapperSpecifier>(x.t)};
1623   Symbol *mapperSym{nullptr};
1624   if (const auto &mapperName{std::get<std::optional<parser::Name>>(spec.t)}) {
1625     mapperSym =
1626         &MakeSymbol(*mapperName, MiscDetails{MiscDetails::Kind::ConstructName});
1627     mapperName->symbol = mapperSym;
1628   } else {
1629     const parser::CharBlock defaultName{"default", 7};
1630     mapperSym = &MakeSymbol(
1631         defaultName, Attrs{}, MiscDetails{MiscDetails::Kind::ConstructName});
1632   }
1633 
1634   PushScope(Scope::Kind::OtherConstruct, nullptr);
1635   Walk(std::get<parser::TypeSpec>(spec.t));
1636   const auto &varName{std::get<parser::ObjectName>(spec.t)};
1637   DeclareObjectEntity(varName);
1638 
1639   Walk(std::get<parser::OmpClauseList>(x.t));
1640 
1641   EndDeclTypeSpec();
1642   PopScope();
1643   return false;
1644 }
1645 
1646 bool OmpVisitor::Pre(const parser::OmpMapClause &x) {
1647   auto &mods{OmpGetModifiers(x)};
1648   if (auto *mapper{OmpGetUniqueModifier<parser::OmpMapper>(mods)}) {
1649     if (auto *symbol{FindSymbol(currScope(), mapper->v)}) {
1650       // TODO: Do we need a specific flag or type here, to distinghuish against
1651       // other ConstructName things? Leaving this for the full implementation
1652       // of mapper lowering.
1653       auto *misc{symbol->detailsIf<MiscDetails>()};
1654       if (!misc || misc->kind() != MiscDetails::Kind::ConstructName)
1655         context().Say(mapper->v.source,
1656             "Name '%s' should be a mapper name"_err_en_US, mapper->v.source);
1657       else
1658         mapper->v.symbol = symbol;
1659     } else {
1660       mapper->v.symbol =
1661           &MakeSymbol(mapper->v, MiscDetails{MiscDetails::Kind::ConstructName});
1662       // TODO: When completing the implementation, we probably want to error if
1663       // the symbol is not declared, but right now, testing that the TODO for
1664       // OmpMapClause happens is obscured by the TODO for declare mapper, so
1665       // leaving this out. Remove the above line once the declare mapper is
1666       // implemented. context().Say(mapper->v.source, "'%s' not
1667       // declared"_err_en_US, mapper->v.source);
1668     }
1669   }
1670   return true;
1671 }
1672 
1673 // Walk the parse tree and resolve names to symbols.
1674 class ResolveNamesVisitor : public virtual ScopeHandler,
1675                             public ModuleVisitor,
1676                             public SubprogramVisitor,
1677                             public ConstructVisitor,
1678                             public OmpVisitor,
1679                             public AccVisitor {
1680 public:
1681   using AccVisitor::Post;
1682   using AccVisitor::Pre;
1683   using ArraySpecVisitor::Post;
1684   using ConstructVisitor::Post;
1685   using ConstructVisitor::Pre;
1686   using DeclarationVisitor::Post;
1687   using DeclarationVisitor::Pre;
1688   using ImplicitRulesVisitor::Post;
1689   using ImplicitRulesVisitor::Pre;
1690   using InterfaceVisitor::Post;
1691   using InterfaceVisitor::Pre;
1692   using ModuleVisitor::Post;
1693   using ModuleVisitor::Pre;
1694   using OmpVisitor::Post;
1695   using OmpVisitor::Pre;
1696   using ScopeHandler::Post;
1697   using ScopeHandler::Pre;
1698   using SubprogramVisitor::Post;
1699   using SubprogramVisitor::Pre;
1700 
1701   ResolveNamesVisitor(
1702       SemanticsContext &context, ImplicitRulesMap &rules, Scope &top)
1703       : BaseVisitor{context, *this, rules}, topScope_{top} {
1704     PushScope(top);
1705   }
1706 
1707   Scope &topScope() const { return topScope_; }
1708 
1709   // Default action for a parse tree node is to visit children.
1710   template <typename T> bool Pre(const T &) { return true; }
1711   template <typename T> void Post(const T &) {}
1712 
1713   bool Pre(const parser::SpecificationPart &);
1714   bool Pre(const parser::Program &);
1715   void Post(const parser::Program &);
1716   bool Pre(const parser::ImplicitStmt &);
1717   void Post(const parser::PointerObject &);
1718   void Post(const parser::AllocateObject &);
1719   bool Pre(const parser::PointerAssignmentStmt &);
1720   void Post(const parser::Designator &);
1721   void Post(const parser::SubstringInquiry &);
1722   template <typename A, typename B>
1723   void Post(const parser::LoopBounds<A, B> &x) {
1724     ResolveName(*parser::Unwrap<parser::Name>(x.name));
1725   }
1726   void Post(const parser::ProcComponentRef &);
1727   bool Pre(const parser::FunctionReference &);
1728   bool Pre(const parser::CallStmt &);
1729   bool Pre(const parser::ImportStmt &);
1730   void Post(const parser::TypeGuardStmt &);
1731   bool Pre(const parser::StmtFunctionStmt &);
1732   bool Pre(const parser::DefinedOpName &);
1733   bool Pre(const parser::ProgramUnit &);
1734   void Post(const parser::AssignStmt &);
1735   void Post(const parser::AssignedGotoStmt &);
1736   void Post(const parser::CompilerDirective &);
1737 
1738   // These nodes should never be reached: they are handled in ProgramUnit
1739   bool Pre(const parser::MainProgram &) {
1740     llvm_unreachable("This node is handled in ProgramUnit");
1741   }
1742   bool Pre(const parser::FunctionSubprogram &) {
1743     llvm_unreachable("This node is handled in ProgramUnit");
1744   }
1745   bool Pre(const parser::SubroutineSubprogram &) {
1746     llvm_unreachable("This node is handled in ProgramUnit");
1747   }
1748   bool Pre(const parser::SeparateModuleSubprogram &) {
1749     llvm_unreachable("This node is handled in ProgramUnit");
1750   }
1751   bool Pre(const parser::Module &) {
1752     llvm_unreachable("This node is handled in ProgramUnit");
1753   }
1754   bool Pre(const parser::Submodule &) {
1755     llvm_unreachable("This node is handled in ProgramUnit");
1756   }
1757   bool Pre(const parser::BlockData &) {
1758     llvm_unreachable("This node is handled in ProgramUnit");
1759   }
1760 
1761   void NoteExecutablePartCall(Symbol::Flag, SourceName, bool hasCUDAChevrons);
1762 
1763   friend void ResolveSpecificationParts(SemanticsContext &, const Symbol &);
1764 
1765 private:
1766   // Kind of procedure we are expecting to see in a ProcedureDesignator
1767   std::optional<Symbol::Flag> expectedProcFlag_;
1768   std::optional<SourceName> prevImportStmt_;
1769   Scope &topScope_;
1770 
1771   void PreSpecificationConstruct(const parser::SpecificationConstruct &);
1772   void CreateCommonBlockSymbols(const parser::CommonStmt &);
1773   void CreateObjectSymbols(const std::list<parser::ObjectDecl> &, Attr);
1774   void CreateGeneric(const parser::GenericSpec &);
1775   void FinishSpecificationPart(const std::list<parser::DeclarationConstruct> &);
1776   void AnalyzeStmtFunctionStmt(const parser::StmtFunctionStmt &);
1777   void CheckImports();
1778   void CheckImport(const SourceName &, const SourceName &);
1779   void HandleCall(Symbol::Flag, const parser::Call &);
1780   void HandleProcedureName(Symbol::Flag, const parser::Name &);
1781   bool CheckImplicitNoneExternal(const SourceName &, const Symbol &);
1782   bool SetProcFlag(const parser::Name &, Symbol &, Symbol::Flag);
1783   void ResolveSpecificationParts(ProgramTree &);
1784   void AddSubpNames(ProgramTree &);
1785   bool BeginScopeForNode(const ProgramTree &);
1786   void EndScopeForNode(const ProgramTree &);
1787   void FinishSpecificationParts(const ProgramTree &);
1788   void FinishExecutionParts(const ProgramTree &);
1789   void FinishDerivedTypeInstantiation(Scope &);
1790   void ResolveExecutionParts(const ProgramTree &);
1791   void UseCUDABuiltinNames();
1792   void HandleDerivedTypesInImplicitStmts(const parser::ImplicitPart &,
1793       const std::list<parser::DeclarationConstruct> &);
1794 };
1795 
1796 // ImplicitRules implementation
1797 
1798 bool ImplicitRules::isImplicitNoneType() const {
1799   if (isImplicitNoneType_) {
1800     return true;
1801   } else if (map_.empty() && inheritFromParent_) {
1802     return parent_->isImplicitNoneType();
1803   } else {
1804     return false; // default if not specified
1805   }
1806 }
1807 
1808 bool ImplicitRules::isImplicitNoneExternal() const {
1809   if (isImplicitNoneExternal_) {
1810     return true;
1811   } else if (inheritFromParent_) {
1812     return parent_->isImplicitNoneExternal();
1813   } else {
1814     return false; // default if not specified
1815   }
1816 }
1817 
1818 const DeclTypeSpec *ImplicitRules::GetType(
1819     SourceName name, bool respectImplicitNoneType) const {
1820   char ch{name.begin()[0]};
1821   if (isImplicitNoneType_ && respectImplicitNoneType) {
1822     return nullptr;
1823   } else if (auto it{map_.find(ch)}; it != map_.end()) {
1824     return &*it->second;
1825   } else if (inheritFromParent_) {
1826     return parent_->GetType(name, respectImplicitNoneType);
1827   } else if (ch >= 'i' && ch <= 'n') {
1828     return &context_.MakeNumericType(TypeCategory::Integer);
1829   } else if (ch >= 'a' && ch <= 'z') {
1830     return &context_.MakeNumericType(TypeCategory::Real);
1831   } else {
1832     return nullptr;
1833   }
1834 }
1835 
1836 void ImplicitRules::SetTypeMapping(const DeclTypeSpec &type,
1837     parser::Location fromLetter, parser::Location toLetter) {
1838   for (char ch = *fromLetter; ch; ch = ImplicitRules::Incr(ch)) {
1839     auto res{map_.emplace(ch, type)};
1840     if (!res.second) {
1841       context_.Say(parser::CharBlock{fromLetter},
1842           "More than one implicit type specified for '%c'"_err_en_US, ch);
1843     }
1844     if (ch == *toLetter) {
1845       break;
1846     }
1847   }
1848 }
1849 
1850 // Return the next char after ch in a way that works for ASCII or EBCDIC.
1851 // Return '\0' for the char after 'z'.
1852 char ImplicitRules::Incr(char ch) {
1853   switch (ch) {
1854   case 'i':
1855     return 'j';
1856   case 'r':
1857     return 's';
1858   case 'z':
1859     return '\0';
1860   default:
1861     return ch + 1;
1862   }
1863 }
1864 
1865 llvm::raw_ostream &operator<<(
1866     llvm::raw_ostream &o, const ImplicitRules &implicitRules) {
1867   o << "ImplicitRules:\n";
1868   for (char ch = 'a'; ch; ch = ImplicitRules::Incr(ch)) {
1869     ShowImplicitRule(o, implicitRules, ch);
1870   }
1871   ShowImplicitRule(o, implicitRules, '_');
1872   ShowImplicitRule(o, implicitRules, '$');
1873   ShowImplicitRule(o, implicitRules, '@');
1874   return o;
1875 }
1876 void ShowImplicitRule(
1877     llvm::raw_ostream &o, const ImplicitRules &implicitRules, char ch) {
1878   auto it{implicitRules.map_.find(ch)};
1879   if (it != implicitRules.map_.end()) {
1880     o << "  " << ch << ": " << *it->second << '\n';
1881   }
1882 }
1883 
1884 template <typename T> void BaseVisitor::Walk(const T &x) {
1885   parser::Walk(x, *this_);
1886 }
1887 
1888 void BaseVisitor::MakePlaceholder(
1889     const parser::Name &name, MiscDetails::Kind kind) {
1890   if (!name.symbol) {
1891     name.symbol = &context_->globalScope().MakeSymbol(
1892         name.source, Attrs{}, MiscDetails{kind});
1893   }
1894 }
1895 
1896 // AttrsVisitor implementation
1897 
1898 bool AttrsVisitor::BeginAttrs() {
1899   CHECK(!attrs_ && !cudaDataAttr_);
1900   attrs_ = Attrs{};
1901   return true;
1902 }
1903 Attrs AttrsVisitor::GetAttrs() {
1904   CHECK(attrs_);
1905   return *attrs_;
1906 }
1907 Attrs AttrsVisitor::EndAttrs() {
1908   Attrs result{GetAttrs()};
1909   attrs_.reset();
1910   cudaDataAttr_.reset();
1911   passName_ = std::nullopt;
1912   bindName_.reset();
1913   isCDefined_ = false;
1914   return result;
1915 }
1916 
1917 bool AttrsVisitor::SetPassNameOn(Symbol &symbol) {
1918   if (!passName_) {
1919     return false;
1920   }
1921   common::visit(common::visitors{
1922                     [&](ProcEntityDetails &x) { x.set_passName(*passName_); },
1923                     [&](ProcBindingDetails &x) { x.set_passName(*passName_); },
1924                     [](auto &) { common::die("unexpected pass name"); },
1925                 },
1926       symbol.details());
1927   return true;
1928 }
1929 
1930 void AttrsVisitor::SetBindNameOn(Symbol &symbol) {
1931   if ((!attrs_ || !attrs_->test(Attr::BIND_C)) &&
1932       !symbol.attrs().test(Attr::BIND_C)) {
1933     return;
1934   }
1935   symbol.SetIsCDefined(isCDefined_);
1936   std::optional<std::string> label{
1937       evaluate::GetScalarConstantValue<evaluate::Ascii>(bindName_)};
1938   // 18.9.2(2): discard leading and trailing blanks
1939   if (label) {
1940     symbol.SetIsExplicitBindName(true);
1941     auto first{label->find_first_not_of(" ")};
1942     if (first == std::string::npos) {
1943       // Empty NAME= means no binding at all (18.10.2p2)
1944       return;
1945     }
1946     auto last{label->find_last_not_of(" ")};
1947     label = label->substr(first, last - first + 1);
1948   } else if (symbol.GetIsExplicitBindName()) {
1949     // don't try to override explicit binding name with default
1950     return;
1951   } else if (ClassifyProcedure(symbol) == ProcedureDefinitionClass::Internal) {
1952     // BIND(C) does not give an implicit binding label to internal procedures.
1953     return;
1954   } else {
1955     label = symbol.name().ToString();
1956   }
1957   // Checks whether a symbol has two Bind names.
1958   std::string oldBindName;
1959   if (const auto *bindName{symbol.GetBindName()}) {
1960     oldBindName = *bindName;
1961   }
1962   symbol.SetBindName(std::move(*label));
1963   if (!oldBindName.empty()) {
1964     if (const std::string * newBindName{symbol.GetBindName()}) {
1965       if (oldBindName != *newBindName) {
1966         Say(symbol.name(),
1967             "The entity '%s' has multiple BIND names ('%s' and '%s')"_err_en_US,
1968             symbol.name(), oldBindName, *newBindName);
1969       }
1970     }
1971   }
1972 }
1973 
1974 void AttrsVisitor::Post(const parser::LanguageBindingSpec &x) {
1975   if (CheckAndSet(Attr::BIND_C)) {
1976     if (const auto &name{
1977             std::get<std::optional<parser::ScalarDefaultCharConstantExpr>>(
1978                 x.t)}) {
1979       bindName_ = EvaluateExpr(*name);
1980     }
1981     isCDefined_ = std::get<bool>(x.t);
1982   }
1983 }
1984 bool AttrsVisitor::Pre(const parser::IntentSpec &x) {
1985   CheckAndSet(IntentSpecToAttr(x));
1986   return false;
1987 }
1988 bool AttrsVisitor::Pre(const parser::Pass &x) {
1989   if (CheckAndSet(Attr::PASS)) {
1990     if (x.v) {
1991       passName_ = x.v->source;
1992       MakePlaceholder(*x.v, MiscDetails::Kind::PassName);
1993     }
1994   }
1995   return false;
1996 }
1997 
1998 // C730, C743, C755, C778, C1543 say no attribute or prefix repetitions
1999 bool AttrsVisitor::IsDuplicateAttr(Attr attrName) {
2000   CHECK(attrs_);
2001   if (attrs_->test(attrName)) {
2002     context().Warn(common::LanguageFeature::RedundantAttribute,
2003         currStmtSource().value(),
2004         "Attribute '%s' cannot be used more than once"_warn_en_US,
2005         AttrToString(attrName));
2006     return true;
2007   }
2008   return false;
2009 }
2010 
2011 // See if attrName violates a constraint cause by a conflict.  attr1 and attr2
2012 // name attributes that cannot be used on the same declaration
2013 bool AttrsVisitor::HaveAttrConflict(Attr attrName, Attr attr1, Attr attr2) {
2014   CHECK(attrs_);
2015   if ((attrName == attr1 && attrs_->test(attr2)) ||
2016       (attrName == attr2 && attrs_->test(attr1))) {
2017     Say(currStmtSource().value(),
2018         "Attributes '%s' and '%s' conflict with each other"_err_en_US,
2019         AttrToString(attr1), AttrToString(attr2));
2020     return true;
2021   }
2022   return false;
2023 }
2024 // C759, C1543
2025 bool AttrsVisitor::IsConflictingAttr(Attr attrName) {
2026   return HaveAttrConflict(attrName, Attr::INTENT_IN, Attr::INTENT_INOUT) ||
2027       HaveAttrConflict(attrName, Attr::INTENT_IN, Attr::INTENT_OUT) ||
2028       HaveAttrConflict(attrName, Attr::INTENT_INOUT, Attr::INTENT_OUT) ||
2029       HaveAttrConflict(attrName, Attr::PASS, Attr::NOPASS) || // C781
2030       HaveAttrConflict(attrName, Attr::PURE, Attr::IMPURE) ||
2031       HaveAttrConflict(attrName, Attr::PUBLIC, Attr::PRIVATE) ||
2032       HaveAttrConflict(attrName, Attr::RECURSIVE, Attr::NON_RECURSIVE);
2033 }
2034 bool AttrsVisitor::CheckAndSet(Attr attrName) {
2035   if (IsConflictingAttr(attrName) || IsDuplicateAttr(attrName)) {
2036     return false;
2037   }
2038   attrs_->set(attrName);
2039   return true;
2040 }
2041 bool AttrsVisitor::Pre(const common::CUDADataAttr x) {
2042   if (cudaDataAttr_.value_or(x) != x) {
2043     Say(currStmtSource().value(),
2044         "CUDA data attributes '%s' and '%s' may not both be specified"_err_en_US,
2045         common::EnumToString(*cudaDataAttr_), common::EnumToString(x));
2046   }
2047   cudaDataAttr_ = x;
2048   return false;
2049 }
2050 
2051 // DeclTypeSpecVisitor implementation
2052 
2053 const DeclTypeSpec *DeclTypeSpecVisitor::GetDeclTypeSpec() {
2054   return state_.declTypeSpec;
2055 }
2056 
2057 void DeclTypeSpecVisitor::BeginDeclTypeSpec() {
2058   CHECK(!state_.expectDeclTypeSpec);
2059   CHECK(!state_.declTypeSpec);
2060   state_.expectDeclTypeSpec = true;
2061 }
2062 void DeclTypeSpecVisitor::EndDeclTypeSpec() {
2063   CHECK(state_.expectDeclTypeSpec);
2064   state_ = {};
2065 }
2066 
2067 void DeclTypeSpecVisitor::SetDeclTypeSpecCategory(
2068     DeclTypeSpec::Category category) {
2069   CHECK(state_.expectDeclTypeSpec);
2070   state_.derived.category = category;
2071 }
2072 
2073 bool DeclTypeSpecVisitor::Pre(const parser::TypeGuardStmt &) {
2074   BeginDeclTypeSpec();
2075   return true;
2076 }
2077 void DeclTypeSpecVisitor::Post(const parser::TypeGuardStmt &) {
2078   EndDeclTypeSpec();
2079 }
2080 
2081 void DeclTypeSpecVisitor::Post(const parser::TypeSpec &typeSpec) {
2082   // Record the resolved DeclTypeSpec in the parse tree for use by
2083   // expression semantics if the DeclTypeSpec is a valid TypeSpec.
2084   // The grammar ensures that it's an intrinsic or derived type spec,
2085   // not TYPE(*) or CLASS(*) or CLASS(T).
2086   if (const DeclTypeSpec * spec{state_.declTypeSpec}) {
2087     switch (spec->category()) {
2088     case DeclTypeSpec::Numeric:
2089     case DeclTypeSpec::Logical:
2090     case DeclTypeSpec::Character:
2091       typeSpec.declTypeSpec = spec;
2092       break;
2093     case DeclTypeSpec::TypeDerived:
2094       if (const DerivedTypeSpec * derived{spec->AsDerived()}) {
2095         CheckForAbstractType(derived->typeSymbol()); // C703
2096         typeSpec.declTypeSpec = spec;
2097       }
2098       break;
2099     default:
2100       CRASH_NO_CASE;
2101     }
2102   }
2103 }
2104 
2105 void DeclTypeSpecVisitor::Post(
2106     const parser::IntrinsicTypeSpec::DoublePrecision &) {
2107   MakeNumericType(TypeCategory::Real, context().doublePrecisionKind());
2108 }
2109 void DeclTypeSpecVisitor::Post(
2110     const parser::IntrinsicTypeSpec::DoubleComplex &) {
2111   MakeNumericType(TypeCategory::Complex, context().doublePrecisionKind());
2112 }
2113 void DeclTypeSpecVisitor::MakeNumericType(TypeCategory category, int kind) {
2114   SetDeclTypeSpec(context().MakeNumericType(category, kind));
2115 }
2116 
2117 void DeclTypeSpecVisitor::CheckForAbstractType(const Symbol &typeSymbol) {
2118   if (typeSymbol.attrs().test(Attr::ABSTRACT)) {
2119     Say("ABSTRACT derived type may not be used here"_err_en_US);
2120   }
2121 }
2122 
2123 void DeclTypeSpecVisitor::Post(const parser::DeclarationTypeSpec::ClassStar &) {
2124   SetDeclTypeSpec(context().globalScope().MakeClassStarType());
2125 }
2126 void DeclTypeSpecVisitor::Post(const parser::DeclarationTypeSpec::TypeStar &) {
2127   SetDeclTypeSpec(context().globalScope().MakeTypeStarType());
2128 }
2129 
2130 // Check that we're expecting to see a DeclTypeSpec (and haven't seen one yet)
2131 // and save it in state_.declTypeSpec.
2132 void DeclTypeSpecVisitor::SetDeclTypeSpec(const DeclTypeSpec &declTypeSpec) {
2133   CHECK(state_.expectDeclTypeSpec);
2134   CHECK(!state_.declTypeSpec);
2135   state_.declTypeSpec = &declTypeSpec;
2136 }
2137 
2138 KindExpr DeclTypeSpecVisitor::GetKindParamExpr(
2139     TypeCategory category, const std::optional<parser::KindSelector> &kind) {
2140   return AnalyzeKindSelector(context(), category, kind);
2141 }
2142 
2143 // MessageHandler implementation
2144 
2145 Message &MessageHandler::Say(MessageFixedText &&msg) {
2146   return context_->Say(currStmtSource().value(), std::move(msg));
2147 }
2148 Message &MessageHandler::Say(MessageFormattedText &&msg) {
2149   return context_->Say(currStmtSource().value(), std::move(msg));
2150 }
2151 Message &MessageHandler::Say(const SourceName &name, MessageFixedText &&msg) {
2152   return Say(name, std::move(msg), name);
2153 }
2154 
2155 // ImplicitRulesVisitor implementation
2156 
2157 void ImplicitRulesVisitor::Post(const parser::ParameterStmt &) {
2158   prevParameterStmt_ = currStmtSource();
2159 }
2160 
2161 bool ImplicitRulesVisitor::Pre(const parser::ImplicitStmt &x) {
2162   bool result{
2163       common::visit(common::visitors{
2164                         [&](const std::list<ImplicitNoneNameSpec> &y) {
2165                           return HandleImplicitNone(y);
2166                         },
2167                         [&](const std::list<parser::ImplicitSpec> &) {
2168                           if (prevImplicitNoneType_) {
2169                             Say("IMPLICIT statement after IMPLICIT NONE or "
2170                                 "IMPLICIT NONE(TYPE) statement"_err_en_US);
2171                             return false;
2172                           }
2173                           implicitRules_->set_isImplicitNoneType(false);
2174                           return true;
2175                         },
2176                     },
2177           x.u)};
2178   prevImplicit_ = currStmtSource();
2179   return result;
2180 }
2181 
2182 bool ImplicitRulesVisitor::Pre(const parser::LetterSpec &x) {
2183   auto loLoc{std::get<parser::Location>(x.t)};
2184   auto hiLoc{loLoc};
2185   if (auto hiLocOpt{std::get<std::optional<parser::Location>>(x.t)}) {
2186     hiLoc = *hiLocOpt;
2187     if (*hiLoc < *loLoc) {
2188       Say(hiLoc, "'%s' does not follow '%s' alphabetically"_err_en_US,
2189           std::string(hiLoc, 1), std::string(loLoc, 1));
2190       return false;
2191     }
2192   }
2193   implicitRules_->SetTypeMapping(*GetDeclTypeSpec(), loLoc, hiLoc);
2194   return false;
2195 }
2196 
2197 bool ImplicitRulesVisitor::Pre(const parser::ImplicitSpec &) {
2198   BeginDeclTypeSpec();
2199   set_allowForwardReferenceToDerivedType(true);
2200   return true;
2201 }
2202 
2203 void ImplicitRulesVisitor::Post(const parser::ImplicitSpec &) {
2204   set_allowForwardReferenceToDerivedType(false);
2205   EndDeclTypeSpec();
2206 }
2207 
2208 void ImplicitRulesVisitor::SetScope(const Scope &scope) {
2209   implicitRules_ = &DEREF(implicitRulesMap_).at(&scope);
2210   prevImplicit_ = std::nullopt;
2211   prevImplicitNone_ = std::nullopt;
2212   prevImplicitNoneType_ = std::nullopt;
2213   prevParameterStmt_ = std::nullopt;
2214 }
2215 void ImplicitRulesVisitor::BeginScope(const Scope &scope) {
2216   // find or create implicit rules for this scope
2217   DEREF(implicitRulesMap_).try_emplace(&scope, context(), implicitRules_);
2218   SetScope(scope);
2219 }
2220 
2221 // TODO: for all of these errors, reference previous statement too
2222 bool ImplicitRulesVisitor::HandleImplicitNone(
2223     const std::list<ImplicitNoneNameSpec> &nameSpecs) {
2224   if (prevImplicitNone_) {
2225     Say("More than one IMPLICIT NONE statement"_err_en_US);
2226     Say(*prevImplicitNone_, "Previous IMPLICIT NONE statement"_en_US);
2227     return false;
2228   }
2229   if (prevParameterStmt_) {
2230     Say("IMPLICIT NONE statement after PARAMETER statement"_err_en_US);
2231     return false;
2232   }
2233   prevImplicitNone_ = currStmtSource();
2234   bool implicitNoneTypeNever{
2235       context().IsEnabled(common::LanguageFeature::ImplicitNoneTypeNever)};
2236   if (nameSpecs.empty()) {
2237     if (!implicitNoneTypeNever) {
2238       prevImplicitNoneType_ = currStmtSource();
2239       implicitRules_->set_isImplicitNoneType(true);
2240       if (prevImplicit_) {
2241         Say("IMPLICIT NONE statement after IMPLICIT statement"_err_en_US);
2242         return false;
2243       }
2244     }
2245   } else {
2246     int sawType{0};
2247     int sawExternal{0};
2248     for (const auto noneSpec : nameSpecs) {
2249       switch (noneSpec) {
2250       case ImplicitNoneNameSpec::External:
2251         implicitRules_->set_isImplicitNoneExternal(true);
2252         ++sawExternal;
2253         break;
2254       case ImplicitNoneNameSpec::Type:
2255         if (!implicitNoneTypeNever) {
2256           prevImplicitNoneType_ = currStmtSource();
2257           implicitRules_->set_isImplicitNoneType(true);
2258           if (prevImplicit_) {
2259             Say("IMPLICIT NONE(TYPE) after IMPLICIT statement"_err_en_US);
2260             return false;
2261           }
2262           ++sawType;
2263         }
2264         break;
2265       }
2266     }
2267     if (sawType > 1) {
2268       Say("TYPE specified more than once in IMPLICIT NONE statement"_err_en_US);
2269       return false;
2270     }
2271     if (sawExternal > 1) {
2272       Say("EXTERNAL specified more than once in IMPLICIT NONE statement"_err_en_US);
2273       return false;
2274     }
2275   }
2276   return true;
2277 }
2278 
2279 // ArraySpecVisitor implementation
2280 
2281 void ArraySpecVisitor::Post(const parser::ArraySpec &x) {
2282   CHECK(arraySpec_.empty());
2283   arraySpec_ = AnalyzeArraySpec(context(), x);
2284 }
2285 void ArraySpecVisitor::Post(const parser::ComponentArraySpec &x) {
2286   CHECK(arraySpec_.empty());
2287   arraySpec_ = AnalyzeArraySpec(context(), x);
2288 }
2289 void ArraySpecVisitor::Post(const parser::CoarraySpec &x) {
2290   CHECK(coarraySpec_.empty());
2291   coarraySpec_ = AnalyzeCoarraySpec(context(), x);
2292 }
2293 
2294 const ArraySpec &ArraySpecVisitor::arraySpec() {
2295   return !arraySpec_.empty() ? arraySpec_ : attrArraySpec_;
2296 }
2297 const ArraySpec &ArraySpecVisitor::coarraySpec() {
2298   return !coarraySpec_.empty() ? coarraySpec_ : attrCoarraySpec_;
2299 }
2300 void ArraySpecVisitor::BeginArraySpec() {
2301   CHECK(arraySpec_.empty());
2302   CHECK(coarraySpec_.empty());
2303   CHECK(attrArraySpec_.empty());
2304   CHECK(attrCoarraySpec_.empty());
2305 }
2306 void ArraySpecVisitor::EndArraySpec() {
2307   CHECK(arraySpec_.empty());
2308   CHECK(coarraySpec_.empty());
2309   attrArraySpec_.clear();
2310   attrCoarraySpec_.clear();
2311 }
2312 void ArraySpecVisitor::PostAttrSpec() {
2313   // Save dimension/codimension from attrs so we can process array/coarray-spec
2314   // on the entity-decl
2315   if (!arraySpec_.empty()) {
2316     if (attrArraySpec_.empty()) {
2317       attrArraySpec_ = arraySpec_;
2318       arraySpec_.clear();
2319     } else {
2320       Say(currStmtSource().value(),
2321           "Attribute 'DIMENSION' cannot be used more than once"_err_en_US);
2322     }
2323   }
2324   if (!coarraySpec_.empty()) {
2325     if (attrCoarraySpec_.empty()) {
2326       attrCoarraySpec_ = coarraySpec_;
2327       coarraySpec_.clear();
2328     } else {
2329       Say(currStmtSource().value(),
2330           "Attribute 'CODIMENSION' cannot be used more than once"_err_en_US);
2331     }
2332   }
2333 }
2334 
2335 // FuncResultStack implementation
2336 
2337 FuncResultStack::~FuncResultStack() { CHECK(stack_.empty()); }
2338 
2339 void FuncResultStack::CompleteFunctionResultType() {
2340   // If the function has a type in the prefix, process it now.
2341   FuncInfo *info{Top()};
2342   if (info && &info->scope == &scopeHandler_.currScope()) {
2343     if (info->parsedType && info->resultSymbol) {
2344       scopeHandler_.messageHandler().set_currStmtSource(info->source);
2345       if (const auto *type{
2346               scopeHandler_.ProcessTypeSpec(*info->parsedType, true)}) {
2347         Symbol &symbol{*info->resultSymbol};
2348         if (!scopeHandler_.context().HasError(symbol)) {
2349           if (symbol.GetType()) {
2350             scopeHandler_.Say(symbol.name(),
2351                 "Function cannot have both an explicit type prefix and a RESULT suffix"_err_en_US);
2352             scopeHandler_.context().SetError(symbol);
2353           } else {
2354             symbol.SetType(*type);
2355           }
2356         }
2357       }
2358       info->parsedType = nullptr;
2359     }
2360   }
2361 }
2362 
2363 // Called from ConvertTo{Object/Proc}Entity to cope with any appearance
2364 // of the function result in a specification expression.
2365 void FuncResultStack::CompleteTypeIfFunctionResult(Symbol &symbol) {
2366   if (FuncInfo * info{Top()}) {
2367     if (info->resultSymbol == &symbol) {
2368       CompleteFunctionResultType();
2369     }
2370   }
2371 }
2372 
2373 void FuncResultStack::Pop() {
2374   if (!stack_.empty() && &stack_.back().scope == &scopeHandler_.currScope()) {
2375     stack_.pop_back();
2376   }
2377 }
2378 
2379 // ScopeHandler implementation
2380 
2381 void ScopeHandler::SayAlreadyDeclared(const parser::Name &name, Symbol &prev) {
2382   SayAlreadyDeclared(name.source, prev);
2383 }
2384 void ScopeHandler::SayAlreadyDeclared(const SourceName &name, Symbol &prev) {
2385   if (context().HasError(prev)) {
2386     // don't report another error about prev
2387   } else {
2388     if (const auto *details{prev.detailsIf<UseDetails>()}) {
2389       Say(name, "'%s' is already declared in this scoping unit"_err_en_US)
2390           .Attach(details->location(),
2391               "It is use-associated with '%s' in module '%s'"_en_US,
2392               details->symbol().name(), GetUsedModule(*details).name());
2393     } else {
2394       SayAlreadyDeclared(name, prev.name());
2395     }
2396     context().SetError(prev);
2397   }
2398 }
2399 void ScopeHandler::SayAlreadyDeclared(
2400     const SourceName &name1, const SourceName &name2) {
2401   if (name1.begin() < name2.begin()) {
2402     SayAlreadyDeclared(name2, name1);
2403   } else {
2404     Say(name1, "'%s' is already declared in this scoping unit"_err_en_US)
2405         .Attach(name2, "Previous declaration of '%s'"_en_US, name2);
2406   }
2407 }
2408 
2409 void ScopeHandler::SayWithReason(const parser::Name &name, Symbol &symbol,
2410     MessageFixedText &&msg1, Message &&msg2) {
2411   bool isFatal{msg1.IsFatal()};
2412   Say(name, std::move(msg1), symbol.name()).Attach(std::move(msg2));
2413   context().SetError(symbol, isFatal);
2414 }
2415 
2416 template <typename... A>
2417 Message &ScopeHandler::SayWithDecl(const parser::Name &name, Symbol &symbol,
2418     MessageFixedText &&msg, A &&...args) {
2419   auto &message{
2420       Say(name.source, std::move(msg), symbol.name(), std::forward<A>(args)...)
2421           .Attach(symbol.name(),
2422               symbol.test(Symbol::Flag::Implicit)
2423                   ? "Implicit declaration of '%s'"_en_US
2424                   : "Declaration of '%s'"_en_US,
2425               name.source)};
2426   if (const auto *proc{symbol.detailsIf<ProcEntityDetails>()}) {
2427     if (auto usedAsProc{proc->usedAsProcedureHere()}) {
2428       if (usedAsProc->begin() != symbol.name().begin()) {
2429         message.Attach(*usedAsProc, "Referenced as a procedure"_en_US);
2430       }
2431     }
2432   }
2433   return message;
2434 }
2435 
2436 void ScopeHandler::SayLocalMustBeVariable(
2437     const parser::Name &name, Symbol &symbol) {
2438   SayWithDecl(name, symbol,
2439       "The name '%s' must be a variable to appear"
2440       " in a locality-spec"_err_en_US);
2441 }
2442 
2443 Message &ScopeHandler::SayDerivedType(
2444     const SourceName &name, MessageFixedText &&msg, const Scope &type) {
2445   const Symbol &typeSymbol{DEREF(type.GetSymbol())};
2446   return Say(name, std::move(msg), name, typeSymbol.name())
2447       .Attach(typeSymbol.name(), "Declaration of derived type '%s'"_en_US,
2448           typeSymbol.name());
2449 }
2450 Message &ScopeHandler::Say2(const SourceName &name1, MessageFixedText &&msg1,
2451     const SourceName &name2, MessageFixedText &&msg2) {
2452   return Say(name1, std::move(msg1)).Attach(name2, std::move(msg2), name2);
2453 }
2454 Message &ScopeHandler::Say2(const SourceName &name, MessageFixedText &&msg1,
2455     Symbol &symbol, MessageFixedText &&msg2) {
2456   bool isFatal{msg1.IsFatal()};
2457   Message &result{Say2(name, std::move(msg1), symbol.name(), std::move(msg2))};
2458   context().SetError(symbol, isFatal);
2459   return result;
2460 }
2461 Message &ScopeHandler::Say2(const parser::Name &name, MessageFixedText &&msg1,
2462     Symbol &symbol, MessageFixedText &&msg2) {
2463   bool isFatal{msg1.IsFatal()};
2464   Message &result{
2465       Say2(name.source, std::move(msg1), symbol.name(), std::move(msg2))};
2466   context().SetError(symbol, isFatal);
2467   return result;
2468 }
2469 
2470 // This is essentially GetProgramUnitContaining(), but it can return
2471 // a mutable Scope &, it ignores statement functions, and it fails
2472 // gracefully for error recovery (returning the original Scope).
2473 template <typename T> static T &GetInclusiveScope(T &scope) {
2474   for (T *s{&scope}; !s->IsGlobal(); s = &s->parent()) {
2475     switch (s->kind()) {
2476     case Scope::Kind::Module:
2477     case Scope::Kind::MainProgram:
2478     case Scope::Kind::Subprogram:
2479     case Scope::Kind::BlockData:
2480       if (!s->IsStmtFunction()) {
2481         return *s;
2482       }
2483       break;
2484     default:;
2485     }
2486   }
2487   return scope;
2488 }
2489 
2490 Scope &ScopeHandler::InclusiveScope() { return GetInclusiveScope(currScope()); }
2491 
2492 Scope *ScopeHandler::GetHostProcedure() {
2493   Scope &parent{InclusiveScope().parent()};
2494   switch (parent.kind()) {
2495   case Scope::Kind::Subprogram:
2496     return &parent;
2497   case Scope::Kind::MainProgram:
2498     return &parent;
2499   default:
2500     return nullptr;
2501   }
2502 }
2503 
2504 Scope &ScopeHandler::NonDerivedTypeScope() {
2505   return currScope_->IsDerivedType() ? currScope_->parent() : *currScope_;
2506 }
2507 
2508 void ScopeHandler::PushScope(Scope::Kind kind, Symbol *symbol) {
2509   PushScope(currScope().MakeScope(kind, symbol));
2510 }
2511 void ScopeHandler::PushScope(Scope &scope) {
2512   currScope_ = &scope;
2513   auto kind{currScope_->kind()};
2514   if (kind != Scope::Kind::BlockConstruct &&
2515       kind != Scope::Kind::OtherConstruct && kind != Scope::Kind::OtherClause) {
2516     BeginScope(scope);
2517   }
2518   // The name of a module or submodule cannot be "used" in its scope,
2519   // as we read 19.3.1(2), so we allow the name to be used as a local
2520   // identifier in the module or submodule too.  Same with programs
2521   // (14.1(3)) and BLOCK DATA.
2522   if (!currScope_->IsDerivedType() && kind != Scope::Kind::Module &&
2523       kind != Scope::Kind::MainProgram && kind != Scope::Kind::BlockData) {
2524     if (auto *symbol{scope.symbol()}) {
2525       // Create a dummy symbol so we can't create another one with the same
2526       // name. It might already be there if we previously pushed the scope.
2527       SourceName name{symbol->name()};
2528       if (!FindInScope(scope, name)) {
2529         auto &newSymbol{MakeSymbol(name)};
2530         if (kind == Scope::Kind::Subprogram) {
2531           // Allow for recursive references.  If this symbol is a function
2532           // without an explicit RESULT(), this new symbol will be discarded
2533           // and replaced with an object of the same name.
2534           newSymbol.set_details(HostAssocDetails{*symbol});
2535         } else {
2536           newSymbol.set_details(MiscDetails{MiscDetails::Kind::ScopeName});
2537         }
2538       }
2539     }
2540   }
2541 }
2542 void ScopeHandler::PopScope() {
2543   CHECK(currScope_ && !currScope_->IsGlobal());
2544   // Entities that are not yet classified as objects or procedures are now
2545   // assumed to be objects.
2546   // TODO: Statement functions
2547   for (auto &pair : currScope()) {
2548     ConvertToObjectEntity(*pair.second);
2549   }
2550   funcResultStack_.Pop();
2551   // If popping back into a global scope, pop back to the main global scope.
2552   SetScope(currScope_->parent().IsGlobal() ? context().globalScope()
2553                                            : currScope_->parent());
2554 }
2555 void ScopeHandler::SetScope(Scope &scope) {
2556   currScope_ = &scope;
2557   ImplicitRulesVisitor::SetScope(InclusiveScope());
2558 }
2559 
2560 Symbol *ScopeHandler::FindSymbol(const parser::Name &name) {
2561   return FindSymbol(currScope(), name);
2562 }
2563 Symbol *ScopeHandler::FindSymbol(const Scope &scope, const parser::Name &name) {
2564   if (scope.IsDerivedType()) {
2565     if (Symbol * symbol{scope.FindComponent(name.source)}) {
2566       if (symbol->has<TypeParamDetails>()) {
2567         return Resolve(name, symbol);
2568       }
2569     }
2570     return FindSymbol(scope.parent(), name);
2571   } else {
2572     // In EQUIVALENCE statements only resolve names in the local scope, see
2573     // 19.5.1.4, paragraph 2, item (10)
2574     return Resolve(name,
2575         inEquivalenceStmt_ ? FindInScope(scope, name)
2576                            : scope.FindSymbol(name.source));
2577   }
2578 }
2579 
2580 Symbol &ScopeHandler::MakeSymbol(
2581     Scope &scope, const SourceName &name, Attrs attrs) {
2582   if (Symbol * symbol{FindInScope(scope, name)}) {
2583     CheckDuplicatedAttrs(name, *symbol, attrs);
2584     SetExplicitAttrs(*symbol, attrs);
2585     return *symbol;
2586   } else {
2587     const auto pair{scope.try_emplace(name, attrs, UnknownDetails{})};
2588     CHECK(pair.second); // name was not found, so must be able to add
2589     return *pair.first->second;
2590   }
2591 }
2592 Symbol &ScopeHandler::MakeSymbol(const SourceName &name, Attrs attrs) {
2593   return MakeSymbol(currScope(), name, attrs);
2594 }
2595 Symbol &ScopeHandler::MakeSymbol(const parser::Name &name, Attrs attrs) {
2596   return Resolve(name, MakeSymbol(name.source, attrs));
2597 }
2598 Symbol &ScopeHandler::MakeHostAssocSymbol(
2599     const parser::Name &name, const Symbol &hostSymbol) {
2600   Symbol &symbol{*NonDerivedTypeScope()
2601                       .try_emplace(name.source, HostAssocDetails{hostSymbol})
2602                       .first->second};
2603   name.symbol = &symbol;
2604   symbol.attrs() = hostSymbol.attrs(); // TODO: except PRIVATE, PUBLIC?
2605   // These attributes can be redundantly reapplied without error
2606   // on the host-associated name, at most once (C815).
2607   symbol.implicitAttrs() =
2608       symbol.attrs() & Attrs{Attr::ASYNCHRONOUS, Attr::VOLATILE};
2609   // SAVE statement in the inner scope will create a new symbol.
2610   // If the host variable is used via host association,
2611   // we have to propagate whether SAVE is implicit in the host scope.
2612   // Otherwise, verifications that do not allow explicit SAVE
2613   // attribute would fail.
2614   symbol.implicitAttrs() |= hostSymbol.implicitAttrs() & Attrs{Attr::SAVE};
2615   symbol.flags() = hostSymbol.flags();
2616   return symbol;
2617 }
2618 Symbol &ScopeHandler::CopySymbol(const SourceName &name, const Symbol &symbol) {
2619   CHECK(!FindInScope(name));
2620   return MakeSymbol(currScope(), name, symbol.attrs());
2621 }
2622 
2623 // Look for name only in scope, not in enclosing scopes.
2624 
2625 Symbol *ScopeHandler::FindInScope(
2626     const Scope &scope, const parser::Name &name) {
2627   return Resolve(name, FindInScope(scope, name.source));
2628 }
2629 Symbol *ScopeHandler::FindInScope(const Scope &scope, const SourceName &name) {
2630   // all variants of names, e.g. "operator(.ne.)" for "operator(/=)"
2631   for (const std::string &n : GetAllNames(context(), name)) {
2632     auto it{scope.find(SourceName{n})};
2633     if (it != scope.end()) {
2634       return &*it->second;
2635     }
2636   }
2637   return nullptr;
2638 }
2639 
2640 // Find a component or type parameter by name in a derived type or its parents.
2641 Symbol *ScopeHandler::FindInTypeOrParents(
2642     const Scope &scope, const parser::Name &name) {
2643   return Resolve(name, scope.FindComponent(name.source));
2644 }
2645 Symbol *ScopeHandler::FindInTypeOrParents(const parser::Name &name) {
2646   return FindInTypeOrParents(currScope(), name);
2647 }
2648 Symbol *ScopeHandler::FindInScopeOrBlockConstructs(
2649     const Scope &scope, SourceName name) {
2650   if (Symbol * symbol{FindInScope(scope, name)}) {
2651     return symbol;
2652   }
2653   for (const Scope &child : scope.children()) {
2654     if (child.kind() == Scope::Kind::BlockConstruct) {
2655       if (Symbol * symbol{FindInScopeOrBlockConstructs(child, name)}) {
2656         return symbol;
2657       }
2658     }
2659   }
2660   return nullptr;
2661 }
2662 
2663 void ScopeHandler::EraseSymbol(const parser::Name &name) {
2664   currScope().erase(name.source);
2665   name.symbol = nullptr;
2666 }
2667 
2668 static bool NeedsType(const Symbol &symbol) {
2669   return !symbol.GetType() &&
2670       common::visit(common::visitors{
2671                         [](const EntityDetails &) { return true; },
2672                         [](const ObjectEntityDetails &) { return true; },
2673                         [](const AssocEntityDetails &) { return true; },
2674                         [&](const ProcEntityDetails &p) {
2675                           return symbol.test(Symbol::Flag::Function) &&
2676                               !symbol.attrs().test(Attr::INTRINSIC) &&
2677                               !p.type() && !p.procInterface();
2678                         },
2679                         [](const auto &) { return false; },
2680                     },
2681           symbol.details());
2682 }
2683 
2684 void ScopeHandler::ApplyImplicitRules(
2685     Symbol &symbol, bool allowForwardReference) {
2686   funcResultStack_.CompleteTypeIfFunctionResult(symbol);
2687   if (context().HasError(symbol) || !NeedsType(symbol)) {
2688     return;
2689   }
2690   if (const DeclTypeSpec * type{GetImplicitType(symbol)}) {
2691     if (!skipImplicitTyping_) {
2692       symbol.set(Symbol::Flag::Implicit);
2693       symbol.SetType(*type);
2694     }
2695     return;
2696   }
2697   if (symbol.has<ProcEntityDetails>() && !symbol.attrs().test(Attr::EXTERNAL)) {
2698     std::optional<Symbol::Flag> functionOrSubroutineFlag;
2699     if (symbol.test(Symbol::Flag::Function)) {
2700       functionOrSubroutineFlag = Symbol::Flag::Function;
2701     } else if (symbol.test(Symbol::Flag::Subroutine)) {
2702       functionOrSubroutineFlag = Symbol::Flag::Subroutine;
2703     }
2704     if (IsIntrinsic(symbol.name(), functionOrSubroutineFlag)) {
2705       // type will be determined in expression semantics
2706       AcquireIntrinsicProcedureFlags(symbol);
2707       return;
2708     }
2709   }
2710   if (allowForwardReference && ImplicitlyTypeForwardRef(symbol)) {
2711     return;
2712   }
2713   if (const auto *entity{symbol.detailsIf<EntityDetails>()};
2714       entity && entity->isDummy()) {
2715     // Dummy argument, no declaration or reference; if it turns
2716     // out to be a subroutine, it's fine, and if it is a function
2717     // or object, it'll be caught later.
2718     return;
2719   }
2720   if (deferImplicitTyping_) {
2721     return;
2722   }
2723   if (!context().HasError(symbol)) {
2724     Say(symbol.name(), "No explicit type declared for '%s'"_err_en_US);
2725     context().SetError(symbol);
2726   }
2727 }
2728 
2729 // Extension: Allow forward references to scalar integer dummy arguments
2730 // or variables in COMMON to appear in specification expressions under
2731 // IMPLICIT NONE(TYPE) when what would otherwise have been their implicit
2732 // type is default INTEGER.
2733 bool ScopeHandler::ImplicitlyTypeForwardRef(Symbol &symbol) {
2734   if (!inSpecificationPart_ || context().HasError(symbol) ||
2735       !(IsDummy(symbol) || FindCommonBlockContaining(symbol)) ||
2736       symbol.Rank() != 0 ||
2737       !context().languageFeatures().IsEnabled(
2738           common::LanguageFeature::ForwardRefImplicitNone)) {
2739     return false;
2740   }
2741   const DeclTypeSpec *type{
2742       GetImplicitType(symbol, false /*ignore IMPLICIT NONE*/)};
2743   if (!type || !type->IsNumeric(TypeCategory::Integer)) {
2744     return false;
2745   }
2746   auto kind{evaluate::ToInt64(type->numericTypeSpec().kind())};
2747   if (!kind || *kind != context().GetDefaultKind(TypeCategory::Integer)) {
2748     return false;
2749   }
2750   if (!ConvertToObjectEntity(symbol)) {
2751     return false;
2752   }
2753   // TODO: check no INTENT(OUT) if dummy?
2754   context().Warn(common::LanguageFeature::ForwardRefImplicitNone, symbol.name(),
2755       "'%s' was used without (or before) being explicitly typed"_warn_en_US,
2756       symbol.name());
2757   symbol.set(Symbol::Flag::Implicit);
2758   symbol.SetType(*type);
2759   return true;
2760 }
2761 
2762 // Ensure that the symbol for an intrinsic procedure is marked with
2763 // the INTRINSIC attribute.  Also set PURE &/or ELEMENTAL as
2764 // appropriate.
2765 void ScopeHandler::AcquireIntrinsicProcedureFlags(Symbol &symbol) {
2766   SetImplicitAttr(symbol, Attr::INTRINSIC);
2767   switch (context().intrinsics().GetIntrinsicClass(symbol.name().ToString())) {
2768   case evaluate::IntrinsicClass::elementalFunction:
2769   case evaluate::IntrinsicClass::elementalSubroutine:
2770     SetExplicitAttr(symbol, Attr::ELEMENTAL);
2771     SetExplicitAttr(symbol, Attr::PURE);
2772     break;
2773   case evaluate::IntrinsicClass::impureSubroutine:
2774     break;
2775   default:
2776     SetExplicitAttr(symbol, Attr::PURE);
2777   }
2778 }
2779 
2780 const DeclTypeSpec *ScopeHandler::GetImplicitType(
2781     Symbol &symbol, bool respectImplicitNoneType) {
2782   const Scope *scope{&symbol.owner()};
2783   if (scope->IsGlobal()) {
2784     scope = &currScope();
2785   }
2786   scope = &GetInclusiveScope(*scope);
2787   const auto *type{implicitRulesMap_->at(scope).GetType(
2788       symbol.name(), respectImplicitNoneType)};
2789   if (type) {
2790     if (const DerivedTypeSpec * derived{type->AsDerived()}) {
2791       // Resolve any forward-referenced derived type; a quick no-op else.
2792       auto &instantiatable{*const_cast<DerivedTypeSpec *>(derived)};
2793       instantiatable.Instantiate(currScope());
2794     }
2795   }
2796   return type;
2797 }
2798 
2799 void ScopeHandler::CheckEntryDummyUse(SourceName source, Symbol *symbol) {
2800   if (!inSpecificationPart_ && symbol &&
2801       symbol->test(Symbol::Flag::EntryDummyArgument)) {
2802     Say(source,
2803         "Dummy argument '%s' may not be used before its ENTRY statement"_err_en_US,
2804         symbol->name());
2805     symbol->set(Symbol::Flag::EntryDummyArgument, false);
2806   }
2807 }
2808 
2809 // Convert symbol to be a ObjectEntity or return false if it can't be.
2810 bool ScopeHandler::ConvertToObjectEntity(Symbol &symbol) {
2811   if (symbol.has<ObjectEntityDetails>()) {
2812     // nothing to do
2813   } else if (symbol.has<UnknownDetails>()) {
2814     // These are attributes that a name could have picked up from
2815     // an attribute statement or type declaration statement.
2816     if (symbol.attrs().HasAny({Attr::EXTERNAL, Attr::INTRINSIC})) {
2817       return false;
2818     }
2819     symbol.set_details(ObjectEntityDetails{});
2820   } else if (auto *details{symbol.detailsIf<EntityDetails>()}) {
2821     if (symbol.attrs().HasAny({Attr::EXTERNAL, Attr::INTRINSIC})) {
2822       return false;
2823     }
2824     funcResultStack_.CompleteTypeIfFunctionResult(symbol);
2825     symbol.set_details(ObjectEntityDetails{std::move(*details)});
2826   } else if (auto *useDetails{symbol.detailsIf<UseDetails>()}) {
2827     return useDetails->symbol().has<ObjectEntityDetails>();
2828   } else if (auto *hostDetails{symbol.detailsIf<HostAssocDetails>()}) {
2829     return hostDetails->symbol().has<ObjectEntityDetails>();
2830   } else {
2831     return false;
2832   }
2833   return true;
2834 }
2835 // Convert symbol to be a ProcEntity or return false if it can't be.
2836 bool ScopeHandler::ConvertToProcEntity(
2837     Symbol &symbol, std::optional<SourceName> usedHere) {
2838   if (symbol.has<ProcEntityDetails>()) {
2839   } else if (symbol.has<UnknownDetails>()) {
2840     symbol.set_details(ProcEntityDetails{});
2841   } else if (auto *details{symbol.detailsIf<EntityDetails>()}) {
2842     if (IsFunctionResult(symbol) &&
2843         !(IsPointer(symbol) && symbol.attrs().test(Attr::EXTERNAL))) {
2844       // Don't turn function result into a procedure pointer unless both
2845       // POINTER and EXTERNAL
2846       return false;
2847     }
2848     funcResultStack_.CompleteTypeIfFunctionResult(symbol);
2849     symbol.set_details(ProcEntityDetails{std::move(*details)});
2850     if (symbol.GetType() && !symbol.test(Symbol::Flag::Implicit)) {
2851       CHECK(!symbol.test(Symbol::Flag::Subroutine));
2852       symbol.set(Symbol::Flag::Function);
2853     }
2854   } else if (auto *useDetails{symbol.detailsIf<UseDetails>()}) {
2855     return useDetails->symbol().has<ProcEntityDetails>();
2856   } else if (auto *hostDetails{symbol.detailsIf<HostAssocDetails>()}) {
2857     return hostDetails->symbol().has<ProcEntityDetails>();
2858   } else {
2859     return false;
2860   }
2861   auto &proc{symbol.get<ProcEntityDetails>()};
2862   if (usedHere && !proc.usedAsProcedureHere()) {
2863     proc.set_usedAsProcedureHere(*usedHere);
2864   }
2865   return true;
2866 }
2867 
2868 const DeclTypeSpec &ScopeHandler::MakeNumericType(
2869     TypeCategory category, const std::optional<parser::KindSelector> &kind) {
2870   KindExpr value{GetKindParamExpr(category, kind)};
2871   if (auto known{evaluate::ToInt64(value)}) {
2872     return MakeNumericType(category, static_cast<int>(*known));
2873   } else {
2874     return currScope_->MakeNumericType(category, std::move(value));
2875   }
2876 }
2877 
2878 const DeclTypeSpec &ScopeHandler::MakeNumericType(
2879     TypeCategory category, int kind) {
2880   return context().MakeNumericType(category, kind);
2881 }
2882 
2883 const DeclTypeSpec &ScopeHandler::MakeLogicalType(
2884     const std::optional<parser::KindSelector> &kind) {
2885   KindExpr value{GetKindParamExpr(TypeCategory::Logical, kind)};
2886   if (auto known{evaluate::ToInt64(value)}) {
2887     return MakeLogicalType(static_cast<int>(*known));
2888   } else {
2889     return currScope_->MakeLogicalType(std::move(value));
2890   }
2891 }
2892 
2893 const DeclTypeSpec &ScopeHandler::MakeLogicalType(int kind) {
2894   return context().MakeLogicalType(kind);
2895 }
2896 
2897 void ScopeHandler::NotePossibleBadForwardRef(const parser::Name &name) {
2898   if (inSpecificationPart_ && !deferImplicitTyping_ && name.symbol) {
2899     auto kind{currScope().kind()};
2900     if ((kind == Scope::Kind::Subprogram && !currScope().IsStmtFunction()) ||
2901         kind == Scope::Kind::BlockConstruct) {
2902       bool isHostAssociated{&name.symbol->owner() == &currScope()
2903               ? name.symbol->has<HostAssocDetails>()
2904               : name.symbol->owner().Contains(currScope())};
2905       if (isHostAssociated) {
2906         specPartState_.forwardRefs.insert(name.source);
2907       }
2908     }
2909   }
2910 }
2911 
2912 std::optional<SourceName> ScopeHandler::HadForwardRef(
2913     const Symbol &symbol) const {
2914   auto iter{specPartState_.forwardRefs.find(symbol.name())};
2915   if (iter != specPartState_.forwardRefs.end()) {
2916     return *iter;
2917   }
2918   return std::nullopt;
2919 }
2920 
2921 bool ScopeHandler::CheckPossibleBadForwardRef(const Symbol &symbol) {
2922   if (!context().HasError(symbol)) {
2923     if (auto fwdRef{HadForwardRef(symbol)}) {
2924       const Symbol *outer{symbol.owner().FindSymbol(symbol.name())};
2925       if (outer && symbol.has<UseDetails>() &&
2926           &symbol.GetUltimate() == &outer->GetUltimate()) {
2927         // e.g. IMPORT of host's USE association
2928         return false;
2929       }
2930       Say(*fwdRef,
2931           "Forward reference to '%s' is not allowed in the same specification part"_err_en_US,
2932           *fwdRef)
2933           .Attach(symbol.name(), "Later declaration of '%s'"_en_US, *fwdRef);
2934       context().SetError(symbol);
2935       return true;
2936     }
2937     if ((IsDummy(symbol) || FindCommonBlockContaining(symbol)) &&
2938         isImplicitNoneType() && symbol.test(Symbol::Flag::Implicit) &&
2939         !context().HasError(symbol)) {
2940       // Dummy or COMMON was implicitly typed despite IMPLICIT NONE(TYPE) in
2941       // ApplyImplicitRules() due to use in a specification expression,
2942       // and no explicit type declaration appeared later.
2943       Say(symbol.name(), "No explicit type declared for '%s'"_err_en_US);
2944       context().SetError(symbol);
2945       return true;
2946     }
2947   }
2948   return false;
2949 }
2950 
2951 void ScopeHandler::MakeExternal(Symbol &symbol) {
2952   if (!symbol.attrs().test(Attr::EXTERNAL)) {
2953     SetImplicitAttr(symbol, Attr::EXTERNAL);
2954     if (symbol.attrs().test(Attr::INTRINSIC)) { // C840
2955       Say(symbol.name(),
2956           "Symbol '%s' cannot have both EXTERNAL and INTRINSIC attributes"_err_en_US,
2957           symbol.name());
2958     }
2959   }
2960 }
2961 
2962 bool ScopeHandler::CheckDuplicatedAttr(
2963     SourceName name, Symbol &symbol, Attr attr) {
2964   if (attr == Attr::SAVE) {
2965     // checked elsewhere
2966   } else if (symbol.attrs().test(attr)) { // C815
2967     if (symbol.implicitAttrs().test(attr)) {
2968       // Implied attribute is now confirmed explicitly
2969       symbol.implicitAttrs().reset(attr);
2970     } else {
2971       Say(name, "%s attribute was already specified on '%s'"_err_en_US,
2972           EnumToString(attr), name);
2973       return false;
2974     }
2975   }
2976   return true;
2977 }
2978 
2979 bool ScopeHandler::CheckDuplicatedAttrs(
2980     SourceName name, Symbol &symbol, Attrs attrs) {
2981   bool ok{true};
2982   attrs.IterateOverMembers(
2983       [&](Attr x) { ok &= CheckDuplicatedAttr(name, symbol, x); });
2984   return ok;
2985 }
2986 
2987 void ScopeHandler::SetCUDADataAttr(SourceName source, Symbol &symbol,
2988     std::optional<common::CUDADataAttr> attr) {
2989   if (attr) {
2990     ConvertToObjectEntity(symbol);
2991     if (auto *object{symbol.detailsIf<ObjectEntityDetails>()}) {
2992       if (*attr != object->cudaDataAttr().value_or(*attr)) {
2993         Say(source,
2994             "'%s' already has another CUDA data attribute ('%s')"_err_en_US,
2995             symbol.name(),
2996             std::string{common::EnumToString(*object->cudaDataAttr())}.c_str());
2997       } else {
2998         object->set_cudaDataAttr(attr);
2999       }
3000     } else {
3001       Say(source,
3002           "'%s' is not an object and may not have a CUDA data attribute"_err_en_US,
3003           symbol.name());
3004     }
3005   }
3006 }
3007 
3008 // ModuleVisitor implementation
3009 
3010 bool ModuleVisitor::Pre(const parser::Only &x) {
3011   common::visit(common::visitors{
3012                     [&](const Indirection<parser::GenericSpec> &generic) {
3013                       GenericSpecInfo genericSpecInfo{generic.value()};
3014                       AddUseOnly(genericSpecInfo.symbolName());
3015                       AddUse(genericSpecInfo);
3016                     },
3017                     [&](const parser::Name &name) {
3018                       AddUseOnly(name.source);
3019                       Resolve(name, AddUse(name.source, name.source).use);
3020                     },
3021                     [&](const parser::Rename &rename) { Walk(rename); },
3022                 },
3023       x.u);
3024   return false;
3025 }
3026 
3027 void ModuleVisitor::CollectUseRenames(const parser::UseStmt &useStmt) {
3028   auto doRename{[&](const parser::Rename &rename) {
3029     if (const auto *names{std::get_if<parser::Rename::Names>(&rename.u)}) {
3030       AddUseRename(std::get<1>(names->t).source, useStmt.moduleName.source);
3031     }
3032   }};
3033   common::visit(
3034       common::visitors{
3035           [&](const std::list<parser::Rename> &renames) {
3036             for (const auto &rename : renames) {
3037               doRename(rename);
3038             }
3039           },
3040           [&](const std::list<parser::Only> &onlys) {
3041             for (const auto &only : onlys) {
3042               if (const auto *rename{std::get_if<parser::Rename>(&only.u)}) {
3043                 doRename(*rename);
3044               }
3045             }
3046           },
3047       },
3048       useStmt.u);
3049 }
3050 
3051 bool ModuleVisitor::Pre(const parser::Rename::Names &x) {
3052   const auto &localName{std::get<0>(x.t)};
3053   const auto &useName{std::get<1>(x.t)};
3054   SymbolRename rename{AddUse(localName.source, useName.source)};
3055   Resolve(useName, rename.use);
3056   Resolve(localName, rename.local);
3057   return false;
3058 }
3059 bool ModuleVisitor::Pre(const parser::Rename::Operators &x) {
3060   const parser::DefinedOpName &local{std::get<0>(x.t)};
3061   const parser::DefinedOpName &use{std::get<1>(x.t)};
3062   GenericSpecInfo localInfo{local};
3063   GenericSpecInfo useInfo{use};
3064   if (IsIntrinsicOperator(context(), local.v.source)) {
3065     Say(local.v,
3066         "Intrinsic operator '%s' may not be used as a defined operator"_err_en_US);
3067   } else if (IsLogicalConstant(context(), local.v.source)) {
3068     Say(local.v,
3069         "Logical constant '%s' may not be used as a defined operator"_err_en_US);
3070   } else {
3071     SymbolRename rename{AddUse(localInfo.symbolName(), useInfo.symbolName())};
3072     useInfo.Resolve(rename.use);
3073     localInfo.Resolve(rename.local);
3074   }
3075   return false;
3076 }
3077 
3078 // Set useModuleScope_ to the Scope of the module being used.
3079 bool ModuleVisitor::Pre(const parser::UseStmt &x) {
3080   std::optional<bool> isIntrinsic;
3081   if (x.nature) {
3082     isIntrinsic = *x.nature == parser::UseStmt::ModuleNature::Intrinsic;
3083   } else if (currScope().IsModule() && currScope().symbol() &&
3084       currScope().symbol()->attrs().test(Attr::INTRINSIC)) {
3085     // Intrinsic modules USE only other intrinsic modules
3086     isIntrinsic = true;
3087   }
3088   useModuleScope_ = FindModule(x.moduleName, isIntrinsic);
3089   if (!useModuleScope_) {
3090     return false;
3091   }
3092   AddAndCheckModuleUse(x.moduleName.source,
3093       useModuleScope_->parent().kind() == Scope::Kind::IntrinsicModules);
3094   // use the name from this source file
3095   useModuleScope_->symbol()->ReplaceName(x.moduleName.source);
3096   return true;
3097 }
3098 
3099 void ModuleVisitor::Post(const parser::UseStmt &x) {
3100   if (const auto *list{std::get_if<std::list<parser::Rename>>(&x.u)}) {
3101     // Not a use-only: collect the names that were used in renames,
3102     // then add a use for each public name that was not renamed.
3103     std::set<SourceName> useNames;
3104     for (const auto &rename : *list) {
3105       common::visit(common::visitors{
3106                         [&](const parser::Rename::Names &names) {
3107                           useNames.insert(std::get<1>(names.t).source);
3108                         },
3109                         [&](const parser::Rename::Operators &ops) {
3110                           useNames.insert(std::get<1>(ops.t).v.source);
3111                         },
3112                     },
3113           rename.u);
3114     }
3115     for (const auto &[name, symbol] : *useModuleScope_) {
3116       if (symbol->attrs().test(Attr::PUBLIC) && !IsUseRenamed(symbol->name()) &&
3117           (!symbol->implicitAttrs().test(Attr::INTRINSIC) ||
3118               symbol->has<UseDetails>()) &&
3119           !symbol->has<MiscDetails>() && useNames.count(name) == 0) {
3120         SourceName location{x.moduleName.source};
3121         if (auto *localSymbol{FindInScope(name)}) {
3122           DoAddUse(location, localSymbol->name(), *localSymbol, *symbol);
3123         } else {
3124           DoAddUse(location, location, CopySymbol(name, *symbol), *symbol);
3125         }
3126       }
3127     }
3128   }
3129   useModuleScope_ = nullptr;
3130 }
3131 
3132 ModuleVisitor::SymbolRename ModuleVisitor::AddUse(
3133     const SourceName &localName, const SourceName &useName) {
3134   return AddUse(localName, useName, FindInScope(*useModuleScope_, useName));
3135 }
3136 
3137 ModuleVisitor::SymbolRename ModuleVisitor::AddUse(
3138     const SourceName &localName, const SourceName &useName, Symbol *useSymbol) {
3139   if (!useModuleScope_) {
3140     return {}; // error occurred finding module
3141   }
3142   if (!useSymbol) {
3143     Say(useName, "'%s' not found in module '%s'"_err_en_US, MakeOpName(useName),
3144         useModuleScope_->GetName().value());
3145     return {};
3146   }
3147   if (useSymbol->attrs().test(Attr::PRIVATE) &&
3148       !FindModuleFileContaining(currScope())) {
3149     // Privacy is not enforced in module files so that generic interfaces
3150     // can be resolved to private specific procedures in specification
3151     // expressions.
3152     Say(useName, "'%s' is PRIVATE in '%s'"_err_en_US, MakeOpName(useName),
3153         useModuleScope_->GetName().value());
3154     return {};
3155   }
3156   auto &localSymbol{MakeSymbol(localName)};
3157   DoAddUse(useName, localName, localSymbol, *useSymbol);
3158   return {&localSymbol, useSymbol};
3159 }
3160 
3161 // symbol must be either a Use or a Generic formed by merging two uses.
3162 // Convert it to a UseError with this additional location.
3163 static bool ConvertToUseError(
3164     Symbol &symbol, const SourceName &location, const Scope &module) {
3165   if (auto *ued{symbol.detailsIf<UseErrorDetails>()}) {
3166     ued->add_occurrence(location, module);
3167     return true;
3168   }
3169   const auto *useDetails{symbol.detailsIf<UseDetails>()};
3170   if (!useDetails) {
3171     if (auto *genericDetails{symbol.detailsIf<GenericDetails>()}) {
3172       if (!genericDetails->uses().empty()) {
3173         useDetails = &genericDetails->uses().at(0)->get<UseDetails>();
3174       }
3175     }
3176   }
3177   if (useDetails) {
3178     symbol.set_details(
3179         UseErrorDetails{*useDetails}.add_occurrence(location, module));
3180     return true;
3181   } else {
3182     return false;
3183   }
3184 }
3185 
3186 void ModuleVisitor::DoAddUse(SourceName location, SourceName localName,
3187     Symbol &originalLocal, const Symbol &useSymbol) {
3188   Symbol *localSymbol{&originalLocal};
3189   if (auto *details{localSymbol->detailsIf<UseErrorDetails>()}) {
3190     details->add_occurrence(location, *useModuleScope_);
3191     return;
3192   }
3193   const Symbol &useUltimate{useSymbol.GetUltimate()};
3194   const auto *useGeneric{useUltimate.detailsIf<GenericDetails>()};
3195   if (localSymbol->has<UnknownDetails>()) {
3196     if (useGeneric &&
3197         ((useGeneric->specific() &&
3198              IsProcedurePointer(*useGeneric->specific())) ||
3199             (useGeneric->derivedType() &&
3200                 useUltimate.name() != localSymbol->name()))) {
3201       // We are use-associating a generic that either shadows a procedure
3202       // pointer or shadows a derived type with a distinct name.
3203       // Local references that might be made to the procedure pointer should
3204       // use a UseDetails symbol for proper data addressing, and a derived
3205       // type needs to be in scope with its local name.  So create an
3206       // empty local generic now into which the use-associated generic may
3207       // be copied.
3208       localSymbol->set_details(GenericDetails{});
3209       localSymbol->get<GenericDetails>().set_kind(useGeneric->kind());
3210     } else { // just create UseDetails
3211       localSymbol->set_details(UseDetails{localName, useSymbol});
3212       localSymbol->attrs() =
3213           useSymbol.attrs() & ~Attrs{Attr::PUBLIC, Attr::PRIVATE, Attr::SAVE};
3214       localSymbol->implicitAttrs() =
3215           localSymbol->attrs() & Attrs{Attr::ASYNCHRONOUS, Attr::VOLATILE};
3216       localSymbol->flags() = useSymbol.flags();
3217       return;
3218     }
3219   }
3220 
3221   Symbol &localUltimate{localSymbol->GetUltimate()};
3222   if (&localUltimate == &useUltimate) {
3223     // use-associating the same symbol again -- ok
3224     return;
3225   }
3226 
3227   // There are many possible combinations of symbol types that could arrive
3228   // with the same (local) name vie USE association from distinct modules.
3229   // Fortran allows a generic interface to share its name with a derived type,
3230   // or with the name of a non-generic procedure (which should be one of the
3231   // generic's specific procedures).  Implementing all these possibilities is
3232   // complicated.
3233   // Error cases are converted into UseErrorDetails symbols to trigger error
3234   // messages when/if bad combinations are actually used later in the program.
3235   // The error cases are:
3236   //   - two distinct derived types
3237   //   - two distinct non-generic procedures
3238   //   - a generic and a non-generic that is not already one of its specifics
3239   //   - anything other than a derived type, non-generic procedure, or
3240   //     generic procedure being combined with something other than an
3241   //     prior USE association of itself
3242   auto *localGeneric{localUltimate.detailsIf<GenericDetails>()};
3243   Symbol *localDerivedType{nullptr};
3244   if (localUltimate.has<DerivedTypeDetails>()) {
3245     localDerivedType = &localUltimate;
3246   } else if (localGeneric) {
3247     if (auto *dt{localGeneric->derivedType()};
3248         dt && !dt->attrs().test(Attr::PRIVATE)) {
3249       localDerivedType = dt;
3250     }
3251   }
3252   const Symbol *useDerivedType{nullptr};
3253   if (useUltimate.has<DerivedTypeDetails>()) {
3254     useDerivedType = &useUltimate;
3255   } else if (useGeneric) {
3256     if (const auto *dt{useGeneric->derivedType()};
3257         dt && !dt->attrs().test(Attr::PRIVATE)) {
3258       useDerivedType = dt;
3259     }
3260   }
3261 
3262   Symbol *localProcedure{nullptr};
3263   if (localGeneric) {
3264     if (localGeneric->specific() &&
3265         !localGeneric->specific()->attrs().test(Attr::PRIVATE)) {
3266       localProcedure = localGeneric->specific();
3267     }
3268   } else if (IsProcedure(localUltimate)) {
3269     localProcedure = &localUltimate;
3270   }
3271   const Symbol *useProcedure{nullptr};
3272   if (useGeneric) {
3273     if (useGeneric->specific() &&
3274         !useGeneric->specific()->attrs().test(Attr::PRIVATE)) {
3275       useProcedure = useGeneric->specific();
3276     }
3277   } else if (IsProcedure(useUltimate)) {
3278     useProcedure = &useUltimate;
3279   }
3280 
3281   // Creates a UseErrorDetails symbol in the current scope for a
3282   // current UseDetails symbol, but leaves the UseDetails in the
3283   // scope's name map.
3284   auto CreateLocalUseError{[&]() {
3285     EraseSymbol(*localSymbol);
3286     CHECK(localSymbol->has<UseDetails>());
3287     UseErrorDetails details{localSymbol->get<UseDetails>()};
3288     details.add_occurrence(location, *useModuleScope_);
3289     Symbol *newSymbol{&MakeSymbol(localName, Attrs{}, std::move(details))};
3290     // Restore *localSymbol in currScope
3291     auto iter{currScope().find(localName)};
3292     CHECK(iter != currScope().end() && &*iter->second == newSymbol);
3293     iter->second = MutableSymbolRef{*localSymbol};
3294     return newSymbol;
3295   }};
3296 
3297   // When two derived types arrived, try to combine them.
3298   const Symbol *combinedDerivedType{nullptr};
3299   if (!useDerivedType) {
3300     combinedDerivedType = localDerivedType;
3301   } else if (!localDerivedType) {
3302     if (useDerivedType->name() == localName) {
3303       combinedDerivedType = useDerivedType;
3304     } else {
3305       combinedDerivedType =
3306           &currScope().MakeSymbol(localSymbol->name(), useDerivedType->attrs(),
3307               UseDetails{localSymbol->name(), *useDerivedType});
3308     }
3309   } else if (&localDerivedType->GetUltimate() ==
3310       &useDerivedType->GetUltimate()) {
3311     combinedDerivedType = localDerivedType;
3312   } else {
3313     const Scope *localScope{localDerivedType->GetUltimate().scope()};
3314     const Scope *useScope{useDerivedType->GetUltimate().scope()};
3315     if (localScope && useScope && localScope->derivedTypeSpec() &&
3316         useScope->derivedTypeSpec() &&
3317         evaluate::AreSameDerivedType(
3318             *localScope->derivedTypeSpec(), *useScope->derivedTypeSpec())) {
3319       combinedDerivedType = localDerivedType;
3320     } else {
3321       // Create a local UseErrorDetails for the ambiguous derived type
3322       if (localGeneric) {
3323         combinedDerivedType = CreateLocalUseError();
3324       } else {
3325         ConvertToUseError(*localSymbol, location, *useModuleScope_);
3326         localDerivedType = nullptr;
3327         localGeneric = nullptr;
3328         combinedDerivedType = localSymbol;
3329       }
3330     }
3331     if (!localGeneric && !useGeneric) {
3332       return; // both symbols are derived types; done
3333     }
3334   }
3335 
3336   auto AreSameProcedure{[&](const Symbol &p1, const Symbol &p2) {
3337     if (&p1 == &p2) {
3338       return true;
3339     } else if (p1.name() != p2.name()) {
3340       return false;
3341     } else if (p1.attrs().test(Attr::INTRINSIC) ||
3342         p2.attrs().test(Attr::INTRINSIC)) {
3343       return p1.attrs().test(Attr::INTRINSIC) &&
3344           p2.attrs().test(Attr::INTRINSIC);
3345     } else if (!IsProcedure(p1) || !IsProcedure(p2)) {
3346       return false;
3347     } else if (IsPointer(p1) || IsPointer(p2)) {
3348       return false;
3349     } else if (const auto *subp{p1.detailsIf<SubprogramDetails>()};
3350                subp && !subp->isInterface()) {
3351       return false; // defined in module, not an external
3352     } else if (const auto *subp{p2.detailsIf<SubprogramDetails>()};
3353                subp && !subp->isInterface()) {
3354       return false; // defined in module, not an external
3355     } else {
3356       // Both are external interfaces, perhaps to the same procedure
3357       auto class1{ClassifyProcedure(p1)};
3358       auto class2{ClassifyProcedure(p2)};
3359       if (class1 == ProcedureDefinitionClass::External &&
3360           class2 == ProcedureDefinitionClass::External) {
3361         auto chars1{evaluate::characteristics::Procedure::Characterize(
3362             p1, GetFoldingContext())};
3363         auto chars2{evaluate::characteristics::Procedure::Characterize(
3364             p2, GetFoldingContext())};
3365         // same procedure interface defined identically in two modules?
3366         return chars1 && chars2 && *chars1 == *chars2;
3367       } else {
3368         return false;
3369       }
3370     }
3371   }};
3372 
3373   // When two non-generic procedures arrived, try to combine them.
3374   const Symbol *combinedProcedure{nullptr};
3375   if (!localProcedure) {
3376     combinedProcedure = useProcedure;
3377   } else if (!useProcedure) {
3378     combinedProcedure = localProcedure;
3379   } else {
3380     if (AreSameProcedure(
3381             localProcedure->GetUltimate(), useProcedure->GetUltimate())) {
3382       if (!localGeneric && !useGeneric) {
3383         return; // both symbols are non-generic procedures
3384       }
3385       combinedProcedure = localProcedure;
3386     }
3387   }
3388 
3389   // Prepare to merge generics
3390   bool cantCombine{false};
3391   if (localGeneric) {
3392     if (useGeneric || useDerivedType) {
3393     } else if (&useUltimate == &BypassGeneric(localUltimate).GetUltimate()) {
3394       return; // nothing to do; used subprogram is local's specific
3395     } else if (useUltimate.attrs().test(Attr::INTRINSIC) &&
3396         useUltimate.name() == localSymbol->name()) {
3397       return; // local generic can extend intrinsic
3398     } else {
3399       for (const auto &ref : localGeneric->specificProcs()) {
3400         if (&ref->GetUltimate() == &useUltimate) {
3401           return; // used non-generic is already a specific of local generic
3402         }
3403       }
3404       cantCombine = true;
3405     }
3406   } else if (useGeneric) {
3407     if (localDerivedType) {
3408     } else if (&localUltimate == &BypassGeneric(useUltimate).GetUltimate() ||
3409         (localSymbol->attrs().test(Attr::INTRINSIC) &&
3410             localUltimate.name() == useUltimate.name())) {
3411       // Local is the specific of the used generic or an intrinsic with the
3412       // same name; replace it.
3413       EraseSymbol(*localSymbol);
3414       Symbol &newSymbol{MakeSymbol(localName,
3415           useUltimate.attrs() & ~Attrs{Attr::PUBLIC, Attr::PRIVATE},
3416           UseDetails{localName, useUltimate})};
3417       newSymbol.flags() = useSymbol.flags();
3418       return;
3419     } else {
3420       for (const auto &ref : useGeneric->specificProcs()) {
3421         if (&ref->GetUltimate() == &localUltimate) {
3422           return; // local non-generic is already a specific of used generic
3423         }
3424       }
3425       cantCombine = true;
3426     }
3427   } else {
3428     cantCombine = true;
3429   }
3430 
3431   // If symbols are not combinable, create a use error.
3432   if (cantCombine) {
3433     if (!ConvertToUseError(*localSymbol, location, *useModuleScope_)) {
3434       Say(location,
3435           "Cannot use-associate '%s'; it is already declared in this scope"_err_en_US,
3436           localName)
3437           .Attach(localSymbol->name(), "Previous declaration of '%s'"_en_US,
3438               localName);
3439     }
3440     return;
3441   }
3442 
3443   // At this point, there must be at least one generic interface.
3444   CHECK(localGeneric || (useGeneric && (localDerivedType || localProcedure)));
3445 
3446   // Ensure that a use-associated specific procedure that is a procedure
3447   // pointer is properly represented as a USE association of an entity.
3448   if (IsProcedurePointer(useProcedure)) {
3449     Symbol &combined{currScope().MakeSymbol(localSymbol->name(),
3450         useProcedure->attrs(), UseDetails{localName, *useProcedure})};
3451     combined.flags() |= useProcedure->flags();
3452     combinedProcedure = &combined;
3453   }
3454 
3455   if (localGeneric) {
3456     // Create a local copy of a previously use-associated generic so that
3457     // it can be locally extended without corrupting the original.
3458     if (localSymbol->has<UseDetails>()) {
3459       GenericDetails generic;
3460       generic.CopyFrom(DEREF(localGeneric));
3461       EraseSymbol(*localSymbol);
3462       Symbol &newSymbol{MakeSymbol(
3463           localSymbol->name(), localSymbol->attrs(), std::move(generic))};
3464       newSymbol.flags() = localSymbol->flags();
3465       localGeneric = &newSymbol.get<GenericDetails>();
3466       localGeneric->AddUse(*localSymbol);
3467       localSymbol = &newSymbol;
3468     }
3469     if (useGeneric) {
3470       // Combine two use-associated generics
3471       localSymbol->attrs() =
3472           useSymbol.attrs() & ~Attrs{Attr::PUBLIC, Attr::PRIVATE};
3473       localSymbol->flags() = useSymbol.flags();
3474       AddGenericUse(*localGeneric, localName, useUltimate);
3475       localGeneric->clear_derivedType();
3476       localGeneric->CopyFrom(*useGeneric);
3477     }
3478     localGeneric->clear_derivedType();
3479     if (combinedDerivedType) {
3480       localGeneric->set_derivedType(*const_cast<Symbol *>(combinedDerivedType));
3481     }
3482     localGeneric->clear_specific();
3483     if (combinedProcedure) {
3484       localGeneric->set_specific(*const_cast<Symbol *>(combinedProcedure));
3485     }
3486   } else {
3487     CHECK(localSymbol->has<UseDetails>());
3488     // Create a local copy of the use-associated generic, then extend it
3489     // with the combined derived type &/or non-generic procedure.
3490     GenericDetails generic;
3491     generic.CopyFrom(*useGeneric);
3492     EraseSymbol(*localSymbol);
3493     Symbol &newSymbol{MakeSymbol(localName,
3494         useUltimate.attrs() & ~Attrs{Attr::PUBLIC, Attr::PRIVATE},
3495         std::move(generic))};
3496     newSymbol.flags() = useUltimate.flags();
3497     auto &newUseGeneric{newSymbol.get<GenericDetails>()};
3498     AddGenericUse(newUseGeneric, localName, useUltimate);
3499     newUseGeneric.AddUse(*localSymbol);
3500     if (combinedDerivedType) {
3501       if (const auto *oldDT{newUseGeneric.derivedType()}) {
3502         CHECK(&oldDT->GetUltimate() == &combinedDerivedType->GetUltimate());
3503       } else {
3504         newUseGeneric.set_derivedType(
3505             *const_cast<Symbol *>(combinedDerivedType));
3506       }
3507     }
3508     if (combinedProcedure) {
3509       newUseGeneric.set_specific(*const_cast<Symbol *>(combinedProcedure));
3510     }
3511   }
3512 }
3513 
3514 void ModuleVisitor::AddUse(const GenericSpecInfo &info) {
3515   if (useModuleScope_) {
3516     const auto &name{info.symbolName()};
3517     auto rename{AddUse(name, name, FindInScope(*useModuleScope_, name))};
3518     info.Resolve(rename.use);
3519   }
3520 }
3521 
3522 // Create a UseDetails symbol for this USE and add it to generic
3523 Symbol &ModuleVisitor::AddGenericUse(
3524     GenericDetails &generic, const SourceName &name, const Symbol &useSymbol) {
3525   Symbol &newSymbol{
3526       currScope().MakeSymbol(name, {}, UseDetails{name, useSymbol})};
3527   generic.AddUse(newSymbol);
3528   return newSymbol;
3529 }
3530 
3531 // Enforce F'2023 C1406 as a warning
3532 void ModuleVisitor::AddAndCheckModuleUse(SourceName name, bool isIntrinsic) {
3533   if (isIntrinsic) {
3534     if (auto iter{nonIntrinsicUses_.find(name)};
3535         iter != nonIntrinsicUses_.end()) {
3536       if (auto *msg{context().Warn(common::LanguageFeature::MiscUseExtensions,
3537               name,
3538               "Should not USE the intrinsic module '%s' in the same scope as a USE of the non-intrinsic module"_port_en_US,
3539               name)}) {
3540         msg->Attach(*iter, "Previous USE of '%s'"_en_US, *iter);
3541       }
3542     }
3543     intrinsicUses_.insert(name);
3544   } else {
3545     if (auto iter{intrinsicUses_.find(name)}; iter != intrinsicUses_.end()) {
3546       if (auto *msg{context().Warn(common::LanguageFeature::MiscUseExtensions,
3547               name,
3548               "Should not USE the non-intrinsic module '%s' in the same scope as a USE of the intrinsic module"_port_en_US,
3549               name)}) {
3550         msg->Attach(*iter, "Previous USE of '%s'"_en_US, *iter);
3551       }
3552     }
3553     nonIntrinsicUses_.insert(name);
3554   }
3555 }
3556 
3557 bool ModuleVisitor::BeginSubmodule(
3558     const parser::Name &name, const parser::ParentIdentifier &parentId) {
3559   const auto &ancestorName{std::get<parser::Name>(parentId.t)};
3560   Scope *parentScope{nullptr};
3561   Scope *ancestor{FindModule(ancestorName, false /*not intrinsic*/)};
3562   if (ancestor) {
3563     if (const auto &parentName{
3564             std::get<std::optional<parser::Name>>(parentId.t)}) {
3565       parentScope = FindModule(*parentName, false /*not intrinsic*/, ancestor);
3566     } else {
3567       parentScope = ancestor;
3568     }
3569   }
3570   if (parentScope) {
3571     PushScope(*parentScope);
3572   } else {
3573     // Error recovery: there's no ancestor scope, so create a dummy one to
3574     // hold the submodule's scope.
3575     SourceName dummyName{context().GetTempName(currScope())};
3576     Symbol &dummySymbol{MakeSymbol(dummyName, Attrs{}, ModuleDetails{false})};
3577     PushScope(Scope::Kind::Module, &dummySymbol);
3578     parentScope = &currScope();
3579   }
3580   BeginModule(name, true);
3581   set_inheritFromParent(false); // submodules don't inherit parents' implicits
3582   if (ancestor && !ancestor->AddSubmodule(name.source, currScope())) {
3583     Say(name, "Module '%s' already has a submodule named '%s'"_err_en_US,
3584         ancestorName.source, name.source);
3585   }
3586   return true;
3587 }
3588 
3589 void ModuleVisitor::BeginModule(const parser::Name &name, bool isSubmodule) {
3590   // Submodule symbols are not visible in their parents' scopes.
3591   Symbol &symbol{isSubmodule ? Resolve(name,
3592                                    currScope().MakeSymbol(name.source, Attrs{},
3593                                        ModuleDetails{true}))
3594                              : MakeSymbol(name, ModuleDetails{false})};
3595   auto &details{symbol.get<ModuleDetails>()};
3596   PushScope(Scope::Kind::Module, &symbol);
3597   details.set_scope(&currScope());
3598   prevAccessStmt_ = std::nullopt;
3599 }
3600 
3601 // Find a module or submodule by name and return its scope.
3602 // If ancestor is present, look for a submodule of that ancestor module.
3603 // May have to read a .mod file to find it.
3604 // If an error occurs, report it and return nullptr.
3605 Scope *ModuleVisitor::FindModule(const parser::Name &name,
3606     std::optional<bool> isIntrinsic, Scope *ancestor) {
3607   ModFileReader reader{context()};
3608   Scope *scope{
3609       reader.Read(name.source, isIntrinsic, ancestor, /*silent=*/false)};
3610   if (scope) {
3611     if (DoesScopeContain(scope, currScope())) { // 14.2.2(1)
3612       std::optional<SourceName> submoduleName;
3613       if (const Scope * container{FindModuleOrSubmoduleContaining(currScope())};
3614           container && container->IsSubmodule()) {
3615         submoduleName = container->GetName();
3616       }
3617       if (submoduleName) {
3618         Say(name.source,
3619             "Module '%s' cannot USE itself from its own submodule '%s'"_err_en_US,
3620             name.source, *submoduleName);
3621       } else {
3622         Say(name, "Module '%s' cannot USE itself"_err_en_US);
3623       }
3624     }
3625     Resolve(name, scope->symbol());
3626   }
3627   return scope;
3628 }
3629 
3630 void ModuleVisitor::ApplyDefaultAccess() {
3631   const auto *moduleDetails{
3632       DEREF(currScope().symbol()).detailsIf<ModuleDetails>()};
3633   CHECK(moduleDetails);
3634   Attr defaultAttr{
3635       DEREF(moduleDetails).isDefaultPrivate() ? Attr::PRIVATE : Attr::PUBLIC};
3636   for (auto &pair : currScope()) {
3637     Symbol &symbol{*pair.second};
3638     if (!symbol.attrs().HasAny({Attr::PUBLIC, Attr::PRIVATE})) {
3639       Attr attr{defaultAttr};
3640       if (auto *generic{symbol.detailsIf<GenericDetails>()}) {
3641         if (generic->derivedType()) {
3642           // If a generic interface has a derived type of the same
3643           // name that has an explicit accessibility attribute, then
3644           // the generic must have the same accessibility.
3645           if (generic->derivedType()->attrs().test(Attr::PUBLIC)) {
3646             attr = Attr::PUBLIC;
3647           } else if (generic->derivedType()->attrs().test(Attr::PRIVATE)) {
3648             attr = Attr::PRIVATE;
3649           }
3650         }
3651       }
3652       SetImplicitAttr(symbol, attr);
3653     }
3654   }
3655 }
3656 
3657 // InterfaceVistor implementation
3658 
3659 bool InterfaceVisitor::Pre(const parser::InterfaceStmt &x) {
3660   bool isAbstract{std::holds_alternative<parser::Abstract>(x.u)};
3661   genericInfo_.emplace(/*isInterface*/ true, isAbstract);
3662   return BeginAttrs();
3663 }
3664 
3665 void InterfaceVisitor::Post(const parser::InterfaceStmt &) { EndAttrs(); }
3666 
3667 void InterfaceVisitor::Post(const parser::EndInterfaceStmt &) {
3668   ResolveNewSpecifics();
3669   genericInfo_.pop();
3670 }
3671 
3672 // Create a symbol in genericSymbol_ for this GenericSpec.
3673 bool InterfaceVisitor::Pre(const parser::GenericSpec &x) {
3674   if (auto *symbol{FindInScope(GenericSpecInfo{x}.symbolName())}) {
3675     SetGenericSymbol(*symbol);
3676   }
3677   return false;
3678 }
3679 
3680 bool InterfaceVisitor::Pre(const parser::ProcedureStmt &x) {
3681   if (!isGeneric()) {
3682     Say("A PROCEDURE statement is only allowed in a generic interface block"_err_en_US);
3683   } else {
3684     auto kind{std::get<parser::ProcedureStmt::Kind>(x.t)};
3685     const auto &names{std::get<std::list<parser::Name>>(x.t)};
3686     AddSpecificProcs(names, kind);
3687   }
3688   return false;
3689 }
3690 
3691 bool InterfaceVisitor::Pre(const parser::GenericStmt &) {
3692   genericInfo_.emplace(/*isInterface*/ false);
3693   return BeginAttrs();
3694 }
3695 void InterfaceVisitor::Post(const parser::GenericStmt &x) {
3696   auto attrs{EndAttrs()};
3697   if (Symbol * symbol{GetGenericInfo().symbol}) {
3698     SetExplicitAttrs(*symbol, attrs);
3699   }
3700   const auto &names{std::get<std::list<parser::Name>>(x.t)};
3701   AddSpecificProcs(names, ProcedureKind::Procedure);
3702   ResolveNewSpecifics();
3703   genericInfo_.pop();
3704 }
3705 
3706 bool InterfaceVisitor::inInterfaceBlock() const {
3707   return !genericInfo_.empty() && GetGenericInfo().isInterface;
3708 }
3709 bool InterfaceVisitor::isGeneric() const {
3710   return !genericInfo_.empty() && GetGenericInfo().symbol;
3711 }
3712 bool InterfaceVisitor::isAbstract() const {
3713   return !genericInfo_.empty() && GetGenericInfo().isAbstract;
3714 }
3715 
3716 void InterfaceVisitor::AddSpecificProcs(
3717     const std::list<parser::Name> &names, ProcedureKind kind) {
3718   if (Symbol * symbol{GetGenericInfo().symbol};
3719       symbol && symbol->has<GenericDetails>()) {
3720     for (const auto &name : names) {
3721       specificsForGenericProcs_.emplace(symbol, std::make_pair(&name, kind));
3722       genericsForSpecificProcs_.emplace(name.source, symbol);
3723     }
3724   }
3725 }
3726 
3727 // By now we should have seen all specific procedures referenced by name in
3728 // this generic interface. Resolve those names to symbols.
3729 void GenericHandler::ResolveSpecificsInGeneric(
3730     Symbol &generic, bool isEndOfSpecificationPart) {
3731   auto &details{generic.get<GenericDetails>()};
3732   UnorderedSymbolSet symbolsSeen;
3733   for (const Symbol &symbol : details.specificProcs()) {
3734     symbolsSeen.insert(symbol.GetUltimate());
3735   }
3736   auto range{specificsForGenericProcs_.equal_range(&generic)};
3737   SpecificProcMapType retain;
3738   for (auto it{range.first}; it != range.second; ++it) {
3739     const parser::Name *name{it->second.first};
3740     auto kind{it->second.second};
3741     const Symbol *symbol{isEndOfSpecificationPart
3742             ? FindSymbol(*name)
3743             : FindInScope(generic.owner(), *name)};
3744     ProcedureDefinitionClass defClass{ProcedureDefinitionClass::None};
3745     const Symbol *specific{symbol};
3746     const Symbol *ultimate{nullptr};
3747     if (symbol) {
3748       // Subtlety: when *symbol is a use- or host-association, the specific
3749       // procedure that is recorded in the GenericDetails below must be *symbol,
3750       // not the specific procedure shadowed by a generic, because that specific
3751       // procedure may be a symbol from another module and its name unavailable
3752       // to emit to a module file.
3753       const Symbol &bypassed{BypassGeneric(*symbol)};
3754       if (symbol == &symbol->GetUltimate()) {
3755         specific = &bypassed;
3756       }
3757       ultimate = &bypassed.GetUltimate();
3758       defClass = ClassifyProcedure(*ultimate);
3759     }
3760     std::optional<MessageFixedText> error;
3761     if (defClass == ProcedureDefinitionClass::Module) {
3762       // ok
3763     } else if (kind == ProcedureKind::ModuleProcedure) {
3764       error = "'%s' is not a module procedure"_err_en_US;
3765     } else {
3766       switch (defClass) {
3767       case ProcedureDefinitionClass::Intrinsic:
3768       case ProcedureDefinitionClass::External:
3769       case ProcedureDefinitionClass::Internal:
3770       case ProcedureDefinitionClass::Dummy:
3771       case ProcedureDefinitionClass::Pointer:
3772         break;
3773       case ProcedureDefinitionClass::None:
3774         error = "'%s' is not a procedure"_err_en_US;
3775         break;
3776       default:
3777         error =
3778             "'%s' is not a procedure that can appear in a generic interface"_err_en_US;
3779         break;
3780       }
3781     }
3782     if (error) {
3783       if (isEndOfSpecificationPart) {
3784         Say(*name, std::move(*error));
3785       } else {
3786         // possible forward reference, catch it later
3787         retain.emplace(&generic, std::make_pair(name, kind));
3788       }
3789     } else if (!ultimate) {
3790     } else if (symbolsSeen.insert(*ultimate).second /*true if added*/) {
3791       // When a specific procedure is a USE association, that association
3792       // is saved in the generic's specifics, not its ultimate symbol,
3793       // so that module file output of interfaces can distinguish them.
3794       details.AddSpecificProc(*specific, name->source);
3795     } else if (specific == ultimate) {
3796       Say(name->source,
3797           "Procedure '%s' is already specified in generic '%s'"_err_en_US,
3798           name->source, MakeOpName(generic.name()));
3799     } else {
3800       Say(name->source,
3801           "Procedure '%s' from module '%s' is already specified in generic '%s'"_err_en_US,
3802           ultimate->name(), ultimate->owner().GetName().value(),
3803           MakeOpName(generic.name()));
3804     }
3805   }
3806   specificsForGenericProcs_.erase(range.first, range.second);
3807   specificsForGenericProcs_.merge(std::move(retain));
3808 }
3809 
3810 void GenericHandler::DeclaredPossibleSpecificProc(Symbol &proc) {
3811   auto range{genericsForSpecificProcs_.equal_range(proc.name())};
3812   for (auto iter{range.first}; iter != range.second; ++iter) {
3813     ResolveSpecificsInGeneric(*iter->second, false);
3814   }
3815 }
3816 
3817 void InterfaceVisitor::ResolveNewSpecifics() {
3818   if (Symbol * generic{genericInfo_.top().symbol};
3819       generic && generic->has<GenericDetails>()) {
3820     ResolveSpecificsInGeneric(*generic, false);
3821   }
3822 }
3823 
3824 // Mixed interfaces are allowed by the standard.
3825 // If there is a derived type with the same name, they must all be functions.
3826 void InterfaceVisitor::CheckGenericProcedures(Symbol &generic) {
3827   ResolveSpecificsInGeneric(generic, true);
3828   auto &details{generic.get<GenericDetails>()};
3829   if (auto *proc{details.CheckSpecific()}) {
3830     context().Warn(common::UsageWarning::HomonymousSpecific,
3831         proc->name().begin() > generic.name().begin() ? proc->name()
3832                                                       : generic.name(),
3833         "'%s' should not be the name of both a generic interface and a procedure unless it is a specific procedure of the generic"_warn_en_US,
3834         generic.name());
3835   }
3836   auto &specifics{details.specificProcs()};
3837   if (specifics.empty()) {
3838     if (details.derivedType()) {
3839       generic.set(Symbol::Flag::Function);
3840     }
3841     return;
3842   }
3843   const Symbol *function{nullptr};
3844   const Symbol *subroutine{nullptr};
3845   for (const Symbol &specific : specifics) {
3846     if (!function && specific.test(Symbol::Flag::Function)) {
3847       function = &specific;
3848     } else if (!subroutine && specific.test(Symbol::Flag::Subroutine)) {
3849       subroutine = &specific;
3850       if (details.derivedType() &&
3851           context().ShouldWarn(
3852               common::LanguageFeature::SubroutineAndFunctionSpecifics) &&
3853           !InModuleFile()) {
3854         SayDerivedType(generic.name(),
3855             "Generic interface '%s' should only contain functions due to derived type with same name"_warn_en_US,
3856             *details.derivedType()->GetUltimate().scope())
3857             .set_languageFeature(
3858                 common::LanguageFeature::SubroutineAndFunctionSpecifics);
3859       }
3860     }
3861     if (function && subroutine) { // F'2023 C1514
3862       if (auto *msg{context().Warn(
3863               common::LanguageFeature::SubroutineAndFunctionSpecifics,
3864               generic.name(),
3865               "Generic interface '%s' has both a function and a subroutine"_warn_en_US,
3866               generic.name())}) {
3867         msg->Attach(function->name(), "Function declaration"_en_US)
3868             .Attach(subroutine->name(), "Subroutine declaration"_en_US);
3869       }
3870       break;
3871     }
3872   }
3873   if (function && !subroutine) {
3874     generic.set(Symbol::Flag::Function);
3875   } else if (subroutine && !function) {
3876     generic.set(Symbol::Flag::Subroutine);
3877   }
3878 }
3879 
3880 // SubprogramVisitor implementation
3881 
3882 // Return false if it is actually an assignment statement.
3883 bool SubprogramVisitor::HandleStmtFunction(const parser::StmtFunctionStmt &x) {
3884   const auto &name{std::get<parser::Name>(x.t)};
3885   const DeclTypeSpec *resultType{nullptr};
3886   // Look up name: provides return type or tells us if it's an array
3887   if (auto *symbol{FindSymbol(name)}) {
3888     Symbol &ultimate{symbol->GetUltimate()};
3889     if (ultimate.has<ObjectEntityDetails>() ||
3890         ultimate.has<AssocEntityDetails>() ||
3891         CouldBeDataPointerValuedFunction(&ultimate) ||
3892         (&symbol->owner() == &currScope() && IsFunctionResult(*symbol))) {
3893       misparsedStmtFuncFound_ = true;
3894       return false;
3895     }
3896     if (IsHostAssociated(*symbol, currScope())) {
3897       context().Warn(common::LanguageFeature::StatementFunctionExtensions,
3898           name.source,
3899           "Name '%s' from host scope should have a type declaration before its local statement function definition"_port_en_US,
3900           name.source);
3901       MakeSymbol(name, Attrs{}, UnknownDetails{});
3902     } else if (auto *entity{ultimate.detailsIf<EntityDetails>()};
3903                entity && !ultimate.has<ProcEntityDetails>()) {
3904       resultType = entity->type();
3905       ultimate.details() = UnknownDetails{}; // will be replaced below
3906     } else {
3907       misparsedStmtFuncFound_ = true;
3908     }
3909   }
3910   if (misparsedStmtFuncFound_) {
3911     Say(name,
3912         "'%s' has not been declared as an array or pointer-valued function"_err_en_US);
3913     return false;
3914   }
3915   auto &symbol{PushSubprogramScope(name, Symbol::Flag::Function)};
3916   symbol.set(Symbol::Flag::StmtFunction);
3917   EraseSymbol(symbol); // removes symbol added by PushSubprogramScope
3918   auto &details{symbol.get<SubprogramDetails>()};
3919   for (const auto &dummyName : std::get<std::list<parser::Name>>(x.t)) {
3920     ObjectEntityDetails dummyDetails{true};
3921     if (auto *dummySymbol{FindInScope(currScope().parent(), dummyName)}) {
3922       if (auto *d{dummySymbol->GetType()}) {
3923         dummyDetails.set_type(*d);
3924       }
3925     }
3926     Symbol &dummy{MakeSymbol(dummyName, std::move(dummyDetails))};
3927     ApplyImplicitRules(dummy);
3928     details.add_dummyArg(dummy);
3929   }
3930   ObjectEntityDetails resultDetails;
3931   if (resultType) {
3932     resultDetails.set_type(*resultType);
3933   }
3934   resultDetails.set_funcResult(true);
3935   Symbol &result{MakeSymbol(name, std::move(resultDetails))};
3936   result.flags().set(Symbol::Flag::StmtFunction);
3937   ApplyImplicitRules(result);
3938   details.set_result(result);
3939   // The analysis of the expression that constitutes the body of the
3940   // statement function is deferred to FinishSpecificationPart() so that
3941   // all declarations and implicit typing are complete.
3942   PopScope();
3943   return true;
3944 }
3945 
3946 bool SubprogramVisitor::Pre(const parser::Suffix &suffix) {
3947   if (suffix.resultName) {
3948     if (IsFunction(currScope())) {
3949       if (FuncResultStack::FuncInfo * info{funcResultStack().Top()}) {
3950         if (info->inFunctionStmt) {
3951           info->resultName = &suffix.resultName.value();
3952         } else {
3953           // will check the result name in Post(EntryStmt)
3954         }
3955       }
3956     } else {
3957       Message &msg{Say(*suffix.resultName,
3958           "RESULT(%s) may appear only in a function"_err_en_US)};
3959       if (const Symbol * subprogram{InclusiveScope().symbol()}) {
3960         msg.Attach(subprogram->name(), "Containing subprogram"_en_US);
3961       }
3962     }
3963   }
3964   // LanguageBindingSpec deferred to Post(EntryStmt) or, for FunctionStmt,
3965   // all the way to EndSubprogram().
3966   return false;
3967 }
3968 
3969 bool SubprogramVisitor::Pre(const parser::PrefixSpec &x) {
3970   // Save this to process after UseStmt and ImplicitPart
3971   if (const auto *parsedType{std::get_if<parser::DeclarationTypeSpec>(&x.u)}) {
3972     if (FuncResultStack::FuncInfo * info{funcResultStack().Top()}) {
3973       if (info->parsedType) { // C1543
3974         Say(currStmtSource().value_or(info->source),
3975             "FUNCTION prefix cannot specify the type more than once"_err_en_US);
3976       } else {
3977         info->parsedType = parsedType;
3978         if (auto at{currStmtSource()}) {
3979           info->source = *at;
3980         }
3981       }
3982     } else {
3983       Say(currStmtSource().value(),
3984           "SUBROUTINE prefix cannot specify a type"_err_en_US);
3985     }
3986     return false;
3987   } else {
3988     return true;
3989   }
3990 }
3991 
3992 bool SubprogramVisitor::Pre(const parser::PrefixSpec::Attributes &attrs) {
3993   if (auto *subp{currScope().symbol()
3994               ? currScope().symbol()->detailsIf<SubprogramDetails>()
3995               : nullptr}) {
3996     for (auto attr : attrs.v) {
3997       if (auto current{subp->cudaSubprogramAttrs()}) {
3998         if (attr == *current ||
3999             (*current == common::CUDASubprogramAttrs::HostDevice &&
4000                 (attr == common::CUDASubprogramAttrs::Host ||
4001                     attr == common::CUDASubprogramAttrs::Device))) {
4002           context().Warn(common::LanguageFeature::RedundantAttribute,
4003               currStmtSource().value(),
4004               "ATTRIBUTES(%s) appears more than once"_warn_en_US,
4005               common::EnumToString(attr));
4006         } else if ((attr == common::CUDASubprogramAttrs::Host ||
4007                        attr == common::CUDASubprogramAttrs::Device) &&
4008             (*current == common::CUDASubprogramAttrs::Host ||
4009                 *current == common::CUDASubprogramAttrs::Device ||
4010                 *current == common::CUDASubprogramAttrs::HostDevice)) {
4011           // HOST,DEVICE or DEVICE,HOST -> HostDevice
4012           subp->set_cudaSubprogramAttrs(
4013               common::CUDASubprogramAttrs::HostDevice);
4014         } else {
4015           Say(currStmtSource().value(),
4016               "ATTRIBUTES(%s) conflicts with earlier ATTRIBUTES(%s)"_err_en_US,
4017               common::EnumToString(attr), common::EnumToString(*current));
4018         }
4019       } else {
4020         subp->set_cudaSubprogramAttrs(attr);
4021       }
4022     }
4023     if (auto attrs{subp->cudaSubprogramAttrs()}) {
4024       if (*attrs == common::CUDASubprogramAttrs::Global ||
4025           *attrs == common::CUDASubprogramAttrs::Device) {
4026         const Scope &scope{currScope()};
4027         const Scope *mod{FindModuleContaining(scope)};
4028         if (mod &&
4029             (mod->GetName().value() == "cudadevice" ||
4030                 mod->GetName().value() == "__cuda_device")) {
4031           return false;
4032         }
4033         // Implicitly USE the cudadevice module by copying its symbols in the
4034         // current scope.
4035         const Scope &cudaDeviceScope{context().GetCUDADeviceScope()};
4036         for (auto sym : cudaDeviceScope.GetSymbols()) {
4037           if (!currScope().FindSymbol(sym->name())) {
4038             auto &localSymbol{MakeSymbol(
4039                 sym->name(), Attrs{}, UseDetails{sym->name(), *sym})};
4040             localSymbol.flags() = sym->flags();
4041           }
4042         }
4043       }
4044     }
4045   }
4046   return false;
4047 }
4048 
4049 void SubprogramVisitor::Post(const parser::PrefixSpec::Launch_Bounds &x) {
4050   std::vector<std::int64_t> bounds;
4051   bool ok{true};
4052   for (const auto &sicx : x.v) {
4053     if (auto value{evaluate::ToInt64(EvaluateExpr(sicx))}) {
4054       bounds.push_back(*value);
4055     } else {
4056       ok = false;
4057     }
4058   }
4059   if (!ok || bounds.size() < 2 || bounds.size() > 3) {
4060     Say(currStmtSource().value(),
4061         "Operands of LAUNCH_BOUNDS() must be 2 or 3 integer constants"_err_en_US);
4062   } else if (auto *subp{currScope().symbol()
4063                      ? currScope().symbol()->detailsIf<SubprogramDetails>()
4064                      : nullptr}) {
4065     if (subp->cudaLaunchBounds().empty()) {
4066       subp->set_cudaLaunchBounds(std::move(bounds));
4067     } else {
4068       Say(currStmtSource().value(),
4069           "LAUNCH_BOUNDS() may only appear once"_err_en_US);
4070     }
4071   }
4072 }
4073 
4074 void SubprogramVisitor::Post(const parser::PrefixSpec::Cluster_Dims &x) {
4075   std::vector<std::int64_t> dims;
4076   bool ok{true};
4077   for (const auto &sicx : x.v) {
4078     if (auto value{evaluate::ToInt64(EvaluateExpr(sicx))}) {
4079       dims.push_back(*value);
4080     } else {
4081       ok = false;
4082     }
4083   }
4084   if (!ok || dims.size() != 3) {
4085     Say(currStmtSource().value(),
4086         "Operands of CLUSTER_DIMS() must be three integer constants"_err_en_US);
4087   } else if (auto *subp{currScope().symbol()
4088                      ? currScope().symbol()->detailsIf<SubprogramDetails>()
4089                      : nullptr}) {
4090     if (subp->cudaClusterDims().empty()) {
4091       subp->set_cudaClusterDims(std::move(dims));
4092     } else {
4093       Say(currStmtSource().value(),
4094           "CLUSTER_DIMS() may only appear once"_err_en_US);
4095     }
4096   }
4097 }
4098 
4099 static bool HasModulePrefix(const std::list<parser::PrefixSpec> &prefixes) {
4100   for (const auto &prefix : prefixes) {
4101     if (std::holds_alternative<parser::PrefixSpec::Module>(prefix.u)) {
4102       return true;
4103     }
4104   }
4105   return false;
4106 }
4107 
4108 bool SubprogramVisitor::Pre(const parser::InterfaceBody::Subroutine &x) {
4109   const auto &stmtTuple{
4110       std::get<parser::Statement<parser::SubroutineStmt>>(x.t).statement.t};
4111   return BeginSubprogram(std::get<parser::Name>(stmtTuple),
4112       Symbol::Flag::Subroutine,
4113       HasModulePrefix(std::get<std::list<parser::PrefixSpec>>(stmtTuple)));
4114 }
4115 void SubprogramVisitor::Post(const parser::InterfaceBody::Subroutine &x) {
4116   const auto &stmt{std::get<parser::Statement<parser::SubroutineStmt>>(x.t)};
4117   EndSubprogram(stmt.source,
4118       &std::get<std::optional<parser::LanguageBindingSpec>>(stmt.statement.t));
4119 }
4120 bool SubprogramVisitor::Pre(const parser::InterfaceBody::Function &x) {
4121   const auto &stmtTuple{
4122       std::get<parser::Statement<parser::FunctionStmt>>(x.t).statement.t};
4123   return BeginSubprogram(std::get<parser::Name>(stmtTuple),
4124       Symbol::Flag::Function,
4125       HasModulePrefix(std::get<std::list<parser::PrefixSpec>>(stmtTuple)));
4126 }
4127 void SubprogramVisitor::Post(const parser::InterfaceBody::Function &x) {
4128   const auto &stmt{std::get<parser::Statement<parser::FunctionStmt>>(x.t)};
4129   const auto &maybeSuffix{
4130       std::get<std::optional<parser::Suffix>>(stmt.statement.t)};
4131   EndSubprogram(stmt.source, maybeSuffix ? &maybeSuffix->binding : nullptr);
4132 }
4133 
4134 bool SubprogramVisitor::Pre(const parser::SubroutineStmt &stmt) {
4135   BeginAttrs();
4136   Walk(std::get<std::list<parser::PrefixSpec>>(stmt.t));
4137   Walk(std::get<parser::Name>(stmt.t));
4138   Walk(std::get<std::list<parser::DummyArg>>(stmt.t));
4139   // Don't traverse the LanguageBindingSpec now; it's deferred to EndSubprogram.
4140   Symbol &symbol{PostSubprogramStmt()};
4141   SubprogramDetails &details{symbol.get<SubprogramDetails>()};
4142   for (const auto &dummyArg : std::get<std::list<parser::DummyArg>>(stmt.t)) {
4143     if (const auto *dummyName{std::get_if<parser::Name>(&dummyArg.u)}) {
4144       CreateDummyArgument(details, *dummyName);
4145     } else {
4146       details.add_alternateReturn();
4147     }
4148   }
4149   return false;
4150 }
4151 bool SubprogramVisitor::Pre(const parser::FunctionStmt &) {
4152   FuncResultStack::FuncInfo &info{DEREF(funcResultStack().Top())};
4153   CHECK(!info.inFunctionStmt);
4154   info.inFunctionStmt = true;
4155   if (auto at{currStmtSource()}) {
4156     info.source = *at;
4157   }
4158   return BeginAttrs();
4159 }
4160 bool SubprogramVisitor::Pre(const parser::EntryStmt &) { return BeginAttrs(); }
4161 
4162 void SubprogramVisitor::Post(const parser::FunctionStmt &stmt) {
4163   const auto &name{std::get<parser::Name>(stmt.t)};
4164   Symbol &symbol{PostSubprogramStmt()};
4165   SubprogramDetails &details{symbol.get<SubprogramDetails>()};
4166   for (const auto &dummyName : std::get<std::list<parser::Name>>(stmt.t)) {
4167     CreateDummyArgument(details, dummyName);
4168   }
4169   const parser::Name *funcResultName;
4170   FuncResultStack::FuncInfo &info{DEREF(funcResultStack().Top())};
4171   CHECK(info.inFunctionStmt);
4172   info.inFunctionStmt = false;
4173   bool distinctResultName{
4174       info.resultName && info.resultName->source != name.source};
4175   if (distinctResultName) {
4176     // Note that RESULT is ignored if it has the same name as the function.
4177     // The symbol created by PushScope() is retained as a place-holder
4178     // for error detection.
4179     funcResultName = info.resultName;
4180   } else {
4181     EraseSymbol(name); // was added by PushScope()
4182     funcResultName = &name;
4183   }
4184   if (details.isFunction()) {
4185     CHECK(context().HasError(currScope().symbol()));
4186   } else {
4187     // RESULT(x) can be the same explicitly-named RESULT(x) as an ENTRY
4188     // statement.
4189     Symbol *result{nullptr};
4190     if (distinctResultName) {
4191       if (auto iter{currScope().find(funcResultName->source)};
4192           iter != currScope().end()) {
4193         Symbol &entryResult{*iter->second};
4194         if (IsFunctionResult(entryResult)) {
4195           result = &entryResult;
4196         }
4197       }
4198     }
4199     if (result) {
4200       Resolve(*funcResultName, *result);
4201     } else {
4202       // add function result to function scope
4203       EntityDetails funcResultDetails;
4204       funcResultDetails.set_funcResult(true);
4205       result = &MakeSymbol(*funcResultName, std::move(funcResultDetails));
4206     }
4207     info.resultSymbol = result;
4208     details.set_result(*result);
4209   }
4210   // C1560.
4211   if (info.resultName && !distinctResultName) {
4212     context().Warn(common::UsageWarning::HomonymousResult,
4213         info.resultName->source,
4214         "The function name should not appear in RESULT; references to '%s' "
4215         "inside the function will be considered as references to the "
4216         "result only"_warn_en_US,
4217         name.source);
4218     // RESULT name was ignored above, the only side effect from doing so will be
4219     // the inability to make recursive calls. The related parser::Name is still
4220     // resolved to the created function result symbol because every parser::Name
4221     // should be resolved to avoid internal errors.
4222     Resolve(*info.resultName, info.resultSymbol);
4223   }
4224   name.symbol = &symbol; // must not be function result symbol
4225   // Clear the RESULT() name now in case an ENTRY statement in the implicit-part
4226   // has a RESULT() suffix.
4227   info.resultName = nullptr;
4228 }
4229 
4230 Symbol &SubprogramVisitor::PostSubprogramStmt() {
4231   Symbol &symbol{*currScope().symbol()};
4232   SetExplicitAttrs(symbol, EndAttrs());
4233   if (symbol.attrs().test(Attr::MODULE)) {
4234     symbol.attrs().set(Attr::EXTERNAL, false);
4235     symbol.implicitAttrs().set(Attr::EXTERNAL, false);
4236   }
4237   return symbol;
4238 }
4239 
4240 void SubprogramVisitor::Post(const parser::EntryStmt &stmt) {
4241   if (const auto &suffix{std::get<std::optional<parser::Suffix>>(stmt.t)}) {
4242     Walk(suffix->binding);
4243   }
4244   PostEntryStmt(stmt);
4245   EndAttrs();
4246 }
4247 
4248 void SubprogramVisitor::CreateDummyArgument(
4249     SubprogramDetails &details, const parser::Name &name) {
4250   Symbol *dummy{FindInScope(name)};
4251   if (dummy) {
4252     if (IsDummy(*dummy)) {
4253       if (dummy->test(Symbol::Flag::EntryDummyArgument)) {
4254         dummy->set(Symbol::Flag::EntryDummyArgument, false);
4255       } else {
4256         Say(name,
4257             "'%s' appears more than once as a dummy argument name in this subprogram"_err_en_US,
4258             name.source);
4259         return;
4260       }
4261     } else {
4262       SayWithDecl(name, *dummy,
4263           "'%s' may not appear as a dummy argument name in this subprogram"_err_en_US);
4264       return;
4265     }
4266   } else {
4267     dummy = &MakeSymbol(name, EntityDetails{true});
4268   }
4269   details.add_dummyArg(DEREF(dummy));
4270 }
4271 
4272 void SubprogramVisitor::CreateEntry(
4273     const parser::EntryStmt &stmt, Symbol &subprogram) {
4274   const auto &entryName{std::get<parser::Name>(stmt.t)};
4275   Scope &outer{currScope().parent()};
4276   Symbol::Flag subpFlag{subprogram.test(Symbol::Flag::Function)
4277           ? Symbol::Flag::Function
4278           : Symbol::Flag::Subroutine};
4279   Attrs attrs;
4280   const auto &suffix{std::get<std::optional<parser::Suffix>>(stmt.t)};
4281   bool hasGlobalBindingName{outer.IsGlobal() && suffix && suffix->binding &&
4282       std::get<std::optional<parser::ScalarDefaultCharConstantExpr>>(
4283           suffix->binding->t)
4284           .has_value()};
4285   if (!hasGlobalBindingName) {
4286     if (Symbol * extant{FindSymbol(outer, entryName)}) {
4287       if (!HandlePreviousCalls(entryName, *extant, subpFlag)) {
4288         if (outer.IsTopLevel()) {
4289           Say2(entryName,
4290               "'%s' is already defined as a global identifier"_err_en_US,
4291               *extant, "Previous definition of '%s'"_en_US);
4292         } else {
4293           SayAlreadyDeclared(entryName, *extant);
4294         }
4295         return;
4296       }
4297       attrs = extant->attrs();
4298     }
4299   }
4300   std::optional<SourceName> distinctResultName;
4301   if (suffix && suffix->resultName &&
4302       suffix->resultName->source != entryName.source) {
4303     distinctResultName = suffix->resultName->source;
4304   }
4305   if (outer.IsModule() && !attrs.test(Attr::PRIVATE)) {
4306     attrs.set(Attr::PUBLIC);
4307   }
4308   Symbol *entrySymbol{nullptr};
4309   if (hasGlobalBindingName) {
4310     // Hide the entry's symbol in a new anonymous global scope so
4311     // that its name doesn't clash with anything.
4312     Symbol &symbol{MakeSymbol(outer, context().GetTempName(outer), Attrs{})};
4313     symbol.set_details(MiscDetails{MiscDetails::Kind::ScopeName});
4314     Scope &hidden{outer.MakeScope(Scope::Kind::Global, &symbol)};
4315     entrySymbol = &MakeSymbol(hidden, entryName.source, attrs);
4316   } else {
4317     entrySymbol = FindInScope(outer, entryName.source);
4318     if (entrySymbol) {
4319       if (auto *generic{entrySymbol->detailsIf<GenericDetails>()}) {
4320         if (auto *specific{generic->specific()}) {
4321           // Forward reference to ENTRY from a generic interface
4322           entrySymbol = specific;
4323           CheckDuplicatedAttrs(entryName.source, *entrySymbol, attrs);
4324           SetExplicitAttrs(*entrySymbol, attrs);
4325         }
4326       }
4327     } else {
4328       entrySymbol = &MakeSymbol(outer, entryName.source, attrs);
4329     }
4330   }
4331   SubprogramDetails entryDetails;
4332   entryDetails.set_entryScope(currScope());
4333   entrySymbol->set(subpFlag);
4334   if (subpFlag == Symbol::Flag::Function) {
4335     Symbol *result{nullptr};
4336     EntityDetails resultDetails;
4337     resultDetails.set_funcResult(true);
4338     if (distinctResultName) {
4339       // An explicit RESULT() can also be an explicit RESULT()
4340       // of the function or another ENTRY.
4341       if (auto iter{currScope().find(suffix->resultName->source)};
4342           iter != currScope().end()) {
4343         result = &*iter->second;
4344       }
4345       if (!result) {
4346         result =
4347             &MakeSymbol(*distinctResultName, Attrs{}, std::move(resultDetails));
4348       } else if (!result->has<EntityDetails>()) {
4349         Say(*distinctResultName,
4350             "ENTRY cannot have RESULT(%s) that is not a variable"_err_en_US,
4351             *distinctResultName)
4352             .Attach(result->name(), "Existing declaration of '%s'"_en_US,
4353                 result->name());
4354         result = nullptr;
4355       }
4356       if (result) {
4357         Resolve(*suffix->resultName, *result);
4358       }
4359     } else {
4360       result = &MakeSymbol(entryName.source, Attrs{}, std::move(resultDetails));
4361     }
4362     if (result) {
4363       entryDetails.set_result(*result);
4364     }
4365   }
4366   if (subpFlag == Symbol::Flag::Subroutine || distinctResultName) {
4367     Symbol &assoc{MakeSymbol(entryName.source)};
4368     assoc.set_details(HostAssocDetails{*entrySymbol});
4369     assoc.set(Symbol::Flag::Subroutine);
4370   }
4371   Resolve(entryName, *entrySymbol);
4372   std::set<SourceName> dummies;
4373   for (const auto &dummyArg : std::get<std::list<parser::DummyArg>>(stmt.t)) {
4374     if (const auto *dummyName{std::get_if<parser::Name>(&dummyArg.u)}) {
4375       auto pair{dummies.insert(dummyName->source)};
4376       if (!pair.second) {
4377         Say(*dummyName,
4378             "'%s' appears more than once as a dummy argument name in this ENTRY statement"_err_en_US,
4379             dummyName->source);
4380         continue;
4381       }
4382       Symbol *dummy{FindInScope(*dummyName)};
4383       if (dummy) {
4384         if (!IsDummy(*dummy)) {
4385           evaluate::AttachDeclaration(
4386               Say(*dummyName,
4387                   "'%s' may not appear as a dummy argument name in this ENTRY statement"_err_en_US,
4388                   dummyName->source),
4389               *dummy);
4390           continue;
4391         }
4392       } else {
4393         dummy = &MakeSymbol(*dummyName, EntityDetails{true});
4394         dummy->set(Symbol::Flag::EntryDummyArgument);
4395       }
4396       entryDetails.add_dummyArg(DEREF(dummy));
4397     } else if (subpFlag == Symbol::Flag::Function) { // C1573
4398       Say(entryName,
4399           "ENTRY in a function may not have an alternate return dummy argument"_err_en_US);
4400       break;
4401     } else {
4402       entryDetails.add_alternateReturn();
4403     }
4404   }
4405   entrySymbol->set_details(std::move(entryDetails));
4406 }
4407 
4408 void SubprogramVisitor::PostEntryStmt(const parser::EntryStmt &stmt) {
4409   // The entry symbol should have already been created and resolved
4410   // in CreateEntry(), called by BeginSubprogram(), with one exception (below).
4411   const auto &name{std::get<parser::Name>(stmt.t)};
4412   Scope &inclusiveScope{InclusiveScope()};
4413   if (!name.symbol) {
4414     if (inclusiveScope.kind() != Scope::Kind::Subprogram) {
4415       Say(name.source,
4416           "ENTRY '%s' may appear only in a subroutine or function"_err_en_US,
4417           name.source);
4418     } else if (FindSeparateModuleSubprogramInterface(inclusiveScope.symbol())) {
4419       Say(name.source,
4420           "ENTRY '%s' may not appear in a separate module procedure"_err_en_US,
4421           name.source);
4422     } else {
4423       // C1571 - entry is nested, so was not put into the program tree; error
4424       // is emitted from MiscChecker in semantics.cpp.
4425     }
4426     return;
4427   }
4428   Symbol &entrySymbol{*name.symbol};
4429   if (context().HasError(entrySymbol)) {
4430     return;
4431   }
4432   if (!entrySymbol.has<SubprogramDetails>()) {
4433     SayAlreadyDeclared(name, entrySymbol);
4434     return;
4435   }
4436   SubprogramDetails &entryDetails{entrySymbol.get<SubprogramDetails>()};
4437   CHECK(entryDetails.entryScope() == &inclusiveScope);
4438   SetCUDADataAttr(name.source, entrySymbol, cudaDataAttr());
4439   entrySymbol.attrs() |= GetAttrs();
4440   SetBindNameOn(entrySymbol);
4441   for (const auto &dummyArg : std::get<std::list<parser::DummyArg>>(stmt.t)) {
4442     if (const auto *dummyName{std::get_if<parser::Name>(&dummyArg.u)}) {
4443       if (Symbol * dummy{FindInScope(*dummyName)}) {
4444         if (dummy->test(Symbol::Flag::EntryDummyArgument)) {
4445           const auto *subp{dummy->detailsIf<SubprogramDetails>()};
4446           if (subp && subp->isInterface()) { // ok
4447           } else if (!dummy->has<EntityDetails>() &&
4448               !dummy->has<ObjectEntityDetails>() &&
4449               !dummy->has<ProcEntityDetails>()) {
4450             SayWithDecl(*dummyName, *dummy,
4451                 "ENTRY dummy argument '%s' was previously declared as an item that may not be used as a dummy argument"_err_en_US);
4452           }
4453           dummy->set(Symbol::Flag::EntryDummyArgument, false);
4454         }
4455       }
4456     }
4457   }
4458 }
4459 
4460 Symbol *ScopeHandler::FindSeparateModuleProcedureInterface(
4461     const parser::Name &name) {
4462   auto *symbol{FindSymbol(name)};
4463   if (symbol && symbol->has<SubprogramNameDetails>()) {
4464     const Scope *parent{nullptr};
4465     if (currScope().IsSubmodule()) {
4466       parent = currScope().symbol()->get<ModuleDetails>().parent();
4467     }
4468     symbol = parent ? FindSymbol(*parent, name) : nullptr;
4469   }
4470   if (symbol) {
4471     if (auto *generic{symbol->detailsIf<GenericDetails>()}) {
4472       symbol = generic->specific();
4473     }
4474   }
4475   if (const Symbol * defnIface{FindSeparateModuleSubprogramInterface(symbol)}) {
4476     // Error recovery in case of multiple definitions
4477     symbol = const_cast<Symbol *>(defnIface);
4478   }
4479   if (!IsSeparateModuleProcedureInterface(symbol)) {
4480     Say(name, "'%s' was not declared a separate module procedure"_err_en_US);
4481     symbol = nullptr;
4482   }
4483   return symbol;
4484 }
4485 
4486 // A subprogram declared with MODULE PROCEDURE
4487 bool SubprogramVisitor::BeginMpSubprogram(const parser::Name &name) {
4488   Symbol *symbol{FindSeparateModuleProcedureInterface(name)};
4489   if (!symbol) {
4490     return false;
4491   }
4492   if (symbol->owner() == currScope() && symbol->scope()) {
4493     // This is a MODULE PROCEDURE whose interface appears in its host.
4494     // Convert the module procedure's interface into a subprogram.
4495     SetScope(DEREF(symbol->scope()));
4496     symbol->get<SubprogramDetails>().set_isInterface(false);
4497     name.symbol = symbol;
4498   } else {
4499     // Copy the interface into a new subprogram scope.
4500     EraseSymbol(name);
4501     Symbol &newSymbol{MakeSymbol(name, SubprogramDetails{})};
4502     PushScope(Scope::Kind::Subprogram, &newSymbol);
4503     auto &newSubprogram{newSymbol.get<SubprogramDetails>()};
4504     newSubprogram.set_moduleInterface(*symbol);
4505     auto &subprogram{symbol->get<SubprogramDetails>()};
4506     if (const auto *name{subprogram.bindName()}) {
4507       newSubprogram.set_bindName(std::string{*name});
4508     }
4509     newSymbol.attrs() |= symbol->attrs();
4510     newSymbol.set(symbol->test(Symbol::Flag::Subroutine)
4511             ? Symbol::Flag::Subroutine
4512             : Symbol::Flag::Function);
4513     MapSubprogramToNewSymbols(*symbol, newSymbol, currScope());
4514   }
4515   return true;
4516 }
4517 
4518 // A subprogram or interface declared with SUBROUTINE or FUNCTION
4519 bool SubprogramVisitor::BeginSubprogram(const parser::Name &name,
4520     Symbol::Flag subpFlag, bool hasModulePrefix,
4521     const parser::LanguageBindingSpec *bindingSpec,
4522     const ProgramTree::EntryStmtList *entryStmts) {
4523   bool isValid{true};
4524   if (hasModulePrefix && !currScope().IsModule() &&
4525       !currScope().IsSubmodule()) { // C1547
4526     Say(name,
4527         "'%s' is a MODULE procedure which must be declared within a "
4528         "MODULE or SUBMODULE"_err_en_US);
4529     // Don't return here because it can be useful to have the scope set for
4530     // other semantic checks run before we print the errors
4531     isValid = false;
4532   }
4533   Symbol *moduleInterface{nullptr};
4534   if (isValid && hasModulePrefix && !inInterfaceBlock()) {
4535     moduleInterface = FindSeparateModuleProcedureInterface(name);
4536     if (moduleInterface && &moduleInterface->owner() == &currScope()) {
4537       // Subprogram is MODULE FUNCTION or MODULE SUBROUTINE with an interface
4538       // previously defined in the same scope.
4539       if (GenericDetails *
4540           generic{DEREF(FindSymbol(name)).detailsIf<GenericDetails>()}) {
4541         generic->clear_specific();
4542         name.symbol = nullptr;
4543       } else {
4544         EraseSymbol(name);
4545       }
4546     }
4547   }
4548   Symbol &newSymbol{
4549       PushSubprogramScope(name, subpFlag, bindingSpec, hasModulePrefix)};
4550   if (moduleInterface) {
4551     newSymbol.get<SubprogramDetails>().set_moduleInterface(*moduleInterface);
4552     if (moduleInterface->attrs().test(Attr::PRIVATE)) {
4553       SetImplicitAttr(newSymbol, Attr::PRIVATE);
4554     } else if (moduleInterface->attrs().test(Attr::PUBLIC)) {
4555       SetImplicitAttr(newSymbol, Attr::PUBLIC);
4556     }
4557   }
4558   if (entryStmts) {
4559     for (const auto &ref : *entryStmts) {
4560       CreateEntry(*ref, newSymbol);
4561     }
4562   }
4563   return true;
4564 }
4565 
4566 void SubprogramVisitor::HandleLanguageBinding(Symbol *symbol,
4567     std::optional<parser::CharBlock> stmtSource,
4568     const std::optional<parser::LanguageBindingSpec> *binding) {
4569   if (binding && *binding && symbol) {
4570     // Finally process the BIND(C,NAME=name) now that symbols in the name
4571     // expression will resolve to local names if needed.
4572     auto flagRestorer{common::ScopedSet(inSpecificationPart_, false)};
4573     auto originalStmtSource{messageHandler().currStmtSource()};
4574     messageHandler().set_currStmtSource(stmtSource);
4575     BeginAttrs();
4576     Walk(**binding);
4577     SetBindNameOn(*symbol);
4578     symbol->attrs() |= EndAttrs();
4579     messageHandler().set_currStmtSource(originalStmtSource);
4580   }
4581 }
4582 
4583 void SubprogramVisitor::EndSubprogram(
4584     std::optional<parser::CharBlock> stmtSource,
4585     const std::optional<parser::LanguageBindingSpec> *binding,
4586     const ProgramTree::EntryStmtList *entryStmts) {
4587   HandleLanguageBinding(currScope().symbol(), stmtSource, binding);
4588   if (entryStmts) {
4589     for (const auto &ref : *entryStmts) {
4590       const parser::EntryStmt &entryStmt{*ref};
4591       if (const auto &suffix{
4592               std::get<std::optional<parser::Suffix>>(entryStmt.t)}) {
4593         const auto &name{std::get<parser::Name>(entryStmt.t)};
4594         HandleLanguageBinding(name.symbol, name.source, &suffix->binding);
4595       }
4596     }
4597   }
4598   if (inInterfaceBlock() && currScope().symbol()) {
4599     DeclaredPossibleSpecificProc(*currScope().symbol());
4600   }
4601   PopScope();
4602 }
4603 
4604 bool SubprogramVisitor::HandlePreviousCalls(
4605     const parser::Name &name, Symbol &symbol, Symbol::Flag subpFlag) {
4606   // If the extant symbol is a generic, check its homonymous specific
4607   // procedure instead if it has one.
4608   if (auto *generic{symbol.detailsIf<GenericDetails>()}) {
4609     return generic->specific() &&
4610         HandlePreviousCalls(name, *generic->specific(), subpFlag);
4611   } else if (const auto *proc{symbol.detailsIf<ProcEntityDetails>()}; proc &&
4612              !proc->isDummy() &&
4613              !symbol.attrs().HasAny(Attrs{Attr::INTRINSIC, Attr::POINTER})) {
4614     // There's a symbol created for previous calls to this subprogram or
4615     // ENTRY's name.  We have to replace that symbol in situ to avoid the
4616     // obligation to rewrite symbol pointers in the parse tree.
4617     if (!symbol.test(subpFlag)) {
4618       auto other{subpFlag == Symbol::Flag::Subroutine
4619               ? Symbol::Flag::Function
4620               : Symbol::Flag::Subroutine};
4621       // External statements issue an explicit EXTERNAL attribute.
4622       if (symbol.attrs().test(Attr::EXTERNAL) &&
4623           !symbol.implicitAttrs().test(Attr::EXTERNAL)) {
4624         // Warn if external statement previously declared.
4625         context().Warn(common::LanguageFeature::RedundantAttribute, name.source,
4626             "EXTERNAL attribute was already specified on '%s'"_warn_en_US,
4627             name.source);
4628       } else if (symbol.test(other)) {
4629         Say2(name,
4630             subpFlag == Symbol::Flag::Function
4631                 ? "'%s' was previously called as a subroutine"_err_en_US
4632                 : "'%s' was previously called as a function"_err_en_US,
4633             symbol, "Previous call of '%s'"_en_US);
4634       } else {
4635         symbol.set(subpFlag);
4636       }
4637     }
4638     EntityDetails entity;
4639     if (proc->type()) {
4640       entity.set_type(*proc->type());
4641     }
4642     symbol.details() = std::move(entity);
4643     return true;
4644   } else {
4645     return symbol.has<UnknownDetails>() || symbol.has<SubprogramNameDetails>();
4646   }
4647 }
4648 
4649 void SubprogramVisitor::CheckExtantProc(
4650     const parser::Name &name, Symbol::Flag subpFlag) {
4651   if (auto *prev{FindSymbol(name)}) {
4652     if (IsDummy(*prev)) {
4653     } else if (auto *entity{prev->detailsIf<EntityDetails>()};
4654                IsPointer(*prev) && entity && !entity->type()) {
4655       // POINTER attribute set before interface
4656     } else if (inInterfaceBlock() && currScope() != prev->owner()) {
4657       // Procedures in an INTERFACE block do not resolve to symbols
4658       // in scopes between the global scope and the current scope.
4659     } else if (!HandlePreviousCalls(name, *prev, subpFlag)) {
4660       SayAlreadyDeclared(name, *prev);
4661     }
4662   }
4663 }
4664 
4665 Symbol &SubprogramVisitor::PushSubprogramScope(const parser::Name &name,
4666     Symbol::Flag subpFlag, const parser::LanguageBindingSpec *bindingSpec,
4667     bool hasModulePrefix) {
4668   Symbol *symbol{GetSpecificFromGeneric(name)};
4669   if (!symbol) {
4670     if (bindingSpec && currScope().IsGlobal() &&
4671         std::get<std::optional<parser::ScalarDefaultCharConstantExpr>>(
4672             bindingSpec->t)
4673             .has_value()) {
4674       // Create this new top-level subprogram with a binding label
4675       // in a new global scope, so that its symbol's name won't clash
4676       // with another symbol that has a distinct binding label.
4677       PushScope(Scope::Kind::Global,
4678           &MakeSymbol(context().GetTempName(currScope()), Attrs{},
4679               MiscDetails{MiscDetails::Kind::ScopeName}));
4680     }
4681     CheckExtantProc(name, subpFlag);
4682     symbol = &MakeSymbol(name, SubprogramDetails{});
4683   }
4684   symbol->ReplaceName(name.source);
4685   symbol->set(subpFlag);
4686   PushScope(Scope::Kind::Subprogram, symbol);
4687   if (subpFlag == Symbol::Flag::Function) {
4688     funcResultStack().Push(currScope(), name.source);
4689   }
4690   if (inInterfaceBlock()) {
4691     auto &details{symbol->get<SubprogramDetails>()};
4692     details.set_isInterface();
4693     if (isAbstract()) {
4694       SetExplicitAttr(*symbol, Attr::ABSTRACT);
4695     } else if (hasModulePrefix) {
4696       SetExplicitAttr(*symbol, Attr::MODULE);
4697     } else {
4698       MakeExternal(*symbol);
4699     }
4700     if (isGeneric()) {
4701       Symbol &genericSymbol{GetGenericSymbol()};
4702       if (auto *details{genericSymbol.detailsIf<GenericDetails>()}) {
4703         details->AddSpecificProc(*symbol, name.source);
4704       } else {
4705         CHECK(context().HasError(genericSymbol));
4706       }
4707     }
4708     set_inheritFromParent(false); // interfaces don't inherit, even if MODULE
4709   }
4710   if (Symbol * found{FindSymbol(name)};
4711       found && found->has<HostAssocDetails>()) {
4712     found->set(subpFlag); // PushScope() created symbol
4713   }
4714   return *symbol;
4715 }
4716 
4717 void SubprogramVisitor::PushBlockDataScope(const parser::Name &name) {
4718   if (auto *prev{FindSymbol(name)}) {
4719     if (prev->attrs().test(Attr::EXTERNAL) && prev->has<ProcEntityDetails>()) {
4720       if (prev->test(Symbol::Flag::Subroutine) ||
4721           prev->test(Symbol::Flag::Function)) {
4722         Say2(name, "BLOCK DATA '%s' has been called"_err_en_US, *prev,
4723             "Previous call of '%s'"_en_US);
4724       }
4725       EraseSymbol(name);
4726     }
4727   }
4728   if (name.source.empty()) {
4729     // Don't let unnamed BLOCK DATA conflict with unnamed PROGRAM
4730     PushScope(Scope::Kind::BlockData, nullptr);
4731   } else {
4732     PushScope(Scope::Kind::BlockData, &MakeSymbol(name, SubprogramDetails{}));
4733   }
4734 }
4735 
4736 // If name is a generic, return specific subprogram with the same name.
4737 Symbol *SubprogramVisitor::GetSpecificFromGeneric(const parser::Name &name) {
4738   // Search for the name but don't resolve it
4739   if (auto *symbol{currScope().FindSymbol(name.source)}) {
4740     if (symbol->has<SubprogramNameDetails>()) {
4741       if (inInterfaceBlock()) {
4742         // Subtle: clear any MODULE flag so that the new interface
4743         // symbol doesn't inherit it and ruin the ability to check it.
4744         symbol->attrs().reset(Attr::MODULE);
4745       }
4746     } else if (auto *details{symbol->detailsIf<GenericDetails>()}) {
4747       // found generic, want specific procedure
4748       auto *specific{details->specific()};
4749       Attrs moduleAttr;
4750       if (inInterfaceBlock()) {
4751         if (specific) {
4752           // Defining an interface in a generic of the same name which is
4753           // already shadowing another procedure.  In some cases, the shadowed
4754           // procedure is about to be replaced.
4755           if (specific->has<SubprogramNameDetails>() &&
4756               specific->attrs().test(Attr::MODULE)) {
4757             // The shadowed procedure is a separate module procedure that is
4758             // actually defined later in this (sub)module.
4759             // Define its interface now as a new symbol.
4760             moduleAttr.set(Attr::MODULE);
4761             specific = nullptr;
4762           } else if (&specific->owner() != &symbol->owner()) {
4763             // The shadowed procedure was from an enclosing scope and will be
4764             // overridden by this interface definition.
4765             specific = nullptr;
4766           }
4767           if (!specific) {
4768             details->clear_specific();
4769           }
4770         } else if (const auto *dType{details->derivedType()}) {
4771           if (&dType->owner() != &symbol->owner()) {
4772             // The shadowed derived type was from an enclosing scope and
4773             // will be overridden by this interface definition.
4774             details->clear_derivedType();
4775           }
4776         }
4777       }
4778       if (!specific) {
4779         specific = &currScope().MakeSymbol(
4780             name.source, std::move(moduleAttr), SubprogramDetails{});
4781         if (details->derivedType()) {
4782           // A specific procedure with the same name as a derived type
4783           SayAlreadyDeclared(name, *details->derivedType());
4784         } else {
4785           details->set_specific(Resolve(name, *specific));
4786         }
4787       } else if (isGeneric()) {
4788         SayAlreadyDeclared(name, *specific);
4789       }
4790       if (specific->has<SubprogramNameDetails>()) {
4791         specific->set_details(Details{SubprogramDetails{}});
4792       }
4793       return specific;
4794     }
4795   }
4796   return nullptr;
4797 }
4798 
4799 // DeclarationVisitor implementation
4800 
4801 bool DeclarationVisitor::BeginDecl() {
4802   BeginDeclTypeSpec();
4803   BeginArraySpec();
4804   return BeginAttrs();
4805 }
4806 void DeclarationVisitor::EndDecl() {
4807   EndDeclTypeSpec();
4808   EndArraySpec();
4809   EndAttrs();
4810 }
4811 
4812 bool DeclarationVisitor::CheckUseError(const parser::Name &name) {
4813   return HadUseError(context(), name.source, name.symbol);
4814 }
4815 
4816 // Report error if accessibility of symbol doesn't match isPrivate.
4817 void DeclarationVisitor::CheckAccessibility(
4818     const SourceName &name, bool isPrivate, Symbol &symbol) {
4819   if (symbol.attrs().test(Attr::PRIVATE) != isPrivate) {
4820     Say2(name,
4821         "'%s' does not have the same accessibility as its previous declaration"_err_en_US,
4822         symbol, "Previous declaration of '%s'"_en_US);
4823   }
4824 }
4825 
4826 bool DeclarationVisitor::Pre(const parser::TypeDeclarationStmt &x) {
4827   BeginDecl();
4828   // If INTRINSIC appears as an attr-spec, handle it now as if the
4829   // names had appeared on an INTRINSIC attribute statement beforehand.
4830   for (const auto &attr : std::get<std::list<parser::AttrSpec>>(x.t)) {
4831     if (std::holds_alternative<parser::Intrinsic>(attr.u)) {
4832       for (const auto &decl : std::get<std::list<parser::EntityDecl>>(x.t)) {
4833         DeclareIntrinsic(parser::GetFirstName(decl));
4834       }
4835       break;
4836     }
4837   }
4838   return true;
4839 }
4840 void DeclarationVisitor::Post(const parser::TypeDeclarationStmt &) {
4841   EndDecl();
4842 }
4843 
4844 void DeclarationVisitor::Post(const parser::DimensionStmt::Declaration &x) {
4845   DeclareObjectEntity(std::get<parser::Name>(x.t));
4846 }
4847 void DeclarationVisitor::Post(const parser::CodimensionDecl &x) {
4848   DeclareObjectEntity(std::get<parser::Name>(x.t));
4849 }
4850 
4851 bool DeclarationVisitor::Pre(const parser::Initialization &) {
4852   // Defer inspection of initializers to Initialization() so that the
4853   // symbol being initialized will be available within the initialization
4854   // expression.
4855   return false;
4856 }
4857 
4858 void DeclarationVisitor::Post(const parser::EntityDecl &x) {
4859   const auto &name{std::get<parser::ObjectName>(x.t)};
4860   Attrs attrs{attrs_ ? HandleSaveName(name.source, *attrs_) : Attrs{}};
4861   attrs.set(Attr::INTRINSIC, false); // dealt with in Pre(TypeDeclarationStmt)
4862   Symbol &symbol{DeclareUnknownEntity(name, attrs)};
4863   symbol.ReplaceName(name.source);
4864   SetCUDADataAttr(name.source, symbol, cudaDataAttr());
4865   if (const auto &init{std::get<std::optional<parser::Initialization>>(x.t)}) {
4866     ConvertToObjectEntity(symbol) || ConvertToProcEntity(symbol);
4867     symbol.set(
4868         Symbol::Flag::EntryDummyArgument, false); // forestall excessive errors
4869     Initialization(name, *init, false);
4870   } else if (attrs.test(Attr::PARAMETER)) { // C882, C883
4871     Say(name, "Missing initialization for parameter '%s'"_err_en_US);
4872   }
4873   if (auto *scopeSymbol{currScope().symbol()}) {
4874     if (auto *details{scopeSymbol->detailsIf<DerivedTypeDetails>()}) {
4875       if (details->isDECStructure()) {
4876         details->add_component(symbol);
4877       }
4878     }
4879   }
4880 }
4881 
4882 void DeclarationVisitor::Post(const parser::PointerDecl &x) {
4883   const auto &name{std::get<parser::Name>(x.t)};
4884   if (const auto &deferredShapeSpecs{
4885           std::get<std::optional<parser::DeferredShapeSpecList>>(x.t)}) {
4886     CHECK(arraySpec().empty());
4887     BeginArraySpec();
4888     set_arraySpec(AnalyzeDeferredShapeSpecList(context(), *deferredShapeSpecs));
4889     Symbol &symbol{DeclareObjectEntity(name, Attrs{Attr::POINTER})};
4890     symbol.ReplaceName(name.source);
4891     EndArraySpec();
4892   } else {
4893     if (const auto *symbol{FindInScope(name)}) {
4894       const auto *subp{symbol->detailsIf<SubprogramDetails>()};
4895       if (!symbol->has<UseDetails>() && // error caught elsewhere
4896           !symbol->has<ObjectEntityDetails>() &&
4897           !symbol->has<ProcEntityDetails>() &&
4898           !symbol->CanReplaceDetails(ObjectEntityDetails{}) &&
4899           !symbol->CanReplaceDetails(ProcEntityDetails{}) &&
4900           !(subp && subp->isInterface())) {
4901         Say(name, "'%s' cannot have the POINTER attribute"_err_en_US);
4902       }
4903     }
4904     HandleAttributeStmt(Attr::POINTER, std::get<parser::Name>(x.t));
4905   }
4906 }
4907 
4908 bool DeclarationVisitor::Pre(const parser::BindEntity &x) {
4909   auto kind{std::get<parser::BindEntity::Kind>(x.t)};
4910   auto &name{std::get<parser::Name>(x.t)};
4911   Symbol *symbol;
4912   if (kind == parser::BindEntity::Kind::Object) {
4913     symbol = &HandleAttributeStmt(Attr::BIND_C, name);
4914   } else {
4915     symbol = &MakeCommonBlockSymbol(name);
4916     SetExplicitAttr(*symbol, Attr::BIND_C);
4917   }
4918   // 8.6.4(1)
4919   // Some entities such as named constant or module name need to checked
4920   // elsewhere. This is to skip the ICE caused by setting Bind name for non-name
4921   // things such as data type and also checks for procedures.
4922   if (symbol->has<CommonBlockDetails>() || symbol->has<ObjectEntityDetails>() ||
4923       symbol->has<EntityDetails>()) {
4924     SetBindNameOn(*symbol);
4925   } else {
4926     Say(name,
4927         "Only variable and named common block can be in BIND statement"_err_en_US);
4928   }
4929   return false;
4930 }
4931 bool DeclarationVisitor::Pre(const parser::OldParameterStmt &x) {
4932   inOldStyleParameterStmt_ = true;
4933   Walk(x.v);
4934   inOldStyleParameterStmt_ = false;
4935   return false;
4936 }
4937 bool DeclarationVisitor::Pre(const parser::NamedConstantDef &x) {
4938   auto &name{std::get<parser::NamedConstant>(x.t).v};
4939   auto &symbol{HandleAttributeStmt(Attr::PARAMETER, name)};
4940   ConvertToObjectEntity(symbol);
4941   auto *details{symbol.detailsIf<ObjectEntityDetails>()};
4942   if (!details || symbol.test(Symbol::Flag::CrayPointer) ||
4943       symbol.test(Symbol::Flag::CrayPointee)) {
4944     SayWithDecl(
4945         name, symbol, "PARAMETER attribute not allowed on '%s'"_err_en_US);
4946     return false;
4947   }
4948   const auto &expr{std::get<parser::ConstantExpr>(x.t)};
4949   if (details->init() || symbol.test(Symbol::Flag::InDataStmt)) {
4950     Say(name, "Named constant '%s' already has a value"_err_en_US);
4951   }
4952   if (inOldStyleParameterStmt_) {
4953     // non-standard extension PARAMETER statement (no parentheses)
4954     Walk(expr);
4955     auto folded{EvaluateExpr(expr)};
4956     if (details->type()) {
4957       SayWithDecl(name, symbol,
4958           "Alternative style PARAMETER '%s' must not already have an explicit type"_err_en_US);
4959     } else if (folded) {
4960       auto at{expr.thing.value().source};
4961       if (evaluate::IsActuallyConstant(*folded)) {
4962         if (const auto *type{currScope().GetType(*folded)}) {
4963           if (type->IsPolymorphic()) {
4964             Say(at, "The expression must not be polymorphic"_err_en_US);
4965           } else if (auto shape{ToArraySpec(
4966                          GetFoldingContext(), evaluate::GetShape(*folded))}) {
4967             // The type of the named constant is assumed from the expression.
4968             details->set_type(*type);
4969             details->set_init(std::move(*folded));
4970             details->set_shape(std::move(*shape));
4971           } else {
4972             Say(at, "The expression must have constant shape"_err_en_US);
4973           }
4974         } else {
4975           Say(at, "The expression must have a known type"_err_en_US);
4976         }
4977       } else {
4978         Say(at, "The expression must be a constant of known type"_err_en_US);
4979       }
4980     }
4981   } else {
4982     // standard-conforming PARAMETER statement (with parentheses)
4983     ApplyImplicitRules(symbol);
4984     Walk(expr);
4985     if (auto converted{EvaluateNonPointerInitializer(
4986             symbol, expr, expr.thing.value().source)}) {
4987       details->set_init(std::move(*converted));
4988     }
4989   }
4990   return false;
4991 }
4992 bool DeclarationVisitor::Pre(const parser::NamedConstant &x) {
4993   const parser::Name &name{x.v};
4994   if (!FindSymbol(name)) {
4995     Say(name, "Named constant '%s' not found"_err_en_US);
4996   } else {
4997     CheckUseError(name);
4998   }
4999   return false;
5000 }
5001 
5002 bool DeclarationVisitor::Pre(const parser::Enumerator &enumerator) {
5003   const parser::Name &name{std::get<parser::NamedConstant>(enumerator.t).v};
5004   Symbol *symbol{FindInScope(name)};
5005   if (symbol && !symbol->has<UnknownDetails>()) {
5006     // Contrary to named constants appearing in a PARAMETER statement,
5007     // enumerator names should not have their type, dimension or any other
5008     // attributes defined before they are declared in the enumerator statement,
5009     // with the exception of accessibility.
5010     // This is not explicitly forbidden by the standard, but they are scalars
5011     // which type is left for the compiler to chose, so do not let users try to
5012     // tamper with that.
5013     SayAlreadyDeclared(name, *symbol);
5014     symbol = nullptr;
5015   } else {
5016     // Enumerators are treated as PARAMETER (section 7.6 paragraph (4))
5017     symbol = &MakeSymbol(name, Attrs{Attr::PARAMETER}, ObjectEntityDetails{});
5018     symbol->SetType(context().MakeNumericType(
5019         TypeCategory::Integer, evaluate::CInteger::kind));
5020   }
5021 
5022   if (auto &init{std::get<std::optional<parser::ScalarIntConstantExpr>>(
5023           enumerator.t)}) {
5024     Walk(*init); // Resolve names in expression before evaluation.
5025     if (auto value{EvaluateInt64(context(), *init)}) {
5026       // Cast all init expressions to C_INT so that they can then be
5027       // safely incremented (see 7.6 Note 2).
5028       enumerationState_.value = static_cast<int>(*value);
5029     } else {
5030       Say(name,
5031           "Enumerator value could not be computed "
5032           "from the given expression"_err_en_US);
5033       // Prevent resolution of next enumerators value
5034       enumerationState_.value = std::nullopt;
5035     }
5036   }
5037 
5038   if (symbol) {
5039     if (enumerationState_.value) {
5040       symbol->get<ObjectEntityDetails>().set_init(SomeExpr{
5041           evaluate::Expr<evaluate::CInteger>{*enumerationState_.value}});
5042     } else {
5043       context().SetError(*symbol);
5044     }
5045   }
5046 
5047   if (enumerationState_.value) {
5048     (*enumerationState_.value)++;
5049   }
5050   return false;
5051 }
5052 
5053 void DeclarationVisitor::Post(const parser::EnumDef &) {
5054   enumerationState_ = EnumeratorState{};
5055 }
5056 
5057 bool DeclarationVisitor::Pre(const parser::AccessSpec &x) {
5058   Attr attr{AccessSpecToAttr(x)};
5059   if (!NonDerivedTypeScope().IsModule()) { // C817
5060     Say(currStmtSource().value(),
5061         "%s attribute may only appear in the specification part of a module"_err_en_US,
5062         EnumToString(attr));
5063   }
5064   CheckAndSet(attr);
5065   return false;
5066 }
5067 
5068 bool DeclarationVisitor::Pre(const parser::AsynchronousStmt &x) {
5069   return HandleAttributeStmt(Attr::ASYNCHRONOUS, x.v);
5070 }
5071 bool DeclarationVisitor::Pre(const parser::ContiguousStmt &x) {
5072   return HandleAttributeStmt(Attr::CONTIGUOUS, x.v);
5073 }
5074 bool DeclarationVisitor::Pre(const parser::ExternalStmt &x) {
5075   HandleAttributeStmt(Attr::EXTERNAL, x.v);
5076   for (const auto &name : x.v) {
5077     auto *symbol{FindSymbol(name)};
5078     if (!ConvertToProcEntity(DEREF(symbol), name.source)) {
5079       // Check if previous symbol is an interface.
5080       if (auto *details{symbol->detailsIf<SubprogramDetails>()}) {
5081         if (details->isInterface()) {
5082           // Warn if interface previously declared.
5083           context().Warn(common::LanguageFeature::RedundantAttribute,
5084               name.source,
5085               "EXTERNAL attribute was already specified on '%s'"_warn_en_US,
5086               name.source);
5087         }
5088       } else {
5089         SayWithDecl(
5090             name, *symbol, "EXTERNAL attribute not allowed on '%s'"_err_en_US);
5091       }
5092     } else if (symbol->attrs().test(Attr::INTRINSIC)) { // C840
5093       Say(symbol->name(),
5094           "Symbol '%s' cannot have both INTRINSIC and EXTERNAL attributes"_err_en_US,
5095           symbol->name());
5096     }
5097   }
5098   return false;
5099 }
5100 bool DeclarationVisitor::Pre(const parser::IntentStmt &x) {
5101   auto &intentSpec{std::get<parser::IntentSpec>(x.t)};
5102   auto &names{std::get<std::list<parser::Name>>(x.t)};
5103   return CheckNotInBlock("INTENT") && // C1107
5104       HandleAttributeStmt(IntentSpecToAttr(intentSpec), names);
5105 }
5106 bool DeclarationVisitor::Pre(const parser::IntrinsicStmt &x) {
5107   for (const auto &name : x.v) {
5108     DeclareIntrinsic(name);
5109   }
5110   return false;
5111 }
5112 void DeclarationVisitor::DeclareIntrinsic(const parser::Name &name) {
5113   HandleAttributeStmt(Attr::INTRINSIC, name);
5114   if (!IsIntrinsic(name.source, std::nullopt)) {
5115     Say(name.source, "'%s' is not a known intrinsic procedure"_err_en_US);
5116   }
5117   auto &symbol{DEREF(FindSymbol(name))};
5118   if (symbol.has<GenericDetails>()) {
5119     // Generic interface is extending intrinsic; ok
5120   } else if (!ConvertToProcEntity(symbol, name.source)) {
5121     SayWithDecl(
5122         name, symbol, "INTRINSIC attribute not allowed on '%s'"_err_en_US);
5123   } else if (symbol.attrs().test(Attr::EXTERNAL)) { // C840
5124     Say(symbol.name(),
5125         "Symbol '%s' cannot have both EXTERNAL and INTRINSIC attributes"_err_en_US,
5126         symbol.name());
5127   } else {
5128     if (symbol.GetType()) {
5129       // These warnings are worded so that they should make sense in either
5130       // order.
5131       if (auto *msg{context().Warn(
5132               common::UsageWarning::IgnoredIntrinsicFunctionType, symbol.name(),
5133               "Explicit type declaration ignored for intrinsic function '%s'"_warn_en_US,
5134               symbol.name())}) {
5135         msg->Attach(name.source,
5136             "INTRINSIC statement for explicitly-typed '%s'"_en_US, name.source);
5137       }
5138     }
5139     if (!symbol.test(Symbol::Flag::Function) &&
5140         !symbol.test(Symbol::Flag::Subroutine)) {
5141       if (context().intrinsics().IsIntrinsicFunction(name.source.ToString())) {
5142         symbol.set(Symbol::Flag::Function);
5143       } else if (context().intrinsics().IsIntrinsicSubroutine(
5144                      name.source.ToString())) {
5145         symbol.set(Symbol::Flag::Subroutine);
5146       }
5147     }
5148   }
5149 }
5150 bool DeclarationVisitor::Pre(const parser::OptionalStmt &x) {
5151   return CheckNotInBlock("OPTIONAL") && // C1107
5152       HandleAttributeStmt(Attr::OPTIONAL, x.v);
5153 }
5154 bool DeclarationVisitor::Pre(const parser::ProtectedStmt &x) {
5155   return HandleAttributeStmt(Attr::PROTECTED, x.v);
5156 }
5157 bool DeclarationVisitor::Pre(const parser::ValueStmt &x) {
5158   return CheckNotInBlock("VALUE") && // C1107
5159       HandleAttributeStmt(Attr::VALUE, x.v);
5160 }
5161 bool DeclarationVisitor::Pre(const parser::VolatileStmt &x) {
5162   return HandleAttributeStmt(Attr::VOLATILE, x.v);
5163 }
5164 bool DeclarationVisitor::Pre(const parser::CUDAAttributesStmt &x) {
5165   auto attr{std::get<common::CUDADataAttr>(x.t)};
5166   for (const auto &name : std::get<std::list<parser::Name>>(x.t)) {
5167     auto *symbol{FindInScope(name)};
5168     if (symbol && symbol->has<UseDetails>()) {
5169       Say(currStmtSource().value(),
5170           "Cannot apply CUDA data attribute to use-associated '%s'"_err_en_US,
5171           name.source);
5172     } else {
5173       if (!symbol) {
5174         symbol = &MakeSymbol(name, ObjectEntityDetails{});
5175       }
5176       SetCUDADataAttr(name.source, *symbol, attr);
5177     }
5178   }
5179   return false;
5180 }
5181 // Handle a statement that sets an attribute on a list of names.
5182 bool DeclarationVisitor::HandleAttributeStmt(
5183     Attr attr, const std::list<parser::Name> &names) {
5184   for (const auto &name : names) {
5185     HandleAttributeStmt(attr, name);
5186   }
5187   return false;
5188 }
5189 Symbol &DeclarationVisitor::HandleAttributeStmt(
5190     Attr attr, const parser::Name &name) {
5191   auto *symbol{FindInScope(name)};
5192   if (attr == Attr::ASYNCHRONOUS || attr == Attr::VOLATILE) {
5193     // these can be set on a symbol that is host-assoc or use-assoc
5194     if (!symbol &&
5195         (currScope().kind() == Scope::Kind::Subprogram ||
5196             currScope().kind() == Scope::Kind::BlockConstruct)) {
5197       if (auto *hostSymbol{FindSymbol(name)}) {
5198         symbol = &MakeHostAssocSymbol(name, *hostSymbol);
5199       }
5200     }
5201   } else if (symbol && symbol->has<UseDetails>()) {
5202     if (symbol->GetUltimate().attrs().test(attr)) {
5203       context().Warn(common::LanguageFeature::RedundantAttribute,
5204           currStmtSource().value(),
5205           "Use-associated '%s' already has '%s' attribute"_warn_en_US,
5206           name.source, EnumToString(attr));
5207     } else {
5208       Say(currStmtSource().value(),
5209           "Cannot change %s attribute on use-associated '%s'"_err_en_US,
5210           EnumToString(attr), name.source);
5211     }
5212     return *symbol;
5213   }
5214   if (!symbol) {
5215     symbol = &MakeSymbol(name, EntityDetails{});
5216   }
5217   if (CheckDuplicatedAttr(name.source, *symbol, attr)) {
5218     HandleSaveName(name.source, Attrs{attr});
5219     SetExplicitAttr(*symbol, attr);
5220   }
5221   return *symbol;
5222 }
5223 // C1107
5224 bool DeclarationVisitor::CheckNotInBlock(const char *stmt) {
5225   if (currScope().kind() == Scope::Kind::BlockConstruct) {
5226     Say(MessageFormattedText{
5227         "%s statement is not allowed in a BLOCK construct"_err_en_US, stmt});
5228     return false;
5229   } else {
5230     return true;
5231   }
5232 }
5233 
5234 void DeclarationVisitor::Post(const parser::ObjectDecl &x) {
5235   CHECK(objectDeclAttr_);
5236   const auto &name{std::get<parser::ObjectName>(x.t)};
5237   DeclareObjectEntity(name, Attrs{*objectDeclAttr_});
5238 }
5239 
5240 // Declare an entity not yet known to be an object or proc.
5241 Symbol &DeclarationVisitor::DeclareUnknownEntity(
5242     const parser::Name &name, Attrs attrs) {
5243   if (!arraySpec().empty() || !coarraySpec().empty()) {
5244     return DeclareObjectEntity(name, attrs);
5245   } else {
5246     Symbol &symbol{DeclareEntity<EntityDetails>(name, attrs)};
5247     if (auto *type{GetDeclTypeSpec()}) {
5248       SetType(name, *type);
5249     }
5250     charInfo_.length.reset();
5251     if (symbol.attrs().test(Attr::EXTERNAL)) {
5252       ConvertToProcEntity(symbol);
5253     } else if (symbol.attrs().HasAny(Attrs{Attr::ALLOCATABLE,
5254                    Attr::ASYNCHRONOUS, Attr::CONTIGUOUS, Attr::PARAMETER,
5255                    Attr::SAVE, Attr::TARGET, Attr::VALUE, Attr::VOLATILE})) {
5256       ConvertToObjectEntity(symbol);
5257     }
5258     if (attrs.test(Attr::BIND_C)) {
5259       SetBindNameOn(symbol);
5260     }
5261     return symbol;
5262   }
5263 }
5264 
5265 bool DeclarationVisitor::HasCycle(
5266     const Symbol &procSymbol, const Symbol *interface) {
5267   SourceOrderedSymbolSet procsInCycle;
5268   procsInCycle.insert(procSymbol);
5269   while (interface) {
5270     if (procsInCycle.count(*interface) > 0) {
5271       for (const auto &procInCycle : procsInCycle) {
5272         Say(procInCycle->name(),
5273             "The interface for procedure '%s' is recursively defined"_err_en_US,
5274             procInCycle->name());
5275         context().SetError(*procInCycle);
5276       }
5277       return true;
5278     } else if (const auto *procDetails{
5279                    interface->detailsIf<ProcEntityDetails>()}) {
5280       procsInCycle.insert(*interface);
5281       interface = procDetails->procInterface();
5282     } else {
5283       break;
5284     }
5285   }
5286   return false;
5287 }
5288 
5289 Symbol &DeclarationVisitor::DeclareProcEntity(
5290     const parser::Name &name, Attrs attrs, const Symbol *interface) {
5291   Symbol *proc{nullptr};
5292   if (auto *extant{FindInScope(name)}) {
5293     if (auto *d{extant->detailsIf<GenericDetails>()}; d && !d->derivedType()) {
5294       // procedure pointer with same name as a generic
5295       if (auto *specific{d->specific()}) {
5296         SayAlreadyDeclared(name, *specific);
5297       } else {
5298         // Create the ProcEntityDetails symbol in the scope as the "specific()"
5299         // symbol behind an existing GenericDetails symbol of the same name.
5300         proc = &Resolve(name,
5301             currScope().MakeSymbol(name.source, attrs, ProcEntityDetails{}));
5302         d->set_specific(*proc);
5303       }
5304     }
5305   }
5306   Symbol &symbol{proc ? *proc : DeclareEntity<ProcEntityDetails>(name, attrs)};
5307   if (auto *details{symbol.detailsIf<ProcEntityDetails>()}) {
5308     if (context().HasError(symbol)) {
5309     } else if (HasCycle(symbol, interface)) {
5310       return symbol;
5311     } else if (interface && (details->procInterface() || details->type())) {
5312       SayWithDecl(name, symbol,
5313           "The interface for procedure '%s' has already been declared"_err_en_US);
5314       context().SetError(symbol);
5315     } else if (interface) {
5316       details->set_procInterfaces(
5317           *interface, BypassGeneric(interface->GetUltimate()));
5318       if (interface->test(Symbol::Flag::Function)) {
5319         symbol.set(Symbol::Flag::Function);
5320       } else if (interface->test(Symbol::Flag::Subroutine)) {
5321         symbol.set(Symbol::Flag::Subroutine);
5322       }
5323     } else if (auto *type{GetDeclTypeSpec()}) {
5324       SetType(name, *type);
5325       symbol.set(Symbol::Flag::Function);
5326     }
5327     SetBindNameOn(symbol);
5328     SetPassNameOn(symbol);
5329   }
5330   return symbol;
5331 }
5332 
5333 Symbol &DeclarationVisitor::DeclareObjectEntity(
5334     const parser::Name &name, Attrs attrs) {
5335   Symbol &symbol{DeclareEntity<ObjectEntityDetails>(name, attrs)};
5336   if (auto *details{symbol.detailsIf<ObjectEntityDetails>()}) {
5337     if (auto *type{GetDeclTypeSpec()}) {
5338       SetType(name, *type);
5339     }
5340     if (!arraySpec().empty()) {
5341       if (details->IsArray()) {
5342         if (!context().HasError(symbol)) {
5343           Say(name,
5344               "The dimensions of '%s' have already been declared"_err_en_US);
5345           context().SetError(symbol);
5346         }
5347       } else if (MustBeScalar(symbol)) {
5348         context().Warn(common::UsageWarning::PreviousScalarUse, name.source,
5349             "'%s' appeared earlier as a scalar actual argument to a specification function"_warn_en_US,
5350             name.source);
5351       } else if (details->init() || symbol.test(Symbol::Flag::InDataStmt)) {
5352         Say(name, "'%s' was initialized earlier as a scalar"_err_en_US);
5353       } else {
5354         details->set_shape(arraySpec());
5355       }
5356     }
5357     if (!coarraySpec().empty()) {
5358       if (details->IsCoarray()) {
5359         if (!context().HasError(symbol)) {
5360           Say(name,
5361               "The codimensions of '%s' have already been declared"_err_en_US);
5362           context().SetError(symbol);
5363         }
5364       } else {
5365         details->set_coshape(coarraySpec());
5366       }
5367     }
5368     SetBindNameOn(symbol);
5369   }
5370   ClearArraySpec();
5371   ClearCoarraySpec();
5372   charInfo_.length.reset();
5373   return symbol;
5374 }
5375 
5376 void DeclarationVisitor::Post(const parser::IntegerTypeSpec &x) {
5377   if (!isVectorType_) {
5378     SetDeclTypeSpec(MakeNumericType(TypeCategory::Integer, x.v));
5379   }
5380 }
5381 void DeclarationVisitor::Post(const parser::UnsignedTypeSpec &x) {
5382   if (!isVectorType_) {
5383     if (!context().IsEnabled(common::LanguageFeature::Unsigned) &&
5384         !context().AnyFatalError()) {
5385       context().Say("-funsigned is required to enable UNSIGNED type"_err_en_US);
5386     }
5387     SetDeclTypeSpec(MakeNumericType(TypeCategory::Unsigned, x.v));
5388   }
5389 }
5390 void DeclarationVisitor::Post(const parser::IntrinsicTypeSpec::Real &x) {
5391   if (!isVectorType_) {
5392     SetDeclTypeSpec(MakeNumericType(TypeCategory::Real, x.kind));
5393   }
5394 }
5395 void DeclarationVisitor::Post(const parser::IntrinsicTypeSpec::Complex &x) {
5396   SetDeclTypeSpec(MakeNumericType(TypeCategory::Complex, x.kind));
5397 }
5398 void DeclarationVisitor::Post(const parser::IntrinsicTypeSpec::Logical &x) {
5399   SetDeclTypeSpec(MakeLogicalType(x.kind));
5400 }
5401 void DeclarationVisitor::Post(const parser::IntrinsicTypeSpec::Character &) {
5402   if (!charInfo_.length) {
5403     charInfo_.length = ParamValue{1, common::TypeParamAttr::Len};
5404   }
5405   if (!charInfo_.kind) {
5406     charInfo_.kind =
5407         KindExpr{context().GetDefaultKind(TypeCategory::Character)};
5408   }
5409   SetDeclTypeSpec(currScope().MakeCharacterType(
5410       std::move(*charInfo_.length), std::move(*charInfo_.kind)));
5411   charInfo_ = {};
5412 }
5413 void DeclarationVisitor::Post(const parser::CharSelector::LengthAndKind &x) {
5414   charInfo_.kind = EvaluateSubscriptIntExpr(x.kind);
5415   std::optional<std::int64_t> intKind{ToInt64(charInfo_.kind)};
5416   if (intKind &&
5417       !context().targetCharacteristics().IsTypeEnabled(
5418           TypeCategory::Character, *intKind)) { // C715, C719
5419     Say(currStmtSource().value(),
5420         "KIND value (%jd) not valid for CHARACTER"_err_en_US, *intKind);
5421     charInfo_.kind = std::nullopt; // prevent further errors
5422   }
5423   if (x.length) {
5424     charInfo_.length = GetParamValue(*x.length, common::TypeParamAttr::Len);
5425   }
5426 }
5427 void DeclarationVisitor::Post(const parser::CharLength &x) {
5428   if (const auto *length{std::get_if<std::uint64_t>(&x.u)}) {
5429     charInfo_.length = ParamValue{
5430         static_cast<ConstantSubscript>(*length), common::TypeParamAttr::Len};
5431   } else {
5432     charInfo_.length = GetParamValue(
5433         std::get<parser::TypeParamValue>(x.u), common::TypeParamAttr::Len);
5434   }
5435 }
5436 void DeclarationVisitor::Post(const parser::LengthSelector &x) {
5437   if (const auto *param{std::get_if<parser::TypeParamValue>(&x.u)}) {
5438     charInfo_.length = GetParamValue(*param, common::TypeParamAttr::Len);
5439   }
5440 }
5441 
5442 bool DeclarationVisitor::Pre(const parser::KindParam &x) {
5443   if (const auto *kind{std::get_if<
5444           parser::Scalar<parser::Integer<parser::Constant<parser::Name>>>>(
5445           &x.u)}) {
5446     const parser::Name &name{kind->thing.thing.thing};
5447     if (!FindSymbol(name)) {
5448       Say(name, "Parameter '%s' not found"_err_en_US);
5449     }
5450   }
5451   return false;
5452 }
5453 
5454 int DeclarationVisitor::GetVectorElementKind(
5455     TypeCategory category, const std::optional<parser::KindSelector> &kind) {
5456   KindExpr value{GetKindParamExpr(category, kind)};
5457   if (auto known{evaluate::ToInt64(value)}) {
5458     return static_cast<int>(*known);
5459   }
5460   common::die("Vector element kind must be known at compile-time");
5461 }
5462 
5463 bool DeclarationVisitor::Pre(const parser::VectorTypeSpec &) {
5464   // PowerPC vector types are allowed only on Power architectures.
5465   if (!currScope().context().targetCharacteristics().isPPC()) {
5466     Say(currStmtSource().value(),
5467         "Vector type is only supported for PowerPC"_err_en_US);
5468     isVectorType_ = false;
5469     return false;
5470   }
5471   isVectorType_ = true;
5472   return true;
5473 }
5474 // Create semantic::DerivedTypeSpec for Vector types here.
5475 void DeclarationVisitor::Post(const parser::VectorTypeSpec &x) {
5476   llvm::StringRef typeName;
5477   llvm::SmallVector<ParamValue> typeParams;
5478   DerivedTypeSpec::Category vectorCategory;
5479 
5480   isVectorType_ = false;
5481   common::visit(
5482       common::visitors{
5483           [&](const parser::IntrinsicVectorTypeSpec &y) {
5484             vectorCategory = DerivedTypeSpec::Category::IntrinsicVector;
5485             int vecElemKind = 0;
5486             typeName = "__builtin_ppc_intrinsic_vector";
5487             common::visit(
5488                 common::visitors{
5489                     [&](const parser::IntegerTypeSpec &z) {
5490                       vecElemKind = GetVectorElementKind(
5491                           TypeCategory::Integer, std::move(z.v));
5492                       typeParams.push_back(ParamValue(
5493                           static_cast<common::ConstantSubscript>(
5494                               common::VectorElementCategory::Integer),
5495                           common::TypeParamAttr::Kind));
5496                     },
5497                     [&](const parser::IntrinsicTypeSpec::Real &z) {
5498                       vecElemKind = GetVectorElementKind(
5499                           TypeCategory::Real, std::move(z.kind));
5500                       typeParams.push_back(
5501                           ParamValue(static_cast<common::ConstantSubscript>(
5502                                          common::VectorElementCategory::Real),
5503                               common::TypeParamAttr::Kind));
5504                     },
5505                     [&](const parser::UnsignedTypeSpec &z) {
5506                       vecElemKind = GetVectorElementKind(
5507                           TypeCategory::Integer, std::move(z.v));
5508                       typeParams.push_back(ParamValue(
5509                           static_cast<common::ConstantSubscript>(
5510                               common::VectorElementCategory::Unsigned),
5511                           common::TypeParamAttr::Kind));
5512                     },
5513                 },
5514                 y.v.u);
5515             typeParams.push_back(
5516                 ParamValue(static_cast<common::ConstantSubscript>(vecElemKind),
5517                     common::TypeParamAttr::Kind));
5518           },
5519           [&](const parser::VectorTypeSpec::PairVectorTypeSpec &y) {
5520             vectorCategory = DerivedTypeSpec::Category::PairVector;
5521             typeName = "__builtin_ppc_pair_vector";
5522           },
5523           [&](const parser::VectorTypeSpec::QuadVectorTypeSpec &y) {
5524             vectorCategory = DerivedTypeSpec::Category::QuadVector;
5525             typeName = "__builtin_ppc_quad_vector";
5526           },
5527       },
5528       x.u);
5529 
5530   auto ppcBuiltinTypesScope = currScope().context().GetPPCBuiltinTypesScope();
5531   if (!ppcBuiltinTypesScope) {
5532     common::die("INTERNAL: The __ppc_types module was not found ");
5533   }
5534 
5535   auto iter{ppcBuiltinTypesScope->find(
5536       semantics::SourceName{typeName.data(), typeName.size()})};
5537   if (iter == ppcBuiltinTypesScope->cend()) {
5538     common::die("INTERNAL: The __ppc_types module does not define "
5539                 "the type '%s'",
5540         typeName.data());
5541   }
5542 
5543   const semantics::Symbol &typeSymbol{*iter->second};
5544   DerivedTypeSpec vectorDerivedType{typeName.data(), typeSymbol};
5545   vectorDerivedType.set_category(vectorCategory);
5546   if (typeParams.size()) {
5547     vectorDerivedType.AddRawParamValue(nullptr, std::move(typeParams[0]));
5548     vectorDerivedType.AddRawParamValue(nullptr, std::move(typeParams[1]));
5549     vectorDerivedType.CookParameters(GetFoldingContext());
5550   }
5551 
5552   if (const DeclTypeSpec *
5553       extant{ppcBuiltinTypesScope->FindInstantiatedDerivedType(
5554           vectorDerivedType, DeclTypeSpec::Category::TypeDerived)}) {
5555     // This derived type and parameter expressions (if any) are already present
5556     // in the __ppc_intrinsics scope.
5557     SetDeclTypeSpec(*extant);
5558   } else {
5559     DeclTypeSpec &type{ppcBuiltinTypesScope->MakeDerivedType(
5560         DeclTypeSpec::Category::TypeDerived, std::move(vectorDerivedType))};
5561     DerivedTypeSpec &derived{type.derivedTypeSpec()};
5562     auto restorer{
5563         GetFoldingContext().messages().SetLocation(currStmtSource().value())};
5564     derived.Instantiate(*ppcBuiltinTypesScope);
5565     SetDeclTypeSpec(type);
5566   }
5567 }
5568 
5569 bool DeclarationVisitor::Pre(const parser::DeclarationTypeSpec::Type &) {
5570   CHECK(GetDeclTypeSpecCategory() == DeclTypeSpec::Category::TypeDerived);
5571   return true;
5572 }
5573 
5574 void DeclarationVisitor::Post(const parser::DeclarationTypeSpec::Type &type) {
5575   const parser::Name &derivedName{std::get<parser::Name>(type.derived.t)};
5576   if (const Symbol * derivedSymbol{derivedName.symbol}) {
5577     CheckForAbstractType(*derivedSymbol); // C706
5578   }
5579 }
5580 
5581 bool DeclarationVisitor::Pre(const parser::DeclarationTypeSpec::Class &) {
5582   SetDeclTypeSpecCategory(DeclTypeSpec::Category::ClassDerived);
5583   return true;
5584 }
5585 
5586 void DeclarationVisitor::Post(
5587     const parser::DeclarationTypeSpec::Class &parsedClass) {
5588   const auto &typeName{std::get<parser::Name>(parsedClass.derived.t)};
5589   if (auto spec{ResolveDerivedType(typeName)};
5590       spec && !IsExtensibleType(&*spec)) { // C705
5591     SayWithDecl(typeName, *typeName.symbol,
5592         "Non-extensible derived type '%s' may not be used with CLASS"
5593         " keyword"_err_en_US);
5594   }
5595 }
5596 
5597 void DeclarationVisitor::Post(const parser::DerivedTypeSpec &x) {
5598   const auto &typeName{std::get<parser::Name>(x.t)};
5599   auto spec{ResolveDerivedType(typeName)};
5600   if (!spec) {
5601     return;
5602   }
5603   bool seenAnyName{false};
5604   for (const auto &typeParamSpec :
5605       std::get<std::list<parser::TypeParamSpec>>(x.t)) {
5606     const auto &optKeyword{
5607         std::get<std::optional<parser::Keyword>>(typeParamSpec.t)};
5608     std::optional<SourceName> name;
5609     if (optKeyword) {
5610       seenAnyName = true;
5611       name = optKeyword->v.source;
5612     } else if (seenAnyName) {
5613       Say(typeName.source, "Type parameter value must have a name"_err_en_US);
5614       continue;
5615     }
5616     const auto &value{std::get<parser::TypeParamValue>(typeParamSpec.t)};
5617     // The expressions in a derived type specifier whose values define
5618     // non-defaulted type parameters are evaluated (folded) in the enclosing
5619     // scope.  The KIND/LEN distinction is resolved later in
5620     // DerivedTypeSpec::CookParameters().
5621     ParamValue param{GetParamValue(value, common::TypeParamAttr::Kind)};
5622     if (!param.isExplicit() || param.GetExplicit()) {
5623       spec->AddRawParamValue(
5624           common::GetPtrFromOptional(optKeyword), std::move(param));
5625     }
5626   }
5627   // The DerivedTypeSpec *spec is used initially as a search key.
5628   // If it turns out to have the same name and actual parameter
5629   // value expressions as another DerivedTypeSpec in the current
5630   // scope does, then we'll use that extant spec; otherwise, when this
5631   // spec is distinct from all derived types previously instantiated
5632   // in the current scope, this spec will be moved into that collection.
5633   const auto &dtDetails{spec->typeSymbol().get<DerivedTypeDetails>()};
5634   auto category{GetDeclTypeSpecCategory()};
5635   if (dtDetails.isForwardReferenced()) {
5636     DeclTypeSpec &type{currScope().MakeDerivedType(category, std::move(*spec))};
5637     SetDeclTypeSpec(type);
5638     return;
5639   }
5640   // Normalize parameters to produce a better search key.
5641   spec->CookParameters(GetFoldingContext());
5642   if (!spec->MightBeParameterized()) {
5643     spec->EvaluateParameters(context());
5644   }
5645   if (const DeclTypeSpec *
5646       extant{currScope().FindInstantiatedDerivedType(*spec, category)}) {
5647     // This derived type and parameter expressions (if any) are already present
5648     // in this scope.
5649     SetDeclTypeSpec(*extant);
5650   } else {
5651     DeclTypeSpec &type{currScope().MakeDerivedType(category, std::move(*spec))};
5652     DerivedTypeSpec &derived{type.derivedTypeSpec()};
5653     if (derived.MightBeParameterized() &&
5654         currScope().IsParameterizedDerivedType()) {
5655       // Defer instantiation; use the derived type's definition's scope.
5656       derived.set_scope(DEREF(spec->typeSymbol().scope()));
5657     } else if (&currScope() == spec->typeSymbol().scope()) {
5658       // Direct recursive use of a type in the definition of one of its
5659       // components: defer instantiation
5660     } else {
5661       auto restorer{
5662           GetFoldingContext().messages().SetLocation(currStmtSource().value())};
5663       derived.Instantiate(currScope());
5664     }
5665     SetDeclTypeSpec(type);
5666   }
5667   // Capture the DerivedTypeSpec in the parse tree for use in building
5668   // structure constructor expressions.
5669   x.derivedTypeSpec = &GetDeclTypeSpec()->derivedTypeSpec();
5670 }
5671 
5672 void DeclarationVisitor::Post(const parser::DeclarationTypeSpec::Record &rec) {
5673   const auto &typeName{rec.v};
5674   if (auto spec{ResolveDerivedType(typeName)}) {
5675     spec->CookParameters(GetFoldingContext());
5676     spec->EvaluateParameters(context());
5677     if (const DeclTypeSpec *
5678         extant{currScope().FindInstantiatedDerivedType(
5679             *spec, DeclTypeSpec::TypeDerived)}) {
5680       SetDeclTypeSpec(*extant);
5681     } else {
5682       Say(typeName.source, "%s is not a known STRUCTURE"_err_en_US,
5683           typeName.source);
5684     }
5685   }
5686 }
5687 
5688 // The descendents of DerivedTypeDef in the parse tree are visited directly
5689 // in this Pre() routine so that recursive use of the derived type can be
5690 // supported in the components.
5691 bool DeclarationVisitor::Pre(const parser::DerivedTypeDef &x) {
5692   auto &stmt{std::get<parser::Statement<parser::DerivedTypeStmt>>(x.t)};
5693   Walk(stmt);
5694   Walk(std::get<std::list<parser::Statement<parser::TypeParamDefStmt>>>(x.t));
5695   auto &scope{currScope()};
5696   CHECK(scope.symbol());
5697   CHECK(scope.symbol()->scope() == &scope);
5698   auto &details{scope.symbol()->get<DerivedTypeDetails>()};
5699   for (auto &paramName : std::get<std::list<parser::Name>>(stmt.statement.t)) {
5700     if (auto *symbol{FindInScope(scope, paramName)}) {
5701       if (auto *details{symbol->detailsIf<TypeParamDetails>()}) {
5702         if (!details->attr()) {
5703           Say(paramName,
5704               "No definition found for type parameter '%s'"_err_en_US); // C742
5705         }
5706       }
5707     }
5708   }
5709   Walk(std::get<std::list<parser::Statement<parser::PrivateOrSequence>>>(x.t));
5710   const auto &componentDefs{
5711       std::get<std::list<parser::Statement<parser::ComponentDefStmt>>>(x.t)};
5712   Walk(componentDefs);
5713   if (derivedTypeInfo_.sequence) {
5714     details.set_sequence(true);
5715     if (componentDefs.empty()) {
5716       // F'2023 C745 - not enforced by any compiler
5717       context().Warn(common::LanguageFeature::EmptySequenceType, stmt.source,
5718           "A sequence type should have at least one component"_warn_en_US);
5719     }
5720     if (!details.paramDeclOrder().empty()) { // C740
5721       Say(stmt.source,
5722           "A sequence type may not have type parameters"_err_en_US);
5723     }
5724     if (derivedTypeInfo_.extends) { // C735
5725       Say(stmt.source,
5726           "A sequence type may not have the EXTENDS attribute"_err_en_US);
5727     }
5728   }
5729   Walk(std::get<std::optional<parser::TypeBoundProcedurePart>>(x.t));
5730   Walk(std::get<parser::Statement<parser::EndTypeStmt>>(x.t));
5731   details.set_isForwardReferenced(false);
5732   derivedTypeInfo_ = {};
5733   PopScope();
5734   return false;
5735 }
5736 
5737 bool DeclarationVisitor::Pre(const parser::DerivedTypeStmt &) {
5738   return BeginAttrs();
5739 }
5740 void DeclarationVisitor::Post(const parser::DerivedTypeStmt &x) {
5741   auto &name{std::get<parser::Name>(x.t)};
5742   // Resolve the EXTENDS() clause before creating the derived
5743   // type's symbol to foil attempts to recursively extend a type.
5744   auto *extendsName{derivedTypeInfo_.extends};
5745   std::optional<DerivedTypeSpec> extendsType{
5746       ResolveExtendsType(name, extendsName)};
5747   DerivedTypeDetails derivedTypeDetails;
5748   // Catch any premature structure constructors within the definition
5749   derivedTypeDetails.set_isForwardReferenced(true);
5750   auto &symbol{MakeSymbol(name, GetAttrs(), std::move(derivedTypeDetails))};
5751   symbol.ReplaceName(name.source);
5752   derivedTypeInfo_.type = &symbol;
5753   PushScope(Scope::Kind::DerivedType, &symbol);
5754   if (extendsType) {
5755     // Declare the "parent component"; private if the type is.
5756     // Any symbol stored in the EXTENDS() clause is temporarily
5757     // hidden so that a new symbol can be created for the parent
5758     // component without producing spurious errors about already
5759     // existing.
5760     const Symbol &extendsSymbol{extendsType->typeSymbol()};
5761     auto restorer{common::ScopedSet(extendsName->symbol, nullptr)};
5762     if (OkToAddComponent(*extendsName, &extendsSymbol)) {
5763       auto &comp{DeclareEntity<ObjectEntityDetails>(*extendsName, Attrs{})};
5764       comp.attrs().set(
5765           Attr::PRIVATE, extendsSymbol.attrs().test(Attr::PRIVATE));
5766       comp.implicitAttrs().set(
5767           Attr::PRIVATE, extendsSymbol.implicitAttrs().test(Attr::PRIVATE));
5768       comp.set(Symbol::Flag::ParentComp);
5769       DeclTypeSpec &type{currScope().MakeDerivedType(
5770           DeclTypeSpec::TypeDerived, std::move(*extendsType))};
5771       type.derivedTypeSpec().set_scope(DEREF(extendsSymbol.scope()));
5772       comp.SetType(type);
5773       DerivedTypeDetails &details{symbol.get<DerivedTypeDetails>()};
5774       details.add_component(comp);
5775     }
5776   }
5777   // Create symbols now for type parameters so that they shadow names
5778   // from the enclosing specification part.
5779   if (auto *details{symbol.detailsIf<DerivedTypeDetails>()}) {
5780     for (const auto &name : std::get<std::list<parser::Name>>(x.t)) {
5781       if (Symbol * symbol{MakeTypeSymbol(name, TypeParamDetails{})}) {
5782         details->add_paramNameOrder(*symbol);
5783       }
5784     }
5785   }
5786   EndAttrs();
5787 }
5788 
5789 void DeclarationVisitor::Post(const parser::TypeParamDefStmt &x) {
5790   auto *type{GetDeclTypeSpec()};
5791   DerivedTypeDetails *derivedDetails{nullptr};
5792   if (Symbol * dtSym{currScope().symbol()}) {
5793     derivedDetails = dtSym->detailsIf<DerivedTypeDetails>();
5794   }
5795   auto attr{std::get<common::TypeParamAttr>(x.t)};
5796   for (auto &decl : std::get<std::list<parser::TypeParamDecl>>(x.t)) {
5797     auto &name{std::get<parser::Name>(decl.t)};
5798     if (Symbol * symbol{FindInScope(currScope(), name)}) {
5799       if (auto *paramDetails{symbol->detailsIf<TypeParamDetails>()}) {
5800         if (!paramDetails->attr()) {
5801           paramDetails->set_attr(attr);
5802           SetType(name, *type);
5803           if (auto &init{std::get<std::optional<parser::ScalarIntConstantExpr>>(
5804                   decl.t)}) {
5805             if (auto maybeExpr{AnalyzeExpr(context(), *init)}) {
5806               if (auto *intExpr{std::get_if<SomeIntExpr>(&maybeExpr->u)}) {
5807                 paramDetails->set_init(std::move(*intExpr));
5808               }
5809             }
5810           }
5811           if (derivedDetails) {
5812             derivedDetails->add_paramDeclOrder(*symbol);
5813           }
5814         } else {
5815           Say(name,
5816               "Type parameter '%s' was already declared in this derived type"_err_en_US);
5817         }
5818       }
5819     } else {
5820       Say(name, "'%s' is not a parameter of this derived type"_err_en_US);
5821     }
5822   }
5823   EndDecl();
5824 }
5825 bool DeclarationVisitor::Pre(const parser::TypeAttrSpec::Extends &x) {
5826   if (derivedTypeInfo_.extends) {
5827     Say(currStmtSource().value(),
5828         "Attribute 'EXTENDS' cannot be used more than once"_err_en_US);
5829   } else {
5830     derivedTypeInfo_.extends = &x.v;
5831   }
5832   return false;
5833 }
5834 
5835 bool DeclarationVisitor::Pre(const parser::PrivateStmt &) {
5836   if (!currScope().parent().IsModule()) {
5837     Say("PRIVATE is only allowed in a derived type that is"
5838         " in a module"_err_en_US); // C766
5839   } else if (derivedTypeInfo_.sawContains) {
5840     derivedTypeInfo_.privateBindings = true;
5841   } else if (!derivedTypeInfo_.privateComps) {
5842     derivedTypeInfo_.privateComps = true;
5843   } else { // C738
5844     context().Warn(common::LanguageFeature::RedundantAttribute,
5845         "PRIVATE should not appear more than once in derived type components"_warn_en_US);
5846   }
5847   return false;
5848 }
5849 bool DeclarationVisitor::Pre(const parser::SequenceStmt &) {
5850   if (derivedTypeInfo_.sequence) { // C738
5851     context().Warn(common::LanguageFeature::RedundantAttribute,
5852         "SEQUENCE should not appear more than once in derived type components"_warn_en_US);
5853   }
5854   derivedTypeInfo_.sequence = true;
5855   return false;
5856 }
5857 void DeclarationVisitor::Post(const parser::ComponentDecl &x) {
5858   const auto &name{std::get<parser::Name>(x.t)};
5859   auto attrs{GetAttrs()};
5860   if (derivedTypeInfo_.privateComps &&
5861       !attrs.HasAny({Attr::PUBLIC, Attr::PRIVATE})) {
5862     attrs.set(Attr::PRIVATE);
5863   }
5864   if (const auto *declType{GetDeclTypeSpec()}) {
5865     if (const auto *derived{declType->AsDerived()}) {
5866       if (!attrs.HasAny({Attr::POINTER, Attr::ALLOCATABLE})) {
5867         if (derivedTypeInfo_.type == &derived->typeSymbol()) { // C744
5868           Say("Recursive use of the derived type requires "
5869               "POINTER or ALLOCATABLE"_err_en_US);
5870         }
5871       }
5872       // TODO: This would be more appropriate in CheckDerivedType()
5873       if (auto it{FindCoarrayUltimateComponent(*derived)}) { // C748
5874         std::string ultimateName{it.BuildResultDesignatorName()};
5875         // Strip off the leading "%"
5876         if (ultimateName.length() > 1) {
5877           ultimateName.erase(0, 1);
5878           if (attrs.HasAny({Attr::POINTER, Attr::ALLOCATABLE})) {
5879             evaluate::AttachDeclaration(
5880                 Say(name.source,
5881                     "A component with a POINTER or ALLOCATABLE attribute may "
5882                     "not "
5883                     "be of a type with a coarray ultimate component (named "
5884                     "'%s')"_err_en_US,
5885                     ultimateName),
5886                 derived->typeSymbol());
5887           }
5888           if (!arraySpec().empty() || !coarraySpec().empty()) {
5889             evaluate::AttachDeclaration(
5890                 Say(name.source,
5891                     "An array or coarray component may not be of a type with a "
5892                     "coarray ultimate component (named '%s')"_err_en_US,
5893                     ultimateName),
5894                 derived->typeSymbol());
5895           }
5896         }
5897       }
5898     }
5899   }
5900   if (OkToAddComponent(name)) {
5901     auto &symbol{DeclareObjectEntity(name, attrs)};
5902     SetCUDADataAttr(name.source, symbol, cudaDataAttr());
5903     if (symbol.has<ObjectEntityDetails>()) {
5904       if (auto &init{std::get<std::optional<parser::Initialization>>(x.t)}) {
5905         Initialization(name, *init, true);
5906       }
5907     }
5908     currScope().symbol()->get<DerivedTypeDetails>().add_component(symbol);
5909   }
5910   ClearArraySpec();
5911   ClearCoarraySpec();
5912 }
5913 void DeclarationVisitor::Post(const parser::FillDecl &x) {
5914   // Replace "%FILL" with a distinct generated name
5915   const auto &name{std::get<parser::Name>(x.t)};
5916   const_cast<SourceName &>(name.source) = context().GetTempName(currScope());
5917   if (OkToAddComponent(name)) {
5918     auto &symbol{DeclareObjectEntity(name, GetAttrs())};
5919     currScope().symbol()->get<DerivedTypeDetails>().add_component(symbol);
5920   }
5921   ClearArraySpec();
5922 }
5923 bool DeclarationVisitor::Pre(const parser::ProcedureDeclarationStmt &x) {
5924   CHECK(!interfaceName_);
5925   const auto &procAttrSpec{std::get<std::list<parser::ProcAttrSpec>>(x.t)};
5926   for (const parser::ProcAttrSpec &procAttr : procAttrSpec) {
5927     if (auto *bindC{std::get_if<parser::LanguageBindingSpec>(&procAttr.u)}) {
5928       if (std::get<std::optional<parser::ScalarDefaultCharConstantExpr>>(
5929               bindC->t)
5930               .has_value()) {
5931         if (std::get<std::list<parser::ProcDecl>>(x.t).size() > 1) {
5932           Say(context().location().value(),
5933               "A procedure declaration statement with a binding name may not declare multiple procedures"_err_en_US);
5934         }
5935         break;
5936       }
5937     }
5938   }
5939   return BeginDecl();
5940 }
5941 void DeclarationVisitor::Post(const parser::ProcedureDeclarationStmt &) {
5942   interfaceName_ = nullptr;
5943   EndDecl();
5944 }
5945 bool DeclarationVisitor::Pre(const parser::DataComponentDefStmt &x) {
5946   // Overrides parse tree traversal so as to handle attributes first,
5947   // so POINTER & ALLOCATABLE enable forward references to derived types.
5948   Walk(std::get<std::list<parser::ComponentAttrSpec>>(x.t));
5949   set_allowForwardReferenceToDerivedType(
5950       GetAttrs().HasAny({Attr::POINTER, Attr::ALLOCATABLE}));
5951   Walk(std::get<parser::DeclarationTypeSpec>(x.t));
5952   set_allowForwardReferenceToDerivedType(false);
5953   if (derivedTypeInfo_.sequence) { // C740
5954     if (const auto *declType{GetDeclTypeSpec()}) {
5955       if (!declType->AsIntrinsic() && !declType->IsSequenceType() &&
5956           !InModuleFile()) {
5957         if (GetAttrs().test(Attr::POINTER) &&
5958             context().IsEnabled(common::LanguageFeature::PointerInSeqType)) {
5959           context().Warn(common::LanguageFeature::PointerInSeqType,
5960               "A sequence type data component that is a pointer to a non-sequence type is not standard"_port_en_US);
5961         } else {
5962           Say("A sequence type data component must either be of an intrinsic type or a derived sequence type"_err_en_US);
5963         }
5964       }
5965     }
5966   }
5967   Walk(std::get<std::list<parser::ComponentOrFill>>(x.t));
5968   return false;
5969 }
5970 bool DeclarationVisitor::Pre(const parser::ProcComponentDefStmt &) {
5971   CHECK(!interfaceName_);
5972   return true;
5973 }
5974 void DeclarationVisitor::Post(const parser::ProcComponentDefStmt &) {
5975   interfaceName_ = nullptr;
5976 }
5977 bool DeclarationVisitor::Pre(const parser::ProcPointerInit &x) {
5978   if (auto *name{std::get_if<parser::Name>(&x.u)}) {
5979     return !NameIsKnownOrIntrinsic(*name) && !CheckUseError(*name);
5980   } else {
5981     const auto &null{DEREF(std::get_if<parser::NullInit>(&x.u))};
5982     Walk(null);
5983     if (auto nullInit{EvaluateExpr(null)}) {
5984       if (!evaluate::IsNullPointer(*nullInit)) {
5985         Say(null.v.value().source,
5986             "Procedure pointer initializer must be a name or intrinsic NULL()"_err_en_US);
5987       }
5988     }
5989     return false;
5990   }
5991 }
5992 void DeclarationVisitor::Post(const parser::ProcInterface &x) {
5993   if (auto *name{std::get_if<parser::Name>(&x.u)}) {
5994     interfaceName_ = name;
5995     NoteInterfaceName(*name);
5996   }
5997 }
5998 void DeclarationVisitor::Post(const parser::ProcDecl &x) {
5999   const auto &name{std::get<parser::Name>(x.t)};
6000   // Don't use BypassGeneric or GetUltimate on this symbol, they can
6001   // lead to unusable names in module files.
6002   const Symbol *procInterface{
6003       interfaceName_ ? interfaceName_->symbol : nullptr};
6004   auto attrs{HandleSaveName(name.source, GetAttrs())};
6005   DerivedTypeDetails *dtDetails{nullptr};
6006   if (Symbol * symbol{currScope().symbol()}) {
6007     dtDetails = symbol->detailsIf<DerivedTypeDetails>();
6008   }
6009   if (!dtDetails) {
6010     attrs.set(Attr::EXTERNAL);
6011   }
6012   Symbol &symbol{DeclareProcEntity(name, attrs, procInterface)};
6013   SetCUDADataAttr(name.source, symbol, cudaDataAttr()); // for error
6014   symbol.ReplaceName(name.source);
6015   if (dtDetails) {
6016     dtDetails->add_component(symbol);
6017   }
6018   DeclaredPossibleSpecificProc(symbol);
6019 }
6020 
6021 bool DeclarationVisitor::Pre(const parser::TypeBoundProcedurePart &) {
6022   derivedTypeInfo_.sawContains = true;
6023   return true;
6024 }
6025 
6026 // Resolve binding names from type-bound generics, saved in genericBindings_.
6027 void DeclarationVisitor::Post(const parser::TypeBoundProcedurePart &) {
6028   // track specifics seen for the current generic to detect duplicates:
6029   const Symbol *currGeneric{nullptr};
6030   std::set<SourceName> specifics;
6031   for (const auto &[generic, bindingName] : genericBindings_) {
6032     if (generic != currGeneric) {
6033       currGeneric = generic;
6034       specifics.clear();
6035     }
6036     auto [it, inserted]{specifics.insert(bindingName->source)};
6037     if (!inserted) {
6038       Say(*bindingName, // C773
6039           "Binding name '%s' was already specified for generic '%s'"_err_en_US,
6040           bindingName->source, generic->name())
6041           .Attach(*it, "Previous specification of '%s'"_en_US, *it);
6042       continue;
6043     }
6044     auto *symbol{FindInTypeOrParents(*bindingName)};
6045     if (!symbol) {
6046       Say(*bindingName, // C772
6047           "Binding name '%s' not found in this derived type"_err_en_US);
6048     } else if (!symbol->has<ProcBindingDetails>()) {
6049       SayWithDecl(*bindingName, *symbol, // C772
6050           "'%s' is not the name of a specific binding of this type"_err_en_US);
6051     } else {
6052       generic->get<GenericDetails>().AddSpecificProc(
6053           *symbol, bindingName->source);
6054     }
6055   }
6056   genericBindings_.clear();
6057 }
6058 
6059 void DeclarationVisitor::Post(const parser::ContainsStmt &) {
6060   if (derivedTypeInfo_.sequence) {
6061     Say("A sequence type may not have a CONTAINS statement"_err_en_US); // C740
6062   }
6063 }
6064 
6065 void DeclarationVisitor::Post(
6066     const parser::TypeBoundProcedureStmt::WithoutInterface &x) {
6067   if (GetAttrs().test(Attr::DEFERRED)) { // C783
6068     Say("DEFERRED is only allowed when an interface-name is provided"_err_en_US);
6069   }
6070   for (auto &declaration : x.declarations) {
6071     auto &bindingName{std::get<parser::Name>(declaration.t)};
6072     auto &optName{std::get<std::optional<parser::Name>>(declaration.t)};
6073     const parser::Name &procedureName{optName ? *optName : bindingName};
6074     Symbol *procedure{FindSymbol(procedureName)};
6075     if (!procedure) {
6076       procedure = NoteInterfaceName(procedureName);
6077     }
6078     if (procedure) {
6079       const Symbol &bindTo{BypassGeneric(*procedure)};
6080       if (auto *s{MakeTypeSymbol(bindingName, ProcBindingDetails{bindTo})}) {
6081         SetPassNameOn(*s);
6082         if (GetAttrs().test(Attr::DEFERRED)) {
6083           context().SetError(*s);
6084         }
6085       }
6086     }
6087   }
6088 }
6089 
6090 void DeclarationVisitor::CheckBindings(
6091     const parser::TypeBoundProcedureStmt::WithoutInterface &tbps) {
6092   CHECK(currScope().IsDerivedType());
6093   for (auto &declaration : tbps.declarations) {
6094     auto &bindingName{std::get<parser::Name>(declaration.t)};
6095     if (Symbol * binding{FindInScope(bindingName)}) {
6096       if (auto *details{binding->detailsIf<ProcBindingDetails>()}) {
6097         const Symbol &ultimate{details->symbol().GetUltimate()};
6098         const Symbol &procedure{BypassGeneric(ultimate)};
6099         if (&procedure != &ultimate) {
6100           details->ReplaceSymbol(procedure);
6101         }
6102         if (!CanBeTypeBoundProc(procedure)) {
6103           if (details->symbol().name() != binding->name()) {
6104             Say(binding->name(),
6105                 "The binding of '%s' ('%s') must be either an accessible "
6106                 "module procedure or an external procedure with "
6107                 "an explicit interface"_err_en_US,
6108                 binding->name(), details->symbol().name());
6109           } else {
6110             Say(binding->name(),
6111                 "'%s' must be either an accessible module procedure "
6112                 "or an external procedure with an explicit interface"_err_en_US,
6113                 binding->name());
6114           }
6115           context().SetError(*binding);
6116         }
6117       }
6118     }
6119   }
6120 }
6121 
6122 void DeclarationVisitor::Post(
6123     const parser::TypeBoundProcedureStmt::WithInterface &x) {
6124   if (!GetAttrs().test(Attr::DEFERRED)) { // C783
6125     Say("DEFERRED is required when an interface-name is provided"_err_en_US);
6126   }
6127   if (Symbol * interface{NoteInterfaceName(x.interfaceName)}) {
6128     for (auto &bindingName : x.bindingNames) {
6129       if (auto *s{
6130               MakeTypeSymbol(bindingName, ProcBindingDetails{*interface})}) {
6131         SetPassNameOn(*s);
6132         if (!GetAttrs().test(Attr::DEFERRED)) {
6133           context().SetError(*s);
6134         }
6135       }
6136     }
6137   }
6138 }
6139 
6140 bool DeclarationVisitor::Pre(const parser::FinalProcedureStmt &x) {
6141   if (currScope().IsDerivedType() && currScope().symbol()) {
6142     if (auto *details{currScope().symbol()->detailsIf<DerivedTypeDetails>()}) {
6143       for (const auto &subrName : x.v) {
6144         Symbol *symbol{FindSymbol(subrName)};
6145         if (!symbol) {
6146           // FINAL procedures must be module subroutines
6147           symbol = &MakeSymbol(
6148               currScope().parent(), subrName.source, Attrs{Attr::MODULE});
6149           Resolve(subrName, symbol);
6150           symbol->set_details(ProcEntityDetails{});
6151           symbol->set(Symbol::Flag::Subroutine);
6152         }
6153         if (auto pair{details->finals().emplace(subrName.source, *symbol)};
6154             !pair.second) { // C787
6155           Say(subrName.source,
6156               "FINAL subroutine '%s' already appeared in this derived type"_err_en_US,
6157               subrName.source)
6158               .Attach(pair.first->first,
6159                   "earlier appearance of this FINAL subroutine"_en_US);
6160         }
6161       }
6162     }
6163   }
6164   return false;
6165 }
6166 
6167 bool DeclarationVisitor::Pre(const parser::TypeBoundGenericStmt &x) {
6168   const auto &accessSpec{std::get<std::optional<parser::AccessSpec>>(x.t)};
6169   const auto &genericSpec{std::get<Indirection<parser::GenericSpec>>(x.t)};
6170   const auto &bindingNames{std::get<std::list<parser::Name>>(x.t)};
6171   GenericSpecInfo info{genericSpec.value()};
6172   SourceName symbolName{info.symbolName()};
6173   bool isPrivate{accessSpec ? accessSpec->v == parser::AccessSpec::Kind::Private
6174                             : derivedTypeInfo_.privateBindings};
6175   auto *genericSymbol{FindInScope(symbolName)};
6176   if (genericSymbol) {
6177     if (!genericSymbol->has<GenericDetails>()) {
6178       genericSymbol = nullptr; // MakeTypeSymbol will report the error below
6179     }
6180   } else {
6181     // look in ancestor types for a generic of the same name
6182     for (const auto &name : GetAllNames(context(), symbolName)) {
6183       if (Symbol * inherited{currScope().FindComponent(SourceName{name})}) {
6184         if (inherited->has<GenericDetails>()) {
6185           CheckAccessibility(symbolName, isPrivate, *inherited); // C771
6186         } else {
6187           Say(symbolName,
6188               "Type bound generic procedure '%s' may not have the same name as a non-generic symbol inherited from an ancestor type"_err_en_US)
6189               .Attach(inherited->name(), "Inherited symbol"_en_US);
6190         }
6191         break;
6192       }
6193     }
6194   }
6195   if (genericSymbol) {
6196     CheckAccessibility(symbolName, isPrivate, *genericSymbol); // C771
6197   } else {
6198     genericSymbol = MakeTypeSymbol(symbolName, GenericDetails{});
6199     if (!genericSymbol) {
6200       return false;
6201     }
6202     if (isPrivate) {
6203       SetExplicitAttr(*genericSymbol, Attr::PRIVATE);
6204     }
6205   }
6206   for (const parser::Name &bindingName : bindingNames) {
6207     genericBindings_.emplace(genericSymbol, &bindingName);
6208   }
6209   info.Resolve(genericSymbol);
6210   return false;
6211 }
6212 
6213 // DEC STRUCTUREs are handled thus to allow for nested definitions.
6214 bool DeclarationVisitor::Pre(const parser::StructureDef &def) {
6215   const auto &structureStatement{
6216       std::get<parser::Statement<parser::StructureStmt>>(def.t)};
6217   auto saveDerivedTypeInfo{derivedTypeInfo_};
6218   derivedTypeInfo_ = {};
6219   derivedTypeInfo_.isStructure = true;
6220   derivedTypeInfo_.sequence = true;
6221   Scope *previousStructure{nullptr};
6222   if (saveDerivedTypeInfo.isStructure) {
6223     previousStructure = &currScope();
6224     PopScope();
6225   }
6226   const parser::StructureStmt &structStmt{structureStatement.statement};
6227   const auto &name{std::get<std::optional<parser::Name>>(structStmt.t)};
6228   if (!name) {
6229     // Construct a distinct generated name for an anonymous structure
6230     auto &mutableName{const_cast<std::optional<parser::Name> &>(name)};
6231     mutableName.emplace(
6232         parser::Name{context().GetTempName(currScope()), nullptr});
6233   }
6234   auto &symbol{MakeSymbol(*name, DerivedTypeDetails{})};
6235   symbol.ReplaceName(name->source);
6236   symbol.get<DerivedTypeDetails>().set_sequence(true);
6237   symbol.get<DerivedTypeDetails>().set_isDECStructure(true);
6238   derivedTypeInfo_.type = &symbol;
6239   PushScope(Scope::Kind::DerivedType, &symbol);
6240   const auto &fields{std::get<std::list<parser::StructureField>>(def.t)};
6241   Walk(fields);
6242   PopScope();
6243   // Complete the definition
6244   DerivedTypeSpec derivedTypeSpec{symbol.name(), symbol};
6245   derivedTypeSpec.set_scope(DEREF(symbol.scope()));
6246   derivedTypeSpec.CookParameters(GetFoldingContext());
6247   derivedTypeSpec.EvaluateParameters(context());
6248   DeclTypeSpec &type{currScope().MakeDerivedType(
6249       DeclTypeSpec::TypeDerived, std::move(derivedTypeSpec))};
6250   type.derivedTypeSpec().Instantiate(currScope());
6251   // Restore previous structure definition context, if any
6252   derivedTypeInfo_ = saveDerivedTypeInfo;
6253   if (previousStructure) {
6254     PushScope(*previousStructure);
6255   }
6256   // Handle any entity declarations on the STRUCTURE statement
6257   const auto &decls{std::get<std::list<parser::EntityDecl>>(structStmt.t)};
6258   if (!decls.empty()) {
6259     BeginDecl();
6260     SetDeclTypeSpec(type);
6261     Walk(decls);
6262     EndDecl();
6263   }
6264   return false;
6265 }
6266 
6267 bool DeclarationVisitor::Pre(const parser::Union::UnionStmt &) {
6268   Say("support for UNION"_todo_en_US); // TODO
6269   return true;
6270 }
6271 
6272 bool DeclarationVisitor::Pre(const parser::StructureField &x) {
6273   if (std::holds_alternative<parser::Statement<parser::DataComponentDefStmt>>(
6274           x.u)) {
6275     BeginDecl();
6276   }
6277   return true;
6278 }
6279 
6280 void DeclarationVisitor::Post(const parser::StructureField &x) {
6281   if (std::holds_alternative<parser::Statement<parser::DataComponentDefStmt>>(
6282           x.u)) {
6283     EndDecl();
6284   }
6285 }
6286 
6287 bool DeclarationVisitor::Pre(const parser::AllocateStmt &) {
6288   BeginDeclTypeSpec();
6289   return true;
6290 }
6291 void DeclarationVisitor::Post(const parser::AllocateStmt &) {
6292   EndDeclTypeSpec();
6293 }
6294 
6295 bool DeclarationVisitor::Pre(const parser::StructureConstructor &x) {
6296   auto &parsedType{std::get<parser::DerivedTypeSpec>(x.t)};
6297   const DeclTypeSpec *type{ProcessTypeSpec(parsedType)};
6298   if (!type) {
6299     return false;
6300   }
6301   const DerivedTypeSpec *spec{type->AsDerived()};
6302   const Scope *typeScope{spec ? spec->scope() : nullptr};
6303   if (!typeScope) {
6304     return false;
6305   }
6306 
6307   // N.B C7102 is implicitly enforced by having inaccessible types not
6308   // being found in resolution.
6309   // More constraints are enforced in expression.cpp so that they
6310   // can apply to structure constructors that have been converted
6311   // from misparsed function references.
6312   for (const auto &component :
6313       std::get<std::list<parser::ComponentSpec>>(x.t)) {
6314     // Visit the component spec expression, but not the keyword, since
6315     // we need to resolve its symbol in the scope of the derived type.
6316     Walk(std::get<parser::ComponentDataSource>(component.t));
6317     if (const auto &kw{std::get<std::optional<parser::Keyword>>(component.t)}) {
6318       FindInTypeOrParents(*typeScope, kw->v);
6319     }
6320   }
6321   return false;
6322 }
6323 
6324 bool DeclarationVisitor::Pre(const parser::BasedPointer &) {
6325   BeginArraySpec();
6326   return true;
6327 }
6328 
6329 void DeclarationVisitor::Post(const parser::BasedPointer &bp) {
6330   const parser::ObjectName &pointerName{std::get<0>(bp.t)};
6331   auto *pointer{FindSymbol(pointerName)};
6332   if (!pointer) {
6333     pointer = &MakeSymbol(pointerName, ObjectEntityDetails{});
6334   } else if (!ConvertToObjectEntity(*pointer)) {
6335     SayWithDecl(pointerName, *pointer, "'%s' is not a variable"_err_en_US);
6336   } else if (IsNamedConstant(*pointer)) {
6337     SayWithDecl(pointerName, *pointer,
6338         "'%s' is a named constant and may not be a Cray pointer"_err_en_US);
6339   } else if (pointer->Rank() > 0) {
6340     SayWithDecl(
6341         pointerName, *pointer, "Cray pointer '%s' must be a scalar"_err_en_US);
6342   } else if (pointer->test(Symbol::Flag::CrayPointee)) {
6343     Say(pointerName,
6344         "'%s' cannot be a Cray pointer as it is already a Cray pointee"_err_en_US);
6345   }
6346   pointer->set(Symbol::Flag::CrayPointer);
6347   const DeclTypeSpec &pointerType{MakeNumericType(
6348       TypeCategory::Integer, context().defaultKinds().subscriptIntegerKind())};
6349   const auto *type{pointer->GetType()};
6350   if (!type) {
6351     pointer->SetType(pointerType);
6352   } else if (*type != pointerType) {
6353     Say(pointerName.source, "Cray pointer '%s' must have type %s"_err_en_US,
6354         pointerName.source, pointerType.AsFortran());
6355   }
6356   const parser::ObjectName &pointeeName{std::get<1>(bp.t)};
6357   DeclareObjectEntity(pointeeName);
6358   if (Symbol * pointee{pointeeName.symbol}) {
6359     if (!ConvertToObjectEntity(*pointee)) {
6360       return;
6361     }
6362     if (IsNamedConstant(*pointee)) {
6363       Say(pointeeName,
6364           "'%s' is a named constant and may not be a Cray pointee"_err_en_US);
6365       return;
6366     }
6367     if (pointee->test(Symbol::Flag::CrayPointer)) {
6368       Say(pointeeName,
6369           "'%s' cannot be a Cray pointee as it is already a Cray pointer"_err_en_US);
6370     } else if (pointee->test(Symbol::Flag::CrayPointee)) {
6371       Say(pointeeName, "'%s' was already declared as a Cray pointee"_err_en_US);
6372     } else {
6373       pointee->set(Symbol::Flag::CrayPointee);
6374     }
6375     if (const auto *pointeeType{pointee->GetType()}) {
6376       if (const auto *derived{pointeeType->AsDerived()}) {
6377         if (!IsSequenceOrBindCType(derived)) {
6378           context().Warn(common::LanguageFeature::NonSequenceCrayPointee,
6379               pointeeName.source,
6380               "Type of Cray pointee '%s' is a derived type that is neither SEQUENCE nor BIND(C)"_warn_en_US,
6381               pointeeName.source);
6382         }
6383       }
6384     }
6385     currScope().add_crayPointer(pointeeName.source, *pointer);
6386   }
6387 }
6388 
6389 bool DeclarationVisitor::Pre(const parser::NamelistStmt::Group &x) {
6390   if (!CheckNotInBlock("NAMELIST")) { // C1107
6391     return false;
6392   }
6393   const auto &groupName{std::get<parser::Name>(x.t)};
6394   auto *groupSymbol{FindInScope(groupName)};
6395   if (!groupSymbol || !groupSymbol->has<NamelistDetails>()) {
6396     groupSymbol = &MakeSymbol(groupName, NamelistDetails{});
6397     groupSymbol->ReplaceName(groupName.source);
6398   }
6399   // Name resolution of group items is deferred to FinishNamelists()
6400   // so that host association is handled correctly.
6401   GetDeferredDeclarationState(true)->namelistGroups.emplace_back(&x);
6402   return false;
6403 }
6404 
6405 void DeclarationVisitor::FinishNamelists() {
6406   if (auto *deferred{GetDeferredDeclarationState()}) {
6407     for (const parser::NamelistStmt::Group *group : deferred->namelistGroups) {
6408       if (auto *groupSymbol{FindInScope(std::get<parser::Name>(group->t))}) {
6409         if (auto *details{groupSymbol->detailsIf<NamelistDetails>()}) {
6410           for (const auto &name : std::get<std::list<parser::Name>>(group->t)) {
6411             auto *symbol{FindSymbol(name)};
6412             if (!symbol) {
6413               symbol = &MakeSymbol(name, ObjectEntityDetails{});
6414               ApplyImplicitRules(*symbol);
6415             } else if (!ConvertToObjectEntity(symbol->GetUltimate())) {
6416               SayWithDecl(name, *symbol, "'%s' is not a variable"_err_en_US);
6417               context().SetError(*groupSymbol);
6418             }
6419             symbol->GetUltimate().set(Symbol::Flag::InNamelist);
6420             details->add_object(*symbol);
6421           }
6422         }
6423       }
6424     }
6425     deferred->namelistGroups.clear();
6426   }
6427 }
6428 
6429 bool DeclarationVisitor::Pre(const parser::IoControlSpec &x) {
6430   if (const auto *name{std::get_if<parser::Name>(&x.u)}) {
6431     auto *symbol{FindSymbol(*name)};
6432     if (!symbol) {
6433       Say(*name, "Namelist group '%s' not found"_err_en_US);
6434     } else if (!symbol->GetUltimate().has<NamelistDetails>()) {
6435       SayWithDecl(
6436           *name, *symbol, "'%s' is not the name of a namelist group"_err_en_US);
6437     }
6438   }
6439   return true;
6440 }
6441 
6442 bool DeclarationVisitor::Pre(const parser::CommonStmt::Block &x) {
6443   CheckNotInBlock("COMMON"); // C1107
6444   return true;
6445 }
6446 
6447 bool DeclarationVisitor::Pre(const parser::CommonBlockObject &) {
6448   BeginArraySpec();
6449   return true;
6450 }
6451 
6452 void DeclarationVisitor::Post(const parser::CommonBlockObject &x) {
6453   const auto &name{std::get<parser::Name>(x.t)};
6454   DeclareObjectEntity(name);
6455   auto pair{specPartState_.commonBlockObjects.insert(name.source)};
6456   if (!pair.second) {
6457     const SourceName &prev{*pair.first};
6458     Say2(name.source, "'%s' is already in a COMMON block"_err_en_US, prev,
6459         "Previous occurrence of '%s' in a COMMON block"_en_US);
6460   }
6461 }
6462 
6463 bool DeclarationVisitor::Pre(const parser::EquivalenceStmt &x) {
6464   // save equivalence sets to be processed after specification part
6465   if (CheckNotInBlock("EQUIVALENCE")) { // C1107
6466     for (const std::list<parser::EquivalenceObject> &set : x.v) {
6467       specPartState_.equivalenceSets.push_back(&set);
6468     }
6469   }
6470   return false; // don't implicitly declare names yet
6471 }
6472 
6473 void DeclarationVisitor::CheckEquivalenceSets() {
6474   EquivalenceSets equivSets{context()};
6475   inEquivalenceStmt_ = true;
6476   for (const auto *set : specPartState_.equivalenceSets) {
6477     const auto &source{set->front().v.value().source};
6478     if (set->size() <= 1) { // R871
6479       Say(source, "Equivalence set must have more than one object"_err_en_US);
6480     }
6481     for (const parser::EquivalenceObject &object : *set) {
6482       const auto &designator{object.v.value()};
6483       // The designator was not resolved when it was encountered, so do it now.
6484       // AnalyzeExpr causes array sections to be changed to substrings as needed
6485       Walk(designator);
6486       if (AnalyzeExpr(context(), designator)) {
6487         equivSets.AddToSet(designator);
6488       }
6489     }
6490     equivSets.FinishSet(source);
6491   }
6492   inEquivalenceStmt_ = false;
6493   for (auto &set : equivSets.sets()) {
6494     if (!set.empty()) {
6495       currScope().add_equivalenceSet(std::move(set));
6496     }
6497   }
6498   specPartState_.equivalenceSets.clear();
6499 }
6500 
6501 bool DeclarationVisitor::Pre(const parser::SaveStmt &x) {
6502   if (x.v.empty()) {
6503     specPartState_.saveInfo.saveAll = currStmtSource();
6504     currScope().set_hasSAVE();
6505   } else {
6506     for (const parser::SavedEntity &y : x.v) {
6507       auto kind{std::get<parser::SavedEntity::Kind>(y.t)};
6508       const auto &name{std::get<parser::Name>(y.t)};
6509       if (kind == parser::SavedEntity::Kind::Common) {
6510         MakeCommonBlockSymbol(name);
6511         AddSaveName(specPartState_.saveInfo.commons, name.source);
6512       } else {
6513         HandleAttributeStmt(Attr::SAVE, name);
6514       }
6515     }
6516   }
6517   return false;
6518 }
6519 
6520 void DeclarationVisitor::CheckSaveStmts() {
6521   for (const SourceName &name : specPartState_.saveInfo.entities) {
6522     auto *symbol{FindInScope(name)};
6523     if (!symbol) {
6524       // error was reported
6525     } else if (specPartState_.saveInfo.saveAll) {
6526       // C889 - note that pgi, ifort, xlf do not enforce this constraint
6527       if (context().ShouldWarn(common::LanguageFeature::RedundantAttribute)) {
6528         Say2(name,
6529             "Explicit SAVE of '%s' is redundant due to global SAVE statement"_warn_en_US,
6530             *specPartState_.saveInfo.saveAll, "Global SAVE statement"_en_US)
6531             .set_languageFeature(common::LanguageFeature::RedundantAttribute);
6532       }
6533     } else if (!IsSaved(*symbol)) {
6534       SetExplicitAttr(*symbol, Attr::SAVE);
6535     }
6536   }
6537   for (const SourceName &name : specPartState_.saveInfo.commons) {
6538     if (auto *symbol{currScope().FindCommonBlock(name)}) {
6539       auto &objects{symbol->get<CommonBlockDetails>().objects()};
6540       if (objects.empty()) {
6541         if (currScope().kind() != Scope::Kind::BlockConstruct) {
6542           Say(name,
6543               "'%s' appears as a COMMON block in a SAVE statement but not in"
6544               " a COMMON statement"_err_en_US);
6545         } else { // C1108
6546           Say(name,
6547               "SAVE statement in BLOCK construct may not contain a"
6548               " common block name '%s'"_err_en_US);
6549         }
6550       } else {
6551         for (auto &object : symbol->get<CommonBlockDetails>().objects()) {
6552           if (!IsSaved(*object)) {
6553             SetImplicitAttr(*object, Attr::SAVE);
6554           }
6555         }
6556       }
6557     }
6558   }
6559   specPartState_.saveInfo = {};
6560 }
6561 
6562 // Record SAVEd names in specPartState_.saveInfo.entities.
6563 Attrs DeclarationVisitor::HandleSaveName(const SourceName &name, Attrs attrs) {
6564   if (attrs.test(Attr::SAVE)) {
6565     AddSaveName(specPartState_.saveInfo.entities, name);
6566   }
6567   return attrs;
6568 }
6569 
6570 // Record a name in a set of those to be saved.
6571 void DeclarationVisitor::AddSaveName(
6572     std::set<SourceName> &set, const SourceName &name) {
6573   auto pair{set.insert(name)};
6574   if (!pair.second &&
6575       context().ShouldWarn(common::LanguageFeature::RedundantAttribute)) {
6576     Say2(name, "SAVE attribute was already specified on '%s'"_warn_en_US,
6577         *pair.first, "Previous specification of SAVE attribute"_en_US)
6578         .set_languageFeature(common::LanguageFeature::RedundantAttribute);
6579   }
6580 }
6581 
6582 // Check types of common block objects, now that they are known.
6583 void DeclarationVisitor::CheckCommonBlocks() {
6584   // check for empty common blocks
6585   for (const auto &pair : currScope().commonBlocks()) {
6586     const auto &symbol{*pair.second};
6587     if (symbol.get<CommonBlockDetails>().objects().empty() &&
6588         symbol.attrs().test(Attr::BIND_C)) {
6589       Say(symbol.name(),
6590           "'%s' appears as a COMMON block in a BIND statement but not in"
6591           " a COMMON statement"_err_en_US);
6592     }
6593   }
6594   // check objects in common blocks
6595   for (const auto &name : specPartState_.commonBlockObjects) {
6596     const auto *symbol{currScope().FindSymbol(name)};
6597     if (!symbol) {
6598       continue;
6599     }
6600     const auto &attrs{symbol->attrs()};
6601     if (attrs.test(Attr::ALLOCATABLE)) {
6602       Say(name,
6603           "ALLOCATABLE object '%s' may not appear in a COMMON block"_err_en_US);
6604     } else if (attrs.test(Attr::BIND_C)) {
6605       Say(name,
6606           "Variable '%s' with BIND attribute may not appear in a COMMON block"_err_en_US);
6607     } else if (IsNamedConstant(*symbol)) {
6608       Say(name,
6609           "A named constant '%s' may not appear in a COMMON block"_err_en_US);
6610     } else if (IsDummy(*symbol)) {
6611       Say(name,
6612           "Dummy argument '%s' may not appear in a COMMON block"_err_en_US);
6613     } else if (symbol->IsFuncResult()) {
6614       Say(name,
6615           "Function result '%s' may not appear in a COMMON block"_err_en_US);
6616     } else if (const DeclTypeSpec * type{symbol->GetType()}) {
6617       if (type->category() == DeclTypeSpec::ClassStar) {
6618         Say(name,
6619             "Unlimited polymorphic pointer '%s' may not appear in a COMMON block"_err_en_US);
6620       } else if (const auto *derived{type->AsDerived()}) {
6621         if (!IsSequenceOrBindCType(derived)) {
6622           Say(name,
6623               "Derived type '%s' in COMMON block must have the BIND or"
6624               " SEQUENCE attribute"_err_en_US);
6625         }
6626         UnorderedSymbolSet typeSet;
6627         CheckCommonBlockDerivedType(name, derived->typeSymbol(), typeSet);
6628       }
6629     }
6630   }
6631   specPartState_.commonBlockObjects = {};
6632 }
6633 
6634 Symbol &DeclarationVisitor::MakeCommonBlockSymbol(const parser::Name &name) {
6635   return Resolve(name, currScope().MakeCommonBlock(name.source));
6636 }
6637 Symbol &DeclarationVisitor::MakeCommonBlockSymbol(
6638     const std::optional<parser::Name> &name) {
6639   if (name) {
6640     return MakeCommonBlockSymbol(*name);
6641   } else {
6642     return MakeCommonBlockSymbol(parser::Name{});
6643   }
6644 }
6645 
6646 bool DeclarationVisitor::NameIsKnownOrIntrinsic(const parser::Name &name) {
6647   return FindSymbol(name) || HandleUnrestrictedSpecificIntrinsicFunction(name);
6648 }
6649 
6650 // Check if this derived type can be in a COMMON block.
6651 void DeclarationVisitor::CheckCommonBlockDerivedType(const SourceName &name,
6652     const Symbol &typeSymbol, UnorderedSymbolSet &typeSet) {
6653   if (auto iter{typeSet.find(SymbolRef{typeSymbol})}; iter != typeSet.end()) {
6654     return;
6655   }
6656   typeSet.emplace(typeSymbol);
6657   if (const auto *scope{typeSymbol.scope()}) {
6658     for (const auto &pair : *scope) {
6659       const Symbol &component{*pair.second};
6660       if (component.attrs().test(Attr::ALLOCATABLE)) {
6661         Say2(name,
6662             "Derived type variable '%s' may not appear in a COMMON block"
6663             " due to ALLOCATABLE component"_err_en_US,
6664             component.name(), "Component with ALLOCATABLE attribute"_en_US);
6665         return;
6666       }
6667       const auto *details{component.detailsIf<ObjectEntityDetails>()};
6668       if (component.test(Symbol::Flag::InDataStmt) ||
6669           (details && details->init())) {
6670         Say2(name,
6671             "Derived type variable '%s' may not appear in a COMMON block due to component with default initialization"_err_en_US,
6672             component.name(), "Component with default initialization"_en_US);
6673         return;
6674       }
6675       if (details) {
6676         if (const auto *type{details->type()}) {
6677           if (const auto *derived{type->AsDerived()}) {
6678             const Symbol &derivedTypeSymbol{derived->typeSymbol()};
6679             CheckCommonBlockDerivedType(name, derivedTypeSymbol, typeSet);
6680           }
6681         }
6682       }
6683     }
6684   }
6685 }
6686 
6687 bool DeclarationVisitor::HandleUnrestrictedSpecificIntrinsicFunction(
6688     const parser::Name &name) {
6689   if (auto interface{context().intrinsics().IsSpecificIntrinsicFunction(
6690           name.source.ToString())}) {
6691     // Unrestricted specific intrinsic function names (e.g., "cos")
6692     // are acceptable as procedure interfaces.  The presence of the
6693     // INTRINSIC flag will cause this symbol to have a complete interface
6694     // recreated for it later on demand, but capturing its result type here
6695     // will make GetType() return a correct result without having to
6696     // probe the intrinsics table again.
6697     Symbol &symbol{MakeSymbol(InclusiveScope(), name.source, Attrs{})};
6698     SetImplicitAttr(symbol, Attr::INTRINSIC);
6699     CHECK(interface->functionResult.has_value());
6700     evaluate::DynamicType dyType{
6701         DEREF(interface->functionResult->GetTypeAndShape()).type()};
6702     CHECK(common::IsNumericTypeCategory(dyType.category()));
6703     const DeclTypeSpec &typeSpec{
6704         MakeNumericType(dyType.category(), dyType.kind())};
6705     ProcEntityDetails details;
6706     details.set_type(typeSpec);
6707     symbol.set_details(std::move(details));
6708     symbol.set(Symbol::Flag::Function);
6709     if (interface->IsElemental()) {
6710       SetExplicitAttr(symbol, Attr::ELEMENTAL);
6711     }
6712     if (interface->IsPure()) {
6713       SetExplicitAttr(symbol, Attr::PURE);
6714     }
6715     Resolve(name, symbol);
6716     return true;
6717   } else {
6718     return false;
6719   }
6720 }
6721 
6722 // Checks for all locality-specs: LOCAL, LOCAL_INIT, and SHARED
6723 bool DeclarationVisitor::PassesSharedLocalityChecks(
6724     const parser::Name &name, Symbol &symbol) {
6725   if (!IsVariableName(symbol)) {
6726     SayLocalMustBeVariable(name, symbol); // C1124
6727     return false;
6728   }
6729   if (symbol.owner() == currScope()) { // C1125 and C1126
6730     SayAlreadyDeclared(name, symbol);
6731     return false;
6732   }
6733   return true;
6734 }
6735 
6736 // Checks for locality-specs LOCAL, LOCAL_INIT, and REDUCE
6737 bool DeclarationVisitor::PassesLocalityChecks(
6738     const parser::Name &name, Symbol &symbol, Symbol::Flag flag) {
6739   bool isReduce{flag == Symbol::Flag::LocalityReduce};
6740   const char *specName{
6741       flag == Symbol::Flag::LocalityLocalInit ? "LOCAL_INIT" : "LOCAL"};
6742   if (IsAllocatable(symbol) && !isReduce) { // F'2023 C1130
6743     SayWithDecl(name, symbol,
6744         "ALLOCATABLE variable '%s' not allowed in a %s locality-spec"_err_en_US,
6745         specName);
6746     return false;
6747   }
6748   if (IsOptional(symbol)) { // F'2023 C1130-C1131
6749     SayWithDecl(name, symbol,
6750         "OPTIONAL argument '%s' not allowed in a locality-spec"_err_en_US);
6751     return false;
6752   }
6753   if (IsIntentIn(symbol)) { // F'2023 C1130-C1131
6754     SayWithDecl(name, symbol,
6755         "INTENT IN argument '%s' not allowed in a locality-spec"_err_en_US);
6756     return false;
6757   }
6758   if (IsFinalizable(symbol) && !isReduce) { // F'2023 C1130
6759     SayWithDecl(name, symbol,
6760         "Finalizable variable '%s' not allowed in a %s locality-spec"_err_en_US,
6761         specName);
6762     return false;
6763   }
6764   if (evaluate::IsCoarray(symbol) && !isReduce) { // F'2023 C1130
6765     SayWithDecl(name, symbol,
6766         "Coarray '%s' not allowed in a %s locality-spec"_err_en_US, specName);
6767     return false;
6768   }
6769   if (const DeclTypeSpec * type{symbol.GetType()}) {
6770     if (type->IsPolymorphic() && IsDummy(symbol) && !IsPointer(symbol) &&
6771         !isReduce) { // F'2023 C1130
6772       SayWithDecl(name, symbol,
6773           "Nonpointer polymorphic argument '%s' not allowed in a %s locality-spec"_err_en_US,
6774           specName);
6775       return false;
6776     }
6777   }
6778   if (symbol.attrs().test(Attr::ASYNCHRONOUS) && isReduce) { // F'2023 C1131
6779     SayWithDecl(name, symbol,
6780         "ASYNCHRONOUS variable '%s' not allowed in a REDUCE locality-spec"_err_en_US);
6781     return false;
6782   }
6783   if (symbol.attrs().test(Attr::VOLATILE) && isReduce) { // F'2023 C1131
6784     SayWithDecl(name, symbol,
6785         "VOLATILE variable '%s' not allowed in a REDUCE locality-spec"_err_en_US);
6786     return false;
6787   }
6788   if (IsAssumedSizeArray(symbol)) { // F'2023 C1130-C1131
6789     SayWithDecl(name, symbol,
6790         "Assumed size array '%s' not allowed in a locality-spec"_err_en_US);
6791     return false;
6792   }
6793   if (std::optional<Message> whyNot{WhyNotDefinable(
6794           name.source, currScope(), DefinabilityFlags{}, symbol)}) {
6795     SayWithReason(name, symbol,
6796         "'%s' may not appear in a locality-spec because it is not definable"_err_en_US,
6797         std::move(whyNot->set_severity(parser::Severity::Because)));
6798     return false;
6799   }
6800   return PassesSharedLocalityChecks(name, symbol);
6801 }
6802 
6803 Symbol &DeclarationVisitor::FindOrDeclareEnclosingEntity(
6804     const parser::Name &name) {
6805   Symbol *prev{FindSymbol(name)};
6806   if (!prev) {
6807     // Declare the name as an object in the enclosing scope so that
6808     // the name can't be repurposed there later as something else.
6809     prev = &MakeSymbol(InclusiveScope(), name.source, Attrs{});
6810     ConvertToObjectEntity(*prev);
6811     ApplyImplicitRules(*prev);
6812   }
6813   return *prev;
6814 }
6815 
6816 void DeclarationVisitor::DeclareLocalEntity(
6817     const parser::Name &name, Symbol::Flag flag) {
6818   Symbol &prev{FindOrDeclareEnclosingEntity(name)};
6819   if (PassesLocalityChecks(name, prev, flag)) {
6820     if (auto *symbol{&MakeHostAssocSymbol(name, prev)}) {
6821       symbol->set(flag);
6822     }
6823   }
6824 }
6825 
6826 Symbol *DeclarationVisitor::DeclareStatementEntity(
6827     const parser::DoVariable &doVar,
6828     const std::optional<parser::IntegerTypeSpec> &type) {
6829   const parser::Name &name{doVar.thing.thing};
6830   const DeclTypeSpec *declTypeSpec{nullptr};
6831   if (auto *prev{FindSymbol(name)}) {
6832     if (prev->owner() == currScope()) {
6833       SayAlreadyDeclared(name, *prev);
6834       return nullptr;
6835     }
6836     name.symbol = nullptr;
6837     // F'2023 19.4 p5 ambiguous rule about outer declarations
6838     declTypeSpec = prev->GetType();
6839   }
6840   Symbol &symbol{DeclareEntity<ObjectEntityDetails>(name, {})};
6841   if (!symbol.has<ObjectEntityDetails>()) {
6842     return nullptr; // error was reported in DeclareEntity
6843   }
6844   if (type) {
6845     declTypeSpec = ProcessTypeSpec(*type);
6846   }
6847   if (declTypeSpec) {
6848     // Subtlety: Don't let a "*length" specifier (if any is pending) affect the
6849     // declaration of this implied DO loop control variable.
6850     auto restorer{
6851         common::ScopedSet(charInfo_.length, std::optional<ParamValue>{})};
6852     SetType(name, *declTypeSpec);
6853   } else {
6854     ApplyImplicitRules(symbol);
6855   }
6856   return Resolve(name, &symbol);
6857 }
6858 
6859 // Set the type of an entity or report an error.
6860 void DeclarationVisitor::SetType(
6861     const parser::Name &name, const DeclTypeSpec &type) {
6862   CHECK(name.symbol);
6863   auto &symbol{*name.symbol};
6864   if (charInfo_.length) { // Declaration has "*length" (R723)
6865     auto length{std::move(*charInfo_.length)};
6866     charInfo_.length.reset();
6867     if (type.category() == DeclTypeSpec::Character) {
6868       auto kind{type.characterTypeSpec().kind()};
6869       // Recurse with correct type.
6870       SetType(name,
6871           currScope().MakeCharacterType(std::move(length), std::move(kind)));
6872       return;
6873     } else { // C753
6874       Say(name,
6875           "A length specifier cannot be used to declare the non-character entity '%s'"_err_en_US);
6876     }
6877   }
6878   if (auto *proc{symbol.detailsIf<ProcEntityDetails>()}) {
6879     if (proc->procInterface()) {
6880       Say(name,
6881           "'%s' has an explicit interface and may not also have a type"_err_en_US);
6882       context().SetError(symbol);
6883       return;
6884     }
6885   }
6886   auto *prevType{symbol.GetType()};
6887   if (!prevType) {
6888     if (symbol.test(Symbol::Flag::InDataStmt) && isImplicitNoneType()) {
6889       context().Warn(common::LanguageFeature::ForwardRefImplicitNoneData,
6890           name.source,
6891           "'%s' appeared in a DATA statement before its type was declared under IMPLICIT NONE(TYPE)"_port_en_US,
6892           name.source);
6893     }
6894     symbol.SetType(type);
6895   } else if (symbol.has<UseDetails>()) {
6896     // error recovery case, redeclaration of use-associated name
6897   } else if (HadForwardRef(symbol)) {
6898     // error recovery after use of host-associated name
6899   } else if (!symbol.test(Symbol::Flag::Implicit)) {
6900     SayWithDecl(
6901         name, symbol, "The type of '%s' has already been declared"_err_en_US);
6902     context().SetError(symbol);
6903   } else if (type != *prevType) {
6904     SayWithDecl(name, symbol,
6905         "The type of '%s' has already been implicitly declared"_err_en_US);
6906     context().SetError(symbol);
6907   } else {
6908     symbol.set(Symbol::Flag::Implicit, false);
6909   }
6910 }
6911 
6912 std::optional<DerivedTypeSpec> DeclarationVisitor::ResolveDerivedType(
6913     const parser::Name &name) {
6914   Scope &outer{NonDerivedTypeScope()};
6915   Symbol *symbol{FindSymbol(outer, name)};
6916   Symbol *ultimate{symbol ? &symbol->GetUltimate() : nullptr};
6917   auto *generic{ultimate ? ultimate->detailsIf<GenericDetails>() : nullptr};
6918   if (generic) {
6919     if (Symbol * genDT{generic->derivedType()}) {
6920       symbol = genDT;
6921       generic = nullptr;
6922     }
6923   }
6924   if (!symbol || symbol->has<UnknownDetails>() ||
6925       (generic && &ultimate->owner() == &outer)) {
6926     if (allowForwardReferenceToDerivedType()) {
6927       if (!symbol) {
6928         symbol = &MakeSymbol(outer, name.source, Attrs{});
6929         Resolve(name, *symbol);
6930       } else if (generic) {
6931         // forward ref to type with later homonymous generic
6932         symbol = &outer.MakeSymbol(name.source, Attrs{}, UnknownDetails{});
6933         generic->set_derivedType(*symbol);
6934         name.symbol = symbol;
6935       }
6936       DerivedTypeDetails details;
6937       details.set_isForwardReferenced(true);
6938       symbol->set_details(std::move(details));
6939     } else { // C732
6940       Say(name, "Derived type '%s' not found"_err_en_US);
6941       return std::nullopt;
6942     }
6943   } else if (&DEREF(symbol).owner() != &outer &&
6944       !ultimate->has<GenericDetails>()) {
6945     // Prevent a later declaration in this scope of a host-associated
6946     // type name.
6947     outer.add_importName(name.source);
6948   }
6949   if (CheckUseError(name)) {
6950     return std::nullopt;
6951   } else if (symbol->GetUltimate().has<DerivedTypeDetails>()) {
6952     return DerivedTypeSpec{name.source, *symbol};
6953   } else {
6954     Say(name, "'%s' is not a derived type"_err_en_US);
6955     return std::nullopt;
6956   }
6957 }
6958 
6959 std::optional<DerivedTypeSpec> DeclarationVisitor::ResolveExtendsType(
6960     const parser::Name &typeName, const parser::Name *extendsName) {
6961   if (extendsName) {
6962     if (typeName.source == extendsName->source) {
6963       Say(extendsName->source,
6964           "Derived type '%s' cannot extend itself"_err_en_US);
6965     } else if (auto dtSpec{ResolveDerivedType(*extendsName)}) {
6966       if (!dtSpec->IsForwardReferenced()) {
6967         return dtSpec;
6968       }
6969       Say(typeName.source,
6970           "Derived type '%s' cannot extend type '%s' that has not yet been defined"_err_en_US,
6971           typeName.source, extendsName->source);
6972     }
6973   }
6974   return std::nullopt;
6975 }
6976 
6977 Symbol *DeclarationVisitor::NoteInterfaceName(const parser::Name &name) {
6978   // The symbol is checked later by CheckExplicitInterface() and
6979   // CheckBindings().  It can be a forward reference.
6980   if (!NameIsKnownOrIntrinsic(name)) {
6981     Symbol &symbol{MakeSymbol(InclusiveScope(), name.source, Attrs{})};
6982     Resolve(name, symbol);
6983   }
6984   return name.symbol;
6985 }
6986 
6987 void DeclarationVisitor::CheckExplicitInterface(const parser::Name &name) {
6988   if (const Symbol * symbol{name.symbol}) {
6989     const Symbol &ultimate{symbol->GetUltimate()};
6990     if (!context().HasError(*symbol) && !context().HasError(ultimate) &&
6991         !BypassGeneric(ultimate).HasExplicitInterface()) {
6992       Say(name,
6993           "'%s' must be an abstract interface or a procedure with an explicit interface"_err_en_US,
6994           symbol->name());
6995     }
6996   }
6997 }
6998 
6999 // Create a symbol for a type parameter, component, or procedure binding in
7000 // the current derived type scope. Return false on error.
7001 Symbol *DeclarationVisitor::MakeTypeSymbol(
7002     const parser::Name &name, Details &&details) {
7003   return Resolve(name, MakeTypeSymbol(name.source, std::move(details)));
7004 }
7005 Symbol *DeclarationVisitor::MakeTypeSymbol(
7006     const SourceName &name, Details &&details) {
7007   Scope &derivedType{currScope()};
7008   CHECK(derivedType.IsDerivedType());
7009   if (auto *symbol{FindInScope(derivedType, name)}) { // C742
7010     Say2(name,
7011         "Type parameter, component, or procedure binding '%s'"
7012         " already defined in this type"_err_en_US,
7013         *symbol, "Previous definition of '%s'"_en_US);
7014     return nullptr;
7015   } else {
7016     auto attrs{GetAttrs()};
7017     // Apply binding-private-stmt if present and this is a procedure binding
7018     if (derivedTypeInfo_.privateBindings &&
7019         !attrs.HasAny({Attr::PUBLIC, Attr::PRIVATE}) &&
7020         std::holds_alternative<ProcBindingDetails>(details)) {
7021       attrs.set(Attr::PRIVATE);
7022     }
7023     Symbol &result{MakeSymbol(name, attrs, std::move(details))};
7024     SetCUDADataAttr(name, result, cudaDataAttr());
7025     return &result;
7026   }
7027 }
7028 
7029 // Return true if it is ok to declare this component in the current scope.
7030 // Otherwise, emit an error and return false.
7031 bool DeclarationVisitor::OkToAddComponent(
7032     const parser::Name &name, const Symbol *extends) {
7033   for (const Scope *scope{&currScope()}; scope;) {
7034     CHECK(scope->IsDerivedType());
7035     if (auto *prev{FindInScope(*scope, name.source)}) {
7036       std::optional<parser::MessageFixedText> msg;
7037       std::optional<common::UsageWarning> warning;
7038       if (context().HasError(*prev)) { // don't pile on
7039       } else if (extends) {
7040         msg = "Type cannot be extended as it has a component named"
7041               " '%s'"_err_en_US;
7042       } else if (CheckAccessibleSymbol(currScope(), *prev)) {
7043         // inaccessible component -- redeclaration is ok
7044         if (context().ShouldWarn(
7045                 common::UsageWarning::RedeclaredInaccessibleComponent)) {
7046           msg =
7047               "Component '%s' is inaccessibly declared in or as a parent of this derived type"_warn_en_US;
7048           warning = common::UsageWarning::RedeclaredInaccessibleComponent;
7049         }
7050       } else if (prev->test(Symbol::Flag::ParentComp)) {
7051         msg =
7052             "'%s' is a parent type of this type and so cannot be a component"_err_en_US;
7053       } else if (scope == &currScope()) {
7054         msg =
7055             "Component '%s' is already declared in this derived type"_err_en_US;
7056       } else {
7057         msg =
7058             "Component '%s' is already declared in a parent of this derived type"_err_en_US;
7059       }
7060       if (msg) {
7061         auto &said{Say2(name, std::move(*msg), *prev,
7062             "Previous declaration of '%s'"_en_US)};
7063         if (msg->severity() == parser::Severity::Error) {
7064           Resolve(name, *prev);
7065           return false;
7066         }
7067         if (warning) {
7068           said.set_usageWarning(*warning);
7069         }
7070       }
7071     }
7072     if (scope == &currScope() && extends) {
7073       // The parent component has not yet been added to the scope.
7074       scope = extends->scope();
7075     } else {
7076       scope = scope->GetDerivedTypeParent();
7077     }
7078   }
7079   return true;
7080 }
7081 
7082 ParamValue DeclarationVisitor::GetParamValue(
7083     const parser::TypeParamValue &x, common::TypeParamAttr attr) {
7084   return common::visit(
7085       common::visitors{
7086           [=](const parser::ScalarIntExpr &x) { // C704
7087             return ParamValue{EvaluateIntExpr(x), attr};
7088           },
7089           [=](const parser::Star &) { return ParamValue::Assumed(attr); },
7090           [=](const parser::TypeParamValue::Deferred &) {
7091             return ParamValue::Deferred(attr);
7092           },
7093       },
7094       x.u);
7095 }
7096 
7097 // ConstructVisitor implementation
7098 
7099 void ConstructVisitor::ResolveIndexName(
7100     const parser::ConcurrentControl &control) {
7101   const parser::Name &name{std::get<parser::Name>(control.t)};
7102   auto *prev{FindSymbol(name)};
7103   if (prev) {
7104     if (prev->owner() == currScope()) {
7105       SayAlreadyDeclared(name, *prev);
7106       return;
7107     } else if (prev->owner().kind() == Scope::Kind::Forall &&
7108         context().ShouldWarn(
7109             common::LanguageFeature::OddIndexVariableRestrictions)) {
7110       SayWithDecl(name, *prev,
7111           "Index variable '%s' should not also be an index in an enclosing FORALL or DO CONCURRENT"_port_en_US)
7112           .set_languageFeature(
7113               common::LanguageFeature::OddIndexVariableRestrictions);
7114     }
7115     name.symbol = nullptr;
7116   }
7117   auto &symbol{DeclareObjectEntity(name)};
7118   if (symbol.GetType()) {
7119     // type came from explicit type-spec
7120   } else if (!prev) {
7121     ApplyImplicitRules(symbol);
7122   } else {
7123     // Odd rules in F'2023 19.4 paras 6 & 8.
7124     Symbol &prevRoot{prev->GetUltimate()};
7125     if (const auto *type{prevRoot.GetType()}) {
7126       symbol.SetType(*type);
7127     } else {
7128       ApplyImplicitRules(symbol);
7129     }
7130     if (prevRoot.has<ObjectEntityDetails>() ||
7131         ConvertToObjectEntity(prevRoot)) {
7132       if (prevRoot.IsObjectArray() &&
7133           context().ShouldWarn(
7134               common::LanguageFeature::OddIndexVariableRestrictions)) {
7135         SayWithDecl(name, *prev,
7136             "Index variable '%s' should be scalar in the enclosing scope"_port_en_US)
7137             .set_languageFeature(
7138                 common::LanguageFeature::OddIndexVariableRestrictions);
7139       }
7140     } else if (!prevRoot.has<CommonBlockDetails>() &&
7141         context().ShouldWarn(
7142             common::LanguageFeature::OddIndexVariableRestrictions)) {
7143       SayWithDecl(name, *prev,
7144           "Index variable '%s' should be a scalar object or common block if it is present in the enclosing scope"_port_en_US)
7145           .set_languageFeature(
7146               common::LanguageFeature::OddIndexVariableRestrictions);
7147     }
7148   }
7149   EvaluateExpr(parser::Scalar{parser::Integer{common::Clone(name)}});
7150 }
7151 
7152 // We need to make sure that all of the index-names get declared before the
7153 // expressions in the loop control are evaluated so that references to the
7154 // index-names in the expressions are correctly detected.
7155 bool ConstructVisitor::Pre(const parser::ConcurrentHeader &header) {
7156   BeginDeclTypeSpec();
7157   Walk(std::get<std::optional<parser::IntegerTypeSpec>>(header.t));
7158   const auto &controls{
7159       std::get<std::list<parser::ConcurrentControl>>(header.t)};
7160   for (const auto &control : controls) {
7161     ResolveIndexName(control);
7162   }
7163   Walk(controls);
7164   Walk(std::get<std::optional<parser::ScalarLogicalExpr>>(header.t));
7165   EndDeclTypeSpec();
7166   return false;
7167 }
7168 
7169 bool ConstructVisitor::Pre(const parser::LocalitySpec::Local &x) {
7170   for (auto &name : x.v) {
7171     DeclareLocalEntity(name, Symbol::Flag::LocalityLocal);
7172   }
7173   return false;
7174 }
7175 
7176 bool ConstructVisitor::Pre(const parser::LocalitySpec::LocalInit &x) {
7177   for (auto &name : x.v) {
7178     DeclareLocalEntity(name, Symbol::Flag::LocalityLocalInit);
7179   }
7180   return false;
7181 }
7182 
7183 bool ConstructVisitor::Pre(const parser::LocalitySpec::Reduce &x) {
7184   for (const auto &name : std::get<std::list<parser::Name>>(x.t)) {
7185     DeclareLocalEntity(name, Symbol::Flag::LocalityReduce);
7186   }
7187   return false;
7188 }
7189 
7190 bool ConstructVisitor::Pre(const parser::LocalitySpec::Shared &x) {
7191   for (const auto &name : x.v) {
7192     if (!FindSymbol(name)) {
7193       context().Warn(common::UsageWarning::ImplicitShared, name.source,
7194           "Variable '%s' with SHARED locality implicitly declared"_warn_en_US,
7195           name.source);
7196     }
7197     Symbol &prev{FindOrDeclareEnclosingEntity(name)};
7198     if (PassesSharedLocalityChecks(name, prev)) {
7199       MakeHostAssocSymbol(name, prev).set(Symbol::Flag::LocalityShared);
7200     }
7201   }
7202   return false;
7203 }
7204 
7205 bool ConstructVisitor::Pre(const parser::AcSpec &x) {
7206   ProcessTypeSpec(x.type);
7207   Walk(x.values);
7208   return false;
7209 }
7210 
7211 // Section 19.4, paragraph 5 says that each ac-do-variable has the scope of the
7212 // enclosing ac-implied-do
7213 bool ConstructVisitor::Pre(const parser::AcImpliedDo &x) {
7214   auto &values{std::get<std::list<parser::AcValue>>(x.t)};
7215   auto &control{std::get<parser::AcImpliedDoControl>(x.t)};
7216   auto &type{std::get<std::optional<parser::IntegerTypeSpec>>(control.t)};
7217   auto &bounds{std::get<parser::AcImpliedDoControl::Bounds>(control.t)};
7218   // F'2018 has the scope of the implied DO variable covering the entire
7219   // implied DO production (19.4(5)), which seems wrong in cases where the name
7220   // of the implied DO variable appears in one of the bound expressions. Thus
7221   // this extension, which shrinks the scope of the variable to exclude the
7222   // expressions in the bounds.
7223   auto restore{BeginCheckOnIndexUseInOwnBounds(bounds.name)};
7224   Walk(bounds.lower);
7225   Walk(bounds.upper);
7226   Walk(bounds.step);
7227   EndCheckOnIndexUseInOwnBounds(restore);
7228   PushScope(Scope::Kind::ImpliedDos, nullptr);
7229   DeclareStatementEntity(bounds.name, type);
7230   Walk(values);
7231   PopScope();
7232   return false;
7233 }
7234 
7235 bool ConstructVisitor::Pre(const parser::DataImpliedDo &x) {
7236   auto &objects{std::get<std::list<parser::DataIDoObject>>(x.t)};
7237   auto &type{std::get<std::optional<parser::IntegerTypeSpec>>(x.t)};
7238   auto &bounds{std::get<parser::DataImpliedDo::Bounds>(x.t)};
7239   // See comment in Pre(AcImpliedDo) above.
7240   auto restore{BeginCheckOnIndexUseInOwnBounds(bounds.name)};
7241   Walk(bounds.lower);
7242   Walk(bounds.upper);
7243   Walk(bounds.step);
7244   EndCheckOnIndexUseInOwnBounds(restore);
7245   bool pushScope{currScope().kind() != Scope::Kind::ImpliedDos};
7246   if (pushScope) {
7247     PushScope(Scope::Kind::ImpliedDos, nullptr);
7248   }
7249   DeclareStatementEntity(bounds.name, type);
7250   Walk(objects);
7251   if (pushScope) {
7252     PopScope();
7253   }
7254   return false;
7255 }
7256 
7257 // Sets InDataStmt flag on a variable (or misidentified function) in a DATA
7258 // statement so that the predicate IsInitialized() will be true
7259 // during semantic analysis before the symbol's initializer is constructed.
7260 bool ConstructVisitor::Pre(const parser::DataIDoObject &x) {
7261   common::visit(
7262       common::visitors{
7263           [&](const parser::Scalar<Indirection<parser::Designator>> &y) {
7264             Walk(y.thing.value());
7265             const parser::Name &first{parser::GetFirstName(y.thing.value())};
7266             if (first.symbol) {
7267               first.symbol->set(Symbol::Flag::InDataStmt);
7268             }
7269           },
7270           [&](const Indirection<parser::DataImpliedDo> &y) { Walk(y.value()); },
7271       },
7272       x.u);
7273   return false;
7274 }
7275 
7276 bool ConstructVisitor::Pre(const parser::DataStmtObject &x) {
7277   // Subtle: DATA statements may appear in both the specification and
7278   // execution parts, but should be treated as if in the execution part
7279   // for purposes of implicit variable declaration vs. host association.
7280   // When a name first appears as an object in a DATA statement, it should
7281   // be implicitly declared locally as if it had been assigned.
7282   auto flagRestorer{common::ScopedSet(inSpecificationPart_, false)};
7283   common::visit(
7284       common::visitors{
7285           [&](const Indirection<parser::Variable> &y) {
7286             auto restorer{common::ScopedSet(deferImplicitTyping_, true)};
7287             Walk(y.value());
7288             const parser::Name &first{parser::GetFirstName(y.value())};
7289             if (first.symbol) {
7290               first.symbol->set(Symbol::Flag::InDataStmt);
7291             }
7292           },
7293           [&](const parser::DataImpliedDo &y) {
7294             PushScope(Scope::Kind::ImpliedDos, nullptr);
7295             Walk(y);
7296             PopScope();
7297           },
7298       },
7299       x.u);
7300   return false;
7301 }
7302 
7303 bool ConstructVisitor::Pre(const parser::DataStmtValue &x) {
7304   const auto &data{std::get<parser::DataStmtConstant>(x.t)};
7305   auto &mutableData{const_cast<parser::DataStmtConstant &>(data)};
7306   if (auto *elem{parser::Unwrap<parser::ArrayElement>(mutableData)}) {
7307     if (const auto *name{std::get_if<parser::Name>(&elem->base.u)}) {
7308       if (const Symbol * symbol{FindSymbol(*name)};
7309           symbol && symbol->GetUltimate().has<DerivedTypeDetails>()) {
7310         mutableData.u = elem->ConvertToStructureConstructor(
7311             DerivedTypeSpec{name->source, *symbol});
7312       }
7313     }
7314   }
7315   return true;
7316 }
7317 
7318 bool ConstructVisitor::Pre(const parser::DoConstruct &x) {
7319   if (x.IsDoConcurrent()) {
7320     // The new scope has Kind::Forall for index variable name conflict
7321     // detection with nested FORALL/DO CONCURRENT constructs in
7322     // ResolveIndexName().
7323     PushScope(Scope::Kind::Forall, nullptr);
7324   }
7325   return true;
7326 }
7327 void ConstructVisitor::Post(const parser::DoConstruct &x) {
7328   if (x.IsDoConcurrent()) {
7329     PopScope();
7330   }
7331 }
7332 
7333 bool ConstructVisitor::Pre(const parser::ForallConstruct &) {
7334   PushScope(Scope::Kind::Forall, nullptr);
7335   return true;
7336 }
7337 void ConstructVisitor::Post(const parser::ForallConstruct &) { PopScope(); }
7338 bool ConstructVisitor::Pre(const parser::ForallStmt &) {
7339   PushScope(Scope::Kind::Forall, nullptr);
7340   return true;
7341 }
7342 void ConstructVisitor::Post(const parser::ForallStmt &) { PopScope(); }
7343 
7344 bool ConstructVisitor::Pre(const parser::BlockConstruct &x) {
7345   const auto &[blockStmt, specPart, execPart, endBlockStmt] = x.t;
7346   Walk(blockStmt);
7347   CheckDef(blockStmt.statement.v);
7348   PushScope(Scope::Kind::BlockConstruct, nullptr);
7349   Walk(specPart);
7350   HandleImpliedAsynchronousInScope(execPart);
7351   Walk(execPart);
7352   Walk(endBlockStmt);
7353   PopScope();
7354   CheckRef(endBlockStmt.statement.v);
7355   return false;
7356 }
7357 
7358 void ConstructVisitor::Post(const parser::Selector &x) {
7359   GetCurrentAssociation().selector = ResolveSelector(x);
7360 }
7361 
7362 void ConstructVisitor::Post(const parser::AssociateStmt &x) {
7363   CheckDef(x.t);
7364   PushScope(Scope::Kind::OtherConstruct, nullptr);
7365   const auto assocCount{std::get<std::list<parser::Association>>(x.t).size()};
7366   for (auto nthLastAssoc{assocCount}; nthLastAssoc > 0; --nthLastAssoc) {
7367     SetCurrentAssociation(nthLastAssoc);
7368     if (auto *symbol{MakeAssocEntity()}) {
7369       const MaybeExpr &expr{GetCurrentAssociation().selector.expr};
7370       if (ExtractCoarrayRef(expr)) { // C1103
7371         Say("Selector must not be a coindexed object"_err_en_US);
7372       }
7373       if (evaluate::IsAssumedRank(expr)) {
7374         Say("Selector must not be assumed-rank"_err_en_US);
7375       }
7376       SetTypeFromAssociation(*symbol);
7377       SetAttrsFromAssociation(*symbol);
7378     }
7379   }
7380   PopAssociation(assocCount);
7381 }
7382 
7383 void ConstructVisitor::Post(const parser::EndAssociateStmt &x) {
7384   PopScope();
7385   CheckRef(x.v);
7386 }
7387 
7388 bool ConstructVisitor::Pre(const parser::Association &x) {
7389   PushAssociation();
7390   const auto &name{std::get<parser::Name>(x.t)};
7391   GetCurrentAssociation().name = &name;
7392   return true;
7393 }
7394 
7395 bool ConstructVisitor::Pre(const parser::ChangeTeamStmt &x) {
7396   CheckDef(x.t);
7397   PushScope(Scope::Kind::OtherConstruct, nullptr);
7398   PushAssociation();
7399   return true;
7400 }
7401 
7402 void ConstructVisitor::Post(const parser::CoarrayAssociation &x) {
7403   const auto &decl{std::get<parser::CodimensionDecl>(x.t)};
7404   const auto &name{std::get<parser::Name>(decl.t)};
7405   if (auto *symbol{FindInScope(name)}) {
7406     const auto &selector{std::get<parser::Selector>(x.t)};
7407     if (auto sel{ResolveSelector(selector)}) {
7408       const Symbol *whole{UnwrapWholeSymbolDataRef(sel.expr)};
7409       if (!whole || whole->Corank() == 0) {
7410         Say(sel.source, // C1116
7411             "Selector in coarray association must name a coarray"_err_en_US);
7412       } else if (auto dynType{sel.expr->GetType()}) {
7413         if (!symbol->GetType()) {
7414           symbol->SetType(ToDeclTypeSpec(std::move(*dynType)));
7415         }
7416       }
7417     }
7418   }
7419 }
7420 
7421 void ConstructVisitor::Post(const parser::EndChangeTeamStmt &x) {
7422   PopAssociation();
7423   PopScope();
7424   CheckRef(x.t);
7425 }
7426 
7427 bool ConstructVisitor::Pre(const parser::SelectTypeConstruct &) {
7428   PushAssociation();
7429   return true;
7430 }
7431 
7432 void ConstructVisitor::Post(const parser::SelectTypeConstruct &) {
7433   PopAssociation();
7434 }
7435 
7436 void ConstructVisitor::Post(const parser::SelectTypeStmt &x) {
7437   auto &association{GetCurrentAssociation()};
7438   if (const std::optional<parser::Name> &name{std::get<1>(x.t)}) {
7439     // This isn't a name in the current scope, it is in each TypeGuardStmt
7440     MakePlaceholder(*name, MiscDetails::Kind::SelectTypeAssociateName);
7441     association.name = &*name;
7442     if (ExtractCoarrayRef(association.selector.expr)) { // C1103
7443       Say("Selector must not be a coindexed object"_err_en_US);
7444     }
7445     if (association.selector.expr) {
7446       auto exprType{association.selector.expr->GetType()};
7447       if (exprType && !exprType->IsPolymorphic()) { // C1159
7448         Say(association.selector.source,
7449             "Selector '%s' in SELECT TYPE statement must be "
7450             "polymorphic"_err_en_US);
7451       }
7452     }
7453   } else {
7454     if (const Symbol *
7455         whole{UnwrapWholeSymbolDataRef(association.selector.expr)}) {
7456       ConvertToObjectEntity(const_cast<Symbol &>(*whole));
7457       if (!IsVariableName(*whole)) {
7458         Say(association.selector.source, // C901
7459             "Selector is not a variable"_err_en_US);
7460         association = {};
7461       }
7462       if (const DeclTypeSpec * type{whole->GetType()}) {
7463         if (!type->IsPolymorphic()) { // C1159
7464           Say(association.selector.source,
7465               "Selector '%s' in SELECT TYPE statement must be "
7466               "polymorphic"_err_en_US);
7467         }
7468       }
7469     } else {
7470       Say(association.selector.source, // C1157
7471           "Selector is not a named variable: 'associate-name =>' is required"_err_en_US);
7472       association = {};
7473     }
7474   }
7475 }
7476 
7477 void ConstructVisitor::Post(const parser::SelectRankStmt &x) {
7478   auto &association{GetCurrentAssociation()};
7479   if (const std::optional<parser::Name> &name{std::get<1>(x.t)}) {
7480     // This isn't a name in the current scope, it is in each SelectRankCaseStmt
7481     MakePlaceholder(*name, MiscDetails::Kind::SelectRankAssociateName);
7482     association.name = &*name;
7483   }
7484 }
7485 
7486 bool ConstructVisitor::Pre(const parser::SelectTypeConstruct::TypeCase &) {
7487   PushScope(Scope::Kind::OtherConstruct, nullptr);
7488   return true;
7489 }
7490 void ConstructVisitor::Post(const parser::SelectTypeConstruct::TypeCase &) {
7491   PopScope();
7492 }
7493 
7494 bool ConstructVisitor::Pre(const parser::SelectRankConstruct::RankCase &) {
7495   PushScope(Scope::Kind::OtherConstruct, nullptr);
7496   return true;
7497 }
7498 void ConstructVisitor::Post(const parser::SelectRankConstruct::RankCase &) {
7499   PopScope();
7500 }
7501 
7502 bool ConstructVisitor::Pre(const parser::TypeGuardStmt::Guard &x) {
7503   if (std::holds_alternative<parser::DerivedTypeSpec>(x.u)) {
7504     // CLASS IS (t)
7505     SetDeclTypeSpecCategory(DeclTypeSpec::Category::ClassDerived);
7506   }
7507   return true;
7508 }
7509 
7510 void ConstructVisitor::Post(const parser::TypeGuardStmt::Guard &x) {
7511   if (auto *symbol{MakeAssocEntity()}) {
7512     if (std::holds_alternative<parser::Default>(x.u)) {
7513       SetTypeFromAssociation(*symbol);
7514     } else if (const auto *type{GetDeclTypeSpec()}) {
7515       symbol->SetType(*type);
7516     }
7517     SetAttrsFromAssociation(*symbol);
7518   }
7519 }
7520 
7521 void ConstructVisitor::Post(const parser::SelectRankCaseStmt::Rank &x) {
7522   if (auto *symbol{MakeAssocEntity()}) {
7523     SetTypeFromAssociation(*symbol);
7524     auto &details{symbol->get<AssocEntityDetails>()};
7525     // Don't call SetAttrsFromAssociation() for SELECT RANK.
7526     Attrs selectorAttrs{
7527         evaluate::GetAttrs(GetCurrentAssociation().selector.expr)};
7528     Attrs attrsToKeep{Attr::ASYNCHRONOUS, Attr::TARGET, Attr::VOLATILE};
7529     if (const auto *rankValue{
7530             std::get_if<parser::ScalarIntConstantExpr>(&x.u)}) {
7531       // RANK(n)
7532       if (auto expr{EvaluateIntExpr(*rankValue)}) {
7533         if (auto val{evaluate::ToInt64(*expr)}) {
7534           details.set_rank(*val);
7535           attrsToKeep |= Attrs{Attr::ALLOCATABLE, Attr::POINTER};
7536         } else {
7537           Say("RANK() expression must be constant"_err_en_US);
7538         }
7539       }
7540     } else if (std::holds_alternative<parser::Star>(x.u)) {
7541       // RANK(*): assumed-size
7542       details.set_IsAssumedSize();
7543     } else {
7544       CHECK(std::holds_alternative<parser::Default>(x.u));
7545       // RANK DEFAULT: assumed-rank
7546       details.set_IsAssumedRank();
7547       attrsToKeep |= Attrs{Attr::ALLOCATABLE, Attr::POINTER};
7548     }
7549     symbol->attrs() |= selectorAttrs & attrsToKeep;
7550   }
7551 }
7552 
7553 bool ConstructVisitor::Pre(const parser::SelectRankConstruct &) {
7554   PushAssociation();
7555   return true;
7556 }
7557 
7558 void ConstructVisitor::Post(const parser::SelectRankConstruct &) {
7559   PopAssociation();
7560 }
7561 
7562 bool ConstructVisitor::CheckDef(const std::optional<parser::Name> &x) {
7563   if (x && !x->symbol) {
7564     // Construct names are not scoped by BLOCK in the standard, but many,
7565     // but not all, compilers do treat them as if they were so scoped.
7566     if (Symbol * inner{FindInScope(currScope(), *x)}) {
7567       SayAlreadyDeclared(*x, *inner);
7568     } else {
7569       if (context().ShouldWarn(common::LanguageFeature::BenignNameClash)) {
7570         if (Symbol *
7571             other{FindInScopeOrBlockConstructs(InclusiveScope(), x->source)}) {
7572           SayWithDecl(*x, *other,
7573               "The construct name '%s' should be distinct at the subprogram level"_port_en_US)
7574               .set_languageFeature(common::LanguageFeature::BenignNameClash);
7575         }
7576       }
7577       MakeSymbol(*x, MiscDetails{MiscDetails::Kind::ConstructName});
7578     }
7579   }
7580   return true;
7581 }
7582 
7583 void ConstructVisitor::CheckRef(const std::optional<parser::Name> &x) {
7584   if (x) {
7585     // Just add an occurrence of this name; checking is done in ValidateLabels
7586     FindSymbol(*x);
7587   }
7588 }
7589 
7590 // Make a symbol for the associating entity of the current association.
7591 Symbol *ConstructVisitor::MakeAssocEntity() {
7592   Symbol *symbol{nullptr};
7593   auto &association{GetCurrentAssociation()};
7594   if (association.name) {
7595     symbol = &MakeSymbol(*association.name, UnknownDetails{});
7596     if (symbol->has<AssocEntityDetails>() && symbol->owner() == currScope()) {
7597       Say(*association.name, // C1102
7598           "The associate name '%s' is already used in this associate statement"_err_en_US);
7599       return nullptr;
7600     }
7601   } else if (const Symbol *
7602       whole{UnwrapWholeSymbolDataRef(association.selector.expr)}) {
7603     symbol = &MakeSymbol(whole->name());
7604   } else {
7605     return nullptr;
7606   }
7607   if (auto &expr{association.selector.expr}) {
7608     symbol->set_details(AssocEntityDetails{common::Clone(*expr)});
7609   } else {
7610     symbol->set_details(AssocEntityDetails{});
7611   }
7612   return symbol;
7613 }
7614 
7615 // Set the type of symbol based on the current association selector.
7616 void ConstructVisitor::SetTypeFromAssociation(Symbol &symbol) {
7617   auto &details{symbol.get<AssocEntityDetails>()};
7618   const MaybeExpr *pexpr{&details.expr()};
7619   if (!*pexpr) {
7620     pexpr = &GetCurrentAssociation().selector.expr;
7621   }
7622   if (*pexpr) {
7623     const SomeExpr &expr{**pexpr};
7624     if (std::optional<evaluate::DynamicType> type{expr.GetType()}) {
7625       if (const auto *charExpr{
7626               evaluate::UnwrapExpr<evaluate::Expr<evaluate::SomeCharacter>>(
7627                   expr)}) {
7628         symbol.SetType(ToDeclTypeSpec(std::move(*type),
7629             FoldExpr(common::visit(
7630                 [](const auto &kindChar) { return kindChar.LEN(); },
7631                 charExpr->u))));
7632       } else {
7633         symbol.SetType(ToDeclTypeSpec(std::move(*type)));
7634       }
7635     } else {
7636       // BOZ literals, procedure designators, &c. are not acceptable
7637       Say(symbol.name(), "Associate name '%s' must have a type"_err_en_US);
7638     }
7639   }
7640 }
7641 
7642 // If current selector is a variable, set some of its attributes on symbol.
7643 // For ASSOCIATE, CHANGE TEAM, and SELECT TYPE only; not SELECT RANK.
7644 void ConstructVisitor::SetAttrsFromAssociation(Symbol &symbol) {
7645   Attrs attrs{evaluate::GetAttrs(GetCurrentAssociation().selector.expr)};
7646   symbol.attrs() |=
7647       attrs & Attrs{Attr::TARGET, Attr::ASYNCHRONOUS, Attr::VOLATILE};
7648   if (attrs.test(Attr::POINTER)) {
7649     SetImplicitAttr(symbol, Attr::TARGET);
7650   }
7651 }
7652 
7653 ConstructVisitor::Selector ConstructVisitor::ResolveSelector(
7654     const parser::Selector &x) {
7655   return common::visit(common::visitors{
7656                            [&](const parser::Expr &expr) {
7657                              return Selector{expr.source, EvaluateExpr(x)};
7658                            },
7659                            [&](const parser::Variable &var) {
7660                              return Selector{var.GetSource(), EvaluateExpr(x)};
7661                            },
7662                        },
7663       x.u);
7664 }
7665 
7666 // Set the current association to the nth to the last association on the
7667 // association stack.  The top of the stack is at n = 1.  This allows access
7668 // to the interior of a list of associations at the top of the stack.
7669 void ConstructVisitor::SetCurrentAssociation(std::size_t n) {
7670   CHECK(n > 0 && n <= associationStack_.size());
7671   currentAssociation_ = &associationStack_[associationStack_.size() - n];
7672 }
7673 
7674 ConstructVisitor::Association &ConstructVisitor::GetCurrentAssociation() {
7675   CHECK(currentAssociation_);
7676   return *currentAssociation_;
7677 }
7678 
7679 void ConstructVisitor::PushAssociation() {
7680   associationStack_.emplace_back(Association{});
7681   currentAssociation_ = &associationStack_.back();
7682 }
7683 
7684 void ConstructVisitor::PopAssociation(std::size_t count) {
7685   CHECK(count > 0 && count <= associationStack_.size());
7686   associationStack_.resize(associationStack_.size() - count);
7687   currentAssociation_ =
7688       associationStack_.empty() ? nullptr : &associationStack_.back();
7689 }
7690 
7691 const DeclTypeSpec &ConstructVisitor::ToDeclTypeSpec(
7692     evaluate::DynamicType &&type) {
7693   switch (type.category()) {
7694     SWITCH_COVERS_ALL_CASES
7695   case common::TypeCategory::Integer:
7696   case common::TypeCategory::Unsigned:
7697   case common::TypeCategory::Real:
7698   case common::TypeCategory::Complex:
7699     return context().MakeNumericType(type.category(), type.kind());
7700   case common::TypeCategory::Logical:
7701     return context().MakeLogicalType(type.kind());
7702   case common::TypeCategory::Derived:
7703     if (type.IsAssumedType()) {
7704       return currScope().MakeTypeStarType();
7705     } else if (type.IsUnlimitedPolymorphic()) {
7706       return currScope().MakeClassStarType();
7707     } else {
7708       return currScope().MakeDerivedType(
7709           type.IsPolymorphic() ? DeclTypeSpec::ClassDerived
7710                                : DeclTypeSpec::TypeDerived,
7711           common::Clone(type.GetDerivedTypeSpec())
7712 
7713       );
7714     }
7715   case common::TypeCategory::Character:
7716     CRASH_NO_CASE;
7717   }
7718 }
7719 
7720 const DeclTypeSpec &ConstructVisitor::ToDeclTypeSpec(
7721     evaluate::DynamicType &&type, MaybeSubscriptIntExpr &&length) {
7722   CHECK(type.category() == common::TypeCategory::Character);
7723   if (length) {
7724     return currScope().MakeCharacterType(
7725         ParamValue{SomeIntExpr{*std::move(length)}, common::TypeParamAttr::Len},
7726         KindExpr{type.kind()});
7727   } else {
7728     return currScope().MakeCharacterType(
7729         ParamValue::Deferred(common::TypeParamAttr::Len),
7730         KindExpr{type.kind()});
7731   }
7732 }
7733 
7734 class ExecutionPartSkimmerBase {
7735 public:
7736   template <typename A> bool Pre(const A &) { return true; }
7737   template <typename A> void Post(const A &) {}
7738 
7739   bool InNestedBlockConstruct() const { return blockDepth_ > 0; }
7740 
7741   bool Pre(const parser::AssociateConstruct &) {
7742     PushScope();
7743     return true;
7744   }
7745   void Post(const parser::AssociateConstruct &) { PopScope(); }
7746   bool Pre(const parser::Association &x) {
7747     Hide(std::get<parser::Name>(x.t));
7748     return true;
7749   }
7750   bool Pre(const parser::BlockConstruct &) {
7751     PushScope();
7752     ++blockDepth_;
7753     return true;
7754   }
7755   void Post(const parser::BlockConstruct &) {
7756     --blockDepth_;
7757     PopScope();
7758   }
7759   // Note declarations of local names in BLOCK constructs.
7760   // Don't have to worry about INTENT(), VALUE, or OPTIONAL
7761   // (pertinent only to dummy arguments), ASYNCHRONOUS/VOLATILE,
7762   // or accessibility attributes,
7763   bool Pre(const parser::EntityDecl &x) {
7764     Hide(std::get<parser::ObjectName>(x.t));
7765     return true;
7766   }
7767   bool Pre(const parser::ObjectDecl &x) {
7768     Hide(std::get<parser::ObjectName>(x.t));
7769     return true;
7770   }
7771   bool Pre(const parser::PointerDecl &x) {
7772     Hide(std::get<parser::Name>(x.t));
7773     return true;
7774   }
7775   bool Pre(const parser::BindEntity &x) {
7776     Hide(std::get<parser::Name>(x.t));
7777     return true;
7778   }
7779   bool Pre(const parser::ContiguousStmt &x) {
7780     for (const parser::Name &name : x.v) {
7781       Hide(name);
7782     }
7783     return true;
7784   }
7785   bool Pre(const parser::DimensionStmt::Declaration &x) {
7786     Hide(std::get<parser::Name>(x.t));
7787     return true;
7788   }
7789   bool Pre(const parser::ExternalStmt &x) {
7790     for (const parser::Name &name : x.v) {
7791       Hide(name);
7792     }
7793     return true;
7794   }
7795   bool Pre(const parser::IntrinsicStmt &x) {
7796     for (const parser::Name &name : x.v) {
7797       Hide(name);
7798     }
7799     return true;
7800   }
7801   bool Pre(const parser::CodimensionStmt &x) {
7802     for (const parser::CodimensionDecl &decl : x.v) {
7803       Hide(std::get<parser::Name>(decl.t));
7804     }
7805     return true;
7806   }
7807   void Post(const parser::ImportStmt &x) {
7808     if (x.kind == common::ImportKind::None ||
7809         x.kind == common::ImportKind::Only) {
7810       if (!nestedScopes_.front().importOnly.has_value()) {
7811         nestedScopes_.front().importOnly.emplace();
7812       }
7813       for (const auto &name : x.names) {
7814         nestedScopes_.front().importOnly->emplace(name.source);
7815       }
7816     } else {
7817       // no special handling needed for explicit names or IMPORT, ALL
7818     }
7819   }
7820   void Post(const parser::UseStmt &x) {
7821     if (const auto *onlyList{std::get_if<std::list<parser::Only>>(&x.u)}) {
7822       for (const auto &only : *onlyList) {
7823         if (const auto *name{std::get_if<parser::Name>(&only.u)}) {
7824           Hide(*name);
7825         } else if (const auto *rename{std::get_if<parser::Rename>(&only.u)}) {
7826           if (const auto *names{
7827                   std::get_if<parser::Rename::Names>(&rename->u)}) {
7828             Hide(std::get<0>(names->t));
7829           }
7830         }
7831       }
7832     } else {
7833       // USE may or may not shadow symbols in host scopes
7834       nestedScopes_.front().hasUseWithoutOnly = true;
7835     }
7836   }
7837   bool Pre(const parser::DerivedTypeStmt &x) {
7838     Hide(std::get<parser::Name>(x.t));
7839     PushScope();
7840     return true;
7841   }
7842   void Post(const parser::DerivedTypeDef &) { PopScope(); }
7843   bool Pre(const parser::SelectTypeConstruct &) {
7844     PushScope();
7845     return true;
7846   }
7847   void Post(const parser::SelectTypeConstruct &) { PopScope(); }
7848   bool Pre(const parser::SelectTypeStmt &x) {
7849     if (const auto &maybeName{std::get<1>(x.t)}) {
7850       Hide(*maybeName);
7851     }
7852     return true;
7853   }
7854   bool Pre(const parser::SelectRankConstruct &) {
7855     PushScope();
7856     return true;
7857   }
7858   void Post(const parser::SelectRankConstruct &) { PopScope(); }
7859   bool Pre(const parser::SelectRankStmt &x) {
7860     if (const auto &maybeName{std::get<1>(x.t)}) {
7861       Hide(*maybeName);
7862     }
7863     return true;
7864   }
7865 
7866   // Iterator-modifiers contain variable declarations, and do introduce
7867   // a new scope. These variables can only have integer types, and their
7868   // scope only extends until the end of the clause. A potential alternative
7869   // to the code below may be to ignore OpenMP clauses, but it's not clear
7870   // if OMP-specific checks can be avoided altogether.
7871   bool Pre(const parser::OmpClause &x) {
7872     if (OmpVisitor::NeedsScope(x)) {
7873       PushScope();
7874     }
7875     return true;
7876   }
7877   void Post(const parser::OmpClause &x) {
7878     if (OmpVisitor::NeedsScope(x)) {
7879       PopScope();
7880     }
7881   }
7882 
7883 protected:
7884   bool IsHidden(SourceName name) {
7885     for (const auto &scope : nestedScopes_) {
7886       if (scope.locals.find(name) != scope.locals.end()) {
7887         return true; // shadowed by nested declaration
7888       }
7889       if (scope.hasUseWithoutOnly) {
7890         break;
7891       }
7892       if (scope.importOnly &&
7893           scope.importOnly->find(name) == scope.importOnly->end()) {
7894         return true; // not imported
7895       }
7896     }
7897     return false;
7898   }
7899 
7900   void EndWalk() { CHECK(nestedScopes_.empty()); }
7901 
7902 private:
7903   void PushScope() { nestedScopes_.emplace_front(); }
7904   void PopScope() { nestedScopes_.pop_front(); }
7905   void Hide(const parser::Name &name) {
7906     nestedScopes_.front().locals.emplace(name.source);
7907   }
7908 
7909   int blockDepth_{0};
7910   struct NestedScopeInfo {
7911     bool hasUseWithoutOnly{false};
7912     std::set<SourceName> locals;
7913     std::optional<std::set<SourceName>> importOnly;
7914   };
7915   std::list<NestedScopeInfo> nestedScopes_;
7916 };
7917 
7918 class ExecutionPartAsyncIOSkimmer : public ExecutionPartSkimmerBase {
7919 public:
7920   explicit ExecutionPartAsyncIOSkimmer(SemanticsContext &context)
7921       : context_{context} {}
7922 
7923   void Walk(const parser::Block &block) {
7924     parser::Walk(block, *this);
7925     EndWalk();
7926   }
7927 
7928   const std::set<SourceName> asyncIONames() const { return asyncIONames_; }
7929 
7930   using ExecutionPartSkimmerBase::Post;
7931   using ExecutionPartSkimmerBase::Pre;
7932 
7933   bool Pre(const parser::IoControlSpec::Asynchronous &async) {
7934     if (auto folded{evaluate::Fold(
7935             context_.foldingContext(), AnalyzeExpr(context_, async.v))}) {
7936       if (auto str{
7937               evaluate::GetScalarConstantValue<evaluate::Ascii>(*folded)}) {
7938         for (char ch : *str) {
7939           if (ch != ' ') {
7940             inAsyncIO_ = ch == 'y' || ch == 'Y';
7941             break;
7942           }
7943         }
7944       }
7945     }
7946     return true;
7947   }
7948   void Post(const parser::ReadStmt &) { inAsyncIO_ = false; }
7949   void Post(const parser::WriteStmt &) { inAsyncIO_ = false; }
7950   void Post(const parser::IoControlSpec::Size &size) {
7951     if (const auto *designator{
7952             std::get_if<common::Indirection<parser::Designator>>(
7953                 &size.v.thing.thing.u)}) {
7954       NoteAsyncIODesignator(designator->value());
7955     }
7956   }
7957   void Post(const parser::InputItem &x) {
7958     if (const auto *var{std::get_if<parser::Variable>(&x.u)}) {
7959       if (const auto *designator{
7960               std::get_if<common::Indirection<parser::Designator>>(&var->u)}) {
7961         NoteAsyncIODesignator(designator->value());
7962       }
7963     }
7964   }
7965   void Post(const parser::OutputItem &x) {
7966     if (const auto *expr{std::get_if<parser::Expr>(&x.u)}) {
7967       if (const auto *designator{
7968               std::get_if<common::Indirection<parser::Designator>>(&expr->u)}) {
7969         NoteAsyncIODesignator(designator->value());
7970       }
7971     }
7972   }
7973 
7974 private:
7975   void NoteAsyncIODesignator(const parser::Designator &designator) {
7976     if (inAsyncIO_ && !InNestedBlockConstruct()) {
7977       const parser::Name &name{parser::GetFirstName(designator)};
7978       if (!IsHidden(name.source)) {
7979         asyncIONames_.insert(name.source);
7980       }
7981     }
7982   }
7983 
7984   SemanticsContext &context_;
7985   bool inAsyncIO_{false};
7986   std::set<SourceName> asyncIONames_;
7987 };
7988 
7989 // Any data list item or SIZE= specifier of an I/O data transfer statement
7990 // with ASYNCHRONOUS="YES" implicitly has the ASYNCHRONOUS attribute in the
7991 // local scope.
7992 void ConstructVisitor::HandleImpliedAsynchronousInScope(
7993     const parser::Block &block) {
7994   ExecutionPartAsyncIOSkimmer skimmer{context()};
7995   skimmer.Walk(block);
7996   for (auto name : skimmer.asyncIONames()) {
7997     if (Symbol * symbol{currScope().FindSymbol(name)}) {
7998       if (!symbol->attrs().test(Attr::ASYNCHRONOUS)) {
7999         if (&symbol->owner() != &currScope()) {
8000           symbol = &*currScope()
8001                          .try_emplace(name, HostAssocDetails{*symbol})
8002                          .first->second;
8003         }
8004         if (symbol->has<AssocEntityDetails>()) {
8005           symbol = const_cast<Symbol *>(&GetAssociationRoot(*symbol));
8006         }
8007         SetImplicitAttr(*symbol, Attr::ASYNCHRONOUS);
8008       }
8009     }
8010   }
8011 }
8012 
8013 // ResolveNamesVisitor implementation
8014 
8015 bool ResolveNamesVisitor::Pre(const parser::FunctionReference &x) {
8016   HandleCall(Symbol::Flag::Function, x.v);
8017   return false;
8018 }
8019 bool ResolveNamesVisitor::Pre(const parser::CallStmt &x) {
8020   HandleCall(Symbol::Flag::Subroutine, x.call);
8021   Walk(x.chevrons);
8022   return false;
8023 }
8024 
8025 bool ResolveNamesVisitor::Pre(const parser::ImportStmt &x) {
8026   auto &scope{currScope()};
8027   // Check C896 and C899: where IMPORT statements are allowed
8028   switch (scope.kind()) {
8029   case Scope::Kind::Module:
8030     if (scope.IsModule()) {
8031       Say("IMPORT is not allowed in a module scoping unit"_err_en_US);
8032       return false;
8033     } else if (x.kind == common::ImportKind::None) {
8034       Say("IMPORT,NONE is not allowed in a submodule scoping unit"_err_en_US);
8035       return false;
8036     }
8037     break;
8038   case Scope::Kind::MainProgram:
8039     Say("IMPORT is not allowed in a main program scoping unit"_err_en_US);
8040     return false;
8041   case Scope::Kind::Subprogram:
8042     if (scope.parent().IsGlobal()) {
8043       Say("IMPORT is not allowed in an external subprogram scoping unit"_err_en_US);
8044       return false;
8045     }
8046     break;
8047   case Scope::Kind::BlockData: // C1415 (in part)
8048     Say("IMPORT is not allowed in a BLOCK DATA subprogram"_err_en_US);
8049     return false;
8050   default:;
8051   }
8052   if (auto error{scope.SetImportKind(x.kind)}) {
8053     Say(std::move(*error));
8054   }
8055   for (auto &name : x.names) {
8056     if (Symbol * outer{FindSymbol(scope.parent(), name)}) {
8057       scope.add_importName(name.source);
8058       if (Symbol * symbol{FindInScope(name)}) {
8059         if (outer->GetUltimate() == symbol->GetUltimate()) {
8060           context().Warn(common::LanguageFeature::BenignNameClash, name.source,
8061               "The same '%s' is already present in this scope"_port_en_US,
8062               name.source);
8063         } else {
8064           Say(name,
8065               "A distinct '%s' is already present in this scope"_err_en_US)
8066               .Attach(symbol->name(), "Previous declaration of '%s'"_en_US)
8067               .Attach(outer->name(), "Declaration of '%s' in host scope"_en_US);
8068         }
8069       }
8070     } else {
8071       Say(name, "'%s' not found in host scope"_err_en_US);
8072     }
8073   }
8074   prevImportStmt_ = currStmtSource();
8075   return false;
8076 }
8077 
8078 const parser::Name *DeclarationVisitor::ResolveStructureComponent(
8079     const parser::StructureComponent &x) {
8080   return FindComponent(ResolveDataRef(x.base), x.component);
8081 }
8082 
8083 const parser::Name *DeclarationVisitor::ResolveDesignator(
8084     const parser::Designator &x) {
8085   return common::visit(
8086       common::visitors{
8087           [&](const parser::DataRef &x) { return ResolveDataRef(x); },
8088           [&](const parser::Substring &x) {
8089             Walk(std::get<parser::SubstringRange>(x.t).t);
8090             return ResolveDataRef(std::get<parser::DataRef>(x.t));
8091           },
8092       },
8093       x.u);
8094 }
8095 
8096 const parser::Name *DeclarationVisitor::ResolveDataRef(
8097     const parser::DataRef &x) {
8098   return common::visit(
8099       common::visitors{
8100           [=](const parser::Name &y) { return ResolveName(y); },
8101           [=](const Indirection<parser::StructureComponent> &y) {
8102             return ResolveStructureComponent(y.value());
8103           },
8104           [&](const Indirection<parser::ArrayElement> &y) {
8105             Walk(y.value().subscripts);
8106             const parser::Name *name{ResolveDataRef(y.value().base)};
8107             if (name && name->symbol) {
8108               if (!IsProcedure(*name->symbol)) {
8109                 ConvertToObjectEntity(*name->symbol);
8110               } else if (!context().HasError(*name->symbol)) {
8111                 SayWithDecl(*name, *name->symbol,
8112                     "Cannot reference function '%s' as data"_err_en_US);
8113                 context().SetError(*name->symbol);
8114               }
8115             }
8116             return name;
8117           },
8118           [&](const Indirection<parser::CoindexedNamedObject> &y) {
8119             Walk(y.value().imageSelector);
8120             return ResolveDataRef(y.value().base);
8121           },
8122       },
8123       x.u);
8124 }
8125 
8126 // If implicit types are allowed, ensure name is in the symbol table.
8127 // Otherwise, report an error if it hasn't been declared.
8128 const parser::Name *DeclarationVisitor::ResolveName(const parser::Name &name) {
8129   FindSymbol(name);
8130   if (CheckForHostAssociatedImplicit(name)) {
8131     NotePossibleBadForwardRef(name);
8132     return &name;
8133   }
8134   if (Symbol * symbol{name.symbol}) {
8135     if (CheckUseError(name)) {
8136       return nullptr; // reported an error
8137     }
8138     NotePossibleBadForwardRef(name);
8139     symbol->set(Symbol::Flag::ImplicitOrError, false);
8140     if (IsUplevelReference(*symbol)) {
8141       MakeHostAssocSymbol(name, *symbol);
8142     } else if (IsDummy(*symbol) ||
8143         (!symbol->GetType() && FindCommonBlockContaining(*symbol))) {
8144       CheckEntryDummyUse(name.source, symbol);
8145       ConvertToObjectEntity(*symbol);
8146       ApplyImplicitRules(*symbol);
8147     } else if (const auto *tpd{symbol->detailsIf<TypeParamDetails>()};
8148                tpd && !tpd->attr()) {
8149       Say(name,
8150           "Type parameter '%s' was referenced before being declared"_err_en_US,
8151           name.source);
8152       context().SetError(*symbol);
8153     }
8154     if (checkIndexUseInOwnBounds_ &&
8155         *checkIndexUseInOwnBounds_ == name.source && !InModuleFile()) {
8156       context().Warn(common::LanguageFeature::ImpliedDoIndexScope, name.source,
8157           "Implied DO index '%s' uses an object of the same name in its bounds expressions"_port_en_US,
8158           name.source);
8159     }
8160     return &name;
8161   }
8162   if (isImplicitNoneType() && !deferImplicitTyping_) {
8163     Say(name, "No explicit type declared for '%s'"_err_en_US);
8164     return nullptr;
8165   }
8166   // Create the symbol, then ensure that it is accessible
8167   if (checkIndexUseInOwnBounds_ && *checkIndexUseInOwnBounds_ == name.source) {
8168     Say(name,
8169         "Implied DO index '%s' uses itself in its own bounds expressions"_err_en_US,
8170         name.source);
8171   }
8172   MakeSymbol(InclusiveScope(), name.source, Attrs{});
8173   auto *symbol{FindSymbol(name)};
8174   if (!symbol) {
8175     Say(name,
8176         "'%s' from host scoping unit is not accessible due to IMPORT"_err_en_US);
8177     return nullptr;
8178   }
8179   ConvertToObjectEntity(*symbol);
8180   ApplyImplicitRules(*symbol);
8181   NotePossibleBadForwardRef(name);
8182   return &name;
8183 }
8184 
8185 // A specification expression may refer to a symbol in the host procedure that
8186 // is implicitly typed. Because specification parts are processed before
8187 // execution parts, this may be the first time we see the symbol. It can't be a
8188 // local in the current scope (because it's in a specification expression) so
8189 // either it is implicitly declared in the host procedure or it is an error.
8190 // We create a symbol in the host assuming it is the former; if that proves to
8191 // be wrong we report an error later in CheckDeclarations().
8192 bool DeclarationVisitor::CheckForHostAssociatedImplicit(
8193     const parser::Name &name) {
8194   if (!inSpecificationPart_ || inEquivalenceStmt_) {
8195     return false;
8196   }
8197   if (name.symbol) {
8198     ApplyImplicitRules(*name.symbol, true);
8199   }
8200   if (Scope * host{GetHostProcedure()}; host && !isImplicitNoneType(*host)) {
8201     Symbol *hostSymbol{nullptr};
8202     if (!name.symbol) {
8203       if (currScope().CanImport(name.source)) {
8204         hostSymbol = &MakeSymbol(*host, name.source, Attrs{});
8205         ConvertToObjectEntity(*hostSymbol);
8206         ApplyImplicitRules(*hostSymbol);
8207         hostSymbol->set(Symbol::Flag::ImplicitOrError);
8208       }
8209     } else if (name.symbol->test(Symbol::Flag::ImplicitOrError)) {
8210       hostSymbol = name.symbol;
8211     }
8212     if (hostSymbol) {
8213       Symbol &symbol{MakeHostAssocSymbol(name, *hostSymbol)};
8214       if (auto *assoc{symbol.detailsIf<HostAssocDetails>()}) {
8215         if (isImplicitNoneType()) {
8216           assoc->implicitOrExplicitTypeError = true;
8217         } else {
8218           assoc->implicitOrSpecExprError = true;
8219         }
8220         return true;
8221       }
8222     }
8223   }
8224   return false;
8225 }
8226 
8227 bool DeclarationVisitor::IsUplevelReference(const Symbol &symbol) {
8228   if (symbol.owner().IsTopLevel()) {
8229     return false;
8230   }
8231   const Scope &symbolUnit{GetProgramUnitContaining(symbol)};
8232   if (symbolUnit == GetProgramUnitContaining(currScope())) {
8233     return false;
8234   } else {
8235     Scope::Kind kind{symbolUnit.kind()};
8236     return kind == Scope::Kind::Subprogram || kind == Scope::Kind::MainProgram;
8237   }
8238 }
8239 
8240 // base is a part-ref of a derived type; find the named component in its type.
8241 // Also handles intrinsic type parameter inquiries (%kind, %len) and
8242 // COMPLEX component references (%re, %im).
8243 const parser::Name *DeclarationVisitor::FindComponent(
8244     const parser::Name *base, const parser::Name &component) {
8245   if (!base || !base->symbol) {
8246     return nullptr;
8247   }
8248   if (auto *misc{base->symbol->detailsIf<MiscDetails>()}) {
8249     if (component.source == "kind") {
8250       if (misc->kind() == MiscDetails::Kind::ComplexPartRe ||
8251           misc->kind() == MiscDetails::Kind::ComplexPartIm ||
8252           misc->kind() == MiscDetails::Kind::KindParamInquiry ||
8253           misc->kind() == MiscDetails::Kind::LenParamInquiry) {
8254         // x%{re,im,kind,len}%kind
8255         MakePlaceholder(component, MiscDetails::Kind::KindParamInquiry);
8256         return &component;
8257       }
8258     }
8259   }
8260   CheckEntryDummyUse(base->source, base->symbol);
8261   auto &symbol{base->symbol->GetUltimate()};
8262   if (!symbol.has<AssocEntityDetails>() && !ConvertToObjectEntity(symbol)) {
8263     SayWithDecl(*base, symbol,
8264         "'%s' is not an object and may not be used as the base of a component reference or type parameter inquiry"_err_en_US);
8265     return nullptr;
8266   }
8267   auto *type{symbol.GetType()};
8268   if (!type) {
8269     return nullptr; // should have already reported error
8270   }
8271   if (const IntrinsicTypeSpec * intrinsic{type->AsIntrinsic()}) {
8272     auto category{intrinsic->category()};
8273     MiscDetails::Kind miscKind{MiscDetails::Kind::None};
8274     if (component.source == "kind") {
8275       miscKind = MiscDetails::Kind::KindParamInquiry;
8276     } else if (category == TypeCategory::Character) {
8277       if (component.source == "len") {
8278         miscKind = MiscDetails::Kind::LenParamInquiry;
8279       }
8280     } else if (category == TypeCategory::Complex) {
8281       if (component.source == "re") {
8282         miscKind = MiscDetails::Kind::ComplexPartRe;
8283       } else if (component.source == "im") {
8284         miscKind = MiscDetails::Kind::ComplexPartIm;
8285       }
8286     }
8287     if (miscKind != MiscDetails::Kind::None) {
8288       MakePlaceholder(component, miscKind);
8289       return &component;
8290     }
8291   } else if (DerivedTypeSpec * derived{type->AsDerived()}) {
8292     derived->Instantiate(currScope()); // in case of forward referenced type
8293     if (const Scope * scope{derived->scope()}) {
8294       if (Resolve(component, scope->FindComponent(component.source))) {
8295         if (auto msg{CheckAccessibleSymbol(currScope(), *component.symbol)}) {
8296           context().Say(component.source, *msg);
8297         }
8298         return &component;
8299       } else {
8300         SayDerivedType(component.source,
8301             "Component '%s' not found in derived type '%s'"_err_en_US, *scope);
8302       }
8303     }
8304     return nullptr;
8305   }
8306   if (symbol.test(Symbol::Flag::Implicit)) {
8307     Say(*base,
8308         "'%s' is not an object of derived type; it is implicitly typed"_err_en_US);
8309   } else {
8310     SayWithDecl(
8311         *base, symbol, "'%s' is not an object of derived type"_err_en_US);
8312   }
8313   return nullptr;
8314 }
8315 
8316 void DeclarationVisitor::Initialization(const parser::Name &name,
8317     const parser::Initialization &init, bool inComponentDecl) {
8318   // Traversal of the initializer was deferred to here so that the
8319   // symbol being declared can be available for use in the expression, e.g.:
8320   //   real, parameter :: x = tiny(x)
8321   if (!name.symbol) {
8322     return;
8323   }
8324   Symbol &ultimate{name.symbol->GetUltimate()};
8325   // TODO: check C762 - all bounds and type parameters of component
8326   // are colons or constant expressions if component is initialized
8327   common::visit(
8328       common::visitors{
8329           [&](const parser::ConstantExpr &expr) {
8330             Walk(expr);
8331             if (IsNamedConstant(ultimate) || inComponentDecl) {
8332               NonPointerInitialization(name, expr);
8333             } else {
8334               // Defer analysis so forward references to nested subprograms
8335               // can be properly resolved when they appear in structure
8336               // constructors.
8337               ultimate.set(Symbol::Flag::InDataStmt);
8338             }
8339           },
8340           [&](const parser::NullInit &null) { // => NULL()
8341             Walk(null);
8342             if (auto nullInit{EvaluateExpr(null)}) {
8343               if (!evaluate::IsNullPointer(*nullInit)) { // C813
8344                 Say(null.v.value().source,
8345                     "Pointer initializer must be intrinsic NULL()"_err_en_US);
8346               } else if (IsPointer(ultimate)) {
8347                 if (auto *object{ultimate.detailsIf<ObjectEntityDetails>()}) {
8348                   CHECK(!object->init());
8349                   object->set_init(std::move(*nullInit));
8350                 } else if (auto *procPtr{
8351                                ultimate.detailsIf<ProcEntityDetails>()}) {
8352                   CHECK(!procPtr->init());
8353                   procPtr->set_init(nullptr);
8354                 }
8355               } else {
8356                 Say(name,
8357                     "Non-pointer component '%s' initialized with null pointer"_err_en_US);
8358               }
8359             }
8360           },
8361           [&](const parser::InitialDataTarget &target) {
8362             // Defer analysis to the end of the specification part
8363             // so that forward references and attribute checks like SAVE
8364             // work better.
8365             auto restorer{common::ScopedSet(deferImplicitTyping_, true)};
8366             Walk(target);
8367             ultimate.set(Symbol::Flag::InDataStmt);
8368           },
8369           [&](const std::list<Indirection<parser::DataStmtValue>> &values) {
8370             // Handled later in data-to-inits conversion
8371             ultimate.set(Symbol::Flag::InDataStmt);
8372             Walk(values);
8373           },
8374       },
8375       init.u);
8376 }
8377 
8378 void DeclarationVisitor::PointerInitialization(
8379     const parser::Name &name, const parser::InitialDataTarget &target) {
8380   if (name.symbol) {
8381     Symbol &ultimate{name.symbol->GetUltimate()};
8382     if (!context().HasError(ultimate)) {
8383       if (IsPointer(ultimate)) {
8384         Walk(target);
8385         if (MaybeExpr expr{EvaluateExpr(target)}) {
8386           // Validation is done in declaration checking.
8387           if (auto *details{ultimate.detailsIf<ObjectEntityDetails>()}) {
8388             CHECK(!details->init());
8389             details->set_init(std::move(*expr));
8390             ultimate.set(Symbol::Flag::InDataStmt, false);
8391           } else if (auto *details{ultimate.detailsIf<ProcEntityDetails>()}) {
8392             // something like "REAL, EXTERNAL, POINTER :: p => t"
8393             if (evaluate::IsNullProcedurePointer(*expr)) {
8394               CHECK(!details->init());
8395               details->set_init(nullptr);
8396             } else if (const Symbol *
8397                 targetSymbol{evaluate::UnwrapWholeSymbolDataRef(*expr)}) {
8398               CHECK(!details->init());
8399               details->set_init(*targetSymbol);
8400             } else {
8401               Say(name,
8402                   "Procedure pointer '%s' must be initialized with a procedure name or NULL()"_err_en_US);
8403               context().SetError(ultimate);
8404             }
8405           }
8406         }
8407       } else {
8408         Say(name,
8409             "'%s' is not a pointer but is initialized like one"_err_en_US);
8410         context().SetError(ultimate);
8411       }
8412     }
8413   }
8414 }
8415 void DeclarationVisitor::PointerInitialization(
8416     const parser::Name &name, const parser::ProcPointerInit &target) {
8417   if (name.symbol) {
8418     Symbol &ultimate{name.symbol->GetUltimate()};
8419     if (!context().HasError(ultimate)) {
8420       if (IsProcedurePointer(ultimate)) {
8421         auto &details{ultimate.get<ProcEntityDetails>()};
8422         CHECK(!details.init());
8423         if (const auto *targetName{std::get_if<parser::Name>(&target.u)}) {
8424           Walk(target);
8425           if (!CheckUseError(*targetName) && targetName->symbol) {
8426             // Validation is done in declaration checking.
8427             details.set_init(*targetName->symbol);
8428           }
8429         } else { // explicit NULL
8430           details.set_init(nullptr);
8431         }
8432       } else {
8433         Say(name,
8434             "'%s' is not a procedure pointer but is initialized "
8435             "like one"_err_en_US);
8436         context().SetError(ultimate);
8437       }
8438     }
8439   }
8440 }
8441 
8442 void DeclarationVisitor::NonPointerInitialization(
8443     const parser::Name &name, const parser::ConstantExpr &expr) {
8444   if (!context().HasError(name.symbol)) {
8445     Symbol &ultimate{name.symbol->GetUltimate()};
8446     if (!context().HasError(ultimate)) {
8447       if (IsPointer(ultimate)) {
8448         Say(name,
8449             "'%s' is a pointer but is not initialized like one"_err_en_US);
8450       } else if (auto *details{ultimate.detailsIf<ObjectEntityDetails>()}) {
8451         if (details->init()) {
8452           SayWithDecl(name, *name.symbol,
8453               "'%s' has already been initialized"_err_en_US);
8454         } else if (IsAllocatable(ultimate)) {
8455           Say(name, "Allocatable object '%s' cannot be initialized"_err_en_US);
8456         } else if (ultimate.owner().IsParameterizedDerivedType()) {
8457           // Save the expression for per-instantiation analysis.
8458           details->set_unanalyzedPDTComponentInit(&expr.thing.value());
8459         } else if (MaybeExpr folded{EvaluateNonPointerInitializer(
8460                        ultimate, expr, expr.thing.value().source)}) {
8461           details->set_init(std::move(*folded));
8462           ultimate.set(Symbol::Flag::InDataStmt, false);
8463         }
8464       } else {
8465         Say(name, "'%s' is not an object that can be initialized"_err_en_US);
8466       }
8467     }
8468   }
8469 }
8470 
8471 void ResolveNamesVisitor::HandleCall(
8472     Symbol::Flag procFlag, const parser::Call &call) {
8473   common::visit(
8474       common::visitors{
8475           [&](const parser::Name &x) { HandleProcedureName(procFlag, x); },
8476           [&](const parser::ProcComponentRef &x) {
8477             Walk(x);
8478             const parser::Name &name{x.v.thing.component};
8479             if (Symbol * symbol{name.symbol}) {
8480               if (IsProcedure(*symbol)) {
8481                 SetProcFlag(name, *symbol, procFlag);
8482               }
8483             }
8484           },
8485       },
8486       std::get<parser::ProcedureDesignator>(call.t).u);
8487   const auto &arguments{std::get<std::list<parser::ActualArgSpec>>(call.t)};
8488   Walk(arguments);
8489   // Once an object has appeared in a specification function reference as
8490   // a whole scalar actual argument, it cannot be (re)dimensioned later.
8491   // The fact that it appeared to be a scalar may determine the resolution
8492   // or the result of an inquiry intrinsic function or generic procedure.
8493   if (inSpecificationPart_) {
8494     for (const auto &argSpec : arguments) {
8495       const auto &actual{std::get<parser::ActualArg>(argSpec.t)};
8496       if (const auto *expr{
8497               std::get_if<common::Indirection<parser::Expr>>(&actual.u)}) {
8498         if (const auto *designator{
8499                 std::get_if<common::Indirection<parser::Designator>>(
8500                     &expr->value().u)}) {
8501           if (const auto *dataRef{
8502                   std::get_if<parser::DataRef>(&designator->value().u)}) {
8503             if (const auto *name{std::get_if<parser::Name>(&dataRef->u)};
8504                 name && name->symbol) {
8505               const Symbol &symbol{*name->symbol};
8506               const auto *object{symbol.detailsIf<ObjectEntityDetails>()};
8507               if (symbol.has<EntityDetails>() ||
8508                   (object && !object->IsArray())) {
8509                 NoteScalarSpecificationArgument(symbol);
8510               }
8511             }
8512           }
8513         }
8514       }
8515     }
8516   }
8517 }
8518 
8519 void ResolveNamesVisitor::HandleProcedureName(
8520     Symbol::Flag flag, const parser::Name &name) {
8521   CHECK(flag == Symbol::Flag::Function || flag == Symbol::Flag::Subroutine);
8522   auto *symbol{FindSymbol(NonDerivedTypeScope(), name)};
8523   if (!symbol) {
8524     if (IsIntrinsic(name.source, flag)) {
8525       symbol = &MakeSymbol(InclusiveScope(), name.source, Attrs{});
8526       SetImplicitAttr(*symbol, Attr::INTRINSIC);
8527     } else if (const auto ppcBuiltinScope =
8528                    currScope().context().GetPPCBuiltinsScope()) {
8529       // Check if it is a builtin from the predefined module
8530       symbol = FindSymbol(*ppcBuiltinScope, name);
8531       if (!symbol) {
8532         symbol = &MakeSymbol(context().globalScope(), name.source, Attrs{});
8533       }
8534     } else {
8535       symbol = &MakeSymbol(context().globalScope(), name.source, Attrs{});
8536     }
8537     Resolve(name, *symbol);
8538     ConvertToProcEntity(*symbol, name.source);
8539     if (!symbol->attrs().test(Attr::INTRINSIC)) {
8540       if (CheckImplicitNoneExternal(name.source, *symbol)) {
8541         MakeExternal(*symbol);
8542         // Create a place-holder HostAssocDetails symbol to preclude later
8543         // use of this name as a local symbol; but don't actually use this new
8544         // HostAssocDetails symbol in expressions.
8545         MakeHostAssocSymbol(name, *symbol);
8546         name.symbol = symbol;
8547       }
8548     }
8549     CheckEntryDummyUse(name.source, symbol);
8550     SetProcFlag(name, *symbol, flag);
8551   } else if (CheckUseError(name)) {
8552     // error was reported
8553   } else {
8554     symbol = &symbol->GetUltimate();
8555     if (!name.symbol ||
8556         (name.symbol->has<HostAssocDetails>() && symbol->owner().IsGlobal() &&
8557             (symbol->has<ProcEntityDetails>() ||
8558                 (symbol->has<SubprogramDetails>() &&
8559                     symbol->scope() /*not ENTRY*/)))) {
8560       name.symbol = symbol;
8561     }
8562     CheckEntryDummyUse(name.source, symbol);
8563     bool convertedToProcEntity{ConvertToProcEntity(*symbol, name.source)};
8564     if (convertedToProcEntity && !symbol->attrs().test(Attr::EXTERNAL) &&
8565         IsIntrinsic(symbol->name(), flag) && !IsDummy(*symbol)) {
8566       AcquireIntrinsicProcedureFlags(*symbol);
8567     }
8568     if (!SetProcFlag(name, *symbol, flag)) {
8569       return; // reported error
8570     }
8571     CheckImplicitNoneExternal(name.source, *symbol);
8572     if (IsProcedure(*symbol) || symbol->has<DerivedTypeDetails>() ||
8573         symbol->has<AssocEntityDetails>()) {
8574       // Symbols with DerivedTypeDetails and AssocEntityDetails are accepted
8575       // here as procedure-designators because this means the related
8576       // FunctionReference are mis-parsed structure constructors or array
8577       // references that will be fixed later when analyzing expressions.
8578     } else if (symbol->has<ObjectEntityDetails>()) {
8579       // Symbols with ObjectEntityDetails are also accepted because this can be
8580       // a mis-parsed array reference that will be fixed later. Ensure that if
8581       // this is a symbol from a host procedure, a symbol with HostAssocDetails
8582       // is created for the current scope.
8583       // Operate on non ultimate symbol so that HostAssocDetails are also
8584       // created for symbols used associated in the host procedure.
8585       ResolveName(name);
8586     } else if (symbol->test(Symbol::Flag::Implicit)) {
8587       Say(name,
8588           "Use of '%s' as a procedure conflicts with its implicit definition"_err_en_US);
8589     } else {
8590       SayWithDecl(name, *symbol,
8591           "Use of '%s' as a procedure conflicts with its declaration"_err_en_US);
8592     }
8593   }
8594 }
8595 
8596 bool ResolveNamesVisitor::CheckImplicitNoneExternal(
8597     const SourceName &name, const Symbol &symbol) {
8598   if (symbol.has<ProcEntityDetails>() && isImplicitNoneExternal() &&
8599       !symbol.attrs().test(Attr::EXTERNAL) &&
8600       !symbol.attrs().test(Attr::INTRINSIC) && !symbol.HasExplicitInterface()) {
8601     Say(name,
8602         "'%s' is an external procedure without the EXTERNAL attribute in a scope with IMPLICIT NONE(EXTERNAL)"_err_en_US);
8603     return false;
8604   }
8605   return true;
8606 }
8607 
8608 // Variant of HandleProcedureName() for use while skimming the executable
8609 // part of a subprogram to catch calls to dummy procedures that are part
8610 // of the subprogram's interface, and to mark as procedures any symbols
8611 // that might otherwise have been miscategorized as objects.
8612 void ResolveNamesVisitor::NoteExecutablePartCall(
8613     Symbol::Flag flag, SourceName name, bool hasCUDAChevrons) {
8614   // Subtlety: The symbol pointers in the parse tree are not set, because
8615   // they might end up resolving elsewhere (e.g., construct entities in
8616   // SELECT TYPE).
8617   if (Symbol * symbol{currScope().FindSymbol(name)}) {
8618     Symbol::Flag other{flag == Symbol::Flag::Subroutine
8619             ? Symbol::Flag::Function
8620             : Symbol::Flag::Subroutine};
8621     if (!symbol->test(other)) {
8622       ConvertToProcEntity(*symbol, name);
8623       if (auto *details{symbol->detailsIf<ProcEntityDetails>()}) {
8624         symbol->set(flag);
8625         if (IsDummy(*symbol)) {
8626           SetImplicitAttr(*symbol, Attr::EXTERNAL);
8627         }
8628         ApplyImplicitRules(*symbol);
8629         if (hasCUDAChevrons) {
8630           details->set_isCUDAKernel();
8631         }
8632       }
8633     }
8634   }
8635 }
8636 
8637 static bool IsLocallyImplicitGlobalSymbol(
8638     const Symbol &symbol, const parser::Name &localName) {
8639   if (symbol.owner().IsGlobal()) {
8640     const auto *subp{symbol.detailsIf<SubprogramDetails>()};
8641     const Scope *scope{
8642         subp && subp->entryScope() ? subp->entryScope() : symbol.scope()};
8643     return !(scope && scope->sourceRange().Contains(localName.source));
8644   }
8645   return false;
8646 }
8647 
8648 static bool TypesMismatchIfNonNull(
8649     const DeclTypeSpec *type1, const DeclTypeSpec *type2) {
8650   return type1 && type2 && *type1 != *type2;
8651 }
8652 
8653 // Check and set the Function or Subroutine flag on symbol; false on error.
8654 bool ResolveNamesVisitor::SetProcFlag(
8655     const parser::Name &name, Symbol &symbol, Symbol::Flag flag) {
8656   if (symbol.test(Symbol::Flag::Function) && flag == Symbol::Flag::Subroutine) {
8657     SayWithDecl(
8658         name, symbol, "Cannot call function '%s' like a subroutine"_err_en_US);
8659     context().SetError(symbol);
8660     return false;
8661   } else if (symbol.test(Symbol::Flag::Subroutine) &&
8662       flag == Symbol::Flag::Function) {
8663     SayWithDecl(
8664         name, symbol, "Cannot call subroutine '%s' like a function"_err_en_US);
8665     context().SetError(symbol);
8666     return false;
8667   } else if (flag == Symbol::Flag::Function &&
8668       IsLocallyImplicitGlobalSymbol(symbol, name) &&
8669       TypesMismatchIfNonNull(symbol.GetType(), GetImplicitType(symbol))) {
8670     SayWithDecl(name, symbol,
8671         "Implicit declaration of function '%s' has a different result type than in previous declaration"_err_en_US);
8672     return false;
8673   } else if (symbol.has<ProcEntityDetails>()) {
8674     symbol.set(flag); // in case it hasn't been set yet
8675     if (flag == Symbol::Flag::Function) {
8676       ApplyImplicitRules(symbol);
8677     }
8678     if (symbol.attrs().test(Attr::INTRINSIC)) {
8679       AcquireIntrinsicProcedureFlags(symbol);
8680     }
8681   } else if (symbol.GetType() && flag == Symbol::Flag::Subroutine) {
8682     SayWithDecl(
8683         name, symbol, "Cannot call function '%s' like a subroutine"_err_en_US);
8684     context().SetError(symbol);
8685   } else if (symbol.attrs().test(Attr::INTRINSIC)) {
8686     AcquireIntrinsicProcedureFlags(symbol);
8687   }
8688   return true;
8689 }
8690 
8691 bool ModuleVisitor::Pre(const parser::AccessStmt &x) {
8692   Attr accessAttr{AccessSpecToAttr(std::get<parser::AccessSpec>(x.t))};
8693   if (!currScope().IsModule()) { // C869
8694     Say(currStmtSource().value(),
8695         "%s statement may only appear in the specification part of a module"_err_en_US,
8696         EnumToString(accessAttr));
8697     return false;
8698   }
8699   const auto &accessIds{std::get<std::list<parser::AccessId>>(x.t)};
8700   if (accessIds.empty()) {
8701     if (prevAccessStmt_) { // C869
8702       Say("The default accessibility of this module has already been declared"_err_en_US)
8703           .Attach(*prevAccessStmt_, "Previous declaration"_en_US);
8704     }
8705     prevAccessStmt_ = currStmtSource();
8706     auto *moduleDetails{DEREF(currScope().symbol()).detailsIf<ModuleDetails>()};
8707     DEREF(moduleDetails).set_isDefaultPrivate(accessAttr == Attr::PRIVATE);
8708   } else {
8709     for (const auto &accessId : accessIds) {
8710       GenericSpecInfo info{accessId.v.value()};
8711       auto *symbol{FindInScope(info.symbolName())};
8712       if (!symbol && !info.kind().IsName()) {
8713         symbol = &MakeSymbol(info.symbolName(), Attrs{}, GenericDetails{});
8714       }
8715       info.Resolve(&SetAccess(info.symbolName(), accessAttr, symbol));
8716     }
8717   }
8718   return false;
8719 }
8720 
8721 // Set the access specification for this symbol.
8722 Symbol &ModuleVisitor::SetAccess(
8723     const SourceName &name, Attr attr, Symbol *symbol) {
8724   if (!symbol) {
8725     symbol = &MakeSymbol(name);
8726   }
8727   Attrs &attrs{symbol->attrs()};
8728   if (attrs.HasAny({Attr::PUBLIC, Attr::PRIVATE})) {
8729     // PUBLIC/PRIVATE already set: make it a fatal error if it changed
8730     Attr prev{attrs.test(Attr::PUBLIC) ? Attr::PUBLIC : Attr::PRIVATE};
8731     if (attr != prev) {
8732       Say(name,
8733           "The accessibility of '%s' has already been specified as %s"_err_en_US,
8734           MakeOpName(name), EnumToString(prev));
8735     } else {
8736       context().Warn(common::LanguageFeature::RedundantAttribute, name,
8737           "The accessibility of '%s' has already been specified as %s"_warn_en_US,
8738           MakeOpName(name), EnumToString(prev));
8739     }
8740   } else {
8741     attrs.set(attr);
8742   }
8743   return *symbol;
8744 }
8745 
8746 static bool NeedsExplicitType(const Symbol &symbol) {
8747   if (symbol.has<UnknownDetails>()) {
8748     return true;
8749   } else if (const auto *details{symbol.detailsIf<EntityDetails>()}) {
8750     return !details->type();
8751   } else if (const auto *details{symbol.detailsIf<ObjectEntityDetails>()}) {
8752     return !details->type();
8753   } else if (const auto *details{symbol.detailsIf<ProcEntityDetails>()}) {
8754     return !details->procInterface() && !details->type();
8755   } else {
8756     return false;
8757   }
8758 }
8759 
8760 void ResolveNamesVisitor::HandleDerivedTypesInImplicitStmts(
8761     const parser::ImplicitPart &implicitPart,
8762     const std::list<parser::DeclarationConstruct> &decls) {
8763   // Detect derived type definitions and create symbols for them now if
8764   // they appear in IMPLICIT statements so that these forward-looking
8765   // references will not be ambiguous with host associations.
8766   std::set<SourceName> implicitDerivedTypes;
8767   for (const auto &ipStmt : implicitPart.v) {
8768     if (const auto *impl{std::get_if<
8769             parser::Statement<common::Indirection<parser::ImplicitStmt>>>(
8770             &ipStmt.u)}) {
8771       if (const auto *specs{std::get_if<std::list<parser::ImplicitSpec>>(
8772               &impl->statement.value().u)}) {
8773         for (const auto &spec : *specs) {
8774           const auto &declTypeSpec{
8775               std::get<parser::DeclarationTypeSpec>(spec.t)};
8776           if (const auto *dtSpec{common::visit(
8777                   common::visitors{
8778                       [](const parser::DeclarationTypeSpec::Type &x) {
8779                         return &x.derived;
8780                       },
8781                       [](const parser::DeclarationTypeSpec::Class &x) {
8782                         return &x.derived;
8783                       },
8784                       [](const auto &) -> const parser::DerivedTypeSpec * {
8785                         return nullptr;
8786                       }},
8787                   declTypeSpec.u)}) {
8788             implicitDerivedTypes.emplace(
8789                 std::get<parser::Name>(dtSpec->t).source);
8790           }
8791         }
8792       }
8793     }
8794   }
8795   if (!implicitDerivedTypes.empty()) {
8796     for (const auto &decl : decls) {
8797       if (const auto *spec{
8798               std::get_if<parser::SpecificationConstruct>(&decl.u)}) {
8799         if (const auto *dtDef{
8800                 std::get_if<common::Indirection<parser::DerivedTypeDef>>(
8801                     &spec->u)}) {
8802           const parser::DerivedTypeStmt &dtStmt{
8803               std::get<parser::Statement<parser::DerivedTypeStmt>>(
8804                   dtDef->value().t)
8805                   .statement};
8806           const parser::Name &name{std::get<parser::Name>(dtStmt.t)};
8807           if (implicitDerivedTypes.find(name.source) !=
8808                   implicitDerivedTypes.end() &&
8809               !FindInScope(name)) {
8810             DerivedTypeDetails details;
8811             details.set_isForwardReferenced(true);
8812             Resolve(name, MakeSymbol(name, std::move(details)));
8813             implicitDerivedTypes.erase(name.source);
8814           }
8815         }
8816       }
8817     }
8818   }
8819 }
8820 
8821 bool ResolveNamesVisitor::Pre(const parser::SpecificationPart &x) {
8822   const auto &[accDecls, ompDecls, compilerDirectives, useStmts, importStmts,
8823       implicitPart, decls] = x.t;
8824   auto flagRestorer{common::ScopedSet(inSpecificationPart_, true)};
8825   auto stateRestorer{
8826       common::ScopedSet(specPartState_, SpecificationPartState{})};
8827   Walk(accDecls);
8828   Walk(ompDecls);
8829   Walk(compilerDirectives);
8830   for (const auto &useStmt : useStmts) {
8831     CollectUseRenames(useStmt.statement.value());
8832   }
8833   Walk(useStmts);
8834   UseCUDABuiltinNames();
8835   ClearUseRenames();
8836   ClearUseOnly();
8837   ClearModuleUses();
8838   Walk(importStmts);
8839   HandleDerivedTypesInImplicitStmts(implicitPart, decls);
8840   Walk(implicitPart);
8841   for (const auto &decl : decls) {
8842     if (const auto *spec{
8843             std::get_if<parser::SpecificationConstruct>(&decl.u)}) {
8844       PreSpecificationConstruct(*spec);
8845     }
8846   }
8847   Walk(decls);
8848   FinishSpecificationPart(decls);
8849   return false;
8850 }
8851 
8852 void ResolveNamesVisitor::UseCUDABuiltinNames() {
8853   if (FindCUDADeviceContext(&currScope())) {
8854     for (const auto &[name, symbol] : context().GetCUDABuiltinsScope()) {
8855       if (!FindInScope(name)) {
8856         auto &localSymbol{MakeSymbol(name)};
8857         localSymbol.set_details(UseDetails{name, *symbol});
8858         localSymbol.flags() = symbol->flags();
8859       }
8860     }
8861   }
8862 }
8863 
8864 // Initial processing on specification constructs, before visiting them.
8865 void ResolveNamesVisitor::PreSpecificationConstruct(
8866     const parser::SpecificationConstruct &spec) {
8867   common::visit(
8868       common::visitors{
8869           [&](const parser::Statement<Indirection<parser::GenericStmt>> &y) {
8870             CreateGeneric(std::get<parser::GenericSpec>(y.statement.value().t));
8871           },
8872           [&](const Indirection<parser::InterfaceBlock> &y) {
8873             const auto &stmt{std::get<parser::Statement<parser::InterfaceStmt>>(
8874                 y.value().t)};
8875             if (const auto *spec{parser::Unwrap<parser::GenericSpec>(stmt)}) {
8876               CreateGeneric(*spec);
8877             }
8878           },
8879           [&](const parser::Statement<parser::OtherSpecificationStmt> &y) {
8880             common::visit(
8881                 common::visitors{
8882                     [&](const common::Indirection<parser::CommonStmt> &z) {
8883                       CreateCommonBlockSymbols(z.value());
8884                     },
8885                     [&](const common::Indirection<parser::TargetStmt> &z) {
8886                       CreateObjectSymbols(z.value().v, Attr::TARGET);
8887                     },
8888                     [](const auto &) {},
8889                 },
8890                 y.statement.u);
8891           },
8892           [](const auto &) {},
8893       },
8894       spec.u);
8895 }
8896 
8897 void ResolveNamesVisitor::CreateCommonBlockSymbols(
8898     const parser::CommonStmt &commonStmt) {
8899   for (const parser::CommonStmt::Block &block : commonStmt.blocks) {
8900     const auto &[name, objects] = block.t;
8901     Symbol &commonBlock{MakeCommonBlockSymbol(name)};
8902     for (const auto &object : objects) {
8903       Symbol &obj{DeclareObjectEntity(std::get<parser::Name>(object.t))};
8904       if (auto *details{obj.detailsIf<ObjectEntityDetails>()}) {
8905         details->set_commonBlock(commonBlock);
8906         commonBlock.get<CommonBlockDetails>().add_object(obj);
8907       }
8908     }
8909   }
8910 }
8911 
8912 void ResolveNamesVisitor::CreateObjectSymbols(
8913     const std::list<parser::ObjectDecl> &decls, Attr attr) {
8914   for (const parser::ObjectDecl &decl : decls) {
8915     SetImplicitAttr(DeclareEntity<ObjectEntityDetails>(
8916                         std::get<parser::ObjectName>(decl.t), Attrs{}),
8917         attr);
8918   }
8919 }
8920 
8921 void ResolveNamesVisitor::CreateGeneric(const parser::GenericSpec &x) {
8922   auto info{GenericSpecInfo{x}};
8923   SourceName symbolName{info.symbolName()};
8924   if (IsLogicalConstant(context(), symbolName)) {
8925     Say(symbolName,
8926         "Logical constant '%s' may not be used as a defined operator"_err_en_US);
8927     return;
8928   }
8929   GenericDetails genericDetails;
8930   Symbol *existing{nullptr};
8931   // Check all variants of names, e.g. "operator(.ne.)" for "operator(/=)"
8932   for (const std::string &n : GetAllNames(context(), symbolName)) {
8933     existing = currScope().FindSymbol(SourceName{n});
8934     if (existing) {
8935       break;
8936     }
8937   }
8938   if (existing) {
8939     Symbol &ultimate{existing->GetUltimate()};
8940     if (auto *existingGeneric{ultimate.detailsIf<GenericDetails>()}) {
8941       if (&existing->owner() == &currScope()) {
8942         if (const auto *existingUse{existing->detailsIf<UseDetails>()}) {
8943           // Create a local copy of a use associated generic so that
8944           // it can be locally extended without corrupting the original.
8945           genericDetails.CopyFrom(*existingGeneric);
8946           if (existingGeneric->specific()) {
8947             genericDetails.set_specific(*existingGeneric->specific());
8948           }
8949           AddGenericUse(
8950               genericDetails, existing->name(), existingUse->symbol());
8951         } else if (existing == &ultimate) {
8952           // Extending an extant generic in the same scope
8953           info.Resolve(existing);
8954           return;
8955         } else {
8956           // Host association of a generic is handled elsewhere
8957           CHECK(existing->has<HostAssocDetails>());
8958         }
8959       } else {
8960         // Create a new generic for this scope.
8961       }
8962     } else if (ultimate.has<SubprogramDetails>() ||
8963         ultimate.has<SubprogramNameDetails>()) {
8964       genericDetails.set_specific(*existing);
8965     } else if (ultimate.has<ProcEntityDetails>()) {
8966       if (existing->name() != symbolName ||
8967           !ultimate.attrs().test(Attr::INTRINSIC)) {
8968         genericDetails.set_specific(*existing);
8969       }
8970     } else if (ultimate.has<DerivedTypeDetails>()) {
8971       genericDetails.set_derivedType(*existing);
8972     } else if (&existing->owner() == &currScope()) {
8973       SayAlreadyDeclared(symbolName, *existing);
8974       return;
8975     }
8976     if (&existing->owner() == &currScope()) {
8977       EraseSymbol(*existing);
8978     }
8979   }
8980   info.Resolve(&MakeSymbol(symbolName, Attrs{}, std::move(genericDetails)));
8981 }
8982 
8983 void ResolveNamesVisitor::FinishSpecificationPart(
8984     const std::list<parser::DeclarationConstruct> &decls) {
8985   misparsedStmtFuncFound_ = false;
8986   funcResultStack().CompleteFunctionResultType();
8987   CheckImports();
8988   for (auto &pair : currScope()) {
8989     auto &symbol{*pair.second};
8990     if (inInterfaceBlock()) {
8991       ConvertToObjectEntity(symbol);
8992     }
8993     if (NeedsExplicitType(symbol)) {
8994       ApplyImplicitRules(symbol);
8995     }
8996     if (IsDummy(symbol) && isImplicitNoneType() &&
8997         symbol.test(Symbol::Flag::Implicit) && !context().HasError(symbol)) {
8998       Say(symbol.name(),
8999           "No explicit type declared for dummy argument '%s'"_err_en_US);
9000       context().SetError(symbol);
9001     }
9002     if (symbol.has<GenericDetails>()) {
9003       CheckGenericProcedures(symbol);
9004     }
9005     if (!symbol.has<HostAssocDetails>()) {
9006       CheckPossibleBadForwardRef(symbol);
9007     }
9008     // Propagate BIND(C) attribute to procedure entities from their interfaces,
9009     // but not the NAME=, even if it is empty (which would be a reasonable
9010     // and useful behavior, actually).  This interpretation is not at all
9011     // clearly described in the standard, but matches the behavior of several
9012     // other compilers.
9013     if (auto *proc{symbol.detailsIf<ProcEntityDetails>()}; proc &&
9014         !proc->isDummy() && !IsPointer(symbol) &&
9015         !symbol.attrs().test(Attr::BIND_C)) {
9016       if (const Symbol * iface{proc->procInterface()};
9017           iface && IsBindCProcedure(*iface)) {
9018         SetImplicitAttr(symbol, Attr::BIND_C);
9019         SetBindNameOn(symbol);
9020       }
9021     }
9022   }
9023   currScope().InstantiateDerivedTypes();
9024   for (const auto &decl : decls) {
9025     if (const auto *statement{std::get_if<
9026             parser::Statement<common::Indirection<parser::StmtFunctionStmt>>>(
9027             &decl.u)}) {
9028       messageHandler().set_currStmtSource(statement->source);
9029       AnalyzeStmtFunctionStmt(statement->statement.value());
9030     }
9031   }
9032   // TODO: what about instantiations in BLOCK?
9033   CheckSaveStmts();
9034   CheckCommonBlocks();
9035   if (!inInterfaceBlock()) {
9036     // TODO: warn for the case where the EQUIVALENCE statement is in a
9037     // procedure declaration in an interface block
9038     CheckEquivalenceSets();
9039   }
9040 }
9041 
9042 // Analyze the bodies of statement functions now that the symbols in this
9043 // specification part have been fully declared and implicitly typed.
9044 // (Statement function references are not allowed in specification
9045 // expressions, so it's safe to defer processing their definitions.)
9046 void ResolveNamesVisitor::AnalyzeStmtFunctionStmt(
9047     const parser::StmtFunctionStmt &stmtFunc) {
9048   const auto &name{std::get<parser::Name>(stmtFunc.t)};
9049   Symbol *symbol{name.symbol};
9050   auto *details{symbol ? symbol->detailsIf<SubprogramDetails>() : nullptr};
9051   if (!details || !symbol->scope() ||
9052       &symbol->scope()->parent() != &currScope() || details->isInterface() ||
9053       details->isDummy() || details->entryScope() ||
9054       details->moduleInterface() || symbol->test(Symbol::Flag::Subroutine)) {
9055     return; // error recovery
9056   }
9057   // Resolve the symbols on the RHS of the statement function.
9058   PushScope(*symbol->scope());
9059   const auto &parsedExpr{std::get<parser::Scalar<parser::Expr>>(stmtFunc.t)};
9060   Walk(parsedExpr);
9061   PopScope();
9062   if (auto expr{AnalyzeExpr(context(), stmtFunc)}) {
9063     if (auto type{evaluate::DynamicType::From(*symbol)}) {
9064       if (auto converted{evaluate::ConvertToType(*type, std::move(*expr))}) {
9065         details->set_stmtFunction(std::move(*converted));
9066       } else {
9067         Say(name.source,
9068             "Defining expression of statement function '%s' cannot be converted to its result type %s"_err_en_US,
9069             name.source, type->AsFortran());
9070       }
9071     } else {
9072       details->set_stmtFunction(std::move(*expr));
9073     }
9074   }
9075   if (!details->stmtFunction()) {
9076     context().SetError(*symbol);
9077   }
9078 }
9079 
9080 void ResolveNamesVisitor::CheckImports() {
9081   auto &scope{currScope()};
9082   switch (scope.GetImportKind()) {
9083   case common::ImportKind::None:
9084     break;
9085   case common::ImportKind::All:
9086     // C8102: all entities in host must not be hidden
9087     for (const auto &pair : scope.parent()) {
9088       auto &name{pair.first};
9089       std::optional<SourceName> scopeName{scope.GetName()};
9090       if (!scopeName || name != *scopeName) {
9091         CheckImport(prevImportStmt_.value(), name);
9092       }
9093     }
9094     break;
9095   case common::ImportKind::Default:
9096   case common::ImportKind::Only:
9097     // C8102: entities named in IMPORT must not be hidden
9098     for (auto &name : scope.importNames()) {
9099       CheckImport(name, name);
9100     }
9101     break;
9102   }
9103 }
9104 
9105 void ResolveNamesVisitor::CheckImport(
9106     const SourceName &location, const SourceName &name) {
9107   if (auto *symbol{FindInScope(name)}) {
9108     const Symbol &ultimate{symbol->GetUltimate()};
9109     if (&ultimate.owner() == &currScope()) {
9110       Say(location, "'%s' from host is not accessible"_err_en_US, name)
9111           .Attach(symbol->name(), "'%s' is hidden by this entity"_because_en_US,
9112               symbol->name());
9113     }
9114   }
9115 }
9116 
9117 bool ResolveNamesVisitor::Pre(const parser::ImplicitStmt &x) {
9118   return CheckNotInBlock("IMPLICIT") && // C1107
9119       ImplicitRulesVisitor::Pre(x);
9120 }
9121 
9122 void ResolveNamesVisitor::Post(const parser::PointerObject &x) {
9123   common::visit(common::visitors{
9124                     [&](const parser::Name &x) { ResolveName(x); },
9125                     [&](const parser::StructureComponent &x) {
9126                       ResolveStructureComponent(x);
9127                     },
9128                 },
9129       x.u);
9130 }
9131 void ResolveNamesVisitor::Post(const parser::AllocateObject &x) {
9132   common::visit(common::visitors{
9133                     [&](const parser::Name &x) { ResolveName(x); },
9134                     [&](const parser::StructureComponent &x) {
9135                       ResolveStructureComponent(x);
9136                     },
9137                 },
9138       x.u);
9139 }
9140 
9141 bool ResolveNamesVisitor::Pre(const parser::PointerAssignmentStmt &x) {
9142   const auto &dataRef{std::get<parser::DataRef>(x.t)};
9143   const auto &bounds{std::get<parser::PointerAssignmentStmt::Bounds>(x.t)};
9144   const auto &expr{std::get<parser::Expr>(x.t)};
9145   ResolveDataRef(dataRef);
9146   Symbol *ptrSymbol{parser::GetLastName(dataRef).symbol};
9147   Walk(bounds);
9148   // Resolve unrestricted specific intrinsic procedures as in "p => cos".
9149   if (const parser::Name * name{parser::Unwrap<parser::Name>(expr)}) {
9150     if (NameIsKnownOrIntrinsic(*name)) {
9151       if (Symbol * symbol{name->symbol}) {
9152         if (IsProcedurePointer(ptrSymbol) &&
9153             !ptrSymbol->test(Symbol::Flag::Function) &&
9154             !ptrSymbol->test(Symbol::Flag::Subroutine)) {
9155           if (symbol->test(Symbol::Flag::Function)) {
9156             ApplyImplicitRules(*ptrSymbol);
9157           }
9158         }
9159         // If the name is known because it is an object entity from a host
9160         // procedure, create a host associated symbol.
9161         if (symbol->GetUltimate().has<ObjectEntityDetails>() &&
9162             IsUplevelReference(*symbol)) {
9163           MakeHostAssocSymbol(*name, *symbol);
9164         }
9165       }
9166       return false;
9167     }
9168     // Can also reference a global external procedure here
9169     if (auto it{context().globalScope().find(name->source)};
9170         it != context().globalScope().end()) {
9171       Symbol &global{*it->second};
9172       if (IsProcedure(global)) {
9173         Resolve(*name, global);
9174         return false;
9175       }
9176     }
9177     if (IsProcedurePointer(parser::GetLastName(dataRef).symbol) &&
9178         !FindSymbol(*name)) {
9179       // Unknown target of procedure pointer must be an external procedure
9180       Symbol &symbol{MakeSymbol(
9181           context().globalScope(), name->source, Attrs{Attr::EXTERNAL})};
9182       symbol.implicitAttrs().set(Attr::EXTERNAL);
9183       Resolve(*name, symbol);
9184       ConvertToProcEntity(symbol, name->source);
9185       return false;
9186     }
9187   }
9188   Walk(expr);
9189   return false;
9190 }
9191 void ResolveNamesVisitor::Post(const parser::Designator &x) {
9192   ResolveDesignator(x);
9193 }
9194 void ResolveNamesVisitor::Post(const parser::SubstringInquiry &x) {
9195   Walk(std::get<parser::SubstringRange>(x.v.t).t);
9196   ResolveDataRef(std::get<parser::DataRef>(x.v.t));
9197 }
9198 
9199 void ResolveNamesVisitor::Post(const parser::ProcComponentRef &x) {
9200   ResolveStructureComponent(x.v.thing);
9201 }
9202 void ResolveNamesVisitor::Post(const parser::TypeGuardStmt &x) {
9203   DeclTypeSpecVisitor::Post(x);
9204   ConstructVisitor::Post(x);
9205 }
9206 bool ResolveNamesVisitor::Pre(const parser::StmtFunctionStmt &x) {
9207   if (HandleStmtFunction(x)) {
9208     return false;
9209   } else {
9210     // This is an array element or pointer-valued function assignment:
9211     // resolve the names of indices/arguments
9212     const auto &names{std::get<std::list<parser::Name>>(x.t)};
9213     for (auto &name : names) {
9214       ResolveName(name);
9215     }
9216     return true;
9217   }
9218 }
9219 
9220 bool ResolveNamesVisitor::Pre(const parser::DefinedOpName &x) {
9221   const parser::Name &name{x.v};
9222   if (FindSymbol(name)) {
9223     // OK
9224   } else if (IsLogicalConstant(context(), name.source)) {
9225     Say(name,
9226         "Logical constant '%s' may not be used as a defined operator"_err_en_US);
9227   } else {
9228     // Resolved later in expression semantics
9229     MakePlaceholder(name, MiscDetails::Kind::TypeBoundDefinedOp);
9230   }
9231   return false;
9232 }
9233 
9234 void ResolveNamesVisitor::Post(const parser::AssignStmt &x) {
9235   if (auto *name{ResolveName(std::get<parser::Name>(x.t))}) {
9236     CheckEntryDummyUse(name->source, name->symbol);
9237     ConvertToObjectEntity(DEREF(name->symbol));
9238   }
9239 }
9240 void ResolveNamesVisitor::Post(const parser::AssignedGotoStmt &x) {
9241   if (auto *name{ResolveName(std::get<parser::Name>(x.t))}) {
9242     CheckEntryDummyUse(name->source, name->symbol);
9243     ConvertToObjectEntity(DEREF(name->symbol));
9244   }
9245 }
9246 
9247 void ResolveNamesVisitor::Post(const parser::CompilerDirective &x) {
9248   if (std::holds_alternative<parser::CompilerDirective::VectorAlways>(x.u)) {
9249     return;
9250   }
9251   if (const auto *tkr{
9252           std::get_if<std::list<parser::CompilerDirective::IgnoreTKR>>(&x.u)}) {
9253     if (currScope().IsTopLevel() ||
9254         GetProgramUnitContaining(currScope()).kind() !=
9255             Scope::Kind::Subprogram) {
9256       Say(x.source,
9257           "!DIR$ IGNORE_TKR directive must appear in a subroutine or function"_err_en_US);
9258       return;
9259     }
9260     if (!inSpecificationPart_) {
9261       Say(x.source,
9262           "!DIR$ IGNORE_TKR directive must appear in the specification part"_err_en_US);
9263       return;
9264     }
9265     if (tkr->empty()) {
9266       Symbol *symbol{currScope().symbol()};
9267       if (SubprogramDetails *
9268           subp{symbol ? symbol->detailsIf<SubprogramDetails>() : nullptr}) {
9269         subp->set_defaultIgnoreTKR(true);
9270       }
9271     } else {
9272       for (const parser::CompilerDirective::IgnoreTKR &item : *tkr) {
9273         common::IgnoreTKRSet set;
9274         if (const auto &maybeList{
9275                 std::get<std::optional<std::list<const char *>>>(item.t)}) {
9276           for (const char *p : *maybeList) {
9277             if (p) {
9278               switch (*p) {
9279               case 't':
9280                 set.set(common::IgnoreTKR::Type);
9281                 break;
9282               case 'k':
9283                 set.set(common::IgnoreTKR::Kind);
9284                 break;
9285               case 'r':
9286                 set.set(common::IgnoreTKR::Rank);
9287                 break;
9288               case 'd':
9289                 set.set(common::IgnoreTKR::Device);
9290                 break;
9291               case 'm':
9292                 set.set(common::IgnoreTKR::Managed);
9293                 break;
9294               case 'c':
9295                 set.set(common::IgnoreTKR::Contiguous);
9296                 break;
9297               case 'a':
9298                 set = common::ignoreTKRAll;
9299                 break;
9300               default:
9301                 Say(x.source,
9302                     "'%c' is not a valid letter for !DIR$ IGNORE_TKR directive"_err_en_US,
9303                     *p);
9304                 set = common::ignoreTKRAll;
9305                 break;
9306               }
9307             }
9308           }
9309           if (set.empty()) {
9310             Say(x.source,
9311                 "!DIR$ IGNORE_TKR directive may not have an empty parenthesized list of letters"_err_en_US);
9312           }
9313         } else { // no (list)
9314           set = common::ignoreTKRAll;
9315           ;
9316         }
9317         const auto &name{std::get<parser::Name>(item.t)};
9318         Symbol *symbol{FindSymbol(name)};
9319         if (!symbol) {
9320           symbol = &MakeSymbol(name, Attrs{}, ObjectEntityDetails{});
9321         }
9322         if (symbol->owner() != currScope()) {
9323           SayWithDecl(
9324               name, *symbol, "'%s' must be local to this subprogram"_err_en_US);
9325         } else {
9326           ConvertToObjectEntity(*symbol);
9327           if (auto *object{symbol->detailsIf<ObjectEntityDetails>()}) {
9328             object->set_ignoreTKR(set);
9329           } else {
9330             SayWithDecl(name, *symbol, "'%s' must be an object"_err_en_US);
9331           }
9332         }
9333       }
9334     }
9335   } else if (context().ShouldWarn(common::UsageWarning::IgnoredDirective)) {
9336     Say(x.source, "Unrecognized compiler directive was ignored"_warn_en_US)
9337         .set_usageWarning(common::UsageWarning::IgnoredDirective);
9338   }
9339 }
9340 
9341 bool ResolveNamesVisitor::Pre(const parser::ProgramUnit &x) {
9342   if (std::holds_alternative<common::Indirection<parser::CompilerDirective>>(
9343           x.u)) {
9344     // TODO: global directives
9345     return true;
9346   }
9347   if (std::holds_alternative<
9348           common::Indirection<parser::OpenACCRoutineConstruct>>(x.u)) {
9349     ResolveAccParts(context(), x, &topScope_);
9350     return false;
9351   }
9352   ProgramTree &root{ProgramTree::Build(x, context())};
9353   SetScope(topScope_);
9354   ResolveSpecificationParts(root);
9355   FinishSpecificationParts(root);
9356   ResolveExecutionParts(root);
9357   FinishExecutionParts(root);
9358   ResolveAccParts(context(), x, /*topScope=*/nullptr);
9359   ResolveOmpParts(context(), x);
9360   return false;
9361 }
9362 
9363 template <typename A> std::set<SourceName> GetUses(const A &x) {
9364   std::set<SourceName> uses;
9365   if constexpr (!std::is_same_v<A, parser::CompilerDirective> &&
9366       !std::is_same_v<A, parser::OpenACCRoutineConstruct>) {
9367     const auto &spec{std::get<parser::SpecificationPart>(x.t)};
9368     const auto &unitUses{std::get<
9369         std::list<parser::Statement<common::Indirection<parser::UseStmt>>>>(
9370         spec.t)};
9371     for (const auto &u : unitUses) {
9372       uses.insert(u.statement.value().moduleName.source);
9373     }
9374   }
9375   return uses;
9376 }
9377 
9378 bool ResolveNamesVisitor::Pre(const parser::Program &x) {
9379   std::map<SourceName, const parser::ProgramUnit *> modules;
9380   std::set<SourceName> uses;
9381   bool disordered{false};
9382   for (const auto &progUnit : x.v) {
9383     if (const auto *indMod{
9384             std::get_if<common::Indirection<parser::Module>>(&progUnit.u)}) {
9385       const parser::Module &mod{indMod->value()};
9386       const auto &moduleStmt{
9387           std::get<parser::Statement<parser::ModuleStmt>>(mod.t)};
9388       const SourceName &name{moduleStmt.statement.v.source};
9389       if (auto iter{modules.find(name)}; iter != modules.end()) {
9390         Say(name,
9391             "Module '%s' appears multiple times in a compilation unit"_err_en_US)
9392             .Attach(iter->first, "First definition of module"_en_US);
9393         return true;
9394       }
9395       modules.emplace(name, &progUnit);
9396       if (auto iter{uses.find(name)}; iter != uses.end()) {
9397         if (context().ShouldWarn(common::LanguageFeature::MiscUseExtensions)) {
9398           Say(name,
9399               "A USE statement referencing module '%s' appears earlier in this compilation unit"_port_en_US,
9400               name)
9401               .Attach(*iter, "First USE of module"_en_US);
9402         }
9403         disordered = true;
9404       }
9405     }
9406     for (SourceName used : common::visit(
9407              [](const auto &indUnit) { return GetUses(indUnit.value()); },
9408              progUnit.u)) {
9409       uses.insert(used);
9410     }
9411   }
9412   if (!disordered) {
9413     return true;
9414   }
9415   // Process modules in topological order
9416   std::vector<const parser::ProgramUnit *> moduleOrder;
9417   while (!modules.empty()) {
9418     bool ok;
9419     for (const auto &pair : modules) {
9420       const SourceName &name{pair.first};
9421       const parser::ProgramUnit &progUnit{*pair.second};
9422       const parser::Module &m{
9423           std::get<common::Indirection<parser::Module>>(progUnit.u).value()};
9424       ok = true;
9425       for (const SourceName &use : GetUses(m)) {
9426         if (modules.find(use) != modules.end()) {
9427           ok = false;
9428           break;
9429         }
9430       }
9431       if (ok) {
9432         moduleOrder.push_back(&progUnit);
9433         modules.erase(name);
9434         break;
9435       }
9436     }
9437     if (!ok) {
9438       Message *msg{nullptr};
9439       for (const auto &pair : modules) {
9440         if (msg) {
9441           msg->Attach(pair.first, "Module in a cycle"_en_US);
9442         } else {
9443           msg = &Say(pair.first,
9444               "Some modules in this compilation unit form one or more cycles of dependence"_err_en_US);
9445         }
9446       }
9447       return false;
9448     }
9449   }
9450   // Modules can be ordered.  Process them first, and then all of the other
9451   // program units.
9452   for (const parser::ProgramUnit *progUnit : moduleOrder) {
9453     Walk(*progUnit);
9454   }
9455   for (const auto &progUnit : x.v) {
9456     if (!std::get_if<common::Indirection<parser::Module>>(&progUnit.u)) {
9457       Walk(progUnit);
9458     }
9459   }
9460   return false;
9461 }
9462 
9463 // References to procedures need to record that their symbols are known
9464 // to be procedures, so that they don't get converted to objects by default.
9465 class ExecutionPartCallSkimmer : public ExecutionPartSkimmerBase {
9466 public:
9467   explicit ExecutionPartCallSkimmer(ResolveNamesVisitor &resolver)
9468       : resolver_{resolver} {}
9469 
9470   void Walk(const parser::ExecutionPart &exec) {
9471     parser::Walk(exec, *this);
9472     EndWalk();
9473   }
9474 
9475   using ExecutionPartSkimmerBase::Post;
9476   using ExecutionPartSkimmerBase::Pre;
9477 
9478   void Post(const parser::FunctionReference &fr) {
9479     NoteCall(Symbol::Flag::Function, fr.v, false);
9480   }
9481   void Post(const parser::CallStmt &cs) {
9482     NoteCall(Symbol::Flag::Subroutine, cs.call, cs.chevrons.has_value());
9483   }
9484 
9485 private:
9486   void NoteCall(
9487       Symbol::Flag flag, const parser::Call &call, bool hasCUDAChevrons) {
9488     auto &designator{std::get<parser::ProcedureDesignator>(call.t)};
9489     if (const auto *name{std::get_if<parser::Name>(&designator.u)}) {
9490       if (!IsHidden(name->source)) {
9491         resolver_.NoteExecutablePartCall(flag, name->source, hasCUDAChevrons);
9492       }
9493     }
9494   }
9495 
9496   ResolveNamesVisitor &resolver_;
9497 };
9498 
9499 // Build the scope tree and resolve names in the specification parts of this
9500 // node and its children
9501 void ResolveNamesVisitor::ResolveSpecificationParts(ProgramTree &node) {
9502   if (node.isSpecificationPartResolved()) {
9503     return; // been here already
9504   }
9505   node.set_isSpecificationPartResolved();
9506   if (!BeginScopeForNode(node)) {
9507     return; // an error prevented scope from being created
9508   }
9509   Scope &scope{currScope()};
9510   node.set_scope(scope);
9511   AddSubpNames(node);
9512   common::visit(
9513       [&](const auto *x) {
9514         if (x) {
9515           Walk(*x);
9516         }
9517       },
9518       node.stmt());
9519   Walk(node.spec());
9520   bool inDeviceSubprogram = false;
9521   // If this is a function, convert result to an object. This is to prevent the
9522   // result from being converted later to a function symbol if it is called
9523   // inside the function.
9524   // If the result is function pointer, then ConvertToObjectEntity will not
9525   // convert the result to an object, and calling the symbol inside the function
9526   // will result in calls to the result pointer.
9527   // A function cannot be called recursively if RESULT was not used to define a
9528   // distinct result name (15.6.2.2 point 4.).
9529   if (Symbol * symbol{scope.symbol()}) {
9530     if (auto *details{symbol->detailsIf<SubprogramDetails>()}) {
9531       if (details->isFunction()) {
9532         ConvertToObjectEntity(const_cast<Symbol &>(details->result()));
9533       }
9534       // Check the current procedure is a device procedure to apply implicit
9535       // attribute at the end.
9536       if (auto attrs{details->cudaSubprogramAttrs()}) {
9537         if (*attrs == common::CUDASubprogramAttrs::Device ||
9538             *attrs == common::CUDASubprogramAttrs::Global ||
9539             *attrs == common::CUDASubprogramAttrs::Grid_Global) {
9540           inDeviceSubprogram = true;
9541         }
9542       }
9543     }
9544   }
9545   if (node.IsModule()) {
9546     ApplyDefaultAccess();
9547   }
9548   for (auto &child : node.children()) {
9549     ResolveSpecificationParts(child);
9550   }
9551   if (node.exec()) {
9552     ExecutionPartCallSkimmer{*this}.Walk(*node.exec());
9553     HandleImpliedAsynchronousInScope(node.exec()->v);
9554   }
9555   EndScopeForNode(node);
9556   // Ensure that every object entity has a type.
9557   bool inModule{node.GetKind() == ProgramTree::Kind::Module ||
9558       node.GetKind() == ProgramTree::Kind::Submodule};
9559   for (auto &pair : *node.scope()) {
9560     Symbol &symbol{*pair.second};
9561     if (inModule && symbol.attrs().test(Attr::EXTERNAL) && !IsPointer(symbol) &&
9562         !symbol.test(Symbol::Flag::Function) &&
9563         !symbol.test(Symbol::Flag::Subroutine)) {
9564       // in a module, external proc without return type is subroutine
9565       symbol.set(
9566           symbol.GetType() ? Symbol::Flag::Function : Symbol::Flag::Subroutine);
9567     }
9568     ApplyImplicitRules(symbol);
9569     // Apply CUDA implicit attributes if needed.
9570     if (inDeviceSubprogram && symbol.has<ObjectEntityDetails>()) {
9571       auto *object{symbol.detailsIf<ObjectEntityDetails>()};
9572       if (!object->cudaDataAttr() && !IsValue(symbol) &&
9573           (IsDummy(symbol) || object->IsArray())) {
9574         // Implicitly set device attribute if none is set in device context.
9575         object->set_cudaDataAttr(common::CUDADataAttr::Device);
9576       }
9577     }
9578   }
9579 }
9580 
9581 // Add SubprogramNameDetails symbols for module and internal subprograms and
9582 // their ENTRY statements.
9583 void ResolveNamesVisitor::AddSubpNames(ProgramTree &node) {
9584   auto kind{
9585       node.IsModule() ? SubprogramKind::Module : SubprogramKind::Internal};
9586   for (auto &child : node.children()) {
9587     auto &symbol{MakeSymbol(child.name(), SubprogramNameDetails{kind, child})};
9588     if (child.HasModulePrefix()) {
9589       SetExplicitAttr(symbol, Attr::MODULE);
9590     }
9591     if (child.bindingSpec()) {
9592       SetExplicitAttr(symbol, Attr::BIND_C);
9593     }
9594     auto childKind{child.GetKind()};
9595     if (childKind == ProgramTree::Kind::Function) {
9596       symbol.set(Symbol::Flag::Function);
9597     } else if (childKind == ProgramTree::Kind::Subroutine) {
9598       symbol.set(Symbol::Flag::Subroutine);
9599     } else {
9600       continue; // make ENTRY symbols only where valid
9601     }
9602     for (const auto &entryStmt : child.entryStmts()) {
9603       SubprogramNameDetails details{kind, child};
9604       auto &symbol{
9605           MakeSymbol(std::get<parser::Name>(entryStmt->t), std::move(details))};
9606       symbol.set(child.GetSubpFlag());
9607       if (child.HasModulePrefix()) {
9608         SetExplicitAttr(symbol, Attr::MODULE);
9609       }
9610       if (child.bindingSpec()) {
9611         SetExplicitAttr(symbol, Attr::BIND_C);
9612       }
9613     }
9614   }
9615   for (const auto &generic : node.genericSpecs()) {
9616     if (const auto *name{std::get_if<parser::Name>(&generic->u)}) {
9617       if (currScope().find(name->source) != currScope().end()) {
9618         // If this scope has both a generic interface and a contained
9619         // subprogram with the same name, create the generic's symbol
9620         // now so that any other generics of the same name that are pulled
9621         // into scope later via USE association will properly merge instead
9622         // of raising a bogus error due a conflict with the subprogram.
9623         CreateGeneric(*generic);
9624       }
9625     }
9626   }
9627 }
9628 
9629 // Push a new scope for this node or return false on error.
9630 bool ResolveNamesVisitor::BeginScopeForNode(const ProgramTree &node) {
9631   switch (node.GetKind()) {
9632     SWITCH_COVERS_ALL_CASES
9633   case ProgramTree::Kind::Program:
9634     PushScope(Scope::Kind::MainProgram,
9635         &MakeSymbol(node.name(), MainProgramDetails{}));
9636     return true;
9637   case ProgramTree::Kind::Function:
9638   case ProgramTree::Kind::Subroutine:
9639     return BeginSubprogram(node.name(), node.GetSubpFlag(),
9640         node.HasModulePrefix(), node.bindingSpec(), &node.entryStmts());
9641   case ProgramTree::Kind::MpSubprogram:
9642     return BeginMpSubprogram(node.name());
9643   case ProgramTree::Kind::Module:
9644     BeginModule(node.name(), false);
9645     return true;
9646   case ProgramTree::Kind::Submodule:
9647     return BeginSubmodule(node.name(), node.GetParentId());
9648   case ProgramTree::Kind::BlockData:
9649     PushBlockDataScope(node.name());
9650     return true;
9651   }
9652 }
9653 
9654 void ResolveNamesVisitor::EndScopeForNode(const ProgramTree &node) {
9655   std::optional<parser::CharBlock> stmtSource;
9656   const std::optional<parser::LanguageBindingSpec> *binding{nullptr};
9657   common::visit(
9658       common::visitors{
9659           [&](const parser::Statement<parser::FunctionStmt> *stmt) {
9660             if (stmt) {
9661               stmtSource = stmt->source;
9662               if (const auto &maybeSuffix{
9663                       std::get<std::optional<parser::Suffix>>(
9664                           stmt->statement.t)}) {
9665                 binding = &maybeSuffix->binding;
9666               }
9667             }
9668           },
9669           [&](const parser::Statement<parser::SubroutineStmt> *stmt) {
9670             if (stmt) {
9671               stmtSource = stmt->source;
9672               binding = &std::get<std::optional<parser::LanguageBindingSpec>>(
9673                   stmt->statement.t);
9674             }
9675           },
9676           [](const auto *) {},
9677       },
9678       node.stmt());
9679   EndSubprogram(stmtSource, binding, &node.entryStmts());
9680 }
9681 
9682 // Some analyses and checks, such as the processing of initializers of
9683 // pointers, are deferred until all of the pertinent specification parts
9684 // have been visited.  This deferred processing enables the use of forward
9685 // references in these circumstances.
9686 // Data statement objects with implicit derived types are finally
9687 // resolved here.
9688 class DeferredCheckVisitor {
9689 public:
9690   explicit DeferredCheckVisitor(ResolveNamesVisitor &resolver)
9691       : resolver_{resolver} {}
9692 
9693   template <typename A> void Walk(const A &x) { parser::Walk(x, *this); }
9694 
9695   template <typename A> bool Pre(const A &) { return true; }
9696   template <typename A> void Post(const A &) {}
9697 
9698   void Post(const parser::DerivedTypeStmt &x) {
9699     const auto &name{std::get<parser::Name>(x.t)};
9700     if (Symbol * symbol{name.symbol}) {
9701       if (Scope * scope{symbol->scope()}) {
9702         if (scope->IsDerivedType()) {
9703           CHECK(outerScope_ == nullptr);
9704           outerScope_ = &resolver_.currScope();
9705           resolver_.SetScope(*scope);
9706         }
9707       }
9708     }
9709   }
9710   void Post(const parser::EndTypeStmt &) {
9711     if (outerScope_) {
9712       resolver_.SetScope(*outerScope_);
9713       outerScope_ = nullptr;
9714     }
9715   }
9716 
9717   void Post(const parser::ProcInterface &pi) {
9718     if (const auto *name{std::get_if<parser::Name>(&pi.u)}) {
9719       resolver_.CheckExplicitInterface(*name);
9720     }
9721   }
9722   bool Pre(const parser::EntityDecl &decl) {
9723     Init(std::get<parser::Name>(decl.t),
9724         std::get<std::optional<parser::Initialization>>(decl.t));
9725     return false;
9726   }
9727   bool Pre(const parser::ComponentDecl &decl) {
9728     Init(std::get<parser::Name>(decl.t),
9729         std::get<std::optional<parser::Initialization>>(decl.t));
9730     return false;
9731   }
9732   bool Pre(const parser::ProcDecl &decl) {
9733     if (const auto &init{
9734             std::get<std::optional<parser::ProcPointerInit>>(decl.t)}) {
9735       resolver_.PointerInitialization(std::get<parser::Name>(decl.t), *init);
9736     }
9737     return false;
9738   }
9739   void Post(const parser::TypeBoundProcedureStmt::WithInterface &tbps) {
9740     resolver_.CheckExplicitInterface(tbps.interfaceName);
9741   }
9742   void Post(const parser::TypeBoundProcedureStmt::WithoutInterface &tbps) {
9743     if (outerScope_) {
9744       resolver_.CheckBindings(tbps);
9745     }
9746   }
9747   bool Pre(const parser::DataStmtObject &) {
9748     ++dataStmtObjectNesting_;
9749     return true;
9750   }
9751   void Post(const parser::DataStmtObject &) { --dataStmtObjectNesting_; }
9752   void Post(const parser::Designator &x) {
9753     if (dataStmtObjectNesting_ > 0) {
9754       resolver_.ResolveDesignator(x);
9755     }
9756   }
9757 
9758 private:
9759   void Init(const parser::Name &name,
9760       const std::optional<parser::Initialization> &init) {
9761     if (init) {
9762       if (const auto *target{
9763               std::get_if<parser::InitialDataTarget>(&init->u)}) {
9764         resolver_.PointerInitialization(name, *target);
9765       } else if (const auto *expr{
9766                      std::get_if<parser::ConstantExpr>(&init->u)}) {
9767         if (name.symbol) {
9768           if (const auto *object{name.symbol->detailsIf<ObjectEntityDetails>()};
9769               !object || !object->init()) {
9770             resolver_.NonPointerInitialization(name, *expr);
9771           }
9772         }
9773       }
9774     }
9775   }
9776 
9777   ResolveNamesVisitor &resolver_;
9778   Scope *outerScope_{nullptr};
9779   int dataStmtObjectNesting_{0};
9780 };
9781 
9782 // Perform checks and completions that need to happen after all of
9783 // the specification parts but before any of the execution parts.
9784 void ResolveNamesVisitor::FinishSpecificationParts(const ProgramTree &node) {
9785   if (!node.scope()) {
9786     return; // error occurred creating scope
9787   }
9788   auto flagRestorer{common::ScopedSet(inSpecificationPart_, true)};
9789   SetScope(*node.scope());
9790   // The initializers of pointers and non-PARAMETER objects, the default
9791   // initializers of components, and non-deferred type-bound procedure
9792   // bindings have not yet been traversed.
9793   // We do that now, when any forward references that appeared
9794   // in those initializers will resolve to the right symbols without
9795   // incurring spurious errors with IMPLICIT NONE or forward references
9796   // to nested subprograms.
9797   DeferredCheckVisitor{*this}.Walk(node.spec());
9798   for (Scope &childScope : currScope().children()) {
9799     if (childScope.IsParameterizedDerivedTypeInstantiation()) {
9800       FinishDerivedTypeInstantiation(childScope);
9801     }
9802   }
9803   for (const auto &child : node.children()) {
9804     FinishSpecificationParts(child);
9805   }
9806 }
9807 
9808 void ResolveNamesVisitor::FinishExecutionParts(const ProgramTree &node) {
9809   if (node.scope()) {
9810     SetScope(*node.scope());
9811     if (node.exec()) {
9812       DeferredCheckVisitor{*this}.Walk(*node.exec());
9813     }
9814     for (const auto &child : node.children()) {
9815       FinishExecutionParts(child);
9816     }
9817   }
9818 }
9819 
9820 // Duplicate and fold component object pointer default initializer designators
9821 // using the actual type parameter values of each particular instantiation.
9822 // Validation is done later in declaration checking.
9823 void ResolveNamesVisitor::FinishDerivedTypeInstantiation(Scope &scope) {
9824   CHECK(scope.IsDerivedType() && !scope.symbol());
9825   if (DerivedTypeSpec * spec{scope.derivedTypeSpec()}) {
9826     spec->Instantiate(currScope());
9827     const Symbol &origTypeSymbol{spec->typeSymbol()};
9828     if (const Scope * origTypeScope{origTypeSymbol.scope()}) {
9829       CHECK(origTypeScope->IsDerivedType() &&
9830           origTypeScope->symbol() == &origTypeSymbol);
9831       auto &foldingContext{GetFoldingContext()};
9832       auto restorer{foldingContext.WithPDTInstance(*spec)};
9833       for (auto &pair : scope) {
9834         Symbol &comp{*pair.second};
9835         const Symbol &origComp{DEREF(FindInScope(*origTypeScope, comp.name()))};
9836         if (IsPointer(comp)) {
9837           if (auto *details{comp.detailsIf<ObjectEntityDetails>()}) {
9838             auto origDetails{origComp.get<ObjectEntityDetails>()};
9839             if (const MaybeExpr & init{origDetails.init()}) {
9840               SomeExpr newInit{*init};
9841               MaybeExpr folded{FoldExpr(std::move(newInit))};
9842               details->set_init(std::move(folded));
9843             }
9844           }
9845         }
9846       }
9847     }
9848   }
9849 }
9850 
9851 // Resolve names in the execution part of this node and its children
9852 void ResolveNamesVisitor::ResolveExecutionParts(const ProgramTree &node) {
9853   if (!node.scope()) {
9854     return; // error occurred creating scope
9855   }
9856   SetScope(*node.scope());
9857   if (const auto *exec{node.exec()}) {
9858     Walk(*exec);
9859   }
9860   FinishNamelists();
9861   if (node.IsModule()) {
9862     // A second final pass to catch new symbols added from implicitly
9863     // typed names in NAMELIST groups or the specification parts of
9864     // module subprograms.
9865     ApplyDefaultAccess();
9866   }
9867   PopScope(); // converts unclassified entities into objects
9868   for (const auto &child : node.children()) {
9869     ResolveExecutionParts(child);
9870   }
9871 }
9872 
9873 void ResolveNamesVisitor::Post(const parser::Program &x) {
9874   // ensure that all temps were deallocated
9875   CHECK(!attrs_);
9876   CHECK(!cudaDataAttr_);
9877   CHECK(!GetDeclTypeSpec());
9878   // Top-level resolution to propagate information across program units after
9879   // each of them has been resolved separately.
9880   ResolveOmpTopLevelParts(context(), x);
9881 }
9882 
9883 // A singleton instance of the scope -> IMPLICIT rules mapping is
9884 // shared by all instances of ResolveNamesVisitor and accessed by this
9885 // pointer when the visitors (other than the top-level original) are
9886 // constructed.
9887 static ImplicitRulesMap *sharedImplicitRulesMap{nullptr};
9888 
9889 bool ResolveNames(
9890     SemanticsContext &context, const parser::Program &program, Scope &top) {
9891   ImplicitRulesMap implicitRulesMap;
9892   auto restorer{common::ScopedSet(sharedImplicitRulesMap, &implicitRulesMap)};
9893   ResolveNamesVisitor{context, implicitRulesMap, top}.Walk(program);
9894   return !context.AnyFatalError();
9895 }
9896 
9897 // Processes a module (but not internal) function when it is referenced
9898 // in a specification expression in a sibling procedure.
9899 void ResolveSpecificationParts(
9900     SemanticsContext &context, const Symbol &subprogram) {
9901   auto originalLocation{context.location()};
9902   ImplicitRulesMap implicitRulesMap;
9903   bool localImplicitRulesMap{false};
9904   if (!sharedImplicitRulesMap) {
9905     sharedImplicitRulesMap = &implicitRulesMap;
9906     localImplicitRulesMap = true;
9907   }
9908   ResolveNamesVisitor visitor{
9909       context, *sharedImplicitRulesMap, context.globalScope()};
9910   const auto &details{subprogram.get<SubprogramNameDetails>()};
9911   ProgramTree &node{details.node()};
9912   const Scope &moduleScope{subprogram.owner()};
9913   if (localImplicitRulesMap) {
9914     visitor.BeginScope(const_cast<Scope &>(moduleScope));
9915   } else {
9916     visitor.SetScope(const_cast<Scope &>(moduleScope));
9917   }
9918   visitor.ResolveSpecificationParts(node);
9919   context.set_location(std::move(originalLocation));
9920   if (localImplicitRulesMap) {
9921     sharedImplicitRulesMap = nullptr;
9922   }
9923 }
9924 
9925 } // namespace Fortran::semantics
9926