Skip to content

Commit

Permalink
Merge branch '103-parse-expr' of github.com:EpitechPromo2027/B-FUN-50…
Browse files Browse the repository at this point in the history
…0-BAR-5-2-glados-oriol.linan into 103-parse-expr
  • Loading branch information
RenzoMaggiori committed Jan 7, 2025
2 parents 1495f4b + 95c6627 commit b91b197
Show file tree
Hide file tree
Showing 3 changed files with 24 additions and 6 deletions.
6 changes: 3 additions & 3 deletions glados.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -66,12 +66,12 @@ test-suite glados-test
default-language: Haskell2010
type: exitcode-stdio-1.0
other-modules:
Ast.ParserSpec
Ast.Parser.TypeSpec
Ast.Parser.TypeDefinitionSpec
Ast.Parser.LiteralSpec
Ast.Parser.OperationSpec
Ast.Parser.TypeDefinitionSpec
Ast.Parser.TypeSpec
Ast.Parser.UnaryOperationSpec
Ast.ParserSpec
Misc.MiscSpec

hs-source-dirs: test
Expand Down
13 changes: 10 additions & 3 deletions lib/Ast/Parser/Env.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,13 +3,14 @@ module Ast.Parser.Env where
import qualified Ast.Types as AT

-- | The environment for storing custom type definitions.
newtype Env = Env
{ types :: [(String, AT.Type)]
data Env = Env
{ types :: [(String, AT.Type)],
vars :: [(String, AT.Type)]
}

-- | Creates an empty environment.
emptyEnv :: Env
emptyEnv = Env []
emptyEnv = Env {types = [], vars = []}

-- | Inserts a custom type into the environment.
-- If the type already exists, it overwrites it.
Expand All @@ -19,3 +20,9 @@ insertType name t env = env {types = (name, t) : types env}
-- | Looks up a custom type in the environment by its name.
lookupType :: String -> Env -> Maybe AT.Type
lookupType name env = lookup name $ types env

insertVar :: String -> AT.Type -> Env -> Env
insertVar name t env = env {vars = (name, t) : vars env}

lookupVar :: String -> Env -> Maybe AT.Type
lookupVar name env = lookup name $ vars env
11 changes: 11 additions & 0 deletions lib/Ast/Parser/Expr.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,10 @@
module Ast.Parser.Expr where

import qualified Ast.Parser.Env as E
import qualified Ast.Parser.Literal as PL
import qualified Ast.Parser.Utils as PU
import qualified Ast.Types as AT
import qualified Control.Monad.State as S
import qualified Text.Megaparsec as M
import qualified Text.Megaparsec.Pos as MP

Expand All @@ -15,6 +17,15 @@ parseLit = do
srcLoc <- parseSrcLoc
return $ AT.Lit srcLoc lit

parseVar :: PU.Parser AT.Expr
parseVar = do
name <- PU.lexeme PU.identifier
srcLoc <- parseSrcLoc
env <- S.get
case E.lookupVar name env of
(Just t) -> return $ AT.Var srcLoc name t
_ -> fail ""

parseSrcLoc :: PU.Parser AT.SrcLoc
parseSrcLoc = do
(MP.SourcePos {MP.sourceName = _sourceName, MP.sourceLine = _sourceLine, MP.sourceColumn = _sourceColumn}) <- M.getSourcePos
Expand Down

0 comments on commit b91b197

Please # to comment.