Skip to content

Instantly share code, notes, and snippets.

@weskerfoot
Created November 28, 2012 21:39
Show Gist options
  • Save weskerfoot/4164772 to your computer and use it in GitHub Desktop.
Save weskerfoot/4164772 to your computer and use it in GitHub Desktop.
L-Systems
module LSystem where
import Control.Monad
data LSymbol = LRule Char | LDeriv String
type Alphabet = [LSymbol]
type Axiom = [LSymbol]
-- a production is a finite mapping of LSymbol -> LSymbol
-- if no production exists for a given LSymbol on the LHS of a Production
-- then an idempotent production is assumed, that is, identity
data Production = Production LSymbol LSymbol deriving (Show)
type Productions = [Production]
instance Eq LSymbol where
(LRule a) == (LDeriv b) = [a] == b
instance Show LSymbol where
show (LRule a) = [a]
show (LDeriv a) = a
instance Eq Production where
(Production a b) == (Production a' b') = a == a' && b == b'
tryProd [] symb = symb
tryProd ((Production pred succ):ps) symb
| pred == symb = succ
| otherwise = tryProd ps symb
prodToDeriv prods xs = convert (map (tryProd prods) xs) where
convert ((LDeriv derivation):[]) = map (LDeriv . (:[])) derivation
convert ((LDeriv derivation):ds) = (map (LDeriv . (:[])) derivation) ++ (convert ds)
algaeProds = [Production (LRule 'A') (LDeriv "AB"), Production (LRule 'B') (LDeriv "A"), Production (LRule 'C') (LDeriv "CBCA")]
algaeAxioms = [LDeriv "ACBC"]
treeProds = [Production (LRule 'X') (LDeriv "F-[[X]+X]+F[+FX]-X"), Production (LRule 'F') (LDeriv "FF")]
treeAxioms = [LDeriv "X"]
genTree n = join $ map show $ foldr (\_ a -> prodToDeriv treeProds a) treeAxioms [1..n]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment