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