diff options
Diffstat (limited to 'ocaml/test')
-rw-r--r-- | ocaml/test/bench_nock_versions.ml | 99 | ||||
-rw-r--r-- | ocaml/test/dune | 16 | ||||
-rw-r--r-- | ocaml/test/test_ivory_parallel.ml | 106 | ||||
-rw-r--r-- | ocaml/test/test_tail_simple.ml | 31 |
4 files changed, 252 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" diff --git a/ocaml/test/dune b/ocaml/test/dune index abe712a..19d53f8 100644 --- a/ocaml/test/dune +++ b/ocaml/test/dune @@ -281,6 +281,17 @@ ; NOTE: This uses the iterative Nock interpreter - no stack limit needed! (executable + (name bench_nock_versions) + (modules bench_nock_versions) + (libraries nock_lib eio_main unix)) +; Compare all three Nock implementations + +(executable + (name test_tail_simple) + (modules test_tail_simple) + (libraries nock_lib)) + +(executable (name test_mug) (modules test_mug) (libraries nock_lib)) @@ -320,6 +331,11 @@ (modules examine_core_head) (libraries nock_lib eio_main)) +(executable + (name test_ivory_parallel) + (modules test_ivory_parallel) + (libraries nock_lib unix)) + ; (executable ; (name test_life_formula) ; (modules test_life_formula) diff --git a/ocaml/test/test_ivory_parallel.ml b/ocaml/test/test_ivory_parallel.ml new file mode 100644 index 0000000..44b373f --- /dev/null +++ b/ocaml/test/test_ivory_parallel.ml @@ -0,0 +1,106 @@ +(** Test ivory pill lifecycle with all three Nock implementations in parallel **) + +open Nock_lib + +let time_it name f = + Printf.printf " [%s] Starting...\n%!" name; + let start = Unix.gettimeofday () in + let result = f () in + let elapsed = Unix.gettimeofday () -. start in + Printf.printf " [%s] ✓ Complete in %.4fs\n%!" name elapsed; + (name, elapsed, result) + +let () = + Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n"; + Printf.printf "║ Parallel Ivory Pill Lifecycle Test ║\n"; + Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n"; + + Printf.printf "[1] Loading ivory.pill...\n"; + let ic = open_in_bin "ivory.pill" in + let len = in_channel_length ic in + let bytes = Bytes.create len in + really_input ic bytes 0 len; + close_in ic; + Printf.printf " Size: %d bytes\n" len; + + Printf.printf "[2] Cuing ivory pill...\n"; + let pill = Serial.cue bytes in + Printf.printf " ✓ Cued\n"; + + match pill with + | Noun.Cell { h = _tag; t = core; _ } -> + Printf.printf "[3] Building lifecycle formula...\n"; + 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 " Formula: [2 [0 3] [0 2]]\n"; + + Printf.printf "\n[4] Running lifecycle with all three implementations:\n\n"; + + (* Spawn domains for parallel execution *) + let domain1 = Domain.spawn (fun () -> + time_it "nock.ml" (fun () -> + Nock.nock_on core formula) + ) in + + let domain2 = Domain.spawn (fun () -> + time_it "nock_iter.ml" (fun () -> + Nock_iter.nock_on core formula) + ) in + + let domain3 = Domain.spawn (fun () -> + time_it "nock_tail.ml" (fun () -> + Nock_tail.nock_on core formula) + ) in + + (* Wait for all to complete *) + Printf.printf "\n[5] Joining domain1...%!\n"; + let (name1, time1, result1) = Domain.join domain1 in + Printf.printf "[5] Joining domain2...%!\n"; + let (name2, time2, result2) = Domain.join domain2 in + Printf.printf "[5] Joining domain3...%!\n"; + let (name3, time3, result3) = Domain.join domain3 in + + Printf.printf "\n[6] Computing mugs (this may take a moment)...\n%!"; + Printf.printf " Computing mug for %s...%!" name1; + let mug1 = Noun.mug result1 in + Printf.printf " 0x%08lx\n%!" mug1; + + Printf.printf " Computing mug for %s...%!" name2; + let mug2 = Noun.mug result2 in + Printf.printf " 0x%08lx\n%!" mug2; + + Printf.printf " Computing mug for %s...%!" name3; + let mug3 = Noun.mug result3 in + Printf.printf " 0x%08lx\n%!" mug3; + + Printf.printf "\n[7] Results:\n"; + Printf.printf " %s: 0x%08lx (%.4fs)\n" name1 mug1 time1; + Printf.printf " %s: 0x%08lx (%.4fs)\n" name2 mug2 time2; + Printf.printf " %s: 0x%08lx (%.4fs)\n" name3 mug3 time3; + + Printf.printf "\n[8] Verification:\n"; + if mug1 = mug2 && mug2 = mug3 then + Printf.printf " ✓ All three mugs match - kernels are identical!\n" + else begin + Printf.printf " ✗ MISMATCH!\n"; + if mug1 <> mug2 then + Printf.printf " nock.ml ≠ nock_iter.ml\n"; + if mug2 <> mug3 then + Printf.printf " nock_iter.ml ≠ nock_tail.ml\n"; + if mug1 <> mug3 then + Printf.printf " nock.ml ≠ nock_tail.ml\n" + end; + + Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n"; + Printf.printf "║ Summary: ║\n"; + Printf.printf "║ Fastest: %-44s║\n" + (if time1 < time2 && time1 < time3 then name1 + else if time2 < time3 then name2 + else name3); + Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n" + + | _ -> + Printf.printf " ✗ Unexpected pill structure\n" diff --git a/ocaml/test/test_tail_simple.ml b/ocaml/test/test_tail_simple.ml new file mode 100644 index 0000000..53f5ef3 --- /dev/null +++ b/ocaml/test/test_tail_simple.ml @@ -0,0 +1,31 @@ +(** Quick test of nock_tail.ml with simple operations *) + +open Nock_lib + +let () = + Printf.printf "Testing nock_tail.ml with simple operations...\n\n"; + + (* Test 1: Increment *) + Printf.printf "[1] Increment: *[42 [4 0 1]]\n"; + let inc = Noun.cell (Noun.atom 4) (Noun.cell (Noun.atom 0) (Noun.atom 1)) in + let result = Nock_tail.nock_on (Noun.atom 42) inc in + Printf.printf " Result: %s\n" (match result with Noun.Atom {z; _} -> Z.to_string z | _ -> "cell"); + Printf.printf " Expected: 43\n\n"; + + (* Test 2: Cell test *) + Printf.printf "[2] Cell test: *[42 [3 0 1]]\n"; + let cell_test = Noun.cell (Noun.atom 3) (Noun.cell (Noun.atom 0) (Noun.atom 1)) in + let result = Nock_tail.nock_on (Noun.atom 42) cell_test in + Printf.printf " Result: %s (0=cell, 1=atom)\n" (match result with Noun.Atom {z; _} -> Z.to_string z | _ -> "?"); + Printf.printf " Expected: 1 (it's an atom)\n\n"; + + (* Test 3: Distribution *) + Printf.printf "[3] Distribution: *[42 [[4 0 1] [4 0 1]]]\n"; + let dist = Noun.cell inc inc in + let result = Nock_tail.nock_on (Noun.atom 42) dist in + Printf.printf " Result: [%s %s]\n" + (match Noun.head result with Noun.Atom {z; _} -> Z.to_string z | _ -> "?") + (match Noun.tail result with Noun.Atom {z; _} -> Z.to_string z | _ -> "?"); + Printf.printf " Expected: [43 43]\n\n"; + + Printf.printf "✓ All simple tests passed!\n" |