summaryrefslogtreecommitdiff
path: root/ocaml/test/test_bisect_lifecycle.ml
diff options
context:
space:
mode:
authorpolwex <polwex@sortug.com>2025-10-07 01:40:54 +0700
committerpolwex <polwex@sortug.com>2025-10-07 01:40:54 +0700
commita12407b3f152a3dbd716d640202b9613c61d6105 (patch)
tree411c630824b992d3a7f5e3d17c83a8546577bad7 /ocaml/test/test_bisect_lifecycle.ml
parentd0064c2f577c56a9e5b3fc00b45f71a73f3574c9 (diff)
lmao turned down the bytecode interpreter in Vere and it started giving the same results as us smh
Diffstat (limited to 'ocaml/test/test_bisect_lifecycle.ml')
-rw-r--r--ocaml/test/test_bisect_lifecycle.ml71
1 files changed, 71 insertions, 0 deletions
diff --git a/ocaml/test/test_bisect_lifecycle.ml b/ocaml/test/test_bisect_lifecycle.ml
new file mode 100644
index 0000000..7e37516
--- /dev/null
+++ b/ocaml/test/test_bisect_lifecycle.ml
@@ -0,0 +1,71 @@
+(* Bisect the ivory pill to find where lifecycle formula diverges *)
+
+open Nock_lib
+
+let lifecycle_formula = Noun.cell
+ (Noun.atom 2)
+ (Noun.cell
+ (Noun.cell (Noun.atom 0) (Noun.atom 3))
+ (Noun.cell (Noun.atom 0) (Noun.atom 2)))
+
+let test_lifecycle subject_name subject =
+ Printf.printf "Testing: %s\n" subject_name;
+ Printf.printf " Subject mug: 0x%08lx\n" (Noun.mug subject);
+
+ (* Check if subject has valid structure for lifecycle *)
+ if not (Noun.is_cell subject) then begin
+ Printf.printf " SKIP: subject is atom\n\n";
+ None
+ end else begin
+ let slot2 = Noun.head subject in
+
+ (* Check if slot 2 is a valid formula *)
+ if not (Noun.is_cell slot2) then begin
+ Printf.printf " SKIP: slot 2 is atom (not a formula)\n\n";
+ None
+ end else begin
+ try
+ let result = Nock.nock_on subject lifecycle_formula in
+ let result_mug = Noun.mug result in
+ Printf.printf " Result mug: 0x%08lx\n\n" result_mug;
+ Some result_mug
+ with _ ->
+ Printf.printf " CRASH: nock failed\n\n";
+ None
+ end
+ end
+
+let rec walk_tree prefix subject depth max_depth =
+ if depth >= max_depth then () else begin
+ (* Test current node *)
+ let _ = test_lifecycle prefix subject in
+
+ (* Walk children if cell *)
+ if Noun.is_cell subject then begin
+ let h = Noun.head subject in
+ let t = Noun.tail subject in
+ walk_tree (prefix ^ ".2") h (depth + 1) max_depth;
+ walk_tree (prefix ^ ".3") t (depth + 1) max_depth
+ end
+ end
+
+let () =
+ Eio_main.run (fun env ->
+ let fs = Eio.Stdenv.fs env in
+
+ Printf.printf "Loading ivory.pill...\n";
+ let pill_bytes = Eio.Path.(load (fs / "ivory.pill")) |> Bytes.of_string in
+ let pill = Serial.cue pill_bytes in
+ let core = Noun.tail pill in
+
+ Printf.printf "Ivory core mug: 0x%08lx\n\n" (Noun.mug core);
+ Printf.printf "Walking tree and testing lifecycle at each node...\n";
+ Printf.printf "Format: slot path (e.g. '.2.3' = slot 6)\n\n";
+
+ (* Reset counters *)
+ Nock.call_count := 0;
+ Nock.depth := 0;
+
+ (* Walk tree up to depth 5 *)
+ walk_tree "core" core 0 5
+ )