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