FLANG
expression.h
1//===-- include/flang/Evaluate/expression.h ---------------------*- C++ -*-===//
2//
3// Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4// See https://llvm.org/LICENSE.txt for license information.
5// SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6//
7//===----------------------------------------------------------------------===//
8
9#ifndef FORTRAN_EVALUATE_EXPRESSION_H_
10#define FORTRAN_EVALUATE_EXPRESSION_H_
11
12// Represent Fortran expressions in a type-safe manner.
13// Expressions are the sole owners of their constituents; i.e., there is no
14// context-independent hash table or sharing of common subexpressions, and
15// thus these are trees, not DAGs. Both deep copy and move semantics are
16// supported for expression construction. Expressions may be compared
17// for equality.
18
19#include "common.h"
20#include "constant.h"
21#include "formatting.h"
22#include "type.h"
23#include "variable.h"
24#include "flang/Common/Fortran.h"
25#include "flang/Common/idioms.h"
26#include "flang/Common/indirection.h"
27#include "flang/Common/template.h"
28#include "flang/Parser/char-block.h"
29#include <algorithm>
30#include <list>
31#include <tuple>
32#include <type_traits>
33#include <variant>
34
35namespace llvm {
36class raw_ostream;
37}
38
39namespace Fortran::evaluate {
40
41using common::LogicalOperator;
42using common::RelationalOperator;
43
44// Expressions are represented by specializations of the class template Expr.
45// Each of these specializations wraps a single data member "u" that
46// is a std::variant<> discriminated union over all of the representational
47// types for the constants, variables, operations, and other entities that
48// can be valid expressions in that context:
49// - Expr<Type<CATEGORY, KIND>> represents an expression whose result is of a
50// specific intrinsic type category and kind, e.g. Type<TypeCategory::Real, 4>
51// - Expr<SomeDerived> wraps data and procedure references that result in an
52// instance of a derived type (or CLASS(*) unlimited polymorphic)
53// - Expr<SomeKind<CATEGORY>> is a union of Expr<Type<CATEGORY, K>> for each
54// kind type parameter value K in that intrinsic type category. It represents
55// an expression with known category and any kind.
56// - Expr<SomeType> is a union of Expr<SomeKind<CATEGORY>> over the five
57// intrinsic type categories of Fortran. It represents any valid expression.
58//
59// Everything that can appear in, or as, a valid Fortran expression must be
60// represented with an instance of some class containing a Result typedef that
61// maps to some instantiation of Type<CATEGORY, KIND>, SomeKind<CATEGORY>,
62// or SomeType. (Exception: BOZ literal constants in generic Expr<SomeType>.)
63template <typename A> using ResultType = typename std::decay_t<A>::Result;
64
65// Common Expr<> behaviors: every Expr<T> derives from ExpressionBase<T>.
66template <typename RESULT> class ExpressionBase {
67public:
68 using Result = RESULT;
69
70private:
71 using Derived = Expr<Result>;
72#if defined(__APPLE__) && defined(__GNUC__)
73 Derived &derived();
74 const Derived &derived() const;
75#else
76 Derived &derived() { return *static_cast<Derived *>(this); }
77 const Derived &derived() const { return *static_cast<const Derived *>(this); }
78#endif
79
80public:
81 template <typename A> Derived &operator=(const A &x) {
82 Derived &d{derived()};
83 d.u = x;
84 return d;
85 }
86
87 template <typename A> common::IfNoLvalue<Derived &, A> operator=(A &&x) {
88 Derived &d{derived()};
89 d.u = std::move(x);
90 return d;
91 }
92
93 std::optional<DynamicType> GetType() const;
94 int Rank() const;
95 int Corank() const;
96 std::string AsFortran() const;
97#if !defined(NDEBUG) || defined(LLVM_ENABLE_DUMP)
98 LLVM_DUMP_METHOD void dump() const;
99#endif
100 llvm::raw_ostream &AsFortran(llvm::raw_ostream &) const;
101 static Derived Rewrite(FoldingContext &, Derived &&);
102};
103
104// Operations always have specific Fortran result types (i.e., with known
105// intrinsic type category and kind parameter value). The classes that
106// represent the operations all inherit from this Operation<> base class
107// template. Note that Operation has as its first type parameter (DERIVED) a
108// "curiously reoccurring template pattern (CRTP)" reference to the specific
109// operation class being derived from Operation; e.g., Add is defined with
110// struct Add : public Operation<Add, ...>. Uses of instances of Operation<>,
111// including its own member functions, can access each specific class derived
112// from it via its derived() member function with compile-time type safety.
113template <typename DERIVED, typename RESULT, typename... OPERANDS>
115 // The extra final member is a dummy that allows a safe unused reference
116 // to element 1 to arise indirectly in the definition of "right()" below
117 // when the operation has but a single operand.
118 using OperandTypes = std::tuple<OPERANDS..., std::monostate>;
119
120public:
121 using Derived = DERIVED;
122 using Result = RESULT;
123 static constexpr std::size_t operands{sizeof...(OPERANDS)};
124 // Allow specific intrinsic types and Parentheses<SomeDerived>
125 static_assert(IsSpecificIntrinsicType<Result> ||
126 (operands == 1 && std::is_same_v<Result, SomeDerived>));
127 template <int J> using Operand = std::tuple_element_t<J, OperandTypes>;
128
129 // Unary operations wrap a single Expr with a CopyableIndirection.
130 // Binary operations wrap a tuple of CopyableIndirections to Exprs.
131private:
132 using Container = std::conditional_t<operands == 1,
134 std::tuple<common::CopyableIndirection<Expr<OPERANDS>>...>>;
135
136public:
137 CLASS_BOILERPLATE(Operation)
138 explicit Operation(const Expr<OPERANDS> &...x) : operand_{x...} {}
139 explicit Operation(Expr<OPERANDS> &&...x) : operand_{std::move(x)...} {}
140
141 Derived &derived() { return *static_cast<Derived *>(this); }
142 const Derived &derived() const { return *static_cast<const Derived *>(this); }
143
144 // References to operand expressions from member functions of derived
145 // classes for specific operators can be made by index, e.g. operand<0>(),
146 // which must be spelled like "this->template operand<0>()" when
147 // inherited in a derived class template. There are convenience aliases
148 // left() and right() that are not templates.
149 template <int J> Expr<Operand<J>> &operand() {
150 if constexpr (operands == 1) {
151 static_assert(J == 0);
152 return operand_.value();
153 } else {
154 return std::get<J>(operand_).value();
155 }
156 }
157 template <int J> const Expr<Operand<J>> &operand() const {
158 if constexpr (operands == 1) {
159 static_assert(J == 0);
160 return operand_.value();
161 } else {
162 return std::get<J>(operand_).value();
163 }
164 }
165
166 Expr<Operand<0>> &left() { return operand<0>(); }
167 const Expr<Operand<0>> &left() const { return operand<0>(); }
168
169 std::conditional_t<(operands > 1), Expr<Operand<1>> &, void> right() {
170 if constexpr (operands > 1) {
171 return operand<1>();
172 }
173 }
174 std::conditional_t<(operands > 1), const Expr<Operand<1>> &, void>
175 right() const {
176 if constexpr (operands > 1) {
177 return operand<1>();
178 }
179 }
180
181 static constexpr std::conditional_t<Result::category != TypeCategory::Derived,
182 std::optional<DynamicType>, void>
183 GetType() {
184 return Result::GetType();
185 }
186 int Rank() const {
187 int rank{left().Rank()};
188 if constexpr (operands > 1) {
189 return std::max(rank, right().Rank());
190 } else {
191 return rank;
192 }
193 }
194 static constexpr int Corank() { return 0; }
195
196 bool operator==(const Operation &that) const {
197 return operand_ == that.operand_;
198 }
199
200 llvm::raw_ostream &AsFortran(llvm::raw_ostream &) const;
201
202private:
203 Container operand_;
204};
205
206// Unary operations
207
208// Conversions to specific types from expressions of known category and
209// dynamic kind.
210template <typename TO, TypeCategory FROMCAT = TO::category>
211struct Convert : public Operation<Convert<TO, FROMCAT>, TO, SomeKind<FROMCAT>> {
212 // Fortran doesn't have conversions between kinds of CHARACTER apart from
213 // assignments, and in those the data must be convertible to/from 7-bit ASCII.
214 static_assert(
215 ((TO::category == TypeCategory::Integer ||
216 TO::category == TypeCategory::Real ||
217 TO::category == TypeCategory::Unsigned) &&
218 (FROMCAT == TypeCategory::Integer || FROMCAT == TypeCategory::Real ||
219 FROMCAT == TypeCategory::Unsigned)) ||
220 TO::category == FROMCAT);
221 using Result = TO;
224 using Base::Base;
225 llvm::raw_ostream &AsFortran(llvm::raw_ostream &) const;
226};
227
228template <typename A>
229struct Parentheses : public Operation<Parentheses<A>, A, A> {
230 using Result = A;
231 using Operand = A;
233 using Base::Base;
234};
235
236template <>
238 : public Operation<Parentheses<SomeDerived>, SomeDerived, SomeDerived> {
239public:
240 using Result = SomeDerived;
241 using Operand = SomeDerived;
243 using Base::Base;
244 DynamicType GetType() const;
245};
246
247template <typename A> struct Negate : public Operation<Negate<A>, A, A> {
248 using Result = A;
249 using Operand = A;
251 using Base::Base;
252};
253
254template <int KIND>
256 : public Operation<ComplexComponent<KIND>, Type<TypeCategory::Real, KIND>,
257 Type<TypeCategory::Complex, KIND>> {
261 CLASS_BOILERPLATE(ComplexComponent)
262 ComplexComponent(bool isImaginary, const Expr<Operand> &x)
263 : Base{x}, isImaginaryPart{isImaginary} {}
264 ComplexComponent(bool isImaginary, Expr<Operand> &&x)
265 : Base{std::move(x)}, isImaginaryPart{isImaginary} {}
266
267 bool isImaginaryPart{true};
268};
269
270template <int KIND>
271struct Not : public Operation<Not<KIND>, Type<TypeCategory::Logical, KIND>,
272 Type<TypeCategory::Logical, KIND>> {
274 using Operand = Result;
276 using Base::Base;
277};
278
279// Character lengths are determined by context in Fortran and do not
280// have explicit syntax for changing them. Expressions represent
281// changes of length (e.g., for assignments and structure constructors)
282// with this operation.
283template <int KIND>
285 : public Operation<SetLength<KIND>, Type<TypeCategory::Character, KIND>,
286 Type<TypeCategory::Character, KIND>, SubscriptInteger> {
288 using CharacterOperand = Result;
291 using Base::Base;
292};
293
294// Binary operations
295
296template <typename A> struct Add : public Operation<Add<A>, A, A, A> {
297 using Result = A;
298 using Operand = A;
300 using Base::Base;
301};
302
303template <typename A> struct Subtract : public Operation<Subtract<A>, A, A, A> {
304 using Result = A;
305 using Operand = A;
307 using Base::Base;
308};
309
310template <typename A> struct Multiply : public Operation<Multiply<A>, A, A, A> {
311 using Result = A;
312 using Operand = A;
314 using Base::Base;
315};
316
317template <typename A> struct Divide : public Operation<Divide<A>, A, A, A> {
318 using Result = A;
319 using Operand = A;
321 using Base::Base;
322};
323
324template <typename A> struct Power : public Operation<Power<A>, A, A, A> {
325 using Result = A;
326 using Operand = A;
328 using Base::Base;
329};
330
331template <typename A>
332struct RealToIntPower : public Operation<RealToIntPower<A>, A, A, SomeInteger> {
334 using Result = A;
335 using BaseOperand = A;
337 using Base::Base;
338};
339
340template <typename A> struct Extremum : public Operation<Extremum<A>, A, A, A> {
341 using Result = A;
342 using Operand = A;
344 CLASS_BOILERPLATE(Extremum)
345 Extremum(Ordering ord, const Expr<Operand> &x, const Expr<Operand> &y)
346 : Base{x, y}, ordering{ord} {}
347 Extremum(Ordering ord, Expr<Operand> &&x, Expr<Operand> &&y)
348 : Base{std::move(x), std::move(y)}, ordering{ord} {}
349 bool operator==(const Extremum &) const;
350 Ordering ordering{Ordering::Greater};
351};
352
353template <int KIND>
355 : public Operation<ComplexConstructor<KIND>,
356 Type<TypeCategory::Complex, KIND>, Type<TypeCategory::Real, KIND>,
357 Type<TypeCategory::Real, KIND>> {
361 using Base::Base;
362};
363
364template <int KIND>
365struct Concat
366 : public Operation<Concat<KIND>, Type<TypeCategory::Character, KIND>,
367 Type<TypeCategory::Character, KIND>,
368 Type<TypeCategory::Character, KIND>> {
370 using Operand = Result;
372 using Base::Base;
373};
374
375template <int KIND>
377 : public Operation<LogicalOperation<KIND>,
378 Type<TypeCategory::Logical, KIND>, Type<TypeCategory::Logical, KIND>,
379 Type<TypeCategory::Logical, KIND>> {
381 using Operand = Result;
383 CLASS_BOILERPLATE(LogicalOperation)
385 LogicalOperator opr, const Expr<Operand> &x, const Expr<Operand> &y)
386 : Base{x, y}, logicalOperator{opr} {}
387 LogicalOperation(LogicalOperator opr, Expr<Operand> &&x, Expr<Operand> &&y)
388 : Base{std::move(x), std::move(y)}, logicalOperator{opr} {}
389 bool operator==(const LogicalOperation &) const;
390 LogicalOperator logicalOperator;
391};
392
393// Array constructors
394template <typename RESULT> class ArrayConstructorValues;
395
397 using Result = SubscriptInteger;
398 bool operator==(const ImpliedDoIndex &) const;
399 static constexpr int Rank() { return 0; }
400 static constexpr int Corank() { return 0; }
401 parser::CharBlock name; // nested implied DOs must use distinct names
402};
403
404template <typename RESULT> class ImpliedDo {
405public:
406 using Result = RESULT;
407 using Index = ResultType<ImpliedDoIndex>;
408 ImpliedDo(parser::CharBlock name, Expr<Index> &&lower, Expr<Index> &&upper,
410 : name_{name}, lower_{std::move(lower)}, upper_{std::move(upper)},
411 stride_{std::move(stride)}, values_{std::move(values)} {}
412 DEFAULT_CONSTRUCTORS_AND_ASSIGNMENTS(ImpliedDo)
413 bool operator==(const ImpliedDo &) const;
414 parser::CharBlock name() const { return name_; }
415 Expr<Index> &lower() { return lower_.value(); }
416 const Expr<Index> &lower() const { return lower_.value(); }
417 Expr<Index> &upper() { return upper_.value(); }
418 const Expr<Index> &upper() const { return upper_.value(); }
419 Expr<Index> &stride() { return stride_.value(); }
420 const Expr<Index> &stride() const { return stride_.value(); }
421 ArrayConstructorValues<Result> &values() { return values_.value(); }
422 const ArrayConstructorValues<Result> &values() const {
423 return values_.value();
424 }
425
426private:
427 parser::CharBlock name_;
428 common::CopyableIndirection<Expr<Index>> lower_, upper_, stride_;
430};
431
432template <typename RESULT> struct ArrayConstructorValue {
433 using Result = RESULT;
434 EVALUATE_UNION_CLASS_BOILERPLATE(ArrayConstructorValue)
435 std::variant<Expr<Result>, ImpliedDo<Result>> u;
436};
437
438template <typename RESULT> class ArrayConstructorValues {
439public:
440 using Result = RESULT;
441 using Values = std::vector<ArrayConstructorValue<Result>>;
442 DEFAULT_CONSTRUCTORS_AND_ASSIGNMENTS(ArrayConstructorValues)
444
445 bool operator==(const ArrayConstructorValues &) const;
446 static constexpr int Rank() { return 1; }
447 static constexpr int Corank() { return 0; }
448 template <typename A> common::NoLvalue<A> Push(A &&x) {
449 values_.emplace_back(std::move(x));
450 }
451
452 typename Values::iterator begin() { return values_.begin(); }
453 typename Values::const_iterator begin() const { return values_.begin(); }
454 typename Values::iterator end() { return values_.end(); }
455 typename Values::const_iterator end() const { return values_.end(); }
456
457protected:
458 Values values_;
459};
460
461// Note that there are specializations of ArrayConstructor for character
462// and derived types, since they must carry additional type information,
463// but that an empty ArrayConstructor can be constructed for any type
464// given an expression from which such type information may be gleaned.
465template <typename RESULT>
467public:
468 using Result = RESULT;
470 DEFAULT_CONSTRUCTORS_AND_ASSIGNMENTS(ArrayConstructor)
471 explicit ArrayConstructor(Base &&values) : Base{std::move(values)} {}
472 template <typename T> explicit ArrayConstructor(const Expr<T> &) {}
473 static constexpr Result result() { return Result{}; }
474 static constexpr DynamicType GetType() { return Result::GetType(); }
475 llvm::raw_ostream &AsFortran(llvm::raw_ostream &) const;
476};
477
478template <int KIND>
479class ArrayConstructor<Type<TypeCategory::Character, KIND>>
480 : public ArrayConstructorValues<Type<TypeCategory::Character, KIND>> {
481public:
484 DEFAULT_CONSTRUCTORS_AND_ASSIGNMENTS(ArrayConstructor)
485 explicit ArrayConstructor(Base &&values) : Base{std::move(values)} {}
486 template <typename T> explicit ArrayConstructor(const Expr<T> &) {}
488 bool operator==(const ArrayConstructor &) const;
489 static constexpr Result result() { return Result{}; }
490 static constexpr DynamicType GetType() { return Result::GetType(); }
491 llvm::raw_ostream &AsFortran(llvm::raw_ostream &) const;
492 const Expr<SubscriptInteger> *LEN() const {
493 return length_ ? &length_->value() : nullptr;
494 }
495
496private:
497 std::optional<common::CopyableIndirection<Expr<SubscriptInteger>>> length_;
498};
499
500template <>
502 : public ArrayConstructorValues<SomeDerived> {
503public:
504 using Result = SomeDerived;
506 CLASS_BOILERPLATE(ArrayConstructor)
507
509 : Base{std::move(v)}, result_{spec} {}
510 template <typename A>
511 explicit ArrayConstructor(const A &prototype)
512 : result_{prototype.GetType().value().GetDerivedTypeSpec()} {}
513
514 bool operator==(const ArrayConstructor &) const;
515 constexpr Result result() const { return result_; }
516 constexpr DynamicType GetType() const { return result_.GetType(); }
517 llvm::raw_ostream &AsFortran(llvm::raw_ostream &) const;
518
519private:
520 Result result_;
521};
522
523// Expression representations for each type category.
524
525template <int KIND>
526class Expr<Type<TypeCategory::Integer, KIND>>
527 : public ExpressionBase<Type<TypeCategory::Integer, KIND>> {
528public:
530
531 EVALUATE_UNION_CLASS_BOILERPLATE(Expr)
532
533private:
534 using Conversions = std::tuple<Convert<Result, TypeCategory::Integer>,
537 using Operations = std::tuple<Parentheses<Result>, Negate<Result>,
540 using Indices = std::conditional_t<KIND == ImpliedDoIndex::Result::kind,
541 std::tuple<ImpliedDoIndex>, std::tuple<>>;
542 using TypeParamInquiries =
543 std::conditional_t<KIND == TypeParamInquiry::Result::kind,
544 std::tuple<TypeParamInquiry>, std::tuple<>>;
545 using DescriptorInquiries =
546 std::conditional_t<KIND == DescriptorInquiry::Result::kind,
547 std::tuple<DescriptorInquiry>, std::tuple<>>;
548 using Others = std::tuple<Constant<Result>, ArrayConstructor<Result>,
550
551public:
552 common::TupleToVariant<common::CombineTuples<Operations, Conversions, Indices,
553 TypeParamInquiries, DescriptorInquiries, Others>>
554 u;
555};
556
557template <int KIND>
558class Expr<Type<TypeCategory::Unsigned, KIND>>
559 : public ExpressionBase<Type<TypeCategory::Unsigned, KIND>> {
560public:
562
563 EVALUATE_UNION_CLASS_BOILERPLATE(Expr)
564
565private:
566 using Conversions = std::tuple<Convert<Result, TypeCategory::Integer>,
569 using Operations =
570 std::tuple<Parentheses<Result>, Negate<Result>, Add<Result>,
572 using Others = std::tuple<Constant<Result>, ArrayConstructor<Result>,
574
575public:
576 common::TupleToVariant<common::CombineTuples<Operations, Conversions, Others>>
577 u;
578};
579
580template <int KIND>
581class Expr<Type<TypeCategory::Real, KIND>>
582 : public ExpressionBase<Type<TypeCategory::Real, KIND>> {
583public:
585
586 EVALUATE_UNION_CLASS_BOILERPLATE(Expr)
587 explicit Expr(const Scalar<Result> &x) : u{Constant<Result>{x}} {}
588
589private:
590 // N.B. Real->Complex and Complex->Real conversions are done with CMPLX
591 // and part access operations (resp.).
592 using Conversions = std::variant<Convert<Result, TypeCategory::Integer>,
595 using Operations = std::variant<ComplexComponent<KIND>, Parentheses<Result>,
598 using Others = std::variant<Constant<Result>, ArrayConstructor<Result>,
600
601public:
602 common::CombineVariants<Operations, Conversions, Others> u;
603};
604
605template <int KIND>
606class Expr<Type<TypeCategory::Complex, KIND>>
607 : public ExpressionBase<Type<TypeCategory::Complex, KIND>> {
608public:
610 EVALUATE_UNION_CLASS_BOILERPLATE(Expr)
611 explicit Expr(const Scalar<Result> &x) : u{Constant<Result>{x}} {}
612 using Operations = std::variant<Parentheses<Result>, Negate<Result>,
616 using Others = std::variant<Constant<Result>, ArrayConstructor<Result>,
618
619public:
620 common::CombineVariants<Operations, Others> u;
621};
622
623FOR_EACH_INTEGER_KIND(extern template class Expr, )
624FOR_EACH_UNSIGNED_KIND(extern template class Expr, )
625FOR_EACH_REAL_KIND(extern template class Expr, )
626FOR_EACH_COMPLEX_KIND(extern template class Expr, )
627
628template <int KIND>
629class Expr<Type<TypeCategory::Character, KIND>>
630 : public ExpressionBase<Type<TypeCategory::Character, KIND>> {
631public:
633 EVALUATE_UNION_CLASS_BOILERPLATE(Expr)
634 explicit Expr(const Scalar<Result> &x) : u{Constant<Result>{x}} {}
635 explicit Expr(Scalar<Result> &&x) : u{Constant<Result>{std::move(x)}} {}
636
637 std::optional<Expr<SubscriptInteger>> LEN() const;
638
639 std::variant<Constant<Result>, ArrayConstructor<Result>, Designator<Result>,
642 u;
643};
644
645FOR_EACH_CHARACTER_KIND(extern template class Expr, )
646
647// The Relational class template is a helper for constructing logical
648// expressions with polymorphism over the cross product of the possible
649// categories and kinds of comparable operands.
650// Fortran defines a numeric relation with distinct types or kinds as
651// first undergoing the same operand conversions that occur with the intrinsic
652// addition operator. Character relations must have the same kind.
653// There are no relations between LOGICAL values.
654
655template <typename T>
656class Relational : public Operation<Relational<T>, LogicalResult, T, T> {
657public:
658 using Result = LogicalResult;
660 using Operand = typename Base::template Operand<0>;
661 static_assert(Operand::category == TypeCategory::Integer ||
662 Operand::category == TypeCategory::Real ||
663 Operand::category == TypeCategory::Complex ||
664 Operand::category == TypeCategory::Character ||
665 Operand::category == TypeCategory::Unsigned);
666 CLASS_BOILERPLATE(Relational)
668 RelationalOperator r, const Expr<Operand> &a, const Expr<Operand> &b)
669 : Base{a, b}, opr{r} {}
670 Relational(RelationalOperator r, Expr<Operand> &&a, Expr<Operand> &&b)
671 : Base{std::move(a), std::move(b)}, opr{r} {}
672 bool operator==(const Relational &) const;
673 RelationalOperator opr;
674};
675
676template <> class Relational<SomeType> {
677 using DirectlyComparableTypes = common::CombineTuples<IntegerTypes, RealTypes,
678 ComplexTypes, CharacterTypes, UnsignedTypes>;
679
680public:
681 using Result = LogicalResult;
682 EVALUATE_UNION_CLASS_BOILERPLATE(Relational)
683 static constexpr DynamicType GetType() { return Result::GetType(); }
684 int Rank() const {
685 return common::visit([](const auto &x) { return x.Rank(); }, u);
686 }
687 static constexpr int Corank() { return 0; }
688 llvm::raw_ostream &AsFortran(llvm::raw_ostream &o) const;
689 common::MapTemplate<Relational, DirectlyComparableTypes> u;
690};
691
692FOR_EACH_INTEGER_KIND(extern template class Relational, )
693FOR_EACH_UNSIGNED_KIND(extern template class Relational, )
694FOR_EACH_REAL_KIND(extern template class Relational, )
695FOR_EACH_CHARACTER_KIND(extern template class Relational, )
696extern template class Relational<SomeType>;
697
698// Logical expressions of a kind bigger than LogicalResult
699// do not include Relational<> operations as possibilities,
700// since the results of Relationals are always LogicalResult
701// (kind=4).
702template <int KIND>
703class Expr<Type<TypeCategory::Logical, KIND>>
704 : public ExpressionBase<Type<TypeCategory::Logical, KIND>> {
705public:
707 EVALUATE_UNION_CLASS_BOILERPLATE(Expr)
708 explicit Expr(const Scalar<Result> &x) : u{Constant<Result>{x}} {}
709 explicit Expr(bool x) : u{Constant<Result>{x}} {}
710
711private:
712 using Operations = std::tuple<Convert<Result>, Parentheses<Result>, Not<KIND>,
714 using Relations = std::conditional_t<KIND == LogicalResult::kind,
715 std::tuple<Relational<SomeType>>, std::tuple<>>;
716 using Others = std::tuple<Constant<Result>, ArrayConstructor<Result>,
718
719public:
720 common::TupleToVariant<common::CombineTuples<Operations, Relations, Others>>
721 u;
722};
723
724FOR_EACH_LOGICAL_KIND(extern template class Expr, )
725
726// StructureConstructor pairs a StructureConstructorValues instance
727// (a map associating symbols with expressions) with a derived type
728// specification. There are two other similar classes:
729// - ArrayConstructor<SomeDerived> comprises a derived type spec &
730// zero or more instances of Expr<SomeDerived>; it has rank 1
731// but not (in the most general case) a known shape.
732// - Constant<SomeDerived> comprises a derived type spec, zero or more
733// homogeneous instances of StructureConstructorValues whose type
734// parameters and component expressions are all constant, and a
735// known shape (possibly scalar).
736// StructureConstructor represents a scalar value of derived type that
737// is not necessarily a constant. It is used only as an Expr<SomeDerived>
738// alternative and as the type Scalar<SomeDerived> (with an assumption
739// of constant component value expressions).
741public:
742 using Result = SomeDerived;
743
745 : result_{spec} {}
747 const semantics::DerivedTypeSpec &, const StructureConstructorValues &);
749 const semantics::DerivedTypeSpec &, StructureConstructorValues &&);
750 CLASS_BOILERPLATE(StructureConstructor)
751
752 constexpr Result result() const { return result_; }
753 const semantics::DerivedTypeSpec &derivedTypeSpec() const {
754 return result_.derivedTypeSpec();
755 }
756 StructureConstructorValues &values() { return values_; }
757 const StructureConstructorValues &values() const { return values_; }
758
759 bool operator==(const StructureConstructor &) const;
760
761 StructureConstructorValues::iterator begin() { return values_.begin(); }
762 StructureConstructorValues::const_iterator begin() const {
763 return values_.begin();
764 }
765 StructureConstructorValues::iterator end() { return values_.end(); }
766 StructureConstructorValues::const_iterator end() const {
767 return values_.end();
768 }
769
770 // can return nullopt
771 std::optional<Expr<SomeType>> Find(const Symbol &) const;
772
774 static constexpr int Rank() { return 0; }
775 static constexpr int Corank() { return 0; }
776 DynamicType GetType() const;
777 llvm::raw_ostream &AsFortran(llvm::raw_ostream &) const;
778
779private:
780 std::optional<Expr<SomeType>> CreateParentComponent(const Symbol &) const;
781 Result result_;
782 StructureConstructorValues values_;
783};
784
785// An expression whose result has a derived type.
786template <> class Expr<SomeDerived> : public ExpressionBase<SomeDerived> {
787public:
788 using Result = SomeDerived;
789 EVALUATE_UNION_CLASS_BOILERPLATE(Expr)
790 std::variant<Constant<Result>, ArrayConstructor<Result>, StructureConstructor,
792 u;
793};
794
795// A polymorphic expression of known intrinsic type category, but dynamic
796// kind, represented as a discriminated union over Expr<Type<CAT, K>>
797// for each supported kind K in the category.
798template <TypeCategory CAT>
799class Expr<SomeKind<CAT>> : public ExpressionBase<SomeKind<CAT>> {
800public:
801 using Result = SomeKind<CAT>;
802 EVALUATE_UNION_CLASS_BOILERPLATE(Expr)
803 int GetKind() const;
804 common::MapTemplate<evaluate::Expr, CategoryTypes<CAT>> u;
805};
806
807template <> class Expr<SomeCharacter> : public ExpressionBase<SomeCharacter> {
808public:
809 using Result = SomeCharacter;
810 EVALUATE_UNION_CLASS_BOILERPLATE(Expr)
811 int GetKind() const;
812 std::optional<Expr<SubscriptInteger>> LEN() const;
813 common::MapTemplate<Expr, CategoryTypes<TypeCategory::Character>> u;
814};
815
816// A variant comprising the Expr<> instantiations over SomeDerived and
817// SomeKind<CATEGORY>.
818using CategoryExpression = common::MapTemplate<Expr, SomeCategory>;
819
820// BOZ literal "typeless" constants must be wide enough to hold a numeric
821// value of any supported kind of INTEGER or REAL. They must also be
822// distinguishable from other integer constants, since they are permitted
823// to be used in only a few situations.
824using BOZLiteralConstant = typename LargestReal::Scalar::Word;
825
826// Null pointers without MOLD= arguments are typed by context.
828 constexpr bool operator==(const NullPointer &) const { return true; }
829 static constexpr int Rank() { return 0; }
830 static constexpr int Corank() { return 0; }
831};
832
833// Procedure pointer targets are treated as if they were typeless.
834// They are either procedure designators or values returned from
835// references to functions that return procedure (not object) pointers.
836using TypelessExpression = std::variant<BOZLiteralConstant, NullPointer,
838
839// A completely generic expression, polymorphic across all of the intrinsic type
840// categories and each of their kinds.
841template <> class Expr<SomeType> : public ExpressionBase<SomeType> {
842public:
843 using Result = SomeType;
844 EVALUATE_UNION_CLASS_BOILERPLATE(Expr)
845
846 // Owning references to these generic expressions can appear in other
847 // compiler data structures (viz., the parse tree and symbol table), so
848 // its destructor is externalized to reduce redundant default instances.
849 ~Expr();
850
851 template <TypeCategory CAT, int KIND>
852 explicit Expr(const Expr<Type<CAT, KIND>> &x) : u{Expr<SomeKind<CAT>>{x}} {}
853
854 template <TypeCategory CAT, int KIND>
855 explicit Expr(Expr<Type<CAT, KIND>> &&x)
856 : u{Expr<SomeKind<CAT>>{std::move(x)}} {}
857
858 template <TypeCategory CAT, int KIND>
859 Expr &operator=(const Expr<Type<CAT, KIND>> &x) {
860 u = Expr<SomeKind<CAT>>{x};
861 return *this;
862 }
863
864 template <TypeCategory CAT, int KIND>
865 Expr &operator=(Expr<Type<CAT, KIND>> &&x) {
866 u = Expr<SomeKind<CAT>>{std::move(x)};
867 return *this;
868 }
869
870public:
871 common::CombineVariants<TypelessExpression, CategoryExpression> u;
872};
873
874// An assignment is either intrinsic, user-defined (with a ProcedureRef to
875// specify the procedure to call), or pointer assignment (with possibly empty
876// BoundsSpec or non-empty BoundsRemapping). In all cases there are Exprs
877// representing the LHS and RHS of the assignment.
879public:
881 : lhs(std::move(lhs)), rhs(std::move(rhs)) {}
882
883 struct Intrinsic {};
884 using BoundsSpec = std::vector<Expr<SubscriptInteger>>;
885 using BoundsRemapping =
886 std::vector<std::pair<Expr<SubscriptInteger>, Expr<SubscriptInteger>>>;
887 llvm::raw_ostream &AsFortran(llvm::raw_ostream &) const;
888
889 Expr<SomeType> lhs;
890 Expr<SomeType> rhs;
891 std::variant<Intrinsic, ProcedureRef, BoundsSpec, BoundsRemapping> u;
892};
893
894// This wrapper class is used, by means of a forward reference with
895// an owning pointer, to cache analyzed expressions in parse tree nodes.
898 explicit GenericExprWrapper(std::optional<Expr<SomeType>> &&x)
899 : v{std::move(x)} {}
901 static void Deleter(GenericExprWrapper *);
902 std::optional<Expr<SomeType>> v; // vacant if error
903};
904
905// Like GenericExprWrapper but for analyzed assignments
908 explicit GenericAssignmentWrapper(Assignment &&x) : v{std::move(x)} {}
909 explicit GenericAssignmentWrapper(std::optional<Assignment> &&x)
910 : v{std::move(x)} {}
912 static void Deleter(GenericAssignmentWrapper *);
913 std::optional<Assignment> v; // vacant if error
914};
915
916FOR_EACH_CATEGORY_TYPE(extern template class Expr, )
917FOR_EACH_TYPE_AND_KIND(extern template class ExpressionBase, )
918FOR_EACH_INTRINSIC_KIND(extern template class ArrayConstructorValues, )
919FOR_EACH_INTRINSIC_KIND(extern template class ArrayConstructor, )
920
921// Template instantiations to resolve these "extern template" declarations.
922#define INSTANTIATE_EXPRESSION_TEMPLATES \
923 FOR_EACH_INTRINSIC_KIND(template class Expr, ) \
924 FOR_EACH_CATEGORY_TYPE(template class Expr, ) \
925 FOR_EACH_INTEGER_KIND(template class Relational, ) \
926 FOR_EACH_UNSIGNED_KIND(template class Relational, ) \
927 FOR_EACH_REAL_KIND(template class Relational, ) \
928 FOR_EACH_CHARACTER_KIND(template class Relational, ) \
929 template class Relational<SomeType>; \
930 FOR_EACH_TYPE_AND_KIND(template class ExpressionBase, ) \
931 FOR_EACH_INTRINSIC_KIND(template class ArrayConstructorValues, ) \
932 FOR_EACH_INTRINSIC_KIND(template class ArrayConstructor, )
933} // namespace Fortran::evaluate
934#endif // FORTRAN_EVALUATE_EXPRESSION_H_
Definition: indirection.h:72
Definition: expression.h:438
Definition: expression.h:466
Definition: expression.h:878
Definition: constant.h:141
Definition: variable.h:393
Definition: type.h:95
Definition: common.h:213
Definition: expression.h:66
Definition: common.h:215
Definition: call.h:282
Definition: expression.h:404
Definition: expression.h:114
Definition: call.h:232
Definition: expression.h:656
Definition: expression.h:740
Definition: type.h:56
Definition: char-block.h:28
Definition: symbol.h:712
Definition: call.h:34
Definition: expression.h:296
Definition: expression.h:432
Definition: expression.h:883
Definition: expression.h:257
Definition: expression.h:357
Definition: expression.h:368
Definition: expression.h:211
Definition: expression.h:317
Definition: expression.h:340
Definition: expression.h:896
Definition: expression.h:396
Definition: expression.h:379
Definition: expression.h:310
Definition: expression.h:247
Definition: expression.h:272
Definition: expression.h:827
Definition: expression.h:229
Definition: expression.h:324
Definition: expression.h:332
Definition: expression.h:286
Definition: type.h:402
Definition: type.h:420
Definition: expression.h:303