module LLVM.ExecutionEngine(
    
    EngineAccess,
    runEngineAccess,
    addModuleProvider,
    addModule,
    getPointerToFunction,
    addFunctionValue,
    addGlobalMappings,
    getFreePointers, FreePointers,
    
    Translatable, Generic,
    generateFunction,
    
    Unsafe,
    unsafePurify,
    
    simpleFunction,
    unsafeGenerateFunction,
    
    module LLVM.ExecutionEngine.Target
    ) where
import System.IO.Unsafe (unsafePerformIO)
import LLVM.ExecutionEngine.Engine
import LLVM.FFI.Core(ValueRef)
import LLVM.Core.CodeGen(Value(..))
import LLVM.Core
import LLVM.ExecutionEngine.Target
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) =>
                    Value (Ptr f) -> EngineAccess f
generateFunction (Value f) = do
    run <- getRunFunction
    return $ translate run [] f
class Unsafe a b | a -> b where
    unsafePurify :: a -> b  
instance (Unsafe b b') => Unsafe (a->b) (a->b') where
    unsafePurify f = unsafePurify . f
instance Unsafe (IO a) a where
    unsafePurify = unsafePerformIO
simpleFunction :: (Translatable f) => CodeGenModule (Function f) -> IO f
simpleFunction bld = do
    m <- newModule
    (func, mappings) <- defineModule m (liftM2 (,) bld getGlobalMappings)
    prov <- createModuleProviderForExistingModule m
    runEngineAccess $ do
        addModuleProvider prov
        addGlobalMappings mappings
        generateFunction func
unsafeGenerateFunction :: (Unsafe t a, Translatable t) =>
                          CodeGenModule (Function t) -> a
unsafeGenerateFunction bld = unsafePerformIO $ do
    fun <- simpleFunction bld
    return $ unsafePurify fun