Add basic JIT
authorLuke Lau <luke_lau@icloud.com>
Sun, 10 Mar 2019 01:56:37 +0000 (01:56 +0000)
committerLuke Lau <luke_lau@icloud.com>
Wed, 17 Apr 2019 22:38:30 +0000 (23:38 +0100)
Main.hs

diff --git a/Main.hs b/Main.hs
index 7a26601b60ab6ca070c604d893332a1bbd1a62ab..37c6cbc788a9849ef721995f58b9c1191ba0385d 100644 (file)
--- a/Main.hs
+++ b/Main.hs
@@ -4,6 +4,11 @@ module Main where
 
 import qualified AST
 import qualified Data.Text.Lazy.IO as Text
+import Foreign.Ptr
+import LLVM.Context
+import LLVM.CodeModel
+import LLVM.ExecutionEngine
+import LLVM.Module
 import LLVM.IRBuilder
 import LLVM.AST.Constant
 import LLVM.AST.Float
@@ -11,14 +16,21 @@ import LLVM.AST.Operand
 import LLVM.AST.Type
 import LLVM.Pretty
 
+foreign import ccall "dynamic" exprFun :: FunPtr (IO Float) -> IO Float
+
 main :: IO ()
 main = do
   ast <- read <$> getContents
   let mdl = buildModule "main" $
-        function "expr" [] float $ \_ -> do
-          build ast
-          return ()
+        function "expr" [] float $ \_ -> build ast >>= ret
   Text.putStrLn (ppllvm mdl)
+  withContext $ \ctx ->
+    withMCJIT ctx Nothing Nothing Nothing Nothing $ \mcjit ->
+      withModuleFromAST ctx mdl $ \mdl' ->
+        withModuleInEngine mcjit mdl' $ \emdl -> do
+          Just f <- getFunction emdl "expr"
+          let f' = castFunPtr f :: FunPtr (IO Float)
+          exprFun f' >>= print
 
 build :: AST.Expr -> IRBuilderT ModuleBuilder Operand
 build (AST.Num a) = pure $ ConstantOperand (Float (Single a))