Skip to content

Instantly share code, notes, and snippets.

@tlehman
Created June 12, 2024 01:00
Show Gist options
  • Save tlehman/65d083d5888615fb778e25170333cbd6 to your computer and use it in GitHub Desktop.
Save tlehman/65d083d5888615fb778e25170333cbd6 to your computer and use it in GitHub Desktop.
Mandelbrot set in Haskell
-- mandelbrot.hs using recursion and lazy infinite lists
module Mandelbrot where
import Data.Complex
-- x :+ y is how the complex number x + iy is represented in Haskell
-- a point c ∈ ℂ is in the Mandelbrot set if |z_n| ≤ 2 for all n>0
-- z_n = z_{n-1}^2 + c
-- this is how the values expand: ((z**2 + c)**2 + c)**2 + c
-- it looks like:
-- foldl (\z c -> \z**2 + c) 0 [c,c,c...]
--
-- repeat :: a -> [a]
-- repeat c
-- => [c,c,c....]
--
-- (zn n c) returns the value z_n, where z_n = z_{n-1}^2 + c
zn :: RealFloat a => Int -> Complex a -> [Complex a]
zn n c = take n $ iterate (\z -> z**2 + c) 0
inMandelbrotSet :: (RealFloat a, Ord a) => Complex a -> Bool
inMandelbrotSet c = (realPart . abs $ last $ zn 1000 c) < 2
-- showBool is for displaying a True value as a * and a False value as a " " for use in print
showBool :: Bool -> Char
showBool b = if b then '*' else ' '
-- split a list into chunks of a given size
chunk :: Int -> [a] -> [[a]]
chunk _ [] = []
chunk n xs = let (ys, zs) = splitAt n xs
in ys : chunk n zs
chunkSize = 20
color = (showBool . inMandelbrotSet)
grid = chunk chunkSize [color (re :+ im) |
re <- take chunkSize [-1.0,-0.9..],
im <- take chunkSize [-1.0,-0.9..]]
main :: IO ()
main = do
putStrLn (concat (map (\l -> l ++ "\n") grid))
@tlehman
Copy link
Author

tlehman commented Jun 12, 2024

λ> main
        *****
        *****
         ***
        *****
      *********
    *************
     ***********
    *************
  *****************
  *****************
    *************
    *************
     ***********
     ***** *****

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment