summaryrefslogtreecommitdiff
path: root/ocaml/test/test_op8.ml
blob: 5c6392631bc0180ac8443f0b0a882d7d819f7764 (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
(* Test opcode 8 (extend) *)

open Nock_lib

let () =
  (* Test: *[[42 99] [8 [1 123] [0 1]]] *)
  (* This should compute: *[[123 [42 99]] [0 1]] = [123 [42 99]] *)

  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))  (* [1 123] produces 123 *)
      (Noun.cell (Noun.atom 0) (Noun.atom 1)))   (* [0 1] returns whole subject *)
  in

  Printf.printf "Subject: [42 99]\n";
  Printf.printf "Subject mug: 0x%08lx\n" (Noun.mug subject);
  Printf.printf "Formula: [8 [1 123] [0 1]]\n";
  Printf.printf "Formula mug: 0x%08lx\n\n" (Noun.mug formula);

  Printf.printf "This should compute:\n";
  Printf.printf "  1. Evaluate [1 123] on [42 99] → 123\n";
  Printf.printf "  2. Extend subject: [123 [42 99]]\n";
  Printf.printf "  3. Evaluate [0 1] on [123 [42 99]] → [123 [42 99]]\n\n";

  let result = Nock.nock_on subject formula in

  Printf.printf "Result mug: 0x%08lx\n" (Noun.mug result);
  Printf.printf "Result: %s\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 (unexpected structure)"
    else "atom")