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.h"
13 #include "flang/Common/idioms.h"
14 #include "flang/Evaluate/common.h"
15 #include "flang/Evaluate/fold.h"
16 #include "flang/Evaluate/tools.h"
17 #include "flang/Parser/characters.h"
18 #include "flang/Parser/dump-parse-tree.h"
19 #include "flang/Parser/parse-tree-visitor.h"
20 #include "flang/Parser/parse-tree.h"
21 #include "flang/Semantics/scope.h"
22 #include "flang/Semantics/semantics.h"
23 #include "flang/Semantics/symbol.h"
24 #include "flang/Semantics/tools.h"
25 #include "llvm/Support/raw_ostream.h"
26 #include <algorithm>
27 #include <functional>
28 #include <optional>
29 #include <set>
30 
31 // Typedef for optional generic expressions (ubiquitous in this file)
32 using MaybeExpr =
33     std::optional<Fortran::evaluate::Expr<Fortran::evaluate::SomeType>>;
34 
35 // Much of the code that implements semantic analysis of expressions is
36 // tightly coupled with their typed representations in lib/Evaluate,
37 // and appears here in namespace Fortran::evaluate for convenience.
38 namespace Fortran::evaluate {
39 
40 using common::LanguageFeature;
41 using common::NumericOperator;
42 using common::TypeCategory;
43 
44 static inline std::string ToUpperCase(const std::string &str) {
45   return parser::ToUpperCaseLetters(str);
46 }
47 
48 struct DynamicTypeWithLength : public DynamicType {
49   explicit DynamicTypeWithLength(const DynamicType &t) : DynamicType{t} {}
50   std::optional<Expr<SubscriptInteger>> LEN() const;
51   std::optional<Expr<SubscriptInteger>> length;
52 };
53 
54 std::optional<Expr<SubscriptInteger>> DynamicTypeWithLength::LEN() const {
55   if (length) {
56     return length;
57   }
58   if (auto *lengthParam{charLength()}) {
59     if (const auto &len{lengthParam->GetExplicit()}) {
60       return ConvertToType<SubscriptInteger>(common::Clone(*len));
61     }
62   }
63   return std::nullopt; // assumed or deferred length
64 }
65 
66 static std::optional<DynamicTypeWithLength> AnalyzeTypeSpec(
67     const std::optional<parser::TypeSpec> &spec) {
68   if (spec) {
69     if (const semantics::DeclTypeSpec * typeSpec{spec->declTypeSpec}) {
70       // Name resolution sets TypeSpec::declTypeSpec only when it's valid
71       // (viz., an intrinsic type with valid known kind or a non-polymorphic
72       // & non-ABSTRACT derived type).
73       if (const semantics::IntrinsicTypeSpec *
74           intrinsic{typeSpec->AsIntrinsic()}) {
75         TypeCategory category{intrinsic->category()};
76         if (auto optKind{ToInt64(intrinsic->kind())}) {
77           int kind{static_cast<int>(*optKind)};
78           if (category == TypeCategory::Character) {
79             const semantics::CharacterTypeSpec &cts{
80                 typeSpec->characterTypeSpec()};
81             const semantics::ParamValue &len{cts.length()};
82             // N.B. CHARACTER(LEN=*) is allowed in type-specs in ALLOCATE() &
83             // type guards, but not in array constructors.
84             return DynamicTypeWithLength{DynamicType{kind, len}};
85           } else {
86             return DynamicTypeWithLength{DynamicType{category, kind}};
87           }
88         }
89       } else if (const semantics::DerivedTypeSpec *
90           derived{typeSpec->AsDerived()}) {
91         return DynamicTypeWithLength{DynamicType{*derived}};
92       }
93     }
94   }
95   return std::nullopt;
96 }
97 
98 // Wraps a object in an explicitly typed representation (e.g., Designator<>
99 // or FunctionRef<>) that has been instantiated on a dynamically chosen type.
100 template <TypeCategory CATEGORY, template <typename> typename WRAPPER,
101     typename WRAPPED>
102 common::IfNoLvalue<MaybeExpr, WRAPPED> WrapperHelper(int kind, WRAPPED &&x) {
103   return common::SearchTypes(
104       TypeKindVisitor<CATEGORY, WRAPPER, WRAPPED>{kind, std::move(x)});
105 }
106 
107 template <template <typename> typename WRAPPER, typename WRAPPED>
108 common::IfNoLvalue<MaybeExpr, WRAPPED> TypedWrapper(
109     const DynamicType &dyType, WRAPPED &&x) {
110   switch (dyType.category()) {
111     SWITCH_COVERS_ALL_CASES
112   case TypeCategory::Integer:
113     return WrapperHelper<TypeCategory::Integer, WRAPPER, WRAPPED>(
114         dyType.kind(), std::move(x));
115   case TypeCategory::Real:
116     return WrapperHelper<TypeCategory::Real, WRAPPER, WRAPPED>(
117         dyType.kind(), std::move(x));
118   case TypeCategory::Complex:
119     return WrapperHelper<TypeCategory::Complex, WRAPPER, WRAPPED>(
120         dyType.kind(), std::move(x));
121   case TypeCategory::Character:
122     return WrapperHelper<TypeCategory::Character, WRAPPER, WRAPPED>(
123         dyType.kind(), std::move(x));
124   case TypeCategory::Logical:
125     return WrapperHelper<TypeCategory::Logical, WRAPPER, WRAPPED>(
126         dyType.kind(), std::move(x));
127   case TypeCategory::Derived:
128     return AsGenericExpr(Expr<SomeDerived>{WRAPPER<SomeDerived>{std::move(x)}});
129   }
130 }
131 
132 class ArgumentAnalyzer {
133 public:
134   explicit ArgumentAnalyzer(ExpressionAnalyzer &context)
135       : context_{context}, allowAssumedType_{false} {}
136   ArgumentAnalyzer(ExpressionAnalyzer &context, parser::CharBlock source,
137       bool allowAssumedType = false)
138       : context_{context}, source_{source}, allowAssumedType_{
139                                                 allowAssumedType} {}
140   bool fatalErrors() const { return fatalErrors_; }
141   ActualArguments &&GetActuals() {
142     CHECK(!fatalErrors_);
143     return std::move(actuals_);
144   }
145   const Expr<SomeType> &GetExpr(std::size_t i) const {
146     return DEREF(actuals_.at(i).value().UnwrapExpr());
147   }
148   Expr<SomeType> &&MoveExpr(std::size_t i) {
149     return std::move(DEREF(actuals_.at(i).value().UnwrapExpr()));
150   }
151   void Analyze(const common::Indirection<parser::Expr> &x) {
152     Analyze(x.value());
153   }
154   void Analyze(const parser::Expr &x) {
155     actuals_.emplace_back(AnalyzeExpr(x));
156     fatalErrors_ |= !actuals_.back();
157   }
158   void Analyze(const parser::Variable &);
159   void Analyze(const parser::ActualArgSpec &, bool isSubroutine);
160 
161   bool IsIntrinsicRelational(RelationalOperator) const;
162   bool IsIntrinsicLogical() const;
163   bool IsIntrinsicNumeric(NumericOperator) const;
164   bool IsIntrinsicConcat() const;
165 
166   // Find and return a user-defined operator or report an error.
167   // The provided message is used if there is no such operator.
168   MaybeExpr TryDefinedOp(
169       const char *, parser::MessageFixedText &&, bool isUserOp = false);
170   template <typename E>
171   MaybeExpr TryDefinedOp(E opr, parser::MessageFixedText &&msg) {
172     return TryDefinedOp(
173         context_.context().languageFeatures().GetNames(opr), std::move(msg));
174   }
175   // Find and return a user-defined assignment
176   std::optional<ProcedureRef> TryDefinedAssignment();
177   std::optional<ProcedureRef> GetDefinedAssignmentProc();
178   void Dump(llvm::raw_ostream &);
179 
180 private:
181   MaybeExpr TryDefinedOp(
182       std::vector<const char *>, parser::MessageFixedText &&);
183   MaybeExpr TryBoundOp(const Symbol &, int passIndex);
184   std::optional<ActualArgument> AnalyzeExpr(const parser::Expr &);
185   bool AreConformable() const;
186   const Symbol *FindBoundOp(parser::CharBlock, int passIndex);
187   bool OkLogicalIntegerAssignment(TypeCategory lhs, TypeCategory rhs);
188   std::optional<DynamicType> GetType(std::size_t) const;
189   int GetRank(std::size_t) const;
190   bool IsBOZLiteral(std::size_t i) const {
191     return std::holds_alternative<BOZLiteralConstant>(GetExpr(i).u);
192   }
193   void SayNoMatch(const std::string &, bool isAssignment = false);
194   std::string TypeAsFortran(std::size_t);
195   bool AnyUntypedOperand();
196 
197   ExpressionAnalyzer &context_;
198   ActualArguments actuals_;
199   parser::CharBlock source_;
200   bool fatalErrors_{false};
201   const bool allowAssumedType_;
202   const Symbol *sawDefinedOp_{nullptr};
203 };
204 
205 // Wraps a data reference in a typed Designator<>, and a procedure
206 // or procedure pointer reference in a ProcedureDesignator.
207 MaybeExpr ExpressionAnalyzer::Designate(DataRef &&ref) {
208   const Symbol &symbol{ref.GetLastSymbol().GetUltimate()};
209   if (semantics::IsProcedure(symbol)) {
210     if (auto *component{std::get_if<Component>(&ref.u)}) {
211       return Expr<SomeType>{ProcedureDesignator{std::move(*component)}};
212     } else if (!std::holds_alternative<SymbolRef>(ref.u)) {
213       DIE("unexpected alternative in DataRef");
214     } else if (!symbol.attrs().test(semantics::Attr::INTRINSIC)) {
215       return Expr<SomeType>{ProcedureDesignator{symbol}};
216     } else if (auto interface{context_.intrinsics().IsSpecificIntrinsicFunction(
217                    symbol.name().ToString())}) {
218       SpecificIntrinsic intrinsic{
219           symbol.name().ToString(), std::move(*interface)};
220       intrinsic.isRestrictedSpecific = interface->isRestrictedSpecific;
221       return Expr<SomeType>{ProcedureDesignator{std::move(intrinsic)}};
222     } else {
223       Say("'%s' is not a specific intrinsic procedure"_err_en_US,
224           symbol.name());
225       return std::nullopt;
226     }
227   } else if (auto dyType{DynamicType::From(symbol)}) {
228     return TypedWrapper<Designator, DataRef>(*dyType, std::move(ref));
229   }
230   return std::nullopt;
231 }
232 
233 // Some subscript semantic checks must be deferred until all of the
234 // subscripts are in hand.
235 MaybeExpr ExpressionAnalyzer::CompleteSubscripts(ArrayRef &&ref) {
236   const Symbol &symbol{ref.GetLastSymbol().GetUltimate()};
237   const auto *object{symbol.detailsIf<semantics::ObjectEntityDetails>()};
238   int symbolRank{symbol.Rank()};
239   int subscripts{static_cast<int>(ref.size())};
240   if (subscripts == 0) {
241     // nothing to check
242   } else if (subscripts != symbolRank) {
243     if (symbolRank != 0) {
244       Say("Reference to rank-%d object '%s' has %d subscripts"_err_en_US,
245           symbolRank, symbol.name(), subscripts);
246     }
247     return std::nullopt;
248   } else if (Component * component{ref.base().UnwrapComponent()}) {
249     int baseRank{component->base().Rank()};
250     if (baseRank > 0) {
251       int subscriptRank{0};
252       for (const auto &expr : ref.subscript()) {
253         subscriptRank += expr.Rank();
254       }
255       if (subscriptRank > 0) {
256         Say("Subscripts of component '%s' of rank-%d derived type "
257             "array have rank %d but must all be scalar"_err_en_US,
258             symbol.name(), baseRank, subscriptRank);
259         return std::nullopt;
260       }
261     }
262   } else if (object) {
263     // C928 & C1002
264     if (Triplet * last{std::get_if<Triplet>(&ref.subscript().back().u)}) {
265       if (!last->upper() && object->IsAssumedSize()) {
266         Say("Assumed-size array '%s' must have explicit final "
267             "subscript upper bound value"_err_en_US,
268             symbol.name());
269         return std::nullopt;
270       }
271     }
272   }
273   return Designate(DataRef{std::move(ref)});
274 }
275 
276 // Applies subscripts to a data reference.
277 MaybeExpr ExpressionAnalyzer::ApplySubscripts(
278     DataRef &&dataRef, std::vector<Subscript> &&subscripts) {
279   return std::visit(
280       common::visitors{
281           [&](SymbolRef &&symbol) {
282             return CompleteSubscripts(ArrayRef{symbol, std::move(subscripts)});
283           },
284           [&](Component &&c) {
285             return CompleteSubscripts(
286                 ArrayRef{std::move(c), std::move(subscripts)});
287           },
288           [&](auto &&) -> MaybeExpr {
289             DIE("bad base for ArrayRef");
290             return std::nullopt;
291           },
292       },
293       std::move(dataRef.u));
294 }
295 
296 // Top-level checks for data references.
297 MaybeExpr ExpressionAnalyzer::TopLevelChecks(DataRef &&dataRef) {
298   if (Component * component{std::get_if<Component>(&dataRef.u)}) {
299     const Symbol &symbol{component->GetLastSymbol()};
300     int componentRank{symbol.Rank()};
301     if (componentRank > 0) {
302       int baseRank{component->base().Rank()};
303       if (baseRank > 0) {
304         Say("Reference to whole rank-%d component '%%%s' of "
305             "rank-%d array of derived type is not allowed"_err_en_US,
306             componentRank, symbol.name(), baseRank);
307       }
308     }
309   }
310   return Designate(std::move(dataRef));
311 }
312 
313 // Parse tree correction after a substring S(j:k) was misparsed as an
314 // array section.  N.B. Fortran substrings have to have a range, not a
315 // single index.
316 static void FixMisparsedSubstring(const parser::Designator &d) {
317   auto &mutate{const_cast<parser::Designator &>(d)};
318   if (auto *dataRef{std::get_if<parser::DataRef>(&mutate.u)}) {
319     if (auto *ae{std::get_if<common::Indirection<parser::ArrayElement>>(
320             &dataRef->u)}) {
321       parser::ArrayElement &arrElement{ae->value()};
322       if (!arrElement.subscripts.empty()) {
323         auto iter{arrElement.subscripts.begin()};
324         if (auto *triplet{std::get_if<parser::SubscriptTriplet>(&iter->u)}) {
325           if (!std::get<2>(triplet->t) /* no stride */ &&
326               ++iter == arrElement.subscripts.end() /* one subscript */) {
327             if (Symbol *
328                 symbol{std::visit(
329                     common::visitors{
330                         [](parser::Name &n) { return n.symbol; },
331                         [](common::Indirection<parser::StructureComponent>
332                                 &sc) { return sc.value().component.symbol; },
333                         [](auto &) -> Symbol * { return nullptr; },
334                     },
335                     arrElement.base.u)}) {
336               const Symbol &ultimate{symbol->GetUltimate()};
337               if (const semantics::DeclTypeSpec * type{ultimate.GetType()}) {
338                 if (!ultimate.IsObjectArray() &&
339                     type->category() == semantics::DeclTypeSpec::Character) {
340                   // The ambiguous S(j:k) was parsed as an array section
341                   // reference, but it's now clear that it's a substring.
342                   // Fix the parse tree in situ.
343                   mutate.u = arrElement.ConvertToSubstring();
344                 }
345               }
346             }
347           }
348         }
349       }
350     }
351   }
352 }
353 
354 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Designator &d) {
355   auto restorer{GetContextualMessages().SetLocation(d.source)};
356   FixMisparsedSubstring(d);
357   // These checks have to be deferred to these "top level" data-refs where
358   // we can be sure that there are no following subscripts (yet).
359   // Substrings have already been run through TopLevelChecks() and
360   // won't be returned by ExtractDataRef().
361   if (MaybeExpr result{Analyze(d.u)}) {
362     if (std::optional<DataRef> dataRef{ExtractDataRef(std::move(result))}) {
363       return TopLevelChecks(std::move(*dataRef));
364     }
365     return result;
366   }
367   return std::nullopt;
368 }
369 
370 // A utility subroutine to repackage optional expressions of various levels
371 // of type specificity as fully general MaybeExpr values.
372 template <typename A> common::IfNoLvalue<MaybeExpr, A> AsMaybeExpr(A &&x) {
373   return std::make_optional(AsGenericExpr(std::move(x)));
374 }
375 template <typename A> MaybeExpr AsMaybeExpr(std::optional<A> &&x) {
376   if (x) {
377     return AsMaybeExpr(std::move(*x));
378   }
379   return std::nullopt;
380 }
381 
382 // Type kind parameter values for literal constants.
383 int ExpressionAnalyzer::AnalyzeKindParam(
384     const std::optional<parser::KindParam> &kindParam, int defaultKind) {
385   if (!kindParam) {
386     return defaultKind;
387   }
388   return std::visit(
389       common::visitors{
390           [](std::uint64_t k) { return static_cast<int>(k); },
391           [&](const parser::Scalar<
392               parser::Integer<parser::Constant<parser::Name>>> &n) {
393             if (MaybeExpr ie{Analyze(n)}) {
394               if (std::optional<std::int64_t> i64{ToInt64(*ie)}) {
395                 int iv = *i64;
396                 if (iv == *i64) {
397                   return iv;
398                 }
399               }
400             }
401             return defaultKind;
402           },
403       },
404       kindParam->u);
405 }
406 
407 // Common handling of parser::IntLiteralConstant and SignedIntLiteralConstant
408 struct IntTypeVisitor {
409   using Result = MaybeExpr;
410   using Types = IntegerTypes;
411   template <typename T> Result Test() {
412     if (T::kind >= kind) {
413       const char *p{digits.begin()};
414       auto value{T::Scalar::Read(p, 10, true /*signed*/)};
415       if (!value.overflow) {
416         if (T::kind > kind) {
417           if (!isDefaultKind ||
418               !analyzer.context().IsEnabled(LanguageFeature::BigIntLiterals)) {
419             return std::nullopt;
420           } else if (analyzer.context().ShouldWarn(
421                          LanguageFeature::BigIntLiterals)) {
422             analyzer.Say(digits,
423                 "Integer literal is too large for default INTEGER(KIND=%d); "
424                 "assuming INTEGER(KIND=%d)"_en_US,
425                 kind, T::kind);
426           }
427         }
428         return Expr<SomeType>{
429             Expr<SomeInteger>{Expr<T>{Constant<T>{std::move(value.value)}}}};
430       }
431     }
432     return std::nullopt;
433   }
434   ExpressionAnalyzer &analyzer;
435   parser::CharBlock digits;
436   int kind;
437   bool isDefaultKind;
438 };
439 
440 template <typename PARSED>
441 MaybeExpr ExpressionAnalyzer::IntLiteralConstant(const PARSED &x) {
442   const auto &kindParam{std::get<std::optional<parser::KindParam>>(x.t)};
443   bool isDefaultKind{!kindParam};
444   int kind{AnalyzeKindParam(kindParam, GetDefaultKind(TypeCategory::Integer))};
445   if (CheckIntrinsicKind(TypeCategory::Integer, kind)) {
446     auto digits{std::get<parser::CharBlock>(x.t)};
447     if (MaybeExpr result{common::SearchTypes(
448             IntTypeVisitor{*this, digits, kind, isDefaultKind})}) {
449       return result;
450     } else if (isDefaultKind) {
451       Say(digits,
452           "Integer literal is too large for any allowable "
453           "kind of INTEGER"_err_en_US);
454     } else {
455       Say(digits, "Integer literal is too large for INTEGER(KIND=%d)"_err_en_US,
456           kind);
457     }
458   }
459   return std::nullopt;
460 }
461 
462 MaybeExpr ExpressionAnalyzer::Analyze(const parser::IntLiteralConstant &x) {
463   auto restorer{
464       GetContextualMessages().SetLocation(std::get<parser::CharBlock>(x.t))};
465   return IntLiteralConstant(x);
466 }
467 
468 MaybeExpr ExpressionAnalyzer::Analyze(
469     const parser::SignedIntLiteralConstant &x) {
470   auto restorer{GetContextualMessages().SetLocation(x.source)};
471   return IntLiteralConstant(x);
472 }
473 
474 template <typename TYPE>
475 Constant<TYPE> ReadRealLiteral(
476     parser::CharBlock source, FoldingContext &context) {
477   const char *p{source.begin()};
478   auto valWithFlags{Scalar<TYPE>::Read(p, context.rounding())};
479   CHECK(p == source.end());
480   RealFlagWarnings(context, valWithFlags.flags, "conversion of REAL literal");
481   auto value{valWithFlags.value};
482   if (context.flushSubnormalsToZero()) {
483     value = value.FlushSubnormalToZero();
484   }
485   return {value};
486 }
487 
488 struct RealTypeVisitor {
489   using Result = std::optional<Expr<SomeReal>>;
490   using Types = RealTypes;
491 
492   RealTypeVisitor(int k, parser::CharBlock lit, FoldingContext &ctx)
493       : kind{k}, literal{lit}, context{ctx} {}
494 
495   template <typename T> Result Test() {
496     if (kind == T::kind) {
497       return {AsCategoryExpr(ReadRealLiteral<T>(literal, context))};
498     }
499     return std::nullopt;
500   }
501 
502   int kind;
503   parser::CharBlock literal;
504   FoldingContext &context;
505 };
506 
507 // Reads a real literal constant and encodes it with the right kind.
508 MaybeExpr ExpressionAnalyzer::Analyze(const parser::RealLiteralConstant &x) {
509   // Use a local message context around the real literal for better
510   // provenance on any messages.
511   auto restorer{GetContextualMessages().SetLocation(x.real.source)};
512   // If a kind parameter appears, it defines the kind of the literal and the
513   // letter used in an exponent part must be 'E' (e.g., the 'E' in
514   // "6.02214E+23").  In the absence of an explicit kind parameter, any
515   // exponent letter determines the kind.  Otherwise, defaults apply.
516   auto &defaults{context_.defaultKinds()};
517   int defaultKind{defaults.GetDefaultKind(TypeCategory::Real)};
518   const char *end{x.real.source.end()};
519   char expoLetter{' '};
520   std::optional<int> letterKind;
521   for (const char *p{x.real.source.begin()}; p < end; ++p) {
522     if (parser::IsLetter(*p)) {
523       expoLetter = *p;
524       switch (expoLetter) {
525       case 'e':
526         letterKind = defaults.GetDefaultKind(TypeCategory::Real);
527         break;
528       case 'd':
529         letterKind = defaults.doublePrecisionKind();
530         break;
531       case 'q':
532         letterKind = defaults.quadPrecisionKind();
533         break;
534       default:
535         Say("Unknown exponent letter '%c'"_err_en_US, expoLetter);
536       }
537       break;
538     }
539   }
540   if (letterKind) {
541     defaultKind = *letterKind;
542   }
543   // C716 requires 'E' as an exponent, but this is more useful
544   auto kind{AnalyzeKindParam(x.kind, defaultKind)};
545   if (letterKind && kind != *letterKind && expoLetter != 'e') {
546     Say("Explicit kind parameter on real constant disagrees with "
547         "exponent letter '%c'"_en_US,
548         expoLetter);
549   }
550   auto result{common::SearchTypes(
551       RealTypeVisitor{kind, x.real.source, GetFoldingContext()})};
552   if (!result) { // C717
553     Say("Unsupported REAL(KIND=%d)"_err_en_US, kind);
554   }
555   return AsMaybeExpr(std::move(result));
556 }
557 
558 MaybeExpr ExpressionAnalyzer::Analyze(
559     const parser::SignedRealLiteralConstant &x) {
560   if (auto result{Analyze(std::get<parser::RealLiteralConstant>(x.t))}) {
561     auto &realExpr{std::get<Expr<SomeReal>>(result->u)};
562     if (auto sign{std::get<std::optional<parser::Sign>>(x.t)}) {
563       if (sign == parser::Sign::Negative) {
564         return {AsGenericExpr(-std::move(realExpr))};
565       }
566     }
567     return result;
568   }
569   return std::nullopt;
570 }
571 
572 MaybeExpr ExpressionAnalyzer::Analyze(
573     const parser::SignedComplexLiteralConstant &x) {
574   auto result{Analyze(std::get<parser::ComplexLiteralConstant>(x.t))};
575   if (!result) {
576     return std::nullopt;
577   } else if (std::get<parser::Sign>(x.t) == parser::Sign::Negative) {
578     return AsGenericExpr(-std::move(std::get<Expr<SomeComplex>>(result->u)));
579   } else {
580     return result;
581   }
582 }
583 
584 MaybeExpr ExpressionAnalyzer::Analyze(const parser::ComplexPart &x) {
585   return Analyze(x.u);
586 }
587 
588 MaybeExpr ExpressionAnalyzer::Analyze(const parser::ComplexLiteralConstant &z) {
589   return AsMaybeExpr(
590       ConstructComplex(GetContextualMessages(), Analyze(std::get<0>(z.t)),
591           Analyze(std::get<1>(z.t)), GetDefaultKind(TypeCategory::Real)));
592 }
593 
594 // CHARACTER literal processing.
595 MaybeExpr ExpressionAnalyzer::AnalyzeString(std::string &&string, int kind) {
596   if (!CheckIntrinsicKind(TypeCategory::Character, kind)) {
597     return std::nullopt;
598   }
599   switch (kind) {
600   case 1:
601     return AsGenericExpr(Constant<Type<TypeCategory::Character, 1>>{
602         parser::DecodeString<std::string, parser::Encoding::LATIN_1>(
603             string, true)});
604   case 2:
605     return AsGenericExpr(Constant<Type<TypeCategory::Character, 2>>{
606         parser::DecodeString<std::u16string, parser::Encoding::UTF_8>(
607             string, true)});
608   case 4:
609     return AsGenericExpr(Constant<Type<TypeCategory::Character, 4>>{
610         parser::DecodeString<std::u32string, parser::Encoding::UTF_8>(
611             string, true)});
612   default:
613     CRASH_NO_CASE;
614   }
615 }
616 
617 MaybeExpr ExpressionAnalyzer::Analyze(const parser::CharLiteralConstant &x) {
618   int kind{
619       AnalyzeKindParam(std::get<std::optional<parser::KindParam>>(x.t), 1)};
620   auto value{std::get<std::string>(x.t)};
621   return AnalyzeString(std::move(value), kind);
622 }
623 
624 MaybeExpr ExpressionAnalyzer::Analyze(
625     const parser::HollerithLiteralConstant &x) {
626   int kind{GetDefaultKind(TypeCategory::Character)};
627   auto value{x.v};
628   return AnalyzeString(std::move(value), kind);
629 }
630 
631 // .TRUE. and .FALSE. of various kinds
632 MaybeExpr ExpressionAnalyzer::Analyze(const parser::LogicalLiteralConstant &x) {
633   auto kind{AnalyzeKindParam(std::get<std::optional<parser::KindParam>>(x.t),
634       GetDefaultKind(TypeCategory::Logical))};
635   bool value{std::get<bool>(x.t)};
636   auto result{common::SearchTypes(
637       TypeKindVisitor<TypeCategory::Logical, Constant, bool>{
638           kind, std::move(value)})};
639   if (!result) {
640     Say("unsupported LOGICAL(KIND=%d)"_err_en_US, kind); // C728
641   }
642   return result;
643 }
644 
645 // BOZ typeless literals
646 MaybeExpr ExpressionAnalyzer::Analyze(const parser::BOZLiteralConstant &x) {
647   const char *p{x.v.c_str()};
648   std::uint64_t base{16};
649   switch (*p++) {
650   case 'b':
651     base = 2;
652     break;
653   case 'o':
654     base = 8;
655     break;
656   case 'z':
657     break;
658   case 'x':
659     break;
660   default:
661     CRASH_NO_CASE;
662   }
663   CHECK(*p == '"');
664   ++p;
665   auto value{BOZLiteralConstant::Read(p, base, false /*unsigned*/)};
666   if (*p != '"') {
667     Say("Invalid digit ('%c') in BOZ literal '%s'"_err_en_US, *p, x.v);
668     return std::nullopt;
669   }
670   if (value.overflow) {
671     Say("BOZ literal '%s' too large"_err_en_US, x.v);
672     return std::nullopt;
673   }
674   return AsGenericExpr(std::move(value.value));
675 }
676 
677 // For use with SearchTypes to create a TypeParamInquiry with the
678 // right integer kind.
679 struct TypeParamInquiryVisitor {
680   using Result = std::optional<Expr<SomeInteger>>;
681   using Types = IntegerTypes;
682   TypeParamInquiryVisitor(int k, NamedEntity &&b, const Symbol &param)
683       : kind{k}, base{std::move(b)}, parameter{param} {}
684   TypeParamInquiryVisitor(int k, const Symbol &param)
685       : kind{k}, parameter{param} {}
686   template <typename T> Result Test() {
687     if (kind == T::kind) {
688       return Expr<SomeInteger>{
689           Expr<T>{TypeParamInquiry<T::kind>{std::move(base), parameter}}};
690     }
691     return std::nullopt;
692   }
693   int kind;
694   std::optional<NamedEntity> base;
695   const Symbol &parameter;
696 };
697 
698 static std::optional<Expr<SomeInteger>> MakeBareTypeParamInquiry(
699     const Symbol *symbol) {
700   if (std::optional<DynamicType> dyType{DynamicType::From(symbol)}) {
701     if (dyType->category() == TypeCategory::Integer) {
702       return common::SearchTypes(
703           TypeParamInquiryVisitor{dyType->kind(), *symbol});
704     }
705   }
706   return std::nullopt;
707 }
708 
709 // Names and named constants
710 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Name &n) {
711   if (std::optional<int> kind{IsAcImpliedDo(n.source)}) {
712     return AsMaybeExpr(ConvertToKind<TypeCategory::Integer>(
713         *kind, AsExpr(ImpliedDoIndex{n.source})));
714   } else if (context_.HasError(n) || !n.symbol) {
715     return std::nullopt;
716   } else {
717     const Symbol &ultimate{n.symbol->GetUltimate()};
718     if (ultimate.has<semantics::TypeParamDetails>()) {
719       // A bare reference to a derived type parameter (within a parameterized
720       // derived type definition)
721       return AsMaybeExpr(MakeBareTypeParamInquiry(&ultimate));
722     } else {
723       if (n.symbol->attrs().test(semantics::Attr::VOLATILE)) {
724         if (const semantics::Scope *
725             pure{semantics::FindPureProcedureContaining(
726                 context_.FindScope(n.source))}) {
727           SayAt(n,
728               "VOLATILE variable '%s' may not be referenced in pure subprogram '%s'"_err_en_US,
729               n.source, DEREF(pure->symbol()).name());
730           n.symbol->attrs().reset(semantics::Attr::VOLATILE);
731         }
732       }
733       return Designate(DataRef{*n.symbol});
734     }
735   }
736 }
737 
738 MaybeExpr ExpressionAnalyzer::Analyze(const parser::NamedConstant &n) {
739   if (MaybeExpr value{Analyze(n.v)}) {
740     Expr<SomeType> folded{Fold(std::move(*value))};
741     if (IsConstantExpr(folded)) {
742       return {folded};
743     }
744     Say(n.v.source, "must be a constant"_err_en_US); // C718
745   }
746   return std::nullopt;
747 }
748 
749 // Substring references
750 std::optional<Expr<SubscriptInteger>> ExpressionAnalyzer::GetSubstringBound(
751     const std::optional<parser::ScalarIntExpr> &bound) {
752   if (bound) {
753     if (MaybeExpr expr{Analyze(*bound)}) {
754       if (expr->Rank() > 1) {
755         Say("substring bound expression has rank %d"_err_en_US, expr->Rank());
756       }
757       if (auto *intExpr{std::get_if<Expr<SomeInteger>>(&expr->u)}) {
758         if (auto *ssIntExpr{std::get_if<Expr<SubscriptInteger>>(&intExpr->u)}) {
759           return {std::move(*ssIntExpr)};
760         }
761         return {Expr<SubscriptInteger>{
762             Convert<SubscriptInteger, TypeCategory::Integer>{
763                 std::move(*intExpr)}}};
764       } else {
765         Say("substring bound expression is not INTEGER"_err_en_US);
766       }
767     }
768   }
769   return std::nullopt;
770 }
771 
772 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Substring &ss) {
773   if (MaybeExpr baseExpr{Analyze(std::get<parser::DataRef>(ss.t))}) {
774     if (std::optional<DataRef> dataRef{ExtractDataRef(std::move(*baseExpr))}) {
775       if (MaybeExpr newBaseExpr{TopLevelChecks(std::move(*dataRef))}) {
776         if (std::optional<DataRef> checked{
777                 ExtractDataRef(std::move(*newBaseExpr))}) {
778           const parser::SubstringRange &range{
779               std::get<parser::SubstringRange>(ss.t)};
780           std::optional<Expr<SubscriptInteger>> first{
781               GetSubstringBound(std::get<0>(range.t))};
782           std::optional<Expr<SubscriptInteger>> last{
783               GetSubstringBound(std::get<1>(range.t))};
784           const Symbol &symbol{checked->GetLastSymbol()};
785           if (std::optional<DynamicType> dynamicType{
786                   DynamicType::From(symbol)}) {
787             if (dynamicType->category() == TypeCategory::Character) {
788               return WrapperHelper<TypeCategory::Character, Designator,
789                   Substring>(dynamicType->kind(),
790                   Substring{std::move(checked.value()), std::move(first),
791                       std::move(last)});
792             }
793           }
794           Say("substring may apply only to CHARACTER"_err_en_US);
795         }
796       }
797     }
798   }
799   return std::nullopt;
800 }
801 
802 // CHARACTER literal substrings
803 MaybeExpr ExpressionAnalyzer::Analyze(
804     const parser::CharLiteralConstantSubstring &x) {
805   const parser::SubstringRange &range{std::get<parser::SubstringRange>(x.t)};
806   std::optional<Expr<SubscriptInteger>> lower{
807       GetSubstringBound(std::get<0>(range.t))};
808   std::optional<Expr<SubscriptInteger>> upper{
809       GetSubstringBound(std::get<1>(range.t))};
810   if (MaybeExpr string{Analyze(std::get<parser::CharLiteralConstant>(x.t))}) {
811     if (auto *charExpr{std::get_if<Expr<SomeCharacter>>(&string->u)}) {
812       Expr<SubscriptInteger> length{
813           std::visit([](const auto &ckExpr) { return ckExpr.LEN().value(); },
814               charExpr->u)};
815       if (!lower) {
816         lower = Expr<SubscriptInteger>{1};
817       }
818       if (!upper) {
819         upper = Expr<SubscriptInteger>{
820             static_cast<std::int64_t>(ToInt64(length).value())};
821       }
822       return std::visit(
823           [&](auto &&ckExpr) -> MaybeExpr {
824             using Result = ResultType<decltype(ckExpr)>;
825             auto *cp{std::get_if<Constant<Result>>(&ckExpr.u)};
826             CHECK(DEREF(cp).size() == 1);
827             StaticDataObject::Pointer staticData{StaticDataObject::Create()};
828             staticData->set_alignment(Result::kind)
829                 .set_itemBytes(Result::kind)
830                 .Push(cp->GetScalarValue().value());
831             Substring substring{std::move(staticData), std::move(lower.value()),
832                 std::move(upper.value())};
833             return AsGenericExpr(Expr<SomeCharacter>{
834                 Expr<Result>{Designator<Result>{std::move(substring)}}});
835           },
836           std::move(charExpr->u));
837     }
838   }
839   return std::nullopt;
840 }
841 
842 // Subscripted array references
843 std::optional<Expr<SubscriptInteger>> ExpressionAnalyzer::AsSubscript(
844     MaybeExpr &&expr) {
845   if (expr) {
846     if (expr->Rank() > 1) {
847       Say("Subscript expression has rank %d greater than 1"_err_en_US,
848           expr->Rank());
849     }
850     if (auto *intExpr{std::get_if<Expr<SomeInteger>>(&expr->u)}) {
851       if (auto *ssIntExpr{std::get_if<Expr<SubscriptInteger>>(&intExpr->u)}) {
852         return std::move(*ssIntExpr);
853       } else {
854         return Expr<SubscriptInteger>{
855             Convert<SubscriptInteger, TypeCategory::Integer>{
856                 std::move(*intExpr)}};
857       }
858     } else {
859       Say("Subscript expression is not INTEGER"_err_en_US);
860     }
861   }
862   return std::nullopt;
863 }
864 
865 std::optional<Expr<SubscriptInteger>> ExpressionAnalyzer::TripletPart(
866     const std::optional<parser::Subscript> &s) {
867   if (s) {
868     return AsSubscript(Analyze(*s));
869   } else {
870     return std::nullopt;
871   }
872 }
873 
874 std::optional<Subscript> ExpressionAnalyzer::AnalyzeSectionSubscript(
875     const parser::SectionSubscript &ss) {
876   return std::visit(common::visitors{
877                         [&](const parser::SubscriptTriplet &t) {
878                           return std::make_optional<Subscript>(
879                               Triplet{TripletPart(std::get<0>(t.t)),
880                                   TripletPart(std::get<1>(t.t)),
881                                   TripletPart(std::get<2>(t.t))});
882                         },
883                         [&](const auto &s) -> std::optional<Subscript> {
884                           if (auto subscriptExpr{AsSubscript(Analyze(s))}) {
885                             return Subscript{std::move(*subscriptExpr)};
886                           } else {
887                             return std::nullopt;
888                           }
889                         },
890                     },
891       ss.u);
892 }
893 
894 // Empty result means an error occurred
895 std::vector<Subscript> ExpressionAnalyzer::AnalyzeSectionSubscripts(
896     const std::list<parser::SectionSubscript> &sss) {
897   bool error{false};
898   std::vector<Subscript> subscripts;
899   for (const auto &s : sss) {
900     if (auto subscript{AnalyzeSectionSubscript(s)}) {
901       subscripts.emplace_back(std::move(*subscript));
902     } else {
903       error = true;
904     }
905   }
906   return !error ? subscripts : std::vector<Subscript>{};
907 }
908 
909 MaybeExpr ExpressionAnalyzer::Analyze(const parser::ArrayElement &ae) {
910   if (MaybeExpr baseExpr{Analyze(ae.base)}) {
911     if (ae.subscripts.empty()) {
912       // will be converted to function call later or error reported
913       return std::nullopt;
914     } else if (baseExpr->Rank() == 0) {
915       if (const Symbol * symbol{GetLastSymbol(*baseExpr)}) {
916         Say("'%s' is not an array"_err_en_US, symbol->name());
917       }
918     } else if (std::optional<DataRef> dataRef{
919                    ExtractDataRef(std::move(*baseExpr))}) {
920       return ApplySubscripts(
921           std::move(*dataRef), AnalyzeSectionSubscripts(ae.subscripts));
922     } else {
923       Say("Subscripts may be applied only to an object, component, or array constant"_err_en_US);
924     }
925   }
926   // error was reported: analyze subscripts without reporting more errors
927   auto restorer{GetContextualMessages().DiscardMessages()};
928   AnalyzeSectionSubscripts(ae.subscripts);
929   return std::nullopt;
930 }
931 
932 // Type parameter inquiries apply to data references, but don't depend
933 // on any trailing (co)subscripts.
934 static NamedEntity IgnoreAnySubscripts(Designator<SomeDerived> &&designator) {
935   return std::visit(
936       common::visitors{
937           [](SymbolRef &&symbol) { return NamedEntity{symbol}; },
938           [](Component &&component) {
939             return NamedEntity{std::move(component)};
940           },
941           [](ArrayRef &&arrayRef) { return std::move(arrayRef.base()); },
942           [](CoarrayRef &&coarrayRef) {
943             return NamedEntity{coarrayRef.GetLastSymbol()};
944           },
945       },
946       std::move(designator.u));
947 }
948 
949 // Components of parent derived types are explicitly represented as such.
950 static std::optional<Component> CreateComponent(
951     DataRef &&base, const Symbol &component, const semantics::Scope &scope) {
952   if (&component.owner() == &scope) {
953     return Component{std::move(base), component};
954   }
955   if (const semantics::Scope * parentScope{scope.GetDerivedTypeParent()}) {
956     if (const Symbol * parentComponent{parentScope->GetSymbol()}) {
957       return CreateComponent(
958           DataRef{Component{std::move(base), *parentComponent}}, component,
959           *parentScope);
960     }
961   }
962   return std::nullopt;
963 }
964 
965 // Derived type component references and type parameter inquiries
966 MaybeExpr ExpressionAnalyzer::Analyze(const parser::StructureComponent &sc) {
967   MaybeExpr base{Analyze(sc.base)};
968   if (!base) {
969     return std::nullopt;
970   }
971   Symbol *sym{sc.component.symbol};
972   if (context_.HasError(sym)) {
973     return std::nullopt;
974   }
975   const auto &name{sc.component.source};
976   if (auto *dtExpr{UnwrapExpr<Expr<SomeDerived>>(*base)}) {
977     const auto *dtSpec{GetDerivedTypeSpec(dtExpr->GetType())};
978     if (sym->detailsIf<semantics::TypeParamDetails>()) {
979       if (auto *designator{UnwrapExpr<Designator<SomeDerived>>(*dtExpr)}) {
980         if (std::optional<DynamicType> dyType{DynamicType::From(*sym)}) {
981           if (dyType->category() == TypeCategory::Integer) {
982             return AsMaybeExpr(
983                 common::SearchTypes(TypeParamInquiryVisitor{dyType->kind(),
984                     IgnoreAnySubscripts(std::move(*designator)), *sym}));
985           }
986         }
987         Say(name, "Type parameter is not INTEGER"_err_en_US);
988       } else {
989         Say(name,
990             "A type parameter inquiry must be applied to "
991             "a designator"_err_en_US);
992       }
993     } else if (!dtSpec || !dtSpec->scope()) {
994       CHECK(context_.AnyFatalError() || !foldingContext_.messages().empty());
995       return std::nullopt;
996     } else if (std::optional<DataRef> dataRef{
997                    ExtractDataRef(std::move(*dtExpr))}) {
998       if (auto component{
999               CreateComponent(std::move(*dataRef), *sym, *dtSpec->scope())}) {
1000         return Designate(DataRef{std::move(*component)});
1001       } else {
1002         Say(name, "Component is not in scope of derived TYPE(%s)"_err_en_US,
1003             dtSpec->typeSymbol().name());
1004       }
1005     } else {
1006       Say(name,
1007           "Base of component reference must be a data reference"_err_en_US);
1008     }
1009   } else if (auto *details{sym->detailsIf<semantics::MiscDetails>()}) {
1010     // special part-ref: %re, %im, %kind, %len
1011     // Type errors are detected and reported in semantics.
1012     using MiscKind = semantics::MiscDetails::Kind;
1013     MiscKind kind{details->kind()};
1014     if (kind == MiscKind::ComplexPartRe || kind == MiscKind::ComplexPartIm) {
1015       if (auto *zExpr{std::get_if<Expr<SomeComplex>>(&base->u)}) {
1016         if (std::optional<DataRef> dataRef{ExtractDataRef(std::move(*zExpr))}) {
1017           Expr<SomeReal> realExpr{std::visit(
1018               [&](const auto &z) {
1019                 using PartType = typename ResultType<decltype(z)>::Part;
1020                 auto part{kind == MiscKind::ComplexPartRe
1021                         ? ComplexPart::Part::RE
1022                         : ComplexPart::Part::IM};
1023                 return AsCategoryExpr(Designator<PartType>{
1024                     ComplexPart{std::move(*dataRef), part}});
1025               },
1026               zExpr->u)};
1027           return {AsGenericExpr(std::move(realExpr))};
1028         }
1029       }
1030     } else if (kind == MiscKind::KindParamInquiry ||
1031         kind == MiscKind::LenParamInquiry) {
1032       // Convert x%KIND -> intrinsic KIND(x), x%LEN -> intrinsic LEN(x)
1033       return MakeFunctionRef(
1034           name, ActualArguments{ActualArgument{std::move(*base)}});
1035     } else {
1036       DIE("unexpected MiscDetails::Kind");
1037     }
1038   } else {
1039     Say(name, "derived type required before component reference"_err_en_US);
1040   }
1041   return std::nullopt;
1042 }
1043 
1044 MaybeExpr ExpressionAnalyzer::Analyze(const parser::CoindexedNamedObject &x) {
1045   if (auto maybeDataRef{ExtractDataRef(Analyze(x.base))}) {
1046     DataRef *dataRef{&*maybeDataRef};
1047     std::vector<Subscript> subscripts;
1048     SymbolVector reversed;
1049     if (auto *aRef{std::get_if<ArrayRef>(&dataRef->u)}) {
1050       subscripts = std::move(aRef->subscript());
1051       reversed.push_back(aRef->GetLastSymbol());
1052       if (Component * component{aRef->base().UnwrapComponent()}) {
1053         dataRef = &component->base();
1054       } else {
1055         dataRef = nullptr;
1056       }
1057     }
1058     if (dataRef) {
1059       while (auto *component{std::get_if<Component>(&dataRef->u)}) {
1060         reversed.push_back(component->GetLastSymbol());
1061         dataRef = &component->base();
1062       }
1063       if (auto *baseSym{std::get_if<SymbolRef>(&dataRef->u)}) {
1064         reversed.push_back(*baseSym);
1065       } else {
1066         Say("Base of coindexed named object has subscripts or cosubscripts"_err_en_US);
1067       }
1068     }
1069     std::vector<Expr<SubscriptInteger>> cosubscripts;
1070     bool cosubsOk{true};
1071     for (const auto &cosub :
1072         std::get<std::list<parser::Cosubscript>>(x.imageSelector.t)) {
1073       MaybeExpr coex{Analyze(cosub)};
1074       if (auto *intExpr{UnwrapExpr<Expr<SomeInteger>>(coex)}) {
1075         cosubscripts.push_back(
1076             ConvertToType<SubscriptInteger>(std::move(*intExpr)));
1077       } else {
1078         cosubsOk = false;
1079       }
1080     }
1081     if (cosubsOk && !reversed.empty()) {
1082       int numCosubscripts{static_cast<int>(cosubscripts.size())};
1083       const Symbol &symbol{reversed.front()};
1084       if (numCosubscripts != symbol.Corank()) {
1085         Say("'%s' has corank %d, but coindexed reference has %d cosubscripts"_err_en_US,
1086             symbol.name(), symbol.Corank(), numCosubscripts);
1087       }
1088     }
1089     // TODO: stat=/team=/team_number=
1090     // Reverse the chain of symbols so that the base is first and coarray
1091     // ultimate component is last.
1092     return Designate(
1093         DataRef{CoarrayRef{SymbolVector{reversed.crbegin(), reversed.crend()},
1094             std::move(subscripts), std::move(cosubscripts)}});
1095   }
1096   return std::nullopt;
1097 }
1098 
1099 int ExpressionAnalyzer::IntegerTypeSpecKind(
1100     const parser::IntegerTypeSpec &spec) {
1101   Expr<SubscriptInteger> value{
1102       AnalyzeKindSelector(TypeCategory::Integer, spec.v)};
1103   if (auto kind{ToInt64(value)}) {
1104     return static_cast<int>(*kind);
1105   }
1106   SayAt(spec, "Constant INTEGER kind value required here"_err_en_US);
1107   return GetDefaultKind(TypeCategory::Integer);
1108 }
1109 
1110 // Array constructors
1111 
1112 // Inverts a collection of generic ArrayConstructorValues<SomeType> that
1113 // all happen to have the same actual type T into one ArrayConstructor<T>.
1114 template <typename T>
1115 ArrayConstructorValues<T> MakeSpecific(
1116     ArrayConstructorValues<SomeType> &&from) {
1117   ArrayConstructorValues<T> to;
1118   for (ArrayConstructorValue<SomeType> &x : from) {
1119     std::visit(
1120         common::visitors{
1121             [&](common::CopyableIndirection<Expr<SomeType>> &&expr) {
1122               auto *typed{UnwrapExpr<Expr<T>>(expr.value())};
1123               to.Push(std::move(DEREF(typed)));
1124             },
1125             [&](ImpliedDo<SomeType> &&impliedDo) {
1126               to.Push(ImpliedDo<T>{impliedDo.name(),
1127                   std::move(impliedDo.lower()), std::move(impliedDo.upper()),
1128                   std::move(impliedDo.stride()),
1129                   MakeSpecific<T>(std::move(impliedDo.values()))});
1130             },
1131         },
1132         std::move(x.u));
1133   }
1134   return to;
1135 }
1136 
1137 class ArrayConstructorContext {
1138 public:
1139   ArrayConstructorContext(
1140       ExpressionAnalyzer &c, std::optional<DynamicTypeWithLength> &&t)
1141       : exprAnalyzer_{c}, type_{std::move(t)} {}
1142 
1143   void Add(const parser::AcValue &);
1144   MaybeExpr ToExpr();
1145 
1146   // These interfaces allow *this to be used as a type visitor argument to
1147   // common::SearchTypes() to convert the array constructor to a typed
1148   // expression in ToExpr().
1149   using Result = MaybeExpr;
1150   using Types = AllTypes;
1151   template <typename T> Result Test() {
1152     if (type_ && type_->category() == T::category) {
1153       if constexpr (T::category == TypeCategory::Derived) {
1154         return AsMaybeExpr(ArrayConstructor<T>{
1155             type_->GetDerivedTypeSpec(), MakeSpecific<T>(std::move(values_))});
1156       } else if (type_->kind() == T::kind) {
1157         if constexpr (T::category == TypeCategory::Character) {
1158           if (auto len{type_->LEN()}) {
1159             return AsMaybeExpr(ArrayConstructor<T>{
1160                 *std::move(len), MakeSpecific<T>(std::move(values_))});
1161           }
1162         } else {
1163           return AsMaybeExpr(
1164               ArrayConstructor<T>{MakeSpecific<T>(std::move(values_))});
1165         }
1166       }
1167     }
1168     return std::nullopt;
1169   }
1170 
1171 private:
1172   void Push(MaybeExpr &&);
1173 
1174   template <int KIND, typename A>
1175   std::optional<Expr<Type<TypeCategory::Integer, KIND>>> GetSpecificIntExpr(
1176       const A &x) {
1177     if (MaybeExpr y{exprAnalyzer_.Analyze(x)}) {
1178       Expr<SomeInteger> *intExpr{UnwrapExpr<Expr<SomeInteger>>(*y)};
1179       return ConvertToType<Type<TypeCategory::Integer, KIND>>(
1180           std::move(DEREF(intExpr)));
1181     }
1182     return std::nullopt;
1183   }
1184 
1185   // Nested array constructors all reference the same ExpressionAnalyzer,
1186   // which represents the nest of active implied DO loop indices.
1187   ExpressionAnalyzer &exprAnalyzer_;
1188   std::optional<DynamicTypeWithLength> type_;
1189   bool explicitType_{type_.has_value()};
1190   std::optional<std::int64_t> constantLength_;
1191   ArrayConstructorValues<SomeType> values_;
1192 };
1193 
1194 void ArrayConstructorContext::Push(MaybeExpr &&x) {
1195   if (!x) {
1196     return;
1197   }
1198   if (auto dyType{x->GetType()}) {
1199     DynamicTypeWithLength xType{*dyType};
1200     if (Expr<SomeCharacter> * charExpr{UnwrapExpr<Expr<SomeCharacter>>(*x)}) {
1201       CHECK(xType.category() == TypeCategory::Character);
1202       xType.length =
1203           std::visit([](const auto &kc) { return kc.LEN(); }, charExpr->u);
1204     }
1205     if (!type_) {
1206       // If there is no explicit type-spec in an array constructor, the type
1207       // of the array is the declared type of all of the elements, which must
1208       // be well-defined and all match.
1209       // TODO: Possible language extension: use the most general type of
1210       // the values as the type of a numeric constructed array, convert all
1211       // of the other values to that type.  Alternative: let the first value
1212       // determine the type, and convert the others to that type.
1213       CHECK(!explicitType_);
1214       type_ = std::move(xType);
1215       constantLength_ = ToInt64(type_->length);
1216       values_.Push(std::move(*x));
1217     } else if (!explicitType_) {
1218       if (static_cast<const DynamicType &>(*type_) ==
1219           static_cast<const DynamicType &>(xType)) {
1220         values_.Push(std::move(*x));
1221         if (auto thisLen{ToInt64(xType.LEN())}) {
1222           if (constantLength_) {
1223             if (exprAnalyzer_.context().warnOnNonstandardUsage() &&
1224                 *thisLen != *constantLength_) {
1225               exprAnalyzer_.Say(
1226                   "Character literal in array constructor without explicit "
1227                   "type has different length than earlier element"_en_US);
1228             }
1229             if (*thisLen > *constantLength_) {
1230               // Language extension: use the longest literal to determine the
1231               // length of the array constructor's character elements, not the
1232               // first, when there is no explicit type.
1233               *constantLength_ = *thisLen;
1234               type_->length = xType.LEN();
1235             }
1236           } else {
1237             constantLength_ = *thisLen;
1238             type_->length = xType.LEN();
1239           }
1240         }
1241       } else {
1242         exprAnalyzer_.Say(
1243             "Values in array constructor must have the same declared type "
1244             "when no explicit type appears"_err_en_US);
1245       }
1246     } else {
1247       if (auto cast{ConvertToType(*type_, std::move(*x))}) {
1248         values_.Push(std::move(*cast));
1249       } else {
1250         exprAnalyzer_.Say(
1251             "Value in array constructor could not be converted to the type "
1252             "of the array"_err_en_US);
1253       }
1254     }
1255   }
1256 }
1257 
1258 void ArrayConstructorContext::Add(const parser::AcValue &x) {
1259   using IntType = ResultType<ImpliedDoIndex>;
1260   std::visit(
1261       common::visitors{
1262           [&](const parser::AcValue::Triplet &triplet) {
1263             // Transform l:u(:s) into (_,_=l,u(,s)) with an anonymous index '_'
1264             std::optional<Expr<IntType>> lower{
1265                 GetSpecificIntExpr<IntType::kind>(std::get<0>(triplet.t))};
1266             std::optional<Expr<IntType>> upper{
1267                 GetSpecificIntExpr<IntType::kind>(std::get<1>(triplet.t))};
1268             std::optional<Expr<IntType>> stride{
1269                 GetSpecificIntExpr<IntType::kind>(std::get<2>(triplet.t))};
1270             if (lower && upper) {
1271               if (!stride) {
1272                 stride = Expr<IntType>{1};
1273               }
1274               if (!type_) {
1275                 type_ = DynamicTypeWithLength{IntType::GetType()};
1276               }
1277               auto v{std::move(values_)};
1278               parser::CharBlock anonymous;
1279               Push(Expr<SomeType>{
1280                   Expr<SomeInteger>{Expr<IntType>{ImpliedDoIndex{anonymous}}}});
1281               std::swap(v, values_);
1282               values_.Push(ImpliedDo<SomeType>{anonymous, std::move(*lower),
1283                   std::move(*upper), std::move(*stride), std::move(v)});
1284             }
1285           },
1286           [&](const common::Indirection<parser::Expr> &expr) {
1287             auto restorer{exprAnalyzer_.GetContextualMessages().SetLocation(
1288                 expr.value().source)};
1289             if (MaybeExpr v{exprAnalyzer_.Analyze(expr.value())}) {
1290               Push(std::move(*v));
1291             }
1292           },
1293           [&](const common::Indirection<parser::AcImpliedDo> &impliedDo) {
1294             const auto &control{
1295                 std::get<parser::AcImpliedDoControl>(impliedDo.value().t)};
1296             const auto &bounds{
1297                 std::get<parser::AcImpliedDoControl::Bounds>(control.t)};
1298             exprAnalyzer_.Analyze(bounds.name);
1299             parser::CharBlock name{bounds.name.thing.thing.source};
1300             const Symbol *symbol{bounds.name.thing.thing.symbol};
1301             int kind{IntType::kind};
1302             if (const auto dynamicType{DynamicType::From(symbol)}) {
1303               kind = dynamicType->kind();
1304             }
1305             if (exprAnalyzer_.AddAcImpliedDo(name, kind)) {
1306               std::optional<Expr<IntType>> lower{
1307                   GetSpecificIntExpr<IntType::kind>(bounds.lower)};
1308               std::optional<Expr<IntType>> upper{
1309                   GetSpecificIntExpr<IntType::kind>(bounds.upper)};
1310               if (lower && upper) {
1311                 std::optional<Expr<IntType>> stride{
1312                     GetSpecificIntExpr<IntType::kind>(bounds.step)};
1313                 auto v{std::move(values_)};
1314                 for (const auto &value :
1315                     std::get<std::list<parser::AcValue>>(impliedDo.value().t)) {
1316                   Add(value);
1317                 }
1318                 if (!stride) {
1319                   stride = Expr<IntType>{1};
1320                 }
1321                 std::swap(v, values_);
1322                 values_.Push(ImpliedDo<SomeType>{name, std::move(*lower),
1323                     std::move(*upper), std::move(*stride), std::move(v)});
1324               }
1325               exprAnalyzer_.RemoveAcImpliedDo(name);
1326             } else {
1327               exprAnalyzer_.SayAt(name,
1328                   "Implied DO index is active in surrounding implied DO loop "
1329                   "and may not have the same name"_err_en_US);
1330             }
1331           },
1332       },
1333       x.u);
1334 }
1335 
1336 MaybeExpr ArrayConstructorContext::ToExpr() {
1337   return common::SearchTypes(std::move(*this));
1338 }
1339 
1340 MaybeExpr ExpressionAnalyzer::Analyze(const parser::ArrayConstructor &array) {
1341   const parser::AcSpec &acSpec{array.v};
1342   ArrayConstructorContext acContext{*this, AnalyzeTypeSpec(acSpec.type)};
1343   for (const parser::AcValue &value : acSpec.values) {
1344     acContext.Add(value);
1345   }
1346   return acContext.ToExpr();
1347 }
1348 
1349 MaybeExpr ExpressionAnalyzer::Analyze(
1350     const parser::StructureConstructor &structure) {
1351   auto &parsedType{std::get<parser::DerivedTypeSpec>(structure.t)};
1352   parser::CharBlock typeName{std::get<parser::Name>(parsedType.t).source};
1353   if (!parsedType.derivedTypeSpec) {
1354     return std::nullopt;
1355   }
1356   const auto &spec{*parsedType.derivedTypeSpec};
1357   const Symbol &typeSymbol{spec.typeSymbol()};
1358   if (!spec.scope() || !typeSymbol.has<semantics::DerivedTypeDetails>()) {
1359     return std::nullopt; // error recovery
1360   }
1361   const auto &typeDetails{typeSymbol.get<semantics::DerivedTypeDetails>()};
1362   const Symbol *parentComponent{typeDetails.GetParentComponent(*spec.scope())};
1363 
1364   if (typeSymbol.attrs().test(semantics::Attr::ABSTRACT)) { // C796
1365     AttachDeclaration(Say(typeName,
1366                           "ABSTRACT derived type '%s' may not be used in a "
1367                           "structure constructor"_err_en_US,
1368                           typeName),
1369         typeSymbol);
1370   }
1371 
1372   // This iterator traverses all of the components in the derived type and its
1373   // parents.  The symbols for whole parent components appear after their
1374   // own components and before the components of the types that extend them.
1375   // E.g., TYPE :: A; REAL X; END TYPE
1376   //       TYPE, EXTENDS(A) :: B; REAL Y; END TYPE
1377   // produces the component list X, A, Y.
1378   // The order is important below because a structure constructor can
1379   // initialize X or A by name, but not both.
1380   auto components{semantics::OrderedComponentIterator{spec}};
1381   auto nextAnonymous{components.begin()};
1382 
1383   std::set<parser::CharBlock> unavailable;
1384   bool anyKeyword{false};
1385   StructureConstructor result{spec};
1386   bool checkConflicts{true}; // until we hit one
1387 
1388   for (const auto &component :
1389       std::get<std::list<parser::ComponentSpec>>(structure.t)) {
1390     const parser::Expr &expr{
1391         std::get<parser::ComponentDataSource>(component.t).v.value()};
1392     parser::CharBlock source{expr.source};
1393     auto &messages{GetContextualMessages()};
1394     auto restorer{messages.SetLocation(source)};
1395     const Symbol *symbol{nullptr};
1396     MaybeExpr value{Analyze(expr)};
1397     std::optional<DynamicType> valueType{DynamicType::From(value)};
1398     if (const auto &kw{std::get<std::optional<parser::Keyword>>(component.t)}) {
1399       anyKeyword = true;
1400       source = kw->v.source;
1401       symbol = kw->v.symbol;
1402       if (!symbol) {
1403         auto componentIter{std::find_if(components.begin(), components.end(),
1404             [=](const Symbol &symbol) { return symbol.name() == source; })};
1405         if (componentIter != components.end()) {
1406           symbol = &*componentIter;
1407         }
1408       }
1409       if (!symbol) { // C7101
1410         Say(source,
1411             "Keyword '%s=' does not name a component of derived type '%s'"_err_en_US,
1412             source, typeName);
1413       }
1414     } else {
1415       if (anyKeyword) { // C7100
1416         Say(source,
1417             "Value in structure constructor lacks a component name"_err_en_US);
1418         checkConflicts = false; // stem cascade
1419       }
1420       // Here's a regrettably common extension of the standard: anonymous
1421       // initialization of parent components, e.g., T(PT(1)) rather than
1422       // T(1) or T(PT=PT(1)).
1423       if (nextAnonymous == components.begin() && parentComponent &&
1424           valueType == DynamicType::From(*parentComponent) &&
1425           context().IsEnabled(LanguageFeature::AnonymousParents)) {
1426         auto iter{
1427             std::find(components.begin(), components.end(), *parentComponent)};
1428         if (iter != components.end()) {
1429           symbol = parentComponent;
1430           nextAnonymous = ++iter;
1431           if (context().ShouldWarn(LanguageFeature::AnonymousParents)) {
1432             Say(source,
1433                 "Whole parent component '%s' in structure "
1434                 "constructor should not be anonymous"_en_US,
1435                 symbol->name());
1436           }
1437         }
1438       }
1439       while (!symbol && nextAnonymous != components.end()) {
1440         const Symbol &next{*nextAnonymous};
1441         ++nextAnonymous;
1442         if (!next.test(Symbol::Flag::ParentComp)) {
1443           symbol = &next;
1444         }
1445       }
1446       if (!symbol) {
1447         Say(source, "Unexpected value in structure constructor"_err_en_US);
1448       }
1449     }
1450     if (symbol) {
1451       if (const auto *currScope{context_.globalScope().FindScope(source)}) {
1452         if (auto msg{CheckAccessibleComponent(*currScope, *symbol)}) {
1453           Say(source, *msg);
1454         }
1455       }
1456       if (checkConflicts) {
1457         auto componentIter{
1458             std::find(components.begin(), components.end(), *symbol)};
1459         if (unavailable.find(symbol->name()) != unavailable.cend()) {
1460           // C797, C798
1461           Say(source,
1462               "Component '%s' conflicts with another component earlier in "
1463               "this structure constructor"_err_en_US,
1464               symbol->name());
1465         } else if (symbol->test(Symbol::Flag::ParentComp)) {
1466           // Make earlier components unavailable once a whole parent appears.
1467           for (auto it{components.begin()}; it != componentIter; ++it) {
1468             unavailable.insert(it->name());
1469           }
1470         } else {
1471           // Make whole parent components unavailable after any of their
1472           // constituents appear.
1473           for (auto it{componentIter}; it != components.end(); ++it) {
1474             if (it->test(Symbol::Flag::ParentComp)) {
1475               unavailable.insert(it->name());
1476             }
1477           }
1478         }
1479       }
1480       unavailable.insert(symbol->name());
1481       if (value) {
1482         if (symbol->has<semantics::ProcEntityDetails>()) {
1483           CHECK(IsPointer(*symbol));
1484         } else if (symbol->has<semantics::ObjectEntityDetails>()) {
1485           // C1594(4)
1486           const auto &innermost{context_.FindScope(expr.source)};
1487           if (const auto *pureProc{FindPureProcedureContaining(innermost)}) {
1488             if (const Symbol * pointer{FindPointerComponent(*symbol)}) {
1489               if (const Symbol *
1490                   object{FindExternallyVisibleObject(*value, *pureProc)}) {
1491                 if (auto *msg{Say(expr.source,
1492                         "Externally visible object '%s' may not be "
1493                         "associated with pointer component '%s' in a "
1494                         "pure procedure"_err_en_US,
1495                         object->name(), pointer->name())}) {
1496                   msg->Attach(object->name(), "Object declaration"_en_US)
1497                       .Attach(pointer->name(), "Pointer declaration"_en_US);
1498                 }
1499               }
1500             }
1501           }
1502         } else if (symbol->has<semantics::TypeParamDetails>()) {
1503           Say(expr.source,
1504               "Type parameter '%s' may not appear as a component "
1505               "of a structure constructor"_err_en_US,
1506               symbol->name());
1507           continue;
1508         } else {
1509           Say(expr.source,
1510               "Component '%s' is neither a procedure pointer "
1511               "nor a data object"_err_en_US,
1512               symbol->name());
1513           continue;
1514         }
1515         if (IsPointer(*symbol)) {
1516           semantics::CheckPointerAssignment(
1517               GetFoldingContext(), *symbol, *value); // C7104, C7105
1518           result.Add(*symbol, Fold(std::move(*value)));
1519         } else if (MaybeExpr converted{
1520                        ConvertToType(*symbol, std::move(*value))}) {
1521           result.Add(*symbol, std::move(*converted));
1522         } else if (IsAllocatable(*symbol) &&
1523             std::holds_alternative<NullPointer>(value->u)) {
1524           // NULL() with no arguments allowed by 7.5.10 para 6 for ALLOCATABLE
1525         } else if (auto symType{DynamicType::From(symbol)}) {
1526           if (valueType) {
1527             AttachDeclaration(
1528                 Say(expr.source,
1529                     "Value in structure constructor of type %s is "
1530                     "incompatible with component '%s' of type %s"_err_en_US,
1531                     valueType->AsFortran(), symbol->name(),
1532                     symType->AsFortran()),
1533                 *symbol);
1534           } else {
1535             AttachDeclaration(
1536                 Say(expr.source,
1537                     "Value in structure constructor is incompatible with "
1538                     " component '%s' of type %s"_err_en_US,
1539                     symbol->name(), symType->AsFortran()),
1540                 *symbol);
1541           }
1542         }
1543       }
1544     }
1545   }
1546 
1547   // Ensure that unmentioned component objects have default initializers.
1548   for (const Symbol &symbol : components) {
1549     if (!symbol.test(Symbol::Flag::ParentComp) &&
1550         unavailable.find(symbol.name()) == unavailable.cend() &&
1551         !IsAllocatable(symbol)) {
1552       if (const auto *details{
1553               symbol.detailsIf<semantics::ObjectEntityDetails>()}) {
1554         if (details->init()) {
1555           result.Add(symbol, common::Clone(*details->init()));
1556         } else { // C799
1557           AttachDeclaration(Say(typeName,
1558                                 "Structure constructor lacks a value for "
1559                                 "component '%s'"_err_en_US,
1560                                 symbol.name()),
1561               symbol);
1562         }
1563       }
1564     }
1565   }
1566 
1567   return AsMaybeExpr(Expr<SomeDerived>{std::move(result)});
1568 }
1569 
1570 static std::optional<parser::CharBlock> GetPassName(
1571     const semantics::Symbol &proc) {
1572   return std::visit(
1573       [](const auto &details) {
1574         if constexpr (std::is_base_of_v<semantics::WithPassArg,
1575                           std::decay_t<decltype(details)>>) {
1576           return details.passName();
1577         } else {
1578           return std::optional<parser::CharBlock>{};
1579         }
1580       },
1581       proc.details());
1582 }
1583 
1584 static int GetPassIndex(const Symbol &proc) {
1585   CHECK(!proc.attrs().test(semantics::Attr::NOPASS));
1586   std::optional<parser::CharBlock> passName{GetPassName(proc)};
1587   const auto *interface{semantics::FindInterface(proc)};
1588   if (!passName || !interface) {
1589     return 0; // first argument is passed-object
1590   }
1591   const auto &subp{interface->get<semantics::SubprogramDetails>()};
1592   int index{0};
1593   for (const auto *arg : subp.dummyArgs()) {
1594     if (arg && arg->name() == passName) {
1595       return index;
1596     }
1597     ++index;
1598   }
1599   DIE("PASS argument name not in dummy argument list");
1600 }
1601 
1602 // Injects an expression into an actual argument list as the "passed object"
1603 // for a type-bound procedure reference that is not NOPASS.  Adds an
1604 // argument keyword if possible, but not when the passed object goes
1605 // before a positional argument.
1606 // e.g., obj%tbp(x) -> tbp(obj,x).
1607 static void AddPassArg(ActualArguments &actuals, const Expr<SomeDerived> &expr,
1608     const Symbol &component, bool isPassedObject = true) {
1609   if (component.attrs().test(semantics::Attr::NOPASS)) {
1610     return;
1611   }
1612   int passIndex{GetPassIndex(component)};
1613   auto iter{actuals.begin()};
1614   int at{0};
1615   while (iter < actuals.end() && at < passIndex) {
1616     if (*iter && (*iter)->keyword()) {
1617       iter = actuals.end();
1618       break;
1619     }
1620     ++iter;
1621     ++at;
1622   }
1623   ActualArgument passed{AsGenericExpr(common::Clone(expr))};
1624   passed.set_isPassedObject(isPassedObject);
1625   if (iter == actuals.end()) {
1626     if (auto passName{GetPassName(component)}) {
1627       passed.set_keyword(*passName);
1628     }
1629   }
1630   actuals.emplace(iter, std::move(passed));
1631 }
1632 
1633 // Return the compile-time resolution of a procedure binding, if possible.
1634 static const Symbol *GetBindingResolution(
1635     const std::optional<DynamicType> &baseType, const Symbol &component) {
1636   const auto *binding{component.detailsIf<semantics::ProcBindingDetails>()};
1637   if (!binding) {
1638     return nullptr;
1639   }
1640   if (!component.attrs().test(semantics::Attr::NON_OVERRIDABLE) &&
1641       (!baseType || baseType->IsPolymorphic())) {
1642     return nullptr;
1643   }
1644   return &binding->symbol();
1645 }
1646 
1647 auto ExpressionAnalyzer::AnalyzeProcedureComponentRef(
1648     const parser::ProcComponentRef &pcr, ActualArguments &&arguments)
1649     -> std::optional<CalleeAndArguments> {
1650   const parser::StructureComponent &sc{pcr.v.thing};
1651   const auto &name{sc.component.source};
1652   if (MaybeExpr base{Analyze(sc.base)}) {
1653     if (const Symbol * sym{sc.component.symbol}) {
1654       if (auto *dtExpr{UnwrapExpr<Expr<SomeDerived>>(*base)}) {
1655         if (sym->has<semantics::GenericDetails>()) {
1656           AdjustActuals adjustment{
1657               [&](const Symbol &proc, ActualArguments &actuals) {
1658                 if (!proc.attrs().test(semantics::Attr::NOPASS)) {
1659                   AddPassArg(actuals, std::move(*dtExpr), proc);
1660                 }
1661                 return true;
1662               }};
1663           sym = ResolveGeneric(*sym, arguments, adjustment);
1664           if (!sym) {
1665             EmitGenericResolutionError(*sc.component.symbol);
1666             return std::nullopt;
1667           }
1668         }
1669         if (const Symbol *
1670             resolution{GetBindingResolution(dtExpr->GetType(), *sym)}) {
1671           AddPassArg(arguments, std::move(*dtExpr), *sym, false);
1672           return CalleeAndArguments{
1673               ProcedureDesignator{*resolution}, std::move(arguments)};
1674         } else if (std::optional<DataRef> dataRef{
1675                        ExtractDataRef(std::move(*dtExpr))}) {
1676           if (sym->attrs().test(semantics::Attr::NOPASS)) {
1677             return CalleeAndArguments{
1678                 ProcedureDesignator{Component{std::move(*dataRef), *sym}},
1679                 std::move(arguments)};
1680           } else {
1681             AddPassArg(arguments,
1682                 Expr<SomeDerived>{Designator<SomeDerived>{std::move(*dataRef)}},
1683                 *sym);
1684             return CalleeAndArguments{
1685                 ProcedureDesignator{*sym}, std::move(arguments)};
1686           }
1687         }
1688       }
1689       Say(name,
1690           "Base of procedure component reference is not a derived-type object"_err_en_US);
1691     }
1692   }
1693   CHECK(!GetContextualMessages().empty());
1694   return std::nullopt;
1695 }
1696 
1697 // Can actual be argument associated with dummy?
1698 static bool CheckCompatibleArgument(bool isElemental,
1699     const ActualArgument &actual, const characteristics::DummyArgument &dummy) {
1700   return std::visit(
1701       common::visitors{
1702           [&](const characteristics::DummyDataObject &x) {
1703             characteristics::TypeAndShape dummyTypeAndShape{x.type};
1704             if (!isElemental && actual.Rank() != dummyTypeAndShape.Rank()) {
1705               return false;
1706             } else if (auto actualType{actual.GetType()}) {
1707               return dummyTypeAndShape.type().IsTkCompatibleWith(*actualType);
1708             } else {
1709               return false;
1710             }
1711           },
1712           [&](const characteristics::DummyProcedure &) {
1713             const auto *expr{actual.UnwrapExpr()};
1714             return expr && IsProcedurePointer(*expr);
1715           },
1716           [&](const characteristics::AlternateReturn &) {
1717             return actual.isAlternateReturn();
1718           },
1719       },
1720       dummy.u);
1721 }
1722 
1723 // Are the actual arguments compatible with the dummy arguments of procedure?
1724 static bool CheckCompatibleArguments(
1725     const characteristics::Procedure &procedure,
1726     const ActualArguments &actuals) {
1727   bool isElemental{procedure.IsElemental()};
1728   const auto &dummies{procedure.dummyArguments};
1729   CHECK(dummies.size() == actuals.size());
1730   for (std::size_t i{0}; i < dummies.size(); ++i) {
1731     const characteristics::DummyArgument &dummy{dummies[i]};
1732     const std::optional<ActualArgument> &actual{actuals[i]};
1733     if (actual && !CheckCompatibleArgument(isElemental, *actual, dummy)) {
1734       return false;
1735     }
1736   }
1737   return true;
1738 }
1739 
1740 // Handles a forward reference to a module function from what must
1741 // be a specification expression.  Return false if the symbol is
1742 // an invalid forward reference.
1743 bool ExpressionAnalyzer::ResolveForward(const Symbol &symbol) {
1744   if (context_.HasError(symbol)) {
1745     return false;
1746   }
1747   if (const auto *details{
1748           symbol.detailsIf<semantics::SubprogramNameDetails>()}) {
1749     if (details->kind() == semantics::SubprogramKind::Module) {
1750       // If this symbol is still a SubprogramNameDetails, we must be
1751       // checking a specification expression in a sibling module
1752       // procedure.  Resolve its names now so that its interface
1753       // is known.
1754       semantics::ResolveSpecificationParts(context_, symbol);
1755       if (symbol.has<semantics::SubprogramNameDetails>()) {
1756         // When the symbol hasn't had its details updated, we must have
1757         // already been in the process of resolving the function's
1758         // specification part; but recursive function calls are not
1759         // allowed in specification parts (10.1.11 para 5).
1760         Say("The module function '%s' may not be referenced recursively in a specification expression"_err_en_US,
1761             symbol.name());
1762         context_.SetError(const_cast<Symbol &>(symbol));
1763         return false;
1764       }
1765     } else { // 10.1.11 para 4
1766       Say("The internal function '%s' may not be referenced in a specification expression"_err_en_US,
1767           symbol.name());
1768       context_.SetError(const_cast<Symbol &>(symbol));
1769       return false;
1770     }
1771   }
1772   return true;
1773 }
1774 
1775 // Resolve a call to a generic procedure with given actual arguments.
1776 // adjustActuals is called on procedure bindings to handle pass arg.
1777 const Symbol *ExpressionAnalyzer::ResolveGeneric(const Symbol &symbol,
1778     const ActualArguments &actuals, const AdjustActuals &adjustActuals,
1779     bool mightBeStructureConstructor) {
1780   const Symbol *elemental{nullptr}; // matching elemental specific proc
1781   const auto &details{symbol.GetUltimate().get<semantics::GenericDetails>()};
1782   for (const Symbol &specific : details.specificProcs()) {
1783     if (!ResolveForward(specific)) {
1784       continue;
1785     }
1786     if (std::optional<characteristics::Procedure> procedure{
1787             characteristics::Procedure::Characterize(
1788                 ProcedureDesignator{specific}, context_.intrinsics())}) {
1789       ActualArguments localActuals{actuals};
1790       if (specific.has<semantics::ProcBindingDetails>()) {
1791         if (!adjustActuals.value()(specific, localActuals)) {
1792           continue;
1793         }
1794       }
1795       if (semantics::CheckInterfaceForGeneric(
1796               *procedure, localActuals, GetFoldingContext())) {
1797         if (CheckCompatibleArguments(*procedure, localActuals)) {
1798           if (!procedure->IsElemental()) {
1799             return &specific; // takes priority over elemental match
1800           }
1801           elemental = &specific;
1802         }
1803       }
1804     }
1805   }
1806   if (elemental) {
1807     return elemental;
1808   }
1809   // Check parent derived type
1810   if (const auto *parentScope{symbol.owner().GetDerivedTypeParent()}) {
1811     if (const Symbol * extended{parentScope->FindComponent(symbol.name())}) {
1812       if (extended->GetUltimate().has<semantics::GenericDetails>()) {
1813         if (const Symbol *
1814             result{ResolveGeneric(*extended, actuals, adjustActuals, false)}) {
1815           return result;
1816         }
1817       }
1818     }
1819   }
1820   if (mightBeStructureConstructor && details.derivedType()) {
1821     return details.derivedType();
1822   }
1823   return nullptr;
1824 }
1825 
1826 void ExpressionAnalyzer::EmitGenericResolutionError(const Symbol &symbol) {
1827   if (semantics::IsGenericDefinedOp(symbol)) {
1828     Say("No specific procedure of generic operator '%s' matches the actual arguments"_err_en_US,
1829         symbol.name());
1830   } else {
1831     Say("No specific procedure of generic '%s' matches the actual arguments"_err_en_US,
1832         symbol.name());
1833   }
1834 }
1835 
1836 auto ExpressionAnalyzer::GetCalleeAndArguments(
1837     const parser::ProcedureDesignator &pd, ActualArguments &&arguments,
1838     bool isSubroutine, bool mightBeStructureConstructor)
1839     -> std::optional<CalleeAndArguments> {
1840   return std::visit(
1841       common::visitors{
1842           [&](const parser::Name &name) {
1843             return GetCalleeAndArguments(name, std::move(arguments),
1844                 isSubroutine, mightBeStructureConstructor);
1845           },
1846           [&](const parser::ProcComponentRef &pcr) {
1847             return AnalyzeProcedureComponentRef(pcr, std::move(arguments));
1848           },
1849       },
1850       pd.u);
1851 }
1852 
1853 auto ExpressionAnalyzer::GetCalleeAndArguments(const parser::Name &name,
1854     ActualArguments &&arguments, bool isSubroutine,
1855     bool mightBeStructureConstructor) -> std::optional<CalleeAndArguments> {
1856   const Symbol *symbol{name.symbol};
1857   if (context_.HasError(symbol)) {
1858     return std::nullopt; // also handles null symbol
1859   }
1860   const Symbol &ultimate{DEREF(symbol).GetUltimate()};
1861   if (ultimate.attrs().test(semantics::Attr::INTRINSIC)) {
1862     if (std::optional<SpecificCall> specificCall{context_.intrinsics().Probe(
1863             CallCharacteristics{ultimate.name().ToString(), isSubroutine},
1864             arguments, GetFoldingContext())}) {
1865       return CalleeAndArguments{
1866           ProcedureDesignator{std::move(specificCall->specificIntrinsic)},
1867           std::move(specificCall->arguments)};
1868     }
1869   } else {
1870     CheckForBadRecursion(name.source, ultimate);
1871     if (ultimate.has<semantics::GenericDetails>()) {
1872       ExpressionAnalyzer::AdjustActuals noAdjustment;
1873       symbol = ResolveGeneric(
1874           *symbol, arguments, noAdjustment, mightBeStructureConstructor);
1875     }
1876     if (symbol) {
1877       if (symbol->GetUltimate().has<semantics::DerivedTypeDetails>()) {
1878         if (mightBeStructureConstructor) {
1879           return CalleeAndArguments{
1880               semantics::SymbolRef{*symbol}, std::move(arguments)};
1881         }
1882       } else {
1883         return CalleeAndArguments{
1884             ProcedureDesignator{*symbol}, std::move(arguments)};
1885       }
1886     } else if (std::optional<SpecificCall> specificCall{
1887                    context_.intrinsics().Probe(
1888                        CallCharacteristics{
1889                            ultimate.name().ToString(), isSubroutine},
1890                        arguments, GetFoldingContext())}) {
1891       // Generics can extend intrinsics
1892       return CalleeAndArguments{
1893           ProcedureDesignator{std::move(specificCall->specificIntrinsic)},
1894           std::move(specificCall->arguments)};
1895     } else {
1896       EmitGenericResolutionError(*name.symbol);
1897     }
1898   }
1899   return std::nullopt;
1900 }
1901 
1902 void ExpressionAnalyzer::CheckForBadRecursion(
1903     parser::CharBlock callSite, const semantics::Symbol &proc) {
1904   if (const auto *scope{proc.scope()}) {
1905     if (scope->sourceRange().Contains(callSite)) {
1906       parser::Message *msg{nullptr};
1907       if (proc.attrs().test(semantics::Attr::NON_RECURSIVE)) { // 15.6.2.1(3)
1908         msg = Say("NON_RECURSIVE procedure '%s' cannot call itself"_err_en_US,
1909             callSite);
1910       } else if (IsAssumedLengthCharacter(proc) && IsExternal(proc)) {
1911         msg = Say( // 15.6.2.1(3)
1912             "Assumed-length CHARACTER(*) function '%s' cannot call itself"_err_en_US,
1913             callSite);
1914       }
1915       AttachDeclaration(msg, proc);
1916     }
1917   }
1918 }
1919 
1920 template <typename A> static const Symbol *AssumedTypeDummy(const A &x) {
1921   if (const auto *designator{
1922           std::get_if<common::Indirection<parser::Designator>>(&x.u)}) {
1923     if (const auto *dataRef{
1924             std::get_if<parser::DataRef>(&designator->value().u)}) {
1925       if (const auto *name{std::get_if<parser::Name>(&dataRef->u)}) {
1926         if (const Symbol * symbol{name->symbol}) {
1927           if (const auto *type{symbol->GetType()}) {
1928             if (type->category() == semantics::DeclTypeSpec::TypeStar) {
1929               return symbol;
1930             }
1931           }
1932         }
1933       }
1934     }
1935   }
1936   return nullptr;
1937 }
1938 
1939 MaybeExpr ExpressionAnalyzer::Analyze(const parser::FunctionReference &funcRef,
1940     std::optional<parser::StructureConstructor> *structureConstructor) {
1941   const parser::Call &call{funcRef.v};
1942   auto restorer{GetContextualMessages().SetLocation(call.source)};
1943   ArgumentAnalyzer analyzer{*this, call.source, true /* allowAssumedType */};
1944   for (const auto &arg : std::get<std::list<parser::ActualArgSpec>>(call.t)) {
1945     analyzer.Analyze(arg, false /* not subroutine call */);
1946   }
1947   if (analyzer.fatalErrors()) {
1948     return std::nullopt;
1949   }
1950   if (std::optional<CalleeAndArguments> callee{
1951           GetCalleeAndArguments(std::get<parser::ProcedureDesignator>(call.t),
1952               analyzer.GetActuals(), false /* not subroutine */,
1953               true /* might be structure constructor */)}) {
1954     if (auto *proc{std::get_if<ProcedureDesignator>(&callee->u)}) {
1955       return MakeFunctionRef(
1956           call.source, std::move(*proc), std::move(callee->arguments));
1957     } else if (structureConstructor) {
1958       // Structure constructor misparsed as function reference?
1959       CHECK(std::holds_alternative<semantics::SymbolRef>(callee->u));
1960       const Symbol &derivedType{*std::get<semantics::SymbolRef>(callee->u)};
1961       const auto &designator{std::get<parser::ProcedureDesignator>(call.t)};
1962       if (const auto *name{std::get_if<parser::Name>(&designator.u)}) {
1963         semantics::Scope &scope{context_.FindScope(name->source)};
1964         const semantics::DeclTypeSpec &type{
1965             semantics::FindOrInstantiateDerivedType(scope,
1966                 semantics::DerivedTypeSpec{
1967                     name->source, derivedType.GetUltimate()},
1968                 context_)};
1969         auto &mutableRef{const_cast<parser::FunctionReference &>(funcRef)};
1970         *structureConstructor =
1971             mutableRef.ConvertToStructureConstructor(type.derivedTypeSpec());
1972         return Analyze(structureConstructor->value());
1973       }
1974     }
1975   }
1976   return std::nullopt;
1977 }
1978 
1979 void ExpressionAnalyzer::Analyze(const parser::CallStmt &callStmt) {
1980   const parser::Call &call{callStmt.v};
1981   auto restorer{GetContextualMessages().SetLocation(call.source)};
1982   ArgumentAnalyzer analyzer{*this, call.source, true /* allowAssumedType */};
1983   for (const auto &arg : std::get<std::list<parser::ActualArgSpec>>(call.t)) {
1984     analyzer.Analyze(arg, true /* is subroutine call */);
1985   }
1986   if (!analyzer.fatalErrors()) {
1987     if (std::optional<CalleeAndArguments> callee{
1988             GetCalleeAndArguments(std::get<parser::ProcedureDesignator>(call.t),
1989                 analyzer.GetActuals(), true /* subroutine */)}) {
1990       ProcedureDesignator *proc{std::get_if<ProcedureDesignator>(&callee->u)};
1991       CHECK(proc);
1992       if (CheckCall(call.source, *proc, callee->arguments)) {
1993         callStmt.typedCall.reset(
1994             new ProcedureRef{std::move(*proc), std::move(callee->arguments)});
1995       }
1996     }
1997   }
1998 }
1999 
2000 const Assignment *ExpressionAnalyzer::Analyze(const parser::AssignmentStmt &x) {
2001   if (!x.typedAssignment) {
2002     ArgumentAnalyzer analyzer{*this};
2003     analyzer.Analyze(std::get<parser::Variable>(x.t));
2004     analyzer.Analyze(std::get<parser::Expr>(x.t));
2005     if (analyzer.fatalErrors()) {
2006       x.typedAssignment.reset(new GenericAssignmentWrapper{});
2007     } else {
2008       std::optional<ProcedureRef> procRef{analyzer.TryDefinedAssignment()};
2009       Assignment assignment{
2010           Fold(analyzer.MoveExpr(0)), Fold(analyzer.MoveExpr(1))};
2011       if (procRef) {
2012         assignment.u = std::move(*procRef);
2013       }
2014       x.typedAssignment.reset(
2015           new GenericAssignmentWrapper{std::move(assignment)});
2016     }
2017   }
2018   return common::GetPtrFromOptional(x.typedAssignment->v);
2019 }
2020 
2021 const Assignment *ExpressionAnalyzer::Analyze(
2022     const parser::PointerAssignmentStmt &x) {
2023   if (!x.typedAssignment) {
2024     MaybeExpr lhs{Analyze(std::get<parser::DataRef>(x.t))};
2025     MaybeExpr rhs{Analyze(std::get<parser::Expr>(x.t))};
2026     if (!lhs || !rhs) {
2027       x.typedAssignment.reset(new GenericAssignmentWrapper{});
2028     } else {
2029       Assignment assignment{std::move(*lhs), std::move(*rhs)};
2030       std::visit(common::visitors{
2031                      [&](const std::list<parser::BoundsRemapping> &list) {
2032                        Assignment::BoundsRemapping bounds;
2033                        for (const auto &elem : list) {
2034                          auto lower{AsSubscript(Analyze(std::get<0>(elem.t)))};
2035                          auto upper{AsSubscript(Analyze(std::get<1>(elem.t)))};
2036                          if (lower && upper) {
2037                            bounds.emplace_back(Fold(std::move(*lower)),
2038                                Fold(std::move(*upper)));
2039                          }
2040                        }
2041                        assignment.u = std::move(bounds);
2042                      },
2043                      [&](const std::list<parser::BoundsSpec> &list) {
2044                        Assignment::BoundsSpec bounds;
2045                        for (const auto &bound : list) {
2046                          if (auto lower{AsSubscript(Analyze(bound.v))}) {
2047                            bounds.emplace_back(Fold(std::move(*lower)));
2048                          }
2049                        }
2050                        assignment.u = std::move(bounds);
2051                      },
2052                  },
2053           std::get<parser::PointerAssignmentStmt::Bounds>(x.t).u);
2054       x.typedAssignment.reset(
2055           new GenericAssignmentWrapper{std::move(assignment)});
2056     }
2057   }
2058   return common::GetPtrFromOptional(x.typedAssignment->v);
2059 }
2060 
2061 static bool IsExternalCalledImplicitly(
2062     parser::CharBlock callSite, const ProcedureDesignator &proc) {
2063   if (const auto *symbol{proc.GetSymbol()}) {
2064     return symbol->has<semantics::SubprogramDetails>() &&
2065         symbol->owner().IsGlobal() &&
2066         (!symbol->scope() /*ENTRY*/ ||
2067             !symbol->scope()->sourceRange().Contains(callSite));
2068   } else {
2069     return false;
2070   }
2071 }
2072 
2073 std::optional<characteristics::Procedure> ExpressionAnalyzer::CheckCall(
2074     parser::CharBlock callSite, const ProcedureDesignator &proc,
2075     ActualArguments &arguments) {
2076   auto chars{
2077       characteristics::Procedure::Characterize(proc, context_.intrinsics())};
2078   if (chars) {
2079     bool treatExternalAsImplicit{IsExternalCalledImplicitly(callSite, proc)};
2080     if (treatExternalAsImplicit && !chars->CanBeCalledViaImplicitInterface()) {
2081       Say(callSite,
2082           "References to the procedure '%s' require an explicit interface"_en_US,
2083           DEREF(proc.GetSymbol()).name());
2084     }
2085     semantics::CheckArguments(*chars, arguments, GetFoldingContext(),
2086         context_.FindScope(callSite), treatExternalAsImplicit);
2087     if (!chars->attrs.test(characteristics::Procedure::Attr::Pure)) {
2088       if (const semantics::Scope *
2089           pure{semantics::FindPureProcedureContaining(
2090               context_.FindScope(callSite))}) {
2091         Say(callSite,
2092             "Procedure '%s' referenced in pure subprogram '%s' must be pure too"_err_en_US,
2093             DEREF(proc.GetSymbol()).name(), DEREF(pure->symbol()).name());
2094       }
2095     }
2096   }
2097   return chars;
2098 }
2099 
2100 // Unary operations
2101 
2102 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Parentheses &x) {
2103   if (MaybeExpr operand{Analyze(x.v.value())}) {
2104     if (const semantics::Symbol * symbol{GetLastSymbol(*operand)}) {
2105       if (const semantics::Symbol * result{FindFunctionResult(*symbol)}) {
2106         if (semantics::IsProcedurePointer(*result)) {
2107           Say("A function reference that returns a procedure "
2108               "pointer may not be parenthesized"_err_en_US); // C1003
2109         }
2110       }
2111     }
2112     return Parenthesize(std::move(*operand));
2113   }
2114   return std::nullopt;
2115 }
2116 
2117 static MaybeExpr NumericUnaryHelper(ExpressionAnalyzer &context,
2118     NumericOperator opr, const parser::Expr::IntrinsicUnary &x) {
2119   ArgumentAnalyzer analyzer{context};
2120   analyzer.Analyze(x.v);
2121   if (analyzer.fatalErrors()) {
2122     return std::nullopt;
2123   } else if (analyzer.IsIntrinsicNumeric(opr)) {
2124     if (opr == NumericOperator::Add) {
2125       return analyzer.MoveExpr(0);
2126     } else {
2127       return Negation(context.GetContextualMessages(), analyzer.MoveExpr(0));
2128     }
2129   } else {
2130     return analyzer.TryDefinedOp(AsFortran(opr),
2131         "Operand of unary %s must be numeric; have %s"_err_en_US);
2132   }
2133 }
2134 
2135 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::UnaryPlus &x) {
2136   return NumericUnaryHelper(*this, NumericOperator::Add, x);
2137 }
2138 
2139 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Negate &x) {
2140   return NumericUnaryHelper(*this, NumericOperator::Subtract, x);
2141 }
2142 
2143 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::NOT &x) {
2144   ArgumentAnalyzer analyzer{*this};
2145   analyzer.Analyze(x.v);
2146   if (analyzer.fatalErrors()) {
2147     return std::nullopt;
2148   } else if (analyzer.IsIntrinsicLogical()) {
2149     return AsGenericExpr(
2150         LogicalNegation(std::get<Expr<SomeLogical>>(analyzer.MoveExpr(0).u)));
2151   } else {
2152     return analyzer.TryDefinedOp(LogicalOperator::Not,
2153         "Operand of %s must be LOGICAL; have %s"_err_en_US);
2154   }
2155 }
2156 
2157 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::PercentLoc &x) {
2158   // Represent %LOC() exactly as if it had been a call to the LOC() extension
2159   // intrinsic function.
2160   // Use the actual source for the name of the call for error reporting.
2161   std::optional<ActualArgument> arg;
2162   if (const Symbol * assumedTypeDummy{AssumedTypeDummy(x.v.value())}) {
2163     arg = ActualArgument{ActualArgument::AssumedType{*assumedTypeDummy}};
2164   } else if (MaybeExpr argExpr{Analyze(x.v.value())}) {
2165     arg = ActualArgument{std::move(*argExpr)};
2166   } else {
2167     return std::nullopt;
2168   }
2169   parser::CharBlock at{GetContextualMessages().at()};
2170   CHECK(at.size() >= 4);
2171   parser::CharBlock loc{at.begin() + 1, 3};
2172   CHECK(loc == "loc");
2173   return MakeFunctionRef(loc, ActualArguments{std::move(*arg)});
2174 }
2175 
2176 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::DefinedUnary &x) {
2177   const auto &name{std::get<parser::DefinedOpName>(x.t).v};
2178   ArgumentAnalyzer analyzer{*this, name.source};
2179   analyzer.Analyze(std::get<1>(x.t));
2180   return analyzer.TryDefinedOp(name.source.ToString().c_str(),
2181       "No operator %s defined for %s"_err_en_US, true);
2182 }
2183 
2184 // Binary (dyadic) operations
2185 
2186 template <template <typename> class OPR>
2187 MaybeExpr NumericBinaryHelper(ExpressionAnalyzer &context, NumericOperator opr,
2188     const parser::Expr::IntrinsicBinary &x) {
2189   ArgumentAnalyzer analyzer{context};
2190   analyzer.Analyze(std::get<0>(x.t));
2191   analyzer.Analyze(std::get<1>(x.t));
2192   if (analyzer.fatalErrors()) {
2193     return std::nullopt;
2194   } else if (analyzer.IsIntrinsicNumeric(opr)) {
2195     return NumericOperation<OPR>(context.GetContextualMessages(),
2196         analyzer.MoveExpr(0), analyzer.MoveExpr(1),
2197         context.GetDefaultKind(TypeCategory::Real));
2198   } else {
2199     return analyzer.TryDefinedOp(AsFortran(opr),
2200         "Operands of %s must be numeric; have %s and %s"_err_en_US);
2201   }
2202 }
2203 
2204 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Power &x) {
2205   return NumericBinaryHelper<Power>(*this, NumericOperator::Power, x);
2206 }
2207 
2208 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Multiply &x) {
2209   return NumericBinaryHelper<Multiply>(*this, NumericOperator::Multiply, x);
2210 }
2211 
2212 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Divide &x) {
2213   return NumericBinaryHelper<Divide>(*this, NumericOperator::Divide, x);
2214 }
2215 
2216 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Add &x) {
2217   return NumericBinaryHelper<Add>(*this, NumericOperator::Add, x);
2218 }
2219 
2220 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Subtract &x) {
2221   return NumericBinaryHelper<Subtract>(*this, NumericOperator::Subtract, x);
2222 }
2223 
2224 MaybeExpr ExpressionAnalyzer::Analyze(
2225     const parser::Expr::ComplexConstructor &x) {
2226   auto re{Analyze(std::get<0>(x.t).value())};
2227   auto im{Analyze(std::get<1>(x.t).value())};
2228   if (re && im) {
2229     ConformabilityCheck(GetContextualMessages(), *re, *im);
2230   }
2231   return AsMaybeExpr(ConstructComplex(GetContextualMessages(), std::move(re),
2232       std::move(im), GetDefaultKind(TypeCategory::Real)));
2233 }
2234 
2235 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Concat &x) {
2236   ArgumentAnalyzer analyzer{*this};
2237   analyzer.Analyze(std::get<0>(x.t));
2238   analyzer.Analyze(std::get<1>(x.t));
2239   if (analyzer.fatalErrors()) {
2240     return std::nullopt;
2241   } else if (analyzer.IsIntrinsicConcat()) {
2242     return std::visit(
2243         [&](auto &&x, auto &&y) -> MaybeExpr {
2244           using T = ResultType<decltype(x)>;
2245           if constexpr (std::is_same_v<T, ResultType<decltype(y)>>) {
2246             return AsGenericExpr(Concat<T::kind>{std::move(x), std::move(y)});
2247           } else {
2248             DIE("different types for intrinsic concat");
2249           }
2250         },
2251         std::move(std::get<Expr<SomeCharacter>>(analyzer.MoveExpr(0).u).u),
2252         std::move(std::get<Expr<SomeCharacter>>(analyzer.MoveExpr(1).u).u));
2253   } else {
2254     return analyzer.TryDefinedOp("//",
2255         "Operands of %s must be CHARACTER with the same kind; have %s and %s"_err_en_US);
2256   }
2257 }
2258 
2259 // The Name represents a user-defined intrinsic operator.
2260 // If the actuals match one of the specific procedures, return a function ref.
2261 // Otherwise report the error in messages.
2262 MaybeExpr ExpressionAnalyzer::AnalyzeDefinedOp(
2263     const parser::Name &name, ActualArguments &&actuals) {
2264   if (auto callee{GetCalleeAndArguments(name, std::move(actuals))}) {
2265     CHECK(std::holds_alternative<ProcedureDesignator>(callee->u));
2266     return MakeFunctionRef(name.source,
2267         std::move(std::get<ProcedureDesignator>(callee->u)),
2268         std::move(callee->arguments));
2269   } else {
2270     return std::nullopt;
2271   }
2272 }
2273 
2274 MaybeExpr RelationHelper(ExpressionAnalyzer &context, RelationalOperator opr,
2275     const parser::Expr::IntrinsicBinary &x) {
2276   ArgumentAnalyzer analyzer{context};
2277   analyzer.Analyze(std::get<0>(x.t));
2278   analyzer.Analyze(std::get<1>(x.t));
2279   if (analyzer.fatalErrors()) {
2280     return std::nullopt;
2281   } else if (analyzer.IsIntrinsicRelational(opr)) {
2282     return AsMaybeExpr(Relate(context.GetContextualMessages(), opr,
2283         analyzer.MoveExpr(0), analyzer.MoveExpr(1)));
2284   } else {
2285     return analyzer.TryDefinedOp(opr,
2286         "Operands of %s must have comparable types; have %s and %s"_err_en_US);
2287   }
2288 }
2289 
2290 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::LT &x) {
2291   return RelationHelper(*this, RelationalOperator::LT, x);
2292 }
2293 
2294 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::LE &x) {
2295   return RelationHelper(*this, RelationalOperator::LE, x);
2296 }
2297 
2298 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::EQ &x) {
2299   return RelationHelper(*this, RelationalOperator::EQ, x);
2300 }
2301 
2302 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::NE &x) {
2303   return RelationHelper(*this, RelationalOperator::NE, x);
2304 }
2305 
2306 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::GE &x) {
2307   return RelationHelper(*this, RelationalOperator::GE, x);
2308 }
2309 
2310 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::GT &x) {
2311   return RelationHelper(*this, RelationalOperator::GT, x);
2312 }
2313 
2314 MaybeExpr LogicalBinaryHelper(ExpressionAnalyzer &context, LogicalOperator opr,
2315     const parser::Expr::IntrinsicBinary &x) {
2316   ArgumentAnalyzer analyzer{context};
2317   analyzer.Analyze(std::get<0>(x.t));
2318   analyzer.Analyze(std::get<1>(x.t));
2319   if (analyzer.fatalErrors()) {
2320     return std::nullopt;
2321   } else if (analyzer.IsIntrinsicLogical()) {
2322     return AsGenericExpr(BinaryLogicalOperation(opr,
2323         std::get<Expr<SomeLogical>>(analyzer.MoveExpr(0).u),
2324         std::get<Expr<SomeLogical>>(analyzer.MoveExpr(1).u)));
2325   } else {
2326     return analyzer.TryDefinedOp(
2327         opr, "Operands of %s must be LOGICAL; have %s and %s"_err_en_US);
2328   }
2329 }
2330 
2331 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::AND &x) {
2332   return LogicalBinaryHelper(*this, LogicalOperator::And, x);
2333 }
2334 
2335 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::OR &x) {
2336   return LogicalBinaryHelper(*this, LogicalOperator::Or, x);
2337 }
2338 
2339 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::EQV &x) {
2340   return LogicalBinaryHelper(*this, LogicalOperator::Eqv, x);
2341 }
2342 
2343 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::NEQV &x) {
2344   return LogicalBinaryHelper(*this, LogicalOperator::Neqv, x);
2345 }
2346 
2347 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::DefinedBinary &x) {
2348   const auto &name{std::get<parser::DefinedOpName>(x.t).v};
2349   ArgumentAnalyzer analyzer{*this, name.source};
2350   analyzer.Analyze(std::get<1>(x.t));
2351   analyzer.Analyze(std::get<2>(x.t));
2352   return analyzer.TryDefinedOp(name.source.ToString().c_str(),
2353       "No operator %s defined for %s and %s"_err_en_US, true);
2354 }
2355 
2356 static void CheckFuncRefToArrayElementRefHasSubscripts(
2357     semantics::SemanticsContext &context,
2358     const parser::FunctionReference &funcRef) {
2359   // Emit message if the function reference fix will end up an array element
2360   // reference with no subscripts because it will not be possible to later tell
2361   // the difference in expressions between empty subscript list due to bad
2362   // subscripts error recovery or because the user did not put any.
2363   if (std::get<std::list<parser::ActualArgSpec>>(funcRef.v.t).empty()) {
2364     auto &proc{std::get<parser::ProcedureDesignator>(funcRef.v.t)};
2365     const auto *name{std::get_if<parser::Name>(&proc.u)};
2366     if (!name) {
2367       name = &std::get<parser::ProcComponentRef>(proc.u).v.thing.component;
2368     }
2369     auto &msg{context.Say(funcRef.v.source,
2370         name->symbol && name->symbol->Rank() == 0
2371             ? "'%s' is not a function"_err_en_US
2372             : "Reference to array '%s' with empty subscript list"_err_en_US,
2373         name->source)};
2374     if (name->symbol) {
2375       if (semantics::IsFunctionResultWithSameNameAsFunction(*name->symbol)) {
2376         msg.Attach(name->source,
2377             "A result variable must be declared with RESULT to allow recursive "
2378             "function calls"_en_US);
2379       } else {
2380         AttachDeclaration(&msg, *name->symbol);
2381       }
2382     }
2383   }
2384 }
2385 
2386 // Converts, if appropriate, an original misparse of ambiguous syntax like
2387 // A(1) as a function reference into an array reference.
2388 // Misparse structure constructors are detected elsewhere after generic
2389 // function call resolution fails.
2390 template <typename... A>
2391 static void FixMisparsedFunctionReference(
2392     semantics::SemanticsContext &context, const std::variant<A...> &constU) {
2393   // The parse tree is updated in situ when resolving an ambiguous parse.
2394   using uType = std::decay_t<decltype(constU)>;
2395   auto &u{const_cast<uType &>(constU)};
2396   if (auto *func{
2397           std::get_if<common::Indirection<parser::FunctionReference>>(&u)}) {
2398     parser::FunctionReference &funcRef{func->value()};
2399     auto &proc{std::get<parser::ProcedureDesignator>(funcRef.v.t)};
2400     if (Symbol *
2401         origSymbol{
2402             std::visit(common::visitors{
2403                            [&](parser::Name &name) { return name.symbol; },
2404                            [&](parser::ProcComponentRef &pcr) {
2405                              return pcr.v.thing.component.symbol;
2406                            },
2407                        },
2408                 proc.u)}) {
2409       Symbol &symbol{origSymbol->GetUltimate()};
2410       if (symbol.has<semantics::ObjectEntityDetails>() ||
2411           symbol.has<semantics::AssocEntityDetails>()) {
2412         // Note that expression in AssocEntityDetails cannot be a procedure
2413         // pointer as per C1105 so this cannot be a function reference.
2414         if constexpr (common::HasMember<common::Indirection<parser::Designator>,
2415                           uType>) {
2416           CheckFuncRefToArrayElementRefHasSubscripts(context, funcRef);
2417           u = common::Indirection{funcRef.ConvertToArrayElementRef()};
2418         } else {
2419           DIE("can't fix misparsed function as array reference");
2420         }
2421       }
2422     }
2423   }
2424 }
2425 
2426 // Common handling of parser::Expr and parser::Variable
2427 template <typename PARSED>
2428 MaybeExpr ExpressionAnalyzer::ExprOrVariable(const PARSED &x) {
2429   if (!x.typedExpr) {
2430     FixMisparsedFunctionReference(context_, x.u);
2431     MaybeExpr result;
2432     if (AssumedTypeDummy(x)) { // C710
2433       Say("TYPE(*) dummy argument may only be used as an actual argument"_err_en_US);
2434     } else {
2435       if constexpr (std::is_same_v<PARSED, parser::Expr>) {
2436         // Analyze the expression in a specified source position context for
2437         // better error reporting.
2438         auto restorer{GetContextualMessages().SetLocation(x.source)};
2439         result = evaluate::Fold(foldingContext_, Analyze(x.u));
2440       } else {
2441         result = Analyze(x.u);
2442       }
2443     }
2444     x.typedExpr.reset(new GenericExprWrapper{std::move(result)});
2445     if (!x.typedExpr->v) {
2446       if (!context_.AnyFatalError()) {
2447         std::string buf;
2448         llvm::raw_string_ostream dump{buf};
2449         parser::DumpTree(dump, x);
2450         Say("Internal error: Expression analysis failed on: %s"_err_en_US,
2451             dump.str());
2452       }
2453       fatalErrors_ = true;
2454     }
2455   }
2456   return x.typedExpr->v;
2457 }
2458 
2459 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr &expr) {
2460   auto restorer{GetContextualMessages().SetLocation(expr.source)};
2461   return ExprOrVariable(expr);
2462 }
2463 
2464 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Variable &variable) {
2465   auto restorer{GetContextualMessages().SetLocation(variable.GetSource())};
2466   return ExprOrVariable(variable);
2467 }
2468 
2469 Expr<SubscriptInteger> ExpressionAnalyzer::AnalyzeKindSelector(
2470     TypeCategory category,
2471     const std::optional<parser::KindSelector> &selector) {
2472   int defaultKind{GetDefaultKind(category)};
2473   if (!selector) {
2474     return Expr<SubscriptInteger>{defaultKind};
2475   }
2476   return std::visit(
2477       common::visitors{
2478           [&](const parser::ScalarIntConstantExpr &x) {
2479             if (MaybeExpr kind{Analyze(x)}) {
2480               Expr<SomeType> folded{Fold(std::move(*kind))};
2481               if (std::optional<std::int64_t> code{ToInt64(folded)}) {
2482                 if (CheckIntrinsicKind(category, *code)) {
2483                   return Expr<SubscriptInteger>{*code};
2484                 }
2485               } else if (auto *intExpr{UnwrapExpr<Expr<SomeInteger>>(folded)}) {
2486                 return ConvertToType<SubscriptInteger>(std::move(*intExpr));
2487               }
2488             }
2489             return Expr<SubscriptInteger>{defaultKind};
2490           },
2491           [&](const parser::KindSelector::StarSize &x) {
2492             std::intmax_t size = x.v;
2493             if (!CheckIntrinsicSize(category, size)) {
2494               size = defaultKind;
2495             } else if (category == TypeCategory::Complex) {
2496               size /= 2;
2497             }
2498             return Expr<SubscriptInteger>{size};
2499           },
2500       },
2501       selector->u);
2502 }
2503 
2504 int ExpressionAnalyzer::GetDefaultKind(common::TypeCategory category) {
2505   return context_.GetDefaultKind(category);
2506 }
2507 
2508 DynamicType ExpressionAnalyzer::GetDefaultKindOfType(
2509     common::TypeCategory category) {
2510   return {category, GetDefaultKind(category)};
2511 }
2512 
2513 bool ExpressionAnalyzer::CheckIntrinsicKind(
2514     TypeCategory category, std::int64_t kind) {
2515   if (IsValidKindOfIntrinsicType(category, kind)) { // C712, C714, C715, C727
2516     return true;
2517   } else {
2518     Say("%s(KIND=%jd) is not a supported type"_err_en_US,
2519         ToUpperCase(EnumToString(category)), kind);
2520     return false;
2521   }
2522 }
2523 
2524 bool ExpressionAnalyzer::CheckIntrinsicSize(
2525     TypeCategory category, std::int64_t size) {
2526   if (category == TypeCategory::Complex) {
2527     // COMPLEX*16 == COMPLEX(KIND=8)
2528     if (size % 2 == 0 && IsValidKindOfIntrinsicType(category, size / 2)) {
2529       return true;
2530     }
2531   } else if (IsValidKindOfIntrinsicType(category, size)) {
2532     return true;
2533   }
2534   Say("%s*%jd is not a supported type"_err_en_US,
2535       ToUpperCase(EnumToString(category)), size);
2536   return false;
2537 }
2538 
2539 bool ExpressionAnalyzer::AddAcImpliedDo(parser::CharBlock name, int kind) {
2540   return acImpliedDos_.insert(std::make_pair(name, kind)).second;
2541 }
2542 
2543 void ExpressionAnalyzer::RemoveAcImpliedDo(parser::CharBlock name) {
2544   auto iter{acImpliedDos_.find(name)};
2545   if (iter != acImpliedDos_.end()) {
2546     acImpliedDos_.erase(iter);
2547   }
2548 }
2549 
2550 std::optional<int> ExpressionAnalyzer::IsAcImpliedDo(
2551     parser::CharBlock name) const {
2552   auto iter{acImpliedDos_.find(name)};
2553   if (iter != acImpliedDos_.cend()) {
2554     return {iter->second};
2555   } else {
2556     return std::nullopt;
2557   }
2558 }
2559 
2560 bool ExpressionAnalyzer::EnforceTypeConstraint(parser::CharBlock at,
2561     const MaybeExpr &result, TypeCategory category, bool defaultKind) {
2562   if (result) {
2563     if (auto type{result->GetType()}) {
2564       if (type->category() != category) { // C885
2565         Say(at, "Must have %s type, but is %s"_err_en_US,
2566             ToUpperCase(EnumToString(category)),
2567             ToUpperCase(type->AsFortran()));
2568         return false;
2569       } else if (defaultKind) {
2570         int kind{context_.GetDefaultKind(category)};
2571         if (type->kind() != kind) {
2572           Say(at, "Must have default kind(%d) of %s type, but is %s"_err_en_US,
2573               kind, ToUpperCase(EnumToString(category)),
2574               ToUpperCase(type->AsFortran()));
2575           return false;
2576         }
2577       }
2578     } else {
2579       Say(at, "Must have %s type, but is typeless"_err_en_US,
2580           ToUpperCase(EnumToString(category)));
2581       return false;
2582     }
2583   }
2584   return true;
2585 }
2586 
2587 MaybeExpr ExpressionAnalyzer::MakeFunctionRef(parser::CharBlock callSite,
2588     ProcedureDesignator &&proc, ActualArguments &&arguments) {
2589   if (const auto *intrinsic{std::get_if<SpecificIntrinsic>(&proc.u)}) {
2590     if (intrinsic->name == "null" && arguments.empty()) {
2591       return Expr<SomeType>{NullPointer{}};
2592     }
2593   }
2594   if (const Symbol * symbol{proc.GetSymbol()}) {
2595     if (!ResolveForward(*symbol)) {
2596       return std::nullopt;
2597     }
2598   }
2599   if (auto chars{CheckCall(callSite, proc, arguments)}) {
2600     if (chars->functionResult) {
2601       const auto &result{*chars->functionResult};
2602       if (result.IsProcedurePointer()) {
2603         return Expr<SomeType>{
2604             ProcedureRef{std::move(proc), std::move(arguments)}};
2605       } else {
2606         // Not a procedure pointer, so type and shape are known.
2607         return TypedWrapper<FunctionRef, ProcedureRef>(
2608             DEREF(result.GetTypeAndShape()).type(),
2609             ProcedureRef{std::move(proc), std::move(arguments)});
2610       }
2611     }
2612   }
2613   return std::nullopt;
2614 }
2615 
2616 MaybeExpr ExpressionAnalyzer::MakeFunctionRef(
2617     parser::CharBlock intrinsic, ActualArguments &&arguments) {
2618   if (std::optional<SpecificCall> specificCall{
2619           context_.intrinsics().Probe(CallCharacteristics{intrinsic.ToString()},
2620               arguments, context_.foldingContext())}) {
2621     return MakeFunctionRef(intrinsic,
2622         ProcedureDesignator{std::move(specificCall->specificIntrinsic)},
2623         std::move(specificCall->arguments));
2624   } else {
2625     return std::nullopt;
2626   }
2627 }
2628 
2629 void ArgumentAnalyzer::Analyze(const parser::Variable &x) {
2630   source_.ExtendToCover(x.GetSource());
2631   if (MaybeExpr expr{context_.Analyze(x)}) {
2632     if (!IsConstantExpr(*expr)) {
2633       actuals_.emplace_back(std::move(*expr));
2634       return;
2635     }
2636     const Symbol *symbol{GetFirstSymbol(*expr)};
2637     context_.Say(x.GetSource(),
2638         "Assignment to constant '%s' is not allowed"_err_en_US,
2639         symbol ? symbol->name() : x.GetSource());
2640   }
2641   fatalErrors_ = true;
2642 }
2643 
2644 void ArgumentAnalyzer::Analyze(
2645     const parser::ActualArgSpec &arg, bool isSubroutine) {
2646   // TODO: C1002: Allow a whole assumed-size array to appear if the dummy
2647   // argument would accept it.  Handle by special-casing the context
2648   // ActualArg -> Variable -> Designator.
2649   // TODO: Actual arguments that are procedures and procedure pointers need to
2650   // be detected and represented (they're not expressions).
2651   // TODO: C1534: Don't allow a "restricted" specific intrinsic to be passed.
2652   std::optional<ActualArgument> actual;
2653   std::visit(common::visitors{
2654                  [&](const common::Indirection<parser::Expr> &x) {
2655                    // TODO: Distinguish & handle procedure name and
2656                    // proc-component-ref
2657                    actual = AnalyzeExpr(x.value());
2658                  },
2659                  [&](const parser::AltReturnSpec &) {
2660                    if (!isSubroutine) {
2661                      context_.Say(
2662                          "alternate return specification may not appear on"
2663                          " function reference"_err_en_US);
2664                    }
2665                  },
2666                  [&](const parser::ActualArg::PercentRef &) {
2667                    context_.Say("TODO: %REF() argument"_err_en_US);
2668                  },
2669                  [&](const parser::ActualArg::PercentVal &) {
2670                    context_.Say("TODO: %VAL() argument"_err_en_US);
2671                  },
2672              },
2673       std::get<parser::ActualArg>(arg.t).u);
2674   if (actual) {
2675     if (const auto &argKW{std::get<std::optional<parser::Keyword>>(arg.t)}) {
2676       actual->set_keyword(argKW->v.source);
2677     }
2678     actuals_.emplace_back(std::move(*actual));
2679   } else {
2680     fatalErrors_ = true;
2681   }
2682 }
2683 
2684 bool ArgumentAnalyzer::IsIntrinsicRelational(RelationalOperator opr) const {
2685   CHECK(actuals_.size() == 2);
2686   return semantics::IsIntrinsicRelational(
2687       opr, *GetType(0), GetRank(0), *GetType(1), GetRank(1));
2688 }
2689 
2690 bool ArgumentAnalyzer::IsIntrinsicNumeric(NumericOperator opr) const {
2691   std::optional<DynamicType> type0{GetType(0)};
2692   if (actuals_.size() == 1) {
2693     if (IsBOZLiteral(0)) {
2694       return opr == NumericOperator::Add;
2695     } else {
2696       return type0 && semantics::IsIntrinsicNumeric(*type0);
2697     }
2698   } else {
2699     std::optional<DynamicType> type1{GetType(1)};
2700     if (IsBOZLiteral(0) && type1) {
2701       auto cat1{type1->category()};
2702       return cat1 == TypeCategory::Integer || cat1 == TypeCategory::Real;
2703     } else if (IsBOZLiteral(1) && type0) { // Integer/Real opr BOZ
2704       auto cat0{type0->category()};
2705       return cat0 == TypeCategory::Integer || cat0 == TypeCategory::Real;
2706     } else {
2707       return type0 && type1 &&
2708           semantics::IsIntrinsicNumeric(*type0, GetRank(0), *type1, GetRank(1));
2709     }
2710   }
2711 }
2712 
2713 bool ArgumentAnalyzer::IsIntrinsicLogical() const {
2714   if (actuals_.size() == 1) {
2715     return semantics::IsIntrinsicLogical(*GetType(0));
2716     return GetType(0)->category() == TypeCategory::Logical;
2717   } else {
2718     return semantics::IsIntrinsicLogical(
2719         *GetType(0), GetRank(0), *GetType(1), GetRank(1));
2720   }
2721 }
2722 
2723 bool ArgumentAnalyzer::IsIntrinsicConcat() const {
2724   return semantics::IsIntrinsicConcat(
2725       *GetType(0), GetRank(0), *GetType(1), GetRank(1));
2726 }
2727 
2728 MaybeExpr ArgumentAnalyzer::TryDefinedOp(
2729     const char *opr, parser::MessageFixedText &&error, bool isUserOp) {
2730   if (AnyUntypedOperand()) {
2731     context_.Say(
2732         std::move(error), ToUpperCase(opr), TypeAsFortran(0), TypeAsFortran(1));
2733     return std::nullopt;
2734   }
2735   {
2736     auto restorer{context_.GetContextualMessages().DiscardMessages()};
2737     std::string oprNameString{
2738         isUserOp ? std::string{opr} : "operator("s + opr + ')'};
2739     parser::CharBlock oprName{oprNameString};
2740     const auto &scope{context_.context().FindScope(source_)};
2741     if (Symbol * symbol{scope.FindSymbol(oprName)}) {
2742       parser::Name name{symbol->name(), symbol};
2743       if (auto result{context_.AnalyzeDefinedOp(name, GetActuals())}) {
2744         return result;
2745       }
2746       sawDefinedOp_ = symbol;
2747     }
2748     for (std::size_t passIndex{0}; passIndex < actuals_.size(); ++passIndex) {
2749       if (const Symbol * symbol{FindBoundOp(oprName, passIndex)}) {
2750         if (MaybeExpr result{TryBoundOp(*symbol, passIndex)}) {
2751           return result;
2752         }
2753       }
2754     }
2755   }
2756   if (sawDefinedOp_) {
2757     SayNoMatch(ToUpperCase(sawDefinedOp_->name().ToString()));
2758   } else if (actuals_.size() == 1 || AreConformable()) {
2759     context_.Say(
2760         std::move(error), ToUpperCase(opr), TypeAsFortran(0), TypeAsFortran(1));
2761   } else {
2762     context_.Say(
2763         "Operands of %s are not conformable; have rank %d and rank %d"_err_en_US,
2764         ToUpperCase(opr), actuals_[0]->Rank(), actuals_[1]->Rank());
2765   }
2766   return std::nullopt;
2767 }
2768 
2769 MaybeExpr ArgumentAnalyzer::TryDefinedOp(
2770     std::vector<const char *> oprs, parser::MessageFixedText &&error) {
2771   for (std::size_t i{1}; i < oprs.size(); ++i) {
2772     auto restorer{context_.GetContextualMessages().DiscardMessages()};
2773     if (auto result{TryDefinedOp(oprs[i], std::move(error))}) {
2774       return result;
2775     }
2776   }
2777   return TryDefinedOp(oprs[0], std::move(error));
2778 }
2779 
2780 MaybeExpr ArgumentAnalyzer::TryBoundOp(const Symbol &symbol, int passIndex) {
2781   ActualArguments localActuals{actuals_};
2782   const Symbol *proc{GetBindingResolution(GetType(passIndex), symbol)};
2783   if (!proc) {
2784     proc = &symbol;
2785     localActuals.at(passIndex).value().set_isPassedObject();
2786   }
2787   return context_.MakeFunctionRef(
2788       source_, ProcedureDesignator{*proc}, std::move(localActuals));
2789 }
2790 
2791 std::optional<ProcedureRef> ArgumentAnalyzer::TryDefinedAssignment() {
2792   using semantics::Tristate;
2793   const Expr<SomeType> &lhs{GetExpr(0)};
2794   const Expr<SomeType> &rhs{GetExpr(1)};
2795   std::optional<DynamicType> lhsType{lhs.GetType()};
2796   std::optional<DynamicType> rhsType{rhs.GetType()};
2797   int lhsRank{lhs.Rank()};
2798   int rhsRank{rhs.Rank()};
2799   Tristate isDefined{
2800       semantics::IsDefinedAssignment(lhsType, lhsRank, rhsType, rhsRank)};
2801   if (isDefined == Tristate::No) {
2802     return std::nullopt; // user-defined assignment not allowed for these args
2803   }
2804   auto restorer{context_.GetContextualMessages().SetLocation(source_)};
2805   if (std::optional<ProcedureRef> procRef{GetDefinedAssignmentProc()}) {
2806     context_.CheckCall(source_, procRef->proc(), procRef->arguments());
2807     return std::move(*procRef);
2808   }
2809   if (isDefined == Tristate::Yes) {
2810     if (!lhsType || !rhsType || (lhsRank != rhsRank && rhsRank != 0) ||
2811         !OkLogicalIntegerAssignment(lhsType->category(), rhsType->category())) {
2812       SayNoMatch("ASSIGNMENT(=)", true);
2813     }
2814   }
2815   return std::nullopt;
2816 }
2817 
2818 bool ArgumentAnalyzer::OkLogicalIntegerAssignment(
2819     TypeCategory lhs, TypeCategory rhs) {
2820   if (!context_.context().languageFeatures().IsEnabled(
2821           common::LanguageFeature::LogicalIntegerAssignment)) {
2822     return false;
2823   }
2824   std::optional<parser::MessageFixedText> msg;
2825   if (lhs == TypeCategory::Integer && rhs == TypeCategory::Logical) {
2826     // allow assignment to LOGICAL from INTEGER as a legacy extension
2827     msg = "nonstandard usage: assignment of LOGICAL to INTEGER"_en_US;
2828   } else if (lhs == TypeCategory::Logical && rhs == TypeCategory::Integer) {
2829     // ... and assignment to LOGICAL from INTEGER
2830     msg = "nonstandard usage: assignment of INTEGER to LOGICAL"_en_US;
2831   } else {
2832     return false;
2833   }
2834   if (context_.context().languageFeatures().ShouldWarn(
2835           common::LanguageFeature::LogicalIntegerAssignment)) {
2836     context_.Say(std::move(*msg));
2837   }
2838   return true;
2839 }
2840 
2841 std::optional<ProcedureRef> ArgumentAnalyzer::GetDefinedAssignmentProc() {
2842   auto restorer{context_.GetContextualMessages().DiscardMessages()};
2843   std::string oprNameString{"assignment(=)"};
2844   parser::CharBlock oprName{oprNameString};
2845   const Symbol *proc{nullptr};
2846   const auto &scope{context_.context().FindScope(source_)};
2847   if (const Symbol * symbol{scope.FindSymbol(oprName)}) {
2848     ExpressionAnalyzer::AdjustActuals noAdjustment;
2849     if (const Symbol *
2850         specific{context_.ResolveGeneric(*symbol, actuals_, noAdjustment)}) {
2851       proc = specific;
2852     } else {
2853       context_.EmitGenericResolutionError(*symbol);
2854     }
2855   }
2856   for (std::size_t passIndex{0}; passIndex < actuals_.size(); ++passIndex) {
2857     if (const Symbol * specific{FindBoundOp(oprName, passIndex)}) {
2858       proc = specific;
2859     }
2860   }
2861   if (proc) {
2862     ActualArguments actualsCopy{actuals_};
2863     actualsCopy[1]->Parenthesize();
2864     return ProcedureRef{ProcedureDesignator{*proc}, std::move(actualsCopy)};
2865   } else {
2866     return std::nullopt;
2867   }
2868 }
2869 
2870 void ArgumentAnalyzer::Dump(llvm::raw_ostream &os) {
2871   os << "source_: " << source_.ToString() << " fatalErrors_ = " << fatalErrors_
2872      << '\n';
2873   for (const auto &actual : actuals_) {
2874     if (!actual.has_value()) {
2875       os << "- error\n";
2876     } else if (const Symbol * symbol{actual->GetAssumedTypeDummy()}) {
2877       os << "- assumed type: " << symbol->name().ToString() << '\n';
2878     } else if (const Expr<SomeType> *expr{actual->UnwrapExpr()}) {
2879       expr->AsFortran(os << "- expr: ") << '\n';
2880     } else {
2881       DIE("bad ActualArgument");
2882     }
2883   }
2884 }
2885 std::optional<ActualArgument> ArgumentAnalyzer::AnalyzeExpr(
2886     const parser::Expr &expr) {
2887   source_.ExtendToCover(expr.source);
2888   if (const Symbol * assumedTypeDummy{AssumedTypeDummy(expr)}) {
2889     expr.typedExpr.reset(new GenericExprWrapper{});
2890     if (allowAssumedType_) {
2891       return ActualArgument{ActualArgument::AssumedType{*assumedTypeDummy}};
2892     } else {
2893       context_.SayAt(expr.source,
2894           "TYPE(*) dummy argument may only be used as an actual argument"_err_en_US);
2895       return std::nullopt;
2896     }
2897   } else if (MaybeExpr argExpr{context_.Analyze(expr)}) {
2898     return ActualArgument{context_.Fold(std::move(*argExpr))};
2899   } else {
2900     return std::nullopt;
2901   }
2902 }
2903 
2904 bool ArgumentAnalyzer::AreConformable() const {
2905   CHECK(!fatalErrors_ && actuals_.size() == 2);
2906   return evaluate::AreConformable(*actuals_[0], *actuals_[1]);
2907 }
2908 
2909 // Look for a type-bound operator in the type of arg number passIndex.
2910 const Symbol *ArgumentAnalyzer::FindBoundOp(
2911     parser::CharBlock oprName, int passIndex) {
2912   const auto *type{GetDerivedTypeSpec(GetType(passIndex))};
2913   if (!type || !type->scope()) {
2914     return nullptr;
2915   }
2916   const Symbol *symbol{type->scope()->FindComponent(oprName)};
2917   if (!symbol) {
2918     return nullptr;
2919   }
2920   sawDefinedOp_ = symbol;
2921   ExpressionAnalyzer::AdjustActuals adjustment{
2922       [&](const Symbol &proc, ActualArguments &) {
2923         return passIndex == GetPassIndex(proc);
2924       }};
2925   const Symbol *result{context_.ResolveGeneric(*symbol, actuals_, adjustment)};
2926   if (!result) {
2927     context_.EmitGenericResolutionError(*symbol);
2928   }
2929   return result;
2930 }
2931 
2932 std::optional<DynamicType> ArgumentAnalyzer::GetType(std::size_t i) const {
2933   return i < actuals_.size() ? actuals_[i].value().GetType() : std::nullopt;
2934 }
2935 int ArgumentAnalyzer::GetRank(std::size_t i) const {
2936   return i < actuals_.size() ? actuals_[i].value().Rank() : 0;
2937 }
2938 
2939 // Report error resolving opr when there is a user-defined one available
2940 void ArgumentAnalyzer::SayNoMatch(const std::string &opr, bool isAssignment) {
2941   std::string type0{TypeAsFortran(0)};
2942   auto rank0{actuals_[0]->Rank()};
2943   if (actuals_.size() == 1) {
2944     if (rank0 > 0) {
2945       context_.Say("No intrinsic or user-defined %s matches "
2946                    "rank %d array of %s"_err_en_US,
2947           opr, rank0, type0);
2948     } else {
2949       context_.Say("No intrinsic or user-defined %s matches "
2950                    "operand type %s"_err_en_US,
2951           opr, type0);
2952     }
2953   } else {
2954     std::string type1{TypeAsFortran(1)};
2955     auto rank1{actuals_[1]->Rank()};
2956     if (rank0 > 0 && rank1 > 0 && rank0 != rank1) {
2957       context_.Say("No intrinsic or user-defined %s matches "
2958                    "rank %d array of %s and rank %d array of %s"_err_en_US,
2959           opr, rank0, type0, rank1, type1);
2960     } else if (isAssignment && rank0 != rank1) {
2961       if (rank0 == 0) {
2962         context_.Say("No intrinsic or user-defined %s matches "
2963                      "scalar %s and rank %d array of %s"_err_en_US,
2964             opr, type0, rank1, type1);
2965       } else {
2966         context_.Say("No intrinsic or user-defined %s matches "
2967                      "rank %d array of %s and scalar %s"_err_en_US,
2968             opr, rank0, type0, type1);
2969       }
2970     } else {
2971       context_.Say("No intrinsic or user-defined %s matches "
2972                    "operand types %s and %s"_err_en_US,
2973           opr, type0, type1);
2974     }
2975   }
2976 }
2977 
2978 std::string ArgumentAnalyzer::TypeAsFortran(std::size_t i) {
2979   if (std::optional<DynamicType> type{GetType(i)}) {
2980     return type->category() == TypeCategory::Derived
2981         ? "TYPE("s + type->AsFortran() + ')'
2982         : type->category() == TypeCategory::Character
2983             ? "CHARACTER(KIND="s + std::to_string(type->kind()) + ')'
2984             : ToUpperCase(type->AsFortran());
2985   } else {
2986     return "untyped";
2987   }
2988 }
2989 
2990 bool ArgumentAnalyzer::AnyUntypedOperand() {
2991   for (const auto &actual : actuals_) {
2992     if (!actual.value().GetType()) {
2993       return true;
2994     }
2995   }
2996   return false;
2997 }
2998 
2999 } // namespace Fortran::evaluate
3000 
3001 namespace Fortran::semantics {
3002 evaluate::Expr<evaluate::SubscriptInteger> AnalyzeKindSelector(
3003     SemanticsContext &context, common::TypeCategory category,
3004     const std::optional<parser::KindSelector> &selector) {
3005   evaluate::ExpressionAnalyzer analyzer{context};
3006   auto restorer{
3007       analyzer.GetContextualMessages().SetLocation(context.location().value())};
3008   return analyzer.AnalyzeKindSelector(category, selector);
3009 }
3010 
3011 void AnalyzeCallStmt(SemanticsContext &context, const parser::CallStmt &call) {
3012   evaluate::ExpressionAnalyzer{context}.Analyze(call);
3013 }
3014 
3015 const evaluate::Assignment *AnalyzeAssignmentStmt(
3016     SemanticsContext &context, const parser::AssignmentStmt &stmt) {
3017   return evaluate::ExpressionAnalyzer{context}.Analyze(stmt);
3018 }
3019 const evaluate::Assignment *AnalyzePointerAssignmentStmt(
3020     SemanticsContext &context, const parser::PointerAssignmentStmt &stmt) {
3021   return evaluate::ExpressionAnalyzer{context}.Analyze(stmt);
3022 }
3023 
3024 ExprChecker::ExprChecker(SemanticsContext &context) : context_{context} {}
3025 
3026 bool ExprChecker::Walk(const parser::Program &program) {
3027   parser::Walk(program, *this);
3028   return !context_.AnyFatalError();
3029 }
3030 
3031 bool ExprChecker::Pre(const parser::DataStmtConstant &x) {
3032   std::visit(common::visitors{
3033                  [&](const parser::NullInit &) {},
3034                  [&](const parser::InitialDataTarget &y) {
3035                    AnalyzeExpr(context_, y.value());
3036                  },
3037                  [&](const auto &y) { AnalyzeExpr(context_, y); },
3038              },
3039       x.u);
3040   return false;
3041 }
3042 
3043 } // namespace Fortran::semantics
3044