[Haskell-cafe] "safe" way to use Rand?

Michael Mossey mpm at alumni.caltech.edu
Mon Oct 12 09:23:03 EDT 2009


I'm looking at Control.Monad.Random which provides the Rand monad. I would 
like to know how to use this for generating multiple infinite series, while 
trusting that the implementation never uses "split" behind the scenes.

(Note: I'm on Windows XP, and there appears to be a bug in getStdGen. It 
does NOT return an arbitrary generator, but rather the same one every time 
I run the program. However, newStdGen DOES return an arbitrary generator. 
So I'm using that, even though I know it accesses split behind the scenes. 
My thinking is that this only happens once so it is okay.)

For example, is this code split-free?

simple :: Rand StdGen [Int]
simple = getRandomRs (0::Int, 10)

main1 = do
    gen <- newStdGen
    let answer = (flip evalRand) gen $ do
               xs <- simple
               ys <- simple
               return $ (take 5 xs) ++ (take 3 ys)
    print answer

Then, to elaborate on my specific problem, I need to create special types 
of infinite series. For example, I might need to create one that looks like 
this:

0 0 5 0 0 0 2 0 0 0 0 0 5 0 9 0 0 8 ...

The pattern here is that there is some random number of zeros followed by a 
single non-zero value, followed again by a random number of zeros, etc. 
forever.

This is one way to implement this. Does all look well here?


makeSeries :: [Int] -> [a] -> a -> [a]
makeSeries (i:is) (f:fs) zero = replicate i zero ++ [f]
                                 ++ makeSeries is fs zero

lessSimple :: Rand StdGen [Int]
lessSimple = do
   counts <- getRandomRs (1::Int  , 5  )
   values <- getRandomRs (1::Int  , 9  )
   return $ makeSeries counts values 0

main2 = do
    gen <- newStdGen
    let answer = evalRand lessSimple gen
    print . take 20 $ answer

We could even have several of these series zipped together. Is this split-free?

main3 = do
   gen <- newStdGen
   let fs = (flip evalRand) gen $ do
              s1 <- lessSimple
              s2 <- lessSimple
              return $ zip s1 s2
   print . take 20 $ fs




More information about the Haskell-Cafe mailing list