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