summaryrefslogtreecommitdiff
path: root/ast.hs
diff options
context:
space:
mode:
Diffstat (limited to 'ast.hs')
-rw-r--r--ast.hs47
1 files changed, 33 insertions, 14 deletions
diff --git a/ast.hs b/ast.hs
index bd845df..e3db600 100644
--- a/ast.hs
+++ b/ast.hs
@@ -1,7 +1,4 @@
-module AST(
- Name,
- Program(..), Declaration(..), Block(..), Type(..), Literal(..),
- BinaryOperator(..), UnaryOperator(..), Expression(..), Statement(..)) where
+module AST where
import Data.List
@@ -52,10 +49,10 @@ data UnaryOperator
= Negate | Not | Invert | Dereference | Address
deriving (Show, Eq)
-data Expression
- = ExLit Literal
- | ExBinOp BinaryOperator Expression Expression
- | ExUnOp UnaryOperator Expression
+data Expression -- (Maybe Type)'s are type annotations by the type checker
+ = ExLit Literal (Maybe Type)
+ | ExBinOp BinaryOperator Expression Expression (Maybe Type)
+ | ExUnOp UnaryOperator Expression (Maybe Type)
deriving (Show)
data Statement
@@ -70,9 +67,24 @@ data Statement
deriving (Show)
-indent :: Int -> String -> String
-indent sz str = intercalate "\n" $ map (prefix++) $ lines str
- where prefix = replicate sz ' '
+exLit_ :: Literal -> Expression
+exLit_ l = ExLit l Nothing
+
+exBinOp_ :: BinaryOperator -> Expression -> Expression -> Expression
+exBinOp_ bo a b = ExBinOp bo a b Nothing
+
+exUnOp_ :: UnaryOperator -> Expression -> Expression
+exUnOp_ uo e = ExUnOp uo e Nothing
+
+exTypeOf :: Expression -> Maybe Type
+exTypeOf (ExLit _ mt) = mt
+exTypeOf (ExBinOp _ _ _ mt) = mt
+exTypeOf (ExUnOp _ _ mt) = mt
+
+-- exSetType :: Type -> Expression -> Expression
+-- exSetType t (ExLit l _) = ExLit l t
+-- exSetType t (ExBinOp bo e1 e2 _) = ExBinOp bo e1 e2 t
+-- exSetType t (ExUnOp bo e _) = ExUnOp bo e t
instance PShow Program where
@@ -92,6 +104,10 @@ instance PShow Declaration where
instance PShow Block where
pshow (Block []) = "{}"
pshow (Block stmts) = concat ["{\n", indent 4 $ intercalate "\n" (map pshow stmts), "\n}"]
+ where
+ indent :: Int -> String -> String
+ indent sz str = intercalate "\n" $ map (prefix++) $ lines str
+ where prefix = replicate sz ' '
instance PShow Type where
pshow (TypeInt sz) = 'i' : pshow sz
@@ -130,9 +146,12 @@ instance PShow UnaryOperator where
pshow Address = "&"
instance PShow Expression where
- pshow (ExLit lit) = pshow lit
- pshow (ExBinOp op a b) = concat [pshow a, " ", pshow op, " ", pshow b]
- pshow (ExUnOp op a) = concat [pshow op, pshow a]
+ pshow (ExLit lit Nothing) = pshow lit
+ pshow (ExLit lit (Just t)) = concat ["(", pshow lit, " :: ", pshow t, ")"]
+ pshow (ExBinOp op a b Nothing) = concat ["(", pshow a, " ", pshow op, " ", pshow b, ")"]
+ pshow (ExBinOp op a b (Just t)) = concat ["(", pshow a, " ", pshow op, " ", pshow b, " :: ", pshow t, ")"]
+ pshow (ExUnOp op a Nothing) = concat [pshow op, pshow a]
+ pshow (ExUnOp op a (Just t)) = concat ["(", pshow op, pshow a, " :: ", pshow t, ")"]
instance PShow Statement where
pshow StEmpty = ";"