change to lens
This commit is contained in:
parent
34bf6b38bd
commit
346cd96d67
48
src/State.hs
48
src/State.hs
@ -1,6 +1,8 @@
|
|||||||
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
module State where
|
module State where
|
||||||
|
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
|
import Control.Lens
|
||||||
|
|
||||||
-- The exec stack must store heterogenous types,
|
-- The exec stack must store heterogenous types,
|
||||||
-- and we must be able to detect that type at runtime.
|
-- and we must be able to detect that type at runtime.
|
||||||
@ -50,33 +52,35 @@ instance Show Gene where
|
|||||||
show (Block xs) = "Block: " <> show xs
|
show (Block xs) = "Block: " <> show xs
|
||||||
|
|
||||||
data State = State
|
data State = State
|
||||||
{ exec :: [Gene],
|
{ _exec :: [Gene],
|
||||||
int :: [Int],
|
_int :: [Int],
|
||||||
float :: [Float],
|
_float :: [Float],
|
||||||
bool :: [Bool],
|
_bool :: [Bool],
|
||||||
string :: [String],
|
_string :: [String],
|
||||||
vectorInt :: [[Int]],
|
_intVector :: [[Int]],
|
||||||
vectorFloat :: [[Float]],
|
_floatVector :: [[Float]],
|
||||||
vectorBool :: [[Bool]],
|
_boolVector :: [[Bool]],
|
||||||
vectorString :: [[String]],
|
_stringVector :: [[String]],
|
||||||
parameter :: [Gene],
|
_parameter :: [Gene],
|
||||||
input :: Map.Map String Gene
|
_input :: Map.Map String Gene
|
||||||
}
|
}
|
||||||
deriving (Show, Eq)
|
deriving (Show, Eq)
|
||||||
|
|
||||||
|
$(makeLenses ''State)
|
||||||
|
|
||||||
emptyState :: State
|
emptyState :: State
|
||||||
emptyState =
|
emptyState =
|
||||||
State
|
State
|
||||||
{ exec = [],
|
{ _exec = [],
|
||||||
int = [],
|
_int = [],
|
||||||
float = [],
|
_float = [],
|
||||||
bool = [],
|
_bool = [],
|
||||||
string = [],
|
_string = [],
|
||||||
parameter = [],
|
_parameter = [],
|
||||||
vectorInt = [],
|
_intVector = [],
|
||||||
vectorFloat = [],
|
_floatVector = [],
|
||||||
vectorBool = [],
|
_boolVector = [],
|
||||||
vectorString = [],
|
_stringVector = [],
|
||||||
input = Map.empty
|
_input = Map.empty
|
||||||
}
|
}
|
||||||
|
|
||||||
|
@ -10,12 +10,12 @@ import Instructions.FloatInstructions
|
|||||||
intTestFunc :: String -> [Int] -> [Gene] -> State -> IO ()
|
intTestFunc :: String -> [Int] -> [Gene] -> State -> IO ()
|
||||||
intTestFunc name goal genome startState =
|
intTestFunc name goal genome startState =
|
||||||
let state = loadProgram genome startState
|
let state = loadProgram genome startState
|
||||||
in assert (goal == int (interpretExec state)) putStrLn (name ++ " passed test.")
|
in assert (goal == _int (interpretExec state)) putStrLn (name ++ " passed test.")
|
||||||
|
|
||||||
floatTestFunc :: String -> [Float] -> [Gene] -> State -> IO ()
|
floatTestFunc :: String -> [Float] -> [Gene] -> State -> IO ()
|
||||||
floatTestFunc name goal genome startState =
|
floatTestFunc name goal genome startState =
|
||||||
let state = loadProgram genome startState
|
let state = loadProgram genome startState
|
||||||
in assert (goal == float (interpretExec state)) putStrLn (name ++ " passed test.")
|
in assert (goal == _float (interpretExec state)) putStrLn (name ++ " passed test.")
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
|
Loading…
x
Reference in New Issue
Block a user