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