summaryrefslogtreecommitdiff
path: root/ocaml/test
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/test')
-rw-r--r--ocaml/test/compare_events_3_4.ml161
-rw-r--r--ocaml/test/debug_event4_slam.ml155
-rw-r--r--ocaml/test/dune95
-rw-r--r--ocaml/test/examine_event3_effects.ml148
-rw-r--r--ocaml/test/examine_pill_events.ml88
-rw-r--r--ocaml/test/explore_kernel_structure.ml108
-rw-r--r--ocaml/test/inspect_boot_events.ml48
-rw-r--r--ocaml/test/inspect_event4_detail.ml132
-rw-r--r--ocaml/test/inspect_events_simple.ml88
-rw-r--r--ocaml/test/parse_solid_pill.ml190
-rw-r--r--ocaml/test/test_arvo_poke_correct.ml128
-rw-r--r--ocaml/test/test_boot_arvo_properly.ml220
-rw-r--r--ocaml/test/test_boot_with_slam.ml202
-rw-r--r--ocaml/test/test_correct_boot.ml131
-rw-r--r--ocaml/test/test_event4_slot42.ml104
-rw-r--r--ocaml/test/test_functional_bios.ml132
-rw-r--r--ocaml/test/test_life_on_bot.ml95
-rw-r--r--ocaml/test/test_slam_directly.ml108
-rw-r--r--ocaml/test/test_solid_cvere_pattern.ml129
-rw-r--r--ocaml/test/test_two_stage_boot.ml245
20 files changed, 2707 insertions, 0 deletions
diff --git a/ocaml/test/compare_events_3_4.ml b/ocaml/test/compare_events_3_4.ml
new file mode 100644
index 0000000..b134d68
--- /dev/null
+++ b/ocaml/test/compare_events_3_4.ml
@@ -0,0 +1,161 @@
+(* Compare Events 3 and 4 structures in detail *)
+
+open Nock_lib
+
+let rec describe_noun noun max_depth current_depth =
+ if current_depth > max_depth then "..."
+ else
+ match noun 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]"
+ (describe_noun h max_depth (current_depth + 1))
+ (describe_noun t max_depth (current_depth + 1))
+
+let rec to_list acc noun =
+ match noun with
+ | Noun.Atom _ -> List.rev acc
+ | Noun.Cell (item, rest) -> to_list (item :: acc) rest
+
+let compare _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
+ Printf.printf "Found %d events\n\n" (List.length event_list);
+
+ (* Compare Event 3 and Event 4 *)
+ let event3 = List.nth_opt event_list 3 in
+ let event4 = List.nth_opt event_list 4 in
+
+ begin match (event3, event4) with
+ | (Some (Noun.Cell (wire3, card3)), Some (Noun.Cell (wire4, card4))) ->
+ Printf.printf "═══════════════════════════════════════════\n";
+ Printf.printf " EVENT 3 (%%park) - SUCCEEDS\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+
+ Printf.printf "Wire structure:\n";
+ Printf.printf " %s\n\n" (describe_noun wire3 3 0);
+
+ begin match card3 with
+ | Noun.Cell (term3, data3) ->
+ Printf.printf "Card term: %s\n" (describe_noun term3 2 0);
+ begin match term3 with
+ | Noun.Atom a ->
+ let bytes = Z.to_bits a in
+ Printf.printf " ASCII: '%s'\n" bytes
+ | _ -> ()
+ end;
+
+ Printf.printf "\nCard data structure (depth 4):\n";
+ Printf.printf " %s\n\n" (describe_noun data3 4 0);
+
+ (* Try to understand data3 structure *)
+ begin match data3 with
+ | Noun.Cell (d3_h, d3_t) ->
+ Printf.printf "Data breakdown:\n";
+ Printf.printf " Head: %s\n" (describe_noun d3_h 3 0);
+ Printf.printf " Tail: %s\n" (describe_noun d3_t 3 0)
+ | _ -> ()
+ end
+
+ | _ -> Printf.printf "Card is not [term data]\n"
+ end;
+
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " EVENT 4 (%%esse) - FAILS\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+
+ Printf.printf "Wire structure:\n";
+ Printf.printf " %s\n\n" (describe_noun wire4 3 0);
+
+ begin match card4 with
+ | Noun.Cell (term4, data4) ->
+ Printf.printf "Card term: %s\n" (describe_noun term4 2 0);
+ begin match term4 with
+ | Noun.Atom a ->
+ let bytes = Z.to_bits a in
+ Printf.printf " ASCII: '%s'\n" bytes
+ | _ -> ()
+ end;
+
+ Printf.printf "\nCard data structure (depth 4):\n";
+ Printf.printf " %s\n\n" (describe_noun data4 4 0);
+
+ (* Try to understand data4 structure *)
+ begin match data4 with
+ | Noun.Cell (d4_h, d4_t) ->
+ Printf.printf "Data breakdown:\n";
+ Printf.printf " Head: %s\n" (describe_noun d4_h 3 0);
+ Printf.printf " Tail: %s\n" (describe_noun d4_t 3 0)
+ | _ -> ()
+ end
+
+ | _ -> Printf.printf "Card is not [term data]\n"
+ end;
+
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " COMPARISON\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+
+ (* Compare wire structures *)
+ let wire3_is_cell = match wire3 with Noun.Cell _ -> true | _ -> false in
+ let wire4_is_cell = match wire4 with Noun.Cell _ -> true | _ -> false in
+
+ Printf.printf "Wire types:\n";
+ Printf.printf " Event 3: %s\n" (if wire3_is_cell then "Cell (path)" else "Atom");
+ Printf.printf " Event 4: %s\n\n" (if wire4_is_cell then "Cell (path)" else "Atom");
+
+ (* Compare card structures *)
+ begin match (card3, card4) with
+ | (Noun.Cell (term3, data3), Noun.Cell (term4, data4)) ->
+ Printf.printf "Card terms:\n";
+ Printf.printf " Event 3: %s\n" (describe_noun term3 1 0);
+ Printf.printf " Event 4: %s\n\n" (describe_noun term4 1 0);
+
+ (* Compare data types *)
+ let data3_type = match data3 with Noun.Atom _ -> "Atom" | Noun.Cell _ -> "Cell" in
+ let data4_type = match data4 with Noun.Atom _ -> "Atom" | Noun.Cell _ -> "Cell" in
+
+ Printf.printf "Data types:\n";
+ Printf.printf " Event 3: %s\n" (data3_type);
+ Printf.printf " Event 4: %s\n\n" (data4_type);
+
+ Printf.printf "KEY DIFFERENCES:\n";
+ if data3_type <> data4_type then
+ Printf.printf " ⚠️ Different data types! (%s vs %s)\n" data3_type data4_type;
+
+ (* Size comparison *)
+ let rec noun_size noun =
+ match noun with
+ | Noun.Atom a -> Z.numbits a
+ | Noun.Cell (h, t) -> (noun_size h) + (noun_size t)
+ in
+ let size3 = noun_size data3 in
+ let size4 = noun_size data4 in
+ Printf.printf " Event 3 data size: %d bits\n" size3;
+ Printf.printf " Event 4 data size: %d bits\n" size4
+
+ | _ -> ()
+ end
+
+ | _ ->
+ Printf.printf "Could not extract both events\n"
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "Pill is atom\n"
+
+let () =
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " Compare Events 3 and 4\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+ Eio_main.run compare
diff --git a/ocaml/test/debug_event4_slam.ml b/ocaml/test/debug_event4_slam.ml
new file mode 100644
index 0000000..3aa2150
--- /dev/null
+++ b/ocaml/test/debug_event4_slam.ml
@@ -0,0 +1,155 @@
+(* Debug exactly what happens when we slam Event 4 *)
+
+open Nock_lib
+
+let slam_on gate event =
+ Printf.printf " Building slam...\n";
+ let battery = Noun.head gate in
+ Printf.printf " Battery: %s\n" (match battery with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
+
+ let payload = Noun.tail gate in
+ Printf.printf " Payload: %s\n" (match payload with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
+
+ let context = Noun.tail payload in
+ Printf.printf " Context (slot 7): %s\n" (match context with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
+
+ let new_core = Noun.cell battery (Noun.cell event context) in
+ Printf.printf " New core: built\n";
+
+ let kick_formula = Noun.cell (Noun.atom 9)
+ (Noun.cell (Noun.atom 2)
+ (Noun.cell (Noun.atom 0) (Noun.atom 1))) in
+ Printf.printf " Kick formula: [9 2 0 1]\n";
+
+ Printf.printf " Executing Nock...\n%!";
+ 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 debug _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 (initial kernel) *)
+ let kernel1 = List.nth event_list 1 in
+
+ (* Slam Event 3 to get kernel after Event 3 *)
+ let event3 = List.nth event_list 3 in
+
+ Printf.printf "\n=== SLAMMING EVENT 3 ===\n\n";
+ let poke_gate3 = Noun.slot (Z.of_int 23) kernel1 in
+ let now3 = Noun.atom 0 in
+ let poke_arg3 = Noun.cell now3 event3 in
+
+ let result3 = slam_on poke_gate3 poke_arg3 in
+
+ let kernel_after_3 = match result3 with
+ | Noun.Cell (_effects, new_kernel) ->
+ Printf.printf "✓ Event 3 succeeded\n\n";
+ new_kernel
+ | Noun.Atom _ ->
+ Printf.printf "✗ Event 3 returned atom\n";
+ kernel1
+ in
+
+ (* Now try Event 4 *)
+ let event4 = List.nth event_list 4 in
+
+ Printf.printf "=== SLAMMING EVENT 4 ===\n\n";
+
+ Printf.printf "Event 4 structure:\n";
+ begin match event4 with
+ | Noun.Cell (wire, card) ->
+ Printf.printf " [wire card]\n";
+ Printf.printf " Wire: %s\n" (match wire with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
+ begin match card with
+ | Noun.Cell (term, data) ->
+ Printf.printf " Card: [term data]\n";
+ Printf.printf " Term: %s\n" (match term with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
+ Printf.printf " Data: %s\n\n" (match data with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
+ | _ -> ()
+ end
+ | _ -> Printf.printf " Not [wire card]\n\n"
+ end;
+
+ Printf.printf "Kernel after Event 3:\n";
+ begin try
+ let _poke23 = Noun.slot (Z.of_int 23) kernel_after_3 in
+ Printf.printf " ✓ Has slot 23\n"
+ with _ ->
+ Printf.printf " ✗ No slot 23\n"
+ end;
+
+ begin try
+ let _poke42 = Noun.slot (Z.of_int 42) kernel_after_3 in
+ Printf.printf " ✓ Has slot 42\n\n"
+ with _ ->
+ Printf.printf " ✗ No slot 42\n\n"
+ end;
+
+ Printf.printf "Attempting Event 4 slam...\n";
+ begin try
+ let poke_gate4 = Noun.slot (Z.of_int 23) kernel_after_3 in
+ Printf.printf " ✓ Found poke gate at slot 23\n";
+
+ let now4 = Noun.atom 0 in
+ let poke_arg4 = Noun.cell now4 event4 in
+ Printf.printf " Poke arg: [now ovum]\n\n";
+
+ let result4 = slam_on poke_gate4 poke_arg4 in
+
+ begin match result4 with
+ | Noun.Cell (_effects, _new_kernel) ->
+ Printf.printf "\n🎉 EVENT 4 SUCCEEDED!\n"
+ | Noun.Atom _ ->
+ Printf.printf "\nResult is atom\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf "\n✗ Nock Exit - examining gate structure...\n\n";
+
+ (* Try to understand why it failed *)
+ begin try
+ let poke_gate4 = Noun.slot (Z.of_int 23) kernel_after_3 in
+ Printf.printf "Poke gate structure:\n";
+ begin match poke_gate4 with
+ | Noun.Cell (battery, payload) ->
+ Printf.printf " Battery: %s\n" (match battery with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
+ begin match payload with
+ | Noun.Cell (sample, context) ->
+ Printf.printf " Payload: [sample context]\n";
+ Printf.printf " Sample: %s\n" (match sample with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
+ Printf.printf " Context: %s\n" (match context with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell")
+ | _ ->
+ Printf.printf " Payload: %s (not [sample context])\n"
+ (match payload with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell")
+ end
+ | Noun.Atom _ ->
+ Printf.printf " Poke gate is an atom!\n"
+ end
+ with e ->
+ Printf.printf "Error examining gate: %s\n" (Printexc.to_string e)
+ end
+
+ | e ->
+ Printf.printf "\n✗ Error: %s\n" (Printexc.to_string e)
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "Pill is atom\n"
+
+let () =
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " Debug Event 4 Slam\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+ Eio_main.run debug
diff --git a/ocaml/test/dune b/ocaml/test/dune
index 0b43bc8..17e84b8 100644
--- a/ocaml/test/dune
+++ b/ocaml/test/dune
@@ -153,6 +153,11 @@
(libraries nock_lib eio_main unix))
(executable
+ (name test_arvo_poke_correct)
+ (modules test_arvo_poke_correct)
+ (libraries nock_lib eio_main unix))
+
+(executable
(name test_arvo_slots)
(modules test_arvo_slots)
(libraries nock_lib eio_main unix))
@@ -176,3 +181,93 @@
(name cache_solid)
(modules cache_solid)
(libraries nock_lib eio_main unix))
+
+(executable
+ (name test_boot_arvo_properly)
+ (modules test_boot_arvo_properly)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name inspect_boot_events)
+ (modules inspect_boot_events)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name inspect_events_simple)
+ (modules inspect_events_simple)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_solid_cvere_pattern)
+ (modules test_solid_cvere_pattern)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name explore_kernel_structure)
+ (modules explore_kernel_structure)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_slam_directly)
+ (modules test_slam_directly)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_boot_with_slam)
+ (modules test_boot_with_slam)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name inspect_event4_detail)
+ (modules inspect_event4_detail)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name compare_events_3_4)
+ (modules compare_events_3_4)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name examine_event3_effects)
+ (modules examine_event3_effects)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_functional_bios)
+ (modules test_functional_bios)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name debug_event4_slam)
+ (modules debug_event4_slam)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_event4_slot42)
+ (modules test_event4_slot42)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_correct_boot)
+ (modules test_correct_boot)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name parse_solid_pill)
+ (modules parse_solid_pill)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name examine_pill_events)
+ (modules examine_pill_events)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_life_on_bot)
+ (modules test_life_on_bot)
+ (libraries nock_lib eio_main unix))
+
+(executable
+ (name test_two_stage_boot)
+ (modules test_two_stage_boot)
+ (libraries nock_lib eio_main unix))
diff --git a/ocaml/test/examine_event3_effects.ml b/ocaml/test/examine_event3_effects.ml
new file mode 100644
index 0000000..de2fec3
--- /dev/null
+++ b/ocaml/test/examine_event3_effects.ml
@@ -0,0 +1,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
diff --git a/ocaml/test/examine_pill_events.ml b/ocaml/test/examine_pill_events.ml
new file mode 100644
index 0000000..8a11117
--- /dev/null
+++ b/ocaml/test/examine_pill_events.ml
@@ -0,0 +1,88 @@
+(* Examine what the bot/mod/use events actually contain *)
+
+open Nock_lib
+
+let describe_noun noun =
+ match noun with
+ | Noun.Atom a ->
+ if Z.numbits a <= 64 then
+ Printf.sprintf "Atom(%s)" (Z.to_string a)
+ else
+ Printf.sprintf "Atom(%d bits)" (Z.numbits a)
+ | Noun.Cell _ -> "Cell"
+
+let rec to_list acc noun =
+ match noun with
+ | Noun.Atom _ -> List.rev acc
+ | Noun.Cell (item, rest) -> to_list (item :: acc) rest
+
+let examine _env =
+ Printf.printf "Loading solid.noun...\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) ->
+ Printf.printf "\n=== solid.noun structure ===\n\n";
+
+ let event_list = to_list [] events in
+ Printf.printf "Total: %d items in list\n\n" (List.length event_list);
+
+ List.iteri (fun i event ->
+ Printf.printf "Item %d: %s\n" i (describe_noun event)
+ ) event_list;
+
+ (* Check if this matches what u3v_life expects *)
+ Printf.printf "\n=== Testing u3v_life on this list ===\n\n";
+
+ (* Functional BIOS formula: [2 [0 3] [0 2]] *)
+ let lyf = Noun.cell (Noun.atom 2)
+ (Noun.cell
+ (Noun.cell (Noun.atom 0) (Noun.atom 3))
+ (Noun.cell (Noun.atom 0) (Noun.atom 2))) in
+
+ Printf.printf "Running [2 [0 3] [0 2]] on events...\n%!";
+
+ begin try
+ (* What does [0 2] get from events? *)
+ let slot2 = Noun.slot (Z.of_int 2) events in
+ Printf.printf " Slot 2 of events: %s\n" (describe_noun slot2);
+
+ (* What does [0 3] get from events? *)
+ let slot3 = Noun.slot (Z.of_int 3) events in
+ Printf.printf " Slot 3 of events: %s\n\n" (describe_noun slot3);
+
+ let start = Unix.gettimeofday () in
+ let gat = Nock.nock_on events lyf in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf "✓ Formula succeeded in %.4fs!\n\n" elapsed;
+
+ (* Extract slot 7 *)
+ let kernel = Noun.slot (Z.of_int 7) gat in
+ Printf.printf "✓ Extracted kernel from slot 7\n\n";
+
+ (* Check if kernel has slot 23 *)
+ begin try
+ let _poke = Noun.slot (Z.of_int 23) kernel in
+ Printf.printf "✓ Kernel has poke at slot 23\n";
+ Printf.printf "\n🎉 This is the correct event list format!\n"
+ with _ ->
+ Printf.printf "✗ No slot 23\n"
+ end
+
+ with
+ | Not_found ->
+ Printf.printf "✗ Slot not found\n"
+ | Noun.Exit ->
+ Printf.printf "✗ Nock Exit\n"
+ | e ->
+ Printf.printf "✗ Error: %s\n" (Printexc.to_string e)
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "Pill is atom\n"
+
+let () =
+ Eio_main.run examine
diff --git a/ocaml/test/explore_kernel_structure.ml b/ocaml/test/explore_kernel_structure.ml
new file mode 100644
index 0000000..513d47f
--- /dev/null
+++ b/ocaml/test/explore_kernel_structure.ml
@@ -0,0 +1,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
diff --git a/ocaml/test/inspect_boot_events.ml b/ocaml/test/inspect_boot_events.ml
new file mode 100644
index 0000000..0a7ba92
--- /dev/null
+++ b/ocaml/test/inspect_boot_events.ml
@@ -0,0 +1,48 @@
+(* Inspect the structure of boot events *)
+
+open Nock_lib
+
+let rec inspect_noun prefix noun depth =
+ let indent = String.make (depth * 2) ' ' in
+ match noun with
+ | Noun.Atom a ->
+ if Z.numbits a <= 32 then
+ Printf.printf "%s%sAtom: %s (0x%s)\n" indent prefix
+ (Z.to_string a) (Z.format "x" a)
+ else
+ Printf.printf "%s%sAtom: large (%d bits)\n" indent prefix (Z.numbits a)
+ | Noun.Cell (h, t) ->
+ Printf.printf "%s%sCell:\n" indent prefix;
+ inspect_noun "head: " h (depth + 1);
+ inspect_noun "tail: " t (depth + 1)
+
+let rec to_list acc noun =
+ match noun with
+ | Noun.Atom _ -> List.rev acc
+ | Noun.Cell (item, rest) -> to_list (item :: acc) rest
+
+let inspect_events _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
+ Printf.printf "Found %d events\n\n" (List.length event_list);
+
+ List.iteri (fun i event ->
+ Printf.printf "═════ EVENT %d ═════\n" i;
+ inspect_noun "" event 0;
+ Printf.printf "\n"
+ ) event_list
+
+ | Noun.Atom _ ->
+ Printf.printf "✗ Pill is an atom\n"
+
+let () =
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " Inspect Boot Events Structure\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+ Eio_main.run inspect_events
diff --git a/ocaml/test/inspect_event4_detail.ml b/ocaml/test/inspect_event4_detail.ml
new file mode 100644
index 0000000..4f4f30a
--- /dev/null
+++ b/ocaml/test/inspect_event4_detail.ml
@@ -0,0 +1,132 @@
+(* Inspect Event 4 in detail *)
+
+open Nock_lib
+
+let to_atom_if_small noun =
+ match noun 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(large, %d bits)" (Z.numbits a)
+ | Noun.Cell _ -> "Cell"
+
+let rec to_list acc noun =
+ match noun with
+ | Noun.Atom _ -> List.rev acc
+ | Noun.Cell (item, rest) -> to_list (item :: acc) rest
+
+let inspect _env =
+ 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
+
+ (* Event 3 *)
+ Printf.printf "=== EVENT 3 ===\n\n";
+ begin match List.nth_opt event_list 3 with
+ | Some (Noun.Cell (wire, card)) ->
+ Printf.printf "Event 3: [wire card]\n\n";
+
+ Printf.printf "Wire:\n";
+ Printf.printf " %s\n" (to_atom_if_small wire);
+
+ (* If wire is a cell (path), show first few elements *)
+ begin match wire with
+ | Noun.Cell (w1, rest1) ->
+ Printf.printf " Head: %s\n" (to_atom_if_small w1);
+ begin match rest1 with
+ | Noun.Cell (w2, rest2) ->
+ Printf.printf " [1]: %s\n" (to_atom_if_small w2);
+ begin match rest2 with
+ | Noun.Cell (w3, _) ->
+ Printf.printf " [2]: %s\n" (to_atom_if_small w3)
+ | Noun.Atom a ->
+ Printf.printf " Tail: Atom(%s)\n" (Z.to_string a)
+ end
+ | Noun.Atom a ->
+ Printf.printf " Tail: Atom(%s)\n" (Z.to_string a)
+ end
+ | Noun.Atom _ -> ()
+ end;
+
+ Printf.printf "\nCard:\n";
+ begin match card with
+ | Noun.Cell (term, data) ->
+ Printf.printf " [term data]\n";
+ Printf.printf " Term: %s\n" (to_atom_if_small term);
+ (* Try to convert term to ASCII *)
+ begin match term with
+ | Noun.Atom a when Z.numbits a <= 32 ->
+ let bytes = Z.to_bits a in
+ Printf.printf " Term ASCII: '%s'\n" bytes
+ | _ -> ()
+ end;
+ Printf.printf " Data: %s\n" (to_atom_if_small data)
+ | Noun.Atom a ->
+ Printf.printf " Atom: %s\n" (Z.to_string a)
+ end
+
+ | _ -> Printf.printf "Event 3 not found or wrong format\n"
+ end;
+
+ Printf.printf "\n═══════════════════════════════════════\n\n";
+
+ (* Event 4 *)
+ Printf.printf "=== EVENT 4 ===\n\n";
+ begin match List.nth_opt event_list 4 with
+ | Some (Noun.Cell (wire, card)) ->
+ Printf.printf "Event 4: [wire card]\n\n";
+
+ Printf.printf "Wire:\n";
+ Printf.printf " %s\n" (to_atom_if_small wire);
+
+ begin match wire with
+ | Noun.Cell (w1, rest1) ->
+ Printf.printf " Head: %s\n" (to_atom_if_small w1);
+ begin match rest1 with
+ | Noun.Cell (w2, rest2) ->
+ Printf.printf " [1]: %s\n" (to_atom_if_small w2);
+ begin match rest2 with
+ | Noun.Cell (w3, _) ->
+ Printf.printf " [2]: %s\n" (to_atom_if_small w3)
+ | Noun.Atom a ->
+ Printf.printf " Tail: Atom(%s)\n" (Z.to_string a)
+ end
+ | Noun.Atom a ->
+ Printf.printf " Tail: Atom(%s)\n" (Z.to_string a)
+ end
+ | Noun.Atom _ -> ()
+ end;
+
+ Printf.printf "\nCard:\n";
+ begin match card with
+ | Noun.Cell (term, data) ->
+ Printf.printf " [term data]\n";
+ Printf.printf " Term: %s\n" (to_atom_if_small term);
+ (* Try to convert term to ASCII *)
+ begin match term with
+ | Noun.Atom a when Z.numbits a <= 32 ->
+ let bytes = Z.to_bits a in
+ Printf.printf " Term ASCII: '%s'\n" bytes
+ | _ -> ()
+ end;
+ Printf.printf " Data: %s\n" (to_atom_if_small data)
+ | Noun.Atom a ->
+ Printf.printf " Atom: %s\n" (Z.to_string a)
+ end
+
+ | _ -> Printf.printf "Event 4 not found or wrong format\n"
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "Pill is atom\n"
+
+let () =
+ Printf.printf "\n═══════════════════════════════════════\n";
+ Printf.printf " Inspect Events 3 and 4 in Detail\n";
+ Printf.printf "═══════════════════════════════════════\n\n";
+ Eio_main.run inspect
diff --git a/ocaml/test/inspect_events_simple.ml b/ocaml/test/inspect_events_simple.ml
new file mode 100644
index 0000000..0cb05c9
--- /dev/null
+++ b/ocaml/test/inspect_events_simple.ml
@@ -0,0 +1,88 @@
+(* Simple event structure inspector *)
+
+open Nock_lib
+
+let describe_noun noun =
+ match noun with
+ | Noun.Atom a ->
+ if Z.numbits a <= 32 then
+ Printf.sprintf "Atom(%s)" (Z.to_string a)
+ else
+ Printf.sprintf "Atom(large, %d bits)" (Z.numbits a)
+ | Noun.Cell _ -> "Cell"
+
+let rec to_list acc noun =
+ match noun with
+ | Noun.Atom _ -> List.rev acc
+ | Noun.Cell (item, rest) -> to_list (item :: acc) rest
+
+let inspect_events _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) ->
+ Printf.printf "Tag: %s\n\n" (describe_noun tag);
+
+ let event_list = to_list [] events in
+ Printf.printf "Found %d events\n\n" (List.length event_list);
+
+ List.iteri (fun i event ->
+ Printf.printf "Event %d: " i;
+ match event with
+ | Noun.Atom a ->
+ Printf.printf "Atom(%s)\n" (Z.to_string a)
+ | Noun.Cell (head, tail) ->
+ Printf.printf "Cell[%s, %s]\n"
+ (describe_noun head) (describe_noun tail)
+ ) event_list;
+
+ (* Look more closely at events 3 and 4 *)
+ Printf.printf "\n=== Detailed look at events 3 and 4 ===\n\n";
+
+ begin match List.nth_opt event_list 3 with
+ | Some (Noun.Cell (wire, card)) ->
+ Printf.printf "Event 3:\n";
+ Printf.printf " wire: %s\n" (describe_noun wire);
+ Printf.printf " card: ";
+ begin match card with
+ | Noun.Cell (term, data) ->
+ Printf.printf "Cell[%s, %s]\n"
+ (describe_noun term) (describe_noun data)
+ | Noun.Atom _ ->
+ Printf.printf "%s\n" (describe_noun card)
+ end
+ | Some (Noun.Atom _) ->
+ Printf.printf "Event 3 is an atom\n"
+ | None ->
+ Printf.printf "No event 3\n"
+ end;
+
+ begin match List.nth_opt event_list 4 with
+ | Some (Noun.Cell (wire, card)) ->
+ Printf.printf "\nEvent 4:\n";
+ Printf.printf " wire: %s\n" (describe_noun wire);
+ Printf.printf " card: ";
+ begin match card with
+ | Noun.Cell (term, data) ->
+ Printf.printf "Cell[%s, %s]\n"
+ (describe_noun term) (describe_noun data)
+ | Noun.Atom _ ->
+ Printf.printf "%s\n" (describe_noun card)
+ end
+ | Some (Noun.Atom _) ->
+ Printf.printf "Event 4 is an atom\n"
+ | None ->
+ Printf.printf "No event 4\n"
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "✗ Pill is an atom\n"
+
+let () =
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " Simple Event Structure Inspector\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+ Eio_main.run inspect_events
diff --git a/ocaml/test/parse_solid_pill.ml b/ocaml/test/parse_solid_pill.ml
new file mode 100644
index 0000000..ef10785
--- /dev/null
+++ b/ocaml/test/parse_solid_pill.ml
@@ -0,0 +1,190 @@
+(* Parse solid pill structure to extract [bot mod use] *)
+
+open Nock_lib
+
+let rec to_list acc noun =
+ match noun with
+ | Noun.Atom _ -> List.rev acc
+ | Noun.Cell (item, rest) -> to_list (item :: acc) rest
+
+let parse_pill _env =
+ Printf.printf "═══════════════════════════════════════\n";
+ Printf.printf " Parsing Solid Pill Structure\n";
+ Printf.printf "═══════════════════════════════════════\n\n";
+
+ (* Load the pill *)
+ let in_channel = open_in_bin "solid.noun" in
+ let pill = (Marshal.from_channel in_channel : Noun.noun) in
+ close_in in_channel;
+
+ (* According to C Vere mars.c:1560, solid pill structure is:
+ * First we cue pil_p (the jammed pill data)
+ * Then we expect: [tag dat]
+ * Where:
+ * tag = %pill or %cash
+ * dat = [type [bot mod use]] or [[cache] [type [bot mod use]]]
+ *)
+
+ Printf.printf "Step 1: Check outer structure\n";
+ match pill with
+ | Noun.Cell (tag, rest) ->
+ Printf.printf " ✓ Pill is a cell [tag rest]\n";
+
+ (* Check what the tag is *)
+ begin match tag with
+ | Noun.Atom z ->
+ let tag_str =
+ try
+ let bytes = Z.to_bits z in
+ let len = String.length bytes in
+ if len > 0 && len <= 20 then
+ String.sub bytes 0 (min len 20)
+ else "too-long"
+ with _ -> "non-ascii"
+ in
+ Printf.printf " Tag (atom): %s\n" tag_str;
+ Printf.printf " Tag (hex): %s\n\n" (Z.format "x" z);
+ | Noun.Cell _ ->
+ Printf.printf " Tag is a cell (unexpected!)\n\n"
+ end;
+
+ (* Now parse rest based on structure *)
+ Printf.printf "Step 2: Parse pill contents\n";
+
+ (* Try to extract as [type [bot mod use]] *)
+ begin match rest with
+ | Noun.Cell (typ, rest2) ->
+ Printf.printf " ✓ rest = [type rest2]\n";
+
+ begin match typ with
+ | Noun.Atom z ->
+ let typ_str =
+ try
+ let bytes = Z.to_bits z in
+ String.sub bytes 0 (min (String.length bytes) 20)
+ with _ -> "non-ascii"
+ in
+ Printf.printf " Type: %s\n\n" typ_str;
+ | Noun.Cell _ ->
+ Printf.printf " Type is cell\n\n"
+ end;
+
+ (* Now try to parse rest2 as [bot mod use] *)
+ begin match rest2 with
+ | Noun.Cell (bot, rest3) ->
+ Printf.printf " ✓ Found bot (boot events)\n";
+ let bot_list = to_list [] bot in
+ Printf.printf " Bot has %d events\n" (List.length bot_list);
+
+ begin match rest3 with
+ | Noun.Cell (mod_, rest4) ->
+ Printf.printf " ✓ Found mod (module events)\n";
+ let mod_list = to_list [] mod_ in
+ Printf.printf " Mod has %d events\n" (List.length mod_list);
+
+ begin match rest4 with
+ | Noun.Cell (use, _) ->
+ Printf.printf " ✓ Found use (userspace events)\n";
+ let use_list = to_list [] use in
+ Printf.printf " Use has %d events\n\n" (List.length use_list);
+
+ (* Total events *)
+ let total = List.length bot_list + List.length mod_list + List.length use_list in
+ Printf.printf "═══════════════════════════════════════\n";
+ Printf.printf " Summary\n";
+ Printf.printf "═══════════════════════════════════════\n\n";
+ Printf.printf "Total events: %d\n" total;
+ Printf.printf " Bot: %d events (lifecycle)\n" (List.length bot_list);
+ Printf.printf " Mod: %d events (vanes)\n" (List.length mod_list);
+ Printf.printf " Use: %d events (apps)\n\n" (List.length use_list);
+
+ (* Concatenate all events *)
+ let all_events = bot_list @ mod_list @ use_list in
+ Printf.printf "Creating full event list...\n";
+
+ (* Convert list back to noun list (NOT a proper list yet) *)
+ let rec make_noun_list events =
+ match events with
+ | [] -> Noun.atom 0 (* null terminator *)
+ | [e] -> Noun.cell e (Noun.atom 0)
+ | e :: rest -> Noun.cell e (make_noun_list rest)
+ in
+
+ let event_noun = make_noun_list all_events in
+ Printf.printf "✓ Event list created\n\n";
+
+ (* Now test functional BIOS formula! *)
+ Printf.printf "═══════════════════════════════════════\n";
+ Printf.printf " Testing Functional BIOS Formula\n";
+ Printf.printf "═══════════════════════════════════════\n\n";
+
+ Printf.printf "Formula: [2 [0 3] [0 2]]\n";
+ Printf.printf "Subject: %d-event list\n\n" total;
+
+ (* Build lifecycle formula: [2 [0 3] [0 2]] *)
+ let lyf = Noun.cell (Noun.atom 2)
+ (Noun.cell
+ (Noun.cell (Noun.atom 0) (Noun.atom 3))
+ (Noun.cell (Noun.atom 0) (Noun.atom 2))) in
+
+ Printf.printf "Running formula...\n%!";
+
+ begin try
+ let start = Unix.gettimeofday () in
+ let gat = Nock.nock_on event_noun lyf in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf "✓ Formula completed in %.4fs!\n\n" elapsed;
+
+ (* Extract slot 7 *)
+ Printf.printf "Extracting kernel from slot 7...\n";
+ let kernel = Noun.slot (Z.of_int 7) gat in
+
+ Printf.printf "✓ Kernel extracted!\n\n";
+
+ Printf.printf "═══════════════════════════════════════\n";
+ Printf.printf " 🎉 SUCCESS! Functional BIOS Works! 🎉\n";
+ Printf.printf "═══════════════════════════════════════\n\n";
+
+ Printf.printf "The kernel has been computed from the event list\n";
+ Printf.printf "using the functional BIOS formula.\n\n";
+
+ (* Check kernel has slot 23 *)
+ begin try
+ let _poke = Noun.slot (Z.of_int 23) kernel in
+ Printf.printf "✓ Kernel has poke gate at slot 23\n"
+ with _ ->
+ Printf.printf "✗ No slot 23 in kernel\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf "✗ Formula failed (Nock Exit)\n"
+ | e ->
+ Printf.printf "✗ Error: %s\n" (Printexc.to_string e)
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf " ✗ rest4 is atom (expected use)\n"
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf " ✗ rest3 is atom (expected [mod use])\n"
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf " ✗ rest2 is atom (expected [bot mod use])\n"
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf " ✗ rest is atom\n"
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "✗ Pill is an atom (expected cell)\n"
+
+let () =
+ Printf.printf "\n═══════════════════════════════════════\n";
+ Printf.printf " Parse Solid Pill Structure\n";
+ Printf.printf "═══════════════════════════════════════\n\n";
+ Eio_main.run parse_pill
diff --git a/ocaml/test/test_arvo_poke_correct.ml b/ocaml/test/test_arvo_poke_correct.ml
new file mode 100644
index 0000000..23259b9
--- /dev/null
+++ b/ocaml/test/test_arvo_poke_correct.ml
@@ -0,0 +1,128 @@
+(* Test Arvo poke with CORRECT interface from docs *)
+
+open Nock_lib
+
+let extract_arvo () =
+ Printf.printf "Loading Arvo from 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;
+
+ (* Extract event 1 - the initial kernel *)
+ match pill with
+ | Noun.Cell (_tag, events) ->
+ let rec nth n noun =
+ match noun with
+ | Noun.Atom _ -> None
+ | Noun.Cell (item, rest) ->
+ if n = 0 then Some item else nth (n - 1) rest
+ in
+ begin match nth 1 events with
+ | Some (Noun.Cell (_wire, card)) -> Some card
+ | _ -> None
+ end
+ | _ -> None
+
+let test_poke _env =
+ Printf.printf "🎯 Testing Arvo Poke (Correct Interface)\n\n";
+ Printf.printf "Based on docs/runtime/api.md:\n";
+ Printf.printf " ++ poke |/ {now/@da ovo/ovum} :: 42\n";
+ Printf.printf " ++ ovum {p/wire q/card}\n";
+ Printf.printf " ++ card {p/@tas q/*}\n\n";
+
+ match extract_arvo () with
+ | None -> Printf.printf "✗ Failed to extract Arvo\n"
+ | Some arvo ->
+ try
+ (* The poke gate is at AXIS 42, not 23! *)
+ Printf.printf "Looking for poke gate at axis 42...\n";
+ let poke_gate = Noun.slot (Z.of_int 42) arvo in
+ Printf.printf "✓ Found poke gate at axis 42!\n\n";
+
+ (* Build proper ovum: [wire card] *)
+ (* wire = / (empty path, represented as 0) *)
+ (* card = [term data] = [%test 42] *)
+ Printf.printf "Building ovum: [wire card]\n";
+ Printf.printf " wire: / (atom 0)\n";
+ Printf.printf " card: [%%test 42]\n";
+
+ let wire = Noun.atom 0 in (* / path *)
+ let term_test = Noun.Atom (Z.of_string "1953719668") in (* 'test' as atom *)
+ let data = Noun.atom 42 in
+ let card = Noun.cell term_test data in
+ let ovum = Noun.cell wire card in
+
+ Printf.printf "\nBuilding poke arguments: [now ovum]\n";
+ (* now = current time as @da (atom) - use a fake timestamp *)
+ let now = Noun.atom 0 in (* epoch *)
+ let poke_arg = Noun.cell now ovum in
+
+ Printf.printf " now: 0 (epoch)\n";
+ Printf.printf " ovum: [0 [1953719668 42]]\n\n";
+
+ (* Build subject for gate call: [sample gate] *)
+ (* Standard gate call: [9 2 [0 2] [0 3]] *)
+ Printf.printf "Calling poke gate...\n";
+ let subject = Noun.cell poke_arg poke_gate in
+ let formula = Noun.cell
+ (Noun.atom 9)
+ (Noun.cell
+ (Noun.atom 2)
+ (Noun.cell
+ (Noun.cell (Noun.atom 0) (Noun.atom 2))
+ (Noun.cell (Noun.atom 0) (Noun.atom 3))))
+ in
+
+ let start = Unix.gettimeofday () in
+ let result = Nock.nock_on subject formula in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf "✓ Poke succeeded in %.4fs!\n\n" elapsed;
+
+ (* Parse result: [effects new-kernel] *)
+ begin match result with
+ | Noun.Cell (effects, new_kernel) ->
+ Printf.printf "Result: [effects new-kernel]\n";
+ Printf.printf " Effects: %s\n"
+ (match effects with Noun.Atom _ -> "atom/nil" | Noun.Cell _ -> "cell/list");
+ Printf.printf " New kernel: %s\n\n"
+ (match new_kernel with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
+
+ (* Verify new kernel still has poke gate *)
+ begin try
+ let _new_poke = Noun.slot (Z.of_int 42) new_kernel in
+ Printf.printf "✓ New kernel has poke gate at axis 42\n\n";
+ Printf.printf "🎉 ARVO POKE IS FULLY WORKING!\n\n";
+ Printf.printf "This means we can:\n";
+ Printf.printf " ✅ Send events to Arvo\n";
+ Printf.printf " ✅ Receive effects (output events)\n";
+ Printf.printf " ✅ Get updated kernel state\n";
+ Printf.printf " ✅ Build a complete Urbit runtime!\n"
+ with _ ->
+ Printf.printf "⚠️ New kernel missing poke gate\n"
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "Result is an atom (unexpected)\n";
+ Printf.printf "This might mean the gate signature doesn't match\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf "✗ Nock failed (Exit)\n\n";
+ Printf.printf "Possible issues:\n";
+ Printf.printf " - Event format still wrong\n";
+ Printf.printf " - Gate formula incorrect\n";
+ Printf.printf " - Arvo kernel not fully initialized\n"
+ | Not_found ->
+ Printf.printf "✗ No gate at axis 42\n";
+ Printf.printf "This kernel might not be Arvo\n"
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Test Arvo Poke (Correct Interface from Docs)\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_poke
diff --git a/ocaml/test/test_boot_arvo_properly.ml b/ocaml/test/test_boot_arvo_properly.ml
new file mode 100644
index 0000000..559264f
--- /dev/null
+++ b/ocaml/test/test_boot_arvo_properly.ml
@@ -0,0 +1,220 @@
+(* Boot Arvo properly through all 5 solid pill events *)
+
+open Nock_lib
+
+let boot_arvo _env =
+ Printf.printf "🚀 Booting Arvo Through All 5 Events\n\n";
+
+ (* Load solid pill *)
+ 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\n\n";
+
+ match pill with
+ | Noun.Cell (_tag, events) ->
+ (* Convert to list *)
+ let rec to_list acc noun =
+ match noun with
+ | Noun.Atom _ -> List.rev acc
+ | Noun.Cell (item, rest) -> to_list (item :: acc) rest
+ in
+
+ let event_list = to_list [] events in
+ Printf.printf "Found %d events\n\n" (List.length event_list);
+
+ (* Start with no kernel *)
+ let kernel = ref None in
+
+ (* Process each event *)
+ List.iteri (fun i event ->
+ Printf.printf "=== Event %d ===\n" i;
+
+ match event with
+ | Noun.Atom a ->
+ Printf.printf "Atom: %s\n" (Z.to_string a);
+ if i = 0 then
+ Printf.printf " (Boot sequence tag)\n"
+ else if i = 2 then
+ Printf.printf " (Separator)\n";
+ Printf.printf "\n"
+
+ | Noun.Cell _ ->
+ if i = 1 then begin
+ (* Event 1: The kernel itself (not wrapped in [wire card]) *)
+ Printf.printf "Cell: Initial kernel\n";
+ Printf.printf " → Setting as kernel\n";
+ kernel := Some event; (* The whole event IS the kernel *)
+
+ (* Verify it has poke gate at axis 42 *)
+ begin try
+ let _gate = Noun.slot (Z.of_int 42) event in
+ Printf.printf " ✓ Has poke gate at axis 42\n"
+ with _ ->
+ Printf.printf " ✗ No poke gate found\n"
+ end;
+ Printf.printf "\n"
+
+ end else if i > 1 then begin
+ (* Events 3 and 4: Boot events as [wire card] *)
+ Printf.printf "Cell: [wire card]\n";
+ match !kernel with
+ | None ->
+ Printf.printf " ✗ No kernel to poke yet\n\n"
+
+ | Some k ->
+ Printf.printf " → Poking kernel with event\n";
+
+ try
+ (* Get poke gate at axis 42 *)
+ let poke_gate = Noun.slot (Z.of_int 42) k in
+ Printf.printf " Found poke gate at axis 42\n";
+
+ (* Build poke arguments: [now ovum] *)
+ (* ovum is the event itself: [wire card] *)
+ let now = Noun.atom 0 in (* Use epoch for now *)
+ let ovum = event in
+ let poke_arg = Noun.cell now ovum in
+
+ (* Build subject: [sample gate] *)
+ let subject = Noun.cell poke_arg poke_gate in
+
+ (* Standard gate call: [9 2 [0 2] [0 3]] *)
+ let formula = Noun.cell
+ (Noun.atom 9)
+ (Noun.cell
+ (Noun.atom 2)
+ (Noun.cell
+ (Noun.cell (Noun.atom 0) (Noun.atom 2))
+ (Noun.cell (Noun.atom 0) (Noun.atom 3))))
+ in
+
+ Printf.printf " Executing poke...\n%!";
+ let start = Unix.gettimeofday () in
+ let result = Nock.nock_on subject formula in
+ let elapsed = Unix.gettimeofday () -. start in
+ Printf.printf " ✓ Completed in %.3fs\n" elapsed;
+
+ (* Parse result: [effects new-kernel] *)
+ begin match result with
+ | Noun.Cell (effects, new_kernel) ->
+ Printf.printf " Result: [effects new-kernel]\n";
+
+ (* Count effects *)
+ let rec count_list n noun =
+ match noun with
+ | Noun.Atom _ -> n
+ | Noun.Cell (_, rest) -> count_list (n + 1) rest
+ in
+ let effect_count = count_list 0 effects in
+ Printf.printf " Effects: %d\n" effect_count;
+
+ (* Update kernel *)
+ kernel := Some new_kernel;
+ Printf.printf " ✓ Kernel updated\n"
+
+ | Noun.Atom _ ->
+ Printf.printf " ✗ Result is atom (unexpected)\n"
+ end;
+
+ Printf.printf "\n"
+
+ with
+ | Noun.Exit ->
+ Printf.printf " ✗ Nock execution failed (Exit)\n";
+ Printf.printf " This event might not be in the right format\n";
+ Printf.printf "\n"
+ | Not_found ->
+ Printf.printf " ✗ No poke gate at axis 42\n\n"
+ end
+ ) event_list;
+
+ (* Final kernel check *)
+ Printf.printf "═══════════════════════════════════════════════════════\n\n";
+
+ begin match !kernel with
+ | None ->
+ Printf.printf "✗ No final kernel\n"
+
+ | Some k ->
+ Printf.printf "🎉 Arvo Boot Complete!\n\n";
+
+ (* Verify poke gate *)
+ begin try
+ let _gate = Noun.slot (Z.of_int 42) k in
+ Printf.printf "✓ Final kernel has poke gate at axis 42\n\n";
+
+ (* Try a test poke! *)
+ Printf.printf "Testing final kernel with a poke...\n";
+
+ let poke_gate = Noun.slot (Z.of_int 42) k in
+
+ (* Build test ovum: [wire card] *)
+ let wire = Noun.atom 0 in (* / *)
+ let term_test = Noun.Atom (Z.of_string "1953719668") in (* 'test' *)
+ let data = Noun.atom 42 in
+ let card = Noun.cell term_test data in
+ let ovum = Noun.cell wire card in
+
+ let now = Noun.atom 0 in
+ let poke_arg = Noun.cell now ovum in
+
+ let subject = Noun.cell poke_arg poke_gate in
+ let formula = Noun.cell
+ (Noun.atom 9)
+ (Noun.cell
+ (Noun.atom 2)
+ (Noun.cell
+ (Noun.cell (Noun.atom 0) (Noun.atom 2))
+ (Noun.cell (Noun.atom 0) (Noun.atom 3))))
+ in
+
+ Printf.printf " Poking with test event [0 [%%test 42]]...\n%!";
+ let start = Unix.gettimeofday () in
+ let result = Nock.nock_on subject formula in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf " ✓ Poke succeeded in %.4fs!\n\n" elapsed;
+
+ begin match result with
+ | Noun.Cell (effects, new_kernel) ->
+ let rec count_list n noun =
+ match noun with
+ | Noun.Atom _ -> n
+ | Noun.Cell (_, rest) -> count_list (n + 1) rest
+ in
+ Printf.printf " Effects produced: %d\n" (count_list 0 effects);
+ Printf.printf " New kernel: %s\n\n"
+ (match new_kernel with Noun.Cell _ -> "cell ✓" | Noun.Atom _ -> "atom");
+
+ Printf.printf "🎊 ARVO IS FULLY OPERATIONAL! 🎊\n\n";
+ Printf.printf "We can now:\n";
+ Printf.printf " ✅ Send events to Arvo\n";
+ Printf.printf " ✅ Receive effects\n";
+ Printf.printf " ✅ Update kernel state\n";
+ Printf.printf " ✅ Build a complete Urbit runtime!\n"
+
+ | Noun.Atom _ ->
+ Printf.printf " Result is atom (unexpected)\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf "✗ Test poke failed\n"
+ | Not_found ->
+ Printf.printf "✗ No poke gate in final kernel\n"
+ end
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "✗ Pill is an atom\n"
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf " Boot Arvo Properly Through All Events\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n";
+ Printf.printf "\n";
+
+ Eio_main.run boot_arvo
diff --git a/ocaml/test/test_boot_with_slam.ml b/ocaml/test/test_boot_with_slam.ml
new file mode 100644
index 0000000..c87c5c8
--- /dev/null
+++ b/ocaml/test/test_boot_with_slam.ml
@@ -0,0 +1,202 @@
+(* Boot Arvo using slam on slot 23 *)
+
+open Nock_lib
+
+let slam_on gate event =
+ (* C Vere slam_on: [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 arm 2: [9 2 0 1] *)
+ 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 boot_arvo _env =
+ Printf.printf "🚀 Booting Arvo with Slot 23 Slam\n\n";
+
+ (* Load solid pill *)
+ 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
+ Printf.printf "Found %d events\n\n" (List.length event_list);
+
+ (* Event 1 is the initial kernel *)
+ let kernel = ref None in
+
+ List.iteri (fun i event ->
+ Printf.printf "=== Event %d ===\n" i;
+
+ match event with
+ | Noun.Atom a ->
+ Printf.printf "Atom: %s\n\n" (Z.to_string a)
+
+ | Noun.Cell _ ->
+ if i = 1 then begin
+ (* Event 1: Initial larval kernel *)
+ Printf.printf "Initial larval kernel\n";
+ kernel := Some event;
+
+ (* Verify slot 23 exists *)
+ begin try
+ let _poke = Noun.slot (Z.of_int 23) event in
+ Printf.printf " ✓ Has poke gate at slot 23\n\n"
+ with _ ->
+ Printf.printf " ✗ No poke at slot 23\n\n"
+ end
+
+ end else if i > 2 then begin
+ (* Events 3-4: Larval initialization events *)
+ Printf.printf "Boot event (ovum)\n";
+
+ match !kernel with
+ | None ->
+ Printf.printf " ✗ No kernel yet\n\n"
+
+ | Some k ->
+ begin try
+ let poke_gate = Noun.slot (Z.of_int 23) k in
+
+ (* Build poke args: [now ovum] *)
+ (* The event itself should be the ovum [wire card] *)
+ let now = Noun.atom 0 in
+ let ovum = event in
+ let poke_arg = Noun.cell now ovum in
+
+ Printf.printf " → Slamming poke at slot 23...\n";
+ let start = Unix.gettimeofday () in
+ let result = slam_on poke_gate poke_arg in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf " ✓ Poke succeeded in %.4fs!\n" elapsed;
+
+ (* Parse result: [effects new-kernel] *)
+ begin match result with
+ | Noun.Cell (_effects, new_kernel) ->
+ Printf.printf " Result: [effects new-kernel]\n";
+
+ (* Update kernel *)
+ kernel := Some new_kernel;
+ Printf.printf " ✓ Kernel updated\n"
+
+ | Noun.Atom _ ->
+ Printf.printf " ✗ Result is atom (unexpected)\n"
+ end;
+
+ Printf.printf "\n"
+
+ with
+ | Noun.Exit ->
+ Printf.printf " ✗ Poke failed (Nock Exit)\n\n"
+ | e ->
+ Printf.printf " ✗ Error: %s\n\n" (Printexc.to_string e)
+ end
+ end else begin
+ Printf.printf "Separator/other\n\n"
+ end
+ ) event_list;
+
+ (* Test final kernel *)
+ Printf.printf "═══════════════════════════════════════\n\n";
+
+ begin match !kernel with
+ | None ->
+ Printf.printf "✗ No final kernel\n"
+
+ | Some k ->
+ Printf.printf "🎉 Boot Complete!\n\n";
+
+ (* Check which slots exist in final kernel *)
+ Printf.printf "Checking final kernel:\n";
+ begin try
+ let _poke23 = Noun.slot (Z.of_int 23) k in
+ Printf.printf " ✓ Has slot 23 (larval poke)\n"
+ with _ ->
+ Printf.printf " ✗ No slot 23\n"
+ end;
+
+ begin try
+ let _poke42 = Noun.slot (Z.of_int 42) k in
+ Printf.printf " ✓ Has slot 42 (adult poke)\n"
+ with _ ->
+ Printf.printf " ✗ No slot 42\n"
+ end;
+
+ Printf.printf "\nTrying test poke on slot 42...\n";
+
+ (* Try slot 42 (adult Arvo) *)
+ begin try
+ let poke_gate = Noun.slot (Z.of_int 42) k in
+ let wire = Noun.atom 0 in
+ let card = Noun.cell (Noun.atom 1953719668) (Noun.atom 42) in
+ let ovum = Noun.cell wire card in
+ let now = Noun.atom 0 in
+ let poke_arg = Noun.cell now ovum in
+
+ Printf.printf " Slamming slot 42...\n";
+ let result = slam_on poke_gate poke_arg in
+
+ begin match result with
+ | Noun.Cell _ ->
+ Printf.printf " 🎊 SLOT 42 WORKS! ARVO IS RUNNING!\n"
+ | Noun.Atom _ ->
+ Printf.printf " Result is atom\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf " ✗ Slot 42 poke failed (Nock Exit)\n"
+ | e ->
+ Printf.printf " ✗ Error: %s\n" (Printexc.to_string e)
+ end;
+
+ Printf.printf "\nTrying test poke on slot 23...\n";
+
+ (* Also try slot 23 *)
+ begin try
+ let poke_gate = Noun.slot (Z.of_int 23) k in
+ let wire = Noun.atom 0 in
+ let card = Noun.cell (Noun.atom 1953719668) (Noun.atom 42) in
+ let ovum = Noun.cell wire card in
+ let now = Noun.atom 0 in
+ let poke_arg = Noun.cell now ovum in
+
+ Printf.printf " Slamming slot 23...\n";
+ let result = slam_on poke_gate poke_arg in
+
+ begin match result with
+ | Noun.Cell _ ->
+ Printf.printf " ✓ Slot 23 also works!\n"
+ | Noun.Atom _ ->
+ Printf.printf " Result is atom\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf " ✗ Slot 23 poke failed (Nock Exit)\n"
+ | e ->
+ Printf.printf " ✗ Error: %s\n" (Printexc.to_string e)
+ end
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "✗ Pill is atom\n"
+
+let () =
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " Boot Arvo with Slot 23 Slam\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+ Eio_main.run boot_arvo
diff --git a/ocaml/test/test_correct_boot.ml b/ocaml/test/test_correct_boot.ml
new file mode 100644
index 0000000..c778d1b
--- /dev/null
+++ b/ocaml/test/test_correct_boot.ml
@@ -0,0 +1,131 @@
+(* Boot using the CORRECT C Vere pattern: compute gates from formulas *)
+
+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 boot _env =
+ Printf.printf "🚀 Booting Arvo with CORRECT C Vere Pattern\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
+ let kernel = ref (List.nth event_list 1) in
+
+ Printf.printf "Initial kernel loaded\n\n";
+
+ (* Process Events 3 and 4 *)
+ List.iteri (fun i event ->
+ if i >= 3 && i <= 4 then begin
+ Printf.printf "═══ Event %d ═══\n" i;
+
+ (* Step 1: Get formula at slot 23 *)
+ Printf.printf "Step 1: Get formula at slot 23...\n";
+ let slot_23_formula = Noun.slot (Z.of_int 23) !kernel in
+ Printf.printf " ✓ Got formula\n";
+
+ (* Step 2: Compute poke gate by running formula *)
+ Printf.printf "Step 2: Compute poke gate...\n";
+ let start_compute = Unix.gettimeofday () in
+ let poke_gate = Nock.nock_on !kernel slot_23_formula in
+ let elapsed_compute = Unix.gettimeofday () -. start_compute in
+ Printf.printf " ✓ Computed in %.4fs\n" elapsed_compute;
+
+ (* Step 3: Slam the computed gate *)
+ Printf.printf "Step 3: Slam poke gate...\n";
+ let now = Noun.atom 0 in
+ let poke_arg = Noun.cell now event in
+
+ let start_slam = Unix.gettimeofday () in
+ begin try
+ let result = slam_on poke_gate poke_arg in
+ let elapsed_slam = Unix.gettimeofday () -. start_slam in
+
+ Printf.printf " ✓ Slam succeeded in %.4fs!\n" elapsed_slam;
+
+ (* Parse result *)
+ begin match result with
+ | Noun.Cell (_effects, new_kernel) ->
+ Printf.printf " Result: [effects new-kernel]\n";
+ kernel := new_kernel;
+ Printf.printf " ✓ Kernel updated\n\n"
+ | Noun.Atom _ ->
+ Printf.printf " ✗ Result is atom\n\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf " ✗ Slam failed (Nock Exit)\n\n"
+ | e ->
+ Printf.printf " ✗ Error: %s\n\n" (Printexc.to_string e)
+ end
+ end
+ ) event_list;
+
+ (* Test final kernel *)
+ Printf.printf "═══════════════════════════════════════\n";
+ Printf.printf " Testing Final Kernel\n";
+ Printf.printf "═══════════════════════════════════════\n\n";
+
+ Printf.printf "Computing poke gate from slot 23...\n";
+ begin try
+ let slot_23_formula = Noun.slot (Z.of_int 23) !kernel in
+ let poke_gate = Nock.nock_on !kernel slot_23_formula in
+ Printf.printf "✓ Computed poke gate\n\n";
+
+ Printf.printf "Testing with [0 [%%test 42]]...\n";
+ let wire = Noun.atom 0 in
+ let card = Noun.cell (Noun.atom 1953719668) (Noun.atom 42) in
+ let ovum = Noun.cell wire card in
+ let now = Noun.atom 0 in
+ let poke_arg = Noun.cell now ovum in
+
+ let result = slam_on poke_gate poke_arg in
+
+ begin match result with
+ | Noun.Cell _ ->
+ Printf.printf "✓ Test poke succeeded!\n\n";
+ Printf.printf "═══════════════════════════════════════\n";
+ Printf.printf " 🎉 ARVO IS FULLY BOOTED! 🎉\n";
+ Printf.printf "═══════════════════════════════════════\n\n";
+ Printf.printf "Boot sequence complete:\n";
+ Printf.printf " 1. Event 1: Initial kernel\n";
+ Printf.printf " 2. Event 3: Boot initialization\n";
+ Printf.printf " 3. Event 4: Final setup\n";
+ Printf.printf " 4. Test poke: SUCCESS\n\n";
+ Printf.printf "The kernel is ready to receive events!\n"
+ | Noun.Atom _ ->
+ Printf.printf "Result is atom\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf "✗ Test poke failed\n"
+ | e ->
+ Printf.printf "✗ Error: %s\n" (Printexc.to_string e)
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "Pill is atom\n"
+
+let () =
+ Printf.printf "\n═══════════════════════════════════════\n";
+ Printf.printf " Boot with Correct C Vere Pattern\n";
+ Printf.printf "═══════════════════════════════════════\n\n";
+ Eio_main.run boot
diff --git a/ocaml/test/test_event4_slot42.ml b/ocaml/test/test_event4_slot42.ml
new file mode 100644
index 0000000..ce98863
--- /dev/null
+++ b/ocaml/test/test_event4_slot42.ml
@@ -0,0 +1,104 @@
+(* Test Event 4 using slot 42 instead of slot 23 *)
+
+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 test _env =
+ Printf.printf "🚀 Testing Event 4 with Slot 42\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
+
+ let kernel1 = List.nth event_list 1 in
+ let event3 = List.nth event_list 3 in
+ let event4 = List.nth event_list 4 in
+
+ (* Slam Event 3 with slot 23 *)
+ Printf.printf "=== Event 3 (slot 23) ===\n";
+ let poke_gate3 = Noun.slot (Z.of_int 23) kernel1 in
+ let result3 = slam_on poke_gate3 (Noun.cell (Noun.atom 0) event3) in
+
+ let kernel_after_3 = match result3 with
+ | Noun.Cell (_effects, new_kernel) ->
+ Printf.printf "✓ Succeeded\n\n";
+ new_kernel
+ | _ -> kernel1
+ in
+
+ (* Try Event 4 with SLOT 42 *)
+ Printf.printf "=== Event 4 (slot 42) ===\n";
+ begin try
+ let poke_gate4 = Noun.slot (Z.of_int 42) kernel_after_3 in
+ Printf.printf "✓ Found poke gate at slot 42\n";
+
+ (* Check gate structure *)
+ begin match poke_gate4 with
+ | Noun.Cell (battery, payload) ->
+ Printf.printf " Battery: %s\n" (match battery with Noun.Atom _ -> "atom" | Noun.Cell _ -> "cell");
+ begin match payload with
+ | Noun.Cell (_sample, _context) ->
+ Printf.printf " Payload: cell [sample context] ✓\n\n"
+ | _ ->
+ Printf.printf " Payload: atom ✗\n\n"
+ end
+ | _ -> ()
+ end;
+
+ Printf.printf "Slamming Event 4...\n";
+ let start = Unix.gettimeofday () in
+ let result4 = slam_on poke_gate4 (Noun.cell (Noun.atom 0) event4) in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ begin match result4 with
+ | Noun.Cell (_effects, _new_kernel) ->
+ Printf.printf "✓ Event 4 succeeded in %.4fs!\n\n" elapsed;
+ Printf.printf "═══════════════════════════════════════════\n";
+ Printf.printf " 🎉🎉🎉 FULL BOOT SUCCESS! 🎉🎉🎉\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+ Printf.printf "Boot sequence:\n";
+ Printf.printf " 1. Event 1: Initial larval kernel\n";
+ Printf.printf " 2. Event 3: Poked with slot 23 (larval)\n";
+ Printf.printf " 3. Kernel metamorphosed!\n";
+ Printf.printf " 4. Event 4: Poked with slot 42 (adult)\n\n";
+ Printf.printf "The kernel has metamorphosed from larval to adult!\n";
+ Printf.printf " - Larval poke: slot 23\n";
+ Printf.printf " - Adult poke: slot 42\n"
+ | Noun.Atom _ ->
+ Printf.printf "Result is atom\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf "✗ Still failed with slot 42\n"
+ | Not_found ->
+ Printf.printf "✗ No slot 42 found\n"
+ | e ->
+ Printf.printf "✗ Error: %s\n" (Printexc.to_string e)
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "Pill is atom\n"
+
+let () =
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " Test Event 4 with Slot 42\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+ Eio_main.run test
diff --git a/ocaml/test/test_functional_bios.ml b/ocaml/test/test_functional_bios.ml
new file mode 100644
index 0000000..5679c3f
--- /dev/null
+++ b/ocaml/test/test_functional_bios.ml
@@ -0,0 +1,132 @@
+(* Test the functional BIOS formula [2 [0 3] [0 2]] on event list *)
+
+open Nock_lib
+
+let test_bios _env =
+ Printf.printf "🚀 Testing Functional BIOS Formula\n\n";
+
+ (* Load solid pill *)
+ 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) ->
+ Printf.printf "Found events\n\n";
+
+ (* Build the functional BIOS formula: [2 [0 3] [0 2]] *)
+ Printf.printf "Building functional BIOS formula: [2 [0 3] [0 2]]\n";
+ let bios_formula = Noun.cell
+ (Noun.atom 2)
+ (Noun.cell
+ (Noun.cell (Noun.atom 0) (Noun.atom 3))
+ (Noun.cell (Noun.atom 0) (Noun.atom 2)))
+ in
+ Printf.printf "Formula: %s\n\n"
+ (match bios_formula with Noun.Cell _ -> "built" | _ -> "error");
+
+ (* Run the formula on the event list! *)
+ Printf.printf "Running formula on entire event list...\n";
+ Printf.printf "(This processes ALL 5 events at once!)\n\n";
+
+ let start = Unix.gettimeofday () in
+
+ begin try
+ let result = Nock.nock_on events bios_formula in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf "✓ Formula succeeded in %.4fs!\n\n" elapsed;
+
+ (* Extract slot 7 from result *)
+ Printf.printf "Extracting slot 7 from result...\n";
+ begin try
+ let kernel = Noun.slot (Z.of_int 7) result in
+ Printf.printf "✓ Got kernel at slot 7!\n\n";
+
+ (* Check what slots this kernel has *)
+ Printf.printf "Checking kernel slots:\n";
+
+ begin try
+ let _poke23 = Noun.slot (Z.of_int 23) kernel in
+ Printf.printf " ✓ Has slot 23 (larval poke)\n"
+ with _ ->
+ Printf.printf " ✗ No slot 23\n"
+ end;
+
+ begin try
+ let _poke42 = Noun.slot (Z.of_int 42) kernel in
+ Printf.printf " ✓ Has slot 42 (adult poke)\n"
+ with _ ->
+ Printf.printf " ✗ No slot 42\n"
+ end;
+
+ Printf.printf "\n🎉 FUNCTIONAL BIOS BOOT COMPLETE!\n\n";
+
+ (* Try a test poke on slot 42 *)
+ Printf.printf "Testing poke on slot 42...\n";
+
+ begin try
+ let poke_gate = Noun.slot (Z.of_int 42) kernel in
+
+ (* Build test event *)
+ let wire = Noun.atom 0 in
+ let card = Noun.cell (Noun.atom 1953719668) (Noun.atom 42) in
+ let ovum = Noun.cell wire card in
+ let now = Noun.atom 0 in
+ let poke_arg = Noun.cell now ovum in
+
+ (* Slam *)
+ let battery = Noun.head poke_gate in
+ let context = Noun.tail (Noun.tail poke_gate) in
+ let new_core = Noun.cell battery (Noun.cell poke_arg 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 poke_result = Nock.nock_on new_core kick_formula in
+
+ begin match poke_result with
+ | Noun.Cell (_effects, _new_kernel) ->
+ Printf.printf " 🎊 SLOT 42 POKE WORKS!\n\n";
+ Printf.printf "═══════════════════════════════════════════\n";
+ Printf.printf " ARVO IS FULLY BOOTED AND OPERATIONAL!\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+ Printf.printf "This means we can now:\n";
+ Printf.printf " ✅ Run the functional BIOS formula\n";
+ Printf.printf " ✅ Extract the booted kernel\n";
+ Printf.printf " ✅ Poke events into Arvo\n";
+ Printf.printf " ✅ Build a complete Urbit runtime!\n"
+ | Noun.Atom _ ->
+ Printf.printf " Result is atom\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf " ✗ Poke failed (Nock Exit)\n"
+ | e ->
+ Printf.printf " ✗ Error: %s\n" (Printexc.to_string e)
+ end
+
+ with
+ | Not_found ->
+ Printf.printf "✗ No slot 7 in result\n"
+ | e ->
+ Printf.printf "✗ Error accessing slot 7: %s\n" (Printexc.to_string e)
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf "✗ Formula failed (Nock Exit)\n"
+ | e ->
+ Printf.printf "✗ Error: %s\n" (Printexc.to_string e)
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "✗ Pill is atom\n"
+
+let () =
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " Test Functional BIOS Formula\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+ Eio_main.run test_bios
diff --git a/ocaml/test/test_life_on_bot.ml b/ocaml/test/test_life_on_bot.ml
new file mode 100644
index 0000000..4aa1080
--- /dev/null
+++ b/ocaml/test/test_life_on_bot.ml
@@ -0,0 +1,95 @@
+(* Test u3v_life() on JUST the bot events from solid pill *)
+
+open Nock_lib
+
+let rec to_list acc noun =
+ match noun with
+ | Noun.Atom _ -> List.rev acc
+ | Noun.Cell (item, rest) -> to_list (item :: acc) rest
+
+let test _env =
+ Printf.printf "═══════════════════════════════════════\n";
+ Printf.printf " Testing u3v_life on Bot Events\n";
+ Printf.printf "═══════════════════════════════════════\n\n";
+
+ (* Cue the solid pill *)
+ Printf.printf "Cuing solid.pill...\n%!";
+ let pill_bytes = Eio.Path.load (Eio.Path.("." / "solid.pill")) |> Bytes.of_string in
+ let pill = Serial.cue pill_bytes in
+ Printf.printf "✓ Pill cued\n\n";
+
+ (* Parse structure *)
+ match pill with
+ | Noun.Cell (_tag, rest) ->
+ begin match rest with
+ | Noun.Cell (_typ, rest2) ->
+ begin match rest2 with
+ | Noun.Cell (bot, _rest3) ->
+ Printf.printf "Extracted bot events\n\n";
+
+ (* Bot should be a list of lifecycle events *)
+ Printf.printf "Testing u3v_life([2 [0 3] [0 2]]) on bot...\n%!";
+
+ (* Build lifecycle formula *)
+ let lyf = Noun.cell (Noun.atom 2)
+ (Noun.cell
+ (Noun.cell (Noun.atom 0) (Noun.atom 3))
+ (Noun.cell (Noun.atom 0) (Noun.atom 2))) in
+
+ begin try
+ let start = Unix.gettimeofday () in
+ let gat = Nock.nock_on bot lyf in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf "✓ Formula completed in %.4fs!\n\n" elapsed;
+
+ (* Extract slot 7 to get kernel *)
+ let kernel = Noun.slot (Z.of_int 7) gat in
+ Printf.printf "✓ Extracted kernel from slot 7\n\n";
+
+ (* Verify kernel has poke at slot 23 *)
+ begin try
+ let _poke = Noun.slot (Z.of_int 23) kernel in
+ Printf.printf "✓ Kernel has poke at slot 23!\n\n";
+
+ Printf.printf "═══════════════════════════════════════\n";
+ Printf.printf " 🎉 SUCCESS! We have a kernel! 🎉\n";
+ Printf.printf "═══════════════════════════════════════\n\n";
+
+ Printf.printf "The functional BIOS worked on bot events!\n"
+
+ with _ ->
+ Printf.printf "✗ No slot 23 in kernel\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf "✗ Formula failed (Nock Exit)\n";
+
+ (* Debug: what's in bot? *)
+ Printf.printf "\nDebugging bot structure:\n";
+ let bot_list = to_list [] bot in
+ Printf.printf " Bot has %d items\n" (List.length bot_list);
+ List.iteri (fun i item ->
+ let desc = match item with
+ | Noun.Atom a -> Printf.sprintf "Atom(%s)" (Z.to_string a)
+ | Noun.Cell _ -> "Cell"
+ in
+ Printf.printf " Item %d: %s\n" i desc
+ ) bot_list
+
+ | e ->
+ Printf.printf "✗ Error: %s\n" (Printexc.to_string e)
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "rest2 is atom\n"
+ end
+ | Noun.Atom _ ->
+ Printf.printf "rest is atom\n"
+ end
+ | Noun.Atom _ ->
+ Printf.printf "Pill is atom\n"
+
+let () =
+ Eio_main.run test
diff --git a/ocaml/test/test_slam_directly.ml b/ocaml/test/test_slam_directly.ml
new file mode 100644
index 0000000..d7248f5
--- /dev/null
+++ b/ocaml/test/test_slam_directly.ml
@@ -0,0 +1,108 @@
+(* Test slamming poke gates directly *)
+
+open Nock_lib
+
+let slam_on gate event =
+ (* C Vere slam_on: [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 arm 2: [9 2 0 1] *)
+ 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 test_slam _env =
+ Printf.printf "Testing direct slam on poke gates...\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 ->
+ (* Build test event: [now ovum] where ovum = [wire card] *)
+ Printf.printf "Building test event...\n";
+ let wire = Noun.atom 0 in
+ let card = Noun.cell (Noun.atom 1953719668) (Noun.atom 42) in
+ let ovum = Noun.cell wire card in
+ let now = Noun.atom 0 in
+ let event = Noun.cell now ovum in
+ Printf.printf " Event: [0 [0 [1953719668 42]]]\n\n";
+
+ (* Try slot 23 *)
+ Printf.printf "=== Testing Slot 23 ===\n";
+ begin try
+ let poke_gate = Noun.slot (Z.of_int 23) kernel in
+ Printf.printf "Slamming slot 23 gate...\n";
+
+ let start = Unix.gettimeofday () in
+ let result = slam_on poke_gate event in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf "✓ Slam succeeded in %.4fs!\n\n" elapsed;
+
+ begin match result with
+ | Noun.Cell (_effects, _new_kernel) ->
+ Printf.printf "🎉 SLOT 23 WORKS! Result is [effects new-kernel]\n\n"
+ | Noun.Atom _ ->
+ Printf.printf "Result is atom (unexpected)\n\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf "✗ Slam failed (Nock Exit)\n\n"
+ | e ->
+ Printf.printf "✗ Error: %s\n\n" (Printexc.to_string e)
+ end;
+
+ (* Try slot 42 *)
+ Printf.printf "=== Testing Slot 42 ===\n";
+ begin try
+ let poke_gate = Noun.slot (Z.of_int 42) kernel in
+ Printf.printf "Slamming slot 42 gate...\n";
+
+ let start = Unix.gettimeofday () in
+ let result = slam_on poke_gate event in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf "✓ Slam succeeded in %.4fs!\n\n" elapsed;
+
+ begin match result with
+ | Noun.Cell (_effects, _new_kernel) ->
+ Printf.printf "🎉 SLOT 42 WORKS! Result is [effects new-kernel]\n\n"
+ | Noun.Atom _ ->
+ Printf.printf "Result is atom (unexpected)\n\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf "✗ Slam failed (Nock Exit)\n\n"
+ | e ->
+ Printf.printf "✗ Error: %s\n\n" (Printexc.to_string e)
+ end
+
+ | None ->
+ Printf.printf "No event 1\n"
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf "Pill is atom\n"
+
+let () =
+ Printf.printf "\n═══════════════════════════════════════════\n";
+ Printf.printf " Test Direct Slam on Poke Gates\n";
+ Printf.printf "═══════════════════════════════════════════\n\n";
+ Eio_main.run test_slam
diff --git a/ocaml/test/test_solid_cvere_pattern.ml b/ocaml/test/test_solid_cvere_pattern.ml
new file mode 100644
index 0000000..a0a4c58
--- /dev/null
+++ b/ocaml/test/test_solid_cvere_pattern.ml
@@ -0,0 +1,129 @@
+(* Test C Vere poke pattern on solid pill *)
+
+open Nock_lib
+
+let slam_on gate event =
+ (* C Vere slam_on: [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 arm 2: [9 2 0 1] *)
+ 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 test_poke _env =
+ Printf.printf "🎯 Testing C Vere Pattern on Solid Pill\n\n";
+
+ (* Load solid pill *)
+ 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
+ Printf.printf "Found %d events\n\n" (List.length event_list);
+
+ (* Event 1 is the initial kernel *)
+ begin match List.nth_opt event_list 1 with
+ | Some kernel ->
+ Printf.printf "Testing on Event 1 (initial kernel):\n\n";
+
+ (* Try slot 23 (C Vere pattern) *)
+ Printf.printf "Step 1: Get formula from slot 23...\n";
+ begin try
+ let slot_23_formula = Noun.slot (Z.of_int 23) kernel in
+ Printf.printf " ✓ Found formula at slot 23\n\n";
+
+ Printf.printf "Step 2: Run formula to compute poke gate...\n";
+ let poke_gate = Nock.nock_on kernel slot_23_formula in
+ Printf.printf " ✓ Computed poke gate\n\n";
+
+ Printf.printf "Step 3: Build test event...\n";
+ (* Build proper ovum: [wire card] *)
+ let wire = Noun.atom 0 in
+ let card = Noun.cell (Noun.atom 1953719668) (Noun.atom 42) in
+ let ovum = Noun.cell wire card in
+
+ (* Build poke args: [now ovum] *)
+ let now = Noun.atom 0 in
+ let event = Noun.cell now ovum in
+ Printf.printf " Event: [now [wire card]]\n\n";
+
+ Printf.printf "Step 4: Slam poke gate...\n";
+ let start = Unix.gettimeofday () in
+ let result = slam_on poke_gate event in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf " ✓ Poke succeeded in %.4fs!\n\n" elapsed;
+
+ begin match result with
+ | Noun.Cell (_effects, _new_kernel) ->
+ Printf.printf "Result: [effects new-kernel]\n";
+ Printf.printf " ✓ Got expected structure!\n\n";
+ Printf.printf "🎉 SOLID PILL ARVO IS WORKING!\n"
+ | Noun.Atom _ ->
+ Printf.printf "Result is atom (unexpected)\n"
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf " ✗ Nock failed (Exit)\n\n";
+
+ (* Try slot 42 instead *)
+ Printf.printf "Trying slot 42 instead...\n";
+ begin try
+ let slot_42 = Noun.slot (Z.of_int 42) kernel in
+ Printf.printf " ✓ Found something at slot 42\n";
+
+ (* Check if it's a formula or a gate *)
+ Printf.printf " Attempting to use as formula...\n";
+ let poke_gate = Nock.nock_on kernel slot_42 in
+ Printf.printf " ✓ Computed gate from slot 42\n\n";
+
+ let wire = Noun.atom 0 in
+ let card = Noun.cell (Noun.atom 1953719668) (Noun.atom 42) in
+ let ovum = Noun.cell wire card in
+ let now = Noun.atom 0 in
+ let event = Noun.cell now ovum in
+
+ let result = slam_on poke_gate event in
+ Printf.printf " ✓ Poke with slot 42 succeeded!\n\n";
+
+ begin match result with
+ | Noun.Cell _ ->
+ Printf.printf "🎉 SLOT 42 WORKS!\n"
+ | Noun.Atom _ ->
+ Printf.printf "Result is atom\n"
+ end
+
+ with
+ | Noun.Exit -> Printf.printf " ✗ Slot 42 also failed\n"
+ | Not_found -> Printf.printf " ✗ No slot 42\n"
+ end
+ | Not_found ->
+ Printf.printf " ✗ No slot 23 found\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 " Test C Vere Pattern on Solid Pill\n";
+ Printf.printf "═══════════════════════════════════════════════════════════\n\n";
+ Eio_main.run test_poke
diff --git a/ocaml/test/test_two_stage_boot.ml b/ocaml/test/test_two_stage_boot.ml
new file mode 100644
index 0000000..090dd50
--- /dev/null
+++ b/ocaml/test/test_two_stage_boot.ml
@@ -0,0 +1,245 @@
+(* Two-Stage Boot Test - Exactly like C Vere *)
+
+open Nock_lib
+
+let () = Printf.printf "\n═══════════════════════════════════════════════════════\n";
+ Printf.printf " Two-Stage Boot Test (C Vere Pattern)\n";
+ Printf.printf "═══════════════════════════════════════════════════════\n\n"
+
+(* Stage 1: Boot ivory pill with null *)
+let stage1_ivory_boot env =
+ Printf.printf "╔═══════════════════════════════════════╗\n";
+ Printf.printf "║ STAGE 1: Ivory Pill Bootstrap ║\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 (%.1f MB)\n%!"
+ (Bytes.length pill_bytes)
+ (float_of_int (Bytes.length pill_bytes) /. 1024.0 /. 1024.0);
+
+ Printf.printf "[2] Cuing ivory pill...\n%!";
+ 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;
+
+ (* Check ivory structure: ["ivory" core] *)
+ Printf.printf "[3] Parsing ivory pill structure...\n%!";
+ match pill with
+ | Noun.Cell (tag, core) ->
+ (* Check 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 "too-long"
+ | _ -> "not-atom"
+ in
+ Printf.printf " Tag: '%s'\n" tag_str;
+ Printf.printf " Core: %s\n\n" (if Noun.is_cell core then "cell" else "atom");
+
+ (* Now boot with the ivory core as eve *)
+ Printf.printf "[4] Running u3v_life() on ivory core...\n%!";
+ Printf.printf " Formula: [2 [0 3] [0 2]]\n";
+ Printf.printf " Subject: ivory pill core\n\n%!";
+
+ let eve_core = core in (* Use the ivory core, not null! *)
+
+ begin try
+ let start = Unix.gettimeofday () in
+ let kernel = Boot.life eve_core in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf " ✓ SUCCESS! Kernel built in %.4fs\n\n" elapsed;
+
+ (* Verify kernel has poke at slot 23 *)
+ Printf.printf "[5] Verifying kernel structure...\n%!";
+ begin try
+ let _poke = Noun.slot (Z.of_int 23) kernel in
+ Printf.printf " ✓ Has poke gate at slot 23\n\n";
+
+ Printf.printf "╔═══════════════════════════════════════╗\n";
+ Printf.printf "║ ✓ STAGE 1 COMPLETE! ║\n";
+ Printf.printf "╚═══════════════════════════════════════╝\n\n";
+
+ Some kernel
+
+ with _ ->
+ Printf.printf " ✗ No slot 23 - kernel invalid\n\n";
+ None
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf " ✗ FAILED: Nock Exit\n\n";
+ None
+ | e ->
+ Printf.printf " ✗ FAILED: %s\n\n" (Printexc.to_string e);
+ None
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf " ✗ Pill is atom (expected cell)\n\n";
+ None
+
+(* Stage 2: Boot solid pill events *)
+let stage2_solid_boot env _ivory_kernel =
+ Printf.printf "\n╔═══════════════════════════════════════╗\n";
+ Printf.printf "║ STAGE 2: Solid Pill Events ║\n";
+ Printf.printf "╚═══════════════════════════════════════╝\n\n";
+
+ (* Load solid pill *)
+ Printf.printf "[1] Loading solid.pill...\n%!";
+ let fs = Eio.Stdenv.fs env in
+ let pill_bytes = Eio.Path.(load (fs / "solid.pill")) |> Bytes.of_string in
+ Printf.printf " Size: %d bytes (%.1f MB)\n%!"
+ (Bytes.length pill_bytes)
+ (float_of_int (Bytes.length pill_bytes) /. 1024.0 /. 1024.0);
+
+ Printf.printf "[2] Cuing solid pill...\n%!";
+ 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;
+
+ (* Parse structure: [%pill %solid [bot mod use]] *)
+ Printf.printf "[3] Parsing solid pill structure...\n%!";
+ match pill with
+ | Noun.Cell (_tag, rest) ->
+ begin match rest with
+ | Noun.Cell (_typ, rest2) ->
+ Printf.printf " Tag: pill\n";
+ Printf.printf " Type: solid\n";
+
+ begin match rest2 with
+ | Noun.Cell (bot, rest3) ->
+ (* Count bot events *)
+ let rec count_list acc n =
+ match n with
+ | Noun.Atom _ -> acc
+ | Noun.Cell (_, rest) -> count_list (acc + 1) rest
+ in
+ let bot_count = count_list 0 bot in
+ Printf.printf " Bot events: %d\n" bot_count;
+
+ begin match rest3 with
+ | Noun.Cell (mod_, rest4) ->
+ let mod_count = count_list 0 mod_ in
+ Printf.printf " Mod events: %d\n" mod_count;
+
+ begin match rest4 with
+ | Noun.Cell (use, _) ->
+ let use_count = count_list 0 use in
+ Printf.printf " Use events: %d\n" use_count;
+
+ let total = bot_count + mod_count + use_count in
+ Printf.printf " Total: %d events\n\n" total;
+
+ (* Concatenate all events into a single list *)
+ Printf.printf "[4] Concatenating all events...\n%!";
+ let rec append_lists l1 l2 =
+ match l1 with
+ | Noun.Atom _ -> l2
+ | Noun.Cell (h, t) -> Noun.cell h (append_lists t l2)
+ in
+ let all_events = append_lists bot (append_lists mod_ use) in
+ Printf.printf " ✓ Event list built\n\n";
+
+ (* Now run u3v_boot on all events *)
+ Printf.printf "[5] Running u3v_boot() on %d events...\n%!" total;
+ Printf.printf " This will call u3v_life() with the event list\n%!";
+
+ begin try
+ let start = Unix.gettimeofday () in
+
+ (* Call the lifecycle formula on the event list *)
+ Printf.printf " Running [2 [0 3] [0 2]] on event list...\n%!";
+ let kernel = Boot.life all_events in
+
+ let elapsed = Unix.gettimeofday () -. start in
+ Printf.printf " ✓ SUCCESS! Kernel updated in %.4fs\n\n" elapsed;
+
+ (* Verify kernel *)
+ Printf.printf "[6] Verifying updated kernel...\n%!";
+ begin try
+ let _poke = Noun.slot (Z.of_int 23) kernel in
+ Printf.printf " ✓ Has poke gate at slot 23\n\n";
+
+ Printf.printf "╔═══════════════════════════════════════╗\n";
+ Printf.printf "║ 🎉🎉🎉 FULL BOOT SUCCESS! 🎉🎉🎉 ║\n";
+ Printf.printf "╚═══════════════════════════════════════╝\n\n";
+
+ Printf.printf "Boot sequence complete:\n";
+ Printf.printf " 1. Stage 1: Ivory pill with null → Initial kernel\n";
+ Printf.printf " 2. Stage 2: Solid pill %d events → Updated kernel\n" total;
+ Printf.printf " 3. Kernel is ready to receive pokes!\n\n";
+
+ true
+
+ with _ ->
+ Printf.printf " ✗ No slot 23 in updated kernel\n\n";
+ false
+ end
+
+ with
+ | Noun.Exit ->
+ Printf.printf " ✗ FAILED: Nock Exit during lifecycle\n\n";
+
+ (* Debug: try with null like C Vere seems to do *)
+ Printf.printf "[DEBUG] Trying with null (like C Vere)...\n%!";
+ begin try
+ let _kernel = Boot.life (Noun.atom 0) in
+ Printf.printf " ✓ Null works! (same as ivory)\n";
+ Printf.printf " This means solid pill events might be processed differently\n\n";
+ false
+ with _ ->
+ Printf.printf " ✗ Null also fails\n\n";
+ false
+ end
+
+ | e ->
+ Printf.printf " ✗ FAILED: %s\n\n" (Printexc.to_string e);
+ false
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf " ✗ rest4 is atom (expected use)\n";
+ false
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf " ✗ rest3 is atom (expected [mod use])\n";
+ false
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf " ✗ rest2 is atom (expected [bot mod use])\n";
+ false
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf " ✗ rest is atom (expected [type ...])\n";
+ false
+ end
+
+ | Noun.Atom _ ->
+ Printf.printf " ✗ Pill is atom (expected cell)\n";
+ false
+
+(* Main test *)
+let main env =
+ (* Stage 1: Ivory *)
+ match stage1_ivory_boot env with
+ | Some ivory_kernel ->
+ (* Stage 2: Solid *)
+ let _success = stage2_solid_boot env ivory_kernel in
+ ()
+
+ | None ->
+ Printf.printf "╔═══════════════════════════════════════╗\n";
+ Printf.printf "║ ✗ STAGE 1 FAILED - Cannot continue ║\n";
+ Printf.printf "╚═══════════════════════════════════════╝\n\n"
+
+let () = Eio_main.run main