1 //===-- lib/Semantics/type.cpp --------------------------------------------===//
2 //
3 // Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4 // See https://llvm.org/LICENSE.txt for license information.
5 // SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6 //
7 //===----------------------------------------------------------------------===//
8 
9 #include "flang/Semantics/type.h"
10 #include "check-declarations.h"
11 #include "compute-offsets.h"
12 #include "flang/Evaluate/fold.h"
13 #include "flang/Parser/characters.h"
14 #include "flang/Semantics/scope.h"
15 #include "flang/Semantics/symbol.h"
16 #include "flang/Semantics/tools.h"
17 #include "llvm/Support/raw_ostream.h"
18 
19 namespace Fortran::semantics {
20 
21 DerivedTypeSpec::DerivedTypeSpec(SourceName name, const Symbol &typeSymbol)
22     : name_{name}, typeSymbol_{typeSymbol} {
23   CHECK(typeSymbol.has<DerivedTypeDetails>());
24 }
25 DerivedTypeSpec::DerivedTypeSpec(const DerivedTypeSpec &that) = default;
26 DerivedTypeSpec::DerivedTypeSpec(DerivedTypeSpec &&that) = default;
27 
28 void DerivedTypeSpec::set_scope(const Scope &scope) {
29   CHECK(!scope_);
30   ReplaceScope(scope);
31 }
32 void DerivedTypeSpec::ReplaceScope(const Scope &scope) {
33   CHECK(scope.IsDerivedType());
34   scope_ = &scope;
35 }
36 
37 void DerivedTypeSpec::AddRawParamValue(
38     const std::optional<parser::Keyword> &keyword, ParamValue &&value) {
39   CHECK(parameters_.empty());
40   rawParameters_.emplace_back(keyword ? &*keyword : nullptr, std::move(value));
41 }
42 
43 void DerivedTypeSpec::CookParameters(evaluate::FoldingContext &foldingContext) {
44   if (cooked_) {
45     return;
46   }
47   cooked_ = true;
48   auto &messages{foldingContext.messages()};
49   if (IsForwardReferenced()) {
50     messages.Say(typeSymbol_.name(),
51         "Derived type '%s' was used but never defined"_err_en_US,
52         typeSymbol_.name());
53     return;
54   }
55 
56   // Parameters of the most deeply nested "base class" come first when the
57   // derived type is an extension.
58   auto parameterNames{OrderParameterNames(typeSymbol_)};
59   auto parameterDecls{OrderParameterDeclarations(typeSymbol_)};
60   auto nextNameIter{parameterNames.begin()};
61   RawParameters raw{std::move(rawParameters_)};
62   for (auto &[maybeKeyword, value] : raw) {
63     SourceName name;
64     common::TypeParamAttr attr{common::TypeParamAttr::Kind};
65     if (maybeKeyword) {
66       name = maybeKeyword->v.source;
67       auto it{std::find_if(parameterDecls.begin(), parameterDecls.end(),
68           [&](const Symbol &symbol) { return symbol.name() == name; })};
69       if (it == parameterDecls.end()) {
70         messages.Say(name,
71             "'%s' is not the name of a parameter for derived type '%s'"_err_en_US,
72             name, typeSymbol_.name());
73       } else {
74         // Resolve the keyword's symbol
75         maybeKeyword->v.symbol = const_cast<Symbol *>(&it->get());
76         attr = it->get().get<TypeParamDetails>().attr();
77       }
78     } else if (nextNameIter != parameterNames.end()) {
79       name = *nextNameIter++;
80       auto it{std::find_if(parameterDecls.begin(), parameterDecls.end(),
81           [&](const Symbol &symbol) { return symbol.name() == name; })};
82       if (it == parameterDecls.end()) {
83         break;
84       }
85       attr = it->get().get<TypeParamDetails>().attr();
86     } else {
87       messages.Say(name_,
88           "Too many type parameters given for derived type '%s'"_err_en_US,
89           typeSymbol_.name());
90       break;
91     }
92     if (FindParameter(name)) {
93       messages.Say(name_,
94           "Multiple values given for type parameter '%s'"_err_en_US, name);
95     } else {
96       value.set_attr(attr);
97       AddParamValue(name, std::move(value));
98     }
99   }
100 }
101 
102 void DerivedTypeSpec::EvaluateParameters(SemanticsContext &context) {
103   evaluate::FoldingContext &foldingContext{context.foldingContext()};
104   CookParameters(foldingContext);
105   if (evaluated_) {
106     return;
107   }
108   evaluated_ = true;
109   auto &messages{foldingContext.messages()};
110 
111   // Fold the explicit type parameter value expressions first.  Do not
112   // fold them within the scope of the derived type being instantiated;
113   // these expressions cannot use its type parameters.  Convert the values
114   // of the expressions to the declared types of the type parameters.
115   auto parameterDecls{OrderParameterDeclarations(typeSymbol_)};
116   for (const Symbol &symbol : parameterDecls) {
117     const SourceName &name{symbol.name()};
118     if (ParamValue * paramValue{FindParameter(name)}) {
119       if (const MaybeIntExpr & expr{paramValue->GetExplicit()}) {
120         if (auto converted{evaluate::ConvertToType(symbol, SomeExpr{*expr})}) {
121           SomeExpr folded{
122               evaluate::Fold(foldingContext, std::move(*converted))};
123           if (auto *intExpr{std::get_if<SomeIntExpr>(&folded.u)}) {
124             paramValue->SetExplicit(std::move(*intExpr));
125             continue;
126           }
127         }
128         if (!context.HasError(symbol)) {
129           evaluate::SayWithDeclaration(messages, symbol,
130               "Value of type parameter '%s' (%s) is not convertible to its"
131               " type"_err_en_US,
132               name, expr->AsFortran());
133         }
134       }
135     }
136   }
137 
138   // Default initialization expressions for the derived type's parameters
139   // may reference other parameters so long as the declaration precedes the
140   // use in the expression (10.1.12).  This is not necessarily the same
141   // order as "type parameter order" (7.5.3.2).
142   // Type parameter default value expressions are folded in declaration order
143   // within the scope of the derived type so that the values of earlier type
144   // parameters are available for use in the default initialization
145   // expressions of later parameters.
146   auto restorer{foldingContext.WithPDTInstance(*this)};
147   for (const Symbol &symbol : parameterDecls) {
148     const SourceName &name{symbol.name()};
149     if (!FindParameter(name)) {
150       const TypeParamDetails &details{symbol.get<TypeParamDetails>()};
151       if (details.init()) {
152         auto expr{evaluate::Fold(foldingContext, SomeExpr{*details.init()})};
153         AddParamValue(name,
154             ParamValue{
155                 std::move(std::get<SomeIntExpr>(expr.u)), details.attr()});
156       } else if (!context.HasError(symbol)) {
157         messages.Say(name_,
158             "Type parameter '%s' lacks a value and has no default"_err_en_US,
159             name);
160       }
161     }
162   }
163 }
164 
165 void DerivedTypeSpec::AddParamValue(SourceName name, ParamValue &&value) {
166   CHECK(cooked_);
167   auto pair{parameters_.insert(std::make_pair(name, std::move(value)))};
168   CHECK(pair.second); // name was not already present
169 }
170 
171 bool DerivedTypeSpec::MightBeParameterized() const {
172   return !cooked_ || !parameters_.empty();
173 }
174 
175 bool DerivedTypeSpec::IsForwardReferenced() const {
176   return typeSymbol_.get<DerivedTypeDetails>().isForwardReferenced();
177 }
178 
179 bool DerivedTypeSpec::HasDefaultInitialization() const {
180   DirectComponentIterator components{*this};
181   return bool{std::find_if(
182       components.begin(), components.end(), [&](const Symbol &component) {
183         return IsInitialized(component, false, &typeSymbol());
184       })};
185 }
186 
187 ParamValue *DerivedTypeSpec::FindParameter(SourceName target) {
188   return const_cast<ParamValue *>(
189       const_cast<const DerivedTypeSpec *>(this)->FindParameter(target));
190 }
191 
192 class InstantiateHelper {
193 public:
194   InstantiateHelper(SemanticsContext &context, Scope &scope)
195       : context_{context}, scope_{scope} {}
196   // Instantiate components from fromScope into scope_
197   void InstantiateComponents(const Scope &);
198 
199 private:
200   evaluate::FoldingContext &foldingContext() {
201     return context_.foldingContext();
202   }
203   template <typename T> T Fold(T &&expr) {
204     return evaluate::Fold(foldingContext(), std::move(expr));
205   }
206   void InstantiateComponent(const Symbol &);
207   const DeclTypeSpec *InstantiateType(const Symbol &);
208   const DeclTypeSpec &InstantiateIntrinsicType(const DeclTypeSpec &);
209   DerivedTypeSpec CreateDerivedTypeSpec(const DerivedTypeSpec &, bool);
210 
211   SemanticsContext &context_;
212   Scope &scope_;
213 };
214 
215 void DerivedTypeSpec::Instantiate(
216     Scope &containingScope, SemanticsContext &context) {
217   if (instantiated_) {
218     return;
219   }
220   instantiated_ = true;
221   auto &foldingContext{context.foldingContext()};
222   if (IsForwardReferenced()) {
223     foldingContext.messages().Say(typeSymbol_.name(),
224         "The derived type '%s' was forward-referenced but not defined"_err_en_US,
225         typeSymbol_.name());
226     return;
227   }
228   EvaluateParameters(context);
229   const Scope &typeScope{DEREF(typeSymbol_.scope())};
230   if (!MightBeParameterized()) {
231     scope_ = &typeScope;
232     for (auto &pair : typeScope) {
233       Symbol &symbol{*pair.second};
234       if (DeclTypeSpec * type{symbol.GetType()}) {
235         if (DerivedTypeSpec * derived{type->AsDerived()}) {
236           if (!(derived->IsForwardReferenced() &&
237                   IsAllocatableOrPointer(symbol))) {
238             derived->Instantiate(containingScope, context);
239           }
240         }
241       }
242       if (!IsPointer(symbol)) {
243         if (auto *object{symbol.detailsIf<ObjectEntityDetails>()}) {
244           if (MaybeExpr & init{object->init()}) {
245             auto restorer{foldingContext.messages().SetLocation(symbol.name())};
246             init = evaluate::NonPointerInitializationExpr(
247                 symbol, std::move(*init), foldingContext);
248           }
249         }
250       }
251     }
252     ComputeOffsets(context, const_cast<Scope &>(typeScope));
253     return;
254   }
255   Scope &newScope{containingScope.MakeScope(Scope::Kind::DerivedType)};
256   newScope.set_derivedTypeSpec(*this);
257   ReplaceScope(newScope);
258   auto restorer{foldingContext.WithPDTInstance(*this)};
259   std::string desc{typeSymbol_.name().ToString()};
260   char sep{'('};
261   for (const Symbol &symbol : OrderParameterDeclarations(typeSymbol_)) {
262     const SourceName &name{symbol.name()};
263     if (typeScope.find(symbol.name()) != typeScope.end()) {
264       // This type parameter belongs to the derived type itself, not to
265       // one of its ancestors.  Put the type parameter expression value
266       // into the new scope as the initialization value for the parameter.
267       if (ParamValue * paramValue{FindParameter(name)}) {
268         const TypeParamDetails &details{symbol.get<TypeParamDetails>()};
269         paramValue->set_attr(details.attr());
270         if (MaybeIntExpr expr{paramValue->GetExplicit()}) {
271           if (auto folded{evaluate::NonPointerInitializationExpr(symbol,
272                   SomeExpr{std::move(*expr)}, foldingContext, &newScope)}) {
273             desc += sep;
274             desc += name.ToString();
275             desc += '=';
276             desc += folded->AsFortran();
277             sep = ',';
278             TypeParamDetails instanceDetails{details.attr()};
279             if (const DeclTypeSpec * type{details.type()}) {
280               instanceDetails.set_type(*type);
281             }
282             instanceDetails.set_init(
283                 std::move(DEREF(evaluate::UnwrapExpr<SomeIntExpr>(*folded))));
284             newScope.try_emplace(name, std::move(instanceDetails));
285           }
286         }
287       }
288     }
289   }
290   parser::Message *contextMessage{nullptr};
291   if (sep != '(') {
292     desc += ')';
293     contextMessage = new parser::Message{foldingContext.messages().at(),
294         "instantiation of parameterized derived type '%s'"_en_US, desc};
295     if (auto outer{containingScope.instantiationContext()}) {
296       contextMessage->SetContext(outer.get());
297     }
298     newScope.set_instantiationContext(contextMessage);
299   }
300   // Instantiate every non-parameter symbol from the original derived
301   // type's scope into the new instance.
302   newScope.AddSourceRange(typeScope.sourceRange());
303   auto restorer2{foldingContext.messages().SetContext(contextMessage)};
304   InstantiateHelper{context, newScope}.InstantiateComponents(typeScope);
305 }
306 
307 void InstantiateHelper::InstantiateComponents(const Scope &fromScope) {
308   for (const auto &pair : fromScope) {
309     InstantiateComponent(*pair.second);
310   }
311   ComputeOffsets(context_, scope_);
312 }
313 
314 void InstantiateHelper::InstantiateComponent(const Symbol &oldSymbol) {
315   auto pair{scope_.try_emplace(
316       oldSymbol.name(), oldSymbol.attrs(), common::Clone(oldSymbol.details()))};
317   Symbol &newSymbol{*pair.first->second};
318   if (!pair.second) {
319     // Symbol was already present in the scope, which can only happen
320     // in the case of type parameters.
321     CHECK(oldSymbol.has<TypeParamDetails>());
322     return;
323   }
324   newSymbol.flags() = oldSymbol.flags();
325   if (auto *details{newSymbol.detailsIf<ObjectEntityDetails>()}) {
326     if (const DeclTypeSpec * newType{InstantiateType(newSymbol)}) {
327       details->ReplaceType(*newType);
328     }
329     for (ShapeSpec &dim : details->shape()) {
330       if (dim.lbound().isExplicit()) {
331         dim.lbound().SetExplicit(Fold(std::move(dim.lbound().GetExplicit())));
332       }
333       if (dim.ubound().isExplicit()) {
334         dim.ubound().SetExplicit(Fold(std::move(dim.ubound().GetExplicit())));
335       }
336     }
337     for (ShapeSpec &dim : details->coshape()) {
338       if (dim.lbound().isExplicit()) {
339         dim.lbound().SetExplicit(Fold(std::move(dim.lbound().GetExplicit())));
340       }
341       if (dim.ubound().isExplicit()) {
342         dim.ubound().SetExplicit(Fold(std::move(dim.ubound().GetExplicit())));
343       }
344     }
345     if (MaybeExpr & init{details->init()}) {
346       // Non-pointer components with default initializers are
347       // processed now so that those default initializers can be used
348       // in PARAMETER structure constructors.
349       auto restorer{foldingContext().messages().SetLocation(newSymbol.name())};
350       init = IsPointer(newSymbol)
351           ? evaluate::Fold(foldingContext(), std::move(*init))
352           : evaluate::NonPointerInitializationExpr(
353                 newSymbol, std::move(*init), foldingContext());
354     }
355   }
356 }
357 
358 const DeclTypeSpec *InstantiateHelper::InstantiateType(const Symbol &symbol) {
359   const DeclTypeSpec *type{symbol.GetType()};
360   if (!type) {
361     return nullptr; // error has occurred
362   } else if (const DerivedTypeSpec * spec{type->AsDerived()}) {
363     return &FindOrInstantiateDerivedType(scope_,
364         CreateDerivedTypeSpec(*spec, symbol.test(Symbol::Flag::ParentComp)),
365         context_, type->category());
366   } else if (type->AsIntrinsic()) {
367     return &InstantiateIntrinsicType(*type);
368   } else if (type->category() == DeclTypeSpec::ClassStar) {
369     return type;
370   } else {
371     common::die("InstantiateType: %s", type->AsFortran().c_str());
372   }
373 }
374 
375 // Apply type parameter values to an intrinsic type spec.
376 const DeclTypeSpec &InstantiateHelper::InstantiateIntrinsicType(
377     const DeclTypeSpec &spec) {
378   const IntrinsicTypeSpec &intrinsic{DEREF(spec.AsIntrinsic())};
379   if (evaluate::ToInt64(intrinsic.kind())) {
380     return spec; // KIND is already a known constant
381   }
382   // The expression was not originally constant, but now it must be so
383   // in the context of a parameterized derived type instantiation.
384   KindExpr copy{Fold(common::Clone(intrinsic.kind()))};
385   int kind{context_.GetDefaultKind(intrinsic.category())};
386   if (auto value{evaluate::ToInt64(copy)}) {
387     if (evaluate::IsValidKindOfIntrinsicType(intrinsic.category(), *value)) {
388       kind = *value;
389     } else {
390       foldingContext().messages().Say(
391           "KIND parameter value (%jd) of intrinsic type %s "
392           "did not resolve to a supported value"_err_en_US,
393           *value,
394           parser::ToUpperCaseLetters(EnumToString(intrinsic.category())));
395     }
396   }
397   switch (spec.category()) {
398   case DeclTypeSpec::Numeric:
399     return scope_.MakeNumericType(intrinsic.category(), KindExpr{kind});
400   case DeclTypeSpec::Logical:
401     return scope_.MakeLogicalType(KindExpr{kind});
402   case DeclTypeSpec::Character:
403     return scope_.MakeCharacterType(
404         ParamValue{spec.characterTypeSpec().length()}, KindExpr{kind});
405   default:
406     CRASH_NO_CASE;
407   }
408 }
409 
410 DerivedTypeSpec InstantiateHelper::CreateDerivedTypeSpec(
411     const DerivedTypeSpec &spec, bool isParentComp) {
412   DerivedTypeSpec result{spec};
413   result.CookParameters(foldingContext()); // enables AddParamValue()
414   if (isParentComp) {
415     // Forward any explicit type parameter values from the
416     // derived type spec under instantiation that define type parameters
417     // of the parent component to the derived type spec of the
418     // parent component.
419     const DerivedTypeSpec &instanceSpec{DEREF(foldingContext().pdtInstance())};
420     for (const auto &[name, value] : instanceSpec.parameters()) {
421       if (scope_.find(name) == scope_.end()) {
422         result.AddParamValue(name, ParamValue{value});
423       }
424     }
425   }
426   return result;
427 }
428 
429 std::string DerivedTypeSpec::AsFortran() const {
430   std::string buf;
431   llvm::raw_string_ostream ss{buf};
432   ss << name_;
433   if (!rawParameters_.empty()) {
434     CHECK(parameters_.empty());
435     ss << '(';
436     bool first = true;
437     for (const auto &[maybeKeyword, value] : rawParameters_) {
438       if (first) {
439         first = false;
440       } else {
441         ss << ',';
442       }
443       if (maybeKeyword) {
444         ss << maybeKeyword->v.source.ToString() << '=';
445       }
446       ss << value.AsFortran();
447     }
448     ss << ')';
449   } else if (!parameters_.empty()) {
450     ss << '(';
451     bool first = true;
452     for (const auto &[name, value] : parameters_) {
453       if (first) {
454         first = false;
455       } else {
456         ss << ',';
457       }
458       ss << name.ToString() << '=' << value.AsFortran();
459     }
460     ss << ')';
461   }
462   return ss.str();
463 }
464 
465 llvm::raw_ostream &operator<<(llvm::raw_ostream &o, const DerivedTypeSpec &x) {
466   return o << x.AsFortran();
467 }
468 
469 Bound::Bound(common::ConstantSubscript bound) : expr_{bound} {}
470 
471 llvm::raw_ostream &operator<<(llvm::raw_ostream &o, const Bound &x) {
472   if (x.isAssumed()) {
473     o << '*';
474   } else if (x.isDeferred()) {
475     o << ':';
476   } else if (x.expr_) {
477     x.expr_->AsFortran(o);
478   } else {
479     o << "<no-expr>";
480   }
481   return o;
482 }
483 
484 llvm::raw_ostream &operator<<(llvm::raw_ostream &o, const ShapeSpec &x) {
485   if (x.lb_.isAssumed()) {
486     CHECK(x.ub_.isAssumed());
487     o << "..";
488   } else {
489     if (!x.lb_.isDeferred()) {
490       o << x.lb_;
491     }
492     o << ':';
493     if (!x.ub_.isDeferred()) {
494       o << x.ub_;
495     }
496   }
497   return o;
498 }
499 
500 llvm::raw_ostream &operator<<(
501     llvm::raw_ostream &os, const ArraySpec &arraySpec) {
502   char sep{'('};
503   for (auto &shape : arraySpec) {
504     os << sep << shape;
505     sep = ',';
506   }
507   if (sep == ',') {
508     os << ')';
509   }
510   return os;
511 }
512 
513 ParamValue::ParamValue(MaybeIntExpr &&expr, common::TypeParamAttr attr)
514     : attr_{attr}, expr_{std::move(expr)} {}
515 ParamValue::ParamValue(SomeIntExpr &&expr, common::TypeParamAttr attr)
516     : attr_{attr}, expr_{std::move(expr)} {}
517 ParamValue::ParamValue(
518     common::ConstantSubscript value, common::TypeParamAttr attr)
519     : ParamValue(SomeIntExpr{evaluate::Expr<evaluate::SubscriptInteger>{value}},
520           attr) {}
521 
522 void ParamValue::SetExplicit(SomeIntExpr &&x) {
523   category_ = Category::Explicit;
524   expr_ = std::move(x);
525 }
526 
527 std::string ParamValue::AsFortran() const {
528   switch (category_) {
529     SWITCH_COVERS_ALL_CASES
530   case Category::Assumed:
531     return "*";
532   case Category::Deferred:
533     return ":";
534   case Category::Explicit:
535     if (expr_) {
536       std::string buf;
537       llvm::raw_string_ostream ss{buf};
538       expr_->AsFortran(ss);
539       return ss.str();
540     } else {
541       return "";
542     }
543   }
544 }
545 
546 llvm::raw_ostream &operator<<(llvm::raw_ostream &o, const ParamValue &x) {
547   return o << x.AsFortran();
548 }
549 
550 IntrinsicTypeSpec::IntrinsicTypeSpec(TypeCategory category, KindExpr &&kind)
551     : category_{category}, kind_{std::move(kind)} {
552   CHECK(category != TypeCategory::Derived);
553 }
554 
555 static std::string KindAsFortran(const KindExpr &kind) {
556   std::string buf;
557   llvm::raw_string_ostream ss{buf};
558   if (auto k{evaluate::ToInt64(kind)}) {
559     ss << *k; // emit unsuffixed kind code
560   } else {
561     kind.AsFortran(ss);
562   }
563   return ss.str();
564 }
565 
566 std::string IntrinsicTypeSpec::AsFortran() const {
567   return parser::ToUpperCaseLetters(common::EnumToString(category_)) + '(' +
568       KindAsFortran(kind_) + ')';
569 }
570 
571 llvm::raw_ostream &operator<<(
572     llvm::raw_ostream &os, const IntrinsicTypeSpec &x) {
573   return os << x.AsFortran();
574 }
575 
576 std::string CharacterTypeSpec::AsFortran() const {
577   return "CHARACTER(" + length_.AsFortran() + ',' + KindAsFortran(kind()) + ')';
578 }
579 
580 llvm::raw_ostream &operator<<(
581     llvm::raw_ostream &os, const CharacterTypeSpec &x) {
582   return os << x.AsFortran();
583 }
584 
585 DeclTypeSpec::DeclTypeSpec(NumericTypeSpec &&typeSpec)
586     : category_{Numeric}, typeSpec_{std::move(typeSpec)} {}
587 DeclTypeSpec::DeclTypeSpec(LogicalTypeSpec &&typeSpec)
588     : category_{Logical}, typeSpec_{std::move(typeSpec)} {}
589 DeclTypeSpec::DeclTypeSpec(const CharacterTypeSpec &typeSpec)
590     : category_{Character}, typeSpec_{typeSpec} {}
591 DeclTypeSpec::DeclTypeSpec(CharacterTypeSpec &&typeSpec)
592     : category_{Character}, typeSpec_{std::move(typeSpec)} {}
593 DeclTypeSpec::DeclTypeSpec(Category category, const DerivedTypeSpec &typeSpec)
594     : category_{category}, typeSpec_{typeSpec} {
595   CHECK(category == TypeDerived || category == ClassDerived);
596 }
597 DeclTypeSpec::DeclTypeSpec(Category category, DerivedTypeSpec &&typeSpec)
598     : category_{category}, typeSpec_{std::move(typeSpec)} {
599   CHECK(category == TypeDerived || category == ClassDerived);
600 }
601 DeclTypeSpec::DeclTypeSpec(Category category) : category_{category} {
602   CHECK(category == TypeStar || category == ClassStar);
603 }
604 bool DeclTypeSpec::IsNumeric(TypeCategory tc) const {
605   return category_ == Numeric && numericTypeSpec().category() == tc;
606 }
607 bool DeclTypeSpec::IsSequenceType() const {
608   if (const DerivedTypeSpec * derivedType{AsDerived()}) {
609     const auto *typeDetails{
610         derivedType->typeSymbol().detailsIf<DerivedTypeDetails>()};
611     return typeDetails && typeDetails->sequence();
612   }
613   return false;
614 }
615 
616 const NumericTypeSpec &DeclTypeSpec::numericTypeSpec() const {
617   CHECK(category_ == Numeric);
618   return std::get<NumericTypeSpec>(typeSpec_);
619 }
620 const LogicalTypeSpec &DeclTypeSpec::logicalTypeSpec() const {
621   CHECK(category_ == Logical);
622   return std::get<LogicalTypeSpec>(typeSpec_);
623 }
624 bool DeclTypeSpec::operator==(const DeclTypeSpec &that) const {
625   return category_ == that.category_ && typeSpec_ == that.typeSpec_;
626 }
627 
628 std::string DeclTypeSpec::AsFortran() const {
629   switch (category_) {
630     SWITCH_COVERS_ALL_CASES
631   case Numeric:
632     return numericTypeSpec().AsFortran();
633   case Logical:
634     return logicalTypeSpec().AsFortran();
635   case Character:
636     return characterTypeSpec().AsFortran();
637   case TypeDerived:
638     return "TYPE(" + derivedTypeSpec().AsFortran() + ')';
639   case ClassDerived:
640     return "CLASS(" + derivedTypeSpec().AsFortran() + ')';
641   case TypeStar:
642     return "TYPE(*)";
643   case ClassStar:
644     return "CLASS(*)";
645   }
646 }
647 
648 llvm::raw_ostream &operator<<(llvm::raw_ostream &o, const DeclTypeSpec &x) {
649   return o << x.AsFortran();
650 }
651 
652 void ProcInterface::set_symbol(const Symbol &symbol) {
653   CHECK(!type_);
654   symbol_ = &symbol;
655 }
656 void ProcInterface::set_type(const DeclTypeSpec &type) {
657   CHECK(!symbol_);
658   type_ = &type;
659 }
660 
661 } // namespace Fortran::semantics
662