
On 07/11/2016 11:56 AM, David Feuer wrote:
Please repost your code, giving a type signature for each top-level binding. Without them, the code is very difficult to follow. I also strongly recommend using a newtype for your custom monad. Something like this:
{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses, StandaloneDeriving, ... #-}
newtype StateReader s c a = SR {runSR :: StateT s (Reader c) a} deriving (Functor, Applicative, Monad)
deriving instance MonadReader c (StateReader s c) deriving instance MonadState s (StateReader s c)
On Jul 11, 2016 11:07 AM, "Christopher Howard"
mailto:ch.howard@zoho.com> wrote: -- I'm a bit embarrassed of this code because I haven't yet optimized -- the 'stamp' algorithm for reduced number of matrix operations. But -- even in this state I should think the memory requirements shouldn't -- exceed 1MB while generating the nth Matrix, unless Matrix n-1, n-2, -- etc. are being preserved in memory unnecessarily.
-- Monad Stack
type StateReader s c a = StateT s (Reader c) a
evalStateReader m s c = (runReader (evalStateT m s)) c
-- Helper function
type Point = (Float, Float) type Metric = Point -> Point -> Float
euclidean :: Metric euclidean (x1, y1) (x2, y2) = sqrt ((x2 - x1)**2 + (y2 - y1)**2)
stamp :: StateReader (Matrix Float, [Point]) Float (Matrix Float, [Point])
-- monadic function. haven't had chance yet to optimize algorithm to -- reduce number of matrix operations
stamp = do radius <- ask (oMatrix, walk) <- get (wX, wY) <- (return . head) walk let nMatrix = matrix (nrows oMatrix) (ncols oMatrix) (\(x, y) -> let (x', y') = (fromIntegral x, fromIntegral y) in if euclidean (x', y') (wX, wY) > radius then getElem x y oMatrix else getElem x y oMatrix + 1) in put (nMatrix, tail walk) >> get
-- sequences and gathers results as list
stampingStates :: Matrix Float -> Float -> [Point] -> [Matrix Float]
stampingStates initMx radius walk = map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) radius
-- Some quick experimentation code. h is the list
h :: [Matrix Float] intensityG :: Picture displayIntensityG :: IO ()
h = stampingStates initMx radius walk' where initMx = zero 250 250 radius = 40 walk' = walk 40 (125, 125) (mkStdGen 31415)
-- get 2001st Matrix and convert to Gloss Picture, employing -- some color interpretation code
intensityG = let mx = head (drop 2000 h) in toImage mx (lightnessInt 272 (minMax mx))
-- http://qlfiles.net To protect my privacy, please use PGP encryption. It's free and easy to use! My public key ID is 0x340EA95A (pgp.mit.edu).