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