Skip to content

Instantly share code, notes, and snippets.

@lewurm
Created September 17, 2012 15:44
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save lewurm/3738101 to your computer and use it in GitHub Desktop.
Save lewurm/3738101 to your computer and use it in GitHub Desktop.
Haskell: LLVM bindings versus Harpy
{-# LANGUAGE ForeignFunctionInterface #-}
module Main where
import Foreign
import Foreign.C.Types
import Control.Monad
import Harpy
type SomeFunType = CInt -> CInt -> IO CInt
foreign import ccall "dynamic"
call_int :: FunPtr SomeFunType -> SomeFunType
mSomeFun :: CodeGen () () (FunPtr SomeFunType)
mSomeFun = do
mov eax (Disp 0x4, esp)
mov ebx (Disp 0x8, esp)
replicateM_ 4000000 (add eax ebx)
ret
liftM castPtrToFunPtr getEntryPoint
main = do
(_, Right someFun) <- runCodeGen mSomeFun () ()
call_int someFun 1337 432 >>= print
module Main where
import Data.Word
import Data.Int
import Control.Monad
import LLVM.Core
import LLVM.ExecutionEngine
mSomeFun :: CodeGenModule (Function (Int32 -> Int32 -> IO Int32))
mSomeFun =
createFunction ExternalLinkage $ \ x y -> do
r <- foldM (\a _ -> add a y) x [1..4000000]
ret r
main = do
someFun <- simpleFunction mSomeFun
someFun 1337 432 >>= print
SHELL := bash
all: llvmmain harpymain
@echo "llvm..."
time ./llvmmain
@echo "harpy..."
time ./harpymain
llvmmain: LLVMMain.hs
ghc --make -O2 $< -o $@
harpymain: HarpyMain.hs
ghc --make -O2 $< -o $@
clean:
rm -rf *.o *.hi llvmmain harpymain
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment