-- | Lindenmayer system definition, expander and renderer. module LSystem.LSystem where import Graphics.PS.Pt import LSystem.Turtle import Data.Map as Map -- | Element of 'Axiom'. type Element = Char -- | An axiom (sequence of 'Elements'). type Axiom = [Element] -- | A 'Map.Map' from 'Element's to 'Axiom's. type Rules = Map.Map Element Axiom -- | An 'LSystem' is an 'Axiom' and a set of 'Rules'. data LSystem = LSystem Axiom Rules deriving (Eq,Show) -- | L-System constructor. -- -- > lSystem "F+F+F" [('F',"F-F+F")] lSystem :: Axiom -> [(Element,[Element])] -> LSystem lSystem a rs = LSystem a (fromList rs) -- | Rule lookup. getRule :: Rules -> Element -> [Element] getRule rs c = Map.findWithDefault [c] c rs -- | Rule application. applyRule :: [Element] -> Rules -> [Element] applyRule a rs = concatMap (getRule rs) a -- | /n/ iterations of the specified 'LSystem'. -- -- > expand (lSystem "F+F+F" [('F',"F-F+F")]) 1 == "F-F+F+F-F+F+F-F+F" expand :: LSystem -> Int -> [Element] expand (LSystem a rs) n = case n of 0 -> a _ -> expand (LSystem (applyRule a rs) rs) (n - 1) -- | State transformer 'Turtle' commands. stateT :: Element -> Turtle -> Turtle stateT e = case e of '+' -> turnRight '-' -> turnLeft '|' -> turnBack '>' -> incrLine '<' -> decrLine '[' -> push ']' -> pop 'f' -> forward _ -> id -- | Operational 'Turtle' commands. cmd :: (Turtle -> b -> (Turtle,b)) -> Element -> Turtle -> b -> (Turtle,b) cmd f e t i = case e of 'F' -> f t i _ -> (stateT e t, i) -- | Fold over an expanded L-system using standard turtle commands. render :: b -> (b -> Pt -> Pt -> b) -> [Element] -> Turtle -> b render i f l t = let g (u,j) c = cmd (stepTurtle f) c u j in snd (foldl g (t, i) l)