summaryrefslogtreecommitdiff
path: root/ocaml/test/test_life_on_bot.ml
diff options
context:
space:
mode:
authorpolwex <polwex@sortug.com>2025-10-06 14:35:41 +0700
committerpolwex <polwex@sortug.com>2025-10-06 14:35:41 +0700
commit256376afffe66faa239a6a6aaebb8f68a9c6cbe4 (patch)
tree52f2ea2ba9da38e7edf64bb810708526cdeb14f5 /ocaml/test/test_life_on_bot.ml
parent4a6067863d415e0334b4b61254fab2bd879a6964 (diff)
very stuck
Diffstat (limited to 'ocaml/test/test_life_on_bot.ml')
-rw-r--r--ocaml/test/test_life_on_bot.ml95
1 files changed, 95 insertions, 0 deletions
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