summaryrefslogtreecommitdiff
path: root/ocaml/test/test_parallel_solid.ml
blob: 1b7a5f5307d8f1289cf24c68923b1223ad8d5e5a (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
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
(** Parallel solid pill test using the Nock_parallel abstraction **)

open Nock_lib

let () =
  Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n";
  Printf.printf "║  Parallel Solid Pill 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 solid.pill...\n";
  let ic = open_in_bin "solid.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 (%.1f MB)\n" len (float_of_int len /. 1024.0 /. 1024.0);

  Printf.printf "[2] Cuing solid pill...\n";
  let start_cue = Unix.gettimeofday () in
  let pill = Serial.cue bytes in
  let elapsed_cue = Unix.gettimeofday () -. start_cue in
  Printf.printf "    ✓ Cued in %.2fs\n" elapsed_cue;

  Printf.printf "[3] Parsing pill structure...\n";

  (* Parse: [tag type [bot mod use]] *)
  match pill with
  | Noun.Cell { h = _tag; t = rest; _ } ->
      (match rest with
       | Noun.Cell { h = _ptype; t = events_triple; _ } ->
           (match events_triple with
            | Noun.Cell { h = bot; t = rest2; _ } ->
                (match rest2 with
                 | Noun.Cell { h = _mod; t = rest3; _ } ->
                     (match rest3 with
                      | Noun.Cell { h = use; t = _; _ } ->
                          (* Concatenate bot and use *)
                          let rec to_list acc n =
                            match n with
                            | Noun.Atom _ -> List.rev acc
                            | Noun.Cell { h; t; _ } -> to_list (h :: acc) t
                          in
                          let bot_list = to_list [] bot in
                          let use_list = to_list [] use in
                          let all_events = bot_list @ use_list in

                          Printf.printf "    Bot events: %d\n" (List.length bot_list);
                          Printf.printf "    Use events: %d\n" (List.length use_list);
                          Printf.printf "    Total: %d events\n" (List.length all_events);

                          (* Convert to proper Nock list format *)
                          let rec from_list = function
                            | [] -> Noun.atom 0
                            | h :: t -> Noun.cell h (from_list t)
                          in
                          let event_list = from_list all_events in

                          Printf.printf "\n[4] 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 multiple identical computations *)
                          let num_computations = 100 in
                          let computations = List.init num_computations (fun _ -> (event_list, formula)) in

                          Printf.printf "\n[5] Running %d parallel solid pill lifecycles...\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[6] 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;
                          if List.length successes > 0 then
                            Printf.printf "    Throughput: %.2f lifecycles/sec\n"
                              (float_of_int (List.length successes) /. elapsed);

                          (* Verify all results are identical *)
                          (match successes with
                           | Nock_parallel.Success first :: rest ->
                               Printf.printf "    Computing mugs...\n%!";
                               let first_mug = Noun.mug first in
                               let all_same = List.for_all (function
                                 | Nock_parallel.Success n -> Noun.mug n = first_mug
                                 | _ -> false
                               ) rest in
                               if all_same then
                                 Printf.printf "    ✓ All results identical (mug: 0x%08lx)\n" first_mug
                               else
                                 Printf.printf "    ✗ Results differ!\n"
                           | [] -> Printf.printf "    (No successes to verify)\n"
                           | _ -> ());

                          (* Show errors if any *)
                          if List.length errors > 0 then begin
                            Printf.printf "\n[7] Errors:\n";
                            List.iteri (fun i err ->
                              match err with
                              | Nock_parallel.Error msg ->
                                  Printf.printf "    [%d] %s\n" i msg
                              | _ -> ()
                            ) errors
                          end;

                          Domain_pool.shutdown pool;

                          Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n";
                          Printf.printf "║  Done! Solid pill parallel execution 🚀               ║\n";
                          Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n"

                      | _ -> Printf.printf "  ✗ Unexpected structure at use level\n"; Domain_pool.shutdown pool)
                 | _ -> Printf.printf "  ✗ Unexpected structure at mod level\n"; Domain_pool.shutdown pool)
            | _ -> Printf.printf "  ✗ Unexpected structure at bot level\n"; Domain_pool.shutdown pool)
       | _ -> Printf.printf "  ✗ Unexpected structure at events level\n"; Domain_pool.shutdown pool)
  | _ -> Printf.printf "  ✗ Unexpected pill structure\n"; Domain_pool.shutdown pool