Reorder language in the CompileUnit description and add a comment.
[oota-llvm.git] / lib / CodeGen / AsmPrinter / DwarfCompileUnit.cpp
1 //===-- llvm/CodeGen/DwarfCompileUnit.cpp - Dwarf Compile Unit ------------===//
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 constructing a dwarf compile unit.
11 //
12 //===----------------------------------------------------------------------===//
13
14 #define DEBUG_TYPE "dwarfdebug"
15
16 #include "DwarfCompileUnit.h"
17 #include "DwarfAccelTable.h"
18 #include "DwarfDebug.h"
19 #include "llvm/ADT/APFloat.h"
20 #include "llvm/DIBuilder.h"
21 #include "llvm/IR/Constants.h"
22 #include "llvm/IR/DataLayout.h"
23 #include "llvm/IR/GlobalVariable.h"
24 #include "llvm/IR/Instructions.h"
25 #include "llvm/MC/MCSection.h"
26 #include "llvm/MC/MCStreamer.h"
27 #include "llvm/Target/Mangler.h"
28 #include "llvm/Target/TargetFrameLowering.h"
29 #include "llvm/Target/TargetMachine.h"
30 #include "llvm/Target/TargetLoweringObjectFile.h"
31 #include "llvm/Target/TargetRegisterInfo.h"
32 #include "llvm/Support/CommandLine.h"
33
34 using namespace llvm;
35
36 static cl::opt<bool> GenerateTypeUnits("generate-type-units", cl::Hidden,
37                                        cl::desc("Generate DWARF4 type units."),
38                                        cl::init(false));
39
40 /// CompileUnit - Compile unit constructor.
41 CompileUnit::CompileUnit(unsigned UID, DIE *D, DICompileUnit Node,
42                          AsmPrinter *A, DwarfDebug *DW, DwarfUnits *DWU)
43     : UniqueID(UID), Node(Node), Language(Node.getLanguage()), CUDie(D), Asm(A),
44       DD(DW), DU(DWU), IndexTyDie(0), DebugInfoOffset(0) {
45   DIEIntegerOne = new (DIEValueAllocator) DIEInteger(1);
46   insertDIE(Node, D);
47 }
48
49 CompileUnit::CompileUnit(unsigned UID, DIE *D, uint16_t Language, AsmPrinter *A,
50                          DwarfDebug *DD, DwarfUnits *DU)
51     : UniqueID(UID), Node(NULL), Language(Language), CUDie(D), Asm(A), DD(DD),
52       DU(DU), IndexTyDie(0), DebugInfoOffset(0) {
53   DIEIntegerOne = new (DIEValueAllocator) DIEInteger(1);
54 }
55
56 /// ~CompileUnit - Destructor for compile unit.
57 CompileUnit::~CompileUnit() {
58   for (unsigned j = 0, M = DIEBlocks.size(); j < M; ++j)
59     DIEBlocks[j]->~DIEBlock();
60 }
61
62 /// createDIEEntry - Creates a new DIEEntry to be a proxy for a debug
63 /// information entry.
64 DIEEntry *CompileUnit::createDIEEntry(DIE *Entry) {
65   DIEEntry *Value = new (DIEValueAllocator) DIEEntry(Entry);
66   return Value;
67 }
68
69 /// getDefaultLowerBound - Return the default lower bound for an array. If the
70 /// DWARF version doesn't handle the language, return -1.
71 int64_t CompileUnit::getDefaultLowerBound() const {
72   switch (getLanguage()) {
73   default:
74     break;
75
76   case dwarf::DW_LANG_C89:
77   case dwarf::DW_LANG_C99:
78   case dwarf::DW_LANG_C:
79   case dwarf::DW_LANG_C_plus_plus:
80   case dwarf::DW_LANG_ObjC:
81   case dwarf::DW_LANG_ObjC_plus_plus:
82     return 0;
83
84   case dwarf::DW_LANG_Fortran77:
85   case dwarf::DW_LANG_Fortran90:
86   case dwarf::DW_LANG_Fortran95:
87     return 1;
88
89   // The languages below have valid values only if the DWARF version >= 4.
90   case dwarf::DW_LANG_Java:
91   case dwarf::DW_LANG_Python:
92   case dwarf::DW_LANG_UPC:
93   case dwarf::DW_LANG_D:
94     if (dwarf::DWARF_VERSION >= 4)
95       return 0;
96     break;
97
98   case dwarf::DW_LANG_Ada83:
99   case dwarf::DW_LANG_Ada95:
100   case dwarf::DW_LANG_Cobol74:
101   case dwarf::DW_LANG_Cobol85:
102   case dwarf::DW_LANG_Modula2:
103   case dwarf::DW_LANG_Pascal83:
104   case dwarf::DW_LANG_PLI:
105     if (dwarf::DWARF_VERSION >= 4)
106       return 1;
107     break;
108   }
109
110   return -1;
111 }
112
113 /// Check whether the DIE for this MDNode can be shared across CUs.
114 static bool isShareableAcrossCUs(DIDescriptor D) {
115   // When the MDNode can be part of the type system, the DIE can be shared
116   // across CUs.
117   // Combining type units and cross-CU DIE sharing is lower value (since
118   // cross-CU DIE sharing is used in LTO and removes type redundancy at that
119   // level already) but may be implementable for some value in projects
120   // building multiple independent libraries with LTO and then linking those
121   // together.
122   return (D.isType() ||
123           (D.isSubprogram() && !DISubprogram(D).isDefinition())) &&
124          !GenerateTypeUnits;
125 }
126
127 /// getDIE - Returns the debug information entry map slot for the
128 /// specified debug variable. We delegate the request to DwarfDebug
129 /// when the DIE for this MDNode can be shared across CUs. The mappings
130 /// will be kept in DwarfDebug for shareable DIEs.
131 DIE *CompileUnit::getDIE(DIDescriptor D) const {
132   if (isShareableAcrossCUs(D))
133     return DD->getDIE(D);
134   return MDNodeToDieMap.lookup(D);
135 }
136
137 /// insertDIE - Insert DIE into the map. We delegate the request to DwarfDebug
138 /// when the DIE for this MDNode can be shared across CUs. The mappings
139 /// will be kept in DwarfDebug for shareable DIEs.
140 void CompileUnit::insertDIE(DIDescriptor Desc, DIE *D) {
141   if (isShareableAcrossCUs(Desc)) {
142     DD->insertDIE(Desc, D);
143     return;
144   }
145   MDNodeToDieMap.insert(std::make_pair(Desc, D));
146 }
147
148 /// addFlag - Add a flag that is true.
149 void CompileUnit::addFlag(DIE *Die, dwarf::Attribute Attribute) {
150   if (DD->getDwarfVersion() >= 4)
151     Die->addValue(Attribute, dwarf::DW_FORM_flag_present, DIEIntegerOne);
152   else
153     Die->addValue(Attribute, dwarf::DW_FORM_flag, DIEIntegerOne);
154 }
155
156 /// addUInt - Add an unsigned integer attribute data and value.
157 ///
158 void CompileUnit::addUInt(DIE *Die, dwarf::Attribute Attribute,
159                           Optional<dwarf::Form> Form, uint64_t Integer) {
160   if (!Form)
161     Form = DIEInteger::BestForm(false, Integer);
162   DIEValue *Value = Integer == 1 ? DIEIntegerOne : new (DIEValueAllocator)
163                         DIEInteger(Integer);
164   Die->addValue(Attribute, *Form, Value);
165 }
166
167 void CompileUnit::addUInt(DIEBlock *Block, dwarf::Form Form, uint64_t Integer) {
168   addUInt(Block, (dwarf::Attribute)0, Form, Integer);
169 }
170
171 /// addSInt - Add an signed integer attribute data and value.
172 ///
173 void CompileUnit::addSInt(DIE *Die, dwarf::Attribute Attribute,
174                           Optional<dwarf::Form> Form, int64_t Integer) {
175   if (!Form)
176     Form = DIEInteger::BestForm(true, Integer);
177   DIEValue *Value = new (DIEValueAllocator) DIEInteger(Integer);
178   Die->addValue(Attribute, *Form, Value);
179 }
180
181 void CompileUnit::addSInt(DIEBlock *Die, Optional<dwarf::Form> Form,
182                           int64_t Integer) {
183   addSInt(Die, (dwarf::Attribute)0, Form, Integer);
184 }
185
186 /// addString - Add a string attribute data and value. We always emit a
187 /// reference to the string pool instead of immediate strings so that DIEs have
188 /// more predictable sizes. In the case of split dwarf we emit an index
189 /// into another table which gets us the static offset into the string
190 /// table.
191 void CompileUnit::addString(DIE *Die, dwarf::Attribute Attribute,
192                             StringRef String) {
193   DIEValue *Value;
194   dwarf::Form Form;
195   if (!DD->useSplitDwarf()) {
196     MCSymbol *Symb = DU->getStringPoolEntry(String);
197     if (Asm->needsRelocationsForDwarfStringPool())
198       Value = new (DIEValueAllocator) DIELabel(Symb);
199     else {
200       MCSymbol *StringPool = DU->getStringPoolSym();
201       Value = new (DIEValueAllocator) DIEDelta(Symb, StringPool);
202     }
203     Form = dwarf::DW_FORM_strp;
204   } else {
205     unsigned idx = DU->getStringPoolIndex(String);
206     Value = new (DIEValueAllocator) DIEInteger(idx);
207     Form = dwarf::DW_FORM_GNU_str_index;
208   }
209   DIEValue *Str = new (DIEValueAllocator) DIEString(Value, String);
210   Die->addValue(Attribute, Form, Str);
211 }
212
213 /// addLocalString - Add a string attribute data and value. This is guaranteed
214 /// to be in the local string pool instead of indirected.
215 void CompileUnit::addLocalString(DIE *Die, dwarf::Attribute Attribute,
216                                  StringRef String) {
217   MCSymbol *Symb = DU->getStringPoolEntry(String);
218   DIEValue *Value;
219   if (Asm->needsRelocationsForDwarfStringPool())
220     Value = new (DIEValueAllocator) DIELabel(Symb);
221   else {
222     MCSymbol *StringPool = DU->getStringPoolSym();
223     Value = new (DIEValueAllocator) DIEDelta(Symb, StringPool);
224   }
225   Die->addValue(Attribute, dwarf::DW_FORM_strp, Value);
226 }
227
228 /// addExpr - Add a Dwarf expression attribute data and value.
229 ///
230 void CompileUnit::addExpr(DIEBlock *Die, dwarf::Form Form, const MCExpr *Expr) {
231   DIEValue *Value = new (DIEValueAllocator) DIEExpr(Expr);
232   Die->addValue((dwarf::Attribute)0, Form, Value);
233 }
234
235 /// addLabel - Add a Dwarf label attribute data and value.
236 ///
237 void CompileUnit::addLabel(DIE *Die, dwarf::Attribute Attribute,
238                            dwarf::Form Form, const MCSymbol *Label) {
239   DIEValue *Value = new (DIEValueAllocator) DIELabel(Label);
240   Die->addValue(Attribute, Form, Value);
241 }
242
243 void CompileUnit::addLabel(DIEBlock *Die, dwarf::Form Form,
244                            const MCSymbol *Label) {
245   addLabel(Die, (dwarf::Attribute)0, Form, Label);
246 }
247
248 /// addLabelAddress - Add a dwarf label attribute data and value using
249 /// DW_FORM_addr or DW_FORM_GNU_addr_index.
250 ///
251 void CompileUnit::addLabelAddress(DIE *Die, dwarf::Attribute Attribute,
252                                   MCSymbol *Label) {
253   if (Label)
254     DD->addArangeLabel(SymbolCU(this, Label));
255
256   if (!DD->useSplitDwarf()) {
257     if (Label != NULL) {
258       DIEValue *Value = new (DIEValueAllocator) DIELabel(Label);
259       Die->addValue(Attribute, dwarf::DW_FORM_addr, Value);
260     } else {
261       DIEValue *Value = new (DIEValueAllocator) DIEInteger(0);
262       Die->addValue(Attribute, dwarf::DW_FORM_addr, Value);
263     }
264   } else {
265     unsigned idx = DU->getAddrPoolIndex(Label);
266     DIEValue *Value = new (DIEValueAllocator) DIEInteger(idx);
267     Die->addValue(Attribute, dwarf::DW_FORM_GNU_addr_index, Value);
268   }
269 }
270
271 /// addOpAddress - Add a dwarf op address data and value using the
272 /// form given and an op of either DW_FORM_addr or DW_FORM_GNU_addr_index.
273 ///
274 void CompileUnit::addOpAddress(DIEBlock *Die, const MCSymbol *Sym) {
275   DD->addArangeLabel(SymbolCU(this, Sym));
276   if (!DD->useSplitDwarf()) {
277     addUInt(Die, dwarf::DW_FORM_data1, dwarf::DW_OP_addr);
278     addLabel(Die, dwarf::DW_FORM_udata, Sym);
279   } else {
280     addUInt(Die, dwarf::DW_FORM_data1, dwarf::DW_OP_GNU_addr_index);
281     addUInt(Die, dwarf::DW_FORM_GNU_addr_index, DU->getAddrPoolIndex(Sym));
282   }
283 }
284
285 /// addDelta - Add a label delta attribute data and value.
286 ///
287 void CompileUnit::addDelta(DIE *Die, dwarf::Attribute Attribute,
288                            dwarf::Form Form, const MCSymbol *Hi,
289                            const MCSymbol *Lo) {
290   DIEValue *Value = new (DIEValueAllocator) DIEDelta(Hi, Lo);
291   Die->addValue(Attribute, Form, Value);
292 }
293
294 /// addDIEEntry - Add a DIE attribute data and value.
295 ///
296 void CompileUnit::addDIEEntry(DIE *Die, dwarf::Attribute Attribute,
297                               DIE *Entry) {
298   addDIEEntry(Die, Attribute, createDIEEntry(Entry));
299 }
300
301 void CompileUnit::addDIEEntry(DIE *Die, dwarf::Attribute Attribute,
302                               DIEEntry *Entry) {
303   const DIE *DieCU = Die->getUnitOrNull();
304   const DIE *EntryCU = Entry->getEntry()->getUnitOrNull();
305   if (!DieCU)
306     // We assume that Die belongs to this CU, if it is not linked to any CU yet.
307     DieCU = getCUDie();
308   if (!EntryCU)
309     EntryCU = getCUDie();
310   Die->addValue(Attribute, EntryCU == DieCU ? dwarf::DW_FORM_ref4
311                                             : dwarf::DW_FORM_ref_addr,
312                 Entry);
313 }
314
315 /// Create a DIE with the given Tag, add the DIE to its parent, and
316 /// call insertDIE if MD is not null.
317 DIE *CompileUnit::createAndAddDIE(unsigned Tag, DIE &Parent, DIDescriptor N) {
318   DIE *Die = new DIE(Tag);
319   Parent.addChild(Die);
320   if (N)
321     insertDIE(N, Die);
322   return Die;
323 }
324
325 /// addBlock - Add block data.
326 ///
327 void CompileUnit::addBlock(DIE *Die, dwarf::Attribute Attribute,
328                            DIEBlock *Block) {
329   Block->ComputeSize(Asm);
330   DIEBlocks.push_back(Block); // Memoize so we can call the destructor later on.
331   Die->addValue(Attribute, Block->BestForm(), Block);
332 }
333
334 /// addSourceLine - Add location information to specified debug information
335 /// entry.
336 void CompileUnit::addSourceLine(DIE *Die, DIVariable V) {
337   // Verify variable.
338   if (!V.isVariable())
339     return;
340
341   unsigned Line = V.getLineNumber();
342   if (Line == 0)
343     return;
344   unsigned FileID =
345       DD->getOrCreateSourceID(V.getContext().getFilename(),
346                               V.getContext().getDirectory(), getUniqueID());
347   assert(FileID && "Invalid file id");
348   addUInt(Die, dwarf::DW_AT_decl_file, None, FileID);
349   addUInt(Die, dwarf::DW_AT_decl_line, None, Line);
350 }
351
352 /// addSourceLine - Add location information to specified debug information
353 /// entry.
354 void CompileUnit::addSourceLine(DIE *Die, DIGlobalVariable G) {
355   // Verify global variable.
356   if (!G.isGlobalVariable())
357     return;
358
359   unsigned Line = G.getLineNumber();
360   if (Line == 0)
361     return;
362   unsigned FileID =
363       DD->getOrCreateSourceID(G.getFilename(), G.getDirectory(), getUniqueID());
364   assert(FileID && "Invalid file id");
365   addUInt(Die, dwarf::DW_AT_decl_file, None, FileID);
366   addUInt(Die, dwarf::DW_AT_decl_line, None, Line);
367 }
368
369 /// addSourceLine - Add location information to specified debug information
370 /// entry.
371 void CompileUnit::addSourceLine(DIE *Die, DISubprogram SP) {
372   // Verify subprogram.
373   if (!SP.isSubprogram())
374     return;
375
376   // If the line number is 0, don't add it.
377   unsigned Line = SP.getLineNumber();
378   if (Line == 0)
379     return;
380
381   unsigned FileID = DD->getOrCreateSourceID(SP.getFilename(), SP.getDirectory(),
382                                             getUniqueID());
383   assert(FileID && "Invalid file id");
384   addUInt(Die, dwarf::DW_AT_decl_file, None, FileID);
385   addUInt(Die, dwarf::DW_AT_decl_line, None, Line);
386 }
387
388 /// addSourceLine - Add location information to specified debug information
389 /// entry.
390 void CompileUnit::addSourceLine(DIE *Die, DIType Ty) {
391   // Verify type.
392   if (!Ty.isType())
393     return;
394
395   unsigned Line = Ty.getLineNumber();
396   if (Line == 0)
397     return;
398   unsigned FileID = DD->getOrCreateSourceID(Ty.getFilename(), Ty.getDirectory(),
399                                             getUniqueID());
400   assert(FileID && "Invalid file id");
401   addUInt(Die, dwarf::DW_AT_decl_file, None, FileID);
402   addUInt(Die, dwarf::DW_AT_decl_line, None, Line);
403 }
404
405 /// addSourceLine - Add location information to specified debug information
406 /// entry.
407 void CompileUnit::addSourceLine(DIE *Die, DIObjCProperty Ty) {
408   // Verify type.
409   if (!Ty.isObjCProperty())
410     return;
411
412   unsigned Line = Ty.getLineNumber();
413   if (Line == 0)
414     return;
415   DIFile File = Ty.getFile();
416   unsigned FileID = DD->getOrCreateSourceID(File.getFilename(),
417                                             File.getDirectory(), getUniqueID());
418   assert(FileID && "Invalid file id");
419   addUInt(Die, dwarf::DW_AT_decl_file, None, FileID);
420   addUInt(Die, dwarf::DW_AT_decl_line, None, Line);
421 }
422
423 /// addSourceLine - Add location information to specified debug information
424 /// entry.
425 void CompileUnit::addSourceLine(DIE *Die, DINameSpace NS) {
426   // Verify namespace.
427   if (!NS.Verify())
428     return;
429
430   unsigned Line = NS.getLineNumber();
431   if (Line == 0)
432     return;
433   StringRef FN = NS.getFilename();
434
435   unsigned FileID =
436       DD->getOrCreateSourceID(FN, NS.getDirectory(), getUniqueID());
437   assert(FileID && "Invalid file id");
438   addUInt(Die, dwarf::DW_AT_decl_file, None, FileID);
439   addUInt(Die, dwarf::DW_AT_decl_line, None, Line);
440 }
441
442 /// addVariableAddress - Add DW_AT_location attribute for a
443 /// DbgVariable based on provided MachineLocation.
444 void CompileUnit::addVariableAddress(const DbgVariable &DV, DIE *Die,
445                                      MachineLocation Location) {
446   if (DV.variableHasComplexAddress())
447     addComplexAddress(DV, Die, dwarf::DW_AT_location, Location);
448   else if (DV.isBlockByrefVariable())
449     addBlockByrefAddress(DV, Die, dwarf::DW_AT_location, Location);
450   else
451     addAddress(Die, dwarf::DW_AT_location, Location,
452                DV.getVariable().isIndirect());
453 }
454
455 /// addRegisterOp - Add register operand.
456 void CompileUnit::addRegisterOp(DIEBlock *TheDie, unsigned Reg) {
457   const TargetRegisterInfo *RI = Asm->TM.getRegisterInfo();
458   unsigned DWReg = RI->getDwarfRegNum(Reg, false);
459   if (DWReg < 32)
460     addUInt(TheDie, dwarf::DW_FORM_data1, dwarf::DW_OP_reg0 + DWReg);
461   else {
462     addUInt(TheDie, dwarf::DW_FORM_data1, dwarf::DW_OP_regx);
463     addUInt(TheDie, dwarf::DW_FORM_udata, DWReg);
464   }
465 }
466
467 /// addRegisterOffset - Add register offset.
468 void CompileUnit::addRegisterOffset(DIEBlock *TheDie, unsigned Reg,
469                                     int64_t Offset) {
470   const TargetRegisterInfo *RI = Asm->TM.getRegisterInfo();
471   unsigned DWReg = RI->getDwarfRegNum(Reg, false);
472   const TargetRegisterInfo *TRI = Asm->TM.getRegisterInfo();
473   if (Reg == TRI->getFrameRegister(*Asm->MF))
474     // If variable offset is based in frame register then use fbreg.
475     addUInt(TheDie, dwarf::DW_FORM_data1, dwarf::DW_OP_fbreg);
476   else if (DWReg < 32)
477     addUInt(TheDie, dwarf::DW_FORM_data1, dwarf::DW_OP_breg0 + DWReg);
478   else {
479     addUInt(TheDie, dwarf::DW_FORM_data1, dwarf::DW_OP_bregx);
480     addUInt(TheDie, dwarf::DW_FORM_udata, DWReg);
481   }
482   addSInt(TheDie, dwarf::DW_FORM_sdata, Offset);
483 }
484
485 /// addAddress - Add an address attribute to a die based on the location
486 /// provided.
487 void CompileUnit::addAddress(DIE *Die, dwarf::Attribute Attribute,
488                              const MachineLocation &Location, bool Indirect) {
489   DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
490
491   if (Location.isReg() && !Indirect)
492     addRegisterOp(Block, Location.getReg());
493   else {
494     addRegisterOffset(Block, Location.getReg(), Location.getOffset());
495     if (Indirect && !Location.isReg()) {
496       addUInt(Block, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
497     }
498   }
499
500   // Now attach the location information to the DIE.
501   addBlock(Die, Attribute, Block);
502 }
503
504 /// addComplexAddress - Start with the address based on the location provided,
505 /// and generate the DWARF information necessary to find the actual variable
506 /// given the extra address information encoded in the DIVariable, starting from
507 /// the starting location.  Add the DWARF information to the die.
508 ///
509 void CompileUnit::addComplexAddress(const DbgVariable &DV, DIE *Die,
510                                     dwarf::Attribute Attribute,
511                                     const MachineLocation &Location) {
512   DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
513   unsigned N = DV.getNumAddrElements();
514   unsigned i = 0;
515   if (Location.isReg()) {
516     if (N >= 2 && DV.getAddrElement(0) == DIBuilder::OpPlus) {
517       // If first address element is OpPlus then emit
518       // DW_OP_breg + Offset instead of DW_OP_reg + Offset.
519       addRegisterOffset(Block, Location.getReg(), DV.getAddrElement(1));
520       i = 2;
521     } else
522       addRegisterOp(Block, Location.getReg());
523   } else
524     addRegisterOffset(Block, Location.getReg(), Location.getOffset());
525
526   for (; i < N; ++i) {
527     uint64_t Element = DV.getAddrElement(i);
528     if (Element == DIBuilder::OpPlus) {
529       addUInt(Block, dwarf::DW_FORM_data1, dwarf::DW_OP_plus_uconst);
530       addUInt(Block, dwarf::DW_FORM_udata, DV.getAddrElement(++i));
531     } else if (Element == DIBuilder::OpDeref) {
532       if (!Location.isReg())
533         addUInt(Block, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
534     } else
535       llvm_unreachable("unknown DIBuilder Opcode");
536   }
537
538   // Now attach the location information to the DIE.
539   addBlock(Die, Attribute, Block);
540 }
541
542 /* Byref variables, in Blocks, are declared by the programmer as "SomeType
543    VarName;", but the compiler creates a __Block_byref_x_VarName struct, and
544    gives the variable VarName either the struct, or a pointer to the struct, as
545    its type.  This is necessary for various behind-the-scenes things the
546    compiler needs to do with by-reference variables in Blocks.
547
548    However, as far as the original *programmer* is concerned, the variable
549    should still have type 'SomeType', as originally declared.
550
551    The function getBlockByrefType dives into the __Block_byref_x_VarName
552    struct to find the original type of the variable, which is then assigned to
553    the variable's Debug Information Entry as its real type.  So far, so good.
554    However now the debugger will expect the variable VarName to have the type
555    SomeType.  So we need the location attribute for the variable to be an
556    expression that explains to the debugger how to navigate through the
557    pointers and struct to find the actual variable of type SomeType.
558
559    The following function does just that.  We start by getting
560    the "normal" location for the variable. This will be the location
561    of either the struct __Block_byref_x_VarName or the pointer to the
562    struct __Block_byref_x_VarName.
563
564    The struct will look something like:
565
566    struct __Block_byref_x_VarName {
567      ... <various fields>
568      struct __Block_byref_x_VarName *forwarding;
569      ... <various other fields>
570      SomeType VarName;
571      ... <maybe more fields>
572    };
573
574    If we are given the struct directly (as our starting point) we
575    need to tell the debugger to:
576
577    1).  Add the offset of the forwarding field.
578
579    2).  Follow that pointer to get the real __Block_byref_x_VarName
580    struct to use (the real one may have been copied onto the heap).
581
582    3).  Add the offset for the field VarName, to find the actual variable.
583
584    If we started with a pointer to the struct, then we need to
585    dereference that pointer first, before the other steps.
586    Translating this into DWARF ops, we will need to append the following
587    to the current location description for the variable:
588
589    DW_OP_deref                    -- optional, if we start with a pointer
590    DW_OP_plus_uconst <forward_fld_offset>
591    DW_OP_deref
592    DW_OP_plus_uconst <varName_fld_offset>
593
594    That is what this function does.  */
595
596 /// addBlockByrefAddress - Start with the address based on the location
597 /// provided, and generate the DWARF information necessary to find the
598 /// actual Block variable (navigating the Block struct) based on the
599 /// starting location.  Add the DWARF information to the die.  For
600 /// more information, read large comment just above here.
601 ///
602 void CompileUnit::addBlockByrefAddress(const DbgVariable &DV, DIE *Die,
603                                        dwarf::Attribute Attribute,
604                                        const MachineLocation &Location) {
605   DIType Ty = DV.getType();
606   DIType TmpTy = Ty;
607   uint16_t Tag = Ty.getTag();
608   bool isPointer = false;
609
610   StringRef varName = DV.getName();
611
612   if (Tag == dwarf::DW_TAG_pointer_type) {
613     DIDerivedType DTy(Ty);
614     TmpTy = resolve(DTy.getTypeDerivedFrom());
615     isPointer = true;
616   }
617
618   DICompositeType blockStruct(TmpTy);
619
620   // Find the __forwarding field and the variable field in the __Block_byref
621   // struct.
622   DIArray Fields = blockStruct.getTypeArray();
623   DIDerivedType varField;
624   DIDerivedType forwardingField;
625
626   for (unsigned i = 0, N = Fields.getNumElements(); i < N; ++i) {
627     DIDerivedType DT(Fields.getElement(i));
628     StringRef fieldName = DT.getName();
629     if (fieldName == "__forwarding")
630       forwardingField = DT;
631     else if (fieldName == varName)
632       varField = DT;
633   }
634
635   // Get the offsets for the forwarding field and the variable field.
636   unsigned forwardingFieldOffset = forwardingField.getOffsetInBits() >> 3;
637   unsigned varFieldOffset = varField.getOffsetInBits() >> 2;
638
639   // Decode the original location, and use that as the start of the byref
640   // variable's location.
641   DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
642
643   if (Location.isReg())
644     addRegisterOp(Block, Location.getReg());
645   else
646     addRegisterOffset(Block, Location.getReg(), Location.getOffset());
647
648   // If we started with a pointer to the __Block_byref... struct, then
649   // the first thing we need to do is dereference the pointer (DW_OP_deref).
650   if (isPointer)
651     addUInt(Block, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
652
653   // Next add the offset for the '__forwarding' field:
654   // DW_OP_plus_uconst ForwardingFieldOffset.  Note there's no point in
655   // adding the offset if it's 0.
656   if (forwardingFieldOffset > 0) {
657     addUInt(Block, dwarf::DW_FORM_data1, dwarf::DW_OP_plus_uconst);
658     addUInt(Block, dwarf::DW_FORM_udata, forwardingFieldOffset);
659   }
660
661   // Now dereference the __forwarding field to get to the real __Block_byref
662   // struct:  DW_OP_deref.
663   addUInt(Block, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
664
665   // Now that we've got the real __Block_byref... struct, add the offset
666   // for the variable's field to get to the location of the actual variable:
667   // DW_OP_plus_uconst varFieldOffset.  Again, don't add if it's 0.
668   if (varFieldOffset > 0) {
669     addUInt(Block, dwarf::DW_FORM_data1, dwarf::DW_OP_plus_uconst);
670     addUInt(Block, dwarf::DW_FORM_udata, varFieldOffset);
671   }
672
673   // Now attach the location information to the DIE.
674   addBlock(Die, Attribute, Block);
675 }
676
677 /// isTypeSigned - Return true if the type is signed.
678 static bool isTypeSigned(DwarfDebug *DD, DIType Ty, int *SizeInBits) {
679   if (Ty.isDerivedType())
680     return isTypeSigned(DD, DD->resolve(DIDerivedType(Ty).getTypeDerivedFrom()),
681                         SizeInBits);
682   if (Ty.isBasicType())
683     if (DIBasicType(Ty).getEncoding() == dwarf::DW_ATE_signed ||
684         DIBasicType(Ty).getEncoding() == dwarf::DW_ATE_signed_char) {
685       *SizeInBits = Ty.getSizeInBits();
686       return true;
687     }
688   return false;
689 }
690
691 /// Return true if type encoding is unsigned.
692 static bool isUnsignedDIType(DwarfDebug *DD, DIType Ty) {
693   DIDerivedType DTy(Ty);
694   if (DTy.isDerivedType())
695     return isUnsignedDIType(DD, DD->resolve(DTy.getTypeDerivedFrom()));
696
697   DIBasicType BTy(Ty);
698   if (BTy.isBasicType()) {
699     unsigned Encoding = BTy.getEncoding();
700     if (Encoding == dwarf::DW_ATE_unsigned ||
701         Encoding == dwarf::DW_ATE_unsigned_char ||
702         Encoding == dwarf::DW_ATE_boolean)
703       return true;
704   }
705   return false;
706 }
707
708 /// If this type is derived from a base type then return base type size.
709 static uint64_t getBaseTypeSize(DwarfDebug *DD, DIDerivedType Ty) {
710   unsigned Tag = Ty.getTag();
711
712   if (Tag != dwarf::DW_TAG_member && Tag != dwarf::DW_TAG_typedef &&
713       Tag != dwarf::DW_TAG_const_type && Tag != dwarf::DW_TAG_volatile_type &&
714       Tag != dwarf::DW_TAG_restrict_type)
715     return Ty.getSizeInBits();
716
717   DIType BaseType = DD->resolve(Ty.getTypeDerivedFrom());
718
719   // If this type is not derived from any type then take conservative approach.
720   if (!BaseType.isValid())
721     return Ty.getSizeInBits();
722
723   // If this is a derived type, go ahead and get the base type, unless it's a
724   // reference then it's just the size of the field. Pointer types have no need
725   // of this since they're a different type of qualification on the type.
726   if (BaseType.getTag() == dwarf::DW_TAG_reference_type ||
727       BaseType.getTag() == dwarf::DW_TAG_rvalue_reference_type)
728     return Ty.getSizeInBits();
729
730   if (BaseType.isDerivedType())
731     return getBaseTypeSize(DD, DIDerivedType(BaseType));
732
733   return BaseType.getSizeInBits();
734 }
735
736 /// addConstantValue - Add constant value entry in variable DIE.
737 void CompileUnit::addConstantValue(DIE *Die, const MachineOperand &MO,
738                                    DIType Ty) {
739   // FIXME: This is a bit conservative/simple - it emits negative values at
740   // their maximum bit width which is a bit unfortunate (& doesn't prefer
741   // udata/sdata over dataN as suggested by the DWARF spec)
742   assert(MO.isImm() && "Invalid machine operand!");
743   int SizeInBits = -1;
744   bool SignedConstant = isTypeSigned(DD, Ty, &SizeInBits);
745   dwarf::Form Form;
746
747   // If we're a signed constant definitely use sdata.
748   if (SignedConstant) {
749     addSInt(Die, dwarf::DW_AT_const_value, dwarf::DW_FORM_sdata, MO.getImm());
750     return;
751   }
752
753   // Else use data for now unless it's larger than we can deal with.
754   switch (SizeInBits) {
755   case 8:
756     Form = dwarf::DW_FORM_data1;
757     break;
758   case 16:
759     Form = dwarf::DW_FORM_data2;
760     break;
761   case 32:
762     Form = dwarf::DW_FORM_data4;
763     break;
764   case 64:
765     Form = dwarf::DW_FORM_data8;
766     break;
767   default:
768     Form = dwarf::DW_FORM_udata;
769     addUInt(Die, dwarf::DW_AT_const_value, Form, MO.getImm());
770     return;
771   }
772   addUInt(Die, dwarf::DW_AT_const_value, Form, MO.getImm());
773 }
774
775 /// addConstantFPValue - Add constant value entry in variable DIE.
776 void CompileUnit::addConstantFPValue(DIE *Die, const MachineOperand &MO) {
777   assert(MO.isFPImm() && "Invalid machine operand!");
778   DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
779   APFloat FPImm = MO.getFPImm()->getValueAPF();
780
781   // Get the raw data form of the floating point.
782   const APInt FltVal = FPImm.bitcastToAPInt();
783   const char *FltPtr = (const char *)FltVal.getRawData();
784
785   int NumBytes = FltVal.getBitWidth() / 8; // 8 bits per byte.
786   bool LittleEndian = Asm->getDataLayout().isLittleEndian();
787   int Incr = (LittleEndian ? 1 : -1);
788   int Start = (LittleEndian ? 0 : NumBytes - 1);
789   int Stop = (LittleEndian ? NumBytes : -1);
790
791   // Output the constant to DWARF one byte at a time.
792   for (; Start != Stop; Start += Incr)
793     addUInt(Block, dwarf::DW_FORM_data1, (unsigned char)0xFF & FltPtr[Start]);
794
795   addBlock(Die, dwarf::DW_AT_const_value, Block);
796 }
797
798 /// addConstantFPValue - Add constant value entry in variable DIE.
799 void CompileUnit::addConstantFPValue(DIE *Die, const ConstantFP *CFP) {
800   // Pass this down to addConstantValue as an unsigned bag of bits.
801   addConstantValue(Die, CFP->getValueAPF().bitcastToAPInt(), true);
802 }
803
804 /// addConstantValue - Add constant value entry in variable DIE.
805 void CompileUnit::addConstantValue(DIE *Die, const ConstantInt *CI,
806                                    bool Unsigned) {
807   addConstantValue(Die, CI->getValue(), Unsigned);
808 }
809
810 // addConstantValue - Add constant value entry in variable DIE.
811 void CompileUnit::addConstantValue(DIE *Die, const APInt &Val, bool Unsigned) {
812   unsigned CIBitWidth = Val.getBitWidth();
813   if (CIBitWidth <= 64) {
814     // If we're a signed constant definitely use sdata.
815     if (!Unsigned) {
816       addSInt(Die, dwarf::DW_AT_const_value, dwarf::DW_FORM_sdata,
817               Val.getSExtValue());
818       return;
819     }
820
821     // Else use data for now unless it's larger than we can deal with.
822     dwarf::Form Form;
823     switch (CIBitWidth) {
824     case 8:
825       Form = dwarf::DW_FORM_data1;
826       break;
827     case 16:
828       Form = dwarf::DW_FORM_data2;
829       break;
830     case 32:
831       Form = dwarf::DW_FORM_data4;
832       break;
833     case 64:
834       Form = dwarf::DW_FORM_data8;
835       break;
836     default:
837       addUInt(Die, dwarf::DW_AT_const_value, dwarf::DW_FORM_udata,
838               Val.getZExtValue());
839       return;
840     }
841     addUInt(Die, dwarf::DW_AT_const_value, Form, Val.getZExtValue());
842     return;
843   }
844
845   DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
846
847   // Get the raw data form of the large APInt.
848   const uint64_t *Ptr64 = Val.getRawData();
849
850   int NumBytes = Val.getBitWidth() / 8; // 8 bits per byte.
851   bool LittleEndian = Asm->getDataLayout().isLittleEndian();
852
853   // Output the constant to DWARF one byte at a time.
854   for (int i = 0; i < NumBytes; i++) {
855     uint8_t c;
856     if (LittleEndian)
857       c = Ptr64[i / 8] >> (8 * (i & 7));
858     else
859       c = Ptr64[(NumBytes - 1 - i) / 8] >> (8 * ((NumBytes - 1 - i) & 7));
860     addUInt(Block, dwarf::DW_FORM_data1, c);
861   }
862
863   addBlock(Die, dwarf::DW_AT_const_value, Block);
864 }
865
866 /// addTemplateParams - Add template parameters into buffer.
867 void CompileUnit::addTemplateParams(DIE &Buffer, DIArray TParams) {
868   // Add template parameters.
869   for (unsigned i = 0, e = TParams.getNumElements(); i != e; ++i) {
870     DIDescriptor Element = TParams.getElement(i);
871     if (Element.isTemplateTypeParameter())
872       constructTemplateTypeParameterDIE(Buffer,
873                                         DITemplateTypeParameter(Element));
874     else if (Element.isTemplateValueParameter())
875       constructTemplateValueParameterDIE(Buffer,
876                                          DITemplateValueParameter(Element));
877   }
878 }
879
880 /// getOrCreateContextDIE - Get context owner's DIE.
881 DIE *CompileUnit::getOrCreateContextDIE(DIScope Context) {
882   if (!Context || Context.isFile())
883     return getCUDie();
884   if (Context.isType())
885     return getOrCreateTypeDIE(DIType(Context));
886   if (Context.isNameSpace())
887     return getOrCreateNameSpace(DINameSpace(Context));
888   if (Context.isSubprogram())
889     return getOrCreateSubprogramDIE(DISubprogram(Context));
890   return getDIE(Context);
891 }
892
893 DIE *CompileUnit::createTypeDIE(DICompositeType Ty) {
894   DIE *ContextDIE = getOrCreateContextDIE(resolve(Ty.getContext()));
895
896   DIE *TyDIE = getDIE(Ty);
897   if (TyDIE)
898     return TyDIE;
899
900   // Create new type.
901   TyDIE = createAndAddDIE(Ty.getTag(), *ContextDIE, Ty);
902
903   constructTypeDIEImpl(*TyDIE, Ty);
904
905   updateAcceleratorTables(Ty, TyDIE);
906   return TyDIE;
907 }
908
909 /// getOrCreateTypeDIE - Find existing DIE or create new DIE for the
910 /// given DIType.
911 DIE *CompileUnit::getOrCreateTypeDIE(const MDNode *TyNode) {
912   if (!TyNode)
913     return NULL;
914
915   DIType Ty(TyNode);
916   assert(Ty.isType());
917
918   // Construct the context before querying for the existence of the DIE in case
919   // such construction creates the DIE.
920   DIE *ContextDIE = getOrCreateContextDIE(resolve(Ty.getContext()));
921   assert(ContextDIE);
922
923   DIE *TyDIE = getDIE(Ty);
924   if (TyDIE)
925     return TyDIE;
926
927   // Create new type.
928   TyDIE = createAndAddDIE(Ty.getTag(), *ContextDIE, Ty);
929
930   if (Ty.isBasicType())
931     constructTypeDIE(*TyDIE, DIBasicType(Ty));
932   else if (Ty.isCompositeType())
933     constructTypeDIE(*TyDIE, DICompositeType(Ty));
934   else {
935     assert(Ty.isDerivedType() && "Unknown kind of DIType");
936     constructTypeDIE(*TyDIE, DIDerivedType(Ty));
937   }
938
939   updateAcceleratorTables(Ty, TyDIE);
940
941   return TyDIE;
942 }
943
944 void CompileUnit::updateAcceleratorTables(DIType Ty, const DIE *TyDIE) {
945   if (!Ty.getName().empty() && !Ty.isForwardDecl()) {
946     bool IsImplementation = 0;
947     if (Ty.isCompositeType()) {
948       DICompositeType CT(Ty);
949       // A runtime language of 0 actually means C/C++ and that any
950       // non-negative value is some version of Objective-C/C++.
951       IsImplementation = (CT.getRunTimeLang() == 0) || CT.isObjcClassComplete();
952     }
953     unsigned Flags = IsImplementation ? dwarf::DW_FLAG_type_implementation : 0;
954     addAccelType(Ty.getName(), std::make_pair(TyDIE, Flags));
955   }
956 }
957
958 /// addType - Add a new type attribute to the specified entity.
959 void CompileUnit::addType(DIE *Entity, DIType Ty, dwarf::Attribute Attribute) {
960   assert(Ty && "Trying to add a type that doesn't exist?");
961
962   // Check for pre-existence.
963   DIEEntry *Entry = getDIEEntry(Ty);
964   // If it exists then use the existing value.
965   if (Entry) {
966     addDIEEntry(Entity, Attribute, Entry);
967     return;
968   }
969
970   // Construct type.
971   DIE *Buffer = getOrCreateTypeDIE(Ty);
972
973   // Set up proxy.
974   Entry = createDIEEntry(Buffer);
975   insertDIEEntry(Ty, Entry);
976   addDIEEntry(Entity, Attribute, Entry);
977
978   // If this is a complete composite type then include it in the
979   // list of global types.
980   addGlobalType(Ty);
981 }
982
983 // Accelerator table mutators - add each name along with its companion
984 // DIE to the proper table while ensuring that the name that we're going
985 // to reference is in the string table. We do this since the names we
986 // add may not only be identical to the names in the DIE.
987 void CompileUnit::addAccelName(StringRef Name, const DIE *Die) {
988   DU->getStringPoolEntry(Name);
989   std::vector<const DIE *> &DIEs = AccelNames[Name];
990   DIEs.push_back(Die);
991 }
992
993 void CompileUnit::addAccelObjC(StringRef Name, const DIE *Die) {
994   DU->getStringPoolEntry(Name);
995   std::vector<const DIE *> &DIEs = AccelObjC[Name];
996   DIEs.push_back(Die);
997 }
998
999 void CompileUnit::addAccelNamespace(StringRef Name, const DIE *Die) {
1000   DU->getStringPoolEntry(Name);
1001   std::vector<const DIE *> &DIEs = AccelNamespace[Name];
1002   DIEs.push_back(Die);
1003 }
1004
1005 void CompileUnit::addAccelType(StringRef Name,
1006                                std::pair<const DIE *, unsigned> Die) {
1007   DU->getStringPoolEntry(Name);
1008   std::vector<std::pair<const DIE *, unsigned> > &DIEs = AccelTypes[Name];
1009   DIEs.push_back(Die);
1010 }
1011
1012 /// addGlobalName - Add a new global name to the compile unit.
1013 void CompileUnit::addGlobalName(StringRef Name, DIE *Die, DIScope Context) {
1014   std::string FullName = getParentContextString(Context) + Name.str();
1015   GlobalNames[FullName] = Die;
1016 }
1017
1018 /// addGlobalType - Add a new global type to the compile unit.
1019 ///
1020 void CompileUnit::addGlobalType(DIType Ty) {
1021   DIScope Context = resolve(Ty.getContext());
1022   if (!Ty.getName().empty() && !Ty.isForwardDecl() &&
1023       (!Context || Context.isCompileUnit() || Context.isFile() ||
1024        Context.isNameSpace()))
1025     if (DIEEntry *Entry = getDIEEntry(Ty)) {
1026       std::string FullName =
1027           getParentContextString(Context) + Ty.getName().str();
1028       GlobalTypes[FullName] = Entry->getEntry();
1029     }
1030 }
1031
1032 /// getParentContextString - Walks the metadata parent chain in a language
1033 /// specific manner (using the compile unit language) and returns
1034 /// it as a string. This is done at the metadata level because DIEs may
1035 /// not currently have been added to the parent context and walking the
1036 /// DIEs looking for names is more expensive than walking the metadata.
1037 std::string CompileUnit::getParentContextString(DIScope Context) const {
1038   if (!Context)
1039     return "";
1040
1041   // FIXME: Decide whether to implement this for non-C++ languages.
1042   if (getLanguage() != dwarf::DW_LANG_C_plus_plus)
1043     return "";
1044
1045   std::string CS;
1046   SmallVector<DIScope, 1> Parents;
1047   while (!Context.isCompileUnit()) {
1048     Parents.push_back(Context);
1049     if (Context.getContext())
1050       Context = resolve(Context.getContext());
1051     else
1052       // Structure, etc types will have a NULL context if they're at the top
1053       // level.
1054       break;
1055   }
1056
1057   // Reverse iterate over our list to go from the outermost construct to the
1058   // innermost.
1059   for (SmallVectorImpl<DIScope>::reverse_iterator I = Parents.rbegin(),
1060                                                   E = Parents.rend();
1061        I != E; ++I) {
1062     DIScope Ctx = *I;
1063     StringRef Name = Ctx.getName();
1064     if (!Name.empty()) {
1065       CS += Name;
1066       CS += "::";
1067     }
1068   }
1069   return CS;
1070 }
1071
1072 /// addPubTypes - Add subprogram argument types for pubtypes section.
1073 void CompileUnit::addPubTypes(DISubprogram SP) {
1074   DICompositeType SPTy = SP.getType();
1075   uint16_t SPTag = SPTy.getTag();
1076   if (SPTag != dwarf::DW_TAG_subroutine_type)
1077     return;
1078
1079   DIArray Args = SPTy.getTypeArray();
1080   for (unsigned i = 0, e = Args.getNumElements(); i != e; ++i) {
1081     DIType ATy(Args.getElement(i));
1082     if (!ATy.isType())
1083       continue;
1084     addGlobalType(ATy);
1085   }
1086 }
1087
1088 /// constructTypeDIE - Construct basic type die from DIBasicType.
1089 void CompileUnit::constructTypeDIE(DIE &Buffer, DIBasicType BTy) {
1090   // Get core information.
1091   StringRef Name = BTy.getName();
1092   // Add name if not anonymous or intermediate type.
1093   if (!Name.empty())
1094     addString(&Buffer, dwarf::DW_AT_name, Name);
1095
1096   // An unspecified type only has a name attribute.
1097   if (BTy.getTag() == dwarf::DW_TAG_unspecified_type)
1098     return;
1099
1100   addUInt(&Buffer, dwarf::DW_AT_encoding, dwarf::DW_FORM_data1,
1101           BTy.getEncoding());
1102
1103   uint64_t Size = BTy.getSizeInBits() >> 3;
1104   addUInt(&Buffer, dwarf::DW_AT_byte_size, None, Size);
1105 }
1106
1107 /// constructTypeDIE - Construct derived type die from DIDerivedType.
1108 void CompileUnit::constructTypeDIE(DIE &Buffer, DIDerivedType DTy) {
1109   // Get core information.
1110   StringRef Name = DTy.getName();
1111   uint64_t Size = DTy.getSizeInBits() >> 3;
1112   uint16_t Tag = Buffer.getTag();
1113
1114   // Map to main type, void will not have a type.
1115   DIType FromTy = resolve(DTy.getTypeDerivedFrom());
1116   if (FromTy)
1117     addType(&Buffer, FromTy);
1118
1119   // Add name if not anonymous or intermediate type.
1120   if (!Name.empty())
1121     addString(&Buffer, dwarf::DW_AT_name, Name);
1122
1123   // Add size if non-zero (derived types might be zero-sized.)
1124   if (Size && Tag != dwarf::DW_TAG_pointer_type)
1125     addUInt(&Buffer, dwarf::DW_AT_byte_size, None, Size);
1126
1127   if (Tag == dwarf::DW_TAG_ptr_to_member_type)
1128     addDIEEntry(&Buffer, dwarf::DW_AT_containing_type,
1129                 getOrCreateTypeDIE(resolve(DTy.getClassType())));
1130   // Add source line info if available and TyDesc is not a forward declaration.
1131   if (!DTy.isForwardDecl())
1132     addSourceLine(&Buffer, DTy);
1133 }
1134
1135 /// Return true if the type is appropriately scoped to be contained inside
1136 /// its own type unit.
1137 static bool isTypeUnitScoped(DIType Ty, const DwarfDebug *DD) {
1138   DIScope Parent = DD->resolve(Ty.getContext());
1139   while (Parent) {
1140     // Don't generate a hash for anything scoped inside a function.
1141     if (Parent.isSubprogram())
1142       return false;
1143     Parent = DD->resolve(Parent.getContext());
1144   }
1145   return true;
1146 }
1147
1148 /// Return true if the type should be split out into a type unit.
1149 static bool shouldCreateTypeUnit(DICompositeType CTy, const DwarfDebug *DD) {
1150   if (!GenerateTypeUnits)
1151     return false;
1152
1153   uint16_t Tag = CTy.getTag();
1154
1155   switch (Tag) {
1156   case dwarf::DW_TAG_structure_type:
1157   case dwarf::DW_TAG_union_type:
1158   case dwarf::DW_TAG_enumeration_type:
1159   case dwarf::DW_TAG_class_type:
1160     // If this is a class, structure, union, or enumeration type
1161     // that is a definition (not a declaration), and not scoped
1162     // inside a function then separate this out as a type unit.
1163     return !CTy.isForwardDecl() && isTypeUnitScoped(CTy, DD);
1164   default:
1165     return false;
1166   }
1167 }
1168
1169 /// constructTypeDIE - Construct type DIE from DICompositeType.
1170 void CompileUnit::constructTypeDIE(DIE &Buffer, DICompositeType CTy) {
1171   // If this is a type applicable to a type unit it then add it to the
1172   // list of types we'll compute a hash for later.
1173   if (shouldCreateTypeUnit(CTy, DD))
1174     DD->addTypeUnitType(&Buffer, CTy);
1175   else
1176     constructTypeDIEImpl(Buffer, CTy);
1177 }
1178
1179 void CompileUnit::constructTypeDIEImpl(DIE &Buffer, DICompositeType CTy) {
1180   // Add name if not anonymous or intermediate type.
1181   StringRef Name = CTy.getName();
1182
1183   uint64_t Size = CTy.getSizeInBits() >> 3;
1184   uint16_t Tag = Buffer.getTag();
1185
1186   switch (Tag) {
1187   case dwarf::DW_TAG_array_type:
1188     constructArrayTypeDIE(Buffer, CTy);
1189     break;
1190   case dwarf::DW_TAG_enumeration_type:
1191     constructEnumTypeDIE(Buffer, CTy);
1192     break;
1193   case dwarf::DW_TAG_subroutine_type: {
1194     // Add return type. A void return won't have a type.
1195     DIArray Elements = CTy.getTypeArray();
1196     DIType RTy(Elements.getElement(0));
1197     if (RTy)
1198       addType(&Buffer, RTy);
1199
1200     bool isPrototyped = true;
1201     // Add arguments.
1202     for (unsigned i = 1, N = Elements.getNumElements(); i < N; ++i) {
1203       DIDescriptor Ty = Elements.getElement(i);
1204       if (Ty.isUnspecifiedParameter()) {
1205         createAndAddDIE(dwarf::DW_TAG_unspecified_parameters, Buffer);
1206         isPrototyped = false;
1207       } else {
1208         DIE *Arg = createAndAddDIE(dwarf::DW_TAG_formal_parameter, Buffer);
1209         addType(Arg, DIType(Ty));
1210         if (DIType(Ty).isArtificial())
1211           addFlag(Arg, dwarf::DW_AT_artificial);
1212       }
1213     }
1214     // Add prototype flag if we're dealing with a C language and the
1215     // function has been prototyped.
1216     uint16_t Language = getLanguage();
1217     if (isPrototyped &&
1218         (Language == dwarf::DW_LANG_C89 || Language == dwarf::DW_LANG_C99 ||
1219          Language == dwarf::DW_LANG_ObjC))
1220       addFlag(&Buffer, dwarf::DW_AT_prototyped);
1221   } break;
1222   case dwarf::DW_TAG_structure_type:
1223   case dwarf::DW_TAG_union_type:
1224   case dwarf::DW_TAG_class_type: {
1225     // Add elements to structure type.
1226     DIArray Elements = CTy.getTypeArray();
1227     for (unsigned i = 0, N = Elements.getNumElements(); i < N; ++i) {
1228       DIDescriptor Element = Elements.getElement(i);
1229       DIE *ElemDie = NULL;
1230       if (Element.isSubprogram()) {
1231         DISubprogram SP(Element);
1232         ElemDie = getOrCreateSubprogramDIE(SP);
1233         if (SP.isProtected())
1234           addUInt(ElemDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1235                   dwarf::DW_ACCESS_protected);
1236         else if (SP.isPrivate())
1237           addUInt(ElemDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1238                   dwarf::DW_ACCESS_private);
1239         else
1240           addUInt(ElemDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1241                   dwarf::DW_ACCESS_public);
1242         if (SP.isExplicit())
1243           addFlag(ElemDie, dwarf::DW_AT_explicit);
1244       } else if (Element.isDerivedType()) {
1245         DIDerivedType DDTy(Element);
1246         if (DDTy.getTag() == dwarf::DW_TAG_friend) {
1247           ElemDie = createAndAddDIE(dwarf::DW_TAG_friend, Buffer);
1248           addType(ElemDie, resolve(DDTy.getTypeDerivedFrom()),
1249                   dwarf::DW_AT_friend);
1250         } else if (DDTy.isStaticMember()) {
1251           getOrCreateStaticMemberDIE(DDTy);
1252         } else {
1253           constructMemberDIE(Buffer, DDTy);
1254         }
1255       } else if (Element.isObjCProperty()) {
1256         DIObjCProperty Property(Element);
1257         ElemDie = createAndAddDIE(Property.getTag(), Buffer);
1258         StringRef PropertyName = Property.getObjCPropertyName();
1259         addString(ElemDie, dwarf::DW_AT_APPLE_property_name, PropertyName);
1260         addType(ElemDie, Property.getType());
1261         addSourceLine(ElemDie, Property);
1262         StringRef GetterName = Property.getObjCPropertyGetterName();
1263         if (!GetterName.empty())
1264           addString(ElemDie, dwarf::DW_AT_APPLE_property_getter, GetterName);
1265         StringRef SetterName = Property.getObjCPropertySetterName();
1266         if (!SetterName.empty())
1267           addString(ElemDie, dwarf::DW_AT_APPLE_property_setter, SetterName);
1268         unsigned PropertyAttributes = 0;
1269         if (Property.isReadOnlyObjCProperty())
1270           PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_readonly;
1271         if (Property.isReadWriteObjCProperty())
1272           PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_readwrite;
1273         if (Property.isAssignObjCProperty())
1274           PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_assign;
1275         if (Property.isRetainObjCProperty())
1276           PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_retain;
1277         if (Property.isCopyObjCProperty())
1278           PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_copy;
1279         if (Property.isNonAtomicObjCProperty())
1280           PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_nonatomic;
1281         if (PropertyAttributes)
1282           addUInt(ElemDie, dwarf::DW_AT_APPLE_property_attribute, None,
1283                   PropertyAttributes);
1284
1285         DIEEntry *Entry = getDIEEntry(Element);
1286         if (!Entry) {
1287           Entry = createDIEEntry(ElemDie);
1288           insertDIEEntry(Element, Entry);
1289         }
1290       } else
1291         continue;
1292     }
1293
1294     if (CTy.isAppleBlockExtension())
1295       addFlag(&Buffer, dwarf::DW_AT_APPLE_block);
1296
1297     DICompositeType ContainingType(resolve(CTy.getContainingType()));
1298     if (ContainingType)
1299       addDIEEntry(&Buffer, dwarf::DW_AT_containing_type,
1300                   getOrCreateTypeDIE(ContainingType));
1301
1302     if (CTy.isObjcClassComplete())
1303       addFlag(&Buffer, dwarf::DW_AT_APPLE_objc_complete_type);
1304
1305     // Add template parameters to a class, structure or union types.
1306     // FIXME: The support isn't in the metadata for this yet.
1307     if (Tag == dwarf::DW_TAG_class_type ||
1308         Tag == dwarf::DW_TAG_structure_type || Tag == dwarf::DW_TAG_union_type)
1309       addTemplateParams(Buffer, CTy.getTemplateParams());
1310
1311     break;
1312   }
1313   default:
1314     break;
1315   }
1316
1317   // Add name if not anonymous or intermediate type.
1318   if (!Name.empty())
1319     addString(&Buffer, dwarf::DW_AT_name, Name);
1320
1321   if (Tag == dwarf::DW_TAG_enumeration_type ||
1322       Tag == dwarf::DW_TAG_class_type || Tag == dwarf::DW_TAG_structure_type ||
1323       Tag == dwarf::DW_TAG_union_type) {
1324     // Add size if non-zero (derived types might be zero-sized.)
1325     // TODO: Do we care about size for enum forward declarations?
1326     if (Size)
1327       addUInt(&Buffer, dwarf::DW_AT_byte_size, None, Size);
1328     else if (!CTy.isForwardDecl())
1329       // Add zero size if it is not a forward declaration.
1330       addUInt(&Buffer, dwarf::DW_AT_byte_size, None, 0);
1331
1332     // If we're a forward decl, say so.
1333     if (CTy.isForwardDecl())
1334       addFlag(&Buffer, dwarf::DW_AT_declaration);
1335
1336     // Add source line info if available.
1337     if (!CTy.isForwardDecl())
1338       addSourceLine(&Buffer, CTy);
1339
1340     // No harm in adding the runtime language to the declaration.
1341     unsigned RLang = CTy.getRunTimeLang();
1342     if (RLang)
1343       addUInt(&Buffer, dwarf::DW_AT_APPLE_runtime_class, dwarf::DW_FORM_data1,
1344               RLang);
1345   }
1346 }
1347
1348 /// constructTemplateTypeParameterDIE - Construct new DIE for the given
1349 /// DITemplateTypeParameter.
1350 void
1351 CompileUnit::constructTemplateTypeParameterDIE(DIE &Buffer,
1352                                                DITemplateTypeParameter TP) {
1353   DIE *ParamDIE =
1354       createAndAddDIE(dwarf::DW_TAG_template_type_parameter, Buffer);
1355   // Add the type if it exists, it could be void and therefore no type.
1356   if (TP.getType())
1357     addType(ParamDIE, resolve(TP.getType()));
1358   if (!TP.getName().empty())
1359     addString(ParamDIE, dwarf::DW_AT_name, TP.getName());
1360 }
1361
1362 /// constructTemplateValueParameterDIE - Construct new DIE for the given
1363 /// DITemplateValueParameter.
1364 void
1365 CompileUnit::constructTemplateValueParameterDIE(DIE &Buffer,
1366                                                 DITemplateValueParameter VP) {
1367   DIE *ParamDIE = createAndAddDIE(VP.getTag(), Buffer);
1368
1369   // Add the type if there is one, template template and template parameter
1370   // packs will not have a type.
1371   if (VP.getTag() == dwarf::DW_TAG_template_value_parameter)
1372     addType(ParamDIE, resolve(VP.getType()));
1373   if (!VP.getName().empty())
1374     addString(ParamDIE, dwarf::DW_AT_name, VP.getName());
1375   if (Value *Val = VP.getValue()) {
1376     if (ConstantInt *CI = dyn_cast<ConstantInt>(Val))
1377       addConstantValue(ParamDIE, CI,
1378                        isUnsignedDIType(DD, resolve(VP.getType())));
1379     else if (GlobalValue *GV = dyn_cast<GlobalValue>(Val)) {
1380       // For declaration non-type template parameters (such as global values and
1381       // functions)
1382       DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
1383       addOpAddress(Block, Asm->getSymbol(GV));
1384       // Emit DW_OP_stack_value to use the address as the immediate value of the
1385       // parameter, rather than a pointer to it.
1386       addUInt(Block, dwarf::DW_FORM_data1, dwarf::DW_OP_stack_value);
1387       addBlock(ParamDIE, dwarf::DW_AT_location, Block);
1388     } else if (VP.getTag() == dwarf::DW_TAG_GNU_template_template_param) {
1389       assert(isa<MDString>(Val));
1390       addString(ParamDIE, dwarf::DW_AT_GNU_template_name,
1391                 cast<MDString>(Val)->getString());
1392     } else if (VP.getTag() == dwarf::DW_TAG_GNU_template_parameter_pack) {
1393       assert(isa<MDNode>(Val));
1394       DIArray A(cast<MDNode>(Val));
1395       addTemplateParams(*ParamDIE, A);
1396     }
1397   }
1398 }
1399
1400 /// getOrCreateNameSpace - Create a DIE for DINameSpace.
1401 DIE *CompileUnit::getOrCreateNameSpace(DINameSpace NS) {
1402   // Construct the context before querying for the existence of the DIE in case
1403   // such construction creates the DIE.
1404   DIE *ContextDIE = getOrCreateContextDIE(NS.getContext());
1405
1406   DIE *NDie = getDIE(NS);
1407   if (NDie)
1408     return NDie;
1409   NDie = createAndAddDIE(dwarf::DW_TAG_namespace, *ContextDIE, NS);
1410
1411   if (!NS.getName().empty()) {
1412     addString(NDie, dwarf::DW_AT_name, NS.getName());
1413     addAccelNamespace(NS.getName(), NDie);
1414     addGlobalName(NS.getName(), NDie, NS.getContext());
1415   } else
1416     addAccelNamespace("(anonymous namespace)", NDie);
1417   addSourceLine(NDie, NS);
1418   return NDie;
1419 }
1420
1421 /// getOrCreateSubprogramDIE - Create new DIE using SP.
1422 DIE *CompileUnit::getOrCreateSubprogramDIE(DISubprogram SP) {
1423   // Construct the context before querying for the existence of the DIE in case
1424   // such construction creates the DIE (as is the case for member function
1425   // declarations).
1426   DIE *ContextDIE = getOrCreateContextDIE(resolve(SP.getContext()));
1427
1428   DIE *SPDie = getDIE(SP);
1429   if (SPDie)
1430     return SPDie;
1431
1432   DISubprogram SPDecl = SP.getFunctionDeclaration();
1433   if (SPDecl.isSubprogram())
1434     // Add subprogram definitions to the CU die directly.
1435     ContextDIE = CUDie.get();
1436
1437   // DW_TAG_inlined_subroutine may refer to this DIE.
1438   SPDie = createAndAddDIE(dwarf::DW_TAG_subprogram, *ContextDIE, SP);
1439
1440   DIE *DeclDie = NULL;
1441   if (SPDecl.isSubprogram())
1442     DeclDie = getOrCreateSubprogramDIE(SPDecl);
1443
1444   // Add function template parameters.
1445   addTemplateParams(*SPDie, SP.getTemplateParams());
1446
1447   // If this DIE is going to refer declaration info using AT_specification
1448   // then there is no need to add other attributes.
1449   if (DeclDie) {
1450     // Refer function declaration directly.
1451     addDIEEntry(SPDie, dwarf::DW_AT_specification, DeclDie);
1452
1453     return SPDie;
1454   }
1455
1456   // Add the linkage name if we have one.
1457   StringRef LinkageName = SP.getLinkageName();
1458   if (!LinkageName.empty())
1459     addString(SPDie, dwarf::DW_AT_MIPS_linkage_name,
1460               GlobalValue::getRealLinkageName(LinkageName));
1461
1462   // Constructors and operators for anonymous aggregates do not have names.
1463   if (!SP.getName().empty())
1464     addString(SPDie, dwarf::DW_AT_name, SP.getName());
1465
1466   addSourceLine(SPDie, SP);
1467
1468   // Add the prototype if we have a prototype and we have a C like
1469   // language.
1470   uint16_t Language = getLanguage();
1471   if (SP.isPrototyped() &&
1472       (Language == dwarf::DW_LANG_C89 || Language == dwarf::DW_LANG_C99 ||
1473        Language == dwarf::DW_LANG_ObjC))
1474     addFlag(SPDie, dwarf::DW_AT_prototyped);
1475
1476   DICompositeType SPTy = SP.getType();
1477   assert(SPTy.getTag() == dwarf::DW_TAG_subroutine_type &&
1478          "the type of a subprogram should be a subroutine");
1479
1480   DIArray Args = SPTy.getTypeArray();
1481   // Add a return type. If this is a type like a C/C++ void type we don't add a
1482   // return type.
1483   if (Args.getElement(0))
1484     addType(SPDie, DIType(Args.getElement(0)));
1485
1486   unsigned VK = SP.getVirtuality();
1487   if (VK) {
1488     addUInt(SPDie, dwarf::DW_AT_virtuality, dwarf::DW_FORM_data1, VK);
1489     DIEBlock *Block = getDIEBlock();
1490     addUInt(Block, dwarf::DW_FORM_data1, dwarf::DW_OP_constu);
1491     addUInt(Block, dwarf::DW_FORM_udata, SP.getVirtualIndex());
1492     addBlock(SPDie, dwarf::DW_AT_vtable_elem_location, Block);
1493     ContainingTypeMap.insert(
1494         std::make_pair(SPDie, resolve(SP.getContainingType())));
1495   }
1496
1497   if (!SP.isDefinition()) {
1498     addFlag(SPDie, dwarf::DW_AT_declaration);
1499
1500     // Add arguments. Do not add arguments for subprogram definition. They will
1501     // be handled while processing variables.
1502     for (unsigned i = 1, N = Args.getNumElements(); i < N; ++i) {
1503       DIE *Arg = createAndAddDIE(dwarf::DW_TAG_formal_parameter, *SPDie);
1504       DIType ATy(Args.getElement(i));
1505       addType(Arg, ATy);
1506       if (ATy.isArtificial())
1507         addFlag(Arg, dwarf::DW_AT_artificial);
1508     }
1509   }
1510
1511   if (SP.isArtificial())
1512     addFlag(SPDie, dwarf::DW_AT_artificial);
1513
1514   if (!SP.isLocalToUnit())
1515     addFlag(SPDie, dwarf::DW_AT_external);
1516
1517   if (SP.isOptimized())
1518     addFlag(SPDie, dwarf::DW_AT_APPLE_optimized);
1519
1520   if (unsigned isa = Asm->getISAEncoding()) {
1521     addUInt(SPDie, dwarf::DW_AT_APPLE_isa, dwarf::DW_FORM_flag, isa);
1522   }
1523
1524   return SPDie;
1525 }
1526
1527 // Return const expression if value is a GEP to access merged global
1528 // constant. e.g.
1529 // i8* getelementptr ({ i8, i8, i8, i8 }* @_MergedGlobals, i32 0, i32 0)
1530 static const ConstantExpr *getMergedGlobalExpr(const Value *V) {
1531   const ConstantExpr *CE = dyn_cast_or_null<ConstantExpr>(V);
1532   if (!CE || CE->getNumOperands() != 3 ||
1533       CE->getOpcode() != Instruction::GetElementPtr)
1534     return NULL;
1535
1536   // First operand points to a global struct.
1537   Value *Ptr = CE->getOperand(0);
1538   if (!isa<GlobalValue>(Ptr) ||
1539       !isa<StructType>(cast<PointerType>(Ptr->getType())->getElementType()))
1540     return NULL;
1541
1542   // Second operand is zero.
1543   const ConstantInt *CI = dyn_cast_or_null<ConstantInt>(CE->getOperand(1));
1544   if (!CI || !CI->isZero())
1545     return NULL;
1546
1547   // Third operand is offset.
1548   if (!isa<ConstantInt>(CE->getOperand(2)))
1549     return NULL;
1550
1551   return CE;
1552 }
1553
1554 /// createGlobalVariableDIE - create global variable DIE.
1555 void CompileUnit::createGlobalVariableDIE(DIGlobalVariable GV) {
1556   // Check for pre-existence.
1557   if (getDIE(GV))
1558     return;
1559
1560   if (!GV.isGlobalVariable())
1561     return;
1562
1563   DIScope GVContext = GV.getContext();
1564   DIType GTy = GV.getType();
1565
1566   // If this is a static data member definition, some attributes belong
1567   // to the declaration DIE.
1568   DIE *VariableDIE = NULL;
1569   bool IsStaticMember = false;
1570   DIDerivedType SDMDecl = GV.getStaticDataMemberDeclaration();
1571   if (SDMDecl.Verify()) {
1572     assert(SDMDecl.isStaticMember() && "Expected static member decl");
1573     // We need the declaration DIE that is in the static member's class.
1574     VariableDIE = getOrCreateStaticMemberDIE(SDMDecl);
1575     IsStaticMember = true;
1576   }
1577
1578   // If this is not a static data member definition, create the variable
1579   // DIE and add the initial set of attributes to it.
1580   if (!VariableDIE) {
1581     // Construct the context before querying for the existence of the DIE in
1582     // case such construction creates the DIE.
1583     DIE *ContextDIE = getOrCreateContextDIE(GVContext);
1584
1585     // Add to map.
1586     VariableDIE = createAndAddDIE(GV.getTag(), *ContextDIE, GV);
1587
1588     // Add name and type.
1589     addString(VariableDIE, dwarf::DW_AT_name, GV.getDisplayName());
1590     addType(VariableDIE, GTy);
1591
1592     // Add scoping info.
1593     if (!GV.isLocalToUnit())
1594       addFlag(VariableDIE, dwarf::DW_AT_external);
1595
1596     // Add line number info.
1597     addSourceLine(VariableDIE, GV);
1598   }
1599
1600   // Add location.
1601   bool addToAccelTable = false;
1602   DIE *VariableSpecDIE = NULL;
1603   bool isGlobalVariable = GV.getGlobal() != NULL;
1604   if (isGlobalVariable) {
1605     addToAccelTable = true;
1606     DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
1607     const MCSymbol *Sym = Asm->getSymbol(GV.getGlobal());
1608     if (GV.getGlobal()->isThreadLocal()) {
1609       // FIXME: Make this work with -gsplit-dwarf.
1610       unsigned PointerSize = Asm->getDataLayout().getPointerSize();
1611       assert((PointerSize == 4 || PointerSize == 8) &&
1612              "Add support for other sizes if necessary");
1613       const MCExpr *Expr =
1614           Asm->getObjFileLowering().getDebugThreadLocalSymbol(Sym);
1615       // Based on GCC's support for TLS:
1616       if (!DD->useSplitDwarf()) {
1617         // 1) Start with a constNu of the appropriate pointer size
1618         addUInt(Block, dwarf::DW_FORM_data1,
1619                 PointerSize == 4 ? dwarf::DW_OP_const4u : dwarf::DW_OP_const8u);
1620         // 2) containing the (relocated) offset of the TLS variable
1621         //    within the module's TLS block.
1622         addExpr(Block, dwarf::DW_FORM_udata, Expr);
1623       } else {
1624         addUInt(Block, dwarf::DW_FORM_data1, dwarf::DW_OP_GNU_const_index);
1625         addUInt(Block, dwarf::DW_FORM_udata, DU->getAddrPoolIndex(Expr));
1626       }
1627       // 3) followed by a custom OP to make the debugger do a TLS lookup.
1628       addUInt(Block, dwarf::DW_FORM_data1, dwarf::DW_OP_GNU_push_tls_address);
1629     } else
1630       addOpAddress(Block, Sym);
1631     // Do not create specification DIE if context is either compile unit
1632     // or a subprogram.
1633     if (GVContext && GV.isDefinition() && !GVContext.isCompileUnit() &&
1634         !GVContext.isFile() && !DD->isSubprogramContext(GVContext)) {
1635       // Create specification DIE.
1636       VariableSpecDIE = createAndAddDIE(dwarf::DW_TAG_variable, *CUDie);
1637       addDIEEntry(VariableSpecDIE, dwarf::DW_AT_specification, VariableDIE);
1638       addBlock(VariableSpecDIE, dwarf::DW_AT_location, Block);
1639       // A static member's declaration is already flagged as such.
1640       if (!SDMDecl.Verify())
1641         addFlag(VariableDIE, dwarf::DW_AT_declaration);
1642     } else {
1643       addBlock(VariableDIE, dwarf::DW_AT_location, Block);
1644     }
1645     // Add the linkage name.
1646     StringRef LinkageName = GV.getLinkageName();
1647     if (!LinkageName.empty())
1648       // From DWARF4: DIEs to which DW_AT_linkage_name may apply include:
1649       // TAG_common_block, TAG_constant, TAG_entry_point, TAG_subprogram and
1650       // TAG_variable.
1651       addString(IsStaticMember && VariableSpecDIE ? VariableSpecDIE
1652                                                   : VariableDIE,
1653                 dwarf::DW_AT_MIPS_linkage_name,
1654                 GlobalValue::getRealLinkageName(LinkageName));
1655   } else if (const ConstantInt *CI =
1656                  dyn_cast_or_null<ConstantInt>(GV.getConstant())) {
1657     // AT_const_value was added when the static member was created. To avoid
1658     // emitting AT_const_value multiple times, we only add AT_const_value when
1659     // it is not a static member.
1660     if (!IsStaticMember)
1661       addConstantValue(VariableDIE, CI, isUnsignedDIType(DD, GTy));
1662   } else if (const ConstantExpr *CE = getMergedGlobalExpr(GV->getOperand(11))) {
1663     addToAccelTable = true;
1664     // GV is a merged global.
1665     DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
1666     Value *Ptr = CE->getOperand(0);
1667     addOpAddress(Block, Asm->getSymbol(cast<GlobalValue>(Ptr)));
1668     addUInt(Block, dwarf::DW_FORM_data1, dwarf::DW_OP_constu);
1669     SmallVector<Value *, 3> Idx(CE->op_begin() + 1, CE->op_end());
1670     addUInt(Block, dwarf::DW_FORM_udata,
1671             Asm->getDataLayout().getIndexedOffset(Ptr->getType(), Idx));
1672     addUInt(Block, dwarf::DW_FORM_data1, dwarf::DW_OP_plus);
1673     addBlock(VariableDIE, dwarf::DW_AT_location, Block);
1674   }
1675
1676   if (addToAccelTable) {
1677     DIE *AddrDIE = VariableSpecDIE ? VariableSpecDIE : VariableDIE;
1678     addAccelName(GV.getName(), AddrDIE);
1679
1680     // If the linkage name is different than the name, go ahead and output
1681     // that as well into the name table.
1682     if (GV.getLinkageName() != "" && GV.getName() != GV.getLinkageName())
1683       addAccelName(GV.getLinkageName(), AddrDIE);
1684   }
1685
1686   if (!GV.isLocalToUnit())
1687     addGlobalName(GV.getName(), VariableSpecDIE ? VariableSpecDIE : VariableDIE,
1688                   GV.getContext());
1689 }
1690
1691 /// constructSubrangeDIE - Construct subrange DIE from DISubrange.
1692 void CompileUnit::constructSubrangeDIE(DIE &Buffer, DISubrange SR,
1693                                        DIE *IndexTy) {
1694   DIE *DW_Subrange = createAndAddDIE(dwarf::DW_TAG_subrange_type, Buffer);
1695   addDIEEntry(DW_Subrange, dwarf::DW_AT_type, IndexTy);
1696
1697   // The LowerBound value defines the lower bounds which is typically zero for
1698   // C/C++. The Count value is the number of elements.  Values are 64 bit. If
1699   // Count == -1 then the array is unbounded and we do not emit
1700   // DW_AT_lower_bound and DW_AT_upper_bound attributes. If LowerBound == 0 and
1701   // Count == 0, then the array has zero elements in which case we do not emit
1702   // an upper bound.
1703   int64_t LowerBound = SR.getLo();
1704   int64_t DefaultLowerBound = getDefaultLowerBound();
1705   int64_t Count = SR.getCount();
1706
1707   if (DefaultLowerBound == -1 || LowerBound != DefaultLowerBound)
1708     addUInt(DW_Subrange, dwarf::DW_AT_lower_bound, None, LowerBound);
1709
1710   if (Count != -1 && Count != 0)
1711     // FIXME: An unbounded array should reference the expression that defines
1712     // the array.
1713     addUInt(DW_Subrange, dwarf::DW_AT_upper_bound, None,
1714             LowerBound + Count - 1);
1715 }
1716
1717 /// constructArrayTypeDIE - Construct array type DIE from DICompositeType.
1718 void CompileUnit::constructArrayTypeDIE(DIE &Buffer, DICompositeType CTy) {
1719   if (CTy.isVector())
1720     addFlag(&Buffer, dwarf::DW_AT_GNU_vector);
1721
1722   // Emit the element type.
1723   addType(&Buffer, resolve(CTy.getTypeDerivedFrom()));
1724
1725   // Get an anonymous type for index type.
1726   // FIXME: This type should be passed down from the front end
1727   // as different languages may have different sizes for indexes.
1728   DIE *IdxTy = getIndexTyDie();
1729   if (!IdxTy) {
1730     // Construct an anonymous type for index type.
1731     IdxTy = createAndAddDIE(dwarf::DW_TAG_base_type, *CUDie.get());
1732     addString(IdxTy, dwarf::DW_AT_name, "int");
1733     addUInt(IdxTy, dwarf::DW_AT_byte_size, None, sizeof(int32_t));
1734     addUInt(IdxTy, dwarf::DW_AT_encoding, dwarf::DW_FORM_data1,
1735             dwarf::DW_ATE_signed);
1736     setIndexTyDie(IdxTy);
1737   }
1738
1739   // Add subranges to array type.
1740   DIArray Elements = CTy.getTypeArray();
1741   for (unsigned i = 0, N = Elements.getNumElements(); i < N; ++i) {
1742     DIDescriptor Element = Elements.getElement(i);
1743     if (Element.getTag() == dwarf::DW_TAG_subrange_type)
1744       constructSubrangeDIE(Buffer, DISubrange(Element), IdxTy);
1745   }
1746 }
1747
1748 /// constructEnumTypeDIE - Construct an enum type DIE from DICompositeType.
1749 void CompileUnit::constructEnumTypeDIE(DIE &Buffer, DICompositeType CTy) {
1750   DIArray Elements = CTy.getTypeArray();
1751
1752   // Add enumerators to enumeration type.
1753   for (unsigned i = 0, N = Elements.getNumElements(); i < N; ++i) {
1754     DIEnumerator Enum(Elements.getElement(i));
1755     if (Enum.isEnumerator()) {
1756       DIE *Enumerator = createAndAddDIE(dwarf::DW_TAG_enumerator, Buffer);
1757       StringRef Name = Enum.getName();
1758       addString(Enumerator, dwarf::DW_AT_name, Name);
1759       int64_t Value = Enum.getEnumValue();
1760       addSInt(Enumerator, dwarf::DW_AT_const_value, dwarf::DW_FORM_sdata,
1761               Value);
1762     }
1763   }
1764   DIType DTy = resolve(CTy.getTypeDerivedFrom());
1765   if (DTy) {
1766     addType(&Buffer, DTy);
1767     addFlag(&Buffer, dwarf::DW_AT_enum_class);
1768   }
1769 }
1770
1771 /// constructContainingTypeDIEs - Construct DIEs for types that contain
1772 /// vtables.
1773 void CompileUnit::constructContainingTypeDIEs() {
1774   for (DenseMap<DIE *, const MDNode *>::iterator CI = ContainingTypeMap.begin(),
1775                                                  CE = ContainingTypeMap.end();
1776        CI != CE; ++CI) {
1777     DIE *SPDie = CI->first;
1778     DIDescriptor D(CI->second);
1779     if (!D)
1780       continue;
1781     DIE *NDie = getDIE(D);
1782     if (!NDie)
1783       continue;
1784     addDIEEntry(SPDie, dwarf::DW_AT_containing_type, NDie);
1785   }
1786 }
1787
1788 /// constructVariableDIE - Construct a DIE for the given DbgVariable.
1789 DIE *CompileUnit::constructVariableDIE(DbgVariable &DV, bool isScopeAbstract) {
1790   StringRef Name = DV.getName();
1791
1792   // Define variable debug information entry.
1793   DIE *VariableDie = new DIE(DV.getTag());
1794   DbgVariable *AbsVar = DV.getAbstractVariable();
1795   DIE *AbsDIE = AbsVar ? AbsVar->getDIE() : NULL;
1796   if (AbsDIE)
1797     addDIEEntry(VariableDie, dwarf::DW_AT_abstract_origin, AbsDIE);
1798   else {
1799     if (!Name.empty())
1800       addString(VariableDie, dwarf::DW_AT_name, Name);
1801     addSourceLine(VariableDie, DV.getVariable());
1802     addType(VariableDie, DV.getType());
1803   }
1804
1805   if (DV.isArtificial())
1806     addFlag(VariableDie, dwarf::DW_AT_artificial);
1807
1808   if (isScopeAbstract) {
1809     DV.setDIE(VariableDie);
1810     return VariableDie;
1811   }
1812
1813   // Add variable address.
1814
1815   unsigned Offset = DV.getDotDebugLocOffset();
1816   if (Offset != ~0U) {
1817     addLabel(VariableDie, dwarf::DW_AT_location,
1818              DD->getDwarfVersion() >= 4 ? dwarf::DW_FORM_sec_offset
1819                                         : dwarf::DW_FORM_data4,
1820              Asm->GetTempSymbol("debug_loc", Offset));
1821     DV.setDIE(VariableDie);
1822     return VariableDie;
1823   }
1824
1825   // Check if variable is described by a DBG_VALUE instruction.
1826   if (const MachineInstr *DVInsn = DV.getMInsn()) {
1827     assert(DVInsn->getNumOperands() == 3);
1828     if (DVInsn->getOperand(0).isReg()) {
1829       const MachineOperand RegOp = DVInsn->getOperand(0);
1830       // If the second operand is an immediate, this is an indirect value.
1831       if (DVInsn->getOperand(1).isImm()) {
1832         MachineLocation Location(RegOp.getReg(),
1833                                  DVInsn->getOperand(1).getImm());
1834         addVariableAddress(DV, VariableDie, Location);
1835       } else if (RegOp.getReg())
1836         addVariableAddress(DV, VariableDie, MachineLocation(RegOp.getReg()));
1837     } else if (DVInsn->getOperand(0).isImm())
1838       addConstantValue(VariableDie, DVInsn->getOperand(0), DV.getType());
1839     else if (DVInsn->getOperand(0).isFPImm())
1840       addConstantFPValue(VariableDie, DVInsn->getOperand(0));
1841     else if (DVInsn->getOperand(0).isCImm())
1842       addConstantValue(VariableDie, DVInsn->getOperand(0).getCImm(),
1843                        isUnsignedDIType(DD, DV.getType()));
1844
1845     DV.setDIE(VariableDie);
1846     return VariableDie;
1847   } else {
1848     // .. else use frame index.
1849     int FI = DV.getFrameIndex();
1850     if (FI != ~0) {
1851       unsigned FrameReg = 0;
1852       const TargetFrameLowering *TFI = Asm->TM.getFrameLowering();
1853       int Offset = TFI->getFrameIndexReference(*Asm->MF, FI, FrameReg);
1854       MachineLocation Location(FrameReg, Offset);
1855       addVariableAddress(DV, VariableDie, Location);
1856     }
1857   }
1858
1859   DV.setDIE(VariableDie);
1860   return VariableDie;
1861 }
1862
1863 /// constructMemberDIE - Construct member DIE from DIDerivedType.
1864 void CompileUnit::constructMemberDIE(DIE &Buffer, DIDerivedType DT) {
1865   DIE *MemberDie = createAndAddDIE(DT.getTag(), Buffer);
1866   StringRef Name = DT.getName();
1867   if (!Name.empty())
1868     addString(MemberDie, dwarf::DW_AT_name, Name);
1869
1870   addType(MemberDie, resolve(DT.getTypeDerivedFrom()));
1871
1872   addSourceLine(MemberDie, DT);
1873
1874   DIEBlock *MemLocationDie = new (DIEValueAllocator) DIEBlock();
1875   addUInt(MemLocationDie, dwarf::DW_FORM_data1, dwarf::DW_OP_plus_uconst);
1876
1877   if (DT.getTag() == dwarf::DW_TAG_inheritance && DT.isVirtual()) {
1878
1879     // For C++, virtual base classes are not at fixed offset. Use following
1880     // expression to extract appropriate offset from vtable.
1881     // BaseAddr = ObAddr + *((*ObAddr) - Offset)
1882
1883     DIEBlock *VBaseLocationDie = new (DIEValueAllocator) DIEBlock();
1884     addUInt(VBaseLocationDie, dwarf::DW_FORM_data1, dwarf::DW_OP_dup);
1885     addUInt(VBaseLocationDie, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
1886     addUInt(VBaseLocationDie, dwarf::DW_FORM_data1, dwarf::DW_OP_constu);
1887     addUInt(VBaseLocationDie, dwarf::DW_FORM_udata, DT.getOffsetInBits());
1888     addUInt(VBaseLocationDie, dwarf::DW_FORM_data1, dwarf::DW_OP_minus);
1889     addUInt(VBaseLocationDie, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
1890     addUInt(VBaseLocationDie, dwarf::DW_FORM_data1, dwarf::DW_OP_plus);
1891
1892     addBlock(MemberDie, dwarf::DW_AT_data_member_location, VBaseLocationDie);
1893   } else {
1894     uint64_t Size = DT.getSizeInBits();
1895     uint64_t FieldSize = getBaseTypeSize(DD, DT);
1896     uint64_t OffsetInBytes;
1897
1898     if (Size != FieldSize) {
1899       // Handle bitfield.
1900       addUInt(MemberDie, dwarf::DW_AT_byte_size, None,
1901               getBaseTypeSize(DD, DT) >> 3);
1902       addUInt(MemberDie, dwarf::DW_AT_bit_size, None, DT.getSizeInBits());
1903
1904       uint64_t Offset = DT.getOffsetInBits();
1905       uint64_t AlignMask = ~(DT.getAlignInBits() - 1);
1906       uint64_t HiMark = (Offset + FieldSize) & AlignMask;
1907       uint64_t FieldOffset = (HiMark - FieldSize);
1908       Offset -= FieldOffset;
1909
1910       // Maybe we need to work from the other end.
1911       if (Asm->getDataLayout().isLittleEndian())
1912         Offset = FieldSize - (Offset + Size);
1913       addUInt(MemberDie, dwarf::DW_AT_bit_offset, None, Offset);
1914
1915       // Here WD_AT_data_member_location points to the anonymous
1916       // field that includes this bit field.
1917       OffsetInBytes = FieldOffset >> 3;
1918     } else
1919       // This is not a bitfield.
1920       OffsetInBytes = DT.getOffsetInBits() >> 3;
1921     addUInt(MemberDie, dwarf::DW_AT_data_member_location, None, OffsetInBytes);
1922   }
1923
1924   if (DT.isProtected())
1925     addUInt(MemberDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1926             dwarf::DW_ACCESS_protected);
1927   else if (DT.isPrivate())
1928     addUInt(MemberDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1929             dwarf::DW_ACCESS_private);
1930   // Otherwise C++ member and base classes are considered public.
1931   else
1932     addUInt(MemberDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1933             dwarf::DW_ACCESS_public);
1934   if (DT.isVirtual())
1935     addUInt(MemberDie, dwarf::DW_AT_virtuality, dwarf::DW_FORM_data1,
1936             dwarf::DW_VIRTUALITY_virtual);
1937
1938   // Objective-C properties.
1939   if (MDNode *PNode = DT.getObjCProperty())
1940     if (DIEEntry *PropertyDie = getDIEEntry(PNode))
1941       MemberDie->addValue(dwarf::DW_AT_APPLE_property, dwarf::DW_FORM_ref4,
1942                           PropertyDie);
1943
1944   if (DT.isArtificial())
1945     addFlag(MemberDie, dwarf::DW_AT_artificial);
1946 }
1947
1948 /// getOrCreateStaticMemberDIE - Create new DIE for C++ static member.
1949 DIE *CompileUnit::getOrCreateStaticMemberDIE(DIDerivedType DT) {
1950   if (!DT.Verify())
1951     return NULL;
1952
1953   // Construct the context before querying for the existence of the DIE in case
1954   // such construction creates the DIE.
1955   DIE *ContextDIE = getOrCreateContextDIE(resolve(DT.getContext()));
1956   assert(dwarf::isType(ContextDIE->getTag()) &&
1957          "Static member should belong to a type.");
1958
1959   DIE *StaticMemberDIE = getDIE(DT);
1960   if (StaticMemberDIE)
1961     return StaticMemberDIE;
1962
1963   StaticMemberDIE = createAndAddDIE(DT.getTag(), *ContextDIE, DT);
1964
1965   DIType Ty = resolve(DT.getTypeDerivedFrom());
1966
1967   addString(StaticMemberDIE, dwarf::DW_AT_name, DT.getName());
1968   addType(StaticMemberDIE, Ty);
1969   addSourceLine(StaticMemberDIE, DT);
1970   addFlag(StaticMemberDIE, dwarf::DW_AT_external);
1971   addFlag(StaticMemberDIE, dwarf::DW_AT_declaration);
1972
1973   // FIXME: We could omit private if the parent is a class_type, and
1974   // public if the parent is something else.
1975   if (DT.isProtected())
1976     addUInt(StaticMemberDIE, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1977             dwarf::DW_ACCESS_protected);
1978   else if (DT.isPrivate())
1979     addUInt(StaticMemberDIE, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1980             dwarf::DW_ACCESS_private);
1981   else
1982     addUInt(StaticMemberDIE, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1983             dwarf::DW_ACCESS_public);
1984
1985   if (const ConstantInt *CI = dyn_cast_or_null<ConstantInt>(DT.getConstant()))
1986     addConstantValue(StaticMemberDIE, CI, isUnsignedDIType(DD, Ty));
1987   if (const ConstantFP *CFP = dyn_cast_or_null<ConstantFP>(DT.getConstant()))
1988     addConstantFPValue(StaticMemberDIE, CFP);
1989
1990   return StaticMemberDIE;
1991 }
1992
1993 void CompileUnit::emitHeader(const MCSection *ASection,
1994                              const MCSymbol *ASectionSym) {
1995   Asm->OutStreamer.AddComment("DWARF version number");
1996   Asm->EmitInt16(DD->getDwarfVersion());
1997   Asm->OutStreamer.AddComment("Offset Into Abbrev. Section");
1998   Asm->EmitSectionOffset(Asm->GetTempSymbol(ASection->getLabelBeginName()),
1999                          ASectionSym);
2000   Asm->OutStreamer.AddComment("Address Size (in bytes)");
2001   Asm->EmitInt8(Asm->getDataLayout().getPointerSize());
2002 }