simple-genetic-algorithm-0.2.0.0: Simple parallel genetic algorithm implementation

Safe HaskellNone

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 g (SinInt xs) (SinInt ys) =
         ( [ SinInt (L.zipWith (\x y -> (x+y)/2) xs ys) ], g)
 
     mutation g (SinInt xs) =
         let (idx, g') = randomR (0, length xs - 1) g
             (dx, g'') = randomR (-10.0, 10.0) g'
             t = xs !! idx
             xs' = take idx xs ++ [t + t*dx] ++ drop (idx+1) xs
         in (SinInt xs', g'')
 
     fitness int =
         let max_err = 1000.0 in
         max_err - (min (err int) max_err)
 
 randomSinInt gen = 
     let (lst, gen') =
             L.foldl'
                 (\(xs, g) _ -> let (x, g') = randomR (-10.0,10.0) g in (x:xs,g') )
                 ([], gen) [0..polynomialOrder]
     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 whereSource

Chromosome interface

Methods

crossover :: RandomGen g => g -> a -> a -> ([a], g)Source

Crossover function

mutation :: RandomGen g => g -> a -> (a, g)Source

Mutation function

fitness :: a -> DoubleSource

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

runGASource

Arguments

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

Random number generator

-> Int

Population size

-> Double

Mutation probability [0, 1]

-> (g -> (a, g))

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.

runGAIOSource

Arguments

:: Chromosome a 
=> Int

Population size

-> Double

Mutation probability [0, 1]

-> (StdGen -> (a, StdGen))

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.

zeroGenerationSource

Arguments

:: RandomGen g 
=> g

Random number generator

-> (g -> (a, g))

Random chromosome generator (hint: use closures)

-> Int

Population size

-> ([a], g)

Zero generation and new RNG

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

nextGenerationSource

Arguments

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

Random number generator

-> [a]

Current generation

-> Int

Population size

-> Double

Mutation probability

-> ([a], g)

Next generation ordered by fitness (best - first) and new RNG

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