Add standard library
[kaleidoscope-hs.git] / Main.hs
diff --git a/Main.hs b/Main.hs
index 468573d865ab4fccb350bc78bf446d4e9d400563..64d73e60e0a059864222aec09f8b2ad0803adcfd 100644 (file)
--- a/Main.hs
+++ b/Main.hs
@@ -1,4 +1,5 @@
 {-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RecursiveDo #-}
 
 import AST as K -- K for Kaleidoscope
 import Utils
@@ -18,12 +19,14 @@ import LLVM.AST.Operand
 import LLVM.AST.Type as Type
 import LLVM.Context
 import LLVM.IRBuilder
+import LLVM.Linking
 import LLVM.Module
 import LLVM.OrcJIT
 import LLVM.OrcJIT.CompileLayer
 import LLVM.PassManager
 import LLVM.Pretty
 import LLVM.Target
+import Numeric
 import System.IO
 import System.IO.Error
 import Text.Read (readMaybe)
@@ -37,7 +40,8 @@ data JITEnv = JITEnv
   }
 
 main :: IO ()
-main =
+main = do
+  loadLibraryPermanently (Just "stdlib.dylib")
   withContext $ \ctx -> withHostTargetMachineDefault $ \tm ->
     withExecutionSession $ \exSession ->
       withSymbolResolver exSession (SymbolResolver symResolver) $ \symResolverPtr ->
@@ -50,7 +54,10 @@ main =
 
 -- This can eventually be used to resolve external functions, e.g. a stdlib call
 symResolver :: MangledSymbol -> IO (Either JITSymbolError JITSymbol)
-symResolver sym = undefined
+symResolver sym = do
+  ptr <- getSymbolAddressInProcess sym
+  putStrLn $ "Resolving " <> show sym <> " to 0x" <> showHex ptr ""
+  return (Right (JITSymbol ptr defaultJITSymbolFlags))
 
 repl :: ModuleBuilderT (ReaderT JITEnv IO) ()
 repl = do
@@ -141,3 +148,60 @@ buildExpr (Call callee params) = do
       ptrTyp = Type.PointerType typ (AddrSpace 0)
       ref = GlobalReference ptrTyp nam
   call (ConstantOperand ref) (zip paramOps (repeat []))
+
+buildExpr (If cond thenE elseE) = mdo
+  _ifB <- block `named` "if"
+
+  -- since everything is a double, false == 0
+  let zero = ConstantOperand (Float (Double 0))
+  condV <- buildExpr cond
+  cmp <- fcmp ONE zero condV `named` "cmp"
+
+  condBr cmp thenB elseB
+
+  thenB <- block `named` "then"
+  thenOp <- buildExpr thenE
+  br mergeB
+
+  elseB <- block `named` "else"
+  elseOp <- buildExpr elseE
+  br mergeB
+
+  mergeB <- block `named` "ifcont"
+  phi [(thenOp, thenB), (elseOp, elseB)]
+
+buildExpr (For name init cond mStep body) = mdo
+  preheaderB <- block `named` "preheader"
+
+  initV <- buildExpr init `named` "init"
+  
+  -- build the condition expression with 'i' in the bindings
+  initCondV <- withReaderT (Map.insert name initV) $
+                (buildExpr cond >>= fcmp ONE zero) `named` "initcond"
+
+  -- skip the loop if we don't meet the condition with the init
+  condBr initCondV loopB afterB
+
+  loopB <- block `named` "loop"
+  i <- phi [(initV, preheaderB), (nextVar, loopB)] `named` "i"
+
+  -- build the body expression with 'i' in the bindings
+  withReaderT (Map.insert name i) $ buildExpr body `named` "body"
+
+  -- default to 1 if there's no step defined
+  stepV <- case mStep of
+    Just step -> buildExpr step
+    Nothing -> return $ ConstantOperand (Float (Double 1))
+
+  nextVar <- fadd i stepV `named` "nextvar"
+
+  let zero = ConstantOperand (Float (Double 0))
+  -- again we need 'i' in the bindings
+  condV <- withReaderT (Map.insert name i) $
+            (buildExpr cond >>= fcmp ONE zero) `named` "cond"
+  condBr condV loopB afterB
+
+  afterB <- block `named` "after"
+  -- since a for loop doesn't really have a value, return 0
+  return $ ConstantOperand (Float (Double 0))
+