Re: [Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-30 Thread Yves Parès
Have you tried to compile your code with optimisations? I guess GHC's
strictness analysis would find strict evaluation is better here.


2012/1/30 Joey Hess j...@kitenet.net

 Claude Heiland-Allen wrote:
  Control.Monad.State.Strict is strict in the actions, but the state
  itself is still lazy, so you end up building a huge thunk in the
  state containing all the updates that ever took place to the initial
  state.
 
  Using this should fix it:
 
  modify' :: MonadState s m = (s - s) - m ()
  modify' f = do
x - get
put $! f x  -- force the new state when storing it

 Thanks!

 So, why does Control.Monad.State.Strict.modify not do that?

 And, I still don't quite understand why this only happened
 when the updated value is obtained using IO.

 --
 see shy jo

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-30 Thread Joey Hess
Yves Parès wrote:
 Have you tried to compile your code with optimisations? I guess GHC's
 strictness analysis would find strict evaluation is better here.

The original code I saw this happen to the wild was built with -O2.
I didn't try building the test case with optimisations.

-- 
see shy jo


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-29 Thread Joey Hess
The attached test case quickly chews up hundreds of MB of memory.
If modified to call work' instead, it runs in constant space.

Somehow the value repeatedly read in from the file and stored in
the state is leaking. Can anyone help me understand why?

(ghc 7.0.4)

-- 
see shy jo
{-# LANGUAGE GeneralizedNewtypeDeriving, BangPatterns #-}

module Main where

import Control.Monad.State.Strict

data MyState = MyState { val :: String }

newtype Foo a = Foo { run :: StateT MyState IO a }
	deriving (
		Monad,
		MonadState MyState,
		MonadIO
	)

main :: IO ()
main = evalStateT (run test) (MyState )
	
test :: Foo ()
test = mapM_ work [1..10]-- massive memory leak
--test = mapM_ work' [1..10] -- constant space

readSomeFile :: Foo String
readSomeFile = liftIO $ readFileStrict /etc/passwd

work :: Integer - Foo ()
work _ = do
	v - readSomeFile
	modify $ \s - s { val = v }

work' :: Integer - Foo ()
work' n = do
	_ - readSomeFile
	modify $ \s - s { val = show n }

readFileStrict :: FilePath - IO String
readFileStrict file = do
	s - readFile file
	length s `seq` return s


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-29 Thread Claude Heiland-Allen

Hi,

On 30/01/12 01:07, Joey Hess wrote:

The attached test case quickly chews up hundreds of MB of memory.
If modified to call work' instead, it runs in constant space.

Somehow the value repeatedly read in from the file and stored in
the state is leaking. Can anyone help me understand why?


Control.Monad.State.Strict is strict in the actions, but the state 
itself is still lazy, so you end up building a huge thunk in the state 
containing all the updates that ever took place to the initial state.


Using this should fix it:

modify' :: MonadState s m = (s - s) - m ()
modify' f = do
  x - get
  put $! f x  -- force the new state when storing it

With the attached code, the first case (using modify) prints out a trace 
like:


test
work:1
modify
work:2
modify
work:3
modify
work:4
modify
work:5
modify
work:6
modify
work:7
modify
work:8
modify
work:9
modify
work:10
modify
update:vnbz
update:dzgd
update:hzla
update:nudd
update:bzfl
update:muht
update:hims
update:jakj
update:lvrt
update:qdxo
initial
MyState {val = vnbz}

Notice how the state updates are only evaluated right at the end, when 
the value is forced - note also that this means that all the data needs 
to hang around until then.


The second case (using modify') forces the state as it goes along:

test'
work:1
modify'
update:zwre
initial
work:2
modify'
update:fefg
work:3
modify'
update:eoqa
work:4
modify'
update:xtak
work:5
modify'
update:tekd
work:6
modify'
update:qrsz
work:7
modify'
update:fdgj
work:8
modify'
update:alwj
work:9
modify'
update:kqsp
work:10
modify'
update:lazz
MyState {val = lazz}



Claude
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Main where

import Debug.Trace
import System.Random

import Control.Monad.State.Strict

modify' :: MonadState s m = (s - s) - m ()
modify' f = do
  x - get
  put $! f x

data MyState = MyState { val :: String } deriving Show

newtype Foo a = Foo { run :: StateT MyState IO a }
	deriving (
		Monad,
		MonadState MyState,
		MonadIO
	)

main :: IO ()
main = do
  print = execStateT (run test) (trace initial $ MyState )
  print = execStateT (run test') (trace initial $ MyState )
	
test :: Foo ()
test = trace test $ mapM_ work [1..10]-- massive memory leak

test' :: Foo ()
test' = trace test' $ mapM_ work' [1..10]

work :: Integer - Foo ()
work n = trace (work:++show n) $ do
  v - readSomeFile
  trace modify modify $ trace (update:++v) (\s - s { val = v })

work' :: Integer - Foo ()
work' n = trace (work:++show n) $ do
  v - readSomeFile
  trace modify' modify' $ trace (update:++v) (\s - s { val = v })

readSomeFile :: Foo String
readSomeFile = liftIO $ replicateM 4 (randomRIO ('a', 'z'))
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] space leak when repeatedly calling Control.Monad.State.Strict.modify

2012-01-29 Thread Joey Hess
Claude Heiland-Allen wrote:
 Control.Monad.State.Strict is strict in the actions, but the state
 itself is still lazy, so you end up building a huge thunk in the
 state containing all the updates that ever took place to the initial
 state.
 
 Using this should fix it:
 
 modify' :: MonadState s m = (s - s) - m ()
 modify' f = do
   x - get
   put $! f x  -- force the new state when storing it

Thanks! 

So, why does Control.Monad.State.Strict.modify not do that?

And, I still don't quite understand why this only happened
when the updated value is obtained using IO.

-- 
see shy jo


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe