{-# LANGUAGE TypeFamilies #-} module LLVM.Extra.Execution {-# DEPRECATED "It is based on ExecutionEngine.getPointerToFunction which is error-prone since llvm-tf-3.1." #-} where import qualified LLVM.ExecutionEngine as EE import qualified LLVM.Core as LLVM import Foreign.Ptr (FunPtr, ) import Control.Monad (liftM2, liftM3, ) class Compile externFunction where type LLVMFunction externFunction :: * compile :: LLVMFunction externFunction -> EE.EngineAccess externFunction instance Compile (FunPtr f) where type LLVMFunction (FunPtr f) = (LLVM.Function f) compile = EE.getPointerToFunction instance (Compile fa, Compile fb) => Compile (fa,fb) where type LLVMFunction (fa,fb) = (LLVMFunction fa, LLVMFunction fb) compile (fa,fb) = liftM2 (,) (compile fa) (compile fb) instance (Compile fa, Compile fb, Compile fc) => Compile (fa,fb,fc) where type LLVMFunction (fa,fb,fc) = (LLVMFunction fa, LLVMFunction fb, LLVMFunction fc) compile (fa,fb,fc) = liftM3 (,,) (compile fa) (compile fb) (compile fc)