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