summaryrefslogtreecommitdiff
path: root/ocaml/test/test_mug.ml
blob: 0f5df7c5c0c5ece281d2d3996a4a8d5e8b284967 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
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"