summaryrefslogtreecommitdiff
path: root/ocaml/test/explore_kernel_structure.ml
blob: 513d47f4be10b90f9844a3ffecf481533e8bc801 (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
(* Explore the structure of Event 1 kernel *)

open Nock_lib

let check_slot noun slot =
  try
    let _val = Noun.slot (Z.of_int slot) noun in
    "✓"
  with _ -> "✗"

let rec to_list acc noun =
  match noun with
  | Noun.Atom _ -> List.rev acc
  | Noun.Cell (item, rest) -> to_list (item :: acc) rest

let explore _env =
  Printf.printf "Exploring Event 1 kernel structure...\n\n";

  let in_channel = open_in_bin "solid.noun" in
  let pill = (Marshal.from_channel in_channel : Noun.noun) in
  close_in in_channel;

  match pill with
  | Noun.Cell (_tag, events) ->
      let event_list = to_list [] events in

      begin match List.nth_opt event_list 1 with
      | Some kernel ->
          Printf.printf "Event 1 (kernel) slot map:\n";
          Printf.printf "  Slot 2 (head): %s\n" (check_slot kernel 2);
          Printf.printf "  Slot 3 (tail): %s\n" (check_slot kernel 3);
          Printf.printf "  Slot 4: %s\n" (check_slot kernel 4);
          Printf.printf "  Slot 5: %s\n" (check_slot kernel 5);
          Printf.printf "  Slot 6: %s\n" (check_slot kernel 6);
          Printf.printf "  Slot 7: %s\n" (check_slot kernel 7);
          Printf.printf "  Slot 20: %s\n" (check_slot kernel 20);
          Printf.printf "  Slot 23: %s\n" (check_slot kernel 23);
          Printf.printf "  Slot 42: %s\n" (check_slot kernel 42);
          Printf.printf "  Slot 87: %s\n" (check_slot kernel 87);
          Printf.printf "\n";

          (* Check if slots 23 and 42 are gates or formulas *)
          Printf.printf "Checking slot 23:\n";
          begin try
            let slot_23 = Noun.slot (Z.of_int 23) kernel in
            match slot_23 with
            | Noun.Atom a ->
                Printf.printf "  Atom: %s\n" (Z.to_string a)
            | Noun.Cell (h, t) ->
                Printf.printf "  Cell (likely a formula or gate)\n";
                Printf.printf "  Head: %s\n" (match h with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
                Printf.printf "  Tail: %s\n" (match t with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");

                (* Check if it looks like a gate [battery payload] *)
                (* Gate structure: [[formula] [sample context]] *)
                begin try
                  let battery = Noun.head slot_23 in
                  let payload = Noun.tail slot_23 in
                  let sample = Noun.head payload in
                  let _context = Noun.tail payload in
                  Printf.printf "  → Looks like a GATE (has battery/payload/sample/context)\n";
                  Printf.printf "     Battery: %s\n" (match battery with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
                  Printf.printf "     Sample: %s\n" (match sample with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell")
                with _ ->
                  Printf.printf "  → Looks like a FORMULA (not gate structure)\n"
                end
          with _ ->
              Printf.printf "  ✗ Error accessing slot 23\n"
          end;

          Printf.printf "\nChecking slot 42:\n";
          begin try
            let slot_42 = Noun.slot (Z.of_int 42) kernel in
            match slot_42 with
            | Noun.Atom a ->
                Printf.printf "  Atom: %s\n" (Z.to_string a)
            | Noun.Cell (h, t) ->
                Printf.printf "  Cell\n";
                Printf.printf "  Head: %s\n" (match h with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
                Printf.printf "  Tail: %s\n" (match t with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");

                begin try
                  let battery = Noun.head slot_42 in
                  let payload = Noun.tail slot_42 in
                  let sample = Noun.head payload in
                  let _context = Noun.tail payload in
                  Printf.printf "  → Looks like a GATE\n";
                  Printf.printf "     Battery: %s\n" (match battery with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
                  Printf.printf "     Sample: %s\n" (match sample with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell")
                with _ ->
                  Printf.printf "  → Looks like a FORMULA\n"
                end
          with _ ->
              Printf.printf "  ✗ Error accessing slot 42\n"
          end

      | None ->
          Printf.printf "No event 1\n"
      end

  | Noun.Atom _ ->
      Printf.printf "Pill is atom\n"

let () =
  Printf.printf "\n═══════════════════════════════════════════\n";
  Printf.printf " Explore Kernel Structure\n";
  Printf.printf "═══════════════════════════════════════════\n\n";
  Eio_main.run explore