Add bool to DebugLocDwarfExpression to control emitting comments.
[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   if (!PrintComments)
112     return BS.EmitInt8(Op, Twine());
113   BS.EmitInt8(
114       Op, Comment ? Twine(Comment) + " " + dwarf::OperationEncodingString(Op)
115                   : dwarf::OperationEncodingString(Op));
116 }
117
118 void DebugLocDwarfExpression::EmitSigned(int64_t Value) {
119   BS.EmitSLEB128(Value, Twine(Value));
120 }
121
122 void DebugLocDwarfExpression::EmitUnsigned(uint64_t Value) {
123   BS.EmitULEB128(Value, Twine(Value));
124 }
125
126 bool DebugLocDwarfExpression::isFrameRegister(unsigned MachineReg) {
127   // This information is not available while emitting .debug_loc entries.
128   return false;
129 }
130
131 //===----------------------------------------------------------------------===//
132
133 /// resolve - Look in the DwarfDebug map for the MDNode that
134 /// corresponds to the reference.
135 template <typename T> T *DbgVariable::resolve(TypedDINodeRef<T> Ref) const {
136   return DD->resolve(Ref);
137 }
138
139 bool DbgVariable::isBlockByrefVariable() const {
140   assert(Var && "Invalid complex DbgVariable!");
141   return Var->getType()
142       .resolve(DD->getTypeIdentifierMap())
143       ->isBlockByrefStruct();
144 }
145
146 const DIType *DbgVariable::getType() const {
147   DIType *Ty = Var->getType().resolve(DD->getTypeIdentifierMap());
148   // FIXME: isBlockByrefVariable should be reformulated in terms of complex
149   // addresses instead.
150   if (Ty->isBlockByrefStruct()) {
151     /* Byref variables, in Blocks, are declared by the programmer as
152        "SomeType VarName;", but the compiler creates a
153        __Block_byref_x_VarName struct, and gives the variable VarName
154        either the struct, or a pointer to the struct, as its type.  This
155        is necessary for various behind-the-scenes things the compiler
156        needs to do with by-reference variables in blocks.
157
158        However, as far as the original *programmer* is concerned, the
159        variable should still have type 'SomeType', as originally declared.
160
161        The following function dives into the __Block_byref_x_VarName
162        struct to find the original type of the variable.  This will be
163        passed back to the code generating the type for the Debug
164        Information Entry for the variable 'VarName'.  'VarName' will then
165        have the original type 'SomeType' in its debug information.
166
167        The original type 'SomeType' will be the type of the field named
168        'VarName' inside the __Block_byref_x_VarName struct.
169
170        NOTE: In order for this to not completely fail on the debugger
171        side, the Debug Information Entry for the variable VarName needs to
172        have a DW_AT_location that tells the debugger how to unwind through
173        the pointers and __Block_byref_x_VarName struct to find the actual
174        value of the variable.  The function addBlockByrefType does this.  */
175     DIType *subType = Ty;
176     uint16_t tag = Ty->getTag();
177
178     if (tag == dwarf::DW_TAG_pointer_type)
179       subType = resolve(cast<DIDerivedType>(Ty)->getBaseType());
180
181     auto Elements = cast<DICompositeTypeBase>(subType)->getElements();
182     for (unsigned i = 0, N = Elements.size(); i < N; ++i) {
183       auto *DT = cast<DIDerivedTypeBase>(Elements[i]);
184       if (getName() == DT->getName())
185         return resolve(DT->getBaseType());
186     }
187   }
188   return Ty;
189 }
190
191 static LLVM_CONSTEXPR DwarfAccelTable::Atom TypeAtoms[] = {
192     DwarfAccelTable::Atom(dwarf::DW_ATOM_die_offset, dwarf::DW_FORM_data4),
193     DwarfAccelTable::Atom(dwarf::DW_ATOM_die_tag, dwarf::DW_FORM_data2),
194     DwarfAccelTable::Atom(dwarf::DW_ATOM_type_flags, dwarf::DW_FORM_data1)};
195
196 DwarfDebug::DwarfDebug(AsmPrinter *A, Module *M)
197     : Asm(A), MMI(Asm->MMI), PrevLabel(nullptr),
198       InfoHolder(A, "info_string", DIEValueAllocator),
199       UsedNonDefaultText(false),
200       SkeletonHolder(A, "skel_string", DIEValueAllocator),
201       IsDarwin(Triple(A->getTargetTriple()).isOSDarwin()),
202       IsPS4(Triple(A->getTargetTriple()).isPS4()),
203       AccelNames(DwarfAccelTable::Atom(dwarf::DW_ATOM_die_offset,
204                                        dwarf::DW_FORM_data4)),
205       AccelObjC(DwarfAccelTable::Atom(dwarf::DW_ATOM_die_offset,
206                                       dwarf::DW_FORM_data4)),
207       AccelNamespace(DwarfAccelTable::Atom(dwarf::DW_ATOM_die_offset,
208                                            dwarf::DW_FORM_data4)),
209       AccelTypes(TypeAtoms) {
210
211   CurFn = nullptr;
212   CurMI = nullptr;
213
214   // Turn on accelerator tables for Darwin by default, pubnames by
215   // default for non-Darwin/PS4, and handle split dwarf.
216   if (DwarfAccelTables == Default)
217     HasDwarfAccelTables = IsDarwin;
218   else
219     HasDwarfAccelTables = DwarfAccelTables == Enable;
220
221   if (SplitDwarf == Default)
222     HasSplitDwarf = false;
223   else
224     HasSplitDwarf = SplitDwarf == Enable;
225
226   if (DwarfPubSections == Default)
227     HasDwarfPubSections = !IsDarwin && !IsPS4;
228   else
229     HasDwarfPubSections = DwarfPubSections == Enable;
230
231   unsigned DwarfVersionNumber = Asm->TM.Options.MCOptions.DwarfVersion;
232   DwarfVersion = DwarfVersionNumber ? DwarfVersionNumber
233                                     : MMI->getModule()->getDwarfVersion();
234
235   // Darwin and PS4 use the standard TLS opcode (defined in DWARF 3).
236   // Everybody else uses GNU's.
237   UseGNUTLSOpcode = !(IsDarwin || IsPS4) || DwarfVersion < 3;
238
239   Asm->OutStreamer->getContext().setDwarfVersion(DwarfVersion);
240
241   {
242     NamedRegionTimer T(DbgTimerName, DWARFGroupName, TimePassesIsEnabled);
243     beginModule();
244   }
245 }
246
247 // Define out of line so we don't have to include DwarfUnit.h in DwarfDebug.h.
248 DwarfDebug::~DwarfDebug() { }
249
250 static bool isObjCClass(StringRef Name) {
251   return Name.startswith("+") || Name.startswith("-");
252 }
253
254 static bool hasObjCCategory(StringRef Name) {
255   if (!isObjCClass(Name))
256     return false;
257
258   return Name.find(") ") != StringRef::npos;
259 }
260
261 static void getObjCClassCategory(StringRef In, StringRef &Class,
262                                  StringRef &Category) {
263   if (!hasObjCCategory(In)) {
264     Class = In.slice(In.find('[') + 1, In.find(' '));
265     Category = "";
266     return;
267   }
268
269   Class = In.slice(In.find('[') + 1, In.find('('));
270   Category = In.slice(In.find('[') + 1, In.find(' '));
271   return;
272 }
273
274 static StringRef getObjCMethodName(StringRef In) {
275   return In.slice(In.find(' ') + 1, In.find(']'));
276 }
277
278 // Add the various names to the Dwarf accelerator table names.
279 // TODO: Determine whether or not we should add names for programs
280 // that do not have a DW_AT_name or DW_AT_linkage_name field - this
281 // is only slightly different than the lookup of non-standard ObjC names.
282 void DwarfDebug::addSubprogramNames(const DISubprogram *SP, DIE &Die) {
283   if (!SP->isDefinition())
284     return;
285   addAccelName(SP->getName(), Die);
286
287   // If the linkage name is different than the name, go ahead and output
288   // that as well into the name table.
289   if (SP->getLinkageName() != "" && SP->getName() != SP->getLinkageName())
290     addAccelName(SP->getLinkageName(), Die);
291
292   // If this is an Objective-C selector name add it to the ObjC accelerator
293   // too.
294   if (isObjCClass(SP->getName())) {
295     StringRef Class, Category;
296     getObjCClassCategory(SP->getName(), Class, Category);
297     addAccelObjC(Class, Die);
298     if (Category != "")
299       addAccelObjC(Category, Die);
300     // Also add the base method name to the name table.
301     addAccelName(getObjCMethodName(SP->getName()), Die);
302   }
303 }
304
305 /// isSubprogramContext - Return true if Context is either a subprogram
306 /// or another context nested inside a subprogram.
307 bool DwarfDebug::isSubprogramContext(const MDNode *Context) {
308   if (!Context)
309     return false;
310   if (isa<DISubprogram>(Context))
311     return true;
312   if (auto *T = dyn_cast<DIType>(Context))
313     return isSubprogramContext(resolve(T->getScope()));
314   return false;
315 }
316
317 /// Check whether we should create a DIE for the given Scope, return true
318 /// if we don't create a DIE (the corresponding DIE is null).
319 bool DwarfDebug::isLexicalScopeDIENull(LexicalScope *Scope) {
320   if (Scope->isAbstractScope())
321     return false;
322
323   // We don't create a DIE if there is no Range.
324   const SmallVectorImpl<InsnRange> &Ranges = Scope->getRanges();
325   if (Ranges.empty())
326     return true;
327
328   if (Ranges.size() > 1)
329     return false;
330
331   // We don't create a DIE if we have a single Range and the end label
332   // is null.
333   return !getLabelAfterInsn(Ranges.front().second);
334 }
335
336 template <typename Func> void forBothCUs(DwarfCompileUnit &CU, Func F) {
337   F(CU);
338   if (auto *SkelCU = CU.getSkeleton())
339     F(*SkelCU);
340 }
341
342 void DwarfDebug::constructAbstractSubprogramScopeDIE(LexicalScope *Scope) {
343   assert(Scope && Scope->getScopeNode());
344   assert(Scope->isAbstractScope());
345   assert(!Scope->getInlinedAt());
346
347   const MDNode *SP = Scope->getScopeNode();
348
349   ProcessedSPNodes.insert(SP);
350
351   // Find the subprogram's DwarfCompileUnit in the SPMap in case the subprogram
352   // was inlined from another compile unit.
353   auto &CU = SPMap[SP];
354   forBothCUs(*CU, [&](DwarfCompileUnit &CU) {
355     CU.constructAbstractSubprogramScopeDIE(Scope);
356   });
357 }
358
359 void DwarfDebug::addGnuPubAttributes(DwarfUnit &U, DIE &D) const {
360   if (!GenerateGnuPubSections)
361     return;
362
363   U.addFlag(D, dwarf::DW_AT_GNU_pubnames);
364 }
365
366 // Create new DwarfCompileUnit for the given metadata node with tag
367 // DW_TAG_compile_unit.
368 DwarfCompileUnit &
369 DwarfDebug::constructDwarfCompileUnit(const DICompileUnit *DIUnit) {
370   StringRef FN = DIUnit->getFilename();
371   CompilationDir = DIUnit->getDirectory();
372
373   auto OwnedUnit = make_unique<DwarfCompileUnit>(
374       InfoHolder.getUnits().size(), DIUnit, Asm, this, &InfoHolder);
375   DwarfCompileUnit &NewCU = *OwnedUnit;
376   DIE &Die = NewCU.getUnitDie();
377   InfoHolder.addUnit(std::move(OwnedUnit));
378   if (useSplitDwarf())
379     NewCU.setSkeleton(constructSkeletonCU(NewCU));
380
381   // LTO with assembly output shares a single line table amongst multiple CUs.
382   // To avoid the compilation directory being ambiguous, let the line table
383   // explicitly describe the directory of all files, never relying on the
384   // compilation directory.
385   if (!Asm->OutStreamer->hasRawTextSupport() || SingleCU)
386     Asm->OutStreamer->getContext().setMCLineTableCompilationDir(
387         NewCU.getUniqueID(), CompilationDir);
388
389   NewCU.addString(Die, dwarf::DW_AT_producer, DIUnit->getProducer());
390   NewCU.addUInt(Die, dwarf::DW_AT_language, dwarf::DW_FORM_data2,
391                 DIUnit->getSourceLanguage());
392   NewCU.addString(Die, dwarf::DW_AT_name, FN);
393
394   if (!useSplitDwarf()) {
395     NewCU.initStmtList();
396
397     // If we're using split dwarf the compilation dir is going to be in the
398     // skeleton CU and so we don't need to duplicate it here.
399     if (!CompilationDir.empty())
400       NewCU.addString(Die, dwarf::DW_AT_comp_dir, CompilationDir);
401
402     addGnuPubAttributes(NewCU, Die);
403   }
404
405   if (DIUnit->isOptimized())
406     NewCU.addFlag(Die, dwarf::DW_AT_APPLE_optimized);
407
408   StringRef Flags = DIUnit->getFlags();
409   if (!Flags.empty())
410     NewCU.addString(Die, dwarf::DW_AT_APPLE_flags, Flags);
411
412   if (unsigned RVer = DIUnit->getRuntimeVersion())
413     NewCU.addUInt(Die, dwarf::DW_AT_APPLE_major_runtime_vers,
414                   dwarf::DW_FORM_data1, RVer);
415
416   if (useSplitDwarf())
417     NewCU.initSection(Asm->getObjFileLowering().getDwarfInfoDWOSection());
418   else
419     NewCU.initSection(Asm->getObjFileLowering().getDwarfInfoSection());
420
421   CUMap.insert(std::make_pair(DIUnit, &NewCU));
422   CUDieMap.insert(std::make_pair(&Die, &NewCU));
423   return NewCU;
424 }
425
426 void DwarfDebug::constructAndAddImportedEntityDIE(DwarfCompileUnit &TheCU,
427                                                   const DIImportedEntity *N) {
428   if (DIE *D = TheCU.getOrCreateContextDIE(N->getScope()))
429     D->addChild(TheCU.constructImportedEntityDIE(N));
430 }
431
432 // Emit all Dwarf sections that should come prior to the content. Create
433 // global DIEs and emit initial debug info sections. This is invoked by
434 // the target AsmPrinter.
435 void DwarfDebug::beginModule() {
436   if (DisableDebugInfoPrinting)
437     return;
438
439   const Module *M = MMI->getModule();
440
441   FunctionDIs = makeSubprogramMap(*M);
442
443   NamedMDNode *CU_Nodes = M->getNamedMetadata("llvm.dbg.cu");
444   if (!CU_Nodes)
445     return;
446   TypeIdentifierMap = generateDITypeIdentifierMap(CU_Nodes);
447
448   SingleCU = CU_Nodes->getNumOperands() == 1;
449
450   for (MDNode *N : CU_Nodes->operands()) {
451     auto *CUNode = cast<DICompileUnit>(N);
452     DwarfCompileUnit &CU = constructDwarfCompileUnit(CUNode);
453     for (auto *IE : CUNode->getImportedEntities())
454       ScopesWithImportedEntities.push_back(std::make_pair(IE->getScope(), IE));
455     // Stable sort to preserve the order of appearance of imported entities.
456     // This is to avoid out-of-order processing of interdependent declarations
457     // within the same scope, e.g. { namespace A = base; namespace B = A; }
458     std::stable_sort(ScopesWithImportedEntities.begin(),
459                      ScopesWithImportedEntities.end(), less_first());
460     for (auto *GV : CUNode->getGlobalVariables())
461       CU.getOrCreateGlobalVariableDIE(GV);
462     for (auto *SP : CUNode->getSubprograms())
463       SPMap.insert(std::make_pair(SP, &CU));
464     for (auto *Ty : CUNode->getEnumTypes()) {
465       // The enum types array by design contains pointers to
466       // MDNodes rather than DIRefs. Unique them here.
467       CU.getOrCreateTypeDIE(cast<DIType>(resolve(Ty->getRef())));
468     }
469     for (auto *Ty : CUNode->getRetainedTypes()) {
470       // The retained types array by design contains pointers to
471       // MDNodes rather than DIRefs. Unique them here.
472       CU.getOrCreateTypeDIE(cast<DIType>(resolve(Ty->getRef())));
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<DISubprogram>(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       auto *TheCU = cast<DICompileUnit>(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         U.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 *
666 DwarfDebug::getExistingAbstractVariable(InlinedVariable IV,
667                                         const DILocalVariable *&Cleansed) {
668   // More then one inlined variable corresponds to one abstract variable.
669   Cleansed = IV.first;
670   auto I = AbstractVariables.find(Cleansed);
671   if (I != AbstractVariables.end())
672     return I->second.get();
673   return nullptr;
674 }
675
676 DbgVariable *DwarfDebug::getExistingAbstractVariable(InlinedVariable IV) {
677   const DILocalVariable *Cleansed;
678   return getExistingAbstractVariable(IV, Cleansed);
679 }
680
681 void DwarfDebug::createAbstractVariable(const DILocalVariable *Var,
682                                         LexicalScope *Scope) {
683   auto AbsDbgVariable =
684       make_unique<DbgVariable>(Var, /* IA */ nullptr, /* Expr */ nullptr, this);
685   InfoHolder.addScopeVariable(Scope, AbsDbgVariable.get());
686   AbstractVariables[Var] = std::move(AbsDbgVariable);
687 }
688
689 void DwarfDebug::ensureAbstractVariableIsCreated(InlinedVariable IV,
690                                                  const MDNode *ScopeNode) {
691   const DILocalVariable *Cleansed = nullptr;
692   if (getExistingAbstractVariable(IV, Cleansed))
693     return;
694
695   createAbstractVariable(Cleansed, LScopes.getOrCreateAbstractScope(
696                                        cast<DILocalScope>(ScopeNode)));
697 }
698
699 void DwarfDebug::ensureAbstractVariableIsCreatedIfScoped(
700     InlinedVariable IV, const MDNode *ScopeNode) {
701   const DILocalVariable *Cleansed = nullptr;
702   if (getExistingAbstractVariable(IV, Cleansed))
703     return;
704
705   if (LexicalScope *Scope =
706           LScopes.findAbstractScope(cast_or_null<DILocalScope>(ScopeNode)))
707     createAbstractVariable(Cleansed, Scope);
708 }
709
710 // Collect variable information from side table maintained by MMI.
711 void DwarfDebug::collectVariableInfoFromMMITable(
712     DenseSet<InlinedVariable> &Processed) {
713   for (const auto &VI : MMI->getVariableDbgInfo()) {
714     if (!VI.Var)
715       continue;
716     assert(VI.Var->isValidLocationForIntrinsic(VI.Loc) &&
717            "Expected inlined-at fields to agree");
718
719     InlinedVariable Var(VI.Var, VI.Loc->getInlinedAt());
720     Processed.insert(Var);
721     LexicalScope *Scope = LScopes.findLexicalScope(VI.Loc);
722
723     // If variable scope is not found then skip this variable.
724     if (!Scope)
725       continue;
726
727     const DIExpression *Expr = cast_or_null<DIExpression>(VI.Expr);
728     ensureAbstractVariableIsCreatedIfScoped(Var, Scope->getScopeNode());
729     auto RegVar =
730         make_unique<DbgVariable>(Var.first, Var.second, Expr, this, VI.Slot);
731     if (InfoHolder.addScopeVariable(Scope, RegVar.get()))
732       ConcreteVariables.push_back(std::move(RegVar));
733   }
734 }
735
736 // Get .debug_loc entry for the instruction range starting at MI.
737 static DebugLocEntry::Value getDebugLocValue(const MachineInstr *MI) {
738   const DIExpression *Expr = MI->getDebugExpression();
739
740   assert(MI->getNumOperands() == 4);
741   if (MI->getOperand(0).isReg()) {
742     MachineLocation MLoc;
743     // If the second operand is an immediate, this is a
744     // register-indirect address.
745     if (!MI->getOperand(1).isImm())
746       MLoc.set(MI->getOperand(0).getReg());
747     else
748       MLoc.set(MI->getOperand(0).getReg(), MI->getOperand(1).getImm());
749     return DebugLocEntry::Value(Expr, MLoc);
750   }
751   if (MI->getOperand(0).isImm())
752     return DebugLocEntry::Value(Expr, MI->getOperand(0).getImm());
753   if (MI->getOperand(0).isFPImm())
754     return DebugLocEntry::Value(Expr, MI->getOperand(0).getFPImm());
755   if (MI->getOperand(0).isCImm())
756     return DebugLocEntry::Value(Expr, MI->getOperand(0).getCImm());
757
758   llvm_unreachable("Unexpected 4-operand DBG_VALUE instruction!");
759 }
760
761 /// Determine whether two variable pieces overlap.
762 static bool piecesOverlap(const DIExpression *P1, const DIExpression *P2) {
763   if (!P1->isBitPiece() || !P2->isBitPiece())
764     return true;
765   unsigned l1 = P1->getBitPieceOffset();
766   unsigned l2 = P2->getBitPieceOffset();
767   unsigned r1 = l1 + P1->getBitPieceSize();
768   unsigned r2 = l2 + P2->getBitPieceSize();
769   // True where [l1,r1[ and [r1,r2[ overlap.
770   return (l1 < r2) && (l2 < r1);
771 }
772
773 /// Build the location list for all DBG_VALUEs in the function that
774 /// describe the same variable.  If the ranges of several independent
775 /// pieces of the same variable overlap partially, split them up and
776 /// combine the ranges. The resulting DebugLocEntries are will have
777 /// strict monotonically increasing begin addresses and will never
778 /// overlap.
779 //
780 // Input:
781 //
782 //   Ranges History [var, loc, piece ofs size]
783 // 0 |      [x, (reg0, piece 0, 32)]
784 // 1 | |    [x, (reg1, piece 32, 32)] <- IsPieceOfPrevEntry
785 // 2 | |    ...
786 // 3   |    [clobber reg0]
787 // 4        [x, (mem, piece 0, 64)] <- overlapping with both previous pieces of
788 //                                     x.
789 //
790 // Output:
791 //
792 // [0-1]    [x, (reg0, piece  0, 32)]
793 // [1-3]    [x, (reg0, piece  0, 32), (reg1, piece 32, 32)]
794 // [3-4]    [x, (reg1, piece 32, 32)]
795 // [4- ]    [x, (mem,  piece  0, 64)]
796 void
797 DwarfDebug::buildLocationList(SmallVectorImpl<DebugLocEntry> &DebugLoc,
798                               const DbgValueHistoryMap::InstrRanges &Ranges) {
799   SmallVector<DebugLocEntry::Value, 4> OpenRanges;
800
801   for (auto I = Ranges.begin(), E = Ranges.end(); I != E; ++I) {
802     const MachineInstr *Begin = I->first;
803     const MachineInstr *End = I->second;
804     assert(Begin->isDebugValue() && "Invalid History entry");
805
806     // Check if a variable is inaccessible in this range.
807     if (Begin->getNumOperands() > 1 &&
808         Begin->getOperand(0).isReg() && !Begin->getOperand(0).getReg()) {
809       OpenRanges.clear();
810       continue;
811     }
812
813     // If this piece overlaps with any open ranges, truncate them.
814     const DIExpression *DIExpr = Begin->getDebugExpression();
815     auto Last = std::remove_if(OpenRanges.begin(), OpenRanges.end(),
816                                [&](DebugLocEntry::Value R) {
817       return piecesOverlap(DIExpr, R.getExpression());
818     });
819     OpenRanges.erase(Last, OpenRanges.end());
820
821     const MCSymbol *StartLabel = getLabelBeforeInsn(Begin);
822     assert(StartLabel && "Forgot label before DBG_VALUE starting a range!");
823
824     const MCSymbol *EndLabel;
825     if (End != nullptr)
826       EndLabel = getLabelAfterInsn(End);
827     else if (std::next(I) == Ranges.end())
828       EndLabel = Asm->getFunctionEnd();
829     else
830       EndLabel = getLabelBeforeInsn(std::next(I)->first);
831     assert(EndLabel && "Forgot label after instruction ending a range!");
832
833     DEBUG(dbgs() << "DotDebugLoc: " << *Begin << "\n");
834
835     auto Value = getDebugLocValue(Begin);
836     DebugLocEntry Loc(StartLabel, EndLabel, Value);
837     bool couldMerge = false;
838
839     // If this is a piece, it may belong to the current DebugLocEntry.
840     if (DIExpr->isBitPiece()) {
841       // Add this value to the list of open ranges.
842       OpenRanges.push_back(Value);
843
844       // Attempt to add the piece to the last entry.
845       if (!DebugLoc.empty())
846         if (DebugLoc.back().MergeValues(Loc))
847           couldMerge = true;
848     }
849
850     if (!couldMerge) {
851       // Need to add a new DebugLocEntry. Add all values from still
852       // valid non-overlapping pieces.
853       if (OpenRanges.size())
854         Loc.addValues(OpenRanges);
855
856       DebugLoc.push_back(std::move(Loc));
857     }
858
859     // Attempt to coalesce the ranges of two otherwise identical
860     // DebugLocEntries.
861     auto CurEntry = DebugLoc.rbegin();
862     auto PrevEntry = std::next(CurEntry);
863     if (PrevEntry != DebugLoc.rend() && PrevEntry->MergeRanges(*CurEntry))
864       DebugLoc.pop_back();
865
866     DEBUG({
867       dbgs() << CurEntry->getValues().size() << " Values:\n";
868       for (auto Value : CurEntry->getValues()) {
869         Value.getExpression()->dump();
870       }
871       dbgs() << "-----\n";
872     });
873   }
874 }
875
876
877 // Find variables for each lexical scope.
878 void DwarfDebug::collectVariableInfo(DwarfCompileUnit &TheCU,
879                                      const DISubprogram *SP,
880                                      DenseSet<InlinedVariable> &Processed) {
881   // Grab the variable info that was squirreled away in the MMI side-table.
882   collectVariableInfoFromMMITable(Processed);
883
884   for (const auto &I : DbgValues) {
885     InlinedVariable IV = I.first;
886     if (Processed.count(IV))
887       continue;
888
889     // Instruction ranges, specifying where IV is accessible.
890     const auto &Ranges = I.second;
891     if (Ranges.empty())
892       continue;
893
894     LexicalScope *Scope = nullptr;
895     if (const DILocation *IA = IV.second)
896       Scope = LScopes.findInlinedScope(IV.first->getScope(), IA);
897     else
898       Scope = LScopes.findLexicalScope(IV.first->getScope());
899     // If variable scope is not found then skip this variable.
900     if (!Scope)
901       continue;
902
903     Processed.insert(IV);
904     const MachineInstr *MInsn = Ranges.front().first;
905     assert(MInsn->isDebugValue() && "History must begin with debug value");
906     ensureAbstractVariableIsCreatedIfScoped(IV, Scope->getScopeNode());
907     ConcreteVariables.push_back(make_unique<DbgVariable>(MInsn, this));
908     DbgVariable *RegVar = ConcreteVariables.back().get();
909     InfoHolder.addScopeVariable(Scope, RegVar);
910
911     // Check if the first DBG_VALUE is valid for the rest of the function.
912     if (Ranges.size() == 1 && Ranges.front().second == nullptr)
913       continue;
914
915     // Handle multiple DBG_VALUE instructions describing one variable.
916     RegVar->setDebugLocListIndex(
917         DebugLocs.startList(&TheCU, Asm->createTempSymbol("debug_loc")));
918
919     // Build the location list for this variable.
920     SmallVector<DebugLocEntry, 8> Entries;
921     buildLocationList(Entries, Ranges);
922
923     // If the variable has an DIBasicType, extract it.  Basic types cannot have
924     // unique identifiers, so don't bother resolving the type with the
925     // identifier map.
926     const DIBasicType *BT = dyn_cast<DIBasicType>(
927         static_cast<const Metadata *>(IV.first->getType()));
928
929     // Finalize the entry by lowering it into a DWARF bytestream.
930     for (auto &Entry : Entries)
931       Entry.finalize(*Asm, DebugLocs, BT);
932   }
933
934   // Collect info for variables that were optimized out.
935   for (const DILocalVariable *DV : SP->getVariables()) {
936     if (!Processed.insert(InlinedVariable(DV, nullptr)).second)
937       continue;
938     if (LexicalScope *Scope = LScopes.findLexicalScope(DV->getScope())) {
939       ensureAbstractVariableIsCreatedIfScoped(InlinedVariable(DV, nullptr),
940                                               Scope->getScopeNode());
941       ConcreteVariables.push_back(make_unique<DbgVariable>(
942           DV, /* IA */ nullptr, /* Expr */ nullptr, this));
943       InfoHolder.addScopeVariable(Scope, ConcreteVariables.back().get());
944     }
945   }
946 }
947
948 // Return Label preceding the instruction.
949 MCSymbol *DwarfDebug::getLabelBeforeInsn(const MachineInstr *MI) {
950   MCSymbol *Label = LabelsBeforeInsn.lookup(MI);
951   assert(Label && "Didn't insert label before instruction");
952   return Label;
953 }
954
955 // Return Label immediately following the instruction.
956 MCSymbol *DwarfDebug::getLabelAfterInsn(const MachineInstr *MI) {
957   return LabelsAfterInsn.lookup(MI);
958 }
959
960 // Process beginning of an instruction.
961 void DwarfDebug::beginInstruction(const MachineInstr *MI) {
962   assert(CurMI == nullptr);
963   CurMI = MI;
964   // Check if source location changes, but ignore DBG_VALUE locations.
965   if (!MI->isDebugValue()) {
966     DebugLoc DL = MI->getDebugLoc();
967     if (DL != PrevInstLoc) {
968       if (DL) {
969         unsigned Flags = 0;
970         PrevInstLoc = DL;
971         if (DL == PrologEndLoc) {
972           Flags |= DWARF2_FLAG_PROLOGUE_END;
973           PrologEndLoc = DebugLoc();
974           Flags |= DWARF2_FLAG_IS_STMT;
975         }
976         if (DL.getLine() !=
977             Asm->OutStreamer->getContext().getCurrentDwarfLoc().getLine())
978           Flags |= DWARF2_FLAG_IS_STMT;
979
980         const MDNode *Scope = DL.getScope();
981         recordSourceLine(DL.getLine(), DL.getCol(), Scope, Flags);
982       } else if (UnknownLocations) {
983         PrevInstLoc = DL;
984         recordSourceLine(0, 0, nullptr, 0);
985       }
986     }
987   }
988
989   // Insert labels where requested.
990   DenseMap<const MachineInstr *, MCSymbol *>::iterator I =
991       LabelsBeforeInsn.find(MI);
992
993   // No label needed.
994   if (I == LabelsBeforeInsn.end())
995     return;
996
997   // Label already assigned.
998   if (I->second)
999     return;
1000
1001   if (!PrevLabel) {
1002     PrevLabel = MMI->getContext().createTempSymbol();
1003     Asm->OutStreamer->EmitLabel(PrevLabel);
1004   }
1005   I->second = PrevLabel;
1006 }
1007
1008 // Process end of an instruction.
1009 void DwarfDebug::endInstruction() {
1010   assert(CurMI != nullptr);
1011   // Don't create a new label after DBG_VALUE instructions.
1012   // They don't generate code.
1013   if (!CurMI->isDebugValue())
1014     PrevLabel = nullptr;
1015
1016   DenseMap<const MachineInstr *, MCSymbol *>::iterator I =
1017       LabelsAfterInsn.find(CurMI);
1018   CurMI = nullptr;
1019
1020   // No label needed.
1021   if (I == LabelsAfterInsn.end())
1022     return;
1023
1024   // Label already assigned.
1025   if (I->second)
1026     return;
1027
1028   // We need a label after this instruction.
1029   if (!PrevLabel) {
1030     PrevLabel = MMI->getContext().createTempSymbol();
1031     Asm->OutStreamer->EmitLabel(PrevLabel);
1032   }
1033   I->second = PrevLabel;
1034 }
1035
1036 // Each LexicalScope has first instruction and last instruction to mark
1037 // beginning and end of a scope respectively. Create an inverse map that list
1038 // scopes starts (and ends) with an instruction. One instruction may start (or
1039 // end) multiple scopes. Ignore scopes that are not reachable.
1040 void DwarfDebug::identifyScopeMarkers() {
1041   SmallVector<LexicalScope *, 4> WorkList;
1042   WorkList.push_back(LScopes.getCurrentFunctionScope());
1043   while (!WorkList.empty()) {
1044     LexicalScope *S = WorkList.pop_back_val();
1045
1046     const SmallVectorImpl<LexicalScope *> &Children = S->getChildren();
1047     if (!Children.empty())
1048       WorkList.append(Children.begin(), Children.end());
1049
1050     if (S->isAbstractScope())
1051       continue;
1052
1053     for (const InsnRange &R : S->getRanges()) {
1054       assert(R.first && "InsnRange does not have first instruction!");
1055       assert(R.second && "InsnRange does not have second instruction!");
1056       requestLabelBeforeInsn(R.first);
1057       requestLabelAfterInsn(R.second);
1058     }
1059   }
1060 }
1061
1062 static DebugLoc findPrologueEndLoc(const MachineFunction *MF) {
1063   // First known non-DBG_VALUE and non-frame setup location marks
1064   // the beginning of the function body.
1065   for (const auto &MBB : *MF)
1066     for (const auto &MI : MBB)
1067       if (!MI.isDebugValue() && !MI.getFlag(MachineInstr::FrameSetup) &&
1068           MI.getDebugLoc()) {
1069         // Did the target forget to set the FrameSetup flag for CFI insns?
1070         assert(!MI.isCFIInstruction() &&
1071                "First non-frame-setup instruction is a CFI instruction.");
1072         return MI.getDebugLoc();
1073       }
1074   return DebugLoc();
1075 }
1076
1077 // Gather pre-function debug information.  Assumes being called immediately
1078 // after the function entry point has been emitted.
1079 void DwarfDebug::beginFunction(const MachineFunction *MF) {
1080   CurFn = MF;
1081
1082   // If there's no debug info for the function we're not going to do anything.
1083   if (!MMI->hasDebugInfo())
1084     return;
1085
1086   auto DI = FunctionDIs.find(MF->getFunction());
1087   if (DI == FunctionDIs.end())
1088     return;
1089
1090   // Grab the lexical scopes for the function, if we don't have any of those
1091   // then we're not going to be able to do anything.
1092   LScopes.initialize(*MF);
1093   if (LScopes.empty())
1094     return;
1095
1096   assert(DbgValues.empty() && "DbgValues map wasn't cleaned!");
1097
1098   // Make sure that each lexical scope will have a begin/end label.
1099   identifyScopeMarkers();
1100
1101   // Set DwarfDwarfCompileUnitID in MCContext to the Compile Unit this function
1102   // belongs to so that we add to the correct per-cu line table in the
1103   // non-asm case.
1104   LexicalScope *FnScope = LScopes.getCurrentFunctionScope();
1105   // FnScope->getScopeNode() and DI->second should represent the same function,
1106   // though they may not be the same MDNode due to inline functions merged in
1107   // LTO where the debug info metadata still differs (either due to distinct
1108   // written differences - two versions of a linkonce_odr function
1109   // written/copied into two separate files, or some sub-optimal metadata that
1110   // isn't structurally identical (see: file path/name info from clang, which
1111   // includes the directory of the cpp file being built, even when the file name
1112   // is absolute (such as an <> lookup header)))
1113   DwarfCompileUnit *TheCU = SPMap.lookup(FnScope->getScopeNode());
1114   assert(TheCU && "Unable to find compile unit!");
1115   if (Asm->OutStreamer->hasRawTextSupport())
1116     // Use a single line table if we are generating assembly.
1117     Asm->OutStreamer->getContext().setDwarfCompileUnitID(0);
1118   else
1119     Asm->OutStreamer->getContext().setDwarfCompileUnitID(TheCU->getUniqueID());
1120
1121   // Calculate history for local variables.
1122   calculateDbgValueHistory(MF, Asm->MF->getSubtarget().getRegisterInfo(),
1123                            DbgValues);
1124
1125   // Request labels for the full history.
1126   for (const auto &I : DbgValues) {
1127     const auto &Ranges = I.second;
1128     if (Ranges.empty())
1129       continue;
1130
1131     // The first mention of a function argument gets the CurrentFnBegin
1132     // label, so arguments are visible when breaking at function entry.
1133     const DILocalVariable *DIVar = Ranges.front().first->getDebugVariable();
1134     if (DIVar->getTag() == dwarf::DW_TAG_arg_variable &&
1135         getDISubprogram(DIVar->getScope())->describes(MF->getFunction())) {
1136       LabelsBeforeInsn[Ranges.front().first] = Asm->getFunctionBegin();
1137       if (Ranges.front().first->getDebugExpression()->isBitPiece()) {
1138         // Mark all non-overlapping initial pieces.
1139         for (auto I = Ranges.begin(); I != Ranges.end(); ++I) {
1140           const DIExpression *Piece = I->first->getDebugExpression();
1141           if (std::all_of(Ranges.begin(), I,
1142                           [&](DbgValueHistoryMap::InstrRange Pred) {
1143                 return !piecesOverlap(Piece, Pred.first->getDebugExpression());
1144               }))
1145             LabelsBeforeInsn[I->first] = Asm->getFunctionBegin();
1146           else
1147             break;
1148         }
1149       }
1150     }
1151
1152     for (const auto &Range : Ranges) {
1153       requestLabelBeforeInsn(Range.first);
1154       if (Range.second)
1155         requestLabelAfterInsn(Range.second);
1156     }
1157   }
1158
1159   PrevInstLoc = DebugLoc();
1160   PrevLabel = Asm->getFunctionBegin();
1161
1162   // Record beginning of function.
1163   PrologEndLoc = findPrologueEndLoc(MF);
1164   if (DILocation *L = PrologEndLoc) {
1165     // We'd like to list the prologue as "not statements" but GDB behaves
1166     // poorly if we do that. Revisit this with caution/GDB (7.5+) testing.
1167     auto *SP = L->getInlinedAtScope()->getSubprogram();
1168     recordSourceLine(SP->getScopeLine(), 0, SP, DWARF2_FLAG_IS_STMT);
1169   }
1170 }
1171
1172 // Gather and emit post-function debug information.
1173 void DwarfDebug::endFunction(const MachineFunction *MF) {
1174   assert(CurFn == MF &&
1175       "endFunction should be called with the same function as beginFunction");
1176
1177   if (!MMI->hasDebugInfo() || LScopes.empty() ||
1178       !FunctionDIs.count(MF->getFunction())) {
1179     // If we don't have a lexical scope for this function then there will
1180     // be a hole in the range information. Keep note of this by setting the
1181     // previously used section to nullptr.
1182     PrevCU = nullptr;
1183     CurFn = nullptr;
1184     return;
1185   }
1186
1187   // Set DwarfDwarfCompileUnitID in MCContext to default value.
1188   Asm->OutStreamer->getContext().setDwarfCompileUnitID(0);
1189
1190   LexicalScope *FnScope = LScopes.getCurrentFunctionScope();
1191   auto *SP = cast<DISubprogram>(FnScope->getScopeNode());
1192   DwarfCompileUnit &TheCU = *SPMap.lookup(SP);
1193
1194   DenseSet<InlinedVariable> ProcessedVars;
1195   collectVariableInfo(TheCU, SP, ProcessedVars);
1196
1197   // Add the range of this function to the list of ranges for the CU.
1198   TheCU.addRange(RangeSpan(Asm->getFunctionBegin(), Asm->getFunctionEnd()));
1199
1200   // Under -gmlt, skip building the subprogram if there are no inlined
1201   // subroutines inside it.
1202   if (TheCU.getCUNode()->getEmissionKind() == DIBuilder::LineTablesOnly &&
1203       LScopes.getAbstractScopesList().empty() && !IsDarwin) {
1204     assert(InfoHolder.getScopeVariables().empty());
1205     assert(DbgValues.empty());
1206     // FIXME: This wouldn't be true in LTO with a -g (with inlining) CU followed
1207     // by a -gmlt CU. Add a test and remove this assertion.
1208     assert(AbstractVariables.empty());
1209     LabelsBeforeInsn.clear();
1210     LabelsAfterInsn.clear();
1211     PrevLabel = nullptr;
1212     CurFn = nullptr;
1213     return;
1214   }
1215
1216 #ifndef NDEBUG
1217   size_t NumAbstractScopes = LScopes.getAbstractScopesList().size();
1218 #endif
1219   // Construct abstract scopes.
1220   for (LexicalScope *AScope : LScopes.getAbstractScopesList()) {
1221     auto *SP = cast<DISubprogram>(AScope->getScopeNode());
1222     // Collect info for variables that were optimized out.
1223     for (const DILocalVariable *DV : SP->getVariables()) {
1224       if (!ProcessedVars.insert(InlinedVariable(DV, nullptr)).second)
1225         continue;
1226       ensureAbstractVariableIsCreated(InlinedVariable(DV, nullptr),
1227                                       DV->getScope());
1228       assert(LScopes.getAbstractScopesList().size() == NumAbstractScopes
1229              && "ensureAbstractVariableIsCreated inserted abstract scopes");
1230     }
1231     constructAbstractSubprogramScopeDIE(AScope);
1232   }
1233
1234   TheCU.constructSubprogramScopeDIE(FnScope);
1235   if (auto *SkelCU = TheCU.getSkeleton())
1236     if (!LScopes.getAbstractScopesList().empty())
1237       SkelCU->constructSubprogramScopeDIE(FnScope);
1238
1239   // Clear debug info
1240   // Ownership of DbgVariables is a bit subtle - ScopeVariables owns all the
1241   // DbgVariables except those that are also in AbstractVariables (since they
1242   // can be used cross-function)
1243   InfoHolder.getScopeVariables().clear();
1244   DbgValues.clear();
1245   LabelsBeforeInsn.clear();
1246   LabelsAfterInsn.clear();
1247   PrevLabel = nullptr;
1248   CurFn = nullptr;
1249 }
1250
1251 // Register a source line with debug info. Returns the  unique label that was
1252 // emitted and which provides correspondence to the source line list.
1253 void DwarfDebug::recordSourceLine(unsigned Line, unsigned Col, const MDNode *S,
1254                                   unsigned Flags) {
1255   StringRef Fn;
1256   StringRef Dir;
1257   unsigned Src = 1;
1258   unsigned Discriminator = 0;
1259   if (auto *Scope = cast_or_null<DIScope>(S)) {
1260     Fn = Scope->getFilename();
1261     Dir = Scope->getDirectory();
1262     if (auto *LBF = dyn_cast<DILexicalBlockFile>(Scope))
1263       Discriminator = LBF->getDiscriminator();
1264
1265     unsigned CUID = Asm->OutStreamer->getContext().getDwarfCompileUnitID();
1266     Src = static_cast<DwarfCompileUnit &>(*InfoHolder.getUnits()[CUID])
1267               .getOrCreateSourceID(Fn, Dir);
1268   }
1269   Asm->OutStreamer->EmitDwarfLocDirective(Src, Line, Col, Flags, 0,
1270                                           Discriminator, Fn);
1271 }
1272
1273 //===----------------------------------------------------------------------===//
1274 // Emit Methods
1275 //===----------------------------------------------------------------------===//
1276
1277 // Emit the debug info section.
1278 void DwarfDebug::emitDebugInfo() {
1279   DwarfFile &Holder = useSplitDwarf() ? SkeletonHolder : InfoHolder;
1280   Holder.emitUnits(/* UseOffsets */ false);
1281 }
1282
1283 // Emit the abbreviation section.
1284 void DwarfDebug::emitAbbreviations() {
1285   DwarfFile &Holder = useSplitDwarf() ? SkeletonHolder : InfoHolder;
1286
1287   Holder.emitAbbrevs(Asm->getObjFileLowering().getDwarfAbbrevSection());
1288 }
1289
1290 void DwarfDebug::emitAccel(DwarfAccelTable &Accel, const MCSection *Section,
1291                            StringRef TableName) {
1292   Accel.FinalizeTable(Asm, TableName);
1293   Asm->OutStreamer->SwitchSection(Section);
1294
1295   // Emit the full data.
1296   Accel.emit(Asm, Section->getBeginSymbol(), this);
1297 }
1298
1299 // Emit visible names into a hashed accelerator table section.
1300 void DwarfDebug::emitAccelNames() {
1301   emitAccel(AccelNames, Asm->getObjFileLowering().getDwarfAccelNamesSection(),
1302             "Names");
1303 }
1304
1305 // Emit objective C classes and categories into a hashed accelerator table
1306 // section.
1307 void DwarfDebug::emitAccelObjC() {
1308   emitAccel(AccelObjC, Asm->getObjFileLowering().getDwarfAccelObjCSection(),
1309             "ObjC");
1310 }
1311
1312 // Emit namespace dies into a hashed accelerator table.
1313 void DwarfDebug::emitAccelNamespaces() {
1314   emitAccel(AccelNamespace,
1315             Asm->getObjFileLowering().getDwarfAccelNamespaceSection(),
1316             "namespac");
1317 }
1318
1319 // Emit type dies into a hashed accelerator table.
1320 void DwarfDebug::emitAccelTypes() {
1321   emitAccel(AccelTypes, Asm->getObjFileLowering().getDwarfAccelTypesSection(),
1322             "types");
1323 }
1324
1325 // Public name handling.
1326 // The format for the various pubnames:
1327 //
1328 // dwarf pubnames - offset/name pairs where the offset is the offset into the CU
1329 // for the DIE that is named.
1330 //
1331 // gnu pubnames - offset/index value/name tuples where the offset is the offset
1332 // into the CU and the index value is computed according to the type of value
1333 // for the DIE that is named.
1334 //
1335 // For type units the offset is the offset of the skeleton DIE. For split dwarf
1336 // it's the offset within the debug_info/debug_types dwo section, however, the
1337 // reference in the pubname header doesn't change.
1338
1339 /// computeIndexValue - Compute the gdb index value for the DIE and CU.
1340 static dwarf::PubIndexEntryDescriptor computeIndexValue(DwarfUnit *CU,
1341                                                         const DIE *Die) {
1342   dwarf::GDBIndexEntryLinkage Linkage = dwarf::GIEL_STATIC;
1343
1344   // We could have a specification DIE that has our most of our knowledge,
1345   // look for that now.
1346   DIEValue *SpecVal = Die->findAttribute(dwarf::DW_AT_specification);
1347   if (SpecVal) {
1348     DIE &SpecDIE = cast<DIEEntry>(SpecVal)->getEntry();
1349     if (SpecDIE.findAttribute(dwarf::DW_AT_external))
1350       Linkage = dwarf::GIEL_EXTERNAL;
1351   } else if (Die->findAttribute(dwarf::DW_AT_external))
1352     Linkage = dwarf::GIEL_EXTERNAL;
1353
1354   switch (Die->getTag()) {
1355   case dwarf::DW_TAG_class_type:
1356   case dwarf::DW_TAG_structure_type:
1357   case dwarf::DW_TAG_union_type:
1358   case dwarf::DW_TAG_enumeration_type:
1359     return dwarf::PubIndexEntryDescriptor(
1360         dwarf::GIEK_TYPE, CU->getLanguage() != dwarf::DW_LANG_C_plus_plus
1361                               ? dwarf::GIEL_STATIC
1362                               : dwarf::GIEL_EXTERNAL);
1363   case dwarf::DW_TAG_typedef:
1364   case dwarf::DW_TAG_base_type:
1365   case dwarf::DW_TAG_subrange_type:
1366     return dwarf::PubIndexEntryDescriptor(dwarf::GIEK_TYPE, dwarf::GIEL_STATIC);
1367   case dwarf::DW_TAG_namespace:
1368     return dwarf::GIEK_TYPE;
1369   case dwarf::DW_TAG_subprogram:
1370     return dwarf::PubIndexEntryDescriptor(dwarf::GIEK_FUNCTION, Linkage);
1371   case dwarf::DW_TAG_variable:
1372     return dwarf::PubIndexEntryDescriptor(dwarf::GIEK_VARIABLE, Linkage);
1373   case dwarf::DW_TAG_enumerator:
1374     return dwarf::PubIndexEntryDescriptor(dwarf::GIEK_VARIABLE,
1375                                           dwarf::GIEL_STATIC);
1376   default:
1377     return dwarf::GIEK_NONE;
1378   }
1379 }
1380
1381 /// emitDebugPubNames - Emit visible names into a debug pubnames section.
1382 ///
1383 void DwarfDebug::emitDebugPubNames(bool GnuStyle) {
1384   const MCSection *PSec =
1385       GnuStyle ? Asm->getObjFileLowering().getDwarfGnuPubNamesSection()
1386                : Asm->getObjFileLowering().getDwarfPubNamesSection();
1387
1388   emitDebugPubSection(GnuStyle, PSec, "Names",
1389                       &DwarfCompileUnit::getGlobalNames);
1390 }
1391
1392 void DwarfDebug::emitDebugPubSection(
1393     bool GnuStyle, const MCSection *PSec, StringRef Name,
1394     const StringMap<const DIE *> &(DwarfCompileUnit::*Accessor)() const) {
1395   for (const auto &NU : CUMap) {
1396     DwarfCompileUnit *TheU = NU.second;
1397
1398     const auto &Globals = (TheU->*Accessor)();
1399
1400     if (Globals.empty())
1401       continue;
1402
1403     if (auto *Skeleton = TheU->getSkeleton())
1404       TheU = Skeleton;
1405
1406     // Start the dwarf pubnames section.
1407     Asm->OutStreamer->SwitchSection(PSec);
1408
1409     // Emit the header.
1410     Asm->OutStreamer->AddComment("Length of Public " + Name + " Info");
1411     MCSymbol *BeginLabel = Asm->createTempSymbol("pub" + Name + "_begin");
1412     MCSymbol *EndLabel = Asm->createTempSymbol("pub" + Name + "_end");
1413     Asm->EmitLabelDifference(EndLabel, BeginLabel, 4);
1414
1415     Asm->OutStreamer->EmitLabel(BeginLabel);
1416
1417     Asm->OutStreamer->AddComment("DWARF Version");
1418     Asm->EmitInt16(dwarf::DW_PUBNAMES_VERSION);
1419
1420     Asm->OutStreamer->AddComment("Offset of Compilation Unit Info");
1421     Asm->emitSectionOffset(TheU->getLabelBegin());
1422
1423     Asm->OutStreamer->AddComment("Compilation Unit Length");
1424     Asm->EmitInt32(TheU->getLength());
1425
1426     // Emit the pubnames for this compilation unit.
1427     for (const auto &GI : Globals) {
1428       const char *Name = GI.getKeyData();
1429       const DIE *Entity = GI.second;
1430
1431       Asm->OutStreamer->AddComment("DIE offset");
1432       Asm->EmitInt32(Entity->getOffset());
1433
1434       if (GnuStyle) {
1435         dwarf::PubIndexEntryDescriptor Desc = computeIndexValue(TheU, Entity);
1436         Asm->OutStreamer->AddComment(
1437             Twine("Kind: ") + dwarf::GDBIndexEntryKindString(Desc.Kind) + ", " +
1438             dwarf::GDBIndexEntryLinkageString(Desc.Linkage));
1439         Asm->EmitInt8(Desc.toBits());
1440       }
1441
1442       Asm->OutStreamer->AddComment("External Name");
1443       Asm->OutStreamer->EmitBytes(StringRef(Name, GI.getKeyLength() + 1));
1444     }
1445
1446     Asm->OutStreamer->AddComment("End Mark");
1447     Asm->EmitInt32(0);
1448     Asm->OutStreamer->EmitLabel(EndLabel);
1449   }
1450 }
1451
1452 void DwarfDebug::emitDebugPubTypes(bool GnuStyle) {
1453   const MCSection *PSec =
1454       GnuStyle ? Asm->getObjFileLowering().getDwarfGnuPubTypesSection()
1455                : Asm->getObjFileLowering().getDwarfPubTypesSection();
1456
1457   emitDebugPubSection(GnuStyle, PSec, "Types",
1458                       &DwarfCompileUnit::getGlobalTypes);
1459 }
1460
1461 // Emit visible names into a debug str section.
1462 void DwarfDebug::emitDebugStr() {
1463   DwarfFile &Holder = useSplitDwarf() ? SkeletonHolder : InfoHolder;
1464   Holder.emitStrings(Asm->getObjFileLowering().getDwarfStrSection());
1465 }
1466
1467 void DwarfDebug::emitDebugLocEntry(ByteStreamer &Streamer,
1468                                    const DebugLocStream::Entry &Entry) {
1469   auto &&Comments = DebugLocs.getComments(Entry);
1470   auto Comment = Comments.begin();
1471   auto End = Comments.end();
1472   for (uint8_t Byte : DebugLocs.getBytes(Entry))
1473     Streamer.EmitInt8(Byte, Comment != End ? *(Comment++) : "");
1474 }
1475
1476 static void emitDebugLocValue(const AsmPrinter &AP, const DIBasicType *BT,
1477                               ByteStreamer &Streamer,
1478                               const DebugLocEntry::Value &Value,
1479                               unsigned PieceOffsetInBits) {
1480   DebugLocDwarfExpression DwarfExpr(*AP.MF->getSubtarget().getRegisterInfo(),
1481                                     AP.getDwarfDebug()->getDwarfVersion(),
1482                                     AP.OutStreamer->hasRawTextSupport(),
1483                                     Streamer);
1484   // Regular entry.
1485   if (Value.isInt()) {
1486     if (BT && (BT->getEncoding() == dwarf::DW_ATE_signed ||
1487                BT->getEncoding() == dwarf::DW_ATE_signed_char))
1488       DwarfExpr.AddSignedConstant(Value.getInt());
1489     else
1490       DwarfExpr.AddUnsignedConstant(Value.getInt());
1491   } else if (Value.isLocation()) {
1492     MachineLocation Loc = Value.getLoc();
1493     const DIExpression *Expr = Value.getExpression();
1494     if (!Expr || !Expr->getNumElements())
1495       // Regular entry.
1496       AP.EmitDwarfRegOp(Streamer, Loc);
1497     else {
1498       // Complex address entry.
1499       if (Loc.getOffset()) {
1500         DwarfExpr.AddMachineRegIndirect(Loc.getReg(), Loc.getOffset());
1501         DwarfExpr.AddExpression(Expr->expr_op_begin(), Expr->expr_op_end(),
1502                                 PieceOffsetInBits);
1503       } else
1504         DwarfExpr.AddMachineRegExpression(Expr, Loc.getReg(),
1505                                           PieceOffsetInBits);
1506     }
1507   }
1508   // else ... ignore constant fp. There is not any good way to
1509   // to represent them here in dwarf.
1510   // FIXME: ^
1511 }
1512
1513 void DebugLocEntry::finalize(const AsmPrinter &AP, DebugLocStream &Locs,
1514                              const DIBasicType *BT) {
1515   Locs.startEntry(Begin, End);
1516   BufferByteStreamer Streamer = Locs.getStreamer();
1517   const DebugLocEntry::Value &Value = Values[0];
1518   if (Value.isBitPiece()) {
1519     // Emit all pieces that belong to the same variable and range.
1520     assert(std::all_of(Values.begin(), Values.end(), [](DebugLocEntry::Value P) {
1521           return P.isBitPiece();
1522         }) && "all values are expected to be pieces");
1523     assert(std::is_sorted(Values.begin(), Values.end()) &&
1524            "pieces are expected to be sorted");
1525    
1526     unsigned Offset = 0;
1527     for (auto Piece : Values) {
1528       const DIExpression *Expr = Piece.getExpression();
1529       unsigned PieceOffset = Expr->getBitPieceOffset();
1530       unsigned PieceSize = Expr->getBitPieceSize();
1531       assert(Offset <= PieceOffset && "overlapping or duplicate pieces");
1532       if (Offset < PieceOffset) {
1533         // The DWARF spec seriously mandates pieces with no locations for gaps.
1534         DebugLocDwarfExpression Expr(*AP.MF->getSubtarget().getRegisterInfo(),
1535                                      AP.getDwarfDebug()->getDwarfVersion(),
1536                                      AP.OutStreamer->hasRawTextSupport(),
1537                                      Streamer);
1538         Expr.AddOpPiece(PieceOffset-Offset, 0);
1539         Offset += PieceOffset-Offset;
1540       }
1541       Offset += PieceSize;
1542
1543       emitDebugLocValue(AP, BT, Streamer, Piece, PieceOffset);
1544     }
1545   } else {
1546     assert(Values.size() == 1 && "only pieces may have >1 value");
1547     emitDebugLocValue(AP, BT, Streamer, Value, 0);
1548   }
1549 }
1550
1551 void DwarfDebug::emitDebugLocEntryLocation(const DebugLocStream::Entry &Entry) {
1552   // Emit the size.
1553   Asm->OutStreamer->AddComment("Loc expr size");
1554   Asm->EmitInt16(DebugLocs.getBytes(Entry).size());
1555
1556   // Emit the entry.
1557   APByteStreamer Streamer(*Asm);
1558   emitDebugLocEntry(Streamer, Entry);
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                                       const 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, cast<DICompositeType>(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 }