llvm-tf-3.0.3.1: Bindings to the LLVM compiler toolkit using type families.

Safe HaskellNone
LanguageHaskell98

LLVM.ExecutionEngine

Contents

Description

An ExecutionEngine is JIT compiler that is used to generate code for an LLVM module.

Synopsis

Execution engine

runEngineAccess :: EngineAccess a -> IO a Source

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.

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 getGlobalMappings.

type FreePointers = (ExecutionEngineRef, 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.

Minimal complete definition

translate

Instances

Generic a => Translatable (IO a) 
(Generic a, Translatable b) => Translatable (a -> b) 

class Generic a Source

Minimal complete definition

toGeneric, fromGeneric

generateFunction :: Translatable f => Function f -> EngineAccess f Source

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 where Source

Methods

unsafeRemoveIO Source

Arguments

:: a 
-> RemoveIO a

Remove the IO from a function return type. This is unsafe in general.

Instances

Unsafe (IO a) 
Unsafe b => Unsafe (a -> b) 

Simplified interface.

simpleFunction :: Translatable f => CodeGenModule (Function f) -> IO f Source

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.

Target information

data TargetData Source

Constructors

TargetData 

Fields

aBIAlignmentOfType :: Type -> Int
 
aBISizeOfType :: Type -> Int
 
littleEndian :: Bool
 
callFrameAlignmentOfType :: Type -> Int
 
intPtrType :: Type
 
pointerSize :: Int
 
preferredAlignmentOfType :: Type -> Int
 
sizeOfTypeInBits :: Type -> Int
 
storeSizeOfType :: Type -> Int
 

Instances

withIntPtrType :: (forall n. Positive n => WordN n -> a) -> a Source