Set up the LLVM context and optimise the module
[kaleidoscope-hs.git] / Main.hs
diff --git a/Main.hs b/Main.hs
index 76a9bdb5d48831da2e59c811ecbcbb5a379bdfb5..bff1c08c965c037080cc6aba052a60c40f1dc999 100644 (file)
--- a/Main.hs
+++ b/Main.hs
@@ -1 +1,103 @@
-main = pure ()
+{-# LANGUAGE OverloadedStrings #-}
+
+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.AddrSpace
+import LLVM.AST.Constant
+import LLVM.AST.Float
+import LLVM.AST.FloatingPointPredicate hiding (False, True)
+import LLVM.AST.Operand
+import LLVM.AST.Type as Type
+import LLVM.Context
+import LLVM.IRBuilder
+import LLVM.Module
+import LLVM.PassManager
+import LLVM.Pretty
+import LLVM.Target
+import System.IO
+import System.IO.Error
+import Text.Read (readMaybe)
+
+main :: IO ()
+main = do
+  mdl' <- buildModuleT "main" repl
+  withContext $ \ctx -> withHostTargetMachine $ \tm ->
+    withModuleFromAST ctx mdl' $ \mdl -> do
+      let spec = defaultCuratedPassSetSpec { optLevel = Just 3 }
+      -- this returns true if the module was modified
+      withPassManager spec $ flip runPassManager mdl
+      Text.hPutStrLn stderr . ("\n" <>) . ppllvm =<< moduleAST mdl
+
+repl :: ModuleBuilderT IO ()
+repl = do
+  liftIO $ hPutStr stderr "ready> "
+  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 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 $ flip runReaderT mempty $ buildExpr x >>= ret
+
+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
+  tmp <- instr opA opB
+  if isCmp
+    then uitofp tmp Type.double
+    else return tmp
+  where isCmp
+          | Cmp _ <- op = True
+          | otherwise = False
+        instr = case op of
+                  K.Add -> fadd
+                  K.Sub -> fsub
+                  K.Mul -> fmul
+                  K.Cmp LT -> fcmp OLT
+                  K.Cmp GT -> fcmp OGT
+                  K.Cmp EQ -> fcmp OEQ
+
+buildExpr (Call callee params) = do
+  paramOps <- mapM buildExpr params
+  let nam = fromString callee
+      -- get a pointer to the function
+      typ = FunctionType Type.double (replicate (length params) Type.double) False
+      ptrTyp = Type.PointerType typ (AddrSpace 0)
+      ref = GlobalReference ptrTyp nam
+  call (ConstantOperand ref) (zip paramOps (repeat []))