As part of the ongoing work in finalizing the accelerator tables, extend
[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 writing dwarf compile unit.
11 //
12 //===----------------------------------------------------------------------===//
13
14 #define DEBUG_TYPE "dwarfdebug"
15
16 #include "DwarfAccelTable.h"
17 #include "DwarfCompileUnit.h"
18 #include "DwarfDebug.h"
19 #include "llvm/Constants.h"
20 #include "llvm/GlobalVariable.h"
21 #include "llvm/Instructions.h"
22 #include "llvm/Analysis/DIBuilder.h"
23 #include "llvm/Support/Debug.h"
24 #include "llvm/Target/Mangler.h"
25 #include "llvm/Target/TargetData.h"
26 #include "llvm/Target/TargetFrameLowering.h"
27 #include "llvm/Target/TargetMachine.h"
28 #include "llvm/Target/TargetRegisterInfo.h"
29 #include "llvm/ADT/APFloat.h"
30 #include "llvm/Support/ErrorHandling.h"
31
32 using namespace llvm;
33
34 /// CompileUnit - Compile unit constructor.
35 CompileUnit::CompileUnit(unsigned I, DIE *D, AsmPrinter *A, DwarfDebug *DW)
36   : ID(I), CUDie(D), Asm(A), DD(DW), IndexTyDie(0) {
37   DIEIntegerOne = new (DIEValueAllocator) DIEInteger(1);
38 }
39
40 /// ~CompileUnit - Destructor for compile unit.
41 CompileUnit::~CompileUnit() {
42   for (unsigned j = 0, M = DIEBlocks.size(); j < M; ++j)
43     DIEBlocks[j]->~DIEBlock();
44 }
45
46 /// createDIEEntry - Creates a new DIEEntry to be a proxy for a debug
47 /// information entry.
48 DIEEntry *CompileUnit::createDIEEntry(DIE *Entry) {
49   DIEEntry *Value = new (DIEValueAllocator) DIEEntry(Entry);
50   return Value;
51 }
52
53 /// addUInt - Add an unsigned integer attribute data and value.
54 ///
55 void CompileUnit::addUInt(DIE *Die, unsigned Attribute,
56                           unsigned Form, uint64_t Integer) {
57   if (!Form) Form = DIEInteger::BestForm(false, Integer);
58   DIEValue *Value = Integer == 1 ?
59     DIEIntegerOne : new (DIEValueAllocator) DIEInteger(Integer);
60   Die->addValue(Attribute, Form, Value);
61 }
62
63 /// addSInt - Add an signed integer attribute data and value.
64 ///
65 void CompileUnit::addSInt(DIE *Die, unsigned Attribute,
66                           unsigned Form, int64_t Integer) {
67   if (!Form) Form = DIEInteger::BestForm(true, Integer);
68   DIEValue *Value = new (DIEValueAllocator) DIEInteger(Integer);
69   Die->addValue(Attribute, Form, Value);
70 }
71
72 /// addString - Add a string attribute data and value. We always emit a
73 /// reference to the string pool instead of immediate strings so that DIEs have
74 /// more predictable sizes.
75 void CompileUnit::addString(DIE *Die, unsigned Attribute, StringRef String) {
76   MCSymbol *Symb = DD->getStringPoolEntry(String);
77   DIEValue *Value;
78   if (Asm->needsRelocationsForDwarfStringPool())
79     Value = new (DIEValueAllocator) DIELabel(Symb);
80   else {
81     MCSymbol *StringPool = DD->getStringPool();
82     Value = new (DIEValueAllocator) DIEDelta(Symb, StringPool);
83   }
84   Die->addValue(Attribute, dwarf::DW_FORM_strp, Value);
85 }
86
87 /// addLabel - Add a Dwarf label attribute data and value.
88 ///
89 void CompileUnit::addLabel(DIE *Die, unsigned Attribute, unsigned Form,
90                            const MCSymbol *Label) {
91   DIEValue *Value = new (DIEValueAllocator) DIELabel(Label);
92   Die->addValue(Attribute, Form, Value);
93 }
94
95 /// addDelta - Add a label delta attribute data and value.
96 ///
97 void CompileUnit::addDelta(DIE *Die, unsigned Attribute, unsigned Form,
98                            const MCSymbol *Hi, const MCSymbol *Lo) {
99   DIEValue *Value = new (DIEValueAllocator) DIEDelta(Hi, Lo);
100   Die->addValue(Attribute, Form, Value);
101 }
102
103 /// addDIEEntry - Add a DIE attribute data and value.
104 ///
105 void CompileUnit::addDIEEntry(DIE *Die, unsigned Attribute, unsigned Form,
106                               DIE *Entry) {
107   Die->addValue(Attribute, Form, createDIEEntry(Entry));
108 }
109
110 /// addBlock - Add block data.
111 ///
112 void CompileUnit::addBlock(DIE *Die, unsigned Attribute, unsigned Form,
113                            DIEBlock *Block) {
114   Block->ComputeSize(Asm);
115   DIEBlocks.push_back(Block); // Memoize so we can call the destructor later on.
116   Die->addValue(Attribute, Block->BestForm(), Block);
117 }
118
119 /// addSourceLine - Add location information to specified debug information
120 /// entry.
121 void CompileUnit::addSourceLine(DIE *Die, DIVariable V) {
122   // Verify variable.
123   if (!V.Verify())
124     return;
125   
126   unsigned Line = V.getLineNumber();
127   if (Line == 0)
128     return;
129   unsigned FileID = DD->GetOrCreateSourceID(V.getContext().getFilename(),
130                                             V.getContext().getDirectory());
131   assert(FileID && "Invalid file id");
132   addUInt(Die, dwarf::DW_AT_decl_file, 0, FileID);
133   addUInt(Die, dwarf::DW_AT_decl_line, 0, Line);
134 }
135
136 /// addSourceLine - Add location information to specified debug information
137 /// entry.
138 void CompileUnit::addSourceLine(DIE *Die, DIGlobalVariable G) {
139   // Verify global variable.
140   if (!G.Verify())
141     return;
142
143   unsigned Line = G.getLineNumber();
144   if (Line == 0)
145     return;
146   unsigned FileID = DD->GetOrCreateSourceID(G.getFilename(), G.getDirectory());
147   assert(FileID && "Invalid file id");
148   addUInt(Die, dwarf::DW_AT_decl_file, 0, FileID);
149   addUInt(Die, dwarf::DW_AT_decl_line, 0, Line);
150 }
151
152 /// addSourceLine - Add location information to specified debug information
153 /// entry.
154 void CompileUnit::addSourceLine(DIE *Die, DISubprogram SP) {
155   // Verify subprogram.
156   if (!SP.Verify())
157     return;
158   // If the line number is 0, don't add it.
159   if (SP.getLineNumber() == 0)
160     return;
161
162   unsigned Line = SP.getLineNumber();
163   if (!SP.getContext().Verify())
164     return;
165   unsigned FileID = DD->GetOrCreateSourceID(SP.getFilename(),
166                                             SP.getDirectory());
167   assert(FileID && "Invalid file id");
168   addUInt(Die, dwarf::DW_AT_decl_file, 0, FileID);
169   addUInt(Die, dwarf::DW_AT_decl_line, 0, Line);
170 }
171
172 /// addSourceLine - Add location information to specified debug information
173 /// entry.
174 void CompileUnit::addSourceLine(DIE *Die, DIType Ty) {
175   // Verify type.
176   if (!Ty.Verify())
177     return;
178
179   unsigned Line = Ty.getLineNumber();
180   if (Line == 0 || !Ty.getContext().Verify())
181     return;
182   unsigned FileID = DD->GetOrCreateSourceID(Ty.getFilename(),
183                                             Ty.getDirectory());
184   assert(FileID && "Invalid file id");
185   addUInt(Die, dwarf::DW_AT_decl_file, 0, FileID);
186   addUInt(Die, dwarf::DW_AT_decl_line, 0, Line);
187 }
188
189 /// addSourceLine - Add location information to specified debug information
190 /// entry.
191 void CompileUnit::addSourceLine(DIE *Die, DINameSpace NS) {
192   // Verify namespace.
193   if (!NS.Verify())
194     return;
195
196   unsigned Line = NS.getLineNumber();
197   if (Line == 0)
198     return;
199   StringRef FN = NS.getFilename();
200
201   unsigned FileID = DD->GetOrCreateSourceID(FN, NS.getDirectory());
202   assert(FileID && "Invalid file id");
203   addUInt(Die, dwarf::DW_AT_decl_file, 0, FileID);
204   addUInt(Die, dwarf::DW_AT_decl_line, 0, Line);
205 }
206
207 /// addVariableAddress - Add DW_AT_location attribute for a 
208 /// DbgVariable based on provided MachineLocation.
209 void CompileUnit::addVariableAddress(DbgVariable *&DV, DIE *Die, 
210                                      MachineLocation Location) {
211   if (DV->variableHasComplexAddress())
212     addComplexAddress(DV, Die, dwarf::DW_AT_location, Location);
213   else if (DV->isBlockByrefVariable())
214     addBlockByrefAddress(DV, Die, dwarf::DW_AT_location, Location);
215   else
216     addAddress(Die, dwarf::DW_AT_location, Location);
217 }
218
219 /// addRegisterOp - Add register operand.
220 void CompileUnit::addRegisterOp(DIE *TheDie, unsigned Reg) {
221   const TargetRegisterInfo *RI = Asm->TM.getRegisterInfo();
222   unsigned DWReg = RI->getDwarfRegNum(Reg, false);
223   if (DWReg < 32)
224     addUInt(TheDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_reg0 + DWReg);
225   else {
226     addUInt(TheDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_regx);
227     addUInt(TheDie, 0, dwarf::DW_FORM_udata, DWReg);
228   }
229 }
230
231 /// addRegisterOffset - Add register offset.
232 void CompileUnit::addRegisterOffset(DIE *TheDie, unsigned Reg,
233                                     int64_t Offset) {
234   const TargetRegisterInfo *RI = Asm->TM.getRegisterInfo();
235   unsigned DWReg = RI->getDwarfRegNum(Reg, false);
236   const TargetRegisterInfo *TRI = Asm->TM.getRegisterInfo();
237   if (Reg == TRI->getFrameRegister(*Asm->MF))
238     // If variable offset is based in frame register then use fbreg.
239     addUInt(TheDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_fbreg);
240   else if (DWReg < 32)
241     addUInt(TheDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_breg0 + DWReg);
242   else {
243     addUInt(TheDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_bregx);
244     addUInt(TheDie, 0, dwarf::DW_FORM_udata, DWReg);
245   }
246   addSInt(TheDie, 0, dwarf::DW_FORM_sdata, Offset);
247 }
248
249 /// addAddress - Add an address attribute to a die based on the location
250 /// provided.
251 void CompileUnit::addAddress(DIE *Die, unsigned Attribute,
252                              const MachineLocation &Location) {
253   DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
254
255   if (Location.isReg())
256     addRegisterOp(Block, Location.getReg());
257   else
258     addRegisterOffset(Block, Location.getReg(), Location.getOffset());
259
260   // Now attach the location information to the DIE.
261   addBlock(Die, Attribute, 0, Block);
262 }
263
264 /// addComplexAddress - Start with the address based on the location provided,
265 /// and generate the DWARF information necessary to find the actual variable
266 /// given the extra address information encoded in the DIVariable, starting from
267 /// the starting location.  Add the DWARF information to the die.
268 ///
269 void CompileUnit::addComplexAddress(DbgVariable *&DV, DIE *Die,
270                                     unsigned Attribute,
271                                     const MachineLocation &Location) {
272   DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
273   unsigned N = DV->getNumAddrElements();
274   unsigned i = 0;
275   if (Location.isReg()) {
276     if (N >= 2 && DV->getAddrElement(0) == DIBuilder::OpPlus) {
277       // If first address element is OpPlus then emit
278       // DW_OP_breg + Offset instead of DW_OP_reg + Offset.
279       addRegisterOffset(Block, Location.getReg(), DV->getAddrElement(1));
280       i = 2;
281     } else
282       addRegisterOp(Block, Location.getReg());
283   }
284   else
285     addRegisterOffset(Block, Location.getReg(), Location.getOffset());
286
287   for (;i < N; ++i) {
288     uint64_t Element = DV->getAddrElement(i);
289     if (Element == DIBuilder::OpPlus) {
290       addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_plus_uconst);
291       addUInt(Block, 0, dwarf::DW_FORM_udata, DV->getAddrElement(++i));
292     } else if (Element == DIBuilder::OpDeref) {
293       addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
294     } else llvm_unreachable("unknown DIBuilder Opcode");
295   }
296
297   // Now attach the location information to the DIE.
298   addBlock(Die, Attribute, 0, Block);
299 }
300
301 /* Byref variables, in Blocks, are declared by the programmer as "SomeType
302    VarName;", but the compiler creates a __Block_byref_x_VarName struct, and
303    gives the variable VarName either the struct, or a pointer to the struct, as
304    its type.  This is necessary for various behind-the-scenes things the
305    compiler needs to do with by-reference variables in Blocks.
306
307    However, as far as the original *programmer* is concerned, the variable
308    should still have type 'SomeType', as originally declared.
309
310    The function getBlockByrefType dives into the __Block_byref_x_VarName
311    struct to find the original type of the variable, which is then assigned to
312    the variable's Debug Information Entry as its real type.  So far, so good.
313    However now the debugger will expect the variable VarName to have the type
314    SomeType.  So we need the location attribute for the variable to be an
315    expression that explains to the debugger how to navigate through the
316    pointers and struct to find the actual variable of type SomeType.
317
318    The following function does just that.  We start by getting
319    the "normal" location for the variable. This will be the location
320    of either the struct __Block_byref_x_VarName or the pointer to the
321    struct __Block_byref_x_VarName.
322
323    The struct will look something like:
324
325    struct __Block_byref_x_VarName {
326      ... <various fields>
327      struct __Block_byref_x_VarName *forwarding;
328      ... <various other fields>
329      SomeType VarName;
330      ... <maybe more fields>
331    };
332
333    If we are given the struct directly (as our starting point) we
334    need to tell the debugger to:
335
336    1).  Add the offset of the forwarding field.
337
338    2).  Follow that pointer to get the real __Block_byref_x_VarName
339    struct to use (the real one may have been copied onto the heap).
340
341    3).  Add the offset for the field VarName, to find the actual variable.
342
343    If we started with a pointer to the struct, then we need to
344    dereference that pointer first, before the other steps.
345    Translating this into DWARF ops, we will need to append the following
346    to the current location description for the variable:
347
348    DW_OP_deref                    -- optional, if we start with a pointer
349    DW_OP_plus_uconst <forward_fld_offset>
350    DW_OP_deref
351    DW_OP_plus_uconst <varName_fld_offset>
352
353    That is what this function does.  */
354
355 /// addBlockByrefAddress - Start with the address based on the location
356 /// provided, and generate the DWARF information necessary to find the
357 /// actual Block variable (navigating the Block struct) based on the
358 /// starting location.  Add the DWARF information to the die.  For
359 /// more information, read large comment just above here.
360 ///
361 void CompileUnit::addBlockByrefAddress(DbgVariable *&DV, DIE *Die,
362                                        unsigned Attribute,
363                                        const MachineLocation &Location) {
364   DIType Ty = DV->getType();
365   DIType TmpTy = Ty;
366   unsigned Tag = Ty.getTag();
367   bool isPointer = false;
368
369   StringRef varName = DV->getName();
370
371   if (Tag == dwarf::DW_TAG_pointer_type) {
372     DIDerivedType DTy = DIDerivedType(Ty);
373     TmpTy = DTy.getTypeDerivedFrom();
374     isPointer = true;
375   }
376
377   DICompositeType blockStruct = DICompositeType(TmpTy);
378
379   // Find the __forwarding field and the variable field in the __Block_byref
380   // struct.
381   DIArray Fields = blockStruct.getTypeArray();
382   DIDescriptor varField = DIDescriptor();
383   DIDescriptor forwardingField = DIDescriptor();
384
385   for (unsigned i = 0, N = Fields.getNumElements(); i < N; ++i) {
386     DIDescriptor Element = Fields.getElement(i);
387     DIDerivedType DT = DIDerivedType(Element);
388     StringRef fieldName = DT.getName();
389     if (fieldName == "__forwarding")
390       forwardingField = Element;
391     else if (fieldName == varName)
392       varField = Element;
393   }
394
395   // Get the offsets for the forwarding field and the variable field.
396   unsigned forwardingFieldOffset =
397     DIDerivedType(forwardingField).getOffsetInBits() >> 3;
398   unsigned varFieldOffset =
399     DIDerivedType(varField).getOffsetInBits() >> 3;
400
401   // Decode the original location, and use that as the start of the byref
402   // variable's location.
403   const TargetRegisterInfo *RI = Asm->TM.getRegisterInfo();
404   unsigned Reg = RI->getDwarfRegNum(Location.getReg(), false);
405   DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
406
407   if (Location.isReg()) {
408     if (Reg < 32)
409       addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_reg0 + Reg);
410     else {
411       addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_regx);
412       addUInt(Block, 0, dwarf::DW_FORM_udata, Reg);
413     }
414   } else {
415     if (Reg < 32)
416       addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_breg0 + Reg);
417     else {
418       addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_bregx);
419       addUInt(Block, 0, dwarf::DW_FORM_udata, Reg);
420     }
421
422     addUInt(Block, 0, dwarf::DW_FORM_sdata, Location.getOffset());
423   }
424
425   // If we started with a pointer to the __Block_byref... struct, then
426   // the first thing we need to do is dereference the pointer (DW_OP_deref).
427   if (isPointer)
428     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
429
430   // Next add the offset for the '__forwarding' field:
431   // DW_OP_plus_uconst ForwardingFieldOffset.  Note there's no point in
432   // adding the offset if it's 0.
433   if (forwardingFieldOffset > 0) {
434     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_plus_uconst);
435     addUInt(Block, 0, dwarf::DW_FORM_udata, forwardingFieldOffset);
436   }
437
438   // Now dereference the __forwarding field to get to the real __Block_byref
439   // struct:  DW_OP_deref.
440   addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
441
442   // Now that we've got the real __Block_byref... struct, add the offset
443   // for the variable's field to get to the location of the actual variable:
444   // DW_OP_plus_uconst varFieldOffset.  Again, don't add if it's 0.
445   if (varFieldOffset > 0) {
446     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_plus_uconst);
447     addUInt(Block, 0, dwarf::DW_FORM_udata, varFieldOffset);
448   }
449
450   // Now attach the location information to the DIE.
451   addBlock(Die, Attribute, 0, Block);
452 }
453
454 /// isTypeSigned - Return true if the type is signed.
455 static bool isTypeSigned(DIType Ty, int *SizeInBits) {
456   if (Ty.isDerivedType())
457     return isTypeSigned(DIDerivedType(Ty).getTypeDerivedFrom(), SizeInBits);
458   if (Ty.isBasicType())
459     if (DIBasicType(Ty).getEncoding() == dwarf::DW_ATE_signed
460         || DIBasicType(Ty).getEncoding() == dwarf::DW_ATE_signed_char) {
461       *SizeInBits = Ty.getSizeInBits();
462       return true;
463     }
464   return false;
465 }
466
467 /// addConstantValue - Add constant value entry in variable DIE.
468 bool CompileUnit::addConstantValue(DIE *Die, const MachineOperand &MO,
469                                    DIType Ty) {
470   assert(MO.isImm() && "Invalid machine operand!");
471   DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
472   int SizeInBits = -1;
473   bool SignedConstant = isTypeSigned(Ty, &SizeInBits);
474   unsigned Form = SignedConstant ? dwarf::DW_FORM_sdata : dwarf::DW_FORM_udata;
475   switch (SizeInBits) {
476     case 8:  Form = dwarf::DW_FORM_data1; break;
477     case 16: Form = dwarf::DW_FORM_data2; break;
478     case 32: Form = dwarf::DW_FORM_data4; break;
479     case 64: Form = dwarf::DW_FORM_data8; break;
480     default: break;
481   }
482   SignedConstant ? addSInt(Block, 0, Form, MO.getImm()) 
483     : addUInt(Block, 0, Form, MO.getImm());
484
485   addBlock(Die, dwarf::DW_AT_const_value, 0, Block);
486   return true;
487 }
488
489 /// addConstantFPValue - Add constant value entry in variable DIE.
490 bool CompileUnit::addConstantFPValue(DIE *Die, const MachineOperand &MO) {
491   assert (MO.isFPImm() && "Invalid machine operand!");
492   DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
493   APFloat FPImm = MO.getFPImm()->getValueAPF();
494
495   // Get the raw data form of the floating point.
496   const APInt FltVal = FPImm.bitcastToAPInt();
497   const char *FltPtr = (const char*)FltVal.getRawData();
498
499   int NumBytes = FltVal.getBitWidth() / 8; // 8 bits per byte.
500   bool LittleEndian = Asm->getTargetData().isLittleEndian();
501   int Incr = (LittleEndian ? 1 : -1);
502   int Start = (LittleEndian ? 0 : NumBytes - 1);
503   int Stop = (LittleEndian ? NumBytes : -1);
504
505   // Output the constant to DWARF one byte at a time.
506   for (; Start != Stop; Start += Incr)
507     addUInt(Block, 0, dwarf::DW_FORM_data1,
508             (unsigned char)0xFF & FltPtr[Start]);
509
510   addBlock(Die, dwarf::DW_AT_const_value, 0, Block);
511   return true;
512 }
513
514 /// addConstantValue - Add constant value entry in variable DIE.
515 bool CompileUnit::addConstantValue(DIE *Die, const ConstantInt *CI,
516                                    bool Unsigned) {
517   unsigned CIBitWidth = CI->getBitWidth();
518   if (CIBitWidth <= 64) {
519     unsigned form = 0;
520     switch (CIBitWidth) {
521     case 8: form = dwarf::DW_FORM_data1; break;
522     case 16: form = dwarf::DW_FORM_data2; break;
523     case 32: form = dwarf::DW_FORM_data4; break;
524     case 64: form = dwarf::DW_FORM_data8; break;
525     default: 
526       form = Unsigned ? dwarf::DW_FORM_udata : dwarf::DW_FORM_sdata;
527     }
528     if (Unsigned)
529       addUInt(Die, dwarf::DW_AT_const_value, form, CI->getZExtValue());
530     else
531       addSInt(Die, dwarf::DW_AT_const_value, form, CI->getSExtValue());
532     return true;
533   }
534
535   DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
536
537   // Get the raw data form of the large APInt.
538   const APInt Val = CI->getValue();
539   const uint64_t *Ptr64 = Val.getRawData();
540
541   int NumBytes = Val.getBitWidth() / 8; // 8 bits per byte.
542   bool LittleEndian = Asm->getTargetData().isLittleEndian();
543
544   // Output the constant to DWARF one byte at a time.
545   for (int i = 0; i < NumBytes; i++) {
546     uint8_t c;
547     if (LittleEndian)
548       c = Ptr64[i / 8] >> (8 * (i & 7));
549     else
550       c = Ptr64[(NumBytes - 1 - i) / 8] >> (8 * ((NumBytes - 1 - i) & 7));
551     addUInt(Block, 0, dwarf::DW_FORM_data1, c);
552   }
553
554   addBlock(Die, dwarf::DW_AT_const_value, 0, Block);
555   return true;
556 }
557
558 /// addTemplateParams - Add template parameters in buffer.
559 void CompileUnit::addTemplateParams(DIE &Buffer, DIArray TParams) {
560   // Add template parameters.
561   for (unsigned i = 0, e = TParams.getNumElements(); i != e; ++i) {
562     DIDescriptor Element = TParams.getElement(i);
563     if (Element.isTemplateTypeParameter())
564       Buffer.addChild(getOrCreateTemplateTypeParameterDIE(
565                         DITemplateTypeParameter(Element)));
566     else if (Element.isTemplateValueParameter())
567       Buffer.addChild(getOrCreateTemplateValueParameterDIE(
568                         DITemplateValueParameter(Element)));
569   }
570 }
571
572 /// addToContextOwner - Add Die into the list of its context owner's children.
573 void CompileUnit::addToContextOwner(DIE *Die, DIDescriptor Context) {
574   if (Context.isType()) {
575     DIE *ContextDIE = getOrCreateTypeDIE(DIType(Context));
576     ContextDIE->addChild(Die);
577   } else if (Context.isNameSpace()) {
578     DIE *ContextDIE = getOrCreateNameSpace(DINameSpace(Context));
579     ContextDIE->addChild(Die);
580   } else if (Context.isSubprogram()) {
581     DIE *ContextDIE = getOrCreateSubprogramDIE(DISubprogram(Context));
582     ContextDIE->addChild(Die);
583   } else if (DIE *ContextDIE = getDIE(Context))
584     ContextDIE->addChild(Die);
585   else
586     addDie(Die);
587 }
588
589 /// getOrCreateTypeDIE - Find existing DIE or create new DIE for the
590 /// given DIType.
591 DIE *CompileUnit::getOrCreateTypeDIE(const MDNode *TyNode) {
592   DIType Ty(TyNode);
593   if (!Ty.Verify())
594     return NULL;
595   DIE *TyDIE = getDIE(Ty);
596   if (TyDIE)
597     return TyDIE;
598
599   // Create new type.
600   TyDIE = new DIE(dwarf::DW_TAG_base_type);
601   insertDIE(Ty, TyDIE);
602   if (Ty.isBasicType())
603     constructTypeDIE(*TyDIE, DIBasicType(Ty));
604   else if (Ty.isCompositeType())
605     constructTypeDIE(*TyDIE, DICompositeType(Ty));
606   else {
607     assert(Ty.isDerivedType() && "Unknown kind of DIType");
608     constructTypeDIE(*TyDIE, DIDerivedType(Ty));
609   }
610   // If this is a named finished type then include it in the list of types
611   // for the accelerator tables.
612   if (!Ty.getName().empty() && !Ty.isForwardDecl()) {
613     bool IsImplementation = 0;
614     if (Ty.isCompositeType()) {
615       DICompositeType CT(Ty);
616       IsImplementation = (CT.getRunTimeLang() == 0) ||
617         CT.isObjcClassComplete();;
618     }
619     
620     addAccelType(Ty.getName(),
621                  std::make_pair(TyDIE,
622                                 (IsImplementation ?
623                                DwarfAccelTable::eTypeFlagClassIsImplementation :
624                                  0)));
625   }
626   
627   addToContextOwner(TyDIE, Ty.getContext());
628   return TyDIE;
629 }
630
631 /// addType - Add a new type attribute to the specified entity.
632 void CompileUnit::addType(DIE *Entity, DIType Ty) {
633   if (!Ty.Verify())
634     return;
635
636   // Check for pre-existence.
637   DIEEntry *Entry = getDIEEntry(Ty);
638   // If it exists then use the existing value.
639   if (Entry) {
640     Entity->addValue(dwarf::DW_AT_type, dwarf::DW_FORM_ref4, Entry);
641     return;
642   }
643
644   // Construct type.
645   DIE *Buffer = getOrCreateTypeDIE(Ty);
646
647   // Set up proxy.
648   Entry = createDIEEntry(Buffer);
649   insertDIEEntry(Ty, Entry);
650   Entity->addValue(dwarf::DW_AT_type, dwarf::DW_FORM_ref4, Entry);
651
652   // If this is a complete composite type then include it in the
653   // list of global types.
654   addGlobalType(Ty);
655 }
656
657 /// addGlobalType - Add a new global type to the compile unit.
658 ///
659 void CompileUnit::addGlobalType(DIType Ty) {
660   DIDescriptor Context = Ty.getContext();
661   if (Ty.isCompositeType() && !Ty.getName().empty() && !Ty.isForwardDecl() 
662       && (!Context || Context.isCompileUnit() || Context.isFile() 
663           || Context.isNameSpace()))
664     if (DIEEntry *Entry = getDIEEntry(Ty))
665       GlobalTypes[Ty.getName()] = Entry->getEntry();
666 }
667
668 /// addPubTypes - Add type for pubtypes section.
669 void CompileUnit::addPubTypes(DISubprogram SP) {
670   DICompositeType SPTy = SP.getType();
671   unsigned SPTag = SPTy.getTag();
672   if (SPTag != dwarf::DW_TAG_subroutine_type)
673     return;
674
675   DIArray Args = SPTy.getTypeArray();
676   for (unsigned i = 0, e = Args.getNumElements(); i != e; ++i) {
677     DIType ATy(Args.getElement(i));
678     if (!ATy.Verify())
679       continue;
680     addGlobalType(ATy);
681   }
682 }
683
684 /// constructTypeDIE - Construct basic type die from DIBasicType.
685 void CompileUnit::constructTypeDIE(DIE &Buffer, DIBasicType BTy) {
686   // Get core information.
687   StringRef Name = BTy.getName();
688   // Add name if not anonymous or intermediate type.
689   if (!Name.empty())
690     addString(&Buffer, dwarf::DW_AT_name, Name);
691
692   if (BTy.getTag() == dwarf::DW_TAG_unspecified_type) {
693     Buffer.setTag(dwarf::DW_TAG_unspecified_type);
694     // Unspecified types has only name, nothing else.
695     return;
696   }
697
698   Buffer.setTag(dwarf::DW_TAG_base_type);
699   addUInt(&Buffer, dwarf::DW_AT_encoding, dwarf::DW_FORM_data1,
700           BTy.getEncoding());
701
702   uint64_t Size = BTy.getSizeInBits() >> 3;
703   addUInt(&Buffer, dwarf::DW_AT_byte_size, 0, Size);
704 }
705
706 /// constructTypeDIE - Construct derived type die from DIDerivedType.
707 void CompileUnit::constructTypeDIE(DIE &Buffer, DIDerivedType DTy) {
708   // Get core information.
709   StringRef Name = DTy.getName();
710   uint64_t Size = DTy.getSizeInBits() >> 3;
711   unsigned Tag = DTy.getTag();
712
713   // FIXME - Workaround for templates.
714   if (Tag == dwarf::DW_TAG_inheritance) Tag = dwarf::DW_TAG_reference_type;
715
716   Buffer.setTag(Tag);
717
718   // Map to main type, void will not have a type.
719   DIType FromTy = DTy.getTypeDerivedFrom();
720   addType(&Buffer, FromTy);
721
722   // Add name if not anonymous or intermediate type.
723   if (!Name.empty())
724     addString(&Buffer, dwarf::DW_AT_name, Name);
725
726   // Add size if non-zero (derived types might be zero-sized.)
727   if (Size)
728     addUInt(&Buffer, dwarf::DW_AT_byte_size, 0, Size);
729
730   // Add source line info if available and TyDesc is not a forward declaration.
731   if (!DTy.isForwardDecl())
732     addSourceLine(&Buffer, DTy);
733 }
734
735 /// constructTypeDIE - Construct type DIE from DICompositeType.
736 void CompileUnit::constructTypeDIE(DIE &Buffer, DICompositeType CTy) {
737   // Get core information.
738   StringRef Name = CTy.getName();
739
740   uint64_t Size = CTy.getSizeInBits() >> 3;
741   unsigned Tag = CTy.getTag();
742   Buffer.setTag(Tag);
743
744   switch (Tag) {
745   case dwarf::DW_TAG_vector_type:
746   case dwarf::DW_TAG_array_type:
747     constructArrayTypeDIE(Buffer, &CTy);
748     break;
749   case dwarf::DW_TAG_enumeration_type: {
750     DIArray Elements = CTy.getTypeArray();
751
752     // Add enumerators to enumeration type.
753     for (unsigned i = 0, N = Elements.getNumElements(); i < N; ++i) {
754       DIE *ElemDie = NULL;
755       DIDescriptor Enum(Elements.getElement(i));
756       if (Enum.isEnumerator()) {
757         ElemDie = constructEnumTypeDIE(DIEnumerator(Enum));
758         Buffer.addChild(ElemDie);
759       }
760     }
761   }
762     break;
763   case dwarf::DW_TAG_subroutine_type: {
764     // Add return type.
765     DIArray Elements = CTy.getTypeArray();
766     DIDescriptor RTy = Elements.getElement(0);
767     addType(&Buffer, DIType(RTy));
768
769     bool isPrototyped = true;
770     // Add arguments.
771     for (unsigned i = 1, N = Elements.getNumElements(); i < N; ++i) {
772       DIDescriptor Ty = Elements.getElement(i);
773       if (Ty.isUnspecifiedParameter()) {
774         DIE *Arg = new DIE(dwarf::DW_TAG_unspecified_parameters);
775         Buffer.addChild(Arg);
776         isPrototyped = false;
777       } else {
778         DIE *Arg = new DIE(dwarf::DW_TAG_formal_parameter);
779         addType(Arg, DIType(Ty));
780         Buffer.addChild(Arg);
781       }
782     }
783     // Add prototype flag.
784     if (isPrototyped)
785       addUInt(&Buffer, dwarf::DW_AT_prototyped, dwarf::DW_FORM_flag, 1);
786   }
787     break;
788   case dwarf::DW_TAG_structure_type:
789   case dwarf::DW_TAG_union_type:
790   case dwarf::DW_TAG_class_type: {
791     // Add elements to structure type.
792     DIArray Elements = CTy.getTypeArray();
793
794     // A forward struct declared type may not have elements available.
795     unsigned N = Elements.getNumElements();
796     if (N == 0)
797       break;
798
799     // Add elements to structure type.
800     for (unsigned i = 0; i < N; ++i) {
801       DIDescriptor Element = Elements.getElement(i);
802       DIE *ElemDie = NULL;
803       if (Element.isSubprogram()) {
804         DISubprogram SP(Element);
805         ElemDie = getOrCreateSubprogramDIE(DISubprogram(Element));
806         if (SP.isProtected())
807           addUInt(ElemDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
808                   dwarf::DW_ACCESS_protected);
809         else if (SP.isPrivate())
810           addUInt(ElemDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
811                   dwarf::DW_ACCESS_private);
812         else 
813           addUInt(ElemDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
814             dwarf::DW_ACCESS_public);
815         if (SP.isExplicit())
816           addUInt(ElemDie, dwarf::DW_AT_explicit, dwarf::DW_FORM_flag, 1);
817       }
818       else if (Element.isVariable()) {
819         DIVariable DV(Element);
820         ElemDie = new DIE(dwarf::DW_TAG_variable);
821         addString(ElemDie, dwarf::DW_AT_name, DV.getName());
822         addType(ElemDie, DV.getType());
823         addUInt(ElemDie, dwarf::DW_AT_declaration, dwarf::DW_FORM_flag, 1);
824         addUInt(ElemDie, dwarf::DW_AT_external, dwarf::DW_FORM_flag, 1);
825         addSourceLine(ElemDie, DV);
826       } else if (Element.isDerivedType())
827         ElemDie = createMemberDIE(DIDerivedType(Element));
828       else
829         continue;
830       Buffer.addChild(ElemDie);
831     }
832
833     if (CTy.isAppleBlockExtension())
834       addUInt(&Buffer, dwarf::DW_AT_APPLE_block, dwarf::DW_FORM_flag, 1);
835
836     unsigned RLang = CTy.getRunTimeLang();
837     if (RLang)
838       addUInt(&Buffer, dwarf::DW_AT_APPLE_runtime_class,
839               dwarf::DW_FORM_data1, RLang);
840
841     DICompositeType ContainingType = CTy.getContainingType();
842     if (DIDescriptor(ContainingType).isCompositeType())
843       addDIEEntry(&Buffer, dwarf::DW_AT_containing_type, dwarf::DW_FORM_ref4,
844                   getOrCreateTypeDIE(DIType(ContainingType)));
845     else {
846       DIDescriptor Context = CTy.getContext();
847       addToContextOwner(&Buffer, Context);
848     }
849
850     if (CTy.isObjcClassComplete())
851       addUInt(&Buffer, dwarf::DW_AT_APPLE_objc_complete_type,
852               dwarf::DW_FORM_flag, 1);
853
854     // Add template parameters to a class, structure or union types.
855     // FIXME: The support isn't in the metadata for this yet.
856     if (Tag == dwarf::DW_TAG_class_type ||
857         Tag == dwarf::DW_TAG_structure_type ||
858         Tag == dwarf::DW_TAG_union_type)
859       addTemplateParams(Buffer, CTy.getTemplateParams());
860
861     break;
862   }
863   default:
864     break;
865   }
866
867   // Add name if not anonymous or intermediate type.
868   if (!Name.empty())
869     addString(&Buffer, dwarf::DW_AT_name, Name);
870
871   if (Tag == dwarf::DW_TAG_enumeration_type || Tag == dwarf::DW_TAG_class_type
872       || Tag == dwarf::DW_TAG_structure_type || Tag == dwarf::DW_TAG_union_type)
873   {
874     // Add size if non-zero (derived types might be zero-sized.)
875     if (Size)
876       addUInt(&Buffer, dwarf::DW_AT_byte_size, 0, Size);
877     else {
878       // Add zero size if it is not a forward declaration.
879       if (CTy.isForwardDecl())
880         addUInt(&Buffer, dwarf::DW_AT_declaration, dwarf::DW_FORM_flag, 1);
881       else
882         addUInt(&Buffer, dwarf::DW_AT_byte_size, 0, 0);
883     }
884
885     // Add source line info if available.
886     if (!CTy.isForwardDecl())
887       addSourceLine(&Buffer, CTy);
888   }
889 }
890
891 /// getOrCreateTemplateTypeParameterDIE - Find existing DIE or create new DIE 
892 /// for the given DITemplateTypeParameter.
893 DIE *
894 CompileUnit::getOrCreateTemplateTypeParameterDIE(DITemplateTypeParameter TP) {
895   DIE *ParamDIE = getDIE(TP);
896   if (ParamDIE)
897     return ParamDIE;
898
899   ParamDIE = new DIE(dwarf::DW_TAG_template_type_parameter);
900   addType(ParamDIE, TP.getType());
901   addString(ParamDIE, dwarf::DW_AT_name, TP.getName());
902   return ParamDIE;
903 }
904
905 /// getOrCreateTemplateValueParameterDIE - Find existing DIE or create new DIE 
906 /// for the given DITemplateValueParameter.
907 DIE *
908 CompileUnit::getOrCreateTemplateValueParameterDIE(DITemplateValueParameter TPV) {
909   DIE *ParamDIE = getDIE(TPV);
910   if (ParamDIE)
911     return ParamDIE;
912
913   ParamDIE = new DIE(dwarf::DW_TAG_template_value_parameter);
914   addType(ParamDIE, TPV.getType());
915   if (!TPV.getName().empty())
916     addString(ParamDIE, dwarf::DW_AT_name, TPV.getName());
917   addUInt(ParamDIE, dwarf::DW_AT_const_value, dwarf::DW_FORM_udata, 
918           TPV.getValue());
919   return ParamDIE;
920 }
921
922 /// getOrCreateNameSpace - Create a DIE for DINameSpace.
923 DIE *CompileUnit::getOrCreateNameSpace(DINameSpace NS) {
924   DIE *NDie = getDIE(NS);
925   if (NDie)
926     return NDie;
927   NDie = new DIE(dwarf::DW_TAG_namespace);
928   insertDIE(NS, NDie);
929   if (!NS.getName().empty()) {
930     addString(NDie, dwarf::DW_AT_name, NS.getName());
931     addAccelNamespace(NS.getName(), NDie);
932   } else
933     addAccelNamespace("(anonymous namespace)", NDie);
934   addSourceLine(NDie, NS);
935   addToContextOwner(NDie, NS.getContext());
936   return NDie;
937 }
938
939 /// getRealLinkageName - If special LLVM prefix that is used to inform the asm
940 /// printer to not emit usual symbol prefix before the symbol name is used then
941 /// return linkage name after skipping this special LLVM prefix.
942 static StringRef getRealLinkageName(StringRef LinkageName) {
943   char One = '\1';
944   if (LinkageName.startswith(StringRef(&One, 1)))
945     return LinkageName.substr(1);
946   return LinkageName;
947 }
948
949 /// getOrCreateSubprogramDIE - Create new DIE using SP.
950 DIE *CompileUnit::getOrCreateSubprogramDIE(DISubprogram SP) {
951   DIE *SPDie = getDIE(SP);
952   if (SPDie)
953     return SPDie;
954
955   DISubprogram SPDecl = SP.getFunctionDeclaration();
956   DIE *DeclDie = NULL;
957   if (SPDecl.isSubprogram()) {
958     DeclDie = getOrCreateSubprogramDIE(SPDecl);
959   }
960
961   SPDie = new DIE(dwarf::DW_TAG_subprogram);
962   
963   // DW_TAG_inlined_subroutine may refer to this DIE.
964   insertDIE(SP, SPDie);
965   
966   // Add to context owner.
967   addToContextOwner(SPDie, SP.getContext());
968
969   // Add function template parameters.
970   addTemplateParams(*SPDie, SP.getTemplateParams());
971
972   StringRef LinkageName = SP.getLinkageName();
973   if (!LinkageName.empty())
974     addString(SPDie, dwarf::DW_AT_MIPS_linkage_name,
975               getRealLinkageName(LinkageName));
976
977   // If this DIE is going to refer declaration info using AT_specification
978   // then there is no need to add other attributes.
979   if (DeclDie) {
980     // Refer function declaration directly.
981     addDIEEntry(SPDie, dwarf::DW_AT_specification, dwarf::DW_FORM_ref4,
982                 DeclDie);
983
984     return SPDie;
985   }
986
987   // Constructors and operators for anonymous aggregates do not have names.
988   if (!SP.getName().empty())
989     addString(SPDie, dwarf::DW_AT_name, SP.getName());
990
991   addSourceLine(SPDie, SP);
992
993   if (SP.isPrototyped()) 
994     addUInt(SPDie, dwarf::DW_AT_prototyped, dwarf::DW_FORM_flag, 1);
995
996   // Add Return Type.
997   DICompositeType SPTy = SP.getType();
998   DIArray Args = SPTy.getTypeArray();
999   unsigned SPTag = SPTy.getTag();
1000
1001   if (Args.getNumElements() == 0 || SPTag != dwarf::DW_TAG_subroutine_type)
1002     addType(SPDie, SPTy);
1003   else
1004     addType(SPDie, DIType(Args.getElement(0)));
1005
1006   unsigned VK = SP.getVirtuality();
1007   if (VK) {
1008     addUInt(SPDie, dwarf::DW_AT_virtuality, dwarf::DW_FORM_data1, VK);
1009     DIEBlock *Block = getDIEBlock();
1010     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_constu);
1011     addUInt(Block, 0, dwarf::DW_FORM_udata, SP.getVirtualIndex());
1012     addBlock(SPDie, dwarf::DW_AT_vtable_elem_location, 0, Block);
1013     ContainingTypeMap.insert(std::make_pair(SPDie,
1014                                             SP.getContainingType()));
1015   }
1016
1017   if (!SP.isDefinition()) {
1018     addUInt(SPDie, dwarf::DW_AT_declaration, dwarf::DW_FORM_flag, 1);
1019     
1020     // Add arguments. Do not add arguments for subprogram definition. They will
1021     // be handled while processing variables.
1022     DICompositeType SPTy = SP.getType();
1023     DIArray Args = SPTy.getTypeArray();
1024     unsigned SPTag = SPTy.getTag();
1025
1026     if (SPTag == dwarf::DW_TAG_subroutine_type)
1027       for (unsigned i = 1, N =  Args.getNumElements(); i < N; ++i) {
1028         DIE *Arg = new DIE(dwarf::DW_TAG_formal_parameter);
1029         DIType ATy = DIType(DIType(Args.getElement(i)));
1030         addType(Arg, ATy);
1031         if (ATy.isArtificial())
1032           addUInt(Arg, dwarf::DW_AT_artificial, dwarf::DW_FORM_flag, 1);
1033         SPDie->addChild(Arg);
1034       }
1035   }
1036
1037   if (SP.isArtificial())
1038     addUInt(SPDie, dwarf::DW_AT_artificial, dwarf::DW_FORM_flag, 1);
1039
1040   if (!SP.isLocalToUnit())
1041     addUInt(SPDie, dwarf::DW_AT_external, dwarf::DW_FORM_flag, 1);
1042
1043   if (SP.isOptimized())
1044     addUInt(SPDie, dwarf::DW_AT_APPLE_optimized, dwarf::DW_FORM_flag, 1);
1045
1046   if (unsigned isa = Asm->getISAEncoding()) {
1047     addUInt(SPDie, dwarf::DW_AT_APPLE_isa, dwarf::DW_FORM_flag, isa);
1048   }
1049
1050   return SPDie;
1051 }
1052
1053 // Return const expression if value is a GEP to access merged global
1054 // constant. e.g.
1055 // i8* getelementptr ({ i8, i8, i8, i8 }* @_MergedGlobals, i32 0, i32 0)
1056 static const ConstantExpr *getMergedGlobalExpr(const Value *V) {
1057   const ConstantExpr *CE = dyn_cast_or_null<ConstantExpr>(V);
1058   if (!CE || CE->getNumOperands() != 3 ||
1059       CE->getOpcode() != Instruction::GetElementPtr)
1060     return NULL;
1061
1062   // First operand points to a global struct.
1063   Value *Ptr = CE->getOperand(0);
1064   if (!isa<GlobalValue>(Ptr) ||
1065       !isa<StructType>(cast<PointerType>(Ptr->getType())->getElementType()))
1066     return NULL;
1067
1068   // Second operand is zero.
1069   const ConstantInt *CI = dyn_cast_or_null<ConstantInt>(CE->getOperand(1));
1070   if (!CI || !CI->isZero())
1071     return NULL;
1072
1073   // Third operand is offset.
1074   if (!isa<ConstantInt>(CE->getOperand(2)))
1075     return NULL;
1076
1077   return CE;
1078 }
1079
1080 /// createGlobalVariableDIE - create global variable DIE.
1081 void CompileUnit::createGlobalVariableDIE(const MDNode *N) {
1082   // Check for pre-existence.
1083   if (getDIE(N))
1084     return;
1085
1086   DIGlobalVariable GV(N);
1087   if (!GV.Verify())
1088     return;
1089
1090   DIE *VariableDIE = new DIE(GV.getTag());
1091   // Add to map.
1092   insertDIE(N, VariableDIE);
1093
1094   // Add name.
1095   addString(VariableDIE, dwarf::DW_AT_name, GV.getDisplayName());
1096   StringRef LinkageName = GV.getLinkageName();
1097   bool isGlobalVariable = GV.getGlobal() != NULL;
1098   if (!LinkageName.empty() && isGlobalVariable)
1099     addString(VariableDIE, dwarf::DW_AT_MIPS_linkage_name,
1100               getRealLinkageName(LinkageName));
1101   // Add type.
1102   DIType GTy = GV.getType();
1103   addType(VariableDIE, GTy);
1104
1105   // Add scoping info.
1106   if (!GV.isLocalToUnit())
1107     addUInt(VariableDIE, dwarf::DW_AT_external, dwarf::DW_FORM_flag, 1);
1108
1109   // Add line number info.
1110   addSourceLine(VariableDIE, GV);
1111   // Add to context owner.
1112   DIDescriptor GVContext = GV.getContext();
1113   addToContextOwner(VariableDIE, GVContext);
1114   // Add location.
1115   bool addToAccelTable = false;
1116   DIE *VariableSpecDIE = NULL;
1117   if (isGlobalVariable) {
1118     addToAccelTable = true;
1119     DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
1120     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_addr);
1121     addLabel(Block, 0, dwarf::DW_FORM_udata,
1122              Asm->Mang->getSymbol(GV.getGlobal()));
1123     // Do not create specification DIE if context is either compile unit
1124     // or a subprogram.
1125     if (GVContext && GV.isDefinition() && !GVContext.isCompileUnit() &&
1126         !GVContext.isFile() && !isSubprogramContext(GVContext)) {
1127       // Create specification DIE.
1128       VariableSpecDIE = new DIE(dwarf::DW_TAG_variable);
1129       addDIEEntry(VariableSpecDIE, dwarf::DW_AT_specification,
1130                   dwarf::DW_FORM_ref4, VariableDIE);
1131       addBlock(VariableSpecDIE, dwarf::DW_AT_location, 0, Block);
1132       addUInt(VariableDIE, dwarf::DW_AT_declaration, dwarf::DW_FORM_flag,
1133                      1);
1134       addDie(VariableSpecDIE);
1135     } else {
1136       addBlock(VariableDIE, dwarf::DW_AT_location, 0, Block);
1137     }
1138   } else if (const ConstantInt *CI = 
1139              dyn_cast_or_null<ConstantInt>(GV.getConstant()))
1140     addConstantValue(VariableDIE, CI, GTy.isUnsignedDIType());
1141   else if (const ConstantExpr *CE = getMergedGlobalExpr(N->getOperand(11))) {
1142     addToAccelTable = true;
1143     // GV is a merged global.
1144     DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
1145     Value *Ptr = CE->getOperand(0);
1146     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_addr);
1147     addLabel(Block, 0, dwarf::DW_FORM_udata,
1148                     Asm->Mang->getSymbol(cast<GlobalValue>(Ptr)));
1149     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_constu);
1150     SmallVector<Value*, 3> Idx(CE->op_begin()+1, CE->op_end());
1151     addUInt(Block, 0, dwarf::DW_FORM_udata, 
1152                    Asm->getTargetData().getIndexedOffset(Ptr->getType(), Idx));
1153     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_plus);
1154     addBlock(VariableDIE, dwarf::DW_AT_location, 0, Block);
1155   }
1156
1157   if (addToAccelTable) {
1158     DIE *AddrDIE = VariableSpecDIE ? VariableSpecDIE : VariableDIE;
1159     addAccelName(GV.getName(), AddrDIE);
1160
1161     // If the linkage name is different than the name, go ahead and output
1162     // that as well into the name table.
1163     if (GV.getLinkageName() != "" && GV.getName() != GV.getLinkageName())
1164       addAccelName(GV.getLinkageName(), AddrDIE);
1165   }
1166
1167   return;
1168 }
1169
1170 /// constructSubrangeDIE - Construct subrange DIE from DISubrange.
1171 void CompileUnit::constructSubrangeDIE(DIE &Buffer, DISubrange SR, DIE *IndexTy){
1172   DIE *DW_Subrange = new DIE(dwarf::DW_TAG_subrange_type);
1173   addDIEEntry(DW_Subrange, dwarf::DW_AT_type, dwarf::DW_FORM_ref4, IndexTy);
1174   uint64_t L = SR.getLo();
1175   uint64_t H = SR.getHi();
1176
1177   // The L value defines the lower bounds which is typically zero for C/C++. The
1178   // H value is the upper bounds.  Values are 64 bit.  H - L + 1 is the size
1179   // of the array. If L > H then do not emit DW_AT_lower_bound and 
1180   // DW_AT_upper_bound attributes. If L is zero and H is also zero then the
1181   // array has one element and in such case do not emit lower bound.
1182
1183   if (L > H) {
1184     Buffer.addChild(DW_Subrange);
1185     return;
1186   }
1187   if (L)
1188     addUInt(DW_Subrange, dwarf::DW_AT_lower_bound, 0, L);
1189   addUInt(DW_Subrange, dwarf::DW_AT_upper_bound, 0, H);
1190   Buffer.addChild(DW_Subrange);
1191 }
1192
1193 /// constructArrayTypeDIE - Construct array type DIE from DICompositeType.
1194 void CompileUnit::constructArrayTypeDIE(DIE &Buffer,
1195                                         DICompositeType *CTy) {
1196   Buffer.setTag(dwarf::DW_TAG_array_type);
1197   if (CTy->getTag() == dwarf::DW_TAG_vector_type)
1198     addUInt(&Buffer, dwarf::DW_AT_GNU_vector, dwarf::DW_FORM_flag, 1);
1199
1200   // Emit derived type.
1201   addType(&Buffer, CTy->getTypeDerivedFrom());
1202   DIArray Elements = CTy->getTypeArray();
1203
1204   // Get an anonymous type for index type.
1205   DIE *IdxTy = getIndexTyDie();
1206   if (!IdxTy) {
1207     // Construct an anonymous type for index type.
1208     IdxTy = new DIE(dwarf::DW_TAG_base_type);
1209     addUInt(IdxTy, dwarf::DW_AT_byte_size, 0, sizeof(int32_t));
1210     addUInt(IdxTy, dwarf::DW_AT_encoding, dwarf::DW_FORM_data1,
1211             dwarf::DW_ATE_signed);
1212     addDie(IdxTy);
1213     setIndexTyDie(IdxTy);
1214   }
1215
1216   // Add subranges to array type.
1217   for (unsigned i = 0, N = Elements.getNumElements(); i < N; ++i) {
1218     DIDescriptor Element = Elements.getElement(i);
1219     if (Element.getTag() == dwarf::DW_TAG_subrange_type)
1220       constructSubrangeDIE(Buffer, DISubrange(Element), IdxTy);
1221   }
1222 }
1223
1224 /// constructEnumTypeDIE - Construct enum type DIE from DIEnumerator.
1225 DIE *CompileUnit::constructEnumTypeDIE(DIEnumerator ETy) {
1226   DIE *Enumerator = new DIE(dwarf::DW_TAG_enumerator);
1227   StringRef Name = ETy.getName();
1228   addString(Enumerator, dwarf::DW_AT_name, Name);
1229   int64_t Value = ETy.getEnumValue();
1230   addSInt(Enumerator, dwarf::DW_AT_const_value, dwarf::DW_FORM_sdata, Value);
1231   return Enumerator;
1232 }
1233
1234 /// constructContainingTypeDIEs - Construct DIEs for types that contain
1235 /// vtables.
1236 void CompileUnit::constructContainingTypeDIEs() {
1237   for (DenseMap<DIE *, const MDNode *>::iterator CI = ContainingTypeMap.begin(),
1238          CE = ContainingTypeMap.end(); CI != CE; ++CI) {
1239     DIE *SPDie = CI->first;
1240     const MDNode *N = CI->second;
1241     if (!N) continue;
1242     DIE *NDie = getDIE(N);
1243     if (!NDie) continue;
1244     addDIEEntry(SPDie, dwarf::DW_AT_containing_type, dwarf::DW_FORM_ref4, NDie);
1245   }
1246 }
1247
1248 /// constructVariableDIE - Construct a DIE for the given DbgVariable.
1249 DIE *CompileUnit::constructVariableDIE(DbgVariable *DV, bool isScopeAbstract) {
1250   StringRef Name = DV->getName();
1251   if (Name.empty())
1252     return NULL;
1253
1254   // Translate tag to proper Dwarf tag.
1255   unsigned Tag = DV->getTag();
1256
1257   // Define variable debug information entry.
1258   DIE *VariableDie = new DIE(Tag);
1259   DbgVariable *AbsVar = DV->getAbstractVariable();
1260   DIE *AbsDIE = AbsVar ? AbsVar->getDIE() : NULL;
1261   if (AbsDIE)
1262     addDIEEntry(VariableDie, dwarf::DW_AT_abstract_origin,
1263                             dwarf::DW_FORM_ref4, AbsDIE);
1264   else {
1265     addString(VariableDie, dwarf::DW_AT_name, Name);
1266     addSourceLine(VariableDie, DV->getVariable());
1267     addType(VariableDie, DV->getType());
1268   }
1269
1270   if (DV->isArtificial())
1271     addUInt(VariableDie, dwarf::DW_AT_artificial,
1272                         dwarf::DW_FORM_flag, 1);
1273
1274   if (isScopeAbstract) {
1275     DV->setDIE(VariableDie);
1276     return VariableDie;
1277   }
1278
1279   // Add variable address.
1280
1281   unsigned Offset = DV->getDotDebugLocOffset();
1282   if (Offset != ~0U) {
1283     addLabel(VariableDie, dwarf::DW_AT_location,
1284                          dwarf::DW_FORM_data4,
1285                          Asm->GetTempSymbol("debug_loc", Offset));
1286     DV->setDIE(VariableDie);
1287     return VariableDie;
1288   }
1289
1290   // Check if variable is described by a DBG_VALUE instruction.
1291   if (const MachineInstr *DVInsn = DV->getMInsn()) {
1292     bool updated = false;
1293     if (DVInsn->getNumOperands() == 3) {
1294       if (DVInsn->getOperand(0).isReg()) {
1295         const MachineOperand RegOp = DVInsn->getOperand(0);
1296         const TargetRegisterInfo *TRI = Asm->TM.getRegisterInfo();
1297         if (DVInsn->getOperand(1).isImm() &&
1298             TRI->getFrameRegister(*Asm->MF) == RegOp.getReg()) {
1299           unsigned FrameReg = 0;
1300           const TargetFrameLowering *TFI = Asm->TM.getFrameLowering();
1301           int Offset = 
1302             TFI->getFrameIndexReference(*Asm->MF, 
1303                                         DVInsn->getOperand(1).getImm(), 
1304                                         FrameReg);
1305           MachineLocation Location(FrameReg, Offset);
1306           addVariableAddress(DV, VariableDie, Location);
1307           
1308         } else if (RegOp.getReg())
1309           addVariableAddress(DV, VariableDie, 
1310                                          MachineLocation(RegOp.getReg()));
1311         updated = true;
1312       }
1313       else if (DVInsn->getOperand(0).isImm())
1314         updated = 
1315           addConstantValue(VariableDie, DVInsn->getOperand(0),
1316                                        DV->getType());
1317       else if (DVInsn->getOperand(0).isFPImm())
1318         updated =
1319           addConstantFPValue(VariableDie, DVInsn->getOperand(0));
1320       else if (DVInsn->getOperand(0).isCImm())
1321         updated =
1322           addConstantValue(VariableDie, 
1323                                        DVInsn->getOperand(0).getCImm(),
1324                                        DV->getType().isUnsignedDIType());
1325     } else {
1326       addVariableAddress(DV, VariableDie, 
1327                                      Asm->getDebugValueLocation(DVInsn));
1328       updated = true;
1329     }
1330     if (!updated) {
1331       // If variableDie is not updated then DBG_VALUE instruction does not
1332       // have valid variable info.
1333       delete VariableDie;
1334       return NULL;
1335     }
1336     DV->setDIE(VariableDie);
1337     return VariableDie;
1338   } else {
1339     // .. else use frame index.
1340     int FI = DV->getFrameIndex();
1341     if (FI != ~0) {
1342       unsigned FrameReg = 0;
1343       const TargetFrameLowering *TFI = Asm->TM.getFrameLowering();
1344       int Offset = 
1345         TFI->getFrameIndexReference(*Asm->MF, FI, FrameReg);
1346       MachineLocation Location(FrameReg, Offset);
1347       addVariableAddress(DV, VariableDie, Location);
1348     }
1349   }
1350
1351   DV->setDIE(VariableDie);
1352   return VariableDie;
1353 }
1354
1355 /// createMemberDIE - Create new member DIE.
1356 DIE *CompileUnit::createMemberDIE(DIDerivedType DT) {
1357   DIE *MemberDie = new DIE(DT.getTag());
1358   StringRef Name = DT.getName();
1359   if (!Name.empty())
1360     addString(MemberDie, dwarf::DW_AT_name, Name);
1361
1362   addType(MemberDie, DT.getTypeDerivedFrom());
1363
1364   addSourceLine(MemberDie, DT);
1365
1366   DIEBlock *MemLocationDie = new (DIEValueAllocator) DIEBlock();
1367   addUInt(MemLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_plus_uconst);
1368
1369   uint64_t Size = DT.getSizeInBits();
1370   uint64_t FieldSize = DT.getOriginalTypeSize();
1371
1372   if (Size != FieldSize) {
1373     // Handle bitfield.
1374     addUInt(MemberDie, dwarf::DW_AT_byte_size, 0, DT.getOriginalTypeSize()>>3);
1375     addUInt(MemberDie, dwarf::DW_AT_bit_size, 0, DT.getSizeInBits());
1376
1377     uint64_t Offset = DT.getOffsetInBits();
1378     uint64_t AlignMask = ~(DT.getAlignInBits() - 1);
1379     uint64_t HiMark = (Offset + FieldSize) & AlignMask;
1380     uint64_t FieldOffset = (HiMark - FieldSize);
1381     Offset -= FieldOffset;
1382
1383     // Maybe we need to work from the other end.
1384     if (Asm->getTargetData().isLittleEndian())
1385       Offset = FieldSize - (Offset + Size);
1386     addUInt(MemberDie, dwarf::DW_AT_bit_offset, 0, Offset);
1387
1388     // Here WD_AT_data_member_location points to the anonymous
1389     // field that includes this bit field.
1390     addUInt(MemLocationDie, 0, dwarf::DW_FORM_udata, FieldOffset >> 3);
1391
1392   } else
1393     // This is not a bitfield.
1394     addUInt(MemLocationDie, 0, dwarf::DW_FORM_udata, DT.getOffsetInBits() >> 3);
1395
1396   if (DT.getTag() == dwarf::DW_TAG_inheritance
1397       && DT.isVirtual()) {
1398
1399     // For C++, virtual base classes are not at fixed offset. Use following
1400     // expression to extract appropriate offset from vtable.
1401     // BaseAddr = ObAddr + *((*ObAddr) - Offset)
1402
1403     DIEBlock *VBaseLocationDie = new (DIEValueAllocator) DIEBlock();
1404     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_dup);
1405     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
1406     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_constu);
1407     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_udata, DT.getOffsetInBits());
1408     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_minus);
1409     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
1410     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_plus);
1411
1412     addBlock(MemberDie, dwarf::DW_AT_data_member_location, 0,
1413              VBaseLocationDie);
1414   } else
1415     addBlock(MemberDie, dwarf::DW_AT_data_member_location, 0, MemLocationDie);
1416
1417   if (DT.isProtected())
1418     addUInt(MemberDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1419             dwarf::DW_ACCESS_protected);
1420   else if (DT.isPrivate())
1421     addUInt(MemberDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1422             dwarf::DW_ACCESS_private);
1423   // Otherwise C++ member and base classes are considered public.
1424   else 
1425     addUInt(MemberDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1426             dwarf::DW_ACCESS_public);
1427   if (DT.isVirtual())
1428     addUInt(MemberDie, dwarf::DW_AT_virtuality, dwarf::DW_FORM_data1,
1429             dwarf::DW_VIRTUALITY_virtual);
1430
1431   // Objective-C properties.
1432   StringRef PropertyName = DT.getObjCPropertyName();
1433   if (!PropertyName.empty()) {
1434     addString(MemberDie, dwarf::DW_AT_APPLE_property_name, PropertyName);
1435     StringRef GetterName = DT.getObjCPropertyGetterName();
1436     if (!GetterName.empty())
1437       addString(MemberDie, dwarf::DW_AT_APPLE_property_getter, GetterName);
1438     StringRef SetterName = DT.getObjCPropertySetterName();
1439     if (!SetterName.empty())
1440       addString(MemberDie, dwarf::DW_AT_APPLE_property_setter, SetterName);
1441     unsigned PropertyAttributes = 0;
1442     if (DT.isReadOnlyObjCProperty())
1443       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_readonly;
1444     if (DT.isReadWriteObjCProperty())
1445       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_readwrite;
1446     if (DT.isAssignObjCProperty())
1447       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_assign;
1448     if (DT.isRetainObjCProperty())
1449       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_retain;
1450     if (DT.isCopyObjCProperty())
1451       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_copy;
1452     if (DT.isNonAtomicObjCProperty())
1453       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_nonatomic;
1454     if (PropertyAttributes)
1455       addUInt(MemberDie, dwarf::DW_AT_APPLE_property_attribute, 0, 
1456               PropertyAttributes);
1457   }
1458   return MemberDie;
1459 }