simple-genetic-algorithm-mr-0.4.0.0: Simple parallel genetic algorithm implementation

Safe HaskellNone
LanguageHaskell2010

AI.GeneticAlgorithm.Simple

Description

Simple parallel genetic algorithm implementation.

import AI.GeneticAlgorithm.Simple
import System.Random
import Text.Printf
import Data.List as L
import Control.DeepSeq

newtype SinInt = SinInt [Double]

instance NFData SinInt where
    rnf (SinInt xs) = rnf xs `seq` ()

instance Show SinInt where
    show (SinInt []) = "<empty SinInt>"
    show (SinInt (x:xs)) =
        let start = printf "%.5f" x
            end = concat $ zipWith (\c p -> printf "%+.5f" c ++ "X^" ++ show p) xs [1 :: Int ..]
        in start ++ end

polynomialOrder = 4 :: Int

err :: SinInt -> Double
err (SinInt xs) =
    let f x = snd $ L.foldl' (\(mlt,s) coeff -> (mlt*x, s + coeff*mlt)) (1,0) xs
    in maximum [ abs $ sin x - f x | x <- [0.0,0.001 .. pi/2]]

instance Chromosome SinInt where
   crossover (SinInt xs) (SinInt ys) =
       return [ SinInt (L.zipWith (\x y -> (x+y)/2) xs ys) ]

   mutation (SinInt xs) = do
       idx <- getRandomR (0, length xs - 1)
       dx  <- getRandomR (-10.0, 10.0)
       let t = xs !! idx
           xs' = take idx xs ++ [t + t*dx] ++ drop (idx+1) xs
       return $ SinInt xs'

    fitness int =
        let max_err = 1000.0 in
        max_err - (min (err int) max_err)

randomSinInt gen =
    lst <- replicateM polynomialOrder (getRandomR (-10.0,10.0))
    in (SinInt lst, gen')

stopf :: SinInt -> Int -> IO Bool
stopf best gnum = do
    let e = err best
    _ <- printf "Generation: %02d, Error: %.8f\n" gnum e
    return $ e < 0.0002 || gnum > 20

main = do
    int <- runGAIO 64 0.1 randomSinInt stopf
    putStrLn ""
    putStrLn $ "Result: " ++ show int

Synopsis

Documentation

class NFData a => Chromosome a where Source

Chromosome interface

Methods

crossover :: RandomGen g => a -> a -> Rand g [a] Source

Crossover function

mutation :: RandomGen g => a -> Rand g a Source

Mutation function

fitness :: a -> Double Source

Fitness function. fitness x > fitness y means that x is better than y

runGA Source

Arguments

:: (RandomGen g, Chromosome a) 
=> g

Random number generator

-> Int

Population size

-> Double

Mutation probability [0, 1]

-> Rand g a

Random chromosome generator (hint: use currying or closures)

-> (a -> Int -> Bool)

Stopping criteria, 1st arg - best chromosome, 2nd arg - generation number

-> a

Best chromosome

Pure GA implementation.

runGAIO Source

Arguments

:: Chromosome a 
=> Int

Population size

-> Double

Mutation probability [0, 1]

-> RandT StdGen IO a

Random chromosome generator (hint: use currying or closures)

-> (a -> Int -> IO Bool)

Stopping criteria, 1st arg - best chromosome, 2nd arg - generation number

-> IO a

Best chromosome

Non-pure GA implementation.

zeroGeneration Source

Arguments

:: (Monad m, RandomGen g, Chromosome a) 
=> RandT g m a

Random chromosome generator (hint: use closures)

-> Int

Population size

-> RandT g m [a]

Zero generation

Generate zero generation. Use this function only if you are going to implement your own runGA.

nextGeneration Source

Arguments

:: (Monad m, RandomGen g, Chromosome a) 
=> [a]

Current generation

-> Int

Population size

-> Double

Mutation probability

-> RandT g m [a]

Next generation ordered by fitness (best - first)

Generate next generation (in parallel) using mutation and crossover. Use this function only if you are going to implement your own runGA.