Generate code for binary operations
authorLuke Lau <luke_lau@icloud.com>
Sat, 18 May 2019 22:43:07 +0000 (23:43 +0100)
committerLuke Lau <luke_lau@icloud.com>
Sun, 19 May 2019 13:17:16 +0000 (14:17 +0100)
Also throw in the rest of the comparisons whilst we're at it.

AST.hs
Main.hs

diff --git a/AST.hs b/AST.hs
index dfa43b7c60c0d0ced86a73268167b1b9584b9d74..9ff555a74d10c6d970fc8b7df0a37c1d98fdbffc 100644 (file)
--- a/AST.hs
+++ b/AST.hs
@@ -18,6 +18,8 @@ instance Read Expr where
                              , parseVar
                              , parseCall
                              , parseBinOp "<" 10 (Cmp LT)
+                             , parseBinOp ">" 10 (Cmp GT)
+                             , parseBinOp "==" 10 (Cmp EQ)
                              , parseBinOp "+" 20 Add
                              , parseBinOp "-" 20 Sub
                              , parseBinOp "*" 40 Mul
diff --git a/Main.hs b/Main.hs
index 816692b758ceb7dce309611947d84935df97e6e8..ca6629ab447cd64b7c8748eec07ffa7fe6b34e9d 100644 (file)
--- a/Main.hs
+++ b/Main.hs
@@ -1,11 +1,12 @@
 {-# LANGUAGE OverloadedStrings #-}
 
-import AST
+import AST as K -- K for Kaleidoscope
 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.FloatingPointPredicate hiding (False, True)
 import LLVM.AST.Operand
 import LLVM.AST.Type as Type
 import LLVM.IRBuilder
@@ -33,3 +34,20 @@ buildAST (TopLevelExpr x) = function "__anon_expr" [] Type.double $
 
 buildExpr :: Expr -> IRBuilderT ModuleBuilder Operand
 buildExpr (Num x) = pure $ ConstantOperand (Float (Double x))
+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