Remove tabs.
[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       // A runtime language of 0 actually means C/C++ and that any
617       // non-negative value is some version of Objective-C/C++.
618       IsImplementation = (CT.getRunTimeLang() == 0) ||
619         CT.isObjcClassComplete();;
620     }
621     unsigned Flags = IsImplementation ?
622                      DwarfAccelTable::eTypeFlagClassIsImplementation : 0;
623     addAccelType(Ty.getName(), std::make_pair(TyDIE, Flags));
624   }
625   
626   addToContextOwner(TyDIE, Ty.getContext());
627   return TyDIE;
628 }
629
630 /// addType - Add a new type attribute to the specified entity.
631 void CompileUnit::addType(DIE *Entity, DIType Ty) {
632   if (!Ty.Verify())
633     return;
634
635   // Check for pre-existence.
636   DIEEntry *Entry = getDIEEntry(Ty);
637   // If it exists then use the existing value.
638   if (Entry) {
639     Entity->addValue(dwarf::DW_AT_type, dwarf::DW_FORM_ref4, Entry);
640     return;
641   }
642
643   // Construct type.
644   DIE *Buffer = getOrCreateTypeDIE(Ty);
645
646   // Set up proxy.
647   Entry = createDIEEntry(Buffer);
648   insertDIEEntry(Ty, Entry);
649   Entity->addValue(dwarf::DW_AT_type, dwarf::DW_FORM_ref4, Entry);
650
651   // If this is a complete composite type then include it in the
652   // list of global types.
653   addGlobalType(Ty);
654 }
655
656 /// addGlobalType - Add a new global type to the compile unit.
657 ///
658 void CompileUnit::addGlobalType(DIType Ty) {
659   DIDescriptor Context = Ty.getContext();
660   if (Ty.isCompositeType() && !Ty.getName().empty() && !Ty.isForwardDecl() 
661       && (!Context || Context.isCompileUnit() || Context.isFile() 
662           || Context.isNameSpace()))
663     if (DIEEntry *Entry = getDIEEntry(Ty))
664       GlobalTypes[Ty.getName()] = Entry->getEntry();
665 }
666
667 /// addPubTypes - Add type for pubtypes section.
668 void CompileUnit::addPubTypes(DISubprogram SP) {
669   DICompositeType SPTy = SP.getType();
670   unsigned SPTag = SPTy.getTag();
671   if (SPTag != dwarf::DW_TAG_subroutine_type)
672     return;
673
674   DIArray Args = SPTy.getTypeArray();
675   for (unsigned i = 0, e = Args.getNumElements(); i != e; ++i) {
676     DIType ATy(Args.getElement(i));
677     if (!ATy.Verify())
678       continue;
679     addGlobalType(ATy);
680   }
681 }
682
683 /// constructTypeDIE - Construct basic type die from DIBasicType.
684 void CompileUnit::constructTypeDIE(DIE &Buffer, DIBasicType BTy) {
685   // Get core information.
686   StringRef Name = BTy.getName();
687   // Add name if not anonymous or intermediate type.
688   if (!Name.empty())
689     addString(&Buffer, dwarf::DW_AT_name, Name);
690
691   if (BTy.getTag() == dwarf::DW_TAG_unspecified_type) {
692     Buffer.setTag(dwarf::DW_TAG_unspecified_type);
693     // Unspecified types has only name, nothing else.
694     return;
695   }
696
697   Buffer.setTag(dwarf::DW_TAG_base_type);
698   addUInt(&Buffer, dwarf::DW_AT_encoding, dwarf::DW_FORM_data1,
699           BTy.getEncoding());
700
701   uint64_t Size = BTy.getSizeInBits() >> 3;
702   addUInt(&Buffer, dwarf::DW_AT_byte_size, 0, Size);
703 }
704
705 /// constructTypeDIE - Construct derived type die from DIDerivedType.
706 void CompileUnit::constructTypeDIE(DIE &Buffer, DIDerivedType DTy) {
707   // Get core information.
708   StringRef Name = DTy.getName();
709   uint64_t Size = DTy.getSizeInBits() >> 3;
710   unsigned Tag = DTy.getTag();
711
712   // FIXME - Workaround for templates.
713   if (Tag == dwarf::DW_TAG_inheritance) Tag = dwarf::DW_TAG_reference_type;
714
715   Buffer.setTag(Tag);
716
717   // Map to main type, void will not have a type.
718   DIType FromTy = DTy.getTypeDerivedFrom();
719   addType(&Buffer, FromTy);
720
721   // Add name if not anonymous or intermediate type.
722   if (!Name.empty())
723     addString(&Buffer, dwarf::DW_AT_name, Name);
724
725   // Add size if non-zero (derived types might be zero-sized.)
726   if (Size)
727     addUInt(&Buffer, dwarf::DW_AT_byte_size, 0, Size);
728
729   // Add source line info if available and TyDesc is not a forward declaration.
730   if (!DTy.isForwardDecl())
731     addSourceLine(&Buffer, DTy);
732 }
733
734 /// constructTypeDIE - Construct type DIE from DICompositeType.
735 void CompileUnit::constructTypeDIE(DIE &Buffer, DICompositeType CTy) {
736   // Get core information.
737   StringRef Name = CTy.getName();
738
739   uint64_t Size = CTy.getSizeInBits() >> 3;
740   unsigned Tag = CTy.getTag();
741   Buffer.setTag(Tag);
742
743   switch (Tag) {
744   case dwarf::DW_TAG_vector_type:
745   case dwarf::DW_TAG_array_type:
746     constructArrayTypeDIE(Buffer, &CTy);
747     break;
748   case dwarf::DW_TAG_enumeration_type: {
749     DIArray Elements = CTy.getTypeArray();
750
751     // Add enumerators to enumeration type.
752     for (unsigned i = 0, N = Elements.getNumElements(); i < N; ++i) {
753       DIE *ElemDie = NULL;
754       DIDescriptor Enum(Elements.getElement(i));
755       if (Enum.isEnumerator()) {
756         ElemDie = constructEnumTypeDIE(DIEnumerator(Enum));
757         Buffer.addChild(ElemDie);
758       }
759     }
760   }
761     break;
762   case dwarf::DW_TAG_subroutine_type: {
763     // Add return type.
764     DIArray Elements = CTy.getTypeArray();
765     DIDescriptor RTy = Elements.getElement(0);
766     addType(&Buffer, DIType(RTy));
767
768     bool isPrototyped = true;
769     // Add arguments.
770     for (unsigned i = 1, N = Elements.getNumElements(); i < N; ++i) {
771       DIDescriptor Ty = Elements.getElement(i);
772       if (Ty.isUnspecifiedParameter()) {
773         DIE *Arg = new DIE(dwarf::DW_TAG_unspecified_parameters);
774         Buffer.addChild(Arg);
775         isPrototyped = false;
776       } else {
777         DIE *Arg = new DIE(dwarf::DW_TAG_formal_parameter);
778         addType(Arg, DIType(Ty));
779         Buffer.addChild(Arg);
780       }
781     }
782     // Add prototype flag.
783     if (isPrototyped)
784       addUInt(&Buffer, dwarf::DW_AT_prototyped, dwarf::DW_FORM_flag, 1);
785   }
786     break;
787   case dwarf::DW_TAG_structure_type:
788   case dwarf::DW_TAG_union_type:
789   case dwarf::DW_TAG_class_type: {
790     // Add elements to structure type.
791     DIArray Elements = CTy.getTypeArray();
792
793     // A forward struct declared type may not have elements available.
794     unsigned N = Elements.getNumElements();
795     if (N == 0)
796       break;
797
798     // Add elements to structure type.
799     for (unsigned i = 0; i < N; ++i) {
800       DIDescriptor Element = Elements.getElement(i);
801       DIE *ElemDie = NULL;
802       if (Element.isSubprogram()) {
803         DISubprogram SP(Element);
804         ElemDie = getOrCreateSubprogramDIE(DISubprogram(Element));
805         if (SP.isProtected())
806           addUInt(ElemDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
807                   dwarf::DW_ACCESS_protected);
808         else if (SP.isPrivate())
809           addUInt(ElemDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
810                   dwarf::DW_ACCESS_private);
811         else 
812           addUInt(ElemDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
813             dwarf::DW_ACCESS_public);
814         if (SP.isExplicit())
815           addUInt(ElemDie, dwarf::DW_AT_explicit, dwarf::DW_FORM_flag, 1);
816       }
817       else if (Element.isVariable()) {
818         DIVariable DV(Element);
819         ElemDie = new DIE(dwarf::DW_TAG_variable);
820         addString(ElemDie, dwarf::DW_AT_name, DV.getName());
821         addType(ElemDie, DV.getType());
822         addUInt(ElemDie, dwarf::DW_AT_declaration, dwarf::DW_FORM_flag, 1);
823         addUInt(ElemDie, dwarf::DW_AT_external, dwarf::DW_FORM_flag, 1);
824         addSourceLine(ElemDie, DV);
825       } else if (Element.isDerivedType())
826         ElemDie = createMemberDIE(DIDerivedType(Element));
827       else if (Element.isObjCProperty()) {
828         DIObjCProperty Property(Element);
829         ElemDie = new DIE(Property.getTag());
830         StringRef PropertyName = Property.getObjCPropertyName();
831         addString(ElemDie, dwarf::DW_AT_APPLE_property_name, PropertyName);
832         StringRef GetterName = Property.getObjCPropertyGetterName();
833         if (!GetterName.empty())
834           addString(ElemDie, dwarf::DW_AT_APPLE_property_getter, GetterName);
835         StringRef SetterName = Property.getObjCPropertySetterName();
836         if (!SetterName.empty())
837           addString(ElemDie, dwarf::DW_AT_APPLE_property_setter, SetterName);
838         unsigned PropertyAttributes = 0;
839         if (Property.isReadOnlyObjCProperty())
840           PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_readonly;
841         if (Property.isReadWriteObjCProperty())
842           PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_readwrite;
843         if (Property.isAssignObjCProperty())
844           PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_assign;
845         if (Property.isRetainObjCProperty())
846           PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_retain;
847         if (Property.isCopyObjCProperty())
848           PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_copy;
849         if (Property.isNonAtomicObjCProperty())
850           PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_nonatomic;
851         if (PropertyAttributes)
852           addUInt(ElemDie, dwarf::DW_AT_APPLE_property_attribute, 0, 
853                  PropertyAttributes);
854
855         DIEEntry *Entry = getDIEEntry(Element);
856         if (!Entry) {
857           Entry = createDIEEntry(ElemDie);
858           insertDIEEntry(Element, Entry);
859         }
860       } else
861         continue;
862       Buffer.addChild(ElemDie);
863     }
864
865     if (CTy.isAppleBlockExtension())
866       addUInt(&Buffer, dwarf::DW_AT_APPLE_block, dwarf::DW_FORM_flag, 1);
867
868     unsigned RLang = CTy.getRunTimeLang();
869     if (RLang)
870       addUInt(&Buffer, dwarf::DW_AT_APPLE_runtime_class,
871               dwarf::DW_FORM_data1, RLang);
872
873     DICompositeType ContainingType = CTy.getContainingType();
874     if (DIDescriptor(ContainingType).isCompositeType())
875       addDIEEntry(&Buffer, dwarf::DW_AT_containing_type, dwarf::DW_FORM_ref4,
876                   getOrCreateTypeDIE(DIType(ContainingType)));
877     else {
878       DIDescriptor Context = CTy.getContext();
879       addToContextOwner(&Buffer, Context);
880     }
881
882     if (CTy.isObjcClassComplete())
883       addUInt(&Buffer, dwarf::DW_AT_APPLE_objc_complete_type,
884               dwarf::DW_FORM_flag, 1);
885
886     // Add template parameters to a class, structure or union types.
887     // FIXME: The support isn't in the metadata for this yet.
888     if (Tag == dwarf::DW_TAG_class_type ||
889         Tag == dwarf::DW_TAG_structure_type ||
890         Tag == dwarf::DW_TAG_union_type)
891       addTemplateParams(Buffer, CTy.getTemplateParams());
892
893     break;
894   }
895   default:
896     break;
897   }
898
899   // Add name if not anonymous or intermediate type.
900   if (!Name.empty())
901     addString(&Buffer, dwarf::DW_AT_name, Name);
902
903   if (Tag == dwarf::DW_TAG_enumeration_type || Tag == dwarf::DW_TAG_class_type
904       || Tag == dwarf::DW_TAG_structure_type || Tag == dwarf::DW_TAG_union_type)
905   {
906     // Add size if non-zero (derived types might be zero-sized.)
907     if (Size)
908       addUInt(&Buffer, dwarf::DW_AT_byte_size, 0, Size);
909     else {
910       // Add zero size if it is not a forward declaration.
911       if (CTy.isForwardDecl())
912         addUInt(&Buffer, dwarf::DW_AT_declaration, dwarf::DW_FORM_flag, 1);
913       else
914         addUInt(&Buffer, dwarf::DW_AT_byte_size, 0, 0);
915     }
916
917     // Add source line info if available.
918     if (!CTy.isForwardDecl())
919       addSourceLine(&Buffer, CTy);
920   }
921 }
922
923 /// getOrCreateTemplateTypeParameterDIE - Find existing DIE or create new DIE 
924 /// for the given DITemplateTypeParameter.
925 DIE *
926 CompileUnit::getOrCreateTemplateTypeParameterDIE(DITemplateTypeParameter TP) {
927   DIE *ParamDIE = getDIE(TP);
928   if (ParamDIE)
929     return ParamDIE;
930
931   ParamDIE = new DIE(dwarf::DW_TAG_template_type_parameter);
932   addType(ParamDIE, TP.getType());
933   addString(ParamDIE, dwarf::DW_AT_name, TP.getName());
934   return ParamDIE;
935 }
936
937 /// getOrCreateTemplateValueParameterDIE - Find existing DIE or create new DIE 
938 /// for the given DITemplateValueParameter.
939 DIE *
940 CompileUnit::getOrCreateTemplateValueParameterDIE(DITemplateValueParameter TPV) {
941   DIE *ParamDIE = getDIE(TPV);
942   if (ParamDIE)
943     return ParamDIE;
944
945   ParamDIE = new DIE(dwarf::DW_TAG_template_value_parameter);
946   addType(ParamDIE, TPV.getType());
947   if (!TPV.getName().empty())
948     addString(ParamDIE, dwarf::DW_AT_name, TPV.getName());
949   addUInt(ParamDIE, dwarf::DW_AT_const_value, dwarf::DW_FORM_udata, 
950           TPV.getValue());
951   return ParamDIE;
952 }
953
954 /// getOrCreateNameSpace - Create a DIE for DINameSpace.
955 DIE *CompileUnit::getOrCreateNameSpace(DINameSpace NS) {
956   DIE *NDie = getDIE(NS);
957   if (NDie)
958     return NDie;
959   NDie = new DIE(dwarf::DW_TAG_namespace);
960   insertDIE(NS, NDie);
961   if (!NS.getName().empty()) {
962     addString(NDie, dwarf::DW_AT_name, NS.getName());
963     addAccelNamespace(NS.getName(), NDie);
964   } else
965     addAccelNamespace("(anonymous namespace)", NDie);
966   addSourceLine(NDie, NS);
967   addToContextOwner(NDie, NS.getContext());
968   return NDie;
969 }
970
971 /// getRealLinkageName - If special LLVM prefix that is used to inform the asm
972 /// printer to not emit usual symbol prefix before the symbol name is used then
973 /// return linkage name after skipping this special LLVM prefix.
974 static StringRef getRealLinkageName(StringRef LinkageName) {
975   char One = '\1';
976   if (LinkageName.startswith(StringRef(&One, 1)))
977     return LinkageName.substr(1);
978   return LinkageName;
979 }
980
981 /// getOrCreateSubprogramDIE - Create new DIE using SP.
982 DIE *CompileUnit::getOrCreateSubprogramDIE(DISubprogram SP) {
983   DIE *SPDie = getDIE(SP);
984   if (SPDie)
985     return SPDie;
986
987   DISubprogram SPDecl = SP.getFunctionDeclaration();
988   DIE *DeclDie = NULL;
989   if (SPDecl.isSubprogram()) {
990     DeclDie = getOrCreateSubprogramDIE(SPDecl);
991   }
992
993   SPDie = new DIE(dwarf::DW_TAG_subprogram);
994   
995   // DW_TAG_inlined_subroutine may refer to this DIE.
996   insertDIE(SP, SPDie);
997   
998   // Add to context owner.
999   addToContextOwner(SPDie, SP.getContext());
1000
1001   // Add function template parameters.
1002   addTemplateParams(*SPDie, SP.getTemplateParams());
1003
1004   StringRef LinkageName = SP.getLinkageName();
1005   if (!LinkageName.empty())
1006     addString(SPDie, dwarf::DW_AT_MIPS_linkage_name,
1007               getRealLinkageName(LinkageName));
1008
1009   // If this DIE is going to refer declaration info using AT_specification
1010   // then there is no need to add other attributes.
1011   if (DeclDie) {
1012     // Refer function declaration directly.
1013     addDIEEntry(SPDie, dwarf::DW_AT_specification, dwarf::DW_FORM_ref4,
1014                 DeclDie);
1015
1016     return SPDie;
1017   }
1018
1019   // Constructors and operators for anonymous aggregates do not have names.
1020   if (!SP.getName().empty())
1021     addString(SPDie, dwarf::DW_AT_name, SP.getName());
1022
1023   addSourceLine(SPDie, SP);
1024
1025   if (SP.isPrototyped()) 
1026     addUInt(SPDie, dwarf::DW_AT_prototyped, dwarf::DW_FORM_flag, 1);
1027
1028   // Add Return Type.
1029   DICompositeType SPTy = SP.getType();
1030   DIArray Args = SPTy.getTypeArray();
1031   unsigned SPTag = SPTy.getTag();
1032
1033   if (Args.getNumElements() == 0 || SPTag != dwarf::DW_TAG_subroutine_type)
1034     addType(SPDie, SPTy);
1035   else
1036     addType(SPDie, DIType(Args.getElement(0)));
1037
1038   unsigned VK = SP.getVirtuality();
1039   if (VK) {
1040     addUInt(SPDie, dwarf::DW_AT_virtuality, dwarf::DW_FORM_data1, VK);
1041     DIEBlock *Block = getDIEBlock();
1042     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_constu);
1043     addUInt(Block, 0, dwarf::DW_FORM_udata, SP.getVirtualIndex());
1044     addBlock(SPDie, dwarf::DW_AT_vtable_elem_location, 0, Block);
1045     ContainingTypeMap.insert(std::make_pair(SPDie,
1046                                             SP.getContainingType()));
1047   }
1048
1049   if (!SP.isDefinition()) {
1050     addUInt(SPDie, dwarf::DW_AT_declaration, dwarf::DW_FORM_flag, 1);
1051     
1052     // Add arguments. Do not add arguments for subprogram definition. They will
1053     // be handled while processing variables.
1054     DICompositeType SPTy = SP.getType();
1055     DIArray Args = SPTy.getTypeArray();
1056     unsigned SPTag = SPTy.getTag();
1057
1058     if (SPTag == dwarf::DW_TAG_subroutine_type)
1059       for (unsigned i = 1, N =  Args.getNumElements(); i < N; ++i) {
1060         DIE *Arg = new DIE(dwarf::DW_TAG_formal_parameter);
1061         DIType ATy = DIType(DIType(Args.getElement(i)));
1062         addType(Arg, ATy);
1063         if (ATy.isArtificial())
1064           addUInt(Arg, dwarf::DW_AT_artificial, dwarf::DW_FORM_flag, 1);
1065         SPDie->addChild(Arg);
1066       }
1067   }
1068
1069   if (SP.isArtificial())
1070     addUInt(SPDie, dwarf::DW_AT_artificial, dwarf::DW_FORM_flag, 1);
1071
1072   if (!SP.isLocalToUnit())
1073     addUInt(SPDie, dwarf::DW_AT_external, dwarf::DW_FORM_flag, 1);
1074
1075   if (SP.isOptimized())
1076     addUInt(SPDie, dwarf::DW_AT_APPLE_optimized, dwarf::DW_FORM_flag, 1);
1077
1078   if (unsigned isa = Asm->getISAEncoding()) {
1079     addUInt(SPDie, dwarf::DW_AT_APPLE_isa, dwarf::DW_FORM_flag, isa);
1080   }
1081
1082   return SPDie;
1083 }
1084
1085 // Return const expression if value is a GEP to access merged global
1086 // constant. e.g.
1087 // i8* getelementptr ({ i8, i8, i8, i8 }* @_MergedGlobals, i32 0, i32 0)
1088 static const ConstantExpr *getMergedGlobalExpr(const Value *V) {
1089   const ConstantExpr *CE = dyn_cast_or_null<ConstantExpr>(V);
1090   if (!CE || CE->getNumOperands() != 3 ||
1091       CE->getOpcode() != Instruction::GetElementPtr)
1092     return NULL;
1093
1094   // First operand points to a global struct.
1095   Value *Ptr = CE->getOperand(0);
1096   if (!isa<GlobalValue>(Ptr) ||
1097       !isa<StructType>(cast<PointerType>(Ptr->getType())->getElementType()))
1098     return NULL;
1099
1100   // Second operand is zero.
1101   const ConstantInt *CI = dyn_cast_or_null<ConstantInt>(CE->getOperand(1));
1102   if (!CI || !CI->isZero())
1103     return NULL;
1104
1105   // Third operand is offset.
1106   if (!isa<ConstantInt>(CE->getOperand(2)))
1107     return NULL;
1108
1109   return CE;
1110 }
1111
1112 /// createGlobalVariableDIE - create global variable DIE.
1113 void CompileUnit::createGlobalVariableDIE(const MDNode *N) {
1114   // Check for pre-existence.
1115   if (getDIE(N))
1116     return;
1117
1118   DIGlobalVariable GV(N);
1119   if (!GV.Verify())
1120     return;
1121
1122   DIE *VariableDIE = new DIE(GV.getTag());
1123   // Add to map.
1124   insertDIE(N, VariableDIE);
1125
1126   // Add name.
1127   addString(VariableDIE, dwarf::DW_AT_name, GV.getDisplayName());
1128   StringRef LinkageName = GV.getLinkageName();
1129   bool isGlobalVariable = GV.getGlobal() != NULL;
1130   if (!LinkageName.empty() && isGlobalVariable)
1131     addString(VariableDIE, dwarf::DW_AT_MIPS_linkage_name,
1132               getRealLinkageName(LinkageName));
1133   // Add type.
1134   DIType GTy = GV.getType();
1135   addType(VariableDIE, GTy);
1136
1137   // Add scoping info.
1138   if (!GV.isLocalToUnit())
1139     addUInt(VariableDIE, dwarf::DW_AT_external, dwarf::DW_FORM_flag, 1);
1140
1141   // Add line number info.
1142   addSourceLine(VariableDIE, GV);
1143   // Add to context owner.
1144   DIDescriptor GVContext = GV.getContext();
1145   addToContextOwner(VariableDIE, GVContext);
1146   // Add location.
1147   bool addToAccelTable = false;
1148   DIE *VariableSpecDIE = NULL;
1149   if (isGlobalVariable) {
1150     addToAccelTable = true;
1151     DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
1152     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_addr);
1153     addLabel(Block, 0, dwarf::DW_FORM_udata,
1154              Asm->Mang->getSymbol(GV.getGlobal()));
1155     // Do not create specification DIE if context is either compile unit
1156     // or a subprogram.
1157     if (GVContext && GV.isDefinition() && !GVContext.isCompileUnit() &&
1158         !GVContext.isFile() && !isSubprogramContext(GVContext)) {
1159       // Create specification DIE.
1160       VariableSpecDIE = new DIE(dwarf::DW_TAG_variable);
1161       addDIEEntry(VariableSpecDIE, dwarf::DW_AT_specification,
1162                   dwarf::DW_FORM_ref4, VariableDIE);
1163       addBlock(VariableSpecDIE, dwarf::DW_AT_location, 0, Block);
1164       addUInt(VariableDIE, dwarf::DW_AT_declaration, dwarf::DW_FORM_flag,
1165                      1);
1166       addDie(VariableSpecDIE);
1167     } else {
1168       addBlock(VariableDIE, dwarf::DW_AT_location, 0, Block);
1169     }
1170   } else if (const ConstantInt *CI = 
1171              dyn_cast_or_null<ConstantInt>(GV.getConstant()))
1172     addConstantValue(VariableDIE, CI, GTy.isUnsignedDIType());
1173   else if (const ConstantExpr *CE = getMergedGlobalExpr(N->getOperand(11))) {
1174     addToAccelTable = true;
1175     // GV is a merged global.
1176     DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
1177     Value *Ptr = CE->getOperand(0);
1178     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_addr);
1179     addLabel(Block, 0, dwarf::DW_FORM_udata,
1180                     Asm->Mang->getSymbol(cast<GlobalValue>(Ptr)));
1181     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_constu);
1182     SmallVector<Value*, 3> Idx(CE->op_begin()+1, CE->op_end());
1183     addUInt(Block, 0, dwarf::DW_FORM_udata, 
1184                    Asm->getTargetData().getIndexedOffset(Ptr->getType(), Idx));
1185     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_plus);
1186     addBlock(VariableDIE, dwarf::DW_AT_location, 0, Block);
1187   }
1188
1189   if (addToAccelTable) {
1190     DIE *AddrDIE = VariableSpecDIE ? VariableSpecDIE : VariableDIE;
1191     addAccelName(GV.getName(), AddrDIE);
1192
1193     // If the linkage name is different than the name, go ahead and output
1194     // that as well into the name table.
1195     if (GV.getLinkageName() != "" && GV.getName() != GV.getLinkageName())
1196       addAccelName(GV.getLinkageName(), AddrDIE);
1197   }
1198
1199   return;
1200 }
1201
1202 /// constructSubrangeDIE - Construct subrange DIE from DISubrange.
1203 void CompileUnit::constructSubrangeDIE(DIE &Buffer, DISubrange SR, DIE *IndexTy){
1204   DIE *DW_Subrange = new DIE(dwarf::DW_TAG_subrange_type);
1205   addDIEEntry(DW_Subrange, dwarf::DW_AT_type, dwarf::DW_FORM_ref4, IndexTy);
1206   uint64_t L = SR.getLo();
1207   uint64_t H = SR.getHi();
1208
1209   // The L value defines the lower bounds which is typically zero for C/C++. The
1210   // H value is the upper bounds.  Values are 64 bit.  H - L + 1 is the size
1211   // of the array. If L > H then do not emit DW_AT_lower_bound and 
1212   // DW_AT_upper_bound attributes. If L is zero and H is also zero then the
1213   // array has one element and in such case do not emit lower bound.
1214
1215   if (L > H) {
1216     Buffer.addChild(DW_Subrange);
1217     return;
1218   }
1219   if (L)
1220     addUInt(DW_Subrange, dwarf::DW_AT_lower_bound, 0, L);
1221   addUInt(DW_Subrange, dwarf::DW_AT_upper_bound, 0, H);
1222   Buffer.addChild(DW_Subrange);
1223 }
1224
1225 /// constructArrayTypeDIE - Construct array type DIE from DICompositeType.
1226 void CompileUnit::constructArrayTypeDIE(DIE &Buffer,
1227                                         DICompositeType *CTy) {
1228   Buffer.setTag(dwarf::DW_TAG_array_type);
1229   if (CTy->getTag() == dwarf::DW_TAG_vector_type)
1230     addUInt(&Buffer, dwarf::DW_AT_GNU_vector, dwarf::DW_FORM_flag, 1);
1231
1232   // Emit derived type.
1233   addType(&Buffer, CTy->getTypeDerivedFrom());
1234   DIArray Elements = CTy->getTypeArray();
1235
1236   // Get an anonymous type for index type.
1237   DIE *IdxTy = getIndexTyDie();
1238   if (!IdxTy) {
1239     // Construct an anonymous type for index type.
1240     IdxTy = new DIE(dwarf::DW_TAG_base_type);
1241     addUInt(IdxTy, dwarf::DW_AT_byte_size, 0, sizeof(int32_t));
1242     addUInt(IdxTy, dwarf::DW_AT_encoding, dwarf::DW_FORM_data1,
1243             dwarf::DW_ATE_signed);
1244     addDie(IdxTy);
1245     setIndexTyDie(IdxTy);
1246   }
1247
1248   // Add subranges to array type.
1249   for (unsigned i = 0, N = Elements.getNumElements(); i < N; ++i) {
1250     DIDescriptor Element = Elements.getElement(i);
1251     if (Element.getTag() == dwarf::DW_TAG_subrange_type)
1252       constructSubrangeDIE(Buffer, DISubrange(Element), IdxTy);
1253   }
1254 }
1255
1256 /// constructEnumTypeDIE - Construct enum type DIE from DIEnumerator.
1257 DIE *CompileUnit::constructEnumTypeDIE(DIEnumerator ETy) {
1258   DIE *Enumerator = new DIE(dwarf::DW_TAG_enumerator);
1259   StringRef Name = ETy.getName();
1260   addString(Enumerator, dwarf::DW_AT_name, Name);
1261   int64_t Value = ETy.getEnumValue();
1262   addSInt(Enumerator, dwarf::DW_AT_const_value, dwarf::DW_FORM_sdata, Value);
1263   return Enumerator;
1264 }
1265
1266 /// constructContainingTypeDIEs - Construct DIEs for types that contain
1267 /// vtables.
1268 void CompileUnit::constructContainingTypeDIEs() {
1269   for (DenseMap<DIE *, const MDNode *>::iterator CI = ContainingTypeMap.begin(),
1270          CE = ContainingTypeMap.end(); CI != CE; ++CI) {
1271     DIE *SPDie = CI->first;
1272     const MDNode *N = CI->second;
1273     if (!N) continue;
1274     DIE *NDie = getDIE(N);
1275     if (!NDie) continue;
1276     addDIEEntry(SPDie, dwarf::DW_AT_containing_type, dwarf::DW_FORM_ref4, NDie);
1277   }
1278 }
1279
1280 /// constructVariableDIE - Construct a DIE for the given DbgVariable.
1281 DIE *CompileUnit::constructVariableDIE(DbgVariable *DV, bool isScopeAbstract) {
1282   StringRef Name = DV->getName();
1283   if (Name.empty())
1284     return NULL;
1285
1286   // Translate tag to proper Dwarf tag.
1287   unsigned Tag = DV->getTag();
1288
1289   // Define variable debug information entry.
1290   DIE *VariableDie = new DIE(Tag);
1291   DbgVariable *AbsVar = DV->getAbstractVariable();
1292   DIE *AbsDIE = AbsVar ? AbsVar->getDIE() : NULL;
1293   if (AbsDIE)
1294     addDIEEntry(VariableDie, dwarf::DW_AT_abstract_origin,
1295                             dwarf::DW_FORM_ref4, AbsDIE);
1296   else {
1297     addString(VariableDie, dwarf::DW_AT_name, Name);
1298     addSourceLine(VariableDie, DV->getVariable());
1299     addType(VariableDie, DV->getType());
1300   }
1301
1302   if (DV->isArtificial())
1303     addUInt(VariableDie, dwarf::DW_AT_artificial,
1304                         dwarf::DW_FORM_flag, 1);
1305
1306   if (isScopeAbstract) {
1307     DV->setDIE(VariableDie);
1308     return VariableDie;
1309   }
1310
1311   // Add variable address.
1312
1313   unsigned Offset = DV->getDotDebugLocOffset();
1314   if (Offset != ~0U) {
1315     addLabel(VariableDie, dwarf::DW_AT_location,
1316                          dwarf::DW_FORM_data4,
1317                          Asm->GetTempSymbol("debug_loc", Offset));
1318     DV->setDIE(VariableDie);
1319     return VariableDie;
1320   }
1321
1322   // Check if variable is described by a DBG_VALUE instruction.
1323   if (const MachineInstr *DVInsn = DV->getMInsn()) {
1324     bool updated = false;
1325     if (DVInsn->getNumOperands() == 3) {
1326       if (DVInsn->getOperand(0).isReg()) {
1327         const MachineOperand RegOp = DVInsn->getOperand(0);
1328         const TargetRegisterInfo *TRI = Asm->TM.getRegisterInfo();
1329         if (DVInsn->getOperand(1).isImm() &&
1330             TRI->getFrameRegister(*Asm->MF) == RegOp.getReg()) {
1331           unsigned FrameReg = 0;
1332           const TargetFrameLowering *TFI = Asm->TM.getFrameLowering();
1333           int Offset = 
1334             TFI->getFrameIndexReference(*Asm->MF, 
1335                                         DVInsn->getOperand(1).getImm(), 
1336                                         FrameReg);
1337           MachineLocation Location(FrameReg, Offset);
1338           addVariableAddress(DV, VariableDie, Location);
1339           
1340         } else if (RegOp.getReg())
1341           addVariableAddress(DV, VariableDie, 
1342                                          MachineLocation(RegOp.getReg()));
1343         updated = true;
1344       }
1345       else if (DVInsn->getOperand(0).isImm())
1346         updated = 
1347           addConstantValue(VariableDie, DVInsn->getOperand(0),
1348                                        DV->getType());
1349       else if (DVInsn->getOperand(0).isFPImm())
1350         updated =
1351           addConstantFPValue(VariableDie, DVInsn->getOperand(0));
1352       else if (DVInsn->getOperand(0).isCImm())
1353         updated =
1354           addConstantValue(VariableDie, 
1355                                        DVInsn->getOperand(0).getCImm(),
1356                                        DV->getType().isUnsignedDIType());
1357     } else {
1358       addVariableAddress(DV, VariableDie, 
1359                                      Asm->getDebugValueLocation(DVInsn));
1360       updated = true;
1361     }
1362     if (!updated) {
1363       // If variableDie is not updated then DBG_VALUE instruction does not
1364       // have valid variable info.
1365       delete VariableDie;
1366       return NULL;
1367     }
1368     DV->setDIE(VariableDie);
1369     return VariableDie;
1370   } else {
1371     // .. else use frame index.
1372     int FI = DV->getFrameIndex();
1373     if (FI != ~0) {
1374       unsigned FrameReg = 0;
1375       const TargetFrameLowering *TFI = Asm->TM.getFrameLowering();
1376       int Offset = 
1377         TFI->getFrameIndexReference(*Asm->MF, FI, FrameReg);
1378       MachineLocation Location(FrameReg, Offset);
1379       addVariableAddress(DV, VariableDie, Location);
1380     }
1381   }
1382
1383   DV->setDIE(VariableDie);
1384   return VariableDie;
1385 }
1386
1387 /// createMemberDIE - Create new member DIE.
1388 DIE *CompileUnit::createMemberDIE(DIDerivedType DT) {
1389   DIE *MemberDie = new DIE(DT.getTag());
1390   StringRef Name = DT.getName();
1391   if (!Name.empty())
1392     addString(MemberDie, dwarf::DW_AT_name, Name);
1393
1394   addType(MemberDie, DT.getTypeDerivedFrom());
1395
1396   addSourceLine(MemberDie, DT);
1397
1398   DIEBlock *MemLocationDie = new (DIEValueAllocator) DIEBlock();
1399   addUInt(MemLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_plus_uconst);
1400
1401   uint64_t Size = DT.getSizeInBits();
1402   uint64_t FieldSize = DT.getOriginalTypeSize();
1403
1404   if (Size != FieldSize) {
1405     // Handle bitfield.
1406     addUInt(MemberDie, dwarf::DW_AT_byte_size, 0, DT.getOriginalTypeSize()>>3);
1407     addUInt(MemberDie, dwarf::DW_AT_bit_size, 0, DT.getSizeInBits());
1408
1409     uint64_t Offset = DT.getOffsetInBits();
1410     uint64_t AlignMask = ~(DT.getAlignInBits() - 1);
1411     uint64_t HiMark = (Offset + FieldSize) & AlignMask;
1412     uint64_t FieldOffset = (HiMark - FieldSize);
1413     Offset -= FieldOffset;
1414
1415     // Maybe we need to work from the other end.
1416     if (Asm->getTargetData().isLittleEndian())
1417       Offset = FieldSize - (Offset + Size);
1418     addUInt(MemberDie, dwarf::DW_AT_bit_offset, 0, Offset);
1419
1420     // Here WD_AT_data_member_location points to the anonymous
1421     // field that includes this bit field.
1422     addUInt(MemLocationDie, 0, dwarf::DW_FORM_udata, FieldOffset >> 3);
1423
1424   } else
1425     // This is not a bitfield.
1426     addUInt(MemLocationDie, 0, dwarf::DW_FORM_udata, DT.getOffsetInBits() >> 3);
1427
1428   if (DT.getTag() == dwarf::DW_TAG_inheritance
1429       && DT.isVirtual()) {
1430
1431     // For C++, virtual base classes are not at fixed offset. Use following
1432     // expression to extract appropriate offset from vtable.
1433     // BaseAddr = ObAddr + *((*ObAddr) - Offset)
1434
1435     DIEBlock *VBaseLocationDie = new (DIEValueAllocator) DIEBlock();
1436     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_dup);
1437     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
1438     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_constu);
1439     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_udata, DT.getOffsetInBits());
1440     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_minus);
1441     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
1442     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_plus);
1443
1444     addBlock(MemberDie, dwarf::DW_AT_data_member_location, 0,
1445              VBaseLocationDie);
1446   } else
1447     addBlock(MemberDie, dwarf::DW_AT_data_member_location, 0, MemLocationDie);
1448
1449   if (DT.isProtected())
1450     addUInt(MemberDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1451             dwarf::DW_ACCESS_protected);
1452   else if (DT.isPrivate())
1453     addUInt(MemberDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1454             dwarf::DW_ACCESS_private);
1455   // Otherwise C++ member and base classes are considered public.
1456   else 
1457     addUInt(MemberDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_data1,
1458             dwarf::DW_ACCESS_public);
1459   if (DT.isVirtual())
1460     addUInt(MemberDie, dwarf::DW_AT_virtuality, dwarf::DW_FORM_data1,
1461             dwarf::DW_VIRTUALITY_virtual);
1462
1463   // Objective-C properties.
1464   if (MDNode *PNode = DT.getObjCProperty())
1465     if (DIEEntry *PropertyDie = getDIEEntry(PNode))
1466       MemberDie->addValue(dwarf::DW_AT_APPLE_property, dwarf::DW_FORM_ref4, 
1467                           PropertyDie);
1468
1469   // This is only for backward compatibility.
1470   StringRef PropertyName = DT.getObjCPropertyName();
1471   if (!PropertyName.empty()) {
1472     addString(MemberDie, dwarf::DW_AT_APPLE_property_name, PropertyName);
1473     StringRef GetterName = DT.getObjCPropertyGetterName();
1474     if (!GetterName.empty())
1475       addString(MemberDie, dwarf::DW_AT_APPLE_property_getter, GetterName);
1476     StringRef SetterName = DT.getObjCPropertySetterName();
1477     if (!SetterName.empty())
1478       addString(MemberDie, dwarf::DW_AT_APPLE_property_setter, SetterName);
1479     unsigned PropertyAttributes = 0;
1480     if (DT.isReadOnlyObjCProperty())
1481       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_readonly;
1482     if (DT.isReadWriteObjCProperty())
1483       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_readwrite;
1484     if (DT.isAssignObjCProperty())
1485       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_assign;
1486     if (DT.isRetainObjCProperty())
1487       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_retain;
1488     if (DT.isCopyObjCProperty())
1489       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_copy;
1490     if (DT.isNonAtomicObjCProperty())
1491       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_nonatomic;
1492     if (PropertyAttributes)
1493       addUInt(MemberDie, dwarf::DW_AT_APPLE_property_attribute, 0, 
1494               PropertyAttributes);
1495   }
1496   return MemberDie;
1497 }