module Micro.Env where import qualified Data.Map as Map import Data.Maybe (isJust) import qualified Micro.Ast as A import Micro.Error import Text.Parsec (SourcePos) data Sym = Sym { symId :: A.Ident, symType :: A.Type, symPriv :: Bool, symRef :: Bool, symPos :: SourcePos } deriving (Show) newSym :: A.Ident -> A.Type -> Bool -> Bool -> SourcePos -> Sym newSym a b c d e = Sym {symId = a, symType = b, symPriv = c, symRef = d, symPos = e} -- XXX: this name is not good toSym :: Bool -> A.FuncParam -> Sym toSym ref (a, b, c, d) = newSym a b c ref d type SymMap = Map.Map A.Ident Sym data Env = Env SymMap (Maybe Env) deriving (Show) emptyEnv :: Env emptyEnv = Env Map.empty Nothing -- | @getSymB local env ident@ checks @local@ parameter to tell if we look on -- the local environment or if we should check also in the parent(s). getSymB :: Bool -> Env -> A.Ident -> Maybe Sym getSymB local (Env m parent) id = case (local, Map.lookup id m) of (False, Nothing) -> do p <- parent getSym p id (_, s) -> s -- | Gets a symbol checking all the environments. getSym :: Env -> A.Ident -> Maybe Sym getSym = getSymB False -- | Gets a symbol checking the local environment. getSyml :: Env -> A.Ident -> Maybe Sym getSyml = getSymB True -- | Checks if a symbol exists. existsSym :: Env -> A.Ident -> Bool existsSym env sym = isJust $ getSym env sym -- | Checks if a local symbol exists in the local environment. existsSyml :: Env -> A.Ident -> Bool existsSyml env sym = isJust $ getSyml env sym -- | @addSym e s@ add symbol @s@ to enviroment @e@ and returns the modified -- environment. It will create a new enviroment if the symbol already exists -- (shadowing). addSym :: Env -> Sym -> Env addSym env@(Env m parent) sym = case getSym env (symId sym) of Nothing -> Env (Map.insert (symId sym) sym m) parent Just _ -> Env (Map.singleton (symId sym) sym) $ Just env -- | @addEnv e@ adds a new local environment using @e@ as parent. addEnv :: Env -> Env addEnv env = Env Map.empty $ Just env -- | @addSymUniq e s@ adds a local symbol @s@ to the enviroment @e@ if it -- doesn't exist. addSymUniq :: Env -> Sym -> Either Error Env addSymUniq ev sym = case getSyml ev (symId sym) of Nothing -> Right $ addSym ev sym Just other -> Left $ Error AlreadyDefined ("\"" ++ symId sym ++ "\" already defined in " ++ show (symPos other)) $ symPos sym