hmep-0.0.0: HMEP Multi Expression Programming – a genetic programming variant

Safe HaskellNone
LanguageHaskell2010

MEP

Contents

Description

Copyright Bogdan Penkovsky (c) 2017

Multiple Expression Programming

Synopsis

Documentation

type Chromosome a = Vector (Gene a Int) Source #

A chromosome is a vector of genes

data Gene a i Source #

Either a terminal symbol or a three-address code (a function and two pointers)

Instances

(Show a, Show i) => Show (Gene a i) Source # 

Methods

showsPrec :: Int -> Gene a i -> ShowS #

show :: Gene a i -> String #

showList :: [Gene a i] -> ShowS #

data Config a Source #

Constructors

Config 

Fields

defaultConfig :: Config Double Source #

defaultConfig = Config
  {
    p'const = 0.1
  , p'var = 0.4
  , p'mutation = 0.1
  , p'crossover = 0.9

  , c'length = 50
  , c'popSize = 100
  , c'popN = 1
  , c'ops = V.empty  -- <-- To be overridden
  , c'vars = 1
  }

type LossFunction a = (Vector a -> Vector a) -> (Vector Int, Double) Source #

A function to minimize.

The argument is a vector evaluation function whose input is a vector (length c'vars) and ouput is a vector with a different length c'length.

The result is a vector of the best indices and a scalar loss value.

Genetic algorithm

initialize :: Config Double -> Rand (Population Double) Source #

Randomly generate a new population

evolve Source #

Arguments

:: Config Double

Common configuration

-> LossFunction Double

Custom loss function

-> (Chromosome Double -> Rand (Chromosome Double))

Mutation

-> (Chromosome Double -> Chromosome Double -> Rand (Chromosome Double, Chromosome Double))

Crossover

-> ([Phenotype Double] -> Rand (Chromosome Double))

A chromosome selection algorithm. Does not need to be random, but may be.

-> [Phenotype Double]

Evaluated population

-> Rand [Phenotype Double]

New generation

Selection operator that produces the next evaluated population.

Standard algorithm: the best offspring O replaces the worst individual W in the current population if O is better than W.

binaryTournament :: Ord a => [Phenotype a] -> Rand (Chromosome a) Source #

Binary tournament selection

crossover :: Chromosome a -> Chromosome a -> Rand (Chromosome a, Chromosome a) Source #

Uniform crossover operator

mutation3 Source #

Arguments

:: Config Double

Common configuration

-> Chromosome Double 
-> Rand (Chromosome Double) 

Mutation operator with up to three mutations per chromosome

smoothMutation Source #

Arguments

:: Double

Probability of gene mutation

-> Config Double

Common configuration

-> Chromosome Double 
-> Rand (Chromosome Double) 

Mutation operator with a fixed mutation probability of each gene

newChromosome Source #

Arguments

:: Config Double

Common configuration

-> Rand (Chromosome Double) 

Randomly initialize a new chromosome. By definition, the first gene is terminal (a constant or a variable).

Random

data Rand a :: * -> * #

A basic random monad, for generating random numbers from pure mersenne twisters.

Instances

Monad Rand 

Methods

(>>=) :: Rand a -> (a -> Rand b) -> Rand b #

(>>) :: Rand a -> Rand b -> Rand b #

return :: a -> Rand a #

fail :: String -> Rand a #

Functor Rand 

Methods

fmap :: (a -> b) -> Rand a -> Rand b #

(<$) :: a -> Rand b -> Rand a #

Applicative Rand 

Methods

pure :: a -> Rand a #

(<*>) :: Rand (a -> b) -> Rand a -> Rand b #

(*>) :: Rand a -> Rand b -> Rand b #

(<*) :: Rand a -> Rand b -> Rand a #

newPureMT :: IO PureMT #

Create a new PureMT generator, using the clocktime as the base for the seed.

runRandom :: Rand a -> PureMT -> (a, PureMT) #

Run a random computation using the generator g, returning the result and the updated generator.

evalRandom :: Rand a -> PureMT -> a #

Evaluate a random computation using the mersenne generator g. Note that the generator g is not returned, so there's no way to recover the updated version of g.