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