added many functions and tests
This commit is contained in:
parent
eb8fd95756
commit
31d54641bc
79
src/Push.hs
79
src/Push.hs
@ -1,4 +1,3 @@
|
|||||||
{-# LANGUAGE DataKinds #-}
|
|
||||||
module Push where
|
module Push where
|
||||||
|
|
||||||
-- import Debug.Trace (trace, traceStack)
|
-- import Debug.Trace (trace, traceStack)
|
||||||
@ -48,7 +47,7 @@ data State = State
|
|||||||
parameter :: [Gene],
|
parameter :: [Gene],
|
||||||
input :: Map.Map String Gene
|
input :: Map.Map String Gene
|
||||||
}
|
}
|
||||||
deriving Show
|
deriving (Show, Eq)
|
||||||
|
|
||||||
emptyState :: State
|
emptyState :: State
|
||||||
emptyState =
|
emptyState =
|
||||||
@ -83,6 +82,46 @@ instructionIntDiv :: State -> State
|
|||||||
instructionIntDiv (State es (i1 : i2 : is) fs bs ss ps im) = State es (i2 `div` i1 : is) fs bs ss ps im
|
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
|
instructionIntDiv state = state
|
||||||
|
|
||||||
|
instructionIntMod :: State -> State
|
||||||
|
instructionIntMod (State es (i1 : i2 : is) fs bs ss ps im) = State es (i2 `mod` i1 : is) fs bs ss ps im
|
||||||
|
instructionIntMod state = state
|
||||||
|
|
||||||
|
instructionIntMin :: State -> State
|
||||||
|
instructionIntMin state@(State es (i1 : i2 : is) fs bs ss ps im) = state {int = min i1 i2 : is}
|
||||||
|
instructionIntMin state = state
|
||||||
|
|
||||||
|
instructionIntMax :: State -> State
|
||||||
|
instructionIntMax state@(State es (i1 : i2 : is) fs bs ss ps im) = state {int = max i1 i2 : is}
|
||||||
|
instructionIntMax state = state
|
||||||
|
|
||||||
|
instructionIntInc :: State -> State
|
||||||
|
instructionIntInc state@(State es (i1 : is) fs bs ss ps im) = state {int = i1 + 1 : is}
|
||||||
|
instructionIntInc state = state
|
||||||
|
|
||||||
|
instructionIntDec :: State -> State
|
||||||
|
instructionIntDec state@(State es (i1 : is) fs bs ss ps im) = state {int = i1 - 1 : is}
|
||||||
|
instructionIntDec state = state
|
||||||
|
|
||||||
|
instructionIntLT :: State -> State
|
||||||
|
instructionIntLT state@(State es (i1 : i2 : is) fs bs ss ps im) = state {int = is, bool = (i1 < i2) : bs}
|
||||||
|
instructionIntLT state = state
|
||||||
|
|
||||||
|
instructionIntGT :: State -> State
|
||||||
|
instructionIntGT state@(State es (i1 : i2 : is) fs bs ss ps im) = state {int = is, bool = (i1 > i2) : bs}
|
||||||
|
instructionIntGT state = state
|
||||||
|
|
||||||
|
instructionIntLTE :: State -> State
|
||||||
|
instructionIntLTE state@(State es (i1 : i2 : is) fs bs ss ps im) = state {int = is, bool = (i1 <= i2) : bs}
|
||||||
|
instructionIntLTE state = state
|
||||||
|
|
||||||
|
instructionIntGTE :: State -> State
|
||||||
|
instructionIntGTE state@(State es (i1 : i2 : is) fs bs ss ps im) = state {int = is, bool = (i1 >= i2) : bs}
|
||||||
|
instructionIntGTE state = state
|
||||||
|
|
||||||
|
instructionIntPop :: State -> State
|
||||||
|
instructionIntPop state@(State es (i1 : is) fs bs ss ps im) = state {int = is}
|
||||||
|
instructionIntPop state = state
|
||||||
|
|
||||||
instructionExecIf :: State -> State
|
instructionExecIf :: State -> State
|
||||||
instructionExecIf (State (e1 : e2 : es) is fs (b : bs) ss ps im) =
|
instructionExecIf (State (e1 : e2 : es) is fs (b : bs) ss ps im) =
|
||||||
case b of
|
case b of
|
||||||
@ -108,6 +147,42 @@ instructionExecDoRange (State (e1 : es) (i0 : i1 : is) fs bs ss ps im) =
|
|||||||
| otherwise = 0
|
| otherwise = 0
|
||||||
instructionExecDoRange state = state
|
instructionExecDoRange state = state
|
||||||
|
|
||||||
|
instructionExecDoCount :: State -> State
|
||||||
|
instructionExecDoCount state@(State (e1 : es) (i1 : is) fs bs ss ps im) =
|
||||||
|
if i1 < 1
|
||||||
|
then state
|
||||||
|
else state {exec = Block [IntGene 0, IntGene $ i1 - 1, StateFunc instructionExecDoRange, e1] : es, int = is}
|
||||||
|
instructionExecDoCount state = state
|
||||||
|
|
||||||
|
instructionExecDoTimes :: State -> State
|
||||||
|
instructionExecDoTimes state@(State (e1 : es) (i1 : is) fs bs ss ps im) =
|
||||||
|
if i1 < 1
|
||||||
|
then state
|
||||||
|
else state {exec = Block [IntGene 0, IntGene $ i1 - 1, StateFunc instructionExecDoRange, Block [StateFunc instructionIntPop, e1]] : es, int = is}
|
||||||
|
instructionExecDoTimes state = state
|
||||||
|
|
||||||
|
instructionExecWhile :: State -> State
|
||||||
|
instructionExecWhile state@(State (e1 : es) is fs [] ss ps im) =
|
||||||
|
state {exec = es}
|
||||||
|
instructionExecWhile state@(State alles@(e1 : es) is fs (b1 : bs) ss ps im) =
|
||||||
|
if b1
|
||||||
|
then state {exec = e1 : StateFunc instructionExecWhile : alles, bool = bs}
|
||||||
|
else state {exec = es}
|
||||||
|
instructionExecWhile state = state
|
||||||
|
|
||||||
|
instructionExecDoWhile :: State -> State
|
||||||
|
instructionExecDoWhile state@(State alles@(e1 : es) is fs bs ss ps im) =
|
||||||
|
state {exec = e1 : StateFunc instructionExecWhile : alles}
|
||||||
|
instructionExecDoWhile state = state
|
||||||
|
|
||||||
|
-- Eats the boolean no matter what
|
||||||
|
instructionExecWhen :: State -> State
|
||||||
|
instructionExecWhen state@(State (e1 : es) is fs (b1 : bs) ss ps im) =
|
||||||
|
if not b1
|
||||||
|
then state {exec = es, bool = bs}
|
||||||
|
else state {bool = bs}
|
||||||
|
instructionExecWhen state = state
|
||||||
|
|
||||||
-- This is one of the push genome functions itself, not infrastructure.
|
-- This is one of the push genome functions itself, not infrastructure.
|
||||||
-- Optionally, split this off into independent functions
|
-- Optionally, split this off into independent functions
|
||||||
instructionParameterLoad :: State -> State
|
instructionParameterLoad :: State -> State
|
||||||
|
26
src/Tests.hs
26
src/Tests.hs
@ -14,6 +14,8 @@ exampleState =
|
|||||||
input = Map.fromList [("in0" , IntGene 1)]
|
input = Map.fromList [("in0" , IntGene 1)]
|
||||||
}
|
}
|
||||||
|
|
||||||
|
-- TODO: Tests for added basic int instructions
|
||||||
|
|
||||||
testResult1 = [8, 3] == int (instructionIntAdd exampleState)
|
testResult1 = [8, 3] == int (instructionIntAdd exampleState)
|
||||||
|
|
||||||
testResult2 = [4, 3] == int (instructionIntSub exampleState)
|
testResult2 = [4, 3] == int (instructionIntSub exampleState)
|
||||||
@ -45,4 +47,28 @@ testResult10 = int loadedState5 !! 0 == 2 && int loadedState5 !! 1 == 2
|
|||||||
loadedState6 = loadProgram [IntGene 2, Block [IntGene 4, IntGene 1, StateFunc instructionExecDoRange], StateFunc instructionIntAdd] emptyState
|
loadedState6 = loadProgram [IntGene 2, Block [IntGene 4, IntGene 1, StateFunc instructionExecDoRange], StateFunc instructionIntAdd] emptyState
|
||||||
testResult11 = [12] == int (interpretExec loadedState6)
|
testResult11 = [12] == int (interpretExec loadedState6)
|
||||||
|
|
||||||
|
-- Tests execDoCount
|
||||||
|
loadedState7 = loadProgram [IntGene 2, Block [IntGene 4, StateFunc instructionExecDoCount], StateFunc instructionIntAdd] emptyState
|
||||||
|
testResult12 = [8] == int (interpretExec loadedState7)
|
||||||
|
|
||||||
|
-- Tests execDoTimes
|
||||||
|
loadedState8 = loadProgram [IntGene 2, Block [IntGene 4, StateFunc instructionExecDoTimes], IntGene 69] emptyState
|
||||||
|
testResult13 = [69, 69, 69, 69, 2] == int (interpretExec loadedState8)
|
||||||
|
|
||||||
|
-- Tests execWhile
|
||||||
|
loadedState9 = loadProgram [BoolGene False, BoolGene True, BoolGene True, StateFunc instructionExecWhile, IntGene 70] emptyState
|
||||||
|
testResult14 = [70, 70] == int (interpretExec loadedState9)
|
||||||
|
|
||||||
|
-- Tests execDoWhile
|
||||||
|
loadedState10 = loadProgram [BoolGene False, BoolGene True, BoolGene True, StateFunc instructionExecDoWhile, IntGene 70] emptyState
|
||||||
|
testResult15 = [70, 70, 70] == int (interpretExec loadedState10)
|
||||||
|
|
||||||
|
-- Tests execWhen
|
||||||
|
loadedState11 = loadProgram [BoolGene False, StateFunc instructionExecWhen, IntGene 71] emptyState
|
||||||
|
testResult16 = emptyState == interpretExec loadedState11
|
||||||
|
|
||||||
|
-- Also tests execWhen
|
||||||
|
loadedState12 = loadProgram [BoolGene True, StateFunc instructionExecWhen, IntGene 71] emptyState
|
||||||
|
testResult17 = [71] == int (interpretExec loadedState12)
|
||||||
|
|
||||||
allTests = and [testResult1, testResult2, testResult3, testResult4, testResult5, testResult6, testResult7, testResult8, testResult9]
|
allTests = and [testResult1, testResult2, testResult3, testResult4, testResult5, testResult6, testResult7, testResult8, testResult9]
|
||||||
|
Loading…
x
Reference in New Issue
Block a user