summaryrefslogtreecommitdiff
path: root/ocaml/test
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/test')
-rw-r--r--ocaml/test/dune5
-rw-r--r--ocaml/test/test_mug.ml161
-rw-r--r--ocaml/test/test_two_stage_boot.ml40
3 files changed, 189 insertions, 17 deletions
diff --git a/ocaml/test/dune b/ocaml/test/dune
index 8087a38..330f064 100644
--- a/ocaml/test/dune
+++ b/ocaml/test/dune
@@ -272,6 +272,11 @@
(modules test_two_stage_boot)
(libraries nock_lib eio_main unix))
+(executable
+ (name test_mug)
+ (modules test_mug)
+ (libraries nock_lib))
+
; (executable
; (name test_life_formula)
; (modules test_life_formula)
diff --git a/ocaml/test/test_mug.ml b/ocaml/test/test_mug.ml
new file mode 100644
index 0000000..0f5df7c
--- /dev/null
+++ b/ocaml/test/test_mug.ml
@@ -0,0 +1,161 @@
+(* Mug Test - Compare OCaml vs C mug computation *)
+
+open Nock_lib
+
+let () = Printf.printf "\n═══════════════════════════════════════\n";
+ Printf.printf " Mug Computation Test\n";
+ Printf.printf "═══════════════════════════════════════\n\n"
+
+(* Helper to print mug with description *)
+let test_mug desc noun =
+ let m = Noun.mug noun in
+ Printf.printf "%-40s 0x%08lx\n" desc m
+
+(* Helper to build a noun from string for readability *)
+let atom = Noun.atom
+let cell = Noun.cell
+
+let () =
+ Printf.printf "ATOMS - Small values:\n";
+ Printf.printf "─────────────────────────────────────\n";
+ test_mug "0" (atom 0);
+ test_mug "1" (atom 1);
+ test_mug "2" (atom 2);
+ test_mug "3" (atom 3);
+ test_mug "10" (atom 10);
+ test_mug "42" (atom 42);
+ test_mug "100" (atom 100);
+ test_mug "255" (atom 255);
+ test_mug "256" (atom 256);
+ test_mug "1000" (atom 1000);
+ Printf.printf "\n";
+
+ Printf.printf "ATOMS - Powers of 2:\n";
+ Printf.printf "─────────────────────────────────────\n";
+ test_mug "2^8 (256)" (atom 256);
+ test_mug "2^16 (65536)" (atom 65536);
+ test_mug "2^20 (1048576)" (atom 1048576);
+ test_mug "2^24 (16777216)" (atom 16777216);
+ test_mug "2^31 - 1 (max signed 32-bit)" (atom 2147483647);
+ Printf.printf "\n";
+
+ Printf.printf "ATOMS - Large values:\n";
+ Printf.printf "─────────────────────────────────────\n";
+ test_mug "2^32" (Noun.Atom { z = Z.shift_left Z.one 32; mug = 0l });
+ test_mug "2^64" (Noun.Atom { z = Z.shift_left Z.one 64; mug = 0l });
+ test_mug "2^128" (Noun.Atom { z = Z.shift_left Z.one 128; mug = 0l });
+ test_mug "0xdeadbeef" (Noun.Atom { z = Z.of_string "0xdeadbeef"; mug = 0l });
+ test_mug "0xcafebabe" (Noun.Atom { z = Z.of_string "0xcafebabe"; mug = 0l });
+ Printf.printf "\n";
+
+ Printf.printf "CELLS - Simple pairs:\n";
+ Printf.printf "─────────────────────────────────────\n";
+ test_mug "[0 0]" (cell (atom 0) (atom 0));
+ test_mug "[0 1]" (cell (atom 0) (atom 1));
+ test_mug "[1 0]" (cell (atom 1) (atom 0));
+ test_mug "[1 1]" (cell (atom 1) (atom 1));
+ test_mug "[1 2]" (cell (atom 1) (atom 2));
+ test_mug "[2 1]" (cell (atom 2) (atom 1));
+ test_mug "[42 0]" (cell (atom 42) (atom 0));
+ test_mug "[0 42]" (cell (atom 0) (atom 42));
+ test_mug "[42 42]" (cell (atom 42) (atom 42));
+ test_mug "[100 200]" (cell (atom 100) (atom 200));
+ Printf.printf "\n";
+
+ Printf.printf "CELLS - Nested structures:\n";
+ Printf.printf "─────────────────────────────────────\n";
+ test_mug "[[0 0] 0]" (cell (cell (atom 0) (atom 0)) (atom 0));
+ test_mug "[0 [0 0]]" (cell (atom 0) (cell (atom 0) (atom 0)));
+ test_mug "[[1 2] 3]" (cell (cell (atom 1) (atom 2)) (atom 3));
+ test_mug "[1 [2 3]]" (cell (atom 1) (cell (atom 2) (atom 3)));
+ test_mug "[[1 2] [3 4]]" (cell (cell (atom 1) (atom 2))
+ (cell (atom 3) (atom 4)));
+ test_mug "[[[0 1] 2] 3]" (cell (cell (cell (atom 0) (atom 1)) (atom 2)) (atom 3));
+ test_mug "[0 [1 [2 3]]]" (cell (atom 0) (cell (atom 1) (cell (atom 2) (atom 3))));
+ Printf.printf "\n";
+
+ Printf.printf "CELLS - Binary trees:\n";
+ Printf.printf "─────────────────────────────────────\n";
+ (* Balanced binary tree depth 2 *)
+ let tree2 = cell (cell (atom 1) (atom 2)) (cell (atom 3) (atom 4)) in
+ test_mug "Balanced tree depth 2" tree2;
+
+ (* Balanced binary tree depth 3 *)
+ let tree3 = cell
+ (cell (cell (atom 1) (atom 2)) (cell (atom 3) (atom 4)))
+ (cell (cell (atom 5) (atom 6)) (cell (atom 7) (atom 8))) in
+ test_mug "Balanced tree depth 3" tree3;
+
+ (* Left-heavy tree *)
+ let left_heavy = cell (cell (cell (atom 1) (atom 2)) (atom 3)) (atom 4) in
+ test_mug "Left-heavy tree" left_heavy;
+
+ (* Right-heavy tree *)
+ let right_heavy = cell (atom 1) (cell (atom 2) (cell (atom 3) (atom 4))) in
+ test_mug "Right-heavy tree" right_heavy;
+ Printf.printf "\n";
+
+ Printf.printf "LISTS - Null-terminated lists:\n";
+ Printf.printf "─────────────────────────────────────\n";
+ (* [1 2 3 ~] = [1 [2 [3 0]]] *)
+ let list_123 = cell (atom 1) (cell (atom 2) (cell (atom 3) (atom 0))) in
+ test_mug "[1 2 3 ~]" list_123;
+
+ (* [0 ~] = [0 0] *)
+ test_mug "[0 ~]" (cell (atom 0) (atom 0));
+
+ (* [42 ~] = [42 0] *)
+ test_mug "[42 ~]" (cell (atom 42) (atom 0));
+
+ (* Empty list: ~ = 0 *)
+ test_mug "~ (null/empty list)" (atom 0);
+
+ (* Longer list [1 2 3 4 5 ~] *)
+ let list_12345 = cell (atom 1)
+ (cell (atom 2)
+ (cell (atom 3)
+ (cell (atom 4)
+ (cell (atom 5) (atom 0))))) in
+ test_mug "[1 2 3 4 5 ~]" list_12345;
+ Printf.printf "\n";
+
+ Printf.printf "SPECIAL - Urbit constants:\n";
+ Printf.printf "─────────────────────────────────────\n";
+ (* YES and NO in Urbit *)
+ test_mug "YES (0)" (atom 0);
+ test_mug "NO (1)" (atom 1);
+
+ (* Common Urbit atoms *)
+ test_mug "~zod (0)" (atom 0);
+ test_mug "~nec (1)" (atom 1);
+ test_mug "~bud (2)" (atom 2);
+
+ (* Cord atoms (text) *)
+ let cord_atom s =
+ let rec loop i acc =
+ if i < 0 then acc
+ else loop (i - 1) (Z.add (Z.mul acc (Z.of_int 256)) (Z.of_int (Char.code s.[i])))
+ in
+ Noun.Atom { z = loop (String.length s - 1) Z.zero; mug = 0l }
+ in
+ test_mug "'hello'" (cord_atom "hello");
+ test_mug "'world'" (cord_atom "world");
+ test_mug "'urbit'" (cord_atom "urbit");
+ test_mug "'nock'" (cord_atom "nock");
+ Printf.printf "\n";
+
+ Printf.printf "EDGE CASES - Repeated values:\n";
+ Printf.printf "─────────────────────────────────────\n";
+ (* Same cell computed multiple times should have same mug *)
+ let pair = cell (atom 123) (atom 456) in
+ test_mug "[123 456] - first computation" pair;
+ test_mug "[123 456] - second computation" (cell (atom 123) (atom 456));
+
+ (* Nested identical cells *)
+ let nested = cell pair pair in
+ test_mug "[[123 456] [123 456]]" nested;
+ Printf.printf "\n";
+
+ Printf.printf "═══════════════════════════════════════\n";
+ Printf.printf "Test complete! Compare with C output.\n";
+ Printf.printf "═══════════════════════════════════════\n\n"
diff --git a/ocaml/test/test_two_stage_boot.ml b/ocaml/test/test_two_stage_boot.ml
index 62d262d..17c72a8 100644
--- a/ocaml/test/test_two_stage_boot.ml
+++ b/ocaml/test/test_two_stage_boot.ml
@@ -24,21 +24,27 @@ let stage1_ivory_boot env =
let start = Unix.gettimeofday () in
let pill = Serial.cue pill_bytes in
let elapsed = Unix.gettimeofday () -. start in
- Printf.printf " ✓ Cued in %.2fs\n\n%!" elapsed;
+ Printf.printf " ✓ Cued in %.2fs\n%!" elapsed;
+
+ let pill_mug = Noun.mug pill in
+ Printf.printf " Pill mug: 0x%08lx\n\n%!" pill_mug;
(* Check ivory structure: ["ivory" core] *)
Printf.printf "[3] Parsing ivory pill structure...\n%!";
match pill with
- | Noun.Cell (tag, core) ->
+ | Noun.Cell { h = tag; t = core; _ } ->
(* Check tag *)
let tag_str = match tag with
- | Noun.Atom z ->
+ | 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");
+ let tag_mug = Noun.mug tag in
+ let core_mug = Noun.mug core in
+ Printf.printf " Tag: '%s' (mug: 0x%08lx)\n" tag_str tag_mug;
+ Printf.printf " Core: %s (mug: 0x%08lx)\n\n"
+ (if Noun.is_cell core then "cell" else "atom") core_mug;
(* KEY DISCOVERY: The ivory pill tail IS the Arvo core! *)
Printf.printf "[4] Using ivory pill tail (Arvo core) for bootstrap...\n%!";
@@ -47,14 +53,16 @@ let stage1_ivory_boot env =
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%!";
+ Printf.printf " Subject: Arvo core (cell, mug: 0x%08lx)\n%!" core_mug;
begin try
let start = Unix.gettimeofday () in
let kernel = Boot.life core in
let elapsed = Unix.gettimeofday () -. start in
- Printf.printf " ✓ SUCCESS! Kernel built in %.4fs\n\n" elapsed;
+ let kernel_mug = Noun.mug kernel in
+ Printf.printf " ✓ SUCCESS! Kernel built in %.4fs\n" elapsed;
+ Printf.printf " Kernel mug: 0x%08lx\n\n%!" kernel_mug;
(* Verify kernel has poke at slot 23 *)
Printf.printf "[6] Verifying kernel structure...\n%!";
@@ -86,14 +94,14 @@ let stage1_ivory_boot env =
(if Noun.is_cell poke_battery then "cell ✓" else "atom ✗")
end;
- (* Compute mugs of small sub-structures for verification *)
+ (* Compute mugs of sub-structures for verification *)
Printf.printf " Computing mugs of sub-structures:\n";
let slot2_mug = Noun.mug slot2 in
let slot3_mug = Noun.mug slot3 in
let poke_mug = Noun.mug poke in
- Printf.printf " Slot 2 mug: 0x%lx\n" slot2_mug;
- Printf.printf " Slot 3 mug: 0x%lx\n" slot3_mug;
- Printf.printf " Poke mug: 0x%lx\n" poke_mug;
+ Printf.printf " Slot 2 (battery) mug: 0x%08lx\n" slot2_mug;
+ Printf.printf " Slot 3 (payload) mug: 0x%08lx\n" slot3_mug;
+ Printf.printf " Slot 23 (poke) mug: 0x%08lx\n" poke_mug;
Printf.printf "\n";
Printf.printf "╔═══════════════════════════════════════╗\n";
@@ -101,10 +109,8 @@ let stage1_ivory_boot env =
Printf.printf "╚═══════════════════════════════════════╝\n\n";
Printf.printf "⚠️ To verify correctness, compare these mugs with C:\n";
- Printf.printf " Run the C test and check if mugs match!\n\n";
-
- (* Print cache stats *)
- Noun.MugCache.stats ();
+ Printf.printf " Run: vere/zig-out/bin/ivory_boot_test\n";
+ Printf.printf " Check if mugs match!\n\n";
Some kernel
@@ -122,8 +128,8 @@ let stage1_ivory_boot env =
None
end
- | Noun.Atom _ ->
- Printf.printf " ✗ Pill is atom (expected cell)\n\n";
+ | Noun.Atom { z; _ } ->
+ Printf.printf " ✗ Pill is atom (expected cell): %s\n\n" (Z.to_string z);
None
(* Stage 2: Boot solid pill events *)