summaryrefslogtreecommitdiff
path: root/ocaml/test/test_nock.ml
blob: ffa4f6381138bcfe40d486a2790fa05617106ef1 (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
open Nock_lib
open Noun
open Nock

let atom = atom_of_int

let check_noun name expect actual =
  let rec to_string noun =
    match noun with
    | Atom z -> Z.to_string z
    | Cell (h, t) -> Printf.sprintf "[%s %s]" (to_string h) (to_string t)
  in
  Printf.printf "[%s] expect=%s actual=%s\n%!"
    name (to_string expect) (to_string actual);
  Alcotest.(check bool) name true (equal expect actual)

let check_eval name subject formula expect =
  let result = nock subject formula in
  check_noun name expect result

let check_exit name f =
  Alcotest.check_raises name Exit f

let test_slots () =
  let tree =
    cell
      (cell (atom 1) (atom 2))
      (cell (atom 3) (atom 4))
  in
  check_noun "slot 1" tree (slot Z.one tree);
  check_noun "slot 2" (cell (atom 1) (atom 2)) (slot (Z.of_int 2) tree);
  check_noun "slot 3" (cell (atom 3) (atom 4)) (slot (Z.of_int 3) tree);
  check_noun "slot 4" (atom 1) (slot (Z.of_int 4) tree);
  check_noun "slot 5" (atom 2) (slot (Z.of_int 5) tree);
  check_noun "slot 6" (atom 3) (slot (Z.of_int 6) tree);
  check_noun "slot 7" (atom 4) (slot (Z.of_int 7) tree);
  check_exit "slot invalid axis" (fun () -> ignore (slot Z.zero tree))

let test_opcode_0 () =
  let subject = cell (atom 4) (atom 5) in
  check_eval "axis 1" subject (cell (atom 0) (atom 1)) subject;
  check_eval "axis 2" subject (cell (atom 0) (atom 2)) (atom 4);
  check_eval "axis 3" subject (cell (atom 0) (atom 3)) (atom 5)

let test_opcode_1 () =
  let subject = atom 99 in
  check_eval "const atom" subject (cell (atom 1) (atom 42)) (atom 42);
  check_eval "const cell" subject (cell (atom 1) (cell (atom 1) (atom 2)))
    (cell (atom 1) (atom 2))

let test_opcode_2 () =
  let subject = atom 42 in
  let formula =
    cell (atom 2)
      (cell (cell (atom 1) (atom 99))
        (cell (atom 1) (cell (atom 0) (atom 1))))
  in
  check_eval "recursive eval" subject formula (atom 99)

let test_opcode_3 () =
  check_eval "cell test atom" (atom 42)
    (cell (atom 3) (cell (atom 1) (atom 42)))
    (atom 1);
  check_eval "cell test cell" (atom 42)
    (cell (atom 3) (cell (atom 1) (cell (atom 1) (atom 2))))
    (atom 0)

let test_opcode_4 () =
  check_eval "increment constant" (atom 0)
    (cell (atom 4) (cell (atom 1) (atom 41)))
    (atom 42);
  check_eval "increment subject" (atom 0)
    (cell (atom 4) (cell (atom 0) (atom 1)))
    (atom 1)

let test_opcode_5 () =
  check_eval "not equal" (atom 0)
    (cell (atom 5)
      (cell (cell (atom 1) (atom 4)) (cell (atom 1) (atom 5))))
    (atom 1);
  check_eval "equal" (atom 0)
    (cell (atom 5)
      (cell (cell (atom 1) (atom 4)) (cell (atom 1) (atom 4))))
    (atom 0)

let test_opcode_6 () =
  check_eval "if zero" (atom 42)
    (cell (atom 6)
      (cell (cell (atom 1) (atom 0))
        (cell (cell (atom 1) (atom 11)) (cell (atom 1) (atom 22)))))
    (atom 11);
  check_eval "if one" (atom 42)
    (cell (atom 6)
      (cell (cell (atom 1) (atom 1))
        (cell (cell (atom 1) (atom 11)) (cell (atom 1) (atom 22)))))
    (atom 22)

let test_opcode_7 () =
  check_eval "compose" (atom 42)
    (cell (atom 7)
      (cell (cell (atom 1) (atom 99)) (cell (atom 0) (atom 1))))
    (atom 99)

let test_opcode_8 () =
  check_eval "push" (atom 42)
    (cell (atom 8)
      (cell (cell (atom 1) (atom 99)) (cell (atom 0) (atom 1))))
    (cell (atom 99) (atom 42))

let test_opcode_9 () =
  let subject =
    cell
      (atom 99)
      (cell (atom 4) (cell (atom 0) (atom 2)))
  in
  let formula =
    cell (atom 9)
      (cell (atom 3)
        (cell (atom 0) (atom 1)))
  in
  check_eval "call formula at axis 3" subject formula (atom 100)

let test_opcode_10 () =
  check_eval "hint" (atom 42)
    (cell (atom 10)
      (cell (atom 99) (cell (atom 1) (atom 11))))
    (atom 11)

let test_opcode_11 () =
  check_eval "hint dyn" (atom 42)
    (cell (atom 11)
      (cell (atom 99) (cell (atom 1) (atom 11))))
    (atom 11)

let tests =
  [
    "slots", `Quick, test_slots;
    "opcode 0", `Quick, test_opcode_0;
    "opcode 1", `Quick, test_opcode_1;
    "opcode 2", `Quick, test_opcode_2;
    "opcode 3", `Quick, test_opcode_3;
    "opcode 4", `Quick, test_opcode_4;
    "opcode 5", `Quick, test_opcode_5;
    "opcode 6", `Quick, test_opcode_6;
    "opcode 7", `Quick, test_opcode_7;
    "opcode 8", `Quick, test_opcode_8;
    "opcode 9", `Quick, test_opcode_9;
    "opcode 10", `Quick, test_opcode_10;
    "opcode 11", `Quick, test_opcode_11;
  ]

let () = Alcotest.run "nock" [ "core", tests ]