Skip to content

Instantly share code, notes, and snippets.

@Lambdanaut
Created April 29, 2012 16:54
Show Gist options
  • Select an option

  • Save Lambdanaut/2551861 to your computer and use it in GitHub Desktop.

Select an option

Save Lambdanaut/2551861 to your computer and use it in GitHub Desktop.
A Mandelbrot Set visualizer in Haskell
module Mandelbrot where
import Graphics.UI.SDL as SDL
import System.Exit
resolution = 30
drawSlowly = True
imageWidth = 400
imageHeight = 400
minRe = -2.0
maxRe = 1.0
minIm = -1.2
maxIm = minIm + (maxRe - minRe) * (imageHeight / imageWidth)
reFactor = (maxRe-minRe)/(imageWidth-1)
imFactor = (maxIm-minIm)/(imageHeight-1)
imageArray = [ (x,y) | x <- [0.. floor imageWidth - 1], y <- [0.. floor imageHeight - 1] ]
inSet :: (Fractional a, Ord a) => (a,a) -> Bool
inSet (x,y) = if resolution == (length $ take resolution $ takeWhile (\ (x,y) -> x^2 + y^2 < 4) $ iterate (\ (zRe, zIm) -> (zRe^2 - zIm^2 + x , 2 * zRe * zIm + y ) ) (x,y) )then True else False
drawSet :: SDL.Surface -> IO ()
drawSet screen = do
putStrLn "Building Image.. please wait! "
black <- SDL.mapRGB (SDL.surfaceGetPixelFormat screen) 0 0 0
mapM_ (\ (x,y) -> if inSet (minRe + fromIntegral x * reFactor, maxIm - fromIntegral y * imFactor ) then (fillRect screen (Just $ SDL.Rect x y 1 1 ) black) >> (if drawSlowly then SDL.flip screen else return ()) else return () ) imageArray
SDL.flip screen
putStrLn "Done! "
initSDL :: IO Surface
initSDL = do
SDL.init [SDL.InitEverything]
SDL.setVideoMode (floor imageWidth) (floor imageHeight) 32 []
SDL.setCaption "Mandelbrot" "Mandelbrot"
screen <- getVideoSurface
white <- SDL.mapRGB (SDL.surfaceGetPixelFormat screen) 255 255 255
fillRect screen Nothing white >> SDL.flip screen
return screen
exitHandler :: IO ()
exitHandler = do
e <- waitEvent
case e of
Quit -> SDL.quit
otherwise -> exitHandler
main :: IO ()
main = do
s <- initSDL
drawSet s
exitHandler
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment