Merge branch 'master' of https://github.com/dopefishh/cc1516
[cc1516.git] / sem.icl
diff --git a/sem.icl b/sem.icl
index 727fc1e..820e45d 100644 (file)
--- a/sem.icl
+++ b/sem.icl
@@ -18,11 +18,11 @@ import StdString
 import StdTuple
 import StdList
 import StdBool
+import GenEq
 
 from Text import class Text(concat), instance Text String
 
 import AST
-from parse import :: ParserOutput, :: Error
 
 :: Gamma :== ('Map'.Map String Type, [String])
 :: Env a :== StateT Gamma (Either SemError) a
@@ -32,7 +32,7 @@ from parse import :: ParserOutput, :: Error
 instance MonadTrans (StateT Gamma) where
     liftT m = StateT \s-> m >>= \a-> return (a, s)
 
-get = gets id
+get :== gets id
 
 sem :: AST -> SemOutput
 sem (AST vd fd) = case runStateT m ('Map'.newMap, getRandomStream 1) of
@@ -40,27 +40,79 @@ sem (AST vd fd) = case runStateT m ('Map'.newMap, getRandomStream 1) of
     Right ((vds, fds), gamma) = Right ((AST vds fds), gamma)
 where 
     m :: Env ([VarDecl], [FunDecl])
-    m = mapM semVarDecl vd >>= \vds ->
-        mapM semFunDecl fd >>= \fds -> 
-        pure (vds, fds)
+    m = mapM semVarDecl vd >>= \vd1 ->
+        mapM semFunDecl fd >>= \fd1 -> 
+//     mapM semVarDecl vd1 >>= \vd2 ->
+//        mapM semFunDecl fd1 >>= \fd2 -> 
+//     mapM semVarDecl vd2 >>= \vd3 ->
+//        mapM semFunDecl fd2 >>= \fd3 -> 
+//     mapM semVarDecl vd3 >>= \vd4 ->
+//        mapM semFunDecl fd3 >>= \fd4 ->  //Dit is puur om te proberen
+        pure (vd1, fd1)
 
 semFunDecl :: FunDecl -> Env FunDecl
 semFunDecl fd=:(FunDecl p f args mt vds stmts) = 
-    saveGamma >>= \gamma ->
     (case mt of
-        Nothing = let t = IdType f in putIdent f t >>| pure t
+        Nothing = genType args >>= \infft->putIdent f infft >>| pure infft
         Just t = putIdent f t >>| pure t) >>= \ft ->
-       matchFunctions args ft >>|
+    saveGamma >>= \gamma ->
+       matchFunctions args ft >>= \tres->
     mapM semVarDecl vds >>= \newvds->
-    mapM_ (checkStmt $ resultType ft) stmts >>| 
-    restoreGamma gamma >>| 
-       pure (FunDecl p f args mt newvds stmts) 
-
-matchFunctions :: [String] Type -> Env Void
-matchFunctions [] (_ ->> _) = liftT $ Left $ Error "Niet genoeg argumentenerror"
-matchFunctions [] t = pure Void
+    mapM (checkStmt tres) stmts >>= \newstmts->
+       inferReturnType stmts >>= \returntype`->
+       unify returntype` tres >>= \returntype->
+       case mt of
+               Nothing = reconstructType args tres
+                       >>= \ftype`->recoverType ftype`
+                       >>= \ftype->restoreGamma gamma 
+                       >>| putIdent f ftype >>| pure (
+                       FunDecl p f args (Just ftype) newvds newstmts)
+               Just t = restoreGamma gamma >>| updateFunType t returntype
+                       >>= \tt-> pure (FunDecl p f args (Just tt) newvds newstmts) 
+
+recoverType :: Type -> Env Type
+recoverType (IdType ident) = gets (\(st, r)->'Map'.get ident st)
+       >>= \mt->case mt of
+               Nothing = pure (IdType ident)
+               Just t = pure t
+recoverType (t1 ->> t2) = recoverType t1 >>= \t1`->recoverType t2 
+       >>= \t2`->pure (t1` ->> t2`) 
+recoverType t = pure t
+
+updateFunType :: Type Type -> Env Type
+updateFunType t1 t2 = unify t1 t2
+updateFunType (t1 ->> t2) t3 = t1 ->> (updateFunType t2 t3)
+
+inferReturnType :: [Stmt] -> Env Type
+inferReturnType [] = pure VoidType
+inferReturnType [ReturnStmt (Just t):rest] = typeExpr t 
+       >>= \tx->inferReturnType rest >>= \ty->unify tx ty
+inferReturnType [ReturnStmt _:rest] = 
+       inferReturnType rest >>= \tx-> unify VoidType tx
+inferReturnType [_:rest] = inferReturnType rest
+
+reconstructType :: [String] Type -> Env Type
+reconstructType [] t = pure t
+reconstructType [x:xs] t = gets (\(st, r)->'Map'.get x st)
+       >>= \mtype->case mtype of
+               Nothing = liftT $ Left $ Error "Not used ????"
+               Just type = reconstructType xs t >>= \resttype->pure (type ->> resttype)
+
+genType :: [String] -> Env Type
+genType [] = freshIdent >>= \fi->pure $ IdType fi
+genType [x:xs] = liftM2 (->>) (freshIdent >>= \fi->pure $ IdType fi)
+       (genType xs)
+
+matchFunctions :: [String] Type -> Env Type
+matchFunctions [] (_ ->> _) = liftT $ Left $ 
+       ArgumentMisMatchError zero "Not enough arguments"
+matchFunctions _ (VoidType ->> _) = liftT $ Left $ 
+       ArgumentMisMatchError zero "Void can't be a non return type"
 matchFunctions [x:xs] (t1 ->> t2) = 
        modify (\(st, r)->('Map'.put x t1 st, r)) >>| matchFunctions xs t2
+matchFunctions [] t = pure t
+matchFunctions _ t = liftT $ Left $ 
+       ArgumentMisMatchError zero "Too much argumnts"
 
 semVarDecl :: VarDecl -> Env VarDecl
 semVarDecl (VarDecl pos type ident ex) = unify type ex
@@ -71,7 +123,10 @@ checkStmt t (IfStmt c st se) = unify BoolType c >>| mapM (checkStmt t) st
     >>= \st1-> mapM (checkStmt t) se >>= \se1-> pure (IfStmt c st1 se1)
 checkStmt t w=:(WhileStmt c et) = unify BoolType c >>| mapM (checkStmt t) et
     >>= \et1-> pure w
-checkStmt t (AssStmt (VarDef ident fs) e) = undef
+checkStmt t a=:(AssStmt (VarDef ident fs) e) = gets (\(st, r)->'Map'.get ident st)
+    >>= \mt->case mt of
+        Nothing = liftT $ Left $ UndeclaredVariableError zero ident
+        Just t = unify t fs >>= \t1 -> unify t1 e >>| pure a
 checkStmt t r=:(FunStmt (FunCall f es)) = typeFun f es >>| pure r
 checkStmt VoidType r=:(ReturnStmt Nothing) = pure r
 checkStmt t r=:(ReturnStmt (Just e)) = unify t e >>| pure r
@@ -102,10 +157,9 @@ typeExpr (VarExpr p (VarDef ident fs)) = gets (\(st, r)->'Map'.get ident st)
     >>= \mt->case mt of
         Nothing = liftT $ Left $ UndeclaredVariableError p ident
         Just t = unify t fs
-
 typeOp2 :: Expr Expr Op2 [Type] Type -> Env Type
 typeOp2 e1 e2 op ts ret = typeExpr e1 >>= \t1-> typeExpr e2 >>= \t2->
-    unify t1 t2 >>= \t3->if (isMember t3 ts) (pure ret)
+    unify t1 t2 >>= \t3->if (isMember t3 [IdType "":ts]) (pure ret)
         (liftT $ Left $ OperatorError (extrPos e1) op t3)
 
 buildFunctionType :: String [Expr] -> Env Type 
@@ -142,10 +196,12 @@ instance unify Expr where
                        "Expression cannot be a higher order function. Yet..."
        unify VoidType e = liftT $ Left $ ParseError (extrPos e)
                        "Expression cannot be a Void type."
-       unify (IdType _) e = liftT $ Left $ ParseError (extrPos e)
-                       "Expression cannot be an polymorf type."
+//     unify (IdType _) e = liftT $ Left $ ParseError (extrPos e)
+//                     "Expression cannot be an polymorf type."
     unify VarType e = typeExpr e
     //we have to cheat to decorate the error, can be done nicer?
+       unify t=:(IdType id) e = typeExpr e >>= \tex->unify t tex
+               >>= \type->putIdent id type >>| pure type
     unify t e = StateT $ \s0 -> let res = runStateT m s0 in case res of
         Left err = Left $ decErr e err
         Right t = Right t //note, t :: (Type, Gamma) 
@@ -161,6 +217,9 @@ instance unify Type where
     unify (ListType t1) (ListType t2) = unify t1 t2 >>| (pure $ ListType t1)
     unify (ta1 ->> ta2) (tb1 ->> tb2) = unify ta1 tb1 >>= \ta-> unify ta2 tb2 
         >>= \tb-> pure (ta ->> tb)
+    unify VoidType t = pure t
+    unify t VoidType = pure t
+    unify VoidType VoidType = pure VoidType
        unify t1 t2 = liftT $ Left $ UnifyError zero t1 t2
 
 instance zero Pos where
@@ -224,15 +283,12 @@ replace ident type = get >>= \(st, fr)->put ('Map'.fromList $
         itupdate _ _ k = k
 
 instance toString SemError where
-    toString (ParseError p e) = concat [
-        toString p,"SemError: ParseError: ", e]
-    toString (Error e) = "SemError: " +++ e
-    toString (UnifyError p t1 t2) = concat [
-        toString p,
+    toString (ParseError p e) = concat [toString p,
+               "SemError: ParseError: ", e]
+    toString (UnifyError p t1 t2) = concat [ toString p,
         "SemError: Cannot unify types. Expected: ",
         toString t1, ". Given: ", toString t2]
-    toString (FieldSelectorError p t fs) = concat [
-        toString p,
+    toString (FieldSelectorError p t fs) = concat [ toString p,
         "SemError: Cannot select ", toString fs, " from type: ",
         toString t]
     toString (OperatorError p o t) = concat [
@@ -241,9 +297,17 @@ instance toString SemError where
         toString t]
     toString (UndeclaredVariableError p ident) = concat [
         toString p, "SemError: identifier: ", ident, " undefined."]
+    toString (ArgumentMisMatchError p s) = concat [toString p,
+               "SemError: Argument mismatch: ", s]
+    toString (Error e) = "SemError: " +++ e
 
 saveGamma :: Env Gamma
 saveGamma = get
 
 restoreGamma :: Gamma -> Env Void
-restoreGamma g = put g
+restoreGamma (oldstate, _) = gets snd >>= \newr->put (oldstate, newr)
+
+derive gEq Type
+instance == Type where 
+       (==) (IdType _) (IdType _) = True
+       (==) o1 o2 = gEq{|*|} o1 o2