infinite list of random elements

I'm trying to do something I thought would be pretty simple, but it's giving me trouble. Given a list, say [1,2,3], I'd like to be able to generate an infinite list of random elements from that list, in this case maybe [1,2,1,3,2,1,3,2,3,1,2,...]. I'm using IO for random purely due to laziness (my own, not Haskell's). I was thinking the best way to do this might be to first write this function: randomElts :: [a] -> [IO a] randomElts [] = [] randomElts [x] = repeat (return x) randomElts xs = repeat r where bds = (1, length xs) xArr = listArray bds xs r = do i <- randomRIO bds return (xArr ! i) Then I should be able to do this in ghci:
sequence . take 5 $ randomElts [1,2,3] [*** Exception: stack overflow
Any idea what's going on? I thought laziness (Haskell's, not my own) would save me on this one. Thanks! Chad

On Mon, Jul 30, 2007 at 02:40:35PM -0700, Chad Scherrer wrote:
I'm trying to do something I thought would be pretty simple, but it's giving me trouble.
Given a list, say [1,2,3], I'd like to be able to generate an infinite list of random elements from that list, in this case maybe [1,2,1,3,2,1,3,2,3,1,2,...]. I'm using IO for random purely due to laziness (my own, not Haskell's).
I was thinking the best way to do this might be to first write this function:
randomElts :: [a] -> [IO a] randomElts [] = [] randomElts [x] = repeat (return x) randomElts xs = repeat r where bds = (1, length xs) xArr = listArray bds xs r = do i <- randomRIO bds return (xArr ! i)
Then I should be able to do this in ghci:
sequence . take 5 $ randomElts [1,2,3] [*** Exception: stack overflow
Any idea what's going on? I thought laziness (Haskell's, not my own) would save me on this one.
The code you posted works fine for me (GHCi 6.7.20070712). However, it's pretty bad style in a way that suggests a misunderstanding of IO. A value of type IO t is not a "tainted t", it's an "action that returns t". So, in general: do let xv = randomRIO (1,20) a <- xv b <- xv return (a == b) will normally return *False*. Why? Because, while the same action is used, it doesn't always return the same value! In general, when you see a type of the form [IO a] or Maybe (IO a) or IO a -> b, ask yourself if that's what you really want. (Sometimes it is, and the flexibility of having IO anywhere is very powerful). A better way to write randomElts is: randomElt :: [a] -> IO a randomElt xs = do ix <- randomRIO bds return (arr ! i) where arr = listArray bds xs bds = (1, length xs) randomElts :: Int -> [a] -> IO [a] randomElts n xs = replicateM n (randomElt xs) -- uses replicateM from Control.Monad Sadly, it's very hard to "just return an infinite list" in IO. it can be done in dedicated monads, however. Stefan

On 30/07/07, Chad Scherrer
I'm trying to do something I thought would be pretty simple, but it's giving me trouble.
Given a list, say [1,2,3], I'd like to be able to generate an infinite list of random elements from that list, in this case maybe [1,2,1,3,2,1,3,2,3,1,2,...]. I'm using IO for random purely due to laziness (my own, not Haskell's).
I was thinking the best way to do this might be to first write this function:
randomElts :: [a] -> [IO a] randomElts [] = [] randomElts [x] = repeat (return x) randomElts xs = repeat r where bds = (1, length xs) xArr = listArray bds xs r = do i <- randomRIO bds return (xArr ! i)
Then I should be able to do this in ghci:
sequence . take 5 $ randomElts [1,2,3] [*** Exception: stack overflow
Any idea what's going on? I thought laziness (Haskell's, not my own) would save me on this one.
I don't get that result. However, you can't compute an infinite random list in IO without using something like unsafeInterleaveIO. However, you will probably be interested in randoms/randomRs, which take a random generator, and give an infinite list of results. Using that, we could write something like: randomElts :: [a] -> IO [a] randomElts [] = return [] randomElts xs = do g <- newStdGen return (map (xArr !) (randomRs bds g)) where bds = (1, length xs) xArr = listArray bds xs which for a nonempty input list, gives an infinite list of pseudorandom elements of that input list. - Cale

Why this obsession with IO? There should be no IO involved in this, except
for getting the initial generator.
Using IO just confuses what is going on.
-- Lennart
On 7/30/07, Cale Gibbard
On 30/07/07, Chad Scherrer
wrote: I'm trying to do something I thought would be pretty simple, but it's giving me trouble.
Given a list, say [1,2,3], I'd like to be able to generate an infinite list of random elements from that list, in this case maybe [1,2,1,3,2,1,3,2,3,1,2,...]. I'm using IO for random purely due to laziness (my own, not Haskell's).
I was thinking the best way to do this might be to first write this function:
randomElts :: [a] -> [IO a] randomElts [] = [] randomElts [x] = repeat (return x) randomElts xs = repeat r where bds = (1, length xs) xArr = listArray bds xs r = do i <- randomRIO bds return (xArr ! i)
Then I should be able to do this in ghci:
sequence . take 5 $ randomElts [1,2,3] [*** Exception: stack overflow
Any idea what's going on? I thought laziness (Haskell's, not my own) would save me on this one.
I don't get that result. However, you can't compute an infinite random list in IO without using something like unsafeInterleaveIO. However, you will probably be interested in randoms/randomRs, which take a random generator, and give an infinite list of results.
Using that, we could write something like:
randomElts :: [a] -> IO [a] randomElts [] = return [] randomElts xs = do g <- newStdGen return (map (xArr !) (randomRs bds g)) where bds = (1, length xs) xArr = listArray bds xs
which for a nonempty input list, gives an infinite list of pseudorandom elements of that input list.
- Cale _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 30/07/07, Lennart Augustsson
Why this obsession with IO? There should be no IO involved in this, except for getting the initial generator. Using IO just confuses what is going on.
Indeed. Here's my version: -- first define a shuffle function, completely pure! pick 1 (x:xs) = (x, xs) pick n (x:xs) = (y, x:ys) where (y, ys) = pick (n-1) xs shuffle gen xs = shuffle' gen xs (length xs) shuffle' _ [] _ = [] shuffle' gen xs n = p : shuffle' gen' xs' (n-1) where (r, gen') = randomR (1,n) gen (p, xs') = pick r xs -- a function for giving us an infinite list of generators from -- an initial generator gens g = unfoldr (Just . split) g -- shuffles the given list an infinite number of times -- with a different generator each time shuffles xs g = zipWith shuffle (gens g) (repeat xs) You can then pass in whatever generator you wish to shuffles. E.g. create a pure one with mkStdGen or create one in the IO monad with newStdGen. -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862

Thanks for your responses. Stefan, I appreciate your taking a step back for me (hard to judge what level of understanding someone is coming from), but the example you gave doesn't contradict my intuition either. I don't consider the output [IO a] a "list of tainted a's", but, as you suggest, a "list of IO actions, each returning an a". I couldn't return an IO [a], since that would force evaluation of an infinite list of random values, so I was using [IO a] as an intermediary, assuming I'd be putting it through something like (sequence . take n) rather than sequence alone. Unfortunately, I can't use your idea of just selecting one, because I don't have any way of knowing in advance how many values I'll need (in my case, that depends on the results of several layers of Map.lookup). Also, I'm using GHC 6.6, so maybe there have been recent fixes that would now allow my idea to work. Cale, that's interesting. I wouldn't have thought this kind of laziness would work in this context. Lennart, I prefer the purely functional approach as well, but I've been bitten several times by laziness causing space leaks in this context. I'm on a bit of a time crunch for this, so I avoided the risk. Sebastian, this seems like a nice abstraction to me, but I don't think it's the same thing statistically. If I'm reading it right, this gives a concatenation of an infinite number of random shuffles of a sequence, rather than sampling with replacement for each value. So shuffles [1,2] g would never return [1,1,...], right? Chad
I was thinking the best way to do this might be to first write this function:
randomElts :: [a] -> [IO a] randomElts [] = [] randomElts [x] = repeat (return x) randomElts xs = repeat r where bds = (1, length xs) xArr = listArray bds xs r = do i <- randomRIO bds return (xArr ! i)
Then I should be able to do this in ghci:
sequence . take 5 $ randomElts [1,2,3] [*** Exception: stack overflow

Chad Scherrer wrote:
I prefer the purely functional approach as well, but I've been bitten several times by laziness causing space leaks in this context. I'm on a bit of a time crunch for this, so I avoided the risk.
Well, space leaks won't magically disappear if you use IO a . Regards, apfelmus

No leak in sight.
-- Lennart
import Random
import Array
randomElts :: RandomGen g => g -> [a] -> [a]
randomElts _ [] = []
randomElts g xs = map (a!) rs
where a = listArray (1, n) xs
rs = randomRs (1, n) g
n = length xs
main = do
g <- getStdGen
let xs = randomElts g [10,2,42::Int]
print $ sum $ take 1000000 xs
On 7/31/07, Chad Scherrer
Thanks for your responses.
Stefan, I appreciate your taking a step back for me (hard to judge what level of understanding someone is coming from), but the example you gave doesn't contradict my intuition either. I don't consider the output [IO a] a "list of tainted a's", but, as you suggest, a "list of IO actions, each returning an a". I couldn't return an IO [a], since that would force evaluation of an infinite list of random values, so I was using [IO a] as an intermediary, assuming I'd be putting it through something like (sequence . take n) rather than sequence alone. Unfortunately, I can't use your idea of just selecting one, because I don't have any way of knowing in advance how many values I'll need (in my case, that depends on the results of several layers of Map.lookup). Also, I'm using GHC 6.6, so maybe there have been recent fixes that would now allow my idea to work.
Cale, that's interesting. I wouldn't have thought this kind of laziness would work in this context.
Lennart, I prefer the purely functional approach as well, but I've been bitten several times by laziness causing space leaks in this context. I'm on a bit of a time crunch for this, so I avoided the risk.
Sebastian, this seems like a nice abstraction to me, but I don't think it's the same thing statistically. If I'm reading it right, this gives a concatenation of an infinite number of random shuffles of a sequence, rather than sampling with replacement for each value. So shuffles [1,2] g would never return [1,1,...], right?
Chad
I was thinking the best way to do this might be to first write this function:
randomElts :: [a] -> [IO a] randomElts [] = [] randomElts [x] = repeat (return x) randomElts xs = repeat r where bds = (1, length xs) xArr = listArray bds xs r = do i <- randomRIO bds return (xArr ! i)
Then I should be able to do this in ghci:
sequence . take 5 $ randomElts [1,2,3] [*** Exception: stack overflow
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Ok, that looks good, but what if I need some random values elsewhere
in the program? This doesn't return a new generator (and it can't
because you never get to the end of the list). Without using IO or ST,
you'd have to thread the parameter by hand or use the State monad,
right? This is where I was leaking space before.
Actually, this makes me wonder... I think what killed it before was
that the state was threaded lazily through the various (= very many)
calls. I suppose a State' monad, strict in the state, could help here.
I wonder how performance for this would compare with IO or ST. Might
have to try that sometime...
Chad
On 7/31/07, Lennart Augustsson
No leak in sight.
-- Lennart
import Random import Array
randomElts :: RandomGen g => g -> [a] -> [a] randomElts _ [] = [] randomElts g xs = map (a!) rs where a = listArray (1, n) xs rs = randomRs (1, n) g n = length xs
main = do g <- getStdGen let xs = randomElts g [10,2,42::Int] print $ sum $ take 1000000 xs

On Jul 31, 2007, at 16:20 , Chad Scherrer wrote:
calls. I suppose a State' monad, strict in the state, could help here.
You mean Control.Monad.State.Strict ? -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Well, I don't know how many generators you need. But I'm sure you can pass
them around in a way that doesn't leak.
On 7/31/07, Chad Scherrer
Ok, that looks good, but what if I need some random values elsewhere in the program? This doesn't return a new generator (and it can't because you never get to the end of the list). Without using IO or ST, you'd have to thread the parameter by hand or use the State monad, right? This is where I was leaking space before.
Actually, this makes me wonder... I think what killed it before was that the state was threaded lazily through the various (= very many) calls. I suppose a State' monad, strict in the state, could help here. I wonder how performance for this would compare with IO or ST. Might have to try that sometime...
Chad
On 7/31/07, Lennart Augustsson
wrote: No leak in sight.
-- Lennart
import Random import Array
randomElts :: RandomGen g => g -> [a] -> [a] randomElts _ [] = [] randomElts g xs = map (a!) rs where a = listArray (1, n) xs rs = randomRs (1, n) g n = length xs
main = do g <- getStdGen let xs = randomElts g [10,2,42::Int] print $ sum $ take 1000000 xs
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Chad Scherrer:
Ok, that looks good, but what if I need some random values elsewhere in the program? This doesn't return a new generator (and it can't because you never get to the end of the list).
To fix that, just replace the call to getStdGen with a call to newStdGen, as has already been suggested by Sebastian. Internally, newStdGen uses "split" to produce an independent generator, and also updates the global generator. Thus, repeated calls to newStdGen all return independent generators. So, bringing together the suggestions so far, we get this:
import Random import Array
-- from Lauri Alanko randomElts rg xs = map (arr !) (randomRs bds rg) where bds = (1, length xs) arr = listArray bds xs
-- see discussion below inspect_stream = foldr (\x -> (seq x).(x:)) []
main = do let foo g = drop 10000000 $ inspect_stream $ randomElts g [10,2,42::Int] g1 <- newStdGen g2 <- newStdGen print $ take 10 $ foo g1 print $ take 10 $ foo g2
No space leaks, independent lazy infinite random sequences. I was somewhat dismayed that I needed to write inspect_stream to make the demonstration using drop work without a stack overflow. This is because the current implementation of randomRs is quite lazy, making it very easy to build up huge thunks which blow the stack if you don't evaluate them from the inside out. For most applications, where you inspect the random numbers in roughly the same order as you extract them from the sequence, this wouldn't be a problem. Are there real applications (as opposed to toy demonstrations) where this wouldn't be the case? I don't know, but perhaps the question of whether randomRs should be more strict warrants some discussion.

On Mon, Jul 30, 2007 at 02:40:35PM -0700, Chad Scherrer wrote:
Given a list, say [1,2,3], I'd like to be able to generate an infinite list of random elements from that list, in this case maybe [1,2,1,3,2,1,3,2,3,1,2,...]. I'm using IO for random purely due to laziness (my own, not Haskell's).
You can be even lazier and let the Random library do more of the work for you, seeing that it includes randomRs: randomElts rg xs = map (arr !) (randomRs bds rg) where bds = (1, length xs) arr = listArray bds xs Lauri
participants (9)
-
apfelmus
-
Brandon S. Allbery KF8NH
-
Cale Gibbard
-
Chad Scherrer
-
Lauri Alanko
-
Lennart Augustsson
-
Matthew Brecknell
-
Sebastian Sylvan
-
Stefan O'Rear