summaryrefslogtreecommitdiff
path: root/ocaml/test/old/examine_ivory.ml
blob: 490f735ad5e233a192d6198b1f18ed35586addac (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
(* Examine ivory.pill structure *)

open Nock_lib

let main env =
  Printf.printf "\n═══════════════════════════════════════\n";
  Printf.printf " Examining ivory.pill Structure\n";
  Printf.printf "═══════════════════════════════════════\n\n";

  (* Load ivory pill *)
  Printf.printf "[1] Loading ivory.pill...\\n%!";
  let fs = Eio.Stdenv.fs env in
  let pill_bytes = Eio.Path.(load (fs / "ivory.pill")) |> Bytes.of_string in
  Printf.printf "    Size: %d bytes\n%!" (Bytes.length pill_bytes);

  (* Cue it *)
  Printf.printf "[2] Cuing ivory pill...\n%!";
  let pill = Serial.cue pill_bytes in
  Printf.printf "    ✓ Cued\n\n";

  (* Check structure *)
  Printf.printf "[3] Structure analysis:\n";
  match pill with
  | Noun.Cell (tag, tail) ->
      (* Print tag *)
      let tag_str = match tag with
        | Noun.Atom z ->
            let bytes = Z.to_bits z in
            if String.length bytes <= 10 then bytes else Printf.sprintf "<atom %d bits>" (Z.numbits z)
        | Noun.Cell _ -> "<cell>"
      in
      Printf.printf "    Tag: %s\n" tag_str;

      (* Analyze tail *)
      Printf.printf "    Tail type: %s\n" (if Noun.is_cell tail then "CELL" else "ATOM");

      (match tail with
      | Noun.Atom z when Z.equal z Z.zero ->
          Printf.printf "    Tail value: 0 (NULL!)\n";
          Printf.printf "\n";
          Printf.printf "    ✓ CONFIRMED: Embedded ivory has structure [\"ivory\" 0]\n";
          Printf.printf "    This means u3v_life() is called with atom 0!\n"

      | Noun.Atom z ->
          Printf.printf "    Tail value: atom with %d bits\n" (Z.numbits z);
          Printf.printf "    Tail decimal: %s\n" (Z.to_string z)

      | Noun.Cell (h, t) ->
          Printf.printf "    Tail is a CELL\n";
          Printf.printf "    Head type: %s\n" (if Noun.is_cell h then "cell" else "atom");
          Printf.printf "    Tail type: %s\n" (if Noun.is_cell t then "cell" else "atom");

          (* Check if it's the Arvo core structure *)
          Printf.printf "\n    Checking if tail is Arvo core...\n";
          begin try
            let _slot2 = Noun.slot (Z.of_int 2) tail in
            let _slot3 = Noun.slot (Z.of_int 3) tail in
            Printf.printf "    ✓ Has slot 2 and 3 (it's a cell with head and tail)\n";

            (* Check for lifecycle formula at slot 2 *)
            begin try
              let slot2 = Noun.slot (Z.of_int 2) tail in
              Printf.printf "    Slot 2 type: %s\n" (if Noun.is_cell slot2 then "cell" else "atom");

              (* The lifecycle formula should be [2 [0 3] [0 2]] *)
              match slot2 with
              | Noun.Cell (Noun.Atom op, _rest) when Z.equal op (Z.of_int 2) ->
                  Printf.printf "    Slot 2 starts with opcode 2 - could be lifecycle formula!\n";
                  Printf.printf "\n    ✓ Tail appears to BE the Arvo core itself!\n";
                  Printf.printf "    This means the lifecycle formula operates on the CORE, not null!\n"
              | Noun.Cell (Noun.Atom op, _rest) ->
                  Printf.printf "    Slot 2 starts with opcode: %s\n" (Z.to_string op)
              | _ ->
                  Printf.printf "    Slot 2 doesn't match expected lifecycle formula pattern\n"
            with _ ->
              Printf.printf "    Could not analyze slot 2\n"
            end
          with Noun.Exit ->
            Printf.printf "    ✗ Cannot access slots 2/3 - not a valid cell structure\n"
          end
      )

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

let () = Eio_main.run main