module Main where {- Visualisierung von Julia-Mengen Vorlage von Jost Berthold, Philipps-Universitaet Marburg Aenderungen Mischa Dieterle, Sommer 2009 (Grundlage: mandelbrot.hs, Steffen Priebe WS 2000/2001) Bei groesseren Aufloesungen Ausgabe umleiten: #> programm > bild.ppm Anzeige der Datei (z.B. bild.ppm) unter Linux mit #> okular bild.ppm ODER #> xview bild.ppm --------------------------------------------------------------------------- -} import Complex import System(getArgs, getProgName) import qualified Control.Seq as S --Strategien mit altem Typ import Control.DeepSeq(rnf) --alte Strategie rnf import Control.Parallel(par,pseq) import Control.Parallel.Strategies --Strategien mit monadischem Typ, rdeepseq st import Data.Time.Clock (diffUTCTime, getCurrentTime) usage name = unlines $ ["" ,"Visualisierung fuer Julia-Mengen" ,"" ,"Verwendung: #>" ++ name ++ " <#Sparks> " ,"" ,"Version 0: Sequentiell" ] main = do name <- getProgName args <- getArgs time1 <- getCurrentTime if (length args < 5) then putStrLn (usage name) else let version = ((read.head) args)::Int nSparks = ((read.head.tail) args)::Int verbose = 0 /= (read (args!!2)) dimx = (read (args!!3))::Int (lo,ru) = frame (drop 4 args) ppm = case version of 0 -> juliaSet juliastart threshold lo ru dimx _ -> juliaSet juliastart threshold lo ru dimx pixels = map rgb $ concat ppm --Zusatz für Faerbung header = "P3\n"++(show dimx)++" "++(show (length ppm))++"\n255\n" in if verbose then putStr $ header ++ (unlines pixels) --Ausgabe else do rnf ppm `seq` putStrLn "done" time2 <- getCurrentTime putStrLn $ "Laufzeit:"++ (show (diffUTCTime time2 time1)) -- Konstanten (sofern nicht Programmparameter) threshold :: Double threshold = 10.0 juliastart :: Complex Double juliastart = 0.35 :+ 0.35 -- Ausschnitt: ("links oben","rechts unten") frame :: [String] -> (Complex Double, Complex Double) -- frame ("free":args) = ... frame args = case lookup (head (head args)) flist of Just f -> f Nothing -> if length args > 4 then (free1,free2) else frame ["c"] where flist = zip ['a'..] [((-0.75):+(0.11),(-0.74) :+ (0.10)) ,((-2.0) :+ (1.5) ,(2.0) :+ (-1.5)) ,((-0.3) :+ (0.5) ,(0.7) :+ (-0.5)) ,((-0.7) :+ (0.0) ,(-0.2) :+ (-1.0)) -- hier ggf. weitere Ausschnitte definieren... ] a = (read (args!!1))::Double b = (read (args!!2))::Double range = (read (args!!3))::Double free1 = a :+ b free2 = free1 + (range :+ (-range)) ---------- (einfache Art) Juliamengen: -------------------------- type JuliaSet = Complex Double -> Double -> Complex Double -> Complex Double -> Int -> [[Int]] --Julia Set juliaSet :: JuliaSet juliaSet cWert schwellwert lo ru dimx = pixels where -- Iteration for Julia-Set: iterJulia = \z -> iter schwellwert z 0 cWert pixels = map (map iterJulia) koords ------------- (dimy, koords) = koord lo ru dimx ----------------------------------------------------------------- -- Pixel faerben rgb :: Int -> String rgb i = unwords [show ri, show gi, show bi] where ri = (i*26) `mod` 255 gi = (i*2) `mod` 255 bi = (i*35) `mod` 255 -- Koordinatenmenge fuer den Ausschnitt bestimmen koord :: Complex Double -> Complex Double -> Int -> (Int, [[Complex Double]]) koord (x1 :+ y1) (x2 :+ y2) dimx = (dimy, ks) where breite = abs (x2 - x1) hoehe = abs (y1 - y2) -- y1 > y2 ("oben" > "unten") schrittx = breite / (fromIntegral dimx) schritty = hoehe / dimy' sx2 = schrittx / 2 sy2 = schritty / 2 dimy = round dimy' dimy' = ((fromIntegral dimx)::Double)*hoehe/breite ks = [ [ (x+sx2) :+ (y-sy2) | x <- [x1,x1+schrittx..x2-schrittx] ] | y <- [y1,y1-schritty..y2+schritty] ] -- Iteration fuer julia/mandelbrot iter :: Double -> Complex Double -> Int -> Complex Double -> Int iter schwellwert x it c | it > 255 = 255 | (betrag x) >= schwellwert = it | betrag (x' - x) < 0.001 = 255 | otherwise = iter schwellwert x' (it+1) c where x' = x*x + c betrag :: Complex Double -> Double betrag (x :+ y) = sqrt (x*x + y*y) -------------------List Strategies------------------------- --basic parList / seqList (old Strategies) parListBasic :: S.Strategy a -> S.Strategy [a] seqListBasic :: S.Strategy a -> S.Strategy [a] parListBasic s [] = () parListBasic s (x:xs) = s x `par` parListBasic s xs seqListBasic s [] = () seqListBasic s (x:xs) = s x `pseq` seqListBasic s xs