summaryrefslogtreecommitdiff
path: root/ocaml/test/old/examine_event3_effects.ml
blob: de2fec3aa1dfc8cd3361b3fbefdabcbb2b627c44 (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
143
144
145
146
147
148
(* Examine what effects Event 3 produces *)

open Nock_lib

let slam_on gate event =
  let battery = Noun.head gate in
  let context = Noun.tail (Noun.tail gate) in
  let new_core = Noun.cell battery (Noun.cell event context) in
  let kick_formula = Noun.cell (Noun.atom 9)
    (Noun.cell (Noun.atom 2)
      (Noun.cell (Noun.atom 0) (Noun.atom 1))) in
  Nock.nock_on new_core kick_formula

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

let rec count_list noun =
  match noun with
  | Noun.Atom _ -> 0
  | Noun.Cell (_, rest) -> 1 + (count_list rest)

let describe_noun noun max_depth current_depth =
  let rec aux n d =
    if d > max_depth then "..."
    else
      match n with
      | Noun.Atom a ->
          if Z.numbits a <= 32 then
            Printf.sprintf "Atom(%s/0x%s)" (Z.to_string a) (Z.format "x" a)
          else
            Printf.sprintf "Atom(%d bits)" (Z.numbits a)
      | Noun.Cell (h, t) ->
          Printf.sprintf "[%s %s]" (aux h (d + 1)) (aux t (d + 1))
  in
  aux noun current_depth

let examine _env =
  Printf.printf "Loading solid pill...\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

      (* Get Event 1 (kernel) *)
      begin match List.nth_opt event_list 1 with
      | Some kernel ->
          (* Get Event 3 *)
          begin match List.nth_opt event_list 3 with
          | Some event3 ->
              Printf.printf "\n═══════════════════════════════════════════\n";
              Printf.printf " Event 3 (%%park) Effects Analysis\n";
              Printf.printf "═══════════════════════════════════════════\n\n";

              (* Poke Event 3 *)
              let poke_gate = Noun.slot (Z.of_int 23) kernel in
              let now = Noun.atom 0 in
              let poke_arg = Noun.cell now event3 in

              Printf.printf "Slamming Event 3...\n";
              let result = slam_on poke_gate poke_arg in

              begin match result with
              | Noun.Cell (effects, new_kernel) ->
                  Printf.printf "✓ Slam succeeded!\n\n";

                  (* Analyze effects *)
                  Printf.printf "Effects analysis:\n";
                  let effect_count = count_list effects in
                  Printf.printf "  Total effects: %d\n\n" effect_count;

                  if effect_count = 0 then
                    Printf.printf "  (No effects - effects is atom/nil)\n\n"
                  else begin
                    Printf.printf "  Effect list:\n";
                    let effects_list = to_list [] effects in
                    List.iteri (fun i eff ->
                      Printf.printf "    Effect %d: %s\n" i
                        (describe_noun eff 2 0)
                    ) effects_list;
                    Printf.printf "\n"
                  end;

                  (* Analyze new kernel *)
                  Printf.printf "New kernel analysis:\n";

                  (* Check if it still has slot 23 *)
                  begin try
                    let _poke23 = Noun.slot (Z.of_int 23) new_kernel in
                    Printf.printf "  ✓ Has slot 23 (larval poke)\n"
                  with _ ->
                    Printf.printf "  ✗ No slot 23\n"
                  end;

                  (* Check if it NOW has slot 42 *)
                  begin try
                    let _poke42 = Noun.slot (Z.of_int 42) new_kernel in
                    Printf.printf "  ✓ Has slot 42 (adult poke?)\n"
                  with _ ->
                    Printf.printf "  ✗ No slot 42\n"
                  end;

                  (* Check if kernel changed *)
                  let kernel_is_same = kernel == new_kernel in
                  Printf.printf "  Kernel changed: %s\n"
                    (if kernel_is_same then "No (same object)" else "Yes (new object)");

                  (* Try to see if there's a metamorphosis indicator *)
                  Printf.printf "\nLooking for metamorphosis indicators...\n";

                  (* Check a few specific slots that might indicate state *)
                  let check_slot kernel slot_num name =
                    try
                      let _val = Noun.slot (Z.of_int slot_num) kernel in
                      Printf.printf "  %s (slot %d): exists\n" name slot_num
                    with _ ->
                      Printf.printf "  %s (slot %d): missing\n" name slot_num
                  in

                  check_slot kernel 2 "Original head";
                  check_slot kernel 3 "Original tail";
                  check_slot new_kernel 2 "New head";
                  check_slot new_kernel 3 "New tail";

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

          | None ->
              Printf.printf "No Event 3\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 " Examine Event 3 Effects\n";
  Printf.printf "═══════════════════════════════════════════\n\n";
  Eio_main.run examine