DebugInfo: factor out dead variable in NDEBUG from r235050
[oota-llvm.git] / lib / CodeGen / AsmPrinter / DwarfDebug.cpp
1 //===-- llvm/CodeGen/DwarfDebug.cpp - Dwarf Debug Framework ---------------===//
2 //
3 //                     The LLVM Compiler Infrastructure
4 //
5 // This file is distributed under the University of Illinois Open Source
6 // License. See LICENSE.TXT for details.
7 //
8 //===----------------------------------------------------------------------===//
9 //
10 // This file contains support for writing dwarf debug info into asm files.
11 //
12 //===----------------------------------------------------------------------===//
13
14 #include "DwarfDebug.h"
15 #include "ByteStreamer.h"
16 #include "DIEHash.h"
17 #include "DwarfCompileUnit.h"
18 #include "DwarfExpression.h"
19 #include "DwarfUnit.h"
20 #include "llvm/ADT/STLExtras.h"
21 #include "llvm/ADT/Statistic.h"
22 #include "llvm/ADT/StringExtras.h"
23 #include "llvm/ADT/Triple.h"
24 #include "llvm/CodeGen/DIE.h"
25 #include "llvm/CodeGen/MachineFunction.h"
26 #include "llvm/CodeGen/MachineModuleInfo.h"
27 #include "llvm/IR/Constants.h"
28 #include "llvm/IR/DIBuilder.h"
29 #include "llvm/IR/DataLayout.h"
30 #include "llvm/IR/DebugInfo.h"
31 #include "llvm/IR/Instructions.h"
32 #include "llvm/IR/Module.h"
33 #include "llvm/IR/ValueHandle.h"
34 #include "llvm/MC/MCAsmInfo.h"
35 #include "llvm/MC/MCSection.h"
36 #include "llvm/MC/MCStreamer.h"
37 #include "llvm/MC/MCSymbol.h"
38 #include "llvm/Support/CommandLine.h"
39 #include "llvm/Support/Debug.h"
40 #include "llvm/Support/Dwarf.h"
41 #include "llvm/Support/Endian.h"
42 #include "llvm/Support/ErrorHandling.h"
43 #include "llvm/Support/FormattedStream.h"
44 #include "llvm/Support/LEB128.h"
45 #include "llvm/Support/MD5.h"
46 #include "llvm/Support/Path.h"
47 #include "llvm/Support/Timer.h"
48 #include "llvm/Support/raw_ostream.h"
49 #include "llvm/Target/TargetFrameLowering.h"
50 #include "llvm/Target/TargetLoweringObjectFile.h"
51 #include "llvm/Target/TargetMachine.h"
52 #include "llvm/Target/TargetOptions.h"
53 #include "llvm/Target/TargetRegisterInfo.h"
54 #include "llvm/Target/TargetSubtargetInfo.h"
55 using namespace llvm;
56
57 #define DEBUG_TYPE "dwarfdebug"
58
59 static cl::opt<bool>
60 DisableDebugInfoPrinting("disable-debug-info-print", cl::Hidden,
61                          cl::desc("Disable debug info printing"));
62
63 static cl::opt<bool> UnknownLocations(
64     "use-unknown-locations", cl::Hidden,
65     cl::desc("Make an absence of debug location information explicit."),
66     cl::init(false));
67
68 static cl::opt<bool>
69 GenerateGnuPubSections("generate-gnu-dwarf-pub-sections", cl::Hidden,
70                        cl::desc("Generate GNU-style pubnames and pubtypes"),
71                        cl::init(false));
72
73 static cl::opt<bool> GenerateARangeSection("generate-arange-section",
74                                            cl::Hidden,
75                                            cl::desc("Generate dwarf aranges"),
76                                            cl::init(false));
77
78 namespace {
79 enum DefaultOnOff { Default, Enable, Disable };
80 }
81
82 static cl::opt<DefaultOnOff>
83 DwarfAccelTables("dwarf-accel-tables", cl::Hidden,
84                  cl::desc("Output prototype dwarf accelerator tables."),
85                  cl::values(clEnumVal(Default, "Default for platform"),
86                             clEnumVal(Enable, "Enabled"),
87                             clEnumVal(Disable, "Disabled"), clEnumValEnd),
88                  cl::init(Default));
89
90 static cl::opt<DefaultOnOff>
91 SplitDwarf("split-dwarf", cl::Hidden,
92            cl::desc("Output DWARF5 split debug info."),
93            cl::values(clEnumVal(Default, "Default for platform"),
94                       clEnumVal(Enable, "Enabled"),
95                       clEnumVal(Disable, "Disabled"), clEnumValEnd),
96            cl::init(Default));
97
98 static cl::opt<DefaultOnOff>
99 DwarfPubSections("generate-dwarf-pub-sections", cl::Hidden,
100                  cl::desc("Generate DWARF pubnames and pubtypes sections"),
101                  cl::values(clEnumVal(Default, "Default for platform"),
102                             clEnumVal(Enable, "Enabled"),
103                             clEnumVal(Disable, "Disabled"), clEnumValEnd),
104                  cl::init(Default));
105
106 static const char *const DWARFGroupName = "DWARF Emission";
107 static const char *const DbgTimerName = "DWARF Debug Writer";
108
109 void DebugLocDwarfExpression::EmitOp(uint8_t Op, const char *Comment) {
110   BS.EmitInt8(
111       Op, Comment ? Twine(Comment) + " " + dwarf::OperationEncodingString(Op)
112                   : dwarf::OperationEncodingString(Op));
113 }
114
115 void DebugLocDwarfExpression::EmitSigned(int64_t Value) {
116   BS.EmitSLEB128(Value, Twine(Value));
117 }
118
119 void DebugLocDwarfExpression::EmitUnsigned(uint64_t Value) {
120   BS.EmitULEB128(Value, Twine(Value));
121 }
122
123 bool DebugLocDwarfExpression::isFrameRegister(unsigned MachineReg) {
124   // This information is not available while emitting .debug_loc entries.
125   return false;
126 }
127
128 //===----------------------------------------------------------------------===//
129
130 /// resolve - Look in the DwarfDebug map for the MDNode that
131 /// corresponds to the reference.
132 template <typename T> T DbgVariable::resolve(DIRef<T> Ref) const {
133   return DD->resolve(Ref);
134 }
135
136 bool DbgVariable::isBlockByrefVariable() const {
137   assert(Var && "Invalid complex DbgVariable!");
138   return Var->getType()
139       .resolve(DD->getTypeIdentifierMap())
140       ->isBlockByrefStruct();
141 }
142
143 DIType DbgVariable::getType() const {
144   DIType Ty = Var->getType().resolve(DD->getTypeIdentifierMap());
145   // FIXME: isBlockByrefVariable should be reformulated in terms of complex
146   // addresses instead.
147   if (Ty->isBlockByrefStruct()) {
148     /* Byref variables, in Blocks, are declared by the programmer as
149        "SomeType VarName;", but the compiler creates a
150        __Block_byref_x_VarName struct, and gives the variable VarName
151        either the struct, or a pointer to the struct, as its type.  This
152        is necessary for various behind-the-scenes things the compiler
153        needs to do with by-reference variables in blocks.
154
155        However, as far as the original *programmer* is concerned, the
156        variable should still have type 'SomeType', as originally declared.
157
158        The following function dives into the __Block_byref_x_VarName
159        struct to find the original type of the variable.  This will be
160        passed back to the code generating the type for the Debug
161        Information Entry for the variable 'VarName'.  'VarName' will then
162        have the original type 'SomeType' in its debug information.
163
164        The original type 'SomeType' will be the type of the field named
165        'VarName' inside the __Block_byref_x_VarName struct.
166
167        NOTE: In order for this to not completely fail on the debugger
168        side, the Debug Information Entry for the variable VarName needs to
169        have a DW_AT_location that tells the debugger how to unwind through
170        the pointers and __Block_byref_x_VarName struct to find the actual
171        value of the variable.  The function addBlockByrefType does this.  */
172     DIType subType = Ty;
173     uint16_t tag = Ty.getTag();
174
175     if (tag == dwarf::DW_TAG_pointer_type)
176       subType = resolve(DITypeRef(cast<MDDerivedType>(Ty)->getBaseType()));
177
178     DIArray Elements(cast<MDCompositeTypeBase>(subType)->getElements());
179     for (unsigned i = 0, N = Elements.size(); i < N; ++i) {
180       DIDerivedType DT = cast<MDDerivedTypeBase>(Elements[i]);
181       if (getName() == DT.getName())
182         return (resolve(DT.getTypeDerivedFrom()));
183     }
184   }
185   return Ty;
186 }
187
188 static LLVM_CONSTEXPR DwarfAccelTable::Atom TypeAtoms[] = {
189     DwarfAccelTable::Atom(dwarf::DW_ATOM_die_offset, dwarf::DW_FORM_data4),
190     DwarfAccelTable::Atom(dwarf::DW_ATOM_die_tag, dwarf::DW_FORM_data2),
191     DwarfAccelTable::Atom(dwarf::DW_ATOM_type_flags, dwarf::DW_FORM_data1)};
192
193 DwarfDebug::DwarfDebug(AsmPrinter *A, Module *M)
194     : Asm(A), MMI(Asm->MMI), PrevLabel(nullptr),
195       InfoHolder(A, "info_string", DIEValueAllocator),
196       UsedNonDefaultText(false),
197       SkeletonHolder(A, "skel_string", DIEValueAllocator),
198       IsDarwin(Triple(A->getTargetTriple()).isOSDarwin()),
199       IsPS4(Triple(A->getTargetTriple()).isPS4()),
200       AccelNames(DwarfAccelTable::Atom(dwarf::DW_ATOM_die_offset,
201                                        dwarf::DW_FORM_data4)),
202       AccelObjC(DwarfAccelTable::Atom(dwarf::DW_ATOM_die_offset,
203                                       dwarf::DW_FORM_data4)),
204       AccelNamespace(DwarfAccelTable::Atom(dwarf::DW_ATOM_die_offset,
205                                            dwarf::DW_FORM_data4)),
206       AccelTypes(TypeAtoms) {
207
208   CurFn = nullptr;
209   CurMI = nullptr;
210
211   // Turn on accelerator tables for Darwin by default, pubnames by
212   // default for non-Darwin/PS4, and handle split dwarf.
213   if (DwarfAccelTables == Default)
214     HasDwarfAccelTables = IsDarwin;
215   else
216     HasDwarfAccelTables = DwarfAccelTables == Enable;
217
218   if (SplitDwarf == Default)
219     HasSplitDwarf = false;
220   else
221     HasSplitDwarf = SplitDwarf == Enable;
222
223   if (DwarfPubSections == Default)
224     HasDwarfPubSections = !IsDarwin && !IsPS4;
225   else
226     HasDwarfPubSections = DwarfPubSections == Enable;
227
228   unsigned DwarfVersionNumber = Asm->TM.Options.MCOptions.DwarfVersion;
229   DwarfVersion = DwarfVersionNumber ? DwarfVersionNumber
230                                     : MMI->getModule()->getDwarfVersion();
231
232   // Darwin and PS4 use the standard TLS opcode (defined in DWARF 3).
233   // Everybody else uses GNU's.
234   UseGNUTLSOpcode = !(IsDarwin || IsPS4) || DwarfVersion < 3;
235
236   Asm->OutStreamer.getContext().setDwarfVersion(DwarfVersion);
237
238   {
239     NamedRegionTimer T(DbgTimerName, DWARFGroupName, TimePassesIsEnabled);
240     beginModule();
241   }
242 }
243
244 // Define out of line so we don't have to include DwarfUnit.h in DwarfDebug.h.
245 DwarfDebug::~DwarfDebug() { }
246
247 static bool isObjCClass(StringRef Name) {
248   return Name.startswith("+") || Name.startswith("-");
249 }
250
251 static bool hasObjCCategory(StringRef Name) {
252   if (!isObjCClass(Name))
253     return false;
254
255   return Name.find(") ") != StringRef::npos;
256 }
257
258 static void getObjCClassCategory(StringRef In, StringRef &Class,
259                                  StringRef &Category) {
260   if (!hasObjCCategory(In)) {
261     Class = In.slice(In.find('[') + 1, In.find(' '));
262     Category = "";
263     return;
264   }
265
266   Class = In.slice(In.find('[') + 1, In.find('('));
267   Category = In.slice(In.find('[') + 1, In.find(' '));
268   return;
269 }
270
271 static StringRef getObjCMethodName(StringRef In) {
272   return In.slice(In.find(' ') + 1, In.find(']'));
273 }
274
275 // Add the various names to the Dwarf accelerator table names.
276 // TODO: Determine whether or not we should add names for programs
277 // that do not have a DW_AT_name or DW_AT_linkage_name field - this
278 // is only slightly different than the lookup of non-standard ObjC names.
279 void DwarfDebug::addSubprogramNames(DISubprogram SP, DIE &Die) {
280   if (!SP->isDefinition())
281     return;
282   addAccelName(SP->getName(), Die);
283
284   // If the linkage name is different than the name, go ahead and output
285   // that as well into the name table.
286   if (SP->getLinkageName() != "" && SP->getName() != SP->getLinkageName())
287     addAccelName(SP->getLinkageName(), Die);
288
289   // If this is an Objective-C selector name add it to the ObjC accelerator
290   // too.
291   if (isObjCClass(SP->getName())) {
292     StringRef Class, Category;
293     getObjCClassCategory(SP->getName(), Class, Category);
294     addAccelObjC(Class, Die);
295     if (Category != "")
296       addAccelObjC(Category, Die);
297     // Also add the base method name to the name table.
298     addAccelName(getObjCMethodName(SP->getName()), Die);
299   }
300 }
301
302 /// isSubprogramContext - Return true if Context is either a subprogram
303 /// or another context nested inside a subprogram.
304 bool DwarfDebug::isSubprogramContext(const MDNode *Context) {
305   if (!Context)
306     return false;
307   if (isa<MDSubprogram>(Context))
308     return true;
309   if (DIType T = dyn_cast<MDType>(Context))
310     return isSubprogramContext(resolve(T.getContext()));
311   return false;
312 }
313
314 /// Check whether we should create a DIE for the given Scope, return true
315 /// if we don't create a DIE (the corresponding DIE is null).
316 bool DwarfDebug::isLexicalScopeDIENull(LexicalScope *Scope) {
317   if (Scope->isAbstractScope())
318     return false;
319
320   // We don't create a DIE if there is no Range.
321   const SmallVectorImpl<InsnRange> &Ranges = Scope->getRanges();
322   if (Ranges.empty())
323     return true;
324
325   if (Ranges.size() > 1)
326     return false;
327
328   // We don't create a DIE if we have a single Range and the end label
329   // is null.
330   return !getLabelAfterInsn(Ranges.front().second);
331 }
332
333 template <typename Func> void forBothCUs(DwarfCompileUnit &CU, Func F) {
334   F(CU);
335   if (auto *SkelCU = CU.getSkeleton())
336     F(*SkelCU);
337 }
338
339 void DwarfDebug::constructAbstractSubprogramScopeDIE(LexicalScope *Scope) {
340   assert(Scope && Scope->getScopeNode());
341   assert(Scope->isAbstractScope());
342   assert(!Scope->getInlinedAt());
343
344   const MDNode *SP = Scope->getScopeNode();
345
346   ProcessedSPNodes.insert(SP);
347
348   // Find the subprogram's DwarfCompileUnit in the SPMap in case the subprogram
349   // was inlined from another compile unit.
350   auto &CU = SPMap[SP];
351   forBothCUs(*CU, [&](DwarfCompileUnit &CU) {
352     CU.constructAbstractSubprogramScopeDIE(Scope);
353   });
354 }
355
356 void DwarfDebug::addGnuPubAttributes(DwarfUnit &U, DIE &D) const {
357   if (!GenerateGnuPubSections)
358     return;
359
360   U.addFlag(D, dwarf::DW_AT_GNU_pubnames);
361 }
362
363 // Create new DwarfCompileUnit for the given metadata node with tag
364 // DW_TAG_compile_unit.
365 DwarfCompileUnit &DwarfDebug::constructDwarfCompileUnit(DICompileUnit DIUnit) {
366   StringRef FN = DIUnit.getFilename();
367   CompilationDir = DIUnit.getDirectory();
368
369   auto OwnedUnit = make_unique<DwarfCompileUnit>(
370       InfoHolder.getUnits().size(), DIUnit, Asm, this, &InfoHolder);
371   DwarfCompileUnit &NewCU = *OwnedUnit;
372   DIE &Die = NewCU.getUnitDie();
373   InfoHolder.addUnit(std::move(OwnedUnit));
374   if (useSplitDwarf())
375     NewCU.setSkeleton(constructSkeletonCU(NewCU));
376
377   // LTO with assembly output shares a single line table amongst multiple CUs.
378   // To avoid the compilation directory being ambiguous, let the line table
379   // explicitly describe the directory of all files, never relying on the
380   // compilation directory.
381   if (!Asm->OutStreamer.hasRawTextSupport() || SingleCU)
382     Asm->OutStreamer.getContext().setMCLineTableCompilationDir(
383         NewCU.getUniqueID(), CompilationDir);
384
385   NewCU.addString(Die, dwarf::DW_AT_producer, DIUnit.getProducer());
386   NewCU.addUInt(Die, dwarf::DW_AT_language, dwarf::DW_FORM_data2,
387                 DIUnit.getLanguage());
388   NewCU.addString(Die, dwarf::DW_AT_name, FN);
389
390   if (!useSplitDwarf()) {
391     NewCU.initStmtList();
392
393     // If we're using split dwarf the compilation dir is going to be in the
394     // skeleton CU and so we don't need to duplicate it here.
395     if (!CompilationDir.empty())
396       NewCU.addString(Die, dwarf::DW_AT_comp_dir, CompilationDir);
397
398     addGnuPubAttributes(NewCU, Die);
399   }
400
401   if (DIUnit.isOptimized())
402     NewCU.addFlag(Die, dwarf::DW_AT_APPLE_optimized);
403
404   StringRef Flags = DIUnit.getFlags();
405   if (!Flags.empty())
406     NewCU.addString(Die, dwarf::DW_AT_APPLE_flags, Flags);
407
408   if (unsigned RVer = DIUnit.getRunTimeVersion())
409     NewCU.addUInt(Die, dwarf::DW_AT_APPLE_major_runtime_vers,
410                   dwarf::DW_FORM_data1, RVer);
411
412   if (useSplitDwarf())
413     NewCU.initSection(Asm->getObjFileLowering().getDwarfInfoDWOSection());
414   else
415     NewCU.initSection(Asm->getObjFileLowering().getDwarfInfoSection());
416
417   CUMap.insert(std::make_pair(DIUnit, &NewCU));
418   CUDieMap.insert(std::make_pair(&Die, &NewCU));
419   return NewCU;
420 }
421
422 void DwarfDebug::constructAndAddImportedEntityDIE(DwarfCompileUnit &TheCU,
423                                                   const MDNode *N) {
424   DIImportedEntity Module = cast<MDImportedEntity>(N);
425   if (DIE *D = TheCU.getOrCreateContextDIE(Module->getScope()))
426     D->addChild(TheCU.constructImportedEntityDIE(Module));
427 }
428
429 // Emit all Dwarf sections that should come prior to the content. Create
430 // global DIEs and emit initial debug info sections. This is invoked by
431 // the target AsmPrinter.
432 void DwarfDebug::beginModule() {
433   if (DisableDebugInfoPrinting)
434     return;
435
436   const Module *M = MMI->getModule();
437
438   FunctionDIs = makeSubprogramMap(*M);
439
440   NamedMDNode *CU_Nodes = M->getNamedMetadata("llvm.dbg.cu");
441   if (!CU_Nodes)
442     return;
443   TypeIdentifierMap = generateDITypeIdentifierMap(CU_Nodes);
444
445   SingleCU = CU_Nodes->getNumOperands() == 1;
446
447   for (MDNode *N : CU_Nodes->operands()) {
448     DICompileUnit CUNode = cast<MDCompileUnit>(N);
449     DwarfCompileUnit &CU = constructDwarfCompileUnit(CUNode);
450     for (auto *IE : CUNode->getImportedEntities())
451       ScopesWithImportedEntities.push_back(std::make_pair(IE->getScope(), IE));
452     // Stable sort to preserve the order of appearance of imported entities.
453     // This is to avoid out-of-order processing of interdependent declarations
454     // within the same scope, e.g. { namespace A = base; namespace B = A; }
455     std::stable_sort(ScopesWithImportedEntities.begin(),
456                      ScopesWithImportedEntities.end(), less_first());
457     for (auto *GV : CUNode->getGlobalVariables())
458       CU.getOrCreateGlobalVariableDIE(GV);
459     for (auto *SP : CUNode->getSubprograms())
460       SPMap.insert(std::make_pair(SP, &CU));
461     for (DIType Ty : CUNode->getEnumTypes()) {
462       // The enum types array by design contains pointers to
463       // MDNodes rather than DIRefs. Unique them here.
464       DIType UniqueTy = cast<MDType>(resolve(Ty.getRef()));
465       CU.getOrCreateTypeDIE(UniqueTy);
466     }
467     for (DIType Ty : CUNode->getRetainedTypes()) {
468       // The retained types array by design contains pointers to
469       // MDNodes rather than DIRefs. Unique them here.
470       DIType UniqueTy = cast<MDType>(resolve(Ty.getRef()));
471       CU.getOrCreateTypeDIE(UniqueTy);
472     }
473     // Emit imported_modules last so that the relevant context is already
474     // available.
475     for (auto *IE : CUNode->getImportedEntities())
476       constructAndAddImportedEntityDIE(CU, IE);
477   }
478
479   // Tell MMI that we have debug info.
480   MMI->setDebugInfoAvailability(true);
481 }
482
483 void DwarfDebug::finishVariableDefinitions() {
484   for (const auto &Var : ConcreteVariables) {
485     DIE *VariableDie = Var->getDIE();
486     assert(VariableDie);
487     // FIXME: Consider the time-space tradeoff of just storing the unit pointer
488     // in the ConcreteVariables list, rather than looking it up again here.
489     // DIE::getUnit isn't simple - it walks parent pointers, etc.
490     DwarfCompileUnit *Unit = lookupUnit(VariableDie->getUnit());
491     assert(Unit);
492     DbgVariable *AbsVar = getExistingAbstractVariable(
493         InlinedVariable(Var->getVariable(), Var->getInlinedAt()));
494     if (AbsVar && AbsVar->getDIE()) {
495       Unit->addDIEEntry(*VariableDie, dwarf::DW_AT_abstract_origin,
496                         *AbsVar->getDIE());
497     } else
498       Unit->applyVariableAttributes(*Var, *VariableDie);
499   }
500 }
501
502 void DwarfDebug::finishSubprogramDefinitions() {
503   for (const auto &P : SPMap)
504     forBothCUs(*P.second, [&](DwarfCompileUnit &CU) {
505       CU.finishSubprogramDefinition(cast<MDSubprogram>(P.first));
506     });
507 }
508
509
510 // Collect info for variables that were optimized out.
511 void DwarfDebug::collectDeadVariables() {
512   const Module *M = MMI->getModule();
513
514   if (NamedMDNode *CU_Nodes = M->getNamedMetadata("llvm.dbg.cu")) {
515     for (MDNode *N : CU_Nodes->operands()) {
516       DICompileUnit TheCU = cast<MDCompileUnit>(N);
517       // Construct subprogram DIE and add variables DIEs.
518       DwarfCompileUnit *SPCU =
519           static_cast<DwarfCompileUnit *>(CUMap.lookup(TheCU));
520       assert(SPCU && "Unable to find Compile Unit!");
521       for (auto *SP : TheCU->getSubprograms()) {
522         if (ProcessedSPNodes.count(SP) != 0)
523           continue;
524         SPCU->collectDeadVariables(SP);
525       }
526     }
527   }
528 }
529
530 void DwarfDebug::finalizeModuleInfo() {
531   const TargetLoweringObjectFile &TLOF = Asm->getObjFileLowering();
532
533   finishSubprogramDefinitions();
534
535   finishVariableDefinitions();
536
537   // Collect info for variables that were optimized out.
538   collectDeadVariables();
539
540   // Handle anything that needs to be done on a per-unit basis after
541   // all other generation.
542   for (const auto &P : CUMap) {
543     auto &TheCU = *P.second;
544     // Emit DW_AT_containing_type attribute to connect types with their
545     // vtable holding type.
546     TheCU.constructContainingTypeDIEs();
547
548     // Add CU specific attributes if we need to add any.
549     // If we're splitting the dwarf out now that we've got the entire
550     // CU then add the dwo id to it.
551     auto *SkCU = TheCU.getSkeleton();
552     if (useSplitDwarf()) {
553       // Emit a unique identifier for this CU.
554       uint64_t ID = DIEHash(Asm).computeCUSignature(TheCU.getUnitDie());
555       TheCU.addUInt(TheCU.getUnitDie(), dwarf::DW_AT_GNU_dwo_id,
556                     dwarf::DW_FORM_data8, ID);
557       SkCU->addUInt(SkCU->getUnitDie(), dwarf::DW_AT_GNU_dwo_id,
558                     dwarf::DW_FORM_data8, ID);
559
560       // We don't keep track of which addresses are used in which CU so this
561       // is a bit pessimistic under LTO.
562       if (!AddrPool.isEmpty()) {
563         const MCSymbol *Sym = TLOF.getDwarfAddrSection()->getBeginSymbol();
564         SkCU->addSectionLabel(SkCU->getUnitDie(), dwarf::DW_AT_GNU_addr_base,
565                               Sym, Sym);
566       }
567       if (!SkCU->getRangeLists().empty()) {
568         const MCSymbol *Sym = TLOF.getDwarfRangesSection()->getBeginSymbol();
569         SkCU->addSectionLabel(SkCU->getUnitDie(), dwarf::DW_AT_GNU_ranges_base,
570                               Sym, Sym);
571       }
572     }
573
574     // If we have code split among multiple sections or non-contiguous
575     // ranges of code then emit a DW_AT_ranges attribute on the unit that will
576     // remain in the .o file, otherwise add a DW_AT_low_pc.
577     // FIXME: We should use ranges allow reordering of code ala
578     // .subsections_via_symbols in mach-o. This would mean turning on
579     // ranges for all subprogram DIEs for mach-o.
580     DwarfCompileUnit &U = SkCU ? *SkCU : TheCU;
581     if (unsigned NumRanges = TheCU.getRanges().size()) {
582       if (NumRanges > 1)
583         // A DW_AT_low_pc attribute may also be specified in combination with
584         // DW_AT_ranges to specify the default base address for use in
585         // location lists (see Section 2.6.2) and range lists (see Section
586         // 2.17.3).
587         U.addUInt(U.getUnitDie(), dwarf::DW_AT_low_pc, dwarf::DW_FORM_addr, 0);
588       else
589         TheCU.setBaseAddress(TheCU.getRanges().front().getStart());
590       U.attachRangesOrLowHighPC(U.getUnitDie(), TheCU.takeRanges());
591     }
592   }
593
594   // Compute DIE offsets and sizes.
595   InfoHolder.computeSizeAndOffsets();
596   if (useSplitDwarf())
597     SkeletonHolder.computeSizeAndOffsets();
598 }
599
600 // Emit all Dwarf sections that should come after the content.
601 void DwarfDebug::endModule() {
602   assert(CurFn == nullptr);
603   assert(CurMI == nullptr);
604
605   // If we aren't actually generating debug info (check beginModule -
606   // conditionalized on !DisableDebugInfoPrinting and the presence of the
607   // llvm.dbg.cu metadata node)
608   if (!MMI->hasDebugInfo())
609     return;
610
611   // Finalize the debug info for the module.
612   finalizeModuleInfo();
613
614   emitDebugStr();
615
616   if (useSplitDwarf())
617     emitDebugLocDWO();
618   else
619     // Emit info into a debug loc section.
620     emitDebugLoc();
621
622   // Corresponding abbreviations into a abbrev section.
623   emitAbbreviations();
624
625   // Emit all the DIEs into a debug info section.
626   emitDebugInfo();
627
628   // Emit info into a debug aranges section.
629   if (GenerateARangeSection)
630     emitDebugARanges();
631
632   // Emit info into a debug ranges section.
633   emitDebugRanges();
634
635   if (useSplitDwarf()) {
636     emitDebugStrDWO();
637     emitDebugInfoDWO();
638     emitDebugAbbrevDWO();
639     emitDebugLineDWO();
640     // Emit DWO addresses.
641     AddrPool.emit(*Asm, Asm->getObjFileLowering().getDwarfAddrSection());
642   }
643
644   // Emit info into the dwarf accelerator table sections.
645   if (useDwarfAccelTables()) {
646     emitAccelNames();
647     emitAccelObjC();
648     emitAccelNamespaces();
649     emitAccelTypes();
650   }
651
652   // Emit the pubnames and pubtypes sections if requested.
653   if (HasDwarfPubSections) {
654     emitDebugPubNames(GenerateGnuPubSections);
655     emitDebugPubTypes(GenerateGnuPubSections);
656   }
657
658   // clean up.
659   SPMap.clear();
660   AbstractVariables.clear();
661 }
662
663 // Find abstract variable, if any, associated with Var.
664 DbgVariable *DwarfDebug::getExistingAbstractVariable(InlinedVariable IV,
665                                                      DIVariable &Cleansed) {
666   // More then one inlined variable corresponds to one abstract variable.
667   Cleansed = IV.first;
668   auto I = AbstractVariables.find(Cleansed);
669   if (I != AbstractVariables.end())
670     return I->second.get();
671   return nullptr;
672 }
673
674 DbgVariable *DwarfDebug::getExistingAbstractVariable(InlinedVariable IV) {
675   DIVariable Cleansed;
676   return getExistingAbstractVariable(IV, Cleansed);
677 }
678
679 void DwarfDebug::createAbstractVariable(const DIVariable &Var,
680                                         LexicalScope *Scope) {
681   auto AbsDbgVariable =
682       make_unique<DbgVariable>(Var, nullptr, DIExpression(), this);
683   InfoHolder.addScopeVariable(Scope, AbsDbgVariable.get());
684   AbstractVariables[Var] = std::move(AbsDbgVariable);
685 }
686
687 void DwarfDebug::ensureAbstractVariableIsCreated(InlinedVariable IV,
688                                                  const MDNode *ScopeNode) {
689   DIVariable Cleansed;
690   if (getExistingAbstractVariable(IV, Cleansed))
691     return;
692
693   createAbstractVariable(Cleansed, LScopes.getOrCreateAbstractScope(
694                                        cast<MDLocalScope>(ScopeNode)));
695 }
696
697 void DwarfDebug::ensureAbstractVariableIsCreatedIfScoped(
698     InlinedVariable IV, const MDNode *ScopeNode) {
699   DIVariable Cleansed;
700   if (getExistingAbstractVariable(IV, Cleansed))
701     return;
702
703   if (LexicalScope *Scope =
704           LScopes.findAbstractScope(cast_or_null<MDLocalScope>(ScopeNode)))
705     createAbstractVariable(Cleansed, Scope);
706 }
707
708 // Collect variable information from side table maintained by MMI.
709 void DwarfDebug::collectVariableInfoFromMMITable(
710     DenseSet<InlinedVariable> &Processed) {
711   for (const auto &VI : MMI->getVariableDbgInfo()) {
712     if (!VI.Var)
713       continue;
714     InlinedVariable Var(VI.Var, VI.Loc ? VI.Loc->getInlinedAt() : nullptr);
715     Processed.insert(Var);
716     LexicalScope *Scope = LScopes.findLexicalScope(VI.Loc);
717
718     // If variable scope is not found then skip this variable.
719     if (!Scope)
720       continue;
721
722     assert(VI.Var->isValidLocationForIntrinsic(VI.Loc) &&
723            "Expected inlined-at fields to agree");
724     DIExpression Expr = cast_or_null<MDExpression>(VI.Expr);
725     ensureAbstractVariableIsCreatedIfScoped(Var, Scope->getScopeNode());
726     auto RegVar =
727         make_unique<DbgVariable>(Var.first, Var.second, Expr, this, VI.Slot);
728     if (InfoHolder.addScopeVariable(Scope, RegVar.get()))
729       ConcreteVariables.push_back(std::move(RegVar));
730   }
731 }
732
733 // Get .debug_loc entry for the instruction range starting at MI.
734 static DebugLocEntry::Value getDebugLocValue(const MachineInstr *MI) {
735   const MDNode *Expr = MI->getDebugExpression();
736   const MDNode *Var = MI->getDebugVariable();
737
738   assert(MI->getNumOperands() == 4);
739   if (MI->getOperand(0).isReg()) {
740     MachineLocation MLoc;
741     // If the second operand is an immediate, this is a
742     // register-indirect address.
743     if (!MI->getOperand(1).isImm())
744       MLoc.set(MI->getOperand(0).getReg());
745     else
746       MLoc.set(MI->getOperand(0).getReg(), MI->getOperand(1).getImm());
747     return DebugLocEntry::Value(Var, Expr, MLoc);
748   }
749   if (MI->getOperand(0).isImm())
750     return DebugLocEntry::Value(Var, Expr, MI->getOperand(0).getImm());
751   if (MI->getOperand(0).isFPImm())
752     return DebugLocEntry::Value(Var, Expr, MI->getOperand(0).getFPImm());
753   if (MI->getOperand(0).isCImm())
754     return DebugLocEntry::Value(Var, Expr, MI->getOperand(0).getCImm());
755
756   llvm_unreachable("Unexpected 4-operand DBG_VALUE instruction!");
757 }
758
759 /// Determine whether two variable pieces overlap.
760 static bool piecesOverlap(DIExpression P1, DIExpression P2) {
761   if (!P1->isBitPiece() || !P2->isBitPiece())
762     return true;
763   unsigned l1 = P1->getBitPieceOffset();
764   unsigned l2 = P2->getBitPieceOffset();
765   unsigned r1 = l1 + P1->getBitPieceSize();
766   unsigned r2 = l2 + P2->getBitPieceSize();
767   // True where [l1,r1[ and [r1,r2[ overlap.
768   return (l1 < r2) && (l2 < r1);
769 }
770
771 /// Build the location list for all DBG_VALUEs in the function that
772 /// describe the same variable.  If the ranges of several independent
773 /// pieces of the same variable overlap partially, split them up and
774 /// combine the ranges. The resulting DebugLocEntries are will have
775 /// strict monotonically increasing begin addresses and will never
776 /// overlap.
777 //
778 // Input:
779 //
780 //   Ranges History [var, loc, piece ofs size]
781 // 0 |      [x, (reg0, piece 0, 32)]
782 // 1 | |    [x, (reg1, piece 32, 32)] <- IsPieceOfPrevEntry
783 // 2 | |    ...
784 // 3   |    [clobber reg0]
785 // 4        [x, (mem, piece 0, 64)] <- overlapping with both previous pieces of
786 //                                     x.
787 //
788 // Output:
789 //
790 // [0-1]    [x, (reg0, piece  0, 32)]
791 // [1-3]    [x, (reg0, piece  0, 32), (reg1, piece 32, 32)]
792 // [3-4]    [x, (reg1, piece 32, 32)]
793 // [4- ]    [x, (mem,  piece  0, 64)]
794 void
795 DwarfDebug::buildLocationList(SmallVectorImpl<DebugLocEntry> &DebugLoc,
796                               const DbgValueHistoryMap::InstrRanges &Ranges) {
797   SmallVector<DebugLocEntry::Value, 4> OpenRanges;
798
799   for (auto I = Ranges.begin(), E = Ranges.end(); I != E; ++I) {
800     const MachineInstr *Begin = I->first;
801     const MachineInstr *End = I->second;
802     assert(Begin->isDebugValue() && "Invalid History entry");
803
804     // Check if a variable is inaccessible in this range.
805     if (Begin->getNumOperands() > 1 &&
806         Begin->getOperand(0).isReg() && !Begin->getOperand(0).getReg()) {
807       OpenRanges.clear();
808       continue;
809     }
810
811     // If this piece overlaps with any open ranges, truncate them.
812     DIExpression DIExpr = Begin->getDebugExpression();
813     auto Last = std::remove_if(OpenRanges.begin(), OpenRanges.end(),
814                                [&](DebugLocEntry::Value R) {
815       return piecesOverlap(DIExpr, R.getExpression());
816     });
817     OpenRanges.erase(Last, OpenRanges.end());
818
819     const MCSymbol *StartLabel = getLabelBeforeInsn(Begin);
820     assert(StartLabel && "Forgot label before DBG_VALUE starting a range!");
821
822     const MCSymbol *EndLabel;
823     if (End != nullptr)
824       EndLabel = getLabelAfterInsn(End);
825     else if (std::next(I) == Ranges.end())
826       EndLabel = Asm->getFunctionEnd();
827     else
828       EndLabel = getLabelBeforeInsn(std::next(I)->first);
829     assert(EndLabel && "Forgot label after instruction ending a range!");
830
831     DEBUG(dbgs() << "DotDebugLoc: " << *Begin << "\n");
832
833     auto Value = getDebugLocValue(Begin);
834     DebugLocEntry Loc(StartLabel, EndLabel, Value);
835     bool couldMerge = false;
836
837     // If this is a piece, it may belong to the current DebugLocEntry.
838     if (DIExpr->isBitPiece()) {
839       // Add this value to the list of open ranges.
840       OpenRanges.push_back(Value);
841
842       // Attempt to add the piece to the last entry.
843       if (!DebugLoc.empty())
844         if (DebugLoc.back().MergeValues(Loc))
845           couldMerge = true;
846     }
847
848     if (!couldMerge) {
849       // Need to add a new DebugLocEntry. Add all values from still
850       // valid non-overlapping pieces.
851       if (OpenRanges.size())
852         Loc.addValues(OpenRanges);
853
854       DebugLoc.push_back(std::move(Loc));
855     }
856
857     // Attempt to coalesce the ranges of two otherwise identical
858     // DebugLocEntries.
859     auto CurEntry = DebugLoc.rbegin();
860     auto PrevEntry = std::next(CurEntry);
861     if (PrevEntry != DebugLoc.rend() && PrevEntry->MergeRanges(*CurEntry))
862       DebugLoc.pop_back();
863
864     DEBUG({
865       dbgs() << CurEntry->getValues().size() << " Values:\n";
866       for (auto Value : CurEntry->getValues()) {
867         Value.getVariable()->dump();
868         Value.getExpression()->dump();
869       }
870       dbgs() << "-----\n";
871     });
872   }
873 }
874
875
876 // Find variables for each lexical scope.
877 void DwarfDebug::collectVariableInfo(DwarfCompileUnit &TheCU, DISubprogram SP,
878                                      DenseSet<InlinedVariable> &Processed) {
879   // Grab the variable info that was squirreled away in the MMI side-table.
880   collectVariableInfoFromMMITable(Processed);
881
882   for (const auto &I : DbgValues) {
883     InlinedVariable IV = I.first;
884     if (Processed.count(IV))
885       continue;
886
887     // Instruction ranges, specifying where IV is accessible.
888     const auto &Ranges = I.second;
889     if (Ranges.empty())
890       continue;
891
892     LexicalScope *Scope = nullptr;
893     if (const MDLocation *IA = IV.second)
894       Scope = LScopes.findInlinedScope(IV.first->getScope(), IA);
895     else
896       Scope = LScopes.findLexicalScope(IV.first->getScope());
897     // If variable scope is not found then skip this variable.
898     if (!Scope)
899       continue;
900
901     Processed.insert(IV);
902     const MachineInstr *MInsn = Ranges.front().first;
903     assert(MInsn->isDebugValue() && "History must begin with debug value");
904     ensureAbstractVariableIsCreatedIfScoped(IV, Scope->getScopeNode());
905     ConcreteVariables.push_back(make_unique<DbgVariable>(MInsn, this));
906     DbgVariable *RegVar = ConcreteVariables.back().get();
907     InfoHolder.addScopeVariable(Scope, RegVar);
908
909     // Check if the first DBG_VALUE is valid for the rest of the function.
910     if (Ranges.size() == 1 && Ranges.front().second == nullptr)
911       continue;
912
913     // Handle multiple DBG_VALUE instructions describing one variable.
914     RegVar->setDotDebugLocOffset(DotDebugLocEntries.size());
915
916     DotDebugLocEntries.resize(DotDebugLocEntries.size() + 1);
917     DebugLocList &LocList = DotDebugLocEntries.back();
918     LocList.CU = &TheCU;
919     LocList.Label = Asm->createTempSymbol("debug_loc");
920
921     // Build the location list for this variable.
922     buildLocationList(LocList.List, Ranges);
923     // Finalize the entry by lowering it into a DWARF bytestream.
924     for (auto &Entry : LocList.List)
925       Entry.finalize(*Asm, TypeIdentifierMap);
926   }
927
928   // Collect info for variables that were optimized out.
929   for (DIVariable DV : SP->getVariables()) {
930     if (!Processed.insert(InlinedVariable(DV, nullptr)).second)
931       continue;
932     if (LexicalScope *Scope = LScopes.findLexicalScope(DV->getScope())) {
933       ensureAbstractVariableIsCreatedIfScoped(InlinedVariable(DV, nullptr),
934                                               Scope->getScopeNode());
935       DIExpression NoExpr;
936       ConcreteVariables.push_back(
937           make_unique<DbgVariable>(DV, nullptr, NoExpr, this));
938       InfoHolder.addScopeVariable(Scope, ConcreteVariables.back().get());
939     }
940   }
941 }
942
943 // Return Label preceding the instruction.
944 MCSymbol *DwarfDebug::getLabelBeforeInsn(const MachineInstr *MI) {
945   MCSymbol *Label = LabelsBeforeInsn.lookup(MI);
946   assert(Label && "Didn't insert label before instruction");
947   return Label;
948 }
949
950 // Return Label immediately following the instruction.
951 MCSymbol *DwarfDebug::getLabelAfterInsn(const MachineInstr *MI) {
952   return LabelsAfterInsn.lookup(MI);
953 }
954
955 // Process beginning of an instruction.
956 void DwarfDebug::beginInstruction(const MachineInstr *MI) {
957   assert(CurMI == nullptr);
958   CurMI = MI;
959   // Check if source location changes, but ignore DBG_VALUE locations.
960   if (!MI->isDebugValue()) {
961     DebugLoc DL = MI->getDebugLoc();
962     if (DL != PrevInstLoc) {
963       if (DL) {
964         unsigned Flags = 0;
965         PrevInstLoc = DL;
966         if (DL == PrologEndLoc) {
967           Flags |= DWARF2_FLAG_PROLOGUE_END;
968           PrologEndLoc = DebugLoc();
969           Flags |= DWARF2_FLAG_IS_STMT;
970         }
971         if (DL.getLine() !=
972             Asm->OutStreamer.getContext().getCurrentDwarfLoc().getLine())
973           Flags |= DWARF2_FLAG_IS_STMT;
974
975         const MDNode *Scope = DL.getScope();
976         recordSourceLine(DL.getLine(), DL.getCol(), Scope, Flags);
977       } else if (UnknownLocations) {
978         PrevInstLoc = DL;
979         recordSourceLine(0, 0, nullptr, 0);
980       }
981     }
982   }
983
984   // Insert labels where requested.
985   DenseMap<const MachineInstr *, MCSymbol *>::iterator I =
986       LabelsBeforeInsn.find(MI);
987
988   // No label needed.
989   if (I == LabelsBeforeInsn.end())
990     return;
991
992   // Label already assigned.
993   if (I->second)
994     return;
995
996   if (!PrevLabel) {
997     PrevLabel = MMI->getContext().CreateTempSymbol();
998     Asm->OutStreamer.EmitLabel(PrevLabel);
999   }
1000   I->second = PrevLabel;
1001 }
1002
1003 // Process end of an instruction.
1004 void DwarfDebug::endInstruction() {
1005   assert(CurMI != nullptr);
1006   // Don't create a new label after DBG_VALUE instructions.
1007   // They don't generate code.
1008   if (!CurMI->isDebugValue())
1009     PrevLabel = nullptr;
1010
1011   DenseMap<const MachineInstr *, MCSymbol *>::iterator I =
1012       LabelsAfterInsn.find(CurMI);
1013   CurMI = nullptr;
1014
1015   // No label needed.
1016   if (I == LabelsAfterInsn.end())
1017     return;
1018
1019   // Label already assigned.
1020   if (I->second)
1021     return;
1022
1023   // We need a label after this instruction.
1024   if (!PrevLabel) {
1025     PrevLabel = MMI->getContext().CreateTempSymbol();
1026     Asm->OutStreamer.EmitLabel(PrevLabel);
1027   }
1028   I->second = PrevLabel;
1029 }
1030
1031 // Each LexicalScope has first instruction and last instruction to mark
1032 // beginning and end of a scope respectively. Create an inverse map that list
1033 // scopes starts (and ends) with an instruction. One instruction may start (or
1034 // end) multiple scopes. Ignore scopes that are not reachable.
1035 void DwarfDebug::identifyScopeMarkers() {
1036   SmallVector<LexicalScope *, 4> WorkList;
1037   WorkList.push_back(LScopes.getCurrentFunctionScope());
1038   while (!WorkList.empty()) {
1039     LexicalScope *S = WorkList.pop_back_val();
1040
1041     const SmallVectorImpl<LexicalScope *> &Children = S->getChildren();
1042     if (!Children.empty())
1043       WorkList.append(Children.begin(), Children.end());
1044
1045     if (S->isAbstractScope())
1046       continue;
1047
1048     for (const InsnRange &R : S->getRanges()) {
1049       assert(R.first && "InsnRange does not have first instruction!");
1050       assert(R.second && "InsnRange does not have second instruction!");
1051       requestLabelBeforeInsn(R.first);
1052       requestLabelAfterInsn(R.second);
1053     }
1054   }
1055 }
1056
1057 static DebugLoc findPrologueEndLoc(const MachineFunction *MF) {
1058   // First known non-DBG_VALUE and non-frame setup location marks
1059   // the beginning of the function body.
1060   for (const auto &MBB : *MF)
1061     for (const auto &MI : MBB)
1062       if (!MI.isDebugValue() && !MI.getFlag(MachineInstr::FrameSetup) &&
1063           MI.getDebugLoc()) {
1064         // Did the target forget to set the FrameSetup flag for CFI insns?
1065         assert(!MI.isCFIInstruction() &&
1066                "First non-frame-setup instruction is a CFI instruction.");
1067         return MI.getDebugLoc();
1068       }
1069   return DebugLoc();
1070 }
1071
1072 // Gather pre-function debug information.  Assumes being called immediately
1073 // after the function entry point has been emitted.
1074 void DwarfDebug::beginFunction(const MachineFunction *MF) {
1075   CurFn = MF;
1076
1077   // If there's no debug info for the function we're not going to do anything.
1078   if (!MMI->hasDebugInfo())
1079     return;
1080
1081   auto DI = FunctionDIs.find(MF->getFunction());
1082   if (DI == FunctionDIs.end())
1083     return;
1084
1085   // Grab the lexical scopes for the function, if we don't have any of those
1086   // then we're not going to be able to do anything.
1087   LScopes.initialize(*MF);
1088   if (LScopes.empty())
1089     return;
1090
1091   assert(DbgValues.empty() && "DbgValues map wasn't cleaned!");
1092
1093   // Make sure that each lexical scope will have a begin/end label.
1094   identifyScopeMarkers();
1095
1096   // Set DwarfDwarfCompileUnitID in MCContext to the Compile Unit this function
1097   // belongs to so that we add to the correct per-cu line table in the
1098   // non-asm case.
1099   LexicalScope *FnScope = LScopes.getCurrentFunctionScope();
1100   // FnScope->getScopeNode() and DI->second should represent the same function,
1101   // though they may not be the same MDNode due to inline functions merged in
1102   // LTO where the debug info metadata still differs (either due to distinct
1103   // written differences - two versions of a linkonce_odr function
1104   // written/copied into two separate files, or some sub-optimal metadata that
1105   // isn't structurally identical (see: file path/name info from clang, which
1106   // includes the directory of the cpp file being built, even when the file name
1107   // is absolute (such as an <> lookup header)))
1108   DwarfCompileUnit *TheCU = SPMap.lookup(FnScope->getScopeNode());
1109   assert(TheCU && "Unable to find compile unit!");
1110   if (Asm->OutStreamer.hasRawTextSupport())
1111     // Use a single line table if we are generating assembly.
1112     Asm->OutStreamer.getContext().setDwarfCompileUnitID(0);
1113   else
1114     Asm->OutStreamer.getContext().setDwarfCompileUnitID(TheCU->getUniqueID());
1115
1116   // Calculate history for local variables.
1117   calculateDbgValueHistory(MF, Asm->MF->getSubtarget().getRegisterInfo(),
1118                            DbgValues);
1119
1120   // Request labels for the full history.
1121   for (const auto &I : DbgValues) {
1122     const auto &Ranges = I.second;
1123     if (Ranges.empty())
1124       continue;
1125
1126     // The first mention of a function argument gets the CurrentFnBegin
1127     // label, so arguments are visible when breaking at function entry.
1128     DIVariable DIVar = Ranges.front().first->getDebugVariable();
1129     if (DIVar->getTag() == dwarf::DW_TAG_arg_variable &&
1130         getDISubprogram(DIVar->getScope())->describes(MF->getFunction())) {
1131       LabelsBeforeInsn[Ranges.front().first] = Asm->getFunctionBegin();
1132       if (Ranges.front().first->getDebugExpression()->isBitPiece()) {
1133         // Mark all non-overlapping initial pieces.
1134         for (auto I = Ranges.begin(); I != Ranges.end(); ++I) {
1135           DIExpression Piece = I->first->getDebugExpression();
1136           if (std::all_of(Ranges.begin(), I,
1137                           [&](DbgValueHistoryMap::InstrRange Pred) {
1138                 return !piecesOverlap(Piece, Pred.first->getDebugExpression());
1139               }))
1140             LabelsBeforeInsn[I->first] = Asm->getFunctionBegin();
1141           else
1142             break;
1143         }
1144       }
1145     }
1146
1147     for (const auto &Range : Ranges) {
1148       requestLabelBeforeInsn(Range.first);
1149       if (Range.second)
1150         requestLabelAfterInsn(Range.second);
1151     }
1152   }
1153
1154   PrevInstLoc = DebugLoc();
1155   PrevLabel = Asm->getFunctionBegin();
1156
1157   // Record beginning of function.
1158   PrologEndLoc = findPrologueEndLoc(MF);
1159   if (MDLocation *L = PrologEndLoc) {
1160     // We'd like to list the prologue as "not statements" but GDB behaves
1161     // poorly if we do that. Revisit this with caution/GDB (7.5+) testing.
1162     auto *SP = L->getInlinedAtScope()->getSubprogram();
1163     recordSourceLine(SP->getScopeLine(), 0, SP, DWARF2_FLAG_IS_STMT);
1164   }
1165 }
1166
1167 // Gather and emit post-function debug information.
1168 void DwarfDebug::endFunction(const MachineFunction *MF) {
1169   assert(CurFn == MF &&
1170       "endFunction should be called with the same function as beginFunction");
1171
1172   if (!MMI->hasDebugInfo() || LScopes.empty() ||
1173       !FunctionDIs.count(MF->getFunction())) {
1174     // If we don't have a lexical scope for this function then there will
1175     // be a hole in the range information. Keep note of this by setting the
1176     // previously used section to nullptr.
1177     PrevCU = nullptr;
1178     CurFn = nullptr;
1179     return;
1180   }
1181
1182   // Set DwarfDwarfCompileUnitID in MCContext to default value.
1183   Asm->OutStreamer.getContext().setDwarfCompileUnitID(0);
1184
1185   LexicalScope *FnScope = LScopes.getCurrentFunctionScope();
1186   DISubprogram SP = cast<MDSubprogram>(FnScope->getScopeNode());
1187   DwarfCompileUnit &TheCU = *SPMap.lookup(SP);
1188
1189   DenseSet<InlinedVariable> ProcessedVars;
1190   collectVariableInfo(TheCU, SP, ProcessedVars);
1191
1192   // Add the range of this function to the list of ranges for the CU.
1193   TheCU.addRange(RangeSpan(Asm->getFunctionBegin(), Asm->getFunctionEnd()));
1194
1195   // Under -gmlt, skip building the subprogram if there are no inlined
1196   // subroutines inside it.
1197   if (TheCU.getCUNode().getEmissionKind() == DIBuilder::LineTablesOnly &&
1198       LScopes.getAbstractScopesList().empty() && !IsDarwin) {
1199     assert(InfoHolder.getScopeVariables().empty());
1200     assert(DbgValues.empty());
1201     // FIXME: This wouldn't be true in LTO with a -g (with inlining) CU followed
1202     // by a -gmlt CU. Add a test and remove this assertion.
1203     assert(AbstractVariables.empty());
1204     LabelsBeforeInsn.clear();
1205     LabelsAfterInsn.clear();
1206     PrevLabel = nullptr;
1207     CurFn = nullptr;
1208     return;
1209   }
1210
1211 #ifndef NDEBUG
1212   size_t NumAbstractScopes = LScopes.getAbstractScopesList().size();
1213 #endif
1214   // Construct abstract scopes.
1215   for (LexicalScope *AScope : LScopes.getAbstractScopesList()) {
1216     DISubprogram SP = cast<MDSubprogram>(AScope->getScopeNode());
1217     // Collect info for variables that were optimized out.
1218     for (DIVariable DV : SP->getVariables()) {
1219       if (!ProcessedVars.insert(InlinedVariable(DV, nullptr)).second)
1220         continue;
1221       ensureAbstractVariableIsCreated(InlinedVariable(DV, nullptr),
1222                                       DV->getScope());
1223       assert(LScopes.getAbstractScopesList().size() == NumAbstractScopes
1224              && "ensureAbstractVariableIsCreated inserted abstract scopes");
1225     }
1226     constructAbstractSubprogramScopeDIE(AScope);
1227   }
1228
1229   TheCU.constructSubprogramScopeDIE(FnScope);
1230   if (auto *SkelCU = TheCU.getSkeleton())
1231     if (!LScopes.getAbstractScopesList().empty())
1232       SkelCU->constructSubprogramScopeDIE(FnScope);
1233
1234   // Clear debug info
1235   // Ownership of DbgVariables is a bit subtle - ScopeVariables owns all the
1236   // DbgVariables except those that are also in AbstractVariables (since they
1237   // can be used cross-function)
1238   InfoHolder.getScopeVariables().clear();
1239   DbgValues.clear();
1240   LabelsBeforeInsn.clear();
1241   LabelsAfterInsn.clear();
1242   PrevLabel = nullptr;
1243   CurFn = nullptr;
1244 }
1245
1246 // Register a source line with debug info. Returns the  unique label that was
1247 // emitted and which provides correspondence to the source line list.
1248 void DwarfDebug::recordSourceLine(unsigned Line, unsigned Col, const MDNode *S,
1249                                   unsigned Flags) {
1250   StringRef Fn;
1251   StringRef Dir;
1252   unsigned Src = 1;
1253   unsigned Discriminator = 0;
1254   if (DIScope Scope = cast_or_null<MDScope>(S)) {
1255     Fn = Scope.getFilename();
1256     Dir = Scope.getDirectory();
1257     if (auto *LBF = dyn_cast<MDLexicalBlockFile>(Scope))
1258       Discriminator = LBF->getDiscriminator();
1259
1260     unsigned CUID = Asm->OutStreamer.getContext().getDwarfCompileUnitID();
1261     Src = static_cast<DwarfCompileUnit &>(*InfoHolder.getUnits()[CUID])
1262               .getOrCreateSourceID(Fn, Dir);
1263   }
1264   Asm->OutStreamer.EmitDwarfLocDirective(Src, Line, Col, Flags, 0,
1265                                          Discriminator, Fn);
1266 }
1267
1268 //===----------------------------------------------------------------------===//
1269 // Emit Methods
1270 //===----------------------------------------------------------------------===//
1271
1272 // Emit the debug info section.
1273 void DwarfDebug::emitDebugInfo() {
1274   DwarfFile &Holder = useSplitDwarf() ? SkeletonHolder : InfoHolder;
1275   Holder.emitUnits(/* UseOffsets */ false);
1276 }
1277
1278 // Emit the abbreviation section.
1279 void DwarfDebug::emitAbbreviations() {
1280   DwarfFile &Holder = useSplitDwarf() ? SkeletonHolder : InfoHolder;
1281
1282   Holder.emitAbbrevs(Asm->getObjFileLowering().getDwarfAbbrevSection());
1283 }
1284
1285 void DwarfDebug::emitAccel(DwarfAccelTable &Accel, const MCSection *Section,
1286                            StringRef TableName) {
1287   Accel.FinalizeTable(Asm, TableName);
1288   Asm->OutStreamer.SwitchSection(Section);
1289
1290   // Emit the full data.
1291   Accel.emit(Asm, Section->getBeginSymbol(), this);
1292 }
1293
1294 // Emit visible names into a hashed accelerator table section.
1295 void DwarfDebug::emitAccelNames() {
1296   emitAccel(AccelNames, Asm->getObjFileLowering().getDwarfAccelNamesSection(),
1297             "Names");
1298 }
1299
1300 // Emit objective C classes and categories into a hashed accelerator table
1301 // section.
1302 void DwarfDebug::emitAccelObjC() {
1303   emitAccel(AccelObjC, Asm->getObjFileLowering().getDwarfAccelObjCSection(),
1304             "ObjC");
1305 }
1306
1307 // Emit namespace dies into a hashed accelerator table.
1308 void DwarfDebug::emitAccelNamespaces() {
1309   emitAccel(AccelNamespace,
1310             Asm->getObjFileLowering().getDwarfAccelNamespaceSection(),
1311             "namespac");
1312 }
1313
1314 // Emit type dies into a hashed accelerator table.
1315 void DwarfDebug::emitAccelTypes() {
1316   emitAccel(AccelTypes, Asm->getObjFileLowering().getDwarfAccelTypesSection(),
1317             "types");
1318 }
1319
1320 // Public name handling.
1321 // The format for the various pubnames:
1322 //
1323 // dwarf pubnames - offset/name pairs where the offset is the offset into the CU
1324 // for the DIE that is named.
1325 //
1326 // gnu pubnames - offset/index value/name tuples where the offset is the offset
1327 // into the CU and the index value is computed according to the type of value
1328 // for the DIE that is named.
1329 //
1330 // For type units the offset is the offset of the skeleton DIE. For split dwarf
1331 // it's the offset within the debug_info/debug_types dwo section, however, the
1332 // reference in the pubname header doesn't change.
1333
1334 /// computeIndexValue - Compute the gdb index value for the DIE and CU.
1335 static dwarf::PubIndexEntryDescriptor computeIndexValue(DwarfUnit *CU,
1336                                                         const DIE *Die) {
1337   dwarf::GDBIndexEntryLinkage Linkage = dwarf::GIEL_STATIC;
1338
1339   // We could have a specification DIE that has our most of our knowledge,
1340   // look for that now.
1341   DIEValue *SpecVal = Die->findAttribute(dwarf::DW_AT_specification);
1342   if (SpecVal) {
1343     DIE &SpecDIE = cast<DIEEntry>(SpecVal)->getEntry();
1344     if (SpecDIE.findAttribute(dwarf::DW_AT_external))
1345       Linkage = dwarf::GIEL_EXTERNAL;
1346   } else if (Die->findAttribute(dwarf::DW_AT_external))
1347     Linkage = dwarf::GIEL_EXTERNAL;
1348
1349   switch (Die->getTag()) {
1350   case dwarf::DW_TAG_class_type:
1351   case dwarf::DW_TAG_structure_type:
1352   case dwarf::DW_TAG_union_type:
1353   case dwarf::DW_TAG_enumeration_type:
1354     return dwarf::PubIndexEntryDescriptor(
1355         dwarf::GIEK_TYPE, CU->getLanguage() != dwarf::DW_LANG_C_plus_plus
1356                               ? dwarf::GIEL_STATIC
1357                               : dwarf::GIEL_EXTERNAL);
1358   case dwarf::DW_TAG_typedef:
1359   case dwarf::DW_TAG_base_type:
1360   case dwarf::DW_TAG_subrange_type:
1361     return dwarf::PubIndexEntryDescriptor(dwarf::GIEK_TYPE, dwarf::GIEL_STATIC);
1362   case dwarf::DW_TAG_namespace:
1363     return dwarf::GIEK_TYPE;
1364   case dwarf::DW_TAG_subprogram:
1365     return dwarf::PubIndexEntryDescriptor(dwarf::GIEK_FUNCTION, Linkage);
1366   case dwarf::DW_TAG_variable:
1367     return dwarf::PubIndexEntryDescriptor(dwarf::GIEK_VARIABLE, Linkage);
1368   case dwarf::DW_TAG_enumerator:
1369     return dwarf::PubIndexEntryDescriptor(dwarf::GIEK_VARIABLE,
1370                                           dwarf::GIEL_STATIC);
1371   default:
1372     return dwarf::GIEK_NONE;
1373   }
1374 }
1375
1376 /// emitDebugPubNames - Emit visible names into a debug pubnames section.
1377 ///
1378 void DwarfDebug::emitDebugPubNames(bool GnuStyle) {
1379   const MCSection *PSec =
1380       GnuStyle ? Asm->getObjFileLowering().getDwarfGnuPubNamesSection()
1381                : Asm->getObjFileLowering().getDwarfPubNamesSection();
1382
1383   emitDebugPubSection(GnuStyle, PSec, "Names",
1384                       &DwarfCompileUnit::getGlobalNames);
1385 }
1386
1387 void DwarfDebug::emitDebugPubSection(
1388     bool GnuStyle, const MCSection *PSec, StringRef Name,
1389     const StringMap<const DIE *> &(DwarfCompileUnit::*Accessor)() const) {
1390   for (const auto &NU : CUMap) {
1391     DwarfCompileUnit *TheU = NU.second;
1392
1393     const auto &Globals = (TheU->*Accessor)();
1394
1395     if (Globals.empty())
1396       continue;
1397
1398     if (auto *Skeleton = TheU->getSkeleton())
1399       TheU = Skeleton;
1400
1401     // Start the dwarf pubnames section.
1402     Asm->OutStreamer.SwitchSection(PSec);
1403
1404     // Emit the header.
1405     Asm->OutStreamer.AddComment("Length of Public " + Name + " Info");
1406     MCSymbol *BeginLabel = Asm->createTempSymbol("pub" + Name + "_begin");
1407     MCSymbol *EndLabel = Asm->createTempSymbol("pub" + Name + "_end");
1408     Asm->EmitLabelDifference(EndLabel, BeginLabel, 4);
1409
1410     Asm->OutStreamer.EmitLabel(BeginLabel);
1411
1412     Asm->OutStreamer.AddComment("DWARF Version");
1413     Asm->EmitInt16(dwarf::DW_PUBNAMES_VERSION);
1414
1415     Asm->OutStreamer.AddComment("Offset of Compilation Unit Info");
1416     Asm->emitSectionOffset(TheU->getLabelBegin());
1417
1418     Asm->OutStreamer.AddComment("Compilation Unit Length");
1419     Asm->EmitInt32(TheU->getLength());
1420
1421     // Emit the pubnames for this compilation unit.
1422     for (const auto &GI : Globals) {
1423       const char *Name = GI.getKeyData();
1424       const DIE *Entity = GI.second;
1425
1426       Asm->OutStreamer.AddComment("DIE offset");
1427       Asm->EmitInt32(Entity->getOffset());
1428
1429       if (GnuStyle) {
1430         dwarf::PubIndexEntryDescriptor Desc = computeIndexValue(TheU, Entity);
1431         Asm->OutStreamer.AddComment(
1432             Twine("Kind: ") + dwarf::GDBIndexEntryKindString(Desc.Kind) + ", " +
1433             dwarf::GDBIndexEntryLinkageString(Desc.Linkage));
1434         Asm->EmitInt8(Desc.toBits());
1435       }
1436
1437       Asm->OutStreamer.AddComment("External Name");
1438       Asm->OutStreamer.EmitBytes(StringRef(Name, GI.getKeyLength() + 1));
1439     }
1440
1441     Asm->OutStreamer.AddComment("End Mark");
1442     Asm->EmitInt32(0);
1443     Asm->OutStreamer.EmitLabel(EndLabel);
1444   }
1445 }
1446
1447 void DwarfDebug::emitDebugPubTypes(bool GnuStyle) {
1448   const MCSection *PSec =
1449       GnuStyle ? Asm->getObjFileLowering().getDwarfGnuPubTypesSection()
1450                : Asm->getObjFileLowering().getDwarfPubTypesSection();
1451
1452   emitDebugPubSection(GnuStyle, PSec, "Types",
1453                       &DwarfCompileUnit::getGlobalTypes);
1454 }
1455
1456 // Emit visible names into a debug str section.
1457 void DwarfDebug::emitDebugStr() {
1458   DwarfFile &Holder = useSplitDwarf() ? SkeletonHolder : InfoHolder;
1459   Holder.emitStrings(Asm->getObjFileLowering().getDwarfStrSection());
1460 }
1461
1462
1463 void DwarfDebug::emitDebugLocEntry(ByteStreamer &Streamer,
1464                                    const DebugLocEntry &Entry) {
1465   auto Comment = Entry.getComments().begin();
1466   auto End = Entry.getComments().end();
1467   for (uint8_t Byte : Entry.getDWARFBytes())
1468     Streamer.EmitInt8(Byte, Comment != End ? *(Comment++) : "");
1469 }
1470
1471 static void emitDebugLocValue(const AsmPrinter &AP,
1472                               const DITypeIdentifierMap &TypeIdentifierMap,
1473                               ByteStreamer &Streamer,
1474                               const DebugLocEntry::Value &Value,
1475                               unsigned PieceOffsetInBits) {
1476   DIVariable DV = Value.getVariable();
1477   DebugLocDwarfExpression DwarfExpr(*AP.MF->getSubtarget().getRegisterInfo(),
1478                                     AP.getDwarfDebug()->getDwarfVersion(),
1479                                     Streamer);
1480   // Regular entry.
1481   if (Value.isInt()) {
1482     MDType *T = DV->getType().resolve(TypeIdentifierMap);
1483     auto *B = dyn_cast<MDBasicType>(T);
1484     if (B && (B->getEncoding() == dwarf::DW_ATE_signed ||
1485               B->getEncoding() == dwarf::DW_ATE_signed_char))
1486       DwarfExpr.AddSignedConstant(Value.getInt());
1487     else
1488       DwarfExpr.AddUnsignedConstant(Value.getInt());
1489   } else if (Value.isLocation()) {
1490     MachineLocation Loc = Value.getLoc();
1491     DIExpression Expr = Value.getExpression();
1492     if (!Expr || !Expr->getNumElements())
1493       // Regular entry.
1494       AP.EmitDwarfRegOp(Streamer, Loc);
1495     else {
1496       // Complex address entry.
1497       if (Loc.getOffset()) {
1498         DwarfExpr.AddMachineRegIndirect(Loc.getReg(), Loc.getOffset());
1499         DwarfExpr.AddExpression(Expr->expr_op_begin(), Expr->expr_op_end(),
1500                                 PieceOffsetInBits);
1501       } else
1502         DwarfExpr.AddMachineRegExpression(Expr, Loc.getReg(),
1503                                           PieceOffsetInBits);
1504     }
1505   }
1506   // else ... ignore constant fp. There is not any good way to
1507   // to represent them here in dwarf.
1508   // FIXME: ^
1509 }
1510
1511
1512 void DebugLocEntry::finalize(const AsmPrinter &AP,
1513                              const DITypeIdentifierMap &TypeIdentifierMap) {
1514   BufferByteStreamer Streamer(DWARFBytes, Comments);
1515   const DebugLocEntry::Value Value = Values[0];
1516   if (Value.isBitPiece()) {
1517     // Emit all pieces that belong to the same variable and range.
1518     assert(std::all_of(Values.begin(), Values.end(), [](DebugLocEntry::Value P) {
1519           return P.isBitPiece();
1520         }) && "all values are expected to be pieces");
1521     assert(std::is_sorted(Values.begin(), Values.end()) &&
1522            "pieces are expected to be sorted");
1523    
1524     unsigned Offset = 0;
1525     for (auto Piece : Values) {
1526       DIExpression Expr = Piece.getExpression();
1527       unsigned PieceOffset = Expr->getBitPieceOffset();
1528       unsigned PieceSize = Expr->getBitPieceSize();
1529       assert(Offset <= PieceOffset && "overlapping or duplicate pieces");
1530       if (Offset < PieceOffset) {
1531         // The DWARF spec seriously mandates pieces with no locations for gaps.
1532         DebugLocDwarfExpression Expr(*AP.MF->getSubtarget().getRegisterInfo(),
1533                                      AP.getDwarfDebug()->getDwarfVersion(),
1534                                      Streamer);
1535         Expr.AddOpPiece(PieceOffset-Offset, 0);
1536         Offset += PieceOffset-Offset;
1537       }
1538       Offset += PieceSize;
1539
1540       emitDebugLocValue(AP, TypeIdentifierMap, Streamer, Piece, PieceOffset);
1541     }
1542   } else {
1543     assert(Values.size() == 1 && "only pieces may have >1 value");
1544     emitDebugLocValue(AP, TypeIdentifierMap, Streamer, Value, 0);
1545   }
1546 }
1547
1548
1549 void DwarfDebug::emitDebugLocEntryLocation(const DebugLocEntry &Entry) {
1550   Asm->OutStreamer.AddComment("Loc expr size");
1551   MCSymbol *begin = Asm->OutStreamer.getContext().CreateTempSymbol();
1552   MCSymbol *end = Asm->OutStreamer.getContext().CreateTempSymbol();
1553   Asm->EmitLabelDifference(end, begin, 2);
1554   Asm->OutStreamer.EmitLabel(begin);
1555   // Emit the entry.
1556   APByteStreamer Streamer(*Asm);
1557   emitDebugLocEntry(Streamer, Entry);
1558   // Close the range.
1559   Asm->OutStreamer.EmitLabel(end);
1560 }
1561
1562 // Emit locations into the debug loc section.
1563 void DwarfDebug::emitDebugLoc() {
1564   // Start the dwarf loc section.
1565   Asm->OutStreamer.SwitchSection(
1566       Asm->getObjFileLowering().getDwarfLocSection());
1567   unsigned char Size = Asm->getDataLayout().getPointerSize();
1568   for (const auto &DebugLoc : DotDebugLocEntries) {
1569     Asm->OutStreamer.EmitLabel(DebugLoc.Label);
1570     const DwarfCompileUnit *CU = DebugLoc.CU;
1571     for (const auto &Entry : DebugLoc.List) {
1572       // Set up the range. This range is relative to the entry point of the
1573       // compile unit. This is a hard coded 0 for low_pc when we're emitting
1574       // ranges, or the DW_AT_low_pc on the compile unit otherwise.
1575       if (auto *Base = CU->getBaseAddress()) {
1576         Asm->EmitLabelDifference(Entry.getBeginSym(), Base, Size);
1577         Asm->EmitLabelDifference(Entry.getEndSym(), Base, Size);
1578       } else {
1579         Asm->OutStreamer.EmitSymbolValue(Entry.getBeginSym(), Size);
1580         Asm->OutStreamer.EmitSymbolValue(Entry.getEndSym(), Size);
1581       }
1582
1583       emitDebugLocEntryLocation(Entry);
1584     }
1585     Asm->OutStreamer.EmitIntValue(0, Size);
1586     Asm->OutStreamer.EmitIntValue(0, Size);
1587   }
1588 }
1589
1590 void DwarfDebug::emitDebugLocDWO() {
1591   Asm->OutStreamer.SwitchSection(
1592       Asm->getObjFileLowering().getDwarfLocDWOSection());
1593   for (const auto &DebugLoc : DotDebugLocEntries) {
1594     Asm->OutStreamer.EmitLabel(DebugLoc.Label);
1595     for (const auto &Entry : DebugLoc.List) {
1596       // Just always use start_length for now - at least that's one address
1597       // rather than two. We could get fancier and try to, say, reuse an
1598       // address we know we've emitted elsewhere (the start of the function?
1599       // The start of the CU or CU subrange that encloses this range?)
1600       Asm->EmitInt8(dwarf::DW_LLE_start_length_entry);
1601       unsigned idx = AddrPool.getIndex(Entry.getBeginSym());
1602       Asm->EmitULEB128(idx);
1603       Asm->EmitLabelDifference(Entry.getEndSym(), Entry.getBeginSym(), 4);
1604
1605       emitDebugLocEntryLocation(Entry);
1606     }
1607     Asm->EmitInt8(dwarf::DW_LLE_end_of_list_entry);
1608   }
1609 }
1610
1611 struct ArangeSpan {
1612   const MCSymbol *Start, *End;
1613 };
1614
1615 // Emit a debug aranges section, containing a CU lookup for any
1616 // address we can tie back to a CU.
1617 void DwarfDebug::emitDebugARanges() {
1618   // Provides a unique id per text section.
1619   MapVector<const MCSection *, SmallVector<SymbolCU, 8>> SectionMap;
1620
1621   // Filter labels by section.
1622   for (const SymbolCU &SCU : ArangeLabels) {
1623     if (SCU.Sym->isInSection()) {
1624       // Make a note of this symbol and it's section.
1625       const MCSection *Section = &SCU.Sym->getSection();
1626       if (!Section->getKind().isMetadata())
1627         SectionMap[Section].push_back(SCU);
1628     } else {
1629       // Some symbols (e.g. common/bss on mach-o) can have no section but still
1630       // appear in the output. This sucks as we rely on sections to build
1631       // arange spans. We can do it without, but it's icky.
1632       SectionMap[nullptr].push_back(SCU);
1633     }
1634   }
1635
1636   // Add terminating symbols for each section.
1637   for (const auto &I : SectionMap) {
1638     const MCSection *Section = I.first;
1639     MCSymbol *Sym = nullptr;
1640
1641     if (Section)
1642       Sym = Asm->OutStreamer.endSection(Section);
1643
1644     // Insert a final terminator.
1645     SectionMap[Section].push_back(SymbolCU(nullptr, Sym));
1646   }
1647
1648   DenseMap<DwarfCompileUnit *, std::vector<ArangeSpan>> Spans;
1649
1650   for (auto &I : SectionMap) {
1651     const MCSection *Section = I.first;
1652     SmallVector<SymbolCU, 8> &List = I.second;
1653     if (List.size() < 2)
1654       continue;
1655
1656     // If we have no section (e.g. common), just write out
1657     // individual spans for each symbol.
1658     if (!Section) {
1659       for (const SymbolCU &Cur : List) {
1660         ArangeSpan Span;
1661         Span.Start = Cur.Sym;
1662         Span.End = nullptr;
1663         if (Cur.CU)
1664           Spans[Cur.CU].push_back(Span);
1665       }
1666       continue;
1667     }
1668
1669     // Sort the symbols by offset within the section.
1670     std::sort(List.begin(), List.end(),
1671               [&](const SymbolCU &A, const SymbolCU &B) {
1672       unsigned IA = A.Sym ? Asm->OutStreamer.GetSymbolOrder(A.Sym) : 0;
1673       unsigned IB = B.Sym ? Asm->OutStreamer.GetSymbolOrder(B.Sym) : 0;
1674
1675       // Symbols with no order assigned should be placed at the end.
1676       // (e.g. section end labels)
1677       if (IA == 0)
1678         return false;
1679       if (IB == 0)
1680         return true;
1681       return IA < IB;
1682     });
1683
1684     // Build spans between each label.
1685     const MCSymbol *StartSym = List[0].Sym;
1686     for (size_t n = 1, e = List.size(); n < e; n++) {
1687       const SymbolCU &Prev = List[n - 1];
1688       const SymbolCU &Cur = List[n];
1689
1690       // Try and build the longest span we can within the same CU.
1691       if (Cur.CU != Prev.CU) {
1692         ArangeSpan Span;
1693         Span.Start = StartSym;
1694         Span.End = Cur.Sym;
1695         Spans[Prev.CU].push_back(Span);
1696         StartSym = Cur.Sym;
1697       }
1698     }
1699   }
1700
1701   // Start the dwarf aranges section.
1702   Asm->OutStreamer.SwitchSection(
1703       Asm->getObjFileLowering().getDwarfARangesSection());
1704
1705   unsigned PtrSize = Asm->getDataLayout().getPointerSize();
1706
1707   // Build a list of CUs used.
1708   std::vector<DwarfCompileUnit *> CUs;
1709   for (const auto &it : Spans) {
1710     DwarfCompileUnit *CU = it.first;
1711     CUs.push_back(CU);
1712   }
1713
1714   // Sort the CU list (again, to ensure consistent output order).
1715   std::sort(CUs.begin(), CUs.end(), [](const DwarfUnit *A, const DwarfUnit *B) {
1716     return A->getUniqueID() < B->getUniqueID();
1717   });
1718
1719   // Emit an arange table for each CU we used.
1720   for (DwarfCompileUnit *CU : CUs) {
1721     std::vector<ArangeSpan> &List = Spans[CU];
1722
1723     // Describe the skeleton CU's offset and length, not the dwo file's.
1724     if (auto *Skel = CU->getSkeleton())
1725       CU = Skel;
1726
1727     // Emit size of content not including length itself.
1728     unsigned ContentSize =
1729         sizeof(int16_t) + // DWARF ARange version number
1730         sizeof(int32_t) + // Offset of CU in the .debug_info section
1731         sizeof(int8_t) +  // Pointer Size (in bytes)
1732         sizeof(int8_t);   // Segment Size (in bytes)
1733
1734     unsigned TupleSize = PtrSize * 2;
1735
1736     // 7.20 in the Dwarf specs requires the table to be aligned to a tuple.
1737     unsigned Padding =
1738         OffsetToAlignment(sizeof(int32_t) + ContentSize, TupleSize);
1739
1740     ContentSize += Padding;
1741     ContentSize += (List.size() + 1) * TupleSize;
1742
1743     // For each compile unit, write the list of spans it covers.
1744     Asm->OutStreamer.AddComment("Length of ARange Set");
1745     Asm->EmitInt32(ContentSize);
1746     Asm->OutStreamer.AddComment("DWARF Arange version number");
1747     Asm->EmitInt16(dwarf::DW_ARANGES_VERSION);
1748     Asm->OutStreamer.AddComment("Offset Into Debug Info Section");
1749     Asm->emitSectionOffset(CU->getLabelBegin());
1750     Asm->OutStreamer.AddComment("Address Size (in bytes)");
1751     Asm->EmitInt8(PtrSize);
1752     Asm->OutStreamer.AddComment("Segment Size (in bytes)");
1753     Asm->EmitInt8(0);
1754
1755     Asm->OutStreamer.EmitFill(Padding, 0xff);
1756
1757     for (const ArangeSpan &Span : List) {
1758       Asm->EmitLabelReference(Span.Start, PtrSize);
1759
1760       // Calculate the size as being from the span start to it's end.
1761       if (Span.End) {
1762         Asm->EmitLabelDifference(Span.End, Span.Start, PtrSize);
1763       } else {
1764         // For symbols without an end marker (e.g. common), we
1765         // write a single arange entry containing just that one symbol.
1766         uint64_t Size = SymSize[Span.Start];
1767         if (Size == 0)
1768           Size = 1;
1769
1770         Asm->OutStreamer.EmitIntValue(Size, PtrSize);
1771       }
1772     }
1773
1774     Asm->OutStreamer.AddComment("ARange terminator");
1775     Asm->OutStreamer.EmitIntValue(0, PtrSize);
1776     Asm->OutStreamer.EmitIntValue(0, PtrSize);
1777   }
1778 }
1779
1780 // Emit visible names into a debug ranges section.
1781 void DwarfDebug::emitDebugRanges() {
1782   // Start the dwarf ranges section.
1783   Asm->OutStreamer.SwitchSection(
1784       Asm->getObjFileLowering().getDwarfRangesSection());
1785
1786   // Size for our labels.
1787   unsigned char Size = Asm->getDataLayout().getPointerSize();
1788
1789   // Grab the specific ranges for the compile units in the module.
1790   for (const auto &I : CUMap) {
1791     DwarfCompileUnit *TheCU = I.second;
1792
1793     if (auto *Skel = TheCU->getSkeleton())
1794       TheCU = Skel;
1795
1796     // Iterate over the misc ranges for the compile units in the module.
1797     for (const RangeSpanList &List : TheCU->getRangeLists()) {
1798       // Emit our symbol so we can find the beginning of the range.
1799       Asm->OutStreamer.EmitLabel(List.getSym());
1800
1801       for (const RangeSpan &Range : List.getRanges()) {
1802         const MCSymbol *Begin = Range.getStart();
1803         const MCSymbol *End = Range.getEnd();
1804         assert(Begin && "Range without a begin symbol?");
1805         assert(End && "Range without an end symbol?");
1806         if (auto *Base = TheCU->getBaseAddress()) {
1807           Asm->EmitLabelDifference(Begin, Base, Size);
1808           Asm->EmitLabelDifference(End, Base, Size);
1809         } else {
1810           Asm->OutStreamer.EmitSymbolValue(Begin, Size);
1811           Asm->OutStreamer.EmitSymbolValue(End, Size);
1812         }
1813       }
1814
1815       // And terminate the list with two 0 values.
1816       Asm->OutStreamer.EmitIntValue(0, Size);
1817       Asm->OutStreamer.EmitIntValue(0, Size);
1818     }
1819   }
1820 }
1821
1822 // DWARF5 Experimental Separate Dwarf emitters.
1823
1824 void DwarfDebug::initSkeletonUnit(const DwarfUnit &U, DIE &Die,
1825                                   std::unique_ptr<DwarfUnit> NewU) {
1826   NewU->addString(Die, dwarf::DW_AT_GNU_dwo_name,
1827                   U.getCUNode().getSplitDebugFilename());
1828
1829   if (!CompilationDir.empty())
1830     NewU->addString(Die, dwarf::DW_AT_comp_dir, CompilationDir);
1831
1832   addGnuPubAttributes(*NewU, Die);
1833
1834   SkeletonHolder.addUnit(std::move(NewU));
1835 }
1836
1837 // This DIE has the following attributes: DW_AT_comp_dir, DW_AT_stmt_list,
1838 // DW_AT_low_pc, DW_AT_high_pc, DW_AT_ranges, DW_AT_dwo_name, DW_AT_dwo_id,
1839 // DW_AT_addr_base, DW_AT_ranges_base.
1840 DwarfCompileUnit &DwarfDebug::constructSkeletonCU(const DwarfCompileUnit &CU) {
1841
1842   auto OwnedUnit = make_unique<DwarfCompileUnit>(
1843       CU.getUniqueID(), CU.getCUNode(), Asm, this, &SkeletonHolder);
1844   DwarfCompileUnit &NewCU = *OwnedUnit;
1845   NewCU.initSection(Asm->getObjFileLowering().getDwarfInfoSection());
1846
1847   NewCU.initStmtList();
1848
1849   initSkeletonUnit(CU, NewCU.getUnitDie(), std::move(OwnedUnit));
1850
1851   return NewCU;
1852 }
1853
1854 // Emit the .debug_info.dwo section for separated dwarf. This contains the
1855 // compile units that would normally be in debug_info.
1856 void DwarfDebug::emitDebugInfoDWO() {
1857   assert(useSplitDwarf() && "No split dwarf debug info?");
1858   // Don't emit relocations into the dwo file.
1859   InfoHolder.emitUnits(/* UseOffsets */ true);
1860 }
1861
1862 // Emit the .debug_abbrev.dwo section for separated dwarf. This contains the
1863 // abbreviations for the .debug_info.dwo section.
1864 void DwarfDebug::emitDebugAbbrevDWO() {
1865   assert(useSplitDwarf() && "No split dwarf?");
1866   InfoHolder.emitAbbrevs(Asm->getObjFileLowering().getDwarfAbbrevDWOSection());
1867 }
1868
1869 void DwarfDebug::emitDebugLineDWO() {
1870   assert(useSplitDwarf() && "No split dwarf?");
1871   Asm->OutStreamer.SwitchSection(
1872       Asm->getObjFileLowering().getDwarfLineDWOSection());
1873   SplitTypeUnitFileTable.Emit(Asm->OutStreamer);
1874 }
1875
1876 // Emit the .debug_str.dwo section for separated dwarf. This contains the
1877 // string section and is identical in format to traditional .debug_str
1878 // sections.
1879 void DwarfDebug::emitDebugStrDWO() {
1880   assert(useSplitDwarf() && "No split dwarf?");
1881   const MCSection *OffSec =
1882       Asm->getObjFileLowering().getDwarfStrOffDWOSection();
1883   InfoHolder.emitStrings(Asm->getObjFileLowering().getDwarfStrDWOSection(),
1884                          OffSec);
1885 }
1886
1887 MCDwarfDwoLineTable *DwarfDebug::getDwoLineTable(const DwarfCompileUnit &CU) {
1888   if (!useSplitDwarf())
1889     return nullptr;
1890   if (SingleCU)
1891     SplitTypeUnitFileTable.setCompilationDir(CU.getCUNode().getDirectory());
1892   return &SplitTypeUnitFileTable;
1893 }
1894
1895 static uint64_t makeTypeSignature(StringRef Identifier) {
1896   MD5 Hash;
1897   Hash.update(Identifier);
1898   // ... take the least significant 8 bytes and return those. Our MD5
1899   // implementation always returns its results in little endian, swap bytes
1900   // appropriately.
1901   MD5::MD5Result Result;
1902   Hash.final(Result);
1903   return support::endian::read64le(Result + 8);
1904 }
1905
1906 void DwarfDebug::addDwarfTypeUnitType(DwarfCompileUnit &CU,
1907                                       StringRef Identifier, DIE &RefDie,
1908                                       DICompositeType CTy) {
1909   // Fast path if we're building some type units and one has already used the
1910   // address pool we know we're going to throw away all this work anyway, so
1911   // don't bother building dependent types.
1912   if (!TypeUnitsUnderConstruction.empty() && AddrPool.hasBeenUsed())
1913     return;
1914
1915   const DwarfTypeUnit *&TU = DwarfTypeUnits[CTy];
1916   if (TU) {
1917     CU.addDIETypeSignature(RefDie, *TU);
1918     return;
1919   }
1920
1921   bool TopLevelType = TypeUnitsUnderConstruction.empty();
1922   AddrPool.resetUsedFlag();
1923
1924   auto OwnedUnit = make_unique<DwarfTypeUnit>(
1925       InfoHolder.getUnits().size() + TypeUnitsUnderConstruction.size(), CU, Asm,
1926       this, &InfoHolder, getDwoLineTable(CU));
1927   DwarfTypeUnit &NewTU = *OwnedUnit;
1928   DIE &UnitDie = NewTU.getUnitDie();
1929   TU = &NewTU;
1930   TypeUnitsUnderConstruction.push_back(
1931       std::make_pair(std::move(OwnedUnit), CTy));
1932
1933   NewTU.addUInt(UnitDie, dwarf::DW_AT_language, dwarf::DW_FORM_data2,
1934                 CU.getLanguage());
1935
1936   uint64_t Signature = makeTypeSignature(Identifier);
1937   NewTU.setTypeSignature(Signature);
1938
1939   if (useSplitDwarf())
1940     NewTU.initSection(Asm->getObjFileLowering().getDwarfTypesDWOSection());
1941   else {
1942     CU.applyStmtList(UnitDie);
1943     NewTU.initSection(
1944         Asm->getObjFileLowering().getDwarfTypesSection(Signature));
1945   }
1946
1947   NewTU.setType(NewTU.createTypeDIE(CTy));
1948
1949   if (TopLevelType) {
1950     auto TypeUnitsToAdd = std::move(TypeUnitsUnderConstruction);
1951     TypeUnitsUnderConstruction.clear();
1952
1953     // Types referencing entries in the address table cannot be placed in type
1954     // units.
1955     if (AddrPool.hasBeenUsed()) {
1956
1957       // Remove all the types built while building this type.
1958       // This is pessimistic as some of these types might not be dependent on
1959       // the type that used an address.
1960       for (const auto &TU : TypeUnitsToAdd)
1961         DwarfTypeUnits.erase(TU.second);
1962
1963       // Construct this type in the CU directly.
1964       // This is inefficient because all the dependent types will be rebuilt
1965       // from scratch, including building them in type units, discovering that
1966       // they depend on addresses, throwing them out and rebuilding them.
1967       CU.constructTypeDIE(RefDie, CTy);
1968       return;
1969     }
1970
1971     // If the type wasn't dependent on fission addresses, finish adding the type
1972     // and all its dependent types.
1973     for (auto &TU : TypeUnitsToAdd)
1974       InfoHolder.addUnit(std::move(TU.first));
1975   }
1976   CU.addDIETypeSignature(RefDie, NewTU);
1977 }
1978
1979 // Accelerator table mutators - add each name along with its companion
1980 // DIE to the proper table while ensuring that the name that we're going
1981 // to reference is in the string table. We do this since the names we
1982 // add may not only be identical to the names in the DIE.
1983 void DwarfDebug::addAccelName(StringRef Name, const DIE &Die) {
1984   if (!useDwarfAccelTables())
1985     return;
1986   AccelNames.AddName(Name, InfoHolder.getStringPool().getSymbol(*Asm, Name),
1987                      &Die);
1988 }
1989
1990 void DwarfDebug::addAccelObjC(StringRef Name, const DIE &Die) {
1991   if (!useDwarfAccelTables())
1992     return;
1993   AccelObjC.AddName(Name, InfoHolder.getStringPool().getSymbol(*Asm, Name),
1994                     &Die);
1995 }
1996
1997 void DwarfDebug::addAccelNamespace(StringRef Name, const DIE &Die) {
1998   if (!useDwarfAccelTables())
1999     return;
2000   AccelNamespace.AddName(Name, InfoHolder.getStringPool().getSymbol(*Asm, Name),
2001                          &Die);
2002 }
2003
2004 void DwarfDebug::addAccelType(StringRef Name, const DIE &Die, char Flags) {
2005   if (!useDwarfAccelTables())
2006     return;
2007   AccelTypes.AddName(Name, InfoHolder.getStringPool().getSymbol(*Asm, Name),
2008                      &Die);
2009 }