[Haskell] trouble with the random number generator

Garrett Mitchener garrett.mitchener at gmail.com
Thu Apr 8 10:20:25 EDT 2010


Hi, I'm having some trouble with the standard random number generator.  I
re-implemented it for speed, but the same problem seems to be present in the
original.  The problem I'm having is in the generation of a random Double.
 If you go down to the function randomIvalDouble in Random.hs (and I'm
looking at the one from http://darcs.haskell.org/packages/random), here's
where something is going wrong:

       case (randomIvalInteger (toInteger (minBound::Int32), toInteger
(maxBound::Int32)) rng) of
         (x, rng') ->
    let
     scaled_x =
 fromDouble ((l+h)/2) +
                fromDouble ((h-l) / realToFrac int32Range) *
fromIntegral (x::Int32)
    in
    (scaled_x, rng')

...
int32Range = toInteger (maxBound::Int32) - toInteger (minBound::Int32)

I use essentially the same calculation in my implementation with l = 0 and h
= 1, that is, I want to generate a random Double in the interval [0,1].
 int32Range comes out to be 2^32-1.  But if the pseudo-random integer x
happens to be minBound, which is -2^31, then the scaled_x comes out

1/2 - 2^31/(2^32-1)  = 2^31( 1/2^32 - 1/(2^32-1) ) = -1.164e-10 < 0

which is outside the required range.  One of my simulations, which has been
running for weeks, actually hit this, and I'd like to know if I'm just
missing something or if this is a real bug.  It breaks my simulation because
it triggers an attempt to access element -1 of an array whose minimum index
is 0, by the way.

My trouble at this point is that I'd really like for my simulation results
to be completely reproduceable, and I'm going to be unhappy if I have to
re-implement the random generation and change it so that I have to throw out
all the results I have so far.  I'm also going to be unhappy if I have to
insert some check that slows everything down...

At any rate, if I'm right, this bug affects GHC and Hugs.  But this code has
surely been around long enough that someone would have found this already?
 But there's not a bug in hackage's trac system.

Help!

-- Garrett Mitchener
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell/attachments/20100408/cb9793a8/attachment.html


More information about the Haskell mailing list