X-Git-Url: https://git.lukelau.me/?p=kaleidoscope-hs.git;a=blobdiff_plain;f=Main.hs;h=f32003bdd2dbb48eba325526bf1849444fd1d09d;hp=76a9bdb5d48831da2e59c811ecbcbb5a379bdfb5;hb=cd0347585b7a03941baad82b4f2ed6deb8ff78f4;hpb=30a26b7d2b0e17ea523ee34cb5d37242a38882df diff --git a/Main.hs b/Main.hs index 76a9bdb..f32003b 100644 --- a/Main.hs +++ b/Main.hs @@ -1 +1,82 @@ -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.Constant +import LLVM.AST.Float +import LLVM.AST.FloatingPointPredicate hiding (False, True) +import LLVM.AST.Operand +import LLVM.AST.Type as Type +import LLVM.IRBuilder +import LLVM.Pretty +import System.IO +import System.IO.Error +import Text.Read (readMaybe) + +main :: IO () +main = buildModuleT "main" repl >>= Text.hPutStrLn stderr . ("\n" <>) . ppll + +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