Is it not:

> noLeak :: State Int ()
> noLeak = do
>   a <- get
*>*  * let a' = (a + 1)
>   a' `seq` put a'*
>   noLeak

??

2011/6/9 Alexey Khudyakov <[email protected]>

> 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
> [email protected]
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to