summaryrefslogtreecommitdiff
path: root/ocaml/test/test_solid_massive.ml
blob: 0d169784db91d21940c8b977d90c500dd2aa1add (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
(** Massive parallel solid pill workload - run lifecycle many times across 32 cores **)

open Nock_lib

module T = Domainslib.Task

let () =
  Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n";
  Printf.printf "║  Massive Parallel Solid Pill Workload (32 cores!)    ║\n";
  Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n";

  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_time = Unix.gettimeofday () in
  let pill = Serial.cue bytes in
  let elapsed = Unix.gettimeofday () -. start_time in
  Printf.printf "    ✓ Cued in %.2fs\n" elapsed;

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

  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 = _; _ } ->
                          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);

                          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";

                          let num_iterations = 10 in   (* Run lifecycle 10 times per worker *)
                          let num_workers = 32 in      (* Use all 32 cores *)

                          Printf.printf "\n[5] Setting up Domainslib pool with %d domains...\n" num_workers;
                          let pool = T.setup_pool ~num_domains:(num_workers - 1) () in

                          Printf.printf "[6] 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 () ->
                            let tasks = List.init num_workers (fun worker_id ->
                              T.async pool (fun () ->
                                Printf.printf "  [Worker %2d] Starting on domain %d with nock_iter...\n%!"
                                  worker_id (Domain.self () :> int);

                                let worker_start = Unix.gettimeofday () in

                                (* Use nock_iter since it won't stack overflow *)
                                for _i = 1 to num_iterations do
                                  ignore (Nock_iter.nock_on event_list formula)
                                done;

                                let worker_elapsed = Unix.gettimeofday () -. worker_start in
                                Printf.printf "  [Worker %2d] ✓ Completed %d lifecycles in %.2fs (domain %d)\n%!"
                                  worker_id num_iterations worker_elapsed (Domain.self () :> int);

                                (worker_id, worker_elapsed)
                              )
                            ) in

                            Printf.printf "\n[7] 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[8] Results:\n";
                          Printf.printf "    Total lifecycles: %d\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 "║  32 cores crushing solid pill! 🔥                     ║\n";
                          Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n"

                      | _ -> Printf.printf "  ✗ Unexpected structure\n")
                 | _ -> Printf.printf "  ✗ Unexpected structure\n")
            | _ -> Printf.printf "  ✗ Unexpected structure\n")
       | _ -> Printf.printf "  ✗ Unexpected structure\n")
  | _ -> Printf.printf "  ✗ Unexpected pill structure\n"