[Haskell-cafe] Why doesn't this work?

Daniel Fischer daniel.is.fischer at web.de
Mon Apr 25 05:37:13 EDT 2005


Am Montag, 25. April 2005 08:16 schrieb Michael Vanier:
> I've been trying to generate an infinite list of random coin flips in GHC
> 6.4, and I've come across some strange behavior:
>
> ----------------------------------------------------------------------
> import System.Random
>
> data Coin = H | T deriving (Eq, Show)
>
> -- Generate a random coin flip.
> coinFlip :: IO Coin
> coinFlip = do b <- getStdRandom random
>               return (bool2coin b)
>            where
>               bool2coin True  = H
>               bool2coin False = T
>
> -- Generate an infinite list of coin flips.
> coinFlips :: IO [Coin]
> coinFlips = sequence cfs
>             where cfs = (coinFlip : cfs)
>
> -- Print n of them.
> test :: Int -> IO ()
> test n = do f <- coinFlips
>             print (take n f)
> ----------------------------------------------------------------------
>
> Now when I do "test 1" (for instance), it hangs forever.  It seems as if
> there is some kind of strictness constraint going on that I don't
> understand.  My understanding is that cfs is an infinite list of (IO Coin),
> sequence lifts this to be IO [Coin] where [Coin] is an infinite list, and
> then test should extract the infinite list of coin flips into f, take some
> number of them, and print them.  But instead, the system appears to be
> trying to compute all the coin flips before taking any of them.  Why is
> this, and how do I fix it?
>
> Thanks,
>
> Mike
>
How to fix it:

test n = sequence (replicate n coinFlip) >>= print

another way to fix it: use unsafeInterleaveIO (I would not recommend it, 
though)
import System.IO.Unsafe

coinFlips = do c <- coinFlip
                     cs <- unsafeInterleaveIO coinFlips
                     return (c:cs)

Why: because coinFlips has to be evaluated before the result can be passed to 
'print . take n' (that's part of the IO monad, executing actions in 
sequence). And this can't be done lazily with sequence:
sequence       :: Monad m => [m a] -> m [a]
{-# INLINE sequence #-}
sequence ms = foldr k (return []) ms
	    where
	      k m m' = do { x <- m; xs <- m'; return (x:xs) }

so 
sequence (ac:acs) = foldr k (return []) (ac:acs)
                             = k ac (foldr k (return []) acs)
                             = do x <- ac
                                     xs <- sequence acs
                                     return (x:xs)
and if sequence acs fails, the overall computation fails and nothing can be 
returned. The point is, the function 'k' from sequence is strict, and folding 
a strict function always uses the entire list (unless an error occurs before 
the end is reached).
Conclusion: sequence only finite lists, otherwise you'll get a Stack overflow.

Cheers,
Daniel


More information about the Haskell-Cafe mailing list