Handle EOFs in the repl
[kaleidoscope-hs.git] / Main.hs
diff --git a/Main.hs b/Main.hs
index ca6629ab447cd64b7c8748eec07ffa7fe6b34e9d..f32003bdd2dbb48eba325526bf1849444fd1d09d 100644 (file)
--- a/Main.hs
+++ b/Main.hs
@@ -2,7 +2,10 @@
 
 import AST as K -- K for Kaleidoscope
 import Utils
+import Control.Monad.Trans.Reader
 import Control.Monad.IO.Class
+import Data.String
+import qualified Data.Map as Map
 import qualified Data.Text.Lazy.IO as Text
 import LLVM.AST.Constant
 import LLVM.AST.Float
@@ -12,28 +15,54 @@ import LLVM.AST.Type as Type
 import LLVM.IRBuilder
 import LLVM.Pretty
 import System.IO
+import System.IO.Error
 import Text.Read (readMaybe)
 
-main = buildModuleT "main" repl
+main :: IO ()
+main = buildModuleT "main" repl >>= Text.hPutStrLn stderr . ("\n" <>) . ppll
 
 repl :: ModuleBuilderT IO ()
 repl = do
   liftIO $ hPutStr stderr "ready> "
-  ast <- liftIO $ readMaybe <$> getLine
-  case ast of
+  mline <- liftIO $ catchIOError (Just <$> getLine) eofHandler
+  case mline of
+    Nothing -> return ()
+    Just l -> do
+      case readMaybe l of
         Nothing ->  liftIO $ hPutStrLn stderr "Couldn't parse"
-    Just x -> do
-      hoist $ buildAST x
+        Just ast -> do
+          hoist $ buildAST ast
           mostRecentDef >>= liftIO . Text.hPutStrLn stderr . ppll
       repl
   where
+    eofHandler e
+      | isEOFError e = return Nothing
+      | otherwise = ioError e
+
+type Binds = Map.Map String Operand
 
 buildAST :: AST -> ModuleBuilder Operand
+buildAST (Function (Prototype nameStr paramStrs) body) = do
+  let n = fromString nameStr
+  function n params Type.double $ \ops -> do
+    let binds = Map.fromList (zip paramStrs ops)
+    flip runReaderT binds $ buildExpr body >>= ret
+  where params = zip (repeat Type.double) (map fromString paramStrs)
+
+buildAST (Extern (Prototype nameStr params)) =
+  extern (fromString nameStr) (replicate (length params) Type.double) Type.double
+
 buildAST (TopLevelExpr x) = function "__anon_expr" [] Type.double $
-  const $ buildExpr x >>= ret
+  const $ flip runReaderT mempty $ buildExpr x >>= ret
 
-buildExpr :: Expr -> IRBuilderT ModuleBuilder Operand
+buildExpr :: Expr -> ReaderT Binds (IRBuilderT ModuleBuilder) Operand
 buildExpr (Num x) = pure $ ConstantOperand (Float (Double x))
+buildExpr (Var n) = do
+  binds <- ask
+  case binds Map.!? n of
+    Just x -> pure x
+    Nothing -> error $ "'" <> n <> "' doesn't exist in scope"
+
 buildExpr (BinOp op a b) = do
   opA <- buildExpr a
   opB <- buildExpr b