[Haskell-cafe] Fun with the ST monad

Luke Palmer lrpalmer at gmail.com
Fri Feb 25 17:19:25 CET 2011


Lazy ST is capable of returning values lazily.  Not naively -- eg. if
you are writing elements to an STRef and then returning the contents
of the STRef at the end, then of course it will not return gradually
(who's to say that the last thing you do before you return isn't to
write [] to the STRef?)

However, if you do it this way:

import Control.Monad.ST.Lazy
import Data.STRef.Lazy

main = print $ runST work
    where
    work = do
        ref <- newSTRef 0
        let loop = do
                x <- readSTRef ref
                writeSTRef ref $! x+1
                fmap (x:) loop
        loop

You will find that it is perfectly lazy.  You just have to communicate
that the computation *must* yield an element regardless of what the
remainder is.  "fmap (x:) rest" is the typical way I yield elements
from lazy ST.

Luke

On Thu, Feb 24, 2011 at 7:55 PM, Sterling Clover <s.clover at gmail.com> wrote:
> On Feb 24, 2011, at 3:45 PM, Andrew Coppin wrote:
>
> OK, so I had a function that looks like
>
>  transform :: [Word8] -> [Word16]
>
> It works nicely, but I'd like to use mutable state inside. No problem! Use
> the ST monad. Something like
>
>  transform :: [Word8] -> [Word16]
>  transform xs = runST (work xs)
>    where
>      work :: [Word8] -> ST s [Word16]
>
> Ah, yes, well there is one *small* problem... If you do that, the function
> becomes too strict.
>
> unsafeInterleaveST?
> http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad-ST.html#v:unsafeInterleaveST
> --Sterl
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



More information about the Haskell-Cafe mailing list