Confused about Random
Ian Lynagh
igloo@earth.li
Thu, 29 Nov 2001 15:32:27 +0000
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