summaryrefslogtreecommitdiff
path: root/ocaml/scripts/test_effects_parsing.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/scripts/test_effects_parsing.ml')
-rw-r--r--ocaml/scripts/test_effects_parsing.ml120
1 files changed, 120 insertions, 0 deletions
diff --git a/ocaml/scripts/test_effects_parsing.ml b/ocaml/scripts/test_effects_parsing.ml
new file mode 100644
index 0000000..f634825
--- /dev/null
+++ b/ocaml/scripts/test_effects_parsing.ml
@@ -0,0 +1,120 @@
+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
+
+(* Create a simple test event to poke Arvo *)
+let make_test_event () =
+ (* Create a simple belt event: [timestamp [wire [%belt %ret]]] *)
+ (* This simulates pressing Enter in the dojo *)
+ (* Timestamp: use a simple value for testing *)
+ 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
+ Noun.cell now ovum
+
+let () =
+ Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n";
+ Printf.printf "║ Effects Parsing Test ║\n";
+ Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n";
+
+ let pier_path = Filename.concat project_root "test-pier-effects-parse" in
+ Printf.printf "Creating test pier at: %s\n%!" pier_path;
+
+ if Sys.file_exists pier_path then begin
+ Printf.printf "Removing old test pier...\n%!";
+ let _ = Sys.command (Printf.sprintf "rm -rf '%s'" pier_path) in
+ ()
+ end;
+
+ Unix.mkdir pier_path 0o755;
+
+ Printf.printf "\n[1] Creating state and booting...\n%!";
+ let state = State.create ~pier_path () in
+
+ (* Boot ivory *)
+ let ivory_path = Filename.concat project_root "pills/ivory.pill" in
+ begin match Boot.boot_ivory state ivory_path with
+ | Error e -> Printf.printf "Ivory boot failed\n"; exit 1
+ | Ok () -> Printf.printf "✓ Ivory kernel loaded\n%!"
+ end;
+
+ (* Boot solid *)
+ let solid_path = Filename.concat project_root "pills/solid.pill" in
+ begin match Boot.boot_solid_lifecycle state solid_path with
+ | Error e -> Printf.printf "Solid boot failed\n"; exit 1
+ | Ok () ->
+ Printf.printf "✓ Solid boot completed\n";
+ Printf.printf " Events: %Ld\n\n%!" (State.event_number state)
+ end;
+
+ Printf.printf "[2] Sending test event to Arvo...\n%!";
+ let test_event = make_test_event () in
+
+ let result = State.poke state test_event in
+
+ Printf.printf "[3] Parsing effects from poke result...\n\n%!";
+
+ begin match result with
+ | Noun.Cell (effects_noun, new_core) ->
+ Printf.printf "Poke returned:\n";
+ Printf.printf " Effects: %s\n" (if Noun.is_cell effects_noun then "list" else "atom");
+ Printf.printf " New core: %s\n\n" (if Noun.is_cell new_core then "valid" else "invalid");
+
+ let effects = Nock_lib.Effects.parse_effects effects_noun in
+ Printf.printf "Parsed %d effects:\n\n" (List.length effects);
+
+ List.iteri (fun i eff ->
+ Printf.printf "Effect %d:\n" (i + 1);
+ Printf.printf " Wire: %s\n" (Nock_lib.Effects.show_wire eff.wire);
+ Printf.printf " Card: %s\n" (Nock_lib.Effects.show_card eff.card);
+
+ (* If it's a blit, show details *)
+ begin match eff.card with
+ | Nock_lib.Effects.Blit (Nock_lib.Effects.Lin text) ->
+ Printf.printf " Text: %S\n" text
+ | Nock_lib.Effects.Blit (Nock_lib.Effects.Mor blits) ->
+ Printf.printf " Contains %d blits:\n" (List.length blits);
+ List.iteri (fun j blit ->
+ match blit with
+ | Nock_lib.Effects.Lin t -> Printf.printf " [%d] %S\n" (j+1) t
+ | _ -> Printf.printf " [%d] (other blit)\n" (j+1)
+ ) blits
+ | _ -> ()
+ end;
+
+ Printf.printf "\n";
+ ) effects;
+
+ if List.length effects = 0 then
+ Printf.printf "No effects returned (this is normal for some events)\n\n";
+
+ | _ ->
+ Printf.printf "Unexpected poke result structure!\n";
+ Printf.printf "Result is an atom: %b\n" (Noun.is_atom result);
+ end;
+
+ State.close_eventlog state;
+
+ Printf.printf "╔═══════════════════════════════════════════════════════╗\n";
+ Printf.printf "║ Effects Parsing Test Complete! 🎉 ║\n";
+ Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n"