Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype DIFlags = DIFlags Word32
- data DITemplateParameterArray
- newtype TupleArray a = TupleArray (Ptr MDTuple)
- isAMDString :: Ptr Metadata -> IO (Ptr MDString)
- isAMDNode :: Ptr Metadata -> IO (Ptr MDNode)
- isAMDValue :: Ptr Metadata -> IO (Ptr MDValue)
- isAMetadataOperand :: Ptr Value -> IO (Ptr MetadataAsVal)
- getMetadataClassId :: Ptr MDNode -> IO MDSubclassID
- getDILocationLine :: Ptr DILocation -> IO Word32
- getDILocationColumn :: Ptr DILocation -> IO Word16
- getDILocationScope :: Ptr DILocation -> IO (Ptr DILocalScope)
- getDILocation :: Ptr Context -> Word32 -> Word16 -> Ptr DILocalScope -> IO (Ptr DILocation)
- getMDValue :: Ptr MDValue -> IO (Ptr Value)
- getMetadataOperand :: Ptr MetadataAsVal -> IO (Ptr Metadata)
- getMDKindIDInContext' :: Ptr Context -> Ptr CChar -> CUInt -> IO MDKindID
- getMDKindIDInContext :: Ptr Context -> (Ptr CChar, CUInt) -> IO MDKindID
- getMDKindNames :: Ptr Context -> Ptr (Ptr CChar) -> Ptr CUInt -> CUInt -> IO CUInt
- getMDString' :: Ptr Context -> CString -> CUInt -> IO (Ptr MDString)
- getMDString :: Ptr Context -> (CString, CUInt) -> IO (Ptr MDString)
- mdValue :: Ptr Value -> IO (Ptr MDValue)
- metadataOperand :: Ptr Context -> Ptr Metadata -> IO (Ptr Value)
- getMDStringValue :: Ptr MDString -> Ptr CUInt -> IO CString
- getMDTuple' :: Ptr Context -> Ptr (Ptr Metadata) -> CUInt -> IO (Ptr MDTuple)
- getMDTuple :: Ptr Context -> (CUInt, Ptr (Ptr Metadata)) -> IO (Ptr MDTuple)
- createTemporaryMDNodeInContext :: Ptr Context -> IO (Ptr MDNode)
- destroyTemporaryMDNode :: Ptr MDNode -> IO ()
- getMDNodeNumOperands :: Ptr MDNode -> IO CUInt
- getMDNodeOperand :: Ptr MDNode -> CUInt -> IO (Ptr Metadata)
- getNamedMetadataName :: Ptr NamedMetadata -> Ptr CUInt -> IO (Ptr CChar)
- getNamedMetadataNumOperands :: Ptr NamedMetadata -> IO CUInt
- getNamedMetadataOperands :: Ptr NamedMetadata -> Ptr (Ptr MDNode) -> IO ()
- namedMetadataAddOperands' :: Ptr NamedMetadata -> Ptr (Ptr MDNode) -> CUInt -> IO ()
- metadataReplaceAllUsesWith :: Ptr MDNode -> Ptr Metadata -> IO ()
- namedMetadataAddOperands :: Ptr NamedMetadata -> (CUInt, Ptr (Ptr MDNode)) -> IO ()
- getDIEnumerator :: Ptr Context -> Int64 -> Ptr MDString -> IO (Ptr DIEnumerator)
- getDIEnumeratorValue :: Ptr DIEnumerator -> IO Int64
- getDIEnumeratorName :: Ptr DIEnumerator -> IO (Ptr MDString)
- getFileFilename :: Ptr DIFile -> IO (Ptr MDString)
- getFileDirectory :: Ptr DIFile -> IO (Ptr MDString)
- getFileChecksum :: Ptr DIFile -> IO (Ptr MDString)
- getFileChecksumKind :: Ptr DIFile -> IO ChecksumKind
- getScopeName :: Ptr DIScope -> Ptr CUInt -> IO CString
- getTypeName :: Ptr DIType -> IO (Ptr MDString)
- getTypeAlignInBits :: Ptr DIType -> IO Word32
- getTypeSizeInBits :: Ptr DIType -> IO Word64
- getTypeOffsetInBits :: Ptr DIType -> IO Word64
- getTag :: Ptr DINode -> IO DwTag
- getTypeLine :: Ptr DIType -> IO Word32
- getTypeFlags :: Ptr DIType -> IO DIFlags
- getElements :: Ptr DICompositeType -> IO (Ptr MDTuple)
- getVTableHolder :: Ptr DICompositeType -> IO (Ptr DIType)
- getCompositeBaseType :: Ptr DICompositeType -> IO (Ptr DIType)
- getRuntimeLang :: Ptr DICompositeType -> IO Word16
- getTemplateParams :: Ptr DICompositeType -> IO (TupleArray DITemplateParameter)
- getIdentifier :: Ptr DICompositeType -> IO (Ptr MDString)
- getDIArrayType :: Ptr Context -> TupleArray DISubrange -> Ptr DIType -> Word64 -> Word32 -> DIFlags -> IO (Ptr DICompositeType)
- getDIEnumerationType :: Ptr Context -> Ptr DIScope -> Ptr MDString -> Ptr DIFile -> Word32 -> Word64 -> Word32 -> TupleArray DIEnumerator -> Ptr DIType -> Ptr MDString -> IO (Ptr DICompositeType)
- getDIStructType :: Ptr Context -> Ptr DIScope -> Ptr MDString -> Ptr DIFile -> Word32 -> Word64 -> Word32 -> DIFlags -> Ptr DIType -> TupleArray DIScope -> Word16 -> Ptr DIType -> Ptr MDString -> IO (Ptr DICompositeType)
- getDIUnionType :: Ptr Context -> Ptr DIScope -> Ptr MDString -> Ptr DIFile -> Word32 -> Word64 -> Word32 -> DIFlags -> TupleArray DIScope -> Word16 -> Ptr MDString -> IO (Ptr DICompositeType)
- getDIClassType :: Ptr Context -> Ptr DIScope -> Ptr MDString -> Ptr DIFile -> Word32 -> Word64 -> Word32 -> DIFlags -> Ptr DIType -> TupleArray DIScope -> Ptr DIType -> TupleArray DITemplateParameter -> Ptr MDString -> IO (Ptr DICompositeType)
- getDINamespace :: Ptr Context -> Ptr DIScope -> Ptr MDString -> LLVMBool -> IO (Ptr DINamespace)
- getNamespaceExportedSymbols :: Ptr DINamespace -> IO LLVMBool
- getScopeScope :: Ptr DIScope -> IO (Ptr DIScope)
- getScopeFile :: Ptr DIScope -> IO (Ptr DIFile)
- getLexicalBlockScope :: Ptr DILexicalBlockBase -> IO (Ptr DILocalScope)
- getLexicalBlockFileDiscriminator :: Ptr DILexicalBlockBase -> IO Word32
- getDILexicalBlockFile :: Ptr Context -> Ptr DILocalScope -> Ptr DIFile -> Word32 -> IO (Ptr DILexicalBlockFile)
- getLexicalBlockLine :: Ptr DILexicalBlockBase -> IO Word32
- getLexicalBlockColumn :: Ptr DILexicalBlockBase -> IO Word16
- getDILexicalBlock :: Ptr Context -> Ptr DILocalScope -> Ptr DIFile -> Word32 -> Word16 -> IO (Ptr DILexicalBlock)
- getDerivedBaseType :: Ptr DIType -> IO (Ptr DIType)
- getDerivedAddressSpace :: Ptr DIType -> Ptr CUInt -> IO LLVMBool
- getDISubroutineType :: Ptr Context -> DIFlags -> Word8 -> TupleArray DIType -> IO (Ptr DISubroutineType)
- getSubroutineCC :: Ptr DISubroutineType -> IO Word8
- getSubroutineTypeArray :: Ptr DISubroutineType -> IO (TupleArray DIType)
- getDIBasicType :: Ptr Context -> DwTag -> Ptr MDString -> Word64 -> Word32 -> Encoding -> IO (Ptr DIBasicType)
- getBasicTypeEncoding :: Ptr DIBasicType -> IO Encoding
- getDIDerivedType :: Ptr Context -> DwTag -> Ptr MDString -> Ptr DIFile -> CUInt -> Ptr DIScope -> Ptr DIType -> Word64 -> Word32 -> Word64 -> Word32 -> LLVMBool -> DIFlags -> IO (Ptr DIDerivedType)
- getDIFile :: Ptr Context -> Ptr MDString -> Ptr MDString -> ChecksumKind -> Ptr MDString -> IO (Ptr DIFile)
- getDISubrange :: Ptr Context -> Int64 -> Int64 -> IO (Ptr DISubrange)
- getDISubrangeCount :: Ptr DISubrange -> IO Int64
- getDISubrangeLowerBound :: Ptr DISubrange -> IO Int64
- getDISubprogramLine :: Ptr DISubprogram -> IO CUInt
- getDISubprogramVirtuality :: Ptr DISubprogram -> IO DwVirtuality
- getDISubprogramVirtualIndex :: Ptr DISubprogram -> IO CUInt
- getDISubprogramScopeLine :: Ptr DISubprogram -> IO CUInt
- getDISubprogramIsOptimized :: Ptr DISubprogram -> IO LLVMBool
- getDISubprogramIsDefinition :: Ptr DISubprogram -> IO LLVMBool
- getDISubprogramLocalToUnit :: Ptr DISubprogram -> IO LLVMBool
- getDISubprogramThisAdjustment :: Ptr DISubprogram -> IO Int32
- getDISubprogramFlags :: Ptr DISubprogram -> IO DIFlags
- getDISubprogramLinkageName :: Ptr DISubprogram -> IO (Ptr MDString)
- getDISubprogramType :: Ptr DISubprogram -> IO (Ptr DISubroutineType)
- getDISubprogramContainingType :: Ptr DISubprogram -> IO (Ptr DIType)
- getDISubprogramUnit :: Ptr DISubprogram -> IO (Ptr DICompileUnit)
- getDISubprogramTemplateParams :: Ptr DISubprogram -> IO (TupleArray DITemplateParameter)
- getDISubprogramVariables :: Ptr DISubprogram -> IO (TupleArray DILocalVariable)
- getDISubprogramThrownTypes :: Ptr DISubprogram -> IO (TupleArray DIType)
- getDISubprogramDeclaration :: Ptr DISubprogram -> IO (Ptr DISubprogram)
- getDISubprogram :: Ptr Context -> Ptr DIScope -> Ptr MDString -> Ptr MDString -> Ptr DIFile -> CUInt -> Ptr DISubroutineType -> LLVMBool -> LLVMBool -> CUInt -> Ptr DIType -> DwVirtuality -> CUInt -> Int32 -> DIFlags -> LLVMBool -> Ptr DICompileUnit -> TupleArray DITemplateParameter -> Ptr DISubprogram -> TupleArray DILocalVariable -> TupleArray DIType -> IO (Ptr DISubprogram)
- getDIExpression' :: Ptr Context -> CUInt -> Ptr Word64 -> IO (Ptr DIExpression)
- getDIExpression :: Ptr Context -> (CUInt, Ptr Word64) -> IO (Ptr DIExpression)
- getDIExpressionNumElements :: Ptr DIExpression -> IO CUInt
- getDIExpressionElement :: Ptr DIExpression -> CUInt -> IO Word64
- getDIVariableScope :: Ptr DIVariable -> IO (Ptr DIScope)
- getDIVariableFile :: Ptr DIVariable -> IO (Ptr DIFile)
- getDIVariableName :: Ptr DIVariable -> IO (Ptr MDString)
- getDIVariableLine :: Ptr DIVariable -> IO CUInt
- getDIVariableType :: Ptr DIVariable -> IO (Ptr DIType)
- getDIVariableAlignInBits :: Ptr DIVariable -> IO Word32
- getDILocalVariable :: Ptr Context -> Ptr DIScope -> CString -> Ptr DIFile -> Word32 -> Ptr DIType -> Word16 -> DIFlags -> Word32 -> IO (Ptr DILocalVariable)
- getDILocalVariableArg :: Ptr DILocalVariable -> IO Word16
- getDILocalVariableFlags :: Ptr DILocalVariable -> IO DIFlags
- getDIGlobalVariable :: Ptr Context -> Ptr DIScope -> Ptr MDString -> Ptr MDString -> Ptr DIFile -> CUInt -> Ptr DIType -> LLVMBool -> LLVMBool -> Ptr DIDerivedType -> Word32 -> IO (Ptr DIGlobalVariable)
- getDIGlobalVariableLocal :: Ptr DIGlobalVariable -> IO LLVMBool
- getDIGlobalVariableDefinition :: Ptr DIGlobalVariable -> IO LLVMBool
- getDIGlobalVariableLinkageName :: Ptr DIGlobalVariable -> IO (Ptr MDString)
- getDIGlobalVariableStaticDataMemberDeclaration :: Ptr DIGlobalVariable -> IO (Ptr DIDerivedType)
- getDICompileUnit :: Ptr Context -> CUInt -> Ptr DIFile -> Ptr MDString -> LLVMBool -> Ptr MDString -> CUInt -> Ptr MDString -> DebugEmissionKind -> TupleArray DICompositeType -> TupleArray DIScope -> TupleArray DIGlobalVariableExpression -> TupleArray DIImportedEntity -> TupleArray DIMacroNode -> Word64 -> LLVMBool -> LLVMBool -> LLVMBool -> IO (Ptr DICompileUnit)
- getDICompileUnitLanguage :: Ptr DICompileUnit -> IO CUInt
- getDICompileUnitSplitDebugInlining :: Ptr DICompileUnit -> IO LLVMBool
- getDICompileUnitDebugInfoForProfiling :: Ptr DICompileUnit -> IO LLVMBool
- getDICompileUnitGnuPubnames :: Ptr DICompileUnit -> IO LLVMBool
- getDICompileUnitOptimized :: Ptr DICompileUnit -> IO LLVMBool
- getDICompileUnitRuntimeVersion :: Ptr DICompileUnit -> IO CUInt
- getDICompileUnitProducer :: Ptr DICompileUnit -> IO (Ptr MDString)
- getDICompileUnitFlags :: Ptr DICompileUnit -> IO (Ptr MDString)
- getDICompileUnitSplitDebugFilename :: Ptr DICompileUnit -> IO (Ptr MDString)
- getDICompileUnitEmissionKind :: Ptr DICompileUnit -> IO DebugEmissionKind
- getDICompileUnitDWOId :: Ptr DICompileUnit -> IO Word64
- getDICompileUnitEnumTypes :: Ptr DICompileUnit -> IO (TupleArray DICompositeType)
- getDICompileUnitRetainedTypes :: Ptr DICompileUnit -> IO (TupleArray DIScope)
- getDICompileUnitGlobalVariables :: Ptr DICompileUnit -> IO (TupleArray DIGlobalVariableExpression)
- getDICompileUnitImportedEntities :: Ptr DICompileUnit -> IO (TupleArray DIImportedEntity)
- getDICompileUnitMacros :: Ptr DICompileUnit -> IO (TupleArray DIMacroNode)
- getDIFlag :: CString -> IO DIFlags
- getDITemplateParameterName :: Ptr DITemplateParameter -> IO (Ptr MDString)
- getDITemplateParameterType :: Ptr DITemplateParameter -> IO (Ptr DIType)
- getDITemplateTypeParameter :: Ptr Context -> Ptr MDString -> Ptr DIType -> IO (Ptr DITemplateTypeParameter)
- getDITemplateValueParameter :: Ptr Context -> Ptr MDString -> Ptr DIType -> DwTag -> Ptr Metadata -> IO (Ptr DITemplateValueParameter)
- getDITemplateValueParameterValue :: Ptr DITemplateValueParameter -> IO (Ptr Metadata)
- getDIMacro :: Ptr Context -> Macinfo -> Word32 -> Ptr MDString -> Ptr MDString -> IO (Ptr DIMacro)
- getDIMacroMacinfo :: Ptr DIMacro -> IO Macinfo
- getDIMacroLine :: Ptr DIMacro -> IO Word32
- getDIMacroName :: Ptr DIMacro -> IO (Ptr MDString)
- getDIMacroValue :: Ptr DIMacro -> IO (Ptr MDString)
- getDIMacroFile :: Ptr Context -> Word32 -> Ptr DIFile -> TupleArray DIMacroNode -> IO (Ptr DIMacroFile)
- getDIMacroFileLine :: Ptr DIMacroFile -> IO Word32
- getDIMacroFileFile :: Ptr DIMacroFile -> IO (Ptr DIFile)
- getDIMacroFileNumElements :: Ptr DIMacroFile -> IO CUInt
- getDIMacroFileElement :: Ptr DIMacroFile -> CUInt -> IO (Ptr DIMacroNode)
- getDIImportedEntity :: Ptr Context -> DwTag -> Ptr DIScope -> Ptr DINode -> Ptr DIFile -> Word32 -> Ptr MDString -> IO (Ptr DIImportedEntity)
- getDIImportedEntityLine :: Ptr DIImportedEntity -> IO Word32
- getDIImportedEntityScope :: Ptr DIImportedEntity -> IO (Ptr DIScope)
- getDIImportedEntityEntity :: Ptr DIImportedEntity -> IO (Ptr DINode)
- getDIImportedEntityName :: Ptr DIImportedEntity -> IO (Ptr MDString)
- getDIImportedEntityFile :: Ptr DIImportedEntity -> IO (Ptr DIFile)
- getDIGlobalVariableExpression :: Ptr Context -> Ptr DIGlobalVariable -> Ptr DIExpression -> IO (Ptr DIGlobalVariableExpression)
- getDIGlobalVariableExpressionVariable :: Ptr DIGlobalVariableExpression -> IO (Ptr DIGlobalVariable)
- getDIGlobalVariableExpressionExpression :: Ptr DIGlobalVariableExpression -> IO (Ptr DIExpression)
- getDIObjCProperty :: Ptr Context -> Ptr MDString -> Ptr DIFile -> Word32 -> Ptr MDString -> Ptr MDString -> Word32 -> Ptr DIType -> IO (Ptr DIObjCProperty)
- getDIObjCPropertyLine :: Ptr DIObjCProperty -> IO Word32
- getDIObjCPropertyAttributes :: Ptr DIObjCProperty -> IO Word32
- getDIObjCPropertyName :: Ptr DIObjCProperty -> IO (Ptr MDString)
- getDIObjCPropertyFile :: Ptr DIObjCProperty -> IO (Ptr DIFile)
- getDIObjCPropertyGetterName :: Ptr DIObjCProperty -> IO (Ptr MDString)
- getDIObjCPropertySetterName :: Ptr DIObjCProperty -> IO (Ptr MDString)
- getDIObjCPropertyType :: Ptr DIObjCProperty -> IO (Ptr DIType)
- getDIModule :: Ptr Context -> Ptr DIScope -> Ptr MDString -> Ptr MDString -> Ptr MDString -> Ptr MDString -> IO (Ptr DIModule)
- getDIModuleConfigurationMacros :: Ptr DIModule -> IO (Ptr MDString)
- getDIModuleIncludePath :: Ptr DIModule -> IO (Ptr MDString)
- getDIModuleISysRoot :: Ptr DIModule -> IO (Ptr MDString)
Documentation
newtype TupleArray a Source #
A 'TupleArray a' stores an array of elements of type 'Ptr a' using an MDTuple
.
Instances
(MonadIO m, MonadAnyCont IO m, DecodeM m a (Ptr a')) => DecodeM m [a] (TupleArray a') Source # | |
Defined in LLVM.Internal.Operand decodeM :: TupleArray a' -> m [a] Source # | |
(MonadIO m, MonadState EncodeState m, MonadAnyCont IO m, EncodeM m a (Ptr a'), DescendentOf Metadata a') => EncodeM m [a] (TupleArray a') Source # | |
Defined in LLVM.Internal.Operand encodeM :: [a] -> m (TupleArray a') Source # |
isAMetadataOperand :: Ptr Value -> IO (Ptr MetadataAsVal) Source #
getMetadataClassId :: Ptr MDNode -> IO MDSubclassID Source #
getDILocationLine :: Ptr DILocation -> IO Word32 Source #
getDILocationColumn :: Ptr DILocation -> IO Word16 Source #
getDILocationScope :: Ptr DILocation -> IO (Ptr DILocalScope) Source #
getDILocation :: Ptr Context -> Word32 -> Word16 -> Ptr DILocalScope -> IO (Ptr DILocation) Source #
getMetadataOperand :: Ptr MetadataAsVal -> IO (Ptr Metadata) Source #
getNamedMetadataName :: Ptr NamedMetadata -> Ptr CUInt -> IO (Ptr CChar) Source #
getNamedMetadataOperands :: Ptr NamedMetadata -> Ptr (Ptr MDNode) -> IO () Source #
namedMetadataAddOperands' :: Ptr NamedMetadata -> Ptr (Ptr MDNode) -> CUInt -> IO () Source #
namedMetadataAddOperands :: Ptr NamedMetadata -> (CUInt, Ptr (Ptr MDNode)) -> IO () Source #
getDIEnumeratorName :: Ptr DIEnumerator -> IO (Ptr MDString) Source #
getElements :: Ptr DICompositeType -> IO (Ptr MDTuple) Source #
getVTableHolder :: Ptr DICompositeType -> IO (Ptr DIType) Source #
getCompositeBaseType :: Ptr DICompositeType -> IO (Ptr DIType) Source #
getRuntimeLang :: Ptr DICompositeType -> IO Word16 Source #
getIdentifier :: Ptr DICompositeType -> IO (Ptr MDString) Source #
getDIArrayType :: Ptr Context -> TupleArray DISubrange -> Ptr DIType -> Word64 -> Word32 -> DIFlags -> IO (Ptr DICompositeType) Source #
getDIEnumerationType :: Ptr Context -> Ptr DIScope -> Ptr MDString -> Ptr DIFile -> Word32 -> Word64 -> Word32 -> TupleArray DIEnumerator -> Ptr DIType -> Ptr MDString -> IO (Ptr DICompositeType) Source #
getDIStructType :: Ptr Context -> Ptr DIScope -> Ptr MDString -> Ptr DIFile -> Word32 -> Word64 -> Word32 -> DIFlags -> Ptr DIType -> TupleArray DIScope -> Word16 -> Ptr DIType -> Ptr MDString -> IO (Ptr DICompositeType) Source #
getDIUnionType :: Ptr Context -> Ptr DIScope -> Ptr MDString -> Ptr DIFile -> Word32 -> Word64 -> Word32 -> DIFlags -> TupleArray DIScope -> Word16 -> Ptr MDString -> IO (Ptr DICompositeType) Source #
getDIClassType :: Ptr Context -> Ptr DIScope -> Ptr MDString -> Ptr DIFile -> Word32 -> Word64 -> Word32 -> DIFlags -> Ptr DIType -> TupleArray DIScope -> Ptr DIType -> TupleArray DITemplateParameter -> Ptr MDString -> IO (Ptr DICompositeType) Source #
getDINamespace :: Ptr Context -> Ptr DIScope -> Ptr MDString -> LLVMBool -> IO (Ptr DINamespace) Source #
getDILexicalBlockFile :: Ptr Context -> Ptr DILocalScope -> Ptr DIFile -> Word32 -> IO (Ptr DILexicalBlockFile) Source #
getDILexicalBlock :: Ptr Context -> Ptr DILocalScope -> Ptr DIFile -> Word32 -> Word16 -> IO (Ptr DILexicalBlock) Source #
getDISubroutineType :: Ptr Context -> DIFlags -> Word8 -> TupleArray DIType -> IO (Ptr DISubroutineType) Source #
getSubroutineCC :: Ptr DISubroutineType -> IO Word8 Source #
getDIBasicType :: Ptr Context -> DwTag -> Ptr MDString -> Word64 -> Word32 -> Encoding -> IO (Ptr DIBasicType) Source #
DIBasicType
getDIDerivedType :: Ptr Context -> DwTag -> Ptr MDString -> Ptr DIFile -> CUInt -> Ptr DIScope -> Ptr DIType -> Word64 -> Word32 -> Word64 -> Word32 -> LLVMBool -> DIFlags -> IO (Ptr DIDerivedType) Source #
getDIFile :: Ptr Context -> Ptr MDString -> Ptr MDString -> ChecksumKind -> Ptr MDString -> IO (Ptr DIFile) Source #
getDISubrange :: Ptr Context -> Int64 -> Int64 -> IO (Ptr DISubrange) Source #
getDISubrangeCount :: Ptr DISubrange -> IO Int64 Source #
getDISubprogramLine :: Ptr DISubprogram -> IO CUInt Source #
getDISubprogramUnit :: Ptr DISubprogram -> IO (Ptr DICompileUnit) Source #
getDISubprogram :: Ptr Context -> Ptr DIScope -> Ptr MDString -> Ptr MDString -> Ptr DIFile -> CUInt -> Ptr DISubroutineType -> LLVMBool -> LLVMBool -> CUInt -> Ptr DIType -> DwVirtuality -> CUInt -> Int32 -> DIFlags -> LLVMBool -> Ptr DICompileUnit -> TupleArray DITemplateParameter -> Ptr DISubprogram -> TupleArray DILocalVariable -> TupleArray DIType -> IO (Ptr DISubprogram) Source #
getDIExpressionElement :: Ptr DIExpression -> CUInt -> IO Word64 Source #
getDIVariableScope :: Ptr DIVariable -> IO (Ptr DIScope) Source #
getDIVariableFile :: Ptr DIVariable -> IO (Ptr DIFile) Source #
getDIVariableName :: Ptr DIVariable -> IO (Ptr MDString) Source #
getDIVariableLine :: Ptr DIVariable -> IO CUInt Source #
getDIVariableType :: Ptr DIVariable -> IO (Ptr DIType) Source #
getDILocalVariable :: Ptr Context -> Ptr DIScope -> CString -> Ptr DIFile -> Word32 -> Ptr DIType -> Word16 -> DIFlags -> Word32 -> IO (Ptr DILocalVariable) Source #
getDIGlobalVariable :: Ptr Context -> Ptr DIScope -> Ptr MDString -> Ptr MDString -> Ptr DIFile -> CUInt -> Ptr DIType -> LLVMBool -> LLVMBool -> Ptr DIDerivedType -> Word32 -> IO (Ptr DIGlobalVariable) Source #
getDIGlobalVariableStaticDataMemberDeclaration :: Ptr DIGlobalVariable -> IO (Ptr DIDerivedType) Source #
getDICompileUnit :: Ptr Context -> CUInt -> Ptr DIFile -> Ptr MDString -> LLVMBool -> Ptr MDString -> CUInt -> Ptr MDString -> DebugEmissionKind -> TupleArray DICompositeType -> TupleArray DIScope -> TupleArray DIGlobalVariableExpression -> TupleArray DIImportedEntity -> TupleArray DIMacroNode -> Word64 -> LLVMBool -> LLVMBool -> LLVMBool -> IO (Ptr DICompileUnit) Source #
getDICompileUnitProducer :: Ptr DICompileUnit -> IO (Ptr MDString) Source #
getDICompileUnitFlags :: Ptr DICompileUnit -> IO (Ptr MDString) Source #
getDICompileUnitGlobalVariables :: Ptr DICompileUnit -> IO (TupleArray DIGlobalVariableExpression) Source #
getDITemplateTypeParameter :: Ptr Context -> Ptr MDString -> Ptr DIType -> IO (Ptr DITemplateTypeParameter) Source #
getDITemplateValueParameter :: Ptr Context -> Ptr MDString -> Ptr DIType -> DwTag -> Ptr Metadata -> IO (Ptr DITemplateValueParameter) Source #
getDIMacro :: Ptr Context -> Macinfo -> Word32 -> Ptr MDString -> Ptr MDString -> IO (Ptr DIMacro) Source #
getDIMacroFile :: Ptr Context -> Word32 -> Ptr DIFile -> TupleArray DIMacroNode -> IO (Ptr DIMacroFile) Source #
getDIMacroFileLine :: Ptr DIMacroFile -> IO Word32 Source #
getDIMacroFileFile :: Ptr DIMacroFile -> IO (Ptr DIFile) Source #
getDIMacroFileElement :: Ptr DIMacroFile -> CUInt -> IO (Ptr DIMacroNode) Source #
getDIImportedEntity :: Ptr Context -> DwTag -> Ptr DIScope -> Ptr DINode -> Ptr DIFile -> Word32 -> Ptr MDString -> IO (Ptr DIImportedEntity) Source #
getDIImportedEntityFile :: Ptr DIImportedEntity -> IO (Ptr DIFile) Source #
getDIGlobalVariableExpression :: Ptr Context -> Ptr DIGlobalVariable -> Ptr DIExpression -> IO (Ptr DIGlobalVariableExpression) Source #
getDIGlobalVariableExpressionVariable :: Ptr DIGlobalVariableExpression -> IO (Ptr DIGlobalVariable) Source #
getDIGlobalVariableExpressionExpression :: Ptr DIGlobalVariableExpression -> IO (Ptr DIExpression) Source #
getDIObjCProperty :: Ptr Context -> Ptr MDString -> Ptr DIFile -> Word32 -> Ptr MDString -> Ptr MDString -> Word32 -> Ptr DIType -> IO (Ptr DIObjCProperty) Source #
getDIObjCPropertyName :: Ptr DIObjCProperty -> IO (Ptr MDString) Source #
getDIObjCPropertyFile :: Ptr DIObjCProperty -> IO (Ptr DIFile) Source #
getDIObjCPropertyType :: Ptr DIObjCProperty -> IO (Ptr DIType) Source #