Confused about Random
Simon Peyton-Jones
simonpj@microsoft.com
Fri, 30 Nov 2001 06:42:31 -0800
Yes, the implementation of
instance Random Int
in GHC's library pre-dates the existence of the genRange class
operation for RandomGen. GHC's implementation of the instance
behaves extremely badly when given a random generator with
only two values (as in your example).
I would love someone to send me a better implementation of the
Random library. Preferably someone who understands the pitfalls.
Simon
| -----Original Message-----
| From: Ian Lynagh [mailto:igloo@earth.li]=20
| Sent: 29 November 2001 15:32
| To: haskell@haskell.org
| Subject: Confused about Random
|=20
|=20
|=20
| With the following module:
|=20
| module Main where
|=20
| import Random
|=20
| data Foo =3D Foo StdGen
|=20
| main :: IO()
| main =3D do let rs =3D randoms (Foo (mkStdGen 39)) :: [Int]
| rRs =3D randomRs (0,9) (Foo (mkStdGen 39)) :: [Int]
| putStrLn $ show $ take 100 rs
| putStrLn $ show $ take 100 rRs
|=20
| instance RandomGen Foo where
| genRange _ =3D (0, 1)
| next (Foo g) =3D (val `mod` 2, Foo g')
| where (val, g') =3D random g
| split _ =3D error "Not implemented"
|=20
| ghc gives me
|=20
| [-2147476078,7482,-2147476078,-2147476078,-2147476079,-2147476
| 078,7483,7482,7482,-2147476079,-2147476078,-2147476079,-214747
| 6079,7482,-2147476078,-2147476078,-2147476078,-2147476079,7482
| ,7483,7482,7483,7482,-2147476078,-2147476078,-2147476078,7483,
| -2147476079,7482,-2147476078,-2147476079,-2147476078,7483,-214
| 7476079,7483,7482,-2147476079,7483,7482,7483,-2147476078,-2147
| 476079,-2147476079,7482,-2147476078,7482,-2147476079,-21474760
| 79,7482,-2147476078,7483,7483,-2147476079,-2147476078,7483,748
| 3,-2147476078,-2147476079,-2147476078,-2147476079,-2147476078,
| 7483,7483,7482,7482,7483,-2147476078,-2147476079,-2147476079,7
| 482,7483,-2147476078,-2147476079,-2147476079,-2147476078,7482,
| 7483,-2147476079,7482,7482,7482,7483,-2147476079,-2147476079,-
| 2147476078,7482,7482,7482,7482,-2147476079,7482,7482,-21474760
| 79,7483,-2147476078,7482,7483,-2147476079,-2147476079,7482]
| [1,2,2,1,1,2,1,2,1,1,1,2,2,2,2,1,2,1,1,1,1,2,1,1,1,1,2,1,1,2,1
| ,2,1,2,1,1,2,1,2,2,2,1,2,2,2,1,1,2,1,2,1,2,2,2,1,1,2,1,1,2,1,1
| ,1,2,2,2,1,1,2,2,2,1,1,1,2,2,2,1,2,2,1,2,1,1,1,1,2,1,1,2,2,1,1
| ,1,1,1,2,1,1,2]
|=20
| The first list doesn't seem to cover the whole spectrum and I=20
| was expecting the second list to be composed over 0s through=20
| 9s. Is my understanding wrong?
|=20
| nhc complains
| Context for Random.Random needed in left hand pattern at=20
| 17:11. and hugs doesn't seem to know genRange exists. With it=20
| commented out it returns the same as ghc.
|=20
|=20
| Thanks
| Ian
|=20
|=20
| _______________________________________________
| Haskell mailing list
| Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell
|=20