summaryrefslogtreecommitdiff
path: root/ocaml/scripts/test_poke_effects.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/scripts/test_poke_effects.ml')
-rw-r--r--ocaml/scripts/test_poke_effects.ml117
1 files changed, 117 insertions, 0 deletions
diff --git a/ocaml/scripts/test_poke_effects.ml b/ocaml/scripts/test_poke_effects.ml
new file mode 100644
index 0000000..1ec9f1b
--- /dev/null
+++ b/ocaml/scripts/test_poke_effects.ml
@@ -0,0 +1,117 @@
+open Nock_lib
+
+let rec find_project_root dir =
+ let pills_dir = Filename.concat dir "pills" in
+ if Sys.file_exists pills_dir && Sys.is_directory pills_dir then dir
+ else
+ let parent = Filename.dirname dir in
+ if String.equal parent dir then failwith "unable to locate project root containing pills/"
+ else find_project_root parent
+
+let project_root =
+ match Sys.getenv_opt "NEOVERE_ROOT" with
+ | Some root -> root
+ | None ->
+ let exe_dir = Filename.dirname Sys.executable_name in
+ find_project_root exe_dir
+
+(* Count noun list length *)
+let rec count_list = function
+ | Noun.Atom z when Z.equal z Z.zero -> 0
+ | Noun.Cell (_, t) -> 1 + count_list t
+ | _ -> 0
+
+let () =
+ Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n";
+ Printf.printf "║ Poke & Effects Test ║\n";
+ Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n";
+
+ let pier_path = Filename.concat project_root "test-pier-poke" in
+ if Sys.file_exists pier_path then begin
+ let _ = Sys.command (Printf.sprintf "rm -rf '%s'" pier_path) in ()
+ end;
+ Unix.mkdir pier_path 0o755;
+
+ Printf.printf "[1] Booting ship...\n%!";
+ let state = State.create ~pier_path () in
+
+ (* Boot ivory + solid *)
+ let ivory_path = Filename.concat project_root "pills/ivory.pill" in
+ let solid_path = Filename.concat project_root "pills/solid.pill" in
+
+ begin match Boot.boot_ivory state ivory_path with
+ | Error _ -> Printf.printf "Ivory boot failed\n"; exit 1
+ | Ok () -> Printf.printf "✓ Ivory loaded\n%!"
+ end;
+
+ begin match Boot.boot_solid_lifecycle state solid_path with
+ | Error _ -> Printf.printf "Solid boot failed\n"; exit 1
+ | Ok () -> Printf.printf "✓ Solid loaded (events: %Ld)\n\n%!" (State.event_number state)
+ end;
+
+ Printf.printf "[2] Testing poke performance...\n\n%!";
+
+ (* Create a simple test event *)
+ let now = Noun.atom (Z.shift_left (Z.of_string "0x8000000cce9e0d80") 64) in
+ let wire = Noun.cell
+ (Noun.atom (Z.of_int (Char.code 'd')))
+ (Noun.cell (Noun.atom_of_string "term")
+ (Noun.cell (Noun.atom (Z.of_int 1)) (Noun.atom Z.zero)))
+ in
+ let belt = Noun.atom_of_string "ret" in
+ let card = Noun.cell (Noun.atom_of_string "belt") belt in
+ let ovum = Noun.cell wire card in
+ let event = Noun.cell now ovum in
+
+ (* Benchmark poke *)
+ let iterations = 100 in
+ Printf.printf "Running %d pokes...\n%!" iterations;
+
+ let start_time = Sys.time () in
+ for i = 1 to iterations do
+ let effects = State.poke state event in
+ (* Just count effects *)
+ let count = count_list effects in
+ if i = 1 then
+ Printf.printf " First poke returned %d effects\n%!" count
+ done;
+ let elapsed = Sys.time () -. start_time in
+
+ Printf.printf "\nPerformance:\n";
+ Printf.printf " Total time: %.3fs\n" elapsed;
+ Printf.printf " Per poke: %.3fms\n" (elapsed *. 1000.0 /. float_of_int iterations);
+ Printf.printf " Pokes/sec: %.0f\n\n" (float_of_int iterations /. elapsed);
+
+ Printf.printf "[3] Examining effects structure...\n\n%!";
+
+ let effects = State.poke state event in
+ Printf.printf "Effects list structure:\n";
+ let rec show_effects depth = function
+ | Noun.Atom z when Z.equal z Z.zero ->
+ Printf.printf "%s~\n" (String.make (depth*2) ' ')
+ | Noun.Cell (h, t) ->
+ Printf.printf "%s[\n" (String.make (depth*2) ' ');
+ (* Show head *)
+ begin match h with
+ | Noun.Cell (wire_h, card_h) ->
+ Printf.printf "%s wire: %s\n" (String.make (depth*2) ' ')
+ (if Noun.is_cell wire_h then "cell" else "atom");
+ Printf.printf "%s card: %s\n" (String.make (depth*2) ' ')
+ (if Noun.is_cell card_h then "cell" else "atom")
+ | _ ->
+ Printf.printf "%s (malformed effect)\n" (String.make (depth*2) ' ')
+ end;
+ Printf.printf "%s]\n" (String.make (depth*2) ' ');
+ show_effects depth t
+ | _ -> Printf.printf "%s(unexpected structure)\n" (String.make (depth*2) ' ')
+ in
+ show_effects 0 effects;
+
+ let effect_count = count_list effects in
+ Printf.printf "\nTotal effects: %d\n\n" effect_count;
+
+ State.close_eventlog state;
+
+ Printf.printf "╔═══════════════════════════════════════════════════════╗\n";
+ Printf.printf "║ Test Complete! 🎉 ║\n";
+ Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n"