The Evolution Of Flibs

July 13, 2012

[ Today’s guest author, Sam Kennedy, is a hobbyist programmer just finishing his A-levels in Newcastle, England. ]

Genetic programming is a branch of artificial intelligence in which programmable machines are evolved to perform a specific task; among other tasks, genetic programming is used in the design of electrical circuits, development of chemical reactions, and solving instances of the travelling salesman problem. In today’s exercise we will look at artificial organisms called flibs (“finite living blobs”) invented by A. K Dewdney in his book The Armchair Universe (which we’ve seen in two previous exercises) which learn to recognize and predict the elements of a sequence.

The DNA of a flib is a finite state machine like that shown above right; the sample machine has three states A, B and C, and two input/output symbols 0 and 1, and can be written in its alternate form 1B1C0C0B1A0A, which we call a chromosome. A gene is a symbol in the chromosome: A, B, C, 0, or 1. An allele is a gene at a particular locus: The allele 0 at locus 7 of chromosome 1B1C0C0B1A0A controls the flib’s output symbol when it is in state B and receives an input symbol of 1. The task performed by a flib is to recognize and predict a sequence of input/output states; for instance, the sample flib responds to the input sequence 0111000010110 with the output sequence 100001100100. By shifting the output bits one place to the right, we see only 6 of the 12 predictions are correct, a score of 50% which is no better than random chance.

The purpose of genetic programming is to evolve a flib that perfectly predicts a random sequence. For instance, the sequence 010011010011010011… (an infinite sequence that repeats 010011 forever) can be predicted perfectly by the sample flib that failed on the earlier input sequence; the input sequence must cycle, as no flib can perfectly predict a random (non-repeating) sequence.

Genetic programming uses two operators. Mutation occurs when an allele is changed at random (think of a gene being struck by a cosmic ray); for instance, the chromosome 0D1C0D0B1A0C1B1A might be changed to 0D0C0D0B1A0C1B1A by mutation. Crossover occurs when two chromosomes breed by exchanging portions of their gene sequence. For instance, the chromosomes 0D1C0D0B1A0C1B1A and 1A1B0D1A0C1D1B0C might breed by replacing the fourth through eighth genes of the second chromosome with those of the first chromosome, forming the offspring chromosome 1A1C0D0B0C1D1B0C; the two crossover points are selected at random.

Given all that, the genetic algorithm takes a set of randomly-generated chromosomes (the gene pool), say a dozen of them, and runs the following loop:

1) calculate the score of each flib on identical input sequences
2) find the flibs with the highest and lowest scores
3) replace the lowest-scoring flib with its crossover with the highest-scoring flib, sometimes
4) mutate a single gene on a single flib

Each time a flib beats the current high score, its score and chromosome are printed; the loop continues until a flib reaches a perfect score or your patience is exhausted. In Step 3, the crossover is only performed sometimes, say 3 times out of 10, because if the flibs breed too often the gene pool becomes very similar to that of the highest-scoring flib and loses diversity; on the other hand, if they breed infrequently the simulation will take longer.

Your task is to write a genetic program that breeds perfect flibs. When you are finished, you are welcome to read or run a suggested solution, or to post your own solution or discuss the exercise in the comments below.

Pages: 1 2

7 Responses to “The Evolution Of Flibs”

  1. phil said

    http://pastebin.com/9Ez1xmU4
    i have all the necessary functions to create a flib simulation, except the run function itself. note that crossover, perhaps the most important function short of the score, is currently poor.

  2. […] today’s Programming Praxis exercise, our goal is to implement a genetic algorithm to evolve finite state […]

  3. My Haskell solution (see http://bonsaicode.wordpress.com/2012/07/13/programming-praxis-the-evolution-of-flibs/ for a version with comments):

    import Control.Monad
    import Data.List
    import System.Random
    
    data Args = Args { _symbols :: String, _numSymbols :: Int
                     , _states  :: String, _numStates :: Int }
    
    runFlib :: Args -> (Char, String) -> Char -> ((Char, String), Char)
    runFlib (Args smbs nsmbs sts _) (s, m) input = ((s',m), out) where
        (out:s':_) = drop (2 * (nsmbs * index s sts + index input smbs)) m
        index x    = head . elemIndices x
    
    score :: Int -> Args -> String -> String -> Int
    score run args flib input = length . filter id . zipWith (==) (tail input') .
        snd . mapAccumL (runFlib args) (head $ _states args,flib) $ init input'
        where input' = take (run + 1) $ cycle input
    
    oneOf :: [a] -> IO a
    oneOf xs = fmap (xs !!) $ randomRIO (0, length xs - 1)
    
    replace :: Int -> a -> [a] -> [a]
    replace i v xs = take i xs ++ v : drop (i + 1) xs
    
    randomFlib :: Args -> IO String
    randomFlib (Args smbs nsmbs sts nsts) = fmap concat $
        replicateM (nsmbs * nsts) (sequence [oneOf smbs, oneOf sts])
    
    crossover :: Args -> String -> String -> IO String
    crossover (Args _ nsmbs _ nsts) a b = do
        start <- randomRIO (0,         2 * nsmbs * nsts - 2)
        end   <- randomRIO (start + 1, 2 * nsmbs * nsts - 1)
        return $ take start a ++ take (end - start) (drop start b) ++ drop end a
        
    mutate :: Args -> String -> IO String
    mutate (Args smbs nsmbs sts nsts) flib = do
        i <- randomRIO (0, 2 * nsmbs * nsts - 1)
        c <- oneOf $ if mod i 2 == 0 then smbs else sts
        return $ replace i c flib
    
    evolve :: String -> Int -> Float -> Int -> String -> IO ()
    evolve states popSize breedChance run input =
        nextGen (0, "") =<< replicateM popSize (randomFlib args) where
        args = Args (map head symbols) (length symbols)
                    states  (length . group $ sort states)
                    where symbols = group $ sort input
        nextGen (top,_) _ | top == run = return ()
        nextGen best pop = do
            let scored = sort $ map (\flib -> (score run args flib input, flib)) pop
            let top = last scored
            when (fst top > fst best) (print top)
            breed <- fmap (< breedChance) $ randomRIO (0, 1)
            mix <- crossover args (snd $ head scored) (snd top)
            let newPop = (if breed then replace 0 mix else id) (map snd scored)
            mutIndex <- randomRIO (0, popSize - 1)
            mutant <- mutate args (newPop !! mutIndex)
            nextGen (max best top) $ replace mutIndex mutant newPop
    
    main :: IO ()
    main = evolve "ABCD" 10 0.3 100 "010011"
    
  4. kawas said

    My Clojure solution where you provide states and input symbols

    (defn rand-flib
      "Generate a random flib based on states and symbols"
      [states symbols]
      (apply str
        (flatten (for [_ states _ symbols]
                      [(rand-nth symbols) (rand-nth states)]))))
    
    (defn rand-flib-coll
      "Generate a random vector population of n flibs"
      [n states symbols]
      (vec (for [_ (range n)] (rand-flib states symbols))))
    
    (defn rand-mutate
      "Mutate a flib's random allele"
      [flib states symbols]
      (let [locus (rand-int (count flib))
            ref-coll (if (zero? (rem locus 2)) symbols states)]
        (str (subs flib 0 locus) (rand-nth ref-coll) (subs flib (inc locus)))))
    
    (defn rand-breed
      "Crossover two flibs on a random portion of their adn"
      [flib flib-hi]
      (let [n (inc (count flib))
            [i1 i2] (sort [(rand-int n) (rand-int n)])]
        (str (subs flib 0 i1) (subs flib-hi i1 i2) (subs flib i2))))
    
    (defn index-of
      "Return index of value in collection"
      [v coll] (first (keep-indexed #(when (= %2 v) %1) coll)))
    
    (defn predict
      "Apply Flib to input to predict output"
      [flib inputs states symbols]
      (let [align-st (* 2 (count symbols))]
        (loop [inputs inputs state (first states) outputs []]
          (if (nil? inputs) outputs
            (let [idx-als (* align-st (index-of state states))
                  align-sy (* 2 (index-of (first inputs) symbols))
                  o (nth flib (+ idx-als align-sy))
                  s (nth flib (+ idx-als align-sy 1))]
              (recur (next inputs) s (conj outputs o)))))))
    
    (defn calc-score
      "Calculate score of flib's output compared to input"
      [inputs outputs]
      (int (* 100
              (/ (count (filter true? (map = (next inputs) (butlast outputs))))
                 (dec (count inputs))))))
    
    (defn evolve
      "Generate Flibs and loop to evaluate flibs predictions
       and mutate population"
      [states symbols nflibs bratio nloop inputs]
      (loop [i 1
             flibs (rand-flib-coll nflibs states symbols)
             score 0]
        (if (or (> i nloop) (= score 100)) nil
          (let [fouts (map #(predict % inputs states symbols) flibs)
                fscr-map (zipmap flibs (map #(calc-score inputs %1) fouts))
                fscr-sorted (sort-by second fscr-map)
                flib-scr-low (first fscr-sorted)
                flib-scr-hi (last fscr-sorted)
                idx-low (index-of (first flib-scr-low) flibs)
                flibs1 (if (>= (rand-int 100) bratio) flibs
                         (assoc flibs idx-low
                                (rand-breed (first flib-scr-hi)
                                            (first flib-scr-low))))
                idx-rnd (rand-int nflibs)
                flibs2 (assoc flibs1 idx-rnd
                              (rand-mutate (flibs idx-rnd) states symbols))]
            (println i flib-scr-hi)
            (recur (inc i) flibs2 (second flib-scr-hi))))))
    
    (evolve "ABCD" "01" 10 30 100 "010011")
    
  5. JP said

    A bit behind the times, but here’s my solution in Racket: Flibs

    I’ve always loved messing with genetic algorithms and have tried to work out a good general purpose solution to this very problem (evolving FSAs) before. Unfortunately it always comes down to adding new structure and actually making the connections to it. Most of the time, the new structure just doesn’t get used and thus gets optimized away instead. We’ll see if I can’t make another crack at it this weekend.

    The version I’ve posted doesn’t exactly match the problem as it uses a different strategy for who and how many new flibs to breed, but it’s pretty close and it does solve the problem:

    > (run (string->input (repeat-string "010011" 5)))
    new best flib: #(1 C 1 C 1 B 1 A 1 A 0 A) scoring 0.8275862068965517
    new best flib: #(1 B 1 A 0 C 0 B 1 A 0 A) scoring 0.8620689655172413
    new best flib: #(1 A 1 C 1 B 0 C 0 A 0 B) scoring 0.9655172413793104
    new best flib: #(1 C 0 A 0 C 1 A 1 B 0 B) scoring 1.0
    '#(1 C 0 A 0 C 1 A 1 B 0 B)
    
  6. […] just appeals to me for some reason. So when I came across a puzzle on on Programming Praxis called The Evolution of Flibs, I just knew that I had to give it a […]

Leave a comment