summaryrefslogtreecommitdiff
path: root/ocaml/test/old/test_boot_solid_events.ml
blob: 41fd32c5beef7b172771cfa028fae8bdc9151273 (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
(* Test processing solid pill boot events *)

open Nock_lib

let test_boot_events _env =
  Printf.printf "šŸš€ Processing Solid Pill Boot Events\n\n";

  (* Load cached solid pill *)
  Printf.printf "Loading solid pill from cache...\n";
  let in_channel = open_in_bin "solid.noun" in
  let pill = (Marshal.from_channel in_channel : Noun.noun) in
  close_in in_channel;
  Printf.printf "āœ“ Loaded\n\n";

  (* Extract events *)
  match pill with
  | Noun.Cell (_tag, events) ->
      Printf.printf "Extracting boot events...\n";

      (* Convert event list to array *)
      let rec to_list acc noun =
        match noun with
        | Noun.Atom _ -> List.rev acc
        | Noun.Cell (item, rest) -> to_list (item :: acc) rest
      in

      let event_list = to_list [] events in
      Printf.printf "āœ“ Found %d events\n\n" (List.length event_list);

      (* Process each event *)
      Printf.printf "Processing events:\n\n";

      let kernel = ref None in

      List.iteri (fun i event ->
        Printf.printf "Event %d:\n" i;

        match event with
        | Noun.Atom a ->
            Printf.printf "  Type: Atom (%s)\n" (Z.to_string a);
            Printf.printf "  (Skipping atom event)\n\n"

        | Noun.Cell (wire, card) ->
            Printf.printf "  Type: Cell [wire card]\n";
            Printf.printf "  Wire: %s\n"
              (match wire with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
            Printf.printf "  Card: %s\n"
              (match card with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");

            (* For the first event, card is the initial kernel *)
            if i = 1 then begin
              Printf.printf "  → Setting as initial kernel\n";
              kernel := Some card
            end
            (* For subsequent events, we need to poke the kernel *)
            else if i > 1 then begin
              match !kernel with
              | None ->
                  Printf.printf "  āœ— No kernel to poke yet\n"

              | Some k ->
                  Printf.printf "  → Poking kernel with event\n";

                  try
                    (* Try to find poke gate at slot 23 *)
                    let gate = Noun.slot (Z.of_int 23) k in
                    Printf.printf "     Found gate at slot 23\n";

                    (* Build subject: [event gate] *)
                    let subject = Noun.cell event gate in

                    (* Call gate: [9 2 [0 2] [0 3]] *)
                    let formula = Noun.cell
                      (Noun.atom 9)
                      (Noun.cell
                        (Noun.atom 2)
                        (Noun.cell
                          (Noun.cell (Noun.atom 0) (Noun.atom 2))
                          (Noun.cell (Noun.atom 0) (Noun.atom 3))))
                    in

                    Printf.printf "     Executing nock...\n%!";
                    let start = Unix.gettimeofday () in
                    let result = Nock.nock_on subject formula in
                    let elapsed = Unix.gettimeofday () -. start in
                    Printf.printf "     āœ“ Completed in %.3fs\n" elapsed;

                    (* Result should be [effects new-kernel] *)
                    begin match result with
                    | Noun.Cell (_effects, new_kernel) ->
                        Printf.printf "     Result: [effects new_kernel]\n";
                        kernel := Some new_kernel

                    | Noun.Atom _ ->
                        Printf.printf "     Result: atom (unexpected)\n"
                    end

                  with
                  | Noun.Exit ->
                      Printf.printf "     āœ— Nock failed (Exit)\n"
                  | Not_found ->
                      Printf.printf "     āœ— No gate at slot 23\n"
            end;

            Printf.printf "\n"
      ) event_list;

      (* Check final kernel *)
      begin match !kernel with
      | None ->
          Printf.printf "āœ— No final kernel\n"

      | Some k ->
          Printf.printf "šŸŽ‰ Final Arvo kernel ready!\n\n";

          (* Check for poke interface *)
          begin try
            let _gate = Noun.slot (Z.of_int 23) k in
            Printf.printf "āœ“ Kernel has poke gate at slot 23\n";
            Printf.printf "\nšŸš€ ARVO IS READY TO USE!\n"
          with _ ->
            Printf.printf "āœ— No poke gate in final kernel\n"
          end
      end

  | Noun.Atom _ ->
      Printf.printf "āœ— Pill is an atom\n"

let () =
  Printf.printf "\n";
  Printf.printf "═══════════════════════════════════════════════════════════\n";
  Printf.printf " Boot Solid Pill Events\n";
  Printf.printf "═══════════════════════════════════════════════════════════\n";
  Printf.printf "\n";

  Eio_main.run test_boot_events