Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 0 additions & 2 deletions llvm/include/llvm-c/DebugInfo.h
Original file line number Diff line number Diff line change
Expand Up @@ -160,8 +160,6 @@ enum {
LLVMDIMacroMetadataKind,
LLVMDIMacroFileMetadataKind,
LLVMDIStringTypeMetadataKind,
LLVMDIFortranArrayTypeMetadataKind,
LLVMDIFortranSubrangeMetadataKind,
LLVMDICommonBlockMetadataKind,
LLVMDIGenericSubrangeMetadataKind
};
Expand Down
2 changes: 0 additions & 2 deletions llvm/include/llvm/Bitcode/LLVMBitCodes.h
Original file line number Diff line number Diff line change
Expand Up @@ -332,8 +332,6 @@ enum MetadataCodes {
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,...]
METADATA_GENERIC_SUBRANGE = 45 // [distinct, count, lo, up, stride]
};
Expand Down
14 changes: 0 additions & 14 deletions llvm/include/llvm/IR/DIBuilder.h
Original file line number Diff line number Diff line change
Expand Up @@ -490,14 +490,6 @@ 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 @@ -583,12 +575,6 @@ 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);

DIGenericSubrange *
getOrCreateGenericSubrange(DIGenericSubrange::BoundType Count,
DIGenericSubrange::BoundType LowerBound,
Expand Down
159 changes: 0 additions & 159 deletions llvm/include/llvm/IR/DebugInfoMetadata.h
Original file line number Diff line number Diff line change
Expand Up @@ -180,13 +180,11 @@ class DINode : public MDNode {
return false;
case GenericDINodeKind:
case DISubrangeKind:
case DIFortranSubrangeKind:
case DIEnumeratorKind:
case DIBasicTypeKind:
case DIStringTypeKind:
case DIDerivedTypeKind:
case DICompositeTypeKind:
case DIFortranArrayTypeKind:
case DISubroutineTypeKind:
case DIFileKind:
case DICompileUnitKind:
Expand Down Expand Up @@ -354,71 +352,6 @@ class DISubrange : public DINode {
}
};

/// Fortran array subrange
class DIFortranSubrange : public DINode {
friend class LLVMContextImpl;
friend class MDNode;

int64_t CLowerBound;
int64_t CUpperBound;
bool NoUpperBound;

DIFortranSubrange(LLVMContext &C, StorageType Storage, int64_t CLowerBound,
int64_t CUpperBound, bool NoUpperBound,
ArrayRef<Metadata *> Ops)
: DINode(C, DIFortranSubrangeKind, Storage,
dwarf::DW_TAG_subrange_type, Ops), CLowerBound(CLowerBound),
CUpperBound(CUpperBound), NoUpperBound(NoUpperBound) {}
~DIFortranSubrange() = default;

static DIFortranSubrange *getImpl(LLVMContext &Context, int64_t CLBound,
int64_t CUBound, bool NoUpperBound,
Metadata *Lbound, Metadata *Lbndexp,
Metadata *Ubound, Metadata *Ubndexp,
StorageType Storage,
bool ShouldCreate = true);

TempDIFortranSubrange cloneImpl() const {
return getTemporary(getContext(), getCLowerBound(), getCUpperBound(),
noUpperBound(), getRawLowerBound(),
getRawLowerBoundExpression(), getRawUpperBound(),
getRawUpperBoundExpression());
}

public:
DEFINE_MDNODE_GET(DIFortranSubrange, (int64_t CLB, int64_t CUB, bool NUB,
Metadata *LBound, Metadata *LBndExp,
Metadata *UBound, Metadata *UBndExp),
(CLB, CUB, NUB, LBound, LBndExp, UBound, UBndExp))

TempDIFortranSubrange clone() const { return cloneImpl(); }

DIVariable *getLowerBound() const {
return cast_or_null<DIVariable>(getRawLowerBound());
}
DIExpression *getLowerBoundExp() const {
return cast_or_null<DIExpression>(getRawLowerBoundExpression());
}
DIVariable *getUpperBound() const {
return cast_or_null<DIVariable>(getRawUpperBound());
}
DIExpression *getUpperBoundExp() const {
return cast_or_null<DIExpression>(getRawUpperBoundExpression());
}

int64_t getCLowerBound() const { return CLowerBound; }
int64_t getCUpperBound() const { return CUpperBound; }
Metadata *getRawLowerBound() const { return getOperand(0); }
Metadata *getRawLowerBoundExpression() const { return getOperand(1); }
Metadata *getRawUpperBound() const { return getOperand(2); }
Metadata *getRawUpperBoundExpression() const { return getOperand(3); }
bool noUpperBound() const { return NoUpperBound; }

static bool classof(const Metadata *MD) {
return MD->getMetadataID() == DIFortranSubrangeKind;
}
};

class DIGenericSubrange : public DINode {
friend class LLVMContextImpl;
friend class MDNode;
Expand Down Expand Up @@ -557,7 +490,6 @@ class DIScope : public DINode {
case DIStringTypeKind:
case DIDerivedTypeKind:
case DICompositeTypeKind:
case DIFortranArrayTypeKind:
case DISubroutineTypeKind:
case DIFileKind:
case DICompileUnitKind:
Expand Down Expand Up @@ -804,7 +736,6 @@ class DIType : public DIScope {
case DIStringTypeKind:
case DIDerivedTypeKind:
case DICompositeTypeKind:
case DIFortranArrayTypeKind:
case DISubroutineTypeKind:
return true;
}
Expand Down Expand Up @@ -852,12 +783,6 @@ class DIBasicType : public DIType {
public:
DEFINE_MDNODE_GET(DIBasicType, (unsigned Tag, StringRef Name),
(Tag, Name, 0, 0, 0, FlagZero))
DEFINE_MDNODE_GET(DIBasicType,
(unsigned Tag, StringRef Name, uint64_t SizeInBits),
(Tag, Name, SizeInBits, 0, 0, FlagZero))
DEFINE_MDNODE_GET(DIBasicType,
(unsigned Tag, MDString *Name, uint64_t SizeInBits),
(Tag, Name, SizeInBits, 0, 0, FlagZero))
DEFINE_MDNODE_GET(DIBasicType,
(unsigned Tag, StringRef Name, uint64_t SizeInBits,
uint32_t AlignInBits, unsigned Encoding, DIFlags Flags),
Expand Down Expand Up @@ -1324,90 +1249,6 @@ class DICompositeType : public DIType {
}
};

/// Fortran array types.
class DIFortranArrayType : public DIType {
friend class LLVMContextImpl;
friend class MDNode;

DIFortranArrayType(LLVMContext &C, StorageType Storage, unsigned Tag,
unsigned Line, uint64_t SizeInBits, uint32_t AlignInBits,
uint64_t OffsetInBits, DIFlags Flags,
ArrayRef<Metadata *> Ops)
: DIType(C, DIFortranArrayTypeKind, Storage, Tag, Line, SizeInBits,
AlignInBits, OffsetInBits, Flags, Ops) {}
~DIFortranArrayType() = default;

static DIFortranArrayType *
getImpl(LLVMContext &Context, unsigned Tag, StringRef Name, Metadata *File,
unsigned Line, DIScope *Scope, DIType *BaseType,
uint64_t SizeInBits, uint32_t AlignInBits, uint64_t OffsetInBits,
DIFlags Flags, DINodeArray Elements, StorageType Storage,
bool ShouldCreate = true) {
return getImpl(
Context, Tag, getCanonicalMDString(Context, Name), File, Line, Scope,
BaseType, SizeInBits, AlignInBits, OffsetInBits, Flags, Elements.get(),
Storage, ShouldCreate);
}
static DIFortranArrayType *
getImpl(LLVMContext &Context, unsigned Tag, MDString *Name, Metadata *File,
unsigned Line, Metadata *Scope, Metadata *BaseType,
uint64_t SizeInBits, uint32_t AlignInBits, uint64_t OffsetInBits,
DIFlags Flags, Metadata *Elements, StorageType Storage,
bool ShouldCreate = true);

TempDIFortranArrayType cloneImpl() const {
return getTemporary(getContext(), getTag(), getName(), getFile(), getLine(),
getScope(), getBaseType(), getSizeInBits(),
getAlignInBits(), getOffsetInBits(), getFlags(),
getElements());
}

public:
DEFINE_MDNODE_GET(DIFortranArrayType,
(unsigned Tag, StringRef Name, DIFile *File, unsigned Line,
DIScope *Scope, DIType *BaseType, uint64_t SizeInBits,
uint32_t AlignInBits, uint64_t OffsetInBits,
DIFlags Flags, DINodeArray Elements),
(Tag, Name, File, Line, Scope, BaseType, SizeInBits,
AlignInBits, OffsetInBits, Flags, Elements))
DEFINE_MDNODE_GET(DIFortranArrayType,
(unsigned Tag, MDString *Name, Metadata *File,
unsigned Line, Metadata *Scope, Metadata *BaseType,
uint64_t SizeInBits, uint32_t AlignInBits,
uint64_t OffsetInBits, DIFlags Flags, Metadata *Elements),
(Tag, Name, File, Line, Scope, BaseType, SizeInBits,
AlignInBits, OffsetInBits, Flags, Elements))

TempDIFortranArrayType clone() const { return cloneImpl(); }

DIType *getBaseType() const { return cast_or_null<DIType>(getRawBaseType()); }
DINodeArray getElements() const {
return cast_or_null<MDTuple>(getRawElements());
}

Metadata *getRawBaseType() const { return getOperand(3); }
Metadata *getRawElements() const { return getOperand(4); }

/// Replace operands.
///
/// If this \a isUniqued() and not \a isResolved(), on a uniquing collision
/// this will be RAUW'ed and deleted. Use a \a TrackingMDRef to keep track
/// of its movement if necessary.
/// @{
void replaceElements(DINodeArray Elements) {
#ifndef NDEBUG
for (DINode *Op : getElements())
assert(is_contained(Elements->operands(), Op) &&
"Lost a member during member list replacement");
#endif
replaceOperandWith(4, Elements.get());
}

static bool classof(const Metadata *MD) {
return MD->getMetadataID() == DIFortranArrayTypeKind;
}
};

/// Type array for a subprogram.
///
/// TODO: Fold the array of types in directly as operands.
Expand Down
2 changes: 0 additions & 2 deletions llvm/include/llvm/IR/Metadata.def
Original file line number Diff line number Diff line change
Expand Up @@ -114,8 +114,6 @@ HANDLE_SPECIALIZED_MDNODE_BRANCH(DIMacroNode)
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIMacro)
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIMacroFile)
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIStringType)
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIFortranArrayType)
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIFortranSubrange)
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DICommonBlock)
HANDLE_SPECIALIZED_MDNODE_LEAF_UNIQUABLE(DIGenericSubrange)

Expand Down
46 changes: 0 additions & 46 deletions llvm/lib/AsmParser/LLParser.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -4485,27 +4485,6 @@ bool LLParser::ParseDISubrange(MDNode *&Result, bool IsDistinct) {
return false;
}

/// ParseDIFortranSubrange:
/// ::= !DIFortranSubrange(lowerBound: 2)
bool LLParser::ParseDIFortranSubrange(MDNode *&Result, bool IsDistinct) {
#define VISIT_MD_FIELDS(OPTIONAL, REQUIRED) \
OPTIONAL(constLowerBound, MDSignedField, (0, INT64_MIN, INT64_MAX)); \
OPTIONAL(constUpperBound, MDSignedField, (0, INT64_MIN, INT64_MAX)); \
OPTIONAL(lowerBound, MDField, ); \
OPTIONAL(lowerBoundExpression, MDField, ); \
OPTIONAL(upperBound, MDField, ); \
OPTIONAL(upperBoundExpression, MDField, );
PARSE_MD_FIELDS();
#undef VISIT_MD_FIELDS

Result = GET_OR_DISTINCT(DIFortranSubrange,
(Context, constLowerBound.Val, constUpperBound.Val,
(!constUpperBound.Seen) && (!upperBound.Seen),
lowerBound.Val, lowerBoundExpression.Val,
upperBound.Val, upperBoundExpression.Val));
return false;
}

/// ParseDIGenericSubrange:
/// ::= !DIGenericSubrange(lowerBound: !node1, upperBound: !node2, stride:
/// !node3)
Expand Down Expand Up @@ -4690,31 +4669,6 @@ bool LLParser::ParseDICompositeType(MDNode *&Result, bool IsDistinct) {
return false;
}

bool LLParser::ParseDIFortranArrayType(MDNode *&Result, bool IsDistinct) {
#define VISIT_MD_FIELDS(OPTIONAL, REQUIRED) \
OPTIONAL(tag, DwarfTagField, (dwarf::DW_TAG_array_type)); \
OPTIONAL(name, MDStringField, ); \
OPTIONAL(file, MDField, ); \
OPTIONAL(line, LineField, ); \
OPTIONAL(scope, MDField, ); \
OPTIONAL(baseType, MDField, ); \
OPTIONAL(size, MDUnsignedField, (0, UINT64_MAX)); \
OPTIONAL(align, MDUnsignedField, (0, UINT32_MAX)); \
OPTIONAL(offset, MDUnsignedField, (0, UINT64_MAX)); \
OPTIONAL(flags, DIFlagField, ); \
OPTIONAL(elements, MDField, );
PARSE_MD_FIELDS();
#undef VISIT_MD_FIELDS

// Create a new node, and save it in the context if it belongs in the type
// map.
Result = GET_OR_DISTINCT(
DIFortranArrayType,
(Context, tag.Val, name.Val, file.Val, line.Val, scope.Val, baseType.Val,
size.Val, align.Val, offset.Val, flags.Val, elements.Val));
return false;
}

bool LLParser::ParseDISubroutineType(MDNode *&Result, bool IsDistinct) {
#define VISIT_MD_FIELDS(OPTIONAL, REQUIRED) \
OPTIONAL(flags, DIFlagField, ); \
Expand Down
48 changes: 0 additions & 48 deletions llvm/lib/Bitcode/Reader/MetadataLoader.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -851,13 +851,11 @@ MetadataLoader::MetadataLoaderImpl::lazyLoadModuleMetadataBlock() {
case bitc::METADATA_LOCATION:
case bitc::METADATA_GENERIC_DEBUG:
case bitc::METADATA_SUBRANGE:
case bitc::METADATA_FORTRAN_SUBRANGE:
case bitc::METADATA_ENUMERATOR:
case bitc::METADATA_BASIC_TYPE:
case bitc::METADATA_STRING_TYPE:
case bitc::METADATA_DERIVED_TYPE:
case bitc::METADATA_COMPOSITE_TYPE:
case bitc::METADATA_FORTRAN_ARRAY_TYPE:
case bitc::METADATA_SUBROUTINE_TYPE:
case bitc::METADATA_MODULE:
case bitc::METADATA_FILE:
Expand Down Expand Up @@ -1290,20 +1288,6 @@ Error MetadataLoader::MetadataLoaderImpl::parseOneMetadata(
NextMetadataNo++;
break;
}
case bitc::METADATA_FORTRAN_SUBRANGE: {
if (Record.size() != 8)
return error("Invalid record");

IsDistinct = Record[0];
MetadataList.assignValue(
GET_OR_DISTINCT(DIFortranSubrange,
(Context, Record[1], Record[2], Record[3],
getMDOrNull(Record[4]), getMDOrNull(Record[5]),
getMDOrNull(Record[6]), getMDOrNull(Record[7]))),
NextMetadataNo);
NextMetadataNo++;
break;
}
case bitc::METADATA_GENERIC_SUBRANGE: {
Metadata *Val = nullptr;
Val = GET_OR_DISTINCT(DIGenericSubrange,
Expand Down Expand Up @@ -1467,38 +1451,6 @@ Error MetadataLoader::MetadataLoaderImpl::parseOneMetadata(
NextMetadataNo++;
break;
}
case bitc::METADATA_FORTRAN_ARRAY_TYPE: {
if (Record.size() != 12)
return error("Invalid record");

// If we have a UUID and this is not a forward declaration, lookup the
// mapping.
IsDistinct = Record[0] & 0x1;
unsigned Tag = Record[1];
MDString *Name = getMDString(Record[2]);
Metadata *File = getMDOrNull(Record[3]);
unsigned Line = Record[4];
Metadata *Scope = getDITypeRefOrNull(Record[5]);
Metadata *BaseType = nullptr;
uint64_t SizeInBits = Record[7];
if (Record[8] > (uint64_t)std::numeric_limits<uint32_t>::max())
return error("Alignment value is too large");
uint32_t AlignInBits = Record[8];
uint64_t OffsetInBits = 0;
DINode::DIFlags Flags = static_cast<DINode::DIFlags>(Record[10]);
Metadata *Elements = nullptr;
BaseType = getDITypeRefOrNull(Record[6]);
OffsetInBits = Record[9];
Elements = getMDOrNull(Record[11]);
DIFortranArrayType *CT =
GET_OR_DISTINCT(DIFortranArrayType,
(Context, Tag, Name, File, Line, Scope, BaseType,
SizeInBits, AlignInBits, OffsetInBits, Flags,
Elements));
MetadataList.assignValue(CT, NextMetadataNo);
NextMetadataNo++;
break;
}
case bitc::METADATA_SUBROUTINE_TYPE: {
if (Record.size() < 3 || Record.size() > 4)
return error("Invalid record");
Expand Down
Loading