Skip to content

Commit 04a4ab9

Browse files
authored
Merge pull request #50 from schweitzpgi/release_70
Changes to support the generation of DW_TAG_common_block (DWARF debug…
2 parents d5545b3 + cf3b4ad commit 04a4ab9

File tree

16 files changed

+331
-59
lines changed

16 files changed

+331
-59
lines changed

include/llvm/Bitcode/LLVMBitCodes.h

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -314,6 +314,7 @@ enum MetadataCodes {
314314
METADATA_STRING_TYPE = 41, // [distinct, name, size, align, ...]
315315
METADATA_FORTRAN_ARRAY_TYPE = 42, // [distinct, name, [bounds ...], ...]
316316
METADATA_FORTRAN_SUBRANGE = 43, // [distinct, lbound, lbnde, ubound, ubnde]
317+
METADATA_COMMON_BLOCK = 44, // [distinct, scope, name, variable,...]
317318
};
318319

319320
// The constants block (CONSTANTS_BLOCK_ID) describes emission for each

include/llvm/IR/DIBuilder.h

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -727,6 +727,17 @@ namespace llvm {
727727
DITemplateParameterArray TParams = nullptr,
728728
DITypeArray ThrownTypes = nullptr);
729729

730+
/// Create common block entry for a Fortran common block
731+
/// \param Scope Scope of this common block
732+
/// \param Name The name of this common block
733+
/// \param File The file this common block is defined
734+
/// \param LineNo Line number
735+
/// \param VarList List of variables that a located in common block
736+
/// \param AlignInBits Common block alignment
737+
DICommonBlock *createCommonBlock(DIScope *Scope, DIGlobalVariable *decl,
738+
StringRef Name, DIFile *File,
739+
unsigned LineNo, uint32_t AlignInBits = 0);
740+
730741
/// This creates new descriptor for a namespace with the specified
731742
/// parent scope.
732743
/// \param Scope Namespace scope

include/llvm/IR/DebugInfoMetadata.h

Lines changed: 64 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -231,6 +231,7 @@ class DINode : public MDNode {
231231
case DILexicalBlockKind:
232232
case DILexicalBlockFileKind:
233233
case DINamespaceKind:
234+
case DICommonBlockKind:
234235
case DITemplateTypeParameterKind:
235236
case DITemplateValueParameterKind:
236237
case DIGlobalVariableKind:
@@ -556,6 +557,7 @@ class DIScope : public DINode {
556557
case DILexicalBlockKind:
557558
case DILexicalBlockFileKind:
558559
case DINamespaceKind:
560+
case DICommonBlockKind:
559561
case DIModuleKind:
560562
return true;
561563
}
@@ -2835,6 +2837,68 @@ class DIGlobalVariable : public DIVariable {
28352837
}
28362838
};
28372839

2840+
class DICommonBlock : public DIScope {
2841+
unsigned LineNo;
2842+
uint32_t AlignInBits;
2843+
2844+
friend class LLVMContextImpl;
2845+
friend class MDNode;
2846+
2847+
DICommonBlock(LLVMContext &Context, StorageType Storage, unsigned LineNo,
2848+
uint32_t AlignInBits, ArrayRef<Metadata *> Ops)
2849+
: DIScope(Context, DICommonBlockKind, Storage, dwarf::DW_TAG_common_block,
2850+
Ops), LineNo(LineNo), AlignInBits(AlignInBits) {}
2851+
~DICommonBlock() = default;
2852+
2853+
static DICommonBlock *getImpl(LLVMContext &Context, DIScope *Scope,
2854+
DIGlobalVariable *Decl, StringRef Name,
2855+
DIFile *File, unsigned LineNo,
2856+
uint32_t AlignInBits, StorageType Storage,
2857+
bool ShouldCreate = true) {
2858+
return getImpl(Context, Scope, Decl, getCanonicalMDString(Context, Name),
2859+
File, LineNo, AlignInBits, Storage, ShouldCreate);
2860+
}
2861+
static DICommonBlock *getImpl(LLVMContext &Context, Metadata *Scope,
2862+
Metadata *Decl, MDString *Name, Metadata *File,
2863+
unsigned LineNo, uint32_t AlignInBits,
2864+
StorageType Storage, bool ShouldCreate = true);
2865+
2866+
TempDICommonBlock cloneImpl() const {
2867+
return getTemporary(getContext(), getScope(), getDecl(), getName(),
2868+
getFile(), getLineNo(), getAlignInBits());
2869+
}
2870+
2871+
public:
2872+
DEFINE_MDNODE_GET(DICommonBlock,
2873+
(DIScope *Scope, DIGlobalVariable *Decl, StringRef Name,
2874+
DIFile *File, unsigned LineNo, uint32_t AlignInBits),
2875+
(Scope, Decl, Name, File, LineNo, AlignInBits))
2876+
DEFINE_MDNODE_GET(DICommonBlock,
2877+
(Metadata *Scope, Metadata *Decl, MDString *Name,
2878+
Metadata *File, unsigned LineNo, uint32_t AlignInBits),
2879+
(Scope, Decl, Name, File, LineNo, AlignInBits))
2880+
2881+
TempDICommonBlock clone() const { return cloneImpl(); }
2882+
2883+
DIScope *getScope() const { return cast_or_null<DIScope>(getRawScope()); }
2884+
DIGlobalVariable *getDecl() const {
2885+
return cast_or_null<DIGlobalVariable>(getRawDecl());
2886+
}
2887+
StringRef getName() const { return getStringOperand(2); }
2888+
DIFile *getFile() const { return cast_or_null<DIFile>(getRawFile()); }
2889+
unsigned getLineNo() const { return LineNo; }
2890+
uint32_t getAlignInBits() const { return AlignInBits; }
2891+
2892+
Metadata *getRawScope() const { return getOperand(0); }
2893+
Metadata *getRawDecl() const { return getOperand(1); }
2894+
MDString *getRawName() const { return getOperandAs<MDString>(2); }
2895+
Metadata *getRawFile() const { return getOperand(3); }
2896+
2897+
static bool classof(const Metadata *MD) {
2898+
return MD->getMetadataID() == DICommonBlockKind;
2899+
}
2900+
};
2901+
28382902
/// Local variable.
28392903
///
28402904
/// TODO: Split up flags.

include/llvm/IR/Metadata.def

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -117,6 +117,7 @@ HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIMacroFile)
117117
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIStringType)
118118
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIFortranArrayType)
119119
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIFortranSubrange)
120+
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DICommonBlock)
120121

121122
#undef HANDLE_METADATA
122123
#undef HANDLE_METADATA_LEAF

lib/AsmParser/LLParser.cpp

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4605,6 +4605,25 @@ bool LLParser::ParseDILexicalBlockFile(MDNode *&Result, bool IsDistinct) {
46054605
return false;
46064606
}
46074607

4608+
/// ParseDICommonBlock:
4609+
/// ::= !DICommonBlock(scope: !0, file: !2, name: "SomeNamespace", line: 9)
4610+
bool LLParser::ParseDICommonBlock(MDNode *&Result, bool IsDistinct) {
4611+
#define VISIT_MD_FIELDS(OPTIONAL, REQUIRED) \
4612+
REQUIRED(scope, MDField, ); \
4613+
OPTIONAL(declaration, MDField, ); \
4614+
OPTIONAL(name, MDStringField, ); \
4615+
OPTIONAL(file, MDField, ); \
4616+
OPTIONAL(line, LineField, ); \
4617+
OPTIONAL(align, MDUnsignedField, (0, UINT32_MAX));
4618+
PARSE_MD_FIELDS();
4619+
#undef VISIT_MD_FIELDS
4620+
4621+
Result = GET_OR_DISTINCT(DICommonBlock,
4622+
(Context, scope.Val, declaration.Val, name.Val,
4623+
file.Val, line.Val, align.Val));
4624+
return false;
4625+
}
4626+
46084627
/// ParseDINamespace:
46094628
/// ::= !DINamespace(scope: !0, file: !2, name: "SomeNamespace", line: 9)
46104629
bool LLParser::ParseDINamespace(MDNode *&Result, bool IsDistinct) {

lib/Bitcode/Reader/MetadataLoader.cpp

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -819,6 +819,7 @@ MetadataLoader::MetadataLoaderImpl::lazyLoadModuleMetadataBlock() {
819819
case bitc::METADATA_LEXICAL_BLOCK:
820820
case bitc::METADATA_LEXICAL_BLOCK_FILE:
821821
case bitc::METADATA_NAMESPACE:
822+
case bitc::METADATA_COMMON_BLOCK:
822823
case bitc::METADATA_MACRO:
823824
case bitc::METADATA_MACRO_FILE:
824825
case bitc::METADATA_TEMPLATE_TYPE:
@@ -1548,6 +1549,17 @@ Error MetadataLoader::MetadataLoaderImpl::parseOneMetadata(
15481549
NextMetadataNo++;
15491550
break;
15501551
}
1552+
case bitc::METADATA_COMMON_BLOCK: {
1553+
IsDistinct = Record[0] & 1;
1554+
MetadataList.assignValue(
1555+
GET_OR_DISTINCT(DICommonBlock,
1556+
(Context, getMDOrNull(Record[1]),
1557+
getMDOrNull(Record[2]), getMDString(Record[3]),
1558+
getMDOrNull(Record[4]), Record[5], Record[6])),
1559+
NextMetadataNo);
1560+
NextMetadataNo++;
1561+
break;
1562+
}
15511563
case bitc::METADATA_NAMESPACE: {
15521564
// Newer versions of DINamespace dropped file and line.
15531565
MDString *Name;

lib/Bitcode/Writer/BitcodeWriter.cpp

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -324,6 +324,8 @@ class ModuleBitcodeWriter : public ModuleBitcodeWriterBase {
324324
void writeDILexicalBlockFile(const DILexicalBlockFile *N,
325325
SmallVectorImpl<uint64_t> &Record,
326326
unsigned Abbrev);
327+
void writeDICommonBlock(const DICommonBlock *N,
328+
SmallVectorImpl<uint64_t> &Record, unsigned Abbrev);
327329
void writeDINamespace(const DINamespace *N, SmallVectorImpl<uint64_t> &Record,
328330
unsigned Abbrev);
329331
void writeDIMacro(const DIMacro *N, SmallVectorImpl<uint64_t> &Record,
@@ -1723,6 +1725,21 @@ void ModuleBitcodeWriter::writeDILexicalBlockFile(
17231725
Record.clear();
17241726
}
17251727

1728+
void ModuleBitcodeWriter::writeDICommonBlock(const DICommonBlock *N,
1729+
SmallVectorImpl<uint64_t> &Record,
1730+
unsigned Abbrev) {
1731+
Record.push_back(N->isDistinct());
1732+
Record.push_back(VE.getMetadataOrNullID(N->getScope()));
1733+
Record.push_back(VE.getMetadataOrNullID(N->getDecl()));
1734+
Record.push_back(VE.getMetadataOrNullID(N->getRawName()));
1735+
Record.push_back(VE.getMetadataOrNullID(N->getFile()));
1736+
Record.push_back(N->getLineNo());
1737+
Record.push_back(N->getAlignInBits());
1738+
1739+
Stream.EmitRecord(bitc::METADATA_COMMON_BLOCK, Record, Abbrev);
1740+
Record.clear();
1741+
}
1742+
17261743
void ModuleBitcodeWriter::writeDINamespace(const DINamespace *N,
17271744
SmallVectorImpl<uint64_t> &Record,
17281745
unsigned Abbrev) {

lib/CodeGen/AsmPrinter/DwarfCompileUnit.cpp

Lines changed: 88 additions & 58 deletions
Original file line numberDiff line numberDiff line change
@@ -108,59 +108,8 @@ unsigned DwarfCompileUnit::getOrCreateSourceID(const DIFile *File) {
108108
File->getSource(), CUID);
109109
}
110110

111-
DIE *DwarfCompileUnit::getOrCreateGlobalVariableDIE(
112-
const DIGlobalVariable *GV, ArrayRef<GlobalExpr> GlobalExprs) {
113-
// Check for pre-existence.
114-
if (DIE *Die = getDIE(GV))
115-
return Die;
116-
117-
assert(GV);
118-
119-
auto *GVContext = GV->getScope();
120-
auto *GTy = DD->resolve(GV->getType());
121-
122-
// Construct the context before querying for the existence of the DIE in
123-
// case such construction creates the DIE.
124-
DIE *ContextDIE = getOrCreateContextDIE(GVContext);
125-
126-
// Add to map.
127-
DIE *VariableDIE = &createAndAddDIE(GV->getTag(), *ContextDIE, GV);
128-
DIScope *DeclContext;
129-
if (auto *SDMDecl = GV->getStaticDataMemberDeclaration()) {
130-
DeclContext = resolve(SDMDecl->getScope());
131-
assert(SDMDecl->isStaticMember() && "Expected static member decl");
132-
assert(GV->isDefinition());
133-
// We need the declaration DIE that is in the static member's class.
134-
DIE *VariableSpecDIE = getOrCreateStaticMemberDIE(SDMDecl);
135-
addDIEEntry(*VariableDIE, dwarf::DW_AT_specification, *VariableSpecDIE);
136-
// If the global variable's type is different from the one in the class
137-
// member type, assume that it's more specific and also emit it.
138-
if (GTy != DD->resolve(SDMDecl->getBaseType()))
139-
addType(*VariableDIE, GTy);
140-
} else {
141-
DeclContext = GV->getScope();
142-
// Add name and type.
143-
addString(*VariableDIE, dwarf::DW_AT_name, GV->getDisplayName());
144-
addType(*VariableDIE, GTy);
145-
146-
// Add scoping info.
147-
if (!GV->isLocalToUnit())
148-
addFlag(*VariableDIE, dwarf::DW_AT_external);
149-
150-
// Add line number info.
151-
addSourceLine(*VariableDIE, GV);
152-
}
153-
154-
if (!GV->isDefinition())
155-
addFlag(*VariableDIE, dwarf::DW_AT_declaration);
156-
else
157-
addGlobalName(GV->getName(), *VariableDIE, DeclContext);
158-
159-
if (uint32_t AlignInBytes = GV->getAlignInBytes())
160-
addUInt(*VariableDIE, dwarf::DW_AT_alignment, dwarf::DW_FORM_udata,
161-
AlignInBytes);
162-
163-
// Add location.
111+
void DwarfCompileUnit::addLocationAttribute(
112+
DIE *ToDIE, const DIGlobalVariable *GV, ArrayRef<GlobalExpr> GlobalExprs) {
164113
bool addToAccelTable = false;
165114
DIELoc *Loc = nullptr;
166115
std::unique_ptr<DIEDwarfExpression> DwarfExpr;
@@ -173,7 +122,7 @@ DIE *DwarfCompileUnit::getOrCreateGlobalVariableDIE(
173122
// DW_AT_const_value(X).
174123
if (GlobalExprs.size() == 1 && Expr && Expr->isConstant()) {
175124
addToAccelTable = true;
176-
addConstantValue(*VariableDIE, /*Unsigned=*/true, Expr->getElement(1));
125+
addConstantValue(*ToDIE, /*Unsigned=*/true, Expr->getElement(1));
177126
break;
178127
}
179128

@@ -239,20 +188,101 @@ DIE *DwarfCompileUnit::getOrCreateGlobalVariableDIE(
239188
DwarfExpr->addExpression(Expr);
240189
}
241190
if (Loc)
242-
addBlock(*VariableDIE, dwarf::DW_AT_location, DwarfExpr->finalize());
191+
addBlock(*ToDIE, dwarf::DW_AT_location, DwarfExpr->finalize());
243192

244193
if (DD->useAllLinkageNames())
245-
addLinkageName(*VariableDIE, GV->getLinkageName());
194+
addLinkageName(*ToDIE, GV->getLinkageName());
246195

247196
if (addToAccelTable) {
248-
DD->addAccelName(GV->getName(), *VariableDIE);
197+
DD->addAccelName(GV->getName(), *ToDIE);
249198

250199
// If the linkage name is different than the name, go ahead and output
251200
// that as well into the name table.
252201
if (GV->getLinkageName() != "" && GV->getName() != GV->getLinkageName() &&
253202
DD->useAllLinkageNames())
254-
DD->addAccelName(GV->getLinkageName(), *VariableDIE);
203+
DD->addAccelName(GV->getLinkageName(), *ToDIE);
204+
}
205+
}
206+
207+
DIE *DwarfCompileUnit::getOrCreateCommonBlock(
208+
const DICommonBlock *CB, ArrayRef<GlobalExpr> GlobalExprs) {
209+
// Construct the context before querying for the existence of the DIE in case
210+
// such construction creates the DIE.
211+
DIE *ContextDIE = getOrCreateContextDIE(CB->getScope());
212+
213+
if (DIE *NDie = getDIE(CB))
214+
return NDie;
215+
DIE &NDie = createAndAddDIE(dwarf::DW_TAG_common_block, *ContextDIE, CB);
216+
StringRef Name = CB->getName().empty() ? "_BLNK_" : CB->getName();
217+
addString(NDie, dwarf::DW_AT_name, Name);
218+
addGlobalName(Name, NDie, CB->getScope());
219+
if (CB->getFile())
220+
addSourceLine(NDie, CB->getLineNo(), CB->getFile());
221+
if (DIGlobalVariable *V = CB->getDecl())
222+
getCU().addLocationAttribute(&NDie, V, GlobalExprs);
223+
if (uint32_t AlignInBits = CB->getAlignInBits()) {
224+
uint32_t AlignInBytes = AlignInBits >> 3;
225+
addUInt(NDie, dwarf::DW_AT_alignment, dwarf::DW_FORM_udata, AlignInBytes);
255226
}
227+
return &NDie;
228+
}
229+
230+
DIE *DwarfCompileUnit::getOrCreateGlobalVariableDIE(
231+
const DIGlobalVariable *GV, ArrayRef<GlobalExpr> GlobalExprs) {
232+
// Check for pre-existence.
233+
if (DIE *Die = getDIE(GV))
234+
return Die;
235+
236+
assert(GV);
237+
238+
auto *GVContext = GV->getScope();
239+
auto *GTy = DD->resolve(GV->getType());
240+
241+
// Construct the context before querying for the existence of the DIE in
242+
// case such construction creates the DIE.
243+
auto *CB = dyn_cast<DICommonBlock>(GVContext);
244+
DIE *ContextDIE = CB ? getOrCreateCommonBlock(CB, GlobalExprs)
245+
: getOrCreateContextDIE(GVContext);
246+
247+
// Add to map.
248+
DIE *VariableDIE = &createAndAddDIE(GV->getTag(), *ContextDIE, GV);
249+
DIScope *DeclContext;
250+
if (auto *SDMDecl = GV->getStaticDataMemberDeclaration()) {
251+
DeclContext = resolve(SDMDecl->getScope());
252+
assert(SDMDecl->isStaticMember() && "Expected static member decl");
253+
assert(GV->isDefinition());
254+
// We need the declaration DIE that is in the static member's class.
255+
DIE *VariableSpecDIE = getOrCreateStaticMemberDIE(SDMDecl);
256+
addDIEEntry(*VariableDIE, dwarf::DW_AT_specification, *VariableSpecDIE);
257+
// If the global variable's type is different from the one in the class
258+
// member type, assume that it's more specific and also emit it.
259+
if (GTy != DD->resolve(SDMDecl->getBaseType()))
260+
addType(*VariableDIE, GTy);
261+
} else {
262+
DeclContext = GV->getScope();
263+
// Add name and type.
264+
addString(*VariableDIE, dwarf::DW_AT_name, GV->getDisplayName());
265+
addType(*VariableDIE, GTy);
266+
267+
// Add scoping info.
268+
if (!GV->isLocalToUnit())
269+
addFlag(*VariableDIE, dwarf::DW_AT_external);
270+
271+
// Add line number info.
272+
addSourceLine(*VariableDIE, GV);
273+
}
274+
275+
if (!GV->isDefinition())
276+
addFlag(*VariableDIE, dwarf::DW_AT_declaration);
277+
else
278+
addGlobalName(GV->getName(), *VariableDIE, DeclContext);
279+
280+
if (uint32_t AlignInBytes = GV->getAlignInBytes())
281+
addUInt(*VariableDIE, dwarf::DW_AT_alignment, dwarf::DW_FORM_udata,
282+
AlignInBytes);
283+
284+
// Add location.
285+
addLocationAttribute(VariableDIE, GV, GlobalExprs);
256286

257287
return VariableDIE;
258288
}

lib/CodeGen/AsmPrinter/DwarfCompileUnit.h

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -132,6 +132,12 @@ class DwarfCompileUnit final : public DwarfUnit {
132132
getOrCreateGlobalVariableDIE(const DIGlobalVariable *GV,
133133
ArrayRef<GlobalExpr> GlobalExprs);
134134

135+
DIE *getOrCreateCommonBlock(const DICommonBlock *CB,
136+
ArrayRef<GlobalExpr> GlobalExprs);
137+
138+
void addLocationAttribute(DIE *ToDIE, const DIGlobalVariable *GV,
139+
ArrayRef<GlobalExpr> GlobalExprs);
140+
135141
/// addLabelAddress - Add a dwarf label attribute data and value using
136142
/// either DW_FORM_addr or DW_FORM_GNU_addr_index.
137143
void addLabelAddress(DIE &Die, dwarf::Attribute Attribute,

0 commit comments

Comments
 (0)