Skip to content

Commit

Permalink
[ClassicFlang] Port release_90 changes from flang-compiler/llvm
Browse files Browse the repository at this point in the history
Cherry-picked commit 2085211cfcca70411dc63f0d08763facc8a02090 by Eric Schweitz,
resolved merge conflicts, fixed build failures (e.g. adapted CGDebugInfo.cpp to
the new API), and fixed the DIGlobalVariable unit tests, which have been broken
since commit edfad65eebdf045b050f37380b6b61d673513982.
  • Loading branch information
bryanpkc authored and michalpasztamobica committed Dec 30, 2020
1 parent 49a4dec commit 82b38d2
Show file tree
Hide file tree
Showing 29 changed files with 1,691 additions and 96 deletions.
10 changes: 6 additions & 4 deletions clang/lib/CodeGen/CGDebugInfo.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -3585,7 +3585,8 @@ CGDebugInfo::getGlobalVariableForwardDeclaration(const VarDecl *VD) {
auto Align = getDeclAlignIfRequired(VD, CGM.getContext());
auto *GV = DBuilder.createTempGlobalVariableFwdDecl(
DContext, Name, LinkageName, Unit, Line, getOrCreateType(T, Unit),
!VD->isExternallyVisible(), nullptr, TemplateParameters, Align);
!VD->isExternallyVisible(), nullptr, TemplateParameters,
llvm::DINode::FlagZero, Align);
FwdDeclReplaceMap.emplace_back(
std::piecewise_construct,
std::make_tuple(cast<VarDecl>(VD->getCanonicalDecl())),
Expand Down Expand Up @@ -4664,7 +4665,7 @@ void CGDebugInfo::EmitGlobalVariable(llvm::GlobalVariable *Var,
Var->hasLocalLinkage(), true,
Expr.empty() ? nullptr : DBuilder.createExpression(Expr),
getOrCreateStaticDataMemberDeclarationOrNull(D), TemplateParameters,
Align);
llvm::DINode::FlagZero, Align);
Var->addDebugInfo(GVE);
}
DeclCache[D->getCanonicalDecl()].reset(GVE);
Expand Down Expand Up @@ -4765,7 +4766,7 @@ void CGDebugInfo::EmitGlobalVariable(const ValueDecl *VD, const APValue &Init) {
GV.reset(DBuilder.createGlobalVariableExpression(
DContext, Name, StringRef(), Unit, getLineNumber(VD->getLocation()), Ty,
true, true, InitExpr, getOrCreateStaticDataMemberDeclarationOrNull(VarD),
TemplateParameters, Align));
TemplateParameters, llvm::DINode::FlagZero, Align));
}

void CGDebugInfo::EmitExternalVariable(llvm::GlobalVariable *Var,
Expand All @@ -4783,7 +4784,8 @@ void CGDebugInfo::EmitExternalVariable(llvm::GlobalVariable *Var,
llvm::DIGlobalVariableExpression *GVE =
DBuilder.createGlobalVariableExpression(
DContext, Name, StringRef(), Unit, getLineNumber(D->getLocation()),
Ty, false, false, nullptr, nullptr, nullptr, Align);
Ty, false, false, nullptr, nullptr, nullptr, llvm::DINode::FlagZero,
Align);
Var->addDebugInfo(GVE);
}

Expand Down
8 changes: 6 additions & 2 deletions llvm/include/llvm-c/DebugInfo.h
Original file line number Diff line number Diff line change
Expand Up @@ -159,6 +159,9 @@ enum {
LLVMDIImportedEntityMetadataKind,
LLVMDIMacroMetadataKind,
LLVMDIMacroFileMetadataKind,
LLVMDIStringTypeMetadataKind,
LLVMDIFortranArrayTypeMetadataKind,
LLVMDIFortranSubrangeMetadataKind,
LLVMDICommonBlockMetadataKind
};
typedef unsigned LLVMMetadataKind;
Expand Down Expand Up @@ -1120,7 +1123,8 @@ LLVMMetadataRef LLVMDIBuilderCreateGlobalVariableExpression(
LLVMDIBuilderRef Builder, LLVMMetadataRef Scope, const char *Name,
size_t NameLen, const char *Linkage, size_t LinkLen, LLVMMetadataRef File,
unsigned LineNo, LLVMMetadataRef Ty, LLVMBool LocalToUnit,
LLVMMetadataRef Expr, LLVMMetadataRef Decl, uint32_t AlignInBits);
LLVMMetadataRef Expr, LLVMMetadataRef Decl, LLVMDIFlags Flags,
uint32_t AlignInBits);

/**
* Retrieves the \c DIVariable associated with this global variable expression.
Expand Down Expand Up @@ -1212,7 +1216,7 @@ LLVMMetadataRef LLVMDIBuilderCreateTempGlobalVariableFwdDecl(
LLVMDIBuilderRef Builder, LLVMMetadataRef Scope, const char *Name,
size_t NameLen, const char *Linkage, size_t LnkLen, LLVMMetadataRef File,
unsigned LineNo, LLVMMetadataRef Ty, LLVMBool LocalToUnit,
LLVMMetadataRef Decl, uint32_t AlignInBits);
LLVMMetadataRef Decl, LLVMDIFlags Flags, uint32_t AlignInBits);

/**
* Insert a new llvm.dbg.declare intrinsic call before the given instruction.
Expand Down
1 change: 1 addition & 0 deletions llvm/include/llvm/Analysis/TargetLibraryInfo.h
Original file line number Diff line number Diff line change
Expand Up @@ -89,6 +89,7 @@ class TargetLibraryInfoImpl {
NoLibrary, // Don't use any vector library.
Accelerate, // Use Accelerate framework.
MASSV, // IBM MASS vector library.
PGMATH, // PGI math library.
SVML // Intel short vector math library.
};

Expand Down
3 changes: 3 additions & 0 deletions llvm/include/llvm/Bitcode/LLVMBitCodes.h
Original file line number Diff line number Diff line change
Expand Up @@ -338,6 +338,9 @@ enum MetadataCodes {
METADATA_INDEX_OFFSET = 38, // [offset]
METADATA_INDEX = 39, // [bitpos]
METADATA_LABEL = 40, // [distinct, scope, name, file, line]
METADATA_STRING_TYPE = 41, // [distinct, name, size, align, ...]
METADATA_FORTRAN_ARRAY_TYPE = 42, // [distinct, name, [bounds ...], ...]
METADATA_FORTRAN_SUBRANGE = 43, // [distinct, lbound, lbnde, ubound, ubnde]
METADATA_COMMON_BLOCK = 44, // [distinct, scope, name, variable,...]
};

Expand Down
39 changes: 36 additions & 3 deletions llvm/include/llvm/IR/DIBuilder.h
Original file line number Diff line number Diff line change
Expand Up @@ -199,6 +199,12 @@ namespace llvm {
unsigned Encoding,
DINode::DIFlags Flags = DINode::FlagZero);

/// Create debugging information entry for a string
/// type.
/// \param Name Type name.
/// \param SizeInBits Size of the type.
DIStringType *createStringType(StringRef Name, uint64_t SizeInBits);

/// Create debugging information entry for a qualified
/// type, e.g. 'const int'.
/// \param Tag Tag identifing type, e.g. dwarf::TAG_volatile_type
Expand Down Expand Up @@ -491,6 +497,14 @@ namespace llvm {
DICompositeType *createArrayType(uint64_t Size, uint32_t AlignInBits,
DIType *Ty, DINodeArray Subscripts);

/// Create debugging information entry for a Fortran array.
/// \param Size Array size.
/// \param AlignInBits Alignment.
/// \param Ty Element type.
/// \param Subscripts Subscripts.
DIFortranArrayType *createFortranArrayType(
uint64_t Size, uint32_t AlignInBits, DIType *Ty, DINodeArray Subs);

/// Create debugging information entry for a vector type.
/// \param Size Array size.
/// \param AlignInBits Alignment.
Expand Down Expand Up @@ -576,6 +590,12 @@ namespace llvm {
DISubrange *getOrCreateSubrange(Metadata *Count, Metadata *LowerBound,
Metadata *UpperBound, Metadata *Stride);

/// Create a descriptor for a value range. This
/// implicitly uniques the values returned.
DIFortranSubrange *getOrCreateFortranSubrange(
int64_t CLBound, int64_t CUBound, bool NoUBound, Metadata *Lbound,
Metadata * Lbndexp, Metadata *Ubound, Metadata * Ubndexp);

/// Create a new descriptor for the specified variable.
/// \param Context Variable scope.
/// \param Name Name of the variable.
Expand All @@ -594,14 +614,16 @@ namespace llvm {
DIScope *Context, StringRef Name, StringRef LinkageName, DIFile *File,
unsigned LineNo, DIType *Ty, bool IsLocalToUnit, bool isDefined = true,
DIExpression *Expr = nullptr, MDNode *Decl = nullptr,
MDTuple *TemplateParams = nullptr, uint32_t AlignInBits = 0);
MDTuple *TemplateParams = nullptr,
DINode::DIFlags Flags = DINode::FlagZero, uint32_t AlignInBits = 0);

/// Identical to createGlobalVariable
/// except that the resulting DbgNode is temporary and meant to be RAUWed.
DIGlobalVariable *createTempGlobalVariableFwdDecl(
DIScope *Context, StringRef Name, StringRef LinkageName, DIFile *File,
unsigned LineNo, DIType *Ty, bool IsLocalToUnit, MDNode *Decl = nullptr,
MDTuple *TemplateParams= nullptr, uint32_t AlignInBits = 0);
unsigned LineNo, DIType *Ty, bool isLocalToUnit, MDNode *Decl = nullptr,
MDTuple *TemplateParams = nullptr,
DINode::DIFlags Flags = DINode::FlagZero, uint32_t AlignInBits = 0);

/// Create a new descriptor for an auto variable. This is a local variable
/// that is not a subprogram parameter.
Expand Down Expand Up @@ -727,6 +749,17 @@ namespace llvm {
StringRef Name, DIFile *File,
unsigned LineNo);

/// Create common block entry for a Fortran common block
/// \param Scope Scope of this common block
/// \param Name The name of this common block
/// \param File The file this common block is defined
/// \param LineNo Line number
/// \param VarList List of variables that a located in common block
/// \param AlignInBits Common block alignment
DICommonBlock *createCommonBlock(DIScope *Scope, DIGlobalVariable *decl,
StringRef Name, DIFile *File,
unsigned LineNo, uint32_t AlignInBits = 0);

/// This creates new descriptor for a namespace with the specified
/// parent scope.
/// \param Scope Namespace scope
Expand Down
Loading

0 comments on commit 82b38d2

Please sign in to comment.