Skip to content

Instantly share code, notes, and snippets.

@roboguy13
Created August 27, 2021 02:04
Show Gist options
  • Save roboguy13/1de2b81b5a3a60c2543258621ee7d94b to your computer and use it in GitHub Desktop.
Save roboguy13/1de2b81b5a3a60c2543258621ee7d94b to your computer and use it in GitHub Desktop.
{-# LANGUAGE Strict #-}
{-# OPTIONS_GHC -O3 #-}
import Data.Complex
import Control.Applicative
import Control.Arrow
import Control.Monad
main :: IO ()
main =
forM_ complexPoints $ \row ->
let symbols = map (asciiSymbol . mandelbrotIterations) row
in
if all (== ' ') symbols
then pure ()
else putStrLn symbols
mandelbrotIterations :: Complex Double -> Int
mandelbrotIterations pt = go 0 (0 :+ 0)
where
go iters z
| magnitude (z*z) <= 2*2 && iters < maxIters = go (iters+1) (z*z + pt)
| otherwise = iters
asciiSymbol :: Int -> Char
asciiSymbol n
| 0 < n && n <= 10 = ' '
| 10 < n && n <= 20 = '`'
| 20 < n && n <= 40 = '*'
| 40 < n && n <= 40 = '+'
| otherwise = '#'
width, height :: Int
width = 30
height = 30
maxIters :: Int
maxIters = 50
mandelbrotScaleX :: (Double, Double)
mandelbrotScaleX = (-2.5, 1)
mandelbrotScaleY :: (Double, Double)
mandelbrotScaleY = (-1, 1)
displayScaleX :: (Double, Double)
displayScaleX = (0, fromIntegral width)
displayScaleY :: (Double, Double)
displayScaleY = (0, fromIntegral height)
scaleTo :: (Double, Double) -> (Double, Double) -> Double -> Double
scaleTo (fromMin, fromMax) (toMin, toMax) v =
let zeroToOne = ((v - fromMin) / (fromMax - fromMin))
in
zeroToOne * (toMax - toMin) + toMin
displayPoints :: [[(Double, Double)]]
displayPoints = [ [ (fromIntegral x, fromIntegral y) | y <- [0..width] ] | x <- [0..height] ]
mandelbrotPoints :: [[(Double, Double)]]
mandelbrotPoints = map (map (scaleX *** scaleY)) displayPoints
where
scaleX = displayScaleX `scaleTo` mandelbrotScaleX
scaleY = displayScaleY `scaleTo` mandelbrotScaleY
complexPoints :: [[Complex Double]]
complexPoints = map (map (uncurry (:+))) mandelbrotPoints
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment