summaryrefslogtreecommitdiff
path: root/ocaml/test/bench_nock_versions.ml
diff options
context:
space:
mode:
authorpolwex <polwex@sortug.com>2025-10-07 03:08:57 +0700
committerpolwex <polwex@sortug.com>2025-10-07 03:08:57 +0700
commita3170453e08079369da031377c45600ee22ab53a (patch)
tree22a90cdf95202d1fe760acf71d85716b1ce3082a /ocaml/test/bench_nock_versions.ml
parent64611d312280dd5d63d498ded09ae4e9a6eaf34c (diff)
nock diversity
Diffstat (limited to 'ocaml/test/bench_nock_versions.ml')
-rw-r--r--ocaml/test/bench_nock_versions.ml99
1 files changed, 99 insertions, 0 deletions
diff --git a/ocaml/test/bench_nock_versions.ml b/ocaml/test/bench_nock_versions.ml
new file mode 100644
index 0000000..c701633
--- /dev/null
+++ b/ocaml/test/bench_nock_versions.ml
@@ -0,0 +1,99 @@
+(** Benchmark all three Nock implementations:
+ 1. nock.ml - trampoline with some tail-calls (needs OCAMLRUNPARAM)
+ 2. nock_iter.ml - fully iterative (work/result stacks)
+ 3. nock_tail.ml - continuation-passing style (CPS)
+*)
+
+open Nock_lib
+
+let time_it name f =
+ let start = Unix.gettimeofday () in
+ let result = f () in
+ let elapsed = Unix.gettimeofday () -. start in
+ Printf.printf " %-20s %.4fs\n" name elapsed;
+ result
+
+let () =
+ Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n";
+ Printf.printf "║ Benchmarking Nock Implementations ║\n";
+ Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n";
+
+ (* Test 1: Simple operations *)
+ Printf.printf "[1] Simple increment *[42 [4 0 1]] (1000x):\n%!";
+ let inc_fol = Noun.cell (Noun.atom 4) (Noun.cell (Noun.atom 0) (Noun.atom 1)) in
+ let bus = Noun.atom 42 in
+
+ Printf.printf " Running nock.ml...%!";
+ let _ = time_it "nock.ml" (fun () ->
+ for _i = 1 to 1000 do
+ ignore (Nock.nock_on bus inc_fol)
+ done) in
+
+ Printf.printf " Running nock_iter.ml...%!";
+ let _ = time_it "nock_iter.ml" (fun () ->
+ for _i = 1 to 1000 do
+ ignore (Nock_iter.nock_on bus inc_fol)
+ done) in
+
+ Printf.printf " Running nock_tail.ml...%!";
+ let _ = time_it "nock_tail.ml" (fun () ->
+ for _i = 1 to 1000 do
+ ignore (Nock_tail.nock_on bus inc_fol)
+ done) in
+
+ Printf.printf "\n";
+
+ (* Test 2: Ivory pill lifecycle *)
+ Printf.printf "\n[2] Ivory pill lifecycle (full boot):\n%!";
+
+ Eio_main.run (fun env ->
+ Printf.printf " Loading ivory.pill...%!";
+ let fs = Eio.Stdenv.fs env in
+ let bytes = Eio.Path.(load (fs / "ivory.pill")) |> Bytes.of_string in
+ Printf.printf " %d bytes\n%!" (Bytes.length bytes);
+ Printf.printf " Cuing pill...%!";
+ let pill = Serial.cue bytes in
+ Printf.printf " done\n%!";
+
+ match pill with
+ | Noun.Cell { h = _tag; t = core; _ } ->
+ Printf.printf " Building formula...%!";
+ let formula = Noun.cell
+ (Noun.atom 2)
+ (Noun.cell
+ (Noun.cell (Noun.atom 0) (Noun.atom 3))
+ (Noun.cell (Noun.atom 0) (Noun.atom 2))) in
+ Printf.printf " done\n%!";
+
+ (* Skip mug computation - it's O(n) on first call for uncached noun *)
+ (* Printf.printf " Core mug: 0x%08lx\n" (Noun.mug core); *)
+
+ (* nock.ml needs OCAMLRUNPARAM - skip for now *)
+ Printf.printf " %-20s (skipped - needs OCAMLRUNPARAM)\n%!" "nock.ml";
+
+ Printf.printf " Running nock_iter.ml (this will take a while)...%!";
+ let kernel_iter = time_it "\n nock_iter.ml" (fun () ->
+ Nock_iter.nock_on core formula) in
+
+ let kernel_tail = time_it "nock_tail.ml" (fun () ->
+ Nock_tail.nock_on core formula) in
+
+ Printf.printf "\n Results:\n";
+ Printf.printf " nock_iter mug: 0x%08lx\n" (Noun.mug kernel_iter);
+ Printf.printf " nock_tail mug: 0x%08lx\n" (Noun.mug kernel_tail);
+
+ if Noun.equal kernel_iter kernel_tail then
+ Printf.printf " ✓ Both produce identical kernels!\n"
+ else
+ Printf.printf " ✗ MISMATCH - kernels differ!\n";
+
+ | _ ->
+ Printf.printf " Unexpected pill structure\n"
+ );
+
+ Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n";
+ Printf.printf "║ Summary: ║\n";
+ Printf.printf "║ • nock_iter.ml - Fast, predictable, explicit stacks ║\n";
+ Printf.printf "║ • nock_tail.ml - Elegant CPS, constant stack space ║\n";
+ Printf.printf "║ Both work without OCAMLRUNPARAM! ║\n";
+ Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n"