Skip to content

Commit

Permalink
Test the hash function with random integers and the chi2 test
Browse files Browse the repository at this point in the history
  • Loading branch information
xavierleroy committed Dec 28, 2023
1 parent cf2f944 commit b9c9676
Show file tree
Hide file tree
Showing 2 changed files with 26 additions and 9 deletions.
2 changes: 1 addition & 1 deletion tests/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ test:: ofstring.exe

test:: chi2.exe
@echo "Testing random number generation..."
@./chi2.exe
@if ./chi2.exe; then echo "chi2: passed"; else echo "chi2: FAILED"; exit 2; fi

bench:: timings.exe
./timings.exe
Expand Down
33 changes: 25 additions & 8 deletions tests/chi2.ml
Original file line number Diff line number Diff line change
@@ -1,12 +1,11 @@
(* Accumulate [n] samples from function [f] and check the chi-square.
Only the low 8 bits of the result of [f] are sampled. *)
Assumes [f] returns integers in the [0..255] range. *)

let chisquare n f =
let r = 256 in
let freq = Array.make r 0 in
for i = 0 to n - 1 do
let t = Z.to_int (Z.logand (f ()) (Z.of_int 0xFF)) in
freq.(t) <- freq.(t) + 1
let t = f () in freq.(t) <- freq.(t) + 1
done;
let expected = float n /. float r in
let t =
Expand All @@ -22,9 +21,19 @@ let chisquare n f =
*)
chi2 <= degfree +. 4.0 *. sqrt (2.0 *. degfree)

let failed = ref false

let test_base name f =
if not (chisquare 100_000 f) then begin
Printf.printf "%s: suspicious result\n%!" name;
failed := true
end

let test name f =
if not (chisquare 100_000 f)
then Printf.printf "%s: suspicious result\n%!" name
(* Test the low 8 bits of the result of f *)
test_base name (fun () -> Z.to_int (Z.logand (f ()) (Z.of_int 0xFF)))

let p = Z.of_string "35742549198872617291353508656626642567"

let _ =
test "random_bits 15 (bits 0-7)"
Expand All @@ -38,6 +47,14 @@ let _ =
test "random_int 2^30 (bits 21-28)"
(fun () -> Z.(shift_right (random_int (shift_left one 30)) 21));
test "random_int (256 * p) / p"
(let p = Z.of_string "35742549198872617291353508656626642567" in
let bound = Z.shift_left p 8 in
fun () -> Z.(div (random_int bound) p))
(let bound = Z.shift_left p 8 in
fun () -> Z.(div (random_int bound) p));
(* Also test our hash function, why not? *)
test_base "hash (random_int p) (bits 0-7)"
(fun () -> Z.(hash (random_int p)) land 0xFF);
test_base "hash (random_int p) (bits 16-23)"
(fun () -> (Z.(hash (random_int p)) lsr 16) land 0xFF);
exit (if !failed then 2 else 0)



0 comments on commit b9c9676

Please sign in to comment.