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 
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 
27 void DerivedTypeSpec::set_scope(const Scope &scope) {
28   CHECK(!scope_);
29   ReplaceScope(scope);
30 }
31 void DerivedTypeSpec::ReplaceScope(const Scope &scope) {
32   CHECK(scope.IsDerivedType());
33   scope_ = &scope;
34 }
35 
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 
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 
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{
152             evaluate::Fold(foldingContext, common::Clone(details.init()))};
153         AddParamValue(name, ParamValue{std::move(*expr), details.attr()});
154       } else if (!context.HasError(symbol)) {
155         messages.Say(name_,
156             "Type parameter '%s' lacks a value and has no default"_err_en_US,
157             name);
158       }
159     }
160   }
161 }
162 
163 void DerivedTypeSpec::AddParamValue(SourceName name, ParamValue &&value) {
164   CHECK(cooked_);
165   auto pair{parameters_.insert(std::make_pair(name, std::move(value)))};
166   CHECK(pair.second); // name was not already present
167 }
168 
169 bool DerivedTypeSpec::MightBeParameterized() const {
170   return !cooked_ || !parameters_.empty();
171 }
172 
173 bool DerivedTypeSpec::IsForwardReferenced() const {
174   return typeSymbol_.get<DerivedTypeDetails>().isForwardReferenced();
175 }
176 
177 bool DerivedTypeSpec::HasDefaultInitialization() const {
178   DirectComponentIterator components{*this};
179   return bool{std::find_if(components.begin(), components.end(),
180       [](const Symbol &component) { return IsInitialized(component); })};
181 }
182 
183 ParamValue *DerivedTypeSpec::FindParameter(SourceName target) {
184   return const_cast<ParamValue *>(
185       const_cast<const DerivedTypeSpec *>(this)->FindParameter(target));
186 }
187 
188 class InstantiateHelper {
189 public:
190   InstantiateHelper(SemanticsContext &context, Scope &scope)
191       : context_{context}, scope_{scope} {}
192   // Instantiate components from fromScope into scope_
193   void InstantiateComponents(const Scope &);
194 
195 private:
196   evaluate::FoldingContext &foldingContext() {
197     return context_.foldingContext();
198   }
199   template <typename T> T Fold(T &&expr) {
200     return evaluate::Fold(foldingContext(), std::move(expr));
201   }
202   void InstantiateComponent(const Symbol &);
203   const DeclTypeSpec *InstantiateType(const Symbol &);
204   const DeclTypeSpec &InstantiateIntrinsicType(const DeclTypeSpec &);
205   DerivedTypeSpec CreateDerivedTypeSpec(const DerivedTypeSpec &, bool);
206 
207   SemanticsContext &context_;
208   Scope &scope_;
209 };
210 
211 void DerivedTypeSpec::Instantiate(
212     Scope &containingScope, SemanticsContext &context) {
213   if (instantiated_) {
214     return;
215   }
216   instantiated_ = true;
217   auto &foldingContext{context.foldingContext()};
218   if (IsForwardReferenced()) {
219     foldingContext.messages().Say(typeSymbol_.name(),
220         "The derived type '%s' was forward-referenced but not defined"_err_en_US,
221         typeSymbol_.name());
222     return;
223   }
224   EvaluateParameters(context);
225   const Scope &typeScope{DEREF(typeSymbol_.scope())};
226   if (!MightBeParameterized()) {
227     scope_ = &typeScope;
228     for (auto &pair : typeScope) {
229       Symbol &symbol{*pair.second};
230       if (DeclTypeSpec * type{symbol.GetType()}) {
231         if (DerivedTypeSpec * derived{type->AsDerived()}) {
232           if (!(derived->IsForwardReferenced() &&
233                   IsAllocatableOrPointer(symbol))) {
234             derived->Instantiate(containingScope, context);
235           }
236         }
237       }
238     }
239     return;
240   }
241   Scope &newScope{containingScope.MakeScope(Scope::Kind::DerivedType)};
242   newScope.set_derivedTypeSpec(*this);
243   ReplaceScope(newScope);
244   for (const Symbol &symbol : OrderParameterDeclarations(typeSymbol_)) {
245     const SourceName &name{symbol.name()};
246     if (typeScope.find(symbol.name()) != typeScope.end()) {
247       // This type parameter belongs to the derived type itself, not to
248       // one of its ancestors.  Put the type parameter expression value
249       // into the new scope as the initialization value for the parameter.
250       if (ParamValue * paramValue{FindParameter(name)}) {
251         const TypeParamDetails &details{symbol.get<TypeParamDetails>()};
252         paramValue->set_attr(details.attr());
253         if (MaybeIntExpr expr{paramValue->GetExplicit()}) {
254           // Ensure that any kind type parameters with values are
255           // constant by now.
256           if (details.attr() == common::TypeParamAttr::Kind) {
257             // Any errors in rank and type will have already elicited
258             // messages, so don't pile on by complaining further here.
259             if (auto maybeDynamicType{expr->GetType()}) {
260               if (expr->Rank() == 0 &&
261                   maybeDynamicType->category() == TypeCategory::Integer) {
262                 if (!evaluate::ToInt64(*expr)) {
263                   if (auto *msg{foldingContext.messages().Say(
264                           "Value of kind type parameter '%s' (%s) is not "
265                           "a scalar INTEGER constant"_err_en_US,
266                           name, expr->AsFortran())}) {
267                     msg->Attach(name, "declared here"_en_US);
268                   }
269                 }
270               }
271             }
272           }
273           TypeParamDetails instanceDetails{details.attr()};
274           if (const DeclTypeSpec * type{details.type()}) {
275             instanceDetails.set_type(*type);
276           }
277           instanceDetails.set_init(std::move(*expr));
278           newScope.try_emplace(name, std::move(instanceDetails));
279         }
280       }
281     }
282   }
283   // Instantiate every non-parameter symbol from the original derived
284   // type's scope into the new instance.
285   auto restorer{foldingContext.WithPDTInstance(*this)};
286   newScope.AddSourceRange(typeScope.sourceRange());
287   InstantiateHelper{context, newScope}.InstantiateComponents(typeScope);
288   CheckInstantiatedDerivedType(context, *this);
289 }
290 
291 void InstantiateHelper::InstantiateComponents(const Scope &fromScope) {
292   for (const auto &pair : fromScope) {
293     InstantiateComponent(*pair.second);
294   }
295 }
296 
297 void InstantiateHelper::InstantiateComponent(const Symbol &oldSymbol) {
298   auto pair{scope_.try_emplace(
299       oldSymbol.name(), oldSymbol.attrs(), common::Clone(oldSymbol.details()))};
300   Symbol &newSymbol{*pair.first->second};
301   if (!pair.second) {
302     // Symbol was already present in the scope, which can only happen
303     // in the case of type parameters.
304     CHECK(oldSymbol.has<TypeParamDetails>());
305     return;
306   }
307   newSymbol.flags() = oldSymbol.flags();
308   if (auto *details{newSymbol.detailsIf<ObjectEntityDetails>()}) {
309     if (const DeclTypeSpec * newType{InstantiateType(newSymbol)}) {
310       details->ReplaceType(*newType);
311     }
312     details->set_init(Fold(std::move(details->init())));
313     for (ShapeSpec &dim : details->shape()) {
314       if (dim.lbound().isExplicit()) {
315         dim.lbound().SetExplicit(Fold(std::move(dim.lbound().GetExplicit())));
316       }
317       if (dim.ubound().isExplicit()) {
318         dim.ubound().SetExplicit(Fold(std::move(dim.ubound().GetExplicit())));
319       }
320     }
321     for (ShapeSpec &dim : details->coshape()) {
322       if (dim.lbound().isExplicit()) {
323         dim.lbound().SetExplicit(Fold(std::move(dim.lbound().GetExplicit())));
324       }
325       if (dim.ubound().isExplicit()) {
326         dim.ubound().SetExplicit(Fold(std::move(dim.ubound().GetExplicit())));
327       }
328     }
329   }
330 }
331 
332 const DeclTypeSpec *InstantiateHelper::InstantiateType(const Symbol &symbol) {
333   const DeclTypeSpec *type{symbol.GetType()};
334   if (!type) {
335     return nullptr; // error has occurred
336   } else if (const DerivedTypeSpec * spec{type->AsDerived()}) {
337     return &FindOrInstantiateDerivedType(scope_,
338         CreateDerivedTypeSpec(*spec, symbol.test(Symbol::Flag::ParentComp)),
339         context_, type->category());
340   } else if (type->AsIntrinsic()) {
341     return &InstantiateIntrinsicType(*type);
342   } else if (type->category() == DeclTypeSpec::ClassStar) {
343     return type;
344   } else {
345     common::die("InstantiateType: %s", type->AsFortran().c_str());
346   }
347 }
348 
349 // Apply type parameter values to an intrinsic type spec.
350 const DeclTypeSpec &InstantiateHelper::InstantiateIntrinsicType(
351     const DeclTypeSpec &spec) {
352   const IntrinsicTypeSpec &intrinsic{DEREF(spec.AsIntrinsic())};
353   if (evaluate::ToInt64(intrinsic.kind())) {
354     return spec; // KIND is already a known constant
355   }
356   // The expression was not originally constant, but now it must be so
357   // in the context of a parameterized derived type instantiation.
358   KindExpr copy{Fold(common::Clone(intrinsic.kind()))};
359   int kind{context_.GetDefaultKind(intrinsic.category())};
360   if (auto value{evaluate::ToInt64(copy)}) {
361     if (evaluate::IsValidKindOfIntrinsicType(intrinsic.category(), *value)) {
362       kind = *value;
363     } else {
364       foldingContext().messages().Say(
365           "KIND parameter value (%jd) of intrinsic type %s "
366           "did not resolve to a supported value"_err_en_US,
367           *value,
368           parser::ToUpperCaseLetters(EnumToString(intrinsic.category())));
369     }
370   }
371   switch (spec.category()) {
372   case DeclTypeSpec::Numeric:
373     return scope_.MakeNumericType(intrinsic.category(), KindExpr{kind});
374   case DeclTypeSpec::Logical:
375     return scope_.MakeLogicalType(KindExpr{kind});
376   case DeclTypeSpec::Character:
377     return scope_.MakeCharacterType(
378         ParamValue{spec.characterTypeSpec().length()}, KindExpr{kind});
379   default:
380     CRASH_NO_CASE;
381   }
382 }
383 
384 DerivedTypeSpec InstantiateHelper::CreateDerivedTypeSpec(
385     const DerivedTypeSpec &spec, bool isParentComp) {
386   DerivedTypeSpec result{spec};
387   result.CookParameters(foldingContext()); // enables AddParamValue()
388   if (isParentComp) {
389     // Forward any explicit type parameter values from the
390     // derived type spec under instantiation that define type parameters
391     // of the parent component to the derived type spec of the
392     // parent component.
393     const DerivedTypeSpec &instanceSpec{DEREF(foldingContext().pdtInstance())};
394     for (const auto &[name, value] : instanceSpec.parameters()) {
395       if (scope_.find(name) == scope_.end()) {
396         result.AddParamValue(name, ParamValue{value});
397       }
398     }
399   }
400   return result;
401 }
402 
403 std::string DerivedTypeSpec::AsFortran() const {
404   std::string buf;
405   llvm::raw_string_ostream ss{buf};
406   ss << name_;
407   if (!rawParameters_.empty()) {
408     CHECK(parameters_.empty());
409     ss << '(';
410     bool first = true;
411     for (const auto &[maybeKeyword, value] : rawParameters_) {
412       if (first) {
413         first = false;
414       } else {
415         ss << ',';
416       }
417       if (maybeKeyword) {
418         ss << maybeKeyword->v.source.ToString() << '=';
419       }
420       ss << value.AsFortran();
421     }
422     ss << ')';
423   } else if (!parameters_.empty()) {
424     ss << '(';
425     bool first = true;
426     for (const auto &[name, value] : parameters_) {
427       if (first) {
428         first = false;
429       } else {
430         ss << ',';
431       }
432       ss << name.ToString() << '=' << value.AsFortran();
433     }
434     ss << ')';
435   }
436   return ss.str();
437 }
438 
439 llvm::raw_ostream &operator<<(llvm::raw_ostream &o, const DerivedTypeSpec &x) {
440   return o << x.AsFortran();
441 }
442 
443 Bound::Bound(common::ConstantSubscript bound) : expr_{bound} {}
444 
445 llvm::raw_ostream &operator<<(llvm::raw_ostream &o, const Bound &x) {
446   if (x.isAssumed()) {
447     o << '*';
448   } else if (x.isDeferred()) {
449     o << ':';
450   } else if (x.expr_) {
451     x.expr_->AsFortran(o);
452   } else {
453     o << "<no-expr>";
454   }
455   return o;
456 }
457 
458 llvm::raw_ostream &operator<<(llvm::raw_ostream &o, const ShapeSpec &x) {
459   if (x.lb_.isAssumed()) {
460     CHECK(x.ub_.isAssumed());
461     o << "..";
462   } else {
463     if (!x.lb_.isDeferred()) {
464       o << x.lb_;
465     }
466     o << ':';
467     if (!x.ub_.isDeferred()) {
468       o << x.ub_;
469     }
470   }
471   return o;
472 }
473 
474 llvm::raw_ostream &operator<<(
475     llvm::raw_ostream &os, const ArraySpec &arraySpec) {
476   char sep{'('};
477   for (auto &shape : arraySpec) {
478     os << sep << shape;
479     sep = ',';
480   }
481   if (sep == ',') {
482     os << ')';
483   }
484   return os;
485 }
486 
487 ParamValue::ParamValue(MaybeIntExpr &&expr, common::TypeParamAttr attr)
488     : attr_{attr}, expr_{std::move(expr)} {}
489 ParamValue::ParamValue(SomeIntExpr &&expr, common::TypeParamAttr attr)
490     : attr_{attr}, expr_{std::move(expr)} {}
491 ParamValue::ParamValue(
492     common::ConstantSubscript value, common::TypeParamAttr attr)
493     : ParamValue(SomeIntExpr{evaluate::Expr<evaluate::SubscriptInteger>{value}},
494           attr) {}
495 
496 void ParamValue::SetExplicit(SomeIntExpr &&x) {
497   category_ = Category::Explicit;
498   expr_ = std::move(x);
499 }
500 
501 std::string ParamValue::AsFortran() const {
502   switch (category_) {
503     SWITCH_COVERS_ALL_CASES
504   case Category::Assumed:
505     return "*";
506   case Category::Deferred:
507     return ":";
508   case Category::Explicit:
509     if (expr_) {
510       std::string buf;
511       llvm::raw_string_ostream ss{buf};
512       expr_->AsFortran(ss);
513       return ss.str();
514     } else {
515       return "";
516     }
517   }
518 }
519 
520 llvm::raw_ostream &operator<<(llvm::raw_ostream &o, const ParamValue &x) {
521   return o << x.AsFortran();
522 }
523 
524 IntrinsicTypeSpec::IntrinsicTypeSpec(TypeCategory category, KindExpr &&kind)
525     : category_{category}, kind_{std::move(kind)} {
526   CHECK(category != TypeCategory::Derived);
527 }
528 
529 static std::string KindAsFortran(const KindExpr &kind) {
530   std::string buf;
531   llvm::raw_string_ostream ss{buf};
532   if (auto k{evaluate::ToInt64(kind)}) {
533     ss << *k; // emit unsuffixed kind code
534   } else {
535     kind.AsFortran(ss);
536   }
537   return ss.str();
538 }
539 
540 std::string IntrinsicTypeSpec::AsFortran() const {
541   return parser::ToUpperCaseLetters(common::EnumToString(category_)) + '(' +
542       KindAsFortran(kind_) + ')';
543 }
544 
545 llvm::raw_ostream &operator<<(
546     llvm::raw_ostream &os, const IntrinsicTypeSpec &x) {
547   return os << x.AsFortran();
548 }
549 
550 std::string CharacterTypeSpec::AsFortran() const {
551   return "CHARACTER(" + length_.AsFortran() + ',' + KindAsFortran(kind()) + ')';
552 }
553 
554 llvm::raw_ostream &operator<<(
555     llvm::raw_ostream &os, const CharacterTypeSpec &x) {
556   return os << x.AsFortran();
557 }
558 
559 DeclTypeSpec::DeclTypeSpec(NumericTypeSpec &&typeSpec)
560     : category_{Numeric}, typeSpec_{std::move(typeSpec)} {}
561 DeclTypeSpec::DeclTypeSpec(LogicalTypeSpec &&typeSpec)
562     : category_{Logical}, typeSpec_{std::move(typeSpec)} {}
563 DeclTypeSpec::DeclTypeSpec(const CharacterTypeSpec &typeSpec)
564     : category_{Character}, typeSpec_{typeSpec} {}
565 DeclTypeSpec::DeclTypeSpec(CharacterTypeSpec &&typeSpec)
566     : category_{Character}, typeSpec_{std::move(typeSpec)} {}
567 DeclTypeSpec::DeclTypeSpec(Category category, const DerivedTypeSpec &typeSpec)
568     : category_{category}, typeSpec_{typeSpec} {
569   CHECK(category == TypeDerived || category == ClassDerived);
570 }
571 DeclTypeSpec::DeclTypeSpec(Category category, DerivedTypeSpec &&typeSpec)
572     : category_{category}, typeSpec_{std::move(typeSpec)} {
573   CHECK(category == TypeDerived || category == ClassDerived);
574 }
575 DeclTypeSpec::DeclTypeSpec(Category category) : category_{category} {
576   CHECK(category == TypeStar || category == ClassStar);
577 }
578 bool DeclTypeSpec::IsNumeric(TypeCategory tc) const {
579   return category_ == Numeric && numericTypeSpec().category() == tc;
580 }
581 bool DeclTypeSpec::IsSequenceType() const {
582   if (const DerivedTypeSpec * derivedType{AsDerived()}) {
583     const auto *typeDetails{
584         derivedType->typeSymbol().detailsIf<DerivedTypeDetails>()};
585     return typeDetails && typeDetails->sequence();
586   }
587   return false;
588 }
589 
590 const NumericTypeSpec &DeclTypeSpec::numericTypeSpec() const {
591   CHECK(category_ == Numeric);
592   return std::get<NumericTypeSpec>(typeSpec_);
593 }
594 const LogicalTypeSpec &DeclTypeSpec::logicalTypeSpec() const {
595   CHECK(category_ == Logical);
596   return std::get<LogicalTypeSpec>(typeSpec_);
597 }
598 bool DeclTypeSpec::operator==(const DeclTypeSpec &that) const {
599   return category_ == that.category_ && typeSpec_ == that.typeSpec_;
600 }
601 
602 std::string DeclTypeSpec::AsFortran() const {
603   switch (category_) {
604     SWITCH_COVERS_ALL_CASES
605   case Numeric:
606     return numericTypeSpec().AsFortran();
607   case Logical:
608     return logicalTypeSpec().AsFortran();
609   case Character:
610     return characterTypeSpec().AsFortran();
611   case TypeDerived:
612     return "TYPE(" + derivedTypeSpec().AsFortran() + ')';
613   case ClassDerived:
614     return "CLASS(" + derivedTypeSpec().AsFortran() + ')';
615   case TypeStar:
616     return "TYPE(*)";
617   case ClassStar:
618     return "CLASS(*)";
619   }
620 }
621 
622 llvm::raw_ostream &operator<<(llvm::raw_ostream &o, const DeclTypeSpec &x) {
623   return o << x.AsFortran();
624 }
625 
626 void ProcInterface::set_symbol(const Symbol &symbol) {
627   CHECK(!type_);
628   symbol_ = &symbol;
629 }
630 void ProcInterface::set_type(const DeclTypeSpec &type) {
631   CHECK(!symbol_);
632   type_ = &type;
633 }
634 } // namespace Fortran::semantics
635