aboutsummaryrefslogtreecommitdiff
path: root/src/Env.hs
blob: d4c4fa37d5c97638846e8442807880efc6f93004 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
module Env where

import qualified Ast as A
import qualified Data.Map as Map
import Data.Maybe (isJust)
import Error
import Text.Parsec (SourcePos)

type Sym = (A.Ident, A.Type, SourcePos)

type SymMap = Map.Map A.Ident Sym

data Env = Env SymMap (Maybe Env) deriving (Show)

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, typ, pos) = case getSym env id of
  Nothing -> Env (Map.insert id sym m) parent
  Just s -> 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, 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, pos)