PR20038: DebugInfo missing DIEs for some concrete variables.
[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 "ByteStreamer.h"
15 #include "DwarfDebug.h"
16 #include "DIE.h"
17 #include "DIEHash.h"
18 #include "DwarfUnit.h"
19 #include "llvm/ADT/STLExtras.h"
20 #include "llvm/ADT/Statistic.h"
21 #include "llvm/ADT/StringExtras.h"
22 #include "llvm/ADT/Triple.h"
23 #include "llvm/CodeGen/MachineFunction.h"
24 #include "llvm/CodeGen/MachineModuleInfo.h"
25 #include "llvm/IR/Constants.h"
26 #include "llvm/IR/DIBuilder.h"
27 #include "llvm/IR/DataLayout.h"
28 #include "llvm/IR/DebugInfo.h"
29 #include "llvm/IR/Instructions.h"
30 #include "llvm/IR/Module.h"
31 #include "llvm/IR/ValueHandle.h"
32 #include "llvm/MC/MCAsmInfo.h"
33 #include "llvm/MC/MCSection.h"
34 #include "llvm/MC/MCStreamer.h"
35 #include "llvm/MC/MCSymbol.h"
36 #include "llvm/Support/CommandLine.h"
37 #include "llvm/Support/Debug.h"
38 #include "llvm/Support/Dwarf.h"
39 #include "llvm/Support/ErrorHandling.h"
40 #include "llvm/Support/FormattedStream.h"
41 #include "llvm/Support/LEB128.h"
42 #include "llvm/Support/MD5.h"
43 #include "llvm/Support/Path.h"
44 #include "llvm/Support/Timer.h"
45 #include "llvm/Target/TargetFrameLowering.h"
46 #include "llvm/Target/TargetLoweringObjectFile.h"
47 #include "llvm/Target/TargetMachine.h"
48 #include "llvm/Target/TargetOptions.h"
49 #include "llvm/Target/TargetRegisterInfo.h"
50 using namespace llvm;
51
52 #define DEBUG_TYPE "dwarfdebug"
53
54 static cl::opt<bool>
55 DisableDebugInfoPrinting("disable-debug-info-print", cl::Hidden,
56                          cl::desc("Disable debug info printing"));
57
58 static cl::opt<bool> UnknownLocations(
59     "use-unknown-locations", cl::Hidden,
60     cl::desc("Make an absence of debug location information explicit."),
61     cl::init(false));
62
63 static cl::opt<bool>
64 GenerateGnuPubSections("generate-gnu-dwarf-pub-sections", cl::Hidden,
65                        cl::desc("Generate GNU-style pubnames and pubtypes"),
66                        cl::init(false));
67
68 static cl::opt<bool> GenerateARangeSection("generate-arange-section",
69                                            cl::Hidden,
70                                            cl::desc("Generate dwarf aranges"),
71                                            cl::init(false));
72
73 namespace {
74 enum DefaultOnOff { Default, Enable, Disable };
75 }
76
77 static cl::opt<DefaultOnOff>
78 DwarfAccelTables("dwarf-accel-tables", cl::Hidden,
79                  cl::desc("Output prototype dwarf accelerator tables."),
80                  cl::values(clEnumVal(Default, "Default for platform"),
81                             clEnumVal(Enable, "Enabled"),
82                             clEnumVal(Disable, "Disabled"), clEnumValEnd),
83                  cl::init(Default));
84
85 static cl::opt<DefaultOnOff>
86 SplitDwarf("split-dwarf", cl::Hidden,
87            cl::desc("Output DWARF5 split debug info."),
88            cl::values(clEnumVal(Default, "Default for platform"),
89                       clEnumVal(Enable, "Enabled"),
90                       clEnumVal(Disable, "Disabled"), clEnumValEnd),
91            cl::init(Default));
92
93 static cl::opt<DefaultOnOff>
94 DwarfPubSections("generate-dwarf-pub-sections", cl::Hidden,
95                  cl::desc("Generate DWARF pubnames and pubtypes sections"),
96                  cl::values(clEnumVal(Default, "Default for platform"),
97                             clEnumVal(Enable, "Enabled"),
98                             clEnumVal(Disable, "Disabled"), clEnumValEnd),
99                  cl::init(Default));
100
101 static cl::opt<unsigned>
102 DwarfVersionNumber("dwarf-version", cl::Hidden,
103                    cl::desc("Generate DWARF for dwarf version."), cl::init(0));
104
105 static const char *const DWARFGroupName = "DWARF Emission";
106 static const char *const DbgTimerName = "DWARF Debug Writer";
107
108 //===----------------------------------------------------------------------===//
109
110 /// resolve - Look in the DwarfDebug map for the MDNode that
111 /// corresponds to the reference.
112 template <typename T> T DbgVariable::resolve(DIRef<T> Ref) const {
113   return DD->resolve(Ref);
114 }
115
116 bool DbgVariable::isBlockByrefVariable() const {
117   assert(Var.isVariable() && "Invalid complex DbgVariable!");
118   return Var.isBlockByrefVariable(DD->getTypeIdentifierMap());
119 }
120
121 DIType DbgVariable::getType() const {
122   DIType Ty = Var.getType().resolve(DD->getTypeIdentifierMap());
123   // FIXME: isBlockByrefVariable should be reformulated in terms of complex
124   // addresses instead.
125   if (Var.isBlockByrefVariable(DD->getTypeIdentifierMap())) {
126     /* Byref variables, in Blocks, are declared by the programmer as
127        "SomeType VarName;", but the compiler creates a
128        __Block_byref_x_VarName struct, and gives the variable VarName
129        either the struct, or a pointer to the struct, as its type.  This
130        is necessary for various behind-the-scenes things the compiler
131        needs to do with by-reference variables in blocks.
132
133        However, as far as the original *programmer* is concerned, the
134        variable should still have type 'SomeType', as originally declared.
135
136        The following function dives into the __Block_byref_x_VarName
137        struct to find the original type of the variable.  This will be
138        passed back to the code generating the type for the Debug
139        Information Entry for the variable 'VarName'.  'VarName' will then
140        have the original type 'SomeType' in its debug information.
141
142        The original type 'SomeType' will be the type of the field named
143        'VarName' inside the __Block_byref_x_VarName struct.
144
145        NOTE: In order for this to not completely fail on the debugger
146        side, the Debug Information Entry for the variable VarName needs to
147        have a DW_AT_location that tells the debugger how to unwind through
148        the pointers and __Block_byref_x_VarName struct to find the actual
149        value of the variable.  The function addBlockByrefType does this.  */
150     DIType subType = Ty;
151     uint16_t tag = Ty.getTag();
152
153     if (tag == dwarf::DW_TAG_pointer_type)
154       subType = resolve(DIDerivedType(Ty).getTypeDerivedFrom());
155
156     DIArray Elements = DICompositeType(subType).getTypeArray();
157     for (unsigned i = 0, N = Elements.getNumElements(); i < N; ++i) {
158       DIDerivedType DT(Elements.getElement(i));
159       if (getName() == DT.getName())
160         return (resolve(DT.getTypeDerivedFrom()));
161     }
162   }
163   return Ty;
164 }
165
166 static LLVM_CONSTEXPR DwarfAccelTable::Atom TypeAtoms[] = {
167     DwarfAccelTable::Atom(dwarf::DW_ATOM_die_offset, dwarf::DW_FORM_data4),
168     DwarfAccelTable::Atom(dwarf::DW_ATOM_die_tag, dwarf::DW_FORM_data2),
169     DwarfAccelTable::Atom(dwarf::DW_ATOM_type_flags, dwarf::DW_FORM_data1)};
170
171 DwarfDebug::DwarfDebug(AsmPrinter *A, Module *M)
172     : Asm(A), MMI(Asm->MMI), FirstCU(nullptr), PrevLabel(nullptr),
173       GlobalRangeCount(0), InfoHolder(A, "info_string", DIEValueAllocator),
174       UsedNonDefaultText(false),
175       SkeletonHolder(A, "skel_string", DIEValueAllocator),
176       AccelNames(DwarfAccelTable::Atom(dwarf::DW_ATOM_die_offset,
177                                        dwarf::DW_FORM_data4)),
178       AccelObjC(DwarfAccelTable::Atom(dwarf::DW_ATOM_die_offset,
179                                       dwarf::DW_FORM_data4)),
180       AccelNamespace(DwarfAccelTable::Atom(dwarf::DW_ATOM_die_offset,
181                                            dwarf::DW_FORM_data4)),
182       AccelTypes(TypeAtoms) {
183
184   DwarfInfoSectionSym = DwarfAbbrevSectionSym = DwarfStrSectionSym = nullptr;
185   DwarfDebugRangeSectionSym = DwarfDebugLocSectionSym = nullptr;
186   DwarfLineSectionSym = nullptr;
187   DwarfAddrSectionSym = nullptr;
188   DwarfAbbrevDWOSectionSym = DwarfStrDWOSectionSym = nullptr;
189   FunctionBeginSym = FunctionEndSym = nullptr;
190   CurFn = nullptr;
191   CurMI = nullptr;
192
193   // Turn on accelerator tables for Darwin by default, pubnames by
194   // default for non-Darwin, and handle split dwarf.
195   bool IsDarwin = Triple(A->getTargetTriple()).isOSDarwin();
196
197   if (DwarfAccelTables == Default)
198     HasDwarfAccelTables = IsDarwin;
199   else
200     HasDwarfAccelTables = DwarfAccelTables == Enable;
201
202   if (SplitDwarf == Default)
203     HasSplitDwarf = false;
204   else
205     HasSplitDwarf = SplitDwarf == Enable;
206
207   if (DwarfPubSections == Default)
208     HasDwarfPubSections = !IsDarwin;
209   else
210     HasDwarfPubSections = DwarfPubSections == Enable;
211
212   DwarfVersion = DwarfVersionNumber ? DwarfVersionNumber
213                                     : MMI->getModule()->getDwarfVersion();
214
215   {
216     NamedRegionTimer T(DbgTimerName, DWARFGroupName, TimePassesIsEnabled);
217     beginModule();
218   }
219 }
220
221 // Define out of line so we don't have to include DwarfUnit.h in DwarfDebug.h.
222 DwarfDebug::~DwarfDebug() { }
223
224 // Switch to the specified MCSection and emit an assembler
225 // temporary label to it if SymbolStem is specified.
226 static MCSymbol *emitSectionSym(AsmPrinter *Asm, const MCSection *Section,
227                                 const char *SymbolStem = nullptr) {
228   Asm->OutStreamer.SwitchSection(Section);
229   if (!SymbolStem)
230     return nullptr;
231
232   MCSymbol *TmpSym = Asm->GetTempSymbol(SymbolStem);
233   Asm->OutStreamer.EmitLabel(TmpSym);
234   return TmpSym;
235 }
236
237 static bool isObjCClass(StringRef Name) {
238   return Name.startswith("+") || Name.startswith("-");
239 }
240
241 static bool hasObjCCategory(StringRef Name) {
242   if (!isObjCClass(Name))
243     return false;
244
245   return Name.find(") ") != StringRef::npos;
246 }
247
248 static void getObjCClassCategory(StringRef In, StringRef &Class,
249                                  StringRef &Category) {
250   if (!hasObjCCategory(In)) {
251     Class = In.slice(In.find('[') + 1, In.find(' '));
252     Category = "";
253     return;
254   }
255
256   Class = In.slice(In.find('[') + 1, In.find('('));
257   Category = In.slice(In.find('[') + 1, In.find(' '));
258   return;
259 }
260
261 static StringRef getObjCMethodName(StringRef In) {
262   return In.slice(In.find(' ') + 1, In.find(']'));
263 }
264
265 // Helper for sorting sections into a stable output order.
266 static bool SectionSort(const MCSection *A, const MCSection *B) {
267   std::string LA = (A ? A->getLabelBeginName() : "");
268   std::string LB = (B ? B->getLabelBeginName() : "");
269   return LA < LB;
270 }
271
272 // Add the various names to the Dwarf accelerator table names.
273 // TODO: Determine whether or not we should add names for programs
274 // that do not have a DW_AT_name or DW_AT_linkage_name field - this
275 // is only slightly different than the lookup of non-standard ObjC names.
276 void DwarfDebug::addSubprogramNames(DISubprogram SP, DIE &Die) {
277   if (!SP.isDefinition())
278     return;
279   addAccelName(SP.getName(), Die);
280
281   // If the linkage name is different than the name, go ahead and output
282   // that as well into the name table.
283   if (SP.getLinkageName() != "" && SP.getName() != SP.getLinkageName())
284     addAccelName(SP.getLinkageName(), Die);
285
286   // If this is an Objective-C selector name add it to the ObjC accelerator
287   // too.
288   if (isObjCClass(SP.getName())) {
289     StringRef Class, Category;
290     getObjCClassCategory(SP.getName(), Class, Category);
291     addAccelObjC(Class, Die);
292     if (Category != "")
293       addAccelObjC(Category, Die);
294     // Also add the base method name to the name table.
295     addAccelName(getObjCMethodName(SP.getName()), Die);
296   }
297 }
298
299 /// isSubprogramContext - Return true if Context is either a subprogram
300 /// or another context nested inside a subprogram.
301 bool DwarfDebug::isSubprogramContext(const MDNode *Context) {
302   if (!Context)
303     return false;
304   DIDescriptor D(Context);
305   if (D.isSubprogram())
306     return true;
307   if (D.isType())
308     return isSubprogramContext(resolve(DIType(Context).getContext()));
309   return false;
310 }
311
312 // Find DIE for the given subprogram and attach appropriate DW_AT_low_pc
313 // and DW_AT_high_pc attributes. If there are global variables in this
314 // scope then create and insert DIEs for these variables.
315 DIE &DwarfDebug::updateSubprogramScopeDIE(DwarfCompileUnit &SPCU,
316                                           DISubprogram SP) {
317   DIE *SPDie = SPCU.getOrCreateSubprogramDIE(SP);
318
319   attachLowHighPC(SPCU, *SPDie, FunctionBeginSym, FunctionEndSym);
320
321   const TargetRegisterInfo *RI = Asm->TM.getRegisterInfo();
322   MachineLocation Location(RI->getFrameRegister(*Asm->MF));
323   SPCU.addAddress(*SPDie, dwarf::DW_AT_frame_base, Location);
324
325   // Add name to the name table, we do this here because we're guaranteed
326   // to have concrete versions of our DW_TAG_subprogram nodes.
327   addSubprogramNames(SP, *SPDie);
328
329   return *SPDie;
330 }
331
332 /// Check whether we should create a DIE for the given Scope, return true
333 /// if we don't create a DIE (the corresponding DIE is null).
334 bool DwarfDebug::isLexicalScopeDIENull(LexicalScope *Scope) {
335   if (Scope->isAbstractScope())
336     return false;
337
338   // We don't create a DIE if there is no Range.
339   const SmallVectorImpl<InsnRange> &Ranges = Scope->getRanges();
340   if (Ranges.empty())
341     return true;
342
343   if (Ranges.size() > 1)
344     return false;
345
346   // We don't create a DIE if we have a single Range and the end label
347   // is null.
348   SmallVectorImpl<InsnRange>::const_iterator RI = Ranges.begin();
349   MCSymbol *End = getLabelAfterInsn(RI->second);
350   return !End;
351 }
352
353 static void addSectionLabel(AsmPrinter &Asm, DwarfUnit &U, DIE &D,
354                             dwarf::Attribute A, const MCSymbol *L,
355                             const MCSymbol *Sec) {
356   if (Asm.MAI->doesDwarfUseRelocationsAcrossSections())
357     U.addSectionLabel(D, A, L);
358   else
359     U.addSectionDelta(D, A, L, Sec);
360 }
361
362 void DwarfDebug::addScopeRangeList(DwarfCompileUnit &TheCU, DIE &ScopeDIE,
363                                    const SmallVectorImpl<InsnRange> &Range) {
364   // Emit offset in .debug_range as a relocatable label. emitDIE will handle
365   // emitting it appropriately.
366   MCSymbol *RangeSym = Asm->GetTempSymbol("debug_ranges", GlobalRangeCount++);
367
368   // Under fission, ranges are specified by constant offsets relative to the
369   // CU's DW_AT_GNU_ranges_base.
370   if (useSplitDwarf())
371     TheCU.addSectionDelta(ScopeDIE, dwarf::DW_AT_ranges, RangeSym,
372                           DwarfDebugRangeSectionSym);
373   else
374     addSectionLabel(*Asm, TheCU, ScopeDIE, dwarf::DW_AT_ranges, RangeSym,
375                     DwarfDebugRangeSectionSym);
376
377   RangeSpanList List(RangeSym);
378   for (const InsnRange &R : Range) {
379     RangeSpan Span(getLabelBeforeInsn(R.first), getLabelAfterInsn(R.second));
380     List.addRange(std::move(Span));
381   }
382
383   // Add the range list to the set of ranges to be emitted.
384   TheCU.addRangeList(std::move(List));
385 }
386
387 void DwarfDebug::attachRangesOrLowHighPC(DwarfCompileUnit &TheCU, DIE &Die,
388                                     const SmallVectorImpl<InsnRange> &Ranges) {
389   assert(!Ranges.empty());
390   if (Ranges.size() == 1)
391     attachLowHighPC(TheCU, Die, getLabelBeforeInsn(Ranges.front().first),
392                     getLabelAfterInsn(Ranges.front().second));
393   else
394     addScopeRangeList(TheCU, Die, Ranges);
395 }
396
397 // Construct new DW_TAG_lexical_block for this scope and attach
398 // DW_AT_low_pc/DW_AT_high_pc labels.
399 std::unique_ptr<DIE>
400 DwarfDebug::constructLexicalScopeDIE(DwarfCompileUnit &TheCU,
401                                      LexicalScope *Scope) {
402   if (isLexicalScopeDIENull(Scope))
403     return nullptr;
404
405   auto ScopeDIE = make_unique<DIE>(dwarf::DW_TAG_lexical_block);
406   if (Scope->isAbstractScope())
407     return ScopeDIE;
408
409   attachRangesOrLowHighPC(TheCU, *ScopeDIE, Scope->getRanges());
410
411   return ScopeDIE;
412 }
413
414 // This scope represents inlined body of a function. Construct DIE to
415 // represent this concrete inlined copy of the function.
416 std::unique_ptr<DIE>
417 DwarfDebug::constructInlinedScopeDIE(DwarfCompileUnit &TheCU,
418                                      LexicalScope *Scope) {
419   assert(Scope->getScopeNode());
420   DIScope DS(Scope->getScopeNode());
421   DISubprogram InlinedSP = getDISubprogram(DS);
422   // Find the subprogram's DwarfCompileUnit in the SPMap in case the subprogram
423   // was inlined from another compile unit.
424   DIE *OriginDIE = AbstractSPDies[InlinedSP];
425   assert(OriginDIE && "Unable to find original DIE for an inlined subprogram.");
426
427   auto ScopeDIE = make_unique<DIE>(dwarf::DW_TAG_inlined_subroutine);
428   TheCU.addDIEEntry(*ScopeDIE, dwarf::DW_AT_abstract_origin, *OriginDIE);
429
430   attachRangesOrLowHighPC(TheCU, *ScopeDIE, Scope->getRanges());
431
432   InlinedSubprogramDIEs.insert(OriginDIE);
433
434   // Add the call site information to the DIE.
435   DILocation DL(Scope->getInlinedAt());
436   TheCU.addUInt(*ScopeDIE, dwarf::DW_AT_call_file, None,
437                 TheCU.getOrCreateSourceID(DL.getFilename(), DL.getDirectory()));
438   TheCU.addUInt(*ScopeDIE, dwarf::DW_AT_call_line, None, DL.getLineNumber());
439
440   // Add name to the name table, we do this here because we're guaranteed
441   // to have concrete versions of our DW_TAG_inlined_subprogram nodes.
442   addSubprogramNames(InlinedSP, *ScopeDIE);
443
444   return ScopeDIE;
445 }
446
447 static std::unique_ptr<DIE> constructVariableDIE(DwarfCompileUnit &TheCU,
448                                                  DbgVariable &DV,
449                                                  const LexicalScope &Scope,
450                                                  DIE *&ObjectPointer) {
451   auto Var = TheCU.constructVariableDIE(DV, Scope.isAbstractScope());
452   if (DV.isObjectPointer())
453     ObjectPointer = Var.get();
454   return Var;
455 }
456
457 DIE *DwarfDebug::createScopeChildrenDIE(
458     DwarfCompileUnit &TheCU, LexicalScope *Scope,
459     SmallVectorImpl<std::unique_ptr<DIE>> &Children) {
460   DIE *ObjectPointer = nullptr;
461
462   // Collect arguments for current function.
463   if (LScopes.isCurrentFunctionScope(Scope)) {
464     for (DbgVariable *ArgDV : CurrentFnArguments)
465       if (ArgDV)
466         Children.push_back(
467             constructVariableDIE(TheCU, *ArgDV, *Scope, ObjectPointer));
468
469     // If this is a variadic function, add an unspecified parameter.
470     DISubprogram SP(Scope->getScopeNode());
471     DIArray FnArgs = SP.getType().getTypeArray();
472     if (FnArgs.getElement(FnArgs.getNumElements() - 1)
473             .isUnspecifiedParameter()) {
474       Children.push_back(
475           make_unique<DIE>(dwarf::DW_TAG_unspecified_parameters));
476     }
477   }
478
479   // Collect lexical scope children first.
480   for (DbgVariable *DV : ScopeVariables.lookup(Scope))
481     Children.push_back(constructVariableDIE(TheCU, *DV, *Scope, ObjectPointer));
482
483   for (LexicalScope *LS : Scope->getChildren())
484     if (std::unique_ptr<DIE> Nested = constructScopeDIE(TheCU, LS))
485       Children.push_back(std::move(Nested));
486   return ObjectPointer;
487 }
488
489 void DwarfDebug::createAndAddScopeChildren(DwarfCompileUnit &TheCU,
490                                            LexicalScope *Scope, DIE &ScopeDIE) {
491   // We create children when the scope DIE is not null.
492   SmallVector<std::unique_ptr<DIE>, 8> Children;
493   if (DIE *ObjectPointer = createScopeChildrenDIE(TheCU, Scope, Children))
494     TheCU.addDIEEntry(ScopeDIE, dwarf::DW_AT_object_pointer, *ObjectPointer);
495
496   // Add children
497   for (auto &I : Children)
498     ScopeDIE.addChild(std::move(I));
499 }
500
501 void DwarfDebug::constructAbstractSubprogramScopeDIE(DwarfCompileUnit &TheCU,
502                                                      LexicalScope *Scope) {
503   assert(Scope && Scope->getScopeNode());
504   assert(Scope->isAbstractScope());
505   assert(!Scope->getInlinedAt());
506
507   DISubprogram SP(Scope->getScopeNode());
508
509   ProcessedSPNodes.insert(SP);
510
511   DIE *&AbsDef = AbstractSPDies[SP];
512   if (AbsDef)
513     return;
514
515   // Find the subprogram's DwarfCompileUnit in the SPMap in case the subprogram
516   // was inlined from another compile unit.
517   DwarfCompileUnit &SPCU = *SPMap[SP];
518   DIE *ContextDIE;
519
520   // Some of this is duplicated from DwarfUnit::getOrCreateSubprogramDIE, with
521   // the important distinction that the DIDescriptor is not associated with the
522   // DIE (since the DIDescriptor will be associated with the concrete DIE, if
523   // any). It could be refactored to some common utility function.
524   if (DISubprogram SPDecl = SP.getFunctionDeclaration()) {
525     ContextDIE = &SPCU.getUnitDie();
526     SPCU.getOrCreateSubprogramDIE(SPDecl);
527   } else
528     ContextDIE = SPCU.getOrCreateContextDIE(resolve(SP.getContext()));
529
530   // Passing null as the associated DIDescriptor because the abstract definition
531   // shouldn't be found by lookup.
532   AbsDef = &SPCU.createAndAddDIE(dwarf::DW_TAG_subprogram, *ContextDIE,
533                                  DIDescriptor());
534   SPCU.applySubprogramAttributesToDefinition(SP, *AbsDef);
535
536   SPCU.addUInt(*AbsDef, dwarf::DW_AT_inline, None, dwarf::DW_INL_inlined);
537   createAndAddScopeChildren(SPCU, Scope, *AbsDef);
538 }
539
540 DIE &DwarfDebug::constructSubprogramScopeDIE(DwarfCompileUnit &TheCU,
541                                              LexicalScope *Scope) {
542   assert(Scope && Scope->getScopeNode());
543   assert(!Scope->getInlinedAt());
544   assert(!Scope->isAbstractScope());
545   DISubprogram Sub(Scope->getScopeNode());
546
547   assert(Sub.isSubprogram());
548
549   ProcessedSPNodes.insert(Sub);
550
551   DIE &ScopeDIE = updateSubprogramScopeDIE(TheCU, Sub);
552
553   createAndAddScopeChildren(TheCU, Scope, ScopeDIE);
554
555   return ScopeDIE;
556 }
557
558 // Construct a DIE for this scope.
559 std::unique_ptr<DIE> DwarfDebug::constructScopeDIE(DwarfCompileUnit &TheCU,
560                                                    LexicalScope *Scope) {
561   if (!Scope || !Scope->getScopeNode())
562     return nullptr;
563
564   DIScope DS(Scope->getScopeNode());
565
566   assert((Scope->getInlinedAt() || !DS.isSubprogram()) &&
567          "Only handle inlined subprograms here, use "
568          "constructSubprogramScopeDIE for non-inlined "
569          "subprograms");
570
571   SmallVector<std::unique_ptr<DIE>, 8> Children;
572
573   // We try to create the scope DIE first, then the children DIEs. This will
574   // avoid creating un-used children then removing them later when we find out
575   // the scope DIE is null.
576   std::unique_ptr<DIE> ScopeDIE;
577   if (Scope->getParent() && DS.isSubprogram()) {
578     ScopeDIE = constructInlinedScopeDIE(TheCU, Scope);
579     if (!ScopeDIE)
580       return nullptr;
581     // We create children when the scope DIE is not null.
582     createScopeChildrenDIE(TheCU, Scope, Children);
583   } else {
584     // Early exit when we know the scope DIE is going to be null.
585     if (isLexicalScopeDIENull(Scope))
586       return nullptr;
587
588     // We create children here when we know the scope DIE is not going to be
589     // null and the children will be added to the scope DIE.
590     createScopeChildrenDIE(TheCU, Scope, Children);
591
592     // There is no need to emit empty lexical block DIE.
593     std::pair<ImportedEntityMap::const_iterator,
594               ImportedEntityMap::const_iterator> Range =
595         std::equal_range(ScopesWithImportedEntities.begin(),
596                          ScopesWithImportedEntities.end(),
597                          std::pair<const MDNode *, const MDNode *>(DS, nullptr),
598                          less_first());
599     if (Children.empty() && Range.first == Range.second)
600       return nullptr;
601     ScopeDIE = constructLexicalScopeDIE(TheCU, Scope);
602     assert(ScopeDIE && "Scope DIE should not be null.");
603     for (ImportedEntityMap::const_iterator i = Range.first; i != Range.second;
604          ++i)
605       constructImportedEntityDIE(TheCU, i->second, *ScopeDIE);
606   }
607
608   // Add children
609   for (auto &I : Children)
610     ScopeDIE->addChild(std::move(I));
611
612   return ScopeDIE;
613 }
614
615 void DwarfDebug::addGnuPubAttributes(DwarfUnit &U, DIE &D) const {
616   if (!GenerateGnuPubSections)
617     return;
618
619   U.addFlag(D, dwarf::DW_AT_GNU_pubnames);
620 }
621
622 // Create new DwarfCompileUnit for the given metadata node with tag
623 // DW_TAG_compile_unit.
624 DwarfCompileUnit &DwarfDebug::constructDwarfCompileUnit(DICompileUnit DIUnit) {
625   StringRef FN = DIUnit.getFilename();
626   CompilationDir = DIUnit.getDirectory();
627
628   auto OwnedUnit = make_unique<DwarfCompileUnit>(
629       InfoHolder.getUnits().size(), DIUnit, Asm, this, &InfoHolder);
630   DwarfCompileUnit &NewCU = *OwnedUnit;
631   DIE &Die = NewCU.getUnitDie();
632   InfoHolder.addUnit(std::move(OwnedUnit));
633
634   // LTO with assembly output shares a single line table amongst multiple CUs.
635   // To avoid the compilation directory being ambiguous, let the line table
636   // explicitly describe the directory of all files, never relying on the
637   // compilation directory.
638   if (!Asm->OutStreamer.hasRawTextSupport() || SingleCU)
639     Asm->OutStreamer.getContext().setMCLineTableCompilationDir(
640         NewCU.getUniqueID(), CompilationDir);
641
642   NewCU.addString(Die, dwarf::DW_AT_producer, DIUnit.getProducer());
643   NewCU.addUInt(Die, dwarf::DW_AT_language, dwarf::DW_FORM_data2,
644                 DIUnit.getLanguage());
645   NewCU.addString(Die, dwarf::DW_AT_name, FN);
646
647   if (!useSplitDwarf()) {
648     NewCU.initStmtList(DwarfLineSectionSym);
649
650     // If we're using split dwarf the compilation dir is going to be in the
651     // skeleton CU and so we don't need to duplicate it here.
652     if (!CompilationDir.empty())
653       NewCU.addString(Die, dwarf::DW_AT_comp_dir, CompilationDir);
654
655     addGnuPubAttributes(NewCU, Die);
656   }
657
658   if (DIUnit.isOptimized())
659     NewCU.addFlag(Die, dwarf::DW_AT_APPLE_optimized);
660
661   StringRef Flags = DIUnit.getFlags();
662   if (!Flags.empty())
663     NewCU.addString(Die, dwarf::DW_AT_APPLE_flags, Flags);
664
665   if (unsigned RVer = DIUnit.getRunTimeVersion())
666     NewCU.addUInt(Die, dwarf::DW_AT_APPLE_major_runtime_vers,
667                   dwarf::DW_FORM_data1, RVer);
668
669   if (!FirstCU)
670     FirstCU = &NewCU;
671
672   if (useSplitDwarf()) {
673     NewCU.initSection(Asm->getObjFileLowering().getDwarfInfoDWOSection(),
674                       DwarfInfoDWOSectionSym);
675     NewCU.setSkeleton(constructSkeletonCU(NewCU));
676   } else
677     NewCU.initSection(Asm->getObjFileLowering().getDwarfInfoSection(),
678                       DwarfInfoSectionSym);
679
680   CUMap.insert(std::make_pair(DIUnit, &NewCU));
681   CUDieMap.insert(std::make_pair(&Die, &NewCU));
682   return NewCU;
683 }
684
685 void DwarfDebug::constructImportedEntityDIE(DwarfCompileUnit &TheCU,
686                                             const MDNode *N) {
687   DIImportedEntity Module(N);
688   assert(Module.Verify());
689   if (DIE *D = TheCU.getOrCreateContextDIE(Module.getContext()))
690     constructImportedEntityDIE(TheCU, Module, *D);
691 }
692
693 void DwarfDebug::constructImportedEntityDIE(DwarfCompileUnit &TheCU,
694                                             const MDNode *N, DIE &Context) {
695   DIImportedEntity Module(N);
696   assert(Module.Verify());
697   return constructImportedEntityDIE(TheCU, Module, Context);
698 }
699
700 void DwarfDebug::constructImportedEntityDIE(DwarfCompileUnit &TheCU,
701                                             const DIImportedEntity &Module,
702                                             DIE &Context) {
703   assert(Module.Verify() &&
704          "Use one of the MDNode * overloads to handle invalid metadata");
705   DIE &IMDie = TheCU.createAndAddDIE(Module.getTag(), Context, Module);
706   DIE *EntityDie;
707   DIDescriptor Entity = resolve(Module.getEntity());
708   if (Entity.isNameSpace())
709     EntityDie = TheCU.getOrCreateNameSpace(DINameSpace(Entity));
710   else if (Entity.isSubprogram())
711     EntityDie = TheCU.getOrCreateSubprogramDIE(DISubprogram(Entity));
712   else if (Entity.isType())
713     EntityDie = TheCU.getOrCreateTypeDIE(DIType(Entity));
714   else
715     EntityDie = TheCU.getDIE(Entity);
716   TheCU.addSourceLine(IMDie, Module.getLineNumber(),
717                       Module.getContext().getFilename(),
718                       Module.getContext().getDirectory());
719   TheCU.addDIEEntry(IMDie, dwarf::DW_AT_import, *EntityDie);
720   StringRef Name = Module.getName();
721   if (!Name.empty())
722     TheCU.addString(IMDie, dwarf::DW_AT_name, Name);
723 }
724
725 // Emit all Dwarf sections that should come prior to the content. Create
726 // global DIEs and emit initial debug info sections. This is invoked by
727 // the target AsmPrinter.
728 void DwarfDebug::beginModule() {
729   if (DisableDebugInfoPrinting)
730     return;
731
732   const Module *M = MMI->getModule();
733
734   // If module has named metadata anchors then use them, otherwise scan the
735   // module using debug info finder to collect debug info.
736   NamedMDNode *CU_Nodes = M->getNamedMetadata("llvm.dbg.cu");
737   if (!CU_Nodes)
738     return;
739   TypeIdentifierMap = generateDITypeIdentifierMap(CU_Nodes);
740
741   // Emit initial sections so we can reference labels later.
742   emitSectionLabels();
743
744   SingleCU = CU_Nodes->getNumOperands() == 1;
745
746   for (MDNode *N : CU_Nodes->operands()) {
747     DICompileUnit CUNode(N);
748     DwarfCompileUnit &CU = constructDwarfCompileUnit(CUNode);
749     DIArray ImportedEntities = CUNode.getImportedEntities();
750     for (unsigned i = 0, e = ImportedEntities.getNumElements(); i != e; ++i)
751       ScopesWithImportedEntities.push_back(std::make_pair(
752           DIImportedEntity(ImportedEntities.getElement(i)).getContext(),
753           ImportedEntities.getElement(i)));
754     std::sort(ScopesWithImportedEntities.begin(),
755               ScopesWithImportedEntities.end(), less_first());
756     DIArray GVs = CUNode.getGlobalVariables();
757     for (unsigned i = 0, e = GVs.getNumElements(); i != e; ++i)
758       CU.createGlobalVariableDIE(DIGlobalVariable(GVs.getElement(i)));
759     DIArray SPs = CUNode.getSubprograms();
760     for (unsigned i = 0, e = SPs.getNumElements(); i != e; ++i)
761       SPMap.insert(std::make_pair(SPs.getElement(i), &CU));
762     DIArray EnumTypes = CUNode.getEnumTypes();
763     for (unsigned i = 0, e = EnumTypes.getNumElements(); i != e; ++i)
764       CU.getOrCreateTypeDIE(EnumTypes.getElement(i));
765     DIArray RetainedTypes = CUNode.getRetainedTypes();
766     for (unsigned i = 0, e = RetainedTypes.getNumElements(); i != e; ++i) {
767       DIType Ty(RetainedTypes.getElement(i));
768       // The retained types array by design contains pointers to
769       // MDNodes rather than DIRefs. Unique them here.
770       DIType UniqueTy(resolve(Ty.getRef()));
771       CU.getOrCreateTypeDIE(UniqueTy);
772     }
773     // Emit imported_modules last so that the relevant context is already
774     // available.
775     for (unsigned i = 0, e = ImportedEntities.getNumElements(); i != e; ++i)
776       constructImportedEntityDIE(CU, ImportedEntities.getElement(i));
777   }
778
779   // Tell MMI that we have debug info.
780   MMI->setDebugInfoAvailability(true);
781
782   // Prime section data.
783   SectionMap[Asm->getObjFileLowering().getTextSection()];
784 }
785
786 void DwarfDebug::finishVariableDefinitions() {
787   for (const auto &Var : ConcreteVariables) {
788     DIE *VariableDie = Var->getDIE();
789     // FIXME: There shouldn't be any variables without DIEs.
790     if (!VariableDie)
791       continue;
792     // FIXME: Consider the time-space tradeoff of just storing the unit pointer
793     // in the ConcreteVariables list, rather than looking it up again here.
794     // DIE::getUnit isn't simple - it walks parent pointers, etc.
795     DwarfCompileUnit *Unit = lookupUnit(VariableDie->getUnit());
796     assert(Unit);
797     DbgVariable *AbsVar = getExistingAbstractVariable(Var->getVariable());
798     if (AbsVar && AbsVar->getDIE()) {
799       Unit->addDIEEntry(*VariableDie, dwarf::DW_AT_abstract_origin,
800                         *AbsVar->getDIE());
801     } else
802       Unit->applyVariableAttributes(*Var, *VariableDie);
803   }
804 }
805
806 void DwarfDebug::finishSubprogramDefinitions() {
807   const Module *M = MMI->getModule();
808
809   NamedMDNode *CU_Nodes = M->getNamedMetadata("llvm.dbg.cu");
810   for (MDNode *N : CU_Nodes->operands()) {
811     DICompileUnit TheCU(N);
812     // Construct subprogram DIE and add variables DIEs.
813     DwarfCompileUnit *SPCU =
814         static_cast<DwarfCompileUnit *>(CUMap.lookup(TheCU));
815     DIArray Subprograms = TheCU.getSubprograms();
816     for (unsigned i = 0, e = Subprograms.getNumElements(); i != e; ++i) {
817       DISubprogram SP(Subprograms.getElement(i));
818       // Perhaps the subprogram is in another CU (such as due to comdat
819       // folding, etc), in which case ignore it here.
820       if (SPMap[SP] != SPCU)
821         continue;
822       DIE *D = SPCU->getDIE(SP);
823       if (DIE *AbsSPDIE = AbstractSPDies.lookup(SP)) {
824         if (D)
825           // If this subprogram has an abstract definition, reference that
826           SPCU->addDIEEntry(*D, dwarf::DW_AT_abstract_origin, *AbsSPDIE);
827       } else {
828         if (!D)
829           // Lazily construct the subprogram if we didn't see either concrete or
830           // inlined versions during codegen.
831           D = SPCU->getOrCreateSubprogramDIE(SP);
832         // And attach the attributes
833         SPCU->applySubprogramAttributesToDefinition(SP, *D);
834       }
835     }
836   }
837 }
838
839
840 // Collect info for variables that were optimized out.
841 void DwarfDebug::collectDeadVariables() {
842   const Module *M = MMI->getModule();
843
844   if (NamedMDNode *CU_Nodes = M->getNamedMetadata("llvm.dbg.cu")) {
845     for (MDNode *N : CU_Nodes->operands()) {
846       DICompileUnit TheCU(N);
847       // Construct subprogram DIE and add variables DIEs.
848       DwarfCompileUnit *SPCU =
849           static_cast<DwarfCompileUnit *>(CUMap.lookup(TheCU));
850       assert(SPCU && "Unable to find Compile Unit!");
851       DIArray Subprograms = TheCU.getSubprograms();
852       for (unsigned i = 0, e = Subprograms.getNumElements(); i != e; ++i) {
853         DISubprogram SP(Subprograms.getElement(i));
854         if (ProcessedSPNodes.count(SP) != 0)
855           continue;
856         assert(SP.isSubprogram() &&
857                "CU's subprogram list contains a non-subprogram");
858         assert(SP.isDefinition() &&
859                "CU's subprogram list contains a subprogram declaration");
860         DIArray Variables = SP.getVariables();
861         if (Variables.getNumElements() == 0)
862           continue;
863
864         DIE *SPDIE = AbstractSPDies.lookup(SP);
865         if (!SPDIE)
866           SPDIE = SPCU->getDIE(SP);
867         assert(SPDIE);
868         for (unsigned vi = 0, ve = Variables.getNumElements(); vi != ve; ++vi) {
869           DIVariable DV(Variables.getElement(vi));
870           assert(DV.isVariable());
871           DbgVariable NewVar(DV, this);
872           auto VariableDie = SPCU->constructVariableDIE(NewVar);
873           SPCU->applyVariableAttributes(NewVar, *VariableDie);
874           SPDIE->addChild(std::move(VariableDie));
875         }
876       }
877     }
878   }
879 }
880
881 void DwarfDebug::finalizeModuleInfo() {
882   finishSubprogramDefinitions();
883
884   finishVariableDefinitions();
885
886   // Collect info for variables that were optimized out.
887   collectDeadVariables();
888
889   // Handle anything that needs to be done on a per-unit basis after
890   // all other generation.
891   for (const auto &TheU : getUnits()) {
892     // Emit DW_AT_containing_type attribute to connect types with their
893     // vtable holding type.
894     TheU->constructContainingTypeDIEs();
895
896     // Add CU specific attributes if we need to add any.
897     if (TheU->getUnitDie().getTag() == dwarf::DW_TAG_compile_unit) {
898       // If we're splitting the dwarf out now that we've got the entire
899       // CU then add the dwo id to it.
900       DwarfCompileUnit *SkCU =
901           static_cast<DwarfCompileUnit *>(TheU->getSkeleton());
902       if (useSplitDwarf()) {
903         // Emit a unique identifier for this CU.
904         uint64_t ID = DIEHash(Asm).computeCUSignature(TheU->getUnitDie());
905         TheU->addUInt(TheU->getUnitDie(), dwarf::DW_AT_GNU_dwo_id,
906                       dwarf::DW_FORM_data8, ID);
907         SkCU->addUInt(SkCU->getUnitDie(), dwarf::DW_AT_GNU_dwo_id,
908                       dwarf::DW_FORM_data8, ID);
909
910         // We don't keep track of which addresses are used in which CU so this
911         // is a bit pessimistic under LTO.
912         if (!AddrPool.isEmpty())
913           addSectionLabel(*Asm, *SkCU, SkCU->getUnitDie(),
914                           dwarf::DW_AT_GNU_addr_base, DwarfAddrSectionSym,
915                           DwarfAddrSectionSym);
916         if (!TheU->getRangeLists().empty())
917           addSectionLabel(*Asm, *SkCU, SkCU->getUnitDie(),
918                           dwarf::DW_AT_GNU_ranges_base,
919                           DwarfDebugRangeSectionSym, DwarfDebugRangeSectionSym);
920       }
921
922       // If we have code split among multiple sections or non-contiguous
923       // ranges of code then emit a DW_AT_ranges attribute on the unit that will
924       // remain in the .o file, otherwise add a DW_AT_low_pc.
925       // FIXME: We should use ranges allow reordering of code ala
926       // .subsections_via_symbols in mach-o. This would mean turning on
927       // ranges for all subprogram DIEs for mach-o.
928       DwarfCompileUnit &U =
929           SkCU ? *SkCU : static_cast<DwarfCompileUnit &>(*TheU);
930       unsigned NumRanges = TheU->getRanges().size();
931       if (NumRanges) {
932         if (NumRanges > 1) {
933           addSectionLabel(*Asm, U, U.getUnitDie(), dwarf::DW_AT_ranges,
934                           Asm->GetTempSymbol("cu_ranges", U.getUniqueID()),
935                           DwarfDebugRangeSectionSym);
936
937           // A DW_AT_low_pc attribute may also be specified in combination with
938           // DW_AT_ranges to specify the default base address for use in
939           // location lists (see Section 2.6.2) and range lists (see Section
940           // 2.17.3).
941           U.addUInt(U.getUnitDie(), dwarf::DW_AT_low_pc, dwarf::DW_FORM_addr,
942                     0);
943         } else {
944           RangeSpan &Range = TheU->getRanges().back();
945           U.addLocalLabelAddress(U.getUnitDie(), dwarf::DW_AT_low_pc,
946                                  Range.getStart());
947           U.addLabelDelta(U.getUnitDie(), dwarf::DW_AT_high_pc, Range.getEnd(),
948                           Range.getStart());
949         }
950       }
951     }
952   }
953
954   // Compute DIE offsets and sizes.
955   InfoHolder.computeSizeAndOffsets();
956   if (useSplitDwarf())
957     SkeletonHolder.computeSizeAndOffsets();
958 }
959
960 void DwarfDebug::endSections() {
961   // Filter labels by section.
962   for (const SymbolCU &SCU : ArangeLabels) {
963     if (SCU.Sym->isInSection()) {
964       // Make a note of this symbol and it's section.
965       const MCSection *Section = &SCU.Sym->getSection();
966       if (!Section->getKind().isMetadata())
967         SectionMap[Section].push_back(SCU);
968     } else {
969       // Some symbols (e.g. common/bss on mach-o) can have no section but still
970       // appear in the output. This sucks as we rely on sections to build
971       // arange spans. We can do it without, but it's icky.
972       SectionMap[nullptr].push_back(SCU);
973     }
974   }
975
976   // Build a list of sections used.
977   std::vector<const MCSection *> Sections;
978   for (const auto &it : SectionMap) {
979     const MCSection *Section = it.first;
980     Sections.push_back(Section);
981   }
982
983   // Sort the sections into order.
984   // This is only done to ensure consistent output order across different runs.
985   std::sort(Sections.begin(), Sections.end(), SectionSort);
986
987   // Add terminating symbols for each section.
988   for (unsigned ID = 0, E = Sections.size(); ID != E; ID++) {
989     const MCSection *Section = Sections[ID];
990     MCSymbol *Sym = nullptr;
991
992     if (Section) {
993       // We can't call MCSection::getLabelEndName, as it's only safe to do so
994       // if we know the section name up-front. For user-created sections, the
995       // resulting label may not be valid to use as a label. (section names can
996       // use a greater set of characters on some systems)
997       Sym = Asm->GetTempSymbol("debug_end", ID);
998       Asm->OutStreamer.SwitchSection(Section);
999       Asm->OutStreamer.EmitLabel(Sym);
1000     }
1001
1002     // Insert a final terminator.
1003     SectionMap[Section].push_back(SymbolCU(nullptr, Sym));
1004   }
1005 }
1006
1007 // Emit all Dwarf sections that should come after the content.
1008 void DwarfDebug::endModule() {
1009   assert(CurFn == nullptr);
1010   assert(CurMI == nullptr);
1011
1012   if (!FirstCU)
1013     return;
1014
1015   // End any existing sections.
1016   // TODO: Does this need to happen?
1017   endSections();
1018
1019   // Finalize the debug info for the module.
1020   finalizeModuleInfo();
1021
1022   emitDebugStr();
1023
1024   // Emit all the DIEs into a debug info section.
1025   emitDebugInfo();
1026
1027   // Corresponding abbreviations into a abbrev section.
1028   emitAbbreviations();
1029
1030   // Emit info into a debug aranges section.
1031   if (GenerateARangeSection)
1032     emitDebugARanges();
1033
1034   // Emit info into a debug ranges section.
1035   emitDebugRanges();
1036
1037   if (useSplitDwarf()) {
1038     emitDebugStrDWO();
1039     emitDebugInfoDWO();
1040     emitDebugAbbrevDWO();
1041     emitDebugLineDWO();
1042     // Emit DWO addresses.
1043     AddrPool.emit(*Asm, Asm->getObjFileLowering().getDwarfAddrSection());
1044     emitDebugLocDWO();
1045   } else
1046     // Emit info into a debug loc section.
1047     emitDebugLoc();
1048
1049   // Emit info into the dwarf accelerator table sections.
1050   if (useDwarfAccelTables()) {
1051     emitAccelNames();
1052     emitAccelObjC();
1053     emitAccelNamespaces();
1054     emitAccelTypes();
1055   }
1056
1057   // Emit the pubnames and pubtypes sections if requested.
1058   if (HasDwarfPubSections) {
1059     emitDebugPubNames(GenerateGnuPubSections);
1060     emitDebugPubTypes(GenerateGnuPubSections);
1061   }
1062
1063   // clean up.
1064   SPMap.clear();
1065   AbstractVariables.clear();
1066
1067   // Reset these for the next Module if we have one.
1068   FirstCU = nullptr;
1069 }
1070
1071 // Find abstract variable, if any, associated with Var.
1072 DbgVariable *DwarfDebug::getExistingAbstractVariable(const DIVariable &DV,
1073                                                      DIVariable &Cleansed) {
1074   LLVMContext &Ctx = DV->getContext();
1075   // More then one inlined variable corresponds to one abstract variable.
1076   // FIXME: This duplication of variables when inlining should probably be
1077   // removed. It's done to allow each DIVariable to describe its location
1078   // because the DebugLoc on the dbg.value/declare isn't accurate. We should
1079   // make it accurate then remove this duplication/cleansing stuff.
1080   Cleansed = cleanseInlinedVariable(DV, Ctx);
1081   auto I = AbstractVariables.find(Cleansed);
1082   if (I != AbstractVariables.end())
1083     return I->second.get();
1084   return nullptr;
1085 }
1086
1087 DbgVariable *DwarfDebug::getExistingAbstractVariable(const DIVariable &DV) {
1088   DIVariable Cleansed;
1089   return getExistingAbstractVariable(DV, Cleansed);
1090 }
1091
1092 void DwarfDebug::createAbstractVariable(const DIVariable &Var,
1093                                         LexicalScope *Scope) {
1094   auto AbsDbgVariable = make_unique<DbgVariable>(Var, this);
1095   addScopeVariable(Scope, AbsDbgVariable.get());
1096   AbstractVariables[Var] = std::move(AbsDbgVariable);
1097 }
1098
1099 void DwarfDebug::ensureAbstractVariableIsCreated(const DIVariable &DV,
1100                                                  const MDNode *ScopeNode) {
1101   DIVariable Cleansed = DV;
1102   if (getExistingAbstractVariable(DV, Cleansed))
1103     return;
1104
1105   createAbstractVariable(Cleansed, LScopes.getOrCreateAbstractScope(ScopeNode));
1106 }
1107
1108 void
1109 DwarfDebug::ensureAbstractVariableIsCreatedIfScoped(const DIVariable &DV,
1110                                                     const MDNode *ScopeNode) {
1111   DIVariable Cleansed = DV;
1112   if (getExistingAbstractVariable(DV, Cleansed))
1113     return;
1114
1115   if (LexicalScope *Scope = LScopes.findAbstractScope(ScopeNode))
1116     createAbstractVariable(Cleansed, Scope);
1117 }
1118
1119 // If Var is a current function argument then add it to CurrentFnArguments list.
1120 bool DwarfDebug::addCurrentFnArgument(DbgVariable *Var, LexicalScope *Scope) {
1121   if (!LScopes.isCurrentFunctionScope(Scope))
1122     return false;
1123   DIVariable DV = Var->getVariable();
1124   if (DV.getTag() != dwarf::DW_TAG_arg_variable)
1125     return false;
1126   unsigned ArgNo = DV.getArgNumber();
1127   if (ArgNo == 0)
1128     return false;
1129
1130   size_t Size = CurrentFnArguments.size();
1131   if (Size == 0)
1132     CurrentFnArguments.resize(CurFn->getFunction()->arg_size());
1133   // llvm::Function argument size is not good indicator of how many
1134   // arguments does the function have at source level.
1135   if (ArgNo > Size)
1136     CurrentFnArguments.resize(ArgNo * 2);
1137   CurrentFnArguments[ArgNo - 1] = Var;
1138   return true;
1139 }
1140
1141 // Collect variable information from side table maintained by MMI.
1142 void DwarfDebug::collectVariableInfoFromMMITable(
1143     SmallPtrSet<const MDNode *, 16> &Processed) {
1144   for (const auto &VI : MMI->getVariableDbgInfo()) {
1145     if (!VI.Var)
1146       continue;
1147     Processed.insert(VI.Var);
1148     DIVariable DV(VI.Var);
1149     LexicalScope *Scope = LScopes.findLexicalScope(VI.Loc);
1150
1151     // If variable scope is not found then skip this variable.
1152     if (!Scope)
1153       continue;
1154
1155     ensureAbstractVariableIsCreatedIfScoped(DV, Scope->getScopeNode());
1156     ConcreteVariables.push_back(make_unique<DbgVariable>(DV, this));
1157     DbgVariable *RegVar = ConcreteVariables.back().get();
1158     RegVar->setFrameIndex(VI.Slot);
1159     addScopeVariable(Scope, RegVar);
1160   }
1161 }
1162
1163 // Get .debug_loc entry for the instruction range starting at MI.
1164 static DebugLocEntry::Value getDebugLocValue(const MachineInstr *MI) {
1165   const MDNode *Var = MI->getDebugVariable();
1166
1167   assert(MI->getNumOperands() == 3);
1168   if (MI->getOperand(0).isReg()) {
1169     MachineLocation MLoc;
1170     // If the second operand is an immediate, this is a
1171     // register-indirect address.
1172     if (!MI->getOperand(1).isImm())
1173       MLoc.set(MI->getOperand(0).getReg());
1174     else
1175       MLoc.set(MI->getOperand(0).getReg(), MI->getOperand(1).getImm());
1176     return DebugLocEntry::Value(Var, MLoc);
1177   }
1178   if (MI->getOperand(0).isImm())
1179     return DebugLocEntry::Value(Var, MI->getOperand(0).getImm());
1180   if (MI->getOperand(0).isFPImm())
1181     return DebugLocEntry::Value(Var, MI->getOperand(0).getFPImm());
1182   if (MI->getOperand(0).isCImm())
1183     return DebugLocEntry::Value(Var, MI->getOperand(0).getCImm());
1184
1185   llvm_unreachable("Unexpected 3 operand DBG_VALUE instruction!");
1186 }
1187
1188 // Find variables for each lexical scope.
1189 void
1190 DwarfDebug::collectVariableInfo(SmallPtrSet<const MDNode *, 16> &Processed) {
1191   LexicalScope *FnScope = LScopes.getCurrentFunctionScope();
1192   DwarfCompileUnit *TheCU = SPMap.lookup(FnScope->getScopeNode());
1193
1194   // Grab the variable info that was squirreled away in the MMI side-table.
1195   collectVariableInfoFromMMITable(Processed);
1196
1197   for (const auto &I : DbgValues) {
1198     DIVariable DV(I.first);
1199     if (Processed.count(DV))
1200       continue;
1201
1202     // Instruction ranges, specifying where DV is accessible.
1203     const auto &Ranges = I.second;
1204     if (Ranges.empty())
1205       continue;
1206
1207     LexicalScope *Scope = nullptr;
1208     if (DV.getTag() == dwarf::DW_TAG_arg_variable &&
1209         DISubprogram(DV.getContext()).describes(CurFn->getFunction()))
1210       Scope = LScopes.getCurrentFunctionScope();
1211     else if (MDNode *IA = DV.getInlinedAt()) {
1212       DebugLoc DL = DebugLoc::getFromDILocation(IA);
1213       Scope = LScopes.findInlinedScope(DebugLoc::get(
1214           DL.getLine(), DL.getCol(), DV.getContext(), IA));
1215     } else
1216       Scope = LScopes.findLexicalScope(DV.getContext());
1217     // If variable scope is not found then skip this variable.
1218     if (!Scope)
1219       continue;
1220
1221     Processed.insert(DV);
1222     const MachineInstr *MInsn = Ranges.front().first;
1223     assert(MInsn->isDebugValue() && "History must begin with debug value");
1224     ensureAbstractVariableIsCreatedIfScoped(DV, Scope->getScopeNode());
1225     ConcreteVariables.push_back(make_unique<DbgVariable>(MInsn, this));
1226     DbgVariable *RegVar = ConcreteVariables.back().get();
1227     addScopeVariable(Scope, RegVar);
1228
1229     // Check if the first DBG_VALUE is valid for the rest of the function.
1230     if (Ranges.size() == 1 && Ranges.front().second == nullptr)
1231       continue;
1232
1233     // Handle multiple DBG_VALUE instructions describing one variable.
1234     RegVar->setDotDebugLocOffset(DotDebugLocEntries.size());
1235
1236     DotDebugLocEntries.resize(DotDebugLocEntries.size() + 1);
1237     DebugLocList &LocList = DotDebugLocEntries.back();
1238     LocList.Label =
1239         Asm->GetTempSymbol("debug_loc", DotDebugLocEntries.size() - 1);
1240     SmallVector<DebugLocEntry, 4> &DebugLoc = LocList.List;
1241     for (auto I = Ranges.begin(), E = Ranges.end(); I != E; ++I) {
1242       const MachineInstr *Begin = I->first;
1243       const MachineInstr *End = I->second;
1244       assert(Begin->isDebugValue() && "Invalid History entry");
1245
1246       // Check if a variable is unaccessible in this range.
1247       if (Begin->getNumOperands() > 1 && Begin->getOperand(0).isReg() &&
1248           !Begin->getOperand(0).getReg())
1249         continue;
1250       DEBUG(dbgs() << "DotDebugLoc Pair:\n" << "\t" << *Begin);
1251       if (End != nullptr)
1252         DEBUG(dbgs() << "\t" << *End);
1253       else
1254         DEBUG(dbgs() << "\tNULL\n");
1255
1256       const MCSymbol *StartLabel = getLabelBeforeInsn(Begin);
1257       assert(StartLabel && "Forgot label before DBG_VALUE starting a range!");
1258
1259       const MCSymbol *EndLabel;
1260       if (End != nullptr)
1261         EndLabel = getLabelAfterInsn(End);
1262       else if (std::next(I) == Ranges.end())
1263         EndLabel = FunctionEndSym;
1264       else
1265         EndLabel = getLabelBeforeInsn(std::next(I)->first);
1266       assert(EndLabel && "Forgot label after instruction ending a range!");
1267
1268       DebugLocEntry Loc(StartLabel, EndLabel, getDebugLocValue(Begin), TheCU);
1269       if (DebugLoc.empty() || !DebugLoc.back().Merge(Loc))
1270         DebugLoc.push_back(std::move(Loc));
1271     }
1272   }
1273
1274   // Collect info for variables that were optimized out.
1275   DIArray Variables = DISubprogram(FnScope->getScopeNode()).getVariables();
1276   for (unsigned i = 0, e = Variables.getNumElements(); i != e; ++i) {
1277     DIVariable DV(Variables.getElement(i));
1278     assert(DV.isVariable());
1279     if (!Processed.insert(DV))
1280       continue;
1281     if (LexicalScope *Scope = LScopes.findLexicalScope(DV.getContext())) {
1282       ensureAbstractVariableIsCreatedIfScoped(DV, Scope->getScopeNode());
1283       ConcreteVariables.push_back(make_unique<DbgVariable>(DV, this));
1284       addScopeVariable(Scope, ConcreteVariables.back().get());
1285     }
1286   }
1287 }
1288
1289 // Return Label preceding the instruction.
1290 MCSymbol *DwarfDebug::getLabelBeforeInsn(const MachineInstr *MI) {
1291   MCSymbol *Label = LabelsBeforeInsn.lookup(MI);
1292   assert(Label && "Didn't insert label before instruction");
1293   return Label;
1294 }
1295
1296 // Return Label immediately following the instruction.
1297 MCSymbol *DwarfDebug::getLabelAfterInsn(const MachineInstr *MI) {
1298   return LabelsAfterInsn.lookup(MI);
1299 }
1300
1301 // Process beginning of an instruction.
1302 void DwarfDebug::beginInstruction(const MachineInstr *MI) {
1303   assert(CurMI == nullptr);
1304   CurMI = MI;
1305   // Check if source location changes, but ignore DBG_VALUE locations.
1306   if (!MI->isDebugValue()) {
1307     DebugLoc DL = MI->getDebugLoc();
1308     if (DL != PrevInstLoc && (!DL.isUnknown() || UnknownLocations)) {
1309       unsigned Flags = 0;
1310       PrevInstLoc = DL;
1311       if (DL == PrologEndLoc) {
1312         Flags |= DWARF2_FLAG_PROLOGUE_END;
1313         PrologEndLoc = DebugLoc();
1314       }
1315       if (PrologEndLoc.isUnknown())
1316         Flags |= DWARF2_FLAG_IS_STMT;
1317
1318       if (!DL.isUnknown()) {
1319         const MDNode *Scope = DL.getScope(Asm->MF->getFunction()->getContext());
1320         recordSourceLine(DL.getLine(), DL.getCol(), Scope, Flags);
1321       } else
1322         recordSourceLine(0, 0, nullptr, 0);
1323     }
1324   }
1325
1326   // Insert labels where requested.
1327   DenseMap<const MachineInstr *, MCSymbol *>::iterator I =
1328       LabelsBeforeInsn.find(MI);
1329
1330   // No label needed.
1331   if (I == LabelsBeforeInsn.end())
1332     return;
1333
1334   // Label already assigned.
1335   if (I->second)
1336     return;
1337
1338   if (!PrevLabel) {
1339     PrevLabel = MMI->getContext().CreateTempSymbol();
1340     Asm->OutStreamer.EmitLabel(PrevLabel);
1341   }
1342   I->second = PrevLabel;
1343 }
1344
1345 // Process end of an instruction.
1346 void DwarfDebug::endInstruction() {
1347   assert(CurMI != nullptr);
1348   // Don't create a new label after DBG_VALUE instructions.
1349   // They don't generate code.
1350   if (!CurMI->isDebugValue())
1351     PrevLabel = nullptr;
1352
1353   DenseMap<const MachineInstr *, MCSymbol *>::iterator I =
1354       LabelsAfterInsn.find(CurMI);
1355   CurMI = nullptr;
1356
1357   // No label needed.
1358   if (I == LabelsAfterInsn.end())
1359     return;
1360
1361   // Label already assigned.
1362   if (I->second)
1363     return;
1364
1365   // We need a label after this instruction.
1366   if (!PrevLabel) {
1367     PrevLabel = MMI->getContext().CreateTempSymbol();
1368     Asm->OutStreamer.EmitLabel(PrevLabel);
1369   }
1370   I->second = PrevLabel;
1371 }
1372
1373 // Each LexicalScope has first instruction and last instruction to mark
1374 // beginning and end of a scope respectively. Create an inverse map that list
1375 // scopes starts (and ends) with an instruction. One instruction may start (or
1376 // end) multiple scopes. Ignore scopes that are not reachable.
1377 void DwarfDebug::identifyScopeMarkers() {
1378   SmallVector<LexicalScope *, 4> WorkList;
1379   WorkList.push_back(LScopes.getCurrentFunctionScope());
1380   while (!WorkList.empty()) {
1381     LexicalScope *S = WorkList.pop_back_val();
1382
1383     const SmallVectorImpl<LexicalScope *> &Children = S->getChildren();
1384     if (!Children.empty())
1385       WorkList.append(Children.begin(), Children.end());
1386
1387     if (S->isAbstractScope())
1388       continue;
1389
1390     for (const InsnRange &R : S->getRanges()) {
1391       assert(R.first && "InsnRange does not have first instruction!");
1392       assert(R.second && "InsnRange does not have second instruction!");
1393       requestLabelBeforeInsn(R.first);
1394       requestLabelAfterInsn(R.second);
1395     }
1396   }
1397 }
1398
1399 static DebugLoc findPrologueEndLoc(const MachineFunction *MF) {
1400   // First known non-DBG_VALUE and non-frame setup location marks
1401   // the beginning of the function body.
1402   for (const auto &MBB : *MF)
1403     for (const auto &MI : MBB)
1404       if (!MI.isDebugValue() && !MI.getFlag(MachineInstr::FrameSetup) &&
1405           !MI.getDebugLoc().isUnknown())
1406         return MI.getDebugLoc();
1407   return DebugLoc();
1408 }
1409
1410 // Gather pre-function debug information.  Assumes being called immediately
1411 // after the function entry point has been emitted.
1412 void DwarfDebug::beginFunction(const MachineFunction *MF) {
1413   CurFn = MF;
1414
1415   // If there's no debug info for the function we're not going to do anything.
1416   if (!MMI->hasDebugInfo())
1417     return;
1418
1419   // Grab the lexical scopes for the function, if we don't have any of those
1420   // then we're not going to be able to do anything.
1421   LScopes.initialize(*MF);
1422   if (LScopes.empty())
1423     return;
1424
1425   assert(DbgValues.empty() && "DbgValues map wasn't cleaned!");
1426
1427   // Make sure that each lexical scope will have a begin/end label.
1428   identifyScopeMarkers();
1429
1430   // Set DwarfDwarfCompileUnitID in MCContext to the Compile Unit this function
1431   // belongs to so that we add to the correct per-cu line table in the
1432   // non-asm case.
1433   LexicalScope *FnScope = LScopes.getCurrentFunctionScope();
1434   DwarfCompileUnit *TheCU = SPMap.lookup(FnScope->getScopeNode());
1435   assert(TheCU && "Unable to find compile unit!");
1436   if (Asm->OutStreamer.hasRawTextSupport())
1437     // Use a single line table if we are generating assembly.
1438     Asm->OutStreamer.getContext().setDwarfCompileUnitID(0);
1439   else
1440     Asm->OutStreamer.getContext().setDwarfCompileUnitID(TheCU->getUniqueID());
1441
1442   // Emit a label for the function so that we have a beginning address.
1443   FunctionBeginSym = Asm->GetTempSymbol("func_begin", Asm->getFunctionNumber());
1444   // Assumes in correct section after the entry point.
1445   Asm->OutStreamer.EmitLabel(FunctionBeginSym);
1446
1447   // Calculate history for local variables.
1448   calculateDbgValueHistory(MF, Asm->TM.getRegisterInfo(), DbgValues);
1449
1450   // Request labels for the full history.
1451   for (const auto &I : DbgValues) {
1452     const auto &Ranges = I.second;
1453     if (Ranges.empty())
1454       continue;
1455
1456     // The first mention of a function argument gets the FunctionBeginSym
1457     // label, so arguments are visible when breaking at function entry.
1458     DIVariable DV(I.first);
1459     if (DV.isVariable() && DV.getTag() == dwarf::DW_TAG_arg_variable &&
1460         getDISubprogram(DV.getContext()).describes(MF->getFunction()))
1461       LabelsBeforeInsn[Ranges.front().first] = FunctionBeginSym;
1462
1463     for (const auto &Range : Ranges) {
1464       requestLabelBeforeInsn(Range.first);
1465       if (Range.second)
1466         requestLabelAfterInsn(Range.second);
1467     }
1468   }
1469
1470   PrevInstLoc = DebugLoc();
1471   PrevLabel = FunctionBeginSym;
1472
1473   // Record beginning of function.
1474   PrologEndLoc = findPrologueEndLoc(MF);
1475   if (!PrologEndLoc.isUnknown()) {
1476     DebugLoc FnStartDL =
1477         PrologEndLoc.getFnDebugLoc(MF->getFunction()->getContext());
1478     recordSourceLine(
1479         FnStartDL.getLine(), FnStartDL.getCol(),
1480         FnStartDL.getScope(MF->getFunction()->getContext()),
1481         // We'd like to list the prologue as "not statements" but GDB behaves
1482         // poorly if we do that. Revisit this with caution/GDB (7.5+) testing.
1483         DWARF2_FLAG_IS_STMT);
1484   }
1485 }
1486
1487 void DwarfDebug::addScopeVariable(LexicalScope *LS, DbgVariable *Var) {
1488   if (addCurrentFnArgument(Var, LS))
1489     return;
1490   SmallVectorImpl<DbgVariable *> &Vars = ScopeVariables[LS];
1491   DIVariable DV = Var->getVariable();
1492   // Variables with positive arg numbers are parameters.
1493   if (unsigned ArgNum = DV.getArgNumber()) {
1494     // Keep all parameters in order at the start of the variable list to ensure
1495     // function types are correct (no out-of-order parameters)
1496     //
1497     // This could be improved by only doing it for optimized builds (unoptimized
1498     // builds have the right order to begin with), searching from the back (this
1499     // would catch the unoptimized case quickly), or doing a binary search
1500     // rather than linear search.
1501     SmallVectorImpl<DbgVariable *>::iterator I = Vars.begin();
1502     while (I != Vars.end()) {
1503       unsigned CurNum = (*I)->getVariable().getArgNumber();
1504       // A local (non-parameter) variable has been found, insert immediately
1505       // before it.
1506       if (CurNum == 0)
1507         break;
1508       // A later indexed parameter has been found, insert immediately before it.
1509       if (CurNum > ArgNum)
1510         break;
1511       ++I;
1512     }
1513     Vars.insert(I, Var);
1514     return;
1515   }
1516
1517   Vars.push_back(Var);
1518 }
1519
1520 // Gather and emit post-function debug information.
1521 void DwarfDebug::endFunction(const MachineFunction *MF) {
1522   // Every beginFunction(MF) call should be followed by an endFunction(MF) call,
1523   // though the beginFunction may not be called at all.
1524   // We should handle both cases.
1525   if (!CurFn)
1526     CurFn = MF;
1527   else
1528     assert(CurFn == MF);
1529   assert(CurFn != nullptr);
1530
1531   if (!MMI->hasDebugInfo() || LScopes.empty()) {
1532     // If we don't have a lexical scope for this function then there will
1533     // be a hole in the range information. Keep note of this by setting the
1534     // previously used section to nullptr.
1535     PrevSection = nullptr;
1536     PrevCU = nullptr;
1537     CurFn = nullptr;
1538     return;
1539   }
1540
1541   // Define end label for subprogram.
1542   FunctionEndSym = Asm->GetTempSymbol("func_end", Asm->getFunctionNumber());
1543   // Assumes in correct section after the entry point.
1544   Asm->OutStreamer.EmitLabel(FunctionEndSym);
1545
1546   // Set DwarfDwarfCompileUnitID in MCContext to default value.
1547   Asm->OutStreamer.getContext().setDwarfCompileUnitID(0);
1548
1549   SmallPtrSet<const MDNode *, 16> ProcessedVars;
1550   collectVariableInfo(ProcessedVars);
1551
1552   LexicalScope *FnScope = LScopes.getCurrentFunctionScope();
1553   DwarfCompileUnit &TheCU = *SPMap.lookup(FnScope->getScopeNode());
1554
1555   // Construct abstract scopes.
1556   for (LexicalScope *AScope : LScopes.getAbstractScopesList()) {
1557     DISubprogram SP(AScope->getScopeNode());
1558     if (!SP.isSubprogram())
1559       continue;
1560     // Collect info for variables that were optimized out.
1561     DIArray Variables = SP.getVariables();
1562     for (unsigned i = 0, e = Variables.getNumElements(); i != e; ++i) {
1563       DIVariable DV(Variables.getElement(i));
1564       assert(DV && DV.isVariable());
1565       if (!ProcessedVars.insert(DV))
1566         continue;
1567       ensureAbstractVariableIsCreated(DV, DV.getContext());
1568     }
1569     constructAbstractSubprogramScopeDIE(TheCU, AScope);
1570   }
1571
1572   DIE &CurFnDIE = constructSubprogramScopeDIE(TheCU, FnScope);
1573   if (!CurFn->getTarget().Options.DisableFramePointerElim(*CurFn))
1574     TheCU.addFlag(CurFnDIE, dwarf::DW_AT_APPLE_omit_frame_ptr);
1575
1576   // Add the range of this function to the list of ranges for the CU.
1577   RangeSpan Span(FunctionBeginSym, FunctionEndSym);
1578   TheCU.addRange(std::move(Span));
1579   PrevSection = Asm->getCurrentSection();
1580   PrevCU = &TheCU;
1581
1582   // Clear debug info
1583   // Ownership of DbgVariables is a bit subtle - ScopeVariables owns all the
1584   // DbgVariables except those that are also in AbstractVariables (since they
1585   // can be used cross-function)
1586   ScopeVariables.clear();
1587   CurrentFnArguments.clear();
1588   DbgValues.clear();
1589   LabelsBeforeInsn.clear();
1590   LabelsAfterInsn.clear();
1591   PrevLabel = nullptr;
1592   CurFn = nullptr;
1593 }
1594
1595 // Register a source line with debug info. Returns the  unique label that was
1596 // emitted and which provides correspondence to the source line list.
1597 void DwarfDebug::recordSourceLine(unsigned Line, unsigned Col, const MDNode *S,
1598                                   unsigned Flags) {
1599   StringRef Fn;
1600   StringRef Dir;
1601   unsigned Src = 1;
1602   unsigned Discriminator = 0;
1603   if (DIScope Scope = DIScope(S)) {
1604     assert(Scope.isScope());
1605     Fn = Scope.getFilename();
1606     Dir = Scope.getDirectory();
1607     if (Scope.isLexicalBlock())
1608       Discriminator = DILexicalBlock(S).getDiscriminator();
1609
1610     unsigned CUID = Asm->OutStreamer.getContext().getDwarfCompileUnitID();
1611     Src = static_cast<DwarfCompileUnit &>(*InfoHolder.getUnits()[CUID])
1612               .getOrCreateSourceID(Fn, Dir);
1613   }
1614   Asm->OutStreamer.EmitDwarfLocDirective(Src, Line, Col, Flags, 0,
1615                                          Discriminator, Fn);
1616 }
1617
1618 //===----------------------------------------------------------------------===//
1619 // Emit Methods
1620 //===----------------------------------------------------------------------===//
1621
1622 // Emit initial Dwarf sections with a label at the start of each one.
1623 void DwarfDebug::emitSectionLabels() {
1624   const TargetLoweringObjectFile &TLOF = Asm->getObjFileLowering();
1625
1626   // Dwarf sections base addresses.
1627   DwarfInfoSectionSym =
1628       emitSectionSym(Asm, TLOF.getDwarfInfoSection(), "section_info");
1629   if (useSplitDwarf())
1630     DwarfInfoDWOSectionSym =
1631         emitSectionSym(Asm, TLOF.getDwarfInfoDWOSection(), "section_info_dwo");
1632   DwarfAbbrevSectionSym =
1633       emitSectionSym(Asm, TLOF.getDwarfAbbrevSection(), "section_abbrev");
1634   if (useSplitDwarf())
1635     DwarfAbbrevDWOSectionSym = emitSectionSym(
1636         Asm, TLOF.getDwarfAbbrevDWOSection(), "section_abbrev_dwo");
1637   if (GenerateARangeSection)
1638     emitSectionSym(Asm, TLOF.getDwarfARangesSection());
1639
1640   DwarfLineSectionSym =
1641       emitSectionSym(Asm, TLOF.getDwarfLineSection(), "section_line");
1642   if (GenerateGnuPubSections) {
1643     DwarfGnuPubNamesSectionSym =
1644         emitSectionSym(Asm, TLOF.getDwarfGnuPubNamesSection());
1645     DwarfGnuPubTypesSectionSym =
1646         emitSectionSym(Asm, TLOF.getDwarfGnuPubTypesSection());
1647   } else if (HasDwarfPubSections) {
1648     emitSectionSym(Asm, TLOF.getDwarfPubNamesSection());
1649     emitSectionSym(Asm, TLOF.getDwarfPubTypesSection());
1650   }
1651
1652   DwarfStrSectionSym =
1653       emitSectionSym(Asm, TLOF.getDwarfStrSection(), "info_string");
1654   if (useSplitDwarf()) {
1655     DwarfStrDWOSectionSym =
1656         emitSectionSym(Asm, TLOF.getDwarfStrDWOSection(), "skel_string");
1657     DwarfAddrSectionSym =
1658         emitSectionSym(Asm, TLOF.getDwarfAddrSection(), "addr_sec");
1659     DwarfDebugLocSectionSym =
1660         emitSectionSym(Asm, TLOF.getDwarfLocDWOSection(), "skel_loc");
1661   } else
1662     DwarfDebugLocSectionSym =
1663         emitSectionSym(Asm, TLOF.getDwarfLocSection(), "section_debug_loc");
1664   DwarfDebugRangeSectionSym =
1665       emitSectionSym(Asm, TLOF.getDwarfRangesSection(), "debug_range");
1666 }
1667
1668 // Recursively emits a debug information entry.
1669 void DwarfDebug::emitDIE(DIE &Die) {
1670   // Get the abbreviation for this DIE.
1671   const DIEAbbrev &Abbrev = Die.getAbbrev();
1672
1673   // Emit the code (index) for the abbreviation.
1674   if (Asm->isVerbose())
1675     Asm->OutStreamer.AddComment("Abbrev [" + Twine(Abbrev.getNumber()) +
1676                                 "] 0x" + Twine::utohexstr(Die.getOffset()) +
1677                                 ":0x" + Twine::utohexstr(Die.getSize()) + " " +
1678                                 dwarf::TagString(Abbrev.getTag()));
1679   Asm->EmitULEB128(Abbrev.getNumber());
1680
1681   const SmallVectorImpl<DIEValue *> &Values = Die.getValues();
1682   const SmallVectorImpl<DIEAbbrevData> &AbbrevData = Abbrev.getData();
1683
1684   // Emit the DIE attribute values.
1685   for (unsigned i = 0, N = Values.size(); i < N; ++i) {
1686     dwarf::Attribute Attr = AbbrevData[i].getAttribute();
1687     dwarf::Form Form = AbbrevData[i].getForm();
1688     assert(Form && "Too many attributes for DIE (check abbreviation)");
1689
1690     if (Asm->isVerbose()) {
1691       Asm->OutStreamer.AddComment(dwarf::AttributeString(Attr));
1692       if (Attr == dwarf::DW_AT_accessibility)
1693         Asm->OutStreamer.AddComment(dwarf::AccessibilityString(
1694             cast<DIEInteger>(Values[i])->getValue()));
1695     }
1696
1697     // Emit an attribute using the defined form.
1698     Values[i]->EmitValue(Asm, Form);
1699   }
1700
1701   // Emit the DIE children if any.
1702   if (Abbrev.hasChildren()) {
1703     for (auto &Child : Die.getChildren())
1704       emitDIE(*Child);
1705
1706     Asm->OutStreamer.AddComment("End Of Children Mark");
1707     Asm->EmitInt8(0);
1708   }
1709 }
1710
1711 // Emit the debug info section.
1712 void DwarfDebug::emitDebugInfo() {
1713   DwarfFile &Holder = useSplitDwarf() ? SkeletonHolder : InfoHolder;
1714
1715   Holder.emitUnits(this, DwarfAbbrevSectionSym);
1716 }
1717
1718 // Emit the abbreviation section.
1719 void DwarfDebug::emitAbbreviations() {
1720   DwarfFile &Holder = useSplitDwarf() ? SkeletonHolder : InfoHolder;
1721
1722   Holder.emitAbbrevs(Asm->getObjFileLowering().getDwarfAbbrevSection());
1723 }
1724
1725 // Emit the last address of the section and the end of the line matrix.
1726 void DwarfDebug::emitEndOfLineMatrix(unsigned SectionEnd) {
1727   // Define last address of section.
1728   Asm->OutStreamer.AddComment("Extended Op");
1729   Asm->EmitInt8(0);
1730
1731   Asm->OutStreamer.AddComment("Op size");
1732   Asm->EmitInt8(Asm->getDataLayout().getPointerSize() + 1);
1733   Asm->OutStreamer.AddComment("DW_LNE_set_address");
1734   Asm->EmitInt8(dwarf::DW_LNE_set_address);
1735
1736   Asm->OutStreamer.AddComment("Section end label");
1737
1738   Asm->OutStreamer.EmitSymbolValue(
1739       Asm->GetTempSymbol("section_end", SectionEnd),
1740       Asm->getDataLayout().getPointerSize());
1741
1742   // Mark end of matrix.
1743   Asm->OutStreamer.AddComment("DW_LNE_end_sequence");
1744   Asm->EmitInt8(0);
1745   Asm->EmitInt8(1);
1746   Asm->EmitInt8(1);
1747 }
1748
1749 // Emit visible names into a hashed accelerator table section.
1750 void DwarfDebug::emitAccelNames() {
1751   AccelNames.FinalizeTable(Asm, "Names");
1752   Asm->OutStreamer.SwitchSection(
1753       Asm->getObjFileLowering().getDwarfAccelNamesSection());
1754   MCSymbol *SectionBegin = Asm->GetTempSymbol("names_begin");
1755   Asm->OutStreamer.EmitLabel(SectionBegin);
1756
1757   // Emit the full data.
1758   AccelNames.Emit(Asm, SectionBegin, &InfoHolder);
1759 }
1760
1761 // Emit objective C classes and categories into a hashed accelerator table
1762 // section.
1763 void DwarfDebug::emitAccelObjC() {
1764   AccelObjC.FinalizeTable(Asm, "ObjC");
1765   Asm->OutStreamer.SwitchSection(
1766       Asm->getObjFileLowering().getDwarfAccelObjCSection());
1767   MCSymbol *SectionBegin = Asm->GetTempSymbol("objc_begin");
1768   Asm->OutStreamer.EmitLabel(SectionBegin);
1769
1770   // Emit the full data.
1771   AccelObjC.Emit(Asm, SectionBegin, &InfoHolder);
1772 }
1773
1774 // Emit namespace dies into a hashed accelerator table.
1775 void DwarfDebug::emitAccelNamespaces() {
1776   AccelNamespace.FinalizeTable(Asm, "namespac");
1777   Asm->OutStreamer.SwitchSection(
1778       Asm->getObjFileLowering().getDwarfAccelNamespaceSection());
1779   MCSymbol *SectionBegin = Asm->GetTempSymbol("namespac_begin");
1780   Asm->OutStreamer.EmitLabel(SectionBegin);
1781
1782   // Emit the full data.
1783   AccelNamespace.Emit(Asm, SectionBegin, &InfoHolder);
1784 }
1785
1786 // Emit type dies into a hashed accelerator table.
1787 void DwarfDebug::emitAccelTypes() {
1788
1789   AccelTypes.FinalizeTable(Asm, "types");
1790   Asm->OutStreamer.SwitchSection(
1791       Asm->getObjFileLowering().getDwarfAccelTypesSection());
1792   MCSymbol *SectionBegin = Asm->GetTempSymbol("types_begin");
1793   Asm->OutStreamer.EmitLabel(SectionBegin);
1794
1795   // Emit the full data.
1796   AccelTypes.Emit(Asm, SectionBegin, &InfoHolder);
1797 }
1798
1799 // Public name handling.
1800 // The format for the various pubnames:
1801 //
1802 // dwarf pubnames - offset/name pairs where the offset is the offset into the CU
1803 // for the DIE that is named.
1804 //
1805 // gnu pubnames - offset/index value/name tuples where the offset is the offset
1806 // into the CU and the index value is computed according to the type of value
1807 // for the DIE that is named.
1808 //
1809 // For type units the offset is the offset of the skeleton DIE. For split dwarf
1810 // it's the offset within the debug_info/debug_types dwo section, however, the
1811 // reference in the pubname header doesn't change.
1812
1813 /// computeIndexValue - Compute the gdb index value for the DIE and CU.
1814 static dwarf::PubIndexEntryDescriptor computeIndexValue(DwarfUnit *CU,
1815                                                         const DIE *Die) {
1816   dwarf::GDBIndexEntryLinkage Linkage = dwarf::GIEL_STATIC;
1817
1818   // We could have a specification DIE that has our most of our knowledge,
1819   // look for that now.
1820   DIEValue *SpecVal = Die->findAttribute(dwarf::DW_AT_specification);
1821   if (SpecVal) {
1822     DIE &SpecDIE = cast<DIEEntry>(SpecVal)->getEntry();
1823     if (SpecDIE.findAttribute(dwarf::DW_AT_external))
1824       Linkage = dwarf::GIEL_EXTERNAL;
1825   } else if (Die->findAttribute(dwarf::DW_AT_external))
1826     Linkage = dwarf::GIEL_EXTERNAL;
1827
1828   switch (Die->getTag()) {
1829   case dwarf::DW_TAG_class_type:
1830   case dwarf::DW_TAG_structure_type:
1831   case dwarf::DW_TAG_union_type:
1832   case dwarf::DW_TAG_enumeration_type:
1833     return dwarf::PubIndexEntryDescriptor(
1834         dwarf::GIEK_TYPE, CU->getLanguage() != dwarf::DW_LANG_C_plus_plus
1835                               ? dwarf::GIEL_STATIC
1836                               : dwarf::GIEL_EXTERNAL);
1837   case dwarf::DW_TAG_typedef:
1838   case dwarf::DW_TAG_base_type:
1839   case dwarf::DW_TAG_subrange_type:
1840     return dwarf::PubIndexEntryDescriptor(dwarf::GIEK_TYPE, dwarf::GIEL_STATIC);
1841   case dwarf::DW_TAG_namespace:
1842     return dwarf::GIEK_TYPE;
1843   case dwarf::DW_TAG_subprogram:
1844     return dwarf::PubIndexEntryDescriptor(dwarf::GIEK_FUNCTION, Linkage);
1845   case dwarf::DW_TAG_constant:
1846   case dwarf::DW_TAG_variable:
1847     return dwarf::PubIndexEntryDescriptor(dwarf::GIEK_VARIABLE, Linkage);
1848   case dwarf::DW_TAG_enumerator:
1849     return dwarf::PubIndexEntryDescriptor(dwarf::GIEK_VARIABLE,
1850                                           dwarf::GIEL_STATIC);
1851   default:
1852     return dwarf::GIEK_NONE;
1853   }
1854 }
1855
1856 /// emitDebugPubNames - Emit visible names into a debug pubnames section.
1857 ///
1858 void DwarfDebug::emitDebugPubNames(bool GnuStyle) {
1859   const MCSection *PSec =
1860       GnuStyle ? Asm->getObjFileLowering().getDwarfGnuPubNamesSection()
1861                : Asm->getObjFileLowering().getDwarfPubNamesSection();
1862
1863   emitDebugPubSection(GnuStyle, PSec, "Names", &DwarfUnit::getGlobalNames);
1864 }
1865
1866 void DwarfDebug::emitDebugPubSection(
1867     bool GnuStyle, const MCSection *PSec, StringRef Name,
1868     const StringMap<const DIE *> &(DwarfUnit::*Accessor)() const) {
1869   for (const auto &NU : CUMap) {
1870     DwarfCompileUnit *TheU = NU.second;
1871
1872     const auto &Globals = (TheU->*Accessor)();
1873
1874     if (Globals.empty())
1875       continue;
1876
1877     if (auto Skeleton = static_cast<DwarfCompileUnit *>(TheU->getSkeleton()))
1878       TheU = Skeleton;
1879     unsigned ID = TheU->getUniqueID();
1880
1881     // Start the dwarf pubnames section.
1882     Asm->OutStreamer.SwitchSection(PSec);
1883
1884     // Emit the header.
1885     Asm->OutStreamer.AddComment("Length of Public " + Name + " Info");
1886     MCSymbol *BeginLabel = Asm->GetTempSymbol("pub" + Name + "_begin", ID);
1887     MCSymbol *EndLabel = Asm->GetTempSymbol("pub" + Name + "_end", ID);
1888     Asm->EmitLabelDifference(EndLabel, BeginLabel, 4);
1889
1890     Asm->OutStreamer.EmitLabel(BeginLabel);
1891
1892     Asm->OutStreamer.AddComment("DWARF Version");
1893     Asm->EmitInt16(dwarf::DW_PUBNAMES_VERSION);
1894
1895     Asm->OutStreamer.AddComment("Offset of Compilation Unit Info");
1896     Asm->EmitSectionOffset(TheU->getLabelBegin(), TheU->getSectionSym());
1897
1898     Asm->OutStreamer.AddComment("Compilation Unit Length");
1899     Asm->EmitLabelDifference(TheU->getLabelEnd(), TheU->getLabelBegin(), 4);
1900
1901     // Emit the pubnames for this compilation unit.
1902     for (const auto &GI : Globals) {
1903       const char *Name = GI.getKeyData();
1904       const DIE *Entity = GI.second;
1905
1906       Asm->OutStreamer.AddComment("DIE offset");
1907       Asm->EmitInt32(Entity->getOffset());
1908
1909       if (GnuStyle) {
1910         dwarf::PubIndexEntryDescriptor Desc = computeIndexValue(TheU, Entity);
1911         Asm->OutStreamer.AddComment(
1912             Twine("Kind: ") + dwarf::GDBIndexEntryKindString(Desc.Kind) + ", " +
1913             dwarf::GDBIndexEntryLinkageString(Desc.Linkage));
1914         Asm->EmitInt8(Desc.toBits());
1915       }
1916
1917       Asm->OutStreamer.AddComment("External Name");
1918       Asm->OutStreamer.EmitBytes(StringRef(Name, GI.getKeyLength() + 1));
1919     }
1920
1921     Asm->OutStreamer.AddComment("End Mark");
1922     Asm->EmitInt32(0);
1923     Asm->OutStreamer.EmitLabel(EndLabel);
1924   }
1925 }
1926
1927 void DwarfDebug::emitDebugPubTypes(bool GnuStyle) {
1928   const MCSection *PSec =
1929       GnuStyle ? Asm->getObjFileLowering().getDwarfGnuPubTypesSection()
1930                : Asm->getObjFileLowering().getDwarfPubTypesSection();
1931
1932   emitDebugPubSection(GnuStyle, PSec, "Types", &DwarfUnit::getGlobalTypes);
1933 }
1934
1935 // Emit visible names into a debug str section.
1936 void DwarfDebug::emitDebugStr() {
1937   DwarfFile &Holder = useSplitDwarf() ? SkeletonHolder : InfoHolder;
1938   Holder.emitStrings(Asm->getObjFileLowering().getDwarfStrSection());
1939 }
1940
1941 void DwarfDebug::emitDebugLocEntry(ByteStreamer &Streamer,
1942                                    const DebugLocEntry &Entry) {
1943   assert(Entry.getValues().size() == 1 &&
1944          "multi-value entries are not supported yet.");
1945   const DebugLocEntry::Value Value = Entry.getValues()[0];
1946   DIVariable DV(Value.getVariable());
1947   if (Value.isInt()) {
1948     DIBasicType BTy(resolve(DV.getType()));
1949     if (BTy.Verify() && (BTy.getEncoding() == dwarf::DW_ATE_signed ||
1950                          BTy.getEncoding() == dwarf::DW_ATE_signed_char)) {
1951       Streamer.EmitInt8(dwarf::DW_OP_consts, "DW_OP_consts");
1952       Streamer.EmitSLEB128(Value.getInt());
1953     } else {
1954       Streamer.EmitInt8(dwarf::DW_OP_constu, "DW_OP_constu");
1955       Streamer.EmitULEB128(Value.getInt());
1956     }
1957   } else if (Value.isLocation()) {
1958     MachineLocation Loc = Value.getLoc();
1959     if (!DV.hasComplexAddress())
1960       // Regular entry.
1961       Asm->EmitDwarfRegOp(Streamer, Loc, DV.isIndirect());
1962     else {
1963       // Complex address entry.
1964       unsigned N = DV.getNumAddrElements();
1965       unsigned i = 0;
1966       if (N >= 2 && DV.getAddrElement(0) == DIBuilder::OpPlus) {
1967         if (Loc.getOffset()) {
1968           i = 2;
1969           Asm->EmitDwarfRegOp(Streamer, Loc, DV.isIndirect());
1970           Streamer.EmitInt8(dwarf::DW_OP_deref, "DW_OP_deref");
1971           Streamer.EmitInt8(dwarf::DW_OP_plus_uconst, "DW_OP_plus_uconst");
1972           Streamer.EmitSLEB128(DV.getAddrElement(1));
1973         } else {
1974           // If first address element is OpPlus then emit
1975           // DW_OP_breg + Offset instead of DW_OP_reg + Offset.
1976           MachineLocation TLoc(Loc.getReg(), DV.getAddrElement(1));
1977           Asm->EmitDwarfRegOp(Streamer, TLoc, DV.isIndirect());
1978           i = 2;
1979         }
1980       } else {
1981         Asm->EmitDwarfRegOp(Streamer, Loc, DV.isIndirect());
1982       }
1983
1984       // Emit remaining complex address elements.
1985       for (; i < N; ++i) {
1986         uint64_t Element = DV.getAddrElement(i);
1987         if (Element == DIBuilder::OpPlus) {
1988           Streamer.EmitInt8(dwarf::DW_OP_plus_uconst, "DW_OP_plus_uconst");
1989           Streamer.EmitULEB128(DV.getAddrElement(++i));
1990         } else if (Element == DIBuilder::OpDeref) {
1991           if (!Loc.isReg())
1992             Streamer.EmitInt8(dwarf::DW_OP_deref, "DW_OP_deref");
1993         } else
1994           llvm_unreachable("unknown Opcode found in complex address");
1995       }
1996     }
1997   }
1998   // else ... ignore constant fp. There is not any good way to
1999   // to represent them here in dwarf.
2000   // FIXME: ^
2001 }
2002
2003 void DwarfDebug::emitDebugLocEntryLocation(const DebugLocEntry &Entry) {
2004   Asm->OutStreamer.AddComment("Loc expr size");
2005   MCSymbol *begin = Asm->OutStreamer.getContext().CreateTempSymbol();
2006   MCSymbol *end = Asm->OutStreamer.getContext().CreateTempSymbol();
2007   Asm->EmitLabelDifference(end, begin, 2);
2008   Asm->OutStreamer.EmitLabel(begin);
2009   // Emit the entry.
2010   APByteStreamer Streamer(*Asm);
2011   emitDebugLocEntry(Streamer, Entry);
2012   // Close the range.
2013   Asm->OutStreamer.EmitLabel(end);
2014 }
2015
2016 // Emit locations into the debug loc section.
2017 void DwarfDebug::emitDebugLoc() {
2018   // Start the dwarf loc section.
2019   Asm->OutStreamer.SwitchSection(
2020       Asm->getObjFileLowering().getDwarfLocSection());
2021   unsigned char Size = Asm->getDataLayout().getPointerSize();
2022   for (const auto &DebugLoc : DotDebugLocEntries) {
2023     Asm->OutStreamer.EmitLabel(DebugLoc.Label);
2024     for (const auto &Entry : DebugLoc.List) {
2025       // Set up the range. This range is relative to the entry point of the
2026       // compile unit. This is a hard coded 0 for low_pc when we're emitting
2027       // ranges, or the DW_AT_low_pc on the compile unit otherwise.
2028       const DwarfCompileUnit *CU = Entry.getCU();
2029       if (CU->getRanges().size() == 1) {
2030         // Grab the begin symbol from the first range as our base.
2031         const MCSymbol *Base = CU->getRanges()[0].getStart();
2032         Asm->EmitLabelDifference(Entry.getBeginSym(), Base, Size);
2033         Asm->EmitLabelDifference(Entry.getEndSym(), Base, Size);
2034       } else {
2035         Asm->OutStreamer.EmitSymbolValue(Entry.getBeginSym(), Size);
2036         Asm->OutStreamer.EmitSymbolValue(Entry.getEndSym(), Size);
2037       }
2038
2039       emitDebugLocEntryLocation(Entry);
2040     }
2041     Asm->OutStreamer.EmitIntValue(0, Size);
2042     Asm->OutStreamer.EmitIntValue(0, Size);
2043   }
2044 }
2045
2046 void DwarfDebug::emitDebugLocDWO() {
2047   Asm->OutStreamer.SwitchSection(
2048       Asm->getObjFileLowering().getDwarfLocDWOSection());
2049   for (const auto &DebugLoc : DotDebugLocEntries) {
2050     Asm->OutStreamer.EmitLabel(DebugLoc.Label);
2051     for (const auto &Entry : DebugLoc.List) {
2052       // Just always use start_length for now - at least that's one address
2053       // rather than two. We could get fancier and try to, say, reuse an
2054       // address we know we've emitted elsewhere (the start of the function?
2055       // The start of the CU or CU subrange that encloses this range?)
2056       Asm->EmitInt8(dwarf::DW_LLE_start_length_entry);
2057       unsigned idx = AddrPool.getIndex(Entry.getBeginSym());
2058       Asm->EmitULEB128(idx);
2059       Asm->EmitLabelDifference(Entry.getEndSym(), Entry.getBeginSym(), 4);
2060
2061       emitDebugLocEntryLocation(Entry);
2062     }
2063     Asm->EmitInt8(dwarf::DW_LLE_end_of_list_entry);
2064   }
2065 }
2066
2067 struct ArangeSpan {
2068   const MCSymbol *Start, *End;
2069 };
2070
2071 // Emit a debug aranges section, containing a CU lookup for any
2072 // address we can tie back to a CU.
2073 void DwarfDebug::emitDebugARanges() {
2074   // Start the dwarf aranges section.
2075   Asm->OutStreamer.SwitchSection(
2076       Asm->getObjFileLowering().getDwarfARangesSection());
2077
2078   typedef DenseMap<DwarfCompileUnit *, std::vector<ArangeSpan>> SpansType;
2079
2080   SpansType Spans;
2081
2082   // Build a list of sections used.
2083   std::vector<const MCSection *> Sections;
2084   for (const auto &it : SectionMap) {
2085     const MCSection *Section = it.first;
2086     Sections.push_back(Section);
2087   }
2088
2089   // Sort the sections into order.
2090   // This is only done to ensure consistent output order across different runs.
2091   std::sort(Sections.begin(), Sections.end(), SectionSort);
2092
2093   // Build a set of address spans, sorted by CU.
2094   for (const MCSection *Section : Sections) {
2095     SmallVector<SymbolCU, 8> &List = SectionMap[Section];
2096     if (List.size() < 2)
2097       continue;
2098
2099     // Sort the symbols by offset within the section.
2100     std::sort(List.begin(), List.end(),
2101               [&](const SymbolCU &A, const SymbolCU &B) {
2102       unsigned IA = A.Sym ? Asm->OutStreamer.GetSymbolOrder(A.Sym) : 0;
2103       unsigned IB = B.Sym ? Asm->OutStreamer.GetSymbolOrder(B.Sym) : 0;
2104
2105       // Symbols with no order assigned should be placed at the end.
2106       // (e.g. section end labels)
2107       if (IA == 0)
2108         return false;
2109       if (IB == 0)
2110         return true;
2111       return IA < IB;
2112     });
2113
2114     // If we have no section (e.g. common), just write out
2115     // individual spans for each symbol.
2116     if (!Section) {
2117       for (const SymbolCU &Cur : List) {
2118         ArangeSpan Span;
2119         Span.Start = Cur.Sym;
2120         Span.End = nullptr;
2121         if (Cur.CU)
2122           Spans[Cur.CU].push_back(Span);
2123       }
2124     } else {
2125       // Build spans between each label.
2126       const MCSymbol *StartSym = List[0].Sym;
2127       for (size_t n = 1, e = List.size(); n < e; n++) {
2128         const SymbolCU &Prev = List[n - 1];
2129         const SymbolCU &Cur = List[n];
2130
2131         // Try and build the longest span we can within the same CU.
2132         if (Cur.CU != Prev.CU) {
2133           ArangeSpan Span;
2134           Span.Start = StartSym;
2135           Span.End = Cur.Sym;
2136           Spans[Prev.CU].push_back(Span);
2137           StartSym = Cur.Sym;
2138         }
2139       }
2140     }
2141   }
2142
2143   unsigned PtrSize = Asm->getDataLayout().getPointerSize();
2144
2145   // Build a list of CUs used.
2146   std::vector<DwarfCompileUnit *> CUs;
2147   for (const auto &it : Spans) {
2148     DwarfCompileUnit *CU = it.first;
2149     CUs.push_back(CU);
2150   }
2151
2152   // Sort the CU list (again, to ensure consistent output order).
2153   std::sort(CUs.begin(), CUs.end(), [](const DwarfUnit *A, const DwarfUnit *B) {
2154     return A->getUniqueID() < B->getUniqueID();
2155   });
2156
2157   // Emit an arange table for each CU we used.
2158   for (DwarfCompileUnit *CU : CUs) {
2159     std::vector<ArangeSpan> &List = Spans[CU];
2160
2161     // Emit size of content not including length itself.
2162     unsigned ContentSize =
2163         sizeof(int16_t) + // DWARF ARange version number
2164         sizeof(int32_t) + // Offset of CU in the .debug_info section
2165         sizeof(int8_t) +  // Pointer Size (in bytes)
2166         sizeof(int8_t);   // Segment Size (in bytes)
2167
2168     unsigned TupleSize = PtrSize * 2;
2169
2170     // 7.20 in the Dwarf specs requires the table to be aligned to a tuple.
2171     unsigned Padding =
2172         OffsetToAlignment(sizeof(int32_t) + ContentSize, TupleSize);
2173
2174     ContentSize += Padding;
2175     ContentSize += (List.size() + 1) * TupleSize;
2176
2177     // For each compile unit, write the list of spans it covers.
2178     Asm->OutStreamer.AddComment("Length of ARange Set");
2179     Asm->EmitInt32(ContentSize);
2180     Asm->OutStreamer.AddComment("DWARF Arange version number");
2181     Asm->EmitInt16(dwarf::DW_ARANGES_VERSION);
2182     Asm->OutStreamer.AddComment("Offset Into Debug Info Section");
2183     Asm->EmitSectionOffset(CU->getLocalLabelBegin(), CU->getLocalSectionSym());
2184     Asm->OutStreamer.AddComment("Address Size (in bytes)");
2185     Asm->EmitInt8(PtrSize);
2186     Asm->OutStreamer.AddComment("Segment Size (in bytes)");
2187     Asm->EmitInt8(0);
2188
2189     Asm->OutStreamer.EmitFill(Padding, 0xff);
2190
2191     for (const ArangeSpan &Span : List) {
2192       Asm->EmitLabelReference(Span.Start, PtrSize);
2193
2194       // Calculate the size as being from the span start to it's end.
2195       if (Span.End) {
2196         Asm->EmitLabelDifference(Span.End, Span.Start, PtrSize);
2197       } else {
2198         // For symbols without an end marker (e.g. common), we
2199         // write a single arange entry containing just that one symbol.
2200         uint64_t Size = SymSize[Span.Start];
2201         if (Size == 0)
2202           Size = 1;
2203
2204         Asm->OutStreamer.EmitIntValue(Size, PtrSize);
2205       }
2206     }
2207
2208     Asm->OutStreamer.AddComment("ARange terminator");
2209     Asm->OutStreamer.EmitIntValue(0, PtrSize);
2210     Asm->OutStreamer.EmitIntValue(0, PtrSize);
2211   }
2212 }
2213
2214 // Emit visible names into a debug ranges section.
2215 void DwarfDebug::emitDebugRanges() {
2216   // Start the dwarf ranges section.
2217   Asm->OutStreamer.SwitchSection(
2218       Asm->getObjFileLowering().getDwarfRangesSection());
2219
2220   // Size for our labels.
2221   unsigned char Size = Asm->getDataLayout().getPointerSize();
2222
2223   // Grab the specific ranges for the compile units in the module.
2224   for (const auto &I : CUMap) {
2225     DwarfCompileUnit *TheCU = I.second;
2226
2227     // Iterate over the misc ranges for the compile units in the module.
2228     for (const RangeSpanList &List : TheCU->getRangeLists()) {
2229       // Emit our symbol so we can find the beginning of the range.
2230       Asm->OutStreamer.EmitLabel(List.getSym());
2231
2232       for (const RangeSpan &Range : List.getRanges()) {
2233         const MCSymbol *Begin = Range.getStart();
2234         const MCSymbol *End = Range.getEnd();
2235         assert(Begin && "Range without a begin symbol?");
2236         assert(End && "Range without an end symbol?");
2237         if (TheCU->getRanges().size() == 1) {
2238           // Grab the begin symbol from the first range as our base.
2239           const MCSymbol *Base = TheCU->getRanges()[0].getStart();
2240           Asm->EmitLabelDifference(Begin, Base, Size);
2241           Asm->EmitLabelDifference(End, Base, Size);
2242         } else {
2243           Asm->OutStreamer.EmitSymbolValue(Begin, Size);
2244           Asm->OutStreamer.EmitSymbolValue(End, Size);
2245         }
2246       }
2247
2248       // And terminate the list with two 0 values.
2249       Asm->OutStreamer.EmitIntValue(0, Size);
2250       Asm->OutStreamer.EmitIntValue(0, Size);
2251     }
2252
2253     // Now emit a range for the CU itself.
2254     if (TheCU->getRanges().size() > 1) {
2255       Asm->OutStreamer.EmitLabel(
2256           Asm->GetTempSymbol("cu_ranges", TheCU->getUniqueID()));
2257       for (const RangeSpan &Range : TheCU->getRanges()) {
2258         const MCSymbol *Begin = Range.getStart();
2259         const MCSymbol *End = Range.getEnd();
2260         assert(Begin && "Range without a begin symbol?");
2261         assert(End && "Range without an end symbol?");
2262         Asm->OutStreamer.EmitSymbolValue(Begin, Size);
2263         Asm->OutStreamer.EmitSymbolValue(End, Size);
2264       }
2265       // And terminate the list with two 0 values.
2266       Asm->OutStreamer.EmitIntValue(0, Size);
2267       Asm->OutStreamer.EmitIntValue(0, Size);
2268     }
2269   }
2270 }
2271
2272 // DWARF5 Experimental Separate Dwarf emitters.
2273
2274 void DwarfDebug::initSkeletonUnit(const DwarfUnit &U, DIE &Die,
2275                                   std::unique_ptr<DwarfUnit> NewU) {
2276   NewU->addLocalString(Die, dwarf::DW_AT_GNU_dwo_name,
2277                        U.getCUNode().getSplitDebugFilename());
2278
2279   if (!CompilationDir.empty())
2280     NewU->addLocalString(Die, dwarf::DW_AT_comp_dir, CompilationDir);
2281
2282   addGnuPubAttributes(*NewU, Die);
2283
2284   SkeletonHolder.addUnit(std::move(NewU));
2285 }
2286
2287 // This DIE has the following attributes: DW_AT_comp_dir, DW_AT_stmt_list,
2288 // DW_AT_low_pc, DW_AT_high_pc, DW_AT_ranges, DW_AT_dwo_name, DW_AT_dwo_id,
2289 // DW_AT_addr_base, DW_AT_ranges_base.
2290 DwarfCompileUnit &DwarfDebug::constructSkeletonCU(const DwarfCompileUnit &CU) {
2291
2292   auto OwnedUnit = make_unique<DwarfCompileUnit>(
2293       CU.getUniqueID(), CU.getCUNode(), Asm, this, &SkeletonHolder);
2294   DwarfCompileUnit &NewCU = *OwnedUnit;
2295   NewCU.initSection(Asm->getObjFileLowering().getDwarfInfoSection(),
2296                     DwarfInfoSectionSym);
2297
2298   NewCU.initStmtList(DwarfLineSectionSym);
2299
2300   initSkeletonUnit(CU, NewCU.getUnitDie(), std::move(OwnedUnit));
2301
2302   return NewCU;
2303 }
2304
2305 // This DIE has the following attributes: DW_AT_comp_dir, DW_AT_dwo_name,
2306 // DW_AT_addr_base.
2307 DwarfTypeUnit &DwarfDebug::constructSkeletonTU(DwarfTypeUnit &TU) {
2308   DwarfCompileUnit &CU = static_cast<DwarfCompileUnit &>(
2309       *SkeletonHolder.getUnits()[TU.getCU().getUniqueID()]);
2310
2311   auto OwnedUnit = make_unique<DwarfTypeUnit>(TU.getUniqueID(), CU, Asm, this,
2312                                               &SkeletonHolder);
2313   DwarfTypeUnit &NewTU = *OwnedUnit;
2314   NewTU.setTypeSignature(TU.getTypeSignature());
2315   NewTU.setType(nullptr);
2316   NewTU.initSection(
2317       Asm->getObjFileLowering().getDwarfTypesSection(TU.getTypeSignature()));
2318
2319   initSkeletonUnit(TU, NewTU.getUnitDie(), std::move(OwnedUnit));
2320   return NewTU;
2321 }
2322
2323 // Emit the .debug_info.dwo section for separated dwarf. This contains the
2324 // compile units that would normally be in debug_info.
2325 void DwarfDebug::emitDebugInfoDWO() {
2326   assert(useSplitDwarf() && "No split dwarf debug info?");
2327   // Don't pass an abbrev symbol, using a constant zero instead so as not to
2328   // emit relocations into the dwo file.
2329   InfoHolder.emitUnits(this, /* AbbrevSymbol */ nullptr);
2330 }
2331
2332 // Emit the .debug_abbrev.dwo section for separated dwarf. This contains the
2333 // abbreviations for the .debug_info.dwo section.
2334 void DwarfDebug::emitDebugAbbrevDWO() {
2335   assert(useSplitDwarf() && "No split dwarf?");
2336   InfoHolder.emitAbbrevs(Asm->getObjFileLowering().getDwarfAbbrevDWOSection());
2337 }
2338
2339 void DwarfDebug::emitDebugLineDWO() {
2340   assert(useSplitDwarf() && "No split dwarf?");
2341   Asm->OutStreamer.SwitchSection(
2342       Asm->getObjFileLowering().getDwarfLineDWOSection());
2343   SplitTypeUnitFileTable.Emit(Asm->OutStreamer);
2344 }
2345
2346 // Emit the .debug_str.dwo section for separated dwarf. This contains the
2347 // string section and is identical in format to traditional .debug_str
2348 // sections.
2349 void DwarfDebug::emitDebugStrDWO() {
2350   assert(useSplitDwarf() && "No split dwarf?");
2351   const MCSection *OffSec =
2352       Asm->getObjFileLowering().getDwarfStrOffDWOSection();
2353   const MCSymbol *StrSym = DwarfStrSectionSym;
2354   InfoHolder.emitStrings(Asm->getObjFileLowering().getDwarfStrDWOSection(),
2355                          OffSec, StrSym);
2356 }
2357
2358 MCDwarfDwoLineTable *DwarfDebug::getDwoLineTable(const DwarfCompileUnit &CU) {
2359   if (!useSplitDwarf())
2360     return nullptr;
2361   if (SingleCU)
2362     SplitTypeUnitFileTable.setCompilationDir(CU.getCUNode().getDirectory());
2363   return &SplitTypeUnitFileTable;
2364 }
2365
2366 static uint64_t makeTypeSignature(StringRef Identifier) {
2367   MD5 Hash;
2368   Hash.update(Identifier);
2369   // ... take the least significant 8 bytes and return those. Our MD5
2370   // implementation always returns its results in little endian, swap bytes
2371   // appropriately.
2372   MD5::MD5Result Result;
2373   Hash.final(Result);
2374   return *reinterpret_cast<support::ulittle64_t *>(Result + 8);
2375 }
2376
2377 void DwarfDebug::addDwarfTypeUnitType(DwarfCompileUnit &CU,
2378                                       StringRef Identifier, DIE &RefDie,
2379                                       DICompositeType CTy) {
2380   // Fast path if we're building some type units and one has already used the
2381   // address pool we know we're going to throw away all this work anyway, so
2382   // don't bother building dependent types.
2383   if (!TypeUnitsUnderConstruction.empty() && AddrPool.hasBeenUsed())
2384     return;
2385
2386   const DwarfTypeUnit *&TU = DwarfTypeUnits[CTy];
2387   if (TU) {
2388     CU.addDIETypeSignature(RefDie, *TU);
2389     return;
2390   }
2391
2392   bool TopLevelType = TypeUnitsUnderConstruction.empty();
2393   AddrPool.resetUsedFlag();
2394
2395   auto OwnedUnit =
2396       make_unique<DwarfTypeUnit>(InfoHolder.getUnits().size(), CU, Asm, this,
2397                                  &InfoHolder, getDwoLineTable(CU));
2398   DwarfTypeUnit &NewTU = *OwnedUnit;
2399   DIE &UnitDie = NewTU.getUnitDie();
2400   TU = &NewTU;
2401   TypeUnitsUnderConstruction.push_back(
2402       std::make_pair(std::move(OwnedUnit), CTy));
2403
2404   NewTU.addUInt(UnitDie, dwarf::DW_AT_language, dwarf::DW_FORM_data2,
2405                 CU.getLanguage());
2406
2407   uint64_t Signature = makeTypeSignature(Identifier);
2408   NewTU.setTypeSignature(Signature);
2409
2410   if (!useSplitDwarf())
2411     CU.applyStmtList(UnitDie);
2412
2413   // FIXME: Skip using COMDAT groups for type units in the .dwo file once tools
2414   // such as DWP ( http://gcc.gnu.org/wiki/DebugFissionDWP ) can cope with it.
2415   NewTU.initSection(
2416       useSplitDwarf()
2417           ? Asm->getObjFileLowering().getDwarfTypesDWOSection(Signature)
2418           : Asm->getObjFileLowering().getDwarfTypesSection(Signature));
2419
2420   NewTU.setType(NewTU.createTypeDIE(CTy));
2421
2422   if (TopLevelType) {
2423     auto TypeUnitsToAdd = std::move(TypeUnitsUnderConstruction);
2424     TypeUnitsUnderConstruction.clear();
2425
2426     // Types referencing entries in the address table cannot be placed in type
2427     // units.
2428     if (AddrPool.hasBeenUsed()) {
2429
2430       // Remove all the types built while building this type.
2431       // This is pessimistic as some of these types might not be dependent on
2432       // the type that used an address.
2433       for (const auto &TU : TypeUnitsToAdd)
2434         DwarfTypeUnits.erase(TU.second);
2435
2436       // Construct this type in the CU directly.
2437       // This is inefficient because all the dependent types will be rebuilt
2438       // from scratch, including building them in type units, discovering that
2439       // they depend on addresses, throwing them out and rebuilding them.
2440       CU.constructTypeDIE(RefDie, CTy);
2441       return;
2442     }
2443
2444     // If the type wasn't dependent on fission addresses, finish adding the type
2445     // and all its dependent types.
2446     for (auto &TU : TypeUnitsToAdd) {
2447       if (useSplitDwarf())
2448         TU.first->setSkeleton(constructSkeletonTU(*TU.first));
2449       InfoHolder.addUnit(std::move(TU.first));
2450     }
2451   }
2452   CU.addDIETypeSignature(RefDie, NewTU);
2453 }
2454
2455 void DwarfDebug::attachLowHighPC(DwarfCompileUnit &Unit, DIE &D,
2456                                  MCSymbol *Begin, MCSymbol *End) {
2457   assert(Begin && "Begin label should not be null!");
2458   assert(End && "End label should not be null!");
2459   assert(Begin->isDefined() && "Invalid starting label");
2460   assert(End->isDefined() && "Invalid end label");
2461
2462   Unit.addLabelAddress(D, dwarf::DW_AT_low_pc, Begin);
2463   if (DwarfVersion < 4)
2464     Unit.addLabelAddress(D, dwarf::DW_AT_high_pc, End);
2465   else
2466     Unit.addLabelDelta(D, dwarf::DW_AT_high_pc, End, Begin);
2467 }
2468
2469 // Accelerator table mutators - add each name along with its companion
2470 // DIE to the proper table while ensuring that the name that we're going
2471 // to reference is in the string table. We do this since the names we
2472 // add may not only be identical to the names in the DIE.
2473 void DwarfDebug::addAccelName(StringRef Name, const DIE &Die) {
2474   if (!useDwarfAccelTables())
2475     return;
2476   AccelNames.AddName(Name, InfoHolder.getStringPool().getSymbol(*Asm, Name),
2477                      &Die);
2478 }
2479
2480 void DwarfDebug::addAccelObjC(StringRef Name, const DIE &Die) {
2481   if (!useDwarfAccelTables())
2482     return;
2483   AccelObjC.AddName(Name, InfoHolder.getStringPool().getSymbol(*Asm, Name),
2484                     &Die);
2485 }
2486
2487 void DwarfDebug::addAccelNamespace(StringRef Name, const DIE &Die) {
2488   if (!useDwarfAccelTables())
2489     return;
2490   AccelNamespace.AddName(Name, InfoHolder.getStringPool().getSymbol(*Asm, Name),
2491                          &Die);
2492 }
2493
2494 void DwarfDebug::addAccelType(StringRef Name, const DIE &Die, char Flags) {
2495   if (!useDwarfAccelTables())
2496     return;
2497   AccelTypes.AddName(Name, InfoHolder.getStringPool().getSymbol(*Asm, Name),
2498                      &Die);
2499 }