summaryrefslogtreecommitdiff
path: root/ocaml/test/test_opcodes.ml
blob: 7ef7a48457a11cc2d842049a3c10f5cde4925e0e (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
(* 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"