update instructions list/formatting
This commit is contained in:
parent
899aaa93a7
commit
84e5c7b1df
2
Makefile
2
Makefile
@ -15,7 +15,7 @@ test: # Runs unit tests.
|
|||||||
runghc -i./src/ test/Main.hs
|
runghc -i./src/ test/Main.hs
|
||||||
|
|
||||||
format: # Formats code using ormolu.
|
format: # Formats code using ormolu.
|
||||||
ormolu --mode inplace app/*.hs src/*.hs test/*.hs
|
ormolu --mode inplace app/*.hs src/HushGP/*.hs test/*.hs
|
||||||
|
|
||||||
hlint: # HLint for lint suggestions.
|
hlint: # HLint for lint suggestions.
|
||||||
hlint src/*.hs
|
hlint src/*.hs
|
||||||
|
2
TODO.md
2
TODO.md
@ -13,7 +13,7 @@
|
|||||||
- [X] Write haddock documentation for each function
|
- [X] Write haddock documentation for each function
|
||||||
- [X] Refactor all functions to take state as the final parameter
|
- [X] Refactor all functions to take state as the final parameter
|
||||||
- [X] Standardize the pattern matching parameter names, such as c1 : cs
|
- [X] Standardize the pattern matching parameter names, such as c1 : cs
|
||||||
- [ ] Write unit/quickcheck tests for all of the instructions
|
- [ ] Write unit/quickcheck tests for the generic functions
|
||||||
~~[ ] Use template haskell to generate function lists~~
|
~~[ ] Use template haskell to generate function lists~~
|
||||||
- [X] Move utility functions to their own file
|
- [X] Move utility functions to their own file
|
||||||
- [ ] Make add/sub/mult/div/mod instructions generic
|
- [ ] Make add/sub/mult/div/mod instructions generic
|
||||||
|
File diff suppressed because it is too large
Load Diff
@ -3,7 +3,6 @@ module HushGP.Instructions.StringInstructions where
|
|||||||
import HushGP.State
|
import HushGP.State
|
||||||
import HushGP.Instructions.GenericInstructions
|
import HushGP.Instructions.GenericInstructions
|
||||||
import HushGP.Instructions.Utility
|
import HushGP.Instructions.Utility
|
||||||
import Control.Lens
|
|
||||||
|
|
||||||
-- |Concats the top two strings on the string stack and pushes the result.
|
-- |Concats the top two strings on the string stack and pushes the result.
|
||||||
instructionStringConcat :: State -> State
|
instructionStringConcat :: State -> State
|
||||||
@ -221,14 +220,6 @@ instructionStringStripWhitespace :: State -> State
|
|||||||
instructionStringStripWhitespace state@(State {_string = s1 : ss}) = state{_string = strip s1 : ss}
|
instructionStringStripWhitespace state@(State {_string = s1 : ss}) = state{_string = strip s1 : ss}
|
||||||
instructionStringStripWhitespace state = state
|
instructionStringStripWhitespace state = state
|
||||||
|
|
||||||
-- |Utility Function: Casts a type based on a lens to a string. Pushes the result
|
|
||||||
-- to the string stack.
|
|
||||||
instructionStringFromLens :: Show a => Lens' State [a] -> State -> State
|
|
||||||
instructionStringFromLens accessor state@(State {_string = ss}) =
|
|
||||||
case uncons (view accessor state) of
|
|
||||||
Nothing -> state
|
|
||||||
Just (x1,_) -> state{_string = show x1 : ss}
|
|
||||||
|
|
||||||
-- |Converts the top bool from the bool stack to a string. Pushes the result to
|
-- |Converts the top bool from the bool stack to a string. Pushes the result to
|
||||||
-- the string stack.
|
-- the string stack.
|
||||||
instructionStringFromBool :: State -> State
|
instructionStringFromBool :: State -> State
|
||||||
|
@ -247,3 +247,13 @@ lstrip s = case s of
|
|||||||
-- this is a tad inefficient
|
-- this is a tad inefficient
|
||||||
rstrip :: String -> String
|
rstrip :: String -> String
|
||||||
rstrip = reverse . lstrip . reverse
|
rstrip = reverse . lstrip . reverse
|
||||||
|
|
||||||
|
-- string utility
|
||||||
|
|
||||||
|
-- |Utility Function: Casts a type based on a lens to a string. Pushes the result
|
||||||
|
-- to the string stack.
|
||||||
|
instructionStringFromLens :: Show a => Lens' State [a] -> State -> State
|
||||||
|
instructionStringFromLens accessor state@(State {_string = ss}) =
|
||||||
|
case uncons (view accessor state) of
|
||||||
|
Nothing -> state
|
||||||
|
Just (x1,_) -> state{_string = show x1 : ss}
|
||||||
|
@ -12,8 +12,8 @@ import HushGP.State
|
|||||||
-- Everntually, this can be part of the apply func to state helpers,
|
-- Everntually, this can be part of the apply func to state helpers,
|
||||||
-- which should take the number and type of parameter they have.
|
-- which should take the number and type of parameter they have.
|
||||||
|
|
||||||
-- |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
|
||||||
instructionParameterLoad state@(State {_parameter = (p : _)}) = case p of
|
instructionParameterLoad state@(State {_parameter = (p : _)}) = case p of
|
||||||
(GeneInt val) -> state & int .~ val : view int state
|
(GeneInt val) -> state & int .~ val : view int state
|
||||||
@ -32,20 +32,20 @@ instructionParameterLoad state@(State {_parameter = (p : _)}) = case p of
|
|||||||
(Block xs) -> state & exec .~ xs <> view exec state
|
(Block xs) -> state & exec .~ xs <> view exec state
|
||||||
instructionParameterLoad state = state
|
instructionParameterLoad state = state
|
||||||
|
|
||||||
-- |Loads a genome into the exec stack
|
-- | Loads a genome into the exec stack
|
||||||
loadProgram :: [Gene] -> State -> State
|
loadProgram :: [Gene] -> State -> State
|
||||||
loadProgram newstack state = state & exec .~ newstack
|
loadProgram newstack state = state & exec .~ newstack
|
||||||
|
|
||||||
-- |Takes a Push state, and generates the next push state via:
|
-- | Takes a Push state, and generates the next push state via:
|
||||||
-- If the first item on the EXEC stack is a single instruction
|
-- If the first item on the EXEC stack is a single instruction
|
||||||
-- then pop it and execute it.
|
-- then pop it and execute it.
|
||||||
-- Else if the first item on the EXEC stack is a literal
|
-- Else if the first item on the EXEC stack is a literal
|
||||||
-- then pop it and push it onto the appropriate stack.
|
-- then pop it and push it onto the appropriate stack.
|
||||||
-- Else (the first item must be a list) pop it and push all of the
|
-- Else (the first item must be a list) pop it and push all of the
|
||||||
-- items that it contains back onto the EXEC stack individually,
|
-- items that it contains back onto the EXEC stack individually,
|
||||||
-- in reverse order (so that the item that was first in the list
|
-- in reverse order (so that the item that was first in the list
|
||||||
-- ends up on top).
|
-- ends up on top).
|
||||||
-- The empty-stack safety of interpretExec on empty stacks depends on the functions it calls.
|
-- The empty-stack safety of interpretExec on empty stacks depends on the functions it calls.
|
||||||
interpretExec :: State -> State
|
interpretExec :: State -> State
|
||||||
interpretExec state@(State {_exec = e : es}) =
|
interpretExec state@(State {_exec = e : es}) =
|
||||||
case e of
|
case e of
|
||||||
|
@ -8,10 +8,10 @@ import Data.Map qualified as Map
|
|||||||
import GHC.Generics
|
import GHC.Generics
|
||||||
import Test.QuickCheck
|
import Test.QuickCheck
|
||||||
|
|
||||||
-- |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.
|
||||||
-- One solution is for the exec stack to be a list of [Gene].
|
-- One solution is for the exec stack to be a list of [Gene].
|
||||||
-- The parameter stack could be singular [Gene] or multiple [atomic] types.
|
-- The parameter stack could be singular [Gene] or multiple [atomic] types.
|
||||||
data Gene
|
data Gene
|
||||||
= GeneInt Int
|
= GeneInt Int
|
||||||
| GeneFloat Float
|
| GeneFloat Float
|
||||||
@ -83,7 +83,7 @@ instance Arbitrary Gene where
|
|||||||
return Close
|
return Close
|
||||||
]
|
]
|
||||||
|
|
||||||
-- |The structure that holds all of the values.
|
-- | The structure that holds all of the values.
|
||||||
data State = State
|
data State = State
|
||||||
{ _exec :: [Gene],
|
{ _exec :: [Gene],
|
||||||
_code :: [Gene],
|
_code :: [Gene],
|
||||||
|
Loading…
x
Reference in New Issue
Block a user