1 //===-- lib/Semantics/mod-file.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 "mod-file.h"
10 #include "resolve-names.h"
11 #include "flang/Common/restorer.h"
12 #include "flang/Evaluate/tools.h"
13 #include "flang/Parser/message.h"
14 #include "flang/Parser/parsing.h"
15 #include "flang/Parser/unparse.h"
16 #include "flang/Semantics/scope.h"
17 #include "flang/Semantics/semantics.h"
18 #include "flang/Semantics/symbol.h"
19 #include "flang/Semantics/tools.h"
20 #include "llvm/Support/FileSystem.h"
21 #include "llvm/Support/MemoryBuffer.h"
22 #include "llvm/Support/raw_ostream.h"
23 #include <algorithm>
24 #include <fstream>
25 #include <set>
26 #include <string_view>
27 #include <vector>
28 
29 namespace Fortran::semantics {
30 
31 using namespace parser::literals;
32 
33 // The first line of a file that identifies it as a .mod file.
34 // The first three bytes are a Unicode byte order mark that ensures
35 // that the module file is decoded as UTF-8 even if source files
36 // are using another encoding.
37 struct ModHeader {
38   static constexpr const char bom[3 + 1]{"\xef\xbb\xbf"};
39   static constexpr int magicLen{13};
40   static constexpr int sumLen{16};
41   static constexpr const char magic[magicLen + 1]{"!mod$ v1 sum:"};
42   static constexpr char terminator{'\n'};
43   static constexpr int len{magicLen + 1 + sumLen};
44 };
45 
46 static std::optional<SourceName> GetSubmoduleParent(const parser::Program &);
47 static void CollectSymbols(const Scope &, SymbolVector &, SymbolVector &);
48 static void PutPassName(llvm::raw_ostream &, const std::optional<SourceName> &);
49 static void PutInit(llvm::raw_ostream &, const Symbol &, const MaybeExpr &,
50     const parser::Expr *);
51 static void PutInit(llvm::raw_ostream &, const MaybeIntExpr &);
52 static void PutBound(llvm::raw_ostream &, const Bound &);
53 static void PutShapeSpec(llvm::raw_ostream &, const ShapeSpec &);
54 static void PutShape(
55     llvm::raw_ostream &, const ArraySpec &, char open, char close);
56 llvm::raw_ostream &PutAttrs(llvm::raw_ostream &, Attrs,
57     const std::string * = nullptr, std::string before = ","s,
58     std::string after = ""s);
59 
60 static llvm::raw_ostream &PutAttr(llvm::raw_ostream &, Attr);
61 static llvm::raw_ostream &PutType(llvm::raw_ostream &, const DeclTypeSpec &);
62 static llvm::raw_ostream &PutLower(llvm::raw_ostream &, const std::string &);
63 static std::error_code WriteFile(
64     const std::string &, const std::string &, bool = true);
65 static bool FileContentsMatch(
66     const std::string &, const std::string &, const std::string &);
67 static std::string CheckSum(const std::string_view &);
68 
69 // Collect symbols needed for a subprogram interface
70 class SubprogramSymbolCollector {
71 public:
SubprogramSymbolCollector(const Symbol & symbol,const Scope & scope)72   SubprogramSymbolCollector(const Symbol &symbol, const Scope &scope)
73       : symbol_{symbol}, scope_{scope} {}
symbols() const74   const SymbolVector &symbols() const { return need_; }
imports() const75   const std::set<SourceName> &imports() const { return imports_; }
76   void Collect();
77 
78 private:
79   const Symbol &symbol_;
80   const Scope &scope_;
81   bool isInterface_{false};
82   SymbolVector need_; // symbols that are needed
83   UnorderedSymbolSet needSet_; // symbols already in need_
84   UnorderedSymbolSet useSet_; // use-associations that might be needed
85   std::set<SourceName> imports_; // imports from host that are needed
86 
87   void DoSymbol(const Symbol &);
88   void DoSymbol(const SourceName &, const Symbol &);
89   void DoType(const DeclTypeSpec *);
90   void DoBound(const Bound &);
91   void DoParamValue(const ParamValue &);
92   bool NeedImport(const SourceName &, const Symbol &);
93 
DoExpr(evaluate::Expr<T> expr)94   template <typename T> void DoExpr(evaluate::Expr<T> expr) {
95     for (const Symbol &symbol : evaluate::CollectSymbols(expr)) {
96       DoSymbol(symbol);
97     }
98   }
99 };
100 
WriteAll()101 bool ModFileWriter::WriteAll() {
102   // this flag affects character literals: force it to be consistent
103   auto restorer{
104       common::ScopedSet(parser::useHexadecimalEscapeSequences, false)};
105   WriteAll(context_.globalScope());
106   return !context_.AnyFatalError();
107 }
108 
WriteAll(const Scope & scope)109 void ModFileWriter::WriteAll(const Scope &scope) {
110   for (const auto &child : scope.children()) {
111     WriteOne(child);
112   }
113 }
114 
WriteOne(const Scope & scope)115 void ModFileWriter::WriteOne(const Scope &scope) {
116   if (scope.kind() == Scope::Kind::Module) {
117     auto *symbol{scope.symbol()};
118     if (!symbol->test(Symbol::Flag::ModFile)) {
119       Write(*symbol);
120     }
121     WriteAll(scope); // write out submodules
122   }
123 }
124 
125 // Construct the name of a module file. Non-empty ancestorName means submodule.
ModFileName(const SourceName & name,const std::string & ancestorName,const std::string & suffix)126 static std::string ModFileName(const SourceName &name,
127     const std::string &ancestorName, const std::string &suffix) {
128   std::string result{name.ToString() + suffix};
129   return ancestorName.empty() ? result : ancestorName + '-' + result;
130 }
131 
132 // Write the module file for symbol, which must be a module or submodule.
Write(const Symbol & symbol)133 void ModFileWriter::Write(const Symbol &symbol) {
134   auto *ancestor{symbol.get<ModuleDetails>().ancestor()};
135   auto ancestorName{ancestor ? ancestor->GetName().value().ToString() : ""s};
136   auto path{context_.moduleDirectory() + '/' +
137       ModFileName(symbol.name(), ancestorName, context_.moduleFileSuffix())};
138   PutSymbols(DEREF(symbol.scope()));
139   if (std::error_code error{
140           WriteFile(path, GetAsString(symbol), context_.debugModuleWriter())}) {
141     context_.Say(
142         symbol.name(), "Error writing %s: %s"_err_en_US, path, error.message());
143   }
144 }
145 
146 // Return the entire body of the module file
147 // and clear saved uses, decls, and contains.
GetAsString(const Symbol & symbol)148 std::string ModFileWriter::GetAsString(const Symbol &symbol) {
149   std::string buf;
150   llvm::raw_string_ostream all{buf};
151   auto &details{symbol.get<ModuleDetails>()};
152   if (!details.isSubmodule()) {
153     all << "module " << symbol.name();
154   } else {
155     auto *parent{details.parent()->symbol()};
156     auto *ancestor{details.ancestor()->symbol()};
157     all << "submodule(" << ancestor->name();
158     if (parent != ancestor) {
159       all << ':' << parent->name();
160     }
161     all << ") " << symbol.name();
162   }
163   all << '\n' << uses_.str();
164   uses_.str().clear();
165   all << useExtraAttrs_.str();
166   useExtraAttrs_.str().clear();
167   all << decls_.str();
168   decls_.str().clear();
169   auto str{contains_.str()};
170   contains_.str().clear();
171   if (!str.empty()) {
172     all << "contains\n" << str;
173   }
174   all << "end\n";
175   return all.str();
176 }
177 
178 // Put out the visible symbols from scope.
PutSymbols(const Scope & scope)179 void ModFileWriter::PutSymbols(const Scope &scope) {
180   SymbolVector sorted;
181   SymbolVector uses;
182   CollectSymbols(scope, sorted, uses);
183   std::string buf; // stuff after CONTAINS in derived type
184   llvm::raw_string_ostream typeBindings{buf};
185   for (const Symbol &symbol : sorted) {
186     if (!symbol.test(Symbol::Flag::CompilerCreated)) {
187       PutSymbol(typeBindings, symbol);
188     }
189   }
190   for (const Symbol &symbol : uses) {
191     PutUse(symbol);
192   }
193   for (const auto &set : scope.equivalenceSets()) {
194     if (!set.empty() &&
195         !set.front().symbol.test(Symbol::Flag::CompilerCreated)) {
196       char punctuation{'('};
197       decls_ << "equivalence";
198       for (const auto &object : set) {
199         decls_ << punctuation << object.AsFortran();
200         punctuation = ',';
201       }
202       decls_ << ")\n";
203     }
204   }
205   CHECK(typeBindings.str().empty());
206 }
207 
208 // Emit components in order
PutComponents(const Symbol & typeSymbol)209 bool ModFileWriter::PutComponents(const Symbol &typeSymbol) {
210   const auto &scope{DEREF(typeSymbol.scope())};
211   std::string buf; // stuff after CONTAINS in derived type
212   llvm::raw_string_ostream typeBindings{buf};
213   UnorderedSymbolSet emitted;
214   SymbolVector symbols{scope.GetSymbols()};
215   // Emit type parameters first
216   for (const Symbol &symbol : symbols) {
217     if (symbol.has<TypeParamDetails>()) {
218       PutSymbol(typeBindings, symbol);
219       emitted.emplace(symbol);
220     }
221   }
222   // Emit components in component order.
223   const auto &details{typeSymbol.get<DerivedTypeDetails>()};
224   for (SourceName name : details.componentNames()) {
225     auto iter{scope.find(name)};
226     if (iter != scope.end()) {
227       const Symbol &component{*iter->second};
228       if (!component.test(Symbol::Flag::ParentComp)) {
229         PutSymbol(typeBindings, component);
230       }
231       emitted.emplace(component);
232     }
233   }
234   // Emit remaining symbols from the type's scope
235   for (const Symbol &symbol : symbols) {
236     if (emitted.find(symbol) == emitted.end()) {
237       PutSymbol(typeBindings, symbol);
238     }
239   }
240   if (auto str{typeBindings.str()}; !str.empty()) {
241     CHECK(scope.IsDerivedType());
242     decls_ << "contains\n" << str;
243     return true;
244   } else {
245     return false;
246   }
247 }
248 
PutGenericName(llvm::raw_ostream & os,const Symbol & symbol)249 static llvm::raw_ostream &PutGenericName(
250     llvm::raw_ostream &os, const Symbol &symbol) {
251   if (IsGenericDefinedOp(symbol)) {
252     return os << "operator(" << symbol.name() << ')';
253   } else {
254     return os << symbol.name();
255   }
256 }
257 
258 // Emit a symbol to decls_, except for bindings in a derived type (type-bound
259 // procedures, type-bound generics, final procedures) which go to typeBindings.
PutSymbol(llvm::raw_ostream & typeBindings,const Symbol & symbol)260 void ModFileWriter::PutSymbol(
261     llvm::raw_ostream &typeBindings, const Symbol &symbol) {
262   common::visit(
263       common::visitors{
264           [&](const ModuleDetails &) { /* should be current module */ },
265           [&](const DerivedTypeDetails &) { PutDerivedType(symbol); },
266           [&](const SubprogramDetails &) { PutSubprogram(symbol); },
267           [&](const GenericDetails &x) {
268             if (symbol.owner().IsDerivedType()) {
269               // generic binding
270               for (const Symbol &proc : x.specificProcs()) {
271                 PutGenericName(typeBindings << "generic::", symbol)
272                     << "=>" << proc.name() << '\n';
273               }
274             } else {
275               PutGeneric(symbol);
276               if (x.specific()) {
277                 PutSymbol(typeBindings, *x.specific());
278               }
279               if (x.derivedType()) {
280                 PutSymbol(typeBindings, *x.derivedType());
281               }
282             }
283           },
284           [&](const UseDetails &) { PutUse(symbol); },
285           [](const UseErrorDetails &) {},
286           [&](const ProcBindingDetails &x) {
287             bool deferred{symbol.attrs().test(Attr::DEFERRED)};
288             typeBindings << "procedure";
289             if (deferred) {
290               typeBindings << '(' << x.symbol().name() << ')';
291             }
292             PutPassName(typeBindings, x.passName());
293             auto attrs{symbol.attrs()};
294             if (x.passName()) {
295               attrs.reset(Attr::PASS);
296             }
297             PutAttrs(typeBindings, attrs);
298             typeBindings << "::" << symbol.name();
299             if (!deferred && x.symbol().name() != symbol.name()) {
300               typeBindings << "=>" << x.symbol().name();
301             }
302             typeBindings << '\n';
303           },
304           [&](const NamelistDetails &x) {
305             decls_ << "namelist/" << symbol.name();
306             char sep{'/'};
307             for (const Symbol &object : x.objects()) {
308               decls_ << sep << object.name();
309               sep = ',';
310             }
311             decls_ << '\n';
312           },
313           [&](const CommonBlockDetails &x) {
314             decls_ << "common/" << symbol.name();
315             char sep = '/';
316             for (const auto &object : x.objects()) {
317               decls_ << sep << object->name();
318               sep = ',';
319             }
320             decls_ << '\n';
321             if (symbol.attrs().test(Attr::BIND_C)) {
322               PutAttrs(decls_, symbol.attrs(), x.bindName(), ""s);
323               decls_ << "::/" << symbol.name() << "/\n";
324             }
325           },
326           [](const HostAssocDetails &) {},
327           [](const MiscDetails &) {},
328           [&](const auto &) {
329             PutEntity(decls_, symbol);
330             if (symbol.test(Symbol::Flag::OmpThreadprivate)) {
331               decls_ << "!$omp threadprivate(" << symbol.name() << ")\n";
332             }
333           },
334       },
335       symbol.details());
336 }
337 
PutDerivedType(const Symbol & typeSymbol,const Scope * scope)338 void ModFileWriter::PutDerivedType(
339     const Symbol &typeSymbol, const Scope *scope) {
340   auto &details{typeSymbol.get<DerivedTypeDetails>()};
341   if (details.isDECStructure()) {
342     PutDECStructure(typeSymbol, scope);
343     return;
344   }
345   PutAttrs(decls_ << "type", typeSymbol.attrs());
346   if (const DerivedTypeSpec * extends{typeSymbol.GetParentTypeSpec()}) {
347     decls_ << ",extends(" << extends->name() << ')';
348   }
349   decls_ << "::" << typeSymbol.name();
350   if (!details.paramNames().empty()) {
351     char sep{'('};
352     for (const auto &name : details.paramNames()) {
353       decls_ << sep << name;
354       sep = ',';
355     }
356     decls_ << ')';
357   }
358   decls_ << '\n';
359   if (details.sequence()) {
360     decls_ << "sequence\n";
361   }
362   bool contains{PutComponents(typeSymbol)};
363   if (!details.finals().empty()) {
364     const char *sep{contains ? "final::" : "contains\nfinal::"};
365     for (const auto &pair : details.finals()) {
366       decls_ << sep << pair.second->name();
367       sep = ",";
368     }
369     if (*sep == ',') {
370       decls_ << '\n';
371     }
372   }
373   decls_ << "end type\n";
374 }
375 
PutDECStructure(const Symbol & typeSymbol,const Scope * scope)376 void ModFileWriter::PutDECStructure(
377     const Symbol &typeSymbol, const Scope *scope) {
378   if (emittedDECStructures_.find(typeSymbol) != emittedDECStructures_.end()) {
379     return;
380   }
381   if (!scope && context_.IsTempName(typeSymbol.name().ToString())) {
382     return; // defer until used
383   }
384   emittedDECStructures_.insert(typeSymbol);
385   decls_ << "structure ";
386   if (!context_.IsTempName(typeSymbol.name().ToString())) {
387     decls_ << typeSymbol.name();
388   }
389   if (scope && scope->kind() == Scope::Kind::DerivedType) {
390     // Nested STRUCTURE: emit entity declarations right now
391     // on the STRUCTURE statement.
392     bool any{false};
393     for (const auto &ref : scope->GetSymbols()) {
394       const auto *object{ref->detailsIf<ObjectEntityDetails>()};
395       if (object && object->type() &&
396           object->type()->category() == DeclTypeSpec::TypeDerived &&
397           &object->type()->derivedTypeSpec().typeSymbol() == &typeSymbol) {
398         if (any) {
399           decls_ << ',';
400         } else {
401           any = true;
402         }
403         decls_ << ref->name();
404         PutShape(decls_, object->shape(), '(', ')');
405         PutInit(decls_, *ref, object->init(), nullptr);
406         emittedDECFields_.insert(*ref);
407       } else if (any) {
408         break; // any later use of this structure will use RECORD/str/
409       }
410     }
411   }
412   decls_ << '\n';
413   PutComponents(typeSymbol);
414   decls_ << "end structure\n";
415 }
416 
417 // Attributes that may be in a subprogram prefix
418 static const Attrs subprogramPrefixAttrs{Attr::ELEMENTAL, Attr::IMPURE,
419     Attr::MODULE, Attr::NON_RECURSIVE, Attr::PURE, Attr::RECURSIVE};
420 
PutSubprogram(const Symbol & symbol)421 void ModFileWriter::PutSubprogram(const Symbol &symbol) {
422   auto &details{symbol.get<SubprogramDetails>()};
423   if (const Symbol * interface{details.moduleInterface()}) {
424     PutSubprogram(*interface);
425   }
426   auto attrs{symbol.attrs()};
427   Attrs bindAttrs{};
428   if (attrs.test(Attr::BIND_C)) {
429     // bind(c) is a suffix, not prefix
430     bindAttrs.set(Attr::BIND_C, true);
431     attrs.set(Attr::BIND_C, false);
432   }
433   bool isAbstract{attrs.test(Attr::ABSTRACT)};
434   if (isAbstract) {
435     attrs.set(Attr::ABSTRACT, false);
436   }
437   Attrs prefixAttrs{subprogramPrefixAttrs & attrs};
438   // emit any non-prefix attributes in an attribute statement
439   attrs &= ~subprogramPrefixAttrs;
440   std::string ssBuf;
441   llvm::raw_string_ostream ss{ssBuf};
442   PutAttrs(ss, attrs);
443   if (!ss.str().empty()) {
444     decls_ << ss.str().substr(1) << "::" << symbol.name() << '\n';
445   }
446   bool isInterface{details.isInterface()};
447   llvm::raw_ostream &os{isInterface ? decls_ : contains_};
448   if (isInterface) {
449     os << (isAbstract ? "abstract " : "") << "interface\n";
450   }
451   PutAttrs(os, prefixAttrs, nullptr, ""s, " "s);
452   os << (details.isFunction() ? "function " : "subroutine ");
453   os << symbol.name() << '(';
454   int n = 0;
455   for (const auto &dummy : details.dummyArgs()) {
456     if (n++ > 0) {
457       os << ',';
458     }
459     if (dummy) {
460       os << dummy->name();
461     } else {
462       os << "*";
463     }
464   }
465   os << ')';
466   PutAttrs(os, bindAttrs, details.bindName(), " "s, ""s);
467   if (details.isFunction()) {
468     const Symbol &result{details.result()};
469     if (result.name() != symbol.name()) {
470       os << " result(" << result.name() << ')';
471     }
472   }
473   os << '\n';
474 
475   // walk symbols, collect ones needed for interface
476   const Scope &scope{
477       details.entryScope() ? *details.entryScope() : DEREF(symbol.scope())};
478   SubprogramSymbolCollector collector{symbol, scope};
479   collector.Collect();
480   std::string typeBindingsBuf;
481   llvm::raw_string_ostream typeBindings{typeBindingsBuf};
482   ModFileWriter writer{context_};
483   for (const Symbol &need : collector.symbols()) {
484     writer.PutSymbol(typeBindings, need);
485   }
486   CHECK(typeBindings.str().empty());
487   os << writer.uses_.str();
488   for (const SourceName &import : collector.imports()) {
489     decls_ << "import::" << import << "\n";
490   }
491   os << writer.decls_.str();
492   os << "end\n";
493   if (isInterface) {
494     os << "end interface\n";
495   }
496 }
497 
IsIntrinsicOp(const Symbol & symbol)498 static bool IsIntrinsicOp(const Symbol &symbol) {
499   if (const auto *details{symbol.GetUltimate().detailsIf<GenericDetails>()}) {
500     return details->kind().IsIntrinsicOperator();
501   } else {
502     return false;
503   }
504 }
505 
PutGeneric(const Symbol & symbol)506 void ModFileWriter::PutGeneric(const Symbol &symbol) {
507   const auto &genericOwner{symbol.owner()};
508   auto &details{symbol.get<GenericDetails>()};
509   PutGenericName(decls_ << "interface ", symbol) << '\n';
510   for (const Symbol &specific : details.specificProcs()) {
511     if (specific.owner() == genericOwner) {
512       decls_ << "procedure::" << specific.name() << '\n';
513     }
514   }
515   decls_ << "end interface\n";
516   if (symbol.attrs().test(Attr::PRIVATE)) {
517     PutGenericName(decls_ << "private::", symbol) << '\n';
518   }
519 }
520 
PutUse(const Symbol & symbol)521 void ModFileWriter::PutUse(const Symbol &symbol) {
522   auto &details{symbol.get<UseDetails>()};
523   auto &use{details.symbol()};
524   const Symbol &module{GetUsedModule(details)};
525   if (use.owner().parent().IsIntrinsicModules()) {
526     uses_ << "use,intrinsic::";
527   } else {
528     uses_ << "use ";
529   }
530   uses_ << module.name() << ",only:";
531   PutGenericName(uses_, symbol);
532   // Can have intrinsic op with different local-name and use-name
533   // (e.g. `operator(<)` and `operator(.lt.)`) but rename is not allowed
534   if (!IsIntrinsicOp(symbol) && use.name() != symbol.name()) {
535     PutGenericName(uses_ << "=>", use);
536   }
537   uses_ << '\n';
538   PutUseExtraAttr(Attr::VOLATILE, symbol, use);
539   PutUseExtraAttr(Attr::ASYNCHRONOUS, symbol, use);
540   if (symbol.attrs().test(Attr::PRIVATE)) {
541     PutGenericName(useExtraAttrs_ << "private::", symbol) << '\n';
542   }
543 }
544 
545 // We have "USE local => use" in this module. If attr was added locally
546 // (i.e. on local but not on use), also write it out in the mod file.
PutUseExtraAttr(Attr attr,const Symbol & local,const Symbol & use)547 void ModFileWriter::PutUseExtraAttr(
548     Attr attr, const Symbol &local, const Symbol &use) {
549   if (local.attrs().test(attr) && !use.attrs().test(attr)) {
550     PutAttr(useExtraAttrs_, attr) << "::";
551     useExtraAttrs_ << local.name() << '\n';
552   }
553 }
554 
555 // When a generic interface has the same name as a derived type
556 // in the same scope, the generic shadows the derived type.
557 // If the derived type were declared first, emit the generic
558 // interface at the position of derived type's declaration.
559 // (ReplaceName() is not used for this purpose because doing so
560 // would confusingly position error messages pertaining to the generic
561 // interface upon the derived type's declaration.)
NameInModuleFile(const Symbol & symbol)562 static inline SourceName NameInModuleFile(const Symbol &symbol) {
563   if (const auto *generic{symbol.detailsIf<GenericDetails>()}) {
564     if (const auto *derivedTypeOverload{generic->derivedType()}) {
565       if (derivedTypeOverload->name().begin() < symbol.name().begin()) {
566         return derivedTypeOverload->name();
567       }
568     }
569   } else if (const auto *use{symbol.detailsIf<UseDetails>()}) {
570     if (use->symbol().attrs().test(Attr::PRIVATE)) {
571       // Avoid the use in sorting of names created to access private
572       // specific procedures as a result of generic resolution;
573       // they're not in the cooked source.
574       return use->symbol().name();
575     }
576   }
577   return symbol.name();
578 }
579 
580 // Collect the symbols of this scope sorted by their original order, not name.
581 // Namelists are an exception: they are sorted after other symbols.
CollectSymbols(const Scope & scope,SymbolVector & sorted,SymbolVector & uses)582 void CollectSymbols(
583     const Scope &scope, SymbolVector &sorted, SymbolVector &uses) {
584   SymbolVector namelist;
585   std::size_t commonSize{scope.commonBlocks().size()};
586   auto symbols{scope.GetSymbols()};
587   sorted.reserve(symbols.size() + commonSize);
588   for (SymbolRef symbol : symbols) {
589     if (!symbol->test(Symbol::Flag::ParentComp)) {
590       if (symbol->has<NamelistDetails>()) {
591         namelist.push_back(symbol);
592       } else {
593         sorted.push_back(symbol);
594       }
595       if (const auto *details{symbol->detailsIf<GenericDetails>()}) {
596         uses.insert(uses.end(), details->uses().begin(), details->uses().end());
597       }
598     }
599   }
600   // Sort most symbols by name: use of Symbol::ReplaceName ensures the source
601   // location of a symbol's name is the first "real" use.
602   std::sort(sorted.begin(), sorted.end(), [](SymbolRef x, SymbolRef y) {
603     return NameInModuleFile(x).begin() < NameInModuleFile(y).begin();
604   });
605   sorted.insert(sorted.end(), namelist.begin(), namelist.end());
606   for (const auto &pair : scope.commonBlocks()) {
607     sorted.push_back(*pair.second);
608   }
609   std::sort(
610       sorted.end() - commonSize, sorted.end(), SymbolSourcePositionCompare{});
611 }
612 
PutEntity(llvm::raw_ostream & os,const Symbol & symbol)613 void ModFileWriter::PutEntity(llvm::raw_ostream &os, const Symbol &symbol) {
614   common::visit(
615       common::visitors{
616           [&](const ObjectEntityDetails &) { PutObjectEntity(os, symbol); },
617           [&](const ProcEntityDetails &) { PutProcEntity(os, symbol); },
618           [&](const TypeParamDetails &) { PutTypeParam(os, symbol); },
619           [&](const auto &) {
620             common::die("PutEntity: unexpected details: %s",
621                 DetailsToString(symbol.details()).c_str());
622           },
623       },
624       symbol.details());
625 }
626 
PutShapeSpec(llvm::raw_ostream & os,const ShapeSpec & x)627 void PutShapeSpec(llvm::raw_ostream &os, const ShapeSpec &x) {
628   if (x.lbound().isStar()) {
629     CHECK(x.ubound().isStar());
630     os << ".."; // assumed rank
631   } else {
632     if (!x.lbound().isColon()) {
633       PutBound(os, x.lbound());
634     }
635     os << ':';
636     if (!x.ubound().isColon()) {
637       PutBound(os, x.ubound());
638     }
639   }
640 }
PutShape(llvm::raw_ostream & os,const ArraySpec & shape,char open,char close)641 void PutShape(
642     llvm::raw_ostream &os, const ArraySpec &shape, char open, char close) {
643   if (!shape.empty()) {
644     os << open;
645     bool first{true};
646     for (const auto &shapeSpec : shape) {
647       if (first) {
648         first = false;
649       } else {
650         os << ',';
651       }
652       PutShapeSpec(os, shapeSpec);
653     }
654     os << close;
655   }
656 }
657 
PutObjectEntity(llvm::raw_ostream & os,const Symbol & symbol)658 void ModFileWriter::PutObjectEntity(
659     llvm::raw_ostream &os, const Symbol &symbol) {
660   auto &details{symbol.get<ObjectEntityDetails>()};
661   if (details.type() &&
662       details.type()->category() == DeclTypeSpec::TypeDerived) {
663     const Symbol &typeSymbol{details.type()->derivedTypeSpec().typeSymbol()};
664     if (typeSymbol.get<DerivedTypeDetails>().isDECStructure()) {
665       PutDerivedType(typeSymbol, &symbol.owner());
666       if (emittedDECFields_.find(symbol) != emittedDECFields_.end()) {
667         return; // symbol was emitted on STRUCTURE statement
668       }
669     }
670   }
671   PutEntity(
672       os, symbol, [&]() { PutType(os, DEREF(symbol.GetType())); },
673       symbol.attrs());
674   PutShape(os, details.shape(), '(', ')');
675   PutShape(os, details.coshape(), '[', ']');
676   PutInit(os, symbol, details.init(), details.unanalyzedPDTComponentInit());
677   os << '\n';
678 }
679 
PutProcEntity(llvm::raw_ostream & os,const Symbol & symbol)680 void ModFileWriter::PutProcEntity(llvm::raw_ostream &os, const Symbol &symbol) {
681   if (symbol.attrs().test(Attr::INTRINSIC)) {
682     os << "intrinsic::" << symbol.name() << '\n';
683     if (symbol.attrs().test(Attr::PRIVATE)) {
684       os << "private::" << symbol.name() << '\n';
685     }
686     return;
687   }
688   const auto &details{symbol.get<ProcEntityDetails>()};
689   const ProcInterface &interface{details.interface()};
690   Attrs attrs{symbol.attrs()};
691   if (details.passName()) {
692     attrs.reset(Attr::PASS);
693   }
694   PutEntity(
695       os, symbol,
696       [&]() {
697         os << "procedure(";
698         if (interface.symbol()) {
699           os << interface.symbol()->name();
700         } else if (interface.type()) {
701           PutType(os, *interface.type());
702         }
703         os << ')';
704         PutPassName(os, details.passName());
705       },
706       attrs);
707   os << '\n';
708 }
709 
PutPassName(llvm::raw_ostream & os,const std::optional<SourceName> & passName)710 void PutPassName(
711     llvm::raw_ostream &os, const std::optional<SourceName> &passName) {
712   if (passName) {
713     os << ",pass(" << *passName << ')';
714   }
715 }
716 
PutTypeParam(llvm::raw_ostream & os,const Symbol & symbol)717 void ModFileWriter::PutTypeParam(llvm::raw_ostream &os, const Symbol &symbol) {
718   auto &details{symbol.get<TypeParamDetails>()};
719   PutEntity(
720       os, symbol,
721       [&]() {
722         PutType(os, DEREF(symbol.GetType()));
723         PutLower(os << ',', common::EnumToString(details.attr()));
724       },
725       symbol.attrs());
726   PutInit(os, details.init());
727   os << '\n';
728 }
729 
PutInit(llvm::raw_ostream & os,const Symbol & symbol,const MaybeExpr & init,const parser::Expr * unanalyzed)730 void PutInit(llvm::raw_ostream &os, const Symbol &symbol, const MaybeExpr &init,
731     const parser::Expr *unanalyzed) {
732   if (symbol.attrs().test(Attr::PARAMETER) || symbol.owner().IsDerivedType()) {
733     const char *assign{symbol.attrs().test(Attr::POINTER) ? "=>" : "="};
734     if (unanalyzed) {
735       parser::Unparse(os << assign, *unanalyzed);
736     } else if (init) {
737       init->AsFortran(os << assign);
738     }
739   }
740 }
741 
PutInit(llvm::raw_ostream & os,const MaybeIntExpr & init)742 void PutInit(llvm::raw_ostream &os, const MaybeIntExpr &init) {
743   if (init) {
744     init->AsFortran(os << '=');
745   }
746 }
747 
PutBound(llvm::raw_ostream & os,const Bound & x)748 void PutBound(llvm::raw_ostream &os, const Bound &x) {
749   if (x.isStar()) {
750     os << '*';
751   } else if (x.isColon()) {
752     os << ':';
753   } else {
754     x.GetExplicit()->AsFortran(os);
755   }
756 }
757 
758 // Write an entity (object or procedure) declaration.
759 // writeType is called to write out the type.
PutEntity(llvm::raw_ostream & os,const Symbol & symbol,std::function<void ()> writeType,Attrs attrs)760 void ModFileWriter::PutEntity(llvm::raw_ostream &os, const Symbol &symbol,
761     std::function<void()> writeType, Attrs attrs) {
762   writeType();
763   PutAttrs(os, attrs, symbol.GetBindName());
764   if (symbol.owner().kind() == Scope::Kind::DerivedType &&
765       context_.IsTempName(symbol.name().ToString())) {
766     os << "::%FILL";
767   } else {
768     os << "::" << symbol.name();
769   }
770 }
771 
772 // Put out each attribute to os, surrounded by `before` and `after` and
773 // mapped to lower case.
PutAttrs(llvm::raw_ostream & os,Attrs attrs,const std::string * bindName,std::string before,std::string after)774 llvm::raw_ostream &PutAttrs(llvm::raw_ostream &os, Attrs attrs,
775     const std::string *bindName, std::string before, std::string after) {
776   attrs.set(Attr::PUBLIC, false); // no need to write PUBLIC
777   attrs.set(Attr::EXTERNAL, false); // no need to write EXTERNAL
778   if (bindName) {
779     os << before << "bind(c, name=\"" << *bindName << "\")" << after;
780     attrs.set(Attr::BIND_C, false);
781   }
782   for (std::size_t i{0}; i < Attr_enumSize; ++i) {
783     Attr attr{static_cast<Attr>(i)};
784     if (attrs.test(attr)) {
785       PutAttr(os << before, attr) << after;
786     }
787   }
788   return os;
789 }
790 
PutAttr(llvm::raw_ostream & os,Attr attr)791 llvm::raw_ostream &PutAttr(llvm::raw_ostream &os, Attr attr) {
792   return PutLower(os, AttrToString(attr));
793 }
794 
PutType(llvm::raw_ostream & os,const DeclTypeSpec & type)795 llvm::raw_ostream &PutType(llvm::raw_ostream &os, const DeclTypeSpec &type) {
796   return PutLower(os, type.AsFortran());
797 }
798 
PutLower(llvm::raw_ostream & os,const std::string & str)799 llvm::raw_ostream &PutLower(llvm::raw_ostream &os, const std::string &str) {
800   for (char c : str) {
801     os << parser::ToLowerCaseLetter(c);
802   }
803   return os;
804 }
805 
806 struct Temp {
TempFortran::semantics::Temp807   Temp(int fd, std::string path) : fd{fd}, path{path} {}
TempFortran::semantics::Temp808   Temp(Temp &&t) : fd{std::exchange(t.fd, -1)}, path{std::move(t.path)} {}
~TempFortran::semantics::Temp809   ~Temp() {
810     if (fd >= 0) {
811       llvm::sys::fs::file_t native{llvm::sys::fs::convertFDToNativeFile(fd)};
812       llvm::sys::fs::closeFile(native);
813       llvm::sys::fs::remove(path.c_str());
814     }
815   }
816   int fd;
817   std::string path;
818 };
819 
820 // Create a temp file in the same directory and with the same suffix as path.
821 // Return an open file descriptor and its path.
MkTemp(const std::string & path)822 static llvm::ErrorOr<Temp> MkTemp(const std::string &path) {
823   auto length{path.length()};
824   auto dot{path.find_last_of("./")};
825   std::string suffix{
826       dot < length && path[dot] == '.' ? path.substr(dot + 1) : ""};
827   CHECK(length > suffix.length() &&
828       path.substr(length - suffix.length()) == suffix);
829   auto prefix{path.substr(0, length - suffix.length())};
830   int fd;
831   llvm::SmallString<16> tempPath;
832   if (std::error_code err{llvm::sys::fs::createUniqueFile(
833           prefix + "%%%%%%" + suffix, fd, tempPath)}) {
834     return err;
835   }
836   return Temp{fd, tempPath.c_str()};
837 }
838 
839 // Write the module file at path, prepending header. If an error occurs,
840 // return errno, otherwise 0.
WriteFile(const std::string & path,const std::string & contents,bool debug)841 static std::error_code WriteFile(
842     const std::string &path, const std::string &contents, bool debug) {
843   auto header{std::string{ModHeader::bom} + ModHeader::magic +
844       CheckSum(contents) + ModHeader::terminator};
845   if (debug) {
846     llvm::dbgs() << "Processing module " << path << ": ";
847   }
848   if (FileContentsMatch(path, header, contents)) {
849     if (debug) {
850       llvm::dbgs() << "module unchanged, not writing\n";
851     }
852     return {};
853   }
854   llvm::ErrorOr<Temp> temp{MkTemp(path)};
855   if (!temp) {
856     return temp.getError();
857   }
858   llvm::raw_fd_ostream writer(temp->fd, /*shouldClose=*/false);
859   writer << header;
860   writer << contents;
861   writer.flush();
862   if (writer.has_error()) {
863     return writer.error();
864   }
865   if (debug) {
866     llvm::dbgs() << "module written\n";
867   }
868   return llvm::sys::fs::rename(temp->path, path);
869 }
870 
871 // Return true if the stream matches what we would write for the mod file.
FileContentsMatch(const std::string & path,const std::string & header,const std::string & contents)872 static bool FileContentsMatch(const std::string &path,
873     const std::string &header, const std::string &contents) {
874   std::size_t hsize{header.size()};
875   std::size_t csize{contents.size()};
876   auto buf_or{llvm::MemoryBuffer::getFile(path)};
877   if (!buf_or) {
878     return false;
879   }
880   auto buf = std::move(buf_or.get());
881   if (buf->getBufferSize() != hsize + csize) {
882     return false;
883   }
884   if (!std::equal(header.begin(), header.end(), buf->getBufferStart(),
885           buf->getBufferStart() + hsize)) {
886     return false;
887   }
888 
889   return std::equal(contents.begin(), contents.end(),
890       buf->getBufferStart() + hsize, buf->getBufferEnd());
891 }
892 
893 // Compute a simple hash of the contents of a module file and
894 // return it as a string of hex digits.
895 // This uses the Fowler-Noll-Vo hash function.
CheckSum(const std::string_view & contents)896 static std::string CheckSum(const std::string_view &contents) {
897   std::uint64_t hash{0xcbf29ce484222325ull};
898   for (char c : contents) {
899     hash ^= c & 0xff;
900     hash *= 0x100000001b3;
901   }
902   static const char *digits = "0123456789abcdef";
903   std::string result(ModHeader::sumLen, '0');
904   for (size_t i{ModHeader::sumLen}; hash != 0; hash >>= 4) {
905     result[--i] = digits[hash & 0xf];
906   }
907   return result;
908 }
909 
VerifyHeader(llvm::ArrayRef<char> content)910 static bool VerifyHeader(llvm::ArrayRef<char> content) {
911   std::string_view sv{content.data(), content.size()};
912   if (sv.substr(0, ModHeader::magicLen) != ModHeader::magic) {
913     return false;
914   }
915   std::string_view expectSum{sv.substr(ModHeader::magicLen, ModHeader::sumLen)};
916   std::string actualSum{CheckSum(sv.substr(ModHeader::len))};
917   return expectSum == actualSum;
918 }
919 
Read(const SourceName & name,std::optional<bool> isIntrinsic,Scope * ancestor,bool silent)920 Scope *ModFileReader::Read(const SourceName &name,
921     std::optional<bool> isIntrinsic, Scope *ancestor, bool silent) {
922   std::string ancestorName; // empty for module
923   Symbol *notAModule{nullptr};
924   bool fatalError{false};
925   if (ancestor) {
926     if (auto *scope{ancestor->FindSubmodule(name)}) {
927       return scope;
928     }
929     ancestorName = ancestor->GetName().value().ToString();
930   } else {
931     if (!isIntrinsic.value_or(false)) {
932       auto it{context_.globalScope().find(name)};
933       if (it != context_.globalScope().end()) {
934         Scope *scope{it->second->scope()};
935         if (scope->kind() == Scope::Kind::Module) {
936           return scope;
937         } else {
938           notAModule = scope->symbol();
939           // USE, NON_INTRINSIC global name isn't a module?
940           fatalError = isIntrinsic.has_value();
941         }
942       }
943     }
944     if (isIntrinsic.value_or(true)) {
945       auto it{context_.intrinsicModulesScope().find(name)};
946       if (it != context_.intrinsicModulesScope().end()) {
947         return it->second->scope();
948       }
949     }
950   }
951   parser::Parsing parsing{context_.allCookedSources()};
952   parser::Options options;
953   options.isModuleFile = true;
954   options.features.Enable(common::LanguageFeature::BackslashEscapes);
955   options.features.Enable(common::LanguageFeature::OpenMP);
956   if (!isIntrinsic.value_or(false) && !notAModule) {
957     // Scan non-intrinsic module directories
958     options.searchDirectories = context_.searchDirectories();
959     // If a directory is in both lists, the intrinsic module directory
960     // takes precedence.
961     for (const auto &dir : context_.intrinsicModuleDirectories()) {
962       std::remove(options.searchDirectories.begin(),
963           options.searchDirectories.end(), dir);
964     }
965     options.searchDirectories.insert(options.searchDirectories.begin(), "."s);
966   }
967   if (isIntrinsic.value_or(true)) {
968     for (const auto &dir : context_.intrinsicModuleDirectories()) {
969       options.searchDirectories.push_back(dir);
970     }
971   }
972   auto path{ModFileName(name, ancestorName, context_.moduleFileSuffix())};
973   const auto *sourceFile{fatalError ? nullptr : parsing.Prescan(path, options)};
974   if (fatalError || parsing.messages().AnyFatalError()) {
975     if (!silent) {
976       if (notAModule) {
977         // Module is not explicitly INTRINSIC, and there's already a global
978         // symbol of the same name that is not a module.
979         context_.SayWithDecl(
980             *notAModule, name, "'%s' is not a module"_err_en_US, name);
981       } else {
982         for (auto &msg : parsing.messages().messages()) {
983           std::string str{msg.ToString()};
984           Say(name, ancestorName,
985               parser::MessageFixedText{str.c_str(), str.size(), msg.severity()},
986               path);
987         }
988       }
989     }
990     return nullptr;
991   }
992   CHECK(sourceFile);
993   if (!VerifyHeader(sourceFile->content())) {
994     Say(name, ancestorName, "File has invalid checksum: %s"_warn_en_US,
995         sourceFile->path());
996     return nullptr;
997   }
998   llvm::raw_null_ostream NullStream;
999   parsing.Parse(NullStream);
1000   std::optional<parser::Program> &parsedProgram{parsing.parseTree()};
1001   if (!parsing.messages().empty() || !parsing.consumedWholeFile() ||
1002       !parsedProgram) {
1003     Say(name, ancestorName, "Module file is corrupt: %s"_err_en_US,
1004         sourceFile->path());
1005     return nullptr;
1006   }
1007   parser::Program &parseTree{context_.SaveParseTree(std::move(*parsedProgram))};
1008   Scope *parentScope; // the scope this module/submodule goes into
1009   if (!isIntrinsic.has_value()) {
1010     for (const auto &dir : context_.intrinsicModuleDirectories()) {
1011       if (sourceFile->path().size() > dir.size() &&
1012           sourceFile->path().find(dir) == 0) {
1013         isIntrinsic = true;
1014         break;
1015       }
1016     }
1017   }
1018   Scope &topScope{isIntrinsic.value_or(false) ? context_.intrinsicModulesScope()
1019                                               : context_.globalScope()};
1020   if (!ancestor) {
1021     parentScope = &topScope;
1022   } else if (std::optional<SourceName> parent{GetSubmoduleParent(parseTree)}) {
1023     parentScope = Read(*parent, false /*not intrinsic*/, ancestor, silent);
1024   } else {
1025     parentScope = ancestor;
1026   }
1027   auto pair{parentScope->try_emplace(name, UnknownDetails{})};
1028   if (!pair.second) {
1029     return nullptr;
1030   }
1031   // Process declarations from the module file
1032   Symbol &modSymbol{*pair.first->second};
1033   modSymbol.set(Symbol::Flag::ModFile);
1034   bool wasInModuleFile{context_.foldingContext().inModuleFile()};
1035   context_.foldingContext().set_inModuleFile(true);
1036   ResolveNames(context_, parseTree, topScope);
1037   context_.foldingContext().set_inModuleFile(wasInModuleFile);
1038   CHECK(modSymbol.has<ModuleDetails>());
1039   CHECK(modSymbol.test(Symbol::Flag::ModFile));
1040   if (isIntrinsic.value_or(false)) {
1041     modSymbol.attrs().set(Attr::INTRINSIC);
1042   }
1043   return modSymbol.scope();
1044 }
1045 
Say(const SourceName & name,const std::string & ancestor,parser::MessageFixedText && msg,const std::string & arg)1046 parser::Message &ModFileReader::Say(const SourceName &name,
1047     const std::string &ancestor, parser::MessageFixedText &&msg,
1048     const std::string &arg) {
1049   return context_.Say(name, "Cannot read module file for %s: %s"_err_en_US,
1050       parser::MessageFormattedText{ancestor.empty()
1051               ? "module '%s'"_en_US
1052               : "submodule '%s' of module '%s'"_en_US,
1053           name, ancestor}
1054           .MoveString(),
1055       parser::MessageFormattedText{std::move(msg), arg}.MoveString());
1056 }
1057 
1058 // program was read from a .mod file for a submodule; return the name of the
1059 // submodule's parent submodule, nullptr if none.
GetSubmoduleParent(const parser::Program & program)1060 static std::optional<SourceName> GetSubmoduleParent(
1061     const parser::Program &program) {
1062   CHECK(program.v.size() == 1);
1063   auto &unit{program.v.front()};
1064   auto &submod{std::get<common::Indirection<parser::Submodule>>(unit.u)};
1065   auto &stmt{
1066       std::get<parser::Statement<parser::SubmoduleStmt>>(submod.value().t)};
1067   auto &parentId{std::get<parser::ParentIdentifier>(stmt.statement.t)};
1068   if (auto &parent{std::get<std::optional<parser::Name>>(parentId.t)}) {
1069     return parent->source;
1070   } else {
1071     return std::nullopt;
1072   }
1073 }
1074 
Collect()1075 void SubprogramSymbolCollector::Collect() {
1076   const auto &details{symbol_.get<SubprogramDetails>()};
1077   isInterface_ = details.isInterface();
1078   for (const Symbol *dummyArg : details.dummyArgs()) {
1079     if (dummyArg) {
1080       DoSymbol(*dummyArg);
1081     }
1082   }
1083   if (details.isFunction()) {
1084     DoSymbol(details.result());
1085   }
1086   for (const auto &pair : scope_) {
1087     const Symbol &symbol{*pair.second};
1088     if (const auto *useDetails{symbol.detailsIf<UseDetails>()}) {
1089       const Symbol &ultimate{useDetails->symbol().GetUltimate()};
1090       bool needed{useSet_.count(ultimate) > 0};
1091       if (const auto *generic{ultimate.detailsIf<GenericDetails>()}) {
1092         // The generic may not be needed itself, but the specific procedure
1093         // &/or derived type that it shadows may be needed.
1094         const Symbol *spec{generic->specific()};
1095         const Symbol *dt{generic->derivedType()};
1096         needed = needed || (spec && useSet_.count(*spec) > 0) ||
1097             (dt && useSet_.count(*dt) > 0);
1098       } else if (const auto *subp{ultimate.detailsIf<SubprogramDetails>()}) {
1099         const Symbol *interface { subp->moduleInterface() };
1100         needed = needed || (interface && useSet_.count(*interface) > 0);
1101       }
1102       if (needed) {
1103         need_.push_back(symbol);
1104       }
1105     } else if (symbol.has<SubprogramDetails>()) {
1106       // An internal subprogram is needed if it is used as interface
1107       // for a dummy or return value procedure.
1108       bool needed{false};
1109       const auto hasInterface{[&symbol](const Symbol *s) -> bool {
1110         // Is 's' a procedure with interface 'symbol'?
1111         if (s) {
1112           if (const auto *sDetails{s->detailsIf<ProcEntityDetails>()}) {
1113             const ProcInterface &sInterface{sDetails->interface()};
1114             if (sInterface.symbol() == &symbol) {
1115               return true;
1116             }
1117           }
1118         }
1119         return false;
1120       }};
1121       for (const Symbol *dummyArg : details.dummyArgs()) {
1122         needed = needed || hasInterface(dummyArg);
1123       }
1124       needed =
1125           needed || (details.isFunction() && hasInterface(&details.result()));
1126       if (needed && needSet_.insert(symbol).second) {
1127         need_.push_back(symbol);
1128       }
1129     }
1130   }
1131 }
1132 
DoSymbol(const Symbol & symbol)1133 void SubprogramSymbolCollector::DoSymbol(const Symbol &symbol) {
1134   DoSymbol(symbol.name(), symbol);
1135 }
1136 
1137 // Do symbols this one depends on; then add to need_
DoSymbol(const SourceName & name,const Symbol & symbol)1138 void SubprogramSymbolCollector::DoSymbol(
1139     const SourceName &name, const Symbol &symbol) {
1140   const auto &scope{symbol.owner()};
1141   if (scope != scope_ && !scope.IsDerivedType()) {
1142     if (scope != scope_.parent()) {
1143       useSet_.insert(symbol);
1144     }
1145     if (NeedImport(name, symbol)) {
1146       imports_.insert(name);
1147     }
1148     return;
1149   }
1150   if (!needSet_.insert(symbol).second) {
1151     return; // already done
1152   }
1153   common::visit(common::visitors{
1154                     [this](const ObjectEntityDetails &details) {
1155                       for (const ShapeSpec &spec : details.shape()) {
1156                         DoBound(spec.lbound());
1157                         DoBound(spec.ubound());
1158                       }
1159                       for (const ShapeSpec &spec : details.coshape()) {
1160                         DoBound(spec.lbound());
1161                         DoBound(spec.ubound());
1162                       }
1163                       if (const Symbol * commonBlock{details.commonBlock()}) {
1164                         DoSymbol(*commonBlock);
1165                       }
1166                     },
1167                     [this](const CommonBlockDetails &details) {
1168                       for (const auto &object : details.objects()) {
1169                         DoSymbol(*object);
1170                       }
1171                     },
1172                     [](const auto &) {},
1173                 },
1174       symbol.details());
1175   if (!symbol.has<UseDetails>()) {
1176     DoType(symbol.GetType());
1177   }
1178   if (!scope.IsDerivedType()) {
1179     need_.push_back(symbol);
1180   }
1181 }
1182 
DoType(const DeclTypeSpec * type)1183 void SubprogramSymbolCollector::DoType(const DeclTypeSpec *type) {
1184   if (!type) {
1185     return;
1186   }
1187   switch (type->category()) {
1188   case DeclTypeSpec::Numeric:
1189   case DeclTypeSpec::Logical:
1190     break; // nothing to do
1191   case DeclTypeSpec::Character:
1192     DoParamValue(type->characterTypeSpec().length());
1193     break;
1194   default:
1195     if (const DerivedTypeSpec * derived{type->AsDerived()}) {
1196       const auto &typeSymbol{derived->typeSymbol()};
1197       if (const DerivedTypeSpec * extends{typeSymbol.GetParentTypeSpec()}) {
1198         DoSymbol(extends->name(), extends->typeSymbol());
1199       }
1200       for (const auto &pair : derived->parameters()) {
1201         DoParamValue(pair.second);
1202       }
1203       for (const auto &pair : *typeSymbol.scope()) {
1204         const Symbol &comp{*pair.second};
1205         DoSymbol(comp);
1206       }
1207       DoSymbol(derived->name(), derived->typeSymbol());
1208     }
1209   }
1210 }
1211 
DoBound(const Bound & bound)1212 void SubprogramSymbolCollector::DoBound(const Bound &bound) {
1213   if (const MaybeSubscriptIntExpr & expr{bound.GetExplicit()}) {
1214     DoExpr(*expr);
1215   }
1216 }
DoParamValue(const ParamValue & paramValue)1217 void SubprogramSymbolCollector::DoParamValue(const ParamValue &paramValue) {
1218   if (const auto &expr{paramValue.GetExplicit()}) {
1219     DoExpr(*expr);
1220   }
1221 }
1222 
1223 // Do we need a IMPORT of this symbol into an interface block?
NeedImport(const SourceName & name,const Symbol & symbol)1224 bool SubprogramSymbolCollector::NeedImport(
1225     const SourceName &name, const Symbol &symbol) {
1226   if (!isInterface_) {
1227     return false;
1228   } else if (symbol.owner().Contains(scope_)) {
1229     return true;
1230   } else if (const Symbol * found{scope_.FindSymbol(name)}) {
1231     // detect import from ancestor of use-associated symbol
1232     return found->has<UseDetails>() && found->owner() != scope_;
1233   } else {
1234     // "found" can be null in the case of a use-associated derived type's parent
1235     // type
1236     CHECK(symbol.has<DerivedTypeDetails>());
1237     return false;
1238   }
1239 }
1240 
1241 } // namespace Fortran::semantics
1242