summaryrefslogtreecommitdiffstats
path: root/stdlib/random.ml
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2012-03-23 09:58:22 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2012-03-23 09:58:22 +0000
commit90fde3e40e13e0fbcd90e72ca43f481278566d60 (patch)
tree83893da10ebdf6f2d896f4dc072dc4c5d3105a69 /stdlib/random.ml
parent875aab099eacef1e89fc6cce349138ca50b09cce (diff)
Updated documentation of Random.self_init and Random.float.
Faster implementation of Random.float: to get a 53-bit random mantissa, combining two calls to Random.bits is enough, three was overkill. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12262 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/random.ml')
-rw-r--r--stdlib/random.ml7
1 files changed, 3 insertions, 4 deletions
diff --git a/stdlib/random.ml b/stdlib/random.ml
index aa47536ba..50b570822 100644
--- a/stdlib/random.ml
+++ b/stdlib/random.ml
@@ -130,13 +130,12 @@ module State = struct
else fun s bound -> Int64.to_nativeint (int64 s (Int64.of_nativeint bound))
;;
- (* Returns a float 0 <= x < 1 with at most 90 bits of precision. *)
+ (* Returns a float 0 <= x <= 1 with at most 60 bits of precision. *)
let rawfloat s =
- let scale = 1073741824.0
- and r0 = Pervasives.float (bits s)
+ let scale = 1073741824.0 (* 2^30 *)
and r1 = Pervasives.float (bits s)
and r2 = Pervasives.float (bits s)
- in ((r0 /. scale +. r1) /. scale +. r2) /. scale
+ in (r1 /. scale +. r2) /. scale
;;
let float s bound = rawfloat s *. bound;;