Skip to content

Commit e759b6c

Browse files
authored
Merge pull request #49 from schweitzpgi/release_60
Changes to support the generation of DW_TAG_common_block (DWARF debug…
2 parents d8b3008 + 0f8087d commit e759b6c

16 files changed

+332
-59
lines changed

include/llvm/Bitcode/LLVMBitCodes.h

+1
Original file line numberDiff line numberDiff line change
@@ -301,6 +301,7 @@ enum MetadataCodes {
301301
METADATA_STRING_TYPE = 40, // [distinct, name, size, align, ...]
302302
METADATA_FORTRAN_ARRAY_TYPE = 41, // [distinct, name, [bounds ...], ...]
303303
METADATA_FORTRAN_SUBRANGE = 42, // [distinct, lbound, lbnde, ubound, ubnde]
304+
METADATA_COMMON_BLOCK = 43, // [distinct, scope, name, variable,...]
304305
};
305306

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

include/llvm/IR/DIBuilder.h

+11
Original file line numberDiff line numberDiff line change
@@ -658,6 +658,17 @@ namespace llvm {
658658
DITemplateParameterArray TParams = nullptr,
659659
DITypeArray ThrownTypes = nullptr);
660660

661+
/// Create common block entry for a Fortran common block
662+
/// \param Scope Scope of this common block
663+
/// \param Name The name of this common block
664+
/// \param File The file this common block is defined
665+
/// \param LineNo Line number
666+
/// \param VarList List of variables that a located in common block
667+
/// \param AlignInBits Common block alignment
668+
DICommonBlock *createCommonBlock(DIScope *Scope, DIGlobalVariable *decl,
669+
StringRef Name, DIFile *File,
670+
unsigned LineNo, uint32_t AlignInBits = 0);
671+
661672
/// This creates new descriptor for a namespace with the specified
662673
/// parent scope.
663674
/// \param Scope Namespace scope

include/llvm/IR/DebugInfoMetadata.h

+64
Original file line numberDiff line numberDiff line change
@@ -229,6 +229,7 @@ class DINode : public MDNode {
229229
case DILexicalBlockKind:
230230
case DILexicalBlockFileKind:
231231
case DINamespaceKind:
232+
case DICommonBlockKind:
232233
case DITemplateTypeParameterKind:
233234
case DITemplateValueParameterKind:
234235
case DIGlobalVariableKind:
@@ -528,6 +529,7 @@ class DIScope : public DINode {
528529
case DILexicalBlockKind:
529530
case DILexicalBlockFileKind:
530531
case DINamespaceKind:
532+
case DICommonBlockKind:
531533
case DIModuleKind:
532534
return true;
533535
}
@@ -2653,6 +2655,68 @@ class DIGlobalVariable : public DIVariable {
26532655
}
26542656
};
26552657

2658+
class DICommonBlock : public DIScope {
2659+
unsigned LineNo;
2660+
uint32_t AlignInBits;
2661+
2662+
friend class LLVMContextImpl;
2663+
friend class MDNode;
2664+
2665+
DICommonBlock(LLVMContext &Context, StorageType Storage, unsigned LineNo,
2666+
uint32_t AlignInBits, ArrayRef<Metadata *> Ops)
2667+
: DIScope(Context, DICommonBlockKind, Storage, dwarf::DW_TAG_common_block,
2668+
Ops), LineNo(LineNo), AlignInBits(AlignInBits) {}
2669+
~DICommonBlock() = default;
2670+
2671+
static DICommonBlock *getImpl(LLVMContext &Context, DIScope *Scope,
2672+
DIGlobalVariable *Decl, StringRef Name,
2673+
DIFile *File, unsigned LineNo,
2674+
uint32_t AlignInBits, StorageType Storage,
2675+
bool ShouldCreate = true) {
2676+
return getImpl(Context, Scope, Decl, getCanonicalMDString(Context, Name),
2677+
File, LineNo, AlignInBits, Storage, ShouldCreate);
2678+
}
2679+
static DICommonBlock *getImpl(LLVMContext &Context, Metadata *Scope,
2680+
Metadata *Decl, MDString *Name, Metadata *File,
2681+
unsigned LineNo, uint32_t AlignInBits,
2682+
StorageType Storage, bool ShouldCreate = true);
2683+
2684+
TempDICommonBlock cloneImpl() const {
2685+
return getTemporary(getContext(), getScope(), getDecl(), getName(),
2686+
getFile(), getLineNo(), getAlignInBits());
2687+
}
2688+
2689+
public:
2690+
DEFINE_MDNODE_GET(DICommonBlock,
2691+
(DIScope *Scope, DIGlobalVariable *Decl, StringRef Name,
2692+
DIFile *File, unsigned LineNo, uint32_t AlignInBits),
2693+
(Scope, Decl, Name, File, LineNo, AlignInBits))
2694+
DEFINE_MDNODE_GET(DICommonBlock,
2695+
(Metadata *Scope, Metadata *Decl, MDString *Name,
2696+
Metadata *File, unsigned LineNo, uint32_t AlignInBits),
2697+
(Scope, Decl, Name, File, LineNo, AlignInBits))
2698+
2699+
TempDICommonBlock clone() const { return cloneImpl(); }
2700+
2701+
DIScope *getScope() const { return cast_or_null<DIScope>(getRawScope()); }
2702+
DIGlobalVariable *getDecl() const {
2703+
return cast_or_null<DIGlobalVariable>(getRawDecl());
2704+
}
2705+
StringRef getName() const { return getStringOperand(2); }
2706+
DIFile *getFile() const { return cast_or_null<DIFile>(getRawFile()); }
2707+
unsigned getLineNo() const { return LineNo; }
2708+
uint32_t getAlignInBits() const { return AlignInBits; }
2709+
2710+
Metadata *getRawScope() const { return getOperand(0); }
2711+
Metadata *getRawDecl() const { return getOperand(1); }
2712+
MDString *getRawName() const { return getOperandAs<MDString>(2); }
2713+
Metadata *getRawFile() const { return getOperand(3); }
2714+
2715+
static bool classof(const Metadata *MD) {
2716+
return MD->getMetadataID() == DICommonBlockKind;
2717+
}
2718+
};
2719+
26562720
/// Local variable.
26572721
///
26582722
/// TODO: Split up flags.

include/llvm/IR/Metadata.def

+1
Original file line numberDiff line numberDiff line change
@@ -116,6 +116,7 @@ HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIMacroFile)
116116
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIStringType)
117117
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIFortranArrayType)
118118
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIFortranSubrange)
119+
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DICommonBlock)
119120

120121
#undef HANDLE_METADATA
121122
#undef HANDLE_METADATA_LEAF

lib/AsmParser/LLParser.cpp

+19
Original file line numberDiff line numberDiff line change
@@ -4310,6 +4310,25 @@ bool LLParser::ParseDILexicalBlockFile(MDNode *&Result, bool IsDistinct) {
43104310
return false;
43114311
}
43124312

4313+
/// ParseDICommonBlock:
4314+
/// ::= !DICommonBlock(scope: !0, file: !2, name: "SomeNamespace", line: 9)
4315+
bool LLParser::ParseDICommonBlock(MDNode *&Result, bool IsDistinct) {
4316+
#define VISIT_MD_FIELDS(OPTIONAL, REQUIRED) \
4317+
REQUIRED(scope, MDField, ); \
4318+
OPTIONAL(declaration, MDField, ); \
4319+
OPTIONAL(name, MDStringField, ); \
4320+
OPTIONAL(file, MDField, ); \
4321+
OPTIONAL(line, LineField, ); \
4322+
OPTIONAL(align, MDUnsignedField, (0, UINT32_MAX));
4323+
PARSE_MD_FIELDS();
4324+
#undef VISIT_MD_FIELDS
4325+
4326+
Result = GET_OR_DISTINCT(DICommonBlock,
4327+
(Context, scope.Val, declaration.Val, name.Val,
4328+
file.Val, line.Val, align.Val));
4329+
return false;
4330+
}
4331+
43134332
/// ParseDINamespace:
43144333
/// ::= !DINamespace(scope: !0, file: !2, name: "SomeNamespace", line: 9)
43154334
bool LLParser::ParseDINamespace(MDNode *&Result, bool IsDistinct) {

lib/Bitcode/Reader/MetadataLoader.cpp

+12
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:
@@ -1524,6 +1525,17 @@ Error MetadataLoader::MetadataLoaderImpl::parseOneMetadata(
15241525
NextMetadataNo++;
15251526
break;
15261527
}
1528+
case bitc::METADATA_COMMON_BLOCK: {
1529+
IsDistinct = Record[0] & 1;
1530+
MetadataList.assignValue(
1531+
GET_OR_DISTINCT(DICommonBlock,
1532+
(Context, getMDOrNull(Record[1]),
1533+
getMDOrNull(Record[2]), getMDString(Record[3]),
1534+
getMDOrNull(Record[4]), Record[5], Record[6])),
1535+
NextMetadataNo);
1536+
NextMetadataNo++;
1537+
break;
1538+
}
15271539
case bitc::METADATA_NAMESPACE: {
15281540
// Newer versions of DINamespace dropped file and line.
15291541
MDString *Name;

lib/Bitcode/Writer/BitcodeWriter.cpp

+17
Original file line numberDiff line numberDiff line change
@@ -317,6 +317,8 @@ class ModuleBitcodeWriter : public ModuleBitcodeWriterBase {
317317
void writeDILexicalBlockFile(const DILexicalBlockFile *N,
318318
SmallVectorImpl<uint64_t> &Record,
319319
unsigned Abbrev);
320+
void writeDICommonBlock(const DICommonBlock *N,
321+
SmallVectorImpl<uint64_t> &Record, unsigned Abbrev);
320322
void writeDINamespace(const DINamespace *N, SmallVectorImpl<uint64_t> &Record,
321323
unsigned Abbrev);
322324
void writeDIMacro(const DIMacro *N, SmallVectorImpl<uint64_t> &Record,
@@ -1695,6 +1697,21 @@ void ModuleBitcodeWriter::writeDILexicalBlockFile(
16951697
Record.clear();
16961698
}
16971699

1700+
void ModuleBitcodeWriter::writeDICommonBlock(const DICommonBlock *N,
1701+
SmallVectorImpl<uint64_t> &Record,
1702+
unsigned Abbrev) {
1703+
Record.push_back(N->isDistinct());
1704+
Record.push_back(VE.getMetadataOrNullID(N->getScope()));
1705+
Record.push_back(VE.getMetadataOrNullID(N->getDecl()));
1706+
Record.push_back(VE.getMetadataOrNullID(N->getRawName()));
1707+
Record.push_back(VE.getMetadataOrNullID(N->getFile()));
1708+
Record.push_back(N->getLineNo());
1709+
Record.push_back(N->getAlignInBits());
1710+
1711+
Stream.EmitRecord(bitc::METADATA_COMMON_BLOCK, Record, Abbrev);
1712+
Record.clear();
1713+
}
1714+
16981715
void ModuleBitcodeWriter::writeDINamespace(const DINamespace *N,
16991716
SmallVectorImpl<uint64_t> &Record,
17001717
unsigned Abbrev) {

lib/CodeGen/AsmPrinter/DwarfCompileUnit.cpp

+89-58
Original file line numberDiff line numberDiff line change
@@ -106,59 +106,8 @@ unsigned DwarfCompileUnit::getOrCreateSourceID(StringRef FileName,
106106
Asm->OutStreamer->hasRawTextSupport() ? 0 : getUniqueID());
107107
}
108108

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

@@ -231,19 +180,101 @@ DIE *DwarfCompileUnit::getOrCreateGlobalVariableDIE(
231180
}
232181
}
233182
if (Loc)
234-
addBlock(*VariableDIE, dwarf::DW_AT_location, DwarfExpr->finalize());
183+
addBlock(*ToDIE, dwarf::DW_AT_location, DwarfExpr->finalize());
235184

236185
if (DD->useAllLinkageNames())
237-
addLinkageName(*VariableDIE, GV->getLinkageName());
186+
addLinkageName(*ToDIE, GV->getLinkageName());
238187

239188
if (addToAccelTable) {
240-
DD->addAccelName(GV->getName(), *VariableDIE);
189+
DD->addAccelName(GV->getName(), *ToDIE);
241190

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

248279
return VariableDIE;
249280
}

lib/CodeGen/AsmPrinter/DwarfCompileUnit.h

+6
Original file line numberDiff line numberDiff line change
@@ -129,6 +129,12 @@ class DwarfCompileUnit final : public DwarfUnit {
129129
getOrCreateGlobalVariableDIE(const DIGlobalVariable *GV,
130130
ArrayRef<GlobalExpr> GlobalExprs);
131131

132+
DIE *getOrCreateCommonBlock(const DICommonBlock *CB,
133+
ArrayRef<GlobalExpr> GlobalExprs);
134+
135+
void addLocationAttribute(DIE *ToDIE, const DIGlobalVariable *GV,
136+
ArrayRef<GlobalExpr> GlobalExprs);
137+
132138
/// addLabelAddress - Add a dwarf label attribute data and value using
133139
/// either DW_FORM_addr or DW_FORM_GNU_addr_index.
134140
void addLabelAddress(DIE &Die, dwarf::Attribute Attribute,

0 commit comments

Comments
 (0)