Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module defines typeclasses to represent the relationships of an object-oriented inheritance hierarchy
Synopsis
- class DescendentOf a b where
- class ChildOf b c | c -> b
- data Value
- data Constant
- data GlobalValue
- data GlobalObject
- data GlobalVariable
- data GlobalAlias
- data Function
- data BasicBlock
- data Parameter
- data Instruction
- data BinaryOperator
- data User
- data MDNode
- data MDTuple
- data MDString
- data MDValue
- data DIExpression
- data DIGlobalVariableExpression
- data DILocation
- data DINode
- data DIImportedEntity
- data DIObjCProperty
- data DISubrange
- data DIEnumerator
- data DIVariable
- data DILocalVariable
- data DIGlobalVariable
- data DITemplateParameter
- data DITemplateTypeParameter
- data DITemplateValueParameter
- data DIScope
- data DIModule
- data DINamespace
- data DIFile
- data DICompileUnit
- data DIType
- data DIBasicType
- data DIDerivedType
- data DISubroutineType
- data DICompositeType
- data DILocalScope
- data DILexicalBlockBase
- data DILexicalBlock
- data DILexicalBlockFile
- data DISubprogram
- data DIMacroNode
- data DIMacro
- data DIMacroFile
- data NamedMetadata
- data InlineAsm
- data Type
- data Metadata
- data MetadataAsVal
- data RawOStream
- data RawPWriteStream
- data StringRef
Documentation
class DescendentOf a b where Source #
a class to represent safe casting of pointers to objects of descendant-classes to ancestor-classes.
Instances
(DescendentOf a b, ChildOf b c) => DescendentOf a c Source # | ancestor-descentant relationships are build out of parent-child relationships |
DescendentOf a a Source # | trivial casts |
class ChildOf b c | c -> b Source #
a class to represent direct parent-child relationships
Instances
Instances
ChildOf Value MetadataAsVal Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf Value InlineAsm Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf Value User Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf Value Parameter Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf Value BasicBlock Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST Operand (Ptr Value) Source # | |
DecodeM DecodeAST CallableOperand (Ptr Value) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST Operand (Ptr Value) Source # | |
EncodeM EncodeAST CallableOperand (Ptr Value) Source # | |
Defined in LLVM.Internal.Operand |
data GlobalValue Source #
Instances
ChildOf GlobalValue GlobalAlias Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf GlobalValue GlobalObject Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf Constant GlobalValue Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy |
data GlobalObject Source #
Instances
data GlobalVariable Source #
Instances
ChildOf GlobalObject GlobalVariable Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy |
data GlobalAlias Source #
Instances
ChildOf GlobalValue GlobalAlias Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy |
Instances
ChildOf GlobalObject Function Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
MonadIO m => EncodeM m PartitioningFn (IORef [IO ()] -> IO (FunPtr PartitioningFn)) Source # | |
Defined in LLVM.Internal.OrcJIT.CompileOnDemandLayer encodeM :: PartitioningFn -> m (IORef [IO ()] -> IO (FunPtr PartitioningFn0)) Source # |
data BasicBlock Source #
Instances
ChildOf Value BasicBlock Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST Name (Ptr BasicBlock) Source # | |
Defined in LLVM.Internal.DecodeAST | |
EncodeM EncodeAST Name (Ptr BasicBlock) Source # | |
Defined in LLVM.Internal.EncodeAST |
data Instruction Source #
Instances
data BinaryOperator Source #
Instances
ChildOf Instruction BinaryOperator Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy |
Instances
ChildOf User Instruction Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf User Constant Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf Value User Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy |
Instances
ChildOf Metadata MDNode Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf MDNode DIMacroNode Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf MDNode DINode Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf MDNode DILocation Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf MDNode DIGlobalVariableExpression Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf MDNode DIExpression Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf MDNode MDTuple Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
EncodeM EncodeAST MDNode (Ptr MDNode) Source # | |
DecodeM DecodeAST [Maybe Metadata] (Ptr MDNode) Source # | |
DecodeM DecodeAST (MDRef MDNode) (Ptr MDNode) Source # | |
Instances
ChildOf Metadata MDString Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST ShortByteString (Ptr MDString) Source # | |
Defined in LLVM.Internal.Metadata | |
EncodeM EncodeAST ShortByteString (Ptr MDString) Source # | |
Defined in LLVM.Internal.Operand |
data DIExpression Source #
Instances
ChildOf MDNode DIExpression Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DIExpression (Ptr DIExpression) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DIExpression (Ptr DIExpression) Source # | |
Defined in LLVM.Internal.Operand encodeM :: DIExpression0 -> EncodeAST (Ptr DIExpression) Source # |
data DIGlobalVariableExpression Source #
Instances
data DILocation Source #
Instances
ChildOf MDNode DILocation Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DILocation (Ptr DILocation) Source # | |
Defined in LLVM.Internal.Operand decodeM :: Ptr DILocation -> DecodeAST DILocation0 Source # | |
EncodeM EncodeAST DILocation (Ptr DILocation) Source # | |
Defined in LLVM.Internal.Operand encodeM :: DILocation0 -> EncodeAST (Ptr DILocation) Source # |
Instances
ChildOf DINode DIScope Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DINode DITemplateParameter Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DINode DIVariable Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DINode DIEnumerator Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DINode DISubrange Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DINode DIObjCProperty Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DINode DIImportedEntity Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf MDNode DINode Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DINode (Ptr DINode) Source # | |
EncodeM EncodeAST DINode (Ptr DINode) Source # | |
data DIImportedEntity Source #
Instances
ChildOf DINode DIImportedEntity Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DIImportedEntity (Ptr DIImportedEntity) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DIImportedEntity (Ptr DIImportedEntity) Source # | |
Defined in LLVM.Internal.Operand |
data DIObjCProperty Source #
Instances
ChildOf DINode DIObjCProperty Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DIObjCProperty (Ptr DIObjCProperty) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DIObjCProperty (Ptr DIObjCProperty) Source # | |
Defined in LLVM.Internal.Operand encodeM :: DIObjCProperty0 -> EncodeAST (Ptr DIObjCProperty) Source # |
data DISubrange Source #
Instances
ChildOf DINode DISubrange Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DISubrange (Ptr DISubrange) Source # | |
Defined in LLVM.Internal.Operand decodeM :: Ptr DISubrange -> DecodeAST DISubrange0 Source # | |
EncodeM EncodeAST DISubrange (Ptr DISubrange) Source # | |
Defined in LLVM.Internal.Operand encodeM :: DISubrange0 -> EncodeAST (Ptr DISubrange) Source # |
data DIEnumerator Source #
Instances
ChildOf DINode DIEnumerator Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DIEnumerator (Ptr DIEnumerator) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DIEnumerator (Ptr DIEnumerator) Source # | |
Defined in LLVM.Internal.Operand encodeM :: DIEnumerator0 -> EncodeAST (Ptr DIEnumerator) Source # |
data DIVariable Source #
Instances
ChildOf DIVariable DIGlobalVariable Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DIVariable DILocalVariable Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DINode DIVariable Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DIVariable (Ptr DIVariable) Source # | |
Defined in LLVM.Internal.Operand decodeM :: Ptr DIVariable -> DecodeAST DIVariable0 Source # | |
EncodeM EncodeAST DIVariable (Ptr DIVariable) Source # | |
Defined in LLVM.Internal.Operand encodeM :: DIVariable0 -> EncodeAST (Ptr DIVariable) Source # |
data DILocalVariable Source #
Instances
ChildOf DIVariable DILocalVariable Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DILocalVariable (Ptr DILocalVariable) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DILocalVariable (Ptr DILocalVariable) Source # | |
Defined in LLVM.Internal.Operand |
data DIGlobalVariable Source #
Instances
ChildOf DIVariable DIGlobalVariable Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DIGlobalVariable (Ptr DIGlobalVariable) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DIGlobalVariable (Ptr DIGlobalVariable) Source # | |
Defined in LLVM.Internal.Operand |
data DITemplateParameter Source #
Instances
data DITemplateTypeParameter Source #
Instances
ChildOf DITemplateParameter DITemplateTypeParameter Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy |
data DITemplateValueParameter Source #
Instances
ChildOf DITemplateParameter DITemplateValueParameter Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy |
Instances
ChildOf DIScope DILocalScope Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DIScope DIType Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DIScope DICompileUnit Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DIScope DIFile Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DIScope DINamespace Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DIScope DIModule Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DINode DIScope Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DIScope (Ptr DIScope) Source # | |
EncodeM EncodeAST DIScope (Ptr DIScope) Source # | |
data DINamespace Source #
Instances
ChildOf DIScope DINamespace Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DINamespace (Ptr DINamespace) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DINamespace (Ptr DINamespace) Source # | |
Defined in LLVM.Internal.Operand encodeM :: DINamespace0 -> EncodeAST (Ptr DINamespace) Source # |
data DICompileUnit Source #
Instances
ChildOf DIScope DICompileUnit Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DICompileUnit (Ptr DICompileUnit) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DICompileUnit (Ptr DICompileUnit) Source # | |
Defined in LLVM.Internal.Operand encodeM :: DICompileUnit0 -> EncodeAST (Ptr DICompileUnit) Source # |
Instances
ChildOf DIType DICompositeType Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DIType DISubroutineType Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DIType DIDerivedType Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DIType DIBasicType Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DIScope DIType Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DIType (Ptr DIType) Source # | |
EncodeM EncodeAST DIType (Ptr DIType) Source # | |
data DIBasicType Source #
Instances
ChildOf DIType DIBasicType Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DIBasicType (Ptr DIBasicType) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DIBasicType (Ptr DIBasicType) Source # | |
Defined in LLVM.Internal.Operand encodeM :: DIBasicType0 -> EncodeAST (Ptr DIBasicType) Source # |
data DIDerivedType Source #
Instances
ChildOf DIType DIDerivedType Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DIDerivedType (Ptr DIDerivedType) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DIDerivedType (Ptr DIDerivedType) Source # | |
Defined in LLVM.Internal.Operand encodeM :: DIDerivedType0 -> EncodeAST (Ptr DIDerivedType) Source # |
data DISubroutineType Source #
Instances
ChildOf DIType DISubroutineType Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DISubroutineType (Ptr DISubroutineType) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DISubroutineType (Ptr DISubroutineType) Source # | |
Defined in LLVM.Internal.Operand |
data DICompositeType Source #
Instances
ChildOf DIType DICompositeType Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DICompositeType (Ptr DICompositeType) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DICompositeType (Ptr DICompositeType) Source # | |
Defined in LLVM.Internal.Operand |
data DILocalScope Source #
Instances
ChildOf DILocalScope DISubprogram Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DILocalScope DILexicalBlockBase Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DIScope DILocalScope Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DILocalScope (Ptr DILocalScope) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DILocalScope (Ptr DILocalScope) Source # | |
Defined in LLVM.Internal.Operand encodeM :: DILocalScope0 -> EncodeAST (Ptr DILocalScope) Source # |
data DILexicalBlockBase Source #
Instances
data DILexicalBlock Source #
Instances
ChildOf DILexicalBlockBase DILexicalBlock Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy |
data DILexicalBlockFile Source #
Instances
ChildOf DILexicalBlockBase DILexicalBlockFile Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy |
data DISubprogram Source #
Instances
ChildOf DILocalScope DISubprogram Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DISubprogram (Ptr DISubprogram) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DISubprogram (Ptr DISubprogram) Source # | |
Defined in LLVM.Internal.Operand encodeM :: DISubprogram0 -> EncodeAST (Ptr DISubprogram) Source # |
data DIMacroNode Source #
Instances
ChildOf DIMacroNode DIMacroFile Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf DIMacroNode DIMacro Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf MDNode DIMacroNode Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST DIMacroNode (Ptr DIMacroNode) Source # | |
Defined in LLVM.Internal.Operand | |
EncodeM EncodeAST DIMacroNode (Ptr DIMacroNode) Source # | |
Defined in LLVM.Internal.Operand encodeM :: DIMacroNode0 -> EncodeAST (Ptr DIMacroNode) Source # |
Instances
ChildOf DIMacroNode DIMacro Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy |
data DIMacroFile Source #
Instances
ChildOf DIMacroNode DIMacroFile Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy |
Instances
ChildOf Value InlineAsm Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST InlineAssembly (Ptr InlineAsm) Source # | |
Defined in LLVM.Internal.InlineAssembly | |
EncodeM EncodeAST InlineAssembly (Ptr InlineAsm) Source # | |
Defined in LLVM.Internal.InlineAssembly |
Instances
ChildOf Metadata MDValue Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf Metadata MDString Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
ChildOf Metadata MDNode Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST Metadata (Ptr Metadata) Source # | |
EncodeM EncodeAST Metadata (Ptr Metadata) Source # | |
data MetadataAsVal Source #
Instances
ChildOf Value MetadataAsVal Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy | |
DecodeM DecodeAST Metadata (Ptr MetadataAsVal) Source # | |
Defined in LLVM.Internal.Operand |
data RawOStream Source #
Instances
ChildOf RawOStream RawPWriteStream Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy |
data RawPWriteStream Source #
Instances
ChildOf RawOStream RawPWriteStream Source # | |
Defined in LLVM.Internal.FFI.PtrHierarchy |