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