summaryrefslogtreecommitdiff
path: root/ocaml/test/test_parallel_clean.ml
blob: b4f3f9eb5ead2260beea4de2163b0f3a395251da (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
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