This is an early release of Haskell bindings for the popular LLVM compiler infrastructure project.
If you don't know what LLVM is, it's a wonderful toybox of compiler components, from a complete toolchain supporting multiple architectures through a set of well-defined APIs and IR formats that are designed for building interesting software with. The official LLVM home page is here: http://llvm.org/ The Haskell bindings are based on Gordon Henriksen's C bindings. The C bindings are almost untyped, but the Haskell bindings re-add type safety to prevent runtime crashes and general badness. Currently, the entire code generation system is implemented, with most LLVM data types supported (notably absent are structs). Also plugged in is JIT support, so you can generate code at runtime from Haskell and run it immediately. I've attached an example. Please join in the hacking fun! darcs get http://darcs.serpentine.com/llvm If you want a source tarball, fetch it from here: http://darcs.serpentine.com/llvm/llvm-0.0.2.tar.gz (Hackage can't host code that uses GHC 6.8.2's language extension names yet.) There's very light documentation at present, but it ought to be enough to get you going. <b
{-# LANGUAGE TypeOperators #-} module Fibonacci (main) where import Control.Monad (forM_) import Data.Int (Int32) import System.Environment (getArgs) import qualified LLVM.Core as Core import qualified LLVM.Core.Builder as B import qualified LLVM.Core.Constant as C import qualified LLVM.Core.Instruction as I import qualified LLVM.Core.Type as T import qualified LLVM.Core.Value as V import qualified LLVM.Core.Utils as U import qualified LLVM.ExecutionEngine as EE buildFib :: T.Module -> IO (V.Function T.Int32 T.Int32) buildFib m = do let one = C.const (1::Int32) two = C.const (2::Int32) (fib, entry) <- U.defineFunction m "fib" (T.function undefined undefined) bld <- B.createBuilder exit <- Core.appendBasicBlock fib "return" recurse <- Core.appendBasicBlock fib "recurse" let arg = V.params fib B.positionAtEnd bld entry test <- B.icmp bld "" I.IntSLE arg two B.condBr bld test exit recurse B.positionAtEnd bld exit B.ret bld one B.positionAtEnd bld recurse x1 <- B.sub bld "" arg one fibx1 <- B.call bld "" fib x1 x2 <- B.sub bld "" arg two fibx2 <- B.call bld "" fib x2 B.add bld "" fibx1 fibx2 >>= B.ret bld return fib main :: IO () main = do args <- getArgs let args' = if null args then ["10"] else args m <- Core.createModule "fib" fib <- buildFib m V.dumpValue fib prov <- Core.createModuleProviderForExistingModule m ee <- EE.createExecutionEngine prov forM_ args' $ \num -> do putStr $ "fib " ++ num ++ " = " parm <- EE.createGeneric (read num :: Int) gv <- EE.runFunction ee fib [parm] print (EE.fromGeneric gv :: Int)
define i32 @fib(i32) { entry: icmp sle i32 %0, 2 ; <i1>:1 [#uses=1] br i1 %1, label %return, label %recurse return: ; preds = %entry ret i32 1 recurse: ; preds = %entry sub i32 %0, 1 ; <i32>:2 [#uses=1] call i32 @fib( i32 %2 ) ; <i32>:3 [#uses=1] sub i32 %0, 2 ; <i32>:4 [#uses=1] call i32 @fib( i32 %4 ) ; <i32>:5 [#uses=1] add i32 %3, %5 ; <i32>:6 [#uses=1] ret i32 %6 } fib 10 = 55
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe