aboutsummaryrefslogtreecommitdiff
path: root/src/Micro/Env.hs
diff options
context:
space:
mode:
authorJuan J. Martinez <jjm@usebox.net>2022-09-07 16:26:50 +0100
committerJuan J. Martinez <jjm@usebox.net>2022-09-07 16:26:50 +0100
commit65c8beecb14f6d09c49504d74beedd58cc7ddd17 (patch)
tree0a39cc6fc3f78153272c6528300936c039351d3e /src/Micro/Env.hs
parent48896c56c39344fa429260d3969eccc93ef8035c (diff)
downloadmicro-lang-hs-65c8beecb14f6d09c49504d74beedd58cc7ddd17.tar.gz
micro-lang-hs-65c8beecb14f6d09c49504d74beedd58cc7ddd17.zip
Better project layout, removed warnings
Diffstat (limited to 'src/Micro/Env.hs')
-rw-r--r--src/Micro/Env.hs63
1 files changed, 63 insertions, 0 deletions
diff --git a/src/Micro/Env.hs b/src/Micro/Env.hs
new file mode 100644
index 0000000..4174158
--- /dev/null
+++ b/src/Micro/Env.hs
@@ -0,0 +1,63 @@
+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)
+
+type Sym = (A.Ident, A.Type, Bool, SourcePos)
+
+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@(id, _, _, _) = case getSym env id of
+ Nothing -> Env (Map.insert id sym m) parent
+ Just _ -> Env (Map.singleton id 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 (id, typ, priv, pos) = case getSyml ev id of
+ Nothing -> Right $ addSym ev sym
+ Just (_, _, _, p) -> Left $ Error AlreadyDefined ("symbol \"" ++ id ++ "\" already defined in " ++ show p) pos
+ where
+ sym = (id, typ, priv, pos)