import Data.Maybe (mapMaybe) import Numeric.QD (QuadDouble) import Numeric.QD.Vec () import Fractal.GRUFF import Fractal.RUFF.Mandelbrot.Address (parseAngledInternalAddress) import Fractal.RUFF.Mandelbrot.Atom (MuAtom(..), findAtom_) import Fractal.RUFF.Types.Complex (Complex((:+))) main :: IO () main = defaultMain animation animation :: [(Image, FilePath)] animation = mapMaybe scene (score `zip` [0..]) scene :: (String, Int) -> Maybe (Image, FilePath) scene (s, n) = do m <- findAtom_ =<< parseAngledInternalAddress s let cx :+ cy = muNucleus m :: Complex QuadDouble f = filename n 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 = 256 , height = 256 , supersamples = 8 } , imageColours = Colours { colourInterior = Colour 1 0 0 , colourBoundary = Colour 0 0 0 , colourExterior = Colour 1 1 1 } , imageLabels = [] , imageLines = [] } return (i, f) filename :: Int -> FilePath filename n = (reverse . take 2 . (++ "00") . reverse . show) n ++ ".ppm" score :: [String] score = [ "1 " ++ show k ++ "/29 " ++ (unwords . map show) [ 30 .. 38 :: Int ] | k <- [ 1 .. 28 ] ++ [ 27, 26 .. 2 :: Int ] ]