diff --git a/Eval.hs b/Eval.hs
index 712aeffed0d73b9972a08678c1be2b06dd4e8293..da91f2fe77ef5520168476b04c4baca1650251de 100644
--- a/Eval.hs
+++ b/Eval.hs
@@ -1,8 +1,12 @@
-eval :: ResultEnvironment -> Expr -> Expr --only focus on one expression
-type Environment = ResultEnvironment
+module Eval where
+import Types
+import Debug
+
+eval :: 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)
     FuncCall func inputSets args -> case func of
@@ -19,9 +23,16 @@ eval env expr = let eval' = eval env in case expr of -- evaluates expression to
 
             --implement later
             --(Map) -> Set $ (map (\r -> FuncCall predicate [] [r]) inputRecords)
-        (FuncDef setParams argParams body) -> eval new_env body
+        (FuncDef setParams argParams body) -> eval newEnv body
             where
-                newEnv = foldl (\env entry@(name, expr) -> addVar env name expr) env --adds entries to environment
-                -- TODO FIx
+                newEnv = notImplemented
+                --newEnv = foldl (\env entry@(name, expr) -> addVar env name expr) env --adds entries to environment
+                -- TODO FIX
     (Var name) -> findVar env name
+
+    control@(Control lastResult exprs) -> if null exprs then lastResult else eval' $ evalControl1 env control
+
     _ -> 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
diff --git a/Interpreter.hs b/Interpreter.hs
index 2fe210e256f73daac1fd68b70bd35e4c8351a44c..15fe6089af57be3d78cfc415e74a20fba636c495 100644
--- a/Interpreter.hs
+++ b/Interpreter.hs
@@ -1,12 +1,35 @@
 import Types
 import Debug
+import Eval
 
-type Control = (ResultEnvironment, [Expr])
-type ResultEnvironment = [(SymbolName, Expr)] -- (result of last calculation, other bindings e.g. let statements)
+parse :: String -> Program
+parse = notImplemented
 
-prepare :: Program -> IO Control -- takes in the AST for the program, reads the csv files and prepares the environment based on the CSV files
-prepare (inputSets,instructions) = zipM (environment, return instructions)
-    where environment = fmap (zip inputSets) $ loadInputFiles inputSets
+--outline
+
+interpret :: String -> IO () -- the main function, takes in source code, prints out result
+interpret source = do
+    let program = parse source -- main abstract syntax tree
+    (env, mainExpr) <- prepare program
+    let output = eval env mainExpr
+    let finalOutput = evalFinal output
+    showFinal finalOutput
+
+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]
+    let env = zip inputSets csvData :: Environment
+    let mainExpr = Control (head csvData) instructions
+    return (env, mainExpr)
+    
+    where loadInputFiles = mapM loadInputFile
+
+
+evalFinal :: Expr -> Expr -- whnf set to ready set
+evalFinal = notImplemented
+
+showFinal :: Expr -> IO ()
+showFinal = notImplemented
 
 ---eval :: Control -> Expr -- fully evaluates the program, returning a set
 zipM (a,b) = do
@@ -18,14 +41,17 @@ zipM (a,b) = do
 
 --------------------------------------------
 
-programStep :: Control -> Control -- updates environment and list
-programStep = notImplemented
-
 
 --------------------------------------------
+loadInputFile :: SymbolName -> IO Expr
+loadInputFile name = do
+    rawData <- readCSV (name ++ ".csv") :: IO [[String]]
+    let output = Set $ map toRecord rawData
+    return output
+
+    where
+        toRecord stringList = Record $ map String stringList
 
-loadInputFiles :: [String] -> IO [[String]]
-loadInputFiles = mapM readCSV
 
 readCSV :: FilePath -> IO [[String]]
-readCSV _ = error ""
\ No newline at end of file
+readCSV = notImplemented
\ No newline at end of file
diff --git a/Types.hs b/Types.hs
index 54db017b2fc199284f2878a17a07c3e6d2885930..d5690df4eeafa7ba5d7e01925c7fa607f4a1cf1e 100644
--- a/Types.hs
+++ b/Types.hs
@@ -3,7 +3,7 @@ type Program = (InputSymbols,Output)
 
 type SymbolName = String
 type InputSymbols = [String] -- .in section
---type Output = [OutputLine] -- .out section
+type Environment = [(SymbolName, Expr)] -- (result of last calculation, other bindings e.g. let statements)
 
 --data OutputLine = Let SymbolName Expr | Expr -- Expr always a function call for a set function, but not enforced by AST.
 type Output = [Expr]
@@ -20,8 +20,10 @@ data PredefFunc = XProduct | XXProduct | IsEqual | IsNotEqual | Add --operators
 
 -- filter [A] (\(r) -> r[1] == "hello")
 -- FuncCall (PredefFunc Filter) [Var "A"] [FuncDef [] ["r"] [(FuncCall (PredefFunc IsEqual) [] (r[1]) ("hello"))]]
-data Expr = FuncCall {func::Expr, inputSets::[Expr], args::[Expr]} -- args: function to call, input sets, extra argument. Applicable for all kinds of functions: the set functions e.g. filter, map or simple functions or even the operators e.g. ==, /= ! We don't define separate expr for each operator
-    -- | FuncDef {name::SymbolName, inputSetNames::[SymbolName], argsNames::[SymbolName], body::Expr} -- function definition
+
+data Expr = Control Expr [Expr] -- result of last computation, sequence of instructions
+    | FuncCall {func::Expr, inputSets::[Expr], args::[Expr]} -- args: function to call, input sets, extra argument. Applicable for all kinds of functions: the set functions e.g. filter, map or simple functions or even the operators e.g. ==, /= ! We don't define separate expr for each operator
+
     | FuncDef {inputSetNames::[SymbolName], argsNames::[SymbolName], body::Expr} -- function definition
     | If Expr Expr Expr
     | Set [Expr]