123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330(**************************************************************************)(* *)(* OCaml *)(* *)(* Damien Doligez, projet Para, INRIA Rocquencourt *)(* *)(* Copyright 1996 Institut National de Recherche en Informatique et *)(* en Automatique. *)(* *)(* All rights reserved. This file is distributed under the terms of *)(* the GNU Lesser General Public License version 2.1, with the *)(* special exception on linking described in the file LICENSE. *)(* *)(**************************************************************************)(* Pseudo-random number generator
This is a lagged-Fibonacci F(55, 24, +) with a modified addition
function to enhance the mixing of bits.
If we use normal addition, the low-order bit fails tests 1 and 7
of the Diehard test suite, and bits 1 and 2 also fail test 7.
If we use multiplication as suggested by Marsaglia, it doesn't fare
much better.
By mixing the bits of one of the numbers before addition (XOR the
5 high-order bits into the low-order bits), we get a generator that
passes all the Diehard tests.
*)externalrandom_seed:unit->intarray="caml_sys_random_seed"moduleState=structtypet={st:intarray;mutableidx:int}letnew_state()={st=Array.make550;idx=0}letassignst1st2=Array.blitst2.st0st1.st055;st1.idx<-st2.idxletfull_initsseed=letcombineaccux=Digest.string(accu^Int.to_stringx)inletextractd=Char.coded.[0]+(Char.coded.[1]lsl8)+(Char.coded.[2]lsl16)+(Char.coded.[3]lsl24)inletseed=ifArray.lengthseed=0then[|0|]elseseedinletl=Array.lengthseedinfori=0to54dos.st.(i)<-i;done;letaccu=ref"x"infori=0to54+Int.max55ldoletj=imod55inletk=imodlinaccu:=combine!accuseed.(k);s.st.(j)<-(s.st.(j)lxorextract!accu)land0x3FFFFFFF;(* PR#5575 *)done;s.idx<-0letmakeseed=letresult=new_state()infull_initresultseed;resultletmake_self_init()=make(random_seed())letcopys=letresult=new_state()inassignresults;result(* Returns 30 random bits as an integer 0 <= x < 1073741824 *)letbitss=s.idx<-(s.idx+1)mod55;letcurval=s.st.(s.idx)inletnewval=s.st.((s.idx+24)mod55)+(curvallxor((curvallsr25)land0x1F))inletnewval30=newvalland0x3FFFFFFFin(* PR#5575 *)s.st.(s.idx)<-newval30;newval30letrecintauxsn=letr=bitssinletv=rmodninifr-v>0x3FFFFFFF-n+1thenintauxsnelsevletintsbound=ifbound>0x3FFFFFFF||bound<=0theninvalid_arg"Random.int"elseintauxsboundletrecint63auxsn=letmax_int_32=(1lsl30)+0x3FFFFFFFin(* 0x7FFFFFFF *)letb1=bitssinletb2=bitssinlet(r,max_int)=ifn<=max_int_32then(* 31 random bits on both 64-bit OCaml and JavaScript.
Use upper 15 bits of b1 and 16 bits of b2. *)letbpos=(((b2land0x3FFFC000)lsl1)lor(b1lsr15))in(bpos,max_int_32)elseletb3=bitssin(* 62 random bits on 64-bit OCaml; unreachable on JavaScript.
Use upper 20 bits of b1 and 21 bits of b2 and b3. *)letbpos=((((b3land0x3FFFFE00)lsl12)lor(b2lsr9))lsl20)lor(b1lsr10)in(bpos,max_int)inletv=rmodninifr-v>max_int-n+1thenint63auxsnelsevletfull_intsbound=ifbound<=0theninvalid_arg"Random.full_int"elseifbound>0x3FFFFFFFthenint63auxsboundelseintauxsboundletrecint32auxsn=letb1=Int32.of_int(bitss)inletb2=Int32.shift_left(Int32.of_int(bitssland1))30inletr=Int32.logorb1b2inletv=Int32.remrninifInt32.subrv>Int32.add(Int32.subInt32.max_intn)1lthenint32auxsnelsevletint32sbound=ifbound<=0ltheninvalid_arg"Random.int32"elseint32auxsboundletrecint64auxsn=letb1=Int64.of_int(bitss)inletb2=Int64.shift_left(Int64.of_int(bitss))30inletb3=Int64.shift_left(Int64.of_int(bitssland7))60inletr=Int64.logorb1(Int64.logorb2b3)inletv=Int64.remrninifInt64.subrv>Int64.add(Int64.subInt64.max_intn)1Lthenint64auxsnelsevletint64sbound=ifbound<=0Ltheninvalid_arg"Random.int64"elseint64auxsboundletnativeint=ifNativeint.size=32thenfunsbound->Nativeint.of_int32(int32s(Nativeint.to_int32bound))elsefunsbound->Int64.to_nativeint(int64s(Int64.of_nativeintbound))(* Returns a float 0 <= x <= 1 with at most 60 bits of precision. *)letrawfloats=letscale=1073741824.0(* 2^30 *)andr1=Stdlib.float(bitss)andr2=Stdlib.float(bitss)in(r1/.scale+.r2)/.scaleletfloatsbound=rawfloats*.boundletbools=(bitssland1=0)letbits32s=letb1=Int32.(shift_right_logical(of_int(bitss))14)in(* 16 bits *)letb2=Int32.(shift_right_logical(of_int(bitss))14)in(* 16 bits *)Int32.(logorb1(shift_leftb216))letbits64s=letb1=Int64.(shift_right_logical(of_int(bitss))9)in(* 21 bits *)letb2=Int64.(shift_right_logical(of_int(bitss))9)in(* 21 bits *)letb3=Int64.(shift_right_logical(of_int(bitss))8)in(* 22 bits *)Int64.(logorb1(logor(shift_leftb221)(shift_leftb342)))letnativebits=ifNativeint.size=32thenfuns->Nativeint.of_int32(bits32s)elsefuns->Int64.to_nativeint(bits64s)end(* This is the state you get with [init 27182818] and then applying
the "land 0x3FFFFFFF" filter to them. See #5575, #5793, #5977. *)letdefault={State.st=[|0x3ae2522b;0x1d8d4634;0x15b4fad0;0x18b14ace;0x12f8a3c4;0x3b086c47;0x16d467d6;0x101d91c7;0x321df177;0x0176c193;0x1ff72bf1;0x1e889109;0x0b464b18;0x2b86b97c;0x0891da48;0x03137463;0x085ac5a1;0x15d61f2f;0x3bced359;0x29c1c132;0x3a86766e;0x366d8c86;0x1f5b6222;0x3ce1b59f;0x2ebf78e1;0x27cd1b86;0x258f3dc3;0x389a8194;0x02e4c44c;0x18c43f7d;0x0f6e534f;0x1e7df359;0x055d0b7e;0x10e84e7e;0x126198e4;0x0e7722cb;0x1cbede28;0x3391b964;0x3d40e92a;0x0c59933d;0x0b8cd0b7;0x24efff1c;0x2803fdaa;0x08ebc72e;0x0f522e32;0x05398edc;0x2144a04c;0x0aef3cbd;0x01ad4719;0x35b93cd6;0x2a559d4f;0x1e6fd768;0x26e27f36;0x186f18c3;0x2fbf967a;|];State.idx=0;}letbits()=State.bitsdefaultletintbound=State.intdefaultboundletfull_intbound=State.full_intdefaultboundletint32bound=State.int32defaultboundletnativeintbound=State.nativeintdefaultboundletint64bound=State.int64defaultboundletfloatscale=State.floatdefaultscaleletbool()=State.booldefaultletbits32()=State.bits32defaultletbits64()=State.bits64defaultletnativebits()=State.nativebitsdefaultletfull_initseed=State.full_initdefaultseedletinitseed=State.full_initdefault[|seed|]letself_init()=full_init(random_seed())(* Manipulating the current state. *)letget_state()=State.copydefaultletset_states=State.assigndefaults(********************
(* Test functions. Not included in the library.
The [chisquare] function should be called with n > 10r.
It returns a triple (low, actual, high).
If low <= actual <= high, the [g] function passed the test,
otherwise it failed.
Some results:
init 27182818; chisquare int 100000 1000
init 27182818; chisquare int 100000 100
init 27182818; chisquare int 100000 5000
init 27182818; chisquare int 1000000 1000
init 27182818; chisquare int 100000 1024
init 299792643; chisquare int 100000 1024
init 14142136; chisquare int 100000 1024
init 27182818; init_diff 1024; chisquare diff 100000 1024
init 27182818; init_diff 100; chisquare diff 100000 100
init 27182818; init_diff2 1024; chisquare diff2 100000 1024
init 27182818; init_diff2 100; chisquare diff2 100000 100
init 14142136; init_diff2 100; chisquare diff2 100000 100
init 299792643; init_diff2 100; chisquare diff2 100000 100
- : float * float * float = (936.754446796632465, 997.5, 1063.24555320336754)
# - : float * float * float = (80., 89.7400000000052387, 120.)
# - : float * float * float = (4858.57864376269, 5045.5, 5141.42135623731)
# - : float * float * float =
(936.754446796632465, 944.805999999982305, 1063.24555320336754)
# - : float * float * float = (960., 1019.19744000000355, 1088.)
# - : float * float * float = (960., 1059.31776000000536, 1088.)
# - : float * float * float = (960., 1039.98463999999512, 1088.)
# - : float * float * float = (960., 1054.38207999999577, 1088.)
# - : float * float * float = (80., 90.096000000005, 120.)
# - : float * float * float = (960., 1076.78720000000612, 1088.)
# - : float * float * float = (80., 85.1760000000067521, 120.)
# - : float * float * float = (80., 85.2160000000003492, 120.)
# - : float * float * float = (80., 80.6220000000030268, 120.)
*)
(* Return the sum of the squares of v[i0,i1[ *)
let rec sumsq v i0 i1 =
if i0 >= i1 then 0.0
else if i1 = i0 + 1 then Stdlib.float v.(i0) *. Stdlib.float v.(i0)
else sumsq v i0 ((i0+i1)/2) +. sumsq v ((i0+i1)/2) i1
let chisquare g n r =
if n <= 10 * r then invalid_arg "chisquare";
let f = Array.make r 0 in
for i = 1 to n do
let t = g r in
f.(t) <- f.(t) + 1
done;
let t = sumsq f 0 r
and r = Stdlib.float r
and n = Stdlib.float n in
let sr = 2.0 *. sqrt r in
(r -. sr, (r *. t /. n) -. n, r +. sr)
(* This is to test for linear dependencies between successive random numbers.
*)
let st = ref 0
let init_diff r = st := int r
let diff r =
let x1 = !st
and x2 = int r
in
st := x2;
if x1 >= x2 then
x1 - x2
else
r + x1 - x2
let st1 = ref 0
and st2 = ref 0
(* This is to test for quadratic dependencies between successive random
numbers.
*)
let init_diff2 r = st1 := int r; st2 := int r
let diff2 r =
let x1 = !st1
and x2 = !st2
and x3 = int r
in
st1 := x2;
st2 := x3;
(x3 - x2 - x2 + x1 + 2*r) mod r
********************)