An ExecutionEngine
is JIT compiler that is used to generate code for an LLVM module.
- data EngineAccess a
- runEngineAccess :: EngineAccess a -> IO a
- addModuleProvider :: ModuleProvider -> EngineAccess ()
- addModule :: Module -> EngineAccess ()
- getPointerToFunction :: Function f -> EngineAccess (FunPtr f)
- addFunctionValue :: Function f -> FunPtr f -> EngineAccess ()
- addGlobalMappings :: GlobalMappings -> EngineAccess ()
- getFreePointers :: Function f -> EngineAccess FreePointers
- type FreePointers = (Ptr ExecutionEngine, ModuleProviderRef, ValueRef)
- class Translatable f
- class Generic a
- class GenericTuple a
- generateFunction :: Translatable f => Value (Ptr f) -> EngineAccess f
- class Unsafe a b | a -> b where
- unsafePurify :: a -> b
- simpleFunction :: Translatable f => CodeGenModule (Function f) -> IO f
- unsafeGenerateFunction :: (Unsafe t a, Translatable t) => CodeGenModule (Function t) -> a
- 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. Nat n => WordN n -> a) -> a
Execution engine
data EngineAccess a 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.
addModule :: Module -> EngineAccess ()Source
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
.
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 LLVM.Core.getGlobalMappings
.
type FreePointers = (Ptr ExecutionEngine, ModuleProviderRef, ValueRef)Source
Get all the information needed to free a function. Freeing code might have to be done from a (C) finalizer, so it has to done from C. The function c_freeFunctionObject take these pointers as arguments and frees the function.
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) | |
(GenericTuple a, Translatable b) => Translatable (:+-> a b) |
class GenericTuple a Source
GenericTuple Double | |
GenericTuple Float | |
GenericTuple Int8 | |
GenericTuple Int16 | |
GenericTuple Int32 | |
GenericTuple Int64 | |
GenericTuple Word8 | |
GenericTuple Word16 | |
GenericTuple Word32 | |
GenericTuple Word64 | |
GenericTuple () | |
GenericTuple (StablePtr a) | |
GenericTuple (Ptr a) | |
(GenericTuple a, GenericTuple b) => GenericTuple (a, b) | |
(GenericTuple a, GenericTuple b, GenericTuple c) => GenericTuple (a, b, c) |
generateFunction :: Translatable f => Value (Ptr 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
class Unsafe a b | a -> b whereSource
:: a | |
-> b | 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 a, Translatable t) => CodeGenModule (Function t) -> aSource
Combine simpleFunction
and unsafePurify
.
Target information
data TargetData Source
TargetData | |
|
withIntPtrType :: (forall n. Nat n => WordN n -> a) -> aSource