module Exercise_13 where {-WETT-} import Codec.Picture import Data.Bits hiding ( rotate ) import Data.Complex import Text.Printf -- Add any code that generates images or videos between these tags -- Please also include instructions on how to invoke your code -- If you need libraries that are not available on the testserver, send your submission to fpv@in.tum.de -- A Program to generate images of the Julia set. I tried and tweaked the parameters -- so nice pictures are produced for 0 + 0.75i, but the code is pretty extensible to work -- for other numbers. -- Running the main function will create a sample of 500x500 pixels. -- Other examples are also provided in the code. -- Two Functions are provided to generate further images. One is genJulia which -- given a Dynamic Image, saves it in "julia.png". The other is genJulia2 -- which gives the option to give a name for the image. -- Caculates the number of iterations till the series "explode" juliaPixel :: Complex Double -> Complex Double -> Int -> Int juliaPixel z c iter | realPart (abs z) >= 10 || iter <= 0 = iter | otherwise = juliaPixel (z * z + c) c (iter - 1) -- Creates the sample points given the width, the height and the range of the real and imaginary parts range :: (Double, Double) -> (Double, Double) -> Int -> Int -> ([Double], [Double]) range (rm, rM) (im, iM) w h = ( [ f rm rM (fromIntegral w) (fromIntegral i) | i <- [0 .. w - 1] ] , [ f im iM (fromIntegral h) (fromIntegral i) | i <- [0 .. h - 1] ] ) where f mi ma n i = mi + i * (ma - mi) / n -- Creates an array of ints representing the number of iterations that each sample point needed juliaArray :: Complex Double -> (Double, Double) -> (Double, Double) -> Int -> Int -> Int -> [[Int]] juliaArray c pr pi iter w h = [ [ juliaPixel (r :+ i) c iter | r <- rangeReal ] | i <- rangeIm ] where (rangeReal, rangeIm) = range pr pi w h -- Julia in black and white bwJulia :: DynamicImage bwJulia = generalJulia 500 500 (0 :+ 0.75) (-2.0, 2.0) (-2.0, 2.0) 51 (0, 0xFFFFFF) -- Sample Julia 500 X 500 sampleJulia :: DynamicImage sampleJulia = generalJulia 500 500 (0 :+ 0.75) (-2.0, 2.0) (-2.0, 2.0) 51 (0xFFFF, 0) -- Same as sample, but bigger prettyJulia :: DynamicImage prettyJulia = generalJulia 1920 1080 (0 :+ 0.75) (-3.5, 3.5) (-2.0, 2.0) 51 (0xFFFF, 0) -- ... even more big thickJulia :: DynamicImage thickJulia = generalJulia 3840 2160 (0 :+ 0.75) (-3.5, 3.5) (-2.0, 2.0) 51 (0xFFFF, 0) -- Given a dynamic image, saves it as a julia.png genJulia :: DynamicImage -> IO () genJulia = savePngImage "julia.png" -- Given a name and a dynamic image, saves it under the name genJulia2 :: String -> DynamicImage -> IO () genJulia2 = savePngImage -- converts an int to a color toPixel :: Int -> PixelRGB8 toPixel i = PixelRGB8 r g b where b = fromIntegral $ i .&. 0xFF g = fromIntegral $ shift (i .&. 0xFF00) (-8 :: Int) r = fromIntegral $ shift (i .&. 0xFF0000) (-16 :: Int) -- Given a value in a range, linearally interpolate it in another range convertRange :: Int -> Int -> Int -> Int -> Int -> Int convertRange x fromm fromM tom toM = floor $ fromIntegral tom + (fromIntegral (x - fromm) / fromIntegral (fromM - fromm)) * fromIntegral (toM - tom) -- Generate a general Julia image generalJulia :: Int -- width -> Int -- height -> Complex Double -- complex number c -> (Double, Double) -- real bounds -> (Double, Double) -- imaginary bounds -> Int -- number of iterations -> (Int, Int) -- color range -> DynamicImage generalJulia width height c boundsReal boundsIm iter (lowestColor, highestColor) = ImageRGB8 (generateImage generateJulia width height) where j = juliaArray c boundsReal boundsIm iter width height raw x y = j !! y !! x generateJulia x y = toPixel (convertRange (raw x y) 0 iter lowestColor highestColor) main :: IO () main = do mapM_ (\(id, i) -> genJulia2 (printf "julia_%04d.png" id) $ generalJulia 700 700 (0.75 * cis (0.002 * i * pi)) (-2, 2) (-2, 2) 51 (0xFFFF, 0)) (zip [(0::Integer)..] [0..1000]) {-TTEW-}