Refactor. Global variables are part of compile unit so let CompileUnit create new...
[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(DIType Ty) {
581   DIE *TyDIE = getDIE(Ty);
582   if (TyDIE)
583     return TyDIE;
584
585   // Create new type.
586   TyDIE = new DIE(dwarf::DW_TAG_base_type);
587   insertDIE(Ty, TyDIE);
588   if (Ty.isBasicType())
589     constructTypeDIE(*TyDIE, DIBasicType(Ty));
590   else if (Ty.isCompositeType())
591     constructTypeDIE(*TyDIE, DICompositeType(Ty));
592   else {
593     assert(Ty.isDerivedType() && "Unknown kind of DIType");
594     constructTypeDIE(*TyDIE, DIDerivedType(Ty));
595   }
596
597   addToContextOwner(TyDIE, Ty.getContext());
598   return TyDIE;
599 }
600
601 /// addType - Add a new type attribute to the specified entity.
602 void CompileUnit::addType(DIE *Entity, DIType Ty) {
603   if (!Ty.Verify())
604     return;
605
606   // Check for pre-existence.
607   DIEEntry *Entry = getDIEEntry(Ty);
608   // If it exists then use the existing value.
609   if (Entry) {
610     Entity->addValue(dwarf::DW_AT_type, dwarf::DW_FORM_ref4, Entry);
611     return;
612   }
613
614   // Construct type.
615   DIE *Buffer = getOrCreateTypeDIE(Ty);
616
617   // Set up proxy.
618   Entry = createDIEEntry(Buffer);
619   insertDIEEntry(Ty, Entry);
620   Entity->addValue(dwarf::DW_AT_type, dwarf::DW_FORM_ref4, Entry);
621
622   // If this is a complete composite type then include it in the
623   // list of global types.
624   addGlobalType(Ty);
625 }
626
627 /// addGlobalType - Add a new global type to the compile unit.
628 ///
629 void CompileUnit::addGlobalType(DIType Ty) {
630   DIDescriptor Context = Ty.getContext();
631   if (Ty.isCompositeType() && !Ty.getName().empty() && !Ty.isForwardDecl() 
632       && (Context.isCompileUnit() || Context.isFile() || Context.isNameSpace()))
633     if (DIEEntry *Entry = getDIEEntry(Ty))
634       GlobalTypes[Ty.getName()] = Entry->getEntry();
635 }
636
637 /// addPubTypes - Add type for pubtypes section.
638 void CompileUnit::addPubTypes(DISubprogram SP) {
639   DICompositeType SPTy = SP.getType();
640   unsigned SPTag = SPTy.getTag();
641   if (SPTag != dwarf::DW_TAG_subroutine_type)
642     return;
643
644   DIArray Args = SPTy.getTypeArray();
645   for (unsigned i = 0, e = Args.getNumElements(); i != e; ++i) {
646     DIType ATy(Args.getElement(i));
647     if (!ATy.Verify())
648       continue;
649     addGlobalType(ATy);
650   }
651 }
652
653 /// constructTypeDIE - Construct basic type die from DIBasicType.
654 void CompileUnit::constructTypeDIE(DIE &Buffer, DIBasicType BTy) {
655   // Get core information.
656   StringRef Name = BTy.getName();
657   Buffer.setTag(dwarf::DW_TAG_base_type);
658   addUInt(&Buffer, dwarf::DW_AT_encoding,  dwarf::DW_FORM_data1,
659           BTy.getEncoding());
660
661   // Add name if not anonymous or intermediate type.
662   if (!Name.empty())
663     addString(&Buffer, dwarf::DW_AT_name, dwarf::DW_FORM_string, Name);
664   uint64_t Size = BTy.getSizeInBits() >> 3;
665   addUInt(&Buffer, dwarf::DW_AT_byte_size, 0, Size);
666 }
667
668 /// constructTypeDIE - Construct derived type die from DIDerivedType.
669 void CompileUnit::constructTypeDIE(DIE &Buffer, DIDerivedType DTy) {
670   // Get core information.
671   StringRef Name = DTy.getName();
672   uint64_t Size = DTy.getSizeInBits() >> 3;
673   unsigned Tag = DTy.getTag();
674
675   // FIXME - Workaround for templates.
676   if (Tag == dwarf::DW_TAG_inheritance) Tag = dwarf::DW_TAG_reference_type;
677
678   Buffer.setTag(Tag);
679
680   // Map to main type, void will not have a type.
681   DIType FromTy = DTy.getTypeDerivedFrom();
682   addType(&Buffer, FromTy);
683
684   // Add name if not anonymous or intermediate type.
685   if (!Name.empty())
686     addString(&Buffer, dwarf::DW_AT_name, dwarf::DW_FORM_string, Name);
687
688   // Add size if non-zero (derived types might be zero-sized.)
689   if (Size)
690     addUInt(&Buffer, dwarf::DW_AT_byte_size, 0, Size);
691
692   // Add source line info if available and TyDesc is not a forward declaration.
693   if (!DTy.isForwardDecl())
694     addSourceLine(&Buffer, DTy);
695 }
696
697 /// constructTypeDIE - Construct type DIE from DICompositeType.
698 void CompileUnit::constructTypeDIE(DIE &Buffer, DICompositeType CTy) {
699   // Get core information.
700   StringRef Name = CTy.getName();
701
702   uint64_t Size = CTy.getSizeInBits() >> 3;
703   unsigned Tag = CTy.getTag();
704   Buffer.setTag(Tag);
705
706   switch (Tag) {
707   case dwarf::DW_TAG_vector_type:
708   case dwarf::DW_TAG_array_type:
709     constructArrayTypeDIE(Buffer, &CTy);
710     break;
711   case dwarf::DW_TAG_enumeration_type: {
712     DIArray Elements = CTy.getTypeArray();
713
714     // Add enumerators to enumeration type.
715     for (unsigned i = 0, N = Elements.getNumElements(); i < N; ++i) {
716       DIE *ElemDie = NULL;
717       DIDescriptor Enum(Elements.getElement(i));
718       if (Enum.isEnumerator()) {
719         ElemDie = constructEnumTypeDIE(DIEnumerator(Enum));
720         Buffer.addChild(ElemDie);
721       }
722     }
723   }
724     break;
725   case dwarf::DW_TAG_subroutine_type: {
726     // Add return type.
727     DIArray Elements = CTy.getTypeArray();
728     DIDescriptor RTy = Elements.getElement(0);
729     addType(&Buffer, DIType(RTy));
730
731     bool isPrototyped = true;
732     // Add arguments.
733     for (unsigned i = 1, N = Elements.getNumElements(); i < N; ++i) {
734       DIDescriptor Ty = Elements.getElement(i);
735       if (Ty.isUnspecifiedParameter()) {
736         DIE *Arg = new DIE(dwarf::DW_TAG_unspecified_parameters);
737         Buffer.addChild(Arg);
738         isPrototyped = false;
739       } else {
740         DIE *Arg = new DIE(dwarf::DW_TAG_formal_parameter);
741         addType(Arg, DIType(Ty));
742         Buffer.addChild(Arg);
743       }
744     }
745     // Add prototype flag.
746     if (isPrototyped)
747       addUInt(&Buffer, dwarf::DW_AT_prototyped, dwarf::DW_FORM_flag, 1);
748   }
749     break;
750   case dwarf::DW_TAG_structure_type:
751   case dwarf::DW_TAG_union_type:
752   case dwarf::DW_TAG_class_type: {
753     // Add elements to structure type.
754     DIArray Elements = CTy.getTypeArray();
755
756     // A forward struct declared type may not have elements available.
757     unsigned N = Elements.getNumElements();
758     if (N == 0)
759       break;
760
761     // Add elements to structure type.
762     for (unsigned i = 0; i < N; ++i) {
763       DIDescriptor Element = Elements.getElement(i);
764       DIE *ElemDie = NULL;
765       if (Element.isSubprogram()) {
766         DISubprogram SP(Element);
767         ElemDie = getOrCreateSubprogramDIE(DISubprogram(Element));
768         if (SP.isProtected())
769           addUInt(ElemDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_flag,
770                   dwarf::DW_ACCESS_protected);
771         else if (SP.isPrivate())
772           addUInt(ElemDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_flag,
773                   dwarf::DW_ACCESS_private);
774         else 
775           addUInt(ElemDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_flag,
776             dwarf::DW_ACCESS_public);
777         if (SP.isExplicit())
778           addUInt(ElemDie, dwarf::DW_AT_explicit, dwarf::DW_FORM_flag, 1);
779       }
780       else if (Element.isVariable()) {
781         DIVariable DV(Element);
782         ElemDie = new DIE(dwarf::DW_TAG_variable);
783         addString(ElemDie, dwarf::DW_AT_name, dwarf::DW_FORM_string,
784                   DV.getName());
785         addType(ElemDie, DV.getType());
786         addUInt(ElemDie, dwarf::DW_AT_declaration, dwarf::DW_FORM_flag, 1);
787         addUInt(ElemDie, dwarf::DW_AT_external, dwarf::DW_FORM_flag, 1);
788         addSourceLine(ElemDie, DV);
789       } else if (Element.isDerivedType())
790         ElemDie = createMemberDIE(DIDerivedType(Element));
791       else
792         continue;
793       Buffer.addChild(ElemDie);
794     }
795
796     if (CTy.isAppleBlockExtension())
797       addUInt(&Buffer, dwarf::DW_AT_APPLE_block, dwarf::DW_FORM_flag, 1);
798
799     unsigned RLang = CTy.getRunTimeLang();
800     if (RLang)
801       addUInt(&Buffer, dwarf::DW_AT_APPLE_runtime_class,
802               dwarf::DW_FORM_data1, RLang);
803
804     DICompositeType ContainingType = CTy.getContainingType();
805     if (DIDescriptor(ContainingType).isCompositeType())
806       addDIEEntry(&Buffer, dwarf::DW_AT_containing_type, dwarf::DW_FORM_ref4,
807                   getOrCreateTypeDIE(DIType(ContainingType)));
808     else {
809       DIDescriptor Context = CTy.getContext();
810       addToContextOwner(&Buffer, Context);
811     }
812
813     if (CTy.isObjcClassComplete())
814       addUInt(&Buffer, dwarf::DW_AT_APPLE_objc_complete_type,
815               dwarf::DW_FORM_flag, 1);
816
817     if (Tag == dwarf::DW_TAG_class_type) 
818       addTemplateParams(Buffer, CTy.getTemplateParams());
819
820     break;
821   }
822   default:
823     break;
824   }
825
826   // Add name if not anonymous or intermediate type.
827   if (!Name.empty())
828     addString(&Buffer, dwarf::DW_AT_name, dwarf::DW_FORM_string, Name);
829
830   if (Tag == dwarf::DW_TAG_enumeration_type || Tag == dwarf::DW_TAG_class_type
831       || Tag == dwarf::DW_TAG_structure_type || Tag == dwarf::DW_TAG_union_type)
832     {
833     // Add size if non-zero (derived types might be zero-sized.)
834     if (Size)
835       addUInt(&Buffer, dwarf::DW_AT_byte_size, 0, Size);
836     else {
837       // Add zero size if it is not a forward declaration.
838       if (CTy.isForwardDecl())
839         addUInt(&Buffer, dwarf::DW_AT_declaration, dwarf::DW_FORM_flag, 1);
840       else
841         addUInt(&Buffer, dwarf::DW_AT_byte_size, 0, 0);
842     }
843
844     // Add source line info if available.
845     if (!CTy.isForwardDecl())
846       addSourceLine(&Buffer, CTy);
847   }
848 }
849
850 /// getOrCreateTemplateTypeParameterDIE - Find existing DIE or create new DIE 
851 /// for the given DITemplateTypeParameter.
852 DIE *
853 CompileUnit::getOrCreateTemplateTypeParameterDIE(DITemplateTypeParameter TP) {
854   DIE *ParamDIE = getDIE(TP);
855   if (ParamDIE)
856     return ParamDIE;
857
858   ParamDIE = new DIE(dwarf::DW_TAG_template_type_parameter);
859   addType(ParamDIE, TP.getType());
860   addString(ParamDIE, dwarf::DW_AT_name, dwarf::DW_FORM_string, TP.getName());
861   return ParamDIE;
862 }
863
864 /// getOrCreateTemplateValueParameterDIE - Find existing DIE or create new DIE 
865 /// for the given DITemplateValueParameter.
866 DIE *
867 CompileUnit::getOrCreateTemplateValueParameterDIE(DITemplateValueParameter TPV) {
868   DIE *ParamDIE = getDIE(TPV);
869   if (ParamDIE)
870     return ParamDIE;
871
872   ParamDIE = new DIE(dwarf::DW_TAG_template_value_parameter);
873   addType(ParamDIE, TPV.getType());
874   if (!TPV.getName().empty())
875     addString(ParamDIE, dwarf::DW_AT_name, dwarf::DW_FORM_string, TPV.getName());
876   addUInt(ParamDIE, dwarf::DW_AT_const_value, dwarf::DW_FORM_udata, 
877           TPV.getValue());
878   return ParamDIE;
879 }
880
881 /// getOrCreateNameSpace - Create a DIE for DINameSpace.
882 DIE *CompileUnit::getOrCreateNameSpace(DINameSpace NS) {
883   DIE *NDie = getDIE(NS);
884   if (NDie)
885     return NDie;
886   NDie = new DIE(dwarf::DW_TAG_namespace);
887   insertDIE(NS, NDie);
888   if (!NS.getName().empty())
889     addString(NDie, dwarf::DW_AT_name, dwarf::DW_FORM_string, NS.getName());
890   addSourceLine(NDie, NS);
891   addToContextOwner(NDie, NS.getContext());
892   return NDie;
893 }
894
895 /// getRealLinkageName - If special LLVM prefix that is used to inform the asm
896 /// printer to not emit usual symbol prefix before the symbol name is used then
897 /// return linkage name after skipping this special LLVM prefix.
898 static StringRef getRealLinkageName(StringRef LinkageName) {
899   char One = '\1';
900   if (LinkageName.startswith(StringRef(&One, 1)))
901     return LinkageName.substr(1);
902   return LinkageName;
903 }
904
905 /// getOrCreateSubprogramDIE - Create new DIE using SP.
906 DIE *CompileUnit::getOrCreateSubprogramDIE(DISubprogram SP) {
907   DIE *SPDie = getDIE(SP);
908   if (SPDie)
909     return SPDie;
910
911   SPDie = new DIE(dwarf::DW_TAG_subprogram);
912   
913   // DW_TAG_inlined_subroutine may refer to this DIE.
914   insertDIE(SP, SPDie);
915   
916   // Add to context owner.
917   addToContextOwner(SPDie, SP.getContext());
918
919   // Add function template parameters.
920   addTemplateParams(*SPDie, SP.getTemplateParams());
921
922   StringRef LinkageName = SP.getLinkageName();
923   if (!LinkageName.empty())
924     addString(SPDie, dwarf::DW_AT_MIPS_linkage_name, 
925                     dwarf::DW_FORM_string,
926                     getRealLinkageName(LinkageName));
927
928   // If this DIE is going to refer declaration info using AT_specification
929   // then there is no need to add other attributes.
930   if (SP.getFunctionDeclaration().isSubprogram())
931     return SPDie;
932
933   // Constructors and operators for anonymous aggregates do not have names.
934   if (!SP.getName().empty())
935     addString(SPDie, dwarf::DW_AT_name, dwarf::DW_FORM_string, 
936                     SP.getName());
937
938   addSourceLine(SPDie, SP);
939
940   if (SP.isPrototyped()) 
941     addUInt(SPDie, dwarf::DW_AT_prototyped, dwarf::DW_FORM_flag, 1);
942
943   // Add Return Type.
944   DICompositeType SPTy = SP.getType();
945   DIArray Args = SPTy.getTypeArray();
946   unsigned SPTag = SPTy.getTag();
947
948   if (Args.getNumElements() == 0 || SPTag != dwarf::DW_TAG_subroutine_type)
949     addType(SPDie, SPTy);
950   else
951     addType(SPDie, DIType(Args.getElement(0)));
952
953   unsigned VK = SP.getVirtuality();
954   if (VK) {
955     addUInt(SPDie, dwarf::DW_AT_virtuality, dwarf::DW_FORM_flag, VK);
956     DIEBlock *Block = getDIEBlock();
957     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_constu);
958     addUInt(Block, 0, dwarf::DW_FORM_udata, SP.getVirtualIndex());
959     addBlock(SPDie, dwarf::DW_AT_vtable_elem_location, 0, Block);
960     ContainingTypeMap.insert(std::make_pair(SPDie,
961                                             SP.getContainingType()));
962   }
963
964   if (!SP.isDefinition()) {
965     addUInt(SPDie, dwarf::DW_AT_declaration, dwarf::DW_FORM_flag, 1);
966     
967     // Add arguments. Do not add arguments for subprogram definition. They will
968     // be handled while processing variables.
969     DICompositeType SPTy = SP.getType();
970     DIArray Args = SPTy.getTypeArray();
971     unsigned SPTag = SPTy.getTag();
972
973     if (SPTag == dwarf::DW_TAG_subroutine_type)
974       for (unsigned i = 1, N =  Args.getNumElements(); i < N; ++i) {
975         DIE *Arg = new DIE(dwarf::DW_TAG_formal_parameter);
976         DIType ATy = DIType(DIType(Args.getElement(i)));
977         addType(Arg, ATy);
978         if (ATy.isArtificial())
979           addUInt(Arg, dwarf::DW_AT_artificial, dwarf::DW_FORM_flag, 1);
980         SPDie->addChild(Arg);
981       }
982   }
983
984   if (SP.isArtificial())
985     addUInt(SPDie, dwarf::DW_AT_artificial, dwarf::DW_FORM_flag, 1);
986
987   if (!SP.isLocalToUnit())
988     addUInt(SPDie, dwarf::DW_AT_external, dwarf::DW_FORM_flag, 1);
989
990   if (SP.isOptimized())
991     addUInt(SPDie, dwarf::DW_AT_APPLE_optimized, dwarf::DW_FORM_flag, 1);
992
993   if (unsigned isa = Asm->getISAEncoding()) {
994     addUInt(SPDie, dwarf::DW_AT_APPLE_isa, dwarf::DW_FORM_flag, isa);
995   }
996
997   return SPDie;
998 }
999
1000 // Return const expression if value is a GEP to access merged global
1001 // constant. e.g.
1002 // i8* getelementptr ({ i8, i8, i8, i8 }* @_MergedGlobals, i32 0, i32 0)
1003 static const ConstantExpr *getMergedGlobalExpr(const Value *V) {
1004   const ConstantExpr *CE = dyn_cast_or_null<ConstantExpr>(V);
1005   if (!CE || CE->getNumOperands() != 3 ||
1006       CE->getOpcode() != Instruction::GetElementPtr)
1007     return NULL;
1008
1009   // First operand points to a global struct.
1010   Value *Ptr = CE->getOperand(0);
1011   if (!isa<GlobalValue>(Ptr) ||
1012       !isa<StructType>(cast<PointerType>(Ptr->getType())->getElementType()))
1013     return NULL;
1014
1015   // Second operand is zero.
1016   const ConstantInt *CI = dyn_cast_or_null<ConstantInt>(CE->getOperand(1));
1017   if (!CI || !CI->isZero())
1018     return NULL;
1019
1020   // Third operand is offset.
1021   if (!isa<ConstantInt>(CE->getOperand(2)))
1022     return NULL;
1023
1024   return CE;
1025 }
1026
1027 /// createGlobalVariableDIE - create global variable DIE.
1028 void CompileUnit::createGlobalVariableDIE(const MDNode *N) {
1029   DIGlobalVariable GV(N);
1030
1031   // Check for pre-existence.
1032   if (getDIE(GV))
1033     return;
1034
1035   DIType GTy = GV.getType();
1036   DIE *VariableDIE = new DIE(GV.getTag());
1037
1038   bool isGlobalVariable = GV.getGlobal() != NULL;
1039
1040   // Add name.
1041   addString(VariableDIE, dwarf::DW_AT_name, dwarf::DW_FORM_string,
1042                    GV.getDisplayName());
1043   StringRef LinkageName = GV.getLinkageName();
1044   if (!LinkageName.empty() && isGlobalVariable)
1045     addString(VariableDIE, dwarf::DW_AT_MIPS_linkage_name, 
1046                      dwarf::DW_FORM_string,
1047                      getRealLinkageName(LinkageName));
1048   // Add type.
1049   addType(VariableDIE, GTy);
1050
1051   // Add scoping info.
1052   if (!GV.isLocalToUnit()) {
1053     addUInt(VariableDIE, dwarf::DW_AT_external, dwarf::DW_FORM_flag, 1);
1054     // Expose as global. 
1055     addGlobal(GV.getName(), VariableDIE);
1056   }
1057   // Add line number info.
1058   addSourceLine(VariableDIE, GV);
1059   // Add to map.
1060   insertDIE(N, VariableDIE);
1061   // Add to context owner.
1062   DIDescriptor GVContext = GV.getContext();
1063   addToContextOwner(VariableDIE, GVContext);
1064   // Add location.
1065   if (isGlobalVariable) {
1066     DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
1067     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_addr);
1068     addLabel(Block, 0, dwarf::DW_FORM_udata,
1069              Asm->Mang->getSymbol(GV.getGlobal()));
1070     // Do not create specification DIE if context is either compile unit
1071     // or a subprogram.
1072     if (GV.isDefinition() && !GVContext.isCompileUnit() &&
1073         !GVContext.isFile() && !isSubprogramContext(GVContext)) {
1074       // Create specification DIE.
1075       DIE *VariableSpecDIE = new DIE(dwarf::DW_TAG_variable);
1076       addDIEEntry(VariableSpecDIE, dwarf::DW_AT_specification,
1077                   dwarf::DW_FORM_ref4, VariableDIE);
1078       addBlock(VariableSpecDIE, dwarf::DW_AT_location, 0, Block);
1079       addUInt(VariableDIE, dwarf::DW_AT_declaration, dwarf::DW_FORM_flag,
1080                      1);
1081       addDie(VariableSpecDIE);
1082     } else {
1083       addBlock(VariableDIE, dwarf::DW_AT_location, 0, Block);
1084     } 
1085   } else if (const ConstantInt *CI = 
1086              dyn_cast_or_null<ConstantInt>(GV.getConstant()))
1087     addConstantValue(VariableDIE, CI, GTy.isUnsignedDIType());
1088   else if (const ConstantExpr *CE = getMergedGlobalExpr(N->getOperand(11))) {
1089     // GV is a merged global.
1090     DIEBlock *Block = new (DIEValueAllocator) DIEBlock();
1091     Value *Ptr = CE->getOperand(0);
1092     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_addr);
1093     addLabel(Block, 0, dwarf::DW_FORM_udata,
1094                     Asm->Mang->getSymbol(cast<GlobalValue>(Ptr)));
1095     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_constu);
1096     SmallVector<Value*, 3> Idx(CE->op_begin()+1, CE->op_end());
1097     addUInt(Block, 0, dwarf::DW_FORM_udata, 
1098                    Asm->getTargetData().getIndexedOffset(Ptr->getType(), Idx));
1099     addUInt(Block, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_plus);
1100     addBlock(VariableDIE, dwarf::DW_AT_location, 0, Block);
1101   }
1102
1103   return;
1104 }
1105
1106 /// constructSubrangeDIE - Construct subrange DIE from DISubrange.
1107 void CompileUnit::constructSubrangeDIE(DIE &Buffer, DISubrange SR, DIE *IndexTy){
1108   DIE *DW_Subrange = new DIE(dwarf::DW_TAG_subrange_type);
1109   addDIEEntry(DW_Subrange, dwarf::DW_AT_type, dwarf::DW_FORM_ref4, IndexTy);
1110   int64_t L = SR.getLo();
1111   int64_t H = SR.getHi();
1112
1113   // The L value defines the lower bounds which is typically zero for C/C++. The
1114   // H value is the upper bounds.  Values are 64 bit.  H - L + 1 is the size
1115   // of the array. If L > H then do not emit DW_AT_lower_bound and 
1116   // DW_AT_upper_bound attributes. If L is zero and H is also zero then the
1117   // array has one element and in such case do not emit lower bound.
1118
1119   if (L > H) {
1120     Buffer.addChild(DW_Subrange);
1121     return;
1122   }
1123   if (L)
1124     addSInt(DW_Subrange, dwarf::DW_AT_lower_bound, 0, L);
1125   addSInt(DW_Subrange, dwarf::DW_AT_upper_bound, 0, H);
1126   Buffer.addChild(DW_Subrange);
1127 }
1128
1129 /// constructArrayTypeDIE - Construct array type DIE from DICompositeType.
1130 void CompileUnit::constructArrayTypeDIE(DIE &Buffer,
1131                                         DICompositeType *CTy) {
1132   Buffer.setTag(dwarf::DW_TAG_array_type);
1133   if (CTy->getTag() == dwarf::DW_TAG_vector_type)
1134     addUInt(&Buffer, dwarf::DW_AT_GNU_vector, dwarf::DW_FORM_flag, 1);
1135
1136   // Emit derived type.
1137   addType(&Buffer, CTy->getTypeDerivedFrom());
1138   DIArray Elements = CTy->getTypeArray();
1139
1140   // Get an anonymous type for index type.
1141   DIE *IdxTy = getIndexTyDie();
1142   if (!IdxTy) {
1143     // Construct an anonymous type for index type.
1144     IdxTy = new DIE(dwarf::DW_TAG_base_type);
1145     addUInt(IdxTy, dwarf::DW_AT_byte_size, 0, sizeof(int32_t));
1146     addUInt(IdxTy, dwarf::DW_AT_encoding, dwarf::DW_FORM_data1,
1147             dwarf::DW_ATE_signed);
1148     addDie(IdxTy);
1149     setIndexTyDie(IdxTy);
1150   }
1151
1152   // Add subranges to array type.
1153   for (unsigned i = 0, N = Elements.getNumElements(); i < N; ++i) {
1154     DIDescriptor Element = Elements.getElement(i);
1155     if (Element.getTag() == dwarf::DW_TAG_subrange_type)
1156       constructSubrangeDIE(Buffer, DISubrange(Element), IdxTy);
1157   }
1158 }
1159
1160 /// constructEnumTypeDIE - Construct enum type DIE from DIEnumerator.
1161 DIE *CompileUnit::constructEnumTypeDIE(DIEnumerator ETy) {
1162   DIE *Enumerator = new DIE(dwarf::DW_TAG_enumerator);
1163   StringRef Name = ETy.getName();
1164   addString(Enumerator, dwarf::DW_AT_name, dwarf::DW_FORM_string, Name);
1165   int64_t Value = ETy.getEnumValue();
1166   addSInt(Enumerator, dwarf::DW_AT_const_value, dwarf::DW_FORM_sdata, Value);
1167   return Enumerator;
1168 }
1169
1170 /// constructContainingTypeDIEs - Construct DIEs for types that contain
1171 /// vtables.
1172 void CompileUnit::constructContainingTypeDIEs() {
1173   for (DenseMap<DIE *, const MDNode *>::iterator CI = ContainingTypeMap.begin(),
1174          CE = ContainingTypeMap.end(); CI != CE; ++CI) {
1175     DIE *SPDie = CI->first;
1176     const MDNode *N = CI->second;
1177     if (!N) continue;
1178     DIE *NDie = getDIE(N);
1179     if (!NDie) continue;
1180     addDIEEntry(SPDie, dwarf::DW_AT_containing_type, dwarf::DW_FORM_ref4, NDie);
1181   }
1182 }
1183
1184 /// createMemberDIE - Create new member DIE.
1185 DIE *CompileUnit::createMemberDIE(DIDerivedType DT) {
1186   DIE *MemberDie = new DIE(DT.getTag());
1187   StringRef Name = DT.getName();
1188   if (!Name.empty())
1189     addString(MemberDie, dwarf::DW_AT_name, dwarf::DW_FORM_string, Name);
1190
1191   addType(MemberDie, DT.getTypeDerivedFrom());
1192
1193   addSourceLine(MemberDie, DT);
1194
1195   DIEBlock *MemLocationDie = new (DIEValueAllocator) DIEBlock();
1196   addUInt(MemLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_plus_uconst);
1197
1198   uint64_t Size = DT.getSizeInBits();
1199   uint64_t FieldSize = DT.getOriginalTypeSize();
1200
1201   if (Size != FieldSize) {
1202     // Handle bitfield.
1203     addUInt(MemberDie, dwarf::DW_AT_byte_size, 0, DT.getOriginalTypeSize()>>3);
1204     addUInt(MemberDie, dwarf::DW_AT_bit_size, 0, DT.getSizeInBits());
1205
1206     uint64_t Offset = DT.getOffsetInBits();
1207     uint64_t AlignMask = ~(DT.getAlignInBits() - 1);
1208     uint64_t HiMark = (Offset + FieldSize) & AlignMask;
1209     uint64_t FieldOffset = (HiMark - FieldSize);
1210     Offset -= FieldOffset;
1211
1212     // Maybe we need to work from the other end.
1213     if (Asm->getTargetData().isLittleEndian())
1214       Offset = FieldSize - (Offset + Size);
1215     addUInt(MemberDie, dwarf::DW_AT_bit_offset, 0, Offset);
1216
1217     // Here WD_AT_data_member_location points to the anonymous
1218     // field that includes this bit field.
1219     addUInt(MemLocationDie, 0, dwarf::DW_FORM_udata, FieldOffset >> 3);
1220
1221   } else
1222     // This is not a bitfield.
1223     addUInt(MemLocationDie, 0, dwarf::DW_FORM_udata, DT.getOffsetInBits() >> 3);
1224
1225   if (DT.getTag() == dwarf::DW_TAG_inheritance
1226       && DT.isVirtual()) {
1227
1228     // For C++, virtual base classes are not at fixed offset. Use following
1229     // expression to extract appropriate offset from vtable.
1230     // BaseAddr = ObAddr + *((*ObAddr) - Offset)
1231
1232     DIEBlock *VBaseLocationDie = new (DIEValueAllocator) DIEBlock();
1233     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_dup);
1234     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
1235     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_constu);
1236     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_udata, DT.getOffsetInBits());
1237     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_minus);
1238     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_deref);
1239     addUInt(VBaseLocationDie, 0, dwarf::DW_FORM_data1, dwarf::DW_OP_plus);
1240
1241     addBlock(MemberDie, dwarf::DW_AT_data_member_location, 0,
1242              VBaseLocationDie);
1243   } else
1244     addBlock(MemberDie, dwarf::DW_AT_data_member_location, 0, MemLocationDie);
1245
1246   if (DT.isProtected())
1247     addUInt(MemberDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_flag,
1248             dwarf::DW_ACCESS_protected);
1249   else if (DT.isPrivate())
1250     addUInt(MemberDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_flag,
1251             dwarf::DW_ACCESS_private);
1252   // Otherwise C++ member and base classes are considered public.
1253   else if (DT.getCompileUnit().getLanguage() == dwarf::DW_LANG_C_plus_plus)
1254     addUInt(MemberDie, dwarf::DW_AT_accessibility, dwarf::DW_FORM_flag,
1255             dwarf::DW_ACCESS_public);
1256   if (DT.isVirtual())
1257     addUInt(MemberDie, dwarf::DW_AT_virtuality, dwarf::DW_FORM_flag,
1258             dwarf::DW_VIRTUALITY_virtual);
1259
1260   // Objective-C properties.
1261   StringRef PropertyName = DT.getObjCPropertyName();
1262   if (!PropertyName.empty()) {
1263     addString(MemberDie, dwarf::DW_AT_APPLE_property_name, dwarf::DW_FORM_string,
1264               PropertyName);
1265     StringRef GetterName = DT.getObjCPropertyGetterName();
1266     if (!GetterName.empty())
1267       addString(MemberDie, dwarf::DW_AT_APPLE_property_getter,
1268                 dwarf::DW_FORM_string, GetterName);
1269     StringRef SetterName = DT.getObjCPropertySetterName();
1270     if (!SetterName.empty())
1271       addString(MemberDie, dwarf::DW_AT_APPLE_property_setter,
1272                 dwarf::DW_FORM_string, SetterName);
1273     unsigned PropertyAttributes = 0;
1274     if (DT.isReadOnlyObjCProperty())
1275       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_readonly;
1276     if (DT.isReadWriteObjCProperty())
1277       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_readwrite;
1278     if (DT.isAssignObjCProperty())
1279       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_assign;
1280     if (DT.isRetainObjCProperty())
1281       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_retain;
1282     if (DT.isCopyObjCProperty())
1283       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_copy;
1284     if (DT.isNonAtomicObjCProperty())
1285       PropertyAttributes |= dwarf::DW_APPLE_PROPERTY_nonatomic;
1286     if (PropertyAttributes)
1287       addUInt(MemberDie, dwarf::DW_AT_APPLE_property_attribute, 0, 
1288               PropertyAttributes);
1289   }
1290   return MemberDie;
1291 }