{-| Module : Graphics.Mars.Graph Description : Brings together the random walk and graph stamping functionaliy. Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com Use the 'graph' function here to generate the raw graph array data based on various parameters. -} module Graphics.Mars.Graph where import Data.Array.IO import Data.Array.Unboxed import Graphics.Mars.Stamp import Graphics.Mars.Walk import System.Random -- |Beginning in the center, follows a random walk path, and stamps a circle -- shape onto the array at each step. Internally uses a mutable unboxed array -- for efficiency, but returns the results in a frozen array. graph :: Int -- ^ height (array rows) -> Int -- ^ width (array columns) -> Float -- ^ stamped circle radius -> Float -- ^ jitter factor of walk, usually nearly the same as radius -> Int -- ^ a seed value for the random number generator -> Int -- ^ numbers of steps to take in random walk -> Float -- ^ magnification factor -> IO (UArray (Int, Int) Float) graph height width radius walkfactor seed iterations scalefactor = do a <- (newArray ((0, 0), (height, width)) 0.0 :: IO (IOUArray (Int, Int) Float)) stampL a (circleStamp (radius * scalefactor) :: UArray (Int, Int) Float) (take iterations [ (round (f1 + (fromIntegral height) * 0.5), round (f2 + (fromIntegral width) * 0.5)) | (f1, f2) <- walk walkfactor (0, 0) (mkStdGen seed) ]) freeze a