aboutsummaryrefslogtreecommitdiff
path: root/src/Env.hs
blob: bf818992cbceb8f9a4fa79d0b46939dda9c6b8ed (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

-- first parameter tells 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

-- get symbol
getSym :: Env -> A.Ident -> Maybe Sym
getSym = getSymB False

-- get symbol local
getSyml :: Env -> A.Ident -> Maybe Sym
getSyml = getSymB True

-- if a symbol exists
existsSym :: Env -> A.Ident -> Bool
existsSym env sym = isJust $ getSym env sym

-- if a local symbol exists
existsSyml :: Env -> A.Ident -> Bool
existsSyml env sym = isJust $ getSyml env sym

-- add symbol
addSym :: Env -> Sym -> Env
addSym (Env m parent) (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
  where
    env = (Env m parent)
    sym = (id, typ, pos)

-- adds a new local environment
addEnv :: Env -> Env
addEnv env = Env Map.empty $ Just env

-- add a local symbol 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 ("\"" ++ id ++ "\" already defined in " ++ show p) pos
  where
    sym = (id, typ, pos)