summaryrefslogtreecommitdiff
path: root/ocaml/test/test_parallel_clean.ml
diff options
context:
space:
mode:
authorpolwex <polwex@sortug.com>2025-10-07 04:00:15 +0700
committerpolwex <polwex@sortug.com>2025-10-07 04:00:15 +0700
commit2a4975c12ec3436a35f907526c121f977d0b5048 (patch)
tree67479cde27b4478d8b85f3b4ed48b62828fb18e5 /ocaml/test/test_parallel_clean.ml
parenta93db7a168a30d1bace8f7a95ac1c6206125a212 (diff)
parallelism kinda done, need speedupsfresh-claude
Diffstat (limited to 'ocaml/test/test_parallel_clean.ml')
-rw-r--r--ocaml/test/test_parallel_clean.ml98
1 files changed, 98 insertions, 0 deletions
diff --git a/ocaml/test/test_parallel_clean.ml b/ocaml/test/test_parallel_clean.ml
new file mode 100644
index 0000000..b4f3f9e
--- /dev/null
+++ b/ocaml/test/test_parallel_clean.ml
@@ -0,0 +1,98 @@
+(** Clean parallel test using the Nock_parallel abstraction **)
+
+open Nock_lib
+
+let () =
+ Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n";
+ Printf.printf "║ Parallel Nock Test (using Nock_parallel) ║\n";
+ Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n";
+
+ (* Create domain pool with all cores *)
+ let num_domains = 32 in
+ let pool = Domain_pool.create ~num_domains () in
+ let stats = Domain_pool.stats pool in
+ Printf.printf "[*] Pool created with %d domains (%d cores available)\n\n"
+ stats.num_domains stats.available_cores;
+
+ 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";
+
+ (* Create 1000 identical computations *)
+ let num_computations = 1000 in
+ let computations = List.init num_computations (fun _ -> (core, formula)) in
+
+ Printf.printf "\n[4] Running %d parallel lifecycle computations...\n" num_computations;
+ let start = Unix.gettimeofday () in
+
+ let results = Nock_parallel.parallel_batch pool computations in
+
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf " ✓ Completed in %.2fs\n" elapsed;
+
+ (* Check results *)
+ let successes = List.filter (function
+ | Nock_parallel.Success _ -> true
+ | _ -> false
+ ) results in
+
+ let errors = List.filter (function
+ | Nock_parallel.Error _ -> true
+ | _ -> false
+ ) results in
+
+ Printf.printf "\n[5] Results:\n";
+ Printf.printf " Successes: %d\n" (List.length successes);
+ Printf.printf " Errors: %d\n" (List.length errors);
+ Printf.printf " Total time: %.2fs\n" elapsed;
+ Printf.printf " Throughput: %.2f lifecycles/sec\n"
+ (float_of_int num_computations /. elapsed);
+
+ (* Verify all results are identical *)
+ (match successes with
+ | Nock_parallel.Success first :: rest ->
+ let all_same = List.for_all (function
+ | Nock_parallel.Success n -> Noun.mug n = Noun.mug first
+ | _ -> false
+ ) rest in
+ if all_same then
+ Printf.printf " ✓ All results identical (mug: 0x%08lx)\n" (Noun.mug first)
+ else
+ Printf.printf " ✗ Results differ!\n"
+ | _ -> ());
+
+ Printf.printf "\n[6] Benchmark comparison:\n";
+ let bench_result = Nock_parallel.parallel_increment_bench pool 100 in
+ Printf.printf " Sequential: %.4fs\n" bench_result.sequential_time;
+ Printf.printf " Parallel: %.4fs\n" bench_result.parallel_time;
+ Printf.printf " Speedup: %.2fx\n" bench_result.speedup;
+ Printf.printf " Results match: %b\n" bench_result.results_match;
+
+ Domain_pool.shutdown pool;
+
+ Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n";
+ Printf.printf "║ Done! Clean parallel abstraction FTW 🚀 ║\n";
+ Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n"
+
+ | _ ->
+ Printf.printf " ✗ Unexpected pill structure\n";
+ Domain_pool.shutdown pool