formatting

This commit is contained in:
Rowan Torbitzky-Lane 2025-02-13 23:34:00 -06:00
parent 915ec947f5
commit ed960acef3
4 changed files with 38 additions and 38 deletions

View File

@ -1,34 +1,34 @@
module HushGP.Genome where
import HushGP.State
import HushGP.Utility
import Data.Map qualified as Map
import Data.List
import Data.List.Split
import Data.Map qualified as Map
import HushGP.Instructions.Opens
import HushGP.State
import HushGP.Utility
-- |Makes a random plushy from variables in a passed argMap and
-- a passed list of instructions.
-- | Makes a random plushy from variables in a passed argMap and
-- a passed list of instructions.
makeRandomPlushy :: Map.Map String String -> [Gene] -> IO [Gene]
makeRandomPlushy argMap = randomInstructions (read @Int (argMap Map.! "maxInitialPlushySize"))
-- |A utility function to generate an amount based on an int rather than
-- from an argmap.
-- | A utility function to generate an amount based on an int rather than
-- from an argmap.
makeRandomPlushy' :: Int -> [Gene] -> IO [Gene]
makeRandomPlushy' = randomInstructions
-- |Checks to see if a Gene is an (Open _) constructor.
-- | Checks to see if a Gene is an (Open _) constructor.
isOpen :: Gene -> Bool
isOpen (Open _) = True
isOpen _ = False
-- |Decrements the count of an (Open _) constructor. Acts as id
-- if the gene isn't an open.
-- | Decrements the count of an (Open _) constructor. Acts as id
-- if the gene isn't an open.
decOpen :: Gene -> Gene
decOpen (Open n) = Open (n - 1)
decOpen gene = gene
-- |Checks to see if the a list of genes with a single element is an opener.
-- | Checks to see if the a list of genes with a single element is an opener.
isOpenerList :: [Gene] -> Bool
isOpenerList [instruction] =
case Map.lookup instruction instructionOpens of
@ -36,7 +36,7 @@ isOpenerList [instruction] =
_ -> False
isOpenerList _ = False
-- |Gets the amount of blocks to open from a list of genes with a single element.
-- | Gets the amount of blocks to open from a list of genes with a single element.
getOpenAmountList :: [Gene] -> Int
getOpenAmountList [instruction] =
case Map.lookup instruction instructionOpens of
@ -44,25 +44,25 @@ getOpenAmountList [instruction] =
_ -> 0
getOpenAmountList _ = 0
-- |Converts a plushy genome into a push genome.
-- | Converts a plushy genome into a push genome.
plushyToPush :: [Gene] -> [Gene]
plushyToPush plushy = plushyToPush' (concatMap (\x -> if isOpenerList x then x <> [Open (getOpenAmountList x)] else x) (chunksOf 1 plushy)) []
-- |Internal function used to convert a plushy genome with opens in it into a push genome.
-- | Internal function used to convert a plushy genome with opens in it into a push genome.
plushyToPush' :: [Gene] -> [Gene] -> [Gene]
plushyToPush' openPlushy push =
if null openPlushy
then
if any isOpen push
then plushyToPush' [Close] push
else push
else
if firstPlushy == Close
then
if any isOpen push
then plushyToPush' (drop 1 openPlushy) (if numOpen (push !! openIndex) == 1 then preOpen <> postOpen else preOpen <> postOpen <> [decOpen (Open (numOpen (push !! openIndex)))])
else plushyToPush' (drop 1 openPlushy) push
else plushyToPush' (drop 1 openPlushy) (push <> [firstPlushy])
then plushyToPush' [Close] push
else push
else
if firstPlushy == Close
then
if any isOpen push
then plushyToPush' (drop 1 openPlushy) (if numOpen (push !! openIndex) == 1 then preOpen <> postOpen else preOpen <> postOpen <> [decOpen (Open (numOpen (push !! openIndex)))])
else plushyToPush' (drop 1 openPlushy) push
else plushyToPush' (drop 1 openPlushy) (push <> [firstPlushy])
where
firstPlushy :: Gene
firstPlushy =

View File

@ -1,9 +1,9 @@
module HushGP.PushTests
-- ( module HushGP.PushTests.GenericTests,
-- module HushGP.PushTests.IntTests,
-- module HushGP.PushTests.UtilTests,
-- )
where
module HushGP.PushTests where
-- ( module HushGP.PushTests.GenericTests,
-- module HushGP.PushTests.IntTests,
-- module HushGP.PushTests.UtilTests,
-- )
-- import HushGP.PushTests.GenericTests
-- import HushGP.PushTests.IntTests

View File

@ -6,10 +6,10 @@ import Control.Lens hiding (elements)
import Data.Map qualified as Map
import System.Random
-- |The exec stack must store heterogenous types,
-- and we must be able to detect that type at runtime.
-- 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 exec stack must store heterogenous types,
-- and we must be able to detect that type at runtime.
-- One solution is for the exec stack to be a list of [Gene].
-- The parameter stack could be singular [Gene] or multiple [atomic] types.
data Gene
= GeneInt Integer
| GeneFloat Double
@ -21,8 +21,8 @@ data Gene
| GeneVectorBool [Bool]
| GeneVectorString [String]
| GeneVectorChar [Char]
-- |State -> State is the function itself. String stores the name of the function.
| StateFunc (State -> State, String)
| -- | State -> State is the function itself. String stores the name of the function.
StateFunc (State -> State, String)
| PlaceInput String
| Close
| Open Int

View File

@ -1,15 +1,15 @@
module HushGP.Utility where
import Control.Monad
import HushGP.State
import System.Random
import Control.Monad
-- |Generates a single random instruction from a list of instructions.
-- | Generates a single random instruction from a list of instructions.
randomInstruction :: [Gene] -> IO Gene
randomInstruction instructions = do
impureGen <- initStdGen
return $ instructions !! fst (uniformR (0, length instructions - 1) impureGen)
-- |Generates a list of random instructions from a list of instructions passed in.
-- | Generates a list of random instructions from a list of instructions passed in.
randomInstructions :: Int -> [Gene] -> IO [Gene]
randomInstructions amt instructions = replicateM amt (randomInstruction instructions)