3

I am trying to express an L-system in Haskell https://en.m.wikipedia.org/wiki/L-system, specifically Lindenmayer's original L-system for modelling the growth of algae.

variables : A B
constants : none
axiom : A
rules : (A → AB), (B → A)

For me the natural way to approach this problem is to apply the rules to each element in the list, which (to me) means that I could model the solution using some type of string substitution.

Example:

For the list of "characters" [A, B, A we'd apply the rules and get [A → AB, B → A, A → AB] = [A, B, A, A, B] (for this model to play along nicely with Haskell you will have to regard AB as a list [A, B] which we will combine with any other results produced with the rules above).

I have produced the code included below which is complete with data constructors to not have to handle other characters than A or B,

data Letter = A | B deriving (Show, Eq)

type Alphabet = [Letter]

algae :: Alphabet -> Alphabet

algae = concat . map (\c -> if
                | c == A -> A:[B]
                | c == B -> [A])

The above code is such that calling it with itself as an argument yields the expected result, viz. that

algae $ algae $algae [A] =  [A, B, A, A, B]

Repeated applications work as expected.

What I want to accomplish next is for the function to apply recursively onto itself, but have failed to express this. By this I mean that I would like to be able to call the function, either as algae [A] or just algae (which would require a type signature change to algae :: Alphabet) which yields an infinite list that one would receive by applying algae onto itself infinitely many times.

Since I have admitted defeat I have looked at http://hackage.haskell.org/package/lindenmayer-0.1.0.0/docs/Lindenmayer-D0L.html but I cannot comprehend the code as it is (yet) and also found other equally confusing implementations.

I've tried my best to attempt to use using folds and the fix function but have failed in doing so. I have also tried to borrow from other recursive definitions such as

fibs = 0 : 1 : zipWith (+) fibs (tail fibs)

But that approach fails since zipWith expects a binary operator. Can this problem be solved without monads? If so, how?

Filip Allberg
  • 3,941
  • 3
  • 20
  • 37
  • It is worth noting that the `Monad` instance for `[a]` is actually just `concatMap`, and is not scary at all! – C. Quilley Oct 15 '15 at 11:25
  • I wrote a thing on L-Systems in Haskell: http://reinh.com/notes/posts/2015-06-27-theoretical-pearl-l-systems-as-final-coalgebras.html – Rein Henrichs Oct 15 '15 at 16:37

2 Answers2

5

You can use iterate. I would also suggest a slight modification to your algae function to use pattern matching:

data Letter = A | B deriving (Show, Eq)

type Alphabet = [Letter]

algae :: Alphabet -> Alphabet
algae = concatMap f
  where f A = [A, B]
        f B = [A]

infAlgae :: [Alphabet]
infAlgae = iterate algae [A]

main :: IO ()
main = print $ infAlgae !! 3 
Sam van Herwaarden
  • 2,321
  • 14
  • 27
  • That is almost what I am trying to accomplish, I would like for `take 4 infAlgae` to be `[A,B,A,A,B]` instead of `[[A],[A,B],[A,B,A],[A,B,A,A,B]]` but I suppose I could figure out a way to wrap it somehow. Nevermind, I see you have already done so using `!!`. Thanks! – Filip Allberg Oct 15 '15 at 11:36
4

I thought you might also be interested in how to efficiently produce an actual infinite list, fibs style:

import Data.List (stripPrefix)

data Letter = A | B deriving (Show, Eq)

type Alphabet = [Letter]

algae :: Alphabet -> Alphabet
algae = concatMap f
  where f A = [A, B]
        f B = [A]

infFromPrefix :: Eq a => ([a] -> [a]) -> [a] -> [a]
infFromPrefix rule prefix = inf where
    inf = prefix ++ case stripPrefix prefix (rule inf) of
        Just suffix -> suffix
        Nothing     -> error "Substitution does not preserve prefix"

infAlgae :: Alphabet
infAlgae = infFromPrefix algae [A]

main :: IO ()
main = print . take 100 $ infAlgae

And in GHCi:

*Main> :main
[A,B,A,A,B,A,B,A,A,B,A,A,B,A,B,A,A,B,A,B,A,A,B,A,A,B,A,B,A,A,B,A,A,B,A,B,A,A,B,A,B,A,A,B,A,A,B,A,B,A,A,B,A,B,A,A,B,A,A,B,A,B,A,A,B,A,A,B,A,B,A,A,B,A,B,A,A,B,A,A,B,A,B,A,A,B,A,A,B,A,B,A,A,B,A,B,A,A,B,A]
Ørjan Johansen
  • 18,119
  • 3
  • 43
  • 53
  • I realize now that I did not read the question very carefully. I was also not aware that the substitution preserves the prefix. Nice answer. – Sam van Herwaarden Oct 15 '15 at 17:09