Portability | requires GHC 6.8, LLVM |
---|---|
Stability | experimental |
Maintainer | bos@serpentine.com |
This module provides direct access to the LLVM C bindings.
- data Module
- type ModuleRef = Ptr Module
- moduleCreateWithName :: CString -> IO ModuleRef
- disposeModule :: ModuleRef -> IO ()
- ptrDisposeModule :: FunPtr (ModuleRef -> IO ())
- getDataLayout :: ModuleRef -> IO CString
- setDataLayout :: ModuleRef -> CString -> IO ()
- getTarget :: ModuleRef -> IO CString
- setTarget :: ModuleRef -> CString -> IO ()
- data ModuleProvider
- type ModuleProviderRef = Ptr ModuleProvider
- createModuleProviderForExistingModule :: ModuleRef -> IO ModuleProviderRef
- ptrDisposeModuleProvider :: FunPtr (ModuleProviderRef -> IO ())
- data Type
- type TypeRef = Ptr Type
- addTypeName :: ModuleRef -> CString -> TypeRef -> IO CInt
- deleteTypeName :: ModuleRef -> CString -> IO ()
- getTypeKind :: TypeRef -> IO TypeKind
- data TypeKind
- int1Type :: TypeRef
- int8Type :: TypeRef
- int16Type :: TypeRef
- int32Type :: TypeRef
- int64Type :: TypeRef
- integerType :: CUInt -> TypeRef
- getIntTypeWidth :: TypeRef -> IO CUInt
- floatType :: TypeRef
- doubleType :: TypeRef
- x86FP80Type :: TypeRef
- fp128Type :: TypeRef
- ppcFP128Type :: TypeRef
- functionType :: TypeRef -> Ptr TypeRef -> CUInt -> CInt -> TypeRef
- isFunctionVarArg :: TypeRef -> IO CInt
- getReturnType :: TypeRef -> IO TypeRef
- countParamTypes :: TypeRef -> IO CUInt
- getParamTypes :: TypeRef -> Ptr TypeRef -> IO ()
- voidType :: TypeRef
- labelType :: TypeRef
- opaqueType :: TypeRef
- arrayType :: TypeRef -> CUInt -> TypeRef
- pointerType :: TypeRef -> CUInt -> TypeRef
- vectorType :: TypeRef -> CUInt -> TypeRef
- getElementType :: TypeRef -> IO TypeRef
- getArrayLength :: TypeRef -> IO CUInt
- getPointerAddressSpace :: TypeRef -> IO CUInt
- getVectorSize :: TypeRef -> IO CUInt
- structType :: Ptr TypeRef -> CUInt -> CInt -> TypeRef
- countStructElementTypes :: TypeRef -> CUInt
- getStructElementTypes :: TypeRef -> Ptr TypeRef -> IO ()
- isPackedStruct :: TypeRef -> CInt
- createTypeHandle :: TypeRef -> IO TypeHandleRef
- refineType :: TypeRef -> TypeRef -> IO ()
- resolveTypeHandle :: TypeHandleRef -> IO TypeRef
- disposeTypeHandle :: TypeHandleRef -> IO ()
- data Value
- type ValueRef = Ptr Value
- typeOf :: ValueRef -> IO TypeRef
- getValueName :: ValueRef -> IO CString
- setValueName :: ValueRef -> CString -> IO ()
- dumpValue :: ValueRef -> IO ()
- constNull :: TypeRef -> ValueRef
- constAllOnes :: TypeRef -> ValueRef
- getUndef :: TypeRef -> ValueRef
- isConstant :: ValueRef -> IO CInt
- isNull :: ValueRef -> IO CInt
- isUndef :: ValueRef -> IO CInt
- data Linkage
- fromLinkage :: Linkage -> CUInt
- toLinkage :: CUInt -> Linkage
- getLinkage :: ValueRef -> IO CUInt
- setLinkage :: ValueRef -> CUInt -> IO ()
- data Visibility
- fromVisibility :: Visibility -> CUInt
- toVisibility :: CUInt -> Visibility
- getVisibility :: ValueRef -> IO CUInt
- setVisibility :: ValueRef -> CUInt -> IO ()
- isDeclaration :: ValueRef -> IO CInt
- getSection :: ValueRef -> IO CString
- setSection :: ValueRef -> CString -> IO ()
- getAlignment :: ValueRef -> IO CUInt
- setAlignment :: ValueRef -> CUInt -> IO ()
- addGlobal :: ModuleRef -> TypeRef -> CString -> IO ValueRef
- getNamedGlobal :: ModuleRef -> CString -> IO ValueRef
- deleteGlobal :: ValueRef -> IO ()
- getInitializer :: ValueRef -> IO ValueRef
- setInitializer :: ValueRef -> ValueRef -> IO ()
- isThreadLocal :: ValueRef -> IO CInt
- setThreadLocal :: ValueRef -> CInt -> IO ()
- isGlobalConstant :: ValueRef -> IO CInt
- setGlobalConstant :: ValueRef -> CInt -> IO ()
- getFirstGlobal :: ModuleRef -> IO ValueRef
- getNextGlobal :: ValueRef -> IO ValueRef
- getPreviousGlobal :: ValueRef -> IO ValueRef
- getLastGlobal :: ModuleRef -> IO ValueRef
- getGlobalParent :: ValueRef -> IO ModuleRef
- addFunction :: ModuleRef -> CString -> TypeRef -> IO ValueRef
- getNamedFunction :: ModuleRef -> CString -> IO ValueRef
- deleteFunction :: ValueRef -> IO ()
- countParams :: ValueRef -> CUInt
- getParams :: ValueRef -> Ptr ValueRef -> IO ()
- getParam :: ValueRef -> CUInt -> ValueRef
- getIntrinsicID :: ValueRef -> CUInt
- getGC :: ValueRef -> IO CString
- setGC :: ValueRef -> CString -> IO ()
- getFirstFunction :: ModuleRef -> IO ValueRef
- getNextFunction :: ValueRef -> IO ValueRef
- getPreviousFunction :: ValueRef -> IO ValueRef
- getLastFunction :: ModuleRef -> IO ValueRef
- getFirstParam :: ValueRef -> IO ValueRef
- getNextParam :: ValueRef -> IO ValueRef
- getPreviousParam :: ValueRef -> IO ValueRef
- getLastParam :: ValueRef -> IO ValueRef
- getParamParent :: ValueRef -> IO ValueRef
- isTailCall :: ValueRef -> IO CInt
- setTailCall :: ValueRef -> CInt -> IO ()
- addIncoming :: ValueRef -> Ptr ValueRef -> Ptr ValueRef -> CUInt -> IO ()
- countIncoming :: ValueRef -> IO CUInt
- getIncomingValue :: ValueRef -> CUInt -> IO ValueRef
- getIncomingBlock :: ValueRef -> CUInt -> IO BasicBlockRef
- data CallingConvention
- = C
- | Fast
- | Cold
- | X86StdCall
- | X86FastCall
- fromCallingConvention :: CallingConvention -> CUInt
- toCallingConvention :: CUInt -> CallingConvention
- getFunctionCallConv :: ValueRef -> IO CUInt
- setFunctionCallConv :: ValueRef -> CUInt -> IO ()
- getInstructionCallConv :: ValueRef -> IO CUInt
- setInstructionCallConv :: ValueRef -> CUInt -> IO ()
- constInt :: TypeRef -> CULLong -> CInt -> ValueRef
- constReal :: TypeRef -> CDouble -> ValueRef
- constArray :: TypeRef -> Ptr ValueRef -> CUInt -> ValueRef
- constString :: CString -> CUInt -> CInt -> ValueRef
- constStruct :: Ptr ValueRef -> CUInt -> CInt -> ValueRef
- constVector :: Ptr ValueRef -> CUInt -> ValueRef
- sizeOf :: TypeRef -> IO ValueRef
- constNeg :: ValueRef -> ValueRef
- constNot :: ValueRef -> ValueRef
- constAdd :: ValueRef -> ValueRef -> ValueRef
- constSub :: ValueRef -> ValueRef -> ValueRef
- constMul :: ValueRef -> ValueRef -> ValueRef
- constExactSDiv :: ValueRef -> ValueRef -> IO ValueRef
- constFAdd :: ValueRef -> ValueRef -> ValueRef
- constFMul :: ValueRef -> ValueRef -> ValueRef
- constFNeg :: ValueRef -> ValueRef
- constFPCast :: ValueRef -> TypeRef -> ValueRef
- constFSub :: ValueRef -> ValueRef -> ValueRef
- constUDiv :: ValueRef -> ValueRef -> ValueRef
- constSDiv :: ValueRef -> ValueRef -> ValueRef
- constFDiv :: ValueRef -> ValueRef -> ValueRef
- constURem :: ValueRef -> ValueRef -> ValueRef
- constSRem :: ValueRef -> ValueRef -> ValueRef
- constFRem :: ValueRef -> ValueRef -> ValueRef
- constAnd :: ValueRef -> ValueRef -> ValueRef
- constOr :: ValueRef -> ValueRef -> ValueRef
- constXor :: ValueRef -> ValueRef -> ValueRef
- constICmp :: CInt -> ValueRef -> ValueRef -> ValueRef
- constFCmp :: CInt -> ValueRef -> ValueRef -> ValueRef
- constShl :: ValueRef -> ValueRef -> ValueRef
- constLShr :: ValueRef -> ValueRef -> ValueRef
- constAShr :: ValueRef -> ValueRef -> ValueRef
- constGEP :: ValueRef -> Ptr ValueRef -> CUInt -> ValueRef
- constTrunc :: ValueRef -> TypeRef -> ValueRef
- constSExt :: ValueRef -> TypeRef -> ValueRef
- constZExt :: ValueRef -> TypeRef -> ValueRef
- constFPTrunc :: ValueRef -> TypeRef -> ValueRef
- constFPExt :: ValueRef -> TypeRef -> ValueRef
- constUIToFP :: ValueRef -> TypeRef -> ValueRef
- constSIToFP :: ValueRef -> TypeRef -> ValueRef
- constFPToUI :: ValueRef -> TypeRef -> ValueRef
- constFPToSI :: ValueRef -> TypeRef -> ValueRef
- constPtrToInt :: ValueRef -> TypeRef -> ValueRef
- constIntToPtr :: ValueRef -> TypeRef -> ValueRef
- constBitCast :: ValueRef -> TypeRef -> ValueRef
- constSelect :: ValueRef -> ValueRef -> ValueRef -> ValueRef
- constExtractElement :: ValueRef -> ValueRef -> ValueRef
- constInsertElement :: ValueRef -> ValueRef -> ValueRef -> ValueRef
- constShuffleVector :: ValueRef -> ValueRef -> ValueRef -> ValueRef
- constExtractValue :: ValueRef -> Ptr ValueRef -> CUInt -> ValueRef
- constInsertValue :: ValueRef -> ValueRef -> Ptr ValueRef -> CUInt -> ValueRef
- constRealOfString :: TypeRef -> CString -> IO ValueRef
- type BasicBlock = Value
- type BasicBlockRef = Ptr BasicBlock
- basicBlockAsValue :: BasicBlockRef -> ValueRef
- valueIsBasicBlock :: ValueRef -> Bool
- valueAsBasicBlock :: ValueRef -> BasicBlockRef
- countBasicBlocks :: ValueRef -> IO CUInt
- getBasicBlocks :: ValueRef -> Ptr BasicBlockRef -> IO ()
- getEntryBasicBlock :: ValueRef -> IO BasicBlockRef
- appendBasicBlock :: ValueRef -> CString -> IO BasicBlockRef
- insertBasicBlock :: BasicBlockRef -> CString -> IO BasicBlockRef
- deleteBasicBlock :: BasicBlockRef -> IO ()
- getFirstBasicBlock :: ValueRef -> IO BasicBlockRef
- getNextBasicBlock :: BasicBlockRef -> IO BasicBlockRef
- getPreviousBasicBlock :: BasicBlockRef -> IO BasicBlockRef
- getLastBasicBlock :: ValueRef -> IO BasicBlockRef
- getInsertBlock :: BuilderRef -> IO BasicBlockRef
- getBasicBlockParent :: BasicBlockRef -> IO ValueRef
- data Builder
- type BuilderRef = Ptr Builder
- createBuilder :: IO BuilderRef
- ptrDisposeBuilder :: FunPtr (BuilderRef -> IO ())
- positionBuilder :: BuilderRef -> BasicBlockRef -> ValueRef -> IO ()
- positionBefore :: BuilderRef -> ValueRef -> IO ()
- positionAtEnd :: BuilderRef -> BasicBlockRef -> IO ()
- getFirstInstruction :: BasicBlockRef -> IO ValueRef
- getNextInstruction :: ValueRef -> IO ValueRef
- getPreviousInstruction :: ValueRef -> IO ValueRef
- getLastInstruction :: BasicBlockRef -> IO ValueRef
- getInstructionParent :: ValueRef -> IO BasicBlockRef
- buildRetVoid :: BuilderRef -> IO ValueRef
- buildRet :: BuilderRef -> ValueRef -> IO ValueRef
- buildBr :: BuilderRef -> BasicBlockRef -> IO ValueRef
- buildCondBr :: BuilderRef -> ValueRef -> BasicBlockRef -> BasicBlockRef -> IO ValueRef
- buildSwitch :: BuilderRef -> ValueRef -> BasicBlockRef -> CUInt -> IO ValueRef
- buildInvoke :: BuilderRef -> ValueRef -> Ptr ValueRef -> CUInt -> BasicBlockRef -> BasicBlockRef -> CString -> IO ValueRef
- buildUnwind :: BuilderRef -> IO ValueRef
- buildUnreachable :: BuilderRef -> IO ValueRef
- buildAdd :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildSub :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildMul :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildFAdd :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildFMul :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildFPCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildFSub :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildUDiv :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildSDiv :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildExactSDiv :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildFDiv :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildURem :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildSRem :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildFRem :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildShl :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildLShr :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildAShr :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildAnd :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildOr :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildXor :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildNeg :: BuilderRef -> ValueRef -> CString -> IO ValueRef
- buildNot :: BuilderRef -> ValueRef -> CString -> IO ValueRef
- buildMalloc :: BuilderRef -> TypeRef -> CString -> IO ValueRef
- buildArrayMalloc :: BuilderRef -> TypeRef -> ValueRef -> CString -> IO ValueRef
- buildAlloca :: BuilderRef -> TypeRef -> CString -> IO ValueRef
- buildArrayAlloca :: BuilderRef -> TypeRef -> ValueRef -> CString -> IO ValueRef
- buildFree :: BuilderRef -> ValueRef -> IO ValueRef
- buildLoad :: BuilderRef -> ValueRef -> CString -> IO ValueRef
- buildStore :: BuilderRef -> ValueRef -> ValueRef -> IO ValueRef
- buildGEP :: BuilderRef -> ValueRef -> Ptr ValueRef -> CUInt -> CString -> IO ValueRef
- buildTrunc :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildZExt :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildSExt :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildFPToUI :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildFPToSI :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildUIToFP :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildSIToFP :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildFPTrunc :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildFPExt :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildPtrToInt :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildIntToPtr :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildBitCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildPointerCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildTruncOrBitCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildZExtOrBitCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildSExtOrBitCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildPtrDiff :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildAggregateRet :: BuilderRef -> Ptr ValueRef -> CUInt -> IO ValueRef
- buildGlobalString :: BuilderRef -> CString -> CString -> IO ValueRef
- buildGlobalStringPtr :: BuilderRef -> CString -> CString -> IO ValueRef
- buildInBoundsGEP :: BuilderRef -> ValueRef -> Ptr ValueRef -> CUInt -> CString -> IO ValueRef
- buildIntCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildIsNotNull :: BuilderRef -> ValueRef -> CString -> IO ValueRef
- buildIsNull :: BuilderRef -> ValueRef -> CString -> IO ValueRef
- buildNSWAdd :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildStructGEP :: BuilderRef -> ValueRef -> CUInt -> CString -> IO ValueRef
- buildICmp :: BuilderRef -> CInt -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildFCmp :: BuilderRef -> CInt -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildPhi :: BuilderRef -> TypeRef -> CString -> IO ValueRef
- buildCall :: BuilderRef -> ValueRef -> Ptr ValueRef -> CUInt -> CString -> IO ValueRef
- buildSelect :: BuilderRef -> ValueRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildVAArg :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRef
- buildExtractElement :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildInsertElement :: BuilderRef -> ValueRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildShuffleVector :: BuilderRef -> ValueRef -> ValueRef -> ValueRef -> CString -> IO ValueRef
- buildExtractValue :: BuilderRef -> ValueRef -> CUInt -> CString -> IO ValueRef
- buildInsertValue :: BuilderRef -> ValueRef -> ValueRef -> CUInt -> CString -> IO ValueRef
- addCase :: ValueRef -> ValueRef -> BasicBlockRef -> IO ()
- data MemoryBuffer
- type MemoryBufferRef = Ptr MemoryBuffer
- createMemoryBufferWithContentsOfFile :: CString -> Ptr MemoryBufferRef -> Ptr CString -> IO CInt
- createMemoryBufferWithSTDIN :: Ptr MemoryBufferRef -> Ptr CString -> IO CInt
- disposeMemoryBuffer :: MemoryBufferRef -> IO ()
- disposeMessage :: CString -> IO ()
- addAttribute :: ValueRef -> CAttribute -> IO ()
- setInstrParamAlignment :: ValueRef -> CUInt -> CUInt -> IO ()
- setParamAlignment :: ValueRef -> CUInt -> IO ()
- data Attribute
- fromAttribute :: Attribute -> CAttribute
- toAttribute :: CAttribute -> Attribute
- addInstrAttribute :: ValueRef -> CUInt -> CAttribute -> IO ()
- removeFunctionAttr :: ValueRef -> CAttribute -> IO ()
- removeAttribute :: ValueRef -> CAttribute -> IO ()
- removeInstrAttribute :: ValueRef -> CUInt -> CAttribute -> IO ()
- addFunctionAttr :: ValueRef -> CAttribute -> IO ()
- data PassManager
- type PassManagerRef = Ptr PassManager
- createFunctionPassManager :: ModuleProviderRef -> IO PassManagerRef
- createPassManager :: IO PassManagerRef
- ptrDisposePassManager :: FunPtr (PassManagerRef -> IO ())
- finalizeFunctionPassManager :: PassManagerRef -> IO CInt
- initializeFunctionPassManager :: PassManagerRef -> IO CInt
- runFunctionPassManager :: PassManagerRef -> ValueRef -> IO CInt
- runPassManager :: PassManagerRef -> ModuleRef -> IO CInt
- data Context
- type ContextRef = Ptr Context
- dumpModule :: ModuleRef -> IO ()
- alignOf :: TypeRef -> IO ValueRef
- constInBoundsGEP :: ValueRef -> Ptr ValueRef -> CUInt -> IO ValueRef
- constIntCast :: ValueRef -> TypeRef -> CUInt -> IO ValueRef
- constIntOfString :: TypeRef -> CString -> CUInt -> IO ValueRef
- constIntOfStringAndSize :: TypeRef -> CString -> CUInt -> CUInt -> IO ValueRef
- constNSWAdd :: ValueRef -> ValueRef -> IO ValueRef
- constPointerCast :: ValueRef -> TypeRef -> IO ValueRef
- constPointerNull :: TypeRef -> IO ValueRef
- constRealOfStringAndSize :: TypeRef -> CString -> CUInt -> IO ValueRef
- constSExtOrBitCast :: ValueRef -> TypeRef -> IO ValueRef
- getTypeByName :: ModuleRef -> CString -> IO TypeRef
- insertIntoBuilderWithName :: BuilderRef -> ValueRef -> CString -> IO ()
- moduleCreateWithNameInContext :: CString -> ContextRef -> IO ModuleRef
- appendBasicBlockInContext :: ContextRef -> ValueRef -> CString -> IO BasicBlockRef
- insertBasicBlockInContext :: ContextRef -> BasicBlockRef -> CString -> IO BasicBlockRef
- createBuilderInContext :: ContextRef -> IO BuilderRef
- contextDispose :: ContextRef -> IO ()
- constStringInContext :: ContextRef -> CString -> CUInt -> CInt -> IO ValueRef
- constStructInContext :: ContextRef -> Ptr ValueRef -> CUInt -> CInt -> IO ValueRef
- constTruncOrBitCast :: ValueRef -> TypeRef -> IO ValueRef
- constZExtOrBitCast :: ValueRef -> TypeRef -> IO ValueRef
- doubleTypeInContext :: ContextRef -> IO TypeRef
- fP128TypeInContext :: ContextRef -> IO TypeRef
- floatTypeInContext :: ContextRef -> IO TypeRef
- int16TypeInContext :: ContextRef -> IO TypeRef
- int1TypeInContext :: ContextRef -> IO TypeRef
- int32TypeInContext :: ContextRef -> IO TypeRef
- int64TypeInContext :: ContextRef -> IO TypeRef
- int8TypeInContext :: ContextRef -> IO TypeRef
- intTypeInContext :: ContextRef -> CUInt -> IO TypeRef
- labelTypeInContext :: ContextRef -> IO TypeRef
- opaqueTypeInContext :: ContextRef -> IO TypeRef
- pPCFP128TypeInContext :: ContextRef -> IO TypeRef
- structTypeInContext :: ContextRef -> Ptr TypeRef -> CUInt -> CInt -> IO TypeRef
- voidTypeInContext :: ContextRef -> IO TypeRef
- x86FP80TypeInContext :: ContextRef -> IO TypeRef
- getTypeContext :: TypeRef -> IO ContextRef
Modules
disposeModule :: ModuleRef -> IO ()Source
Module providers
Types
getTypeKind :: TypeRef -> IO TypeKindSource
Integer types
getIntTypeWidth :: TypeRef -> IO CUIntSource
Real types
Function types
:: TypeRef | return type |
-> Ptr TypeRef | array of argument types |
-> CUInt | number of elements in array |
-> CInt | non-zero if function is varargs |
-> TypeRef |
Create a function type.
isFunctionVarArg :: TypeRef -> IO CIntSource
Indicate whether a function takes varargs.
getReturnType :: TypeRef -> IO TypeRefSource
Give a function's return type.
countParamTypes :: TypeRef -> IO CUIntSource
Give the number of fixed parameters that a function takes.
getParamTypes :: TypeRef -> Ptr TypeRef -> IO ()Source
Fill out an array with the types of a function's fixed parameters.
Other types
Array, pointer, and vector types
getElementType :: TypeRef -> IO TypeRefSource
Get the type of a sequential type's elements.
getArrayLength :: TypeRef -> IO CUIntSource
getVectorSize :: TypeRef -> IO CUIntSource
Struct types
isPackedStruct :: TypeRef -> CIntSource
Type handles
createTypeHandle :: TypeRef -> IO TypeHandleRefSource
resolveTypeHandle :: TypeHandleRef -> IO TypeRefSource
disposeTypeHandle :: TypeHandleRef -> IO ()Source
Values
getValueName :: ValueRef -> IO CStringSource
Constants
isConstant :: ValueRef -> IO CIntSource
Global variables, functions, and aliases (globals)
An enumeration for the kinds of linkage for global values.
ExternalLinkage | Externally visible function |
AvailableExternallyLinkage | |
LinkOnceAnyLinkage | Keep one copy of function when linking (inline) |
LinkOnceODRLinkage | Same, but only replaced by something equivalent. |
WeakAnyLinkage | Keep one copy of named function when linking (weak) |
WeakODRLinkage | Same, but only replaced by something equivalent. |
AppendingLinkage | Special purpose, only applies to global arrays |
InternalLinkage | Rename collisions when linking (static functions) |
PrivateLinkage | Like Internal, but omit from symbol table |
DLLImportLinkage | Function to be imported from DLL |
DLLExportLinkage | Function to be accessible from DLL |
ExternalWeakLinkage | ExternalWeak linkage description |
GhostLinkage | Stand-in functions for streaming fns from BC files |
CommonLinkage | Tentative definitions |
LinkerPrivateLinkage | Like Private, but linker removes. |
fromLinkage :: Linkage -> CUIntSource
getLinkage :: ValueRef -> IO CUIntSource
data Visibility Source
An enumeration for the kinds of visibility of global values.
DefaultVisibility | The GV is visible |
HiddenVisibility | The GV is hidden |
ProtectedVisibility | The GV is protected |
getVisibility :: ValueRef -> IO CUIntSource
isDeclaration :: ValueRef -> IO CIntSource
getSection :: ValueRef -> IO CStringSource
getAlignment :: ValueRef -> IO CUIntSource
Global variables
deleteGlobal :: ValueRef -> IO ()Source
isThreadLocal :: ValueRef -> IO CIntSource
isGlobalConstant :: ValueRef -> IO CIntSource
Functions
getNextParam :: ValueRef -> IO ValueRefSource
getLastParam :: ValueRef -> IO ValueRefSource
isTailCall :: ValueRef -> IO CIntSource
Phi nodes
countIncoming :: ValueRef -> IO CUIntSource
getIncomingBlock :: ValueRef -> CUInt -> IO BasicBlockRefSource
Calling conventions
data CallingConvention Source
Constants
Scalar constants
Composite constants
Constant expressions
constFPCast :: ValueRef -> TypeRef -> ValueRefSource
constTrunc :: ValueRef -> TypeRef -> ValueRefSource
constFPTrunc :: ValueRef -> TypeRef -> ValueRefSource
constFPExt :: ValueRef -> TypeRef -> ValueRefSource
constUIToFP :: ValueRef -> TypeRef -> ValueRefSource
constSIToFP :: ValueRef -> TypeRef -> ValueRefSource
constFPToUI :: ValueRef -> TypeRef -> ValueRefSource
constFPToSI :: ValueRef -> TypeRef -> ValueRefSource
constPtrToInt :: ValueRef -> TypeRef -> ValueRefSource
constIntToPtr :: ValueRef -> TypeRef -> ValueRefSource
constBitCast :: ValueRef -> TypeRef -> ValueRefSource
Basic blocks
type BasicBlock = ValueSource
type BasicBlockRef = Ptr BasicBlockSource
:: ValueRef | basic block |
-> BasicBlockRef |
:: ValueRef | function |
-> Ptr BasicBlockRef | array to fill out |
-> IO () |
:: ValueRef | function |
-> IO BasicBlockRef |
:: ValueRef | function |
-> CString | name for label |
-> IO BasicBlockRef |
:: BasicBlockRef | insert before this one |
-> CString | name for label |
-> IO BasicBlockRef |
Instruction building
type BuilderRef = Ptr BuilderSource
ptrDisposeBuilder :: FunPtr (BuilderRef -> IO ())Source
positionBuilder :: BuilderRef -> BasicBlockRef -> ValueRef -> IO ()Source
positionBefore :: BuilderRef -> ValueRef -> IO ()Source
positionAtEnd :: BuilderRef -> BasicBlockRef -> IO ()Source
Terminators
buildBr :: BuilderRef -> BasicBlockRef -> IO ValueRefSource
buildCondBr :: BuilderRef -> ValueRef -> BasicBlockRef -> BasicBlockRef -> IO ValueRefSource
buildSwitch :: BuilderRef -> ValueRef -> BasicBlockRef -> CUInt -> IO ValueRefSource
buildInvoke :: BuilderRef -> ValueRef -> Ptr ValueRef -> CUInt -> BasicBlockRef -> BasicBlockRef -> CString -> IO ValueRefSource
Arithmetic
buildFPCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildExactSDiv :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRefSource
Memory
buildMalloc :: BuilderRef -> TypeRef -> CString -> IO ValueRefSource
buildArrayMalloc :: BuilderRef -> TypeRef -> ValueRef -> CString -> IO ValueRefSource
buildAlloca :: BuilderRef -> TypeRef -> CString -> IO ValueRefSource
buildArrayAlloca :: BuilderRef -> TypeRef -> ValueRef -> CString -> IO ValueRefSource
buildStore :: BuilderRef -> ValueRef -> ValueRef -> IO ValueRefSource
Casts
buildTrunc :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildFPToUI :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildFPToSI :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildUIToFP :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildSIToFP :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildFPTrunc :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildFPExt :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildPtrToInt :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildIntToPtr :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildBitCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildPointerCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildTruncOrBitCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildZExtOrBitCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildSExtOrBitCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildPtrDiff :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRefSource
Misc
buildAggregateRet :: BuilderRef -> Ptr ValueRef -> CUInt -> IO ValueRefSource
buildGlobalString :: BuilderRef -> CString -> CString -> IO ValueRefSource
buildGlobalStringPtr :: BuilderRef -> CString -> CString -> IO ValueRefSource
buildInBoundsGEP :: BuilderRef -> ValueRef -> Ptr ValueRef -> CUInt -> CString -> IO ValueRefSource
buildIntCast :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildIsNotNull :: BuilderRef -> ValueRef -> CString -> IO ValueRefSource
buildIsNull :: BuilderRef -> ValueRef -> CString -> IO ValueRefSource
buildNSWAdd :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRefSource
buildStructGEP :: BuilderRef -> ValueRef -> CUInt -> CString -> IO ValueRefSource
Comparisons
Miscellaneous instructions
buildSelect :: BuilderRef -> ValueRef -> ValueRef -> ValueRef -> CString -> IO ValueRefSource
buildVAArg :: BuilderRef -> ValueRef -> TypeRef -> CString -> IO ValueRefSource
buildExtractElement :: BuilderRef -> ValueRef -> ValueRef -> CString -> IO ValueRefSource
buildInsertElement :: BuilderRef -> ValueRef -> ValueRef -> ValueRef -> CString -> IO ValueRefSource
buildShuffleVector :: BuilderRef -> ValueRef -> ValueRef -> ValueRef -> CString -> IO ValueRefSource
buildExtractValue :: BuilderRef -> ValueRef -> CUInt -> CString -> IO ValueRefSource
buildInsertValue :: BuilderRef -> ValueRef -> ValueRef -> CUInt -> CString -> IO ValueRefSource
Other helpers
Memory buffers
type MemoryBufferRef = Ptr MemoryBufferSource
createMemoryBufferWithContentsOfFile :: CString -> Ptr MemoryBufferRef -> Ptr CString -> IO CIntSource
Error handling
disposeMessage :: CString -> IO ()Source
Parameter passing
addAttribute :: ValueRef -> CAttribute -> IO ()Source
fromAttribute :: Attribute -> CAttributeSource
toAttribute :: CAttribute -> AttributeSource
removeFunctionAttr :: ValueRef -> CAttribute -> IO ()Source
removeAttribute :: ValueRef -> CAttribute -> IO ()Source
addFunctionAttr :: ValueRef -> CAttribute -> IO ()Source
Pass manager
type PassManagerRef = Ptr PassManagerSource
runPassManager :: PassManagerRef -> ModuleRef -> IO CIntSource
Context functions
type ContextRef = Ptr ContextSource
Debug
dumpModule :: ModuleRef -> IO ()Source
Misc
insertIntoBuilderWithName :: BuilderRef -> ValueRef -> CString -> IO ()Source
Context functions
contextDispose :: ContextRef -> IO ()Source
constStringInContext :: ContextRef -> CString -> CUInt -> CInt -> IO ValueRefSource
constStructInContext :: ContextRef -> Ptr ValueRef -> CUInt -> CInt -> IO ValueRefSource
intTypeInContext :: ContextRef -> CUInt -> IO TypeRefSource
structTypeInContext :: ContextRef -> Ptr TypeRef -> CUInt -> CInt -> IO TypeRefSource