Begin codegen
[kaleidoscope-hs.git] / Main.hs
diff --git a/Main.hs b/Main.hs
index 76a9bdb5d48831da2e59c811ecbcbb5a379bdfb5..816692b758ceb7dce309611947d84935df97e6e8 100644 (file)
--- a/Main.hs
+++ b/Main.hs
@@ -1 +1,35 @@
-main = pure ()
+{-# LANGUAGE OverloadedStrings #-}
+
+import AST
+import Utils
+import Control.Monad.IO.Class
+import qualified Data.Text.Lazy.IO as Text
+import LLVM.AST.Constant
+import LLVM.AST.Float
+import LLVM.AST.Operand
+import LLVM.AST.Type as Type
+import LLVM.IRBuilder
+import LLVM.Pretty
+import System.IO
+import Text.Read (readMaybe)
+
+main = buildModuleT "main" repl
+
+repl :: ModuleBuilderT IO ()
+repl = do
+  liftIO $ hPutStr stderr "ready> "
+  ast <- liftIO $ readMaybe <$> getLine
+  case ast of
+    Nothing ->  liftIO $ hPutStrLn stderr "Couldn't parse"
+    Just x -> do
+      hoist $ buildAST x
+      mostRecentDef >>= liftIO . Text.hPutStrLn stderr . ppll
+  repl
+  where 
+
+buildAST :: AST -> ModuleBuilder Operand
+buildAST (TopLevelExpr x) = function "__anon_expr" [] Type.double $
+  const $ buildExpr x >>= ret
+
+buildExpr :: Expr -> IRBuilderT ModuleBuilder Operand
+buildExpr (Num x) = pure $ ConstantOperand (Float (Double x))