| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
LLVM.Internal.OrcJIT
Synopsis
- newtype MangledSymbol = MangledSymbol ByteString
- newtype ExecutionSession = ExecutionSession (Ptr ExecutionSession)
- data JITSymbolFlags = JITSymbolFlags {
- jitSymbolWeak :: !Bool
- jitSymbolCommon :: !Bool
- jitSymbolAbsolute :: !Bool
- jitSymbolExported :: !Bool
- defaultJITSymbolFlags :: JITSymbolFlags
- data JITSymbol = JITSymbol {}
- data JITSymbolError = JITSymbolError ShortByteString
- newtype SymbolResolver = SymbolResolver (MangledSymbol -> IO (Either JITSymbolError JITSymbol))
- withSymbolResolver :: ExecutionSession -> SymbolResolver -> (Ptr SymbolResolver -> IO a) -> IO a
- allocWithCleanup :: IORef [IO ()] -> IO a -> (a -> IO ()) -> IO a
- allocFunPtr :: IORef [IO ()] -> IO (FunPtr a) -> IO (FunPtr a)
- createRegisteredDataLayout :: MonadAnyCont IO m => TargetMachine -> IORef [IO ()] -> m (Ptr DataLayout)
- createExecutionSession :: IO ExecutionSession
- disposeExecutionSession :: ExecutionSession -> IO ()
- withExecutionSession :: (ExecutionSession -> IO a) -> IO a
- allocateModuleKey :: ExecutionSession -> IO ModuleKey
- releaseModuleKey :: ExecutionSession -> ModuleKey -> IO ()
- withModuleKey :: ExecutionSession -> (ModuleKey -> IO a) -> IO a
Documentation
newtype MangledSymbol Source #
A mangled symbol which can be used in findSymbol. This can be
created using mangleSymbol.
Constructors
| MangledSymbol ByteString |
Instances
newtype ExecutionSession Source #
Constructors
| ExecutionSession (Ptr ExecutionSession) |
data JITSymbolFlags Source #
Contrary to the C++ interface, we do not store the HasError flag here. Instead decoding a JITSymbol produces a sumtype based on whether that flag is set or not.
Constructors
| JITSymbolFlags | |
Fields
| |
Instances
Constructors
| JITSymbol | |
Fields
| |
Instances
| Eq JITSymbol Source # | |
| Ord JITSymbol Source # | |
| Show JITSymbol Source # | |
| (MonadIO m, MonadAnyCont IO m) => DecodeM m (Either JITSymbolError JITSymbol) (Ptr JITSymbol) Source # | |
Defined in LLVM.Internal.OrcJIT Methods decodeM :: Ptr JITSymbol0 -> m (Either JITSymbolError JITSymbol) Source # | |
| MonadIO m => EncodeM m (MangledSymbol -> IO (Either JITSymbolError JITSymbol)) (FunPtr SymbolResolverFn) Source # | |
Defined in LLVM.Internal.OrcJIT Methods encodeM :: (MangledSymbol -> IO (Either JITSymbolError JITSymbol)) -> m (FunPtr SymbolResolverFn) Source # | |
| MonadIO m => EncodeM m (Either JITSymbolError JITSymbol) (Ptr JITSymbol -> IO ()) Source # | |
Defined in LLVM.Internal.OrcJIT Methods encodeM :: Either JITSymbolError JITSymbol -> m (Ptr JITSymbol0 -> IO ()) Source # | |
data JITSymbolError Source #
Constructors
| JITSymbolError ShortByteString |
Instances
newtype SymbolResolver Source #
Specifies how external symbols in a module added to a
CompileLayer should be resolved.
Constructors
| SymbolResolver (MangledSymbol -> IO (Either JITSymbolError JITSymbol)) |
Instances
| MonadIO m => EncodeM m SymbolResolver (IORef [IO ()] -> Ptr ExecutionSession -> IO (Ptr SymbolResolver)) Source # | |
Defined in LLVM.Internal.OrcJIT Methods encodeM :: SymbolResolver -> m (IORef [IO ()] -> Ptr ExecutionSession -> IO (Ptr SymbolResolver0)) Source # | |
withSymbolResolver :: ExecutionSession -> SymbolResolver -> (Ptr SymbolResolver -> IO a) -> IO a Source #
Create a SymbolResolver that can be used with the JIT.
allocWithCleanup :: IORef [IO ()] -> IO a -> (a -> IO ()) -> IO a Source #
Allocate the resource and register it for cleanup.
allocFunPtr :: IORef [IO ()] -> IO (FunPtr a) -> IO (FunPtr a) Source #
Allocate a function pointer and register it for cleanup.
createRegisteredDataLayout :: MonadAnyCont IO m => TargetMachine -> IORef [IO ()] -> m (Ptr DataLayout) Source #
createExecutionSession :: IO ExecutionSession Source #
Create a new ExecutionSession.
disposeExecutionSession :: ExecutionSession -> IO () Source #
Dispose of an ExecutionSession. This should be called when the
ExecutionSession is not needed anymore.
withExecutionSession :: (ExecutionSession -> IO a) -> IO a Source #
bracket-style wrapper around createExecutionSession and
disposeExecutionSession.
allocateModuleKey :: ExecutionSession -> IO ModuleKey Source #
Allocate a module key for a new module to add to the JIT.
releaseModuleKey :: ExecutionSession -> ModuleKey -> IO () Source #
Return a module key to the ExecutionSession so that it can be
re-used.
withModuleKey :: ExecutionSession -> (ModuleKey -> IO a) -> IO a Source #
bracket-style wrapper around allocateModuleKey and
releaseModuleKey.