{- Heighway dragon. See http://en.wikipedia.org/wiki/Dragon_curve. -} module Main where import Graphics.Rendering.Diagrams import Control.Monad.State import Data.Maybe dragonStr :: Int -> String dragonStr 0 = "FX" dragonStr n = concatMap rules $ dragonStr (n-1) where rules 'X' = "X+YF+" rules 'Y' = "-FX-Y" rules c = [c] strToPath :: String -> Path strToPath s = pathFromVectors . catMaybes $ evalState c (0,-1) where c = mapM exec s exec 'F' = Just `fmap` get exec '-' = modify left >> return Nothing exec '+' = modify right >> return Nothing exec _ = return Nothing left (x,y) = (-y,x) right (x,y) = (y,-x) dragon :: Int -> Diagram dragon = lc red . curved 0.8 . strToPath . dragonStr main = renderAs PNG "dragon.png" (Height 500) (dragon 14)