]> ruin.nu Git - proglang.git/commitdiff
Interpreter works
authorMichael Andreen <harv@ruin.nu>
Sat, 11 Mar 2006 17:48:20 +0000 (17:48 +0000)
committerMichael Andreen <harv@ruin.nu>
Sat, 11 Mar 2006 17:48:20 +0000 (17:48 +0000)
Interpret.hs
Interpreter.hs
Typecheck.hs
examples/func

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) })
index 6cfbbda91af2804ac58cd53a96a1447e4dd1cea0..e41759db1c93d656391b6d0d53bf4c20193fb152 100644 (file)
@@ -14,6 +14,7 @@ import Abssyntax
 import Typecheck
 import Interpret
 import Control.Monad.State hiding (State)
+import Control.Concurrent.MVar
 import Data.Map as Map hiding (showTree)
 
 import ErrM
@@ -48,7 +49,8 @@ run v p s = let ts = myLLexer s in case p ts of
                runStateT (do mapM Typecheck.addFunction fun; mapM typeCheckFunction fun; mapM typeCheckStm st) Typecheck.emptyState
                print "The program is type-correct!!"
                print "Running program:"
-               runStateT (do mapM Interpret.addFunction fun; mapM execute st) Interpret.emptyState
+               mv <- newEmptyMVar
+               runStateT (do mapM Interpret.addFunction fun; mapM execute st) Interpret.emptyState{ret=mv}
                print "Done running program!"
                return ()
 
index a701b6e85bf92a0e9f0807251e5eecbfa83c7592..e2aa3d7182d61eef64d28b462efb2f3d9efde328 100644 (file)
@@ -13,10 +13,6 @@ data State = State {variables::Types,functions::(Map Ident Function),function::I
 
 emptyState = State{variables=[empty], functions=(empty), function=(Ident "")}
 
-inList :: Eq a => a -> [a] -> Bool
-inList _ [] = False
-inList a (x:xs) = if a == x then True else inList a xs
-
 assert :: Monad m => Bool -> String -> m ()
 assert True _ = return ()
 assert False s = fail s
@@ -26,10 +22,10 @@ typeCheckExp (BiOpExp e o e') = do
        t1 <- typeCheckExp e
        t2 <- typeCheckExp e'
        assert (t1 == t2) "The parameters for the binary operator aren't equal"
-       if inList o [Eq,NEq] then return TBool
+       if elem o [Eq,NEq] then return TBool
                else do 
                        assert (t1 == TInt) "The parameters need to be of type int" 
-                       if inList o [Plus,Minus,Times,Div]
+                       if elem o [Plus,Minus,Times,Div]
                                then return TInt
                                else return TBool
 typeCheckExp (EVar i) = typeCheckVar i
index 0f79e78090479f4a8eabe3ff9f79b2662b4392ba..ad56e85ef091ca28ed25891fe091ac8b219196c2 100644 (file)
@@ -2,6 +2,10 @@ int a = fac(3);
 int b = fib(2);
 int c = func(a,b);
 
+print a;
+print b;
+print c;
+
 if (boolfunc(b,c)) print true;
 
 int fac(int n){
@@ -12,15 +16,9 @@ int fac(int n){
 }
 
 int fib(int n){
-       int n1 = 0;
-       int n2 = 1;
+       if (n < 2) return 1;
 
-       while (n-- > 0){
-               int temp = n1+n2;
-               n1 = n2;
-               n2 = temp;
-       }
-       return n2;
+       return (fib(n-1)+fib(n-2));
 }
 
 int func(int a, int b){