
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

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

On Sun, 2005-04-24 at 23:16 -0700, Michael Vanier wrote:
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?
My first guess is that this is because sequence is strict in it's list. This is the normal behaviour that you would expect for this function since otherwise the side effects from all the IO actions are not going to happen before it returns (which is the ordinary behaviour for IO actions; one of the main purposes of the IO monad is for sequencing side effects). You can lazily defer IO actions using unsafeInterleaveIO. However in this case that's probably not the most elegant approach. It might be better to make the coinFlip function pure (ie not in the IO monad) and instead to pass it a random number generator which it returns as an extra component of the result (having extracted a random value using 'random'). Then you can use getStdGen once and pass the result to a function which generates an infinite lazy list of random numbers by threading the generator between calls to coinFlip. (Or if you want to cheat you can use randoms which will do all this for you) See: http://haskell.org/ghc/docs/latest/html/libraries/base/System.Random.html Duncan

On 4/25/05, 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?
I think you're doing too much in the IO monad and sequence introduces unwanted strictness. Try this instead: coins :: RandomGen g => g -> [Coin] coins g = map bool2coin (randoms g) where bool2coin True = H bool2coin False = T coinFlips :: IO [Coin] coinFlips = do g <- newStdGen return (coins g) test :: Int -> IO () test n = do f <- coinFlips print (take n f) Basically: Don't do stuff in the IO monad unless it really belongs in the IO monad. /S -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

On 2005 April 25 Monday 02:16, Michael Vanier wrote:
-- Generate an infinite list of coin flips. coinFlips :: IO [Coin] coinFlips = sequence cfs where cfs = (coinFlip : cfs) ----------------------------------------------------------------------
[...] 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, Names that have type IO t (such as coinFlip and coinFlips) are actions that, when invoked, are guaranteed to be executed in sequence. CoinFlips cannot terminate because it invokes the coinFlip action an infinite number of times.
and how do I fix it? In this case, you can add a parameter to coinFlips. -- Generate an finite list of coin flips. coinFlips :: Integer -> IO [Coin] coinFlips n = sequence cfs where cfs = take n (coinFlip : cfs)
What you have in mind is more along the lines of using the Random module's 'randoms', as in test n <- do rng <- getStdGen print (take n (randoms rng :: [Bool])) In the above, 'randoms rng' is an infinite list of random Bool values. You want an infinite list of Coin values. You can transform the list of Bool to list of Coin. Even niftier is to make Coin an instance of the Random class, to enable the following: test n <- do rng <- getStdGen print (take n (randoms rng :: [Coin]))
participants (5)
-
Daniel Fischer
-
Duncan Coutts
-
Michael Vanier
-
Scott Turner
-
Sebastian Sylvan