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