Safe Haskell | None |
---|
An ExecutionEngine
is JIT compiler that is used to generate code for an LLVM module.
- data EngineAccess a
- data ExecutionEngine
- getEngine :: EngineAccess ExecutionEngine
- runEngineAccess :: EngineAccess a -> IO a
- runEngineAccessWithModule :: Module -> EngineAccess a -> IO a
- addModule :: Module -> EngineAccess ()
- class ExecutionFunction f
- getExecutionFunction :: ExecutionFunction f => (FunPtr f -> f) -> Function f -> EngineAccess f
- getPointerToFunction :: Function f -> EngineAccess (FunPtr f)
- addFunctionValue :: Function f -> FunPtr f -> EngineAccess ()
- addGlobalMappings :: GlobalMappings -> EngineAccess ()
- class Translatable f
- class Generic a
- generateFunction :: Translatable f => Function f -> EngineAccess f
- class Unsafe a where
- unsafeRemoveIO :: a -> RemoveIO a
- simpleFunction :: Translatable f => CodeGenModule (Function f) -> IO f
- unsafeGenerateFunction :: (Unsafe t, Translatable t) => CodeGenModule (Function t) -> RemoveIO t
- data TargetData = TargetData {
- abiAlignmentOfType :: Type -> Int
- abiSizeOfType :: Type -> Int
- littleEndian :: Bool
- callFrameAlignmentOfType :: Type -> Int
- intPtrType :: Type
- pointerSize :: Int
- preferredAlignmentOfType :: Type -> Int
- sizeOfTypeInBits :: Type -> Int
- storeSizeOfType :: Type -> Int
- getTargetData :: IO TargetData
- targetDataFromString :: String -> TargetData
- withIntPtrType :: (forall n. Positive n => WordN n -> a) -> a
Execution engine
data EngineAccess a Source
data ExecutionEngine Source
runEngineAccess :: EngineAccess a -> IO aSource
The LLVM execution engine is encapsulated so it cannot be accessed directly. The reason is that (currently) there must only ever be one engine, so access to it is wrapped in a monad.
runEngineAccessWithModule :: Module -> EngineAccess a -> IO aSource
addModule :: Module -> EngineAccess ()Source
class ExecutionFunction f Source
ExecutionFunction (IO a) | |
ExecutionFunction f => ExecutionFunction (a -> f) |
getExecutionFunction :: ExecutionFunction f => (FunPtr f -> f) -> Function f -> EngineAccess fSource
getPointerToFunction :: Function f -> EngineAccess (FunPtr f)Source
In contrast to generateFunction
this compiles a function once.
Thus it is faster for many calls to the same function.
See examples/Vector.hs
.
If the function calls back into Haskell code,
you also have to set the function addresses
using addFunctionValue
or addGlobalMappings
.
You must keep the execution engine alive
as long as you want to call the function.
Better use getExecutionFunction
which handles this for you.
addFunctionValue :: Function f -> FunPtr f -> EngineAccess ()Source
Tell LLVM the address of an external function
if it cannot resolve a name automatically.
Alternatively you may declare the function
with staticFunction
instead of externFunction
.
addGlobalMappings :: GlobalMappings -> EngineAccess ()Source
Pass a list of global mappings to LLVM
that can be obtained from getGlobalMappings
.
Translation
class Translatable f Source
Class of LLVM function types that can be translated to the corresponding Haskell type.
Generic a => Translatable (IO a) | |
(Generic a, Translatable b) => Translatable (a -> b) |
generateFunction :: Translatable f => Function f -> EngineAccess fSource
Generate a Haskell function from an LLVM function.
Note that the function is compiled for every call (Just-In-Time compilation).
If you want to compile the function once and call it a lot of times
then you should better use getPointerToFunction
.
Unsafe type conversion
:: a | |
-> RemoveIO a | Remove the IO from a function return type. This is unsafe in general. |
Simplified interface.
simpleFunction :: Translatable f => CodeGenModule (Function f) -> IO fSource
Translate a function to Haskell code. This is a simplified interface to
the execution engine and module mechanism.
It is based on generateFunction
, so see there for limitations.
unsafeGenerateFunction :: (Unsafe t, Translatable t) => CodeGenModule (Function t) -> RemoveIO tSource
Combine simpleFunction
and unsafeRemoveIO
.
Target information
data TargetData Source
TargetData | |
|
withIntPtrType :: (forall n. Positive n => WordN n -> a) -> aSource