summaryrefslogtreecommitdiffstats
path: root/stdlib/random.ml
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/random.ml')
-rw-r--r--stdlib/random.ml4
1 files changed, 2 insertions, 2 deletions
diff --git a/stdlib/random.ml b/stdlib/random.ml
index 2da5e98f0..2c2f2408f 100644
--- a/stdlib/random.ml
+++ b/stdlib/random.ml
@@ -42,9 +42,9 @@ let default = {
(* Returns 30 random bits as an integer 0 <= x < 1073741824 *)
let s_bits s =
s.idx <- (s.idx + 1) mod 55;
- let newval = s.st.((s.idx + 24) mod 55) + s.st.(s.idx) in
+ let newval = (s.st.((s.idx + 24) mod 55) + s.st.(s.idx)) land 0x3FFFFFFF in
s.st.(s.idx) <- newval;
- newval land 0x3FFFFFFF
+ newval
;;
(* Returns a float 0 <= x < 1 with at most 90 bits of precision. *)