Safe Haskell | Safe |
---|
- linkInInterpreter :: IO ()
- linkInMCJIT :: IO ()
- data GenericValue
- type GenericValueRef = Ptr GenericValue
- createGenericValueOfInt :: TypeRef -> CULLong -> Bool -> IO GenericValueRef
- createGenericValueOfPointer :: Ptr a -> IO GenericValueRef
- createGenericValueOfFloat :: TypeRef -> CDouble -> IO GenericValueRef
- genericValueIntWidth :: GenericValueRef -> IO CUInt
- genericValueToInt :: GenericValueRef -> Bool -> IO CULLong
- genericValueToPointer :: GenericValueRef -> IO (Ptr a)
- genericValueToFloat :: TypeRef -> GenericValueRef -> IO CDouble
- ptrDisposeGenericValue :: FunPtr (GenericValueRef -> IO ())
- data ExecutionEngine
- type ExecutionEngineRef = Ptr ExecutionEngine
- data EngineKind
- = JIT
- | Interpreter
- type EngineKindSet = T CUInt EngineKind
- kindJIT :: EngineKindSet
- kindInterpreter :: EngineKindSet
- kindEither :: EngineKindSet
- createExecutionEngineKindForModuleCPU :: Ptr ExecutionEngineRef -> EngineKindSet -> ModuleRef -> Ptr CString -> IO Bool
- createExecutionEngineForModule :: Ptr ExecutionEngineRef -> ModuleRef -> Ptr CString -> IO Bool
- createExecutionEngineForModuleCPU :: Ptr ExecutionEngineRef -> ModuleRef -> Ptr CString -> IO Bool
- createInterpreterForModule :: Ptr ExecutionEngineRef -> ModuleRef -> Ptr CString -> IO Bool
- createInterpreterForModuleCPU :: Ptr ExecutionEngineRef -> ModuleRef -> Ptr CString -> IO Bool
- createJITCompilerForModule :: Ptr ExecutionEngineRef -> ModuleRef -> CUInt -> Ptr CString -> IO Bool
- createMCJITCompilerForModule :: Ptr ExecutionEngineRef -> ModuleRef -> MCJITCompilerOptionsRef -> CSize -> Ptr CString -> IO Bool
- initializeMCJITCompilerOptions :: MCJITCompilerOptionsRef -> CSize -> IO ()
- ptrDisposeExecutionEngine :: FunPtr (ExecutionEngineRef -> IO ())
- disposeExecutionEngine :: ExecutionEngineRef -> IO ()
- runStaticConstructors :: ExecutionEngineRef -> IO ()
- runStaticDestructors :: ExecutionEngineRef -> IO ()
- runFunctionAsMain :: ExecutionEngineRef -> ValueRef -> CUInt -> Ptr CString -> Ptr CString -> IO CInt
- freeMachineCodeForFunction :: ExecutionEngineRef -> ValueRef -> IO ()
- addModule :: ExecutionEngineRef -> ModuleRef -> IO ()
- removeModule :: ExecutionEngineRef -> ModuleRef -> Ptr ModuleRef -> Ptr CString -> IO Bool
- findFunction :: ExecutionEngineRef -> CString -> Ptr ValueRef -> IO Bool
- recompileAndRelinkFunction :: ExecutionEngineRef -> ValueRef -> IO (FunPtr a)
- runFunction :: ExecutionEngineRef -> ValueRef -> CUInt -> Ptr GenericValueRef -> IO GenericValueRef
- getExecutionEngineTargetData :: ExecutionEngineRef -> IO TargetDataRef
- addGlobalMapping :: ExecutionEngineRef -> ValueRef -> Ptr a -> IO ()
- addFunctionMapping :: ExecutionEngineRef -> ValueRef -> FunPtr a -> IO ()
- getPointerToGlobal :: ExecutionEngineRef -> ValueRef -> IO (Ptr a)
- getPointerToFunction :: ExecutionEngineRef -> ValueRef -> IO (FunPtr a)
Linking
Generic values
type GenericValueRef = Ptr GenericValueSource
createGenericValueOfInt :: TypeRef -> CULLong -> Bool -> IO GenericValueRefSource
createGenericValueOfFloat :: TypeRef -> CDouble -> IO GenericValueRefSource
genericValueIntWidth :: GenericValueRef -> IO CUIntSource
genericValueToInt :: GenericValueRef -> Bool -> IO CULLongSource
genericValueToPointer :: GenericValueRef -> IO (Ptr a)Source
genericValueToFloat :: TypeRef -> GenericValueRef -> IO CDoubleSource
Execution engines
data EngineKind Source
type EngineKindSet = T CUInt EngineKindSource
createExecutionEngineKindForModuleCPU :: Ptr ExecutionEngineRef -> EngineKindSet -> ModuleRef -> Ptr CString -> IO BoolSource
createExecutionEngineForModule :: Ptr ExecutionEngineRef -> ModuleRef -> Ptr CString -> IO BoolSource
createExecutionEngineForModuleCPU :: Ptr ExecutionEngineRef -> ModuleRef -> Ptr CString -> IO BoolSource
createInterpreterForModuleCPU :: Ptr ExecutionEngineRef -> ModuleRef -> Ptr CString -> IO BoolSource
createJITCompilerForModule :: Ptr ExecutionEngineRef -> ModuleRef -> CUInt -> Ptr CString -> IO BoolSource
createMCJITCompilerForModule :: Ptr ExecutionEngineRef -> ModuleRef -> MCJITCompilerOptionsRef -> CSize -> Ptr CString -> IO BoolSource
initializeMCJITCompilerOptions :: MCJITCompilerOptionsRef -> CSize -> IO ()Source
removeModule :: ExecutionEngineRef -> ModuleRef -> Ptr ModuleRef -> Ptr CString -> IO BoolSource
findFunction :: ExecutionEngineRef -> CString -> Ptr ValueRef -> IO BoolSource
recompileAndRelinkFunction :: ExecutionEngineRef -> ValueRef -> IO (FunPtr a)Source
runFunction :: ExecutionEngineRef -> ValueRef -> CUInt -> Ptr GenericValueRef -> IO GenericValueRefSource
addGlobalMapping :: ExecutionEngineRef -> ValueRef -> Ptr a -> IO ()Source
disfunctional in LLVM-3.6, see https://llvm.org/bugs/show_bug.cgi?id=20656
addFunctionMapping :: ExecutionEngineRef -> ValueRef -> FunPtr a -> IO ()Source
getPointerToGlobal :: ExecutionEngineRef -> ValueRef -> IO (Ptr a)Source
getPointerToFunction :: ExecutionEngineRef -> ValueRef -> IO (FunPtr a)Source