pure (vds, fds)
semFunDecl :: FunDecl -> Env FunDecl
-semFunDecl fd=:(FunDecl p f _ mt vds stmts) = mapM_ semVarDecl vds >>|
+semFunDecl fd=:(FunDecl p f args mt vds stmts) = (case mt of
+ Nothing = typeFun f args
+ Just t = putIdent f t) >>|
+ mapM_ semVarDecl vds >>|
mapM_ (checkStmt IntType) stmts >>|
case mt of
Nothing = let t = IdType f in putIdent f t >>| pure fd
>>= \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 r=:(FunStmt funcall) = typeFun funcall >>| pure r
+checkStmt t (AssStmt (VarDef ident fs) e) =
+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
>>= \t2-> unify (ListType t1) t2
typeExpr (EmptyListExpr p) = freshIdent >>= \frsh-> let t = IdType frsh in
putIdent frsh t >>| pure t
-typeExpr (FunExpr p funcall) = typeFun funcall
+typeExpr (FunExpr p (FunCall f es)) = typeFun f es
typeExpr (VarExpr p (VarDef ident fs)) = gets (\(st, r)->'Map'.get ident st)
>>= \mt->case mt of
Nothing = liftT $ Left $ UndeclaredVariableError p ident
instance zero Pos where
zero = {line=0,col=0}
-typeFun :: FunCall -> Env Type
-typeFun (FunCall f es) = gets (\(st, r)->'Map'.get f st) >>= \mt-> case mt of
+typeFun :: String [String] -> Env Type
+typeFun f es = gets (\(st, r)->'Map'.get f st) >>= \mt-> case mt of
Nothing = freshIdent >>= \frsh-> buildFunctionType frsh es
>>= \ft-> putIdent f ft >>| (pure $ IdType frsh)
Just t = unifyApp t es
+
+
decErr :: Expr SemError -> SemError
decErr e (UnifyError _ t1 t2) = UnifyError (extrPos e) t1 t2
decErr e (FieldSelectorError _ t fs) = FieldSelectorError (extrPos e) t fs
toString (mp, _) = concat
[concat [k, ": ", toString v, "\n"]\\(k, v) <- 'Map'.toList mp]
-
-// class free a :: a -> Env [a]