1 //===-- lib/Semantics/expression.cpp --------------------------------------===//
2 //
3 // Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4 // See https://llvm.org/LICENSE.txt for license information.
5 // SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6 //
7 //===----------------------------------------------------------------------===//
8 
9 #include "flang/Semantics/expression.h"
10 #include "check-call.h"
11 #include "pointer-assignment.h"
12 #include "resolve-names-utils.h"
13 #include "resolve-names.h"
14 #include "flang/Common/Fortran.h"
15 #include "flang/Common/idioms.h"
16 #include "flang/Evaluate/common.h"
17 #include "flang/Evaluate/fold.h"
18 #include "flang/Evaluate/tools.h"
19 #include "flang/Parser/characters.h"
20 #include "flang/Parser/dump-parse-tree.h"
21 #include "flang/Parser/parse-tree-visitor.h"
22 #include "flang/Parser/parse-tree.h"
23 #include "flang/Semantics/scope.h"
24 #include "flang/Semantics/semantics.h"
25 #include "flang/Semantics/symbol.h"
26 #include "flang/Semantics/tools.h"
27 #include "llvm/Support/raw_ostream.h"
28 #include <algorithm>
29 #include <functional>
30 #include <optional>
31 #include <set>
32 
33 // Typedef for optional generic expressions (ubiquitous in this file)
34 using MaybeExpr =
35     std::optional<Fortran::evaluate::Expr<Fortran::evaluate::SomeType>>;
36 
37 // Much of the code that implements semantic analysis of expressions is
38 // tightly coupled with their typed representations in lib/Evaluate,
39 // and appears here in namespace Fortran::evaluate for convenience.
40 namespace Fortran::evaluate {
41 
42 using common::LanguageFeature;
43 using common::NumericOperator;
44 using common::TypeCategory;
45 
46 static inline std::string ToUpperCase(const std::string &str) {
47   return parser::ToUpperCaseLetters(str);
48 }
49 
50 struct DynamicTypeWithLength : public DynamicType {
51   explicit DynamicTypeWithLength(const DynamicType &t) : DynamicType{t} {}
52   std::optional<Expr<SubscriptInteger>> LEN() const;
53   std::optional<Expr<SubscriptInteger>> length;
54 };
55 
56 std::optional<Expr<SubscriptInteger>> DynamicTypeWithLength::LEN() const {
57   if (length) {
58     return length;
59   } else {
60     return GetCharLength();
61   }
62 }
63 
64 static std::optional<DynamicTypeWithLength> AnalyzeTypeSpec(
65     const std::optional<parser::TypeSpec> &spec) {
66   if (spec) {
67     if (const semantics::DeclTypeSpec * typeSpec{spec->declTypeSpec}) {
68       // Name resolution sets TypeSpec::declTypeSpec only when it's valid
69       // (viz., an intrinsic type with valid known kind or a non-polymorphic
70       // & non-ABSTRACT derived type).
71       if (const semantics::IntrinsicTypeSpec *
72           intrinsic{typeSpec->AsIntrinsic()}) {
73         TypeCategory category{intrinsic->category()};
74         if (auto optKind{ToInt64(intrinsic->kind())}) {
75           int kind{static_cast<int>(*optKind)};
76           if (category == TypeCategory::Character) {
77             const semantics::CharacterTypeSpec &cts{
78                 typeSpec->characterTypeSpec()};
79             const semantics::ParamValue &len{cts.length()};
80             // N.B. CHARACTER(LEN=*) is allowed in type-specs in ALLOCATE() &
81             // type guards, but not in array constructors.
82             return DynamicTypeWithLength{DynamicType{kind, len}};
83           } else {
84             return DynamicTypeWithLength{DynamicType{category, kind}};
85           }
86         }
87       } else if (const semantics::DerivedTypeSpec *
88           derived{typeSpec->AsDerived()}) {
89         return DynamicTypeWithLength{DynamicType{*derived}};
90       }
91     }
92   }
93   return std::nullopt;
94 }
95 
96 // Utilities to set a source location, if we have one, on an actual argument,
97 // when it is statically present.
98 static void SetArgSourceLocation(ActualArgument &x, parser::CharBlock at) {
99   x.set_sourceLocation(at);
100 }
101 static void SetArgSourceLocation(
102     std::optional<ActualArgument> &x, parser::CharBlock at) {
103   if (x) {
104     x->set_sourceLocation(at);
105   }
106 }
107 static void SetArgSourceLocation(
108     std::optional<ActualArgument> &x, std::optional<parser::CharBlock> at) {
109   if (x && at) {
110     x->set_sourceLocation(*at);
111   }
112 }
113 
114 class ArgumentAnalyzer {
115 public:
116   explicit ArgumentAnalyzer(ExpressionAnalyzer &context)
117       : context_{context}, source_{context.GetContextualMessages().at()},
118         isProcedureCall_{false} {}
119   ArgumentAnalyzer(ExpressionAnalyzer &context, parser::CharBlock source,
120       bool isProcedureCall = false)
121       : context_{context}, source_{source}, isProcedureCall_{isProcedureCall} {}
122   bool fatalErrors() const { return fatalErrors_; }
123   ActualArguments &&GetActuals() {
124     CHECK(!fatalErrors_);
125     return std::move(actuals_);
126   }
127   const Expr<SomeType> &GetExpr(std::size_t i) const {
128     return DEREF(actuals_.at(i).value().UnwrapExpr());
129   }
130   Expr<SomeType> &&MoveExpr(std::size_t i) {
131     return std::move(DEREF(actuals_.at(i).value().UnwrapExpr()));
132   }
133   void Analyze(const common::Indirection<parser::Expr> &x) {
134     Analyze(x.value());
135   }
136   void Analyze(const parser::Expr &x) {
137     actuals_.emplace_back(AnalyzeExpr(x));
138     SetArgSourceLocation(actuals_.back(), x.source);
139     fatalErrors_ |= !actuals_.back();
140   }
141   void Analyze(const parser::Variable &);
142   void Analyze(const parser::ActualArgSpec &, bool isSubroutine);
143   void ConvertBOZ(std::optional<DynamicType> &thisType, std::size_t i,
144       std::optional<DynamicType> otherType);
145 
146   bool IsIntrinsicRelational(
147       RelationalOperator, const DynamicType &, const DynamicType &) const;
148   bool IsIntrinsicLogical() const;
149   bool IsIntrinsicNumeric(NumericOperator) const;
150   bool IsIntrinsicConcat() const;
151 
152   bool CheckConformance();
153   bool CheckForNullPointer(const char *where = "as an operand here");
154 
155   // Find and return a user-defined operator or report an error.
156   // The provided message is used if there is no such operator.
157   MaybeExpr TryDefinedOp(const char *, parser::MessageFixedText,
158       const Symbol **definedOpSymbolPtr = nullptr, bool isUserOp = false);
159   template <typename E>
160   MaybeExpr TryDefinedOp(E opr, parser::MessageFixedText msg) {
161     return TryDefinedOp(
162         context_.context().languageFeatures().GetNames(opr), msg);
163   }
164   // Find and return a user-defined assignment
165   std::optional<ProcedureRef> TryDefinedAssignment();
166   std::optional<ProcedureRef> GetDefinedAssignmentProc();
167   std::optional<DynamicType> GetType(std::size_t) const;
168   void Dump(llvm::raw_ostream &);
169 
170 private:
171   MaybeExpr TryDefinedOp(std::vector<const char *>, parser::MessageFixedText);
172   MaybeExpr TryBoundOp(const Symbol &, int passIndex);
173   std::optional<ActualArgument> AnalyzeExpr(const parser::Expr &);
174   MaybeExpr AnalyzeExprOrWholeAssumedSizeArray(const parser::Expr &);
175   bool AreConformable() const;
176   const Symbol *FindBoundOp(
177       parser::CharBlock, int passIndex, const Symbol *&definedOp);
178   void AddAssignmentConversion(
179       const DynamicType &lhsType, const DynamicType &rhsType);
180   bool OkLogicalIntegerAssignment(TypeCategory lhs, TypeCategory rhs);
181   int GetRank(std::size_t) const;
182   bool IsBOZLiteral(std::size_t i) const {
183     return evaluate::IsBOZLiteral(GetExpr(i));
184   }
185   void SayNoMatch(const std::string &, bool isAssignment = false);
186   std::string TypeAsFortran(std::size_t);
187   bool AnyUntypedOrMissingOperand();
188 
189   ExpressionAnalyzer &context_;
190   ActualArguments actuals_;
191   parser::CharBlock source_;
192   bool fatalErrors_{false};
193   const bool isProcedureCall_; // false for user-defined op or assignment
194 };
195 
196 // Wraps a data reference in a typed Designator<>, and a procedure
197 // or procedure pointer reference in a ProcedureDesignator.
198 MaybeExpr ExpressionAnalyzer::Designate(DataRef &&ref) {
199   const Symbol &last{ref.GetLastSymbol()};
200   const Symbol &symbol{BypassGeneric(last).GetUltimate()};
201   if (semantics::IsProcedure(symbol)) {
202     if (auto *component{std::get_if<Component>(&ref.u)}) {
203       return Expr<SomeType>{ProcedureDesignator{std::move(*component)}};
204     } else if (!std::holds_alternative<SymbolRef>(ref.u)) {
205       DIE("unexpected alternative in DataRef");
206     } else if (!symbol.attrs().test(semantics::Attr::INTRINSIC)) {
207       if (symbol.has<semantics::GenericDetails>()) {
208         Say("'%s' is not a specific procedure"_err_en_US, symbol.name());
209       } else {
210         return Expr<SomeType>{ProcedureDesignator{symbol}};
211       }
212     } else if (auto interface{context_.intrinsics().IsSpecificIntrinsicFunction(
213                    symbol.name().ToString())};
214                interface && !interface->isRestrictedSpecific) {
215       SpecificIntrinsic intrinsic{
216           symbol.name().ToString(), std::move(*interface)};
217       intrinsic.isRestrictedSpecific = interface->isRestrictedSpecific;
218       return Expr<SomeType>{ProcedureDesignator{std::move(intrinsic)}};
219     } else {
220       Say("'%s' is not an unrestricted specific intrinsic procedure"_err_en_US,
221           symbol.name());
222     }
223     return std::nullopt;
224   } else if (MaybeExpr result{AsGenericExpr(std::move(ref))}) {
225     return result;
226   } else {
227     if (!context_.HasError(last) && !context_.HasError(symbol)) {
228       AttachDeclaration(
229           Say("'%s' is not an object that can appear in an expression"_err_en_US,
230               last.name()),
231           symbol);
232       context_.SetError(last);
233     }
234     return std::nullopt;
235   }
236 }
237 
238 // Some subscript semantic checks must be deferred until all of the
239 // subscripts are in hand.
240 MaybeExpr ExpressionAnalyzer::CompleteSubscripts(ArrayRef &&ref) {
241   const Symbol &symbol{ref.GetLastSymbol().GetUltimate()};
242   int symbolRank{symbol.Rank()};
243   int subscripts{static_cast<int>(ref.size())};
244   if (subscripts == 0) {
245     return std::nullopt; // error recovery
246   } else if (subscripts != symbolRank) {
247     if (symbolRank != 0) {
248       Say("Reference to rank-%d object '%s' has %d subscripts"_err_en_US,
249           symbolRank, symbol.name(), subscripts);
250     }
251     return std::nullopt;
252   } else if (const auto *object{
253                  symbol.detailsIf<semantics::ObjectEntityDetails>()}) {
254     // C928 & C1002
255     if (Triplet * last{std::get_if<Triplet>(&ref.subscript().back().u)}) {
256       if (!last->upper() && object->IsAssumedSize()) {
257         Say("Assumed-size array '%s' must have explicit final "
258             "subscript upper bound value"_err_en_US,
259             symbol.name());
260         return std::nullopt;
261       }
262     }
263   } else {
264     // Shouldn't get here from Analyze(ArrayElement) without a valid base,
265     // which, if not an object, must be a construct entity from
266     // SELECT TYPE/RANK or ASSOCIATE.
267     CHECK(symbol.has<semantics::AssocEntityDetails>());
268   }
269   return Designate(DataRef{std::move(ref)});
270 }
271 
272 // Applies subscripts to a data reference.
273 MaybeExpr ExpressionAnalyzer::ApplySubscripts(
274     DataRef &&dataRef, std::vector<Subscript> &&subscripts) {
275   if (subscripts.empty()) {
276     return std::nullopt; // error recovery
277   }
278   return common::visit(
279       common::visitors{
280           [&](SymbolRef &&symbol) {
281             return CompleteSubscripts(ArrayRef{symbol, std::move(subscripts)});
282           },
283           [&](Component &&c) {
284             return CompleteSubscripts(
285                 ArrayRef{std::move(c), std::move(subscripts)});
286           },
287           [&](auto &&) -> MaybeExpr {
288             DIE("bad base for ArrayRef");
289             return std::nullopt;
290           },
291       },
292       std::move(dataRef.u));
293 }
294 
295 // C919a - only one part-ref of a data-ref may have rank > 0
296 bool ExpressionAnalyzer::CheckRanks(const DataRef &dataRef) {
297   return common::visit(
298       common::visitors{
299           [this](const Component &component) {
300             const Symbol &symbol{component.GetLastSymbol()};
301             if (int componentRank{symbol.Rank()}; componentRank > 0) {
302               if (int baseRank{component.base().Rank()}; baseRank > 0) {
303                 Say("Reference to whole rank-%d component '%s' of rank-%d array of derived type is not allowed"_err_en_US,
304                     componentRank, symbol.name(), baseRank);
305                 return false;
306               }
307             } else {
308               return CheckRanks(component.base());
309             }
310             return true;
311           },
312           [this](const ArrayRef &arrayRef) {
313             if (const auto *component{arrayRef.base().UnwrapComponent()}) {
314               int subscriptRank{0};
315               for (const Subscript &subscript : arrayRef.subscript()) {
316                 subscriptRank += subscript.Rank();
317               }
318               if (subscriptRank > 0) {
319                 if (int componentBaseRank{component->base().Rank()};
320                     componentBaseRank > 0) {
321                   Say("Subscripts of component '%s' of rank-%d derived type array have rank %d but must all be scalar"_err_en_US,
322                       component->GetLastSymbol().name(), componentBaseRank,
323                       subscriptRank);
324                   return false;
325                 }
326               } else {
327                 return CheckRanks(component->base());
328               }
329             }
330             return true;
331           },
332           [](const SymbolRef &) { return true; },
333           [](const CoarrayRef &) { return true; },
334       },
335       dataRef.u);
336 }
337 
338 // Parse tree correction after a substring S(j:k) was misparsed as an
339 // array section.  N.B. Fortran substrings have to have a range, not a
340 // single index.
341 static void FixMisparsedSubstring(const parser::Designator &d) {
342   auto &mutate{const_cast<parser::Designator &>(d)};
343   if (auto *dataRef{std::get_if<parser::DataRef>(&mutate.u)}) {
344     if (auto *ae{std::get_if<common::Indirection<parser::ArrayElement>>(
345             &dataRef->u)}) {
346       parser::ArrayElement &arrElement{ae->value()};
347       if (!arrElement.subscripts.empty()) {
348         auto iter{arrElement.subscripts.begin()};
349         if (auto *triplet{std::get_if<parser::SubscriptTriplet>(&iter->u)}) {
350           if (!std::get<2>(triplet->t) /* no stride */ &&
351               ++iter == arrElement.subscripts.end() /* one subscript */) {
352             if (Symbol *
353                 symbol{common::visit(
354                     common::visitors{
355                         [](parser::Name &n) { return n.symbol; },
356                         [](common::Indirection<parser::StructureComponent>
357                                 &sc) { return sc.value().component.symbol; },
358                         [](auto &) -> Symbol * { return nullptr; },
359                     },
360                     arrElement.base.u)}) {
361               const Symbol &ultimate{symbol->GetUltimate()};
362               if (const semantics::DeclTypeSpec * type{ultimate.GetType()}) {
363                 if (!ultimate.IsObjectArray() &&
364                     type->category() == semantics::DeclTypeSpec::Character) {
365                   // The ambiguous S(j:k) was parsed as an array section
366                   // reference, but it's now clear that it's a substring.
367                   // Fix the parse tree in situ.
368                   mutate.u = arrElement.ConvertToSubstring();
369                 }
370               }
371             }
372           }
373         }
374       }
375     }
376   }
377 }
378 
379 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Designator &d) {
380   auto restorer{GetContextualMessages().SetLocation(d.source)};
381   FixMisparsedSubstring(d);
382   // These checks have to be deferred to these "top level" data-refs where
383   // we can be sure that there are no following subscripts (yet).
384   if (MaybeExpr result{Analyze(d.u)}) {
385     if (std::optional<DataRef> dataRef{ExtractDataRef(std::move(result))}) {
386       if (!CheckRanks(std::move(*dataRef))) {
387         return std::nullopt;
388       }
389       return Designate(std::move(*dataRef));
390     } else if (std::optional<DataRef> dataRef{
391                    ExtractDataRef(std::move(result), /*intoSubstring=*/true)}) {
392       if (!CheckRanks(std::move(*dataRef))) {
393         return std::nullopt;
394       }
395     } else if (std::optional<DataRef> dataRef{ExtractDataRef(std::move(result),
396                    /*intoSubstring=*/false, /*intoComplexPart=*/true)}) {
397       if (!CheckRanks(std::move(*dataRef))) {
398         return std::nullopt;
399       }
400     }
401     return result;
402   }
403   return std::nullopt;
404 }
405 
406 // A utility subroutine to repackage optional expressions of various levels
407 // of type specificity as fully general MaybeExpr values.
408 template <typename A> common::IfNoLvalue<MaybeExpr, A> AsMaybeExpr(A &&x) {
409   return AsGenericExpr(std::move(x));
410 }
411 template <typename A> MaybeExpr AsMaybeExpr(std::optional<A> &&x) {
412   if (x) {
413     return AsMaybeExpr(std::move(*x));
414   }
415   return std::nullopt;
416 }
417 
418 // Type kind parameter values for literal constants.
419 int ExpressionAnalyzer::AnalyzeKindParam(
420     const std::optional<parser::KindParam> &kindParam, int defaultKind) {
421   if (!kindParam) {
422     return defaultKind;
423   }
424   return common::visit(
425       common::visitors{
426           [](std::uint64_t k) { return static_cast<int>(k); },
427           [&](const parser::Scalar<
428               parser::Integer<parser::Constant<parser::Name>>> &n) {
429             if (MaybeExpr ie{Analyze(n)}) {
430               if (std::optional<std::int64_t> i64{ToInt64(*ie)}) {
431                 int iv = *i64;
432                 if (iv == *i64) {
433                   return iv;
434                 }
435               }
436             }
437             return defaultKind;
438           },
439       },
440       kindParam->u);
441 }
442 
443 // Common handling of parser::IntLiteralConstant and SignedIntLiteralConstant
444 struct IntTypeVisitor {
445   using Result = MaybeExpr;
446   using Types = IntegerTypes;
447   template <typename T> Result Test() {
448     if (T::kind >= kind) {
449       const char *p{digits.begin()};
450       using Int = typename T::Scalar;
451       typename Int::ValueWithOverflow num{0, false};
452       if (isNegated) {
453         auto unsignedNum{Int::Read(p, 10, false /*unsigned*/)};
454         num.value = unsignedNum.value.Negate().value;
455         num.overflow = unsignedNum.overflow || num.value > Int{0};
456         if (!num.overflow && num.value.Negate().overflow &&
457             !analyzer.context().IsInModuleFile(digits)) {
458           analyzer.Say(digits,
459               "negated maximum INTEGER(KIND=%d) literal"_port_en_US, T::kind);
460         }
461       } else {
462         num = Int::Read(p, 10, true /*signed*/);
463       }
464       if (!num.overflow) {
465         if (T::kind > kind) {
466           if (!isDefaultKind ||
467               !analyzer.context().IsEnabled(LanguageFeature::BigIntLiterals)) {
468             return std::nullopt;
469           } else if (analyzer.context().ShouldWarn(
470                          LanguageFeature::BigIntLiterals)) {
471             analyzer.Say(digits,
472                 "Integer literal is too large for default INTEGER(KIND=%d); "
473                 "assuming INTEGER(KIND=%d)"_port_en_US,
474                 kind, T::kind);
475           }
476         }
477         return Expr<SomeType>{
478             Expr<SomeInteger>{Expr<T>{Constant<T>{std::move(num.value)}}}};
479       }
480     }
481     return std::nullopt;
482   }
483   ExpressionAnalyzer &analyzer;
484   parser::CharBlock digits;
485   int kind;
486   bool isDefaultKind;
487   bool isNegated;
488 };
489 
490 template <typename PARSED>
491 MaybeExpr ExpressionAnalyzer::IntLiteralConstant(
492     const PARSED &x, bool isNegated) {
493   const auto &kindParam{std::get<std::optional<parser::KindParam>>(x.t)};
494   bool isDefaultKind{!kindParam};
495   int kind{AnalyzeKindParam(kindParam, GetDefaultKind(TypeCategory::Integer))};
496   if (CheckIntrinsicKind(TypeCategory::Integer, kind)) {
497     auto digits{std::get<parser::CharBlock>(x.t)};
498     if (MaybeExpr result{common::SearchTypes(
499             IntTypeVisitor{*this, digits, kind, isDefaultKind, isNegated})}) {
500       return result;
501     } else if (isDefaultKind) {
502       Say(digits,
503           "Integer literal is too large for any allowable "
504           "kind of INTEGER"_err_en_US);
505     } else {
506       Say(digits, "Integer literal is too large for INTEGER(KIND=%d)"_err_en_US,
507           kind);
508     }
509   }
510   return std::nullopt;
511 }
512 
513 MaybeExpr ExpressionAnalyzer::Analyze(
514     const parser::IntLiteralConstant &x, bool isNegated) {
515   auto restorer{
516       GetContextualMessages().SetLocation(std::get<parser::CharBlock>(x.t))};
517   return IntLiteralConstant(x, isNegated);
518 }
519 
520 MaybeExpr ExpressionAnalyzer::Analyze(
521     const parser::SignedIntLiteralConstant &x) {
522   auto restorer{GetContextualMessages().SetLocation(x.source)};
523   return IntLiteralConstant(x);
524 }
525 
526 template <typename TYPE>
527 Constant<TYPE> ReadRealLiteral(
528     parser::CharBlock source, FoldingContext &context) {
529   const char *p{source.begin()};
530   auto valWithFlags{
531       Scalar<TYPE>::Read(p, context.targetCharacteristics().roundingMode())};
532   CHECK(p == source.end());
533   RealFlagWarnings(context, valWithFlags.flags, "conversion of REAL literal");
534   auto value{valWithFlags.value};
535   if (context.targetCharacteristics().areSubnormalsFlushedToZero()) {
536     value = value.FlushSubnormalToZero();
537   }
538   return {value};
539 }
540 
541 struct RealTypeVisitor {
542   using Result = std::optional<Expr<SomeReal>>;
543   using Types = RealTypes;
544 
545   RealTypeVisitor(int k, parser::CharBlock lit, FoldingContext &ctx)
546       : kind{k}, literal{lit}, context{ctx} {}
547 
548   template <typename T> Result Test() {
549     if (kind == T::kind) {
550       return {AsCategoryExpr(ReadRealLiteral<T>(literal, context))};
551     }
552     return std::nullopt;
553   }
554 
555   int kind;
556   parser::CharBlock literal;
557   FoldingContext &context;
558 };
559 
560 // Reads a real literal constant and encodes it with the right kind.
561 MaybeExpr ExpressionAnalyzer::Analyze(const parser::RealLiteralConstant &x) {
562   // Use a local message context around the real literal for better
563   // provenance on any messages.
564   auto restorer{GetContextualMessages().SetLocation(x.real.source)};
565   // If a kind parameter appears, it defines the kind of the literal and the
566   // letter used in an exponent part must be 'E' (e.g., the 'E' in
567   // "6.02214E+23").  In the absence of an explicit kind parameter, any
568   // exponent letter determines the kind.  Otherwise, defaults apply.
569   auto &defaults{context_.defaultKinds()};
570   int defaultKind{defaults.GetDefaultKind(TypeCategory::Real)};
571   const char *end{x.real.source.end()};
572   char expoLetter{' '};
573   std::optional<int> letterKind;
574   for (const char *p{x.real.source.begin()}; p < end; ++p) {
575     if (parser::IsLetter(*p)) {
576       expoLetter = *p;
577       switch (expoLetter) {
578       case 'e':
579         letterKind = defaults.GetDefaultKind(TypeCategory::Real);
580         break;
581       case 'd':
582         letterKind = defaults.doublePrecisionKind();
583         break;
584       case 'q':
585         letterKind = defaults.quadPrecisionKind();
586         break;
587       default:
588         Say("Unknown exponent letter '%c'"_err_en_US, expoLetter);
589       }
590       break;
591     }
592   }
593   if (letterKind) {
594     defaultKind = *letterKind;
595   }
596   // C716 requires 'E' as an exponent.
597   // Extension: allow exponent-letter matching the kind-param.
598   auto kind{AnalyzeKindParam(x.kind, defaultKind)};
599   if (letterKind && expoLetter != 'e') {
600     if (kind != *letterKind) {
601       Say("Explicit kind parameter on real constant disagrees with "
602           "exponent letter '%c'"_warn_en_US,
603           expoLetter);
604     } else if (x.kind &&
605         context_.ShouldWarn(
606             common::LanguageFeature::ExponentMatchingKindParam)) {
607       Say("Explicit kind parameter together with non-'E' exponent letter "
608           "is not standard"_port_en_US);
609     }
610   }
611   auto result{common::SearchTypes(
612       RealTypeVisitor{kind, x.real.source, GetFoldingContext()})};
613   if (!result) { // C717
614     Say("Unsupported REAL(KIND=%d)"_err_en_US, kind);
615   }
616   return AsMaybeExpr(std::move(result));
617 }
618 
619 MaybeExpr ExpressionAnalyzer::Analyze(
620     const parser::SignedRealLiteralConstant &x) {
621   if (auto result{Analyze(std::get<parser::RealLiteralConstant>(x.t))}) {
622     auto &realExpr{std::get<Expr<SomeReal>>(result->u)};
623     if (auto sign{std::get<std::optional<parser::Sign>>(x.t)}) {
624       if (sign == parser::Sign::Negative) {
625         return AsGenericExpr(-std::move(realExpr));
626       }
627     }
628     return result;
629   }
630   return std::nullopt;
631 }
632 
633 MaybeExpr ExpressionAnalyzer::Analyze(
634     const parser::SignedComplexLiteralConstant &x) {
635   auto result{Analyze(std::get<parser::ComplexLiteralConstant>(x.t))};
636   if (!result) {
637     return std::nullopt;
638   } else if (std::get<parser::Sign>(x.t) == parser::Sign::Negative) {
639     return AsGenericExpr(-std::move(std::get<Expr<SomeComplex>>(result->u)));
640   } else {
641     return result;
642   }
643 }
644 
645 MaybeExpr ExpressionAnalyzer::Analyze(const parser::ComplexPart &x) {
646   return Analyze(x.u);
647 }
648 
649 MaybeExpr ExpressionAnalyzer::Analyze(const parser::ComplexLiteralConstant &z) {
650   return AsMaybeExpr(
651       ConstructComplex(GetContextualMessages(), Analyze(std::get<0>(z.t)),
652           Analyze(std::get<1>(z.t)), GetDefaultKind(TypeCategory::Real)));
653 }
654 
655 // CHARACTER literal processing.
656 MaybeExpr ExpressionAnalyzer::AnalyzeString(std::string &&string, int kind) {
657   if (!CheckIntrinsicKind(TypeCategory::Character, kind)) {
658     return std::nullopt;
659   }
660   switch (kind) {
661   case 1:
662     return AsGenericExpr(Constant<Type<TypeCategory::Character, 1>>{
663         parser::DecodeString<std::string, parser::Encoding::LATIN_1>(
664             string, true)});
665   case 2:
666     return AsGenericExpr(Constant<Type<TypeCategory::Character, 2>>{
667         parser::DecodeString<std::u16string, parser::Encoding::UTF_8>(
668             string, true)});
669   case 4:
670     return AsGenericExpr(Constant<Type<TypeCategory::Character, 4>>{
671         parser::DecodeString<std::u32string, parser::Encoding::UTF_8>(
672             string, true)});
673   default:
674     CRASH_NO_CASE;
675   }
676 }
677 
678 MaybeExpr ExpressionAnalyzer::Analyze(const parser::CharLiteralConstant &x) {
679   int kind{
680       AnalyzeKindParam(std::get<std::optional<parser::KindParam>>(x.t), 1)};
681   auto value{std::get<std::string>(x.t)};
682   return AnalyzeString(std::move(value), kind);
683 }
684 
685 MaybeExpr ExpressionAnalyzer::Analyze(
686     const parser::HollerithLiteralConstant &x) {
687   int kind{GetDefaultKind(TypeCategory::Character)};
688   auto value{x.v};
689   return AnalyzeString(std::move(value), kind);
690 }
691 
692 // .TRUE. and .FALSE. of various kinds
693 MaybeExpr ExpressionAnalyzer::Analyze(const parser::LogicalLiteralConstant &x) {
694   auto kind{AnalyzeKindParam(std::get<std::optional<parser::KindParam>>(x.t),
695       GetDefaultKind(TypeCategory::Logical))};
696   bool value{std::get<bool>(x.t)};
697   auto result{common::SearchTypes(
698       TypeKindVisitor<TypeCategory::Logical, Constant, bool>{
699           kind, std::move(value)})};
700   if (!result) {
701     Say("unsupported LOGICAL(KIND=%d)"_err_en_US, kind); // C728
702   }
703   return result;
704 }
705 
706 // BOZ typeless literals
707 MaybeExpr ExpressionAnalyzer::Analyze(const parser::BOZLiteralConstant &x) {
708   const char *p{x.v.c_str()};
709   std::uint64_t base{16};
710   switch (*p++) {
711   case 'b':
712     base = 2;
713     break;
714   case 'o':
715     base = 8;
716     break;
717   case 'z':
718     break;
719   case 'x':
720     break;
721   default:
722     CRASH_NO_CASE;
723   }
724   CHECK(*p == '"');
725   ++p;
726   auto value{BOZLiteralConstant::Read(p, base, false /*unsigned*/)};
727   if (*p != '"') {
728     Say("Invalid digit ('%c') in BOZ literal '%s'"_err_en_US, *p,
729         x.v); // C7107, C7108
730     return std::nullopt;
731   }
732   if (value.overflow) {
733     Say("BOZ literal '%s' too large"_err_en_US, x.v);
734     return std::nullopt;
735   }
736   return AsGenericExpr(std::move(value.value));
737 }
738 
739 // Names and named constants
740 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Name &n) {
741   auto restorer{GetContextualMessages().SetLocation(n.source)};
742   if (std::optional<int> kind{IsImpliedDo(n.source)}) {
743     return AsMaybeExpr(ConvertToKind<TypeCategory::Integer>(
744         *kind, AsExpr(ImpliedDoIndex{n.source})));
745   }
746   if (context_.HasError(n.symbol)) { // includes case of no symbol
747     return std::nullopt;
748   } else {
749     const Symbol &ultimate{n.symbol->GetUltimate()};
750     if (ultimate.has<semantics::TypeParamDetails>()) {
751       // A bare reference to a derived type parameter (within a parameterized
752       // derived type definition)
753       return Fold(ConvertToType(
754           ultimate, AsGenericExpr(TypeParamInquiry{std::nullopt, ultimate})));
755     } else {
756       if (n.symbol->attrs().test(semantics::Attr::VOLATILE)) {
757         if (const semantics::Scope *
758             pure{semantics::FindPureProcedureContaining(
759                 context_.FindScope(n.source))}) {
760           SayAt(n,
761               "VOLATILE variable '%s' may not be referenced in pure subprogram '%s'"_err_en_US,
762               n.source, DEREF(pure->symbol()).name());
763           n.symbol->attrs().reset(semantics::Attr::VOLATILE);
764         }
765       }
766       if (!isWholeAssumedSizeArrayOk_ &&
767           semantics::IsAssumedSizeArray(*n.symbol)) { // C1002, C1014, C1231
768         AttachDeclaration(
769             SayAt(n,
770                 "Whole assumed-size array '%s' may not appear here without subscripts"_err_en_US,
771                 n.source),
772             *n.symbol);
773       }
774       return Designate(DataRef{*n.symbol});
775     }
776   }
777 }
778 
779 MaybeExpr ExpressionAnalyzer::Analyze(const parser::NamedConstant &n) {
780   auto restorer{GetContextualMessages().SetLocation(n.v.source)};
781   if (MaybeExpr value{Analyze(n.v)}) {
782     Expr<SomeType> folded{Fold(std::move(*value))};
783     if (IsConstantExpr(folded)) {
784       return folded;
785     }
786     Say(n.v.source, "must be a constant"_err_en_US); // C718
787   }
788   return std::nullopt;
789 }
790 
791 MaybeExpr ExpressionAnalyzer::Analyze(const parser::NullInit &n) {
792   if (MaybeExpr value{Analyze(n.v)}) {
793     // Subtle: when the NullInit is a DataStmtConstant, it might
794     // be a misparse of a structure constructor without parameters
795     // or components (e.g., T()).  Checking the result to ensure
796     // that a "=>" data entity initializer actually resolved to
797     // a null pointer has to be done by the caller.
798     return Fold(std::move(*value));
799   }
800   return std::nullopt;
801 }
802 
803 MaybeExpr ExpressionAnalyzer::Analyze(const parser::InitialDataTarget &x) {
804   return Analyze(x.value());
805 }
806 
807 MaybeExpr ExpressionAnalyzer::Analyze(const parser::DataStmtValue &x) {
808   if (const auto &repeat{
809           std::get<std::optional<parser::DataStmtRepeat>>(x.t)}) {
810     x.repetitions = -1;
811     if (MaybeExpr expr{Analyze(repeat->u)}) {
812       Expr<SomeType> folded{Fold(std::move(*expr))};
813       if (auto value{ToInt64(folded)}) {
814         if (*value >= 0) { // C882
815           x.repetitions = *value;
816         } else {
817           Say(FindSourceLocation(repeat),
818               "Repeat count (%jd) for data value must not be negative"_err_en_US,
819               *value);
820         }
821       }
822     }
823   }
824   return Analyze(std::get<parser::DataStmtConstant>(x.t));
825 }
826 
827 // Substring references
828 std::optional<Expr<SubscriptInteger>> ExpressionAnalyzer::GetSubstringBound(
829     const std::optional<parser::ScalarIntExpr> &bound) {
830   if (bound) {
831     if (MaybeExpr expr{Analyze(*bound)}) {
832       if (expr->Rank() > 1) {
833         Say("substring bound expression has rank %d"_err_en_US, expr->Rank());
834       }
835       if (auto *intExpr{std::get_if<Expr<SomeInteger>>(&expr->u)}) {
836         if (auto *ssIntExpr{std::get_if<Expr<SubscriptInteger>>(&intExpr->u)}) {
837           return {std::move(*ssIntExpr)};
838         }
839         return {Expr<SubscriptInteger>{
840             Convert<SubscriptInteger, TypeCategory::Integer>{
841                 std::move(*intExpr)}}};
842       } else {
843         Say("substring bound expression is not INTEGER"_err_en_US);
844       }
845     }
846   }
847   return std::nullopt;
848 }
849 
850 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Substring &ss) {
851   if (MaybeExpr baseExpr{Analyze(std::get<parser::DataRef>(ss.t))}) {
852     if (std::optional<DataRef> dataRef{ExtractDataRef(std::move(*baseExpr))}) {
853       if (MaybeExpr newBaseExpr{Designate(std::move(*dataRef))}) {
854         if (std::optional<DataRef> checked{
855                 ExtractDataRef(std::move(*newBaseExpr))}) {
856           const parser::SubstringRange &range{
857               std::get<parser::SubstringRange>(ss.t)};
858           std::optional<Expr<SubscriptInteger>> first{
859               GetSubstringBound(std::get<0>(range.t))};
860           std::optional<Expr<SubscriptInteger>> last{
861               GetSubstringBound(std::get<1>(range.t))};
862           const Symbol &symbol{checked->GetLastSymbol()};
863           if (std::optional<DynamicType> dynamicType{
864                   DynamicType::From(symbol)}) {
865             if (dynamicType->category() == TypeCategory::Character) {
866               return WrapperHelper<TypeCategory::Character, Designator,
867                   Substring>(dynamicType->kind(),
868                   Substring{std::move(checked.value()), std::move(first),
869                       std::move(last)});
870             }
871           }
872           Say("substring may apply only to CHARACTER"_err_en_US);
873         }
874       }
875     }
876   }
877   return std::nullopt;
878 }
879 
880 // CHARACTER literal substrings
881 MaybeExpr ExpressionAnalyzer::Analyze(
882     const parser::CharLiteralConstantSubstring &x) {
883   const parser::SubstringRange &range{std::get<parser::SubstringRange>(x.t)};
884   std::optional<Expr<SubscriptInteger>> lower{
885       GetSubstringBound(std::get<0>(range.t))};
886   std::optional<Expr<SubscriptInteger>> upper{
887       GetSubstringBound(std::get<1>(range.t))};
888   if (MaybeExpr string{Analyze(std::get<parser::CharLiteralConstant>(x.t))}) {
889     if (auto *charExpr{std::get_if<Expr<SomeCharacter>>(&string->u)}) {
890       Expr<SubscriptInteger> length{
891           common::visit([](const auto &ckExpr) { return ckExpr.LEN().value(); },
892               charExpr->u)};
893       if (!lower) {
894         lower = Expr<SubscriptInteger>{1};
895       }
896       if (!upper) {
897         upper = Expr<SubscriptInteger>{
898             static_cast<std::int64_t>(ToInt64(length).value())};
899       }
900       return common::visit(
901           [&](auto &&ckExpr) -> MaybeExpr {
902             using Result = ResultType<decltype(ckExpr)>;
903             auto *cp{std::get_if<Constant<Result>>(&ckExpr.u)};
904             CHECK(DEREF(cp).size() == 1);
905             StaticDataObject::Pointer staticData{StaticDataObject::Create()};
906             staticData->set_alignment(Result::kind)
907                 .set_itemBytes(Result::kind)
908                 .Push(cp->GetScalarValue().value(),
909                     foldingContext_.targetCharacteristics().isBigEndian());
910             Substring substring{std::move(staticData), std::move(lower.value()),
911                 std::move(upper.value())};
912             return AsGenericExpr(
913                 Expr<Result>{Designator<Result>{std::move(substring)}});
914           },
915           std::move(charExpr->u));
916     }
917   }
918   return std::nullopt;
919 }
920 
921 // Subscripted array references
922 std::optional<Expr<SubscriptInteger>> ExpressionAnalyzer::AsSubscript(
923     MaybeExpr &&expr) {
924   if (expr) {
925     if (expr->Rank() > 1) {
926       Say("Subscript expression has rank %d greater than 1"_err_en_US,
927           expr->Rank());
928     }
929     if (auto *intExpr{std::get_if<Expr<SomeInteger>>(&expr->u)}) {
930       if (auto *ssIntExpr{std::get_if<Expr<SubscriptInteger>>(&intExpr->u)}) {
931         return std::move(*ssIntExpr);
932       } else {
933         return Expr<SubscriptInteger>{
934             Convert<SubscriptInteger, TypeCategory::Integer>{
935                 std::move(*intExpr)}};
936       }
937     } else {
938       Say("Subscript expression is not INTEGER"_err_en_US);
939     }
940   }
941   return std::nullopt;
942 }
943 
944 std::optional<Expr<SubscriptInteger>> ExpressionAnalyzer::TripletPart(
945     const std::optional<parser::Subscript> &s) {
946   if (s) {
947     return AsSubscript(Analyze(*s));
948   } else {
949     return std::nullopt;
950   }
951 }
952 
953 std::optional<Subscript> ExpressionAnalyzer::AnalyzeSectionSubscript(
954     const parser::SectionSubscript &ss) {
955   return common::visit(
956       common::visitors{
957           [&](const parser::SubscriptTriplet &t) -> std::optional<Subscript> {
958             const auto &lower{std::get<0>(t.t)};
959             const auto &upper{std::get<1>(t.t)};
960             const auto &stride{std::get<2>(t.t)};
961             auto result{Triplet{
962                 TripletPart(lower), TripletPart(upper), TripletPart(stride)}};
963             if ((lower && !result.lower()) || (upper && !result.upper())) {
964               return std::nullopt;
965             } else {
966               return std::make_optional<Subscript>(result);
967             }
968           },
969           [&](const auto &s) -> std::optional<Subscript> {
970             if (auto subscriptExpr{AsSubscript(Analyze(s))}) {
971               return Subscript{std::move(*subscriptExpr)};
972             } else {
973               return std::nullopt;
974             }
975           },
976       },
977       ss.u);
978 }
979 
980 // Empty result means an error occurred
981 std::vector<Subscript> ExpressionAnalyzer::AnalyzeSectionSubscripts(
982     const std::list<parser::SectionSubscript> &sss) {
983   bool error{false};
984   std::vector<Subscript> subscripts;
985   for (const auto &s : sss) {
986     if (auto subscript{AnalyzeSectionSubscript(s)}) {
987       subscripts.emplace_back(std::move(*subscript));
988     } else {
989       error = true;
990     }
991   }
992   return !error ? subscripts : std::vector<Subscript>{};
993 }
994 
995 MaybeExpr ExpressionAnalyzer::Analyze(const parser::ArrayElement &ae) {
996   MaybeExpr baseExpr;
997   {
998     auto restorer{AllowWholeAssumedSizeArray()};
999     baseExpr = Analyze(ae.base);
1000   }
1001   if (baseExpr) {
1002     if (ae.subscripts.empty()) {
1003       // will be converted to function call later or error reported
1004     } else if (baseExpr->Rank() == 0) {
1005       if (const Symbol * symbol{GetLastSymbol(*baseExpr)}) {
1006         if (!context_.HasError(symbol)) {
1007           if (inDataStmtConstant_) {
1008             // Better error for NULL(X) with a MOLD= argument
1009             Say("'%s' must be an array or structure constructor if used with non-empty parentheses as a DATA statement constant"_err_en_US,
1010                 symbol->name());
1011           } else {
1012             Say("'%s' is not an array"_err_en_US, symbol->name());
1013           }
1014           context_.SetError(*symbol);
1015         }
1016       }
1017     } else if (std::optional<DataRef> dataRef{
1018                    ExtractDataRef(std::move(*baseExpr))}) {
1019       return ApplySubscripts(
1020           std::move(*dataRef), AnalyzeSectionSubscripts(ae.subscripts));
1021     } else {
1022       Say("Subscripts may be applied only to an object, component, or array constant"_err_en_US);
1023     }
1024   }
1025   // error was reported: analyze subscripts without reporting more errors
1026   auto restorer{GetContextualMessages().DiscardMessages()};
1027   AnalyzeSectionSubscripts(ae.subscripts);
1028   return std::nullopt;
1029 }
1030 
1031 // Type parameter inquiries apply to data references, but don't depend
1032 // on any trailing (co)subscripts.
1033 static NamedEntity IgnoreAnySubscripts(Designator<SomeDerived> &&designator) {
1034   return common::visit(
1035       common::visitors{
1036           [](SymbolRef &&symbol) { return NamedEntity{symbol}; },
1037           [](Component &&component) {
1038             return NamedEntity{std::move(component)};
1039           },
1040           [](ArrayRef &&arrayRef) { return std::move(arrayRef.base()); },
1041           [](CoarrayRef &&coarrayRef) {
1042             return NamedEntity{coarrayRef.GetLastSymbol()};
1043           },
1044       },
1045       std::move(designator.u));
1046 }
1047 
1048 // Components of parent derived types are explicitly represented as such.
1049 std::optional<Component> ExpressionAnalyzer::CreateComponent(
1050     DataRef &&base, const Symbol &component, const semantics::Scope &scope) {
1051   if (IsAllocatableOrPointer(component) && base.Rank() > 0) { // C919b
1052     Say("An allocatable or pointer component reference must be applied to a scalar base"_err_en_US);
1053   }
1054   if (&component.owner() == &scope) {
1055     return Component{std::move(base), component};
1056   }
1057   if (const Symbol * typeSymbol{scope.GetSymbol()}) {
1058     if (const Symbol *
1059         parentComponent{typeSymbol->GetParentComponent(&scope)}) {
1060       if (const auto *object{
1061               parentComponent->detailsIf<semantics::ObjectEntityDetails>()}) {
1062         if (const auto *parentType{object->type()}) {
1063           if (const semantics::Scope *
1064               parentScope{parentType->derivedTypeSpec().scope()}) {
1065             return CreateComponent(
1066                 DataRef{Component{std::move(base), *parentComponent}},
1067                 component, *parentScope);
1068           }
1069         }
1070       }
1071     }
1072   }
1073   return std::nullopt;
1074 }
1075 
1076 // Derived type component references and type parameter inquiries
1077 MaybeExpr ExpressionAnalyzer::Analyze(const parser::StructureComponent &sc) {
1078   MaybeExpr base{Analyze(sc.base)};
1079   Symbol *sym{sc.component.symbol};
1080   if (!base || !sym || context_.HasError(sym)) {
1081     return std::nullopt;
1082   }
1083   const auto &name{sc.component.source};
1084   if (auto *dtExpr{UnwrapExpr<Expr<SomeDerived>>(*base)}) {
1085     const auto *dtSpec{GetDerivedTypeSpec(dtExpr->GetType())};
1086     if (sym->detailsIf<semantics::TypeParamDetails>()) {
1087       if (auto *designator{UnwrapExpr<Designator<SomeDerived>>(*dtExpr)}) {
1088         if (std::optional<DynamicType> dyType{DynamicType::From(*sym)}) {
1089           if (dyType->category() == TypeCategory::Integer) {
1090             auto restorer{GetContextualMessages().SetLocation(name)};
1091             return Fold(ConvertToType(*dyType,
1092                 AsGenericExpr(TypeParamInquiry{
1093                     IgnoreAnySubscripts(std::move(*designator)), *sym})));
1094           }
1095         }
1096         Say(name, "Type parameter is not INTEGER"_err_en_US);
1097       } else {
1098         Say(name,
1099             "A type parameter inquiry must be applied to "
1100             "a designator"_err_en_US);
1101       }
1102     } else if (!dtSpec || !dtSpec->scope()) {
1103       CHECK(context_.AnyFatalError() || !foldingContext_.messages().empty());
1104       return std::nullopt;
1105     } else if (std::optional<DataRef> dataRef{
1106                    ExtractDataRef(std::move(*dtExpr))}) {
1107       if (auto component{
1108               CreateComponent(std::move(*dataRef), *sym, *dtSpec->scope())}) {
1109         return Designate(DataRef{std::move(*component)});
1110       } else {
1111         Say(name, "Component is not in scope of derived TYPE(%s)"_err_en_US,
1112             dtSpec->typeSymbol().name());
1113       }
1114     } else {
1115       Say(name,
1116           "Base of component reference must be a data reference"_err_en_US);
1117     }
1118   } else if (auto *details{sym->detailsIf<semantics::MiscDetails>()}) {
1119     // special part-ref: %re, %im, %kind, %len
1120     // Type errors on the base of %re/%im/%len are detected and
1121     // reported in name resolution.
1122     using MiscKind = semantics::MiscDetails::Kind;
1123     MiscKind kind{details->kind()};
1124     if (kind == MiscKind::ComplexPartRe || kind == MiscKind::ComplexPartIm) {
1125       if (auto *zExpr{std::get_if<Expr<SomeComplex>>(&base->u)}) {
1126         if (std::optional<DataRef> dataRef{ExtractDataRef(*zExpr)}) {
1127           // Represent %RE/%IM as a designator
1128           Expr<SomeReal> realExpr{common::visit(
1129               [&](const auto &z) {
1130                 using PartType = typename ResultType<decltype(z)>::Part;
1131                 auto part{kind == MiscKind::ComplexPartRe
1132                         ? ComplexPart::Part::RE
1133                         : ComplexPart::Part::IM};
1134                 return AsCategoryExpr(Designator<PartType>{
1135                     ComplexPart{std::move(*dataRef), part}});
1136               },
1137               zExpr->u)};
1138           return AsGenericExpr(std::move(realExpr));
1139         }
1140       }
1141     } else if (kind == MiscKind::KindParamInquiry ||
1142         kind == MiscKind::LenParamInquiry) {
1143       ActualArgument arg{std::move(*base)};
1144       SetArgSourceLocation(arg, name);
1145       return MakeFunctionRef(name, ActualArguments{std::move(arg)});
1146     } else {
1147       DIE("unexpected MiscDetails::Kind");
1148     }
1149   } else {
1150     Say(name, "derived type required before component reference"_err_en_US);
1151   }
1152   return std::nullopt;
1153 }
1154 
1155 MaybeExpr ExpressionAnalyzer::Analyze(const parser::CoindexedNamedObject &x) {
1156   if (auto maybeDataRef{ExtractDataRef(Analyze(x.base))}) {
1157     DataRef *dataRef{&*maybeDataRef};
1158     std::vector<Subscript> subscripts;
1159     SymbolVector reversed;
1160     if (auto *aRef{std::get_if<ArrayRef>(&dataRef->u)}) {
1161       subscripts = std::move(aRef->subscript());
1162       reversed.push_back(aRef->GetLastSymbol());
1163       if (Component * component{aRef->base().UnwrapComponent()}) {
1164         dataRef = &component->base();
1165       } else {
1166         dataRef = nullptr;
1167       }
1168     }
1169     if (dataRef) {
1170       while (auto *component{std::get_if<Component>(&dataRef->u)}) {
1171         reversed.push_back(component->GetLastSymbol());
1172         dataRef = &component->base();
1173       }
1174       if (auto *baseSym{std::get_if<SymbolRef>(&dataRef->u)}) {
1175         reversed.push_back(*baseSym);
1176       } else {
1177         Say("Base of coindexed named object has subscripts or cosubscripts"_err_en_US);
1178       }
1179     }
1180     std::vector<Expr<SubscriptInteger>> cosubscripts;
1181     bool cosubsOk{true};
1182     for (const auto &cosub :
1183         std::get<std::list<parser::Cosubscript>>(x.imageSelector.t)) {
1184       MaybeExpr coex{Analyze(cosub)};
1185       if (auto *intExpr{UnwrapExpr<Expr<SomeInteger>>(coex)}) {
1186         cosubscripts.push_back(
1187             ConvertToType<SubscriptInteger>(std::move(*intExpr)));
1188       } else {
1189         cosubsOk = false;
1190       }
1191     }
1192     if (cosubsOk && !reversed.empty()) {
1193       int numCosubscripts{static_cast<int>(cosubscripts.size())};
1194       const Symbol &symbol{reversed.front()};
1195       if (numCosubscripts != symbol.Corank()) {
1196         Say("'%s' has corank %d, but coindexed reference has %d cosubscripts"_err_en_US,
1197             symbol.name(), symbol.Corank(), numCosubscripts);
1198       }
1199     }
1200     for (const auto &imageSelSpec :
1201         std::get<std::list<parser::ImageSelectorSpec>>(x.imageSelector.t)) {
1202       common::visit(
1203           common::visitors{
1204               [&](const auto &x) { Analyze(x.v); },
1205           },
1206           imageSelSpec.u);
1207     }
1208     // Reverse the chain of symbols so that the base is first and coarray
1209     // ultimate component is last.
1210     if (cosubsOk) {
1211       return Designate(
1212           DataRef{CoarrayRef{SymbolVector{reversed.crbegin(), reversed.crend()},
1213               std::move(subscripts), std::move(cosubscripts)}});
1214     }
1215   }
1216   return std::nullopt;
1217 }
1218 
1219 int ExpressionAnalyzer::IntegerTypeSpecKind(
1220     const parser::IntegerTypeSpec &spec) {
1221   Expr<SubscriptInteger> value{
1222       AnalyzeKindSelector(TypeCategory::Integer, spec.v)};
1223   if (auto kind{ToInt64(value)}) {
1224     return static_cast<int>(*kind);
1225   }
1226   SayAt(spec, "Constant INTEGER kind value required here"_err_en_US);
1227   return GetDefaultKind(TypeCategory::Integer);
1228 }
1229 
1230 // Array constructors
1231 
1232 // Inverts a collection of generic ArrayConstructorValues<SomeType> that
1233 // all happen to have the same actual type T into one ArrayConstructor<T>.
1234 template <typename T>
1235 ArrayConstructorValues<T> MakeSpecific(
1236     ArrayConstructorValues<SomeType> &&from) {
1237   ArrayConstructorValues<T> to;
1238   for (ArrayConstructorValue<SomeType> &x : from) {
1239     common::visit(
1240         common::visitors{
1241             [&](common::CopyableIndirection<Expr<SomeType>> &&expr) {
1242               auto *typed{UnwrapExpr<Expr<T>>(expr.value())};
1243               to.Push(std::move(DEREF(typed)));
1244             },
1245             [&](ImpliedDo<SomeType> &&impliedDo) {
1246               to.Push(ImpliedDo<T>{impliedDo.name(),
1247                   std::move(impliedDo.lower()), std::move(impliedDo.upper()),
1248                   std::move(impliedDo.stride()),
1249                   MakeSpecific<T>(std::move(impliedDo.values()))});
1250             },
1251         },
1252         std::move(x.u));
1253   }
1254   return to;
1255 }
1256 
1257 class ArrayConstructorContext {
1258 public:
1259   ArrayConstructorContext(
1260       ExpressionAnalyzer &c, std::optional<DynamicTypeWithLength> &&t)
1261       : exprAnalyzer_{c}, type_{std::move(t)} {}
1262 
1263   void Add(const parser::AcValue &);
1264   MaybeExpr ToExpr();
1265 
1266   // These interfaces allow *this to be used as a type visitor argument to
1267   // common::SearchTypes() to convert the array constructor to a typed
1268   // expression in ToExpr().
1269   using Result = MaybeExpr;
1270   using Types = AllTypes;
1271   template <typename T> Result Test() {
1272     if (type_ && type_->category() == T::category) {
1273       if constexpr (T::category == TypeCategory::Derived) {
1274         if (!type_->IsUnlimitedPolymorphic()) {
1275           return AsMaybeExpr(ArrayConstructor<T>{type_->GetDerivedTypeSpec(),
1276               MakeSpecific<T>(std::move(values_))});
1277         }
1278       } else if (type_->kind() == T::kind) {
1279         if constexpr (T::category == TypeCategory::Character) {
1280           if (auto len{type_->LEN()}) {
1281             return AsMaybeExpr(ArrayConstructor<T>{
1282                 *std::move(len), MakeSpecific<T>(std::move(values_))});
1283           }
1284         } else {
1285           return AsMaybeExpr(
1286               ArrayConstructor<T>{MakeSpecific<T>(std::move(values_))});
1287         }
1288       }
1289     }
1290     return std::nullopt;
1291   }
1292 
1293 private:
1294   using ImpliedDoIntType = ResultType<ImpliedDoIndex>;
1295 
1296   void Push(MaybeExpr &&);
1297   void Add(const parser::AcValue::Triplet &);
1298   void Add(const parser::Expr &);
1299   void Add(const parser::AcImpliedDo &);
1300   void UnrollConstantImpliedDo(const parser::AcImpliedDo &,
1301       parser::CharBlock name, std::int64_t lower, std::int64_t upper,
1302       std::int64_t stride);
1303 
1304   template <int KIND, typename A>
1305   std::optional<Expr<Type<TypeCategory::Integer, KIND>>> GetSpecificIntExpr(
1306       const A &x) {
1307     if (MaybeExpr y{exprAnalyzer_.Analyze(x)}) {
1308       Expr<SomeInteger> *intExpr{UnwrapExpr<Expr<SomeInteger>>(*y)};
1309       return Fold(exprAnalyzer_.GetFoldingContext(),
1310           ConvertToType<Type<TypeCategory::Integer, KIND>>(
1311               std::move(DEREF(intExpr))));
1312     }
1313     return std::nullopt;
1314   }
1315 
1316   // Nested array constructors all reference the same ExpressionAnalyzer,
1317   // which represents the nest of active implied DO loop indices.
1318   ExpressionAnalyzer &exprAnalyzer_;
1319   std::optional<DynamicTypeWithLength> type_;
1320   bool explicitType_{type_.has_value()};
1321   std::optional<std::int64_t> constantLength_;
1322   ArrayConstructorValues<SomeType> values_;
1323   std::uint64_t messageDisplayedSet_{0};
1324 };
1325 
1326 void ArrayConstructorContext::Push(MaybeExpr &&x) {
1327   if (!x) {
1328     return;
1329   }
1330   if (!type_) {
1331     if (auto *boz{std::get_if<BOZLiteralConstant>(&x->u)}) {
1332       // Treat an array constructor of BOZ as if default integer.
1333       if (exprAnalyzer_.context().ShouldWarn(
1334               common::LanguageFeature::BOZAsDefaultInteger)) {
1335         exprAnalyzer_.Say(
1336             "BOZ literal in array constructor without explicit type is assumed to be default INTEGER"_port_en_US);
1337       }
1338       x = AsGenericExpr(ConvertToKind<TypeCategory::Integer>(
1339           exprAnalyzer_.GetDefaultKind(TypeCategory::Integer),
1340           std::move(*boz)));
1341     }
1342   }
1343   std::optional<DynamicType> dyType{x->GetType()};
1344   if (!dyType) {
1345     if (auto *boz{std::get_if<BOZLiteralConstant>(&x->u)}) {
1346       if (!type_) {
1347         // Treat an array constructor of BOZ as if default integer.
1348         if (exprAnalyzer_.context().ShouldWarn(
1349                 common::LanguageFeature::BOZAsDefaultInteger)) {
1350           exprAnalyzer_.Say(
1351               "BOZ literal in array constructor without explicit type is assumed to be default INTEGER"_port_en_US);
1352         }
1353         x = AsGenericExpr(ConvertToKind<TypeCategory::Integer>(
1354             exprAnalyzer_.GetDefaultKind(TypeCategory::Integer),
1355             std::move(*boz)));
1356         dyType = x.value().GetType();
1357       } else if (auto cast{ConvertToType(*type_, std::move(*x))}) {
1358         x = std::move(cast);
1359         dyType = *type_;
1360       } else {
1361         if (!(messageDisplayedSet_ & 0x80)) {
1362           exprAnalyzer_.Say(
1363               "BOZ literal is not suitable for use in this array constructor"_err_en_US);
1364           messageDisplayedSet_ |= 0x80;
1365         }
1366         return;
1367       }
1368     } else { // procedure name, &c.
1369       if (!(messageDisplayedSet_ & 0x40)) {
1370         exprAnalyzer_.Say(
1371             "Item is not suitable for use in an array constructor"_err_en_US);
1372         messageDisplayedSet_ |= 0x40;
1373       }
1374       return;
1375     }
1376   } else if (dyType->IsUnlimitedPolymorphic()) {
1377     if (!(messageDisplayedSet_ & 8)) {
1378       exprAnalyzer_.Say("Cannot have an unlimited polymorphic value in an "
1379                         "array constructor"_err_en_US); // C7113
1380       messageDisplayedSet_ |= 8;
1381     }
1382     return;
1383   }
1384   DynamicTypeWithLength xType{dyType.value()};
1385   if (Expr<SomeCharacter> * charExpr{UnwrapExpr<Expr<SomeCharacter>>(*x)}) {
1386     CHECK(xType.category() == TypeCategory::Character);
1387     xType.length =
1388         common::visit([](const auto &kc) { return kc.LEN(); }, charExpr->u);
1389   }
1390   if (!type_) {
1391     // If there is no explicit type-spec in an array constructor, the type
1392     // of the array is the declared type of all of the elements, which must
1393     // be well-defined and all match.
1394     // TODO: Possible language extension: use the most general type of
1395     // the values as the type of a numeric constructed array, convert all
1396     // of the other values to that type.  Alternative: let the first value
1397     // determine the type, and convert the others to that type.
1398     CHECK(!explicitType_);
1399     type_ = std::move(xType);
1400     constantLength_ = ToInt64(type_->length);
1401     values_.Push(std::move(*x));
1402   } else if (!explicitType_) {
1403     if (type_->IsTkCompatibleWith(xType) && xType.IsTkCompatibleWith(*type_)) {
1404       values_.Push(std::move(*x));
1405       if (auto thisLen{ToInt64(xType.LEN())}) {
1406         if (constantLength_) {
1407           if (exprAnalyzer_.context().warnOnNonstandardUsage() &&
1408               *thisLen != *constantLength_) {
1409             if (!(messageDisplayedSet_ & 1)) {
1410               exprAnalyzer_.Say(
1411                   "Character literal in array constructor without explicit "
1412                   "type has different length than earlier elements"_port_en_US);
1413               messageDisplayedSet_ |= 1;
1414             }
1415           }
1416           if (*thisLen > *constantLength_) {
1417             // Language extension: use the longest literal to determine the
1418             // length of the array constructor's character elements, not the
1419             // first, when there is no explicit type.
1420             *constantLength_ = *thisLen;
1421             type_->length = xType.LEN();
1422           }
1423         } else {
1424           constantLength_ = *thisLen;
1425           type_->length = xType.LEN();
1426         }
1427       }
1428     } else {
1429       if (!(messageDisplayedSet_ & 2)) {
1430         exprAnalyzer_.Say(
1431             "Values in array constructor must have the same declared type "
1432             "when no explicit type appears"_err_en_US); // C7110
1433         messageDisplayedSet_ |= 2;
1434       }
1435     }
1436   } else {
1437     if (auto cast{ConvertToType(*type_, std::move(*x))}) {
1438       values_.Push(std::move(*cast));
1439     } else if (!(messageDisplayedSet_ & 4)) {
1440       exprAnalyzer_.Say("Value in array constructor of type '%s' could not "
1441                         "be converted to the type of the array '%s'"_err_en_US,
1442           x->GetType()->AsFortran(), type_->AsFortran()); // C7111, C7112
1443       messageDisplayedSet_ |= 4;
1444     }
1445   }
1446 }
1447 
1448 void ArrayConstructorContext::Add(const parser::AcValue &x) {
1449   common::visit(
1450       common::visitors{
1451           [&](const parser::AcValue::Triplet &triplet) { Add(triplet); },
1452           [&](const common::Indirection<parser::Expr> &expr) {
1453             Add(expr.value());
1454           },
1455           [&](const common::Indirection<parser::AcImpliedDo> &impliedDo) {
1456             Add(impliedDo.value());
1457           },
1458       },
1459       x.u);
1460 }
1461 
1462 // Transforms l:u(:s) into (_,_=l,u(,s)) with an anonymous index '_'
1463 void ArrayConstructorContext::Add(const parser::AcValue::Triplet &triplet) {
1464   std::optional<Expr<ImpliedDoIntType>> lower{
1465       GetSpecificIntExpr<ImpliedDoIntType::kind>(std::get<0>(triplet.t))};
1466   std::optional<Expr<ImpliedDoIntType>> upper{
1467       GetSpecificIntExpr<ImpliedDoIntType::kind>(std::get<1>(triplet.t))};
1468   std::optional<Expr<ImpliedDoIntType>> stride{
1469       GetSpecificIntExpr<ImpliedDoIntType::kind>(std::get<2>(triplet.t))};
1470   if (lower && upper) {
1471     if (!stride) {
1472       stride = Expr<ImpliedDoIntType>{1};
1473     }
1474     if (!type_) {
1475       type_ = DynamicTypeWithLength{ImpliedDoIntType::GetType()};
1476     }
1477     auto v{std::move(values_)};
1478     parser::CharBlock anonymous;
1479     Push(Expr<SomeType>{
1480         Expr<SomeInteger>{Expr<ImpliedDoIntType>{ImpliedDoIndex{anonymous}}}});
1481     std::swap(v, values_);
1482     values_.Push(ImpliedDo<SomeType>{anonymous, std::move(*lower),
1483         std::move(*upper), std::move(*stride), std::move(v)});
1484   }
1485 }
1486 
1487 void ArrayConstructorContext::Add(const parser::Expr &expr) {
1488   auto restorer{exprAnalyzer_.GetContextualMessages().SetLocation(expr.source)};
1489   Push(exprAnalyzer_.Analyze(expr));
1490 }
1491 
1492 void ArrayConstructorContext::Add(const parser::AcImpliedDo &impliedDo) {
1493   const auto &control{std::get<parser::AcImpliedDoControl>(impliedDo.t)};
1494   const auto &bounds{std::get<parser::AcImpliedDoControl::Bounds>(control.t)};
1495   exprAnalyzer_.Analyze(bounds.name);
1496   parser::CharBlock name{bounds.name.thing.thing.source};
1497   const Symbol *symbol{bounds.name.thing.thing.symbol};
1498   int kind{ImpliedDoIntType::kind};
1499   if (const auto dynamicType{DynamicType::From(symbol)}) {
1500     kind = dynamicType->kind();
1501   }
1502   std::optional<Expr<ImpliedDoIntType>> lower{
1503       GetSpecificIntExpr<ImpliedDoIntType::kind>(bounds.lower)};
1504   std::optional<Expr<ImpliedDoIntType>> upper{
1505       GetSpecificIntExpr<ImpliedDoIntType::kind>(bounds.upper)};
1506   if (lower && upper) {
1507     std::optional<Expr<ImpliedDoIntType>> stride{
1508         GetSpecificIntExpr<ImpliedDoIntType::kind>(bounds.step)};
1509     if (!stride) {
1510       stride = Expr<ImpliedDoIntType>{1};
1511     }
1512     if (exprAnalyzer_.AddImpliedDo(name, kind)) {
1513       // Check for constant bounds; the loop may require complete unrolling
1514       // of the parse tree if all bounds are constant in order to allow the
1515       // implied DO loop index to qualify as a constant expression.
1516       auto cLower{ToInt64(lower)};
1517       auto cUpper{ToInt64(upper)};
1518       auto cStride{ToInt64(stride)};
1519       if (!(messageDisplayedSet_ & 0x10) && cStride && *cStride == 0) {
1520         exprAnalyzer_.SayAt(bounds.step.value().thing.thing.value().source,
1521             "The stride of an implied DO loop must not be zero"_err_en_US);
1522         messageDisplayedSet_ |= 0x10;
1523       }
1524       bool isConstant{cLower && cUpper && cStride && *cStride != 0};
1525       bool isNonemptyConstant{isConstant &&
1526           ((*cStride > 0 && *cLower <= *cUpper) ||
1527               (*cStride < 0 && *cLower >= *cUpper))};
1528       bool unrollConstantLoop{false};
1529       parser::Messages buffer;
1530       auto saveMessagesDisplayed{messageDisplayedSet_};
1531       {
1532         auto messageRestorer{
1533             exprAnalyzer_.GetContextualMessages().SetMessages(buffer)};
1534         auto v{std::move(values_)};
1535         for (const auto &value :
1536             std::get<std::list<parser::AcValue>>(impliedDo.t)) {
1537           Add(value);
1538         }
1539         std::swap(v, values_);
1540         if (isNonemptyConstant && buffer.AnyFatalError()) {
1541           unrollConstantLoop = true;
1542         } else {
1543           values_.Push(ImpliedDo<SomeType>{name, std::move(*lower),
1544               std::move(*upper), std::move(*stride), std::move(v)});
1545         }
1546       }
1547       if (unrollConstantLoop) {
1548         messageDisplayedSet_ = saveMessagesDisplayed;
1549         UnrollConstantImpliedDo(impliedDo, name, *cLower, *cUpper, *cStride);
1550       } else if (auto *messages{
1551                      exprAnalyzer_.GetContextualMessages().messages()}) {
1552         messages->Annex(std::move(buffer));
1553       }
1554       exprAnalyzer_.RemoveImpliedDo(name);
1555     } else if (!(messageDisplayedSet_ & 0x20)) {
1556       exprAnalyzer_.SayAt(name,
1557           "Implied DO index '%s' is active in a surrounding implied DO loop "
1558           "and may not have the same name"_err_en_US,
1559           name); // C7115
1560       messageDisplayedSet_ |= 0x20;
1561     }
1562   }
1563 }
1564 
1565 // Fortran considers an implied DO index of an array constructor to be
1566 // a constant expression if the bounds of the implied DO loop are constant.
1567 // Usually this doesn't matter, but if we emitted spurious messages as a
1568 // result of not using constant values for the index while analyzing the
1569 // items, we need to do it again the "hard" way with multiple iterations over
1570 // the parse tree.
1571 void ArrayConstructorContext::UnrollConstantImpliedDo(
1572     const parser::AcImpliedDo &impliedDo, parser::CharBlock name,
1573     std::int64_t lower, std::int64_t upper, std::int64_t stride) {
1574   auto &foldingContext{exprAnalyzer_.GetFoldingContext()};
1575   auto restorer{exprAnalyzer_.DoNotUseSavedTypedExprs()};
1576   for (auto &at{foldingContext.StartImpliedDo(name, lower)};
1577        (stride > 0 && at <= upper) || (stride < 0 && at >= upper);
1578        at += stride) {
1579     for (const auto &value :
1580         std::get<std::list<parser::AcValue>>(impliedDo.t)) {
1581       Add(value);
1582     }
1583   }
1584   foldingContext.EndImpliedDo(name);
1585 }
1586 
1587 MaybeExpr ArrayConstructorContext::ToExpr() {
1588   return common::SearchTypes(std::move(*this));
1589 }
1590 
1591 MaybeExpr ExpressionAnalyzer::Analyze(const parser::ArrayConstructor &array) {
1592   const parser::AcSpec &acSpec{array.v};
1593   ArrayConstructorContext acContext{*this, AnalyzeTypeSpec(acSpec.type)};
1594   for (const parser::AcValue &value : acSpec.values) {
1595     acContext.Add(value);
1596   }
1597   return acContext.ToExpr();
1598 }
1599 
1600 MaybeExpr ExpressionAnalyzer::Analyze(
1601     const parser::StructureConstructor &structure) {
1602   auto &parsedType{std::get<parser::DerivedTypeSpec>(structure.t)};
1603   parser::Name structureType{std::get<parser::Name>(parsedType.t)};
1604   parser::CharBlock &typeName{structureType.source};
1605   if (semantics::Symbol * typeSymbol{structureType.symbol}) {
1606     if (typeSymbol->has<semantics::DerivedTypeDetails>()) {
1607       semantics::DerivedTypeSpec dtSpec{typeName, typeSymbol->GetUltimate()};
1608       if (!CheckIsValidForwardReference(dtSpec)) {
1609         return std::nullopt;
1610       }
1611     }
1612   }
1613   if (!parsedType.derivedTypeSpec) {
1614     return std::nullopt;
1615   }
1616   const auto &spec{*parsedType.derivedTypeSpec};
1617   const Symbol &typeSymbol{spec.typeSymbol()};
1618   if (!spec.scope() || !typeSymbol.has<semantics::DerivedTypeDetails>()) {
1619     return std::nullopt; // error recovery
1620   }
1621   const auto &typeDetails{typeSymbol.get<semantics::DerivedTypeDetails>()};
1622   const Symbol *parentComponent{typeDetails.GetParentComponent(*spec.scope())};
1623 
1624   if (typeSymbol.attrs().test(semantics::Attr::ABSTRACT)) { // C796
1625     AttachDeclaration(Say(typeName,
1626                           "ABSTRACT derived type '%s' may not be used in a "
1627                           "structure constructor"_err_en_US,
1628                           typeName),
1629         typeSymbol); // C7114
1630   }
1631 
1632   // This iterator traverses all of the components in the derived type and its
1633   // parents.  The symbols for whole parent components appear after their
1634   // own components and before the components of the types that extend them.
1635   // E.g., TYPE :: A; REAL X; END TYPE
1636   //       TYPE, EXTENDS(A) :: B; REAL Y; END TYPE
1637   // produces the component list X, A, Y.
1638   // The order is important below because a structure constructor can
1639   // initialize X or A by name, but not both.
1640   auto components{semantics::OrderedComponentIterator{spec}};
1641   auto nextAnonymous{components.begin()};
1642 
1643   std::set<parser::CharBlock> unavailable;
1644   bool anyKeyword{false};
1645   StructureConstructor result{spec};
1646   bool checkConflicts{true}; // until we hit one
1647   auto &messages{GetContextualMessages()};
1648 
1649   for (const auto &component :
1650       std::get<std::list<parser::ComponentSpec>>(structure.t)) {
1651     const parser::Expr &expr{
1652         std::get<parser::ComponentDataSource>(component.t).v.value()};
1653     parser::CharBlock source{expr.source};
1654     auto restorer{messages.SetLocation(source)};
1655     const Symbol *symbol{nullptr};
1656     MaybeExpr value{Analyze(expr)};
1657     std::optional<DynamicType> valueType{DynamicType::From(value)};
1658     if (const auto &kw{std::get<std::optional<parser::Keyword>>(component.t)}) {
1659       anyKeyword = true;
1660       source = kw->v.source;
1661       symbol = kw->v.symbol;
1662       if (!symbol) {
1663         auto componentIter{std::find_if(components.begin(), components.end(),
1664             [=](const Symbol &symbol) { return symbol.name() == source; })};
1665         if (componentIter != components.end()) {
1666           symbol = &*componentIter;
1667         }
1668       }
1669       if (!symbol) { // C7101
1670         Say(source,
1671             "Keyword '%s=' does not name a component of derived type '%s'"_err_en_US,
1672             source, typeName);
1673       }
1674     } else {
1675       if (anyKeyword) { // C7100
1676         Say(source,
1677             "Value in structure constructor lacks a component name"_err_en_US);
1678         checkConflicts = false; // stem cascade
1679       }
1680       // Here's a regrettably common extension of the standard: anonymous
1681       // initialization of parent components, e.g., T(PT(1)) rather than
1682       // T(1) or T(PT=PT(1)).
1683       if (nextAnonymous == components.begin() && parentComponent &&
1684           valueType == DynamicType::From(*parentComponent) &&
1685           context().IsEnabled(LanguageFeature::AnonymousParents)) {
1686         auto iter{
1687             std::find(components.begin(), components.end(), *parentComponent)};
1688         if (iter != components.end()) {
1689           symbol = parentComponent;
1690           nextAnonymous = ++iter;
1691           if (context().ShouldWarn(LanguageFeature::AnonymousParents)) {
1692             Say(source,
1693                 "Whole parent component '%s' in structure "
1694                 "constructor should not be anonymous"_port_en_US,
1695                 symbol->name());
1696           }
1697         }
1698       }
1699       while (!symbol && nextAnonymous != components.end()) {
1700         const Symbol &next{*nextAnonymous};
1701         ++nextAnonymous;
1702         if (!next.test(Symbol::Flag::ParentComp)) {
1703           symbol = &next;
1704         }
1705       }
1706       if (!symbol) {
1707         Say(source, "Unexpected value in structure constructor"_err_en_US);
1708       }
1709     }
1710     if (symbol) {
1711       if (const auto *currScope{context_.globalScope().FindScope(source)}) {
1712         if (auto msg{CheckAccessibleComponent(*currScope, *symbol)}) {
1713           Say(source, *msg);
1714         }
1715       }
1716       if (checkConflicts) {
1717         auto componentIter{
1718             std::find(components.begin(), components.end(), *symbol)};
1719         if (unavailable.find(symbol->name()) != unavailable.cend()) {
1720           // C797, C798
1721           Say(source,
1722               "Component '%s' conflicts with another component earlier in "
1723               "this structure constructor"_err_en_US,
1724               symbol->name());
1725         } else if (symbol->test(Symbol::Flag::ParentComp)) {
1726           // Make earlier components unavailable once a whole parent appears.
1727           for (auto it{components.begin()}; it != componentIter; ++it) {
1728             unavailable.insert(it->name());
1729           }
1730         } else {
1731           // Make whole parent components unavailable after any of their
1732           // constituents appear.
1733           for (auto it{componentIter}; it != components.end(); ++it) {
1734             if (it->test(Symbol::Flag::ParentComp)) {
1735               unavailable.insert(it->name());
1736             }
1737           }
1738         }
1739       }
1740       unavailable.insert(symbol->name());
1741       if (value) {
1742         if (symbol->has<semantics::ProcEntityDetails>()) {
1743           CHECK(IsPointer(*symbol));
1744         } else if (symbol->has<semantics::ObjectEntityDetails>()) {
1745           // C1594(4)
1746           const auto &innermost{context_.FindScope(expr.source)};
1747           if (const auto *pureProc{FindPureProcedureContaining(innermost)}) {
1748             if (const Symbol * pointer{FindPointerComponent(*symbol)}) {
1749               if (const Symbol *
1750                   object{FindExternallyVisibleObject(*value, *pureProc)}) {
1751                 if (auto *msg{Say(expr.source,
1752                         "Externally visible object '%s' may not be "
1753                         "associated with pointer component '%s' in a "
1754                         "pure procedure"_err_en_US,
1755                         object->name(), pointer->name())}) {
1756                   msg->Attach(object->name(), "Object declaration"_en_US)
1757                       .Attach(pointer->name(), "Pointer declaration"_en_US);
1758                 }
1759               }
1760             }
1761           }
1762         } else if (symbol->has<semantics::TypeParamDetails>()) {
1763           Say(expr.source,
1764               "Type parameter '%s' may not appear as a component "
1765               "of a structure constructor"_err_en_US,
1766               symbol->name());
1767           continue;
1768         } else {
1769           Say(expr.source,
1770               "Component '%s' is neither a procedure pointer "
1771               "nor a data object"_err_en_US,
1772               symbol->name());
1773           continue;
1774         }
1775         if (IsPointer(*symbol)) {
1776           semantics::CheckPointerAssignment(
1777               GetFoldingContext(), *symbol, *value); // C7104, C7105
1778           result.Add(*symbol, Fold(std::move(*value)));
1779         } else if (MaybeExpr converted{
1780                        ConvertToType(*symbol, std::move(*value))}) {
1781           if (auto componentShape{GetShape(GetFoldingContext(), *symbol)}) {
1782             if (auto valueShape{GetShape(GetFoldingContext(), *converted)}) {
1783               if (GetRank(*componentShape) == 0 && GetRank(*valueShape) > 0) {
1784                 AttachDeclaration(
1785                     Say(expr.source,
1786                         "Rank-%d array value is not compatible with scalar component '%s'"_err_en_US,
1787                         GetRank(*valueShape), symbol->name()),
1788                     *symbol);
1789               } else {
1790                 auto checked{
1791                     CheckConformance(messages, *componentShape, *valueShape,
1792                         CheckConformanceFlags::RightIsExpandableDeferred,
1793                         "component", "value")};
1794                 if (checked && *checked && GetRank(*componentShape) > 0 &&
1795                     GetRank(*valueShape) == 0 &&
1796                     !IsExpandableScalar(*converted)) {
1797                   AttachDeclaration(
1798                       Say(expr.source,
1799                           "Scalar value cannot be expanded to shape of array component '%s'"_err_en_US,
1800                           symbol->name()),
1801                       *symbol);
1802                 }
1803                 if (checked.value_or(true)) {
1804                   result.Add(*symbol, std::move(*converted));
1805                 }
1806               }
1807             } else {
1808               Say(expr.source, "Shape of value cannot be determined"_err_en_US);
1809             }
1810           } else {
1811             AttachDeclaration(
1812                 Say(expr.source,
1813                     "Shape of component '%s' cannot be determined"_err_en_US,
1814                     symbol->name()),
1815                 *symbol);
1816           }
1817         } else if (IsAllocatable(*symbol) && IsBareNullPointer(&*value)) {
1818           // NULL() with no arguments allowed by 7.5.10 para 6 for ALLOCATABLE.
1819           result.Add(*symbol, Expr<SomeType>{NullPointer{}});
1820         } else if (auto symType{DynamicType::From(symbol)}) {
1821           if (IsAllocatable(*symbol) && symType->IsUnlimitedPolymorphic() &&
1822               valueType) {
1823             // ok
1824           } else if (valueType) {
1825             AttachDeclaration(
1826                 Say(expr.source,
1827                     "Value in structure constructor of type '%s' is "
1828                     "incompatible with component '%s' of type '%s'"_err_en_US,
1829                     valueType->AsFortran(), symbol->name(),
1830                     symType->AsFortran()),
1831                 *symbol);
1832           } else {
1833             AttachDeclaration(
1834                 Say(expr.source,
1835                     "Value in structure constructor is incompatible with "
1836                     "component '%s' of type %s"_err_en_US,
1837                     symbol->name(), symType->AsFortran()),
1838                 *symbol);
1839           }
1840         }
1841       }
1842     }
1843   }
1844 
1845   // Ensure that unmentioned component objects have default initializers.
1846   for (const Symbol &symbol : components) {
1847     if (!symbol.test(Symbol::Flag::ParentComp) &&
1848         unavailable.find(symbol.name()) == unavailable.cend()) {
1849       if (IsAllocatable(symbol)) {
1850         // Set all remaining allocatables to explicit NULL()
1851         result.Add(symbol, Expr<SomeType>{NullPointer{}});
1852       } else if (const auto *details{
1853                      symbol.detailsIf<semantics::ObjectEntityDetails>()}) {
1854         if (details->init()) {
1855           result.Add(symbol, common::Clone(*details->init()));
1856         } else { // C799
1857           AttachDeclaration(Say(typeName,
1858                                 "Structure constructor lacks a value for "
1859                                 "component '%s'"_err_en_US,
1860                                 symbol.name()),
1861               symbol);
1862         }
1863       }
1864     }
1865   }
1866 
1867   return AsMaybeExpr(Expr<SomeDerived>{std::move(result)});
1868 }
1869 
1870 static std::optional<parser::CharBlock> GetPassName(
1871     const semantics::Symbol &proc) {
1872   return common::visit(
1873       [](const auto &details) {
1874         if constexpr (std::is_base_of_v<semantics::WithPassArg,
1875                           std::decay_t<decltype(details)>>) {
1876           return details.passName();
1877         } else {
1878           return std::optional<parser::CharBlock>{};
1879         }
1880       },
1881       proc.details());
1882 }
1883 
1884 static int GetPassIndex(const Symbol &proc) {
1885   CHECK(!proc.attrs().test(semantics::Attr::NOPASS));
1886   std::optional<parser::CharBlock> passName{GetPassName(proc)};
1887   const auto *interface { semantics::FindInterface(proc) };
1888   if (!passName || !interface) {
1889     return 0; // first argument is passed-object
1890   }
1891   const auto &subp{interface->get<semantics::SubprogramDetails>()};
1892   int index{0};
1893   for (const auto *arg : subp.dummyArgs()) {
1894     if (arg && arg->name() == passName) {
1895       return index;
1896     }
1897     ++index;
1898   }
1899   DIE("PASS argument name not in dummy argument list");
1900 }
1901 
1902 // Injects an expression into an actual argument list as the "passed object"
1903 // for a type-bound procedure reference that is not NOPASS.  Adds an
1904 // argument keyword if possible, but not when the passed object goes
1905 // before a positional argument.
1906 // e.g., obj%tbp(x) -> tbp(obj,x).
1907 static void AddPassArg(ActualArguments &actuals, const Expr<SomeDerived> &expr,
1908     const Symbol &component, bool isPassedObject = true) {
1909   if (component.attrs().test(semantics::Attr::NOPASS)) {
1910     return;
1911   }
1912   int passIndex{GetPassIndex(component)};
1913   auto iter{actuals.begin()};
1914   int at{0};
1915   while (iter < actuals.end() && at < passIndex) {
1916     if (*iter && (*iter)->keyword()) {
1917       iter = actuals.end();
1918       break;
1919     }
1920     ++iter;
1921     ++at;
1922   }
1923   ActualArgument passed{AsGenericExpr(common::Clone(expr))};
1924   passed.set_isPassedObject(isPassedObject);
1925   if (iter == actuals.end()) {
1926     if (auto passName{GetPassName(component)}) {
1927       passed.set_keyword(*passName);
1928     }
1929   }
1930   actuals.emplace(iter, std::move(passed));
1931 }
1932 
1933 // Return the compile-time resolution of a procedure binding, if possible.
1934 static const Symbol *GetBindingResolution(
1935     const std::optional<DynamicType> &baseType, const Symbol &component) {
1936   const auto *binding{component.detailsIf<semantics::ProcBindingDetails>()};
1937   if (!binding) {
1938     return nullptr;
1939   }
1940   if (!component.attrs().test(semantics::Attr::NON_OVERRIDABLE) &&
1941       (!baseType || baseType->IsPolymorphic())) {
1942     return nullptr;
1943   }
1944   return &binding->symbol();
1945 }
1946 
1947 auto ExpressionAnalyzer::AnalyzeProcedureComponentRef(
1948     const parser::ProcComponentRef &pcr, ActualArguments &&arguments,
1949     bool isSubroutine) -> std::optional<CalleeAndArguments> {
1950   const parser::StructureComponent &sc{pcr.v.thing};
1951   if (MaybeExpr base{Analyze(sc.base)}) {
1952     if (const Symbol * sym{sc.component.symbol}) {
1953       if (context_.HasError(sym)) {
1954         return std::nullopt;
1955       }
1956       if (!IsProcedure(*sym)) {
1957         AttachDeclaration(
1958             Say(sc.component.source, "'%s' is not a procedure"_err_en_US,
1959                 sc.component.source),
1960             *sym);
1961         return std::nullopt;
1962       }
1963       if (auto *dtExpr{UnwrapExpr<Expr<SomeDerived>>(*base)}) {
1964         if (sym->has<semantics::GenericDetails>()) {
1965           AdjustActuals adjustment{
1966               [&](const Symbol &proc, ActualArguments &actuals) {
1967                 if (!proc.attrs().test(semantics::Attr::NOPASS)) {
1968                   AddPassArg(actuals, std::move(*dtExpr), proc);
1969                 }
1970                 return true;
1971               }};
1972           auto pair{ResolveGeneric(*sym, arguments, adjustment, isSubroutine)};
1973           sym = pair.first;
1974           if (sym) {
1975             // re-resolve the name to the specific binding
1976             sc.component.symbol = const_cast<Symbol *>(sym);
1977           } else {
1978             EmitGenericResolutionError(*sc.component.symbol, pair.second);
1979             return std::nullopt;
1980           }
1981         }
1982         std::optional<DataRef> dataRef{ExtractDataRef(std::move(*dtExpr))};
1983         if (dataRef.has_value() && !CheckRanks(std::move(*dataRef))) {
1984           return std::nullopt;
1985         }
1986         if (const Symbol *
1987             resolution{GetBindingResolution(dtExpr->GetType(), *sym)}) {
1988           AddPassArg(arguments, std::move(*dtExpr), *sym, false);
1989           return CalleeAndArguments{
1990               ProcedureDesignator{*resolution}, std::move(arguments)};
1991         } else if (dataRef.has_value()) {
1992           if (sym->attrs().test(semantics::Attr::NOPASS)) {
1993             return CalleeAndArguments{
1994                 ProcedureDesignator{Component{std::move(*dataRef), *sym}},
1995                 std::move(arguments)};
1996           } else {
1997             AddPassArg(arguments,
1998                 Expr<SomeDerived>{Designator<SomeDerived>{std::move(*dataRef)}},
1999                 *sym);
2000             return CalleeAndArguments{
2001                 ProcedureDesignator{*sym}, std::move(arguments)};
2002           }
2003         }
2004       }
2005       Say(sc.component.source,
2006           "Base of procedure component reference is not a derived-type object"_err_en_US);
2007     }
2008   }
2009   CHECK(context_.AnyFatalError());
2010   return std::nullopt;
2011 }
2012 
2013 // Can actual be argument associated with dummy?
2014 static bool CheckCompatibleArgument(bool isElemental,
2015     const ActualArgument &actual, const characteristics::DummyArgument &dummy) {
2016   const auto *expr{actual.UnwrapExpr()};
2017   return common::visit(
2018       common::visitors{
2019           [&](const characteristics::DummyDataObject &x) {
2020             if (x.attrs.test(characteristics::DummyDataObject::Attr::Pointer) &&
2021                 IsBareNullPointer(expr)) {
2022               // NULL() without MOLD= is compatible with any dummy data pointer
2023               // but cannot be allowed to lead to ambiguity.
2024               return true;
2025             } else if (!isElemental && actual.Rank() != x.type.Rank() &&
2026                 !x.type.attrs().test(
2027                     characteristics::TypeAndShape::Attr::AssumedRank)) {
2028               return false;
2029             } else if (auto actualType{actual.GetType()}) {
2030               return x.type.type().IsTkCompatibleWith(*actualType);
2031             }
2032             return false;
2033           },
2034           [&](const characteristics::DummyProcedure &) {
2035             return expr && IsProcedurePointerTarget(*expr);
2036           },
2037           [&](const characteristics::AlternateReturn &) {
2038             return actual.isAlternateReturn();
2039           },
2040       },
2041       dummy.u);
2042 }
2043 
2044 // Are the actual arguments compatible with the dummy arguments of procedure?
2045 static bool CheckCompatibleArguments(
2046     const characteristics::Procedure &procedure,
2047     const ActualArguments &actuals) {
2048   bool isElemental{procedure.IsElemental()};
2049   const auto &dummies{procedure.dummyArguments};
2050   CHECK(dummies.size() == actuals.size());
2051   for (std::size_t i{0}; i < dummies.size(); ++i) {
2052     const characteristics::DummyArgument &dummy{dummies[i]};
2053     const std::optional<ActualArgument> &actual{actuals[i]};
2054     if (actual && !CheckCompatibleArgument(isElemental, *actual, dummy)) {
2055       return false;
2056     }
2057   }
2058   return true;
2059 }
2060 
2061 // Handles a forward reference to a module function from what must
2062 // be a specification expression.  Return false if the symbol is
2063 // an invalid forward reference.
2064 bool ExpressionAnalyzer::ResolveForward(const Symbol &symbol) {
2065   if (context_.HasError(symbol)) {
2066     return false;
2067   }
2068   if (const auto *details{
2069           symbol.detailsIf<semantics::SubprogramNameDetails>()}) {
2070     if (details->kind() == semantics::SubprogramKind::Module) {
2071       // If this symbol is still a SubprogramNameDetails, we must be
2072       // checking a specification expression in a sibling module
2073       // procedure.  Resolve its names now so that its interface
2074       // is known.
2075       semantics::ResolveSpecificationParts(context_, symbol);
2076       if (symbol.has<semantics::SubprogramNameDetails>()) {
2077         // When the symbol hasn't had its details updated, we must have
2078         // already been in the process of resolving the function's
2079         // specification part; but recursive function calls are not
2080         // allowed in specification parts (10.1.11 para 5).
2081         Say("The module function '%s' may not be referenced recursively in a specification expression"_err_en_US,
2082             symbol.name());
2083         context_.SetError(symbol);
2084         return false;
2085       }
2086     } else { // 10.1.11 para 4
2087       Say("The internal function '%s' may not be referenced in a specification expression"_err_en_US,
2088           symbol.name());
2089       context_.SetError(symbol);
2090       return false;
2091     }
2092   }
2093   return true;
2094 }
2095 
2096 // Resolve a call to a generic procedure with given actual arguments.
2097 // adjustActuals is called on procedure bindings to handle pass arg.
2098 std::pair<const Symbol *, bool> ExpressionAnalyzer::ResolveGeneric(
2099     const Symbol &symbol, const ActualArguments &actuals,
2100     const AdjustActuals &adjustActuals, bool isSubroutine,
2101     bool mightBeStructureConstructor) {
2102   const Symbol *elemental{nullptr}; // matching elemental specific proc
2103   const Symbol *nonElemental{nullptr}; // matching non-elemental specific
2104   const Symbol &ultimate{symbol.GetUltimate()};
2105   // Check for a match with an explicit INTRINSIC
2106   if (ultimate.attrs().test(semantics::Attr::INTRINSIC)) {
2107     parser::Messages buffer;
2108     auto restorer{foldingContext_.messages().SetMessages(buffer)};
2109     ActualArguments localActuals{actuals};
2110     if (context_.intrinsics().Probe(
2111             CallCharacteristics{ultimate.name().ToString(), isSubroutine},
2112             localActuals, foldingContext_) &&
2113         !buffer.AnyFatalError()) {
2114       return {&ultimate, false};
2115     }
2116   }
2117   if (const auto *details{ultimate.detailsIf<semantics::GenericDetails>()}) {
2118     bool anyBareNullActual{
2119         std::find_if(actuals.begin(), actuals.end(), [](auto iter) {
2120           return IsBareNullPointer(iter->UnwrapExpr());
2121         }) != actuals.end()};
2122     for (const Symbol &specific : details->specificProcs()) {
2123       if (!ResolveForward(specific)) {
2124         continue;
2125       }
2126       if (std::optional<characteristics::Procedure> procedure{
2127               characteristics::Procedure::Characterize(
2128                   ProcedureDesignator{specific}, context_.foldingContext())}) {
2129         ActualArguments localActuals{actuals};
2130         if (specific.has<semantics::ProcBindingDetails>()) {
2131           if (!adjustActuals.value()(specific, localActuals)) {
2132             continue;
2133           }
2134         }
2135         if (semantics::CheckInterfaceForGeneric(*procedure, localActuals,
2136                 GetFoldingContext(), false /* no integer conversions */) &&
2137             CheckCompatibleArguments(*procedure, localActuals)) {
2138           if ((procedure->IsElemental() && elemental) ||
2139               (!procedure->IsElemental() && nonElemental)) {
2140             // 16.9.144(6): a bare NULL() is not allowed as an actual
2141             // argument to a generic procedure if the specific procedure
2142             // cannot be unambiguously distinguished
2143             return {nullptr, true /* due to NULL actuals */};
2144           }
2145           if (!procedure->IsElemental()) {
2146             // takes priority over elemental match
2147             nonElemental = &specific;
2148             if (!anyBareNullActual) {
2149               break; // unambiguous case
2150             }
2151           } else {
2152             elemental = &specific;
2153           }
2154         }
2155       }
2156     }
2157     if (nonElemental) {
2158       return {&AccessSpecific(symbol, *nonElemental), false};
2159     } else if (elemental) {
2160       return {&AccessSpecific(symbol, *elemental), false};
2161     }
2162     // Check parent derived type
2163     if (const auto *parentScope{symbol.owner().GetDerivedTypeParent()}) {
2164       if (const Symbol * extended{parentScope->FindComponent(symbol.name())}) {
2165         auto pair{ResolveGeneric(
2166             *extended, actuals, adjustActuals, isSubroutine, false)};
2167         if (pair.first) {
2168           return pair;
2169         }
2170       }
2171     }
2172     if (mightBeStructureConstructor && details->derivedType()) {
2173       return {details->derivedType(), false};
2174     }
2175   }
2176   // Check for generic or explicit INTRINSIC of the same name in outer scopes.
2177   // See 15.5.5.2 for details.
2178   if (!symbol.owner().IsGlobal() && !symbol.owner().IsDerivedType()) {
2179     for (const std::string &n : GetAllNames(context_, symbol.name())) {
2180       if (const Symbol * outer{symbol.owner().parent().FindSymbol(n)}) {
2181         auto pair{ResolveGeneric(*outer, actuals, adjustActuals, isSubroutine,
2182             mightBeStructureConstructor)};
2183         if (pair.first) {
2184           return pair;
2185         }
2186       }
2187     }
2188   }
2189   return {nullptr, false};
2190 }
2191 
2192 const Symbol &ExpressionAnalyzer::AccessSpecific(
2193     const Symbol &originalGeneric, const Symbol &specific) {
2194   if (const auto *hosted{
2195           originalGeneric.detailsIf<semantics::HostAssocDetails>()}) {
2196     return AccessSpecific(hosted->symbol(), specific);
2197   } else if (const auto *used{
2198                  originalGeneric.detailsIf<semantics::UseDetails>()}) {
2199     const auto &scope{originalGeneric.owner()};
2200     if (auto iter{scope.find(specific.name())}; iter != scope.end()) {
2201       if (const auto *useDetails{
2202               iter->second->detailsIf<semantics::UseDetails>()}) {
2203         const Symbol &usedSymbol{useDetails->symbol()};
2204         const auto *usedGeneric{
2205             usedSymbol.detailsIf<semantics::GenericDetails>()};
2206         if (&usedSymbol == &specific ||
2207             (usedGeneric && usedGeneric->specific() == &specific)) {
2208           return specific;
2209         }
2210       }
2211     }
2212     // Create a renaming USE of the specific procedure.
2213     auto rename{context_.SaveTempName(
2214         used->symbol().owner().GetName().value().ToString() + "$" +
2215         specific.owner().GetName().value().ToString() + "$" +
2216         specific.name().ToString())};
2217     return *const_cast<semantics::Scope &>(scope)
2218                 .try_emplace(rename, specific.attrs(),
2219                     semantics::UseDetails{rename, specific})
2220                 .first->second;
2221   } else {
2222     return specific;
2223   }
2224 }
2225 
2226 void ExpressionAnalyzer::EmitGenericResolutionError(
2227     const Symbol &symbol, bool dueToNullActuals) {
2228   Say(dueToNullActuals
2229           ? "One or more NULL() actual arguments to the generic procedure '%s' requires a MOLD= for disambiguation"_err_en_US
2230           : semantics::IsGenericDefinedOp(symbol)
2231           ? "No specific procedure of generic operator '%s' matches the actual arguments"_err_en_US
2232           : "No specific procedure of generic '%s' matches the actual arguments"_err_en_US,
2233       symbol.name());
2234 }
2235 
2236 auto ExpressionAnalyzer::GetCalleeAndArguments(
2237     const parser::ProcedureDesignator &pd, ActualArguments &&arguments,
2238     bool isSubroutine, bool mightBeStructureConstructor)
2239     -> std::optional<CalleeAndArguments> {
2240   return common::visit(
2241       common::visitors{
2242           [&](const parser::Name &name) {
2243             return GetCalleeAndArguments(name, std::move(arguments),
2244                 isSubroutine, mightBeStructureConstructor);
2245           },
2246           [&](const parser::ProcComponentRef &pcr) {
2247             return AnalyzeProcedureComponentRef(
2248                 pcr, std::move(arguments), isSubroutine);
2249           },
2250       },
2251       pd.u);
2252 }
2253 
2254 auto ExpressionAnalyzer::GetCalleeAndArguments(const parser::Name &name,
2255     ActualArguments &&arguments, bool isSubroutine,
2256     bool mightBeStructureConstructor) -> std::optional<CalleeAndArguments> {
2257   const Symbol *symbol{name.symbol};
2258   if (context_.HasError(symbol)) {
2259     return std::nullopt; // also handles null symbol
2260   }
2261   const Symbol &ultimate{DEREF(symbol).GetUltimate()};
2262   CheckForBadRecursion(name.source, ultimate);
2263   bool dueToNullActual{false};
2264   bool isGenericInterface{ultimate.has<semantics::GenericDetails>()};
2265   bool isExplicitIntrinsic{ultimate.attrs().test(semantics::Attr::INTRINSIC)};
2266   const Symbol *resolution{nullptr};
2267   if (isGenericInterface || isExplicitIntrinsic) {
2268     ExpressionAnalyzer::AdjustActuals noAdjustment;
2269     auto pair{ResolveGeneric(*symbol, arguments, noAdjustment, isSubroutine,
2270         mightBeStructureConstructor)};
2271     resolution = pair.first;
2272     dueToNullActual = pair.second;
2273     if (resolution) {
2274       // re-resolve name to the specific procedure
2275       name.symbol = const_cast<Symbol *>(resolution);
2276     }
2277   } else {
2278     resolution = symbol;
2279   }
2280   if (!resolution || resolution->attrs().test(semantics::Attr::INTRINSIC)) {
2281     // Not generic, or no resolution; may be intrinsic
2282     if (std::optional<SpecificCall> specificCall{context_.intrinsics().Probe(
2283             CallCharacteristics{ultimate.name().ToString(), isSubroutine},
2284             arguments, GetFoldingContext())}) {
2285       CheckBadExplicitType(*specificCall, *symbol);
2286       return CalleeAndArguments{
2287           ProcedureDesignator{std::move(specificCall->specificIntrinsic)},
2288           std::move(specificCall->arguments)};
2289     } else {
2290       if (isGenericInterface) {
2291         EmitGenericResolutionError(*symbol, dueToNullActual);
2292       }
2293       return std::nullopt;
2294     }
2295   }
2296   if (resolution->GetUltimate().has<semantics::DerivedTypeDetails>()) {
2297     if (mightBeStructureConstructor) {
2298       return CalleeAndArguments{
2299           semantics::SymbolRef{*resolution}, std::move(arguments)};
2300     }
2301   } else if (IsProcedure(*resolution)) {
2302     return CalleeAndArguments{
2303         ProcedureDesignator{*resolution}, std::move(arguments)};
2304   }
2305   if (!context_.HasError(*resolution)) {
2306     AttachDeclaration(
2307         Say(name.source, "'%s' is not a callable procedure"_err_en_US,
2308             name.source),
2309         *resolution);
2310   }
2311   return std::nullopt;
2312 }
2313 
2314 // Fortran 2018 expressly states (8.2 p3) that any declared type for a
2315 // generic intrinsic function "has no effect" on the result type of a
2316 // call to that intrinsic.  So one can declare "character*8 cos" and
2317 // still get a real result from "cos(1.)".  This is a dangerous feature,
2318 // especially since implementations are free to extend their sets of
2319 // intrinsics, and in doing so might clash with a name in a program.
2320 // So we emit a warning in this situation, and perhaps it should be an
2321 // error -- any correctly working program can silence the message by
2322 // simply deleting the pointless type declaration.
2323 void ExpressionAnalyzer::CheckBadExplicitType(
2324     const SpecificCall &call, const Symbol &intrinsic) {
2325   if (intrinsic.GetUltimate().GetType()) {
2326     const auto &procedure{call.specificIntrinsic.characteristics.value()};
2327     if (const auto &result{procedure.functionResult}) {
2328       if (const auto *typeAndShape{result->GetTypeAndShape()}) {
2329         if (auto declared{
2330                 typeAndShape->Characterize(intrinsic, GetFoldingContext())}) {
2331           if (!declared->type().IsTkCompatibleWith(typeAndShape->type())) {
2332             if (auto *msg{Say(
2333                     "The result type '%s' of the intrinsic function '%s' is not the explicit declared type '%s'"_warn_en_US,
2334                     typeAndShape->AsFortran(), intrinsic.name(),
2335                     declared->AsFortran())}) {
2336               msg->Attach(intrinsic.name(),
2337                   "Ignored declaration of intrinsic function '%s'"_en_US,
2338                   intrinsic.name());
2339             }
2340           }
2341         }
2342       }
2343     }
2344   }
2345 }
2346 
2347 void ExpressionAnalyzer::CheckForBadRecursion(
2348     parser::CharBlock callSite, const semantics::Symbol &proc) {
2349   if (const auto *scope{proc.scope()}) {
2350     if (scope->sourceRange().Contains(callSite)) {
2351       parser::Message *msg{nullptr};
2352       if (proc.attrs().test(semantics::Attr::NON_RECURSIVE)) { // 15.6.2.1(3)
2353         msg = Say("NON_RECURSIVE procedure '%s' cannot call itself"_err_en_US,
2354             callSite);
2355       } else if (IsAssumedLengthCharacter(proc) && IsExternal(proc)) {
2356         // TODO: Also catch assumed PDT type parameters
2357         msg = Say( // 15.6.2.1(3)
2358             "Assumed-length CHARACTER(*) function '%s' cannot call itself"_err_en_US,
2359             callSite);
2360       }
2361       AttachDeclaration(msg, proc);
2362     }
2363   }
2364 }
2365 
2366 template <typename A> static const Symbol *AssumedTypeDummy(const A &x) {
2367   if (const auto *designator{
2368           std::get_if<common::Indirection<parser::Designator>>(&x.u)}) {
2369     if (const auto *dataRef{
2370             std::get_if<parser::DataRef>(&designator->value().u)}) {
2371       if (const auto *name{std::get_if<parser::Name>(&dataRef->u)}) {
2372         return AssumedTypeDummy(*name);
2373       }
2374     }
2375   }
2376   return nullptr;
2377 }
2378 template <>
2379 const Symbol *AssumedTypeDummy<parser::Name>(const parser::Name &name) {
2380   if (const Symbol * symbol{name.symbol}) {
2381     if (const auto *type{symbol->GetType()}) {
2382       if (type->category() == semantics::DeclTypeSpec::TypeStar) {
2383         return symbol;
2384       }
2385     }
2386   }
2387   return nullptr;
2388 }
2389 template <typename A>
2390 static const Symbol *AssumedTypePointerOrAllocatableDummy(const A &object) {
2391   // It is illegal for allocatable of pointer objects to be TYPE(*), but at that
2392   // point it is is not guaranteed that it has been checked the object has
2393   // POINTER or ALLOCATABLE attribute, so do not assume nullptr can be directly
2394   // returned.
2395   return common::visit(
2396       common::visitors{
2397           [&](const parser::StructureComponent &x) {
2398             return AssumedTypeDummy(x.component);
2399           },
2400           [&](const parser::Name &x) { return AssumedTypeDummy(x); },
2401       },
2402       object.u);
2403 }
2404 template <>
2405 const Symbol *AssumedTypeDummy<parser::AllocateObject>(
2406     const parser::AllocateObject &x) {
2407   return AssumedTypePointerOrAllocatableDummy(x);
2408 }
2409 template <>
2410 const Symbol *AssumedTypeDummy<parser::PointerObject>(
2411     const parser::PointerObject &x) {
2412   return AssumedTypePointerOrAllocatableDummy(x);
2413 }
2414 
2415 bool ExpressionAnalyzer::CheckIsValidForwardReference(
2416     const semantics::DerivedTypeSpec &dtSpec) {
2417   if (dtSpec.IsForwardReferenced()) {
2418     Say("Cannot construct value for derived type '%s' "
2419         "before it is defined"_err_en_US,
2420         dtSpec.name());
2421     return false;
2422   }
2423   return true;
2424 }
2425 
2426 MaybeExpr ExpressionAnalyzer::Analyze(const parser::FunctionReference &funcRef,
2427     std::optional<parser::StructureConstructor> *structureConstructor) {
2428   const parser::Call &call{funcRef.v};
2429   auto restorer{GetContextualMessages().SetLocation(call.source)};
2430   ArgumentAnalyzer analyzer{*this, call.source, true /* isProcedureCall */};
2431   for (const auto &arg : std::get<std::list<parser::ActualArgSpec>>(call.t)) {
2432     analyzer.Analyze(arg, false /* not subroutine call */);
2433   }
2434   if (analyzer.fatalErrors()) {
2435     return std::nullopt;
2436   }
2437   if (std::optional<CalleeAndArguments> callee{
2438           GetCalleeAndArguments(std::get<parser::ProcedureDesignator>(call.t),
2439               analyzer.GetActuals(), false /* not subroutine */,
2440               true /* might be structure constructor */)}) {
2441     if (auto *proc{std::get_if<ProcedureDesignator>(&callee->u)}) {
2442       return MakeFunctionRef(
2443           call.source, std::move(*proc), std::move(callee->arguments));
2444     }
2445     CHECK(std::holds_alternative<semantics::SymbolRef>(callee->u));
2446     const Symbol &symbol{*std::get<semantics::SymbolRef>(callee->u)};
2447     if (structureConstructor) {
2448       // Structure constructor misparsed as function reference?
2449       const auto &designator{std::get<parser::ProcedureDesignator>(call.t)};
2450       if (const auto *name{std::get_if<parser::Name>(&designator.u)}) {
2451         semantics::Scope &scope{context_.FindScope(name->source)};
2452         semantics::DerivedTypeSpec dtSpec{name->source, symbol.GetUltimate()};
2453         if (!CheckIsValidForwardReference(dtSpec)) {
2454           return std::nullopt;
2455         }
2456         const semantics::DeclTypeSpec &type{
2457             semantics::FindOrInstantiateDerivedType(scope, std::move(dtSpec))};
2458         auto &mutableRef{const_cast<parser::FunctionReference &>(funcRef)};
2459         *structureConstructor =
2460             mutableRef.ConvertToStructureConstructor(type.derivedTypeSpec());
2461         return Analyze(structureConstructor->value());
2462       }
2463     }
2464     if (!context_.HasError(symbol)) {
2465       AttachDeclaration(
2466           Say("'%s' is called like a function but is not a procedure"_err_en_US,
2467               symbol.name()),
2468           symbol);
2469       context_.SetError(symbol);
2470     }
2471   }
2472   return std::nullopt;
2473 }
2474 
2475 static bool HasAlternateReturns(const evaluate::ActualArguments &args) {
2476   for (const auto &arg : args) {
2477     if (arg && arg->isAlternateReturn()) {
2478       return true;
2479     }
2480   }
2481   return false;
2482 }
2483 
2484 void ExpressionAnalyzer::Analyze(const parser::CallStmt &callStmt) {
2485   const parser::Call &call{callStmt.v};
2486   auto restorer{GetContextualMessages().SetLocation(call.source)};
2487   ArgumentAnalyzer analyzer{*this, call.source, true /* isProcedureCall */};
2488   const auto &actualArgList{std::get<std::list<parser::ActualArgSpec>>(call.t)};
2489   for (const auto &arg : actualArgList) {
2490     analyzer.Analyze(arg, true /* is subroutine call */);
2491   }
2492   if (!analyzer.fatalErrors()) {
2493     if (std::optional<CalleeAndArguments> callee{
2494             GetCalleeAndArguments(std::get<parser::ProcedureDesignator>(call.t),
2495                 analyzer.GetActuals(), true /* subroutine */)}) {
2496       ProcedureDesignator *proc{std::get_if<ProcedureDesignator>(&callee->u)};
2497       CHECK(proc);
2498       if (CheckCall(call.source, *proc, callee->arguments)) {
2499         callStmt.typedCall.Reset(
2500             new ProcedureRef{std::move(*proc), std::move(callee->arguments),
2501                 HasAlternateReturns(callee->arguments)},
2502             ProcedureRef::Deleter);
2503         return;
2504       }
2505     }
2506     if (!context_.AnyFatalError()) {
2507       std::string buf;
2508       llvm::raw_string_ostream dump{buf};
2509       parser::DumpTree(dump, callStmt);
2510       Say("Internal error: Expression analysis failed on CALL statement: %s"_err_en_US,
2511           dump.str());
2512     }
2513   }
2514 }
2515 
2516 const Assignment *ExpressionAnalyzer::Analyze(const parser::AssignmentStmt &x) {
2517   if (!x.typedAssignment) {
2518     ArgumentAnalyzer analyzer{*this};
2519     analyzer.Analyze(std::get<parser::Variable>(x.t));
2520     analyzer.Analyze(std::get<parser::Expr>(x.t));
2521     std::optional<Assignment> assignment;
2522     if (!analyzer.fatalErrors()) {
2523       std::optional<ProcedureRef> procRef{analyzer.TryDefinedAssignment()};
2524       if (!procRef) {
2525         analyzer.CheckForNullPointer(
2526             "in a non-pointer intrinsic assignment statement");
2527       }
2528       assignment.emplace(analyzer.MoveExpr(0), analyzer.MoveExpr(1));
2529       if (procRef) {
2530         assignment->u = std::move(*procRef);
2531       }
2532     }
2533     x.typedAssignment.Reset(new GenericAssignmentWrapper{std::move(assignment)},
2534         GenericAssignmentWrapper::Deleter);
2535   }
2536   return common::GetPtrFromOptional(x.typedAssignment->v);
2537 }
2538 
2539 const Assignment *ExpressionAnalyzer::Analyze(
2540     const parser::PointerAssignmentStmt &x) {
2541   if (!x.typedAssignment) {
2542     MaybeExpr lhs{Analyze(std::get<parser::DataRef>(x.t))};
2543     MaybeExpr rhs{Analyze(std::get<parser::Expr>(x.t))};
2544     if (!lhs || !rhs) {
2545       x.typedAssignment.Reset(
2546           new GenericAssignmentWrapper{}, GenericAssignmentWrapper::Deleter);
2547     } else {
2548       Assignment assignment{std::move(*lhs), std::move(*rhs)};
2549       common::visit(
2550           common::visitors{
2551               [&](const std::list<parser::BoundsRemapping> &list) {
2552                 Assignment::BoundsRemapping bounds;
2553                 for (const auto &elem : list) {
2554                   auto lower{AsSubscript(Analyze(std::get<0>(elem.t)))};
2555                   auto upper{AsSubscript(Analyze(std::get<1>(elem.t)))};
2556                   if (lower && upper) {
2557                     bounds.emplace_back(
2558                         Fold(std::move(*lower)), Fold(std::move(*upper)));
2559                   }
2560                 }
2561                 assignment.u = std::move(bounds);
2562               },
2563               [&](const std::list<parser::BoundsSpec> &list) {
2564                 Assignment::BoundsSpec bounds;
2565                 for (const auto &bound : list) {
2566                   if (auto lower{AsSubscript(Analyze(bound.v))}) {
2567                     bounds.emplace_back(Fold(std::move(*lower)));
2568                   }
2569                 }
2570                 assignment.u = std::move(bounds);
2571               },
2572           },
2573           std::get<parser::PointerAssignmentStmt::Bounds>(x.t).u);
2574       x.typedAssignment.Reset(
2575           new GenericAssignmentWrapper{std::move(assignment)},
2576           GenericAssignmentWrapper::Deleter);
2577     }
2578   }
2579   return common::GetPtrFromOptional(x.typedAssignment->v);
2580 }
2581 
2582 static bool IsExternalCalledImplicitly(
2583     parser::CharBlock callSite, const ProcedureDesignator &proc) {
2584   if (const auto *symbol{proc.GetSymbol()}) {
2585     return symbol->has<semantics::SubprogramDetails>() &&
2586         symbol->owner().IsGlobal() &&
2587         (!symbol->scope() /*ENTRY*/ ||
2588             !symbol->scope()->sourceRange().Contains(callSite));
2589   } else {
2590     return false;
2591   }
2592 }
2593 
2594 std::optional<characteristics::Procedure> ExpressionAnalyzer::CheckCall(
2595     parser::CharBlock callSite, const ProcedureDesignator &proc,
2596     ActualArguments &arguments) {
2597   auto chars{characteristics::Procedure::Characterize(
2598       proc, context_.foldingContext())};
2599   if (chars) {
2600     bool treatExternalAsImplicit{IsExternalCalledImplicitly(callSite, proc)};
2601     if (treatExternalAsImplicit && !chars->CanBeCalledViaImplicitInterface()) {
2602       Say(callSite,
2603           "References to the procedure '%s' require an explicit interface"_err_en_US,
2604           DEREF(proc.GetSymbol()).name());
2605     }
2606     // Checks for ASSOCIATED() are done in intrinsic table processing
2607     const SpecificIntrinsic *specificIntrinsic{proc.GetSpecificIntrinsic()};
2608     bool procIsAssociated{
2609         specificIntrinsic && specificIntrinsic->name == "associated"};
2610     if (!procIsAssociated) {
2611       const Symbol *procSymbol{proc.GetSymbol()};
2612       bool procIsDummy{procSymbol && IsDummy(*procSymbol)};
2613       if (chars->functionResult &&
2614           chars->functionResult->IsAssumedLengthCharacter() &&
2615           !specificIntrinsic && !procIsDummy) {
2616         Say(callSite,
2617             "Assumed-length character function must be defined with a length to be called"_err_en_US);
2618       }
2619       semantics::CheckArguments(*chars, arguments, GetFoldingContext(),
2620           context_.FindScope(callSite), treatExternalAsImplicit,
2621           specificIntrinsic);
2622       if (procSymbol && !IsPureProcedure(*procSymbol)) {
2623         if (const semantics::Scope *
2624             pure{semantics::FindPureProcedureContaining(
2625                 context_.FindScope(callSite))}) {
2626           Say(callSite,
2627               "Procedure '%s' referenced in pure subprogram '%s' must be pure too"_err_en_US,
2628               procSymbol->name(), DEREF(pure->symbol()).name());
2629         }
2630       }
2631     }
2632   }
2633   return chars;
2634 }
2635 
2636 // Unary operations
2637 
2638 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Parentheses &x) {
2639   if (MaybeExpr operand{Analyze(x.v.value())}) {
2640     if (const semantics::Symbol * symbol{GetLastSymbol(*operand)}) {
2641       if (const semantics::Symbol * result{FindFunctionResult(*symbol)}) {
2642         if (semantics::IsProcedurePointer(*result)) {
2643           Say("A function reference that returns a procedure "
2644               "pointer may not be parenthesized"_err_en_US); // C1003
2645         }
2646       }
2647     }
2648     return Parenthesize(std::move(*operand));
2649   }
2650   return std::nullopt;
2651 }
2652 
2653 static MaybeExpr NumericUnaryHelper(ExpressionAnalyzer &context,
2654     NumericOperator opr, const parser::Expr::IntrinsicUnary &x) {
2655   ArgumentAnalyzer analyzer{context};
2656   analyzer.Analyze(x.v);
2657   if (!analyzer.fatalErrors()) {
2658     if (analyzer.IsIntrinsicNumeric(opr)) {
2659       analyzer.CheckForNullPointer();
2660       if (opr == NumericOperator::Add) {
2661         return analyzer.MoveExpr(0);
2662       } else {
2663         return Negation(context.GetContextualMessages(), analyzer.MoveExpr(0));
2664       }
2665     } else {
2666       return analyzer.TryDefinedOp(AsFortran(opr),
2667           "Operand of unary %s must be numeric; have %s"_err_en_US);
2668     }
2669   }
2670   return std::nullopt;
2671 }
2672 
2673 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::UnaryPlus &x) {
2674   return NumericUnaryHelper(*this, NumericOperator::Add, x);
2675 }
2676 
2677 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Negate &x) {
2678   if (const auto *litConst{
2679           std::get_if<parser::LiteralConstant>(&x.v.value().u)}) {
2680     if (const auto *intConst{
2681             std::get_if<parser::IntLiteralConstant>(&litConst->u)}) {
2682       return Analyze(*intConst, true);
2683     }
2684   }
2685   return NumericUnaryHelper(*this, NumericOperator::Subtract, x);
2686 }
2687 
2688 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::NOT &x) {
2689   ArgumentAnalyzer analyzer{*this};
2690   analyzer.Analyze(x.v);
2691   if (!analyzer.fatalErrors()) {
2692     if (analyzer.IsIntrinsicLogical()) {
2693       analyzer.CheckForNullPointer();
2694       return AsGenericExpr(
2695           LogicalNegation(std::get<Expr<SomeLogical>>(analyzer.MoveExpr(0).u)));
2696     } else {
2697       return analyzer.TryDefinedOp(LogicalOperator::Not,
2698           "Operand of %s must be LOGICAL; have %s"_err_en_US);
2699     }
2700   }
2701   return std::nullopt;
2702 }
2703 
2704 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::PercentLoc &x) {
2705   // Represent %LOC() exactly as if it had been a call to the LOC() extension
2706   // intrinsic function.
2707   // Use the actual source for the name of the call for error reporting.
2708   std::optional<ActualArgument> arg;
2709   if (const Symbol * assumedTypeDummy{AssumedTypeDummy(x.v.value())}) {
2710     arg = ActualArgument{ActualArgument::AssumedType{*assumedTypeDummy}};
2711   } else if (MaybeExpr argExpr{Analyze(x.v.value())}) {
2712     arg = ActualArgument{std::move(*argExpr)};
2713   } else {
2714     return std::nullopt;
2715   }
2716   parser::CharBlock at{GetContextualMessages().at()};
2717   CHECK(at.size() >= 4);
2718   parser::CharBlock loc{at.begin() + 1, 3};
2719   CHECK(loc == "loc");
2720   return MakeFunctionRef(loc, ActualArguments{std::move(*arg)});
2721 }
2722 
2723 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::DefinedUnary &x) {
2724   const auto &name{std::get<parser::DefinedOpName>(x.t).v};
2725   ArgumentAnalyzer analyzer{*this, name.source};
2726   analyzer.Analyze(std::get<1>(x.t));
2727   return analyzer.TryDefinedOp(name.source.ToString().c_str(),
2728       "No operator %s defined for %s"_err_en_US, nullptr, true);
2729 }
2730 
2731 // Binary (dyadic) operations
2732 
2733 template <template <typename> class OPR>
2734 MaybeExpr NumericBinaryHelper(ExpressionAnalyzer &context, NumericOperator opr,
2735     const parser::Expr::IntrinsicBinary &x) {
2736   ArgumentAnalyzer analyzer{context};
2737   analyzer.Analyze(std::get<0>(x.t));
2738   analyzer.Analyze(std::get<1>(x.t));
2739   if (!analyzer.fatalErrors()) {
2740     if (analyzer.IsIntrinsicNumeric(opr)) {
2741       analyzer.CheckForNullPointer();
2742       analyzer.CheckConformance();
2743       return NumericOperation<OPR>(context.GetContextualMessages(),
2744           analyzer.MoveExpr(0), analyzer.MoveExpr(1),
2745           context.GetDefaultKind(TypeCategory::Real));
2746     } else {
2747       return analyzer.TryDefinedOp(AsFortran(opr),
2748           "Operands of %s must be numeric; have %s and %s"_err_en_US);
2749     }
2750   }
2751   return std::nullopt;
2752 }
2753 
2754 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Power &x) {
2755   return NumericBinaryHelper<Power>(*this, NumericOperator::Power, x);
2756 }
2757 
2758 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Multiply &x) {
2759   return NumericBinaryHelper<Multiply>(*this, NumericOperator::Multiply, x);
2760 }
2761 
2762 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Divide &x) {
2763   return NumericBinaryHelper<Divide>(*this, NumericOperator::Divide, x);
2764 }
2765 
2766 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Add &x) {
2767   return NumericBinaryHelper<Add>(*this, NumericOperator::Add, x);
2768 }
2769 
2770 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Subtract &x) {
2771   return NumericBinaryHelper<Subtract>(*this, NumericOperator::Subtract, x);
2772 }
2773 
2774 MaybeExpr ExpressionAnalyzer::Analyze(
2775     const parser::Expr::ComplexConstructor &x) {
2776   auto re{Analyze(std::get<0>(x.t).value())};
2777   auto im{Analyze(std::get<1>(x.t).value())};
2778   if (re && im) {
2779     ConformabilityCheck(GetContextualMessages(), *re, *im);
2780   }
2781   return AsMaybeExpr(ConstructComplex(GetContextualMessages(), std::move(re),
2782       std::move(im), GetDefaultKind(TypeCategory::Real)));
2783 }
2784 
2785 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Concat &x) {
2786   ArgumentAnalyzer analyzer{*this};
2787   analyzer.Analyze(std::get<0>(x.t));
2788   analyzer.Analyze(std::get<1>(x.t));
2789   if (!analyzer.fatalErrors()) {
2790     if (analyzer.IsIntrinsicConcat()) {
2791       analyzer.CheckForNullPointer();
2792       return common::visit(
2793           [&](auto &&x, auto &&y) -> MaybeExpr {
2794             using T = ResultType<decltype(x)>;
2795             if constexpr (std::is_same_v<T, ResultType<decltype(y)>>) {
2796               return AsGenericExpr(Concat<T::kind>{std::move(x), std::move(y)});
2797             } else {
2798               DIE("different types for intrinsic concat");
2799             }
2800           },
2801           std::move(std::get<Expr<SomeCharacter>>(analyzer.MoveExpr(0).u).u),
2802           std::move(std::get<Expr<SomeCharacter>>(analyzer.MoveExpr(1).u).u));
2803     } else {
2804       return analyzer.TryDefinedOp("//",
2805           "Operands of %s must be CHARACTER with the same kind; have %s and %s"_err_en_US);
2806     }
2807   }
2808   return std::nullopt;
2809 }
2810 
2811 // The Name represents a user-defined intrinsic operator.
2812 // If the actuals match one of the specific procedures, return a function ref.
2813 // Otherwise report the error in messages.
2814 MaybeExpr ExpressionAnalyzer::AnalyzeDefinedOp(
2815     const parser::Name &name, ActualArguments &&actuals) {
2816   if (auto callee{GetCalleeAndArguments(name, std::move(actuals))}) {
2817     CHECK(std::holds_alternative<ProcedureDesignator>(callee->u));
2818     return MakeFunctionRef(name.source,
2819         std::move(std::get<ProcedureDesignator>(callee->u)),
2820         std::move(callee->arguments));
2821   } else {
2822     return std::nullopt;
2823   }
2824 }
2825 
2826 MaybeExpr RelationHelper(ExpressionAnalyzer &context, RelationalOperator opr,
2827     const parser::Expr::IntrinsicBinary &x) {
2828   ArgumentAnalyzer analyzer{context};
2829   analyzer.Analyze(std::get<0>(x.t));
2830   analyzer.Analyze(std::get<1>(x.t));
2831   if (!analyzer.fatalErrors()) {
2832     std::optional<DynamicType> leftType{analyzer.GetType(0)};
2833     std::optional<DynamicType> rightType{analyzer.GetType(1)};
2834     analyzer.ConvertBOZ(leftType, 0, rightType);
2835     analyzer.ConvertBOZ(rightType, 1, leftType);
2836     if (leftType && rightType &&
2837         analyzer.IsIntrinsicRelational(opr, *leftType, *rightType)) {
2838       analyzer.CheckForNullPointer("as a relational operand");
2839       return AsMaybeExpr(Relate(context.GetContextualMessages(), opr,
2840           analyzer.MoveExpr(0), analyzer.MoveExpr(1)));
2841     } else {
2842       return analyzer.TryDefinedOp(opr,
2843           leftType && leftType->category() == TypeCategory::Logical &&
2844                   rightType && rightType->category() == TypeCategory::Logical
2845               ? "LOGICAL operands must be compared using .EQV. or .NEQV."_err_en_US
2846               : "Operands of %s must have comparable types; have %s and %s"_err_en_US);
2847     }
2848   }
2849   return std::nullopt;
2850 }
2851 
2852 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::LT &x) {
2853   return RelationHelper(*this, RelationalOperator::LT, x);
2854 }
2855 
2856 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::LE &x) {
2857   return RelationHelper(*this, RelationalOperator::LE, x);
2858 }
2859 
2860 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::EQ &x) {
2861   return RelationHelper(*this, RelationalOperator::EQ, x);
2862 }
2863 
2864 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::NE &x) {
2865   return RelationHelper(*this, RelationalOperator::NE, x);
2866 }
2867 
2868 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::GE &x) {
2869   return RelationHelper(*this, RelationalOperator::GE, x);
2870 }
2871 
2872 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::GT &x) {
2873   return RelationHelper(*this, RelationalOperator::GT, x);
2874 }
2875 
2876 MaybeExpr LogicalBinaryHelper(ExpressionAnalyzer &context, LogicalOperator opr,
2877     const parser::Expr::IntrinsicBinary &x) {
2878   ArgumentAnalyzer analyzer{context};
2879   analyzer.Analyze(std::get<0>(x.t));
2880   analyzer.Analyze(std::get<1>(x.t));
2881   if (!analyzer.fatalErrors()) {
2882     if (analyzer.IsIntrinsicLogical()) {
2883       analyzer.CheckForNullPointer("as a logical operand");
2884       return AsGenericExpr(BinaryLogicalOperation(opr,
2885           std::get<Expr<SomeLogical>>(analyzer.MoveExpr(0).u),
2886           std::get<Expr<SomeLogical>>(analyzer.MoveExpr(1).u)));
2887     } else {
2888       return analyzer.TryDefinedOp(
2889           opr, "Operands of %s must be LOGICAL; have %s and %s"_err_en_US);
2890     }
2891   }
2892   return std::nullopt;
2893 }
2894 
2895 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::AND &x) {
2896   return LogicalBinaryHelper(*this, LogicalOperator::And, x);
2897 }
2898 
2899 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::OR &x) {
2900   return LogicalBinaryHelper(*this, LogicalOperator::Or, x);
2901 }
2902 
2903 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::EQV &x) {
2904   return LogicalBinaryHelper(*this, LogicalOperator::Eqv, x);
2905 }
2906 
2907 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::NEQV &x) {
2908   return LogicalBinaryHelper(*this, LogicalOperator::Neqv, x);
2909 }
2910 
2911 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::DefinedBinary &x) {
2912   const auto &name{std::get<parser::DefinedOpName>(x.t).v};
2913   ArgumentAnalyzer analyzer{*this, name.source};
2914   analyzer.Analyze(std::get<1>(x.t));
2915   analyzer.Analyze(std::get<2>(x.t));
2916   return analyzer.TryDefinedOp(name.source.ToString().c_str(),
2917       "No operator %s defined for %s and %s"_err_en_US, nullptr, true);
2918 }
2919 
2920 // Returns true if a parsed function reference should be converted
2921 // into an array element reference.
2922 static bool CheckFuncRefToArrayElement(semantics::SemanticsContext &context,
2923     const parser::FunctionReference &funcRef) {
2924   // Emit message if the function reference fix will end up an array element
2925   // reference with no subscripts, or subscripts on a scalar, because it will
2926   // not be possible to later distinguish in expressions between an empty
2927   // subscript list due to bad subscripts error recovery or because the
2928   // user did not put any.
2929   auto &proc{std::get<parser::ProcedureDesignator>(funcRef.v.t)};
2930   const auto *name{std::get_if<parser::Name>(&proc.u)};
2931   if (!name) {
2932     name = &std::get<parser::ProcComponentRef>(proc.u).v.thing.component;
2933   }
2934   if (!name->symbol) {
2935     return false;
2936   } else if (name->symbol->Rank() == 0) {
2937     if (const Symbol *
2938         function{
2939             semantics::IsFunctionResultWithSameNameAsFunction(*name->symbol)}) {
2940       auto &msg{context.Say(funcRef.v.source,
2941           "Recursive call to '%s' requires a distinct RESULT in its declaration"_err_en_US,
2942           name->source)};
2943       AttachDeclaration(&msg, *function);
2944       name->symbol = const_cast<Symbol *>(function);
2945     }
2946     return false;
2947   } else {
2948     if (std::get<std::list<parser::ActualArgSpec>>(funcRef.v.t).empty()) {
2949       auto &msg{context.Say(funcRef.v.source,
2950           "Reference to array '%s' with empty subscript list"_err_en_US,
2951           name->source)};
2952       if (name->symbol) {
2953         AttachDeclaration(&msg, *name->symbol);
2954       }
2955     }
2956     return true;
2957   }
2958 }
2959 
2960 // Converts, if appropriate, an original misparse of ambiguous syntax like
2961 // A(1) as a function reference into an array reference.
2962 // Misparsed structure constructors are detected elsewhere after generic
2963 // function call resolution fails.
2964 template <typename... A>
2965 static void FixMisparsedFunctionReference(
2966     semantics::SemanticsContext &context, const std::variant<A...> &constU) {
2967   // The parse tree is updated in situ when resolving an ambiguous parse.
2968   using uType = std::decay_t<decltype(constU)>;
2969   auto &u{const_cast<uType &>(constU)};
2970   if (auto *func{
2971           std::get_if<common::Indirection<parser::FunctionReference>>(&u)}) {
2972     parser::FunctionReference &funcRef{func->value()};
2973     auto &proc{std::get<parser::ProcedureDesignator>(funcRef.v.t)};
2974     if (Symbol *
2975         origSymbol{
2976             common::visit(common::visitors{
2977                               [&](parser::Name &name) { return name.symbol; },
2978                               [&](parser::ProcComponentRef &pcr) {
2979                                 return pcr.v.thing.component.symbol;
2980                               },
2981                           },
2982                 proc.u)}) {
2983       Symbol &symbol{origSymbol->GetUltimate()};
2984       if (symbol.has<semantics::ObjectEntityDetails>() ||
2985           symbol.has<semantics::AssocEntityDetails>()) {
2986         // Note that expression in AssocEntityDetails cannot be a procedure
2987         // pointer as per C1105 so this cannot be a function reference.
2988         if constexpr (common::HasMember<common::Indirection<parser::Designator>,
2989                           uType>) {
2990           if (CheckFuncRefToArrayElement(context, funcRef)) {
2991             u = common::Indirection{funcRef.ConvertToArrayElementRef()};
2992           }
2993         } else {
2994           DIE("can't fix misparsed function as array reference");
2995         }
2996       }
2997     }
2998   }
2999 }
3000 
3001 // Common handling of parse tree node types that retain the
3002 // representation of the analyzed expression.
3003 template <typename PARSED>
3004 MaybeExpr ExpressionAnalyzer::ExprOrVariable(
3005     const PARSED &x, parser::CharBlock source) {
3006   if (useSavedTypedExprs_ && x.typedExpr) {
3007     return x.typedExpr->v;
3008   }
3009   auto restorer{GetContextualMessages().SetLocation(source)};
3010   if constexpr (std::is_same_v<PARSED, parser::Expr> ||
3011       std::is_same_v<PARSED, parser::Variable>) {
3012     FixMisparsedFunctionReference(context_, x.u);
3013   }
3014   if (AssumedTypeDummy(x)) { // C710
3015     Say("TYPE(*) dummy argument may only be used as an actual argument"_err_en_US);
3016     ResetExpr(x);
3017     return std::nullopt;
3018   }
3019   MaybeExpr result;
3020   if constexpr (common::HasMember<parser::StructureConstructor,
3021                     std::decay_t<decltype(x.u)>> &&
3022       common::HasMember<common::Indirection<parser::FunctionReference>,
3023           std::decay_t<decltype(x.u)>>) {
3024     if (const auto *funcRef{
3025             std::get_if<common::Indirection<parser::FunctionReference>>(
3026                 &x.u)}) {
3027       // Function references in Exprs might turn out to be misparsed structure
3028       // constructors; we have to try generic procedure resolution
3029       // first to be sure.
3030       std::optional<parser::StructureConstructor> ctor;
3031       result = Analyze(funcRef->value(), &ctor);
3032       if (result && ctor) {
3033         // A misparsed function reference is really a structure
3034         // constructor.  Repair the parse tree in situ.
3035         const_cast<PARSED &>(x).u = std::move(*ctor);
3036       }
3037     } else {
3038       result = Analyze(x.u);
3039     }
3040   } else {
3041     result = Analyze(x.u);
3042   }
3043   if (result) {
3044     SetExpr(x, Fold(std::move(*result)));
3045     return x.typedExpr->v;
3046   } else {
3047     ResetExpr(x);
3048     if (!context_.AnyFatalError()) {
3049       std::string buf;
3050       llvm::raw_string_ostream dump{buf};
3051       parser::DumpTree(dump, x);
3052       Say("Internal error: Expression analysis failed on: %s"_err_en_US,
3053           dump.str());
3054     }
3055     return std::nullopt;
3056   }
3057 }
3058 
3059 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr &expr) {
3060   return ExprOrVariable(expr, expr.source);
3061 }
3062 
3063 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Variable &variable) {
3064   return ExprOrVariable(variable, variable.GetSource());
3065 }
3066 
3067 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Selector &selector) {
3068   if (const auto *var{std::get_if<parser::Variable>(&selector.u)}) {
3069     if (!useSavedTypedExprs_ || !var->typedExpr) {
3070       parser::CharBlock source{var->GetSource()};
3071       auto restorer{GetContextualMessages().SetLocation(source)};
3072       FixMisparsedFunctionReference(context_, var->u);
3073       if (const auto *funcRef{
3074               std::get_if<common::Indirection<parser::FunctionReference>>(
3075                   &var->u)}) {
3076         // A Selector that parsed as a Variable might turn out during analysis
3077         // to actually be a structure constructor.  In that case, repair the
3078         // Variable parse tree node into an Expr
3079         std::optional<parser::StructureConstructor> ctor;
3080         if (MaybeExpr result{Analyze(funcRef->value(), &ctor)}) {
3081           if (ctor) {
3082             auto &writable{const_cast<parser::Selector &>(selector)};
3083             writable.u = parser::Expr{std::move(*ctor)};
3084             auto &expr{std::get<parser::Expr>(writable.u)};
3085             expr.source = source;
3086             SetExpr(expr, Fold(std::move(*result)));
3087             return expr.typedExpr->v;
3088           } else {
3089             SetExpr(*var, Fold(std::move(*result)));
3090             return var->typedExpr->v;
3091           }
3092         } else {
3093           ResetExpr(*var);
3094           if (context_.AnyFatalError()) {
3095             return std::nullopt;
3096           }
3097         }
3098       }
3099     }
3100   }
3101   // Not a Variable -> FunctionReference; handle normally as Variable or Expr
3102   return Analyze(selector.u);
3103 }
3104 
3105 MaybeExpr ExpressionAnalyzer::Analyze(const parser::DataStmtConstant &x) {
3106   auto restorer{common::ScopedSet(inDataStmtConstant_, true)};
3107   return ExprOrVariable(x, x.source);
3108 }
3109 
3110 MaybeExpr ExpressionAnalyzer::Analyze(const parser::AllocateObject &x) {
3111   return ExprOrVariable(x, parser::FindSourceLocation(x));
3112 }
3113 
3114 MaybeExpr ExpressionAnalyzer::Analyze(const parser::PointerObject &x) {
3115   return ExprOrVariable(x, parser::FindSourceLocation(x));
3116 }
3117 
3118 Expr<SubscriptInteger> ExpressionAnalyzer::AnalyzeKindSelector(
3119     TypeCategory category,
3120     const std::optional<parser::KindSelector> &selector) {
3121   int defaultKind{GetDefaultKind(category)};
3122   if (!selector) {
3123     return Expr<SubscriptInteger>{defaultKind};
3124   }
3125   return common::visit(
3126       common::visitors{
3127           [&](const parser::ScalarIntConstantExpr &x) {
3128             if (MaybeExpr kind{Analyze(x)}) {
3129               if (std::optional<std::int64_t> code{ToInt64(*kind)}) {
3130                 if (CheckIntrinsicKind(category, *code)) {
3131                   return Expr<SubscriptInteger>{*code};
3132                 }
3133               } else if (auto *intExpr{UnwrapExpr<Expr<SomeInteger>>(*kind)}) {
3134                 return ConvertToType<SubscriptInteger>(std::move(*intExpr));
3135               }
3136             }
3137             return Expr<SubscriptInteger>{defaultKind};
3138           },
3139           [&](const parser::KindSelector::StarSize &x) {
3140             std::intmax_t size = x.v;
3141             if (!CheckIntrinsicSize(category, size)) {
3142               size = defaultKind;
3143             } else if (category == TypeCategory::Complex) {
3144               size /= 2;
3145             }
3146             return Expr<SubscriptInteger>{size};
3147           },
3148       },
3149       selector->u);
3150 }
3151 
3152 int ExpressionAnalyzer::GetDefaultKind(common::TypeCategory category) {
3153   return context_.GetDefaultKind(category);
3154 }
3155 
3156 DynamicType ExpressionAnalyzer::GetDefaultKindOfType(
3157     common::TypeCategory category) {
3158   return {category, GetDefaultKind(category)};
3159 }
3160 
3161 bool ExpressionAnalyzer::CheckIntrinsicKind(
3162     TypeCategory category, std::int64_t kind) {
3163   if (foldingContext_.targetCharacteristics().IsTypeEnabled(
3164           category, kind)) { // C712, C714, C715, C727
3165     return true;
3166   } else if (foldingContext_.targetCharacteristics().CanSupportType(
3167                  category, kind)) {
3168     Say("%s(KIND=%jd) is not an enabled type for this targe"_warn_en_US,
3169         ToUpperCase(EnumToString(category)), kind);
3170     return true;
3171   } else {
3172     Say("%s(KIND=%jd) is not a supported type"_err_en_US,
3173         ToUpperCase(EnumToString(category)), kind);
3174     return false;
3175   }
3176 }
3177 
3178 bool ExpressionAnalyzer::CheckIntrinsicSize(
3179     TypeCategory category, std::int64_t size) {
3180   std::int64_t kind{size};
3181   if (category == TypeCategory::Complex) {
3182     // COMPLEX*16 == COMPLEX(KIND=8)
3183     if (size % 2 == 0) {
3184       kind = size / 2;
3185     } else {
3186       Say("COMPLEX*%jd is not a supported type"_err_en_US, size);
3187       return false;
3188     }
3189   }
3190   if (foldingContext_.targetCharacteristics().IsTypeEnabled(
3191           category, kind)) { // C712, C714, C715, C727
3192     return true;
3193   } else if (foldingContext_.targetCharacteristics().CanSupportType(
3194                  category, kind)) {
3195     Say("%s*%jd is not an enabled type for this target"_warn_en_US,
3196         ToUpperCase(EnumToString(category)), size);
3197     return true;
3198   } else {
3199     Say("%s*%jd is not a supported type"_err_en_US,
3200         ToUpperCase(EnumToString(category)), size);
3201     return false;
3202   }
3203 }
3204 
3205 bool ExpressionAnalyzer::AddImpliedDo(parser::CharBlock name, int kind) {
3206   return impliedDos_.insert(std::make_pair(name, kind)).second;
3207 }
3208 
3209 void ExpressionAnalyzer::RemoveImpliedDo(parser::CharBlock name) {
3210   auto iter{impliedDos_.find(name)};
3211   if (iter != impliedDos_.end()) {
3212     impliedDos_.erase(iter);
3213   }
3214 }
3215 
3216 std::optional<int> ExpressionAnalyzer::IsImpliedDo(
3217     parser::CharBlock name) const {
3218   auto iter{impliedDos_.find(name)};
3219   if (iter != impliedDos_.cend()) {
3220     return {iter->second};
3221   } else {
3222     return std::nullopt;
3223   }
3224 }
3225 
3226 bool ExpressionAnalyzer::EnforceTypeConstraint(parser::CharBlock at,
3227     const MaybeExpr &result, TypeCategory category, bool defaultKind) {
3228   if (result) {
3229     if (auto type{result->GetType()}) {
3230       if (type->category() != category) { // C885
3231         Say(at, "Must have %s type, but is %s"_err_en_US,
3232             ToUpperCase(EnumToString(category)),
3233             ToUpperCase(type->AsFortran()));
3234         return false;
3235       } else if (defaultKind) {
3236         int kind{context_.GetDefaultKind(category)};
3237         if (type->kind() != kind) {
3238           Say(at, "Must have default kind(%d) of %s type, but is %s"_err_en_US,
3239               kind, ToUpperCase(EnumToString(category)),
3240               ToUpperCase(type->AsFortran()));
3241           return false;
3242         }
3243       }
3244     } else {
3245       Say(at, "Must have %s type, but is typeless"_err_en_US,
3246           ToUpperCase(EnumToString(category)));
3247       return false;
3248     }
3249   }
3250   return true;
3251 }
3252 
3253 MaybeExpr ExpressionAnalyzer::MakeFunctionRef(parser::CharBlock callSite,
3254     ProcedureDesignator &&proc, ActualArguments &&arguments) {
3255   if (const auto *intrinsic{std::get_if<SpecificIntrinsic>(&proc.u)}) {
3256     if (intrinsic->characteristics.value().attrs.test(
3257             characteristics::Procedure::Attr::NullPointer) &&
3258         arguments.empty()) {
3259       return Expr<SomeType>{NullPointer{}};
3260     }
3261   }
3262   if (const Symbol * symbol{proc.GetSymbol()}) {
3263     if (!ResolveForward(*symbol)) {
3264       return std::nullopt;
3265     }
3266   }
3267   if (auto chars{CheckCall(callSite, proc, arguments)}) {
3268     if (chars->functionResult) {
3269       const auto &result{*chars->functionResult};
3270       if (result.IsProcedurePointer()) {
3271         return Expr<SomeType>{
3272             ProcedureRef{std::move(proc), std::move(arguments)}};
3273       } else {
3274         // Not a procedure pointer, so type and shape are known.
3275         return TypedWrapper<FunctionRef, ProcedureRef>(
3276             DEREF(result.GetTypeAndShape()).type(),
3277             ProcedureRef{std::move(proc), std::move(arguments)});
3278       }
3279     } else {
3280       Say("Function result characteristics are not known"_err_en_US);
3281     }
3282   }
3283   return std::nullopt;
3284 }
3285 
3286 MaybeExpr ExpressionAnalyzer::MakeFunctionRef(
3287     parser::CharBlock intrinsic, ActualArguments &&arguments) {
3288   if (std::optional<SpecificCall> specificCall{
3289           context_.intrinsics().Probe(CallCharacteristics{intrinsic.ToString()},
3290               arguments, GetFoldingContext())}) {
3291     return MakeFunctionRef(intrinsic,
3292         ProcedureDesignator{std::move(specificCall->specificIntrinsic)},
3293         std::move(specificCall->arguments));
3294   } else {
3295     return std::nullopt;
3296   }
3297 }
3298 
3299 void ArgumentAnalyzer::Analyze(const parser::Variable &x) {
3300   source_.ExtendToCover(x.GetSource());
3301   if (MaybeExpr expr{context_.Analyze(x)}) {
3302     if (!IsConstantExpr(*expr)) {
3303       actuals_.emplace_back(std::move(*expr));
3304       SetArgSourceLocation(actuals_.back(), x.GetSource());
3305       return;
3306     }
3307     const Symbol *symbol{GetLastSymbol(*expr)};
3308     if (!symbol) {
3309       context_.SayAt(x, "Assignment to constant '%s' is not allowed"_err_en_US,
3310           x.GetSource());
3311     } else if (auto *subp{symbol->detailsIf<semantics::SubprogramDetails>()}) {
3312       auto *msg{context_.SayAt(x,
3313           "Assignment to subprogram '%s' is not allowed"_err_en_US,
3314           symbol->name())};
3315       if (subp->isFunction()) {
3316         const auto &result{subp->result().name()};
3317         msg->Attach(result, "Function result is '%s'"_en_US, result);
3318       }
3319     } else {
3320       context_.SayAt(x, "Assignment to constant '%s' is not allowed"_err_en_US,
3321           symbol->name());
3322     }
3323   }
3324   fatalErrors_ = true;
3325 }
3326 
3327 void ArgumentAnalyzer::Analyze(
3328     const parser::ActualArgSpec &arg, bool isSubroutine) {
3329   // TODO: Actual arguments that are procedures and procedure pointers need to
3330   // be detected and represented (they're not expressions).
3331   // TODO: C1534: Don't allow a "restricted" specific intrinsic to be passed.
3332   std::optional<ActualArgument> actual;
3333   common::visit(
3334       common::visitors{
3335           [&](const common::Indirection<parser::Expr> &x) {
3336             actual = AnalyzeExpr(x.value());
3337             SetArgSourceLocation(actual, x.value().source);
3338           },
3339           [&](const parser::AltReturnSpec &label) {
3340             if (!isSubroutine) {
3341               context_.Say("alternate return specification may not appear on"
3342                            " function reference"_err_en_US);
3343             }
3344             actual = ActualArgument(label.v);
3345           },
3346           [&](const parser::ActualArg::PercentRef &) {
3347             context_.Say("%REF() intrinsic for arguments"_todo_en_US);
3348           },
3349           [&](const parser::ActualArg::PercentVal &) {
3350             context_.Say("%VAL() intrinsic for arguments"_todo_en_US);
3351           },
3352       },
3353       std::get<parser::ActualArg>(arg.t).u);
3354   if (actual) {
3355     if (const auto &argKW{std::get<std::optional<parser::Keyword>>(arg.t)}) {
3356       actual->set_keyword(argKW->v.source);
3357     }
3358     actuals_.emplace_back(std::move(*actual));
3359   } else {
3360     fatalErrors_ = true;
3361   }
3362 }
3363 
3364 bool ArgumentAnalyzer::IsIntrinsicRelational(RelationalOperator opr,
3365     const DynamicType &leftType, const DynamicType &rightType) const {
3366   CHECK(actuals_.size() == 2);
3367   return semantics::IsIntrinsicRelational(
3368       opr, leftType, GetRank(0), rightType, GetRank(1));
3369 }
3370 
3371 bool ArgumentAnalyzer::IsIntrinsicNumeric(NumericOperator opr) const {
3372   std::optional<DynamicType> leftType{GetType(0)};
3373   if (actuals_.size() == 1) {
3374     if (IsBOZLiteral(0)) {
3375       return opr == NumericOperator::Add; // unary '+'
3376     } else {
3377       return leftType && semantics::IsIntrinsicNumeric(*leftType);
3378     }
3379   } else {
3380     std::optional<DynamicType> rightType{GetType(1)};
3381     if (IsBOZLiteral(0) && rightType) { // BOZ opr Integer/Real
3382       auto cat1{rightType->category()};
3383       return cat1 == TypeCategory::Integer || cat1 == TypeCategory::Real;
3384     } else if (IsBOZLiteral(1) && leftType) { // Integer/Real opr BOZ
3385       auto cat0{leftType->category()};
3386       return cat0 == TypeCategory::Integer || cat0 == TypeCategory::Real;
3387     } else {
3388       return leftType && rightType &&
3389           semantics::IsIntrinsicNumeric(
3390               *leftType, GetRank(0), *rightType, GetRank(1));
3391     }
3392   }
3393 }
3394 
3395 bool ArgumentAnalyzer::IsIntrinsicLogical() const {
3396   if (std::optional<DynamicType> leftType{GetType(0)}) {
3397     if (actuals_.size() == 1) {
3398       return semantics::IsIntrinsicLogical(*leftType);
3399     } else if (std::optional<DynamicType> rightType{GetType(1)}) {
3400       return semantics::IsIntrinsicLogical(
3401           *leftType, GetRank(0), *rightType, GetRank(1));
3402     }
3403   }
3404   return false;
3405 }
3406 
3407 bool ArgumentAnalyzer::IsIntrinsicConcat() const {
3408   if (std::optional<DynamicType> leftType{GetType(0)}) {
3409     if (std::optional<DynamicType> rightType{GetType(1)}) {
3410       return semantics::IsIntrinsicConcat(
3411           *leftType, GetRank(0), *rightType, GetRank(1));
3412     }
3413   }
3414   return false;
3415 }
3416 
3417 bool ArgumentAnalyzer::CheckConformance() {
3418   if (actuals_.size() == 2) {
3419     const auto *lhs{actuals_.at(0).value().UnwrapExpr()};
3420     const auto *rhs{actuals_.at(1).value().UnwrapExpr()};
3421     if (lhs && rhs) {
3422       auto &foldingContext{context_.GetFoldingContext()};
3423       auto lhShape{GetShape(foldingContext, *lhs)};
3424       auto rhShape{GetShape(foldingContext, *rhs)};
3425       if (lhShape && rhShape) {
3426         if (!evaluate::CheckConformance(foldingContext.messages(), *lhShape,
3427                 *rhShape, CheckConformanceFlags::EitherScalarExpandable,
3428                 "left operand", "right operand")
3429                  .value_or(false /*fail when conformance is not known now*/)) {
3430           fatalErrors_ = true;
3431           return false;
3432         }
3433       }
3434     }
3435   }
3436   return true; // no proven problem
3437 }
3438 
3439 bool ArgumentAnalyzer::CheckForNullPointer(const char *where) {
3440   for (const std::optional<ActualArgument> &arg : actuals_) {
3441     if (arg) {
3442       if (const Expr<SomeType> *expr{arg->UnwrapExpr()}) {
3443         if (IsNullPointer(*expr)) {
3444           context_.Say(
3445               source_, "A NULL() pointer is not allowed %s"_err_en_US, where);
3446           fatalErrors_ = true;
3447           return false;
3448         }
3449       }
3450     }
3451   }
3452   return true;
3453 }
3454 
3455 MaybeExpr ArgumentAnalyzer::TryDefinedOp(const char *opr,
3456     parser::MessageFixedText error, const Symbol **definedOpSymbolPtr,
3457     bool isUserOp) {
3458   if (AnyUntypedOrMissingOperand()) {
3459     context_.Say(error, ToUpperCase(opr), TypeAsFortran(0), TypeAsFortran(1));
3460     return std::nullopt;
3461   }
3462   const Symbol *localDefinedOpSymbolPtr{nullptr};
3463   if (!definedOpSymbolPtr) {
3464     definedOpSymbolPtr = &localDefinedOpSymbolPtr;
3465   }
3466   {
3467     auto restorer{context_.GetContextualMessages().DiscardMessages()};
3468     std::string oprNameString{
3469         isUserOp ? std::string{opr} : "operator("s + opr + ')'};
3470     parser::CharBlock oprName{oprNameString};
3471     const auto &scope{context_.context().FindScope(source_)};
3472     if (Symbol * symbol{scope.FindSymbol(oprName)}) {
3473       *definedOpSymbolPtr = symbol;
3474       parser::Name name{symbol->name(), symbol};
3475       if (auto result{context_.AnalyzeDefinedOp(name, GetActuals())}) {
3476         return result;
3477       }
3478     }
3479     for (std::size_t passIndex{0}; passIndex < actuals_.size(); ++passIndex) {
3480       if (const Symbol *
3481           symbol{FindBoundOp(oprName, passIndex, *definedOpSymbolPtr)}) {
3482         if (MaybeExpr result{TryBoundOp(*symbol, passIndex)}) {
3483           return result;
3484         }
3485       }
3486     }
3487   }
3488   if (*definedOpSymbolPtr) {
3489     SayNoMatch(ToUpperCase((*definedOpSymbolPtr)->name().ToString()));
3490   } else if (actuals_.size() == 1 || AreConformable()) {
3491     if (CheckForNullPointer()) {
3492       context_.Say(error, ToUpperCase(opr), TypeAsFortran(0), TypeAsFortran(1));
3493     }
3494   } else {
3495     context_.Say(
3496         "Operands of %s are not conformable; have rank %d and rank %d"_err_en_US,
3497         ToUpperCase(opr), actuals_[0]->Rank(), actuals_[1]->Rank());
3498   }
3499   return std::nullopt;
3500 }
3501 
3502 MaybeExpr ArgumentAnalyzer::TryDefinedOp(
3503     std::vector<const char *> oprs, parser::MessageFixedText error) {
3504   const Symbol *definedOpSymbolPtr{nullptr};
3505   for (std::size_t i{1}; i < oprs.size(); ++i) {
3506     auto restorer{context_.GetContextualMessages().DiscardMessages()};
3507     if (auto result{TryDefinedOp(oprs[i], error, &definedOpSymbolPtr)}) {
3508       return result;
3509     }
3510   }
3511   return TryDefinedOp(oprs[0], error, &definedOpSymbolPtr);
3512 }
3513 
3514 MaybeExpr ArgumentAnalyzer::TryBoundOp(const Symbol &symbol, int passIndex) {
3515   ActualArguments localActuals{actuals_};
3516   const Symbol *proc{GetBindingResolution(GetType(passIndex), symbol)};
3517   if (!proc) {
3518     proc = &symbol;
3519     localActuals.at(passIndex).value().set_isPassedObject();
3520   }
3521   CheckConformance();
3522   return context_.MakeFunctionRef(
3523       source_, ProcedureDesignator{*proc}, std::move(localActuals));
3524 }
3525 
3526 std::optional<ProcedureRef> ArgumentAnalyzer::TryDefinedAssignment() {
3527   using semantics::Tristate;
3528   const Expr<SomeType> &lhs{GetExpr(0)};
3529   const Expr<SomeType> &rhs{GetExpr(1)};
3530   std::optional<DynamicType> lhsType{lhs.GetType()};
3531   std::optional<DynamicType> rhsType{rhs.GetType()};
3532   int lhsRank{lhs.Rank()};
3533   int rhsRank{rhs.Rank()};
3534   Tristate isDefined{
3535       semantics::IsDefinedAssignment(lhsType, lhsRank, rhsType, rhsRank)};
3536   if (isDefined == Tristate::No) {
3537     if (lhsType && rhsType) {
3538       AddAssignmentConversion(*lhsType, *rhsType);
3539     }
3540     return std::nullopt; // user-defined assignment not allowed for these args
3541   }
3542   auto restorer{context_.GetContextualMessages().SetLocation(source_)};
3543   if (std::optional<ProcedureRef> procRef{GetDefinedAssignmentProc()}) {
3544     if (context_.inWhereBody() && !procRef->proc().IsElemental()) { // C1032
3545       context_.Say(
3546           "Defined assignment in WHERE must be elemental, but '%s' is not"_err_en_US,
3547           DEREF(procRef->proc().GetSymbol()).name());
3548     }
3549     context_.CheckCall(source_, procRef->proc(), procRef->arguments());
3550     return std::move(*procRef);
3551   }
3552   if (isDefined == Tristate::Yes) {
3553     if (!lhsType || !rhsType || (lhsRank != rhsRank && rhsRank != 0) ||
3554         !OkLogicalIntegerAssignment(lhsType->category(), rhsType->category())) {
3555       SayNoMatch("ASSIGNMENT(=)", true);
3556     }
3557   }
3558   return std::nullopt;
3559 }
3560 
3561 bool ArgumentAnalyzer::OkLogicalIntegerAssignment(
3562     TypeCategory lhs, TypeCategory rhs) {
3563   if (!context_.context().languageFeatures().IsEnabled(
3564           common::LanguageFeature::LogicalIntegerAssignment)) {
3565     return false;
3566   }
3567   std::optional<parser::MessageFixedText> msg;
3568   if (lhs == TypeCategory::Integer && rhs == TypeCategory::Logical) {
3569     // allow assignment to LOGICAL from INTEGER as a legacy extension
3570     msg = "assignment of LOGICAL to INTEGER"_port_en_US;
3571   } else if (lhs == TypeCategory::Logical && rhs == TypeCategory::Integer) {
3572     // ... and assignment to LOGICAL from INTEGER
3573     msg = "assignment of INTEGER to LOGICAL"_port_en_US;
3574   } else {
3575     return false;
3576   }
3577   if (context_.context().languageFeatures().ShouldWarn(
3578           common::LanguageFeature::LogicalIntegerAssignment)) {
3579     context_.Say(std::move(*msg));
3580   }
3581   return true;
3582 }
3583 
3584 std::optional<ProcedureRef> ArgumentAnalyzer::GetDefinedAssignmentProc() {
3585   auto restorer{context_.GetContextualMessages().DiscardMessages()};
3586   std::string oprNameString{"assignment(=)"};
3587   parser::CharBlock oprName{oprNameString};
3588   const Symbol *proc{nullptr};
3589   const auto &scope{context_.context().FindScope(source_)};
3590   if (const Symbol * symbol{scope.FindSymbol(oprName)}) {
3591     ExpressionAnalyzer::AdjustActuals noAdjustment;
3592     auto pair{context_.ResolveGeneric(*symbol, actuals_, noAdjustment, true)};
3593     if (pair.first) {
3594       proc = pair.first;
3595     } else {
3596       context_.EmitGenericResolutionError(*symbol, pair.second);
3597     }
3598   }
3599   int passedObjectIndex{-1};
3600   const Symbol *definedOpSymbol{nullptr};
3601   for (std::size_t i{0}; i < actuals_.size(); ++i) {
3602     if (const Symbol * specific{FindBoundOp(oprName, i, definedOpSymbol)}) {
3603       if (const Symbol *
3604           resolution{GetBindingResolution(GetType(i), *specific)}) {
3605         proc = resolution;
3606       } else {
3607         proc = specific;
3608         passedObjectIndex = i;
3609       }
3610     }
3611   }
3612   if (!proc) {
3613     return std::nullopt;
3614   }
3615   ActualArguments actualsCopy{actuals_};
3616   if (passedObjectIndex >= 0) {
3617     actualsCopy[passedObjectIndex]->set_isPassedObject();
3618   }
3619   return ProcedureRef{ProcedureDesignator{*proc}, std::move(actualsCopy)};
3620 }
3621 
3622 void ArgumentAnalyzer::Dump(llvm::raw_ostream &os) {
3623   os << "source_: " << source_.ToString() << " fatalErrors_ = " << fatalErrors_
3624      << '\n';
3625   for (const auto &actual : actuals_) {
3626     if (!actual.has_value()) {
3627       os << "- error\n";
3628     } else if (const Symbol * symbol{actual->GetAssumedTypeDummy()}) {
3629       os << "- assumed type: " << symbol->name().ToString() << '\n';
3630     } else if (const Expr<SomeType> *expr{actual->UnwrapExpr()}) {
3631       expr->AsFortran(os << "- expr: ") << '\n';
3632     } else {
3633       DIE("bad ActualArgument");
3634     }
3635   }
3636 }
3637 
3638 std::optional<ActualArgument> ArgumentAnalyzer::AnalyzeExpr(
3639     const parser::Expr &expr) {
3640   source_.ExtendToCover(expr.source);
3641   if (const Symbol * assumedTypeDummy{AssumedTypeDummy(expr)}) {
3642     expr.typedExpr.Reset(new GenericExprWrapper{}, GenericExprWrapper::Deleter);
3643     if (isProcedureCall_) {
3644       ActualArgument arg{ActualArgument::AssumedType{*assumedTypeDummy}};
3645       SetArgSourceLocation(arg, expr.source);
3646       return std::move(arg);
3647     }
3648     context_.SayAt(expr.source,
3649         "TYPE(*) dummy argument may only be used as an actual argument"_err_en_US);
3650   } else if (MaybeExpr argExpr{AnalyzeExprOrWholeAssumedSizeArray(expr)}) {
3651     if (isProcedureCall_ || !IsProcedure(*argExpr)) {
3652       ActualArgument arg{std::move(*argExpr)};
3653       SetArgSourceLocation(arg, expr.source);
3654       return std::move(arg);
3655     }
3656     context_.SayAt(expr.source,
3657         IsFunction(*argExpr) ? "Function call must have argument list"_err_en_US
3658                              : "Subroutine name is not allowed here"_err_en_US);
3659   }
3660   return std::nullopt;
3661 }
3662 
3663 MaybeExpr ArgumentAnalyzer::AnalyzeExprOrWholeAssumedSizeArray(
3664     const parser::Expr &expr) {
3665   // If an expression's parse tree is a whole assumed-size array:
3666   //   Expr -> Designator -> DataRef -> Name
3667   // treat it as a special case for argument passing and bypass
3668   // the C1002/C1014 constraint checking in expression semantics.
3669   if (const auto *name{parser::Unwrap<parser::Name>(expr)}) {
3670     if (name->symbol && semantics::IsAssumedSizeArray(*name->symbol)) {
3671       auto restorer{context_.AllowWholeAssumedSizeArray()};
3672       return context_.Analyze(expr);
3673     }
3674   }
3675   return context_.Analyze(expr);
3676 }
3677 
3678 bool ArgumentAnalyzer::AreConformable() const {
3679   CHECK(actuals_.size() == 2);
3680   return actuals_[0] && actuals_[1] &&
3681       evaluate::AreConformable(*actuals_[0], *actuals_[1]);
3682 }
3683 
3684 // Look for a type-bound operator in the type of arg number passIndex.
3685 const Symbol *ArgumentAnalyzer::FindBoundOp(
3686     parser::CharBlock oprName, int passIndex, const Symbol *&definedOp) {
3687   const auto *type{GetDerivedTypeSpec(GetType(passIndex))};
3688   if (!type || !type->scope()) {
3689     return nullptr;
3690   }
3691   const Symbol *symbol{type->scope()->FindComponent(oprName)};
3692   if (!symbol) {
3693     return nullptr;
3694   }
3695   definedOp = symbol;
3696   ExpressionAnalyzer::AdjustActuals adjustment{
3697       [&](const Symbol &proc, ActualArguments &) {
3698         return passIndex == GetPassIndex(proc);
3699       }};
3700   auto pair{context_.ResolveGeneric(*symbol, actuals_, adjustment, false)};
3701   if (!pair.first) {
3702     context_.EmitGenericResolutionError(*symbol, pair.second);
3703   }
3704   return pair.first;
3705 }
3706 
3707 // If there is an implicit conversion between intrinsic types, make it explicit
3708 void ArgumentAnalyzer::AddAssignmentConversion(
3709     const DynamicType &lhsType, const DynamicType &rhsType) {
3710   if (lhsType.category() == rhsType.category() &&
3711       (lhsType.category() == TypeCategory::Derived ||
3712           lhsType.kind() == rhsType.kind())) {
3713     // no conversion necessary
3714   } else if (auto rhsExpr{evaluate::ConvertToType(lhsType, MoveExpr(1))}) {
3715     std::optional<parser::CharBlock> source;
3716     if (actuals_[1]) {
3717       source = actuals_[1]->sourceLocation();
3718     }
3719     actuals_[1] = ActualArgument{*rhsExpr};
3720     SetArgSourceLocation(actuals_[1], source);
3721   } else {
3722     actuals_[1] = std::nullopt;
3723   }
3724 }
3725 
3726 std::optional<DynamicType> ArgumentAnalyzer::GetType(std::size_t i) const {
3727   return i < actuals_.size() ? actuals_[i].value().GetType() : std::nullopt;
3728 }
3729 int ArgumentAnalyzer::GetRank(std::size_t i) const {
3730   return i < actuals_.size() ? actuals_[i].value().Rank() : 0;
3731 }
3732 
3733 // If the argument at index i is a BOZ literal, convert its type to match the
3734 // otherType.  If it's REAL convert to REAL, otherwise convert to INTEGER.
3735 // Note that IBM supports comparing BOZ literals to CHARACTER operands.  That
3736 // is not currently supported.
3737 void ArgumentAnalyzer::ConvertBOZ(std::optional<DynamicType> &thisType,
3738     std::size_t i, std::optional<DynamicType> otherType) {
3739   if (IsBOZLiteral(i)) {
3740     Expr<SomeType> &&argExpr{MoveExpr(i)};
3741     auto *boz{std::get_if<BOZLiteralConstant>(&argExpr.u)};
3742     if (otherType && otherType->category() == TypeCategory::Real) {
3743       int kind{context_.context().GetDefaultKind(TypeCategory::Real)};
3744       MaybeExpr realExpr{
3745           ConvertToKind<TypeCategory::Real>(kind, std::move(*boz))};
3746       actuals_[i] = std::move(*realExpr);
3747       thisType.emplace(TypeCategory::Real, kind);
3748     } else {
3749       int kind{context_.context().GetDefaultKind(TypeCategory::Integer)};
3750       MaybeExpr intExpr{
3751           ConvertToKind<TypeCategory::Integer>(kind, std::move(*boz))};
3752       actuals_[i] = std::move(*intExpr);
3753       thisType.emplace(TypeCategory::Integer, kind);
3754     }
3755   }
3756 }
3757 
3758 // Report error resolving opr when there is a user-defined one available
3759 void ArgumentAnalyzer::SayNoMatch(const std::string &opr, bool isAssignment) {
3760   std::string type0{TypeAsFortran(0)};
3761   auto rank0{actuals_[0]->Rank()};
3762   if (actuals_.size() == 1) {
3763     if (rank0 > 0) {
3764       context_.Say("No intrinsic or user-defined %s matches "
3765                    "rank %d array of %s"_err_en_US,
3766           opr, rank0, type0);
3767     } else {
3768       context_.Say("No intrinsic or user-defined %s matches "
3769                    "operand type %s"_err_en_US,
3770           opr, type0);
3771     }
3772   } else {
3773     std::string type1{TypeAsFortran(1)};
3774     auto rank1{actuals_[1]->Rank()};
3775     if (rank0 > 0 && rank1 > 0 && rank0 != rank1) {
3776       context_.Say("No intrinsic or user-defined %s matches "
3777                    "rank %d array of %s and rank %d array of %s"_err_en_US,
3778           opr, rank0, type0, rank1, type1);
3779     } else if (isAssignment && rank0 != rank1) {
3780       if (rank0 == 0) {
3781         context_.Say("No intrinsic or user-defined %s matches "
3782                      "scalar %s and rank %d array of %s"_err_en_US,
3783             opr, type0, rank1, type1);
3784       } else {
3785         context_.Say("No intrinsic or user-defined %s matches "
3786                      "rank %d array of %s and scalar %s"_err_en_US,
3787             opr, rank0, type0, type1);
3788       }
3789     } else {
3790       context_.Say("No intrinsic or user-defined %s matches "
3791                    "operand types %s and %s"_err_en_US,
3792           opr, type0, type1);
3793     }
3794   }
3795 }
3796 
3797 std::string ArgumentAnalyzer::TypeAsFortran(std::size_t i) {
3798   if (i >= actuals_.size() || !actuals_[i]) {
3799     return "missing argument";
3800   } else if (std::optional<DynamicType> type{GetType(i)}) {
3801     return type->IsAssumedType()         ? "TYPE(*)"s
3802         : type->IsUnlimitedPolymorphic() ? "CLASS(*)"s
3803         : type->IsPolymorphic()          ? "CLASS("s + type->AsFortran() + ')'
3804         : type->category() == TypeCategory::Derived
3805         ? "TYPE("s + type->AsFortran() + ')'
3806         : type->category() == TypeCategory::Character
3807         ? "CHARACTER(KIND="s + std::to_string(type->kind()) + ')'
3808         : ToUpperCase(type->AsFortran());
3809   } else {
3810     return "untyped";
3811   }
3812 }
3813 
3814 bool ArgumentAnalyzer::AnyUntypedOrMissingOperand() {
3815   for (const auto &actual : actuals_) {
3816     if (!actual ||
3817         (!actual->GetType() && !IsBareNullPointer(actual->UnwrapExpr()))) {
3818       return true;
3819     }
3820   }
3821   return false;
3822 }
3823 } // namespace Fortran::evaluate
3824 
3825 namespace Fortran::semantics {
3826 evaluate::Expr<evaluate::SubscriptInteger> AnalyzeKindSelector(
3827     SemanticsContext &context, common::TypeCategory category,
3828     const std::optional<parser::KindSelector> &selector) {
3829   evaluate::ExpressionAnalyzer analyzer{context};
3830   auto restorer{
3831       analyzer.GetContextualMessages().SetLocation(context.location().value())};
3832   return analyzer.AnalyzeKindSelector(category, selector);
3833 }
3834 
3835 ExprChecker::ExprChecker(SemanticsContext &context) : context_{context} {}
3836 
3837 bool ExprChecker::Pre(const parser::DataImpliedDo &ido) {
3838   parser::Walk(std::get<parser::DataImpliedDo::Bounds>(ido.t), *this);
3839   const auto &bounds{std::get<parser::DataImpliedDo::Bounds>(ido.t)};
3840   auto name{bounds.name.thing.thing};
3841   int kind{evaluate::ResultType<evaluate::ImpliedDoIndex>::kind};
3842   if (const auto dynamicType{evaluate::DynamicType::From(*name.symbol)}) {
3843     if (dynamicType->category() == TypeCategory::Integer) {
3844       kind = dynamicType->kind();
3845     }
3846   }
3847   exprAnalyzer_.AddImpliedDo(name.source, kind);
3848   parser::Walk(std::get<std::list<parser::DataIDoObject>>(ido.t), *this);
3849   exprAnalyzer_.RemoveImpliedDo(name.source);
3850   return false;
3851 }
3852 
3853 bool ExprChecker::Walk(const parser::Program &program) {
3854   parser::Walk(program, *this);
3855   return !context_.AnyFatalError();
3856 }
3857 } // namespace Fortran::semantics
3858