llvm-tf-12.0.0.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

data EngineAccess a #

Instances
Monad EngineAccess 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Functor EngineAccess 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

fmap :: (a -> b) -> EngineAccess a -> EngineAccess b #

(<$) :: a -> EngineAccess b -> EngineAccess a #

Applicative EngineAccess 
Instance details

Defined in LLVM.ExecutionEngine.Engine

MonadIO EngineAccess 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

liftIO :: IO a -> EngineAccess a #

class ExecutionFunction f #

Minimal complete definition

keepAlive

Instances
ExecutionFunction (IO a) 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

keepAlive :: ExecutionEngine -> IO a -> IO a

ExecutionFunction f => ExecutionFunction (a -> f) 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

keepAlive :: ExecutionEngine -> (a -> f) -> a -> f

type Importer f = FunPtr f -> f #

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) Source # 
Instance details

Defined in LLVM.ExecutionEngine

Methods

translate :: (ValueRef -> [GenericValue] -> IO GenericValue) -> [GenericValue] -> ValueRef -> IO a

(Generic a, Translatable b) => Translatable (a -> b) Source # 
Instance details

Defined in LLVM.ExecutionEngine

Methods

translate :: (ValueRef -> [GenericValue] -> IO GenericValue) -> [GenericValue] -> ValueRef -> a -> b

class Generic a #

Minimal complete definition

toGeneric, fromGeneric

Instances
Generic Double 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Double -> GenericValue

fromGeneric :: GenericValue -> Double

Generic Float 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Float -> GenericValue

fromGeneric :: GenericValue -> Float

Generic Int 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Int -> GenericValue

fromGeneric :: GenericValue -> Int

Generic Int8 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Int8 -> GenericValue

fromGeneric :: GenericValue -> Int8

Generic Int16 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Int16 -> GenericValue

fromGeneric :: GenericValue -> Int16

Generic Int32 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Int32 -> GenericValue

fromGeneric :: GenericValue -> Int32

Generic Int64 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Int64 -> GenericValue

fromGeneric :: GenericValue -> Int64

Generic Word 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Word -> GenericValue

fromGeneric :: GenericValue -> Word

Generic Word8 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Word8 -> GenericValue

fromGeneric :: GenericValue -> Word8

Generic Word16 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Word16 -> GenericValue

fromGeneric :: GenericValue -> Word16

Generic Word32 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Word32 -> GenericValue

fromGeneric :: GenericValue -> Word32

Generic Word64 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Word64 -> GenericValue

fromGeneric :: GenericValue -> Word64

Generic () 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: () -> GenericValue

fromGeneric :: GenericValue -> ()

Generic (StablePtr a) 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: StablePtr a -> GenericValue

fromGeneric :: GenericValue -> StablePtr a

Generic (Ptr a) 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Ptr a -> GenericValue

fromGeneric :: GenericValue -> Ptr a

Generic (Ptr a) 
Instance details

Defined in LLVM.ExecutionEngine.Engine

Methods

toGeneric :: Ptr a -> GenericValue

fromGeneric :: GenericValue -> Ptr a

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

Minimal complete definition

unsafeRemoveIO

Instances
Unsafe (IO a) Source # 
Instance details

Defined in LLVM.ExecutionEngine

Associated Types

type RemoveIO (IO a) :: Type

Methods

unsafeRemoveIO :: IO a -> RemoveIO (IO a) Source #

Unsafe b => Unsafe (a -> b) Source # 
Instance details

Defined in LLVM.ExecutionEngine

Associated Types

type RemoveIO (a -> b) :: Type

Methods

unsafeRemoveIO :: (a -> b) -> RemoveIO (a -> b) Source #

unsafeRemoveIO Source #

Arguments

:: Unsafe a 
=> 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 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

Exchange data with JIT code in memory

class IsType a => Marshal a where #

Methods

peek :: Ptr a -> IO a #

poke :: Ptr a -> a -> IO () #

Instances
Marshal Bool 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr Bool -> IO Bool #

poke :: Ptr Bool -> Bool -> IO () #

Marshal Double 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr Double -> IO Double #

poke :: Ptr Double -> Double -> IO () #

Marshal Float 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr Float -> IO Float #

poke :: Ptr Float -> Float -> IO () #

Marshal Int 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr Int -> IO Int #

poke :: Ptr Int -> Int -> IO () #

Marshal Int8 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr Int8 -> IO Int8 #

poke :: Ptr Int8 -> Int8 -> IO () #

Marshal Int16 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr Int16 -> IO Int16 #

poke :: Ptr Int16 -> Int16 -> IO () #

Marshal Int32 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Marshal Int64 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Marshal Word 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr Word -> IO Word #

poke :: Ptr Word -> Word -> IO () #

Marshal Word8 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Marshal Word16 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr Word16 -> IO Word16 #

poke :: Ptr Word16 -> Word16 -> IO () #

Marshal Word32 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr Word32 -> IO Word32 #

poke :: Ptr Word32 -> Word32 -> IO () #

Marshal Word64 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr Word64 -> IO Word64 #

poke :: Ptr Word64 -> Word64 -> IO () #

Marshal (StablePtr a) 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr (StablePtr a) -> IO (StablePtr a) #

poke :: Ptr (StablePtr a) -> StablePtr a -> IO () #

Storable a => Marshal (Ptr a) 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr0 (Ptr a) -> IO (Ptr a) #

poke :: Ptr0 (Ptr a) -> Ptr a -> IO () #

IsFunction a => Marshal (FunPtr a) 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr (FunPtr a) -> IO (FunPtr a) #

poke :: Ptr (FunPtr a) -> FunPtr a -> IO () #

Positive d => Marshal (IntN d) 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr (IntN d) -> IO (IntN d) #

poke :: Ptr (IntN d) -> IntN d -> IO () #

IsType a => Marshal (Ptr a) 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr (Ptr a) -> IO (Ptr a) #

poke :: Ptr (Ptr a) -> Ptr a -> IO () #

StructFields fields => Marshal (Struct fields) 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr (Struct fields) -> IO (Struct fields) #

poke :: Ptr (Struct fields) -> Struct fields -> IO () #

Positive d => Marshal (WordN d) 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr (WordN d) -> IO (WordN d) #

poke :: Ptr (WordN d) -> WordN d -> IO () #

(Natural n, Marshal a, IsSized a) => Marshal (Array n a) 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr (Array n a) -> IO (Array n a) #

poke :: Ptr (Array n a) -> Array n a -> IO () #

(Positive n, MarshalVector a) => Marshal (Vector n a) 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peek :: Ptr (Vector n a) -> IO (Vector n a) #

poke :: Ptr (Vector n a) -> Vector n a -> IO () #

class IsPrimitive a => MarshalVector a where #

Methods

peekVector :: Positive n => Ptr (Vector n a) -> IO (Vector n a) #

pokeVector :: Positive n => Ptr (Vector n a) -> Vector n a -> IO () #

Instances
MarshalVector Bool 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n Bool) -> IO (Vector n Bool) #

pokeVector :: Positive n => Ptr (Vector n Bool) -> Vector n Bool -> IO () #

MarshalVector Double 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n Double) -> IO (Vector n Double) #

pokeVector :: Positive n => Ptr (Vector n Double) -> Vector n Double -> IO () #

MarshalVector Float 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n Float) -> IO (Vector n Float) #

pokeVector :: Positive n => Ptr (Vector n Float) -> Vector n Float -> IO () #

MarshalVector Int 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n Int) -> IO (Vector n Int) #

pokeVector :: Positive n => Ptr (Vector n Int) -> Vector n Int -> IO () #

MarshalVector Int8 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n Int8) -> IO (Vector n Int8) #

pokeVector :: Positive n => Ptr (Vector n Int8) -> Vector n Int8 -> IO () #

MarshalVector Int16 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n Int16) -> IO (Vector n Int16) #

pokeVector :: Positive n => Ptr (Vector n Int16) -> Vector n Int16 -> IO () #

MarshalVector Int32 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n Int32) -> IO (Vector n Int32) #

pokeVector :: Positive n => Ptr (Vector n Int32) -> Vector n Int32 -> IO () #

MarshalVector Int64 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n Int64) -> IO (Vector n Int64) #

pokeVector :: Positive n => Ptr (Vector n Int64) -> Vector n Int64 -> IO () #

MarshalVector Word 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n Word) -> IO (Vector n Word) #

pokeVector :: Positive n => Ptr (Vector n Word) -> Vector n Word -> IO () #

MarshalVector Word8 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n Word8) -> IO (Vector n Word8) #

pokeVector :: Positive n => Ptr (Vector n Word8) -> Vector n Word8 -> IO () #

MarshalVector Word16 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n Word16) -> IO (Vector n Word16) #

pokeVector :: Positive n => Ptr (Vector n Word16) -> Vector n Word16 -> IO () #

MarshalVector Word32 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n Word32) -> IO (Vector n Word32) #

pokeVector :: Positive n => Ptr (Vector n Word32) -> Vector n Word32 -> IO () #

MarshalVector Word64 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n Word64) -> IO (Vector n Word64) #

pokeVector :: Positive n => Ptr (Vector n Word64) -> Vector n Word64 -> IO () #

Positive d => MarshalVector (IntN d) 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n (IntN d)) -> IO (Vector n (IntN d)) #

pokeVector :: Positive n => Ptr (Vector n (IntN d)) -> Vector n (IntN d) -> IO () #

Positive d => MarshalVector (WordN d) 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekVector :: Positive n => Ptr (Vector n (WordN d)) -> IO (Vector n (WordN d)) #

pokeVector :: Positive n => Ptr (Vector n (WordN d)) -> Vector n (WordN d) -> IO () #

sizeOf :: IsType a => Proxy a -> Int #

alignment :: IsType a => Proxy a -> Int #

class StructFields fields => StructFields fields #

Minimal complete definition

peekStruct, pokeStruct

Instances
StructFields () 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekStruct :: TypeRef -> Int -> Ptr struct -> IO ()

pokeStruct :: TypeRef -> Int -> Ptr struct -> () -> IO ()

(Marshal a, IsSized a, StructFields as) => StructFields (a, as) 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

peekStruct :: TypeRef -> Int -> Ptr struct -> IO (a, as)

pokeStruct :: TypeRef -> Int -> Ptr struct -> (a, as) -> IO ()

sizeOfArray :: IsType a => Proxy a -> Int -> Int #

pokeList :: Marshal a => Ptr a -> [a] -> IO () #

with :: Marshal a => a -> (Ptr a -> IO b) -> IO b #

alloca :: IsType a => (Ptr a -> IO b) -> IO b #

newtype Stored a #

Constructors

Stored 

Fields

Instances
Marshal a => Storable (Stored a) 
Instance details

Defined in LLVM.ExecutionEngine.Marshal

Methods

sizeOf :: Stored a -> Int #

alignment :: Stored a -> Int #

peekElemOff :: Ptr (Stored a) -> Int -> IO (Stored a) #

pokeElemOff :: Ptr (Stored a) -> Int -> Stored a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Stored a) #

pokeByteOff :: Ptr b -> Int -> Stored a -> IO () #

peek :: Ptr (Stored a) -> IO (Stored a) #

poke :: Ptr (Stored a) -> Stored a -> IO () #

castToStoredPtr :: Ptr a -> Ptr (Stored a) #

castFromStoredPtr :: Ptr (Stored a) -> Ptr a #