Matt Harden wrote:
> 
> ...  Darn.  Now I want the genRange operation again.  The
> "clarification" can really be a significant performance cost.  Not to
> mention, you're also shortening the period of the RNG (perhaps by a
> factor of 4!).
> 
> Can we have both (see below)?
> 
> > class RandomGen g where
> >    next :: g -> (Int, g)
> >    split :: g -> (g, g)
> >    genRange :: g -> (Int, Int)
> >    genRange _ = (minBound, maxBound)
> 
> Put the "clarification" in, but then allow the implementer to optionally
> provide a different range?  If a genRange is provided, it should fit the
> requirements described earlier, of course.  And as someone suggested,
> (genRange _|_) should always be defined (not _|_).
> 
> Regards,
> Matt Harden

Simon, do you think we could have the *optional* genRange described
above?  If that approach is chosen, then the changes to GHC and Hugs
are rather painless.  In fact, below I've attached a patch based on
Hugs98-Sept1999 (a context diff).  After this patch, my tests that
failed before now pass with flying colors.  I do need to put some
comments in though.  By the way, I think it's clear that much of the
code in Random.hs could be made more efficient.  I went for the
simplest possible change in this case, however.


*** Random.hs.orig      Fri Oct 15 21:50:13 1999
--- Random.hs   Fri Feb  4 22:57:39 2000
***************
*** 28,33 ****
--- 28,35 ----
  class RandomGen g where
     next  :: g -> (Int, g)
     split :: g -> (g, g)
+    genRange :: g -> (Int, Int)
+    genRange = const (minBound, maxBound)


  -- An efficient and portable combined random number generator: ---------------
***************
*** 84,94 ****
--- 86,100 ----

                          StdGen t1 t2 = snd (next std)

+ stdRange            :: StdGen -> (Int, Int)
+ stdRange             = const (1, 2147483562)
+
  -- A standard instance of RandomGen: -----------------------------------------

  instance RandomGen StdGen where
    next  = stdNext
    split = stdSplit
+   genRange = stdRange

  instance Show StdGen where
    showsPrec p (StdGen s1 s2)
***************
*** 167,182 ****
  randomIvalInteger :: (RandomGen g, Num a) => (Integer, Integer) -> g -> (a, g)
  randomIvalInteger (l,h) rng
   | l > h     = randomIvalInteger (h,l) rng
!  | otherwise = case (f n 1 rng) of
!                  (v, rng') -> (fromInteger (l + v `mod` k), rng')
     where
       k = h - l + 1
!      b = 2147483561
       n = iLogBase b k

       f 0 acc g = (acc, g)
       f n acc g = let (x,g') = next g
!                in f (n-1) (fromInt x + acc * b) g'

  randomIvalDouble :: (RandomGen g, Fractional a)
                        => (Double, Double) -> (Double -> a) -> g -> (a, g)
--- 173,190 ----
  randomIvalInteger :: (RandomGen g, Num a) => (Integer, Integer) -> g -> (a, g)
  randomIvalInteger (l,h) rng
   | l > h     = randomIvalInteger (h,l) rng
!  | otherwise = case (f n 0 rng) of
!                  (v, rng') | v < (b^n `mod` k) -> randomIvalInteger (l,h) rng'
!                            | otherwise         -> (fromInteger (l + v `mod` k), rng')
     where
       k = h - l + 1
!      (c,d) = genRange rng
!      b = (toInteger d) - (toInteger c) + 1
       n = iLogBase b k

       f 0 acc g = (acc, g)
       f n acc g = let (x,g') = next g
!                in f (n-1) ((fromInt x - fromInt c) + acc * b) g'

  randomIvalDouble :: (RandomGen g, Fractional a)
                        => (Double, Double) -> (Double -> a) -> g -> (a, g)
***************
*** 197,203 ****
  intRange  = toInteger (maxBound::Int) - toInteger (minBound::Int)

  iLogBase :: Integer -> Integer -> Integer
! iLogBase b i = if i < b then 1 else 1 + iLogBase b (i `div` b)


  -- The global standard random number generator: ------------------------------
--- 205,212 ----
  intRange  = toInteger (maxBound::Int) - toInteger (minBound::Int)

  iLogBase :: Integer -> Integer -> Integer
! iLogBase b 1 = 0
! iLogBase b i | i>1 = 1 + iLogBase b ((i-1) `div` b + 1)


  -- The global standard random number generator: ------------------------------

Reply via email to