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