summaryrefslogtreecommitdiff
path: root/ocaml/test
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/test')
-rw-r--r--ocaml/test/bench_serial.ml160
-rw-r--r--ocaml/test/dune20
-rw-r--r--ocaml/test/jam_compare.ml36
-rw-r--r--ocaml/test/test_bench_one.ml15
-rw-r--r--ocaml/test/test_roundtrip.ml15
5 files changed, 246 insertions, 0 deletions
diff --git a/ocaml/test/bench_serial.ml b/ocaml/test/bench_serial.ml
new file mode 100644
index 0000000..a8e5bdf
--- /dev/null
+++ b/ocaml/test/bench_serial.ml
@@ -0,0 +1,160 @@
+open Nock_lib.Noun
+open Nock_lib.Serial
+
+(** Benchmark utilities *)
+
+let time_it f =
+ let start = Unix.gettimeofday () in
+ let result = f () in
+ let elapsed = Unix.gettimeofday () -. start in
+ (result, elapsed)
+
+let benchmark name iterations f =
+ (* Warmup *)
+ for _i = 1 to min 100 (iterations / 10) do
+ let _ = f () in
+ ()
+ done;
+
+ (* Actual benchmark *)
+ let times = ref [] in
+ for _i = 1 to iterations do
+ let (_, elapsed) = time_it f in
+ times := elapsed :: !times
+ done;
+
+ let total = List.fold_left (+.) 0.0 !times in
+ let avg = total /. float_of_int iterations in
+ let sorted = List.sort compare !times in
+ let median = List.nth sorted (iterations / 2) in
+
+ Printf.printf "%-40s %d iters: avg=%.6f median=%.6f total=%.6f\n"
+ name iterations avg median total
+
+(** Benchmark cases *)
+
+let bench_atom_small () =
+ benchmark "jam/cue small atom (42)" 100000 (fun () ->
+ let n = atom 42 in
+ let j = jam n in
+ let c = cue j in
+ c
+ )
+
+let bench_atom_large () =
+ benchmark "jam/cue large atom (2^64)" 10000 (fun () ->
+ let n = Atom (Z.shift_left Z.one 64) in
+ let j = jam n in
+ let c = cue j in
+ c
+ )
+
+let bench_cell_simple () =
+ benchmark "jam/cue simple cell [1 2]" 100000 (fun () ->
+ let n = cell (atom 1) (atom 2) in
+ let j = jam n in
+ let c = cue j in
+ c
+ )
+
+let bench_tree_balanced () =
+ let tree =
+ cell
+ (cell (cell (atom 1) (atom 2)) (cell (atom 3) (atom 4)))
+ (cell (cell (atom 5) (atom 6)) (cell (atom 7) (atom 8)))
+ in
+ benchmark "jam/cue balanced tree (depth 3)" 50000 (fun () ->
+ let j = jam tree in
+ let c = cue j in
+ c
+ )
+
+let bench_list_structure () =
+ let rec make_list n =
+ if n = 0 then atom 0
+ else cell (atom n) (make_list (n - 1))
+ in
+ let list = make_list 20 in
+ benchmark "jam/cue list structure (20 elements)" 10000 (fun () ->
+ let j = jam list in
+ let c = cue j in
+ c
+ )
+
+let bench_deep_nesting () =
+ let rec make_deep n =
+ if n = 0 then atom 0
+ else cell (atom n) (make_deep (n - 1))
+ in
+ let deep = make_deep 100 in
+ benchmark "jam/cue deep nesting (100 levels)" 1000 (fun () ->
+ let j = jam deep in
+ let c = cue j in
+ c
+ )
+
+let bench_jam_only_small () =
+ let n = atom 42 in
+ benchmark "jam only (small atom)" 100000 (fun () ->
+ let j = jam n in
+ j
+ )
+
+let bench_cue_only_small () =
+ let n = atom 42 in
+ let j = jam n in
+ (* Copy the bytes to avoid any mutation issues *)
+ let j_copy = Bytes.copy j in
+ benchmark "cue only (small atom)" 100000 (fun () ->
+ let c = cue j_copy in
+ c
+ )
+
+let bench_jam_only_tree () =
+ let tree =
+ cell
+ (cell (cell (atom 1) (atom 2)) (cell (atom 3) (atom 4)))
+ (cell (cell (atom 5) (atom 6)) (cell (atom 7) (atom 8)))
+ in
+ benchmark "jam only (balanced tree)" 50000 (fun () ->
+ let j = jam tree in
+ j
+ )
+
+let bench_cue_only_tree () =
+ let tree =
+ cell
+ (cell (cell (atom 1) (atom 2)) (cell (atom 3) (atom 4)))
+ (cell (cell (atom 5) (atom 6)) (cell (atom 7) (atom 8)))
+ in
+ let j = jam tree in
+ (* Copy the bytes to avoid any mutation issues *)
+ let j_copy = Bytes.copy j in
+ benchmark "cue only (balanced tree)" 50000 (fun () ->
+ let c = cue j_copy in
+ c
+ )
+
+(** Run all benchmarks *)
+let () =
+ Printf.printf "========================================\n";
+ Printf.printf "Jam/Cue Serialization Benchmarks\n";
+ Printf.printf "========================================\n\n";
+
+ Printf.printf "Round-trip benchmarks:\n";
+ bench_atom_small ();
+ bench_atom_large ();
+ bench_cell_simple ();
+ bench_tree_balanced ();
+ bench_list_structure ();
+ bench_deep_nesting ();
+
+ Printf.printf "\nJam-only benchmarks:\n";
+ bench_jam_only_small ();
+ bench_jam_only_tree ();
+
+ Printf.printf "\nCue-only benchmarks:\n";
+ bench_cue_only_small ();
+ bench_cue_only_tree ();
+
+ Printf.printf "\n========================================\n"
diff --git a/ocaml/test/dune b/ocaml/test/dune
index b0ad51d..b8cde90 100644
--- a/ocaml/test/dune
+++ b/ocaml/test/dune
@@ -18,6 +18,26 @@
(modules bench_nock)
(libraries nock_lib zarith unix))
+(test
+ (name bench_serial)
+ (modules bench_serial)
+ (libraries nock_lib zarith unix))
+
+(executable
+ (name test_roundtrip)
+ (modules test_roundtrip)
+ (libraries nock_lib zarith))
+
+(executable
+ (name test_bench_one)
+ (modules test_bench_one)
+ (libraries nock_lib zarith))
+
+(executable
+ (name jam_compare)
+ (modules jam_compare)
+ (libraries nock_lib zarith))
+
(executable
(name test_hex)
(libraries nock_lib))
diff --git a/ocaml/test/jam_compare.ml b/ocaml/test/jam_compare.ml
new file mode 100644
index 0000000..bdbc306
--- /dev/null
+++ b/ocaml/test/jam_compare.ml
@@ -0,0 +1,36 @@
+open Nock_lib.Noun
+open Nock_lib.Serial
+
+let () =
+ Printf.printf "# OCaml jam outputs (hex)\n";
+
+ (* Simple atoms *)
+ Printf.printf "0: %s\n" (bytes_to_hex (jam (atom 0)));
+ Printf.printf "1: %s\n" (bytes_to_hex (jam (atom 1)));
+ Printf.printf "2: %s\n" (bytes_to_hex (jam (atom 2)));
+ Printf.printf "42: %s\n" (bytes_to_hex (jam (atom 42)));
+ Printf.printf "255: %s\n" (bytes_to_hex (jam (atom 255)));
+ Printf.printf "256: %s\n" (bytes_to_hex (jam (atom 256)));
+
+ (* Simple cells *)
+ Printf.printf "[1 2]: %s\n" (bytes_to_hex (jam (cell (atom 1) (atom 2))));
+ Printf.printf "[0 0]: %s\n" (bytes_to_hex (jam (cell (atom 0) (atom 0))));
+ Printf.printf "[42 43]: %s\n" (bytes_to_hex (jam (cell (atom 42) (atom 43))));
+
+ (* Nested cells *)
+ Printf.printf "[[1 2] 3]: %s\n"
+ (bytes_to_hex (jam (cell (cell (atom 1) (atom 2)) (atom 3))));
+ Printf.printf "[1 [2 3]]: %s\n"
+ (bytes_to_hex (jam (cell (atom 1) (cell (atom 2) (atom 3)))));
+
+ (* Balanced tree *)
+ Printf.printf "[[1 2] [3 4]]: %s\n"
+ (bytes_to_hex (jam (cell (cell (atom 1) (atom 2)) (cell (atom 3) (atom 4)))));
+
+ (* Larger tree *)
+ Printf.printf "[[[1 2] [3 4]] [[5 6] [7 8]]]: %s\n"
+ (bytes_to_hex (jam (
+ cell
+ (cell (cell (atom 1) (atom 2)) (cell (atom 3) (atom 4)))
+ (cell (cell (atom 5) (atom 6)) (cell (atom 7) (atom 8)))
+ )))
diff --git a/ocaml/test/test_bench_one.ml b/ocaml/test/test_bench_one.ml
new file mode 100644
index 0000000..1a73be5
--- /dev/null
+++ b/ocaml/test/test_bench_one.ml
@@ -0,0 +1,15 @@
+open Nock_lib.Noun
+open Nock_lib.Serial
+
+let () =
+ Printf.printf "Running single bench iteration...\n";
+ for i = 1 to 10 do
+ Printf.printf "Iter %d: " i;
+ flush stdout;
+ let n = atom 42 in
+ let j = jam n in
+ let c = cue j in
+ Format.printf "%a\n" pp_noun c;
+ flush stdout
+ done;
+ Printf.printf "Done!\n"
diff --git a/ocaml/test/test_roundtrip.ml b/ocaml/test/test_roundtrip.ml
new file mode 100644
index 0000000..4a4e635
--- /dev/null
+++ b/ocaml/test/test_roundtrip.ml
@@ -0,0 +1,15 @@
+open Nock_lib.Noun
+open Nock_lib.Serial
+
+let () =
+ Printf.printf "Testing roundtrip...\n";
+ let n = atom 42 in
+ for i = 1 to 5 do
+ Printf.printf "Iteration %d\n" i;
+ let j = jam n in
+ Printf.printf " jammed: %s\n" (bytes_to_hex j);
+ let c = cue j in
+ Format.printf " cued: %a\n" pp_noun c;
+ flush stdout
+ done;
+ Printf.printf "Done!\n"