[Haskell-cafe] infinite list of random elements

Lennart Augustsson lennart at augustsson.net
Tue Jul 31 15:48:09 EDT 2007


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 <chad.scherrer at gmail.com> wrote:
>
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070731/4360a1a6/attachment.htm


More information about the Haskell-Cafe mailing list