RE: Confused about Random

2001-11-30 Thread Simon Peyton-Jones

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:[EMAIL PROTECTED]] 
| Sent: 29 November 2001 15:32
| To: [EMAIL PROTECTED]
| Subject: Confused about Random
| 
| 
| 
| With the following module:
| 
| module Main where
| 
| import Random
| 
| data Foo = Foo StdGen
| 
| main :: IO()
| main = do let rs = randoms (Foo (mkStdGen 39)) :: [Int]
|   rRs =  randomRs (0,9) (Foo (mkStdGen 39)) :: [Int]
|   putStrLn $ show $ take 100 rs
|   putStrLn $ show $ take 100 rRs
| 
| instance RandomGen Foo where
|  genRange _ = (0, 1)
|  next (Foo g) = (val `mod` 2, Foo g')
|   where (val, g') = random g
|  split _ = error Not implemented
| 
| ghc gives me
| 
| [-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]
| 
| The first list doesn't seem to cover the whole spectrum and I 
| was expecting the second list to be composed over 0s through 
| 9s. Is my understanding wrong?
| 
| nhc complains
| Context for Random.Random needed in left hand pattern at 
| 17:11. and hugs doesn't seem to know genRange exists. With it 
| commented out it returns the same as ghc.
| 
| 
| Thanks
| Ian
| 
| 
| ___
| Haskell mailing list
| [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
| 

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Confused about Random

2001-11-29 Thread Ian Lynagh


With the following module:

module Main where

import Random

data Foo = Foo StdGen

main :: IO()
main = do let rs = randoms (Foo (mkStdGen 39)) :: [Int]
  rRs =  randomRs (0,9) (Foo (mkStdGen 39)) :: [Int]
  putStrLn $ show $ take 100 rs
  putStrLn $ show $ take 100 rRs

instance RandomGen Foo where
 genRange _ = (0, 1)
 next (Foo g) = (val `mod` 2, Foo g')
  where (val, g') = random g
 split _ = error Not implemented

ghc gives me

[-2147476078,7482,-2147476078,-2147476078,-2147476079,-2147476078,7483,7482,7482,-2147476079,-2147476078,-2147476079,-2147476079,7482,-2147476078,-2147476078,-2147476078,-2147476079,7482,7483,7482,7483,7482,-2147476078,-2147476078,-2147476078,7483,-2147476079,7482,-2147476078,-2147476079,-2147476078,7483,-2147476079,7483,7482,-2147476079,7483,7482,7483,-2147476078,-2147476079,-2147476079,7482,-2147476078,7482,-2147476079,-2147476079,7482,-2147476078,7483,7483,-2147476079,-2147476078,7483,7483,-2147476078,-2147476079,-2147476078,-2147476079,-2147476078,7483,7483,7482,7482,7483,-2147476078,-2147476079,-2147476079,7482,7483,-2147476078,-2147476079,-2147476079,-2147476078,7482,7483,-2147476079,7482,7482,7482,7483,-2147476079,-2147476079,-2147476078,7482,7482,7482,7482,-2147476079,7482,7482,-2147476079,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]

The first list doesn't seem to cover the whole spectrum and I was
expecting the second list to be composed over 0s through 9s. Is my
understanding wrong?

nhc complains
Context for Random.Random needed in left hand pattern at 17:11.
and hugs doesn't seem to know genRange exists. With it commented out it
returns the same as ghc.


Thanks
Ian


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell