Memory Management and Lists

Hi, short version of the question: when elements are 'drop'ped from a list, when is the memory for those elements released? And is there some way to control that? Longer version: I have this situation where I've got a State monad carrying a Data.Matrix, and I... 1) generate in infinite list of monadic operations with (repeat mf) where mf is a monadic function. 2) 'sequence' (from Control.Monad) to get a monad containing the infinite list of all states (i.e., a list of Matrices). 3) evalState(T) to extract the list 4) extract the nth state with (head (drop (n-1))) I like this approach. However, there seems to be a memory management issue: a Matrix itself should only be, I'm guessing, somewhere around 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. Maybe I'm generating list elements (Matrices) a lot faster than memory management is releasing them...? -- 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).

I'm not an expert here, but the GC should not allow that to happen if you were truly no longer using the elements. Most likely you have a dangling reference to the list head or something. Please post your code. Will
On Jul 10, 2016, at 11:41, Christopher Howard
wrote: Hi, short version of the question: when elements are 'drop'ped from a list, when is the memory for those elements released? And is there some way to control that?
Longer version: I have this situation where I've got a State monad carrying a Data.Matrix, and I...
1) generate in infinite list of monadic operations with (repeat mf) where mf is a monadic function. 2) 'sequence' (from Control.Monad) to get a monad containing the infinite list of all states (i.e., a list of Matrices). 3) evalState(T) to extract the list 4) extract the nth state with (head (drop (n-1)))
I like this approach. However, there seems to be a memory management issue: a Matrix itself should only be, I'm guessing, somewhere around 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. Maybe I'm generating list elements (Matrices) a lot faster than memory management is releasing them...?
-- 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).
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Haskell is lazy evaluated. So data isn't "dropped" until all the thunks
that use it are evaluated.
Play around with foldl and foldl'. The strict evaluation of the accumulator
in foldl' prevents a large thunk from forming and eating up all the memory
On Sun, Jul 10, 2016 at 10:26 AM Will Yager
I'm not an expert here, but the GC should not allow that to happen if you were truly no longer using the elements. Most likely you have a dangling reference to the list head or something. Please post your code.
Will
On Jul 10, 2016, at 11:41, Christopher Howard
wrote: Hi, short version of the question: when elements are 'drop'ped from a list, when is the memory for those elements released? And is there some way to control that?
Longer version: I have this situation where I've got a State monad carrying a Data.Matrix, and I...
1) generate in infinite list of monadic operations with (repeat mf) where mf is a monadic function. 2) 'sequence' (from Control.Monad) to get a monad containing the infinite list of all states (i.e., a list of Matrices). 3) evalState(T) to extract the list 4) extract the nth state with (head (drop (n-1)))
I like this approach. However, there seems to be a memory management issue: a Matrix itself should only be, I'm guessing, somewhere around 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. Maybe I'm generating list elements (Matrices) a lot faster than memory management is releasing them...?
-- 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).
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote:
issue: a Matrix itself should only be, I'm guessing, somewhere around 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. Maybe I'm generating list elements (Matrices) a lot faster than memory management is releasing them...?
You have almost certainly got a space leak. Can you post your code?

-- 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) -- 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 initMx radius walk = map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) radius -- Some quick experimentation code. h is the list 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)) On 07/10/2016 10:30 AM, Tom Ellis wrote:
On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote:
issue: a Matrix itself should only be, I'm guessing, somewhere around 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. Maybe I'm generating list elements (Matrices) a lot faster than memory management is releasing them...?
You have almost certainly got a space leak. Can you post your code? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- 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).

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"
-- 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)
-- 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 initMx radius walk = map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) radius
-- Some quick experimentation code. h is the list
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))
On 07/10/2016 10:30 AM, Tom Ellis wrote:
On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote:
issue: a Matrix itself should only be, I'm guessing, somewhere around 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. Maybe I'm generating list elements (Matrices) a lot faster than memory management is releasing them...?
You have almost certainly got a space leak. Can you post your code? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- 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).
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Just out of curiosity, what is the advantage to using a newtype in this
case when you will not be writing your own instances of typeclasses?
On Mon, Jul 11, 2016, 15:56 David Feuer
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"
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)
-- 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 initMx radius walk = map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) radius
-- Some quick experimentation code. h is the list
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))
On 07/10/2016 10:30 AM, Tom Ellis wrote:
On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote:
issue: a Matrix itself should only be, I'm guessing, somewhere around 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. Maybe I'm generating list elements (Matrices) a lot faster than memory management is releasing them...?
You have almost certainly got a space leak. Can you post your code? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- 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).
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

The advantage of using a newtype is that it hides the structure from the
outside. Users of StateReader don't need to know that it's made of StateT
and Reader. If something else gets tossed onto the transformer stack,
existing users of StateReader won't need to change.
On Jul 11, 2016 6:08 PM, "Jake"
Just out of curiosity, what is the advantage to using a newtype in this case when you will not be writing your own instances of typeclasses?
On Mon, Jul 11, 2016, 15:56 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"
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)
-- 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 initMx radius walk = map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) radius
-- Some quick experimentation code. h is the list
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))
On 07/10/2016 10:30 AM, Tom Ellis wrote:
On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote:
issue: a Matrix itself should only be, I'm guessing, somewhere around 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. Maybe I'm generating list elements (Matrices) a lot faster than memory management is releasing them...?
You have almost certainly got a space leak. Can you post your code? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- 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).
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

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).

have you tried adding some strict evaluation to your algorithm? The easy
spot to do that when using the state monad is in the state variable.
On Mon, Jul 11, 2016 at 5:12 PM Christopher Howard
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).
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

I can't run this code because it's missing several things, including the definition of Matrix and walk, and imports. Certainly you are building up a large chain of thunks repeatedly applying the calculation for nMatrix, but how to solve it I cannot say without more information. On Mon, Jul 11, 2016 at 07:01:24AM -0800, Christopher Howard 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)
-- 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 initMx radius walk = map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) radius
-- Some quick experimentation code. h is the list
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))
On 07/10/2016 10:30 AM, Tom Ellis wrote:
On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote:
issue: a Matrix itself should only be, I'm guessing, somewhere around 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. Maybe I'm generating list elements (Matrices) a lot faster than memory management is releasing them...?
You have almost certainly got a space leak. Can you post your code?

I guess I was hesitating on posting the entire program source code in an cafe email. I suppose I could send you a tarball, if you really wanted it... Matrix is from Data.Matrix http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html. It is hard to understand how thunks alone would explain it... there would be at most 2000 thunks, right? Unless... Could there be a thunk for every single call to getElem? That would be a lot of thunks! Somebody suggested adding some strictness here... could you elaborate on that? I tried inserting seq, but I didn't really understand how I was supposed to use it... On 07/12/2016 10:40 AM, Tom Ellis wrote:
I can't run this code because it's missing several things, including the definition of Matrix and walk, and imports.
Certainly you are building up a large chain of thunks repeatedly applying the calculation for nMatrix, but how to solve it I cannot say without more information.
On Mon, Jul 11, 2016 at 07:01:24AM -0800, Christopher Howard 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)
-- 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 initMx radius walk = map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) radius
-- Some quick experimentation code. h is the list
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))
On 07/10/2016 10:30 AM, Tom Ellis wrote:
On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote:
issue: a Matrix itself should only be, I'm guessing, somewhere around 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. Maybe I'm generating list elements (Matrices) a lot faster than memory management is releasing them...?
You have almost certainly got a space leak. Can you post your code?
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- 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).

After pondering this problem some more, I found a solution to the problem was to introduce strictness, not deep down in the StateReader monad, but rather at the top level, i.e., forcing evaluation of each Matrix as soon as it is pulled of the list of Matrices. I found I could do this simply by summing all the elements in each matrix and printing the sum to std out. With this approach, i successfully run the full program and never even saw my memory performance graph move up. I suppose there might be a way to do the same thing more efficiently with seq...? On 07/12/2016 06:39 PM, Christopher Howard wrote:
I guess I was hesitating on posting the entire program source code in an cafe email. I suppose I could send you a tarball, if you really wanted it...
Matrix is from Data.Matrix http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html.
It is hard to understand how thunks alone would explain it... there would be at most 2000 thunks, right? Unless... Could there be a thunk for every single call to getElem? That would be a lot of thunks!
Somebody suggested adding some strictness here... could you elaborate on that? I tried inserting seq, but I didn't really understand how I was supposed to use it...
-- 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).

You probably want Control.DeepSeq. No extraneous work doing addition that
way either.
Will
On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard
After pondering this problem some more, I found a solution to the problem was to introduce strictness, not deep down in the StateReader monad, but rather at the top level, i.e., forcing evaluation of each Matrix as soon as it is pulled of the list of Matrices. I found I could do this simply by summing all the elements in each matrix and printing the sum to std out. With this approach, i successfully run the full program and never even saw my memory performance graph move up.
I suppose there might be a way to do the same thing more efficiently with seq...?
On 07/12/2016 06:39 PM, Christopher Howard wrote:
I guess I was hesitating on posting the entire program source code in an cafe email. I suppose I could send you a tarball, if you really wanted it...
Matrix is from Data.Matrix <http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html .
It is hard to understand how thunks alone would explain it... there would be at most 2000 thunks, right? Unless... Could there be a thunk for every single call to getElem? That would be a lot of thunks!
Somebody suggested adding some strictness here... could you elaborate on that? I tried inserting seq, but I didn't really understand how I was supposed to use it...
-- 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).
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

You have to be careful with deepseq. Using it in the wrong place can
lead to very bad performance. It's a big hammer. Its blow can
sometimes be softened using the NF type from the nf package, but it's
really not the right thing most of the time.
On Tue, Jul 12, 2016 at 11:56 PM, William Yager
You probably want Control.DeepSeq. No extraneous work doing addition that way either.
Will
On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard
wrote: After pondering this problem some more, I found a solution to the problem was to introduce strictness, not deep down in the StateReader monad, but rather at the top level, i.e., forcing evaluation of each Matrix as soon as it is pulled of the list of Matrices. I found I could do this simply by summing all the elements in each matrix and printing the sum to std out. With this approach, i successfully run the full program and never even saw my memory performance graph move up.
I suppose there might be a way to do the same thing more efficiently with seq...?
On 07/12/2016 06:39 PM, Christopher Howard wrote:
I guess I was hesitating on posting the entire program source code in an cafe email. I suppose I could send you a tarball, if you really wanted it...
Matrix is from Data.Matrix
http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html.
It is hard to understand how thunks alone would explain it... there would be at most 2000 thunks, right? Unless... Could there be a thunk for every single call to getElem? That would be a lot of thunks!
Somebody suggested adding some strictness here... could you elaborate on that? I tried inserting seq, but I didn't really understand how I was supposed to use it...
-- 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).
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

For deepseq also see the"Once trick". I'm surprised it's not quoted more
often. In fact our would make sense to mention it in the deepseq docs.
On Wed, Jul 13, 2016, 21:32 David Feuer
You have to be careful with deepseq. Using it in the wrong place can lead to very bad performance. It's a big hammer. Its blow can sometimes be softened using the NF type from the nf package, but it's really not the right thing most of the time.
On Tue, Jul 12, 2016 at 11:56 PM, William Yager
wrote: You probably want Control.DeepSeq. No extraneous work doing addition that way either.
Will
On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard
wrote:
After pondering this problem some more, I found a solution to the problem was to introduce strictness, not deep down in the StateReader monad, but rather at the top level, i.e., forcing evaluation of each Matrix as soon as it is pulled of the list of Matrices. I found I could do this simply by summing all the elements in each matrix and printing the sum to std out. With this approach, i successfully run the full program and never even saw my memory performance graph move up.
I suppose there might be a way to do the same thing more efficiently with seq...?
On 07/12/2016 06:39 PM, Christopher Howard wrote:
I guess I was hesitating on posting the entire program source code in
an
cafe email. I suppose I could send you a tarball, if you really wanted it...
Matrix is from Data.Matrix
< http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html>.
It is hard to understand how thunks alone would explain it... there would be at most 2000 thunks, right? Unless... Could there be a thunk for every single call to getElem? That would be a lot of thunks!
Somebody suggested adding some strictness here... could you elaborate on that? I tried inserting seq, but I didn't really understand how I was supposed to use it...
-- 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).
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Yes, this is a very neat trick and very effective. (I couldn't acutally find it on Hoogle. Does anyone have a link?) On Thu, Jul 14, 2016 at 07:45:33AM +0000, Robin Palotai wrote:
For deepseq also see the"Once trick". I'm surprised it's not quoted more often. In fact our would make sense to mention it in the deepseq docs.
On Wed, Jul 13, 2016, 21:32 David Feuer
wrote: You have to be careful with deepseq. Using it in the wrong place can lead to very bad performance. It's a big hammer. Its blow can sometimes be softened using the NF type from the nf package, but it's really not the right thing most of the time.
On Tue, Jul 12, 2016 at 11:56 PM, William Yager
wrote: You probably want Control.DeepSeq. No extraneous work doing addition that way either.
Will
On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard
wrote:
After pondering this problem some more, I found a solution to the problem was to introduce strictness, not deep down in the StateReader monad, but rather at the top level, i.e., forcing evaluation of each Matrix as soon as it is pulled of the list of Matrices. I found I could do this simply by summing all the elements in each matrix and printing the sum to std out. With this approach, i successfully run the full program and never even saw my memory performance graph move up.
I suppose there might be a way to do the same thing more efficiently with seq...?
On 07/12/2016 06:39 PM, Christopher Howard wrote:
I guess I was hesitating on posting the entire program source code in
an
cafe email. I suppose I could send you a tarball, if you really wanted it...
Matrix is from Data.Matrix
< http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html>.
It is hard to understand how thunks alone would explain it... there would be at most 2000 thunks, right? Unless... Could there be a thunk for every single call to getElem? That would be a lot of thunks!
Somebody suggested adding some strictness here... could you elaborate on that? I tried inserting seq, but I didn't really understand how I was supposed to use it...
-- 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).
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

https://www.schoolofhaskell.com/user/edwardk/snippets/once Cool trick :) On Thu, 14 Jul 2016 at 08:56 Tom Ellis < tom-lists-haskell-cafe-2013@jaguarpaw.co.uk> wrote:
Yes, this is a very neat trick and very effective. (I couldn't acutally find it on Hoogle. Does anyone have a link?)
For deepseq also see the"Once trick". I'm surprised it's not quoted more often. In fact our would make sense to mention it in the deepseq docs.
On Wed, Jul 13, 2016, 21:32 David Feuer
wrote: You have to be careful with deepseq. Using it in the wrong place can lead to very bad performance. It's a big hammer. Its blow can sometimes be softened using the NF type from the nf package, but it's really not the right thing most of the time.
On Tue, Jul 12, 2016 at 11:56 PM, William Yager
wrote: You probably want Control.DeepSeq. No extraneous work doing addition
way either.
Will
On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard < ch.howard@zoho.com
wrote:
After pondering this problem some more, I found a solution to the problem was to introduce strictness, not deep down in the
StateReader
monad, but rather at the top level, i.e., forcing evaluation of each Matrix as soon as it is pulled of the list of Matrices. I found I could do this simply by summing all the elements in each matrix and
the sum to std out. With this approach, i successfully run the full program and never even saw my memory performance graph move up.
I suppose there might be a way to do the same thing more efficiently with seq...?
On 07/12/2016 06:39 PM, Christopher Howard wrote:
I guess I was hesitating on posting the entire program source code in an cafe email. I suppose I could send you a tarball, if you really wanted it...
Matrix is from Data.Matrix
<
http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html>.
It is hard to understand how thunks alone would explain it...
would be at most 2000 thunks, right? Unless... Could there be a
On Thu, Jul 14, 2016 at 07:45:33AM +0000, Robin Palotai wrote: that printing there thunk
for every single call to getElem? That would be a lot of thunks!
Somebody suggested adding some strictness here... could you elaborate on that? I tried inserting seq, but I didn't really understand how I was supposed to use it...
-- 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).
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

I faced the same problem in an RWS monad, where adding a print to the
evalRWS resolves the space leak. Obviously, it's not very elegant to
clutter the output. I tried the unsafeInterleaveIO (works sometimes),
seq/deepseq (works on Windows but not on Linux??), strictness annotations
(didn't seem to help at all?), but finally settled on using pipes/conduit.
It's remarkable how a streaming library is more practical than the
language's core feature - laziness.
On 14 July 2016 at 16:32, Matthew Bray
https://www.schoolofhaskell.com/user/edwardk/snippets/once
Cool trick :)
On Thu, 14 Jul 2016 at 08:56 Tom Ellis < tom-lists-haskell-cafe-2013@jaguarpaw.co.uk> wrote:
Yes, this is a very neat trick and very effective. (I couldn't acutally find it on Hoogle. Does anyone have a link?)
For deepseq also see the"Once trick". I'm surprised it's not quoted more often. In fact our would make sense to mention it in the deepseq docs.
On Wed, Jul 13, 2016, 21:32 David Feuer
wrote: You have to be careful with deepseq. Using it in the wrong place can lead to very bad performance. It's a big hammer. Its blow can sometimes be softened using the NF type from the nf package, but it's really not the right thing most of the time.
On Tue, Jul 12, 2016 at 11:56 PM, William Yager
wrote:
You probably want Control.DeepSeq. No extraneous work doing addition that way either.
Will
On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard < ch.howard@zoho.com
wrote:
After pondering this problem some more, I found a solution to the problem was to introduce strictness, not deep down in the
StateReader
monad, but rather at the top level, i.e., forcing evaluation of each Matrix as soon as it is pulled of the list of Matrices. I found I could do this simply by summing all the elements in each matrix and
the sum to std out. With this approach, i successfully run the full program and never even saw my memory performance graph move up.
I suppose there might be a way to do the same thing more efficiently with seq...?
On 07/12/2016 06:39 PM, Christopher Howard wrote: > I guess I was hesitating on posting the entire program source code in an > cafe email. I suppose I could send you a tarball, if you really wanted > it... > > Matrix is from Data.Matrix > > <
http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html>.
> > It is hard to understand how thunks alone would explain it...
> would be at most 2000 thunks, right? Unless... Could there be a
On Thu, Jul 14, 2016 at 07:45:33AM +0000, Robin Palotai wrote: printing there thunk
> for every single call to getElem? That would be a lot of thunks! > > Somebody suggested adding some strictness here... could you elaborate on > that? I tried inserting seq, but I didn't really understand how I was > supposed to use it... >
-- 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).
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

See http://comments.gmane.org/gmane.comp.lang.haskell.libraries/18980 The W part of RWS is bad for performance. Best approach is to implement R, W, and S using a strict StateT. Will
On Jul 14, 2016, at 11:43, Lian Hung Hon
wrote: I faced the same problem in an RWS monad, where adding a print to the evalRWS resolves the space leak. Obviously, it's not very elegant to clutter the output. I tried the unsafeInterleaveIO (works sometimes), seq/deepseq (works on Windows but not on Linux??), strictness annotations (didn't seem to help at all?), but finally settled on using pipes/conduit. It's remarkable how a streaming library is more practical than the language's core feature - laziness.
On 14 July 2016 at 16:32, Matthew Bray
wrote: https://www.schoolofhaskell.com/user/edwardk/snippets/once Cool trick :)
On Thu, 14 Jul 2016 at 08:56 Tom Ellis
wrote: Yes, this is a very neat trick and very effective. (I couldn't acutally find it on Hoogle. Does anyone have a link?) On Thu, Jul 14, 2016 at 07:45:33AM +0000, Robin Palotai wrote:
For deepseq also see the"Once trick". I'm surprised it's not quoted more often. In fact our would make sense to mention it in the deepseq docs.
On Wed, Jul 13, 2016, 21:32 David Feuer
wrote: You have to be careful with deepseq. Using it in the wrong place can lead to very bad performance. It's a big hammer. Its blow can sometimes be softened using the NF type from the nf package, but it's really not the right thing most of the time.
On Tue, Jul 12, 2016 at 11:56 PM, William Yager
wrote: You probably want Control.DeepSeq. No extraneous work doing addition that way either.
Will
On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard
wrote: > > After pondering this problem some more, I found a solution to the > problem was to introduce strictness, not deep down in the StateReader > monad, but rather at the top level, i.e., forcing evaluation of each > Matrix as soon as it is pulled of the list of Matrices. I found I could > do this simply by summing all the elements in each matrix and printing > the sum to std out. With this approach, i successfully run the full > program and never even saw my memory performance graph move up. > > I suppose there might be a way to do the same thing more efficiently > with seq...? > > On 07/12/2016 06:39 PM, Christopher Howard wrote: > > I guess I was hesitating on posting the entire program source code in an > > cafe email. I suppose I could send you a tarball, if you really wanted > > it... > > > > Matrix is from Data.Matrix > > > > < http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html>. > > > > It is hard to understand how thunks alone would explain it... there > > would be at most 2000 thunks, right? Unless... Could there be a thunk > > for every single call to getElem? That would be a lot of thunks! > > > > Somebody suggested adding some strictness here... could you elaborate on > > that? I tried inserting seq, but I didn't really understand how I was > > supposed to use it... > > > > -- > 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). > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Tue, Jul 12, 2016 at 07:28:05PM -0800, Christopher Howard wrote:
After pondering this problem some more, I found a solution to the problem was to introduce strictness, not deep down in the StateReader monad, but rather at the top level, i.e., forcing evaluation of each Matrix as soon as it is pulled of the list of Matrices. I found I could do this simply by summing all the elements in each matrix and printing the sum to std out. With this approach, i successfully run the full program and never even saw my memory performance graph move up.
I suppose there might be a way to do the same thing more efficiently with seq...?
Undoubtedly, but it's customary when asking for help to produce a complete minimal example that reproduces the problem. I can't help if I can't run your code!
participants (10)
-
Anatoly Yakovenko
-
Christopher Howard
-
David Feuer
-
Jake
-
Lian Hung Hon
-
Matthew Bray
-
Robin Palotai
-
Tom Ellis
-
Will Yager
-
William Yager