module LLVM.ExecutionEngine(
EngineAccess,
ExecutionEngine,
getEngine,
runEngineAccess,
runEngineAccessWithModule,
addModule,
ExecutionFunction,
getExecutionFunction,
getPointerToFunction,
addFunctionValue,
addGlobalMappings,
Translatable, Generic,
generateFunction,
Unsafe,
unsafeRemoveIO,
simpleFunction,
unsafeGenerateFunction,
module LLVM.ExecutionEngine.Target
) where
import LLVM.ExecutionEngine.Engine
import LLVM.ExecutionEngine.Target
import LLVM.Core.CodeGen (Value(..))
import LLVM.Core
(CodeGenModule, Function, newModule, defineModule, getGlobalMappings,
setTarget, hostTriple)
import LLVM.FFI.Core (ValueRef)
import System.IO.Unsafe (unsafePerformIO)
import Control.Monad (liftM2, )
class Translatable f where
translate :: (ValueRef -> [GenericValue] -> IO GenericValue) -> [GenericValue] -> ValueRef -> f
instance (Generic a, Translatable b) => Translatable (a -> b) where
translate run args f = \ arg -> translate run (toGeneric arg : args) f
instance (Generic a) => Translatable (IO a) where
translate run args f = fmap fromGeneric $ run f $ reverse args
generateFunction ::
(Translatable f) =>
Function f -> EngineAccess f
generateFunction (Value f) = do
run <- getRunFunction
return $ translate run [] f
class Unsafe a where
type RemoveIO a :: *
unsafeRemoveIO :: a -> RemoveIO a
instance (Unsafe b) => Unsafe (a->b) where
type RemoveIO (a -> b) = a -> RemoveIO b
unsafeRemoveIO f = unsafeRemoveIO . f
instance Unsafe (IO a) where
type RemoveIO (IO a) = a
unsafeRemoveIO = unsafePerformIO
simpleFunction :: (Translatable f) => CodeGenModule (Function f) -> IO f
simpleFunction bld = do
m <- newModule
(func, mappings) <-
defineModule m $
setTarget hostTriple >> liftM2 (,) bld getGlobalMappings
runEngineAccessInterpreterWithModule m $ do
addGlobalMappings mappings
generateFunction func
unsafeGenerateFunction :: (Unsafe t, Translatable t) =>
CodeGenModule (Function t) -> RemoveIO t
unsafeGenerateFunction bld = unsafePerformIO $ do
fun <- simpleFunction bld
return $ unsafeRemoveIO fun