[Haskell-cafe] Re: [Haskell] Laziness and the IO Monad (randomness)

Matthew Brecknell haskell at brecknell.org
Fri Mar 2 08:44:27 EST 2007


Dave Tapley wrote:
> However this latter case gets stuck in an infinite loop, terminating on a stack overflow.

Kirsten Chevalier said:
> You didn't say which function you had narrowed down the stack overflow
> to, but I suspect it's here:
> 
> > firstTen :: IO [Int]
> > firstTen = do
> >     infiniteNums <- iterateM addRand randNum
> >     return (take 10 infiniteNums)
> 
> In order for IO to work the way you'd expect, you have to be able to
> specify which IO operations happen in what order, which is exactly
> what a do-block within the IO monad specifies. But specifying the
> order of operations also means specifying in what order evaluation
> happens. So, the code you've written means "evaluate infiniteNums
> fully (in order that we might do whatever IO operations it involves
> before the return statement), then return the first 10 elements of its
> result." Since you're forcing evaluation of an infinite list, the
> program loops infinitely.

I don't think the IO monad is to blame in this case. There's no reason
that an IO action can't return a lazily generated list. For a trivial
example:

infM f i = return (iterate f i)

runFooM = do
  inf <- infM succ 0
  print $ take 10 inf

The strictness of the IO monad depends on the IO primitives used. In
particular, return is not strict in its argument.

The real culprit here is iterateM, since it has to run the (infinitely
recursive) tail action before it can return the cons of head and tail.
There is no way around this, since the function being iterated is a
monadic action. The only way for iterateM to return anything at all is
for the head action to fail at some iteration. By "fail", I just mean
any case where (>>=) returns without calling its second argument. For
example, in the Maybe monad:

Prelude> iterateM return (Just 42)
*** Exception: stack overflow
Prelude> iterateM return Nothing
Nothing

Unfortunately, failure at any iteration will mean failure altogether,
and that means no list is returned. I suspect this would be true in any
monad, though I don't know how to prove it. An example in the Maybe
monad:

testMaybe x | x > 0 = Just (x-1)
testMaybe _ = Nothing

Prelude> iterateM testMaybe (Just 42)
Nothing

In the IO monad, iterateM must result in either a runtime error, or an
infinite loop leading to inevitable resource exhaustion. But the main
point is that iterateM cannot be expected to return a lazily-generated
list in any monad.

The possible solutions are as suggested by Kirsten and David. If you use
randomRs based on the global generator, be sure to use split or
newStdGen to avoid accidentally reusing pseudo-random subsequences, for
example:

randomSequence :: (Random a) => (a,a) -> IO [a]
randomSequence range = do
  gen <- newStdGen
  return (randomRs range gen)

If you've made it this far, you might also want to take a look at
MonadRandom and friends:

http://haskell.org/haskellwiki/New_monads/MonadRandom



More information about the Haskell-Cafe mailing list