xref: /llvm-project/flang/include/flang/Evaluate/type.h (revision 038b42ba5b47b1aa2d47ef5706a713f6bfbbc37c)
1 //===-- include/flang/Evaluate/type.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_TYPE_H_
10 #define FORTRAN_EVALUATE_TYPE_H_
11 
12 // These definitions map Fortran's intrinsic types, characterized by byte
13 // sizes encoded in KIND type parameter values, to their value representation
14 // types in the evaluation library, which are parameterized in terms of
15 // total bit width and real precision.  Instances of the Type class template
16 // are suitable for use as template parameters to instantiate other class
17 // templates, like expressions, over the supported types and kinds.
18 
19 #include "common.h"
20 #include "complex.h"
21 #include "formatting.h"
22 #include "integer.h"
23 #include "logical.h"
24 #include "real.h"
25 #include "flang/Common/Fortran-features.h"
26 #include "flang/Common/Fortran.h"
27 #include "flang/Common/idioms.h"
28 #include "flang/Common/real.h"
29 #include "flang/Common/template.h"
30 #include <cinttypes>
31 #include <optional>
32 #include <string>
33 #include <type_traits>
34 #include <variant>
35 
36 namespace Fortran::semantics {
37 class DeclTypeSpec;
38 class DerivedTypeSpec;
39 class ParamValue;
40 class Symbol;
41 // IsDescriptor() is true when an object requires the use of a descriptor
42 // in memory when "at rest".  IsPassedViaDescriptor() is sometimes false
43 // when IsDescriptor() is true, including the cases of CHARACTER dummy
44 // arguments and explicit & assumed-size dummy arrays.
45 bool IsDescriptor(const Symbol &);
46 bool IsPassedViaDescriptor(const Symbol &);
47 } // namespace Fortran::semantics
48 
49 namespace Fortran::evaluate {
50 
51 using common::TypeCategory;
52 class TargetCharacteristics;
53 
54 // Specific intrinsic types are represented by specializations of
55 // this class template Type<CATEGORY, KIND>.
56 template <TypeCategory CATEGORY, int KIND = 0> class Type;
57 
58 using SubscriptInteger = Type<TypeCategory::Integer, 8>;
59 using CInteger = Type<TypeCategory::Integer, 4>;
60 using LargestInt = Type<TypeCategory::Integer, 16>;
61 using LogicalResult = Type<TypeCategory::Logical, 4>;
62 using LargestReal = Type<TypeCategory::Real, 16>;
63 using Ascii = Type<TypeCategory::Character, 1>;
64 
65 // A predicate that is true when a kind value is a kind that could possibly
66 // be supported for an intrinsic type category on some target instruction
67 // set architecture.
68 static constexpr bool IsValidKindOfIntrinsicType(
69     TypeCategory category, std::int64_t kind) {
70   switch (category) {
71   case TypeCategory::Integer:
72   case TypeCategory::Unsigned:
73     return kind == 1 || kind == 2 || kind == 4 || kind == 8 || kind == 16;
74   case TypeCategory::Real:
75   case TypeCategory::Complex:
76     return kind == 2 || kind == 3 || kind == 4 || kind == 8 || kind == 10 ||
77         kind == 16;
78   case TypeCategory::Character:
79     return kind == 1 || kind == 2 || kind == 4;
80   case TypeCategory::Logical:
81     return kind == 1 || kind == 2 || kind == 4 || kind == 8;
82   default:
83     return false;
84   }
85 }
86 
87 // DynamicType is meant to be suitable for use as the result type for
88 // GetType() functions and member functions; consequently, it must be
89 // capable of being used in a constexpr context.  So it does *not*
90 // directly hold anything requiring a destructor, such as an arbitrary
91 // CHARACTER length type parameter expression.  Those must be derived
92 // via LEN() member functions, packaged elsewhere (e.g. as in
93 // ArrayConstructor), copied from a parameter spec in the symbol table
94 // if one is supplied, or a known integer value.
95 class DynamicType {
96 public:
97   constexpr DynamicType(TypeCategory cat, int k) : category_{cat}, kind_{k} {
98     CHECK(IsValidKindOfIntrinsicType(category_, kind_));
99   }
100   DynamicType(int charKind, const semantics::ParamValue &len);
101   // When a known length is presented, resolve it to its effective
102   // length of zero if it is negative.
103   constexpr DynamicType(int k, std::int64_t len)
104       : category_{TypeCategory::Character}, kind_{k}, knownLength_{
105                                                           len >= 0 ? len : 0} {
106     CHECK(IsValidKindOfIntrinsicType(category_, kind_));
107   }
108   explicit constexpr DynamicType(
109       const semantics::DerivedTypeSpec &dt, bool poly = false)
110       : category_{TypeCategory::Derived}, derived_{&dt} {
111     if (poly) {
112       kind_ = ClassKind;
113     }
114   }
115   CONSTEXPR_CONSTRUCTORS_AND_ASSIGNMENTS(DynamicType)
116 
117   // A rare use case used for representing the characteristics of an
118   // intrinsic function like REAL() that accepts a typeless BOZ literal
119   // argument and for typeless pointers -- things that real user Fortran can't
120   // do.
121   static constexpr DynamicType TypelessIntrinsicArgument() {
122     DynamicType result;
123     result.category_ = TypeCategory::Integer;
124     result.kind_ = TypelessKind;
125     return result;
126   }
127 
128   static constexpr DynamicType UnlimitedPolymorphic() {
129     DynamicType result;
130     result.category_ = TypeCategory::Derived;
131     result.kind_ = ClassKind;
132     result.derived_ = nullptr;
133     return result; // CLASS(*)
134   }
135 
136   static constexpr DynamicType AssumedType() {
137     DynamicType result;
138     result.category_ = TypeCategory::Derived;
139     result.kind_ = AssumedTypeKind;
140     result.derived_ = nullptr;
141     return result; // TYPE(*)
142   }
143 
144   // Comparison is deep -- type parameters are compared independently.
145   bool operator==(const DynamicType &) const;
146   bool operator!=(const DynamicType &that) const { return !(*this == that); }
147 
148   constexpr TypeCategory category() const { return category_; }
149   constexpr int kind() const {
150     CHECK(kind_ > 0);
151     return kind_;
152   }
153   constexpr const semantics::ParamValue *charLengthParamValue() const {
154     return charLengthParamValue_;
155   }
156   constexpr std::optional<std::int64_t> knownLength() const {
157 #if defined(_GLIBCXX_RELEASE) && _GLIBCXX_RELEASE == 7
158     if (knownLength_ < 0) {
159       return std::nullopt;
160     }
161 #endif
162     return knownLength_;
163   }
164   std::optional<Expr<SubscriptInteger>> GetCharLength() const;
165 
166   std::size_t GetAlignment(const TargetCharacteristics &) const;
167   std::optional<Expr<SubscriptInteger>> MeasureSizeInBytes(FoldingContext &,
168       bool aligned,
169       std::optional<std::int64_t> charLength = std::nullopt) const;
170 
171   std::string AsFortran() const;
172   std::string AsFortran(std::string &&charLenExpr) const;
173   DynamicType ResultTypeForMultiply(const DynamicType &) const;
174 
175   bool IsAssumedLengthCharacter() const;
176   bool IsNonConstantLengthCharacter() const;
177   bool IsTypelessIntrinsicArgument() const;
178   constexpr bool IsAssumedType() const { // TYPE(*)
179     return kind_ == AssumedTypeKind;
180   }
181   constexpr bool IsPolymorphic() const { // TYPE(*) or CLASS()
182     return kind_ == ClassKind || IsAssumedType();
183   }
184   constexpr bool IsUnlimitedPolymorphic() const { // TYPE(*) or CLASS(*)
185     return IsPolymorphic() && !derived_;
186   }
187   bool IsLengthlessIntrinsicType() const;
188   constexpr const semantics::DerivedTypeSpec &GetDerivedTypeSpec() const {
189     return DEREF(derived_);
190   }
191 
192   bool RequiresDescriptor() const;
193   bool HasDeferredTypeParameter() const;
194 
195   // 7.3.2.3 & 15.5.2.4 type compatibility.
196   // x.IsTkCompatibleWith(y) is true if "x => y" or passing actual y to
197   // dummy argument x would be valid.  Be advised, this is not a reflexive
198   // relation.  Kind type parameters must match, but CHARACTER lengths
199   // need not do so.
200   bool IsTkCompatibleWith(const DynamicType &) const;
201   bool IsTkCompatibleWith(const DynamicType &, common::IgnoreTKRSet) const;
202 
203   // A stronger compatibility check that does not allow distinct known
204   // values for CHARACTER lengths for e.g. MOVE_ALLOC().
205   bool IsTkLenCompatibleWith(const DynamicType &) const;
206 
207   // EXTENDS_TYPE_OF (16.9.76); ignores type parameter values
208   std::optional<bool> ExtendsTypeOf(const DynamicType &) const;
209   // SAME_TYPE_AS (16.9.165); ignores type parameter values
210   std::optional<bool> SameTypeAs(const DynamicType &) const;
211 
212   // 7.5.2.4 type equivalence; like operator==(), but SEQUENCE/BIND(C)
213   // derived types can be structurally equivalent.
214   bool IsEquivalentTo(const DynamicType &) const;
215 
216   // Result will be missing when a symbol is absent or
217   // has an erroneous type, e.g., REAL(KIND=666).
218   static std::optional<DynamicType> From(const semantics::DeclTypeSpec &);
219   static std::optional<DynamicType> From(const semantics::Symbol &);
220 
221   template <typename A> static std::optional<DynamicType> From(const A &x) {
222     return x.GetType();
223   }
224   template <typename A> static std::optional<DynamicType> From(const A *p) {
225     if (!p) {
226       return std::nullopt;
227     } else {
228       return From(*p);
229     }
230   }
231   template <typename A>
232   static std::optional<DynamicType> From(const std::optional<A> &x) {
233     if (x) {
234       return From(*x);
235     } else {
236       return std::nullopt;
237     }
238   }
239 
240   // Get a copy of this dynamic type where charLengthParamValue_ is reset if it
241   // is not a constant expression. This avoids propagating symbol references in
242   // scopes where they do not belong. Returns the type unmodified if it is not
243   // a character or if the length is not explicit.
244   DynamicType DropNonConstantCharacterLength() const;
245 
246 private:
247   // Special kind codes are used to distinguish the following Fortran types.
248   enum SpecialKind {
249     TypelessKind = -1, // BOZ actual argument to intrinsic function or pointer
250                        // argument to ASSOCIATED
251     ClassKind = -2, // CLASS(T) or CLASS(*)
252     AssumedTypeKind = -3, // TYPE(*)
253   };
254 
255   constexpr DynamicType() {}
256 
257   TypeCategory category_{TypeCategory::Derived}; // overridable default
258   int kind_{0};
259   const semantics::ParamValue *charLengthParamValue_{nullptr};
260 #if defined(_GLIBCXX_RELEASE) && _GLIBCXX_RELEASE == 7
261   // GCC 7's optional<> lacks a constexpr operator=
262   std::int64_t knownLength_{-1};
263 #else
264   std::optional<std::int64_t> knownLength_;
265 #endif
266   const semantics::DerivedTypeSpec *derived_{nullptr}; // TYPE(T), CLASS(T)
267 };
268 
269 // Return the DerivedTypeSpec of a DynamicType if it has one.
270 const semantics::DerivedTypeSpec *GetDerivedTypeSpec(const DynamicType &);
271 const semantics::DerivedTypeSpec *GetDerivedTypeSpec(
272     const std::optional<DynamicType> &);
273 const semantics::DerivedTypeSpec *GetParentTypeSpec(
274     const semantics::DerivedTypeSpec &);
275 
276 template <TypeCategory CATEGORY, int KIND = 0> struct TypeBase {
277   static constexpr TypeCategory category{CATEGORY};
278   static constexpr int kind{KIND};
279   constexpr bool operator==(const TypeBase &) const { return true; }
280   static constexpr DynamicType GetType() { return {category, kind}; }
281   static std::string AsFortran() { return GetType().AsFortran(); }
282 };
283 
284 template <int KIND>
285 class Type<TypeCategory::Integer, KIND>
286     : public TypeBase<TypeCategory::Integer, KIND> {
287 public:
288   using Scalar = value::Integer<8 * KIND>;
289 };
290 
291 template <int KIND>
292 class Type<TypeCategory::Unsigned, KIND>
293     : public TypeBase<TypeCategory::Unsigned, KIND> {
294 public:
295   using Scalar = value::Integer<8 * KIND>;
296 };
297 
298 template <int KIND>
299 class Type<TypeCategory::Real, KIND>
300     : public TypeBase<TypeCategory::Real, KIND> {
301 public:
302   static constexpr int precision{common::PrecisionOfRealKind(KIND)};
303   static constexpr int bits{common::BitsForBinaryPrecision(precision)};
304   using Scalar =
305       value::Real<std::conditional_t<precision == 64,
306                       value::X87IntegerContainer, value::Integer<bits>>,
307           precision>;
308 };
309 
310 // The KIND type parameter on COMPLEX is the kind of each of its components.
311 template <int KIND>
312 class Type<TypeCategory::Complex, KIND>
313     : public TypeBase<TypeCategory::Complex, KIND> {
314 public:
315   using Part = Type<TypeCategory::Real, KIND>;
316   using Scalar = value::Complex<typename Part::Scalar>;
317 };
318 
319 template <>
320 class Type<TypeCategory::Character, 1>
321     : public TypeBase<TypeCategory::Character, 1> {
322 public:
323   using Scalar = std::string;
324 };
325 
326 template <>
327 class Type<TypeCategory::Character, 2>
328     : public TypeBase<TypeCategory::Character, 2> {
329 public:
330   using Scalar = std::u16string;
331 };
332 
333 template <>
334 class Type<TypeCategory::Character, 4>
335     : public TypeBase<TypeCategory::Character, 4> {
336 public:
337   using Scalar = std::u32string;
338 };
339 
340 template <int KIND>
341 class Type<TypeCategory::Logical, KIND>
342     : public TypeBase<TypeCategory::Logical, KIND> {
343 public:
344   using Scalar = value::Logical<8 * KIND>;
345 };
346 
347 // Type functions
348 
349 // Given a specific type, find the type of the same kind in another category.
350 template <TypeCategory CATEGORY, typename T>
351 using SameKind = Type<CATEGORY, std::decay_t<T>::kind>;
352 
353 // Many expressions, including subscripts, CHARACTER lengths, array bounds,
354 // and effective type parameter values, are of a maximal kind of INTEGER.
355 using IndirectSubscriptIntegerExpr =
356     common::CopyableIndirection<Expr<SubscriptInteger>>;
357 
358 // For each intrinsic type category CAT, CategoryTypes<CAT> is an instantiation
359 // of std::tuple<Type<CAT, K>> that comprises every kind value K in that
360 // category that could possibly be supported on any target.
361 template <TypeCategory CATEGORY, int KIND>
362 using CategoryKindTuple =
363     std::conditional_t<IsValidKindOfIntrinsicType(CATEGORY, KIND),
364         std::tuple<Type<CATEGORY, KIND>>, std::tuple<>>;
365 
366 template <TypeCategory CATEGORY, int... KINDS>
367 using CategoryTypesHelper =
368     common::CombineTuples<CategoryKindTuple<CATEGORY, KINDS>...>;
369 
370 template <TypeCategory CATEGORY>
371 using CategoryTypes = CategoryTypesHelper<CATEGORY, 1, 2, 3, 4, 8, 10, 16, 32>;
372 
373 using IntegerTypes = CategoryTypes<TypeCategory::Integer>;
374 using RealTypes = CategoryTypes<TypeCategory::Real>;
375 using ComplexTypes = CategoryTypes<TypeCategory::Complex>;
376 using CharacterTypes = CategoryTypes<TypeCategory::Character>;
377 using LogicalTypes = CategoryTypes<TypeCategory::Logical>;
378 using UnsignedTypes = CategoryTypes<TypeCategory::Unsigned>;
379 
380 using FloatingTypes = common::CombineTuples<RealTypes, ComplexTypes>;
381 using NumericTypes =
382     common::CombineTuples<IntegerTypes, FloatingTypes, UnsignedTypes>;
383 using RelationalTypes = common::CombineTuples<IntegerTypes, RealTypes,
384     CharacterTypes, UnsignedTypes>;
385 using AllIntrinsicTypes =
386     common::CombineTuples<NumericTypes, CharacterTypes, LogicalTypes>;
387 using LengthlessIntrinsicTypes =
388     common::CombineTuples<NumericTypes, LogicalTypes>;
389 
390 // Predicates: does a type represent a specific intrinsic type?
391 template <typename T>
392 constexpr bool IsSpecificIntrinsicType{common::HasMember<T, AllIntrinsicTypes>};
393 
394 // Predicate: is a type an intrinsic type that is completely characterized
395 // by its category and kind parameter value, or might it have a derived type
396 // &/or a length type parameter?
397 template <typename T>
398 constexpr bool IsLengthlessIntrinsicType{
399     common::HasMember<T, LengthlessIntrinsicTypes>};
400 
401 // Represents a type of any supported kind within a particular category.
402 template <TypeCategory CATEGORY> struct SomeKind {
403   static constexpr TypeCategory category{CATEGORY};
404   constexpr bool operator==(const SomeKind &) const { return true; }
405   static std::string AsFortran() {
406     return "Some"s + std::string{common::EnumToString(category)};
407   }
408 };
409 
410 using NumericCategoryTypes =
411     std::tuple<SomeKind<TypeCategory::Integer>, SomeKind<TypeCategory::Real>,
412         SomeKind<TypeCategory::Complex>, SomeKind<TypeCategory::Unsigned>>;
413 using AllIntrinsicCategoryTypes =
414     std::tuple<SomeKind<TypeCategory::Integer>, SomeKind<TypeCategory::Real>,
415         SomeKind<TypeCategory::Complex>, SomeKind<TypeCategory::Character>,
416         SomeKind<TypeCategory::Logical>, SomeKind<TypeCategory::Unsigned>>;
417 
418 // Represents a completely generic type (or, for Expr<SomeType>, a typeless
419 // value like a BOZ literal or NULL() pointer).
420 struct SomeType {
421   static std::string AsFortran() { return "SomeType"s; }
422 };
423 
424 class StructureConstructor;
425 
426 // Represents any derived type, polymorphic or not, as well as CLASS(*).
427 template <> class SomeKind<TypeCategory::Derived> {
428 public:
429   static constexpr TypeCategory category{TypeCategory::Derived};
430   using Scalar = StructureConstructor;
431 
432   constexpr SomeKind() {} // CLASS(*)
433   constexpr explicit SomeKind(const semantics::DerivedTypeSpec &dts)
434       : derivedTypeSpec_{&dts} {}
435   constexpr explicit SomeKind(const DynamicType &dt)
436       : SomeKind(dt.GetDerivedTypeSpec()) {}
437   CONSTEXPR_CONSTRUCTORS_AND_ASSIGNMENTS(SomeKind)
438 
439   bool IsUnlimitedPolymorphic() const { return !derivedTypeSpec_; }
440   constexpr DynamicType GetType() const {
441     if (!derivedTypeSpec_) {
442       return DynamicType::UnlimitedPolymorphic();
443     } else {
444       return DynamicType{*derivedTypeSpec_};
445     }
446   }
447   const semantics::DerivedTypeSpec &derivedTypeSpec() const {
448     CHECK(derivedTypeSpec_);
449     return *derivedTypeSpec_;
450   }
451   bool operator==(const SomeKind &) const;
452   std::string AsFortran() const;
453 
454 private:
455   const semantics::DerivedTypeSpec *derivedTypeSpec_{nullptr};
456 };
457 
458 using SomeInteger = SomeKind<TypeCategory::Integer>;
459 using SomeReal = SomeKind<TypeCategory::Real>;
460 using SomeComplex = SomeKind<TypeCategory::Complex>;
461 using SomeCharacter = SomeKind<TypeCategory::Character>;
462 using SomeLogical = SomeKind<TypeCategory::Logical>;
463 using SomeUnsigned = SomeKind<TypeCategory::Unsigned>;
464 using SomeDerived = SomeKind<TypeCategory::Derived>;
465 using SomeCategory = std::tuple<SomeInteger, SomeReal, SomeComplex,
466     SomeCharacter, SomeLogical, SomeUnsigned, SomeDerived>;
467 
468 using AllTypes =
469     common::CombineTuples<AllIntrinsicTypes, std::tuple<SomeDerived>>;
470 
471 template <typename T> using Scalar = typename std::decay_t<T>::Scalar;
472 
473 // When Scalar<T> is S, then TypeOf<S> is T.
474 // TypeOf is implemented by scanning all supported types for a match
475 // with Type<T>::Scalar.
476 template <typename CONST> struct TypeOfHelper {
477   template <typename T> struct Predicate {
478     static constexpr bool value() {
479       return std::is_same_v<std::decay_t<CONST>,
480           std::decay_t<typename T::Scalar>>;
481     }
482   };
483   static constexpr int index{
484       common::SearchMembers<Predicate, AllIntrinsicTypes>};
485   using type = std::conditional_t<index >= 0,
486       std::tuple_element_t<index, AllIntrinsicTypes>, void>;
487 };
488 
489 template <typename CONST> using TypeOf = typename TypeOfHelper<CONST>::type;
490 
491 int SelectedCharKind(const std::string &, int defaultKind);
492 // SelectedIntKind and SelectedRealKind are now member functions of
493 // TargetCharactertics.
494 
495 // Given the dynamic types and kinds of two operands, determine the common
496 // type to which they must be converted in order to be compared with
497 // intrinsic OPERATOR(==) or .EQV.
498 std::optional<DynamicType> ComparisonType(
499     const DynamicType &, const DynamicType &);
500 
501 // Returns nullopt for deferred, assumed, and non-constant lengths.
502 std::optional<bool> IsInteroperableIntrinsicType(const DynamicType &,
503     const common::LanguageFeatureControl * = nullptr,
504     bool checkCharLength = true);
505 bool IsCUDAIntrinsicType(const DynamicType &);
506 
507 // Determine whether two derived type specs are sufficiently identical
508 // to be considered the "same" type even if declared separately.
509 bool AreSameDerivedType(
510     const semantics::DerivedTypeSpec &, const semantics::DerivedTypeSpec &);
511 bool AreSameDerivedTypeIgnoringTypeParameters(
512     const semantics::DerivedTypeSpec &, const semantics::DerivedTypeSpec &);
513 bool AreSameDerivedTypeIgnoringSequence(
514     const semantics::DerivedTypeSpec &, const semantics::DerivedTypeSpec &);
515 
516 // For generating "[extern] template class", &c. boilerplate
517 #define EXPAND_FOR_EACH_INTEGER_KIND(M, P, S) \
518   M(P, S, 1) M(P, S, 2) M(P, S, 4) M(P, S, 8) M(P, S, 16)
519 #define EXPAND_FOR_EACH_REAL_KIND(M, P, S) \
520   M(P, S, 2) M(P, S, 3) M(P, S, 4) M(P, S, 8) M(P, S, 10) M(P, S, 16)
521 #define EXPAND_FOR_EACH_COMPLEX_KIND(M, P, S) EXPAND_FOR_EACH_REAL_KIND(M, P, S)
522 #define EXPAND_FOR_EACH_CHARACTER_KIND(M, P, S) M(P, S, 1) M(P, S, 2) M(P, S, 4)
523 #define EXPAND_FOR_EACH_LOGICAL_KIND(M, P, S) \
524   M(P, S, 1) M(P, S, 2) M(P, S, 4) M(P, S, 8)
525 #define EXPAND_FOR_EACH_UNSIGNED_KIND EXPAND_FOR_EACH_INTEGER_KIND
526 
527 #define FOR_EACH_INTEGER_KIND_HELP(PREFIX, SUFFIX, K) \
528   PREFIX<Type<TypeCategory::Integer, K>> SUFFIX;
529 #define FOR_EACH_REAL_KIND_HELP(PREFIX, SUFFIX, K) \
530   PREFIX<Type<TypeCategory::Real, K>> SUFFIX;
531 #define FOR_EACH_COMPLEX_KIND_HELP(PREFIX, SUFFIX, K) \
532   PREFIX<Type<TypeCategory::Complex, K>> SUFFIX;
533 #define FOR_EACH_CHARACTER_KIND_HELP(PREFIX, SUFFIX, K) \
534   PREFIX<Type<TypeCategory::Character, K>> SUFFIX;
535 #define FOR_EACH_LOGICAL_KIND_HELP(PREFIX, SUFFIX, K) \
536   PREFIX<Type<TypeCategory::Logical, K>> SUFFIX;
537 #define FOR_EACH_UNSIGNED_KIND_HELP(PREFIX, SUFFIX, K) \
538   PREFIX<Type<TypeCategory::Unsigned, K>> SUFFIX;
539 
540 #define FOR_EACH_INTEGER_KIND(PREFIX, SUFFIX) \
541   EXPAND_FOR_EACH_INTEGER_KIND(FOR_EACH_INTEGER_KIND_HELP, PREFIX, SUFFIX)
542 #define FOR_EACH_REAL_KIND(PREFIX, SUFFIX) \
543   EXPAND_FOR_EACH_REAL_KIND(FOR_EACH_REAL_KIND_HELP, PREFIX, SUFFIX)
544 #define FOR_EACH_COMPLEX_KIND(PREFIX, SUFFIX) \
545   EXPAND_FOR_EACH_COMPLEX_KIND(FOR_EACH_COMPLEX_KIND_HELP, PREFIX, SUFFIX)
546 #define FOR_EACH_CHARACTER_KIND(PREFIX, SUFFIX) \
547   EXPAND_FOR_EACH_CHARACTER_KIND(FOR_EACH_CHARACTER_KIND_HELP, PREFIX, SUFFIX)
548 #define FOR_EACH_LOGICAL_KIND(PREFIX, SUFFIX) \
549   EXPAND_FOR_EACH_LOGICAL_KIND(FOR_EACH_LOGICAL_KIND_HELP, PREFIX, SUFFIX)
550 #define FOR_EACH_UNSIGNED_KIND(PREFIX, SUFFIX) \
551   EXPAND_FOR_EACH_UNSIGNED_KIND(FOR_EACH_UNSIGNED_KIND_HELP, PREFIX, SUFFIX)
552 
553 #define FOR_EACH_LENGTHLESS_INTRINSIC_KIND(PREFIX, SUFFIX) \
554   FOR_EACH_INTEGER_KIND(PREFIX, SUFFIX) \
555   FOR_EACH_REAL_KIND(PREFIX, SUFFIX) \
556   FOR_EACH_COMPLEX_KIND(PREFIX, SUFFIX) \
557   FOR_EACH_LOGICAL_KIND(PREFIX, SUFFIX) \
558   FOR_EACH_UNSIGNED_KIND(PREFIX, SUFFIX)
559 #define FOR_EACH_INTRINSIC_KIND(PREFIX, SUFFIX) \
560   FOR_EACH_LENGTHLESS_INTRINSIC_KIND(PREFIX, SUFFIX) \
561   FOR_EACH_CHARACTER_KIND(PREFIX, SUFFIX)
562 #define FOR_EACH_SPECIFIC_TYPE(PREFIX, SUFFIX) \
563   FOR_EACH_INTRINSIC_KIND(PREFIX, SUFFIX) \
564   PREFIX<SomeDerived> SUFFIX;
565 
566 #define FOR_EACH_CATEGORY_TYPE(PREFIX, SUFFIX) \
567   PREFIX<SomeInteger> SUFFIX; \
568   PREFIX<SomeReal> SUFFIX; \
569   PREFIX<SomeComplex> SUFFIX; \
570   PREFIX<SomeCharacter> SUFFIX; \
571   PREFIX<SomeLogical> SUFFIX; \
572   PREFIX<SomeUnsigned> SUFFIX; \
573   PREFIX<SomeDerived> SUFFIX; \
574   PREFIX<SomeType> SUFFIX;
575 #define FOR_EACH_TYPE_AND_KIND(PREFIX, SUFFIX) \
576   FOR_EACH_INTRINSIC_KIND(PREFIX, SUFFIX) \
577   FOR_EACH_CATEGORY_TYPE(PREFIX, SUFFIX)
578 } // namespace Fortran::evaluate
579 #endif // FORTRAN_EVALUATE_TYPE_H_
580