diff --git a/ast.hs b/ast.hs new file mode 100644 index 0000000..cf216ea --- /dev/null +++ b/ast.hs @@ -0,0 +1,22 @@ +module AST where + +data AST = Add AST AST + | Mul AST AST + | Block [AST] + | FunDef String (Pattern, AST) + | Def String AST + | Var String + | Lambda [(Pattern, [AST])] + | Call String [AST] + | UnitConst + | ListConst [AST] + | StrConst String + | IntConst Integer + deriving (Show, Eq) + +data Pattern = VarP String + | IntP Integer + | UnitP + | ConsP Pattern Pattern + | ListP [Pattern] + deriving (Show, Eq) \ No newline at end of file diff --git a/interp.hs b/interp.hs index 26fef7e..620df2a 100644 --- a/interp.hs +++ b/interp.hs @@ -1,24 +1,11 @@ import Control.Monad.State (State, runState, evalState, get, put) import qualified Data.Map as M +import AST +import Parser (parseProgram) -data AST = Add AST AST - | Def String AST - | Var String - | Lambda [(Pattern, [AST])] - | Call String [AST] - | ListConst [AST] - | StrConst String - | IntConst Int - deriving (Show, Eq) - -data Pattern = VarP String - | IntP Int - | ConsP Pattern Pattern - | ListP [Pattern] - deriving (Show, Eq) - -data Value = IntV Int +data Value = IntV Integer | StrV String + | UnitV | ListV [Value] | FnV [(Pattern, [AST])] -- pattern->body bindings deriving (Show, Eq) @@ -37,6 +24,8 @@ eval :: AST -> InterpState Value eval (IntConst i) = return $ IntV i eval (StrConst s) = return $ StrV s +eval UnitConst = return UnitV + eval (ListConst v) = mapM eval v >>= \xs -> return $ ListV xs @@ -76,6 +65,9 @@ patternBindings (IntP n) (IntV v) | otherwise = Nothing patternBindings (IntP n) _ = Nothing +patternBindings UnitP UnitV = Just M.empty +patternBindings UnitP _ = Nothing + patternBindings (ConsP x (ListP [])) (ListV (y:[])) = patternBindings x y patternBindings (ConsP _ _) (ListV (_:[])) = Nothing patternBindings (ConsP xp xsp) (ListV (x:xs)) =