moo-1.0: Genetic algorithm library

Safe HaskellNone

Moo.GeneticAlgorithm.Run

Contents

Description

Helper functions to run genetic algorithms and control iterations.

Synopsis

Running algorithm

runGASource

Arguments

:: Rand [Genome a]

function to create initial population

-> ([Genome a] -> Rand b)

genetic algorithm, see also loop and loopWithLog

-> IO b

final population

Helper function to run the entire algorithm in the Rand monad. It takes care of generating a new random number generator.

runIOSource

Arguments

:: Rand [Genome a]

function to create initial population

-> (IORef PureMT -> [Genome a] -> IO (Population a))

genetic algorithm, see also loopIO

-> IO (Population a)

final population

Helper function to run the entire algorithm in the IO monad.

nextGenerationSource

Arguments

:: ObjectiveFunction objectivefn a 
=> ProblemType

a type of the optimization problem

-> objectivefn

objective function

-> SelectionOp a

selection operator

-> Int

elite, the number of genomes to keep intact

-> CrossoverOp a

crossover operator

-> MutationOp a

mutation operator

-> StepGA Rand a 

Construct a single step of the genetic algorithm.

See Moo.GeneticAlgorithm.Binary and Moo.GeneticAlgorithm.Continuous for the building blocks of the algorithm.

nextSteadyStateSource

Arguments

:: ObjectiveFunction objectivefn a 
=> Int

n, number of worst solutions to replace

-> ProblemType

a type of the optimization problem

-> objectivefn

objective function

-> SelectionOp a

selection operator

-> CrossoverOp a

crossover operator

-> MutationOp a

mutation operator

-> StepGA Rand a 

Construct a single step of the incremental (steady-steate) genetic algorithm. Exactly n worst solutions are replaced with newly born children.

See Moo.GeneticAlgorithm.Binary and Moo.GeneticAlgorithm.Continuous for the building blocks of the algorithm.

makeStoppable :: (ObjectiveFunction objectivefn a, Monad m) => objectivefn -> (Population a -> m (Population a)) -> StepGA m aSource

Wrap a population transformation with pre- and post-conditions to indicate the end of simulation.

Use this function to define custom replacement strategies in addition to nextGeneration and nextSteadyState.

Iteration control

loopSource

Arguments

:: Monad m 
=> Cond a

termination condition cond

-> StepGA m a

step function to produce the next generation

-> [Genome a]

initial population

-> m (Population a)

final population

Run strict iterations of the genetic algorithm defined by step. Return the result of the last step.

loopWithLogSource

Arguments

:: (Monad m, Monoid w) 
=> LogHook a m w

periodic logging action

-> Cond a

termination condition cond

-> StepGA m a

step function to produce the next generation

-> [Genome a]

initial population

-> m (Population a, w)

final population

GA iteration interleaved with the same-monad logging hooks.

loopIOSource

Arguments

:: [IOHook a]

input-output actions, special and time-dependent stop conditions

-> Cond a

termination condition cond

-> StepGA Rand a

step function to produce the next generation

-> IORef PureMT

reference to the random number generator

-> [Genome a]

initial population pop0

-> IO (Population a)

final population

GA iteration interleaved with IO (for logging or saving the intermediate results); it takes and returns the updated random number generator explicitly.

data Cond a Source

Iterations stop when the condition evaluates as True.

Constructors

Generations Int

stop after n generations

IfObjective ([Objective] -> Bool)

stop when objective values satisfy the predicate

forall b . Eq b => GensNoChange

terminate when evolution stalls

Fields

c'maxgens :: Int

max number of generations for an indicator to be the same

c'indicator :: [Objective] -> b

stall indicator function

c'counter :: Maybe (b, Int)

a counter (initially Nothing)

Or (Cond a) (Cond a)

stop when at least one of two conditions holds

And (Cond a) (Cond a)

stop when both conditions hold

data (Monad m, Monoid w) => LogHook a m w Source

Logging to run every nth iteration starting from 0 (the first parameter). The logging function takes the current generation count and population.

Constructors

WriteEvery Int (Int -> Population a -> w) 

data IOHook a Source

Input-output actions, interactive and time-dependent stop conditions.

Constructors

DoEvery

action to run every nth iteration, starting from 0; initially (at iteration 0) the objective value is zero.

Fields

io'n :: Int
 
io'action :: Int -> Population a -> IO ()
 
StopWhen (IO Bool)

custom or interactive stop condition

TimeLimit

terminate iteration after t seconds

Fields

io't :: Double