-- | -- Module : Mandelbrot -- Copyright : (c) Philipps Universitaet Marburg 2014-2015 -- License : BSD-style (see the file LICENSE) -- -- Maintainer : eden@mathematik.uni-marburg.de -- Stability : beta -- Portability : not portable -- -- The following Haskell module implements Mandelbrot fractals with Eden. -- -- Depends on the Eden Compiler. -- -- Eden Project -------------------------------------------------------------------------------- -- -- Mandelbrot fractal computation -- -- Arguments: 1. Example-coordinates (0 or 1) -- 2. number of pixels per image row -- 3. chunk size -- 4. prefetch (used only for workpool skeletons) -- 5. Skeleton selection (0=farm (splitIntoN), -- 1=offlineFarm (splitIntoN), -- 2=workpool, -- 3=farm (unshuffle) -- 4=offlineFarm (unshuffle) -- 5=offlineWorkpool -- -- Output: PPM-Format to Stdout, only if 6th argument is "-out" -- otherwise output is suppressed, return value: "Done" -- -------------------------------------------------------------------------------- import System.Environment import Control.Seq import Control.Parallel (pseq) import Control.Parallel.Eden import Control.Parallel.Eden.Map import Control.Parallel.Eden.Workpool import Control.Parallel.Eden.Auxiliary import Data.Complex import Data.List usage = "Mandelbrot fractal computation\n" ++ " Arguments: 1. Example-coordinates (0 or 1)\n" ++ " 2. number of pixels per image row\n" ++ " 3. chunk size\n" ++ " 4. prefetch (used only for workpool skeletons)\n" ++ " 5. Skeleton selection (0=farm (splitIntoN),\n" ++ " 1=offlineFarm (splitIntoN),\n" ++ " 2=workpool,\n" ++ " 3=farm (unshuffle)\n" ++ " 4=offlineFarm (unshuffle)\n" ++ " 5=offlineWorkpool\n" ++ "\n" ++ " Output: PPM-Format to Stdout, only if 6th argument is \"-out\"\n" ++ " otherwise output is suppressed, return value: \"Done\"\n" -- Parallel -------------------------------------------------------------------- -- instance NFData a => NFData (Complex a) instance (RealFloat a, Trans a) => Trans (Complex a) -- Main ------------------------------------------------------------------------ main = do args <- getArgs if length args < 5 then putStrLn $ "Arguments missing...\n" ++ usage else do let (lo, ru) = examples!!(read (args!!0)) let dimx = read (args!!1) let np = noPe let chunksize = read (args!!2) let pf = read (args!!3) let skel = if length args > 4 then read (args!!4) else 2 let b = bild 10.0 lo ru dimx np pf chunksize skel if length args > 5 && (args!!5) == "-out" then putStr b else rnf b `seq` putStrLn "Done (no output)" examples = [ ((-0.75104) :+ (0.10511), (-0.74080) :+ (0.11441)), ((-2.5) :+ (-1.5), (1.5) :+ (1.5)) ] -- Lazy Box to transfer inputs without prior evaluation to receiver processes newtype LBox a = LBox {unLBox :: a} instance Trans a => Trans (LBox a) instance NFData a => NFData (LBox a) where rnf (LBox _) = () -- a lazy box will not be evaluated -- Compute image (bild) ------------------------------------------------- bild :: Double -> Complex Double -> Complex Double -> Integer -> Int -> Int -> Int -> Int -> String bild schwellwert lo ru dimx np pf d s = header ++ ( concat result ) --' where ---------------------------------------------- result = concat . (skels!!s) . (chunk d) $ tasks skels = cycle [farm (splitIntoN (np - 1)) concat (map wf) , offlineFarm (np - 1) (splitIntoN (np - 1)) concat (map wf) , workpoolSorted (np - 1) pf (map wf) , farm (unshuffle (np - 1)) shuffle (map wf) , offlineFarm (np - 1) (unshuffle (np - 1)) shuffle (map wf) , (workpoolSorted (np - 1) pf (map wf.unLBox)) . (map LBox) ] ---------------------------------------------- -- tasks :: [[Complex Double]] tasks = lines wf :: [Complex Double] -> String wf t = concatMap (rgb . (iter schwellwert (0.0 :+ 0.0) 0)) t header = "P3\n"++(show (dimx+1))++" "++(show dimy)++"\n255\n" (dimy, lines) = koord lo ru dimx rgb i = i' ++ " " ++ i' ++ " " ++ i' ++ "\n" where i' = show i -- Koordinaten aufspannen, Iteration ------------------------------------------- koord :: Complex Double -> Complex Double -> Integer -> (Integer, [[Complex Double]]) koord (x1 :+ y1) (x2 :+ y2) dimx = (dimy, ks) where breite = abs (x2 - x1) hoehe = abs (y2 - y1) schrittx = breite / ((fromInteger dimx)::Double) schritty = hoehe / ((fromInteger dimy)::Double) sx2 = schrittx / 2.0 sy2 = schritty / 2.0 dimy = round ((((fromInteger dimx)::Double)*hoehe)/breite) ks = [ [(x+sx2) :+ (y+sy2) | x <- [x1,x1+schrittx..x2]] | y <- [y1,y1+schritty..y2] ] iter :: Double -> Complex Double -> Integer -> Complex Double -> Integer iter schwellwert x it c | it > 255 = 255 | (betrag x) >= schwellwert = it | otherwise = iter schwellwert x' it' c where it' = it + 1 x' = x*x + c betrag :: Complex Double -> Double betrag (x :+ y) = sqrt (x*x + y*y)