summaryrefslogtreecommitdiff
path: root/ocaml/test
diff options
context:
space:
mode:
authorpolwex <polwex@sortug.com>2025-10-06 17:07:33 +0700
committerpolwex <polwex@sortug.com>2025-10-06 17:07:33 +0700
commita4615148975bed241ae26ffa2655dc9c407107d8 (patch)
treebd127b13f0027cd2870b8f016c5658465785d3df /ocaml/test
parent256376afffe66faa239a6a6aaebb8f68a9c6cbe4 (diff)
maybe now maybe now
Diffstat (limited to 'ocaml/test')
-rw-r--r--ocaml/test/dune10
-rw-r--r--ocaml/test/examine_ivory.ml84
-rw-r--r--ocaml/test/test_life_formula.ml48
-rw-r--r--ocaml/test/test_two_stage_boot.ml27
4 files changed, 151 insertions, 18 deletions
diff --git a/ocaml/test/dune b/ocaml/test/dune
index 17e84b8..c7cf6da 100644
--- a/ocaml/test/dune
+++ b/ocaml/test/dune
@@ -271,3 +271,13 @@
(name test_two_stage_boot)
(modules test_two_stage_boot)
(libraries nock_lib eio_main unix))
+
+(executable
+ (name test_life_formula)
+ (modules test_life_formula)
+ (libraries nock_lib))
+
+(executable
+ (name examine_ivory)
+ (modules examine_ivory)
+ (libraries nock_lib eio_main))
diff --git a/ocaml/test/examine_ivory.ml b/ocaml/test/examine_ivory.ml
new file mode 100644
index 0000000..34b5fed
--- /dev/null
+++ b/ocaml/test/examine_ivory.ml
@@ -0,0 +1,84 @@
+(* Examine ivory.pill structure *)
+
+open Nock_lib
+
+let main env =
+ Printf.printf "\n═══════════════════════════════════════\n";
+ Printf.printf " Examining ivory.pill Structure\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\n%!" (Bytes.length pill_bytes);
+
+ (* Cue it *)
+ Printf.printf "[2] Cuing ivory pill...\n%!";
+ let pill = Serial.cue pill_bytes in
+ Printf.printf " ✓ Cued\n\n";
+
+ (* Check structure *)
+ Printf.printf "[3] Structure analysis:\n";
+ match pill with
+ | Noun.Cell (tag, tail) ->
+ (* Print 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 Printf.sprintf "<atom %d bits>" (Z.numbits z)
+ | Noun.Cell _ -> "<cell>"
+ in
+ Printf.printf " Tag: %s\n" tag_str;
+
+ (* Analyze tail *)
+ Printf.printf " Tail type: %s\n" (if Noun.is_cell tail then "CELL" else "ATOM");
+
+ (match tail with
+ | Noun.Atom z when Z.equal z Z.zero ->
+ Printf.printf " Tail value: 0 (NULL!)\n";
+ Printf.printf "\n";
+ Printf.printf " ✓ CONFIRMED: Embedded ivory has structure [\"ivory\" 0]\n";
+ Printf.printf " This means u3v_life() is called with atom 0!\n"
+
+ | Noun.Atom z ->
+ Printf.printf " Tail value: atom with %d bits\n" (Z.numbits z);
+ Printf.printf " Tail decimal: %s\n" (Z.to_string z)
+
+ | Noun.Cell (h, t) ->
+ Printf.printf " Tail is a CELL\n";
+ Printf.printf " Head type: %s\n" (if Noun.is_cell h then "cell" else "atom");
+ Printf.printf " Tail type: %s\n" (if Noun.is_cell t then "cell" else "atom");
+
+ (* Check if it's the Arvo core structure *)
+ Printf.printf "\n Checking if tail is Arvo core...\n";
+ begin try
+ let _slot2 = Noun.slot (Z.of_int 2) tail in
+ let _slot3 = Noun.slot (Z.of_int 3) tail in
+ Printf.printf " ✓ Has slot 2 and 3 (it's a cell with head and tail)\n";
+
+ (* Check for lifecycle formula at slot 2 *)
+ begin try
+ let slot2 = Noun.slot (Z.of_int 2) tail in
+ Printf.printf " Slot 2 type: %s\n" (if Noun.is_cell slot2 then "cell" else "atom");
+
+ (* The lifecycle formula should be [2 [0 3] [0 2]] *)
+ match slot2 with
+ | Noun.Cell (Noun.Atom op, _rest) when Z.equal op (Z.of_int 2) ->
+ Printf.printf " Slot 2 starts with opcode 2 - could be lifecycle formula!\n";
+ Printf.printf "\n ✓ Tail appears to BE the Arvo core itself!\n";
+ Printf.printf " This means the lifecycle formula operates on the CORE, not null!\n"
+ | _ ->
+ Printf.printf " Slot 2 doesn't match expected lifecycle formula pattern\n"
+ with _ ->
+ Printf.printf " Could not analyze slot 2\n"
+ end
+ with Noun.Exit ->
+ Printf.printf " ✗ Cannot access slots 2/3 - not a valid cell structure\n"
+ end
+ )
+
+ | Noun.Atom _ ->
+ Printf.printf " ✗ Pill is an atom (unexpected)\n"
+
+let () = Eio_main.run main
diff --git a/ocaml/test/test_life_formula.ml b/ocaml/test/test_life_formula.ml
new file mode 100644
index 0000000..722154b
--- /dev/null
+++ b/ocaml/test/test_life_formula.ml
@@ -0,0 +1,48 @@
+(* Test lifecycle formula on atom 0 *)
+
+open Nock_lib
+
+let () =
+ Printf.printf "Testing lifecycle formula [2 [0 3] [0 2]] on atom 0\n\n%!";
+
+ (* Build the 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
+
+ Printf.printf "Formula: [2 [0 3] [0 2]]\n%!";
+ Printf.printf "Subject: 0 (null)\n\n%!";
+
+ (* Try running it *)
+ begin try
+ let result = Nock.nock_on (Noun.atom 0) lyf in
+ Printf.printf "✓ SUCCESS! Result: %s\n%!" (match result with
+ | Noun.Atom z -> Z.to_string z
+ | Noun.Cell _ -> "[cell]")
+ with
+ | Noun.Exit ->
+ Printf.printf "✗ FAILED with Nock Exit\n%!";
+
+ (* Let's trace through the formula step by step *)
+ Printf.printf "\nStep-by-step trace:\n%!";
+ Printf.printf "Formula: *[0 [2 [0 3] [0 2]]]\n%!";
+ Printf.printf "Opcode 2: *[a [2 b c]] = *[*[a b] *[a c]]\n%!";
+ Printf.printf " b = [0 3]\n%!";
+ Printf.printf " c = [0 2]\n%!";
+ Printf.printf "\n*[a b] = *[0 [0 3]] = slot 3 of atom 0\n%!";
+
+ (* Try slot 3 on atom 0 *)
+ begin try
+ let s3 = Noun.slot (Z.of_int 3) (Noun.atom 0) in
+ Printf.printf " slot 3 of 0 = %s (unexpected!)\n%!" (match s3 with
+ | Noun.Atom z -> Z.to_string z
+ | Noun.Cell _ -> "[cell]")
+ with Noun.Exit ->
+ Printf.printf " slot 3 of 0 = ERROR (as expected)\n%!"
+ end;
+
+ Printf.printf "\nThis proves the formula CANNOT work on atom 0!\n%!"
+ | e ->
+ Printf.printf "✗ FAILED with: %s\n%!" (Printexc.to_string e)
+ end
diff --git a/ocaml/test/test_two_stage_boot.ml b/ocaml/test/test_two_stage_boot.ml
index 090dd50..f8311b5 100644
--- a/ocaml/test/test_two_stage_boot.ml
+++ b/ocaml/test/test_two_stage_boot.ml
@@ -40,16 +40,18 @@ let stage1_ivory_boot env =
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%!";
+ (* KEY DISCOVERY: The ivory pill tail IS the Arvo core! *)
+ Printf.printf "[4] Using ivory pill tail (Arvo core) for bootstrap...\n%!";
+ Printf.printf " Ivory structure: [\"ivory\" ARVO_CORE]\n";
+ Printf.printf " The tail is a CELL, not null!\n\n";
- let eve_core = core in (* Use the ivory core, not null! *)
+ Printf.printf "[5] Running u3v_life() on Arvo core...\n%!";
+ Printf.printf " Formula: [2 [0 3] [0 2]]\n";
+ Printf.printf " Subject: Arvo core (cell)\n%!";
begin try
let start = Unix.gettimeofday () in
- let kernel = Boot.life eve_core in
+ let kernel = Boot.life core in
let elapsed = Unix.gettimeofday () -. start in
Printf.printf " ✓ SUCCESS! Kernel built in %.4fs\n\n" elapsed;
@@ -186,18 +188,7 @@ let stage2_solid_boot env _ivory_kernel =
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
+ false
| e ->
Printf.printf " ✗ FAILED: %s\n\n" (Printexc.to_string e);