summaryrefslogtreecommitdiff
path: root/ocaml/test
diff options
context:
space:
mode:
authorpolwex <polwex@sortug.com>2025-10-06 10:30:19 +0700
committerpolwex <polwex@sortug.com>2025-10-06 10:30:19 +0700
commit4be1d7f999ffb3eb1c12c54e863b141af21b3fbf (patch)
tree6e33b141cd98985799e02a253dddcf201fec6b74 /ocaml/test
parentc3545b7ba9e8448226417fab6edaa2d039c9babe (diff)
some progress but man
Diffstat (limited to 'ocaml/test')
-rw-r--r--ocaml/test/cache_solid.ml43
-rw-r--r--ocaml/test/dune60
-rw-r--r--ocaml/test/examine_solid_structure.c109
-rw-r--r--ocaml/test/test_arms.ml73
-rw-r--r--ocaml/test/test_arvo.ml69
-rw-r--r--ocaml/test/test_arvo_slots.ml74
-rw-r--r--ocaml/test/test_arvo_structure.ml116
-rw-r--r--ocaml/test/test_cvere_poke.ml105
-rw-r--r--ocaml/test/test_ivory_boot.ml97
-rw-r--r--ocaml/test/test_ivory_structure.ml105
-rw-r--r--ocaml/test/test_pill_depth.ml98
-rw-r--r--ocaml/test/test_poke_formulas.ml85
-rw-r--r--ocaml/test/test_real_arvo.ml111
-rw-r--r--ocaml/test/test_solid_boot.ml116
14 files changed, 1261 insertions, 0 deletions
diff --git a/ocaml/test/cache_solid.ml b/ocaml/test/cache_solid.ml
new file mode 100644
index 0000000..f82e0b8
--- /dev/null
+++ b/ocaml/test/cache_solid.ml
@@ -0,0 +1,43 @@
+(* Cache Solid Pill - Cue once and save marshalled OCaml noun
+ *
+ * This cues the solid pill once (slow) and saves the resulting
+ * noun using OCaml's Marshal for fast loading later
+ *)
+
+open Nock_lib
+
+let cache_solid env =
+ Printf.printf "Caching solid pill...\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Load and cue solid pill *)
+ Printf.printf "Step 1: Loading solid.pill (8.7 MB)...\n";
+ let file_path = Eio.Path.(fs / "solid.pill") in
+ let pill_bytes = Eio.Path.load file_path |> Bytes.of_string in
+ Printf.printf " Loaded %d bytes\n\n" (Bytes.length pill_bytes);
+
+ Printf.printf "Step 2: Cuing (this will take several minutes)...\n";
+ let start = Unix.gettimeofday () in
+ let pill = Serial.cue pill_bytes in
+ let elapsed = Unix.gettimeofday () -. start in
+ Printf.printf " ✓ Cued in %.1fs\n\n" elapsed;
+
+ Printf.printf "Step 3: Marshalling noun to solid.noun...\n";
+ let out_channel = open_out_bin "solid.noun" in
+ Marshal.to_channel out_channel pill [];
+ close_out out_channel;
+ Printf.printf " ✓ Saved to solid.noun\n\n";
+
+ Printf.printf "Step 4: Testing reload speed...\n";
+ let start = Unix.gettimeofday () in
+ let in_channel = open_in_bin "solid.noun" in
+ let _reloaded = (Marshal.from_channel in_channel : Noun.noun) in
+ close_in in_channel;
+ let elapsed = Unix.gettimeofday () -. start in
+ Printf.printf " ✓ Reloaded in %.4fs (much faster!)\n\n" elapsed;
+
+ Printf.printf "Done! Use solid.noun for fast testing.\n"
+
+let () = Eio_main.run cache_solid
diff --git a/ocaml/test/dune b/ocaml/test/dune
index 4916c6c..787672b 100644
--- a/ocaml/test/dune
+++ b/ocaml/test/dune
@@ -86,3 +86,63 @@
(name test_dill_iris)
(modules test_dill_iris)
(libraries nock_lib io_drivers eio_main unix))
+
+(executable
+ (name test_arvo)
+ (modules test_arvo)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_arvo_structure)
+ (modules test_arvo_structure)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_poke_formulas)
+ (modules test_poke_formulas)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_arms)
+ (modules test_arms)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_pill_depth)
+ (modules test_pill_depth)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_real_arvo)
+ (modules test_real_arvo)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_cvere_poke)
+ (modules test_cvere_poke)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_arvo_slots)
+ (modules test_arvo_slots)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_ivory_boot)
+ (modules test_ivory_boot)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_ivory_structure)
+ (modules test_ivory_structure)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_solid_boot)
+ (modules test_solid_boot)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name cache_solid)
+ (modules cache_solid)
+ (libraries nock_lib eio_main unix))
diff --git a/ocaml/test/examine_solid_structure.c b/ocaml/test/examine_solid_structure.c
new file mode 100644
index 0000000..158083c
--- /dev/null
+++ b/ocaml/test/examine_solid_structure.c
@@ -0,0 +1,109 @@
+/// Examine solid pill structure using C Vere
+
+#include <sys/stat.h>
+#include <stdio.h>
+#include <stdlib.h>
+#include "noun.h"
+#include "ur/ur.h"
+#include "vere.h"
+
+static void print_noun_structure(u3_noun noun, int depth, int max_depth) {
+ if (depth > max_depth) {
+ printf("...");
+ return;
+ }
+
+ if (u3_none == noun) {
+ printf("none");
+ return;
+ }
+
+ if (c3y == u3a_is_atom(noun)) {
+ if (u3r_met(3, noun) < 20) {
+ printf("atom(%u)", u3r_word(0, noun));
+ } else {
+ printf("atom(large, %u bytes)", u3r_met(3, noun));
+ }
+ } else {
+ printf("[");
+ print_noun_structure(u3h(noun), depth + 1, max_depth);
+ printf(" ");
+ print_noun_structure(u3t(noun), depth + 1, max_depth);
+ printf("]");
+ }
+}
+
+int main(int argc, char* argv[]) {
+ const char* pill_path = argc > 1 ? argv[1] : "../../../ocaml/solid.pill";
+
+ // Read pill
+ FILE* f = fopen(pill_path, "rb");
+ if (!f) {
+ printf("Error: cannot open %s\n", pill_path);
+ return 1;
+ }
+
+ struct stat st;
+ fstat(fileno(f), &st);
+ c3_d len_d = st.st_size;
+ c3_y* byt_y = malloc(len_d);
+ fread(byt_y, 1, len_d, f);
+ fclose(f);
+
+ printf("Examining solid pill structure...\n\n");
+
+ // Initialize runtime
+ u3C.wag_w |= u3o_hashless;
+ u3m_boot_lite(1 << 26);
+
+ // Cue pill
+ u3_cue_xeno* sil_u = u3s_cue_xeno_init_with(ur_fib27, ur_fib28);
+ u3_weak pil = u3s_cue_xeno_with(sil_u, len_d, byt_y);
+ u3s_cue_xeno_done(sil_u);
+
+ if (u3_none == pil) {
+ printf("Error: cue failed\n");
+ return 1;
+ }
+
+ printf("Pill top-level structure:\n");
+ print_noun_structure(pil, 0, 3);
+ printf("\n\n");
+
+ // Check if it's a cell
+ if (c3y == u3a_is_cell(pil)) {
+ printf("Pill is a cell [head tail]\n\n");
+
+ u3_noun head = u3h(pil);
+ u3_noun tail = u3t(pil);
+
+ printf("Head: ");
+ print_noun_structure(head, 0, 2);
+ printf("\n\n");
+
+ printf("Tail: ");
+ print_noun_structure(tail, 0, 2);
+ printf("\n\n");
+
+ // Check if head is an atom (tag)
+ if (c3y == u3a_is_atom(head) && u3r_met(3, head) < 20) {
+ printf("Head is small atom: %u\n", u3r_word(0, head));
+ printf(" (might be a tag)\n\n");
+ }
+
+ // If tail is a list, count elements
+ if (c3y == u3a_is_cell(tail)) {
+ int count = 0;
+ u3_noun cur = tail;
+ while (c3y == u3a_is_cell(cur) && count < 100) {
+ count++;
+ cur = u3t(cur);
+ }
+ printf("Tail appears to be a list with ~%d elements\n", count);
+ printf(" (these might be boot events)\n");
+ }
+ }
+
+ free(byt_y);
+ return 0;
+}
diff --git a/ocaml/test/test_arms.ml b/ocaml/test/test_arms.ml
new file mode 100644
index 0000000..0847f6f
--- /dev/null
+++ b/ocaml/test/test_arms.ml
@@ -0,0 +1,73 @@
+(* Test Different Arms
+ *
+ * Try calling different arms of the Arvo kernel
+ *)
+
+open Nock_lib
+
+let test_arm arm_num kernel =
+ Printf.printf "Testing arm %d: " arm_num;
+
+ try
+ let formula = Noun.cell (Noun.atom 9)
+ (Noun.cell (Noun.atom arm_num)
+ (Noun.cell (Noun.atom 0) (Noun.atom 1))) in
+
+ let _result = Nock.nock_on kernel formula in
+ Printf.printf "✓ Success!\n";
+ true
+ with e ->
+ Printf.printf "✗ %s\n" (Printexc.to_string e);
+ false
+
+let test_arms env =
+ Printf.printf "🔍 Testing Different Arms of Arvo\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Load ivory pill *)
+ let state = State.create () in
+ match Boot.boot_from_file ~fs state "ivory.pill" with
+ | Error msg ->
+ Printf.printf "✗ Failed to load pill: %s\n%!" msg
+ | Ok () ->
+ let kernel = State.get_arvo state in
+
+ Printf.printf "Trying arms 2 through 10...\n\n";
+
+ for arm = 2 to 10 do
+ let _ = test_arm arm kernel in
+ ()
+ done;
+
+ Printf.printf "\nNow trying specific formulas:\n\n";
+
+ (* Try the actual C Vere poke formula from u3v_poke *)
+ Printf.printf "C Vere style (simplified): ";
+ try
+ (* Subject is [now kernel] typically *)
+ let now = Noun.atom 0 in
+ let poke_subject = Noun.cell now kernel in
+
+ (* Formula to replace sample and call *)
+ (* [8 kernel-with-new-sample [9 2 [0 1]]] *)
+ let formula = Noun.cell (Noun.atom 8)
+ (Noun.cell kernel
+ (Noun.cell (Noun.atom 9)
+ (Noun.cell (Noun.atom 2)
+ (Noun.cell (Noun.atom 0) (Noun.atom 1))))) in
+
+ let _result = Nock.nock_on poke_subject formula in
+ Printf.printf "✓ Success!\n"
+ with e ->
+ Printf.printf "✗ %s\n" (Printexc.to_string e)
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Testing Arms of Arvo Kernel\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_arms
diff --git a/ocaml/test/test_arvo.ml b/ocaml/test/test_arvo.ml
new file mode 100644
index 0000000..8325589
--- /dev/null
+++ b/ocaml/test/test_arvo.ml
@@ -0,0 +1,69 @@
+(* Test Real Arvo Execution
+ *
+ * Load ivory pill and try to poke Arvo with a test event
+ *)
+
+open Nock_lib
+
+let test_load_and_poke env =
+ Printf.printf "🧪 Testing Real Arvo Execution\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Load ivory pill *)
+ Printf.printf "Loading ivory pill...\n%!";
+ let state = State.create () in
+
+ match Boot.boot_from_file ~fs state "ivory.pill" with
+ | Error msg ->
+ Printf.printf "✗ Failed to load pill: %s\n%!" msg;
+ failwith "Pill load failed"
+
+ | Ok () ->
+ Printf.printf "✓ Ivory kernel loaded!\n\n";
+
+ (* Create a simple test event (ovum) *)
+ Printf.printf "Creating test event...\n%!";
+ let test_event = Noun.cell
+ (Noun.atom 0) (* wire: simple routing *)
+ (Noun.cell
+ (Noun.atom 1) (* vane tag *)
+ (Noun.atom 42)) (* simple data *)
+ in
+
+ Printf.printf "Test event: [wire card]\n%!";
+ Printf.printf " wire: 0\n%!";
+ Printf.printf " card: [1 42]\n\n%!";
+
+ (* Try to poke Arvo! *)
+ Printf.printf "🚀 Poking Arvo with test event...\n%!";
+
+ try
+ let start = Unix.gettimeofday () in
+ let effects = State.poke state test_event in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf "✓ Poke succeeded in %.4f seconds!\n\n" elapsed;
+
+ Printf.printf "Effects returned: %d\n%!" (List.length effects);
+ Printf.printf "New event number: %Ld\n\n%!" (State.event_num state);
+
+ Printf.printf "🎉 ARVO IS RUNNING!\n%!";
+
+ with e ->
+ Printf.printf "✗ Poke failed with exception:\n%!";
+ Printf.printf " %s\n\n%!" (Printexc.to_string e);
+ Printf.printf "This is expected - we need to figure out:\n%!";
+ Printf.printf " 1. Correct event format\n%!";
+ Printf.printf " 2. Correct poke formula\n%!";
+ Printf.printf " 3. How to parse results\n%!"
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Testing Real Arvo Execution with Ivory Pill\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_load_and_poke
diff --git a/ocaml/test/test_arvo_slots.ml b/ocaml/test/test_arvo_slots.ml
new file mode 100644
index 0000000..5ec9f76
--- /dev/null
+++ b/ocaml/test/test_arvo_slots.ml
@@ -0,0 +1,74 @@
+(* Test Available Slots on Arvo Core
+ *
+ * Check what slots are available on the Arvo core we found
+ *)
+
+open Nock_lib
+
+let test_slot slot arvo =
+ try
+ let value = Noun.slot (Z.of_int slot) arvo in
+ Printf.printf " Slot %2d: exists (%s)\n" slot
+ (if Noun.is_cell value then "cell" else "atom");
+ Some value
+ with _ ->
+ Printf.printf " Slot %2d: does not exist\n" slot;
+ None
+
+let test_arvo_slots env =
+ Printf.printf "🔍 Testing Available Slots on Arvo Core\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Load solid pill *)
+ let state = State.create () in
+ match Boot.boot_from_file ~fs state "solid.pill" with
+ | Error msg ->
+ Printf.printf "✗ Failed to load pill: %s\n%!" msg
+ | Ok () ->
+ let pill_root = State.get_arvo state in
+
+ Printf.printf "=== Testing PILL ROOT ===\n\n";
+ Printf.printf "Testing slots 2-30 on pill root:\n\n";
+ List.iter (fun slot -> ignore (test_slot slot pill_root))
+ (List.init 29 (fun i -> i + 2));
+
+ Printf.printf "\n\n=== Testing ARVO CORE (at depth 8) ===\n\n";
+
+ (* Navigate to real Arvo *)
+ let path = [3; 3; 2; 3; 2; 3; 3; 2] in
+ let rec navigate noun = function
+ | [] -> noun
+ | slot :: rest ->
+ navigate (Noun.slot (Z.of_int slot) noun) rest
+ in
+ let arvo = navigate pill_root path in
+
+ Printf.printf "Testing slots 2-30 on Arvo core:\n\n";
+ List.iter (fun slot -> ignore (test_slot slot arvo))
+ (List.init 29 (fun i -> i + 2));
+
+ Printf.printf "\nLooking for formula slots that might be poke...\n\n";
+
+ (* Check if any slot contains a formula (cell starting with opcode) *)
+ for slot = 2 to 30 do
+ match test_slot slot arvo with
+ | Some value when Noun.is_cell value ->
+ (match Noun.head value with
+ | Noun.Atom z when Z.numbits z < 8 ->
+ let opcode = Z.to_int z in
+ if opcode >= 0 && opcode <= 11 then
+ Printf.printf " Slot %d contains formula with opcode %d\n" slot opcode
+ | _ -> ())
+ | _ -> ()
+ done
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Testing Arvo Core Slots\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_arvo_slots
diff --git a/ocaml/test/test_arvo_structure.ml b/ocaml/test/test_arvo_structure.ml
new file mode 100644
index 0000000..cbd9f65
--- /dev/null
+++ b/ocaml/test/test_arvo_structure.ml
@@ -0,0 +1,116 @@
+(* Examine Arvo Kernel Structure
+ *
+ * Load the ivory pill and inspect the kernel to understand:
+ * - Is it a gate (cell)?
+ * - Where is the battery?
+ * - What's the structure?
+ *)
+
+open Nock_lib
+
+let rec describe_noun_structure noun depth =
+ if depth > 5 then
+ "..."
+ else
+ match noun with
+ | Noun.Atom z ->
+ if Z.numbits z > 64 then
+ Printf.sprintf "Atom(huge: %d bits)" (Z.numbits z)
+ else
+ Printf.sprintf "Atom(%s)" (Z.to_string z)
+ | Noun.Cell (a, b) ->
+ Printf.sprintf "Cell(\n%s%s,\n%s%s)"
+ (String.make (depth * 2) ' ')
+ (describe_noun_structure a (depth + 1))
+ (String.make (depth * 2) ' ')
+ (describe_noun_structure b (depth + 1))
+
+let test_arvo_structure env =
+ Printf.printf "🔍 Examining Arvo Kernel Structure\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Load ivory pill *)
+ Printf.printf "Loading ivory pill...\n%!";
+ let state = State.create () in
+
+ match Boot.boot_from_file ~fs state "ivory.pill" with
+ | Error msg ->
+ Printf.printf "✗ Failed to load pill: %s\n%!" msg
+ | Ok () ->
+ Printf.printf "✓ Pill loaded!\n\n";
+
+ let kernel = State.get_arvo state in
+
+ (* Check if it's a cell *)
+ Printf.printf "Kernel structure:\n";
+ if Noun.is_cell kernel then begin
+ Printf.printf " ✓ Kernel is a CELL (likely a gate!)\n\n";
+
+ let head = Noun.head kernel in
+ let tail = Noun.tail kernel in
+
+ Printf.printf "Head (slot 2 - battery?):\n";
+ if Noun.is_cell head then
+ Printf.printf " Cell (battery with multiple arms)\n"
+ else
+ (match head with
+ | Noun.Atom z -> Printf.printf " Atom: %s\n" (Z.to_string z)
+ | _ -> ());
+
+ Printf.printf "\nTail (slot 3 - sample + context?):\n";
+ if Noun.is_cell tail then begin
+ Printf.printf " Cell (has sample and context)\n";
+ let sample = Noun.head tail in
+ let context = Noun.tail tail in
+
+ Printf.printf "\n Sample (slot 6):\n";
+ Printf.printf " %s\n" (describe_noun_structure sample 2);
+
+ Printf.printf "\n Context (slot 7):\n";
+ if Noun.is_atom context then
+ (match context with
+ | Noun.Atom z -> Printf.printf " Atom: %s\n" (Z.to_string z)
+ | _ -> ())
+ else
+ Printf.printf " Cell (nested context)\n"
+ end else
+ (match tail with
+ | Noun.Atom z -> Printf.printf " Atom: %s\n" (Z.to_string z)
+ | _ -> ());
+
+ (* Test: Try to call arm 2 with current sample *)
+ Printf.printf "\n🧪 Testing gate call with opcode 9...\n";
+ Printf.printf "Formula: [9 2 0 1] (call arm 2 of whole subject)\n\n";
+
+ try
+ let formula = Noun.cell
+ (Noun.atom 9)
+ (Noun.cell (Noun.atom 2) (Noun.cell (Noun.atom 0) (Noun.atom 1))) in
+
+ let start = Unix.gettimeofday () in
+ let _result = Nock.nock_on kernel formula in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf "✓ Gate call succeeded in %.4f seconds!\n" elapsed;
+ Printf.printf "This proves Arvo is a proper gate!\n\n"
+ with e ->
+ Printf.printf "✗ Gate call failed: %s\n" (Printexc.to_string e);
+ Printf.printf "Kernel might not be a standard gate structure\n\n"
+
+ end else begin
+ (match kernel with
+ | Noun.Atom z -> Printf.printf " Kernel is an ATOM: %s\n" (Z.to_string z)
+ | _ -> ());
+ Printf.printf " This is unexpected - Arvo should be a gate (cell)\n"
+ end
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Examining Arvo Kernel Structure from Ivory Pill\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_arvo_structure
diff --git a/ocaml/test/test_cvere_poke.ml b/ocaml/test/test_cvere_poke.ml
new file mode 100644
index 0000000..28b0c78
--- /dev/null
+++ b/ocaml/test/test_cvere_poke.ml
@@ -0,0 +1,105 @@
+(* Test C Vere Poke Pattern
+ *
+ * Implement the exact poke sequence from C Vere:
+ * 1. Get slot 23 from Arvo core (poke formula)
+ * 2. Run Nock to compute the poke gate
+ * 3. Slam: build [battery [event context]] and call arm 2
+ *)
+
+open Nock_lib
+
+let slam_on gate event =
+ (* C Vere slam_on: u3nc(u3k(u3h(gat)), u3nc(sam, u3k(u3t(u3t(gat))))) *)
+ (* Build: [battery [new-sample context]] *)
+ let battery = Noun.head gate in
+ let context = Noun.tail (Noun.tail gate) in (* slot 7 *)
+ let new_core = Noun.cell battery (Noun.cell event context) in
+
+ (* Kick: call arm 2 *)
+ 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 test_cvere_poke env =
+ Printf.printf "🎯 Testing C Vere Poke Pattern\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Load ivory pill *)
+ let state = State.create () in
+ match Boot.boot_from_file ~fs state "ivory.pill" with
+ | Error msg ->
+ Printf.printf "✗ Failed to load pill: %s\n%!" msg
+ | Ok () ->
+ let pill_root = State.get_arvo state in
+
+ Printf.printf "Step 0: Navigate to real Arvo core\n";
+ Printf.printf " Path: [3 3 2 3 2 3 3 2]\n";
+
+ (* Navigate to real Arvo *)
+ let path = [3; 3; 2; 3; 2; 3; 3; 2] in
+ let rec navigate noun = function
+ | [] -> noun
+ | slot :: rest ->
+ navigate (Noun.slot (Z.of_int slot) noun) rest
+ in
+ let arvo = navigate pill_root path in
+ Printf.printf " ✓ Found real Arvo core\n\n";
+
+ Printf.printf "Step 1: Get slot 23 from Arvo core\n";
+ let slot_23_formula = Noun.slot (Z.of_int 23) arvo in
+ Printf.printf " ✓ Got formula from slot 23\n\n";
+
+ Printf.printf "Step 2: Run Nock to compute poke gate\n";
+ Printf.printf " Subject: Arvo core\n";
+ Printf.printf " Formula: slot 23 contents\n";
+
+ let poke_gate = Nock.nock_on arvo slot_23_formula in
+ Printf.printf " ✓ Computed poke gate\n\n";
+
+ Printf.printf "Step 3: Create test event (ovum)\n";
+ let event = Noun.cell (Noun.atom 0) (Noun.atom 42) in
+ Printf.printf " Event: [0 42]\n\n";
+
+ Printf.printf "Step 4: Slam poke gate with event\n";
+ Printf.printf " Building: [battery [event context]]\n";
+ Printf.printf " Calling: arm 2\n\n";
+
+ let start = Unix.gettimeofday () in
+ (try
+ let result = slam_on poke_gate event in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf "🎉 POKE SUCCEEDED in %.4fs!\n\n" elapsed;
+
+ (* Result should be [effects new-core] *)
+ if Noun.is_cell result then begin
+ Printf.printf "Result structure: Cell\n";
+ let effects = Noun.head result in
+ let new_core = Noun.tail result in
+
+ Printf.printf " Effects: %s\n"
+ (if Noun.is_cell effects then "Cell (list)" else "Atom");
+ Printf.printf " New core: %s\n"
+ (if Noun.is_cell new_core then "Cell (updated Arvo)" else "Atom");
+
+ Printf.printf "\n✨ ARVO IS RUNNING!\n";
+ Printf.printf "We can now poke Arvo with events!\n"
+ end else
+ Printf.printf "Result is atom (unexpected)\n"
+
+ with e ->
+ Printf.printf "✗ Poke failed: %s\n" (Printexc.to_string e);
+ Printf.printf "Stack trace:\n%s\n" (Printexc.get_backtrace ()))
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Testing C Vere Poke Pattern on Arvo\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_cvere_poke
diff --git a/ocaml/test/test_ivory_boot.ml b/ocaml/test/test_ivory_boot.ml
new file mode 100644
index 0000000..7cada9e
--- /dev/null
+++ b/ocaml/test/test_ivory_boot.ml
@@ -0,0 +1,97 @@
+(* Test Ivory Pill Boot Sequence
+ *
+ * Implements C Vere's u3v_life() lifecycle boot
+ *)
+
+open Nock_lib
+
+let test_ivory_boot env =
+ Printf.printf "🎯 Testing Ivory Pill Boot (C Vere u3v_life pattern)\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Create state *)
+ let state = State.create () in
+
+ (* Boot using ivory boot sequence *)
+ Printf.printf "Step 1: Load ivory pill\n";
+ Printf.printf "Step 2: Validate 'ivory' tag\n";
+ Printf.printf "Step 3: Run lifecycle formula [2 [0 3] [0 2]]\n";
+ Printf.printf "Step 4: Extract slot 7 from result\n\n";
+
+ match Boot.boot_ivory ~fs state "ivory.pill" with
+ | Error msg ->
+ Printf.printf "✗ Boot failed: %s\n%!" msg
+
+ | Ok () ->
+ let arvo = State.get_arvo state in
+ Printf.printf "\n✨ SUCCESS! Ivory pill booted!\n\n";
+
+ (* Verify structure *)
+ Printf.printf "Verifying booted core structure:\n";
+ Printf.printf " Is cell: %s\n" (if Noun.is_cell arvo then "✓" else "✗");
+
+ if Noun.is_cell arvo then begin
+ let battery = Noun.head arvo in
+ let payload = Noun.tail arvo in
+
+ Printf.printf " Battery: %s\n"
+ (if Noun.is_cell battery then "✓ Cell (contains code)" else "Atom");
+ Printf.printf " Payload: %s\n\n"
+ (if Noun.is_cell payload then "✓ Cell (contains data)" else "Atom");
+
+ (* Now try the C Vere poke pattern on this booted core *)
+ Printf.printf "Testing if this core has slot 23 (poke interface)...\n";
+ (try
+ let slot_23 = Noun.slot (Z.of_int 23) arvo in
+ Printf.printf " ✓ Slot 23 exists!\n";
+ Printf.printf " Is formula: %s\n"
+ (if Noun.is_cell slot_23 then "✓ Cell" else "Atom");
+
+ (* Try to run poke sequence *)
+ Printf.printf "\nAttempting C Vere poke sequence:\n";
+ Printf.printf " 1. Get slot 23 formula\n";
+ Printf.printf " 2. Run formula on Arvo core\n";
+ Printf.printf " 3. Slam result with test event\n\n";
+
+ let poke_gate = Nock.nock_on arvo slot_23 in
+ Printf.printf " ✓ Got poke gate from slot 23\n";
+
+ (* Create test event *)
+ let event = Noun.cell (Noun.atom 0) (Noun.atom 42) in
+
+ (* Slam: build [battery [event context]] and call arm 2 *)
+ let battery = Noun.head poke_gate in
+ let context = Noun.tail (Noun.tail poke_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
+
+ let start = Unix.gettimeofday () in
+ let result = Nock.nock_on new_core kick_formula in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf " ✓ Poke succeeded in %.4fs!\n" elapsed;
+ Printf.printf " Result: %s\n\n"
+ (if Noun.is_cell result then "Cell (effects + new state)" else "Atom");
+
+ Printf.printf "🎉 FULL ARVO BOOT SUCCESSFUL!\n";
+ Printf.printf "We have a working Arvo instance!\n"
+
+ with e ->
+ Printf.printf " ✗ Slot 23 not found: %s\n" (Printexc.to_string e);
+ Printf.printf "\nThis is expected for ivory pills.\n";
+ Printf.printf "Ivory contains %%zuse core, not full Arvo.\n";
+ Printf.printf "For full poke interface, need solid/brass pill.\n")
+ end
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Testing Ivory Pill Boot Sequence (u3v_life)\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_ivory_boot
diff --git a/ocaml/test/test_ivory_structure.ml b/ocaml/test/test_ivory_structure.ml
new file mode 100644
index 0000000..2ed76a9
--- /dev/null
+++ b/ocaml/test/test_ivory_structure.ml
@@ -0,0 +1,105 @@
+(* Examine Ivory Pill Structure *)
+
+open Nock_lib
+
+let test_ivory_structure env =
+ Printf.printf "🔍 Examining Ivory Pill Structure\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Load ivory pill *)
+ let file_path = Eio.Path.(fs / "ivory.pill") in
+ let pill_bytes = Eio.Path.load file_path |> Bytes.of_string in
+
+ Printf.printf "Loading ivory pill (%d bytes)...\n" (Bytes.length pill_bytes);
+ let start = Unix.gettimeofday () in
+ let pill = Serial.cue pill_bytes in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf "Cued in %.2fs\n\n" elapsed;
+
+ Printf.printf "Top-level structure:\n";
+ if Noun.is_cell pill then begin
+ Printf.printf " ✓ Is cell\n";
+ let head = Noun.head pill in
+ let tail = Noun.tail pill in
+
+ Printf.printf "\nHead:\n";
+ (match head with
+ | Noun.Atom z ->
+ Printf.printf " Atom: %s\n" (Z.to_string z);
+ Printf.printf " Hex: 0x%s\n" (Z.format "x" z);
+ Printf.printf " Bits: %d\n" (Z.numbits z);
+
+ (* Try to decode as ASCII cord *)
+ if Z.numbits z <= 64 then begin
+ let bytes = Z.to_bits z in
+ Printf.printf " ASCII (reversed): ";
+ for i = 0 to String.length bytes - 1 do
+ let c = bytes.[i] in
+ if c >= ' ' && c <= '~' then
+ Printf.printf "%c" c
+ else
+ Printf.printf "\\x%02x" (Char.code c)
+ done;
+ Printf.printf "\n"
+ end;
+
+ (* Check specific values *)
+ if Z.equal z (Z.of_string "129293697897") then
+ Printf.printf " ✓ This is 'ivory' tag!\n"
+
+ | Noun.Cell _ ->
+ Printf.printf " Cell\n");
+
+ Printf.printf "\nTail (the ivory core):\n";
+ Printf.printf " %s\n" (if Noun.is_cell tail then "Cell" else "Atom");
+
+ if Noun.is_cell tail then begin
+ Printf.printf " Head of tail: %s\n"
+ (if Noun.is_cell (Noun.head tail) then "Cell (battery?)" else "Atom");
+ Printf.printf " Tail of tail: %s\n"
+ (if Noun.is_cell (Noun.tail tail) then "Cell (payload?)" else "Atom");
+
+ (* Test which slots exist on the core *)
+ Printf.printf "\nTesting slots 2-10 on ivory core:\n";
+ for slot = 2 to 10 do
+ try
+ let value = Noun.slot (Z.of_int slot) tail in
+ Printf.printf " Slot %2d: exists (%s)\n" slot
+ (if Noun.is_cell value then "cell" else "atom")
+ with _ ->
+ Printf.printf " Slot %2d: does not exist\n" slot
+ done;
+
+ (* Check if it's actually a gate [battery sample context] *)
+ Printf.printf "\nGate structure analysis:\n";
+ if Noun.is_cell tail then begin
+ let battery = Noun.head tail in
+ let rest = Noun.tail tail in
+ Printf.printf " Battery (slot 2): %s\n"
+ (if Noun.is_cell battery then "Cell (contains formulas)" else "Atom");
+
+ if Noun.is_cell rest then begin
+ let sample = Noun.head rest in
+ let context = Noun.tail rest in
+ Printf.printf " Sample (slot 6): %s\n"
+ (if Noun.is_cell sample then "Cell" else "Atom");
+ Printf.printf " Context (slot 7): %s\n"
+ (if Noun.is_cell context then "Cell" else "Atom")
+ end
+ end
+ end
+
+ end else
+ Printf.printf " Atom (unexpected)\n"
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Examining Ivory Pill Structure\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_ivory_structure
diff --git a/ocaml/test/test_pill_depth.ml b/ocaml/test/test_pill_depth.ml
new file mode 100644
index 0000000..329465b
--- /dev/null
+++ b/ocaml/test/test_pill_depth.ml
@@ -0,0 +1,98 @@
+(* Examine Pill Structure at Depth
+ *
+ * Maybe Arvo is nested inside the pill structure
+ *)
+
+open Nock_lib
+
+let rec find_gates noun depth max_depth path =
+ if depth > max_depth then []
+ else
+ match noun with
+ | Noun.Atom _ -> []
+ | Noun.Cell (head, tail) ->
+ let this_is_gate =
+ (* A gate has: [battery sample context] where battery is a cell *)
+ Noun.is_cell head &&
+ Noun.is_cell tail &&
+ Noun.is_cell (Noun.head tail) in (* tail = [sample context] *)
+
+ let gates = if this_is_gate then [(depth, List.rev path, noun)] else [] in
+ let head_gates = find_gates head (depth + 1) max_depth (2 :: path) in
+ let tail_gates = find_gates tail (depth + 1) max_depth (3 :: path) in
+ gates @ head_gates @ tail_gates
+
+let test_pill_depth env =
+ Printf.printf "🔍 Searching for Gates in Pill Structure\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Load ivory pill *)
+ let state = State.create () in
+ match Boot.boot_from_file ~fs state "ivory.pill" with
+ | Error msg ->
+ Printf.printf "✗ Failed to load pill: %s\n%!" msg
+ | Ok () ->
+ let kernel = State.get_arvo state in
+
+ Printf.printf "Searching for gate structures (depth 0-8)...\n\n";
+
+ let gates = find_gates kernel 0 8 [] in
+
+ if List.length gates = 0 then
+ Printf.printf "No gate structures found!\n\n"
+ else begin
+ Printf.printf "Found %d potential gates:\n\n" (List.length gates);
+ List.iteri (fun i (depth, path, gate) ->
+ Printf.printf "%d. At depth %d, path: [%s]\n" (i + 1) depth
+ (String.concat " " (List.map string_of_int path));
+
+ (* Try to call it *)
+ try
+ let formula = Noun.cell (Noun.atom 9)
+ (Noun.cell (Noun.atom 2)
+ (Noun.cell (Noun.atom 0) (Noun.atom 1))) in
+ let _result = Nock.nock_on gate formula in
+ Printf.printf " ✓ CALLABLE! Path to Arvo: [%s]\n\n"
+ (String.concat " " (List.map string_of_int path))
+ with e ->
+ Printf.printf " ✗ Not callable: %s\n\n" (Printexc.to_string e)
+ ) gates
+ end;
+
+ (* Also check: maybe pill is [type data] *)
+ Printf.printf "Checking if pill is a tagged pair...\n";
+ if Noun.is_cell kernel then begin
+ let tag = Noun.head kernel in
+ let payload = Noun.tail kernel in
+
+ match tag with
+ | Noun.Atom z when Z.numbits z < 32 ->
+ Printf.printf " Tag: %s\n" (Z.to_string z);
+ Printf.printf " Payload: %s\n"
+ (if Noun.is_cell payload then "Cell" else "Atom");
+
+ (* Try calling payload *)
+ if Noun.is_cell payload then begin
+ Printf.printf "\n Trying to call payload...\n";
+ try
+ let formula = Noun.cell (Noun.atom 9)
+ (Noun.cell (Noun.atom 2)
+ (Noun.cell (Noun.atom 0) (Noun.atom 1))) in
+ let _result = Nock.nock_on payload formula in
+ Printf.printf " ✓ Payload is callable!\n"
+ with e ->
+ Printf.printf " ✗ Payload not callable: %s\n" (Printexc.to_string e)
+ end
+ | _ -> Printf.printf " Not a simple tagged pair\n"
+ end
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Searching for Arvo in Pill Structure\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_pill_depth
diff --git a/ocaml/test/test_poke_formulas.ml b/ocaml/test/test_poke_formulas.ml
new file mode 100644
index 0000000..54c08ff
--- /dev/null
+++ b/ocaml/test/test_poke_formulas.ml
@@ -0,0 +1,85 @@
+(* Test Different Poke Formulas
+ *
+ * Try various Nock formulas to figure out how to call Arvo
+ *)
+
+open Nock_lib
+
+let test_formula name formula kernel event =
+ Printf.printf "Testing: %s\n" name;
+ Printf.printf " Formula: %s\n" formula;
+
+ let subject = Noun.cell event kernel in
+
+ try
+ let start = Unix.gettimeofday () in
+ let result = Nock.nock_on subject
+ (match name with
+ | "Slot 3" -> Noun.cell (Noun.atom 0) (Noun.atom 3)
+ | "Call slot 3 arm 2" ->
+ Noun.cell (Noun.atom 9)
+ (Noun.cell (Noun.atom 2)
+ (Noun.cell (Noun.atom 0) (Noun.atom 3)))
+ | "Compose [event kernel] then call" ->
+ (* [7 formula-a formula-b]: compute a, use as subject for b *)
+ Noun.cell (Noun.atom 7)
+ (Noun.cell
+ (Noun.cell (Noun.atom 0) (Noun.atom 2)) (* formula-a: get event *)
+ (Noun.cell (Noun.atom 9) (* formula-b: call arm 2 *)
+ (Noun.cell (Noun.atom 2)
+ (Noun.cell (Noun.atom 0) (Noun.atom 3))))) (* of kernel *)
+ | _ -> Noun.cell (Noun.atom 0) (Noun.atom 1)) in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf " ✓ Success in %.4fs\n" elapsed;
+ (match result with
+ | Noun.Atom z ->
+ if Z.numbits z < 20 then
+ Printf.printf " Result: Atom(%s)\n" (Z.to_string z)
+ else
+ Printf.printf " Result: Atom(large: %d bits)\n" (Z.numbits z)
+ | Noun.Cell _ -> Printf.printf " Result: Cell(...)\n");
+ Printf.printf "\n";
+ true
+
+ with e ->
+ Printf.printf " ✗ Failed: %s\n\n" (Printexc.to_string e);
+ false
+
+let test_poke_formulas env =
+ Printf.printf "🧪 Testing Different Poke Formulas\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Load ivory pill *)
+ let state = State.create () in
+ match Boot.boot_from_file ~fs state "ivory.pill" with
+ | Error msg ->
+ Printf.printf "✗ Failed to load pill: %s\n%!" msg
+ | Ok () ->
+ let kernel = State.get_arvo state in
+ let event = Noun.cell (Noun.atom 0) (Noun.atom 42) in
+
+ Printf.printf "Kernel loaded, trying different formulas...\n\n";
+
+ let formulas = [
+ ("Slot 3", "[0 3] - just return kernel");
+ ("Call slot 3 arm 2", "[9 2 0 3] - call arm 2 of kernel");
+ ("Compose [event kernel] then call", "[7 [0 2] [0 3] [9 2 0 1]]");
+ ] in
+
+ let _ = List.map (fun (name, desc) ->
+ test_formula name desc kernel event
+ ) formulas in
+
+ ()
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Testing Different Poke Formulas on Arvo\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_poke_formulas
diff --git a/ocaml/test/test_real_arvo.ml b/ocaml/test/test_real_arvo.ml
new file mode 100644
index 0000000..0c052d7
--- /dev/null
+++ b/ocaml/test/test_real_arvo.ml
@@ -0,0 +1,111 @@
+(* Extract and Test Real Arvo
+ *
+ * We found a callable gate at depth 8 - let's extract and test it!
+ *)
+
+open Nock_lib
+
+let rec navigate_to_depth noun path =
+ match path with
+ | [] -> noun
+ | slot :: rest ->
+ let next = Noun.slot (Z.of_int slot) noun in
+ navigate_to_depth next rest
+
+let test_real_arvo env =
+ Printf.printf "🎯 Testing Real Arvo Gate\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Load ivory pill *)
+ let state = State.create () in
+ match Boot.boot_from_file ~fs state "ivory.pill" with
+ | Error msg ->
+ Printf.printf "✗ Failed to load pill: %s\n%!" msg
+ | Ok () ->
+ let pill = State.get_arvo state in
+
+ (* Navigate to the callable gate we found
+ * We need to find which path leads to depth 8 callable gate
+ * Let me try common paths *)
+
+ let test_paths = [
+ ([3; 3; 2; 3; 2; 3; 3; 2], "REAL ARVO PATH");
+ ] in
+
+ Printf.printf "Trying different paths to depth 8...\n\n";
+
+ List.iter (fun (path, desc) ->
+ Printf.printf "Path %s: " desc;
+ try
+ let gate = navigate_to_depth pill path in
+
+ (* Check if it's a gate *)
+ if Noun.is_cell gate &&
+ Noun.is_cell (Noun.head gate) && (* battery is cell *)
+ Noun.is_cell (Noun.tail gate) then begin
+
+ (* Try to call it *)
+ try
+ let formula = Noun.cell (Noun.atom 9)
+ (Noun.cell (Noun.atom 2)
+ (Noun.cell (Noun.atom 0) (Noun.atom 1))) in
+ let _result = Nock.nock_on gate formula in
+ Printf.printf "✓ FOUND ARVO!\n\n";
+
+ (* Now try a real poke *)
+ Printf.printf " Testing poke with event...\n";
+ let event = Noun.cell (Noun.atom 0) (Noun.atom 42) in
+ let poke_subject = Noun.cell event gate in
+
+ (* Try different poke formulas *)
+
+ (* Formula 1: [8 gate [9 2 [0 1]]] - push gate, call arm 2 *)
+ Printf.printf " Trying formula 1: [8 gate [9 2 [0 1]]]...\n";
+ (try
+ let f1 = Noun.cell (Noun.atom 8)
+ (Noun.cell gate
+ (Noun.cell (Noun.atom 9)
+ (Noun.cell (Noun.atom 2)
+ (Noun.cell (Noun.atom 0) (Noun.atom 1))))) in
+ let _ = Nock.nock_on poke_subject f1 in
+ Printf.printf " ✓ Formula 1 works!\n"
+ with e ->
+ Printf.printf " ✗ Formula 1 failed: %s\n" (Printexc.to_string e));
+
+ (* Formula 2: [7 [[0 2] gate] [9 2 [0 1]]] - compose event with gate, call *)
+ Printf.printf " Trying formula 2: [7 [[0 2] gate] [9 2 [0 1]]]...\n";
+ let poke_formula = Noun.cell (Noun.atom 7)
+ (Noun.cell
+ (Noun.cell (Noun.cell (Noun.atom 0) (Noun.atom 2)) gate) (* [event gate] *)
+ (Noun.cell (Noun.atom 9)
+ (Noun.cell (Noun.atom 2)
+ (Noun.cell (Noun.atom 0) (Noun.atom 1))))) in (* call arm 2 *)
+
+ let start = Unix.gettimeofday () in
+ let result = Nock.nock_on poke_subject poke_formula in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf " ✓ POKE SUCCEEDED in %.4fs!\n" elapsed;
+ Printf.printf " Result is: %s\n\n"
+ (if Noun.is_cell result then "Cell (new state + effects)" else "Atom");
+
+ Printf.printf "🎉 WE CAN CALL ARVO!\n"
+ with e ->
+ Printf.printf "✗ Call failed: %s\n\n" (Printexc.to_string e)
+ end else
+ Printf.printf "not a gate\n"
+
+ with e ->
+ Printf.printf "✗ %s\n" (Printexc.to_string e)
+ ) test_paths
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Extracting and Testing Real Arvo\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_real_arvo
diff --git a/ocaml/test/test_solid_boot.ml b/ocaml/test/test_solid_boot.ml
new file mode 100644
index 0000000..08382da
--- /dev/null
+++ b/ocaml/test/test_solid_boot.ml
@@ -0,0 +1,116 @@
+(* Test Solid Pill Boot
+ *
+ * Try loading solid pill which contains full Arvo kernel
+ *)
+
+open Nock_lib
+
+let test_solid_boot env =
+ Printf.printf "🎯 Testing Solid Pill Boot\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Load solid pill *)
+ Printf.printf "Loading solid pill (this may take a while)...\n";
+ let file_path = Eio.Path.(fs / "solid.pill") in
+ let pill_bytes = Eio.Path.load file_path |> Bytes.of_string in
+
+ Printf.printf "Pill size: %.1f MB\n"
+ (float_of_int (Bytes.length pill_bytes) /. 1024.0 /. 1024.0);
+
+ let start = Unix.gettimeofday () in
+ let pill = Serial.cue pill_bytes in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf "Cued in %.2fs\n\n" elapsed;
+
+ (* Examine structure *)
+ Printf.printf "Examining solid pill structure:\n";
+ if Noun.is_cell pill then begin
+ Printf.printf " ✓ Is cell\n";
+
+ (* Check for tag *)
+ let head = Noun.head pill in
+ let tail = Noun.tail pill in
+
+ Printf.printf " Head: %s\n" (if Noun.is_cell head then "Cell" else "Atom");
+ (match head with
+ | Noun.Atom z ->
+ Printf.printf " Value: %s\n" (Z.to_string z);
+ Printf.printf " Hex: 0x%s\n" (Z.format "x" z)
+ | _ -> ());
+
+ Printf.printf " Tail: %s\n\n" (if Noun.is_cell tail then "Cell" else "Atom");
+
+ (* Try to navigate to Arvo core at known path *)
+ Printf.printf "Navigating to Arvo core at [3 3 2 3 2 3 3 2]...\n";
+ let path = [3; 3; 2; 3; 2; 3; 3; 2] in
+ let rec navigate noun = function
+ | [] -> noun
+ | slot :: rest ->
+ navigate (Noun.slot (Z.of_int slot) noun) rest
+ in
+
+ try
+ let arvo = navigate tail path in
+ Printf.printf " ✓ Found Arvo core\n\n";
+
+ (* Test for slot 23 *)
+ Printf.printf "Testing for slot 23 (poke interface)...\n";
+ (try
+ let slot_23 = Noun.slot (Z.of_int 23) arvo in
+ Printf.printf " ✓ Slot 23 exists!\n";
+ Printf.printf " Type: %s\n\n"
+ (if Noun.is_cell slot_23 then "Cell (formula)" else "Atom");
+
+ (* Try C Vere poke sequence *)
+ Printf.printf "Attempting poke sequence:\n";
+ Printf.printf " 1. Run slot 23 formula on Arvo core\n";
+
+ let start = Unix.gettimeofday () in
+ let poke_gate = Nock.nock_on arvo slot_23 in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf " ✓ Got poke gate (%.4fs)\n" elapsed;
+
+ Printf.printf " 2. Slam poke gate with test event\n";
+ let event = Noun.cell (Noun.atom 0) (Noun.atom 42) in
+
+ (* Slam: [battery [event context]] *)
+ let battery = Noun.head poke_gate in
+ let context = Noun.tail (Noun.tail poke_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
+
+ Printf.printf " 3. Call arm 2\n";
+ let start = Unix.gettimeofday () in
+ let result = Nock.nock_on new_core kick_formula in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf " ✓ Poke succeeded in %.4fs!\n" elapsed;
+ Printf.printf " Result: %s\n\n"
+ (if Noun.is_cell result then "Cell (effects + new state)" else "Atom");
+
+ Printf.printf "🎉 SOLID PILL WORKS!\n";
+ Printf.printf "We have successfully poked Arvo!\n"
+
+ with e ->
+ Printf.printf " ✗ Slot 23 test failed: %s\n" (Printexc.to_string e))
+
+ with e ->
+ Printf.printf " ✗ Navigation failed: %s\n" (Printexc.to_string e)
+
+ end else
+ Printf.printf " ✗ Not a cell\n"
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Testing Solid Pill Boot\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_solid_boot