summaryrefslogtreecommitdiff
path: root/ocaml/test/test_parallel_workload.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/test/test_parallel_workload.ml')
-rw-r--r--ocaml/test/test_parallel_workload.ml92
1 files changed, 92 insertions, 0 deletions
diff --git a/ocaml/test/test_parallel_workload.ml b/ocaml/test/test_parallel_workload.ml
new file mode 100644
index 0000000..d4261aa
--- /dev/null
+++ b/ocaml/test/test_parallel_workload.ml
@@ -0,0 +1,92 @@
+(** Massively parallel Nock workload to test multicore - 32 cores edition! **)
+
+open Nock_lib
+
+module T = Domainslib.Task
+
+let () =
+ Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n";
+ Printf.printf "║ Massively Parallel Nock Workload (32 cores!) ║\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";
+
+ let num_iterations = 1000 in (* Run lifecycle 1000 times *)
+ let num_workers = 32 in (* Use all 32 cores *)
+
+ Printf.printf "\n[4] Setting up Domainslib pool with %d domains...\n" num_workers;
+ let pool = T.setup_pool ~num_domains:(num_workers - 1) () in
+
+ Printf.printf "[5] Launching %d parallel tasks (each runs lifecycle %d times)...\n\n"
+ num_workers num_iterations;
+
+ let start_time = Unix.gettimeofday () in
+
+ let results = T.run pool (fun () ->
+ (* Create tasks list *)
+ let tasks = List.init num_workers (fun worker_id ->
+ T.async pool (fun () ->
+ Printf.printf " [Worker %2d] Starting on domain %d...\n%!"
+ worker_id (Domain.self () :> int);
+
+ let worker_start = Unix.gettimeofday () in
+
+ (* Each worker runs lifecycle many times *)
+ for _i = 1 to num_iterations do
+ ignore (Nock.nock_on core formula)
+ done;
+
+ let worker_elapsed = Unix.gettimeofday () -. worker_start in
+ Printf.printf " [Worker %2d] ✓ Completed %d iterations in %.2fs (domain %d)\n%!"
+ worker_id num_iterations worker_elapsed (Domain.self () :> int);
+
+ (worker_id, worker_elapsed)
+ )
+ ) in
+
+ (* Await all results *)
+ Printf.printf "\n[6] Waiting for all workers to complete...\n%!";
+ List.map (T.await pool) tasks
+ ) in
+
+ let total_elapsed = Unix.gettimeofday () -. start_time in
+
+ T.teardown_pool pool;
+
+ Printf.printf "\n[7] Results:\n";
+ Printf.printf " Total work: %d lifecycles\n" (num_workers * num_iterations);
+ Printf.printf " Wall time: %.2fs\n" total_elapsed;
+ Printf.printf " Workers: %d\n" num_workers;
+
+ let total_worker_time = List.fold_left (fun acc (_, t) -> acc +. t) 0.0 results in
+ Printf.printf " Total CPU time: %.2fs\n" total_worker_time;
+ Printf.printf " Speedup: %.2fx\n" (total_worker_time /. total_elapsed);
+ Printf.printf " Parallel efficiency: %.1f%%\n"
+ (100.0 *. total_worker_time /. (total_elapsed *. float_of_int num_workers));
+
+ Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n";
+ Printf.printf "║ All 32 cores SMASHED! 💪 ║\n";
+ Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n"
+
+ | _ ->
+ Printf.printf " ✗ Unexpected pill structure\n"