]> ruin.nu Git - proglang.git/blobdiff - Interpret.hs
Interpreter works
[proglang.git] / Interpret.hs
index b82398d22bc63b114eb0d5c6f7f344f80cd34c31..1938e55308263f3076063e629d8e12d998f17f21 100644 (file)
@@ -2,6 +2,8 @@ module Interpret (eval, execute,addFunction, emptyState, Value(..), State(..)) w
 
 import Abssyntax
 import Control.Monad.State hiding (State)
+import Control.Monad.Error
+import Control.Concurrent.MVar
 import Data.Map as Map
 import Prelude hiding (lookup)
 
@@ -17,11 +19,7 @@ instance Show Value where
 type Variables = [Map Ident Value]
 type Function = ([Decl],[Stm])
 
-data State = State {variables::Variables,functions::(Map Ident Function)}
-
-inList :: Eq a => a -> [a] -> Bool
-inList _ [] = False
-inList a (x:xs) = if a == x then True else inList a xs
+data State = State {variables::Variables,functions::(Map Ident Function),ret::(MVar Value)}
 
 --eval :: (MonadState Variables m) => Exp -> m Value
 eval :: Exp -> StateT State IO Value
@@ -32,7 +30,7 @@ eval (EAss i e) = setVariableValue i e
 eval (BiOpExp e o e') = do
        v <- eval e
        v'<- eval e'
-       if inList o [Eq,NEq] then return $ opE o v v'
+       if elem o [Eq,NEq] then return $ opE o v v'
                else let (VInt n1) = v in let (VInt n2) = v' in return $ op o n1 n2
 eval (EPost i o) = do
        (VInt n) <- getVariableValue i
@@ -50,11 +48,29 @@ eval EReadI = do
 eval EReadB = do
        s <- lift $ getWord
        return $ VBool $ if (read s == 0) then False else True
+eval (EFunc i as) = do
+       vs <- mapM eval as
+       state <- get
+       (ds,ss) <- lookup i $ functions state
+       modify (\s -> s{variables=[empty]})
+       addParams vs ds
+       mapM_ execute ss `catchError` (\_ -> return ())
+       put state
+       v <- lift $ takeMVar $ ret state
+       return v
+
+addParams :: [Value] -> [Decl] -> StateT State IO () 
+addParams [] [] = return ()
+addParams (v:vs) ((Decl t i):ds) = do
+       state <- get
+       let (m:ms) = variables state in modify (\s -> s{variables=insert i v m:ms })
+       addParams vs ds
+
 
 getWord :: IO String
 getWord =  do
        c <- getChar
-       if inList c [' ', '\n', '\t', '\r']
+       if elem c [' ', '\n', '\t', '\r']
                then return ""
                else do
                        l <- getWord
@@ -122,6 +138,11 @@ execute (SDecl t i e) =do
        v <- eval e
        state <- get
        let (m:ms) = variables state in modify (\s -> s{variables=insert i v m:ms })
+execute (SReturn e) = do
+       v <- eval e
+       s <- get
+       lift $ putMVar (ret s) v
+       throwError $ userError "Returning.."
 
 addFunction :: (MonadState State m) => Func -> m ()
 addFunction (Func _ i d ss) = modify (\s -> s{functions=insert i (d,ss) (functions s) })