[Haskell-cafe] Plug space leak with seq. How?
Yves Parès
limestrael at gmail.com
Thu Jun 9 18:09:44 CEST 2011
Is it not:
> noLeak :: State Int ()
> noLeak = do
> a <- get
*>* * let a' = (a + 1)
> a' `seq` put a'*
> noLeak
??
2011/6/9 Alexey Khudyakov <alexey.skladnoy at gmail.com>
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110609/6675ecf2/attachment.htm>
More information about the Haskell-Cafe
mailing list