[Haskell-cafe] System.Random

Ketil Malde ketil at ii.uib.no
Mon Apr 16 10:18:53 EDT 2007


Hi,

I've recently stumbled upon some issues with the System.Random module,
and thought I'd try to remedy them.  However, I'm not quite sure what an
optimal resolution is.

Problem 1 is that I often get the same "random" number on consecutive
program runs [1].  Looking at the code for initialization (called with
'0' argument on program start):

  mkStdRNG :: Integer -> IO StdGen
  mkStdRNG o = do
      ct          <- getCPUTime
      (TOD sec ms) <- getClockTime
      return (createStdGen (sec * 12345 + ms + ct + o))

Considering that 'getCPUTime' tends to return 0 early in the program,
and that we simply ignore the picosecond part of 'getClockTime', it's
fairly obvious why we get this result.  What is not obvious is the
rationale for discarding 'ms', or for that matter, the 12345
multiplication - can anybody shed some light on this?

Anyway, on my Linux system, I get (unsurprisingly considering the
defintion of time_t) picoseconds in even millions, and successive calls
to getClockTime are not successive enough to give the same result in my
cases.  A better implementation would perhaps use /dev/urandom, but that
is possibly not portable enough?

The second issue is reading the random state from a string [2]. I
realize (as Simon points out) that you can use 'reads' to get the
remainder of the string, but as many find it confusing (at least the OP
and I :-), I wonder what the rationale is behind this kind of interface?

And checking how the state is actually calculated:

  stdFromString         :: String -> (StdGen, String)
  stdFromString s        = (mkStdGen num, rest)
	where (cs, rest) = splitAt 6 s
              num        = foldl (\a x -> x + 3 * a) 1 (map ord cs)

So, it picks six chars, and folds them into an Int for mkStdGen.  Now,
this number (due to the low multiplier) never exceeds 93549.  Since we
have an Int of state, why not use the whole range?  Why not fold with a
multiplier of 256?

(All of this is trivial to fix of course, but I worry about changing
code I don't understand the rationale behind.)

One final question: are there build and install instructions for 'base'?
I got the code from darcs, but I haven't find a way to build it and
replace the bundled 'base' with a new version.

-k

References:

[1] http://hackage.haskell.org/trac/ghc/ticket/1272
[2] http://www.nabble.com/Re%
3A--Haskell-cafe--System.Random-StdGen-read-fails-on-some-strings--tf3394495.html#a9450043
[3]
http://web.archive.org/web/20011027002011/http://dilbert.com/comics/dilbert/archive/images/dilbert2001182781025.gif



More information about the Haskell-Cafe mailing list