@@ -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:
@@ -639,8 +709,10 @@ class DIType : public DIScope {
639709 default :
640710 return false ;
641711 case DIBasicTypeKind:
712+ case DIStringTypeKind:
642713 case DIDerivedTypeKind:
643714 case DICompositeTypeKind:
715+ case DIFortranArrayTypeKind:
644716 case DISubroutineTypeKind:
645717 return true ;
646718 }
@@ -685,6 +757,12 @@ class DIBasicType : public DIType {
685757public:
686758 DEFINE_MDNODE_GET (DIBasicType, (unsigned Tag, StringRef Name),
687759 (Tag, Name, 0 , 0 , 0 ))
760+ DEFINE_MDNODE_GET(DIBasicType,
761+ (unsigned Tag, StringRef Name, uint64_t SizeInBits),
762+ (Tag, Name, SizeInBits, 0 , 0 ))
763+ DEFINE_MDNODE_GET(DIBasicType,
764+ (unsigned Tag, MDString *Name, uint64_t SizeInBits),
765+ (Tag, Name, SizeInBits, 0 , 0 ))
688766 DEFINE_MDNODE_GET(DIBasicType,
689767 (unsigned Tag, StringRef Name, uint64_t SizeInBits,
690768 uint32_t AlignInBits, unsigned Encoding),
@@ -703,6 +781,99 @@ class DIBasicType : public DIType {
703781 }
704782};
705783
784+ // / String type, Fortran CHARACTER(n)
785+ class DIStringType : public DIType {
786+ friend class LLVMContextImpl ;
787+ friend class MDNode ;
788+
789+ unsigned Encoding;
790+
791+ DIStringType (LLVMContext &C, StorageType Storage, unsigned Tag,
792+ uint64_t SizeInBits, uint32_t AlignInBits, unsigned Encoding,
793+ ArrayRef<Metadata *> Ops)
794+ : DIType(C, DIStringTypeKind, Storage, Tag, 0 , SizeInBits, AlignInBits, 0 ,
795+ FlagZero, Ops),
796+ Encoding (Encoding) {}
797+ ~DIStringType () = default ;
798+
799+ static DIStringType *getImpl (LLVMContext &Context, unsigned Tag,
800+ StringRef Name, Metadata *StringLength,
801+ Metadata *StrLenExp, uint64_t SizeInBits,
802+ uint32_t AlignInBits, unsigned Encoding,
803+ StorageType Storage, bool ShouldCreate = true ) {
804+ return getImpl (Context, Tag, getCanonicalMDString (Context, Name),
805+ StringLength, StrLenExp, SizeInBits, AlignInBits, Encoding,
806+ Storage, ShouldCreate);
807+ }
808+ static DIStringType *getImpl (LLVMContext &Context, unsigned Tag,
809+ MDString *Name, Metadata *StringLength,
810+ Metadata *StrLenExp, uint64_t SizeInBits,
811+ uint32_t AlignInBits, unsigned Encoding,
812+ StorageType Storage, bool ShouldCreate = true );
813+
814+ TempDIStringType cloneImpl () const {
815+ return getTemporary (getContext (), getTag (), getName (), getRawStringLength (),
816+ getRawStringLengthExp (), getSizeInBits (),
817+ getAlignInBits (), getEncoding ());
818+ }
819+
820+ public:
821+ DEFINE_MDNODE_GET (DIStringType, (unsigned Tag, StringRef Name),
822+ (Tag, Name, nullptr , nullptr , 0 , 0 , 0 ))
823+ DEFINE_MDNODE_GET(DIStringType,
824+ (unsigned Tag, StringRef Name, uint64_t SizeInBits,
825+ uint32_t AlignInBits),
826+ (Tag, Name, nullptr , nullptr , SizeInBits, AlignInBits, 0 ))
827+ DEFINE_MDNODE_GET(DIStringType,
828+ (unsigned Tag, MDString *Name, uint64_t SizeInBits,
829+ uint32_t AlignInBits),
830+ (Tag, Name, nullptr , nullptr , SizeInBits, AlignInBits, 0 ))
831+ DEFINE_MDNODE_GET(DIStringType,
832+ (unsigned Tag, StringRef Name, Metadata *StringLength,
833+ Metadata *StringLengthExp, uint64_t SizeInBits,
834+ uint32_t AlignInBits),
835+ (Tag, Name, StringLength, StringLengthExp, SizeInBits,
836+ AlignInBits, 0 ))
837+ DEFINE_MDNODE_GET(DIStringType,
838+ (unsigned Tag, MDString *Name, Metadata *StringLength,
839+ Metadata *StringLengthExp, uint64_t SizeInBits,
840+ uint32_t AlignInBits),
841+ (Tag, Name, StringLength, StringLengthExp, SizeInBits,
842+ AlignInBits, 0 ))
843+ DEFINE_MDNODE_GET(DIStringType,
844+ (unsigned Tag, StringRef Name, Metadata *StringLength,
845+ Metadata *StringLengthExp, uint64_t SizeInBits,
846+ uint32_t AlignInBits, unsigned Encoding),
847+ (Tag, Name, StringLength, StringLengthExp, SizeInBits,
848+ AlignInBits, Encoding))
849+ DEFINE_MDNODE_GET(DIStringType,
850+ (unsigned Tag, MDString *Name, Metadata *StringLength,
851+ Metadata *StringLengthExp, uint64_t SizeInBits,
852+ uint32_t AlignInBits, unsigned Encoding),
853+ (Tag, Name, StringLength, StringLengthExp, SizeInBits,
854+ AlignInBits, Encoding))
855+
856+ TempDIStringType clone() const { return cloneImpl (); }
857+
858+ static bool classof (const Metadata *MD) {
859+ return MD->getMetadataID () == DIStringTypeKind;
860+ }
861+
862+ DIVariable *getStringLength () const {
863+ return cast_or_null<DIVariable>(getRawStringLength ());
864+ }
865+
866+ DIExpression *getStringLengthExp () const {
867+ return cast_or_null<DIExpression>(getRawStringLengthExp ());
868+ }
869+
870+ unsigned getEncoding () const { return Encoding; }
871+
872+ Metadata *getRawStringLength () const { return getOperand (3 ); }
873+
874+ Metadata *getRawStringLengthExp () const { return getOperand (4 ); }
875+ };
876+
706877// / Derived types.
707878// /
708879// / This includes qualified types, pointers, references, friends, typedefs, and
@@ -990,6 +1161,90 @@ class DICompositeType : public DIType {
9901161 }
9911162};
9921163
1164+ // / Fortran array types.
1165+ class DIFortranArrayType : public DIType {
1166+ friend class LLVMContextImpl ;
1167+ friend class MDNode ;
1168+
1169+ DIFortranArrayType (LLVMContext &C, StorageType Storage, unsigned Tag,
1170+ unsigned Line, uint64_t SizeInBits, uint32_t AlignInBits,
1171+ uint64_t OffsetInBits, DIFlags Flags,
1172+ ArrayRef<Metadata *> Ops)
1173+ : DIType(C, DIFortranArrayTypeKind, Storage, Tag, Line, SizeInBits,
1174+ AlignInBits, OffsetInBits, Flags, Ops) {}
1175+ ~DIFortranArrayType () = default ;
1176+
1177+ static DIFortranArrayType *
1178+ getImpl (LLVMContext &Context, unsigned Tag, StringRef Name, Metadata *File,
1179+ unsigned Line, DIScopeRef Scope, DITypeRef BaseType,
1180+ uint64_t SizeInBits, uint32_t AlignInBits, uint64_t OffsetInBits,
1181+ DIFlags Flags, DINodeArray Elements, StorageType Storage,
1182+ bool ShouldCreate = true ) {
1183+ return getImpl (
1184+ Context, Tag, getCanonicalMDString (Context, Name), File, Line, Scope,
1185+ BaseType, SizeInBits, AlignInBits, OffsetInBits, Flags, Elements.get (),
1186+ Storage, ShouldCreate);
1187+ }
1188+ static DIFortranArrayType *
1189+ getImpl (LLVMContext &Context, unsigned Tag, MDString *Name, Metadata *File,
1190+ unsigned Line, Metadata *Scope, Metadata *BaseType,
1191+ uint64_t SizeInBits, uint32_t AlignInBits, uint64_t OffsetInBits,
1192+ DIFlags Flags, Metadata *Elements, StorageType Storage,
1193+ bool ShouldCreate = true );
1194+
1195+ TempDIFortranArrayType cloneImpl () const {
1196+ return getTemporary (getContext (), getTag (), getName (), getFile (), getLine (),
1197+ getScope (), getBaseType (), getSizeInBits (),
1198+ getAlignInBits (), getOffsetInBits (), getFlags (),
1199+ getElements ());
1200+ }
1201+
1202+ public:
1203+ DEFINE_MDNODE_GET (DIFortranArrayType,
1204+ (unsigned Tag, StringRef Name, DIFile *File, unsigned Line,
1205+ DIScopeRef Scope, DITypeRef BaseType, uint64_t SizeInBits,
1206+ uint32_t AlignInBits, uint64_t OffsetInBits,
1207+ DIFlags Flags, DINodeArray Elements),
1208+ (Tag, Name, File, Line, Scope, BaseType, SizeInBits,
1209+ AlignInBits, OffsetInBits, Flags, Elements))
1210+ DEFINE_MDNODE_GET (DIFortranArrayType,
1211+ (unsigned Tag, MDString *Name, Metadata *File,
1212+ unsigned Line, Metadata *Scope, Metadata *BaseType,
1213+ uint64_t SizeInBits, uint32_t AlignInBits,
1214+ uint64_t OffsetInBits, DIFlags Flags, Metadata *Elements),
1215+ (Tag, Name, File, Line, Scope, BaseType, SizeInBits,
1216+ AlignInBits, OffsetInBits, Flags, Elements))
1217+
1218+ TempDIFortranArrayType clone () const { return cloneImpl (); }
1219+
1220+ DITypeRef getBaseType () const { return DITypeRef (getRawBaseType ()); }
1221+ DINodeArray getElements () const {
1222+ return cast_or_null<MDTuple>(getRawElements ());
1223+ }
1224+
1225+ Metadata *getRawBaseType () const { return getOperand (3 ); }
1226+ Metadata *getRawElements () const { return getOperand (4 ); }
1227+
1228+ // / Replace operands.
1229+ // /
1230+ // / If this \a isUniqued() and not \a isResolved(), on a uniquing collision
1231+ // / this will be RAUW'ed and deleted. Use a \a TrackingMDRef to keep track
1232+ // / of its movement if necessary.
1233+ // / @{
1234+ void replaceElements (DINodeArray Elements) {
1235+ #ifndef NDEBUG
1236+ for (DINode *Op : getElements ())
1237+ assert (is_contained (Elements->operands (), Op) &&
1238+ " Lost a member during member list replacement" );
1239+ #endif
1240+ replaceOperandWith (4 , Elements.get ());
1241+ }
1242+
1243+ static bool classof (const Metadata *MD) {
1244+ return MD->getMetadataID () == DIFortranArrayTypeKind;
1245+ }
1246+ };
1247+
9931248// / Type array for a subprogram.
9941249// /
9951250// / TODO: Fold the array of types in directly as operands.
@@ -1605,6 +1860,9 @@ class DISubprogram : public DILocalScope {
16051860 bool isExplicit () const { return getFlags () & FlagExplicit; }
16061861 bool isPrototyped () const { return getFlags () & FlagPrototyped; }
16071862 bool isMainSubprogram () const { return getFlags () & FlagMainSubprogram; }
1863+ bool isPure () const { return getFlags () & FlagPure; }
1864+ bool isElemental () const { return getFlags () & FlagElemental; }
1865+ bool isRecursive () const { return getFlags () & FlagRecursive; }
16081866
16091867 // / Check if this is reference-qualified.
16101868 // /
0 commit comments