module Compiler where import qualified Ast as A import Control.Monad.State import Env import Error import System.Environment (getEnv, getEnvironment) import Text.Parsec (ParseError, SourcePos) import Text.Read (Lexeme (String)) toFuncType :: [A.FuncParam] -> Maybe A.Type -> A.Type toFuncType params rtyp = A.FuncType (map (\(_, t, _) -> t) params) rtyp type CompState = (Env, [Error]) type CompResult = Either [Error] () startState :: CompState startState = (emptyEnv, []) compile :: [A.Expr] -> State CompState CompResult compile (x : xs) = do case x of (A.Module name pos) -> return $ Right () (A.BinOp _ a b) -> compile [a, b] (A.Func ident params ret body priv pos) -> do -- current env (ev, errs) <- get -- with function and parameters (nev, nerrs) <- return $ case addSymUniq ev (ident, toFuncType params ret, pos) of Left e -> (ev, e : errs) Right fev -> foldl ( \(ev, errs) (id, typ, pos) -> case addSymUniq ev (id, typ, pos) of Right ev -> (ev, errs) Left nerr -> (ev, nerr : errs) ) (addEnv fev, errs) params put (nev, nerrs) r <- compile body (_, errs) <- get put (ev, errs) return r (A.Call ident args pos) -> do id <- compile [ident] return $ Right () (A.Return value pos) -> case value of Nothing -> return $ Right () Just v -> compile [v] (A.Var ident pos) -> do (ev, errs) <- get if existsSym ev ident then return $ Right () else do put (ev, Error ("undefined variable \"" ++ ident ++ "\"") pos : errs) return $ Right () _ -> compile [] compile xs compile [] = do (_, errs) <- get case errs of [] -> return $ Right () _ -> return $ Left errs