{-# LANGUAGE DuplicateRecordFields #-}
module LLVM.AST.Operand
( module LLVM.AST.Operand
)
where
import LLVM.Prelude
import LLVM.AST.Name
import LLVM.AST.Constant
import LLVM.AST.InlineAssembly
import LLVM.AST.Type
data Operand
= LocalReference Type Name
| ConstantOperand Constant
| MetadataOperand Metadata
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
type CallableOperand = Either InlineAssembly Operand
data Metadata
= MDString ShortByteString
| MDNode (MDRef MDNode)
| MDValue Operand
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
newtype MetadataNodeID = MetadataNodeID Word
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data MDRef a
= MDRef MetadataNodeID
| MDInline a
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
instance Functor MDRef where
fmap _ (MDRef i) = MDRef i
fmap f (MDInline a) = MDInline (f a)
data DWOpFragment = DW_OP_LLVM_Fragment
{ offset :: Word64
, size :: Word64
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DWOp
= DwOpFragment DWOpFragment
| DW_OP_StackValue
| DW_OP_Swap
| DW_OP_ConstU Word64
| DW_OP_PlusUConst Word64
| DW_OP_Plus
| DW_OP_Minus
| DW_OP_Mul
| DW_OP_Deref
| DW_OP_XDeref
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data MDNode
= MDTuple [Maybe Metadata]
| DIExpression DIExpression
| DIGlobalVariableExpression DIGlobalVariableExpression
| DILocation DILocation
| DIMacroNode DIMacroNode
| DINode DINode
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DILocation = Location
{ line :: Word32
, column :: Word16
, scope :: MDRef DILocalScope
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIExpression = Expression
{ operands :: [DWOp]
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIGlobalVariableExpression = GlobalVariableExpression
{ var :: MDRef DIGlobalVariable
, expr :: MDRef DIExpression
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIAccessibility
= Private
| Protected
| Public
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIInheritance
= SingleInheritance
| MultipleInheritance
| VirtualInheritance
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIFlag
= Accessibility DIAccessibility
| FwdDecl
| AppleBlock
| BlockByrefStruct
| VirtualFlag
| Artificial
| Explicit
| Prototyped
| ObjcClassComplete
| ObjectPointer
| Vector
| StaticMember
| LValueReference
| RValueReference
| InheritanceFlag DIInheritance
| IntroducedVirtual
| BitField
| NoReturn
| MainSubprogram
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIMacroInfo = Define | Undef
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIMacroNode
= DIMacro
{ info :: DIMacroInfo
, line :: Word32
, name :: ShortByteString
, value :: ShortByteString
}
| DIMacroFile
{ line :: Word32
, file :: MDRef DIFile
, elements :: [MDRef DIMacroNode]
}
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DINode
= DIEnumerator DIEnumerator
| DIImportedEntity DIImportedEntity
| DIObjCProperty DIObjCProperty
| DIScope DIScope
| DISubrange DISubrange
| DITemplateParameter DITemplateParameter
| DIVariable DIVariable
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIObjCProperty = ObjCProperty
{ name :: ShortByteString
, file :: Maybe (MDRef DIFile)
, line :: Word32
, getterName :: ShortByteString
, setterName :: ShortByteString
, attributes :: Word32
, type' :: Maybe (MDRef DIType)
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data ImportedEntityTag = ImportedModule | ImportedDeclaration
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIImportedEntity = ImportedEntity
{ tag :: ImportedEntityTag
, name :: ShortByteString
, scope :: MDRef DIScope
, entity :: Maybe (MDRef DINode)
, file :: Maybe (MDRef DIFile)
, line :: Word32
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIEnumerator =
Enumerator { value :: Int64, name :: ShortByteString }
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DISubrange =
Subrange { count :: Int64, lowerBound :: Int64 }
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIScope
= DICompileUnit DICompileUnit
| DIFile DIFile
| DILocalScope DILocalScope
| DIModule DIModule
| DINamespace DINamespace
| DIType DIType
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIModule = Module
{ scope :: Maybe (MDRef DIScope)
, name :: ShortByteString
, configurationMacros :: ShortByteString
, includePath :: ShortByteString
, isysRoot :: ShortByteString
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DINamespace = Namespace
{ name :: ShortByteString
, scope :: Maybe (MDRef DIScope)
, exportSymbols :: Bool
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DebugEmissionKind = NoDebug | FullDebug | LineTablesOnly
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DICompileUnit = CompileUnit
{ language :: Word32
, file :: MDRef DIFile
, producer :: ShortByteString
, optimized :: Bool
, flags :: ShortByteString
, runtimeVersion :: Word32
, splitDebugFileName :: ShortByteString
, emissionKind :: DebugEmissionKind
, enums :: [MDRef DICompositeType]
, retainedTypes :: [MDRef (Either DIType DISubprogram)]
, globals :: [MDRef DIGlobalVariableExpression]
, imports :: [MDRef DIImportedEntity]
, macros :: [MDRef DIMacroNode]
, dWOId :: Word64
, splitDebugInlining :: Bool
, debugInfoForProfiling :: Bool
, gnuPubnames :: Bool
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIFile = File
{ filename :: ShortByteString
, directory :: ShortByteString
, checksum :: ShortByteString
, checksumKind :: ChecksumKind
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data ChecksumKind = None | MD5 | SHA1
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DILocalScope
= DILexicalBlockBase DILexicalBlockBase
| DISubprogram DISubprogram
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DISubprogram = Subprogram
{ scope :: Maybe (MDRef DIScope)
, name :: ShortByteString
, linkageName :: ShortByteString
, file :: Maybe (MDRef DIFile)
, line :: Word32
, type' :: Maybe (MDRef DISubroutineType)
, localToUnit :: Bool
, definition :: Bool
, scopeLine :: Word32
, containingType :: Maybe (MDRef DIType)
, virtuality :: Virtuality
, virtualityIndex :: Word32
, thisAdjustment :: Int32
, flags :: [DIFlag]
, optimized :: Bool
, unit :: Maybe (MDRef DICompileUnit)
, templateParams :: [MDRef DITemplateParameter]
, declaration :: Maybe (MDRef DISubprogram)
, variables :: [MDRef DILocalVariable]
, thrownTypes :: [MDRef DIType]
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data Virtuality = NoVirtuality | Virtual | PureVirtual
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data BasicTypeTag = BaseType | UnspecifiedType
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIType
= DIBasicType DIBasicType
| DICompositeType DICompositeType
| DIDerivedType DIDerivedType
| DISubroutineType DISubroutineType
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIBasicType = BasicType
{ name :: ShortByteString
, sizeInBits :: Word64
, alignInBits :: Word32
, encoding :: Maybe Encoding
, tag :: BasicTypeTag
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DISubroutineType = SubroutineType
{ flags :: [DIFlag]
, cc :: Word8
, typeArray :: [Maybe (MDRef DIType)]
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DerivedTypeTag
= Typedef
| PointerType
| PtrToMemberType
| ReferenceType
| RValueReferenceType
| ConstType
| VolatileType
| RestrictType
| AtomicType
| Member
| Inheritance
| Friend
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIDerivedType =
DerivedType
{ tag :: DerivedTypeTag
, name :: ShortByteString
, file :: Maybe (MDRef DIFile)
, line :: Word32
, scope :: Maybe (MDRef DIScope)
, baseType :: MDRef DIType
, sizeInBits :: Word64
, alignInBits :: Word32
, offsetInBits :: Word64
, addressSpace :: Maybe Word32
, flags :: [DIFlag]
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DICompositeType
= DIArrayType
{ subscripts :: [DISubrange]
, elementTy :: Maybe (MDRef DIType)
, sizeInBits :: Word64
, alignInBits :: Word32
, flags :: [DIFlag]
}
| DIClassType
{ scope :: Maybe (MDRef DIScope)
, name :: ShortByteString
, file :: Maybe (MDRef DIFile)
, line :: Word32
, flags :: [DIFlag]
, derivedFrom :: Maybe (MDRef DIType)
, elements :: [MDRef (Either DIDerivedType DISubprogram)]
, vtableHolder :: Maybe (MDRef DIType)
, templateParams :: [DITemplateParameter]
, identifier :: ShortByteString
, sizeInBits :: Word64
, alignInBits :: Word32
}
| DIEnumerationType
{ scope :: Maybe (MDRef DIScope)
, name :: ShortByteString
, file :: Maybe (MDRef DIFile)
, line :: Word32
, values :: [DIEnumerator]
, baseType :: Maybe (MDRef DIType)
, identifier :: ShortByteString
, sizeInBits :: Word64
, alignInBits :: Word32
}
| DIStructureType
{ scope :: Maybe (MDRef DIScope)
, name :: ShortByteString
, file :: Maybe (MDRef DIFile)
, line :: Word32
, flags :: [DIFlag]
, derivedFrom :: Maybe (MDRef DIType)
, elements :: [MDRef (Either DIDerivedType DISubprogram)]
, runtimeLang :: Word16
, vtableHolder :: Maybe (MDRef DIType)
, identifier :: ShortByteString
, sizeInBits :: Word64
, alignInBits :: Word32
}
| DIUnionType
{ scope :: Maybe (MDRef DIScope)
, name :: ShortByteString
, file :: Maybe (MDRef DIFile)
, line :: Word32
, flags :: [DIFlag]
, elements :: [MDRef (Either DIDerivedType DISubprogram)]
, runtimeLang :: Word16
, identifier :: ShortByteString
, sizeInBits :: Word64
, alignInBits :: Word32
}
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data Encoding
= AddressEncoding
| BooleanEncoding
| FloatEncoding
| SignedEncoding
| SignedCharEncoding
| UnsignedEncoding
| UnsignedCharEncoding
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data TemplateValueParameterTag
= TemplateValueParameter
| GNUTemplateTemplateParam
| GNUTemplateParameterPack
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DITemplateParameter
= DITemplateTypeParameter
{ name :: ShortByteString
, type' :: MDRef DIType
}
| DITemplateValueParameter
{ name :: ShortByteString
, type' :: MDRef DIType
, value :: Metadata
, tag :: TemplateValueParameterTag
}
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DILexicalBlockBase
= DILexicalBlock
{ scope :: MDRef DILocalScope
, file :: Maybe (MDRef DIFile)
, line :: Word32
, column :: Word16
}
| DILexicalBlockFile
{ scope :: MDRef DILocalScope
, file :: Maybe (MDRef DIFile)
, discriminator :: Word32
}
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIVariable
= DIGlobalVariable DIGlobalVariable
| DILocalVariable DILocalVariable
deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DIGlobalVariable = GlobalVariable
{ name :: ShortByteString
, scope :: Maybe (MDRef DIScope)
, file :: Maybe (MDRef DIFile)
, line :: Word32
, type' :: Maybe (MDRef DIType)
, linkageName :: ShortByteString
, local :: Bool
, definition :: Bool
, staticDataMemberDeclaration :: Maybe (MDRef DIDerivedType)
, alignInBits :: Word32
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)
data DILocalVariable = LocalVariable
{ name :: ShortByteString
, scope :: MDRef DIScope
, file :: Maybe (MDRef DIFile)
, line :: Word32
, type' :: Maybe (MDRef DIType)
, flags :: [DIFlag]
, arg :: Word16
, alignInBits :: Word32
} deriving (Eq, Ord, Read, Show, Typeable, Data, Generic)