summaryrefslogtreecommitdiff
path: root/ocaml/test/old/test_solid_structure.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/test/old/test_solid_structure.ml')
-rw-r--r--ocaml/test/old/test_solid_structure.ml119
1 files changed, 119 insertions, 0 deletions
diff --git a/ocaml/test/old/test_solid_structure.ml b/ocaml/test/old/test_solid_structure.ml
new file mode 100644
index 0000000..21a9433
--- /dev/null
+++ b/ocaml/test/old/test_solid_structure.ml
@@ -0,0 +1,119 @@
+(* Explore solid pill structure to find Arvo *)
+
+open Nock_lib
+
+let test_solid env =
+ Printf.printf "šŸ” Exploring Solid Pill Structure\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let _fs = Eio.Stdenv.fs env in
+
+ (* Load solid pill (use cached .noun for speed) *)
+ 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 from solid.noun\n\n";
+
+ (* Solid pill structure: [tag boot-events] *)
+ match pill with
+ | Noun.Atom _ ->
+ Printf.printf "āœ— Pill is an atom (unexpected)\n"
+
+ | Noun.Cell (tag, events) ->
+ Printf.printf "Pill structure: [tag events]\n";
+ begin match tag with
+ | Noun.Atom a ->
+ Printf.printf " Tag: %s (hex: 0x%s)\n"
+ (Z.to_string a) (Z.format "x" a)
+ | _ -> Printf.printf " Tag: cell\n"
+ end;
+
+ (* Events should be a list *)
+ Printf.printf "\nExploring boot events...\n";
+ let rec count_list n noun =
+ match noun with
+ | Noun.Atom _ -> (n, noun) (* terminator *)
+ | Noun.Cell (item, rest) ->
+ Printf.printf " Event %d: %s\n" n
+ (match item with
+ | Noun.Atom _ -> "atom"
+ | Noun.Cell _ -> "cell");
+ count_list (n + 1) rest
+ in
+
+ let (event_count, terminator) = count_list 0 events in
+ Printf.printf "\nTotal events: %d\n" event_count;
+ Printf.printf "Terminator: %s\n\n"
+ (match terminator with
+ | Noun.Atom a -> Printf.sprintf "atom %s" (Z.to_string a)
+ | Noun.Cell _ -> "cell");
+
+ (* The 5th event should be the final Arvo kernel *)
+ Printf.printf "Extracting final Arvo kernel (last event)...\n";
+ let rec get_last noun =
+ match noun with
+ | Noun.Atom _ -> None
+ | Noun.Cell (item, rest) ->
+ match rest with
+ | Noun.Atom _ -> Some item (* This is the last *)
+ | Noun.Cell _ -> get_last rest
+ in
+
+ match get_last events with
+ | None -> Printf.printf "āœ— Could not find last event\n"
+ | Some last_event ->
+ Printf.printf "āœ“ Found last event\n";
+
+ (* Last event structure: [wire card] where card produces Arvo *)
+ begin match last_event with
+ | Noun.Cell (_wire, card) ->
+ Printf.printf " Event is [wire card]\n";
+ Printf.printf " Card: %s\n\n"
+ (match card with
+ | Noun.Atom _ -> "atom"
+ | Noun.Cell _ -> "cell");
+
+ (* Try to run this event to get Arvo *)
+ Printf.printf "Attempting to extract Arvo kernel...\n";
+
+ (* The card might be the kernel directly, or we need to eval it *)
+ (* Let's check if card has the poke interface at slot 23 *)
+ begin try
+ let potential_arvo = card in
+ let _gate = Noun.slot (Z.of_int 23) potential_arvo in
+ Printf.printf "āœ“ Found gate at slot 23 in card!\n";
+ Printf.printf "\nThis looks like the Arvo kernel!\n";
+ Printf.printf "Let's explore it...\n\n";
+
+ (* Show structure *)
+ for i = 2 to 30 do
+ try
+ let slot_val = Noun.slot (Z.of_int i) potential_arvo in
+ let typ = match slot_val with
+ | Noun.Cell _ -> "cell"
+ | Noun.Atom _ -> "atom"
+ in
+ Printf.printf " Slot %d: %s\n" i typ
+ with _ -> ()
+ done;
+
+ Printf.printf "\nšŸŽ‰ Found Arvo in solid pill!\n"
+
+ with _ ->
+ Printf.printf "āœ— No gate at slot 23\n";
+ Printf.printf "Card might need to be evaluated first\n"
+ end
+
+ | _ ->
+ Printf.printf " Event is not a cell\n"
+ end
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Exploring Solid Pill Structure\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_solid