xref: /llvm-project/flang/lib/Semantics/mod-file.cpp (revision c8ad8024435df43a0811edb51be6ee517c44d332)
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     std::map<const Symbol *, SourceName> &);
49 static void PutPassName(llvm::raw_ostream &, const std::optional<SourceName> &);
50 static void PutInit(llvm::raw_ostream &, const Symbol &, const MaybeExpr &,
51     const parser::Expr *, const std::map<const Symbol *, SourceName> &);
52 static void PutInit(llvm::raw_ostream &, const MaybeIntExpr &);
53 static void PutBound(llvm::raw_ostream &, const Bound &);
54 static void PutShapeSpec(llvm::raw_ostream &, const ShapeSpec &);
55 static void PutShape(
56     llvm::raw_ostream &, const ArraySpec &, char open, char close);
57 
58 static llvm::raw_ostream &PutAttr(llvm::raw_ostream &, Attr);
59 static llvm::raw_ostream &PutType(llvm::raw_ostream &, const DeclTypeSpec &);
60 static llvm::raw_ostream &PutLower(llvm::raw_ostream &, std::string_view);
61 static std::error_code WriteFile(
62     const std::string &, const std::string &, bool = true);
63 static bool FileContentsMatch(
64     const std::string &, const std::string &, const std::string &);
65 static std::string CheckSum(const std::string_view &);
66 
67 // Collect symbols needed for a subprogram interface
68 class SubprogramSymbolCollector {
69 public:
70   SubprogramSymbolCollector(const Symbol &symbol, const Scope &scope)
71       : symbol_{symbol}, scope_{scope} {}
72   const SymbolVector &symbols() const { return need_; }
73   const std::set<SourceName> &imports() const { return imports_; }
74   void Collect();
75 
76 private:
77   const Symbol &symbol_;
78   const Scope &scope_;
79   bool isInterface_{false};
80   SymbolVector need_; // symbols that are needed
81   UnorderedSymbolSet needSet_; // symbols already in need_
82   UnorderedSymbolSet useSet_; // use-associations that might be needed
83   std::set<SourceName> imports_; // imports from host that are needed
84 
85   void DoSymbol(const Symbol &);
86   void DoSymbol(const SourceName &, const Symbol &);
87   void DoType(const DeclTypeSpec *);
88   void DoBound(const Bound &);
89   void DoParamValue(const ParamValue &);
90   bool NeedImport(const SourceName &, const Symbol &);
91 
92   template <typename T> void DoExpr(evaluate::Expr<T> expr) {
93     for (const Symbol &symbol : evaluate::CollectSymbols(expr)) {
94       DoSymbol(symbol);
95     }
96   }
97 };
98 
99 bool ModFileWriter::WriteAll() {
100   // this flag affects character literals: force it to be consistent
101   auto restorer{
102       common::ScopedSet(parser::useHexadecimalEscapeSequences, false)};
103   WriteAll(context_.globalScope());
104   return !context_.AnyFatalError();
105 }
106 
107 void ModFileWriter::WriteAll(const Scope &scope) {
108   for (const auto &child : scope.children()) {
109     WriteOne(child);
110   }
111 }
112 
113 void ModFileWriter::WriteOne(const Scope &scope) {
114   if (scope.kind() == Scope::Kind::Module) {
115     auto *symbol{scope.symbol()};
116     if (!symbol->test(Symbol::Flag::ModFile)) {
117       Write(*symbol);
118     }
119     WriteAll(scope); // write out submodules
120   }
121 }
122 
123 // Construct the name of a module file. Non-empty ancestorName means submodule.
124 static std::string ModFileName(const SourceName &name,
125     const std::string &ancestorName, const std::string &suffix) {
126   std::string result{name.ToString() + suffix};
127   return ancestorName.empty() ? result : ancestorName + '-' + result;
128 }
129 
130 // Write the module file for symbol, which must be a module or submodule.
131 void ModFileWriter::Write(const Symbol &symbol) {
132   auto *ancestor{symbol.get<ModuleDetails>().ancestor()};
133   isSubmodule_ = ancestor != nullptr;
134   auto ancestorName{ancestor ? ancestor->GetName().value().ToString() : ""s};
135   auto path{context_.moduleDirectory() + '/' +
136       ModFileName(symbol.name(), ancestorName, context_.moduleFileSuffix())};
137   PutSymbols(DEREF(symbol.scope()));
138   if (std::error_code error{
139           WriteFile(path, GetAsString(symbol), context_.debugModuleWriter())}) {
140     context_.Say(
141         symbol.name(), "Error writing %s: %s"_err_en_US, path, error.message());
142   }
143 }
144 
145 // Return the entire body of the module file
146 // and clear saved uses, decls, and contains.
147 std::string ModFileWriter::GetAsString(const Symbol &symbol) {
148   std::string buf;
149   llvm::raw_string_ostream all{buf};
150   auto &details{symbol.get<ModuleDetails>()};
151   if (!details.isSubmodule()) {
152     all << "module " << symbol.name();
153   } else {
154     auto *parent{details.parent()->symbol()};
155     auto *ancestor{details.ancestor()->symbol()};
156     all << "submodule(" << ancestor->name();
157     if (parent != ancestor) {
158       all << ':' << parent->name();
159     }
160     all << ") " << symbol.name();
161   }
162   all << '\n' << uses_.str();
163   uses_.str().clear();
164   all << useExtraAttrs_.str();
165   useExtraAttrs_.str().clear();
166   all << decls_.str();
167   decls_.str().clear();
168   auto str{contains_.str()};
169   contains_.str().clear();
170   if (!str.empty()) {
171     all << "contains\n" << str;
172   }
173   all << "end\n";
174   return all.str();
175 }
176 
177 // Collect symbols from initializations that are being referenced directly
178 // from other modules; they may require new USE associations.
179 static void HarvestInitializerSymbols(
180     SourceOrderedSymbolSet &set, const Scope &scope) {
181   for (const auto &[_, symbol] : scope) {
182     if (symbol->has<DerivedTypeDetails>()) {
183       if (symbol->scope()) {
184         HarvestInitializerSymbols(set, *symbol->scope());
185       }
186     } else if (IsNamedConstant(*symbol) || scope.IsDerivedType()) {
187       if (const auto *object{symbol->detailsIf<ObjectEntityDetails>()}) {
188         if (object->init()) {
189           for (SymbolRef ref : evaluate::CollectSymbols(*object->init())) {
190             set.emplace(*ref);
191           }
192         }
193       } else if (const auto *proc{symbol->detailsIf<ProcEntityDetails>()}) {
194         if (proc->init() && *proc->init()) {
195           set.emplace(**proc->init());
196         }
197       }
198     }
199   }
200 }
201 
202 void ModFileWriter::PrepareRenamings(const Scope &scope) {
203   SourceOrderedSymbolSet symbolsInInits;
204   HarvestInitializerSymbols(symbolsInInits, scope);
205   for (SymbolRef s : symbolsInInits) {
206     const Scope *sMod{FindModuleContaining(s->owner())};
207     if (!sMod) {
208       continue;
209     }
210     SourceName rename{s->name()};
211     if (const Symbol * found{scope.FindSymbol(s->name())}) {
212       if (found == &*s) {
213         continue; // available in scope
214       }
215       if (const auto *generic{found->detailsIf<GenericDetails>()}) {
216         if (generic->derivedType() == &*s || generic->specific() == &*s) {
217           continue;
218         }
219       } else if (found->has<UseDetails>()) {
220         if (&found->GetUltimate() == &*s) {
221           continue; // already use-associated with same name
222         }
223       }
224       if (&s->owner() != &found->owner()) { // Symbol needs renaming
225         rename = scope.context().SaveTempName(
226             DEREF(sMod->symbol()).name().ToString() + "$" +
227             s->name().ToString());
228       }
229     }
230     // Symbol is used in this scope but not visible under its name
231     if (sMod->parent().IsIntrinsicModules()) {
232       uses_ << "use,intrinsic::";
233     } else {
234       uses_ << "use ";
235     }
236     uses_ << DEREF(sMod->symbol()).name() << ",only:";
237     if (rename != s->name()) {
238       uses_ << rename << "=>";
239     }
240     uses_ << s->name() << '\n';
241     useExtraAttrs_ << "private::" << rename << '\n';
242     renamings_.emplace(&*s, rename);
243   }
244 }
245 
246 // Put out the visible symbols from scope.
247 void ModFileWriter::PutSymbols(const Scope &scope) {
248   SymbolVector sorted;
249   SymbolVector uses;
250   PrepareRenamings(scope);
251   CollectSymbols(scope, sorted, uses, renamings_);
252   std::string buf; // stuff after CONTAINS in derived type
253   llvm::raw_string_ostream typeBindings{buf};
254   for (const Symbol &symbol : sorted) {
255     if (!symbol.test(Symbol::Flag::CompilerCreated)) {
256       PutSymbol(typeBindings, symbol);
257     }
258   }
259   for (const Symbol &symbol : uses) {
260     PutUse(symbol);
261   }
262   for (const auto &set : scope.equivalenceSets()) {
263     if (!set.empty() &&
264         !set.front().symbol.test(Symbol::Flag::CompilerCreated)) {
265       char punctuation{'('};
266       decls_ << "equivalence";
267       for (const auto &object : set) {
268         decls_ << punctuation << object.AsFortran();
269         punctuation = ',';
270       }
271       decls_ << ")\n";
272     }
273   }
274   CHECK(typeBindings.str().empty());
275 }
276 
277 // Emit components in order
278 bool ModFileWriter::PutComponents(const Symbol &typeSymbol) {
279   const auto &scope{DEREF(typeSymbol.scope())};
280   std::string buf; // stuff after CONTAINS in derived type
281   llvm::raw_string_ostream typeBindings{buf};
282   UnorderedSymbolSet emitted;
283   SymbolVector symbols{scope.GetSymbols()};
284   // Emit type parameters first
285   for (const Symbol &symbol : symbols) {
286     if (symbol.has<TypeParamDetails>()) {
287       PutSymbol(typeBindings, symbol);
288       emitted.emplace(symbol);
289     }
290   }
291   // Emit components in component order.
292   const auto &details{typeSymbol.get<DerivedTypeDetails>()};
293   for (SourceName name : details.componentNames()) {
294     auto iter{scope.find(name)};
295     if (iter != scope.end()) {
296       const Symbol &component{*iter->second};
297       if (!component.test(Symbol::Flag::ParentComp)) {
298         PutSymbol(typeBindings, component);
299       }
300       emitted.emplace(component);
301     }
302   }
303   // Emit remaining symbols from the type's scope
304   for (const Symbol &symbol : symbols) {
305     if (emitted.find(symbol) == emitted.end()) {
306       PutSymbol(typeBindings, symbol);
307     }
308   }
309   if (auto str{typeBindings.str()}; !str.empty()) {
310     CHECK(scope.IsDerivedType());
311     decls_ << "contains\n" << str;
312     return true;
313   } else {
314     return false;
315   }
316 }
317 
318 // Return the symbol's attributes that should be written
319 // into the mod file.
320 static Attrs getSymbolAttrsToWrite(const Symbol &symbol) {
321   // Is SAVE attribute is implicit, it should be omitted
322   // to not violate F202x C862 for a common block member.
323   return symbol.attrs() & ~(symbol.implicitAttrs() & Attrs{Attr::SAVE});
324 }
325 
326 static llvm::raw_ostream &PutGenericName(
327     llvm::raw_ostream &os, const Symbol &symbol) {
328   if (IsGenericDefinedOp(symbol)) {
329     return os << "operator(" << symbol.name() << ')';
330   } else {
331     return os << symbol.name();
332   }
333 }
334 
335 // Emit a symbol to decls_, except for bindings in a derived type (type-bound
336 // procedures, type-bound generics, final procedures) which go to typeBindings.
337 void ModFileWriter::PutSymbol(
338     llvm::raw_ostream &typeBindings, const Symbol &symbol) {
339   common::visit(
340       common::visitors{
341           [&](const ModuleDetails &) { /* should be current module */ },
342           [&](const DerivedTypeDetails &) { PutDerivedType(symbol); },
343           [&](const SubprogramDetails &) { PutSubprogram(symbol); },
344           [&](const GenericDetails &x) {
345             if (symbol.owner().IsDerivedType()) {
346               // generic binding
347               for (const Symbol &proc : x.specificProcs()) {
348                 PutGenericName(typeBindings << "generic::", symbol)
349                     << "=>" << proc.name() << '\n';
350               }
351             } else {
352               PutGeneric(symbol);
353             }
354           },
355           [&](const UseDetails &) { PutUse(symbol); },
356           [](const UseErrorDetails &) {},
357           [&](const ProcBindingDetails &x) {
358             bool deferred{symbol.attrs().test(Attr::DEFERRED)};
359             typeBindings << "procedure";
360             if (deferred) {
361               typeBindings << '(' << x.symbol().name() << ')';
362             }
363             PutPassName(typeBindings, x.passName());
364             auto attrs{symbol.attrs()};
365             if (x.passName()) {
366               attrs.reset(Attr::PASS);
367             }
368             PutAttrs(typeBindings, attrs);
369             typeBindings << "::" << symbol.name();
370             if (!deferred && x.symbol().name() != symbol.name()) {
371               typeBindings << "=>" << x.symbol().name();
372             }
373             typeBindings << '\n';
374           },
375           [&](const NamelistDetails &x) {
376             decls_ << "namelist/" << symbol.name();
377             char sep{'/'};
378             for (const Symbol &object : x.objects()) {
379               decls_ << sep << object.name();
380               sep = ',';
381             }
382             decls_ << '\n';
383             if (!isSubmodule_ && symbol.attrs().test(Attr::PRIVATE)) {
384               decls_ << "private::" << symbol.name() << '\n';
385             }
386           },
387           [&](const CommonBlockDetails &x) {
388             decls_ << "common/" << symbol.name();
389             char sep = '/';
390             for (const auto &object : x.objects()) {
391               decls_ << sep << object->name();
392               sep = ',';
393             }
394             decls_ << '\n';
395             if (symbol.attrs().test(Attr::BIND_C)) {
396               PutAttrs(decls_, getSymbolAttrsToWrite(symbol), x.bindName(),
397                   x.isExplicitBindName(), ""s);
398               decls_ << "::/" << symbol.name() << "/\n";
399             }
400           },
401           [](const HostAssocDetails &) {},
402           [](const MiscDetails &) {},
403           [&](const auto &) {
404             PutEntity(decls_, symbol);
405             PutDirective(decls_, symbol);
406           },
407       },
408       symbol.details());
409 }
410 
411 void ModFileWriter::PutDerivedType(
412     const Symbol &typeSymbol, const Scope *scope) {
413   auto &details{typeSymbol.get<DerivedTypeDetails>()};
414   if (details.isDECStructure()) {
415     PutDECStructure(typeSymbol, scope);
416     return;
417   }
418   PutAttrs(decls_ << "type", typeSymbol.attrs());
419   if (const DerivedTypeSpec * extends{typeSymbol.GetParentTypeSpec()}) {
420     decls_ << ",extends(" << extends->name() << ')';
421   }
422   decls_ << "::" << typeSymbol.name();
423   if (!details.paramNames().empty()) {
424     char sep{'('};
425     for (const auto &name : details.paramNames()) {
426       decls_ << sep << name;
427       sep = ',';
428     }
429     decls_ << ')';
430   }
431   decls_ << '\n';
432   if (details.sequence()) {
433     decls_ << "sequence\n";
434   }
435   bool contains{PutComponents(typeSymbol)};
436   if (!details.finals().empty()) {
437     const char *sep{contains ? "final::" : "contains\nfinal::"};
438     for (const auto &pair : details.finals()) {
439       decls_ << sep << pair.second->name();
440       sep = ",";
441     }
442     if (*sep == ',') {
443       decls_ << '\n';
444     }
445   }
446   decls_ << "end type\n";
447 }
448 
449 void ModFileWriter::PutDECStructure(
450     const Symbol &typeSymbol, const Scope *scope) {
451   if (emittedDECStructures_.find(typeSymbol) != emittedDECStructures_.end()) {
452     return;
453   }
454   if (!scope && context_.IsTempName(typeSymbol.name().ToString())) {
455     return; // defer until used
456   }
457   emittedDECStructures_.insert(typeSymbol);
458   decls_ << "structure ";
459   if (!context_.IsTempName(typeSymbol.name().ToString())) {
460     decls_ << typeSymbol.name();
461   }
462   if (scope && scope->kind() == Scope::Kind::DerivedType) {
463     // Nested STRUCTURE: emit entity declarations right now
464     // on the STRUCTURE statement.
465     bool any{false};
466     for (const auto &ref : scope->GetSymbols()) {
467       const auto *object{ref->detailsIf<ObjectEntityDetails>()};
468       if (object && object->type() &&
469           object->type()->category() == DeclTypeSpec::TypeDerived &&
470           &object->type()->derivedTypeSpec().typeSymbol() == &typeSymbol) {
471         if (any) {
472           decls_ << ',';
473         } else {
474           any = true;
475         }
476         decls_ << ref->name();
477         PutShape(decls_, object->shape(), '(', ')');
478         PutInit(decls_, *ref, object->init(), nullptr, renamings_);
479         emittedDECFields_.insert(*ref);
480       } else if (any) {
481         break; // any later use of this structure will use RECORD/str/
482       }
483     }
484   }
485   decls_ << '\n';
486   PutComponents(typeSymbol);
487   decls_ << "end structure\n";
488 }
489 
490 // Attributes that may be in a subprogram prefix
491 static const Attrs subprogramPrefixAttrs{Attr::ELEMENTAL, Attr::IMPURE,
492     Attr::MODULE, Attr::NON_RECURSIVE, Attr::PURE, Attr::RECURSIVE};
493 
494 static void PutOpenACCDeviceTypeRoutineInfo(
495     llvm::raw_ostream &os, const OpenACCRoutineDeviceTypeInfo &info) {
496   if (info.isSeq()) {
497     os << " seq";
498   }
499   if (info.isGang()) {
500     os << " gang";
501     if (info.gangDim() > 0) {
502       os << "(dim: " << info.gangDim() << ")";
503     }
504   }
505   if (info.isVector()) {
506     os << " vector";
507   }
508   if (info.isWorker()) {
509     os << " worker";
510   }
511   if (info.bindName()) {
512     os << " bind(" << *info.bindName() << ")";
513   }
514 }
515 
516 static void PutOpenACCRoutineInfo(
517     llvm::raw_ostream &os, const SubprogramDetails &details) {
518   for (auto info : details.openACCRoutineInfos()) {
519     os << "!$acc routine";
520 
521     PutOpenACCDeviceTypeRoutineInfo(os, info);
522 
523     if (info.isNohost()) {
524       os << " nohost";
525     }
526 
527     for (auto dtype : info.deviceTypeInfos()) {
528       os << " device_type(";
529       if (dtype.dType() == common::OpenACCDeviceType::Star) {
530         os << "*";
531       } else {
532         os << parser::ToLowerCaseLetters(common::EnumToString(dtype.dType()));
533       }
534       os << ")";
535 
536       PutOpenACCDeviceTypeRoutineInfo(os, dtype);
537     }
538 
539     os << "\n";
540   }
541 }
542 
543 void ModFileWriter::PutSubprogram(const Symbol &symbol) {
544   auto &details{symbol.get<SubprogramDetails>()};
545   if (const Symbol * interface{details.moduleInterface()}) {
546     const Scope *module{FindModuleContaining(interface->owner())};
547     if (module && module != &symbol.owner()) {
548       // Interface is in ancestor module
549     } else {
550       PutSubprogram(*interface);
551     }
552   }
553   auto attrs{symbol.attrs()};
554   Attrs bindAttrs{};
555   if (attrs.test(Attr::BIND_C)) {
556     // bind(c) is a suffix, not prefix
557     bindAttrs.set(Attr::BIND_C, true);
558     attrs.set(Attr::BIND_C, false);
559   }
560   bool isAbstract{attrs.test(Attr::ABSTRACT)};
561   if (isAbstract) {
562     attrs.set(Attr::ABSTRACT, false);
563   }
564   Attrs prefixAttrs{subprogramPrefixAttrs & attrs};
565   // emit any non-prefix attributes in an attribute statement
566   attrs &= ~subprogramPrefixAttrs;
567   std::string ssBuf;
568   llvm::raw_string_ostream ss{ssBuf};
569   PutAttrs(ss, attrs);
570   if (!ss.str().empty()) {
571     decls_ << ss.str().substr(1) << "::" << symbol.name() << '\n';
572   }
573   bool isInterface{details.isInterface()};
574   llvm::raw_ostream &os{isInterface ? decls_ : contains_};
575   if (isInterface) {
576     os << (isAbstract ? "abstract " : "") << "interface\n";
577   }
578   PutAttrs(os, prefixAttrs, nullptr, false, ""s, " "s);
579   if (auto attrs{details.cudaSubprogramAttrs()}) {
580     if (*attrs == common::CUDASubprogramAttrs::HostDevice) {
581       os << "attributes(host,device) ";
582     } else {
583       PutLower(os << "attributes(", common::EnumToString(*attrs)) << ") ";
584     }
585     if (!details.cudaLaunchBounds().empty()) {
586       os << "launch_bounds";
587       char sep{'('};
588       for (auto x : details.cudaLaunchBounds()) {
589         os << sep << x;
590         sep = ',';
591       }
592       os << ") ";
593     }
594     if (!details.cudaClusterDims().empty()) {
595       os << "cluster_dims";
596       char sep{'('};
597       for (auto x : details.cudaClusterDims()) {
598         os << sep << x;
599         sep = ',';
600       }
601       os << ") ";
602     }
603   }
604   os << (details.isFunction() ? "function " : "subroutine ");
605   os << symbol.name() << '(';
606   int n = 0;
607   for (const auto &dummy : details.dummyArgs()) {
608     if (n++ > 0) {
609       os << ',';
610     }
611     if (dummy) {
612       os << dummy->name();
613     } else {
614       os << "*";
615     }
616   }
617   os << ')';
618   PutAttrs(os, bindAttrs, details.bindName(), details.isExplicitBindName(),
619       " "s, ""s);
620   if (details.isFunction()) {
621     const Symbol &result{details.result()};
622     if (result.name() != symbol.name()) {
623       os << " result(" << result.name() << ')';
624     }
625   }
626   os << '\n';
627   // walk symbols, collect ones needed for interface
628   const Scope &scope{
629       details.entryScope() ? *details.entryScope() : DEREF(symbol.scope())};
630   SubprogramSymbolCollector collector{symbol, scope};
631   collector.Collect();
632   std::string typeBindingsBuf;
633   llvm::raw_string_ostream typeBindings{typeBindingsBuf};
634   ModFileWriter writer{context_};
635   for (const Symbol &need : collector.symbols()) {
636     writer.PutSymbol(typeBindings, need);
637   }
638   CHECK(typeBindings.str().empty());
639   os << writer.uses_.str();
640   for (const SourceName &import : collector.imports()) {
641     decls_ << "import::" << import << "\n";
642   }
643   os << writer.decls_.str();
644   PutOpenACCRoutineInfo(os, details);
645   os << "end\n";
646   if (isInterface) {
647     os << "end interface\n";
648   }
649 }
650 
651 static bool IsIntrinsicOp(const Symbol &symbol) {
652   if (const auto *details{symbol.GetUltimate().detailsIf<GenericDetails>()}) {
653     return details->kind().IsIntrinsicOperator();
654   } else {
655     return false;
656   }
657 }
658 
659 void ModFileWriter::PutGeneric(const Symbol &symbol) {
660   const auto &genericOwner{symbol.owner()};
661   auto &details{symbol.get<GenericDetails>()};
662   PutGenericName(decls_ << "interface ", symbol) << '\n';
663   for (const Symbol &specific : details.specificProcs()) {
664     if (specific.owner() == genericOwner) {
665       decls_ << "procedure::" << specific.name() << '\n';
666     }
667   }
668   decls_ << "end interface\n";
669   if (!isSubmodule_ && symbol.attrs().test(Attr::PRIVATE)) {
670     PutGenericName(decls_ << "private::", symbol) << '\n';
671   }
672 }
673 
674 void ModFileWriter::PutUse(const Symbol &symbol) {
675   auto &details{symbol.get<UseDetails>()};
676   auto &use{details.symbol()};
677   const Symbol &module{GetUsedModule(details)};
678   if (use.owner().parent().IsIntrinsicModules()) {
679     uses_ << "use,intrinsic::";
680   } else {
681     uses_ << "use ";
682   }
683   uses_ << module.name() << ",only:";
684   PutGenericName(uses_, symbol);
685   // Can have intrinsic op with different local-name and use-name
686   // (e.g. `operator(<)` and `operator(.lt.)`) but rename is not allowed
687   if (!IsIntrinsicOp(symbol) && use.name() != symbol.name()) {
688     PutGenericName(uses_ << "=>", use);
689   }
690   uses_ << '\n';
691   PutUseExtraAttr(Attr::VOLATILE, symbol, use);
692   PutUseExtraAttr(Attr::ASYNCHRONOUS, symbol, use);
693   if (!isSubmodule_ && symbol.attrs().test(Attr::PRIVATE)) {
694     PutGenericName(useExtraAttrs_ << "private::", symbol) << '\n';
695   }
696 }
697 
698 // We have "USE local => use" in this module. If attr was added locally
699 // (i.e. on local but not on use), also write it out in the mod file.
700 void ModFileWriter::PutUseExtraAttr(
701     Attr attr, const Symbol &local, const Symbol &use) {
702   if (local.attrs().test(attr) && !use.attrs().test(attr)) {
703     PutAttr(useExtraAttrs_, attr) << "::";
704     useExtraAttrs_ << local.name() << '\n';
705   }
706 }
707 
708 static inline SourceName NameInModuleFile(const Symbol &symbol) {
709   if (const auto *use{symbol.detailsIf<UseDetails>()}) {
710     if (use->symbol().attrs().test(Attr::PRIVATE)) {
711       // Avoid the use in sorting of names created to access private
712       // specific procedures as a result of generic resolution;
713       // they're not in the cooked source.
714       return use->symbol().name();
715     }
716   }
717   return symbol.name();
718 }
719 
720 // Collect the symbols of this scope sorted by their original order, not name.
721 // Generics and namelists are exceptions: they are sorted after other symbols.
722 void CollectSymbols(const Scope &scope, SymbolVector &sorted,
723     SymbolVector &uses, std::map<const Symbol *, SourceName> &renamings) {
724   SymbolVector namelist, generics;
725   auto symbols{scope.GetSymbols()};
726   std::size_t commonSize{scope.commonBlocks().size()};
727   sorted.reserve(symbols.size() + commonSize);
728   for (SymbolRef symbol : symbols) {
729     if (symbol->test(Symbol::Flag::ParentComp)) {
730     } else if (symbol->has<NamelistDetails>()) {
731       namelist.push_back(symbol);
732     } else if (const auto *generic{symbol->detailsIf<GenericDetails>()}) {
733       if (generic->specific() &&
734           &generic->specific()->owner() == &symbol->owner()) {
735         sorted.push_back(*generic->specific());
736       } else if (generic->derivedType() &&
737           &generic->derivedType()->owner() == &symbol->owner()) {
738         sorted.push_back(*generic->derivedType());
739       }
740       generics.push_back(symbol);
741     } else {
742       sorted.push_back(symbol);
743     }
744     if (const auto *details{symbol->detailsIf<GenericDetails>()}) {
745       uses.insert(uses.end(), details->uses().begin(), details->uses().end());
746     }
747   }
748   // Sort most symbols by name: use of Symbol::ReplaceName ensures the source
749   // location of a symbol's name is the first "real" use.
750   auto sorter{[](SymbolRef x, SymbolRef y) {
751     return NameInModuleFile(*x).begin() < NameInModuleFile(*y).begin();
752   }};
753   std::sort(sorted.begin(), sorted.end(), sorter);
754   std::sort(generics.begin(), generics.end(), sorter);
755   sorted.insert(sorted.end(), generics.begin(), generics.end());
756   sorted.insert(sorted.end(), namelist.begin(), namelist.end());
757   for (const auto &pair : scope.commonBlocks()) {
758     sorted.push_back(*pair.second);
759   }
760   std::sort(
761       sorted.end() - commonSize, sorted.end(), SymbolSourcePositionCompare{});
762 }
763 
764 void ModFileWriter::PutEntity(llvm::raw_ostream &os, const Symbol &symbol) {
765   common::visit(
766       common::visitors{
767           [&](const ObjectEntityDetails &) { PutObjectEntity(os, symbol); },
768           [&](const ProcEntityDetails &) { PutProcEntity(os, symbol); },
769           [&](const TypeParamDetails &) { PutTypeParam(os, symbol); },
770           [&](const auto &) {
771             common::die("PutEntity: unexpected details: %s",
772                 DetailsToString(symbol.details()).c_str());
773           },
774       },
775       symbol.details());
776 }
777 
778 void PutShapeSpec(llvm::raw_ostream &os, const ShapeSpec &x) {
779   if (x.lbound().isStar()) {
780     CHECK(x.ubound().isStar());
781     os << ".."; // assumed rank
782   } else {
783     if (!x.lbound().isColon()) {
784       PutBound(os, x.lbound());
785     }
786     os << ':';
787     if (!x.ubound().isColon()) {
788       PutBound(os, x.ubound());
789     }
790   }
791 }
792 void PutShape(
793     llvm::raw_ostream &os, const ArraySpec &shape, char open, char close) {
794   if (!shape.empty()) {
795     os << open;
796     bool first{true};
797     for (const auto &shapeSpec : shape) {
798       if (first) {
799         first = false;
800       } else {
801         os << ',';
802       }
803       PutShapeSpec(os, shapeSpec);
804     }
805     os << close;
806   }
807 }
808 
809 void ModFileWriter::PutObjectEntity(
810     llvm::raw_ostream &os, const Symbol &symbol) {
811   auto &details{symbol.get<ObjectEntityDetails>()};
812   if (details.type() &&
813       details.type()->category() == DeclTypeSpec::TypeDerived) {
814     const Symbol &typeSymbol{details.type()->derivedTypeSpec().typeSymbol()};
815     if (typeSymbol.get<DerivedTypeDetails>().isDECStructure()) {
816       PutDerivedType(typeSymbol, &symbol.owner());
817       if (emittedDECFields_.find(symbol) != emittedDECFields_.end()) {
818         return; // symbol was emitted on STRUCTURE statement
819       }
820     }
821   }
822   PutEntity(
823       os, symbol, [&]() { PutType(os, DEREF(symbol.GetType())); },
824       getSymbolAttrsToWrite(symbol));
825   PutShape(os, details.shape(), '(', ')');
826   PutShape(os, details.coshape(), '[', ']');
827   PutInit(os, symbol, details.init(), details.unanalyzedPDTComponentInit(),
828       renamings_);
829   os << '\n';
830   if (auto tkr{GetIgnoreTKR(symbol)}; !tkr.empty()) {
831     os << "!dir$ ignore_tkr(";
832     tkr.IterateOverMembers([&](common::IgnoreTKR tkr) {
833       switch (tkr) {
834         SWITCH_COVERS_ALL_CASES
835       case common::IgnoreTKR::Type:
836         os << 't';
837         break;
838       case common::IgnoreTKR::Kind:
839         os << 'k';
840         break;
841       case common::IgnoreTKR::Rank:
842         os << 'r';
843         break;
844       case common::IgnoreTKR::Device:
845         os << 'd';
846         break;
847       case common::IgnoreTKR::Managed:
848         os << 'm';
849         break;
850       case common::IgnoreTKR::Contiguous:
851         os << 'c';
852         break;
853       }
854     });
855     os << ") " << symbol.name() << '\n';
856   }
857   if (auto attr{details.cudaDataAttr()}) {
858     PutLower(os << "attributes(", common::EnumToString(*attr))
859         << ") " << symbol.name() << '\n';
860   }
861   if (symbol.test(Fortran::semantics::Symbol::Flag::CrayPointer)) {
862     if (!symbol.owner().crayPointers().empty()) {
863       for (const auto &[pointee, pointer] : symbol.owner().crayPointers()) {
864         if (pointer == symbol) {
865           os << "pointer(" << symbol.name() << "," << pointee << ")\n";
866         }
867       }
868     }
869   }
870 }
871 
872 void ModFileWriter::PutProcEntity(llvm::raw_ostream &os, const Symbol &symbol) {
873   if (symbol.attrs().test(Attr::INTRINSIC)) {
874     os << "intrinsic::" << symbol.name() << '\n';
875     if (!isSubmodule_ && symbol.attrs().test(Attr::PRIVATE)) {
876       os << "private::" << symbol.name() << '\n';
877     }
878     return;
879   }
880   const auto &details{symbol.get<ProcEntityDetails>()};
881   Attrs attrs{symbol.attrs()};
882   if (details.passName()) {
883     attrs.reset(Attr::PASS);
884   }
885   PutEntity(
886       os, symbol,
887       [&]() {
888         os << "procedure(";
889         if (details.procInterface()) {
890           os << details.procInterface()->name();
891         } else if (details.type()) {
892           PutType(os, *details.type());
893         }
894         os << ')';
895         PutPassName(os, details.passName());
896       },
897       attrs);
898   os << '\n';
899 }
900 
901 void PutPassName(
902     llvm::raw_ostream &os, const std::optional<SourceName> &passName) {
903   if (passName) {
904     os << ",pass(" << *passName << ')';
905   }
906 }
907 
908 void ModFileWriter::PutTypeParam(llvm::raw_ostream &os, const Symbol &symbol) {
909   auto &details{symbol.get<TypeParamDetails>()};
910   PutEntity(
911       os, symbol,
912       [&]() {
913         PutType(os, DEREF(symbol.GetType()));
914         PutLower(os << ',', common::EnumToString(details.attr()));
915       },
916       symbol.attrs());
917   PutInit(os, details.init());
918   os << '\n';
919 }
920 
921 void PutInit(llvm::raw_ostream &os, const Symbol &symbol, const MaybeExpr &init,
922     const parser::Expr *unanalyzed,
923     const std::map<const Symbol *, SourceName> &renamings) {
924   if (IsNamedConstant(symbol) || symbol.owner().IsDerivedType()) {
925     const char *assign{symbol.attrs().test(Attr::POINTER) ? "=>" : "="};
926     if (unanalyzed) {
927       parser::Unparse(os << assign, *unanalyzed);
928     } else if (init) {
929       if (const auto *dtConst{
930               evaluate::UnwrapExpr<evaluate::Constant<evaluate::SomeDerived>>(
931                   *init)}) {
932         const Symbol &dtSym{dtConst->result().derivedTypeSpec().typeSymbol()};
933         if (auto iter{renamings.find(&dtSym)}; iter != renamings.end()) {
934           // Initializer is a constant whose derived type's name has
935           // been brought into scope from a module under a new name
936           // to avoid a conflict.
937           dtConst->AsFortran(os << assign, &iter->second);
938           return;
939         }
940       }
941       init->AsFortran(os << assign);
942     }
943   }
944 }
945 
946 void PutInit(llvm::raw_ostream &os, const MaybeIntExpr &init) {
947   if (init) {
948     init->AsFortran(os << '=');
949   }
950 }
951 
952 void PutBound(llvm::raw_ostream &os, const Bound &x) {
953   if (x.isStar()) {
954     os << '*';
955   } else if (x.isColon()) {
956     os << ':';
957   } else {
958     x.GetExplicit()->AsFortran(os);
959   }
960 }
961 
962 // Write an entity (object or procedure) declaration.
963 // writeType is called to write out the type.
964 void ModFileWriter::PutEntity(llvm::raw_ostream &os, const Symbol &symbol,
965     std::function<void()> writeType, Attrs attrs) {
966   writeType();
967   PutAttrs(os, attrs, symbol.GetBindName(), symbol.GetIsExplicitBindName());
968   if (symbol.owner().kind() == Scope::Kind::DerivedType &&
969       context_.IsTempName(symbol.name().ToString())) {
970     os << "::%FILL";
971   } else {
972     os << "::" << symbol.name();
973   }
974 }
975 
976 // Put out each attribute to os, surrounded by `before` and `after` and
977 // mapped to lower case.
978 llvm::raw_ostream &ModFileWriter::PutAttrs(llvm::raw_ostream &os, Attrs attrs,
979     const std::string *bindName, bool isExplicitBindName, std::string before,
980     std::string after) const {
981   attrs.set(Attr::PUBLIC, false); // no need to write PUBLIC
982   attrs.set(Attr::EXTERNAL, false); // no need to write EXTERNAL
983   if (isSubmodule_) {
984     attrs.set(Attr::PRIVATE, false);
985   }
986   if (bindName || isExplicitBindName) {
987     os << before << "bind(c";
988     if (isExplicitBindName) {
989       os << ",name=\"" << (bindName ? *bindName : ""s) << '"';
990     }
991     os << ')' << after;
992     attrs.set(Attr::BIND_C, false);
993   }
994   for (std::size_t i{0}; i < Attr_enumSize; ++i) {
995     Attr attr{static_cast<Attr>(i)};
996     if (attrs.test(attr)) {
997       PutAttr(os << before, attr) << after;
998     }
999   }
1000   return os;
1001 }
1002 
1003 llvm::raw_ostream &PutAttr(llvm::raw_ostream &os, Attr attr) {
1004   return PutLower(os, AttrToString(attr));
1005 }
1006 
1007 llvm::raw_ostream &PutType(llvm::raw_ostream &os, const DeclTypeSpec &type) {
1008   return PutLower(os, type.AsFortran());
1009 }
1010 
1011 llvm::raw_ostream &PutLower(llvm::raw_ostream &os, std::string_view str) {
1012   for (char c : str) {
1013     os << parser::ToLowerCaseLetter(c);
1014   }
1015   return os;
1016 }
1017 
1018 void PutOpenACCDirective(llvm::raw_ostream &os, const Symbol &symbol) {
1019   if (symbol.test(Symbol::Flag::AccDeclare)) {
1020     os << "!$acc declare ";
1021     if (symbol.test(Symbol::Flag::AccCopy)) {
1022       os << "copy";
1023     } else if (symbol.test(Symbol::Flag::AccCopyIn) ||
1024         symbol.test(Symbol::Flag::AccCopyInReadOnly)) {
1025       os << "copyin";
1026     } else if (symbol.test(Symbol::Flag::AccCopyOut)) {
1027       os << "copyout";
1028     } else if (symbol.test(Symbol::Flag::AccCreate)) {
1029       os << "create";
1030     } else if (symbol.test(Symbol::Flag::AccPresent)) {
1031       os << "present";
1032     } else if (symbol.test(Symbol::Flag::AccDevicePtr)) {
1033       os << "deviceptr";
1034     } else if (symbol.test(Symbol::Flag::AccDeviceResident)) {
1035       os << "device_resident";
1036     } else if (symbol.test(Symbol::Flag::AccLink)) {
1037       os << "link";
1038     }
1039     os << "(";
1040     if (symbol.test(Symbol::Flag::AccCopyInReadOnly)) {
1041       os << "readonly: ";
1042     }
1043     os << symbol.name() << ")\n";
1044   }
1045 }
1046 
1047 void PutOpenMPDirective(llvm::raw_ostream &os, const Symbol &symbol) {
1048   if (symbol.test(Symbol::Flag::OmpThreadprivate)) {
1049     os << "!$omp threadprivate(" << symbol.name() << ")\n";
1050   }
1051 }
1052 
1053 void ModFileWriter::PutDirective(llvm::raw_ostream &os, const Symbol &symbol) {
1054   PutOpenACCDirective(os, symbol);
1055   PutOpenMPDirective(os, symbol);
1056 }
1057 
1058 struct Temp {
1059   Temp(int fd, std::string path) : fd{fd}, path{path} {}
1060   Temp(Temp &&t) : fd{std::exchange(t.fd, -1)}, path{std::move(t.path)} {}
1061   ~Temp() {
1062     if (fd >= 0) {
1063       llvm::sys::fs::file_t native{llvm::sys::fs::convertFDToNativeFile(fd)};
1064       llvm::sys::fs::closeFile(native);
1065       llvm::sys::fs::remove(path.c_str());
1066     }
1067   }
1068   int fd;
1069   std::string path;
1070 };
1071 
1072 // Create a temp file in the same directory and with the same suffix as path.
1073 // Return an open file descriptor and its path.
1074 static llvm::ErrorOr<Temp> MkTemp(const std::string &path) {
1075   auto length{path.length()};
1076   auto dot{path.find_last_of("./")};
1077   std::string suffix{
1078       dot < length && path[dot] == '.' ? path.substr(dot + 1) : ""};
1079   CHECK(length > suffix.length() &&
1080       path.substr(length - suffix.length()) == suffix);
1081   auto prefix{path.substr(0, length - suffix.length())};
1082   int fd;
1083   llvm::SmallString<16> tempPath;
1084   if (std::error_code err{llvm::sys::fs::createUniqueFile(
1085           prefix + "%%%%%%" + suffix, fd, tempPath)}) {
1086     return err;
1087   }
1088   return Temp{fd, tempPath.c_str()};
1089 }
1090 
1091 // Write the module file at path, prepending header. If an error occurs,
1092 // return errno, otherwise 0.
1093 static std::error_code WriteFile(
1094     const std::string &path, const std::string &contents, bool debug) {
1095   auto header{std::string{ModHeader::bom} + ModHeader::magic +
1096       CheckSum(contents) + ModHeader::terminator};
1097   if (debug) {
1098     llvm::dbgs() << "Processing module " << path << ": ";
1099   }
1100   if (FileContentsMatch(path, header, contents)) {
1101     if (debug) {
1102       llvm::dbgs() << "module unchanged, not writing\n";
1103     }
1104     return {};
1105   }
1106   llvm::ErrorOr<Temp> temp{MkTemp(path)};
1107   if (!temp) {
1108     return temp.getError();
1109   }
1110   llvm::raw_fd_ostream writer(temp->fd, /*shouldClose=*/false);
1111   writer << header;
1112   writer << contents;
1113   writer.flush();
1114   if (writer.has_error()) {
1115     return writer.error();
1116   }
1117   if (debug) {
1118     llvm::dbgs() << "module written\n";
1119   }
1120   return llvm::sys::fs::rename(temp->path, path);
1121 }
1122 
1123 // Return true if the stream matches what we would write for the mod file.
1124 static bool FileContentsMatch(const std::string &path,
1125     const std::string &header, const std::string &contents) {
1126   std::size_t hsize{header.size()};
1127   std::size_t csize{contents.size()};
1128   auto buf_or{llvm::MemoryBuffer::getFile(path)};
1129   if (!buf_or) {
1130     return false;
1131   }
1132   auto buf = std::move(buf_or.get());
1133   if (buf->getBufferSize() != hsize + csize) {
1134     return false;
1135   }
1136   if (!std::equal(header.begin(), header.end(), buf->getBufferStart(),
1137           buf->getBufferStart() + hsize)) {
1138     return false;
1139   }
1140 
1141   return std::equal(contents.begin(), contents.end(),
1142       buf->getBufferStart() + hsize, buf->getBufferEnd());
1143 }
1144 
1145 // Compute a simple hash of the contents of a module file and
1146 // return it as a string of hex digits.
1147 // This uses the Fowler-Noll-Vo hash function.
1148 static std::string CheckSum(const std::string_view &contents) {
1149   std::uint64_t hash{0xcbf29ce484222325ull};
1150   for (char c : contents) {
1151     hash ^= c & 0xff;
1152     hash *= 0x100000001b3;
1153   }
1154   static const char *digits = "0123456789abcdef";
1155   std::string result(ModHeader::sumLen, '0');
1156   for (size_t i{ModHeader::sumLen}; hash != 0; hash >>= 4) {
1157     result[--i] = digits[hash & 0xf];
1158   }
1159   return result;
1160 }
1161 
1162 static bool VerifyHeader(llvm::ArrayRef<char> content) {
1163   std::string_view sv{content.data(), content.size()};
1164   if (sv.substr(0, ModHeader::magicLen) != ModHeader::magic) {
1165     return false;
1166   }
1167   std::string_view expectSum{sv.substr(ModHeader::magicLen, ModHeader::sumLen)};
1168   std::string actualSum{CheckSum(sv.substr(ModHeader::len))};
1169   return expectSum == actualSum;
1170 }
1171 
1172 Scope *ModFileReader::Read(const SourceName &name,
1173     std::optional<bool> isIntrinsic, Scope *ancestor, bool silent) {
1174   std::string ancestorName; // empty for module
1175   Symbol *notAModule{nullptr};
1176   bool fatalError{false};
1177   if (ancestor) {
1178     if (auto *scope{ancestor->FindSubmodule(name)}) {
1179       return scope;
1180     }
1181     ancestorName = ancestor->GetName().value().ToString();
1182   }
1183   if (!isIntrinsic.value_or(false) && !ancestor) {
1184     // Already present in the symbol table as a usable non-intrinsic module?
1185     auto it{context_.globalScope().find(name)};
1186     if (it != context_.globalScope().end()) {
1187       Scope *scope{it->second->scope()};
1188       if (scope->kind() == Scope::Kind::Module) {
1189         return scope;
1190       } else {
1191         notAModule = scope->symbol();
1192         // USE, NON_INTRINSIC global name isn't a module?
1193         fatalError = isIntrinsic.has_value();
1194       }
1195     }
1196   }
1197   auto path{ModFileName(name, ancestorName, context_.moduleFileSuffix())};
1198   parser::Parsing parsing{context_.allCookedSources()};
1199   parser::Options options;
1200   options.isModuleFile = true;
1201   options.features.Enable(common::LanguageFeature::BackslashEscapes);
1202   options.features.Enable(common::LanguageFeature::OpenMP);
1203   options.features.Enable(common::LanguageFeature::CUDA);
1204   if (!isIntrinsic.value_or(false) && !notAModule) {
1205     // The search for this module file will scan non-intrinsic module
1206     // directories.  If a directory is in both the intrinsic and non-intrinsic
1207     // directory lists, the intrinsic module directory takes precedence.
1208     options.searchDirectories = context_.searchDirectories();
1209     for (const auto &dir : context_.intrinsicModuleDirectories()) {
1210       options.searchDirectories.erase(
1211           std::remove(options.searchDirectories.begin(),
1212               options.searchDirectories.end(), dir),
1213           options.searchDirectories.end());
1214     }
1215     options.searchDirectories.insert(options.searchDirectories.begin(), "."s);
1216   }
1217   bool foundNonIntrinsicModuleFile{false};
1218   if (!isIntrinsic) {
1219     std::list<std::string> searchDirs;
1220     for (const auto &d : options.searchDirectories) {
1221       searchDirs.push_back(d);
1222     }
1223     foundNonIntrinsicModuleFile =
1224         parser::LocateSourceFile(path, searchDirs).has_value();
1225   }
1226   if (isIntrinsic.value_or(!foundNonIntrinsicModuleFile)) {
1227     // Explicitly intrinsic, or not specified and not found in the search
1228     // path; see whether it's already in the symbol table as an intrinsic
1229     // module.
1230     auto it{context_.intrinsicModulesScope().find(name)};
1231     if (it != context_.intrinsicModulesScope().end()) {
1232       return it->second->scope();
1233     }
1234   }
1235   // We don't have this module in the symbol table yet.
1236   // Find its module file and parse it.  Define or extend the search
1237   // path with intrinsic module directories, if appropriate.
1238   if (isIntrinsic.value_or(true)) {
1239     for (const auto &dir : context_.intrinsicModuleDirectories()) {
1240       options.searchDirectories.push_back(dir);
1241     }
1242   }
1243   const auto *sourceFile{fatalError ? nullptr : parsing.Prescan(path, options)};
1244   if (fatalError || parsing.messages().AnyFatalError()) {
1245     if (!silent) {
1246       if (notAModule) {
1247         // Module is not explicitly INTRINSIC, and there's already a global
1248         // symbol of the same name that is not a module.
1249         context_.SayWithDecl(
1250             *notAModule, name, "'%s' is not a module"_err_en_US, name);
1251       } else {
1252         for (auto &msg : parsing.messages().messages()) {
1253           std::string str{msg.ToString()};
1254           Say(name, ancestorName,
1255               parser::MessageFixedText{str.c_str(), str.size(), msg.severity()},
1256               path);
1257         }
1258       }
1259     }
1260     return nullptr;
1261   }
1262   CHECK(sourceFile);
1263   if (!VerifyHeader(sourceFile->content())) {
1264     Say(name, ancestorName, "File has invalid checksum: %s"_warn_en_US,
1265         sourceFile->path());
1266     return nullptr;
1267   }
1268   llvm::raw_null_ostream NullStream;
1269   parsing.Parse(NullStream);
1270   std::optional<parser::Program> &parsedProgram{parsing.parseTree()};
1271   if (!parsing.messages().empty() || !parsing.consumedWholeFile() ||
1272       !parsedProgram) {
1273     Say(name, ancestorName, "Module file is corrupt: %s"_err_en_US,
1274         sourceFile->path());
1275     return nullptr;
1276   }
1277   parser::Program &parseTree{context_.SaveParseTree(std::move(*parsedProgram))};
1278   Scope *parentScope; // the scope this module/submodule goes into
1279   if (!isIntrinsic.has_value()) {
1280     for (const auto &dir : context_.intrinsicModuleDirectories()) {
1281       if (sourceFile->path().size() > dir.size() &&
1282           sourceFile->path().find(dir) == 0) {
1283         isIntrinsic = true;
1284         break;
1285       }
1286     }
1287   }
1288   Scope &topScope{isIntrinsic.value_or(false) ? context_.intrinsicModulesScope()
1289                                               : context_.globalScope()};
1290   Symbol *moduleSymbol{nullptr};
1291   if (!ancestor) { // module, not submodule
1292     parentScope = &topScope;
1293     auto pair{parentScope->try_emplace(name, UnknownDetails{})};
1294     if (!pair.second) {
1295       return nullptr;
1296     }
1297     moduleSymbol = &*pair.first->second;
1298     moduleSymbol->set(Symbol::Flag::ModFile);
1299   } else if (std::optional<SourceName> parent{GetSubmoduleParent(parseTree)}) {
1300     // submodule with submodule parent
1301     parentScope = Read(*parent, false /*not intrinsic*/, ancestor, silent);
1302   } else {
1303     // submodule with module parent
1304     parentScope = ancestor;
1305   }
1306   // Process declarations from the module file
1307   bool wasInModuleFile{context_.foldingContext().inModuleFile()};
1308   context_.foldingContext().set_inModuleFile(true);
1309   ResolveNames(context_, parseTree, topScope);
1310   context_.foldingContext().set_inModuleFile(wasInModuleFile);
1311   if (!moduleSymbol) {
1312     // Submodule symbols' storage are owned by their parents' scopes,
1313     // but their names are not in their parents' dictionaries -- we
1314     // don't want to report bogus errors about clashes between submodule
1315     // names and other objects in the parent scopes.
1316     if (Scope * submoduleScope{ancestor->FindSubmodule(name)}) {
1317       moduleSymbol = submoduleScope->symbol();
1318       if (moduleSymbol) {
1319         moduleSymbol->set(Symbol::Flag::ModFile);
1320       }
1321     }
1322   }
1323   if (moduleSymbol) {
1324     CHECK(moduleSymbol->has<ModuleDetails>());
1325     CHECK(moduleSymbol->test(Symbol::Flag::ModFile));
1326     if (isIntrinsic.value_or(false)) {
1327       moduleSymbol->attrs().set(Attr::INTRINSIC);
1328     }
1329     return moduleSymbol->scope();
1330   } else {
1331     return nullptr;
1332   }
1333 }
1334 
1335 parser::Message &ModFileReader::Say(const SourceName &name,
1336     const std::string &ancestor, parser::MessageFixedText &&msg,
1337     const std::string &arg) {
1338   return context_.Say(name, "Cannot read module file for %s: %s"_err_en_US,
1339       parser::MessageFormattedText{ancestor.empty()
1340               ? "module '%s'"_en_US
1341               : "submodule '%s' of module '%s'"_en_US,
1342           name, ancestor}
1343           .MoveString(),
1344       parser::MessageFormattedText{std::move(msg), arg}.MoveString());
1345 }
1346 
1347 // program was read from a .mod file for a submodule; return the name of the
1348 // submodule's parent submodule, nullptr if none.
1349 static std::optional<SourceName> GetSubmoduleParent(
1350     const parser::Program &program) {
1351   CHECK(program.v.size() == 1);
1352   auto &unit{program.v.front()};
1353   auto &submod{std::get<common::Indirection<parser::Submodule>>(unit.u)};
1354   auto &stmt{
1355       std::get<parser::Statement<parser::SubmoduleStmt>>(submod.value().t)};
1356   auto &parentId{std::get<parser::ParentIdentifier>(stmt.statement.t)};
1357   if (auto &parent{std::get<std::optional<parser::Name>>(parentId.t)}) {
1358     return parent->source;
1359   } else {
1360     return std::nullopt;
1361   }
1362 }
1363 
1364 void SubprogramSymbolCollector::Collect() {
1365   const auto &details{symbol_.get<SubprogramDetails>()};
1366   isInterface_ = details.isInterface();
1367   for (const Symbol *dummyArg : details.dummyArgs()) {
1368     if (dummyArg) {
1369       DoSymbol(*dummyArg);
1370     }
1371   }
1372   if (details.isFunction()) {
1373     DoSymbol(details.result());
1374   }
1375   for (const auto &pair : scope_) {
1376     const Symbol &symbol{*pair.second};
1377     if (const auto *useDetails{symbol.detailsIf<UseDetails>()}) {
1378       const Symbol &ultimate{useDetails->symbol().GetUltimate()};
1379       bool needed{useSet_.count(ultimate) > 0};
1380       if (const auto *generic{ultimate.detailsIf<GenericDetails>()}) {
1381         // The generic may not be needed itself, but the specific procedure
1382         // &/or derived type that it shadows may be needed.
1383         const Symbol *spec{generic->specific()};
1384         const Symbol *dt{generic->derivedType()};
1385         needed = needed || (spec && useSet_.count(*spec) > 0) ||
1386             (dt && useSet_.count(*dt) > 0);
1387       } else if (const auto *subp{ultimate.detailsIf<SubprogramDetails>()}) {
1388         const Symbol *interface { subp->moduleInterface() };
1389         needed = needed || (interface && useSet_.count(*interface) > 0);
1390       }
1391       if (needed) {
1392         need_.push_back(symbol);
1393       }
1394     } else if (symbol.has<SubprogramDetails>()) {
1395       // An internal subprogram is needed if it is used as interface
1396       // for a dummy or return value procedure.
1397       bool needed{false};
1398       const auto hasInterface{[&symbol](const Symbol *s) -> bool {
1399         // Is 's' a procedure with interface 'symbol'?
1400         if (s) {
1401           if (const auto *sDetails{s->detailsIf<ProcEntityDetails>()}) {
1402             if (sDetails->procInterface() == &symbol) {
1403               return true;
1404             }
1405           }
1406         }
1407         return false;
1408       }};
1409       for (const Symbol *dummyArg : details.dummyArgs()) {
1410         needed = needed || hasInterface(dummyArg);
1411       }
1412       needed =
1413           needed || (details.isFunction() && hasInterface(&details.result()));
1414       if (needed && needSet_.insert(symbol).second) {
1415         need_.push_back(symbol);
1416       }
1417     }
1418   }
1419 }
1420 
1421 void SubprogramSymbolCollector::DoSymbol(const Symbol &symbol) {
1422   DoSymbol(symbol.name(), symbol);
1423 }
1424 
1425 // Do symbols this one depends on; then add to need_
1426 void SubprogramSymbolCollector::DoSymbol(
1427     const SourceName &name, const Symbol &symbol) {
1428   const auto &scope{symbol.owner()};
1429   if (scope != scope_ && !scope.IsDerivedType()) {
1430     if (scope != scope_.parent()) {
1431       useSet_.insert(symbol);
1432     }
1433     if (NeedImport(name, symbol)) {
1434       imports_.insert(name);
1435     }
1436     return;
1437   }
1438   if (!needSet_.insert(symbol).second) {
1439     return; // already done
1440   }
1441   common::visit(common::visitors{
1442                     [this](const ObjectEntityDetails &details) {
1443                       for (const ShapeSpec &spec : details.shape()) {
1444                         DoBound(spec.lbound());
1445                         DoBound(spec.ubound());
1446                       }
1447                       for (const ShapeSpec &spec : details.coshape()) {
1448                         DoBound(spec.lbound());
1449                         DoBound(spec.ubound());
1450                       }
1451                       if (const Symbol * commonBlock{details.commonBlock()}) {
1452                         DoSymbol(*commonBlock);
1453                       }
1454                     },
1455                     [this](const CommonBlockDetails &details) {
1456                       for (const auto &object : details.objects()) {
1457                         DoSymbol(*object);
1458                       }
1459                     },
1460                     [this](const ProcEntityDetails &details) {
1461                       if (details.procInterface()) {
1462                         DoSymbol(*details.procInterface());
1463                       } else {
1464                         DoType(details.type());
1465                       }
1466                     },
1467                     [](const auto &) {},
1468                 },
1469       symbol.details());
1470   if (!symbol.has<UseDetails>()) {
1471     DoType(symbol.GetType());
1472   }
1473   if (!scope.IsDerivedType()) {
1474     need_.push_back(symbol);
1475   }
1476 }
1477 
1478 void SubprogramSymbolCollector::DoType(const DeclTypeSpec *type) {
1479   if (!type) {
1480     return;
1481   }
1482   switch (type->category()) {
1483   case DeclTypeSpec::Numeric:
1484   case DeclTypeSpec::Logical:
1485     break; // nothing to do
1486   case DeclTypeSpec::Character:
1487     DoParamValue(type->characterTypeSpec().length());
1488     break;
1489   default:
1490     if (const DerivedTypeSpec * derived{type->AsDerived()}) {
1491       const auto &typeSymbol{derived->typeSymbol()};
1492       if (const DerivedTypeSpec * extends{typeSymbol.GetParentTypeSpec()}) {
1493         DoSymbol(extends->name(), extends->typeSymbol());
1494       }
1495       for (const auto &pair : derived->parameters()) {
1496         DoParamValue(pair.second);
1497       }
1498       for (const auto &pair : *typeSymbol.scope()) {
1499         const Symbol &comp{*pair.second};
1500         DoSymbol(comp);
1501       }
1502       DoSymbol(derived->name(), derived->typeSymbol());
1503     }
1504   }
1505 }
1506 
1507 void SubprogramSymbolCollector::DoBound(const Bound &bound) {
1508   if (const MaybeSubscriptIntExpr & expr{bound.GetExplicit()}) {
1509     DoExpr(*expr);
1510   }
1511 }
1512 void SubprogramSymbolCollector::DoParamValue(const ParamValue &paramValue) {
1513   if (const auto &expr{paramValue.GetExplicit()}) {
1514     DoExpr(*expr);
1515   }
1516 }
1517 
1518 // Do we need a IMPORT of this symbol into an interface block?
1519 bool SubprogramSymbolCollector::NeedImport(
1520     const SourceName &name, const Symbol &symbol) {
1521   if (!isInterface_) {
1522     return false;
1523   } else if (IsSeparateModuleProcedureInterface(&symbol_)) {
1524     return false; // IMPORT needed only for external and dummy procedure
1525                   // interfaces
1526   } else if (&symbol == scope_.symbol()) {
1527     return false;
1528   } else if (symbol.owner().Contains(scope_)) {
1529     return true;
1530   } else if (const Symbol *found{scope_.FindSymbol(name)}) {
1531     // detect import from ancestor of use-associated symbol
1532     return found->has<UseDetails>() && found->owner() != scope_;
1533   } else {
1534     // "found" can be null in the case of a use-associated derived type's parent
1535     // type
1536     CHECK(symbol.has<DerivedTypeDetails>());
1537     return false;
1538   }
1539 }
1540 
1541 } // namespace Fortran::semantics
1542