7

I'm writing a genetic algorithm to generate the string "helloworld". But the evolve function creates a stack overflow when n is 10,000 or more.

module Genetics where

import Data.List (sortBy)
import Random (randomRIO)
import Control.Monad (foldM)

class Gene g where
    -- How ideal is the gene from 0.0 to 1.0?
    fitness :: g -> Float

    -- How does a gene mutate?
    mutate :: g -> IO g

    -- How many species will be explored?
    species :: [g] -> Int

orderFitness :: (Gene g) => [g] -> [g]
orderFitness = reverse . sortBy (\a b -> compare (fitness a) (fitness b))

compete :: (Gene g) => [g] -> IO [g]
compete pool = do
    let s = species pool
    variants <- (mapM (mapM mutate) . map (replicate s)) pool
    let pool' = (map head . map orderFitness) variants
    return pool'

evolve :: (Gene g) => Int -> [g] -> IO [g]
evolve 0 pool = return pool
evolve n pool = do
    pool' <- compete pool
    evolve (n - 1) pool'

With species pool = 8, a pool of 8 genes replicates to 8 groups. Each group mutates, and the fittest of each group is selected for further evolution (back to 8 genes).

GitHub

Don Stewart
  • 137,316
  • 36
  • 365
  • 468
mcandre
  • 22,868
  • 20
  • 88
  • 147
  • 2
    Assuming you're using `ghc -O2` as your compiler, your first version doesn't have any stack overflow in the `evolve` function. Since we can't see the implementation of `compete`, that's all that can be said. – Don Stewart May 10 '11 at 21:25
  • The GitHub link provided above (https://github.com/mcandre/genetics) specifies `compete` as well as a Makefile that indeed uses `ghc -O2`. I thought `<-` in the first example was good enough to prevent stack overflow. I'm not sure where the problem is located. – mcandre May 10 '11 at 21:32
  • >>= should be equal to the do notation, theres no difference there. – alternative May 10 '11 at 21:36
  • 2
    As dons noted, the problem is entirely in the compete function, which is doubtless getting run many many times on top of one another building up a datastructure that has a big chain of thunks. I'm sure the github link has the necessary data but it would be much more helpful to those that want to help you to post a complete working example demonstrating your issue here -- and preferrably one as reduced as possible. In the meantime, the quick+dirty solution is to rnf or otherwise force your pool on each recursive call. – sclv May 10 '11 at 21:38
  • 1
    Hmm, why do they use the IO monad here in the first place? Seems ugly and non-idiomatic. They should probably use a randomness monad instead, or provide random numbers directly to the mutation function. – alternative May 10 '11 at 21:39
  • @mathepic Sounds like a good idea from what I gather about monads. I'm using IO only because I'm new to Haskell and it's the only one I understand. – mcandre May 10 '11 at 21:42
  • @all Added `compete`. I agree, the poster should make the effort to elaborate on his code. – mcandre May 10 '11 at 21:44
  • That's a fabulous first two sentences, and deliberately misinterpreting your purpose amused me greatly: This has to be the most indirect Hello World implementation I've seen, and certainly the only one I've come across which has issues with stack overflow. Wow! Have you tried `main = print "Hello World"`? (Just joking, but I couldn't resist, sorry. +1 for depth.) – AndrewC Sep 22 '12 at 14:35

3 Answers3

3

If you're interested in performance, I'd use a fast random number generator, such as:

Secondly, compete looks very suspicious, as it is entirely lazy, despite building some potentially large structures. Try rewriting it to be a bit stricter, using the deepseq hammer:

import Control.DeepSeq    

compete :: (Gene g, NFData g) => [g] -> IO [g]
compete pool = do
    let s = species pool
    variants <- (mapM (mapM mutate) . map (replicate s)) pool
    let pool' = (map head . map orderFitness) variants
    pool' `deepseq` return pool'

None of this stuff needs to be in IO, though, (separate issue). Something like the Rand monad may be more appropriate.

mcandre
  • 22,868
  • 20
  • 88
  • 147
Don Stewart
  • 137,316
  • 36
  • 365
  • 468
  • @Don The `deepseq` hammer solves the problem (upvote). But it feels like cheating. I'd like to find out where in `compete` the stack overflow occurs. – mcandre May 10 '11 at 22:53
  • A likely candidate is the use of nested `mapM`. However, to be sure: profile. Like this: http://stackoverflow.com/questions/5939630/best-way-of-looping-over-a-2-d-array-using-repa/5940537#5940537 – Don Stewart May 10 '11 at 23:06
  • @mcandre you might be interested in [RWH # space profiling](http://book.realworldhaskell.org/read/profiling-and-optimization.html#id678078) – Dan Burton May 10 '11 at 23:07
  • 1
    @Don Separating `(mapM (mapM ...` and `(map head ...)` into two functions (`drift` and `compete`) and moving `deepseq` into `drift` works, so the problem is somewhere in `(mapM (mapM mutate) . map (replicate s)) pool`. I believe `(mapM (mapM ...` creates a stack overflow. – mcandre May 10 '11 at 23:10
  • @Don Wow, you Galois folks know your stuff. Could you add example code to the mersenne-random-pure64 Hackage page (http://hackage.haskell.org/package/mersenne-random-pure64), in particular, how to seed Mersenne using the system clock or other source? – mcandre May 10 '11 at 23:46
  • 1
    @mcandre - check the haddocks, you use `pureMT :: Word64 -> PureMT` to initialize the generator with a 64 bit int, which might come from anywhere, or `newPureMT` if you want to seed from the clock. – Don Stewart May 11 '11 at 00:09
  • @Don Thanks for the RWH link, great book. I added profiling (https://github.com/mcandre/genetics/blob/master/Makefile) and random number generation was a thin line compared to other function calls. For more complicated genes than "helloworld", efficient PRNGs will be necessary. – mcandre May 11 '11 at 00:14
2

Thanks to Don's deepseq suggestion, I was able to narrow the problem to mapM mutate which made too many thunks. The new version has mutate', which uses seq to prevent thunking.

module Genetics where

import Data.List (maximumBy)
import Random (randomRIO)

class Gene g where
    -- How ideal is the gene from 0.0 to 1.0?
    fitness :: g -> Float

    -- How does a gene mutate?
    mutate :: g -> IO g

    -- How many species will be explored in each round?
    species :: [g] -> Int

best :: (Gene g) => [g] -> g
best = maximumBy (\a b -> compare (fitness a) (fitness b))

-- Prevents stack overflow
mutate' :: (Gene g) => g -> IO g
mutate' gene = do
    gene' <- mutate gene
    gene' `seq` return gene'

drift :: (Gene g) => [[g]] -> IO [[g]]
drift = mapM (mapM mutate')

compete :: (Gene g) => [g] -> IO [g]
compete pool = do
    let islands = map (replicate (species pool)) pool
    islands' <- drift islands
    let representatives = map best islands'
    return representatives

evolve :: (Gene g) => Int -> [g] -> IO [g]
evolve 0 pool = return pool
evolve n pool = compete pool >>= evolve (n - 1)

GitHub

mcandre
  • 22,868
  • 20
  • 88
  • 147
1

Instead of using (map head . map orderFitness) where orderFitness is a sortBy you could use maximumBy and a single map. That doesn't save too much (since you are going from an O(n log n) to O(n) and might be getting another factor of two from eliminating the double map), but is at the least somewhat simpler and more efficient. You would also get rid of a call to reverse.

I doubt this fixes the problem without a deepseq, but it should be an improvement none the less.

Edit: if the standard library and GHC were perfect, then head . sortBy would produce identical code to maximumBy and map head . map sortBy would produce identical code to map (head . sortBy) sadly neither of these things is likely to be true in practice. sortBy will tend to do a bunch of extra memory allocation because it is a divide and conquer algorithm. Combining maps is an optimization you sometimes get, but should not count on.

More importantly, using maximumBy is more declarative. It is easier to see what the code does and how long it will take. It should also be easier to take advantage of in optimizations, because we know what the goal is, not just how we get it.

Philip JF
  • 28,199
  • 5
  • 70
  • 77