Plug space leak with seq. How?

Hello café! This mail is literate haskell I have some difficulties with understanding how bang patterns and seq works.
{-# LANGUAGE BangPatterns #-} import Control.Monad import Control.Monad.Trans.State.Strict
leak :: State Int () leak = do a <- get put (a+1) leak
This function have obvious space leak. It builds huge chain of thunks so callling `runState leak 0' in ghci will eat all memory. Fix is trivial - add bang pattern. However I couldn't achieve same effect with seq. How could it be done?
noLeak :: State Int () noLeak = do a <- get let !a' = (a + 1) put a' noLeak
Thanks.

Is it not:
noLeak :: State Int () noLeak = do a <- get *>* * let a' = (a + 1) a' `seq` put a'* noLeak
??
2011/6/9 Alexey Khudyakov
Hello café!
This mail is literate haskell
I have some difficulties with understanding how bang patterns and seq works.
{-# LANGUAGE BangPatterns #-} import Control.Monad import Control.Monad.Trans.State.Strict
leak :: State Int () leak = do a <- get put (a+1) leak
This function have obvious space leak. It builds huge chain of thunks so callling `runState leak 0' in ghci will eat all memory. Fix is trivial - add bang pattern. However I couldn't achieve same effect with seq. How could it be done?
noLeak :: State Int () noLeak = do a <- get let !a' = (a + 1) put a' noLeak
Thanks.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thursday 09 June 2011, 18:09:44, Yves Parès wrote:
Is it not:
noLeak :: State Int () noLeak = do
a <- get
*>* * let a' = (a + 1)
a' `seq` put a'* noLeak
??
Alternatively, noLeak = do a <- get a `seq` put (a+1) noLeak or noLeak = do a <- get put $! a+1 noLeak should eliminate the leak too.

On 09.06.2011 20:09, Yves Parès wrote:
Is it not:
noLeak :: State Int () noLeak = do a <- get *>* *let a' = (a + 1) a' `seq` put a'* noLeak
??
Indeed. Now I understand. It didn't work for me earlier because of different behavior of 'forever' in ghci and compiled code. This function leaks in ghci and do not in compiled code without optimizations (with optimizations GHC is smart enough to make everything strict).
noLeak = forever $ do { a <- get; let a' = a+1; a' `seq` put a' }
Function with explicit recursion do not leak in both cases.
noLeak = do { a <- get; let a' = a+1; a' `seq` put a'; noLeak }
What causes this difference?

On Thursday 09 June 2011, 18:41:40, Alexey Khudyakov wrote:
On 09.06.2011 20:09, Yves Parès wrote:
Is it not:
noLeak :: State Int () noLeak = do
a <- get
*>* *let a' = (a + 1)
a' `seq` put a'* noLeak
??
Indeed. Now I understand. It didn't work for me earlier because of different behavior of 'forever' in ghci and compiled code.
This function leaks in ghci and do not in compiled code without optimizations (with optimizations GHC is smart enough to make everything strict).
noLeak = forever $ do { a <- get; let a' = a+1; a' `seq` put a' }
Function with explicit recursion do not leak in both cases.
noLeak = do { a <- get; let a' = a+1; a' `seq` put a'; noLeak }
What causes this difference?
forever a = a >> forever a doesn't tie to itself without optimisations, so my guess is that it gets expanded when you run/eval/execState it in ghci, building the thunk a >> a >> a >> a >> ... If you define forever' a = let a' = a >> a' in a' the variant using forever' runs in constant space in ghci. This, like the explicit recursion, builds a cyclic structure, hence avoids the leak.

forever a = a>> forever a
doesn't tie to itself without optimisations, so my guess is that it gets expanded when you run/eval/execState it in ghci, building the thunk
a>> a>> a>> a>> ...
If you define
forever' a = let a' = a>> a' in a'
the variant using forever' runs in constant space in ghci. This, like the explicit recursion, builds a cyclic structure, hence avoids the leak.
I see. It's difficult to reason about space complexity in presence of optimizer.
participants (3)
-
Alexey Khudyakov
-
Daniel Fischer
-
Yves Parès