diff --git a/src/Push.hs b/src/Push.hs index 0dcc55a..a609d7e 100644 --- a/src/Push.hs +++ b/src/Push.hs @@ -1,6 +1,7 @@ module Push where -- import Debug.Trace (trace, traceStack) +import qualified Data.Map as Map -- The exec stack must store heterogenous types, -- and we must be able to detect that type at runtime. @@ -12,6 +13,7 @@ data Gene | BoolGene Bool | StringGene String | StateFunc (State -> State) + | PlaceInput String | Close | Block [Gene] @@ -21,7 +23,8 @@ data State = State float :: [Float], bool :: [Bool], string :: [String], - parameter :: [Gene] + parameter :: [Gene], + input :: Map.Map String Gene } emptyState :: State @@ -32,7 +35,8 @@ emptyState = float = [], bool = [], string = [], - parameter = [] + parameter = [], + input = Map.empty } -- Each core func should be: (State -> State -> State) @@ -41,41 +45,41 @@ emptyState = -- Everntually, this can be part of the apply func to state helpers, -- which should take the number and type of parameter they have. instructionIntAdd :: State -> State -instructionIntAdd (State es (i1 : i2 : is) fs bs ss ps) = State es (i2 + i1 : is) fs bs ss ps +instructionIntAdd (State es (i1 : i2 : is) fs bs ss ps im) = State es (i2 + i1 : is) fs bs ss ps im instructionIntAdd state = state instructionIntSub :: State -> State -instructionIntSub (State es (i1 : i2 : is) fs bs ss ps) = State es (i2 - i1 : is) fs bs ss ps +instructionIntSub (State es (i1 : i2 : is) fs bs ss ps im) = State es (i2 - i1 : is) fs bs ss ps im instructionIntSub state = state instructionIntMul :: State -> State -instructionIntMul (State es (i1 : i2 : is) fs bs ss ps) = State es (i2 * i1 : is) fs bs ss ps +instructionIntMul (State es (i1 : i2 : is) fs bs ss ps im) = State es (i2 * i1 : is) fs bs ss ps im instructionIntMul state = state instructionIntDiv :: State -> State -instructionIntDiv (State es (i1 : i2 : is) fs bs ss ps) = State es (i2 `div` i1 : is) fs bs ss ps +instructionIntDiv (State es (i1 : i2 : is) fs bs ss ps im) = State es (i2 `div` i1 : is) fs bs ss ps im instructionIntDiv state = state instructionExecIf :: State -> State -instructionExecIf (State (e1 : e2 : es) is fs (b : bs) ss ps) = +instructionExecIf (State (e1 : e2 : es) is fs (b : bs) ss ps im) = case b of - True -> State (e1 : es) is fs bs ss ps - False -> State (e2 : es) is fs bs ss ps + True -> State (e1 : es) is fs bs ss ps im + False -> State (e2 : es) is fs bs ss ps im instructionExecIf state = state -- This is one of the push genome functions itself, not infrastructure. -- Optionally, split this off into independent functions instructionParameterLoad :: State -> State -instructionParameterLoad (State es is fs bs ss (p : ps)) = case p of - (IntGene val) -> State es (val : is) fs bs ss ps - (FloatGene val) -> State es is (val : fs) bs ss ps - (BoolGene val) -> State es is fs (val : bs) ss ps - (StringGene val) -> State es is fs bs (val : ss) ps +instructionParameterLoad (State es is fs bs ss (p : ps) im) = case p of + (IntGene val) -> State es (val : is) fs bs ss ps im + (FloatGene val) -> State es is (val : fs) bs ss ps im + (BoolGene val) -> State es is fs (val : bs) ss ps im + (StringGene val) -> State es is fs bs (val : ss) ps im instructionParameterLoad state = state -- Loads a genome into the exec stack -loadProgarm :: [Gene] -> State -> State -loadProgarm newstack (State _ i f b s p) = State newstack i f b s p +loadProgram :: [Gene] -> State -> State +loadProgram newstack (State _ i f b s p im) = State newstack i f b s p im -- Takes a Push state, and generates the next push state via: -- If the first item on the EXEC stack is a single instruction @@ -88,14 +92,15 @@ loadProgarm newstack (State _ i f b s p) = State newstack i f b s p -- ends up on top). -- The empty-stack safety of interpretExec on empty stacks depends on the functions it calls. interpretExec :: State -> State -interpretExec (State [] is fs bs ss ps) = State [] is fs bs ss ps -interpretExec (State (e : es) is fs bs ss ps) = +interpretExec (State [] is fs bs ss ps im) = State [] is fs bs ss ps im +interpretExec (State (e : es) is fs bs ss ps im) = case e of - (IntGene val) -> interpretExec (State es (val : is) fs bs ss ps) - (FloatGene val) -> interpretExec (State es is (val : fs) bs ss ps) - (BoolGene val) -> interpretExec (State es is fs (val : bs) ss ps) - (StringGene val) -> interpretExec (State es is fs bs (val : ss) ps) - (StateFunc func) -> interpretExec (func (State es is fs bs ss ps)) - (Block block) -> interpretExec (State (block ++ es) is fs bs ss ps) + (IntGene val) -> interpretExec (State es (val : is) fs bs ss ps im) + (FloatGene val) -> interpretExec (State es is (val : fs) bs ss ps im) + (BoolGene val) -> interpretExec (State es is fs (val : bs) ss ps im) + (StringGene val) -> interpretExec (State es is fs bs (val : ss) ps im) + (StateFunc func) -> interpretExec (func (State es is fs bs ss ps im)) + (Block block) -> interpretExec (State (block ++ es) is fs bs ss ps im) + (PlaceInput input) -> interpretExec (State (im Map.! input : es) is fs bs ss ps im) -- Need to make interpretExec strict, right? diff --git a/src/Tests.hs b/src/Tests.hs index 2966ff9..1027dab 100644 --- a/src/Tests.hs +++ b/src/Tests.hs @@ -1,5 +1,6 @@ module Tests where +import qualified Data.Map as Map import Push exampleState = @@ -9,7 +10,8 @@ exampleState = float = [1.2, 1.7], bool = [True, False], string = ["Hello", "Push"], - parameter = [IntGene 1, StringGene "Hi", BoolGene True, FloatGene 1.3] + parameter = [IntGene 1, StringGene "Hi", BoolGene True, FloatGene 1.3], + input = Map.fromList [("in0" , IntGene 1)] } testResult1 = [8, 3] == int (instructionIntAdd exampleState) @@ -22,13 +24,16 @@ testResult4 = [3, 3] == int (instructionIntDiv exampleState) testResult5 = [6, 2, 6, 3] == int (interpretExec exampleState) -loadedState = loadProgarm [IntGene 6, IntGene 6, StateFunc instructionIntAdd] emptyState +loadedState = loadProgram [IntGene 6, IntGene 6, StateFunc instructionIntAdd] emptyState testResult6 = [12] == int (interpretExec loadedState) -loadedState2 = loadProgarm [BoolGene True, StateFunc instructionExecIf, Block [IntGene 5, IntGene 6], Block [IntGene 7, IntGene 8]] emptyState +loadedState2 = loadProgram [BoolGene True, StateFunc instructionExecIf, Block [IntGene 5, IntGene 6], Block [IntGene 7, IntGene 8]] emptyState testResult7 = [6, 5] == int (interpretExec loadedState2) -loadedState3 = loadProgarm [BoolGene False, StateFunc instructionExecIf, Block [IntGene 5, IntGene 6], Block [IntGene 7, IntGene 8]] emptyState +loadedState3 = loadProgram [BoolGene False, StateFunc instructionExecIf, Block [IntGene 5, IntGene 6], Block [IntGene 7, IntGene 8]] emptyState testResult8 = [8, 7] == int (interpretExec loadedState3) -allTests = and [testResult1, testResult2, testResult3, testResult4, testResult5, testResult6, testResult7, testResult8] \ No newline at end of file +loadedState4 = loadProgram [BoolGene False, PlaceInput "in0", StateFunc instructionIntAdd] exampleState +testResult9 = [3, 6, 3] == int (interpretExec loadedState4) + +allTests = and [testResult1, testResult2, testResult3, testResult4, testResult5, testResult6, testResult7, testResult8, testResult9]