import Data.Maybe (mapMaybe) import Fractal.GRUFF import Fractal.RUFF.Mandelbrot.Address (parseAngledInternalAddress) import Fractal.RUFF.Mandelbrot.Atom (MuAtom(..), findAtom_) import Fractal.RUFF.Types.Complex (Complex((:+))) import Number (R) main :: IO () main = defaultMain animation animation :: [(Image, FilePath)] animation = mapMaybe scene score scene :: String -> Maybe (Image, FilePath) scene s = do m <- findAtom_ =<< parseAngledInternalAddress s let cx :+ cy = muNucleus m :: Complex R f = filename s i = Image { imageLocation = Location { center = toRational cx :+ toRational cy , radius = muSize m * 16 } , imageViewport = Viewport { aspect = 1 , orient = muOrient m - pi / 2 } , imageWindow = Window { width = 512 , height = 288 , supersamples = 8 } , imageColours = Colours { colourInterior = Colour 1 0.75 0 , colourBoundary = Colour 0 0 0 , colourExterior = Colour 1 1 1 } , imageLabels = [] , imageLines = [] } return (i, f) filename :: String -> FilePath filename s = map filechar s ++ ".ppm" where filechar ' ' = '_' filechar '/' = '-' filechar c = c score :: [String] score = [ "1 1/5 5 6 " ++ accum deltas | l <- [0 .. 124] , let m = l `div` 5 , let n = l `mod` 5 + 1 , let deltas = replicate m 5 ++ [n] ] where accum = unwords . map show . scanl (+) 11