summaryrefslogtreecommitdiff
path: root/ocaml/test/test_opcodes.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_opcodes.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_opcodes.ml')
-rw-r--r--ocaml/test/test_opcodes.ml75
1 files changed, 75 insertions, 0 deletions
diff --git a/ocaml/test/test_opcodes.ml b/ocaml/test/test_opcodes.ml
new file mode 100644
index 0000000..7ef7a48
--- /dev/null
+++ b/ocaml/test/test_opcodes.ml
@@ -0,0 +1,75 @@
+(* Consolidated opcode tests *)
+
+open Nock_lib
+
+let test_name name =
+ Printf.printf "\n=== %s ===\n" name
+
+let test_op2_simple () =
+ test_name "Opcode 2: Simple lifecycle [0 1] → 99";
+ let formula_slot2 = Noun.cell (Noun.atom 0) (Noun.atom 1) in
+ let payload = Noun.atom 99 in
+ let subject = Noun.cell formula_slot2 payload in
+ let formula = Noun.cell (Noun.atom 2)
+ (Noun.cell (Noun.cell (Noun.atom 0) (Noun.atom 3))
+ (Noun.cell (Noun.atom 0) (Noun.atom 2))) in
+
+ let result = Nock.nock_on subject formula in
+ Printf.printf "Result: %s, mug: 0x%08lx\n"
+ (match result with Noun.Atom { z; _ } -> Z.to_string z | _ -> "cell")
+ (Noun.mug result)
+
+let test_op7_compose () =
+ test_name "Opcode 7: Compose with [0 1]";
+ let formula_slot2 = Noun.cell (Noun.atom 7)
+ (Noun.cell (Noun.cell (Noun.atom 0) (Noun.atom 3))
+ (Noun.cell (Noun.atom 0) (Noun.atom 1))) in
+ let payload = Noun.cell (Noun.atom 42) (Noun.atom 99) in
+ let subject = Noun.cell formula_slot2 payload in
+ let formula = Noun.cell (Noun.atom 2)
+ (Noun.cell (Noun.cell (Noun.atom 0) (Noun.atom 3))
+ (Noun.cell (Noun.atom 0) (Noun.atom 2))) in
+
+ let result = Nock.nock_on subject formula in
+ Printf.printf "Result mug: 0x%08lx\n" (Noun.mug result)
+
+let test_op8_extend () =
+ test_name "Opcode 8: Extend subject";
+ let subject = Noun.cell (Noun.atom 42) (Noun.atom 99) in
+ let formula = Noun.cell (Noun.atom 8)
+ (Noun.cell (Noun.cell (Noun.atom 1) (Noun.atom 123))
+ (Noun.cell (Noun.atom 0) (Noun.atom 1))) in
+
+ let result = Nock.nock_on subject formula in
+ Printf.printf "Result: %s, mug: 0x%08lx\n"
+ (if Noun.is_cell result then
+ let h = Noun.head result in
+ let t = Noun.tail result in
+ match (h, t) with
+ | (Noun.Atom { z = zh; _ }, Noun.Cell { h = Noun.Atom { z = zth; _ }; t = Noun.Atom { z = ztt; _ }; _ }) ->
+ Printf.sprintf "[%s [%s %s]]" (Z.to_string zh) (Z.to_string zth) (Z.to_string ztt)
+ | _ -> "cell"
+ else "atom")
+ (Noun.mug result)
+
+let test_op9_invoke () =
+ test_name "Opcode 9: Invoke core arm";
+ let core = Noun.cell
+ (Noun.cell (Noun.atom 0) (Noun.atom 3))
+ (Noun.atom 42) in
+ let formula = Noun.cell (Noun.atom 9)
+ (Noun.cell (Noun.atom 2)
+ (Noun.cell (Noun.atom 0) (Noun.atom 1))) in
+
+ let result = Nock.nock_on core formula in
+ Printf.printf "Result: %s, mug: 0x%08lx\n"
+ (match result with Noun.Atom { z; _ } -> Z.to_string z | _ -> "cell")
+ (Noun.mug result)
+
+let () =
+ Printf.printf "Testing Nock opcodes...\n";
+ test_op2_simple ();
+ test_op7_compose ();
+ test_op8_extend ();
+ test_op9_invoke ();
+ Printf.printf "\nAll tests complete.\n"