[Haskell-cafe] Splittable random numbers

Luke Palmer lrpalmer at gmail.com
Fri Nov 12 15:34:08 EST 2010


On Fri, Nov 12, 2010 at 3:33 AM, Richard Senington <sc06r2s at leeds.ac.uk> wrote:
> In short, I am worried by the properties of this random number generator. I
> propose improving the testing system, and then posting both the test suite
> and this random generator to
> Hackage, unless you really want it up now in a very very preliminary form.

Yeah I think a package of randomness tests could be really useful.  Cool :-)

> RS
>
>>> 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
>>>
>>
>> This can be pure:
>>
>> mkLehmerTreeFromRandom :: (RandomGen g) =>  g ->  LehmerTree
>>
>>
>>>
>>> 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''
>>>
>>>
>>>
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>>>
>>>
>>
>>
>
>


More information about the Haskell-Cafe mailing list