summaryrefslogtreecommitdiff
path: root/ocaml/test/old/test_arvo_structure.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/test/old/test_arvo_structure.ml')
-rw-r--r--ocaml/test/old/test_arvo_structure.ml116
1 files changed, 116 insertions, 0 deletions
diff --git a/ocaml/test/old/test_arvo_structure.ml b/ocaml/test/old/test_arvo_structure.ml
new file mode 100644
index 0000000..cbd9f65
--- /dev/null
+++ b/ocaml/test/old/test_arvo_structure.ml
@@ -0,0 +1,116 @@
+(* Examine Arvo Kernel Structure
+ *
+ * Load the ivory pill and inspect the kernel to understand:
+ * - Is it a gate (cell)?
+ * - Where is the battery?
+ * - What's the structure?
+ *)
+
+open Nock_lib
+
+let rec describe_noun_structure noun depth =
+ if depth > 5 then
+ "..."
+ else
+ match noun with
+ | Noun.Atom z ->
+ if Z.numbits z > 64 then
+ Printf.sprintf "Atom(huge: %d bits)" (Z.numbits z)
+ else
+ Printf.sprintf "Atom(%s)" (Z.to_string z)
+ | Noun.Cell (a, b) ->
+ Printf.sprintf "Cell(\n%s%s,\n%s%s)"
+ (String.make (depth * 2) ' ')
+ (describe_noun_structure a (depth + 1))
+ (String.make (depth * 2) ' ')
+ (describe_noun_structure b (depth + 1))
+
+let test_arvo_structure env =
+ Printf.printf "๐Ÿ” Examining Arvo Kernel Structure\n\n";
+
+ Eio.Switch.run @@ fun _sw ->
+ let fs = Eio.Stdenv.fs env in
+
+ (* Load ivory pill *)
+ Printf.printf "Loading ivory pill...\n%!";
+ let state = State.create () in
+
+ match Boot.boot_from_file ~fs state "ivory.pill" with
+ | Error msg ->
+ Printf.printf "โœ— Failed to load pill: %s\n%!" msg
+ | Ok () ->
+ Printf.printf "โœ“ Pill loaded!\n\n";
+
+ let kernel = State.get_arvo state in
+
+ (* Check if it's a cell *)
+ Printf.printf "Kernel structure:\n";
+ if Noun.is_cell kernel then begin
+ Printf.printf " โœ“ Kernel is a CELL (likely a gate!)\n\n";
+
+ let head = Noun.head kernel in
+ let tail = Noun.tail kernel in
+
+ Printf.printf "Head (slot 2 - battery?):\n";
+ if Noun.is_cell head then
+ Printf.printf " Cell (battery with multiple arms)\n"
+ else
+ (match head with
+ | Noun.Atom z -> Printf.printf " Atom: %s\n" (Z.to_string z)
+ | _ -> ());
+
+ Printf.printf "\nTail (slot 3 - sample + context?):\n";
+ if Noun.is_cell tail then begin
+ Printf.printf " Cell (has sample and context)\n";
+ let sample = Noun.head tail in
+ let context = Noun.tail tail in
+
+ Printf.printf "\n Sample (slot 6):\n";
+ Printf.printf " %s\n" (describe_noun_structure sample 2);
+
+ Printf.printf "\n Context (slot 7):\n";
+ if Noun.is_atom context then
+ (match context with
+ | Noun.Atom z -> Printf.printf " Atom: %s\n" (Z.to_string z)
+ | _ -> ())
+ else
+ Printf.printf " Cell (nested context)\n"
+ end else
+ (match tail with
+ | Noun.Atom z -> Printf.printf " Atom: %s\n" (Z.to_string z)
+ | _ -> ());
+
+ (* Test: Try to call arm 2 with current sample *)
+ Printf.printf "\n๐Ÿงช Testing gate call with opcode 9...\n";
+ Printf.printf "Formula: [9 2 0 1] (call arm 2 of whole subject)\n\n";
+
+ try
+ let formula = Noun.cell
+ (Noun.atom 9)
+ (Noun.cell (Noun.atom 2) (Noun.cell (Noun.atom 0) (Noun.atom 1))) in
+
+ let start = Unix.gettimeofday () in
+ let _result = Nock.nock_on kernel formula in
+ let elapsed = Unix.gettimeofday () -. start in
+
+ Printf.printf "โœ“ Gate call succeeded in %.4f seconds!\n" elapsed;
+ Printf.printf "This proves Arvo is a proper gate!\n\n"
+ with e ->
+ Printf.printf "โœ— Gate call failed: %s\n" (Printexc.to_string e);
+ Printf.printf "Kernel might not be a standard gate structure\n\n"
+
+ end else begin
+ (match kernel with
+ | Noun.Atom z -> Printf.printf " Kernel is an ATOM: %s\n" (Z.to_string z)
+ | _ -> ());
+ Printf.printf " This is unexpected - Arvo should be a gate (cell)\n"
+ end
+
+let () =
+ Printf.printf "\n";
+ Printf.printf "โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•\n";
+ Printf.printf " Examining Arvo Kernel Structure from Ivory Pill\n";
+ Printf.printf "โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•โ•\n";
+ Printf.printf "\n";
+
+ Eio_main.run test_arvo_structure