diff --git a/Eval.hs b/Eval.hs index da91f2fe77ef5520168476b04c4baca1650251de..8e95c1f92dc34cd932b1766d4325ccd3f58fe136 100644 --- a/Eval.hs +++ b/Eval.hs @@ -2,21 +2,21 @@ module Eval where import Types import Debug -eval :: Environment -> Expr -> Expr --only focus on one expression +eval, evalFull :: Environment -> Expr -> Expr --only focus on one expression findVar :: Environment -> SymbolName -> Expr findVar = notImplemented addVar :: Environment -> SymbolName -> Expr -> Environment addVar = notImplemented -eval env expr = let eval' = eval env in case expr of -- evaluates expression to weak-head normal form (i.e. top level data structure is not a FuncCall) +eval env expr = let (eval', evalFull') = (eval env, evalFull env) in case expr of -- evaluates expression to weak-head normal form (i.e. top level data structure is not a FuncCall) FuncCall func inputSets args -> case func of (PredefFunc f) -> case f of (Filter) -> let (Set inputRecords,predicate) = (eval' $ head inputSets, eval' $ head args) in Set $ filter ((==Boolean True).eval')(map (\r -> FuncCall predicate [] [r]) inputRecords) -- result is weak-head normal form --Set $ map (eval env) (map (\r -> FuncCall predicate [] [r]) inputRecords) # don't evaluate last step - (IsEqual) -> let (e1:e2:_) = args in - Boolean (eval' e1 == eval' e2) + (IsEqual) -> let (e1:e2:_) = args in -- TODO not sufficent. + Boolean (evalFull' e1 == evalFull' e2) (RecordIndex) -> let (Record recordData, Int index) = (eval' $ args !! 0, eval' $ args !! 1) in recordData !! index @@ -25,7 +25,7 @@ eval env expr = let eval' = eval env in case expr of -- evaluates expression to --(Map) -> Set $ (map (\r -> FuncCall predicate [] [r]) inputRecords) (FuncDef setParams argParams body) -> eval newEnv body where - newEnv = notImplemented + newEnv = let (setEnv, argsEnv) = (zip setParams inputSets, zip argParams args) in setEnv ++ argsEnv ++ env --newEnv = foldl (\env entry@(name, expr) -> addVar env name expr) env --adds entries to environment -- TODO FIX (Var name) -> findVar env name @@ -35,4 +35,7 @@ eval env expr = let eval' = eval env in case expr of -- evaluates expression to _ -> expr evalControl1 :: Environment -> Expr -> Expr -evalControl1 env (Control _ (currentExpr:exprs)) = let output = eval env currentExpr in Control output exprs \ No newline at end of file +evalControl1 env (Control _ (currentExpr:exprs)) = let output = eval env currentExpr in Control output exprs + +evalFull = eval -- evaluates expression fully (not just weak head normal form) +--TODO implement properly \ No newline at end of file diff --git a/Interpreter.hs b/Interpreter.hs index 15fe6089af57be3d78cfc415e74a20fba636c495..ec36d026de26741a7462a7fe658c655b94b6af0e 100644 --- a/Interpreter.hs +++ b/Interpreter.hs @@ -1,14 +1,16 @@ import Types import Debug import Eval +import System.IO parse :: String -> Program parse = notImplemented --outline -interpret :: String -> IO () -- the main function, takes in source code, prints out result -interpret source = do +interpret :: FilePath -> IO () -- the main function, takes in file name, prints out result +interpret sourceFName = do + source <- readFile sourceFName let program = parse source -- main abstract syntax tree (env, mainExpr) <- prepare program let output = eval env mainExpr @@ -17,27 +19,21 @@ interpret source = do prepare :: Program -> IO (Environment, Expr) -- takes in the AST for the program, reads the csv files and prepares the environment based on the CSV files prepare (inputSets,instructions) = do - csvData <- loadInputFiles inputSets ::IO [Expr] + csvData <- loadInputFiles inputSets ::IO [Expr] let env = zip inputSets csvData :: Environment let mainExpr = Control (head csvData) instructions return (env, mainExpr) - where loadInputFiles = mapM loadInputFile + where + loadInputFiles = mapM loadInputFile evalFinal :: Expr -> Expr -- whnf set to ready set -evalFinal = notImplemented +evalFinal = evalFull [] showFinal :: Expr -> IO () showFinal = notImplemented ----eval :: Control -> Expr -- fully evaluates the program, returning a set -zipM (a,b) = do - a' <- a - b' <- b - return (a',b') - ---pairmap f s = (s, fs) --------------------------------------------