{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Moo.GeneticAlgorithm.Binary (
module Moo.GeneticAlgorithm.Types
, encodeGray
, decodeGray
, encodeBinary
, decodeBinary
, encodeGrayReal
, decodeGrayReal
, bitsNeeded
, splitEvery
, getRandomBinaryGenomes
, rouletteSelect
, stochasticUniversalSampling
, tournamentSelect
, withPopulationTransform
, withScale
, rankScale
, withFitnessSharing
, hammingDistance
, bestFirst
, module Moo.GeneticAlgorithm.Crossover
, pointMutate
, asymmetricMutate
, constFrequencyMutate
, module Moo.GeneticAlgorithm.Random
, module Moo.GeneticAlgorithm.Run
) where
import Codec.Binary.Gray.List
import Data.Bits
import Data.List (genericLength)
import Moo.GeneticAlgorithm.Crossover
import Moo.GeneticAlgorithm.Random
import Moo.GeneticAlgorithm.Selection
import Moo.GeneticAlgorithm.Types
import Moo.GeneticAlgorithm.Run
import Moo.GeneticAlgorithm.Random
import Moo.GeneticAlgorithm.Utilities (getRandomGenomes)
bitsNeeded :: (Integral a, Integral b) => (a, a) -> b
bitsNeeded (from, to) =
let from' = min from to
to'= max from to
in ceiling . logBase (2::Double) . fromIntegral $ (to' - from' + 1)
#if MIN_VERSION_base(4, 7, 0)
encodeGray :: (FiniteBits b, Bits b, Integral b) => (b, b) -> b -> [Bool]
#else
encodeGray :: (Bits b, Integral b) => (b, b) -> b -> [Bool]
#endif
encodeGray = encodeWithCode gray
#if MIN_VERSION_base(4, 7, 0)
decodeGray :: (FiniteBits b, Bits b, Integral b) => (b, b) -> [Bool] -> b
#else
decodeGray :: (Bits b, Integral b) => (b, b) -> [Bool] -> b
#endif
decodeGray = decodeWithCode binary
#if MIN_VERSION_base(4, 7, 0)
encodeBinary :: (FiniteBits b, Bits b, Integral b) => (b, b) -> b -> [Bool]
#else
encodeBinary :: (Bits b, Integral b) => (b, b) -> b -> [Bool]
#endif
encodeBinary = encodeWithCode id
#if MIN_VERSION_base(4, 7, 0)
decodeBinary :: (FiniteBits b, Bits b, Integral b) => (b, b) -> [Bool] -> b
#else
decodeBinary :: (Bits b, Integral b) => (b, b) -> [Bool] -> b
#endif
decodeBinary = decodeWithCode id
encodeGrayReal :: (RealFrac a) => (a, a) -> Int -> a -> [Bool]
encodeGrayReal range n = encodeGray (0, n-1) . toDiscreteR range n
decodeGrayReal :: (RealFrac a) => (a, a) -> Int -> [Bool] -> a
decodeGrayReal range n = fromDiscreteR range n . decodeGray (0, n-1)
toDiscreteR :: (RealFrac a)
=> (a, a)
-> Int
-> a
-> Int
toDiscreteR range n val =
let from = uncurry min range
to = uncurry max range
dx = (to - from) / (fromIntegral (n - 1))
in round $ (val - from) / dx
fromDiscreteR :: (RealFrac a)
=> (a, a)
-> Int
-> Int
-> a
fromDiscreteR range n i =
let from = uncurry min range
to = uncurry max range
dx = (to - from) / (fromIntegral (n - 1))
in from + (fromIntegral i) * dx
splitEvery :: Int -> [a] -> [[a]]
splitEvery _ [] = []
splitEvery n xs = let (nxs,rest) = splitAt n xs in nxs : splitEvery n rest
#if MIN_VERSION_base(4, 7, 0)
encodeWithCode :: (FiniteBits b, Bits b, Integral b) => ([Bool] -> [Bool]) -> (b, b) -> b -> [Bool]
#else
encodeWithCode :: (Bits b, Integral b) => ([Bool] -> [Bool]) -> (b, b) -> b -> [Bool]
#endif
encodeWithCode code (from, to) n =
let from' = min from to
to' = max from to
nbits = bitsNeeded (from', to')
in code . take nbits $ toList (n - from') ++ (repeat False)
#if MIN_VERSION_base(4, 7, 0)
decodeWithCode :: (FiniteBits b, Bits b, Integral b) => ([Bool] -> [Bool]) -> (b, b) -> [Bool] -> b
#else
decodeWithCode :: (Bits b, Integral b) => ([Bool] -> [Bool]) -> (b, b) -> [Bool] -> b
#endif
decodeWithCode decode (from, to) bits =
let from' = min from to
in (from' +) . fromList . decode $ bits
getRandomBinaryGenomes :: Int
-> Int
-> Rand ([Genome Bool])
getRandomBinaryGenomes n len = getRandomGenomes n (replicate len (False,True))
pointMutate :: Double -> MutationOp Bool
pointMutate p = withProbability p $ \bits -> do
r <- getRandomR (0, length bits - 1)
let (before, (bit:after)) = splitAt r bits
return (before ++ (not bit:after))
asymmetricMutate :: Double
-> Double
-> MutationOp Bool
asymmetricMutate prob0to1 prob1to0 = mapM flipbit
where
flipbit False = withProbability prob0to1 (return . not) False
flipbit True = withProbability prob1to0 (return . not) True
constFrequencyMutate :: Real a
=> a
-> MutationOp Bool
constFrequencyMutate m bits =
let (ones, zeros) = foldr (\b (o,z) -> if b then (o+1,z) else (o,z+1)) (0,0) bits
p0to1 = fromRational $ 0.5 * (toRational m) / zeros
p1to0 = fromRational $ 0.5 * (toRational m) / ones
in asymmetricMutate p0to1 p1to0 bits
hammingDistance :: (Eq a, Num i) => [a] -> [a] -> i
hammingDistance xs ys = genericLength . filter id $ zipWith (/=) xs ys