[Haskell-cafe] Splittable random numbers

Richard Senington sc06r2s at leeds.ac.uk
Thu Nov 11 05:13:00 EST 2010


I got hold of, and looked through the paper suggested in the root of 
this thread "Pseudo random trees in Monte-Carlo 
<http://portal.acm.org/citation.cfm?id=1746034>", and based upon this
I have thrown together a version of the binary tree based random number 
generator suggested.

I would like to point out that I do not know very much about random 
number generators, the underlying mathematics or any subsequent papers 
on this subject, this is just a very naive implementation based upon 
this one paper.

As a question, the following code actually generates a stream of numbers 
that is more random than I was expecting, if anyone can explain why I 
would be very interested.

import System.Random

data LehmerTree = LehmerTree {nextInt :: Int,
                               leftBranch :: LehmerTree,
                               rightBranch :: LehmerTree}

instance Show LehmerTree where
   show g = "LehmerTree, current root = "++(show $ nextInt g)

mkLehmerTree :: Int->Int->Int->Int->Int->Int->LehmerTree
mkLehmerTree aL aR cL cR m x0 = innerMkTree x0
   where
     mkLeft x = (aL * x + cL) `mod` m
     mkRight x = (aR * x + cR) `mod` m
     innerMkTree x = let l = innerMkTree (mkLeft x)
                         r = innerMkTree (mkRight x)
                     in LehmerTree x l r

mkLehmerTreeFromRandom :: IO LehmerTree
mkLehmerTreeFromRandom = do gen<-getStdGen
                             let a:b:c:d:e:f:_ = randoms gen
                             return $ mkLehmerTree a b c d e f

instance RandomGen LehmerTree where
   next g = (fromIntegral.nextInt $ g, leftBranch g)
   split g = (leftBranch g, rightBranch g)
   genRange _ = (0, 2147483562) -- duplicate of stdRange



test :: IO()
test = do gen<-mkLehmerTreeFromRandom
           print gen
           let (g1,g2) = split gen
           let p = take 10 $ randoms gen :: [Int]
           let p' = take 10 $ randoms g1 :: [Int]
           -- let p'' = take 10 $ randoms g2 :: [Float]
           print p
           print p'
           -- print p''


-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20101111/7448ad15/attachment-0001.html


More information about the Haskell-Cafe mailing list