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