Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

[Haskell-cafe] unsafeInerleaveIO and randomIO

0 views
Skip to first unread message

Marc Weber

unread,
Apr 17, 2007, 2:18:09 AM4/17/07
to haskel...@haskell.org
stefan has pointed me a nice version:

============= =======================================================
randomInts :: IO [Int]
randomInts = randoms `fmap` newStdGen

main = do
ints <- randomInts
print $ take 5 ints
=========== =========================================================

Anyway I'm curious why

============= =======================================================
module Main where
import Data.Char
import Control.Monad
import Random
import System.IO.Unsafe

randomInts :: IO [Int]
randomInts = unsafeInterleaveIO $
sequence $ cycle [unsafeInterleaveIO randomIO]

main = do
ints <- unsafeInterleaveIO randomInts
print $ take 5 ints
============= =======================================================

doesn't return.
Where did I miss another unsafeInerleaveIO to make it lazy enough?
I still need a hint.

Marc
_______________________________________________
Haskell-Cafe mailing list
Haskel...@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Bertram Felgenhauer

unread,
Apr 17, 2007, 6:35:59 AM4/17/07
to haskel...@haskell.org
Marc Weber wrote:
> stefan has pointed me a nice version:
>
> Anyway I'm curious why
>
> ============= =======================================================
> randomInts :: IO [Int]
> randomInts = unsafeInterleaveIO $
> sequence $ cycle [unsafeInterleaveIO randomIO]
> ============= =======================================================
>
> doesn't return.

sequence isn't lazy (not in the IO monad at least); it will try to run
to completion, returning an infinite list of (as yet unevaluated, due
to unsafeInterleaveIO) thunks. The construction of that list will never
finish though.

I think you want something like (untested)

> unsafeInterleaveSequence :: [IO a] -> IO [a]
> unsafeInterleaveSequence [] = return []
> unsafeInterleaveSequence (x:xs) =
> unsafeInterleaveIO $ liftM2 (:) x (unsafeInterleaveSequence xs)
>
> randomInts = unsafeInterleaveSequence $ repeat randomIO

or maybe (unsafeInterleaveIO randomIO) instead of randomIO.

Bertram

Matthew Brecknell

unread,
Apr 17, 2007, 7:32:25 AM4/17/07
to haskel...@haskell.org
Bertram Felgenhauer:

> > unsafeInterleaveSequence :: [IO a] -> IO [a]
> > unsafeInterleaveSequence [] = return []
> > unsafeInterleaveSequence (x:xs) =
> > unsafeInterleaveIO $ liftM2 (:) x (unsafeInterleaveSequence xs)
> >
> > randomInts = unsafeInterleaveSequence $ repeat randomIO

I took a peek at GHC's Random.hs to get an idea of how "unsafe" this
approach might be. I see that theStdGen is stored in an IORef, and that
newStdGen and getStdGen are implemented in terms of the unsynchronised
getStdGen and setStdGen. I guess this allows a race condition in which
randomIO and friends could return duplicate random numbers in different
threads?

Something like this might be better:

> getStdRandom f = atomicModifyIORef theStdGen (swap . f)
> where swap (v,g) = (g,v)
> newStdGen = atomicModifyIORef theStdGen split

Now let's see if I can figure out how to submit my first patch...

Marc Weber

unread,
Apr 17, 2007, 6:24:29 PM4/17/07
to haskel...@haskell.org
> sequence isn't lazy (not in the IO monad at least); it will try to run
> to completion, returning an infinite list of (as yet unevaluated, due

I should have learned that lesson already..

This is the second time I could have needed a lazy IO monad version..
Does something like this already exist?

============= LazyIO test ============================================
module Main where
import Control.Monad
import System.IO.Unsafe

import Random

data LazyIO a = LazyIO (IO a)

-- conversion
unLazy :: LazyIO a -> IO a
unLazy (LazyIO a) = a

-- my lazy monad
instance Monad LazyIO where
return a = LazyIO (return a)
(LazyIO m) >>= k = LazyIO $ unsafeInterleaveIO $ m >>= unLazy . k

main = do
print "LazyIO test"
putStrLn "this should work : (LazyIO version)"
randoms <- unLazy . sequence . cycle $ [ LazyIO (randomIO :: IO Int) ]
print $ take 5 randoms
putStrLn "this should hang : (IO version)"
randoms <- sequence . cycle $ [ randomIO :: IO Int ]
print $ take 5 randoms
============= LazyIO test ============================================

compare this (adding unLazy and LazyIO) to reimplementing
sequence, mapM, ...


> > unsafeInterleaveSequence :: [IO a] -> IO [a]
> > unsafeInterleaveSequence [] = return []
> > unsafeInterleaveSequence (x:xs) =
> > unsafeInterleaveIO $ liftM2 (:) x (unsafeInterleaveSequence xs)

I really start to love haskell :)
Marc

0 new messages