Compare commits

...

3 Commits

Author SHA1 Message Date
Ivy c15a736236 Now when a var is evaluated, the new evaluation replaces the old 2021-01-30 00:55:05 +01:00
Ivy 2a351374a7 Strict evaluation when evaluating single variables 2021-01-30 00:43:52 +01:00
Ivy cde29b7fcc Changed module names 2021-01-30 00:11:03 +01:00
6 changed files with 14 additions and 16 deletions

View File

@ -19,12 +19,11 @@ executable cherry
default-language: Haskell2010
other-modules: ExprType,
ExprParser,
Parser,
TokenType,
TokenParser,
Lexer,
Evaluator,
ParserUtils,
TokenParser
ParserUtils
build-depends: base >= 4.7 && < 5,
containers,

View File

@ -4,11 +4,9 @@ import qualified Data.Map as M
import ExprType
type Env = M.Map String Expr
type Proc = String
-- TODO: create a separated file for builtinProcs
-- TODO: create a BuiltinProc or something like that in data Expr, and make + a builtin proc
-- TODO: create enviroments
base :: Env
base = M.fromList [
@ -17,7 +15,8 @@ base = M.fromList [
eval :: Env -> Expr -> (Env, Expr)
eval env (IntE x) = (env, IntE x)
eval env (VarE v) = (env, env M.! v)
eval env (VarE v) = (M.insert v nExpr nEnv, nExpr)
where (nEnv, nExpr) = eval env $ env M.! v
eval env (SetE v expr) = (M.insert v expr env, NilE)
eval env NilE = (env, NilE)

View File

@ -4,9 +4,9 @@ data Expr = IntE Integer
| VarE String
| ProcedureE String [Expr]
| SetE String Expr
| NilE
| NilE deriving (Show)
instance Show Expr where
show (IntE x) = show x
show (VarE x) = x ++ " ; var"
show NilE = "nil"
-- instance Show Expr where
-- show (IntE x) = show x
-- show (VarE x) = x ++ " ; var"
-- show NilE = "nil"

View File

@ -1,4 +1,4 @@
module TokenParser where
module Lexer where
import Text.ParserCombinators.Parsec
import ParserUtils

View File

@ -1,7 +1,7 @@
module Main where
import Evaluator
import ExprParser
import Parser
import Control.Monad
import Data.Maybe
import System.Console.Haskeline

View File

@ -1,8 +1,8 @@
module ExprParser where
module Parser where
import Text.Parsec
import Text.Parsec.String
import TokenParser
import Lexer
import TokenType
import ExprType