[lldb] Add ability to hide the root name of a value
[llvm-project.git] / flang / lib / Semantics / expression.cpp
blob14f2b0f0f7be9af20b17840b9f211649145785b9
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 //===----------------------------------------------------------------------===//
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 #include <vector>
34 // Typedef for optional generic expressions (ubiquitous in this file)
35 using MaybeExpr =
36 std::optional<Fortran::evaluate::Expr<Fortran::evaluate::SomeType>>;
38 // Much of the code that implements semantic analysis of expressions is
39 // tightly coupled with their typed representations in lib/Evaluate,
40 // and appears here in namespace Fortran::evaluate for convenience.
41 namespace Fortran::evaluate {
43 using common::LanguageFeature;
44 using common::NumericOperator;
45 using common::TypeCategory;
47 static inline std::string ToUpperCase(std::string_view str) {
48 return parser::ToUpperCaseLetters(str);
51 struct DynamicTypeWithLength : public DynamicType {
52 explicit DynamicTypeWithLength(const DynamicType &t) : DynamicType{t} {}
53 std::optional<Expr<SubscriptInteger>> LEN() const;
54 std::optional<Expr<SubscriptInteger>> length;
57 std::optional<Expr<SubscriptInteger>> DynamicTypeWithLength::LEN() const {
58 if (length) {
59 return length;
60 } else {
61 return GetCharLength();
65 static std::optional<DynamicTypeWithLength> AnalyzeTypeSpec(
66 const std::optional<parser::TypeSpec> &spec) {
67 if (spec) {
68 if (const semantics::DeclTypeSpec *typeSpec{spec->declTypeSpec}) {
69 // Name resolution sets TypeSpec::declTypeSpec only when it's valid
70 // (viz., an intrinsic type with valid known kind or a non-polymorphic
71 // & non-ABSTRACT derived type).
72 if (const semantics::IntrinsicTypeSpec *intrinsic{
73 typeSpec->AsIntrinsic()}) {
74 TypeCategory category{intrinsic->category()};
75 if (auto optKind{ToInt64(intrinsic->kind())}) {
76 int kind{static_cast<int>(*optKind)};
77 if (category == TypeCategory::Character) {
78 const semantics::CharacterTypeSpec &cts{
79 typeSpec->characterTypeSpec()};
80 const semantics::ParamValue &len{cts.length()};
81 // N.B. CHARACTER(LEN=*) is allowed in type-specs in ALLOCATE() &
82 // type guards, but not in array constructors.
83 return DynamicTypeWithLength{DynamicType{kind, len}};
84 } else {
85 return DynamicTypeWithLength{DynamicType{category, kind}};
88 } else if (const semantics::DerivedTypeSpec *derived{
89 typeSpec->AsDerived()}) {
90 return DynamicTypeWithLength{DynamicType{*derived}};
94 return std::nullopt;
97 // Utilities to set a source location, if we have one, on an actual argument,
98 // when it is statically present.
99 static void SetArgSourceLocation(ActualArgument &x, parser::CharBlock at) {
100 x.set_sourceLocation(at);
102 static void SetArgSourceLocation(
103 std::optional<ActualArgument> &x, parser::CharBlock at) {
104 if (x) {
105 x->set_sourceLocation(at);
108 static void SetArgSourceLocation(
109 std::optional<ActualArgument> &x, std::optional<parser::CharBlock> at) {
110 if (x && at) {
111 x->set_sourceLocation(*at);
115 class ArgumentAnalyzer {
116 public:
117 explicit ArgumentAnalyzer(ExpressionAnalyzer &context)
118 : context_{context}, source_{context.GetContextualMessages().at()},
119 isProcedureCall_{false} {}
120 ArgumentAnalyzer(ExpressionAnalyzer &context, parser::CharBlock source,
121 bool isProcedureCall = false)
122 : context_{context}, source_{source}, isProcedureCall_{isProcedureCall} {}
123 bool fatalErrors() const { return fatalErrors_; }
124 ActualArguments &&GetActuals() {
125 CHECK(!fatalErrors_);
126 return std::move(actuals_);
128 const Expr<SomeType> &GetExpr(std::size_t i) const {
129 return DEREF(actuals_.at(i).value().UnwrapExpr());
131 Expr<SomeType> &&MoveExpr(std::size_t i) {
132 return std::move(DEREF(actuals_.at(i).value().UnwrapExpr()));
134 void Analyze(const common::Indirection<parser::Expr> &x) {
135 Analyze(x.value());
137 void Analyze(const parser::Expr &x) {
138 actuals_.emplace_back(AnalyzeExpr(x));
139 SetArgSourceLocation(actuals_.back(), x.source);
140 fatalErrors_ |= !actuals_.back();
142 void Analyze(const parser::Variable &);
143 void Analyze(const parser::ActualArgSpec &, bool isSubroutine);
144 void ConvertBOZ(std::optional<DynamicType> &thisType, std::size_t i,
145 std::optional<DynamicType> otherType);
147 bool IsIntrinsicRelational(
148 RelationalOperator, const DynamicType &, const DynamicType &) const;
149 bool IsIntrinsicLogical() const;
150 bool IsIntrinsicNumeric(NumericOperator) const;
151 bool IsIntrinsicConcat() const;
153 bool CheckConformance();
154 bool CheckAssignmentConformance();
155 bool CheckForNullPointer(const char *where = "as an operand here");
157 // Find and return a user-defined operator or report an error.
158 // The provided message is used if there is no such operator.
159 // If a definedOpSymbolPtr is provided, the caller must check
160 // for its accessibility.
161 MaybeExpr TryDefinedOp(
162 const char *, parser::MessageFixedText, bool isUserOp = false);
163 template <typename E>
164 MaybeExpr TryDefinedOp(E opr, parser::MessageFixedText msg) {
165 return TryDefinedOp(
166 context_.context().languageFeatures().GetNames(opr), msg);
168 // Find and return a user-defined assignment
169 std::optional<ProcedureRef> TryDefinedAssignment();
170 std::optional<ProcedureRef> GetDefinedAssignmentProc();
171 std::optional<DynamicType> GetType(std::size_t) const;
172 void Dump(llvm::raw_ostream &);
174 private:
175 MaybeExpr TryDefinedOp(std::vector<const char *>, parser::MessageFixedText);
176 MaybeExpr TryBoundOp(const Symbol &, int passIndex);
177 std::optional<ActualArgument> AnalyzeExpr(const parser::Expr &);
178 MaybeExpr AnalyzeExprOrWholeAssumedSizeArray(const parser::Expr &);
179 bool AreConformable() const;
180 const Symbol *FindBoundOp(parser::CharBlock, int passIndex,
181 const Symbol *&generic, bool isSubroutine);
182 void AddAssignmentConversion(
183 const DynamicType &lhsType, const DynamicType &rhsType);
184 bool OkLogicalIntegerAssignment(TypeCategory lhs, TypeCategory rhs);
185 int GetRank(std::size_t) const;
186 bool IsBOZLiteral(std::size_t i) const {
187 return evaluate::IsBOZLiteral(GetExpr(i));
189 void SayNoMatch(const std::string &, bool isAssignment = false);
190 std::string TypeAsFortran(std::size_t);
191 bool AnyUntypedOrMissingOperand();
193 ExpressionAnalyzer &context_;
194 ActualArguments actuals_;
195 parser::CharBlock source_;
196 bool fatalErrors_{false};
197 const bool isProcedureCall_; // false for user-defined op or assignment
200 // Wraps a data reference in a typed Designator<>, and a procedure
201 // or procedure pointer reference in a ProcedureDesignator.
202 MaybeExpr ExpressionAnalyzer::Designate(DataRef &&ref) {
203 const Symbol &last{ref.GetLastSymbol()};
204 const Symbol &symbol{BypassGeneric(last).GetUltimate()};
205 if (semantics::IsProcedure(symbol)) {
206 if (symbol.attrs().test(semantics::Attr::ABSTRACT)) {
207 Say("Abstract procedure interface '%s' may not be used as a designator"_err_en_US,
208 last.name());
210 if (auto *component{std::get_if<Component>(&ref.u)}) {
211 if (!CheckDataRef(ref)) {
212 return std::nullopt;
214 return Expr<SomeType>{ProcedureDesignator{std::move(*component)}};
215 } else if (!std::holds_alternative<SymbolRef>(ref.u)) {
216 DIE("unexpected alternative in DataRef");
217 } else if (!symbol.attrs().test(semantics::Attr::INTRINSIC)) {
218 if (symbol.has<semantics::GenericDetails>()) {
219 Say("'%s' is not a specific procedure"_err_en_US, symbol.name());
220 } else {
221 return Expr<SomeType>{ProcedureDesignator{symbol}};
223 } else if (auto interface{context_.intrinsics().IsSpecificIntrinsicFunction(
224 symbol.name().ToString())};
225 interface && !interface->isRestrictedSpecific) {
226 SpecificIntrinsic intrinsic{
227 symbol.name().ToString(), std::move(*interface)};
228 intrinsic.isRestrictedSpecific = interface->isRestrictedSpecific;
229 return Expr<SomeType>{ProcedureDesignator{std::move(intrinsic)}};
230 } else {
231 Say("'%s' is not an unrestricted specific intrinsic procedure"_err_en_US,
232 symbol.name());
234 return std::nullopt;
235 } else if (MaybeExpr result{AsGenericExpr(std::move(ref))}) {
236 return result;
237 } else {
238 if (!context_.HasError(last) && !context_.HasError(symbol)) {
239 AttachDeclaration(
240 Say("'%s' is not an object that can appear in an expression"_err_en_US,
241 last.name()),
242 symbol);
243 context_.SetError(last);
245 return std::nullopt;
249 // Some subscript semantic checks must be deferred until all of the
250 // subscripts are in hand.
251 MaybeExpr ExpressionAnalyzer::CompleteSubscripts(ArrayRef &&ref) {
252 const Symbol &symbol{ref.GetLastSymbol().GetUltimate()};
253 int symbolRank{symbol.Rank()};
254 int subscripts{static_cast<int>(ref.size())};
255 if (subscripts == 0) {
256 return std::nullopt; // error recovery
257 } else if (subscripts != symbolRank) {
258 if (symbolRank != 0) {
259 Say("Reference to rank-%d object '%s' has %d subscripts"_err_en_US,
260 symbolRank, symbol.name(), subscripts);
262 return std::nullopt;
263 } else if (const auto *object{
264 symbol.detailsIf<semantics::ObjectEntityDetails>()}) {
265 // C928 & C1002
266 if (Triplet *last{std::get_if<Triplet>(&ref.subscript().back().u)}) {
267 if (!last->upper() && object->IsAssumedSize()) {
268 Say("Assumed-size array '%s' must have explicit final "
269 "subscript upper bound value"_err_en_US,
270 symbol.name());
271 return std::nullopt;
274 } else {
275 // Shouldn't get here from Analyze(ArrayElement) without a valid base,
276 // which, if not an object, must be a construct entity from
277 // SELECT TYPE/RANK or ASSOCIATE.
278 CHECK(symbol.has<semantics::AssocEntityDetails>());
280 if (!semantics::IsNamedConstant(symbol) && !inDataStmtObject_) {
281 // Subscripts of named constants are checked in folding.
282 // Subscripts of DATA statement objects are checked in data statement
283 // conversion to initializers.
284 CheckConstantSubscripts(ref);
286 return Designate(DataRef{std::move(ref)});
289 // Applies subscripts to a data reference.
290 MaybeExpr ExpressionAnalyzer::ApplySubscripts(
291 DataRef &&dataRef, std::vector<Subscript> &&subscripts) {
292 if (subscripts.empty()) {
293 return std::nullopt; // error recovery
295 return common::visit(
296 common::visitors{
297 [&](SymbolRef &&symbol) {
298 return CompleteSubscripts(ArrayRef{symbol, std::move(subscripts)});
300 [&](Component &&c) {
301 return CompleteSubscripts(
302 ArrayRef{std::move(c), std::move(subscripts)});
304 [&](auto &&) -> MaybeExpr {
305 DIE("bad base for ArrayRef");
306 return std::nullopt;
309 std::move(dataRef.u));
312 void ExpressionAnalyzer::CheckConstantSubscripts(ArrayRef &ref) {
313 // Fold subscript expressions and check for an empty triplet.
314 Shape lb{GetLBOUNDs(foldingContext_, ref.base())};
315 CHECK(lb.size() >= ref.subscript().size());
316 Shape ub{GetUBOUNDs(foldingContext_, ref.base())};
317 CHECK(ub.size() >= ref.subscript().size());
318 bool anyPossiblyEmptyDim{false};
319 int dim{0};
320 for (Subscript &ss : ref.subscript()) {
321 if (Triplet * triplet{std::get_if<Triplet>(&ss.u)}) {
322 auto expr{Fold(triplet->stride())};
323 auto stride{ToInt64(expr)};
324 triplet->set_stride(std::move(expr));
325 std::optional<ConstantSubscript> lower, upper;
326 if (auto expr{triplet->lower()}) {
327 *expr = Fold(std::move(*expr));
328 lower = ToInt64(*expr);
329 triplet->set_lower(std::move(*expr));
330 } else {
331 lower = ToInt64(lb[dim]);
333 if (auto expr{triplet->upper()}) {
334 *expr = Fold(std::move(*expr));
335 upper = ToInt64(*expr);
336 triplet->set_upper(std::move(*expr));
337 } else {
338 upper = ToInt64(ub[dim]);
340 if (stride) {
341 if (*stride == 0) {
342 Say("Stride of triplet must not be zero"_err_en_US);
343 return;
345 if (lower && upper) {
346 if (*stride > 0) {
347 anyPossiblyEmptyDim |= *lower > *upper;
348 } else {
349 anyPossiblyEmptyDim |= *lower < *upper;
351 } else {
352 anyPossiblyEmptyDim = true;
354 } else { // non-constant stride
355 if (lower && upper && *lower == *upper) {
356 // stride is not relevant
357 } else {
358 anyPossiblyEmptyDim = true;
361 } else { // not triplet
362 auto &expr{std::get<IndirectSubscriptIntegerExpr>(ss.u).value()};
363 expr = Fold(std::move(expr));
364 anyPossiblyEmptyDim |= expr.Rank() > 0; // vector subscript
366 ++dim;
368 if (anyPossiblyEmptyDim) {
369 return;
371 dim = 0;
372 for (Subscript &ss : ref.subscript()) {
373 auto dimLB{ToInt64(lb[dim])};
374 auto dimUB{ToInt64(ub[dim])};
375 std::optional<ConstantSubscript> val[2];
376 int vals{0};
377 if (auto *triplet{std::get_if<Triplet>(&ss.u)}) {
378 auto stride{ToInt64(triplet->stride())};
379 std::optional<ConstantSubscript> lower, upper;
380 if (const auto *lowerExpr{triplet->GetLower()}) {
381 lower = ToInt64(*lowerExpr);
382 } else if (lb[dim]) {
383 lower = ToInt64(*lb[dim]);
385 if (const auto *upperExpr{triplet->GetUpper()}) {
386 upper = ToInt64(*upperExpr);
387 } else if (ub[dim]) {
388 upper = ToInt64(*ub[dim]);
390 if (lower) {
391 val[vals++] = *lower;
392 if (upper && *upper != lower && (stride && *stride != 0)) {
393 // Normalize upper bound for non-unit stride
394 // 1:10:2 -> 1:9:2, 10:1:-2 -> 10:2:-2
395 val[vals++] = *lower + *stride * ((*upper - *lower) / *stride);
398 } else {
399 val[vals++] =
400 ToInt64(std::get<IndirectSubscriptIntegerExpr>(ss.u).value());
402 for (int j{0}; j < vals; ++j) {
403 if (val[j]) {
404 if (dimLB && *val[j] < *dimLB) {
405 AttachDeclaration(
406 Say("Subscript %jd is less than lower bound %jd for dimension %d of array"_err_en_US,
407 static_cast<std::intmax_t>(*val[j]),
408 static_cast<std::intmax_t>(*dimLB), dim + 1),
409 ref.base().GetLastSymbol());
411 if (dimUB && *val[j] > *dimUB) {
412 AttachDeclaration(
413 Say("Subscript %jd is greater than upper bound %jd for dimension %d of array"_err_en_US,
414 static_cast<std::intmax_t>(*val[j]),
415 static_cast<std::intmax_t>(*dimUB), dim + 1),
416 ref.base().GetLastSymbol());
420 ++dim;
424 // C919a - only one part-ref of a data-ref may have rank > 0
425 bool ExpressionAnalyzer::CheckRanks(const DataRef &dataRef) {
426 return common::visit(
427 common::visitors{
428 [this](const Component &component) {
429 const Symbol &symbol{component.GetLastSymbol()};
430 if (int componentRank{symbol.Rank()}; componentRank > 0) {
431 if (int baseRank{component.base().Rank()}; baseRank > 0) {
432 Say("Reference to whole rank-%d component '%s' of rank-%d array of derived type is not allowed"_err_en_US,
433 componentRank, symbol.name(), baseRank);
434 return false;
436 } else {
437 return CheckRanks(component.base());
439 return true;
441 [this](const ArrayRef &arrayRef) {
442 if (const auto *component{arrayRef.base().UnwrapComponent()}) {
443 int subscriptRank{0};
444 for (const Subscript &subscript : arrayRef.subscript()) {
445 subscriptRank += subscript.Rank();
447 if (subscriptRank > 0) {
448 if (int componentBaseRank{component->base().Rank()};
449 componentBaseRank > 0) {
450 Say("Subscripts of component '%s' of rank-%d derived type array have rank %d but must all be scalar"_err_en_US,
451 component->GetLastSymbol().name(), componentBaseRank,
452 subscriptRank);
453 return false;
455 } else {
456 return CheckRanks(component->base());
459 return true;
461 [](const SymbolRef &) { return true; },
462 [](const CoarrayRef &) { return true; },
464 dataRef.u);
467 // C911 - if the last name in a data-ref has an abstract derived type,
468 // it must also be polymorphic.
469 bool ExpressionAnalyzer::CheckPolymorphic(const DataRef &dataRef) {
470 if (auto type{DynamicType::From(dataRef.GetLastSymbol())}) {
471 if (type->category() == TypeCategory::Derived && !type->IsPolymorphic()) {
472 const Symbol &typeSymbol{
473 type->GetDerivedTypeSpec().typeSymbol().GetUltimate()};
474 if (typeSymbol.attrs().test(semantics::Attr::ABSTRACT)) {
475 AttachDeclaration(
476 Say("Reference to object with abstract derived type '%s' must be polymorphic"_err_en_US,
477 typeSymbol.name()),
478 typeSymbol);
479 return false;
483 return true;
486 bool ExpressionAnalyzer::CheckDataRef(const DataRef &dataRef) {
487 // Always check both, don't short-circuit
488 bool ranksOk{CheckRanks(dataRef)};
489 bool polyOk{CheckPolymorphic(dataRef)};
490 return ranksOk && polyOk;
493 // Parse tree correction after a substring S(j:k) was misparsed as an
494 // array section. Fortran substrings must have a range, not a
495 // single index.
496 static std::optional<parser::Substring> FixMisparsedSubstringDataRef(
497 parser::DataRef &dataRef) {
498 if (auto *ae{
499 std::get_if<common::Indirection<parser::ArrayElement>>(&dataRef.u)}) {
500 // ...%a(j:k) and "a" is a character scalar
501 parser::ArrayElement &arrElement{ae->value()};
502 if (arrElement.subscripts.size() == 1) {
503 if (auto *triplet{std::get_if<parser::SubscriptTriplet>(
504 &arrElement.subscripts.front().u)}) {
505 if (!std::get<2 /*stride*/>(triplet->t).has_value()) {
506 if (const Symbol *symbol{
507 parser::GetLastName(arrElement.base).symbol}) {
508 const Symbol &ultimate{symbol->GetUltimate()};
509 if (const semantics::DeclTypeSpec *type{ultimate.GetType()}) {
510 if (!ultimate.IsObjectArray() &&
511 type->category() == semantics::DeclTypeSpec::Character) {
512 // The ambiguous S(j:k) was parsed as an array section
513 // reference, but it's now clear that it's a substring.
514 // Fix the parse tree in situ.
515 return arrElement.ConvertToSubstring();
523 return std::nullopt;
526 // When a designator is a misparsed type-param-inquiry of a misparsed
527 // substring -- it looks like a structure component reference of an array
528 // slice -- fix the substring and then convert to an intrinsic function
529 // call to KIND() or LEN(). And when the designator is a misparsed
530 // substring, convert it into a substring reference in place.
531 MaybeExpr ExpressionAnalyzer::FixMisparsedSubstring(
532 const parser::Designator &d) {
533 auto &mutate{const_cast<parser::Designator &>(d)};
534 if (auto *dataRef{std::get_if<parser::DataRef>(&mutate.u)}) {
535 if (auto *sc{std::get_if<common::Indirection<parser::StructureComponent>>(
536 &dataRef->u)}) {
537 parser::StructureComponent &structComponent{sc->value()};
538 parser::CharBlock which{structComponent.component.source};
539 if (which == "kind" || which == "len") {
540 if (auto substring{
541 FixMisparsedSubstringDataRef(structComponent.base)}) {
542 // ...%a(j:k)%kind or %len and "a" is a character scalar
543 mutate.u = std::move(*substring);
544 if (MaybeExpr substringExpr{Analyze(d)}) {
545 return MakeFunctionRef(which,
546 ActualArguments{ActualArgument{std::move(*substringExpr)}});
550 } else if (auto substring{FixMisparsedSubstringDataRef(*dataRef)}) {
551 mutate.u = std::move(*substring);
554 return std::nullopt;
557 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Designator &d) {
558 auto restorer{GetContextualMessages().SetLocation(d.source)};
559 if (auto substringInquiry{FixMisparsedSubstring(d)}) {
560 return substringInquiry;
562 // These checks have to be deferred to these "top level" data-refs where
563 // we can be sure that there are no following subscripts (yet).
564 MaybeExpr result{Analyze(d.u)};
565 if (result) {
566 std::optional<DataRef> dataRef{ExtractDataRef(std::move(result))};
567 if (!dataRef) {
568 dataRef = ExtractDataRef(std::move(result), /*intoSubstring=*/true);
570 if (!dataRef) {
571 dataRef = ExtractDataRef(std::move(result),
572 /*intoSubstring=*/false, /*intoComplexPart=*/true);
574 if (dataRef && !CheckDataRef(*dataRef)) {
575 result.reset();
578 return result;
581 // A utility subroutine to repackage optional expressions of various levels
582 // of type specificity as fully general MaybeExpr values.
583 template <typename A> common::IfNoLvalue<MaybeExpr, A> AsMaybeExpr(A &&x) {
584 return AsGenericExpr(std::move(x));
586 template <typename A> MaybeExpr AsMaybeExpr(std::optional<A> &&x) {
587 if (x) {
588 return AsMaybeExpr(std::move(*x));
590 return std::nullopt;
593 // Type kind parameter values for literal constants.
594 int ExpressionAnalyzer::AnalyzeKindParam(
595 const std::optional<parser::KindParam> &kindParam, int defaultKind) {
596 if (!kindParam) {
597 return defaultKind;
599 std::int64_t kind{common::visit(
600 common::visitors{
601 [](std::uint64_t k) { return static_cast<std::int64_t>(k); },
602 [&](const parser::Scalar<
603 parser::Integer<parser::Constant<parser::Name>>> &n) {
604 if (MaybeExpr ie{Analyze(n)}) {
605 return ToInt64(*ie).value_or(defaultKind);
607 return static_cast<std::int64_t>(defaultKind);
610 kindParam->u)};
611 if (kind != static_cast<int>(kind)) {
612 Say("Unsupported type kind value (%jd)"_err_en_US,
613 static_cast<std::intmax_t>(kind));
614 kind = defaultKind;
616 return static_cast<int>(kind);
619 // Common handling of parser::IntLiteralConstant and SignedIntLiteralConstant
620 struct IntTypeVisitor {
621 using Result = MaybeExpr;
622 using Types = IntegerTypes;
623 template <typename T> Result Test() {
624 if (T::kind >= kind) {
625 const char *p{digits.begin()};
626 using Int = typename T::Scalar;
627 typename Int::ValueWithOverflow num{0, false};
628 if (isNegated) {
629 auto unsignedNum{Int::Read(p, 10, false /*unsigned*/)};
630 num.value = unsignedNum.value.Negate().value;
631 num.overflow = unsignedNum.overflow || num.value > Int{0};
632 if (!num.overflow && num.value.Negate().overflow &&
633 !analyzer.context().IsInModuleFile(digits)) {
634 analyzer.Say(digits,
635 "negated maximum INTEGER(KIND=%d) literal"_port_en_US, T::kind);
637 } else {
638 num = Int::Read(p, 10, true /*signed*/);
640 if (!num.overflow) {
641 if (T::kind > kind) {
642 if (!isDefaultKind ||
643 !analyzer.context().IsEnabled(LanguageFeature::BigIntLiterals)) {
644 return std::nullopt;
645 } else if (analyzer.context().ShouldWarn(
646 LanguageFeature::BigIntLiterals)) {
647 analyzer.Say(digits,
648 "Integer literal is too large for default INTEGER(KIND=%d); "
649 "assuming INTEGER(KIND=%d)"_port_en_US,
650 kind, T::kind);
653 return Expr<SomeType>{
654 Expr<SomeInteger>{Expr<T>{Constant<T>{std::move(num.value)}}}};
657 return std::nullopt;
659 ExpressionAnalyzer &analyzer;
660 parser::CharBlock digits;
661 std::int64_t kind;
662 bool isDefaultKind;
663 bool isNegated;
666 template <typename PARSED>
667 MaybeExpr ExpressionAnalyzer::IntLiteralConstant(
668 const PARSED &x, bool isNegated) {
669 const auto &kindParam{std::get<std::optional<parser::KindParam>>(x.t)};
670 bool isDefaultKind{!kindParam};
671 int kind{AnalyzeKindParam(kindParam, GetDefaultKind(TypeCategory::Integer))};
672 if (CheckIntrinsicKind(TypeCategory::Integer, kind)) {
673 auto digits{std::get<parser::CharBlock>(x.t)};
674 if (MaybeExpr result{common::SearchTypes(
675 IntTypeVisitor{*this, digits, kind, isDefaultKind, isNegated})}) {
676 return result;
677 } else if (isDefaultKind) {
678 Say(digits,
679 "Integer literal is too large for any allowable "
680 "kind of INTEGER"_err_en_US);
681 } else {
682 Say(digits, "Integer literal is too large for INTEGER(KIND=%d)"_err_en_US,
683 kind);
686 return std::nullopt;
689 MaybeExpr ExpressionAnalyzer::Analyze(
690 const parser::IntLiteralConstant &x, bool isNegated) {
691 auto restorer{
692 GetContextualMessages().SetLocation(std::get<parser::CharBlock>(x.t))};
693 return IntLiteralConstant(x, isNegated);
696 MaybeExpr ExpressionAnalyzer::Analyze(
697 const parser::SignedIntLiteralConstant &x) {
698 auto restorer{GetContextualMessages().SetLocation(x.source)};
699 return IntLiteralConstant(x);
702 template <typename TYPE>
703 Constant<TYPE> ReadRealLiteral(
704 parser::CharBlock source, FoldingContext &context) {
705 const char *p{source.begin()};
706 auto valWithFlags{
707 Scalar<TYPE>::Read(p, context.targetCharacteristics().roundingMode())};
708 CHECK(p == source.end());
709 RealFlagWarnings(context, valWithFlags.flags, "conversion of REAL literal");
710 auto value{valWithFlags.value};
711 if (context.targetCharacteristics().areSubnormalsFlushedToZero()) {
712 value = value.FlushSubnormalToZero();
714 return {value};
717 struct RealTypeVisitor {
718 using Result = std::optional<Expr<SomeReal>>;
719 using Types = RealTypes;
721 RealTypeVisitor(int k, parser::CharBlock lit, FoldingContext &ctx)
722 : kind{k}, literal{lit}, context{ctx} {}
724 template <typename T> Result Test() {
725 if (kind == T::kind) {
726 return {AsCategoryExpr(ReadRealLiteral<T>(literal, context))};
728 return std::nullopt;
731 int kind;
732 parser::CharBlock literal;
733 FoldingContext &context;
736 // Reads a real literal constant and encodes it with the right kind.
737 MaybeExpr ExpressionAnalyzer::Analyze(const parser::RealLiteralConstant &x) {
738 // Use a local message context around the real literal for better
739 // provenance on any messages.
740 auto restorer{GetContextualMessages().SetLocation(x.real.source)};
741 // If a kind parameter appears, it defines the kind of the literal and the
742 // letter used in an exponent part must be 'E' (e.g., the 'E' in
743 // "6.02214E+23"). In the absence of an explicit kind parameter, any
744 // exponent letter determines the kind. Otherwise, defaults apply.
745 auto &defaults{context_.defaultKinds()};
746 int defaultKind{defaults.GetDefaultKind(TypeCategory::Real)};
747 const char *end{x.real.source.end()};
748 char expoLetter{' '};
749 std::optional<int> letterKind;
750 for (const char *p{x.real.source.begin()}; p < end; ++p) {
751 if (parser::IsLetter(*p)) {
752 expoLetter = *p;
753 switch (expoLetter) {
754 case 'e':
755 letterKind = defaults.GetDefaultKind(TypeCategory::Real);
756 break;
757 case 'd':
758 letterKind = defaults.doublePrecisionKind();
759 break;
760 case 'q':
761 letterKind = defaults.quadPrecisionKind();
762 break;
763 default:
764 Say("Unknown exponent letter '%c'"_err_en_US, expoLetter);
766 break;
769 if (letterKind) {
770 defaultKind = *letterKind;
772 // C716 requires 'E' as an exponent.
773 // Extension: allow exponent-letter matching the kind-param.
774 auto kind{AnalyzeKindParam(x.kind, defaultKind)};
775 if (letterKind && expoLetter != 'e') {
776 if (kind != *letterKind) {
777 Say("Explicit kind parameter on real constant disagrees with "
778 "exponent letter '%c'"_warn_en_US,
779 expoLetter);
780 } else if (x.kind &&
781 context_.ShouldWarn(
782 common::LanguageFeature::ExponentMatchingKindParam)) {
783 Say("Explicit kind parameter together with non-'E' exponent letter "
784 "is not standard"_port_en_US);
787 auto result{common::SearchTypes(
788 RealTypeVisitor{kind, x.real.source, GetFoldingContext()})};
789 if (!result) { // C717
790 Say("Unsupported REAL(KIND=%d)"_err_en_US, kind);
792 return AsMaybeExpr(std::move(result));
795 MaybeExpr ExpressionAnalyzer::Analyze(
796 const parser::SignedRealLiteralConstant &x) {
797 if (auto result{Analyze(std::get<parser::RealLiteralConstant>(x.t))}) {
798 auto &realExpr{std::get<Expr<SomeReal>>(result->u)};
799 if (auto sign{std::get<std::optional<parser::Sign>>(x.t)}) {
800 if (sign == parser::Sign::Negative) {
801 return AsGenericExpr(-std::move(realExpr));
804 return result;
806 return std::nullopt;
809 MaybeExpr ExpressionAnalyzer::Analyze(
810 const parser::SignedComplexLiteralConstant &x) {
811 auto result{Analyze(std::get<parser::ComplexLiteralConstant>(x.t))};
812 if (!result) {
813 return std::nullopt;
814 } else if (std::get<parser::Sign>(x.t) == parser::Sign::Negative) {
815 return AsGenericExpr(-std::move(std::get<Expr<SomeComplex>>(result->u)));
816 } else {
817 return result;
821 MaybeExpr ExpressionAnalyzer::Analyze(const parser::ComplexPart &x) {
822 return Analyze(x.u);
825 MaybeExpr ExpressionAnalyzer::Analyze(const parser::ComplexLiteralConstant &z) {
826 return AnalyzeComplex(Analyze(std::get<0>(z.t)), Analyze(std::get<1>(z.t)),
827 "complex literal constant");
830 // CHARACTER literal processing.
831 MaybeExpr ExpressionAnalyzer::AnalyzeString(std::string &&string, int kind) {
832 if (!CheckIntrinsicKind(TypeCategory::Character, kind)) {
833 return std::nullopt;
835 switch (kind) {
836 case 1:
837 return AsGenericExpr(Constant<Type<TypeCategory::Character, 1>>{
838 parser::DecodeString<std::string, parser::Encoding::LATIN_1>(
839 string, true)});
840 case 2:
841 return AsGenericExpr(Constant<Type<TypeCategory::Character, 2>>{
842 parser::DecodeString<std::u16string, parser::Encoding::UTF_8>(
843 string, true)});
844 case 4:
845 return AsGenericExpr(Constant<Type<TypeCategory::Character, 4>>{
846 parser::DecodeString<std::u32string, parser::Encoding::UTF_8>(
847 string, true)});
848 default:
849 CRASH_NO_CASE;
853 MaybeExpr ExpressionAnalyzer::Analyze(const parser::CharLiteralConstant &x) {
854 int kind{
855 AnalyzeKindParam(std::get<std::optional<parser::KindParam>>(x.t), 1)};
856 auto value{std::get<std::string>(x.t)};
857 return AnalyzeString(std::move(value), kind);
860 MaybeExpr ExpressionAnalyzer::Analyze(
861 const parser::HollerithLiteralConstant &x) {
862 int kind{GetDefaultKind(TypeCategory::Character)};
863 auto value{x.v};
864 return AnalyzeString(std::move(value), kind);
867 // .TRUE. and .FALSE. of various kinds
868 MaybeExpr ExpressionAnalyzer::Analyze(const parser::LogicalLiteralConstant &x) {
869 auto kind{AnalyzeKindParam(std::get<std::optional<parser::KindParam>>(x.t),
870 GetDefaultKind(TypeCategory::Logical))};
871 bool value{std::get<bool>(x.t)};
872 auto result{common::SearchTypes(
873 TypeKindVisitor<TypeCategory::Logical, Constant, bool>{
874 kind, std::move(value)})};
875 if (!result) {
876 Say("unsupported LOGICAL(KIND=%d)"_err_en_US, kind); // C728
878 return result;
881 // BOZ typeless literals
882 MaybeExpr ExpressionAnalyzer::Analyze(const parser::BOZLiteralConstant &x) {
883 const char *p{x.v.c_str()};
884 std::uint64_t base{16};
885 switch (*p++) {
886 case 'b':
887 base = 2;
888 break;
889 case 'o':
890 base = 8;
891 break;
892 case 'z':
893 break;
894 case 'x':
895 break;
896 default:
897 CRASH_NO_CASE;
899 CHECK(*p == '"');
900 ++p;
901 auto value{BOZLiteralConstant::Read(p, base, false /*unsigned*/)};
902 if (*p != '"') {
903 Say("Invalid digit ('%c') in BOZ literal '%s'"_err_en_US, *p,
904 x.v); // C7107, C7108
905 return std::nullopt;
907 if (value.overflow) {
908 Say("BOZ literal '%s' too large"_err_en_US, x.v);
909 return std::nullopt;
911 return AsGenericExpr(std::move(value.value));
914 // Names and named constants
915 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Name &n) {
916 auto restorer{GetContextualMessages().SetLocation(n.source)};
917 if (std::optional<int> kind{IsImpliedDo(n.source)}) {
918 return AsMaybeExpr(ConvertToKind<TypeCategory::Integer>(
919 *kind, AsExpr(ImpliedDoIndex{n.source})));
921 if (context_.HasError(n.symbol)) { // includes case of no symbol
922 return std::nullopt;
923 } else {
924 const Symbol &ultimate{n.symbol->GetUltimate()};
925 if (ultimate.has<semantics::TypeParamDetails>()) {
926 // A bare reference to a derived type parameter (within a parameterized
927 // derived type definition)
928 return Fold(ConvertToType(
929 ultimate, AsGenericExpr(TypeParamInquiry{std::nullopt, ultimate})));
930 } else {
931 if (n.symbol->attrs().test(semantics::Attr::VOLATILE)) {
932 if (const semantics::Scope *pure{semantics::FindPureProcedureContaining(
933 context_.FindScope(n.source))}) {
934 SayAt(n,
935 "VOLATILE variable '%s' may not be referenced in pure subprogram '%s'"_err_en_US,
936 n.source, DEREF(pure->symbol()).name());
937 n.symbol->attrs().reset(semantics::Attr::VOLATILE);
940 if (!isWholeAssumedSizeArrayOk_ &&
941 semantics::IsAssumedSizeArray(*n.symbol)) { // C1002, C1014, C1231
942 AttachDeclaration(
943 SayAt(n,
944 "Whole assumed-size array '%s' may not appear here without subscripts"_err_en_US,
945 n.source),
946 *n.symbol);
948 return Designate(DataRef{*n.symbol});
953 MaybeExpr ExpressionAnalyzer::Analyze(const parser::NamedConstant &n) {
954 auto restorer{GetContextualMessages().SetLocation(n.v.source)};
955 if (MaybeExpr value{Analyze(n.v)}) {
956 Expr<SomeType> folded{Fold(std::move(*value))};
957 if (IsConstantExpr(folded)) {
958 return folded;
960 Say(n.v.source, "must be a constant"_err_en_US); // C718
962 return std::nullopt;
965 MaybeExpr ExpressionAnalyzer::Analyze(const parser::NullInit &n) {
966 auto restorer{AllowNullPointer()};
967 if (MaybeExpr value{Analyze(n.v.value())}) {
968 // Subtle: when the NullInit is a DataStmtConstant, it might
969 // be a misparse of a structure constructor without parameters
970 // or components (e.g., T()). Checking the result to ensure
971 // that a "=>" data entity initializer actually resolved to
972 // a null pointer has to be done by the caller.
973 return Fold(std::move(*value));
975 return std::nullopt;
978 MaybeExpr ExpressionAnalyzer::Analyze(
979 const parser::StmtFunctionStmt &stmtFunc) {
980 inStmtFunctionDefinition_ = true;
981 return Analyze(std::get<parser::Scalar<parser::Expr>>(stmtFunc.t));
984 MaybeExpr ExpressionAnalyzer::Analyze(const parser::InitialDataTarget &x) {
985 return Analyze(x.value());
988 MaybeExpr ExpressionAnalyzer::Analyze(const parser::DataStmtValue &x) {
989 if (const auto &repeat{
990 std::get<std::optional<parser::DataStmtRepeat>>(x.t)}) {
991 x.repetitions = -1;
992 if (MaybeExpr expr{Analyze(repeat->u)}) {
993 Expr<SomeType> folded{Fold(std::move(*expr))};
994 if (auto value{ToInt64(folded)}) {
995 if (*value >= 0) { // C882
996 x.repetitions = *value;
997 } else {
998 Say(FindSourceLocation(repeat),
999 "Repeat count (%jd) for data value must not be negative"_err_en_US,
1000 *value);
1005 return Analyze(std::get<parser::DataStmtConstant>(x.t));
1008 // Substring references
1009 std::optional<Expr<SubscriptInteger>> ExpressionAnalyzer::GetSubstringBound(
1010 const std::optional<parser::ScalarIntExpr> &bound) {
1011 if (bound) {
1012 if (MaybeExpr expr{Analyze(*bound)}) {
1013 if (expr->Rank() > 1) {
1014 Say("substring bound expression has rank %d"_err_en_US, expr->Rank());
1016 if (auto *intExpr{std::get_if<Expr<SomeInteger>>(&expr->u)}) {
1017 if (auto *ssIntExpr{std::get_if<Expr<SubscriptInteger>>(&intExpr->u)}) {
1018 return {std::move(*ssIntExpr)};
1020 return {Expr<SubscriptInteger>{
1021 Convert<SubscriptInteger, TypeCategory::Integer>{
1022 std::move(*intExpr)}}};
1023 } else {
1024 Say("substring bound expression is not INTEGER"_err_en_US);
1028 return std::nullopt;
1031 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Substring &ss) {
1032 if (MaybeExpr baseExpr{Analyze(std::get<parser::DataRef>(ss.t))}) {
1033 if (std::optional<DataRef> dataRef{ExtractDataRef(std::move(*baseExpr))}) {
1034 if (MaybeExpr newBaseExpr{Designate(std::move(*dataRef))}) {
1035 if (std::optional<DataRef> checked{
1036 ExtractDataRef(std::move(*newBaseExpr))}) {
1037 const parser::SubstringRange &range{
1038 std::get<parser::SubstringRange>(ss.t)};
1039 std::optional<Expr<SubscriptInteger>> first{
1040 GetSubstringBound(std::get<0>(range.t))};
1041 std::optional<Expr<SubscriptInteger>> last{
1042 GetSubstringBound(std::get<1>(range.t))};
1043 const Symbol &symbol{checked->GetLastSymbol()};
1044 if (std::optional<DynamicType> dynamicType{
1045 DynamicType::From(symbol)}) {
1046 if (dynamicType->category() == TypeCategory::Character) {
1047 return WrapperHelper<TypeCategory::Character, Designator,
1048 Substring>(dynamicType->kind(),
1049 Substring{std::move(checked.value()), std::move(first),
1050 std::move(last)});
1053 Say("substring may apply only to CHARACTER"_err_en_US);
1058 return std::nullopt;
1061 // CHARACTER literal substrings
1062 MaybeExpr ExpressionAnalyzer::Analyze(
1063 const parser::CharLiteralConstantSubstring &x) {
1064 const parser::SubstringRange &range{std::get<parser::SubstringRange>(x.t)};
1065 std::optional<Expr<SubscriptInteger>> lower{
1066 GetSubstringBound(std::get<0>(range.t))};
1067 std::optional<Expr<SubscriptInteger>> upper{
1068 GetSubstringBound(std::get<1>(range.t))};
1069 if (MaybeExpr string{Analyze(std::get<parser::CharLiteralConstant>(x.t))}) {
1070 if (auto *charExpr{std::get_if<Expr<SomeCharacter>>(&string->u)}) {
1071 Expr<SubscriptInteger> length{
1072 common::visit([](const auto &ckExpr) { return ckExpr.LEN().value(); },
1073 charExpr->u)};
1074 if (!lower) {
1075 lower = Expr<SubscriptInteger>{1};
1077 if (!upper) {
1078 upper = Expr<SubscriptInteger>{
1079 static_cast<std::int64_t>(ToInt64(length).value())};
1081 return common::visit(
1082 [&](auto &&ckExpr) -> MaybeExpr {
1083 using Result = ResultType<decltype(ckExpr)>;
1084 auto *cp{std::get_if<Constant<Result>>(&ckExpr.u)};
1085 CHECK(DEREF(cp).size() == 1);
1086 StaticDataObject::Pointer staticData{StaticDataObject::Create()};
1087 staticData->set_alignment(Result::kind)
1088 .set_itemBytes(Result::kind)
1089 .Push(cp->GetScalarValue().value(),
1090 foldingContext_.targetCharacteristics().isBigEndian());
1091 Substring substring{std::move(staticData), std::move(lower.value()),
1092 std::move(upper.value())};
1093 return AsGenericExpr(
1094 Expr<Result>{Designator<Result>{std::move(substring)}});
1096 std::move(charExpr->u));
1099 return std::nullopt;
1102 // substring%KIND/LEN
1103 MaybeExpr ExpressionAnalyzer::Analyze(const parser::SubstringInquiry &x) {
1104 if (MaybeExpr substring{Analyze(x.v)}) {
1105 CHECK(x.source.size() >= 8);
1106 int nameLen{x.source.end()[-1] == 'n' ? 3 /*LEN*/ : 4 /*KIND*/};
1107 parser::CharBlock name{
1108 x.source.end() - nameLen, static_cast<std::size_t>(nameLen)};
1109 CHECK(name == "len" || name == "kind");
1110 return MakeFunctionRef(
1111 name, ActualArguments{ActualArgument{std::move(*substring)}});
1112 } else {
1113 return std::nullopt;
1117 // Subscripted array references
1118 std::optional<Expr<SubscriptInteger>> ExpressionAnalyzer::AsSubscript(
1119 MaybeExpr &&expr) {
1120 if (expr) {
1121 if (expr->Rank() > 1) {
1122 Say("Subscript expression has rank %d greater than 1"_err_en_US,
1123 expr->Rank());
1125 if (auto *intExpr{std::get_if<Expr<SomeInteger>>(&expr->u)}) {
1126 if (auto *ssIntExpr{std::get_if<Expr<SubscriptInteger>>(&intExpr->u)}) {
1127 return std::move(*ssIntExpr);
1128 } else {
1129 return Expr<SubscriptInteger>{
1130 Convert<SubscriptInteger, TypeCategory::Integer>{
1131 std::move(*intExpr)}};
1133 } else {
1134 Say("Subscript expression is not INTEGER"_err_en_US);
1137 return std::nullopt;
1140 std::optional<Expr<SubscriptInteger>> ExpressionAnalyzer::TripletPart(
1141 const std::optional<parser::Subscript> &s) {
1142 if (s) {
1143 return AsSubscript(Analyze(*s));
1144 } else {
1145 return std::nullopt;
1149 std::optional<Subscript> ExpressionAnalyzer::AnalyzeSectionSubscript(
1150 const parser::SectionSubscript &ss) {
1151 return common::visit(
1152 common::visitors{
1153 [&](const parser::SubscriptTriplet &t) -> std::optional<Subscript> {
1154 const auto &lower{std::get<0>(t.t)};
1155 const auto &upper{std::get<1>(t.t)};
1156 const auto &stride{std::get<2>(t.t)};
1157 auto result{Triplet{
1158 TripletPart(lower), TripletPart(upper), TripletPart(stride)}};
1159 if ((lower && !result.lower()) || (upper && !result.upper())) {
1160 return std::nullopt;
1161 } else {
1162 return std::make_optional<Subscript>(result);
1165 [&](const auto &s) -> std::optional<Subscript> {
1166 if (auto subscriptExpr{AsSubscript(Analyze(s))}) {
1167 return Subscript{std::move(*subscriptExpr)};
1168 } else {
1169 return std::nullopt;
1173 ss.u);
1176 // Empty result means an error occurred
1177 std::vector<Subscript> ExpressionAnalyzer::AnalyzeSectionSubscripts(
1178 const std::list<parser::SectionSubscript> &sss) {
1179 bool error{false};
1180 std::vector<Subscript> subscripts;
1181 for (const auto &s : sss) {
1182 if (auto subscript{AnalyzeSectionSubscript(s)}) {
1183 subscripts.emplace_back(std::move(*subscript));
1184 } else {
1185 error = true;
1188 return !error ? subscripts : std::vector<Subscript>{};
1191 MaybeExpr ExpressionAnalyzer::Analyze(const parser::ArrayElement &ae) {
1192 MaybeExpr baseExpr;
1194 auto restorer{AllowWholeAssumedSizeArray()};
1195 baseExpr = Analyze(ae.base);
1197 if (baseExpr) {
1198 if (ae.subscripts.empty()) {
1199 // will be converted to function call later or error reported
1200 } else if (baseExpr->Rank() == 0) {
1201 if (const Symbol *symbol{GetLastSymbol(*baseExpr)}) {
1202 if (!context_.HasError(symbol)) {
1203 if (inDataStmtConstant_) {
1204 // Better error for NULL(X) with a MOLD= argument
1205 Say("'%s' must be an array or structure constructor if used with non-empty parentheses as a DATA statement constant"_err_en_US,
1206 symbol->name());
1207 } else {
1208 Say("'%s' is not an array"_err_en_US, symbol->name());
1210 context_.SetError(*symbol);
1213 } else if (std::optional<DataRef> dataRef{
1214 ExtractDataRef(std::move(*baseExpr))}) {
1215 return ApplySubscripts(
1216 std::move(*dataRef), AnalyzeSectionSubscripts(ae.subscripts));
1217 } else {
1218 Say("Subscripts may be applied only to an object, component, or array constant"_err_en_US);
1221 // error was reported: analyze subscripts without reporting more errors
1222 auto restorer{GetContextualMessages().DiscardMessages()};
1223 AnalyzeSectionSubscripts(ae.subscripts);
1224 return std::nullopt;
1227 // Type parameter inquiries apply to data references, but don't depend
1228 // on any trailing (co)subscripts.
1229 static NamedEntity IgnoreAnySubscripts(Designator<SomeDerived> &&designator) {
1230 return common::visit(
1231 common::visitors{
1232 [](SymbolRef &&symbol) { return NamedEntity{symbol}; },
1233 [](Component &&component) {
1234 return NamedEntity{std::move(component)};
1236 [](ArrayRef &&arrayRef) { return std::move(arrayRef.base()); },
1237 [](CoarrayRef &&coarrayRef) {
1238 return NamedEntity{coarrayRef.GetLastSymbol()};
1241 std::move(designator.u));
1244 // Components of parent derived types are explicitly represented as such.
1245 std::optional<Component> ExpressionAnalyzer::CreateComponent(
1246 DataRef &&base, const Symbol &component, const semantics::Scope &scope) {
1247 if (IsAllocatableOrPointer(component) && base.Rank() > 0) { // C919b
1248 Say("An allocatable or pointer component reference must be applied to a scalar base"_err_en_US);
1250 if (&component.owner() == &scope) {
1251 return Component{std::move(base), component};
1253 if (const Symbol *typeSymbol{scope.GetSymbol()}) {
1254 if (const Symbol *parentComponent{typeSymbol->GetParentComponent(&scope)}) {
1255 if (const auto *object{
1256 parentComponent->detailsIf<semantics::ObjectEntityDetails>()}) {
1257 if (const auto *parentType{object->type()}) {
1258 if (const semantics::Scope *parentScope{
1259 parentType->derivedTypeSpec().scope()}) {
1260 return CreateComponent(
1261 DataRef{Component{std::move(base), *parentComponent}},
1262 component, *parentScope);
1268 return std::nullopt;
1271 // Derived type component references and type parameter inquiries
1272 MaybeExpr ExpressionAnalyzer::Analyze(const parser::StructureComponent &sc) {
1273 MaybeExpr base{Analyze(sc.base)};
1274 Symbol *sym{sc.component.symbol};
1275 if (!base || !sym || context_.HasError(sym)) {
1276 return std::nullopt;
1278 const auto &name{sc.component.source};
1279 if (auto *dtExpr{UnwrapExpr<Expr<SomeDerived>>(*base)}) {
1280 const auto *dtSpec{GetDerivedTypeSpec(dtExpr->GetType())};
1281 if (sym->detailsIf<semantics::TypeParamDetails>()) {
1282 if (auto *designator{UnwrapExpr<Designator<SomeDerived>>(*dtExpr)}) {
1283 if (std::optional<DynamicType> dyType{DynamicType::From(*sym)}) {
1284 if (dyType->category() == TypeCategory::Integer) {
1285 auto restorer{GetContextualMessages().SetLocation(name)};
1286 return Fold(ConvertToType(*dyType,
1287 AsGenericExpr(TypeParamInquiry{
1288 IgnoreAnySubscripts(std::move(*designator)), *sym})));
1291 Say(name, "Type parameter is not INTEGER"_err_en_US);
1292 } else {
1293 Say(name,
1294 "A type parameter inquiry must be applied to "
1295 "a designator"_err_en_US);
1297 } else if (!dtSpec || !dtSpec->scope()) {
1298 CHECK(context_.AnyFatalError() || !foldingContext_.messages().empty());
1299 return std::nullopt;
1300 } else if (std::optional<DataRef> dataRef{
1301 ExtractDataRef(std::move(*dtExpr))}) {
1302 auto restorer{GetContextualMessages().SetLocation(name)};
1303 if (auto component{
1304 CreateComponent(std::move(*dataRef), *sym, *dtSpec->scope())}) {
1305 return Designate(DataRef{std::move(*component)});
1306 } else {
1307 Say(name, "Component is not in scope of derived TYPE(%s)"_err_en_US,
1308 dtSpec->typeSymbol().name());
1310 } else {
1311 Say(name,
1312 "Base of component reference must be a data reference"_err_en_US);
1314 } else if (auto *details{sym->detailsIf<semantics::MiscDetails>()}) {
1315 // special part-ref: %re, %im, %kind, %len
1316 // Type errors on the base of %re/%im/%len are detected and
1317 // reported in name resolution.
1318 using MiscKind = semantics::MiscDetails::Kind;
1319 MiscKind kind{details->kind()};
1320 if (kind == MiscKind::ComplexPartRe || kind == MiscKind::ComplexPartIm) {
1321 if (auto *zExpr{std::get_if<Expr<SomeComplex>>(&base->u)}) {
1322 if (std::optional<DataRef> dataRef{ExtractDataRef(*zExpr)}) {
1323 // Represent %RE/%IM as a designator
1324 Expr<SomeReal> realExpr{common::visit(
1325 [&](const auto &z) {
1326 using PartType = typename ResultType<decltype(z)>::Part;
1327 auto part{kind == MiscKind::ComplexPartRe
1328 ? ComplexPart::Part::RE
1329 : ComplexPart::Part::IM};
1330 return AsCategoryExpr(Designator<PartType>{
1331 ComplexPart{std::move(*dataRef), part}});
1333 zExpr->u)};
1334 return AsGenericExpr(std::move(realExpr));
1337 } else if (kind == MiscKind::KindParamInquiry ||
1338 kind == MiscKind::LenParamInquiry) {
1339 ActualArgument arg{std::move(*base)};
1340 SetArgSourceLocation(arg, name);
1341 return MakeFunctionRef(name, ActualArguments{std::move(arg)});
1342 } else {
1343 DIE("unexpected MiscDetails::Kind");
1345 } else {
1346 Say(name, "derived type required before component reference"_err_en_US);
1348 return std::nullopt;
1351 MaybeExpr ExpressionAnalyzer::Analyze(const parser::CoindexedNamedObject &x) {
1352 if (auto maybeDataRef{ExtractDataRef(Analyze(x.base))}) {
1353 DataRef *dataRef{&*maybeDataRef};
1354 std::vector<Subscript> subscripts;
1355 SymbolVector reversed;
1356 if (auto *aRef{std::get_if<ArrayRef>(&dataRef->u)}) {
1357 subscripts = std::move(aRef->subscript());
1358 reversed.push_back(aRef->GetLastSymbol());
1359 if (Component *component{aRef->base().UnwrapComponent()}) {
1360 dataRef = &component->base();
1361 } else {
1362 dataRef = nullptr;
1365 if (dataRef) {
1366 while (auto *component{std::get_if<Component>(&dataRef->u)}) {
1367 reversed.push_back(component->GetLastSymbol());
1368 dataRef = &component->base();
1370 if (auto *baseSym{std::get_if<SymbolRef>(&dataRef->u)}) {
1371 reversed.push_back(*baseSym);
1372 } else {
1373 Say("Base of coindexed named object has subscripts or cosubscripts"_err_en_US);
1376 std::vector<Expr<SubscriptInteger>> cosubscripts;
1377 bool cosubsOk{true};
1378 for (const auto &cosub :
1379 std::get<std::list<parser::Cosubscript>>(x.imageSelector.t)) {
1380 MaybeExpr coex{Analyze(cosub)};
1381 if (auto *intExpr{UnwrapExpr<Expr<SomeInteger>>(coex)}) {
1382 cosubscripts.push_back(
1383 ConvertToType<SubscriptInteger>(std::move(*intExpr)));
1384 } else {
1385 cosubsOk = false;
1388 if (cosubsOk && !reversed.empty()) {
1389 int numCosubscripts{static_cast<int>(cosubscripts.size())};
1390 const Symbol &symbol{reversed.front()};
1391 if (numCosubscripts != symbol.Corank()) {
1392 Say("'%s' has corank %d, but coindexed reference has %d cosubscripts"_err_en_US,
1393 symbol.name(), symbol.Corank(), numCosubscripts);
1396 for (const auto &imageSelSpec :
1397 std::get<std::list<parser::ImageSelectorSpec>>(x.imageSelector.t)) {
1398 common::visit(
1399 common::visitors{
1400 [&](const auto &x) { Analyze(x.v); },
1402 imageSelSpec.u);
1404 // Reverse the chain of symbols so that the base is first and coarray
1405 // ultimate component is last.
1406 if (cosubsOk) {
1407 return Designate(
1408 DataRef{CoarrayRef{SymbolVector{reversed.crbegin(), reversed.crend()},
1409 std::move(subscripts), std::move(cosubscripts)}});
1412 return std::nullopt;
1415 int ExpressionAnalyzer::IntegerTypeSpecKind(
1416 const parser::IntegerTypeSpec &spec) {
1417 Expr<SubscriptInteger> value{
1418 AnalyzeKindSelector(TypeCategory::Integer, spec.v)};
1419 if (auto kind{ToInt64(value)}) {
1420 return static_cast<int>(*kind);
1422 SayAt(spec, "Constant INTEGER kind value required here"_err_en_US);
1423 return GetDefaultKind(TypeCategory::Integer);
1426 // Array constructors
1428 // Inverts a collection of generic ArrayConstructorValues<SomeType> that
1429 // all happen to have the same actual type T into one ArrayConstructor<T>.
1430 template <typename T>
1431 ArrayConstructorValues<T> MakeSpecific(
1432 ArrayConstructorValues<SomeType> &&from) {
1433 ArrayConstructorValues<T> to;
1434 for (ArrayConstructorValue<SomeType> &x : from) {
1435 common::visit(
1436 common::visitors{
1437 [&](common::CopyableIndirection<Expr<SomeType>> &&expr) {
1438 auto *typed{UnwrapExpr<Expr<T>>(expr.value())};
1439 to.Push(std::move(DEREF(typed)));
1441 [&](ImpliedDo<SomeType> &&impliedDo) {
1442 to.Push(ImpliedDo<T>{impliedDo.name(),
1443 std::move(impliedDo.lower()), std::move(impliedDo.upper()),
1444 std::move(impliedDo.stride()),
1445 MakeSpecific<T>(std::move(impliedDo.values()))});
1448 std::move(x.u));
1450 return to;
1453 class ArrayConstructorContext {
1454 public:
1455 ArrayConstructorContext(
1456 ExpressionAnalyzer &c, std::optional<DynamicTypeWithLength> &&t)
1457 : exprAnalyzer_{c}, type_{std::move(t)} {}
1459 void Add(const parser::AcValue &);
1460 MaybeExpr ToExpr();
1462 // These interfaces allow *this to be used as a type visitor argument to
1463 // common::SearchTypes() to convert the array constructor to a typed
1464 // expression in ToExpr().
1465 using Result = MaybeExpr;
1466 using Types = AllTypes;
1467 template <typename T> Result Test() {
1468 if (type_ && type_->category() == T::category) {
1469 if constexpr (T::category == TypeCategory::Derived) {
1470 if (!type_->IsUnlimitedPolymorphic()) {
1471 return AsMaybeExpr(ArrayConstructor<T>{type_->GetDerivedTypeSpec(),
1472 MakeSpecific<T>(std::move(values_))});
1474 } else if (type_->kind() == T::kind) {
1475 ArrayConstructor<T> result{MakeSpecific<T>(std::move(values_))};
1476 if constexpr (T::category == TypeCategory::Character) {
1477 if (auto len{type_->LEN()}) {
1478 if (IsConstantExpr(*len)) {
1479 result.set_LEN(std::move(*len));
1483 return AsMaybeExpr(std::move(result));
1486 return std::nullopt;
1489 private:
1490 using ImpliedDoIntType = ResultType<ImpliedDoIndex>;
1492 void Push(MaybeExpr &&);
1493 void Add(const parser::AcValue::Triplet &);
1494 void Add(const parser::Expr &);
1495 void Add(const parser::AcImpliedDo &);
1496 void UnrollConstantImpliedDo(const parser::AcImpliedDo &,
1497 parser::CharBlock name, std::int64_t lower, std::int64_t upper,
1498 std::int64_t stride);
1500 template <int KIND, typename A>
1501 std::optional<Expr<Type<TypeCategory::Integer, KIND>>> GetSpecificIntExpr(
1502 const A &x) {
1503 if (MaybeExpr y{exprAnalyzer_.Analyze(x)}) {
1504 Expr<SomeInteger> *intExpr{UnwrapExpr<Expr<SomeInteger>>(*y)};
1505 return Fold(exprAnalyzer_.GetFoldingContext(),
1506 ConvertToType<Type<TypeCategory::Integer, KIND>>(
1507 std::move(DEREF(intExpr))));
1509 return std::nullopt;
1512 // Nested array constructors all reference the same ExpressionAnalyzer,
1513 // which represents the nest of active implied DO loop indices.
1514 ExpressionAnalyzer &exprAnalyzer_;
1515 std::optional<DynamicTypeWithLength> type_;
1516 bool explicitType_{type_.has_value()};
1517 std::optional<std::int64_t> constantLength_;
1518 ArrayConstructorValues<SomeType> values_;
1519 std::uint64_t messageDisplayedSet_{0};
1522 void ArrayConstructorContext::Push(MaybeExpr &&x) {
1523 if (!x) {
1524 return;
1526 if (!type_) {
1527 if (auto *boz{std::get_if<BOZLiteralConstant>(&x->u)}) {
1528 // Treat an array constructor of BOZ as if default integer.
1529 if (exprAnalyzer_.context().ShouldWarn(
1530 common::LanguageFeature::BOZAsDefaultInteger)) {
1531 exprAnalyzer_.Say(
1532 "BOZ literal in array constructor without explicit type is assumed to be default INTEGER"_port_en_US);
1534 x = AsGenericExpr(ConvertToKind<TypeCategory::Integer>(
1535 exprAnalyzer_.GetDefaultKind(TypeCategory::Integer),
1536 std::move(*boz)));
1539 std::optional<DynamicType> dyType{x->GetType()};
1540 if (!dyType) {
1541 if (auto *boz{std::get_if<BOZLiteralConstant>(&x->u)}) {
1542 if (!type_) {
1543 // Treat an array constructor of BOZ as if default integer.
1544 if (exprAnalyzer_.context().ShouldWarn(
1545 common::LanguageFeature::BOZAsDefaultInteger)) {
1546 exprAnalyzer_.Say(
1547 "BOZ literal in array constructor without explicit type is assumed to be default INTEGER"_port_en_US);
1549 x = AsGenericExpr(ConvertToKind<TypeCategory::Integer>(
1550 exprAnalyzer_.GetDefaultKind(TypeCategory::Integer),
1551 std::move(*boz)));
1552 dyType = x.value().GetType();
1553 } else if (auto cast{ConvertToType(*type_, std::move(*x))}) {
1554 x = std::move(cast);
1555 dyType = *type_;
1556 } else {
1557 if (!(messageDisplayedSet_ & 0x80)) {
1558 exprAnalyzer_.Say(
1559 "BOZ literal is not suitable for use in this array constructor"_err_en_US);
1560 messageDisplayedSet_ |= 0x80;
1562 return;
1564 } else { // procedure name, &c.
1565 if (!(messageDisplayedSet_ & 0x40)) {
1566 exprAnalyzer_.Say(
1567 "Item is not suitable for use in an array constructor"_err_en_US);
1568 messageDisplayedSet_ |= 0x40;
1570 return;
1572 } else if (dyType->IsUnlimitedPolymorphic()) {
1573 if (!(messageDisplayedSet_ & 8)) {
1574 exprAnalyzer_.Say("Cannot have an unlimited polymorphic value in an "
1575 "array constructor"_err_en_US); // C7113
1576 messageDisplayedSet_ |= 8;
1578 return;
1580 DynamicTypeWithLength xType{dyType.value()};
1581 if (Expr<SomeCharacter> * charExpr{UnwrapExpr<Expr<SomeCharacter>>(*x)}) {
1582 CHECK(xType.category() == TypeCategory::Character);
1583 xType.length =
1584 common::visit([](const auto &kc) { return kc.LEN(); }, charExpr->u);
1586 if (!type_) {
1587 // If there is no explicit type-spec in an array constructor, the type
1588 // of the array is the declared type of all of the elements, which must
1589 // be well-defined and all match.
1590 // TODO: Possible language extension: use the most general type of
1591 // the values as the type of a numeric constructed array, convert all
1592 // of the other values to that type. Alternative: let the first value
1593 // determine the type, and convert the others to that type.
1594 CHECK(!explicitType_);
1595 type_ = std::move(xType);
1596 constantLength_ = ToInt64(type_->length);
1597 values_.Push(std::move(*x));
1598 } else if (!explicitType_) {
1599 if (type_->IsTkCompatibleWith(xType) && xType.IsTkCompatibleWith(*type_)) {
1600 values_.Push(std::move(*x));
1601 if (auto thisLen{ToInt64(xType.LEN())}) {
1602 if (constantLength_) {
1603 if (exprAnalyzer_.context().warnOnNonstandardUsage() &&
1604 *thisLen != *constantLength_) {
1605 if (!(messageDisplayedSet_ & 1)) {
1606 exprAnalyzer_.Say(
1607 "Character literal in array constructor without explicit "
1608 "type has different length than earlier elements"_port_en_US);
1609 messageDisplayedSet_ |= 1;
1612 if (*thisLen > *constantLength_) {
1613 // Language extension: use the longest literal to determine the
1614 // length of the array constructor's character elements, not the
1615 // first, when there is no explicit type.
1616 *constantLength_ = *thisLen;
1617 type_->length = xType.LEN();
1619 } else {
1620 constantLength_ = *thisLen;
1621 type_->length = xType.LEN();
1624 } else {
1625 if (!(messageDisplayedSet_ & 2)) {
1626 exprAnalyzer_.Say(
1627 "Values in array constructor must have the same declared type "
1628 "when no explicit type appears"_err_en_US); // C7110
1629 messageDisplayedSet_ |= 2;
1632 } else {
1633 if (auto cast{ConvertToType(*type_, std::move(*x))}) {
1634 values_.Push(std::move(*cast));
1635 } else if (!(messageDisplayedSet_ & 4)) {
1636 exprAnalyzer_.Say("Value in array constructor of type '%s' could not "
1637 "be converted to the type of the array '%s'"_err_en_US,
1638 x->GetType()->AsFortran(), type_->AsFortran()); // C7111, C7112
1639 messageDisplayedSet_ |= 4;
1644 void ArrayConstructorContext::Add(const parser::AcValue &x) {
1645 common::visit(
1646 common::visitors{
1647 [&](const parser::AcValue::Triplet &triplet) { Add(triplet); },
1648 [&](const common::Indirection<parser::Expr> &expr) {
1649 Add(expr.value());
1651 [&](const common::Indirection<parser::AcImpliedDo> &impliedDo) {
1652 Add(impliedDo.value());
1655 x.u);
1658 // Transforms l:u(:s) into (_,_=l,u(,s)) with an anonymous index '_'
1659 void ArrayConstructorContext::Add(const parser::AcValue::Triplet &triplet) {
1660 std::optional<Expr<ImpliedDoIntType>> lower{
1661 GetSpecificIntExpr<ImpliedDoIntType::kind>(std::get<0>(triplet.t))};
1662 std::optional<Expr<ImpliedDoIntType>> upper{
1663 GetSpecificIntExpr<ImpliedDoIntType::kind>(std::get<1>(triplet.t))};
1664 std::optional<Expr<ImpliedDoIntType>> stride{
1665 GetSpecificIntExpr<ImpliedDoIntType::kind>(std::get<2>(triplet.t))};
1666 if (lower && upper) {
1667 if (!stride) {
1668 stride = Expr<ImpliedDoIntType>{1};
1670 if (!type_) {
1671 type_ = DynamicTypeWithLength{ImpliedDoIntType::GetType()};
1673 auto v{std::move(values_)};
1674 parser::CharBlock anonymous;
1675 Push(Expr<SomeType>{
1676 Expr<SomeInteger>{Expr<ImpliedDoIntType>{ImpliedDoIndex{anonymous}}}});
1677 std::swap(v, values_);
1678 values_.Push(ImpliedDo<SomeType>{anonymous, std::move(*lower),
1679 std::move(*upper), std::move(*stride), std::move(v)});
1683 void ArrayConstructorContext::Add(const parser::Expr &expr) {
1684 auto restorer{exprAnalyzer_.GetContextualMessages().SetLocation(expr.source)};
1685 Push(exprAnalyzer_.Analyze(expr));
1688 void ArrayConstructorContext::Add(const parser::AcImpliedDo &impliedDo) {
1689 const auto &control{std::get<parser::AcImpliedDoControl>(impliedDo.t)};
1690 const auto &bounds{std::get<parser::AcImpliedDoControl::Bounds>(control.t)};
1691 exprAnalyzer_.Analyze(bounds.name);
1692 parser::CharBlock name{bounds.name.thing.thing.source};
1693 const Symbol *symbol{bounds.name.thing.thing.symbol};
1694 int kind{ImpliedDoIntType::kind};
1695 if (const auto dynamicType{DynamicType::From(symbol)}) {
1696 kind = dynamicType->kind();
1698 std::optional<Expr<ImpliedDoIntType>> lower{
1699 GetSpecificIntExpr<ImpliedDoIntType::kind>(bounds.lower)};
1700 std::optional<Expr<ImpliedDoIntType>> upper{
1701 GetSpecificIntExpr<ImpliedDoIntType::kind>(bounds.upper)};
1702 if (lower && upper) {
1703 std::optional<Expr<ImpliedDoIntType>> stride{
1704 GetSpecificIntExpr<ImpliedDoIntType::kind>(bounds.step)};
1705 if (!stride) {
1706 stride = Expr<ImpliedDoIntType>{1};
1708 if (exprAnalyzer_.AddImpliedDo(name, kind)) {
1709 // Check for constant bounds; the loop may require complete unrolling
1710 // of the parse tree if all bounds are constant in order to allow the
1711 // implied DO loop index to qualify as a constant expression.
1712 auto cLower{ToInt64(lower)};
1713 auto cUpper{ToInt64(upper)};
1714 auto cStride{ToInt64(stride)};
1715 if (!(messageDisplayedSet_ & 0x10) && cStride && *cStride == 0) {
1716 exprAnalyzer_.SayAt(bounds.step.value().thing.thing.value().source,
1717 "The stride of an implied DO loop must not be zero"_err_en_US);
1718 messageDisplayedSet_ |= 0x10;
1720 bool isConstant{cLower && cUpper && cStride && *cStride != 0};
1721 bool isNonemptyConstant{isConstant &&
1722 ((*cStride > 0 && *cLower <= *cUpper) ||
1723 (*cStride < 0 && *cLower >= *cUpper))};
1724 bool unrollConstantLoop{false};
1725 parser::Messages buffer;
1726 auto saveMessagesDisplayed{messageDisplayedSet_};
1728 auto messageRestorer{
1729 exprAnalyzer_.GetContextualMessages().SetMessages(buffer)};
1730 auto v{std::move(values_)};
1731 for (const auto &value :
1732 std::get<std::list<parser::AcValue>>(impliedDo.t)) {
1733 Add(value);
1735 std::swap(v, values_);
1736 if (isNonemptyConstant && buffer.AnyFatalError()) {
1737 unrollConstantLoop = true;
1738 } else {
1739 values_.Push(ImpliedDo<SomeType>{name, std::move(*lower),
1740 std::move(*upper), std::move(*stride), std::move(v)});
1743 if (unrollConstantLoop) {
1744 messageDisplayedSet_ = saveMessagesDisplayed;
1745 UnrollConstantImpliedDo(impliedDo, name, *cLower, *cUpper, *cStride);
1746 } else if (auto *messages{
1747 exprAnalyzer_.GetContextualMessages().messages()}) {
1748 messages->Annex(std::move(buffer));
1750 exprAnalyzer_.RemoveImpliedDo(name);
1751 } else if (!(messageDisplayedSet_ & 0x20)) {
1752 exprAnalyzer_.SayAt(name,
1753 "Implied DO index '%s' is active in a surrounding implied DO loop "
1754 "and may not have the same name"_err_en_US,
1755 name); // C7115
1756 messageDisplayedSet_ |= 0x20;
1761 // Fortran considers an implied DO index of an array constructor to be
1762 // a constant expression if the bounds of the implied DO loop are constant.
1763 // Usually this doesn't matter, but if we emitted spurious messages as a
1764 // result of not using constant values for the index while analyzing the
1765 // items, we need to do it again the "hard" way with multiple iterations over
1766 // the parse tree.
1767 void ArrayConstructorContext::UnrollConstantImpliedDo(
1768 const parser::AcImpliedDo &impliedDo, parser::CharBlock name,
1769 std::int64_t lower, std::int64_t upper, std::int64_t stride) {
1770 auto &foldingContext{exprAnalyzer_.GetFoldingContext()};
1771 auto restorer{exprAnalyzer_.DoNotUseSavedTypedExprs()};
1772 for (auto &at{foldingContext.StartImpliedDo(name, lower)};
1773 (stride > 0 && at <= upper) || (stride < 0 && at >= upper);
1774 at += stride) {
1775 for (const auto &value :
1776 std::get<std::list<parser::AcValue>>(impliedDo.t)) {
1777 Add(value);
1780 foldingContext.EndImpliedDo(name);
1783 MaybeExpr ArrayConstructorContext::ToExpr() {
1784 return common::SearchTypes(std::move(*this));
1787 MaybeExpr ExpressionAnalyzer::Analyze(const parser::ArrayConstructor &array) {
1788 const parser::AcSpec &acSpec{array.v};
1789 ArrayConstructorContext acContext{*this, AnalyzeTypeSpec(acSpec.type)};
1790 for (const parser::AcValue &value : acSpec.values) {
1791 acContext.Add(value);
1793 return acContext.ToExpr();
1796 MaybeExpr ExpressionAnalyzer::Analyze(
1797 const parser::StructureConstructor &structure) {
1798 auto &parsedType{std::get<parser::DerivedTypeSpec>(structure.t)};
1799 parser::Name structureType{std::get<parser::Name>(parsedType.t)};
1800 parser::CharBlock &typeName{structureType.source};
1801 if (semantics::Symbol *typeSymbol{structureType.symbol}) {
1802 if (typeSymbol->has<semantics::DerivedTypeDetails>()) {
1803 semantics::DerivedTypeSpec dtSpec{typeName, typeSymbol->GetUltimate()};
1804 if (!CheckIsValidForwardReference(dtSpec)) {
1805 return std::nullopt;
1809 if (!parsedType.derivedTypeSpec) {
1810 return std::nullopt;
1812 const auto &spec{*parsedType.derivedTypeSpec};
1813 const Symbol &typeSymbol{spec.typeSymbol()};
1814 if (!spec.scope() || !typeSymbol.has<semantics::DerivedTypeDetails>()) {
1815 return std::nullopt; // error recovery
1817 const auto &typeDetails{typeSymbol.get<semantics::DerivedTypeDetails>()};
1818 const Symbol *parentComponent{typeDetails.GetParentComponent(*spec.scope())};
1820 if (typeSymbol.attrs().test(semantics::Attr::ABSTRACT)) { // C796
1821 AttachDeclaration(Say(typeName,
1822 "ABSTRACT derived type '%s' may not be used in a "
1823 "structure constructor"_err_en_US,
1824 typeName),
1825 typeSymbol); // C7114
1828 // This iterator traverses all of the components in the derived type and its
1829 // parents. The symbols for whole parent components appear after their
1830 // own components and before the components of the types that extend them.
1831 // E.g., TYPE :: A; REAL X; END TYPE
1832 // TYPE, EXTENDS(A) :: B; REAL Y; END TYPE
1833 // produces the component list X, A, Y.
1834 // The order is important below because a structure constructor can
1835 // initialize X or A by name, but not both.
1836 auto components{semantics::OrderedComponentIterator{spec}};
1837 auto nextAnonymous{components.begin()};
1839 std::set<parser::CharBlock> unavailable;
1840 bool anyKeyword{false};
1841 StructureConstructor result{spec};
1842 bool checkConflicts{true}; // until we hit one
1843 auto &messages{GetContextualMessages()};
1845 // NULL() can be a valid component
1846 auto restorer{AllowNullPointer()};
1848 for (const auto &component :
1849 std::get<std::list<parser::ComponentSpec>>(structure.t)) {
1850 const parser::Expr &expr{
1851 std::get<parser::ComponentDataSource>(component.t).v.value()};
1852 parser::CharBlock source{expr.source};
1853 auto restorer{messages.SetLocation(source)};
1854 const Symbol *symbol{nullptr};
1855 MaybeExpr value{Analyze(expr)};
1856 std::optional<DynamicType> valueType{DynamicType::From(value)};
1857 if (const auto &kw{std::get<std::optional<parser::Keyword>>(component.t)}) {
1858 anyKeyword = true;
1859 source = kw->v.source;
1860 symbol = kw->v.symbol;
1861 if (!symbol) {
1862 // Skip overridden inaccessible parent components in favor of
1863 // their later overrides.
1864 for (const Symbol &sym : components) {
1865 if (sym.name() == source) {
1866 symbol = &sym;
1870 if (!symbol) { // C7101
1871 Say(source,
1872 "Keyword '%s=' does not name a component of derived type '%s'"_err_en_US,
1873 source, typeName);
1875 } else {
1876 if (anyKeyword) { // C7100
1877 Say(source,
1878 "Value in structure constructor lacks a component name"_err_en_US);
1879 checkConflicts = false; // stem cascade
1881 // Here's a regrettably common extension of the standard: anonymous
1882 // initialization of parent components, e.g., T(PT(1)) rather than
1883 // T(1) or T(PT=PT(1)).
1884 if (nextAnonymous == components.begin() && parentComponent &&
1885 valueType == DynamicType::From(*parentComponent) &&
1886 context().IsEnabled(LanguageFeature::AnonymousParents)) {
1887 auto iter{
1888 std::find(components.begin(), components.end(), *parentComponent)};
1889 if (iter != components.end()) {
1890 symbol = parentComponent;
1891 nextAnonymous = ++iter;
1892 if (context().ShouldWarn(LanguageFeature::AnonymousParents)) {
1893 Say(source,
1894 "Whole parent component '%s' in structure "
1895 "constructor should not be anonymous"_port_en_US,
1896 symbol->name());
1900 while (!symbol && nextAnonymous != components.end()) {
1901 const Symbol &next{*nextAnonymous};
1902 ++nextAnonymous;
1903 if (!next.test(Symbol::Flag::ParentComp)) {
1904 symbol = &next;
1907 if (!symbol) {
1908 Say(source, "Unexpected value in structure constructor"_err_en_US);
1911 if (symbol) {
1912 const semantics::Scope &innermost{context_.FindScope(expr.source)};
1913 if (auto msg{CheckAccessibleSymbol(innermost, *symbol)}) {
1914 Say(expr.source, std::move(*msg));
1916 if (checkConflicts) {
1917 auto componentIter{
1918 std::find(components.begin(), components.end(), *symbol)};
1919 if (unavailable.find(symbol->name()) != unavailable.cend()) {
1920 // C797, C798
1921 Say(source,
1922 "Component '%s' conflicts with another component earlier in "
1923 "this structure constructor"_err_en_US,
1924 symbol->name());
1925 } else if (symbol->test(Symbol::Flag::ParentComp)) {
1926 // Make earlier components unavailable once a whole parent appears.
1927 for (auto it{components.begin()}; it != componentIter; ++it) {
1928 unavailable.insert(it->name());
1930 } else {
1931 // Make whole parent components unavailable after any of their
1932 // constituents appear.
1933 for (auto it{componentIter}; it != components.end(); ++it) {
1934 if (it->test(Symbol::Flag::ParentComp)) {
1935 unavailable.insert(it->name());
1940 unavailable.insert(symbol->name());
1941 if (value) {
1942 if (symbol->has<semantics::ProcEntityDetails>()) {
1943 CHECK(IsPointer(*symbol));
1944 } else if (symbol->has<semantics::ObjectEntityDetails>()) {
1945 // C1594(4)
1946 if (const auto *pureProc{FindPureProcedureContaining(innermost)}) {
1947 if (const Symbol *pointer{FindPointerComponent(*symbol)}) {
1948 if (const Symbol *object{
1949 FindExternallyVisibleObject(*value, *pureProc)}) {
1950 if (auto *msg{Say(expr.source,
1951 "Externally visible object '%s' may not be "
1952 "associated with pointer component '%s' in a "
1953 "pure procedure"_err_en_US,
1954 object->name(), pointer->name())}) {
1955 msg->Attach(object->name(), "Object declaration"_en_US)
1956 .Attach(pointer->name(), "Pointer declaration"_en_US);
1961 } else if (symbol->has<semantics::TypeParamDetails>()) {
1962 Say(expr.source,
1963 "Type parameter '%s' may not appear as a component "
1964 "of a structure constructor"_err_en_US,
1965 symbol->name());
1966 continue;
1967 } else {
1968 Say(expr.source,
1969 "Component '%s' is neither a procedure pointer "
1970 "nor a data object"_err_en_US,
1971 symbol->name());
1972 continue;
1974 if (IsPointer(*symbol)) {
1975 semantics::CheckStructConstructorPointerComponent(
1976 GetFoldingContext(), *symbol, *value, innermost); // C7104, C7105
1977 result.Add(*symbol, Fold(std::move(*value)));
1978 continue;
1980 if (IsNullPointer(*value)) {
1981 if (IsAllocatable(*symbol)) {
1982 if (IsBareNullPointer(&*value)) {
1983 // NULL() with no arguments allowed by 7.5.10 para 6 for
1984 // ALLOCATABLE.
1985 result.Add(*symbol, Expr<SomeType>{NullPointer{}});
1986 continue;
1988 if (IsNullObjectPointer(*value)) {
1989 AttachDeclaration(
1990 Say(expr.source,
1991 "NULL() with arguments is not standard conforming as the value for allocatable component '%s'"_port_en_US,
1992 symbol->name()),
1993 *symbol);
1994 // proceed to check type & shape
1995 } else {
1996 AttachDeclaration(
1997 Say(expr.source,
1998 "A NULL procedure pointer may not be used as the value for component '%s'"_err_en_US,
1999 symbol->name()),
2000 *symbol);
2001 continue;
2003 } else {
2004 AttachDeclaration(
2005 Say(expr.source,
2006 "A NULL pointer may not be used as the value for component '%s'"_err_en_US,
2007 symbol->name()),
2008 *symbol);
2009 continue;
2012 if (MaybeExpr converted{ConvertToType(*symbol, std::move(*value))}) {
2013 if (auto componentShape{GetShape(GetFoldingContext(), *symbol)}) {
2014 if (auto valueShape{GetShape(GetFoldingContext(), *converted)}) {
2015 if (GetRank(*componentShape) == 0 && GetRank(*valueShape) > 0) {
2016 AttachDeclaration(
2017 Say(expr.source,
2018 "Rank-%d array value is not compatible with scalar component '%s'"_err_en_US,
2019 GetRank(*valueShape), symbol->name()),
2020 *symbol);
2021 } else {
2022 auto checked{
2023 CheckConformance(messages, *componentShape, *valueShape,
2024 CheckConformanceFlags::RightIsExpandableDeferred,
2025 "component", "value")};
2026 if (checked && *checked && GetRank(*componentShape) > 0 &&
2027 GetRank(*valueShape) == 0 &&
2028 (IsDeferredShape(*symbol) ||
2029 !IsExpandableScalar(*converted, GetFoldingContext(),
2030 *componentShape, true /*admit PURE call*/))) {
2031 AttachDeclaration(
2032 Say(expr.source,
2033 "Scalar value cannot be expanded to shape of array component '%s'"_err_en_US,
2034 symbol->name()),
2035 *symbol);
2037 if (checked.value_or(true)) {
2038 result.Add(*symbol, std::move(*converted));
2041 } else {
2042 Say(expr.source, "Shape of value cannot be determined"_err_en_US);
2044 } else {
2045 AttachDeclaration(
2046 Say(expr.source,
2047 "Shape of component '%s' cannot be determined"_err_en_US,
2048 symbol->name()),
2049 *symbol);
2051 } else if (auto symType{DynamicType::From(symbol)}) {
2052 if (IsAllocatable(*symbol) && symType->IsUnlimitedPolymorphic() &&
2053 valueType) {
2054 // ok
2055 } else if (valueType) {
2056 AttachDeclaration(
2057 Say(expr.source,
2058 "Value in structure constructor of type '%s' is "
2059 "incompatible with component '%s' of type '%s'"_err_en_US,
2060 valueType->AsFortran(), symbol->name(),
2061 symType->AsFortran()),
2062 *symbol);
2063 } else {
2064 AttachDeclaration(
2065 Say(expr.source,
2066 "Value in structure constructor is incompatible with "
2067 "component '%s' of type %s"_err_en_US,
2068 symbol->name(), symType->AsFortran()),
2069 *symbol);
2076 // Ensure that unmentioned component objects have default initializers.
2077 for (const Symbol &symbol : components) {
2078 if (!symbol.test(Symbol::Flag::ParentComp) &&
2079 unavailable.find(symbol.name()) == unavailable.cend()) {
2080 if (IsAllocatable(symbol)) {
2081 // Set all remaining allocatables to explicit NULL()
2082 result.Add(symbol, Expr<SomeType>{NullPointer{}});
2083 } else if (const auto *details{
2084 symbol.detailsIf<semantics::ObjectEntityDetails>()}) {
2085 if (details->init()) {
2086 result.Add(symbol, common::Clone(*details->init()));
2087 } else { // C799
2088 AttachDeclaration(Say(typeName,
2089 "Structure constructor lacks a value for "
2090 "component '%s'"_err_en_US,
2091 symbol.name()),
2092 symbol);
2098 return AsMaybeExpr(Expr<SomeDerived>{std::move(result)});
2101 static std::optional<parser::CharBlock> GetPassName(
2102 const semantics::Symbol &proc) {
2103 return common::visit(
2104 [](const auto &details) {
2105 if constexpr (std::is_base_of_v<semantics::WithPassArg,
2106 std::decay_t<decltype(details)>>) {
2107 return details.passName();
2108 } else {
2109 return std::optional<parser::CharBlock>{};
2112 proc.details());
2115 static int GetPassIndex(const Symbol &proc) {
2116 CHECK(!proc.attrs().test(semantics::Attr::NOPASS));
2117 std::optional<parser::CharBlock> passName{GetPassName(proc)};
2118 const auto *interface {
2119 semantics::FindInterface(proc)
2121 if (!passName || !interface) {
2122 return 0; // first argument is passed-object
2124 const auto &subp{interface->get<semantics::SubprogramDetails>()};
2125 int index{0};
2126 for (const auto *arg : subp.dummyArgs()) {
2127 if (arg && arg->name() == passName) {
2128 return index;
2130 ++index;
2132 DIE("PASS argument name not in dummy argument list");
2135 // Injects an expression into an actual argument list as the "passed object"
2136 // for a type-bound procedure reference that is not NOPASS. Adds an
2137 // argument keyword if possible, but not when the passed object goes
2138 // before a positional argument.
2139 // e.g., obj%tbp(x) -> tbp(obj,x).
2140 static void AddPassArg(ActualArguments &actuals, const Expr<SomeDerived> &expr,
2141 const Symbol &component, bool isPassedObject = true) {
2142 if (component.attrs().test(semantics::Attr::NOPASS)) {
2143 return;
2145 int passIndex{GetPassIndex(component)};
2146 auto iter{actuals.begin()};
2147 int at{0};
2148 while (iter < actuals.end() && at < passIndex) {
2149 if (*iter && (*iter)->keyword()) {
2150 iter = actuals.end();
2151 break;
2153 ++iter;
2154 ++at;
2156 ActualArgument passed{AsGenericExpr(common::Clone(expr))};
2157 passed.set_isPassedObject(isPassedObject);
2158 if (iter == actuals.end()) {
2159 if (auto passName{GetPassName(component)}) {
2160 passed.set_keyword(*passName);
2163 actuals.emplace(iter, std::move(passed));
2166 // Return the compile-time resolution of a procedure binding, if possible.
2167 static const Symbol *GetBindingResolution(
2168 const std::optional<DynamicType> &baseType, const Symbol &component) {
2169 const auto *binding{component.detailsIf<semantics::ProcBindingDetails>()};
2170 if (!binding) {
2171 return nullptr;
2173 if (!component.attrs().test(semantics::Attr::NON_OVERRIDABLE) &&
2174 (!baseType || baseType->IsPolymorphic())) {
2175 return nullptr;
2177 return &binding->symbol();
2180 auto ExpressionAnalyzer::AnalyzeProcedureComponentRef(
2181 const parser::ProcComponentRef &pcr, ActualArguments &&arguments,
2182 bool isSubroutine) -> std::optional<CalleeAndArguments> {
2183 const parser::StructureComponent &sc{pcr.v.thing};
2184 if (MaybeExpr base{Analyze(sc.base)}) {
2185 if (const Symbol *sym{sc.component.symbol}) {
2186 if (context_.HasError(sym)) {
2187 return std::nullopt;
2189 if (!IsProcedure(*sym)) {
2190 AttachDeclaration(
2191 Say(sc.component.source, "'%s' is not a procedure"_err_en_US,
2192 sc.component.source),
2193 *sym);
2194 return std::nullopt;
2196 if (auto *dtExpr{UnwrapExpr<Expr<SomeDerived>>(*base)}) {
2197 if (sym->has<semantics::GenericDetails>()) {
2198 auto dyType{dtExpr->GetType()};
2199 AdjustActuals adjustment{
2200 [&](const Symbol &proc, ActualArguments &actuals) {
2201 if (!proc.attrs().test(semantics::Attr::NOPASS)) {
2202 AddPassArg(actuals, std::move(*dtExpr), proc);
2204 return true;
2206 auto pair{ResolveGeneric(*sym, arguments, adjustment, isSubroutine)};
2207 sym = pair.first;
2208 if (sym) {
2209 // re-resolve the name to the specific binding
2210 CHECK(sym->has<semantics::ProcBindingDetails>());
2211 // Use the most recent override of the binding, if any
2212 CHECK(dyType && dyType->category() == TypeCategory::Derived &&
2213 !dyType->IsUnlimitedPolymorphic());
2214 if (const Symbol *latest{
2215 DEREF(dyType->GetDerivedTypeSpec().typeSymbol().scope())
2216 .FindComponent(sym->name())}) {
2217 sym = latest;
2219 sc.component.symbol = const_cast<Symbol *>(sym);
2220 } else {
2221 EmitGenericResolutionError(
2222 *sc.component.symbol, pair.second, isSubroutine);
2223 return std::nullopt;
2226 std::optional<DataRef> dataRef{ExtractDataRef(std::move(*dtExpr))};
2227 if (dataRef && !CheckDataRef(*dataRef)) {
2228 return std::nullopt;
2230 if (dataRef && dataRef->Rank() > 0) {
2231 if (sym->has<semantics::ProcBindingDetails>() &&
2232 sym->attrs().test(semantics::Attr::NOPASS)) {
2233 // C1529 seems unnecessary and most compilers don't enforce it.
2234 AttachDeclaration(
2235 Say(sc.component.source,
2236 "Base of NOPASS type-bound procedure reference should be scalar"_port_en_US),
2237 *sym);
2238 } else if (IsProcedurePointer(*sym)) { // C919
2239 Say(sc.component.source,
2240 "Base of procedure component reference must be scalar"_err_en_US);
2243 if (const Symbol *resolution{
2244 GetBindingResolution(dtExpr->GetType(), *sym)}) {
2245 AddPassArg(arguments, std::move(*dtExpr), *sym, false);
2246 return CalleeAndArguments{
2247 ProcedureDesignator{*resolution}, std::move(arguments)};
2248 } else if (dataRef.has_value()) {
2249 if (sym->attrs().test(semantics::Attr::NOPASS)) {
2250 return CalleeAndArguments{
2251 ProcedureDesignator{Component{std::move(*dataRef), *sym}},
2252 std::move(arguments)};
2253 } else {
2254 AddPassArg(arguments,
2255 Expr<SomeDerived>{Designator<SomeDerived>{std::move(*dataRef)}},
2256 *sym);
2257 return CalleeAndArguments{
2258 ProcedureDesignator{*sym}, std::move(arguments)};
2262 Say(sc.component.source,
2263 "Base of procedure component reference is not a derived-type object"_err_en_US);
2266 CHECK(context_.AnyFatalError());
2267 return std::nullopt;
2270 // Can actual be argument associated with dummy?
2271 static bool CheckCompatibleArgument(bool isElemental,
2272 const ActualArgument &actual, const characteristics::DummyArgument &dummy) {
2273 const auto *expr{actual.UnwrapExpr()};
2274 return common::visit(
2275 common::visitors{
2276 [&](const characteristics::DummyDataObject &x) {
2277 if (x.attrs.test(characteristics::DummyDataObject::Attr::Pointer) &&
2278 IsBareNullPointer(expr)) {
2279 // NULL() without MOLD= is compatible with any dummy data pointer
2280 // but cannot be allowed to lead to ambiguity.
2281 return true;
2282 } else if (!isElemental && actual.Rank() != x.type.Rank() &&
2283 !x.type.attrs().test(
2284 characteristics::TypeAndShape::Attr::AssumedRank)) {
2285 return false;
2286 } else if (auto actualType{actual.GetType()}) {
2287 return x.type.type().IsTkCompatibleWith(*actualType);
2289 return false;
2291 [&](const characteristics::DummyProcedure &) {
2292 return expr && IsProcedurePointerTarget(*expr);
2294 [&](const characteristics::AlternateReturn &) {
2295 return actual.isAlternateReturn();
2298 dummy.u);
2301 // Are the actual arguments compatible with the dummy arguments of procedure?
2302 static bool CheckCompatibleArguments(
2303 const characteristics::Procedure &procedure,
2304 const ActualArguments &actuals) {
2305 bool isElemental{procedure.IsElemental()};
2306 const auto &dummies{procedure.dummyArguments};
2307 CHECK(dummies.size() == actuals.size());
2308 for (std::size_t i{0}; i < dummies.size(); ++i) {
2309 const characteristics::DummyArgument &dummy{dummies[i]};
2310 const std::optional<ActualArgument> &actual{actuals[i]};
2311 if (actual && !CheckCompatibleArgument(isElemental, *actual, dummy)) {
2312 return false;
2315 return true;
2318 // Handles a forward reference to a module function from what must
2319 // be a specification expression. Return false if the symbol is
2320 // an invalid forward reference.
2321 bool ExpressionAnalyzer::ResolveForward(const Symbol &symbol) {
2322 if (context_.HasError(symbol)) {
2323 return false;
2325 if (const auto *details{
2326 symbol.detailsIf<semantics::SubprogramNameDetails>()}) {
2327 if (details->kind() == semantics::SubprogramKind::Module) {
2328 // If this symbol is still a SubprogramNameDetails, we must be
2329 // checking a specification expression in a sibling module
2330 // procedure. Resolve its names now so that its interface
2331 // is known.
2332 semantics::ResolveSpecificationParts(context_, symbol);
2333 if (symbol.has<semantics::SubprogramNameDetails>()) {
2334 // When the symbol hasn't had its details updated, we must have
2335 // already been in the process of resolving the function's
2336 // specification part; but recursive function calls are not
2337 // allowed in specification parts (10.1.11 para 5).
2338 Say("The module function '%s' may not be referenced recursively in a specification expression"_err_en_US,
2339 symbol.name());
2340 context_.SetError(symbol);
2341 return false;
2343 } else if (inStmtFunctionDefinition_) {
2344 semantics::ResolveSpecificationParts(context_, symbol);
2345 CHECK(symbol.has<semantics::SubprogramDetails>());
2346 } else { // 10.1.11 para 4
2347 Say("The internal function '%s' may not be referenced in a specification expression"_err_en_US,
2348 symbol.name());
2349 context_.SetError(symbol);
2350 return false;
2353 return true;
2356 // Resolve a call to a generic procedure with given actual arguments.
2357 // adjustActuals is called on procedure bindings to handle pass arg.
2358 std::pair<const Symbol *, bool> ExpressionAnalyzer::ResolveGeneric(
2359 const Symbol &symbol, const ActualArguments &actuals,
2360 const AdjustActuals &adjustActuals, bool isSubroutine,
2361 bool mightBeStructureConstructor) {
2362 const Symbol *elemental{nullptr}; // matching elemental specific proc
2363 const Symbol *nonElemental{nullptr}; // matching non-elemental specific
2364 const Symbol &ultimate{symbol.GetUltimate()};
2365 // Check for a match with an explicit INTRINSIC
2366 if (ultimate.attrs().test(semantics::Attr::INTRINSIC)) {
2367 parser::Messages buffer;
2368 auto restorer{foldingContext_.messages().SetMessages(buffer)};
2369 ActualArguments localActuals{actuals};
2370 if (context_.intrinsics().Probe(
2371 CallCharacteristics{ultimate.name().ToString(), isSubroutine},
2372 localActuals, foldingContext_) &&
2373 !buffer.AnyFatalError()) {
2374 return {&ultimate, false};
2377 if (const auto *details{ultimate.detailsIf<semantics::GenericDetails>()}) {
2378 for (const Symbol &specific : details->specificProcs()) {
2379 if (isSubroutine != !IsFunction(specific)) {
2380 continue;
2382 if (!ResolveForward(specific)) {
2383 continue;
2385 if (std::optional<characteristics::Procedure> procedure{
2386 characteristics::Procedure::Characterize(
2387 ProcedureDesignator{specific}, context_.foldingContext())}) {
2388 ActualArguments localActuals{actuals};
2389 if (specific.has<semantics::ProcBindingDetails>()) {
2390 if (!adjustActuals.value()(specific, localActuals)) {
2391 continue;
2394 if (semantics::CheckInterfaceForGeneric(*procedure, localActuals,
2395 GetFoldingContext(), false /* no integer conversions */) &&
2396 CheckCompatibleArguments(*procedure, localActuals)) {
2397 if ((procedure->IsElemental() && elemental) ||
2398 (!procedure->IsElemental() && nonElemental)) {
2399 // 16.9.144(6): a bare NULL() is not allowed as an actual
2400 // argument to a generic procedure if the specific procedure
2401 // cannot be unambiguously distinguished
2402 // Underspecified external procedure actual arguments can
2403 // also lead to ambiguity.
2404 return {nullptr, true /* due to ambiguity */};
2406 if (!procedure->IsElemental()) {
2407 // takes priority over elemental match
2408 nonElemental = &specific;
2409 } else {
2410 elemental = &specific;
2415 if (nonElemental) {
2416 return {&AccessSpecific(symbol, *nonElemental), false};
2417 } else if (elemental) {
2418 return {&AccessSpecific(symbol, *elemental), false};
2420 // Check parent derived type
2421 if (const auto *parentScope{symbol.owner().GetDerivedTypeParent()}) {
2422 if (const Symbol *extended{parentScope->FindComponent(symbol.name())}) {
2423 auto pair{ResolveGeneric(
2424 *extended, actuals, adjustActuals, isSubroutine, false)};
2425 if (pair.first) {
2426 return pair;
2430 if (mightBeStructureConstructor && details->derivedType()) {
2431 return {details->derivedType(), false};
2434 // Check for generic or explicit INTRINSIC of the same name in outer scopes.
2435 // See 15.5.5.2 for details.
2436 if (!symbol.owner().IsGlobal() && !symbol.owner().IsDerivedType()) {
2437 for (const std::string &n : GetAllNames(context_, symbol.name())) {
2438 if (const Symbol *outer{symbol.owner().parent().FindSymbol(n)}) {
2439 auto pair{ResolveGeneric(*outer, actuals, adjustActuals, isSubroutine,
2440 mightBeStructureConstructor)};
2441 if (pair.first) {
2442 return pair;
2447 return {nullptr, false};
2450 const Symbol &ExpressionAnalyzer::AccessSpecific(
2451 const Symbol &originalGeneric, const Symbol &specific) {
2452 if (const auto *hosted{
2453 originalGeneric.detailsIf<semantics::HostAssocDetails>()}) {
2454 return AccessSpecific(hosted->symbol(), specific);
2455 } else if (const auto *used{
2456 originalGeneric.detailsIf<semantics::UseDetails>()}) {
2457 const auto &scope{originalGeneric.owner()};
2458 if (auto iter{scope.find(specific.name())}; iter != scope.end()) {
2459 if (const auto *useDetails{
2460 iter->second->detailsIf<semantics::UseDetails>()}) {
2461 const Symbol &usedSymbol{useDetails->symbol()};
2462 const auto *usedGeneric{
2463 usedSymbol.detailsIf<semantics::GenericDetails>()};
2464 if (&usedSymbol == &specific ||
2465 (usedGeneric && usedGeneric->specific() == &specific)) {
2466 return specific;
2470 // Create a renaming USE of the specific procedure.
2471 auto rename{context_.SaveTempName(
2472 used->symbol().owner().GetName().value().ToString() + "$" +
2473 specific.owner().GetName().value().ToString() + "$" +
2474 specific.name().ToString())};
2475 return *const_cast<semantics::Scope &>(scope)
2476 .try_emplace(rename, specific.attrs(),
2477 semantics::UseDetails{rename, specific})
2478 .first->second;
2479 } else {
2480 return specific;
2484 void ExpressionAnalyzer::EmitGenericResolutionError(
2485 const Symbol &symbol, bool dueToAmbiguity, bool isSubroutine) {
2486 Say(dueToAmbiguity
2487 ? "One or more actual arguments to the generic procedure '%s' matched multiple specific procedures, perhaps due to use of NULL() without MOLD= or an actual procedure with an implicit interface"_err_en_US
2488 : semantics::IsGenericDefinedOp(symbol)
2489 ? "No specific procedure of generic operator '%s' matches the actual arguments"_err_en_US
2490 : isSubroutine
2491 ? "No specific subroutine of generic '%s' matches the actual arguments"_err_en_US
2492 : "No specific function of generic '%s' matches the actual arguments"_err_en_US,
2493 symbol.name());
2496 auto ExpressionAnalyzer::GetCalleeAndArguments(
2497 const parser::ProcedureDesignator &pd, ActualArguments &&arguments,
2498 bool isSubroutine, bool mightBeStructureConstructor)
2499 -> std::optional<CalleeAndArguments> {
2500 return common::visit(common::visitors{
2501 [&](const parser::Name &name) {
2502 return GetCalleeAndArguments(name,
2503 std::move(arguments), isSubroutine,
2504 mightBeStructureConstructor);
2506 [&](const parser::ProcComponentRef &pcr) {
2507 return AnalyzeProcedureComponentRef(
2508 pcr, std::move(arguments), isSubroutine);
2511 pd.u);
2514 auto ExpressionAnalyzer::GetCalleeAndArguments(const parser::Name &name,
2515 ActualArguments &&arguments, bool isSubroutine,
2516 bool mightBeStructureConstructor) -> std::optional<CalleeAndArguments> {
2517 const Symbol *symbol{name.symbol};
2518 if (context_.HasError(symbol)) {
2519 return std::nullopt; // also handles null symbol
2521 const Symbol &ultimate{DEREF(symbol).GetUltimate()};
2522 CheckForBadRecursion(name.source, ultimate);
2523 bool dueToAmbiguity{false};
2524 bool isGenericInterface{ultimate.has<semantics::GenericDetails>()};
2525 bool isExplicitIntrinsic{ultimate.attrs().test(semantics::Attr::INTRINSIC)};
2526 const Symbol *resolution{nullptr};
2527 if (isGenericInterface || isExplicitIntrinsic) {
2528 ExpressionAnalyzer::AdjustActuals noAdjustment;
2529 auto pair{ResolveGeneric(*symbol, arguments, noAdjustment, isSubroutine,
2530 mightBeStructureConstructor)};
2531 resolution = pair.first;
2532 dueToAmbiguity = pair.second;
2533 if (resolution) {
2534 // re-resolve name to the specific procedure
2535 name.symbol = const_cast<Symbol *>(resolution);
2537 } else if (IsProcedure(ultimate) &&
2538 ultimate.attrs().test(semantics::Attr::ABSTRACT)) {
2539 Say("Abstract procedure interface '%s' may not be referenced"_err_en_US,
2540 name.source);
2541 } else {
2542 resolution = symbol;
2544 if (!resolution || resolution->attrs().test(semantics::Attr::INTRINSIC)) {
2545 // Not generic, or no resolution; may be intrinsic
2546 if (std::optional<SpecificCall> specificCall{context_.intrinsics().Probe(
2547 CallCharacteristics{ultimate.name().ToString(), isSubroutine},
2548 arguments, GetFoldingContext())}) {
2549 CheckBadExplicitType(*specificCall, *symbol);
2550 return CalleeAndArguments{
2551 ProcedureDesignator{std::move(specificCall->specificIntrinsic)},
2552 std::move(specificCall->arguments)};
2553 } else {
2554 if (isGenericInterface) {
2555 EmitGenericResolutionError(*symbol, dueToAmbiguity, isSubroutine);
2557 return std::nullopt;
2560 if (resolution->GetUltimate().has<semantics::DerivedTypeDetails>()) {
2561 if (mightBeStructureConstructor) {
2562 return CalleeAndArguments{
2563 semantics::SymbolRef{*resolution}, std::move(arguments)};
2565 } else if (IsProcedure(*resolution)) {
2566 return CalleeAndArguments{
2567 ProcedureDesignator{*resolution}, std::move(arguments)};
2569 if (!context_.HasError(*resolution)) {
2570 AttachDeclaration(
2571 Say(name.source, "'%s' is not a callable procedure"_err_en_US,
2572 name.source),
2573 *resolution);
2575 return std::nullopt;
2578 // Fortran 2018 expressly states (8.2 p3) that any declared type for a
2579 // generic intrinsic function "has no effect" on the result type of a
2580 // call to that intrinsic. So one can declare "character*8 cos" and
2581 // still get a real result from "cos(1.)". This is a dangerous feature,
2582 // especially since implementations are free to extend their sets of
2583 // intrinsics, and in doing so might clash with a name in a program.
2584 // So we emit a warning in this situation, and perhaps it should be an
2585 // error -- any correctly working program can silence the message by
2586 // simply deleting the pointless type declaration.
2587 void ExpressionAnalyzer::CheckBadExplicitType(
2588 const SpecificCall &call, const Symbol &intrinsic) {
2589 if (intrinsic.GetUltimate().GetType()) {
2590 const auto &procedure{call.specificIntrinsic.characteristics.value()};
2591 if (const auto &result{procedure.functionResult}) {
2592 if (const auto *typeAndShape{result->GetTypeAndShape()}) {
2593 if (auto declared{
2594 typeAndShape->Characterize(intrinsic, GetFoldingContext())}) {
2595 if (!declared->type().IsTkCompatibleWith(typeAndShape->type())) {
2596 if (auto *msg{Say(
2597 "The result type '%s' of the intrinsic function '%s' is not the explicit declared type '%s'"_warn_en_US,
2598 typeAndShape->AsFortran(), intrinsic.name(),
2599 declared->AsFortran())}) {
2600 msg->Attach(intrinsic.name(),
2601 "Ignored declaration of intrinsic function '%s'"_en_US,
2602 intrinsic.name());
2611 void ExpressionAnalyzer::CheckForBadRecursion(
2612 parser::CharBlock callSite, const semantics::Symbol &proc) {
2613 if (const auto *scope{proc.scope()}) {
2614 if (scope->sourceRange().Contains(callSite)) {
2615 parser::Message *msg{nullptr};
2616 if (proc.attrs().test(semantics::Attr::NON_RECURSIVE)) { // 15.6.2.1(3)
2617 msg = Say("NON_RECURSIVE procedure '%s' cannot call itself"_err_en_US,
2618 callSite);
2619 } else if (IsAssumedLengthCharacter(proc) && IsExternal(proc)) {
2620 // TODO: Also catch assumed PDT type parameters
2621 msg = Say( // 15.6.2.1(3)
2622 "Assumed-length CHARACTER(*) function '%s' cannot call itself"_err_en_US,
2623 callSite);
2625 AttachDeclaration(msg, proc);
2630 template <typename A> static const Symbol *AssumedTypeDummy(const A &x) {
2631 if (const auto *designator{
2632 std::get_if<common::Indirection<parser::Designator>>(&x.u)}) {
2633 if (const auto *dataRef{
2634 std::get_if<parser::DataRef>(&designator->value().u)}) {
2635 if (const auto *name{std::get_if<parser::Name>(&dataRef->u)}) {
2636 return AssumedTypeDummy(*name);
2640 return nullptr;
2642 template <>
2643 const Symbol *AssumedTypeDummy<parser::Name>(const parser::Name &name) {
2644 if (const Symbol *symbol{name.symbol}) {
2645 if (const auto *type{symbol->GetType()}) {
2646 if (type->category() == semantics::DeclTypeSpec::TypeStar) {
2647 return symbol;
2651 return nullptr;
2653 template <typename A>
2654 static const Symbol *AssumedTypePointerOrAllocatableDummy(const A &object) {
2655 // It is illegal for allocatable of pointer objects to be TYPE(*), but at that
2656 // point it is is not guaranteed that it has been checked the object has
2657 // POINTER or ALLOCATABLE attribute, so do not assume nullptr can be directly
2658 // returned.
2659 return common::visit(
2660 common::visitors{
2661 [&](const parser::StructureComponent &x) {
2662 return AssumedTypeDummy(x.component);
2664 [&](const parser::Name &x) { return AssumedTypeDummy(x); },
2666 object.u);
2668 template <>
2669 const Symbol *AssumedTypeDummy<parser::AllocateObject>(
2670 const parser::AllocateObject &x) {
2671 return AssumedTypePointerOrAllocatableDummy(x);
2673 template <>
2674 const Symbol *AssumedTypeDummy<parser::PointerObject>(
2675 const parser::PointerObject &x) {
2676 return AssumedTypePointerOrAllocatableDummy(x);
2679 bool ExpressionAnalyzer::CheckIsValidForwardReference(
2680 const semantics::DerivedTypeSpec &dtSpec) {
2681 if (dtSpec.IsForwardReferenced()) {
2682 Say("Cannot construct value for derived type '%s' "
2683 "before it is defined"_err_en_US,
2684 dtSpec.name());
2685 return false;
2687 return true;
2690 MaybeExpr ExpressionAnalyzer::Analyze(const parser::FunctionReference &funcRef,
2691 std::optional<parser::StructureConstructor> *structureConstructor) {
2692 const parser::Call &call{funcRef.v};
2693 auto restorer{GetContextualMessages().SetLocation(call.source)};
2694 ArgumentAnalyzer analyzer{*this, call.source, true /* isProcedureCall */};
2695 for (const auto &arg : std::get<std::list<parser::ActualArgSpec>>(call.t)) {
2696 analyzer.Analyze(arg, false /* not subroutine call */);
2698 if (analyzer.fatalErrors()) {
2699 return std::nullopt;
2701 if (std::optional<CalleeAndArguments> callee{
2702 GetCalleeAndArguments(std::get<parser::ProcedureDesignator>(call.t),
2703 analyzer.GetActuals(), false /* not subroutine */,
2704 true /* might be structure constructor */)}) {
2705 if (auto *proc{std::get_if<ProcedureDesignator>(&callee->u)}) {
2706 return MakeFunctionRef(
2707 call.source, std::move(*proc), std::move(callee->arguments));
2709 CHECK(std::holds_alternative<semantics::SymbolRef>(callee->u));
2710 const Symbol &symbol{*std::get<semantics::SymbolRef>(callee->u)};
2711 if (structureConstructor) {
2712 // Structure constructor misparsed as function reference?
2713 const auto &designator{std::get<parser::ProcedureDesignator>(call.t)};
2714 if (const auto *name{std::get_if<parser::Name>(&designator.u)}) {
2715 semantics::Scope &scope{context_.FindScope(name->source)};
2716 semantics::DerivedTypeSpec dtSpec{name->source, symbol.GetUltimate()};
2717 if (!CheckIsValidForwardReference(dtSpec)) {
2718 return std::nullopt;
2720 const semantics::DeclTypeSpec &type{
2721 semantics::FindOrInstantiateDerivedType(scope, std::move(dtSpec))};
2722 auto &mutableRef{const_cast<parser::FunctionReference &>(funcRef)};
2723 *structureConstructor =
2724 mutableRef.ConvertToStructureConstructor(type.derivedTypeSpec());
2725 return Analyze(structureConstructor->value());
2728 if (!context_.HasError(symbol)) {
2729 AttachDeclaration(
2730 Say("'%s' is called like a function but is not a procedure"_err_en_US,
2731 symbol.name()),
2732 symbol);
2733 context_.SetError(symbol);
2736 return std::nullopt;
2739 static bool HasAlternateReturns(const evaluate::ActualArguments &args) {
2740 for (const auto &arg : args) {
2741 if (arg && arg->isAlternateReturn()) {
2742 return true;
2745 return false;
2748 void ExpressionAnalyzer::Analyze(const parser::CallStmt &callStmt) {
2749 const parser::Call &call{callStmt.v};
2750 auto restorer{GetContextualMessages().SetLocation(call.source)};
2751 ArgumentAnalyzer analyzer{*this, call.source, true /* isProcedureCall */};
2752 const auto &actualArgList{std::get<std::list<parser::ActualArgSpec>>(call.t)};
2753 for (const auto &arg : actualArgList) {
2754 analyzer.Analyze(arg, true /* is subroutine call */);
2756 if (!analyzer.fatalErrors()) {
2757 if (std::optional<CalleeAndArguments> callee{
2758 GetCalleeAndArguments(std::get<parser::ProcedureDesignator>(call.t),
2759 analyzer.GetActuals(), true /* subroutine */)}) {
2760 ProcedureDesignator *proc{std::get_if<ProcedureDesignator>(&callee->u)};
2761 CHECK(proc);
2762 if (CheckCall(call.source, *proc, callee->arguments)) {
2763 callStmt.typedCall.Reset(
2764 new ProcedureRef{std::move(*proc), std::move(callee->arguments),
2765 HasAlternateReturns(callee->arguments)},
2766 ProcedureRef::Deleter);
2767 return;
2770 if (!context_.AnyFatalError()) {
2771 std::string buf;
2772 llvm::raw_string_ostream dump{buf};
2773 parser::DumpTree(dump, callStmt);
2774 Say("Internal error: Expression analysis failed on CALL statement: %s"_err_en_US,
2775 dump.str());
2780 const Assignment *ExpressionAnalyzer::Analyze(const parser::AssignmentStmt &x) {
2781 if (!x.typedAssignment) {
2782 ArgumentAnalyzer analyzer{*this};
2783 const auto &variable{std::get<parser::Variable>(x.t)};
2784 analyzer.Analyze(variable);
2785 analyzer.Analyze(std::get<parser::Expr>(x.t));
2786 std::optional<Assignment> assignment;
2787 if (!analyzer.fatalErrors()) {
2788 auto restorer{GetContextualMessages().SetLocation(variable.GetSource())};
2789 std::optional<ProcedureRef> procRef{analyzer.TryDefinedAssignment()};
2790 if (!procRef) {
2791 analyzer.CheckForNullPointer(
2792 "in a non-pointer intrinsic assignment statement");
2793 const Expr<SomeType> &lhs{analyzer.GetExpr(0)};
2794 if (auto dyType{lhs.GetType()};
2795 dyType && dyType->IsPolymorphic()) { // 10.2.1.2p1(1)
2796 const Symbol *lastWhole0{UnwrapWholeSymbolOrComponentDataRef(lhs)};
2797 const Symbol *lastWhole{
2798 lastWhole0 ? &lastWhole0->GetUltimate() : nullptr};
2799 if (!lastWhole || !IsAllocatable(*lastWhole)) {
2800 Say("Left-hand side of assignment may not be polymorphic unless assignment is to an entire allocatable"_err_en_US);
2801 } else if (evaluate::IsCoarray(*lastWhole)) {
2802 Say("Left-hand side of assignment may not be polymorphic if it is a coarray"_err_en_US);
2806 assignment.emplace(analyzer.MoveExpr(0), analyzer.MoveExpr(1));
2807 if (procRef) {
2808 assignment->u = std::move(*procRef);
2811 x.typedAssignment.Reset(new GenericAssignmentWrapper{std::move(assignment)},
2812 GenericAssignmentWrapper::Deleter);
2814 return common::GetPtrFromOptional(x.typedAssignment->v);
2817 const Assignment *ExpressionAnalyzer::Analyze(
2818 const parser::PointerAssignmentStmt &x) {
2819 if (!x.typedAssignment) {
2820 MaybeExpr lhs{Analyze(std::get<parser::DataRef>(x.t))};
2821 MaybeExpr rhs;
2823 auto restorer{AllowNullPointer()};
2824 rhs = Analyze(std::get<parser::Expr>(x.t));
2826 if (!lhs || !rhs) {
2827 x.typedAssignment.Reset(
2828 new GenericAssignmentWrapper{}, GenericAssignmentWrapper::Deleter);
2829 } else {
2830 Assignment assignment{std::move(*lhs), std::move(*rhs)};
2831 common::visit(
2832 common::visitors{
2833 [&](const std::list<parser::BoundsRemapping> &list) {
2834 Assignment::BoundsRemapping bounds;
2835 for (const auto &elem : list) {
2836 auto lower{AsSubscript(Analyze(std::get<0>(elem.t)))};
2837 auto upper{AsSubscript(Analyze(std::get<1>(elem.t)))};
2838 if (lower && upper) {
2839 bounds.emplace_back(
2840 Fold(std::move(*lower)), Fold(std::move(*upper)));
2843 assignment.u = std::move(bounds);
2845 [&](const std::list<parser::BoundsSpec> &list) {
2846 Assignment::BoundsSpec bounds;
2847 for (const auto &bound : list) {
2848 if (auto lower{AsSubscript(Analyze(bound.v))}) {
2849 bounds.emplace_back(Fold(std::move(*lower)));
2852 assignment.u = std::move(bounds);
2855 std::get<parser::PointerAssignmentStmt::Bounds>(x.t).u);
2856 x.typedAssignment.Reset(
2857 new GenericAssignmentWrapper{std::move(assignment)},
2858 GenericAssignmentWrapper::Deleter);
2861 return common::GetPtrFromOptional(x.typedAssignment->v);
2864 static bool IsExternalCalledImplicitly(
2865 parser::CharBlock callSite, const ProcedureDesignator &proc) {
2866 if (const auto *symbol{proc.GetSymbol()}) {
2867 return symbol->has<semantics::SubprogramDetails>() &&
2868 symbol->owner().IsGlobal() &&
2869 (!symbol->scope() /*ENTRY*/ ||
2870 !symbol->scope()->sourceRange().Contains(callSite));
2871 } else {
2872 return false;
2876 std::optional<characteristics::Procedure> ExpressionAnalyzer::CheckCall(
2877 parser::CharBlock callSite, const ProcedureDesignator &proc,
2878 ActualArguments &arguments) {
2879 bool treatExternalAsImplicit{IsExternalCalledImplicitly(callSite, proc)};
2880 const Symbol *procSymbol{proc.GetSymbol()};
2881 std::optional<characteristics::Procedure> chars;
2882 if (procSymbol && procSymbol->has<semantics::ProcEntityDetails>() &&
2883 procSymbol->owner().IsGlobal()) {
2884 // Unknown global external, implicit interface; assume
2885 // characteristics from the actual arguments, and check
2886 // for consistency with other references.
2887 chars = characteristics::Procedure::FromActuals(
2888 proc, arguments, context_.foldingContext());
2889 if (chars && procSymbol) {
2890 // Ensure calls over implicit interfaces are consistent
2891 auto name{procSymbol->name()};
2892 if (auto iter{implicitInterfaces_.find(name)};
2893 iter != implicitInterfaces_.end()) {
2894 std::string whyNot;
2895 if (!chars->IsCompatibleWith(iter->second.second, &whyNot)) {
2896 if (auto *msg{Say(callSite,
2897 "Reference to the procedure '%s' has an implicit interface that is distinct from another reference: %s"_warn_en_US,
2898 name, whyNot)}) {
2899 msg->Attach(
2900 iter->second.first, "previous reference to '%s'"_en_US, name);
2903 } else {
2904 implicitInterfaces_.insert(
2905 std::make_pair(name, std::make_pair(callSite, *chars)));
2909 if (!chars) {
2910 chars = characteristics::Procedure::Characterize(
2911 proc, context_.foldingContext());
2913 bool ok{true};
2914 if (chars) {
2915 if (treatExternalAsImplicit && !chars->CanBeCalledViaImplicitInterface()) {
2916 Say(callSite,
2917 "References to the procedure '%s' require an explicit interface"_err_en_US,
2918 DEREF(procSymbol).name());
2920 const SpecificIntrinsic *specificIntrinsic{proc.GetSpecificIntrinsic()};
2921 bool procIsDummy{procSymbol && IsDummy(*procSymbol)};
2922 if (chars->functionResult &&
2923 chars->functionResult->IsAssumedLengthCharacter() &&
2924 !specificIntrinsic && !procIsDummy) {
2925 Say(callSite,
2926 "Assumed-length character function must be defined with a length to be called"_err_en_US);
2928 ok &= semantics::CheckArguments(*chars, arguments, GetFoldingContext(),
2929 context_.FindScope(callSite), treatExternalAsImplicit,
2930 specificIntrinsic);
2931 if (procSymbol && !IsPureProcedure(*procSymbol)) {
2932 if (const semantics::Scope *
2933 pure{semantics::FindPureProcedureContaining(
2934 context_.FindScope(callSite))}) {
2935 Say(callSite,
2936 "Procedure '%s' referenced in pure subprogram '%s' must be pure too"_err_en_US,
2937 procSymbol->name(), DEREF(pure->symbol()).name());
2941 if (ok && !treatExternalAsImplicit && procSymbol &&
2942 !(chars && chars->HasExplicitInterface())) {
2943 if (const Symbol *global{FindGlobal(*procSymbol)};
2944 global && global != procSymbol && IsProcedure(*global)) {
2945 // Check a known global definition behind a local interface
2946 if (auto globalChars{characteristics::Procedure::Characterize(
2947 *global, context_.foldingContext())}) {
2948 semantics::CheckArguments(*globalChars, arguments, GetFoldingContext(),
2949 context_.FindScope(callSite), true,
2950 nullptr /*not specific intrinsic*/);
2954 return chars;
2957 // Unary operations
2959 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Parentheses &x) {
2960 if (MaybeExpr operand{Analyze(x.v.value())}) {
2961 if (const semantics::Symbol *symbol{GetLastSymbol(*operand)}) {
2962 if (const semantics::Symbol *result{FindFunctionResult(*symbol)}) {
2963 if (semantics::IsProcedurePointer(*result)) {
2964 Say("A function reference that returns a procedure "
2965 "pointer may not be parenthesized"_err_en_US); // C1003
2969 return Parenthesize(std::move(*operand));
2971 return std::nullopt;
2974 static MaybeExpr NumericUnaryHelper(ExpressionAnalyzer &context,
2975 NumericOperator opr, const parser::Expr::IntrinsicUnary &x) {
2976 ArgumentAnalyzer analyzer{context};
2977 analyzer.Analyze(x.v);
2978 if (!analyzer.fatalErrors()) {
2979 if (analyzer.IsIntrinsicNumeric(opr)) {
2980 analyzer.CheckForNullPointer();
2981 if (opr == NumericOperator::Add) {
2982 return analyzer.MoveExpr(0);
2983 } else {
2984 return Negation(context.GetContextualMessages(), analyzer.MoveExpr(0));
2986 } else {
2987 return analyzer.TryDefinedOp(AsFortran(opr),
2988 "Operand of unary %s must be numeric; have %s"_err_en_US);
2991 return std::nullopt;
2994 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::UnaryPlus &x) {
2995 return NumericUnaryHelper(*this, NumericOperator::Add, x);
2998 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Negate &x) {
2999 if (const auto *litConst{
3000 std::get_if<parser::LiteralConstant>(&x.v.value().u)}) {
3001 if (const auto *intConst{
3002 std::get_if<parser::IntLiteralConstant>(&litConst->u)}) {
3003 return Analyze(*intConst, true);
3006 return NumericUnaryHelper(*this, NumericOperator::Subtract, x);
3009 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::NOT &x) {
3010 ArgumentAnalyzer analyzer{*this};
3011 analyzer.Analyze(x.v);
3012 if (!analyzer.fatalErrors()) {
3013 if (analyzer.IsIntrinsicLogical()) {
3014 analyzer.CheckForNullPointer();
3015 return AsGenericExpr(
3016 LogicalNegation(std::get<Expr<SomeLogical>>(analyzer.MoveExpr(0).u)));
3017 } else {
3018 return analyzer.TryDefinedOp(LogicalOperator::Not,
3019 "Operand of %s must be LOGICAL; have %s"_err_en_US);
3022 return std::nullopt;
3025 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::PercentLoc &x) {
3026 // Represent %LOC() exactly as if it had been a call to the LOC() extension
3027 // intrinsic function.
3028 // Use the actual source for the name of the call for error reporting.
3029 std::optional<ActualArgument> arg;
3030 if (const Symbol *assumedTypeDummy{AssumedTypeDummy(x.v.value())}) {
3031 arg = ActualArgument{ActualArgument::AssumedType{*assumedTypeDummy}};
3032 } else if (MaybeExpr argExpr{Analyze(x.v.value())}) {
3033 arg = ActualArgument{std::move(*argExpr)};
3034 } else {
3035 return std::nullopt;
3037 parser::CharBlock at{GetContextualMessages().at()};
3038 CHECK(at.size() >= 4);
3039 parser::CharBlock loc{at.begin() + 1, 3};
3040 CHECK(loc == "loc");
3041 return MakeFunctionRef(loc, ActualArguments{std::move(*arg)});
3044 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::DefinedUnary &x) {
3045 const auto &name{std::get<parser::DefinedOpName>(x.t).v};
3046 ArgumentAnalyzer analyzer{*this, name.source};
3047 analyzer.Analyze(std::get<1>(x.t));
3048 return analyzer.TryDefinedOp(name.source.ToString().c_str(),
3049 "No operator %s defined for %s"_err_en_US, true);
3052 // Binary (dyadic) operations
3054 template <template <typename> class OPR>
3055 MaybeExpr NumericBinaryHelper(ExpressionAnalyzer &context, NumericOperator opr,
3056 const parser::Expr::IntrinsicBinary &x) {
3057 ArgumentAnalyzer analyzer{context};
3058 analyzer.Analyze(std::get<0>(x.t));
3059 analyzer.Analyze(std::get<1>(x.t));
3060 if (!analyzer.fatalErrors()) {
3061 if (analyzer.IsIntrinsicNumeric(opr)) {
3062 analyzer.CheckForNullPointer();
3063 analyzer.CheckConformance();
3064 return NumericOperation<OPR>(context.GetContextualMessages(),
3065 analyzer.MoveExpr(0), analyzer.MoveExpr(1),
3066 context.GetDefaultKind(TypeCategory::Real));
3067 } else {
3068 return analyzer.TryDefinedOp(AsFortran(opr),
3069 "Operands of %s must be numeric; have %s and %s"_err_en_US);
3072 return std::nullopt;
3075 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Power &x) {
3076 return NumericBinaryHelper<Power>(*this, NumericOperator::Power, x);
3079 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Multiply &x) {
3080 return NumericBinaryHelper<Multiply>(*this, NumericOperator::Multiply, x);
3083 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Divide &x) {
3084 return NumericBinaryHelper<Divide>(*this, NumericOperator::Divide, x);
3087 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Add &x) {
3088 return NumericBinaryHelper<Add>(*this, NumericOperator::Add, x);
3091 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Subtract &x) {
3092 return NumericBinaryHelper<Subtract>(*this, NumericOperator::Subtract, x);
3095 MaybeExpr ExpressionAnalyzer::Analyze(
3096 const parser::Expr::ComplexConstructor &z) {
3097 return AnalyzeComplex(Analyze(std::get<0>(z.t).value()),
3098 Analyze(std::get<1>(z.t).value()), "complex constructor");
3101 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::Concat &x) {
3102 ArgumentAnalyzer analyzer{*this};
3103 analyzer.Analyze(std::get<0>(x.t));
3104 analyzer.Analyze(std::get<1>(x.t));
3105 if (!analyzer.fatalErrors()) {
3106 if (analyzer.IsIntrinsicConcat()) {
3107 analyzer.CheckForNullPointer();
3108 return common::visit(
3109 [&](auto &&x, auto &&y) -> MaybeExpr {
3110 using T = ResultType<decltype(x)>;
3111 if constexpr (std::is_same_v<T, ResultType<decltype(y)>>) {
3112 return AsGenericExpr(Concat<T::kind>{std::move(x), std::move(y)});
3113 } else {
3114 DIE("different types for intrinsic concat");
3117 std::move(std::get<Expr<SomeCharacter>>(analyzer.MoveExpr(0).u).u),
3118 std::move(std::get<Expr<SomeCharacter>>(analyzer.MoveExpr(1).u).u));
3119 } else {
3120 return analyzer.TryDefinedOp("//",
3121 "Operands of %s must be CHARACTER with the same kind; have %s and %s"_err_en_US);
3124 return std::nullopt;
3127 // The Name represents a user-defined intrinsic operator.
3128 // If the actuals match one of the specific procedures, return a function ref.
3129 // Otherwise report the error in messages.
3130 MaybeExpr ExpressionAnalyzer::AnalyzeDefinedOp(
3131 const parser::Name &name, ActualArguments &&actuals) {
3132 if (auto callee{GetCalleeAndArguments(name, std::move(actuals))}) {
3133 CHECK(std::holds_alternative<ProcedureDesignator>(callee->u));
3134 return MakeFunctionRef(name.source,
3135 std::move(std::get<ProcedureDesignator>(callee->u)),
3136 std::move(callee->arguments));
3137 } else {
3138 return std::nullopt;
3142 MaybeExpr RelationHelper(ExpressionAnalyzer &context, RelationalOperator opr,
3143 const parser::Expr::IntrinsicBinary &x) {
3144 ArgumentAnalyzer analyzer{context};
3145 analyzer.Analyze(std::get<0>(x.t));
3146 analyzer.Analyze(std::get<1>(x.t));
3147 if (!analyzer.fatalErrors()) {
3148 std::optional<DynamicType> leftType{analyzer.GetType(0)};
3149 std::optional<DynamicType> rightType{analyzer.GetType(1)};
3150 analyzer.ConvertBOZ(leftType, 0, rightType);
3151 analyzer.ConvertBOZ(rightType, 1, leftType);
3152 if (leftType && rightType &&
3153 analyzer.IsIntrinsicRelational(opr, *leftType, *rightType)) {
3154 analyzer.CheckForNullPointer("as a relational operand");
3155 return AsMaybeExpr(Relate(context.GetContextualMessages(), opr,
3156 analyzer.MoveExpr(0), analyzer.MoveExpr(1)));
3157 } else {
3158 return analyzer.TryDefinedOp(opr,
3159 leftType && leftType->category() == TypeCategory::Logical &&
3160 rightType && rightType->category() == TypeCategory::Logical
3161 ? "LOGICAL operands must be compared using .EQV. or .NEQV."_err_en_US
3162 : "Operands of %s must have comparable types; have %s and %s"_err_en_US);
3165 return std::nullopt;
3168 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::LT &x) {
3169 return RelationHelper(*this, RelationalOperator::LT, x);
3172 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::LE &x) {
3173 return RelationHelper(*this, RelationalOperator::LE, x);
3176 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::EQ &x) {
3177 return RelationHelper(*this, RelationalOperator::EQ, x);
3180 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::NE &x) {
3181 return RelationHelper(*this, RelationalOperator::NE, x);
3184 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::GE &x) {
3185 return RelationHelper(*this, RelationalOperator::GE, x);
3188 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::GT &x) {
3189 return RelationHelper(*this, RelationalOperator::GT, x);
3192 MaybeExpr LogicalBinaryHelper(ExpressionAnalyzer &context, LogicalOperator opr,
3193 const parser::Expr::IntrinsicBinary &x) {
3194 ArgumentAnalyzer analyzer{context};
3195 analyzer.Analyze(std::get<0>(x.t));
3196 analyzer.Analyze(std::get<1>(x.t));
3197 if (!analyzer.fatalErrors()) {
3198 if (analyzer.IsIntrinsicLogical()) {
3199 analyzer.CheckForNullPointer("as a logical operand");
3200 return AsGenericExpr(BinaryLogicalOperation(opr,
3201 std::get<Expr<SomeLogical>>(analyzer.MoveExpr(0).u),
3202 std::get<Expr<SomeLogical>>(analyzer.MoveExpr(1).u)));
3203 } else {
3204 return analyzer.TryDefinedOp(
3205 opr, "Operands of %s must be LOGICAL; have %s and %s"_err_en_US);
3208 return std::nullopt;
3211 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::AND &x) {
3212 return LogicalBinaryHelper(*this, LogicalOperator::And, x);
3215 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::OR &x) {
3216 return LogicalBinaryHelper(*this, LogicalOperator::Or, x);
3219 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::EQV &x) {
3220 return LogicalBinaryHelper(*this, LogicalOperator::Eqv, x);
3223 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::NEQV &x) {
3224 return LogicalBinaryHelper(*this, LogicalOperator::Neqv, x);
3227 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr::DefinedBinary &x) {
3228 const auto &name{std::get<parser::DefinedOpName>(x.t).v};
3229 ArgumentAnalyzer analyzer{*this, name.source};
3230 analyzer.Analyze(std::get<1>(x.t));
3231 analyzer.Analyze(std::get<2>(x.t));
3232 return analyzer.TryDefinedOp(name.source.ToString().c_str(),
3233 "No operator %s defined for %s and %s"_err_en_US, true);
3236 // Returns true if a parsed function reference should be converted
3237 // into an array element reference.
3238 static bool CheckFuncRefToArrayElement(semantics::SemanticsContext &context,
3239 const parser::FunctionReference &funcRef) {
3240 // Emit message if the function reference fix will end up an array element
3241 // reference with no subscripts, or subscripts on a scalar, because it will
3242 // not be possible to later distinguish in expressions between an empty
3243 // subscript list due to bad subscripts error recovery or because the
3244 // user did not put any.
3245 auto &proc{std::get<parser::ProcedureDesignator>(funcRef.v.t)};
3246 const auto *name{std::get_if<parser::Name>(&proc.u)};
3247 if (!name) {
3248 name = &std::get<parser::ProcComponentRef>(proc.u).v.thing.component;
3250 if (!name->symbol) {
3251 return false;
3252 } else if (name->symbol->Rank() == 0) {
3253 if (const Symbol *function{
3254 semantics::IsFunctionResultWithSameNameAsFunction(*name->symbol)}) {
3255 auto &msg{context.Say(funcRef.v.source,
3256 function->flags().test(Symbol::Flag::StmtFunction)
3257 ? "Recursive call to statement function '%s' is not allowed"_err_en_US
3258 : "Recursive call to '%s' requires a distinct RESULT in its declaration"_err_en_US,
3259 name->source)};
3260 AttachDeclaration(&msg, *function);
3261 name->symbol = const_cast<Symbol *>(function);
3263 return false;
3264 } else {
3265 if (std::get<std::list<parser::ActualArgSpec>>(funcRef.v.t).empty()) {
3266 auto &msg{context.Say(funcRef.v.source,
3267 "Reference to array '%s' with empty subscript list"_err_en_US,
3268 name->source)};
3269 if (name->symbol) {
3270 AttachDeclaration(&msg, *name->symbol);
3273 return true;
3277 // Converts, if appropriate, an original misparse of ambiguous syntax like
3278 // A(1) as a function reference into an array reference.
3279 // Misparsed structure constructors are detected elsewhere after generic
3280 // function call resolution fails.
3281 template <typename... A>
3282 static void FixMisparsedFunctionReference(
3283 semantics::SemanticsContext &context, const std::variant<A...> &constU) {
3284 // The parse tree is updated in situ when resolving an ambiguous parse.
3285 using uType = std::decay_t<decltype(constU)>;
3286 auto &u{const_cast<uType &>(constU)};
3287 if (auto *func{
3288 std::get_if<common::Indirection<parser::FunctionReference>>(&u)}) {
3289 parser::FunctionReference &funcRef{func->value()};
3290 // Ensure that there are no argument keywords
3291 for (const auto &arg :
3292 std::get<std::list<parser::ActualArgSpec>>(funcRef.v.t)) {
3293 if (std::get<std::optional<parser::Keyword>>(arg.t)) {
3294 return;
3297 auto &proc{std::get<parser::ProcedureDesignator>(funcRef.v.t)};
3298 if (Symbol *origSymbol{
3299 common::visit(common::visitors{
3300 [&](parser::Name &name) { return name.symbol; },
3301 [&](parser::ProcComponentRef &pcr) {
3302 return pcr.v.thing.component.symbol;
3305 proc.u)}) {
3306 Symbol &symbol{origSymbol->GetUltimate()};
3307 if (symbol.has<semantics::ObjectEntityDetails>() ||
3308 symbol.has<semantics::AssocEntityDetails>()) {
3309 // Note that expression in AssocEntityDetails cannot be a procedure
3310 // pointer as per C1105 so this cannot be a function reference.
3311 if constexpr (common::HasMember<common::Indirection<parser::Designator>,
3312 uType>) {
3313 if (CheckFuncRefToArrayElement(context, funcRef)) {
3314 u = common::Indirection{funcRef.ConvertToArrayElementRef()};
3316 } else {
3317 DIE("can't fix misparsed function as array reference");
3324 // Common handling of parse tree node types that retain the
3325 // representation of the analyzed expression.
3326 template <typename PARSED>
3327 MaybeExpr ExpressionAnalyzer::ExprOrVariable(
3328 const PARSED &x, parser::CharBlock source) {
3329 auto restorer{GetContextualMessages().SetLocation(source)};
3330 if constexpr (std::is_same_v<PARSED, parser::Expr> ||
3331 std::is_same_v<PARSED, parser::Variable>) {
3332 FixMisparsedFunctionReference(context_, x.u);
3334 if (AssumedTypeDummy(x)) { // C710
3335 Say("TYPE(*) dummy argument may only be used as an actual argument"_err_en_US);
3336 ResetExpr(x);
3337 return std::nullopt;
3339 MaybeExpr result;
3340 if constexpr (common::HasMember<parser::StructureConstructor,
3341 std::decay_t<decltype(x.u)>> &&
3342 common::HasMember<common::Indirection<parser::FunctionReference>,
3343 std::decay_t<decltype(x.u)>>) {
3344 if (const auto *funcRef{
3345 std::get_if<common::Indirection<parser::FunctionReference>>(
3346 &x.u)}) {
3347 // Function references in Exprs might turn out to be misparsed structure
3348 // constructors; we have to try generic procedure resolution
3349 // first to be sure.
3350 std::optional<parser::StructureConstructor> ctor;
3351 result = Analyze(funcRef->value(), &ctor);
3352 if (result && ctor) {
3353 // A misparsed function reference is really a structure
3354 // constructor. Repair the parse tree in situ.
3355 const_cast<PARSED &>(x).u = std::move(*ctor);
3357 } else {
3358 result = Analyze(x.u);
3360 } else {
3361 result = Analyze(x.u);
3363 if (result) {
3364 if constexpr (std::is_same_v<PARSED, parser::Expr>) {
3365 if (!isNullPointerOk_ && IsNullPointer(*result)) {
3366 Say(source,
3367 "NULL() may not be used as an expression in this context"_err_en_US);
3370 SetExpr(x, Fold(std::move(*result)));
3371 return x.typedExpr->v;
3372 } else {
3373 ResetExpr(x);
3374 if (!context_.AnyFatalError()) {
3375 std::string buf;
3376 llvm::raw_string_ostream dump{buf};
3377 parser::DumpTree(dump, x);
3378 Say("Internal error: Expression analysis failed on: %s"_err_en_US,
3379 dump.str());
3381 return std::nullopt;
3385 // This is an optional preliminary pass over parser::Expr subtrees.
3386 // Given an expression tree, iteratively traverse it in a bottom-up order
3387 // to analyze all of its subexpressions. A later normal top-down analysis
3388 // will then be able to use the results that will have been saved in the
3389 // parse tree without having to recurse deeply. This technique keeps
3390 // absurdly deep expression parse trees from causing the analyzer to overflow
3391 // its stack.
3392 MaybeExpr ExpressionAnalyzer::IterativelyAnalyzeSubexpressions(
3393 const parser::Expr &top) {
3394 std::vector<const parser::Expr *> queue, finish;
3395 queue.push_back(&top);
3396 do {
3397 const parser::Expr &expr{*queue.back()};
3398 queue.pop_back();
3399 if (!expr.typedExpr) {
3400 const parser::Expr::IntrinsicUnary *unary{nullptr};
3401 const parser::Expr::IntrinsicBinary *binary{nullptr};
3402 common::visit(
3403 [&unary, &binary](auto &y) {
3404 if constexpr (std::is_convertible_v<decltype(&y),
3405 decltype(unary)>) {
3406 // Don't evaluate a constant operand to Negate
3407 if (!std::holds_alternative<parser::LiteralConstant>(
3408 y.v.value().u)) {
3409 unary = &y;
3411 } else if constexpr (std::is_convertible_v<decltype(&y),
3412 decltype(binary)>) {
3413 binary = &y;
3416 expr.u);
3417 if (unary) {
3418 queue.push_back(&unary->v.value());
3419 } else if (binary) {
3420 queue.push_back(&std::get<0>(binary->t).value());
3421 queue.push_back(&std::get<1>(binary->t).value());
3423 finish.push_back(&expr);
3425 } while (!queue.empty());
3426 // Analyze the collected subexpressions in bottom-up order.
3427 // On an error, bail out and leave partial results in place.
3428 MaybeExpr result;
3429 for (auto riter{finish.rbegin()}; riter != finish.rend(); ++riter) {
3430 const parser::Expr &expr{**riter};
3431 result = ExprOrVariable(expr, expr.source);
3432 if (!result) {
3433 return result;
3436 return result; // last value was from analysis of "top"
3439 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Expr &expr) {
3440 bool wasIterativelyAnalyzing{iterativelyAnalyzingSubexpressions_};
3441 MaybeExpr result;
3442 if (useSavedTypedExprs_) {
3443 if (expr.typedExpr) {
3444 return expr.typedExpr->v;
3446 if (!wasIterativelyAnalyzing && !context_.anyDefinedIntrinsicOperator()) {
3447 iterativelyAnalyzingSubexpressions_ = true;
3448 result = IterativelyAnalyzeSubexpressions(expr);
3451 if (!result) {
3452 result = ExprOrVariable(expr, expr.source);
3454 iterativelyAnalyzingSubexpressions_ = wasIterativelyAnalyzing;
3455 return result;
3458 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Variable &variable) {
3459 if (useSavedTypedExprs_ && variable.typedExpr) {
3460 return variable.typedExpr->v;
3462 return ExprOrVariable(variable, variable.GetSource());
3465 MaybeExpr ExpressionAnalyzer::Analyze(const parser::Selector &selector) {
3466 if (const auto *var{std::get_if<parser::Variable>(&selector.u)}) {
3467 if (!useSavedTypedExprs_ || !var->typedExpr) {
3468 parser::CharBlock source{var->GetSource()};
3469 auto restorer{GetContextualMessages().SetLocation(source)};
3470 FixMisparsedFunctionReference(context_, var->u);
3471 if (const auto *funcRef{
3472 std::get_if<common::Indirection<parser::FunctionReference>>(
3473 &var->u)}) {
3474 // A Selector that parsed as a Variable might turn out during analysis
3475 // to actually be a structure constructor. In that case, repair the
3476 // Variable parse tree node into an Expr
3477 std::optional<parser::StructureConstructor> ctor;
3478 if (MaybeExpr result{Analyze(funcRef->value(), &ctor)}) {
3479 if (ctor) {
3480 auto &writable{const_cast<parser::Selector &>(selector)};
3481 writable.u = parser::Expr{std::move(*ctor)};
3482 auto &expr{std::get<parser::Expr>(writable.u)};
3483 expr.source = source;
3484 SetExpr(expr, Fold(std::move(*result)));
3485 return expr.typedExpr->v;
3486 } else {
3487 SetExpr(*var, Fold(std::move(*result)));
3488 return var->typedExpr->v;
3490 } else {
3491 ResetExpr(*var);
3492 if (context_.AnyFatalError()) {
3493 return std::nullopt;
3499 // Not a Variable -> FunctionReference; handle normally as Variable or Expr
3500 return Analyze(selector.u);
3503 MaybeExpr ExpressionAnalyzer::Analyze(const parser::DataStmtConstant &x) {
3504 auto restorer{common::ScopedSet(inDataStmtConstant_, true)};
3505 return ExprOrVariable(x, x.source);
3508 MaybeExpr ExpressionAnalyzer::Analyze(const parser::AllocateObject &x) {
3509 return ExprOrVariable(x, parser::FindSourceLocation(x));
3512 MaybeExpr ExpressionAnalyzer::Analyze(const parser::PointerObject &x) {
3513 return ExprOrVariable(x, parser::FindSourceLocation(x));
3516 Expr<SubscriptInteger> ExpressionAnalyzer::AnalyzeKindSelector(
3517 TypeCategory category,
3518 const std::optional<parser::KindSelector> &selector) {
3519 int defaultKind{GetDefaultKind(category)};
3520 if (!selector) {
3521 return Expr<SubscriptInteger>{defaultKind};
3523 return common::visit(
3524 common::visitors{
3525 [&](const parser::ScalarIntConstantExpr &x) {
3526 if (MaybeExpr kind{Analyze(x)}) {
3527 if (std::optional<std::int64_t> code{ToInt64(*kind)}) {
3528 if (CheckIntrinsicKind(category, *code)) {
3529 return Expr<SubscriptInteger>{*code};
3531 } else if (auto *intExpr{UnwrapExpr<Expr<SomeInteger>>(*kind)}) {
3532 return ConvertToType<SubscriptInteger>(std::move(*intExpr));
3535 return Expr<SubscriptInteger>{defaultKind};
3537 [&](const parser::KindSelector::StarSize &x) {
3538 std::intmax_t size = x.v;
3539 if (!CheckIntrinsicSize(category, size)) {
3540 size = defaultKind;
3541 } else if (category == TypeCategory::Complex) {
3542 size /= 2;
3544 return Expr<SubscriptInteger>{size};
3547 selector->u);
3550 int ExpressionAnalyzer::GetDefaultKind(common::TypeCategory category) {
3551 return context_.GetDefaultKind(category);
3554 DynamicType ExpressionAnalyzer::GetDefaultKindOfType(
3555 common::TypeCategory category) {
3556 return {category, GetDefaultKind(category)};
3559 bool ExpressionAnalyzer::CheckIntrinsicKind(
3560 TypeCategory category, std::int64_t kind) {
3561 if (foldingContext_.targetCharacteristics().IsTypeEnabled(
3562 category, kind)) { // C712, C714, C715, C727
3563 return true;
3564 } else if (foldingContext_.targetCharacteristics().CanSupportType(
3565 category, kind)) {
3566 Say("%s(KIND=%jd) is not an enabled type for this targe"_warn_en_US,
3567 ToUpperCase(EnumToString(category)), kind);
3568 return true;
3569 } else {
3570 Say("%s(KIND=%jd) is not a supported type"_err_en_US,
3571 ToUpperCase(EnumToString(category)), kind);
3572 return false;
3576 bool ExpressionAnalyzer::CheckIntrinsicSize(
3577 TypeCategory category, std::int64_t size) {
3578 std::int64_t kind{size};
3579 if (category == TypeCategory::Complex) {
3580 // COMPLEX*16 == COMPLEX(KIND=8)
3581 if (size % 2 == 0) {
3582 kind = size / 2;
3583 } else {
3584 Say("COMPLEX*%jd is not a supported type"_err_en_US, size);
3585 return false;
3588 if (foldingContext_.targetCharacteristics().IsTypeEnabled(
3589 category, kind)) { // C712, C714, C715, C727
3590 return true;
3591 } else if (foldingContext_.targetCharacteristics().CanSupportType(
3592 category, kind)) {
3593 Say("%s*%jd is not an enabled type for this target"_warn_en_US,
3594 ToUpperCase(EnumToString(category)), size);
3595 return true;
3596 } else {
3597 Say("%s*%jd is not a supported type"_err_en_US,
3598 ToUpperCase(EnumToString(category)), size);
3599 return false;
3603 bool ExpressionAnalyzer::AddImpliedDo(parser::CharBlock name, int kind) {
3604 return impliedDos_.insert(std::make_pair(name, kind)).second;
3607 void ExpressionAnalyzer::RemoveImpliedDo(parser::CharBlock name) {
3608 auto iter{impliedDos_.find(name)};
3609 if (iter != impliedDos_.end()) {
3610 impliedDos_.erase(iter);
3614 std::optional<int> ExpressionAnalyzer::IsImpliedDo(
3615 parser::CharBlock name) const {
3616 auto iter{impliedDos_.find(name)};
3617 if (iter != impliedDos_.cend()) {
3618 return {iter->second};
3619 } else {
3620 return std::nullopt;
3624 bool ExpressionAnalyzer::EnforceTypeConstraint(parser::CharBlock at,
3625 const MaybeExpr &result, TypeCategory category, bool defaultKind) {
3626 if (result) {
3627 if (auto type{result->GetType()}) {
3628 if (type->category() != category) { // C885
3629 Say(at, "Must have %s type, but is %s"_err_en_US,
3630 ToUpperCase(EnumToString(category)),
3631 ToUpperCase(type->AsFortran()));
3632 return false;
3633 } else if (defaultKind) {
3634 int kind{context_.GetDefaultKind(category)};
3635 if (type->kind() != kind) {
3636 Say(at, "Must have default kind(%d) of %s type, but is %s"_err_en_US,
3637 kind, ToUpperCase(EnumToString(category)),
3638 ToUpperCase(type->AsFortran()));
3639 return false;
3642 } else {
3643 Say(at, "Must have %s type, but is typeless"_err_en_US,
3644 ToUpperCase(EnumToString(category)));
3645 return false;
3648 return true;
3651 MaybeExpr ExpressionAnalyzer::MakeFunctionRef(parser::CharBlock callSite,
3652 ProcedureDesignator &&proc, ActualArguments &&arguments) {
3653 if (const auto *intrinsic{std::get_if<SpecificIntrinsic>(&proc.u)}) {
3654 if (intrinsic->characteristics.value().attrs.test(
3655 characteristics::Procedure::Attr::NullPointer) &&
3656 arguments.empty()) {
3657 return Expr<SomeType>{NullPointer{}};
3660 if (const Symbol *symbol{proc.GetSymbol()}) {
3661 if (!ResolveForward(*symbol)) {
3662 return std::nullopt;
3665 if (auto chars{CheckCall(callSite, proc, arguments)}) {
3666 if (chars->functionResult) {
3667 const auto &result{*chars->functionResult};
3668 if (result.IsProcedurePointer()) {
3669 return Expr<SomeType>{
3670 ProcedureRef{std::move(proc), std::move(arguments)}};
3671 } else {
3672 // Not a procedure pointer, so type and shape are known.
3673 return TypedWrapper<FunctionRef, ProcedureRef>(
3674 DEREF(result.GetTypeAndShape()).type(),
3675 ProcedureRef{std::move(proc), std::move(arguments)});
3677 } else {
3678 Say("Function result characteristics are not known"_err_en_US);
3681 return std::nullopt;
3684 MaybeExpr ExpressionAnalyzer::MakeFunctionRef(
3685 parser::CharBlock intrinsic, ActualArguments &&arguments) {
3686 if (std::optional<SpecificCall> specificCall{
3687 context_.intrinsics().Probe(CallCharacteristics{intrinsic.ToString()},
3688 arguments, GetFoldingContext())}) {
3689 return MakeFunctionRef(intrinsic,
3690 ProcedureDesignator{std::move(specificCall->specificIntrinsic)},
3691 std::move(specificCall->arguments));
3692 } else {
3693 return std::nullopt;
3697 MaybeExpr ExpressionAnalyzer::AnalyzeComplex(
3698 MaybeExpr &&re, MaybeExpr &&im, const char *what) {
3699 if (re && re->Rank() > 0) {
3700 Say("Real part of %s is not scalar"_port_en_US, what);
3702 if (im && im->Rank() > 0) {
3703 Say("Imaginary part of %s is not scalar"_port_en_US, what);
3705 if (re && im) {
3706 ConformabilityCheck(GetContextualMessages(), *re, *im);
3708 return AsMaybeExpr(ConstructComplex(GetContextualMessages(), std::move(re),
3709 std::move(im), GetDefaultKind(TypeCategory::Real)));
3712 void ArgumentAnalyzer::Analyze(const parser::Variable &x) {
3713 source_.ExtendToCover(x.GetSource());
3714 if (MaybeExpr expr{context_.Analyze(x)}) {
3715 if (!IsConstantExpr(*expr)) {
3716 actuals_.emplace_back(std::move(*expr));
3717 SetArgSourceLocation(actuals_.back(), x.GetSource());
3718 return;
3720 const Symbol *symbol{GetLastSymbol(*expr)};
3721 if (!symbol) {
3722 context_.SayAt(x, "Assignment to constant '%s' is not allowed"_err_en_US,
3723 x.GetSource());
3724 } else if (IsProcedure(*symbol)) {
3725 if (auto *msg{context_.SayAt(x,
3726 "Assignment to procedure '%s' is not allowed"_err_en_US,
3727 symbol->name())}) {
3728 if (auto *subp{symbol->detailsIf<semantics::SubprogramDetails>()}) {
3729 if (subp->isFunction()) {
3730 const auto &result{subp->result().name()};
3731 msg->Attach(result, "Function result is '%s'"_en_US, result);
3735 } else {
3736 context_.SayAt(
3737 x, "Assignment to '%s' is not allowed"_err_en_US, symbol->name());
3740 fatalErrors_ = true;
3743 void ArgumentAnalyzer::Analyze(
3744 const parser::ActualArgSpec &arg, bool isSubroutine) {
3745 // TODO: C1534: Don't allow a "restricted" specific intrinsic to be passed.
3746 std::optional<ActualArgument> actual;
3747 common::visit(common::visitors{
3748 [&](const common::Indirection<parser::Expr> &x) {
3749 actual = AnalyzeExpr(x.value());
3750 SetArgSourceLocation(actual, x.value().source);
3752 [&](const parser::AltReturnSpec &label) {
3753 if (!isSubroutine) {
3754 context_.Say(
3755 "alternate return specification may not appear on"
3756 " function reference"_err_en_US);
3758 actual = ActualArgument(label.v);
3760 [&](const parser::ActualArg::PercentRef &) {
3761 context_.Say("%REF() intrinsic for arguments"_todo_en_US);
3763 [&](const parser::ActualArg::PercentVal &) {
3764 context_.Say("%VAL() intrinsic for arguments"_todo_en_US);
3767 std::get<parser::ActualArg>(arg.t).u);
3768 if (actual) {
3769 if (const auto &argKW{std::get<std::optional<parser::Keyword>>(arg.t)}) {
3770 actual->set_keyword(argKW->v.source);
3772 actuals_.emplace_back(std::move(*actual));
3773 } else {
3774 fatalErrors_ = true;
3778 bool ArgumentAnalyzer::IsIntrinsicRelational(RelationalOperator opr,
3779 const DynamicType &leftType, const DynamicType &rightType) const {
3780 CHECK(actuals_.size() == 2);
3781 return semantics::IsIntrinsicRelational(
3782 opr, leftType, GetRank(0), rightType, GetRank(1));
3785 bool ArgumentAnalyzer::IsIntrinsicNumeric(NumericOperator opr) const {
3786 std::optional<DynamicType> leftType{GetType(0)};
3787 if (actuals_.size() == 1) {
3788 if (IsBOZLiteral(0)) {
3789 return opr == NumericOperator::Add; // unary '+'
3790 } else {
3791 return leftType && semantics::IsIntrinsicNumeric(*leftType);
3793 } else {
3794 std::optional<DynamicType> rightType{GetType(1)};
3795 if (IsBOZLiteral(0) && rightType) { // BOZ opr Integer/Real
3796 auto cat1{rightType->category()};
3797 return cat1 == TypeCategory::Integer || cat1 == TypeCategory::Real;
3798 } else if (IsBOZLiteral(1) && leftType) { // Integer/Real opr BOZ
3799 auto cat0{leftType->category()};
3800 return cat0 == TypeCategory::Integer || cat0 == TypeCategory::Real;
3801 } else {
3802 return leftType && rightType &&
3803 semantics::IsIntrinsicNumeric(
3804 *leftType, GetRank(0), *rightType, GetRank(1));
3809 bool ArgumentAnalyzer::IsIntrinsicLogical() const {
3810 if (std::optional<DynamicType> leftType{GetType(0)}) {
3811 if (actuals_.size() == 1) {
3812 return semantics::IsIntrinsicLogical(*leftType);
3813 } else if (std::optional<DynamicType> rightType{GetType(1)}) {
3814 return semantics::IsIntrinsicLogical(
3815 *leftType, GetRank(0), *rightType, GetRank(1));
3818 return false;
3821 bool ArgumentAnalyzer::IsIntrinsicConcat() const {
3822 if (std::optional<DynamicType> leftType{GetType(0)}) {
3823 if (std::optional<DynamicType> rightType{GetType(1)}) {
3824 return semantics::IsIntrinsicConcat(
3825 *leftType, GetRank(0), *rightType, GetRank(1));
3828 return false;
3831 bool ArgumentAnalyzer::CheckConformance() {
3832 if (actuals_.size() == 2) {
3833 const auto *lhs{actuals_.at(0).value().UnwrapExpr()};
3834 const auto *rhs{actuals_.at(1).value().UnwrapExpr()};
3835 if (lhs && rhs) {
3836 auto &foldingContext{context_.GetFoldingContext()};
3837 auto lhShape{GetShape(foldingContext, *lhs)};
3838 auto rhShape{GetShape(foldingContext, *rhs)};
3839 if (lhShape && rhShape) {
3840 if (!evaluate::CheckConformance(foldingContext.messages(), *lhShape,
3841 *rhShape, CheckConformanceFlags::EitherScalarExpandable,
3842 "left operand", "right operand")
3843 .value_or(false /*fail when conformance is not known now*/)) {
3844 fatalErrors_ = true;
3845 return false;
3850 return true; // no proven problem
3853 bool ArgumentAnalyzer::CheckAssignmentConformance() {
3854 if (actuals_.size() == 2) {
3855 const auto *lhs{actuals_.at(0).value().UnwrapExpr()};
3856 const auto *rhs{actuals_.at(1).value().UnwrapExpr()};
3857 if (lhs && rhs) {
3858 auto &foldingContext{context_.GetFoldingContext()};
3859 auto lhShape{GetShape(foldingContext, *lhs)};
3860 auto rhShape{GetShape(foldingContext, *rhs)};
3861 if (lhShape && rhShape) {
3862 if (!evaluate::CheckConformance(foldingContext.messages(), *lhShape,
3863 *rhShape, CheckConformanceFlags::RightScalarExpandable,
3864 "left-hand side", "right-hand side")
3865 .value_or(true /*ok when conformance is not known now*/)) {
3866 fatalErrors_ = true;
3867 return false;
3872 return true; // no proven problem
3875 bool ArgumentAnalyzer::CheckForNullPointer(const char *where) {
3876 for (const std::optional<ActualArgument> &arg : actuals_) {
3877 if (arg) {
3878 if (const Expr<SomeType> *expr{arg->UnwrapExpr()}) {
3879 if (IsNullPointer(*expr)) {
3880 context_.Say(
3881 source_, "A NULL() pointer is not allowed %s"_err_en_US, where);
3882 fatalErrors_ = true;
3883 return false;
3888 return true;
3891 MaybeExpr ArgumentAnalyzer::TryDefinedOp(
3892 const char *opr, parser::MessageFixedText error, bool isUserOp) {
3893 if (AnyUntypedOrMissingOperand()) {
3894 context_.Say(error, ToUpperCase(opr), TypeAsFortran(0), TypeAsFortran(1));
3895 return std::nullopt;
3897 MaybeExpr result;
3898 bool anyPossibilities{false};
3899 std::optional<parser::MessageFormattedText> inaccessible;
3900 std::vector<const Symbol *> hit;
3901 std::string oprNameString{
3902 isUserOp ? std::string{opr} : "operator("s + opr + ')'};
3903 parser::CharBlock oprName{oprNameString};
3905 auto restorer{context_.GetContextualMessages().DiscardMessages()};
3906 const auto &scope{context_.context().FindScope(source_)};
3907 if (Symbol *symbol{scope.FindSymbol(oprName)}) {
3908 anyPossibilities = true;
3909 parser::Name name{symbol->name(), symbol};
3910 result = context_.AnalyzeDefinedOp(name, GetActuals());
3911 if (result) {
3912 inaccessible = CheckAccessibleSymbol(scope, *symbol);
3913 if (inaccessible) {
3914 result.reset();
3915 } else {
3916 hit.push_back(symbol);
3920 for (std::size_t passIndex{0}; passIndex < actuals_.size(); ++passIndex) {
3921 const Symbol *generic{nullptr};
3922 if (const Symbol *binding{
3923 FindBoundOp(oprName, passIndex, generic, false)}) {
3924 anyPossibilities = true;
3925 if (MaybeExpr thisResult{TryBoundOp(*binding, passIndex)}) {
3926 if (auto thisInaccessible{
3927 CheckAccessibleSymbol(scope, DEREF(generic))}) {
3928 inaccessible = thisInaccessible;
3929 } else {
3930 result = std::move(thisResult);
3931 hit.push_back(binding);
3937 if (result) {
3938 if (hit.size() > 1) {
3939 if (auto *msg{context_.Say(
3940 "%zd matching accessible generic interfaces for %s were found"_err_en_US,
3941 hit.size(), ToUpperCase(opr))}) {
3942 for (const Symbol *symbol : hit) {
3943 AttachDeclaration(*msg, *symbol);
3947 } else if (inaccessible) {
3948 context_.Say(source_, std::move(*inaccessible));
3949 } else if (anyPossibilities) {
3950 SayNoMatch(ToUpperCase(oprNameString), false);
3951 } else if (actuals_.size() == 2 && !AreConformable()) {
3952 context_.Say(
3953 "Operands of %s are not conformable; have rank %d and rank %d"_err_en_US,
3954 ToUpperCase(opr), actuals_[0]->Rank(), actuals_[1]->Rank());
3955 } else if (CheckForNullPointer()) {
3956 context_.Say(error, ToUpperCase(opr), TypeAsFortran(0), TypeAsFortran(1));
3958 return result;
3961 MaybeExpr ArgumentAnalyzer::TryDefinedOp(
3962 std::vector<const char *> oprs, parser::MessageFixedText error) {
3963 if (oprs.size() == 1) {
3964 return TryDefinedOp(oprs[0], error);
3966 MaybeExpr result;
3967 std::vector<const char *> hit;
3969 auto restorer{context_.GetContextualMessages().DiscardMessages()};
3970 for (std::size_t i{0}; i < oprs.size(); ++i) {
3971 if (MaybeExpr thisResult{TryDefinedOp(oprs[i], error)}) {
3972 result = std::move(thisResult);
3973 hit.push_back(oprs[i]);
3977 if (hit.empty()) { // for the error
3978 result = TryDefinedOp(oprs[0], error);
3979 } else if (hit.size() > 1) {
3980 context_.Say(
3981 "Matching accessible definitions were found with %zd variant spellings of the generic operator ('%s', '%s')"_err_en_US,
3982 hit.size(), ToUpperCase(hit[0]), ToUpperCase(hit[1]));
3984 return result;
3987 MaybeExpr ArgumentAnalyzer::TryBoundOp(const Symbol &symbol, int passIndex) {
3988 ActualArguments localActuals{actuals_};
3989 const Symbol *proc{GetBindingResolution(GetType(passIndex), symbol)};
3990 if (!proc) {
3991 proc = &symbol;
3992 localActuals.at(passIndex).value().set_isPassedObject();
3994 CheckConformance();
3995 return context_.MakeFunctionRef(
3996 source_, ProcedureDesignator{*proc}, std::move(localActuals));
3999 std::optional<ProcedureRef> ArgumentAnalyzer::TryDefinedAssignment() {
4000 using semantics::Tristate;
4001 const Expr<SomeType> &lhs{GetExpr(0)};
4002 const Expr<SomeType> &rhs{GetExpr(1)};
4003 std::optional<DynamicType> lhsType{lhs.GetType()};
4004 std::optional<DynamicType> rhsType{rhs.GetType()};
4005 int lhsRank{lhs.Rank()};
4006 int rhsRank{rhs.Rank()};
4007 Tristate isDefined{
4008 semantics::IsDefinedAssignment(lhsType, lhsRank, rhsType, rhsRank)};
4009 if (isDefined == Tristate::No) {
4010 if (lhsType && rhsType) {
4011 AddAssignmentConversion(*lhsType, *rhsType);
4013 if (!fatalErrors_) {
4014 CheckAssignmentConformance();
4016 return std::nullopt; // user-defined assignment not allowed for these args
4018 auto restorer{context_.GetContextualMessages().SetLocation(source_)};
4019 if (std::optional<ProcedureRef> procRef{GetDefinedAssignmentProc()}) {
4020 if (context_.inWhereBody() && !procRef->proc().IsElemental()) { // C1032
4021 context_.Say(
4022 "Defined assignment in WHERE must be elemental, but '%s' is not"_err_en_US,
4023 DEREF(procRef->proc().GetSymbol()).name());
4025 context_.CheckCall(source_, procRef->proc(), procRef->arguments());
4026 return std::move(*procRef);
4028 if (isDefined == Tristate::Yes) {
4029 if (!lhsType || !rhsType || (lhsRank != rhsRank && rhsRank != 0) ||
4030 !OkLogicalIntegerAssignment(lhsType->category(), rhsType->category())) {
4031 SayNoMatch("ASSIGNMENT(=)", true);
4034 return std::nullopt;
4037 bool ArgumentAnalyzer::OkLogicalIntegerAssignment(
4038 TypeCategory lhs, TypeCategory rhs) {
4039 if (!context_.context().languageFeatures().IsEnabled(
4040 common::LanguageFeature::LogicalIntegerAssignment)) {
4041 return false;
4043 std::optional<parser::MessageFixedText> msg;
4044 if (lhs == TypeCategory::Integer && rhs == TypeCategory::Logical) {
4045 // allow assignment to LOGICAL from INTEGER as a legacy extension
4046 msg = "assignment of LOGICAL to INTEGER"_port_en_US;
4047 } else if (lhs == TypeCategory::Logical && rhs == TypeCategory::Integer) {
4048 // ... and assignment to LOGICAL from INTEGER
4049 msg = "assignment of INTEGER to LOGICAL"_port_en_US;
4050 } else {
4051 return false;
4053 if (context_.context().languageFeatures().ShouldWarn(
4054 common::LanguageFeature::LogicalIntegerAssignment)) {
4055 context_.Say(std::move(*msg));
4057 return true;
4060 std::optional<ProcedureRef> ArgumentAnalyzer::GetDefinedAssignmentProc() {
4061 const Symbol *proc{nullptr};
4062 int passedObjectIndex{-1};
4063 std::string oprNameString{"assignment(=)"};
4064 parser::CharBlock oprName{oprNameString};
4065 const auto &scope{context_.context().FindScope(source_)};
4066 // If multiple resolutions were possible, they will have been already
4067 // diagnosed.
4069 auto restorer{context_.GetContextualMessages().DiscardMessages()};
4070 if (const Symbol *symbol{scope.FindSymbol(oprName)}) {
4071 ExpressionAnalyzer::AdjustActuals noAdjustment;
4072 proc =
4073 context_.ResolveGeneric(*symbol, actuals_, noAdjustment, true).first;
4075 for (std::size_t i{0}; !proc && i < actuals_.size(); ++i) {
4076 const Symbol *generic{nullptr};
4077 if (const Symbol *binding{FindBoundOp(oprName, i, generic, true)}) {
4078 if (CheckAccessibleSymbol(scope, DEREF(generic))) {
4079 // ignore inaccessible type-bound ASSIGNMENT(=) generic
4080 } else if (const Symbol *
4081 resolution{GetBindingResolution(GetType(i), *binding)}) {
4082 proc = resolution;
4083 } else {
4084 proc = binding;
4085 passedObjectIndex = i;
4090 if (!proc) {
4091 return std::nullopt;
4093 ActualArguments actualsCopy{actuals_};
4094 if (passedObjectIndex >= 0) {
4095 actualsCopy[passedObjectIndex]->set_isPassedObject();
4097 return ProcedureRef{ProcedureDesignator{*proc}, std::move(actualsCopy)};
4100 void ArgumentAnalyzer::Dump(llvm::raw_ostream &os) {
4101 os << "source_: " << source_.ToString() << " fatalErrors_ = " << fatalErrors_
4102 << '\n';
4103 for (const auto &actual : actuals_) {
4104 if (!actual.has_value()) {
4105 os << "- error\n";
4106 } else if (const Symbol *symbol{actual->GetAssumedTypeDummy()}) {
4107 os << "- assumed type: " << symbol->name().ToString() << '\n';
4108 } else if (const Expr<SomeType> *expr{actual->UnwrapExpr()}) {
4109 expr->AsFortran(os << "- expr: ") << '\n';
4110 } else {
4111 DIE("bad ActualArgument");
4116 std::optional<ActualArgument> ArgumentAnalyzer::AnalyzeExpr(
4117 const parser::Expr &expr) {
4118 source_.ExtendToCover(expr.source);
4119 if (const Symbol *assumedTypeDummy{AssumedTypeDummy(expr)}) {
4120 ResetExpr(expr);
4121 if (isProcedureCall_) {
4122 ActualArgument arg{ActualArgument::AssumedType{*assumedTypeDummy}};
4123 SetArgSourceLocation(arg, expr.source);
4124 return std::move(arg);
4126 context_.SayAt(expr.source,
4127 "TYPE(*) dummy argument may only be used as an actual argument"_err_en_US);
4128 } else if (MaybeExpr argExpr{AnalyzeExprOrWholeAssumedSizeArray(expr)}) {
4129 if (isProcedureCall_ || !IsProcedure(*argExpr)) {
4130 ActualArgument arg{std::move(*argExpr)};
4131 SetArgSourceLocation(arg, expr.source);
4132 return std::move(arg);
4134 context_.SayAt(expr.source,
4135 IsFunction(*argExpr) ? "Function call must have argument list"_err_en_US
4136 : "Subroutine name is not allowed here"_err_en_US);
4138 return std::nullopt;
4141 MaybeExpr ArgumentAnalyzer::AnalyzeExprOrWholeAssumedSizeArray(
4142 const parser::Expr &expr) {
4143 // If an expression's parse tree is a whole assumed-size array:
4144 // Expr -> Designator -> DataRef -> Name
4145 // treat it as a special case for argument passing and bypass
4146 // the C1002/C1014 constraint checking in expression semantics.
4147 if (const auto *name{parser::Unwrap<parser::Name>(expr)}) {
4148 if (name->symbol && semantics::IsAssumedSizeArray(*name->symbol)) {
4149 auto restorer{context_.AllowWholeAssumedSizeArray()};
4150 return context_.Analyze(expr);
4153 auto restorer{context_.AllowNullPointer()};
4154 return context_.Analyze(expr);
4157 bool ArgumentAnalyzer::AreConformable() const {
4158 CHECK(actuals_.size() == 2);
4159 return actuals_[0] && actuals_[1] &&
4160 evaluate::AreConformable(*actuals_[0], *actuals_[1]);
4163 // Look for a type-bound operator in the type of arg number passIndex.
4164 const Symbol *ArgumentAnalyzer::FindBoundOp(parser::CharBlock oprName,
4165 int passIndex, const Symbol *&generic, bool isSubroutine) {
4166 const auto *type{GetDerivedTypeSpec(GetType(passIndex))};
4167 const semantics::Scope *scope{type ? type->scope() : nullptr};
4168 if (scope) {
4169 // Use the original type definition's scope, since PDT
4170 // instantiations don't have redundant copies of bindings or
4171 // generics.
4172 scope = DEREF(scope->derivedTypeSpec()).typeSymbol().scope();
4174 generic = scope ? scope->FindComponent(oprName) : nullptr;
4175 if (generic) {
4176 ExpressionAnalyzer::AdjustActuals adjustment{
4177 [&](const Symbol &proc, ActualArguments &) {
4178 return passIndex == GetPassIndex(proc);
4180 auto pair{
4181 context_.ResolveGeneric(*generic, actuals_, adjustment, isSubroutine)};
4182 if (const Symbol *binding{pair.first}) {
4183 CHECK(binding->has<semantics::ProcBindingDetails>());
4184 // Use the most recent override of the binding, if any
4185 return scope->FindComponent(binding->name());
4186 } else {
4187 context_.EmitGenericResolutionError(*generic, pair.second, isSubroutine);
4190 return nullptr;
4193 // If there is an implicit conversion between intrinsic types, make it explicit
4194 void ArgumentAnalyzer::AddAssignmentConversion(
4195 const DynamicType &lhsType, const DynamicType &rhsType) {
4196 if (lhsType.category() == rhsType.category() &&
4197 (lhsType.category() == TypeCategory::Derived ||
4198 lhsType.kind() == rhsType.kind())) {
4199 // no conversion necessary
4200 } else if (auto rhsExpr{evaluate::Fold(context_.GetFoldingContext(),
4201 evaluate::ConvertToType(lhsType, MoveExpr(1)))}) {
4202 std::optional<parser::CharBlock> source;
4203 if (actuals_[1]) {
4204 source = actuals_[1]->sourceLocation();
4206 actuals_[1] = ActualArgument{*rhsExpr};
4207 SetArgSourceLocation(actuals_[1], source);
4208 } else {
4209 actuals_[1] = std::nullopt;
4213 std::optional<DynamicType> ArgumentAnalyzer::GetType(std::size_t i) const {
4214 return i < actuals_.size() ? actuals_[i].value().GetType() : std::nullopt;
4216 int ArgumentAnalyzer::GetRank(std::size_t i) const {
4217 return i < actuals_.size() ? actuals_[i].value().Rank() : 0;
4220 // If the argument at index i is a BOZ literal, convert its type to match the
4221 // otherType. If it's REAL convert to REAL, otherwise convert to INTEGER.
4222 // Note that IBM supports comparing BOZ literals to CHARACTER operands. That
4223 // is not currently supported.
4224 void ArgumentAnalyzer::ConvertBOZ(std::optional<DynamicType> &thisType,
4225 std::size_t i, std::optional<DynamicType> otherType) {
4226 if (IsBOZLiteral(i)) {
4227 Expr<SomeType> &&argExpr{MoveExpr(i)};
4228 auto *boz{std::get_if<BOZLiteralConstant>(&argExpr.u)};
4229 if (otherType && otherType->category() == TypeCategory::Real) {
4230 int kind{context_.context().GetDefaultKind(TypeCategory::Real)};
4231 MaybeExpr realExpr{
4232 ConvertToKind<TypeCategory::Real>(kind, std::move(*boz))};
4233 actuals_[i] = std::move(*realExpr);
4234 thisType.emplace(TypeCategory::Real, kind);
4235 } else {
4236 int kind{context_.context().GetDefaultKind(TypeCategory::Integer)};
4237 MaybeExpr intExpr{
4238 ConvertToKind<TypeCategory::Integer>(kind, std::move(*boz))};
4239 actuals_[i] = std::move(*intExpr);
4240 thisType.emplace(TypeCategory::Integer, kind);
4245 // Report error resolving opr when there is a user-defined one available
4246 void ArgumentAnalyzer::SayNoMatch(const std::string &opr, bool isAssignment) {
4247 std::string type0{TypeAsFortran(0)};
4248 auto rank0{actuals_[0]->Rank()};
4249 if (actuals_.size() == 1) {
4250 if (rank0 > 0) {
4251 context_.Say("No intrinsic or user-defined %s matches "
4252 "rank %d array of %s"_err_en_US,
4253 opr, rank0, type0);
4254 } else {
4255 context_.Say("No intrinsic or user-defined %s matches "
4256 "operand type %s"_err_en_US,
4257 opr, type0);
4259 } else {
4260 std::string type1{TypeAsFortran(1)};
4261 auto rank1{actuals_[1]->Rank()};
4262 if (rank0 > 0 && rank1 > 0 && rank0 != rank1) {
4263 context_.Say("No intrinsic or user-defined %s matches "
4264 "rank %d array of %s and rank %d array of %s"_err_en_US,
4265 opr, rank0, type0, rank1, type1);
4266 } else if (isAssignment && rank0 != rank1) {
4267 if (rank0 == 0) {
4268 context_.Say("No intrinsic or user-defined %s matches "
4269 "scalar %s and rank %d array of %s"_err_en_US,
4270 opr, type0, rank1, type1);
4271 } else {
4272 context_.Say("No intrinsic or user-defined %s matches "
4273 "rank %d array of %s and scalar %s"_err_en_US,
4274 opr, rank0, type0, type1);
4276 } else {
4277 context_.Say("No intrinsic or user-defined %s matches "
4278 "operand types %s and %s"_err_en_US,
4279 opr, type0, type1);
4284 std::string ArgumentAnalyzer::TypeAsFortran(std::size_t i) {
4285 if (i >= actuals_.size() || !actuals_[i]) {
4286 return "missing argument";
4287 } else if (std::optional<DynamicType> type{GetType(i)}) {
4288 return type->IsAssumedType() ? "TYPE(*)"s
4289 : type->IsUnlimitedPolymorphic() ? "CLASS(*)"s
4290 : type->IsPolymorphic() ? type->AsFortran()
4291 : type->category() == TypeCategory::Derived
4292 ? "TYPE("s + type->AsFortran() + ')'
4293 : type->category() == TypeCategory::Character
4294 ? "CHARACTER(KIND="s + std::to_string(type->kind()) + ')'
4295 : ToUpperCase(type->AsFortran());
4296 } else {
4297 return "untyped";
4301 bool ArgumentAnalyzer::AnyUntypedOrMissingOperand() {
4302 for (const auto &actual : actuals_) {
4303 if (!actual ||
4304 (!actual->GetType() && !IsBareNullPointer(actual->UnwrapExpr()))) {
4305 return true;
4308 return false;
4310 } // namespace Fortran::evaluate
4312 namespace Fortran::semantics {
4313 evaluate::Expr<evaluate::SubscriptInteger> AnalyzeKindSelector(
4314 SemanticsContext &context, common::TypeCategory category,
4315 const std::optional<parser::KindSelector> &selector) {
4316 evaluate::ExpressionAnalyzer analyzer{context};
4317 auto restorer{
4318 analyzer.GetContextualMessages().SetLocation(context.location().value())};
4319 return analyzer.AnalyzeKindSelector(category, selector);
4322 ExprChecker::ExprChecker(SemanticsContext &context) : context_{context} {}
4324 bool ExprChecker::Pre(const parser::DataStmtObject &obj) {
4325 exprAnalyzer_.set_inDataStmtObject(true);
4326 return true;
4329 void ExprChecker::Post(const parser::DataStmtObject &obj) {
4330 exprAnalyzer_.set_inDataStmtObject(false);
4333 bool ExprChecker::Pre(const parser::DataImpliedDo &ido) {
4334 parser::Walk(std::get<parser::DataImpliedDo::Bounds>(ido.t), *this);
4335 const auto &bounds{std::get<parser::DataImpliedDo::Bounds>(ido.t)};
4336 auto name{bounds.name.thing.thing};
4337 int kind{evaluate::ResultType<evaluate::ImpliedDoIndex>::kind};
4338 if (const auto dynamicType{evaluate::DynamicType::From(*name.symbol)}) {
4339 if (dynamicType->category() == TypeCategory::Integer) {
4340 kind = dynamicType->kind();
4343 exprAnalyzer_.AddImpliedDo(name.source, kind);
4344 parser::Walk(std::get<std::list<parser::DataIDoObject>>(ido.t), *this);
4345 exprAnalyzer_.RemoveImpliedDo(name.source);
4346 return false;
4349 bool ExprChecker::Walk(const parser::Program &program) {
4350 parser::Walk(program, *this);
4351 return !context_.AnyFatalError();
4353 } // namespace Fortran::semantics