@@ -215,10 +215,13 @@ class DINode : public MDNode {
215215 return false ;
216216 case GenericDINodeKind:
217217 case DISubrangeKind:
218+ case DIFortranSubrangeKind:
218219 case DIEnumeratorKind:
219220 case DIBasicTypeKind:
221+ case DIStringTypeKind:
220222 case DIDerivedTypeKind:
221223 case DICompositeTypeKind:
224+ case DIFortranArrayTypeKind:
222225 case DISubroutineTypeKind:
223226 case DIFileKind:
224227 case DICompileUnitKind:
@@ -363,6 +366,71 @@ class DISubrange : public DINode {
363366 }
364367};
365368
369+ // / Fortran array subrange
370+ class DIFortranSubrange : public DINode {
371+ friend class LLVMContextImpl ;
372+ friend class MDNode ;
373+
374+ int64_t CLowerBound;
375+ int64_t CUpperBound;
376+ bool NoUpperBound;
377+
378+ DIFortranSubrange (LLVMContext &C, StorageType Storage, int64_t CLowerBound,
379+ int64_t CUpperBound, bool NoUpperBound,
380+ ArrayRef<Metadata *> Ops)
381+ : DINode(C, DIFortranSubrangeKind, Storage,
382+ dwarf::DW_TAG_subrange_type, Ops), CLowerBound(CLowerBound),
383+ CUpperBound (CUpperBound), NoUpperBound(NoUpperBound) {}
384+ ~DIFortranSubrange () = default ;
385+
386+ static DIFortranSubrange *getImpl (LLVMContext &Context, int64_t CLBound,
387+ int64_t CUBound, bool NoUpperBound,
388+ Metadata *Lbound, Metadata *Lbndexp,
389+ Metadata *Ubound, Metadata *Ubndexp,
390+ StorageType Storage,
391+ bool ShouldCreate = true );
392+
393+ TempDIFortranSubrange cloneImpl () const {
394+ return getTemporary (getContext (), getCLowerBound (), getCUpperBound (),
395+ noUpperBound (), getRawLowerBound (),
396+ getRawLowerBoundExpression (), getRawUpperBound (),
397+ getRawUpperBoundExpression ());
398+ }
399+
400+ public:
401+ DEFINE_MDNODE_GET (DIFortranSubrange, (int64_t CLB, int64_t CUB, bool NUB,
402+ Metadata *LBound, Metadata *LBndExp,
403+ Metadata *UBound, Metadata *UBndExp),
404+ (CLB, CUB, NUB, LBound, LBndExp, UBound, UBndExp))
405+
406+ TempDIFortranSubrange clone() const { return cloneImpl (); }
407+
408+ DIVariable *getLowerBound () const {
409+ return cast_or_null<DIVariable>(getRawLowerBound ());
410+ }
411+ DIExpression *getLowerBoundExp () const {
412+ return cast_or_null<DIExpression>(getRawLowerBoundExpression ());
413+ }
414+ DIVariable *getUpperBound () const {
415+ return cast_or_null<DIVariable>(getRawUpperBound ());
416+ }
417+ DIExpression *getUpperBoundExp () const {
418+ return cast_or_null<DIExpression>(getRawUpperBoundExpression ());
419+ }
420+
421+ int64_t getCLowerBound () const { return CLowerBound; }
422+ int64_t getCUpperBound () const { return CUpperBound; }
423+ Metadata *getRawLowerBound () const { return getOperand (0 ); }
424+ Metadata *getRawLowerBoundExpression () const { return getOperand (1 ); }
425+ Metadata *getRawUpperBound () const { return getOperand (2 ); }
426+ Metadata *getRawUpperBoundExpression () const { return getOperand (3 ); }
427+ bool noUpperBound () const { return NoUpperBound; }
428+
429+ static bool classof (const Metadata *MD) {
430+ return MD->getMetadataID () == DIFortranSubrangeKind;
431+ }
432+ };
433+
366434// / Enumeration value.
367435// /
368436// / TODO: Add a pointer to the context (DW_TAG_enumeration_type) once that no
@@ -449,8 +517,10 @@ class DIScope : public DINode {
449517 default :
450518 return false ;
451519 case DIBasicTypeKind:
520+ case DIStringTypeKind:
452521 case DIDerivedTypeKind:
453522 case DICompositeTypeKind:
523+ case DIFortranArrayTypeKind:
454524 case DISubroutineTypeKind:
455525 case DIFileKind:
456526 case DICompileUnitKind:
@@ -637,8 +707,10 @@ class DIType : public DIScope {
637707 default :
638708 return false ;
639709 case DIBasicTypeKind:
710+ case DIStringTypeKind:
640711 case DIDerivedTypeKind:
641712 case DICompositeTypeKind:
713+ case DIFortranArrayTypeKind:
642714 case DISubroutineTypeKind:
643715 return true ;
644716 }
@@ -683,6 +755,12 @@ class DIBasicType : public DIType {
683755public:
684756 DEFINE_MDNODE_GET (DIBasicType, (unsigned Tag, StringRef Name),
685757 (Tag, Name, 0 , 0 , 0 ))
758+ DEFINE_MDNODE_GET(DIBasicType,
759+ (unsigned Tag, StringRef Name, uint64_t SizeInBits),
760+ (Tag, Name, SizeInBits, 0 , 0 ))
761+ DEFINE_MDNODE_GET(DIBasicType,
762+ (unsigned Tag, MDString *Name, uint64_t SizeInBits),
763+ (Tag, Name, SizeInBits, 0 , 0 ))
686764 DEFINE_MDNODE_GET(DIBasicType,
687765 (unsigned Tag, StringRef Name, uint64_t SizeInBits,
688766 uint32_t AlignInBits, unsigned Encoding),
@@ -701,6 +779,99 @@ class DIBasicType : public DIType {
701779 }
702780};
703781
782+ // / String type, Fortran CHARACTER(n)
783+ class DIStringType : public DIType {
784+ friend class LLVMContextImpl ;
785+ friend class MDNode ;
786+
787+ unsigned Encoding;
788+
789+ DIStringType (LLVMContext &C, StorageType Storage, unsigned Tag,
790+ uint64_t SizeInBits, uint32_t AlignInBits, unsigned Encoding,
791+ ArrayRef<Metadata *> Ops)
792+ : DIType(C, DIStringTypeKind, Storage, Tag, 0 , SizeInBits, AlignInBits, 0 ,
793+ FlagZero, Ops),
794+ Encoding (Encoding) {}
795+ ~DIStringType () = default ;
796+
797+ static DIStringType *getImpl (LLVMContext &Context, unsigned Tag,
798+ StringRef Name, Metadata *StringLength,
799+ Metadata *StrLenExp, uint64_t SizeInBits,
800+ uint32_t AlignInBits, unsigned Encoding,
801+ StorageType Storage, bool ShouldCreate = true ) {
802+ return getImpl (Context, Tag, getCanonicalMDString (Context, Name),
803+ StringLength, StrLenExp, SizeInBits, AlignInBits, Encoding,
804+ Storage, ShouldCreate);
805+ }
806+ static DIStringType *getImpl (LLVMContext &Context, unsigned Tag,
807+ MDString *Name, Metadata *StringLength,
808+ Metadata *StrLenExp, uint64_t SizeInBits,
809+ uint32_t AlignInBits, unsigned Encoding,
810+ StorageType Storage, bool ShouldCreate = true );
811+
812+ TempDIStringType cloneImpl () const {
813+ return getTemporary (getContext (), getTag (), getName (), getRawStringLength (),
814+ getRawStringLengthExp (), getSizeInBits (),
815+ getAlignInBits (), getEncoding ());
816+ }
817+
818+ public:
819+ DEFINE_MDNODE_GET (DIStringType, (unsigned Tag, StringRef Name),
820+ (Tag, Name, nullptr , nullptr , 0 , 0 , 0 ))
821+ DEFINE_MDNODE_GET(DIStringType,
822+ (unsigned Tag, StringRef Name, uint64_t SizeInBits,
823+ uint32_t AlignInBits),
824+ (Tag, Name, nullptr , nullptr , SizeInBits, AlignInBits, 0 ))
825+ DEFINE_MDNODE_GET(DIStringType,
826+ (unsigned Tag, MDString *Name, uint64_t SizeInBits,
827+ uint32_t AlignInBits),
828+ (Tag, Name, nullptr , nullptr , SizeInBits, AlignInBits, 0 ))
829+ DEFINE_MDNODE_GET(DIStringType,
830+ (unsigned Tag, StringRef Name, Metadata *StringLength,
831+ Metadata *StringLengthExp, uint64_t SizeInBits,
832+ uint32_t AlignInBits),
833+ (Tag, Name, StringLength, StringLengthExp, SizeInBits,
834+ AlignInBits, 0 ))
835+ DEFINE_MDNODE_GET(DIStringType,
836+ (unsigned Tag, MDString *Name, Metadata *StringLength,
837+ Metadata *StringLengthExp, uint64_t SizeInBits,
838+ uint32_t AlignInBits),
839+ (Tag, Name, StringLength, StringLengthExp, SizeInBits,
840+ AlignInBits, 0 ))
841+ DEFINE_MDNODE_GET(DIStringType,
842+ (unsigned Tag, StringRef Name, Metadata *StringLength,
843+ Metadata *StringLengthExp, uint64_t SizeInBits,
844+ uint32_t AlignInBits, unsigned Encoding),
845+ (Tag, Name, StringLength, StringLengthExp, SizeInBits,
846+ AlignInBits, Encoding))
847+ DEFINE_MDNODE_GET(DIStringType,
848+ (unsigned Tag, MDString *Name, Metadata *StringLength,
849+ Metadata *StringLengthExp, uint64_t SizeInBits,
850+ uint32_t AlignInBits, unsigned Encoding),
851+ (Tag, Name, StringLength, StringLengthExp, SizeInBits,
852+ AlignInBits, Encoding))
853+
854+ TempDIStringType clone() const { return cloneImpl (); }
855+
856+ static bool classof (const Metadata *MD) {
857+ return MD->getMetadataID () == DIStringTypeKind;
858+ }
859+
860+ DIVariable *getStringLength () const {
861+ return cast_or_null<DIVariable>(getRawStringLength ());
862+ }
863+
864+ DIExpression *getStringLengthExp () const {
865+ return cast_or_null<DIExpression>(getRawStringLengthExp ());
866+ }
867+
868+ unsigned getEncoding () const { return Encoding; }
869+
870+ Metadata *getRawStringLength () const { return getOperand (3 ); }
871+
872+ Metadata *getRawStringLengthExp () const { return getOperand (4 ); }
873+ };
874+
704875// / Derived types.
705876// /
706877// / This includes qualified types, pointers, references, friends, typedefs, and
@@ -988,6 +1159,90 @@ class DICompositeType : public DIType {
9881159 }
9891160};
9901161
1162+ // / Fortran array types.
1163+ class DIFortranArrayType : public DIType {
1164+ friend class LLVMContextImpl ;
1165+ friend class MDNode ;
1166+
1167+ DIFortranArrayType (LLVMContext &C, StorageType Storage, unsigned Tag,
1168+ unsigned Line, uint64_t SizeInBits, uint32_t AlignInBits,
1169+ uint64_t OffsetInBits, DIFlags Flags,
1170+ ArrayRef<Metadata *> Ops)
1171+ : DIType(C, DIFortranArrayTypeKind, Storage, Tag, Line, SizeInBits,
1172+ AlignInBits, OffsetInBits, Flags, Ops) {}
1173+ ~DIFortranArrayType () = default ;
1174+
1175+ static DIFortranArrayType *
1176+ getImpl (LLVMContext &Context, unsigned Tag, StringRef Name, Metadata *File,
1177+ unsigned Line, DIScopeRef Scope, DITypeRef BaseType,
1178+ uint64_t SizeInBits, uint32_t AlignInBits, uint64_t OffsetInBits,
1179+ DIFlags Flags, DINodeArray Elements, StorageType Storage,
1180+ bool ShouldCreate = true ) {
1181+ return getImpl (
1182+ Context, Tag, getCanonicalMDString (Context, Name), File, Line, Scope,
1183+ BaseType, SizeInBits, AlignInBits, OffsetInBits, Flags, Elements.get (),
1184+ Storage, ShouldCreate);
1185+ }
1186+ static DIFortranArrayType *
1187+ getImpl (LLVMContext &Context, unsigned Tag, MDString *Name, Metadata *File,
1188+ unsigned Line, Metadata *Scope, Metadata *BaseType,
1189+ uint64_t SizeInBits, uint32_t AlignInBits, uint64_t OffsetInBits,
1190+ DIFlags Flags, Metadata *Elements, StorageType Storage,
1191+ bool ShouldCreate = true );
1192+
1193+ TempDIFortranArrayType cloneImpl () const {
1194+ return getTemporary (getContext (), getTag (), getName (), getFile (), getLine (),
1195+ getScope (), getBaseType (), getSizeInBits (),
1196+ getAlignInBits (), getOffsetInBits (), getFlags (),
1197+ getElements ());
1198+ }
1199+
1200+ public:
1201+ DEFINE_MDNODE_GET (DIFortranArrayType,
1202+ (unsigned Tag, StringRef Name, DIFile *File, unsigned Line,
1203+ DIScopeRef Scope, DITypeRef BaseType, uint64_t SizeInBits,
1204+ uint32_t AlignInBits, uint64_t OffsetInBits,
1205+ DIFlags Flags, DINodeArray Elements),
1206+ (Tag, Name, File, Line, Scope, BaseType, SizeInBits,
1207+ AlignInBits, OffsetInBits, Flags, Elements))
1208+ DEFINE_MDNODE_GET (DIFortranArrayType,
1209+ (unsigned Tag, MDString *Name, Metadata *File,
1210+ unsigned Line, Metadata *Scope, Metadata *BaseType,
1211+ uint64_t SizeInBits, uint32_t AlignInBits,
1212+ uint64_t OffsetInBits, DIFlags Flags, Metadata *Elements),
1213+ (Tag, Name, File, Line, Scope, BaseType, SizeInBits,
1214+ AlignInBits, OffsetInBits, Flags, Elements))
1215+
1216+ TempDIFortranArrayType clone () const { return cloneImpl (); }
1217+
1218+ DITypeRef getBaseType () const { return DITypeRef (getRawBaseType ()); }
1219+ DINodeArray getElements () const {
1220+ return cast_or_null<MDTuple>(getRawElements ());
1221+ }
1222+
1223+ Metadata *getRawBaseType () const { return getOperand (3 ); }
1224+ Metadata *getRawElements () const { return getOperand (4 ); }
1225+
1226+ // / Replace operands.
1227+ // /
1228+ // / If this \a isUniqued() and not \a isResolved(), on a uniquing collision
1229+ // / this will be RAUW'ed and deleted. Use a \a TrackingMDRef to keep track
1230+ // / of its movement if necessary.
1231+ // / @{
1232+ void replaceElements (DINodeArray Elements) {
1233+ #ifndef NDEBUG
1234+ for (DINode *Op : getElements ())
1235+ assert (is_contained (Elements->operands (), Op) &&
1236+ " Lost a member during member list replacement" );
1237+ #endif
1238+ replaceOperandWith (4 , Elements.get ());
1239+ }
1240+
1241+ static bool classof (const Metadata *MD) {
1242+ return MD->getMetadataID () == DIFortranArrayTypeKind;
1243+ }
1244+ };
1245+
9911246// / Type array for a subprogram.
9921247// /
9931248// / TODO: Fold the array of types in directly as operands.
@@ -1601,6 +1856,9 @@ class DISubprogram : public DILocalScope {
16011856 bool isExplicit () const { return getFlags () & FlagExplicit; }
16021857 bool isPrototyped () const { return getFlags () & FlagPrototyped; }
16031858 bool isMainSubprogram () const { return getFlags () & FlagMainSubprogram; }
1859+ bool isPure () const { return getFlags () & FlagPure; }
1860+ bool isElemental () const { return getFlags () & FlagElemental; }
1861+ bool isRecursive () const { return getFlags () & FlagRecursive; }
16041862
16051863 // / Check if this is reference-qualified.
16061864 // /
0 commit comments