parallelism/start the individual creation
This commit is contained in:
parent
090a402f06
commit
88b5b52813
@ -28,7 +28,7 @@ category: Data
|
||||
build-type: Simple
|
||||
|
||||
common warnings
|
||||
ghc-options: -Wall -XTemplateHaskell
|
||||
ghc-options: -Wall -XTemplateHaskell -threaded
|
||||
|
||||
library
|
||||
-- Import common warning flags.
|
||||
@ -73,7 +73,7 @@ library
|
||||
|
||||
-- Other library packages from which modules are imported.
|
||||
build-depends:
|
||||
base, containers, lens, split, QuickCheck, regex-tdfa, template-haskell, random
|
||||
base, containers, lens, split, QuickCheck, regex-tdfa, template-haskell, random, parallel
|
||||
|
||||
-- Directories containing source files.
|
||||
hs-source-dirs: src
|
||||
|
@ -3,12 +3,21 @@ module HushGP.GP where
|
||||
import HushGP.State
|
||||
import HushGP.Genome
|
||||
import HushGP.GP.PushArgs
|
||||
import Control.Monad
|
||||
import Control.Parallel.Strategies
|
||||
-- import Debug.Trace (trace, traceStack)
|
||||
|
||||
-- generatePopulation :: PushArgs -> [Gene] -> IO [[Gene]]
|
||||
-- generatePopulation pushArgs instructions = do
|
||||
-- randomPop <- makeRandomPlushy pushArgs
|
||||
-- replicate (populationSize pushArgs) (makeRandomPlushy pushArgs)
|
||||
-- | Using a PushArgs object, generates a population of the specified size with the
|
||||
-- specified instructions in parallel.
|
||||
generatePopulation :: PushArgs -> [Individual]
|
||||
generatePopulation pushArgs =
|
||||
replicate (populationSize pushArgs) (makeRandomIndividual pushArgs) `using` rpar
|
||||
|
||||
evaluatePopulation :: PushArgs -> [Individual] -> IO [Individual]
|
||||
evaluatePopulation pushArgs population = map (fmap (errorFunction pushArgs pushArgs (trainingData pushArgs)) . plushy) population
|
||||
|
||||
-- | The start of the gp loop. TODO: Make this more accurate later.
|
||||
gpLoop :: PushArgs -> IO ()
|
||||
gpLoop = undefined
|
||||
gpLoop pushArgs = do
|
||||
let unEvaledPopulation = generatePopulation pushArgs
|
||||
print "gamer"
|
||||
|
@ -132,8 +132,8 @@ defaultPushArgs = PushArgs {
|
||||
ssxNotBmx = False,
|
||||
stepLimit = 1000,
|
||||
tournamentSize = 5,
|
||||
testingData = [],
|
||||
trainingData = [],
|
||||
testingData = ([], []),
|
||||
trainingData = ([], []),
|
||||
umadRate = 0.1,
|
||||
variation = Map.fromList [("umad", 1.0)]
|
||||
}
|
||||
|
@ -10,30 +10,21 @@ import HushGP.GP.PushArgs
|
||||
-- import HushGP.Instructions
|
||||
-- import Debug.Trace
|
||||
|
||||
-- tempPlushy :: [Gene]
|
||||
-- tempPlushy = [
|
||||
-- StateFunc (instructionIntDiv, "instructionIntDiv"),
|
||||
-- StateFunc (instructionExecDup, "instructionExecDup"),
|
||||
-- GeneInt 1,
|
||||
-- GeneInt 0,
|
||||
-- StateFunc (instructionIntDiv, "instructionIntDiv"),
|
||||
-- Skip,
|
||||
-- GeneInt (-15),
|
||||
-- StateFunc (instructionExecDup, "instructionExecDup"),
|
||||
-- StateFunc (instructionIntSub, "instructionIntSub"),
|
||||
-- StateFunc (instructionFloatMul, "instructionFloatMul"),
|
||||
-- Skip,
|
||||
-- Close,
|
||||
-- -- StateFunc (instructionNoOpBlock, "instructionNoOpBlock"),
|
||||
-- StateFunc (instructionExecIf, "instructionExecIf"),
|
||||
-- Close,
|
||||
-- Close
|
||||
-- ]
|
||||
-- | The structure for an individual containing the genome, the totalFitness, and
|
||||
-- the individual fitness cases for lexicase.
|
||||
data Individual = Individual {
|
||||
plushy :: IO [Gene],
|
||||
totalFitness :: Maybe Double,
|
||||
fitnessCases :: Maybe [Double]
|
||||
}
|
||||
|
||||
-- | Makes a random plushy from variables in a passed argMap and
|
||||
-- a passed list of instructions.
|
||||
makeRandomPlushy :: PushArgs -> [Gene] -> IO [Gene]
|
||||
makeRandomPlushy pushArgs = randomInstructions (maxInitialPlushySize pushArgs)
|
||||
-- | Makes a random individual based on the variables in a passed PushArgs.
|
||||
makeRandomIndividual :: PushArgs -> Individual
|
||||
makeRandomIndividual pushArgs = Individual {plushy = makeRandomPlushy pushArgs, totalFitness = Nothing, fitnessCases = Nothing}
|
||||
|
||||
-- | Makes a random plushy from variables in a passed PushArgs.
|
||||
makeRandomPlushy :: PushArgs -> IO [Gene]
|
||||
makeRandomPlushy pushArgs = randomInstructions (maxInitialPlushySize pushArgs) (instructionList pushArgs)
|
||||
|
||||
-- | A utility function to generate an amount based on an int rather than
|
||||
-- from an argmap.
|
||||
|
@ -61,8 +61,8 @@ intErrorFunction :: PushArgs -> ([[Gene]], [Gene]) -> [Gene] -> [Double]
|
||||
intErrorFunction _args (inputData, outputData) plushy =
|
||||
map abs $ zipWith (-) (map ((fromIntegral @Integer @Double . (errorHead . _int) . interpretExec) . loadState plushy) inputData) (map (fromIntegral @Integer @Double . extractGeneInt) outputData)
|
||||
|
||||
intArgMap :: PushArgs
|
||||
intArgMap = defaultPushArgs
|
||||
intPushArgs :: PushArgs
|
||||
intPushArgs = defaultPushArgs
|
||||
{
|
||||
instructionList = runInstructions,
|
||||
errorFunction = intErrorFunction,
|
||||
@ -80,4 +80,4 @@ intArgMap = defaultPushArgs
|
||||
}
|
||||
|
||||
main :: IO ()
|
||||
main = gpLoop intArgMap
|
||||
main = gpLoop intPushArgs
|
||||
|
Loading…
x
Reference in New Issue
Block a user