middle of converting to PushData
This commit is contained in:
parent
058bbbfd94
commit
76493bc362
@ -9,6 +9,7 @@ import HushGP.Genome
|
|||||||
import HushGP.State
|
import HushGP.State
|
||||||
import HushGP.GP.Variation
|
import HushGP.GP.Variation
|
||||||
import HushGP.GP.Downsample
|
import HushGP.GP.Downsample
|
||||||
|
import HushGP.GP.PushData
|
||||||
import HushGP.Utility
|
import HushGP.Utility
|
||||||
|
|
||||||
-- import Debug.Trace (trace, traceStack)
|
-- import Debug.Trace (trace, traceStack)
|
||||||
@ -22,7 +23,7 @@ generatePopulation pushArgs = do
|
|||||||
|
|
||||||
-- | Evaluates a population of plushies with the error function passed in via PushArgs and sorts them.
|
-- | Evaluates a population of plushies with the error function passed in via PushArgs and sorts them.
|
||||||
-- TODO: Need to make this runnable in parallel too.
|
-- TODO: Need to make this runnable in parallel too.
|
||||||
evaluatePopulation :: PushArgs -> ([[Gene]], [Gene], [Int]) -> [Individual] -> [Individual]
|
evaluatePopulation :: PushArgs -> [PushData] -> [Individual] -> [Individual]
|
||||||
evaluatePopulation pushArgs passedTrainingData population = sort $ zipWith updateIndividual (map (errorFunction pushArgs pushArgs passedTrainingData . plushy) population) population
|
evaluatePopulation pushArgs passedTrainingData population = sort $ zipWith updateIndividual (map (errorFunction pushArgs pushArgs passedTrainingData . plushy) population) population
|
||||||
|
|
||||||
-- | A helper function used in evaluatePopulation. Takes a [Double] as the error scores and an individual.
|
-- | A helper function used in evaluatePopulation. Takes a [Double] as the error scores and an individual.
|
||||||
|
@ -1,8 +1,9 @@
|
|||||||
module HushGP.GP.PushArgs where
|
module HushGP.GP.PushArgs where
|
||||||
|
|
||||||
import HushGP.State
|
import HushGP.State
|
||||||
import Data.Map qualified as Map
|
|
||||||
import HushGP.Instructions
|
import HushGP.Instructions
|
||||||
|
import HushGP.GP.PushData
|
||||||
|
import Data.Map qualified as Map
|
||||||
|
|
||||||
-- | The structure holding the arguments for the various aspects
|
-- | The structure holding the arguments for the various aspects
|
||||||
-- of the evolutionary run in Hush.
|
-- of the evolutionary run in Hush.
|
||||||
@ -46,10 +47,10 @@ data PushArgs = PushArgs
|
|||||||
elitism :: Bool,
|
elitism :: Bool,
|
||||||
-- | User must provide their own error function.
|
-- | User must provide their own error function.
|
||||||
-- Arg 1: PushArgs for the current set of arguments.
|
-- Arg 1: PushArgs for the current set of arguments.
|
||||||
-- Arg 2: ([[Gene]], [Gene]) is the input data. Input is the first index and output is the second index.
|
-- Arg 2: [PushData] is the input data.
|
||||||
-- Arg 3: [Gene] is the plushy representation of a program.
|
-- Arg 3: [Gene] is the plushy representation of a program.
|
||||||
-- Returns the error list for a given set of inputs of type [Double].
|
-- Returns the error list for a given set of inputs of type [Double].
|
||||||
errorFunction :: PushArgs -> ([[Gene]], [Gene], [Int]) -> [Gene] -> [Double],
|
errorFunction :: PushArgs -> [PushData] -> [Gene] -> [Double],
|
||||||
-- | Type of informed downsampling. "solved", "elite", "soft".
|
-- | Type of informed downsampling. "solved", "elite", "soft".
|
||||||
informedDownsamplingType :: String,
|
informedDownsamplingType :: String,
|
||||||
-- | List of instructions to use in the evolutionary run.
|
-- | List of instructions to use in the evolutionary run.
|
||||||
@ -83,9 +84,9 @@ data PushArgs = PushArgs
|
|||||||
-- | For tournament selection, amount of individuals in each tournament.
|
-- | For tournament selection, amount of individuals in each tournament.
|
||||||
tournamentSize :: Int,
|
tournamentSize :: Int,
|
||||||
-- | Training data for the gp, must be provided.
|
-- | Training data for the gp, must be provided.
|
||||||
trainingData :: ([[Gene]], [Gene]),
|
trainingData :: [PushData],
|
||||||
-- | Testing data for the gp, must be provided if there is any.
|
-- | Testing data for the gp, must be provided if there is any.
|
||||||
testingData :: ([[Gene]], [Gene]),
|
testingData :: [PushData],
|
||||||
-- | Addition rate for UMAD (deletion rate derived from this).
|
-- | Addition rate for UMAD (deletion rate derived from this).
|
||||||
umadRate :: Float,
|
umadRate :: Float,
|
||||||
-- | Genetic operators and probabilities for their use, should sum to one
|
-- | Genetic operators and probabilities for their use, should sum to one
|
||||||
@ -134,8 +135,8 @@ defaultPushArgs = PushArgs {
|
|||||||
ssxNotBmx = False,
|
ssxNotBmx = False,
|
||||||
stepLimit = 1000,
|
stepLimit = 1000,
|
||||||
tournamentSize = 5,
|
tournamentSize = 5,
|
||||||
testingData = ([], []),
|
testingData = error "Must supply the testingData yourself",
|
||||||
trainingData = ([], []),
|
trainingData = error "Must supply the trainingData yourself",
|
||||||
umadRate = 0.1,
|
umadRate = 0.1,
|
||||||
variation = Map.fromList [("umad", 1.0)],
|
variation = Map.fromList [("umad", 1.0)],
|
||||||
epsilons = Nothing
|
epsilons = Nothing
|
||||||
|
@ -4,7 +4,11 @@ import HushGP.State
|
|||||||
|
|
||||||
data PushData = PushData {
|
data PushData = PushData {
|
||||||
inputData :: [Gene],
|
inputData :: [Gene],
|
||||||
outputData :: [Gene],
|
outputData :: Gene,
|
||||||
downsampleIndex :: Int,
|
downsampleIndex :: Maybe Int,
|
||||||
caseDistances :: [Double]
|
caseDistances :: Maybe [Double]
|
||||||
}
|
}
|
||||||
|
|
||||||
|
-- |Utility function: Sets the index of the passed training data.
|
||||||
|
makeIndexedTrainingData :: [PushData] -> [PushData]
|
||||||
|
makeIndexedTrainingData oldData = zipWith (\dat idx -> dat{downsampleIndex = Just idx}) oldData [0..]
|
||||||
|
@ -6,6 +6,7 @@ import Data.Map qualified as Map
|
|||||||
import HushGP.State
|
import HushGP.State
|
||||||
import HushGP.Instructions
|
import HushGP.Instructions
|
||||||
import HushGP.GP.PushArgs
|
import HushGP.GP.PushArgs
|
||||||
|
import HushGP.GP.PushData
|
||||||
import HushGP.Genome
|
import HushGP.Genome
|
||||||
import HushGP.Push
|
import HushGP.Push
|
||||||
import HushGP.Instructions.Utility
|
import HushGP.Instructions.Utility
|
||||||
@ -25,12 +26,23 @@ targetFunction :: Integer -> Integer
|
|||||||
targetFunction x = (x * x * x) + (2 * x)
|
targetFunction x = (x * x * x) + (2 * x)
|
||||||
|
|
||||||
-- | The training data for the model.
|
-- | The training data for the model.
|
||||||
trainData :: ([[Gene]], [Gene])
|
trainData :: [PushData]
|
||||||
trainData = (chunksOf 1 $ map GeneInt [-10..10], map (GeneInt . targetFunction) [-10..11])
|
trainData = map (\num -> PushData {
|
||||||
|
inputData = [GeneInt num],
|
||||||
|
outputData = (GeneInt . targetFunction) num,
|
||||||
|
downsampleIndex = Nothing,
|
||||||
|
caseDistances = Nothing})
|
||||||
|
[-10..10]
|
||||||
|
|
||||||
-- | The testing data for the model.
|
-- | The testing data for the model.
|
||||||
testData :: ([[Gene]], [Gene])
|
testData :: [PushData]
|
||||||
testData = (chunksOf 1 $ map GeneInt $ [-20..(-11)] <> [11..21], map (GeneInt . targetFunction) ([-20..(-11)] <> [11..21]))
|
-- testData = (chunksOf 1 $ map GeneInt $ [-20..(-11)] <> [11..21], map (GeneInt . targetFunction) ([-20..(-11)] <> [11..21]))
|
||||||
|
testData = map (\num -> PushData {
|
||||||
|
inputData = [GeneInt num],
|
||||||
|
outputData = (GeneInt . targetFunction) num,
|
||||||
|
downsampleIndex = Nothing,
|
||||||
|
caseDistances = Nothing})
|
||||||
|
[-20..(-11)] <> [11..21]
|
||||||
|
|
||||||
-- | The instructions used in the evolutionary run.
|
-- | The instructions used in the evolutionary run.
|
||||||
runInstructions :: [Gene]
|
runInstructions :: [Gene]
|
||||||
@ -57,9 +69,9 @@ loadState plushy vals =
|
|||||||
(loadProgram (plushyToPush plushy) emptyState){_input = Map.fromList (zip [0..] vals)}
|
(loadProgram (plushyToPush plushy) emptyState){_input = Map.fromList (zip [0..] vals)}
|
||||||
|
|
||||||
-- | The error function for a single set of inputs and outputs.
|
-- | The error function for a single set of inputs and outputs.
|
||||||
intErrorFunction :: PushArgs -> ([[Gene]], [Gene], [Int]) -> [Gene] -> [Double]
|
intErrorFunction :: PushArgs -> [PushData] -> [Gene] -> [Double]
|
||||||
intErrorFunction _args (inputData, outputData, _) plushy =
|
intErrorFunction _args pushData plushy =
|
||||||
map abs $ zipWith (-) (map ((fromIntegral @Integer @Double . (errorHead . _int) . interpretExec) . loadState plushy) inputData) (map (fromIntegral @Integer @Double . extractGeneInt) outputData)
|
map abs $ zipWith (-) (map ((fromIntegral @Integer @Double . (errorHead . _int) . interpretExec) . loadState plushy) pushData) (map (fromIntegral @Integer @Double . extractGeneInt) outputData)
|
||||||
|
|
||||||
intPushArgs :: PushArgs
|
intPushArgs :: PushArgs
|
||||||
intPushArgs = defaultPushArgs
|
intPushArgs = defaultPushArgs
|
||||||
|
@ -30,7 +30,3 @@ thrd (_, _, x) = x
|
|||||||
-- |Utility function: Converts a tuple to a triple with a passed value.
|
-- |Utility function: Converts a tuple to a triple with a passed value.
|
||||||
tupleToTriple :: (a, b) -> c -> (a, b, c)
|
tupleToTriple :: (a, b) -> c -> (a, b, c)
|
||||||
tupleToTriple (x, y) z = (x, y, z)
|
tupleToTriple (x, y) z = (x, y, z)
|
||||||
|
|
||||||
-- |Utility function: Converts the training data passed in to an indexed representation
|
|
||||||
makeIndexedTrainingData :: ([[Gene]], [Gene]) -> ([[Gene]], [Gene], [Int])
|
|
||||||
makeIndexedTrainingData (inputs, outputs) = (inputs, outputs, [0..(length inputs)])
|
|
||||||
|
Loading…
x
Reference in New Issue
Block a user