diff options
Diffstat (limited to 'ocaml/test')
-rw-r--r-- | ocaml/test/dune | 10 | ||||
-rw-r--r-- | ocaml/test/test_bisect_lifecycle.ml | 71 | ||||
-rw-r--r-- | ocaml/test/test_op8.ml | 38 | ||||
-rw-r--r-- | ocaml/test/test_op9.ml | 45 | ||||
-rw-r--r-- | ocaml/test/test_opcodes.ml | 75 | ||||
-rw-r--r-- | ocaml/test/test_simple_lifecycle.ml | 47 | ||||
-rw-r--r-- | ocaml/test/test_two_stage_boot.ml | 5 |
7 files changed, 291 insertions, 0 deletions
diff --git a/ocaml/test/dune b/ocaml/test/dune index 84a47a3..d23fc4d 100644 --- a/ocaml/test/dune +++ b/ocaml/test/dune @@ -278,6 +278,16 @@ (libraries nock_lib)) (executable + (name test_opcodes) + (modules test_opcodes) + (libraries nock_lib)) + +(executable + (name test_bisect_lifecycle) + (modules test_bisect_lifecycle) + (libraries nock_lib eio_main)) + +(executable (name test_slot3) (modules test_slot3) (libraries nock_lib eio_main)) diff --git a/ocaml/test/test_bisect_lifecycle.ml b/ocaml/test/test_bisect_lifecycle.ml new file mode 100644 index 0000000..7e37516 --- /dev/null +++ b/ocaml/test/test_bisect_lifecycle.ml @@ -0,0 +1,71 @@ +(* Bisect the ivory pill to find where lifecycle formula diverges *) + +open Nock_lib + +let lifecycle_formula = Noun.cell + (Noun.atom 2) + (Noun.cell + (Noun.cell (Noun.atom 0) (Noun.atom 3)) + (Noun.cell (Noun.atom 0) (Noun.atom 2))) + +let test_lifecycle subject_name subject = + Printf.printf "Testing: %s\n" subject_name; + Printf.printf " Subject mug: 0x%08lx\n" (Noun.mug subject); + + (* Check if subject has valid structure for lifecycle *) + if not (Noun.is_cell subject) then begin + Printf.printf " SKIP: subject is atom\n\n"; + None + end else begin + let slot2 = Noun.head subject in + + (* Check if slot 2 is a valid formula *) + if not (Noun.is_cell slot2) then begin + Printf.printf " SKIP: slot 2 is atom (not a formula)\n\n"; + None + end else begin + try + let result = Nock.nock_on subject lifecycle_formula in + let result_mug = Noun.mug result in + Printf.printf " Result mug: 0x%08lx\n\n" result_mug; + Some result_mug + with _ -> + Printf.printf " CRASH: nock failed\n\n"; + None + end + end + +let rec walk_tree prefix subject depth max_depth = + if depth >= max_depth then () else begin + (* Test current node *) + let _ = test_lifecycle prefix subject in + + (* Walk children if cell *) + if Noun.is_cell subject then begin + let h = Noun.head subject in + let t = Noun.tail subject in + walk_tree (prefix ^ ".2") h (depth + 1) max_depth; + walk_tree (prefix ^ ".3") t (depth + 1) max_depth + end + end + +let () = + Eio_main.run (fun env -> + let fs = Eio.Stdenv.fs env in + + Printf.printf "Loading ivory.pill...\n"; + let pill_bytes = Eio.Path.(load (fs / "ivory.pill")) |> Bytes.of_string in + let pill = Serial.cue pill_bytes in + let core = Noun.tail pill in + + Printf.printf "Ivory core mug: 0x%08lx\n\n" (Noun.mug core); + Printf.printf "Walking tree and testing lifecycle at each node...\n"; + Printf.printf "Format: slot path (e.g. '.2.3' = slot 6)\n\n"; + + (* Reset counters *) + Nock.call_count := 0; + Nock.depth := 0; + + (* Walk tree up to depth 5 *) + walk_tree "core" core 0 5 + ) diff --git a/ocaml/test/test_op8.ml b/ocaml/test/test_op8.ml new file mode 100644 index 0000000..5c63926 --- /dev/null +++ b/ocaml/test/test_op8.ml @@ -0,0 +1,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") diff --git a/ocaml/test/test_op9.ml b/ocaml/test/test_op9.ml new file mode 100644 index 0000000..dc34c8a --- /dev/null +++ b/ocaml/test/test_op9.ml @@ -0,0 +1,45 @@ +(* Test opcode 9 (invoke) *) + +open Nock_lib + +let () = + (* Build a simple core: [[formula] payload] *) + (* Formula at slot 2: [0 3] (returns payload) *) + (* Payload at slot 3: 42 *) + let core = Noun.cell + (Noun.cell (Noun.atom 0) (Noun.atom 3)) + (Noun.atom 42) + in + + (* Test: *[core [9 2 [0 1]]] *) + (* This should: + 1. Evaluate [0 1] on core → core + 2. Extract slot 2 from core → [0 3] + 3. Evaluate [0 3] on core → 42 + *) + + let subject = core in + let formula = Noun.cell + (Noun.atom 9) + (Noun.cell + (Noun.atom 2) + (Noun.cell (Noun.atom 0) (Noun.atom 1))) + in + + Printf.printf "Subject (core): [[0 3] 42]\n"; + Printf.printf "Subject mug: 0x%08lx\n" (Noun.mug subject); + Printf.printf "Formula: [9 2 [0 1]]\n"; + Printf.printf "Formula mug: 0x%08lx\n\n" (Noun.mug formula); + + Printf.printf "This should compute:\n"; + Printf.printf " 1. Evaluate [0 1] on core → core\n"; + Printf.printf " 2. Extract slot 2 from result → [0 3]\n"; + Printf.printf " 3. Evaluate [0 3] on core → 42\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" + (match result with + | Noun.Atom { z; _ } -> Z.to_string z + | Noun.Cell _ -> "cell") 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" diff --git a/ocaml/test/test_simple_lifecycle.ml b/ocaml/test/test_simple_lifecycle.ml new file mode 100644 index 0000000..96e0603 --- /dev/null +++ b/ocaml/test/test_simple_lifecycle.ml @@ -0,0 +1,47 @@ +(* Simple test of lifecycle formula on small noun *) + +open Nock_lib + +let () = + (* Test subject: [[formula] payload] *) + (* Formula: [7 [0 3] [0 1]] - compose: *[payload [0 1]] returns payload *) + (* Payload: [42 99] *) + 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 + + (* Lifecycle formula: [2 [0 3] [0 2]] *) + 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 + + Printf.printf "Subject: [[7 [0 3] [0 1]] [42 99]]\n"; + Printf.printf "Subject mug: 0x%08lx\n" (Noun.mug subject); + Printf.printf "Formula: [2 [0 3] [0 2]]\n"; + Printf.printf "Formula mug: 0x%08lx\n\n" (Noun.mug formula); + + Printf.printf "Slot 2 of subject (formula): [7 [0 3] [0 1]] (mug=0x%08lx)\n" + (Noun.mug formula_slot2); + + Printf.printf "Slot 3 of subject (payload): [42 99] (mug=0x%08lx)\n\n" + (Noun.mug payload); + + Printf.printf "Running nock...\n"; + Printf.printf "This should compute: *[[42 99] [7 [0 3] [0 1]]]\n"; + Printf.printf "Which is: *[99 [0 1]] = 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" + (match result with + | Noun.Atom { z; _ } -> Z.to_string z + | Noun.Cell _ -> "cell") diff --git a/ocaml/test/test_two_stage_boot.ml b/ocaml/test/test_two_stage_boot.ml index 863c3a1..258e882 100644 --- a/ocaml/test/test_two_stage_boot.ml +++ b/ocaml/test/test_two_stage_boot.ml @@ -54,6 +54,11 @@ let stage1_ivory_boot env = Printf.printf "[5] Running u3v_life() on Arvo core...\n%!"; Printf.printf " Formula: [2 [0 3] [0 2]]\n"; Printf.printf " Subject: Arvo core (cell, mug: 0x%08lx)\n%!" core_mug; + + (* Check slot 3 of input core *) + let core_slot3 = Noun.slot (Z.of_int 3) core in + Printf.printf " Core slot 3 (before lifecycle) mug: 0x%08lx\n%!" (Noun.mug core_slot3); + Printf.printf " Enabling mug logging for all nock steps...\n%!"; (* Enable mug logging at every step *) |