summaryrefslogtreecommitdiff
path: root/ocaml/scripts/inspect_bot_events.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/scripts/inspect_bot_events.ml')
-rw-r--r--ocaml/scripts/inspect_bot_events.ml89
1 files changed, 89 insertions, 0 deletions
diff --git a/ocaml/scripts/inspect_bot_events.ml b/ocaml/scripts/inspect_bot_events.ml
new file mode 100644
index 0000000..f65e5c6
--- /dev/null
+++ b/ocaml/scripts/inspect_bot_events.ml
@@ -0,0 +1,89 @@
+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
+
+(* Helper to show noun structure *)
+let rec noun_shape ?(depth=0) ?(max_depth=5) noun =
+ if depth >= max_depth then "..."
+ else match noun with
+ | Noun.Atom z ->
+ if Z.equal z Z.zero then "0"
+ else if Z.numbits z <= 32 then
+ Printf.sprintf "%Ld" (Z.to_int64 z)
+ else
+ Printf.sprintf "atom(%d bits)" (Z.numbits z)
+ | Noun.Cell (h, t) ->
+ Printf.sprintf "[%s %s]"
+ (noun_shape ~depth:(depth+1) ~max_depth h)
+ (noun_shape ~depth:(depth+1) ~max_depth t)
+
+(* Convert list to OCaml list *)
+let rec list_to_ocaml_list noun =
+ match noun with
+ | Noun.Atom z when Z.equal z Z.zero -> []
+ | Noun.Cell (h, t) -> h :: list_to_ocaml_list t
+ | _ -> failwith "malformed list"
+
+let () =
+ Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n";
+ Printf.printf "║ Bot Events Inspector ║\n";
+ Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n";
+
+ let solid_path = Filename.concat project_root "pills/solid.pill" in
+ Printf.printf "Loading solid.pill...\n%!";
+
+ let pill = Boot.cue_file solid_path in
+
+ Printf.printf "Parsing solid pill structure...\n%!";
+
+ match Boot.parse_solid pill with
+ | Error e ->
+ Printf.printf "Failed to parse: %s\n" (match e with
+ | Boot.Invalid_pill msg -> msg
+ | Boot.Unsupported msg -> msg)
+ | Ok (bot, _mod_, _use_) ->
+ Printf.printf "✓ Solid pill parsed\n\n";
+
+ let bot_list = list_to_ocaml_list bot in
+ Printf.printf "Bot events: %d\n\n" (List.length bot_list);
+
+ List.iteri (fun i event ->
+ Printf.printf "Bot Event %d:\n" (i + 1);
+ Printf.printf " Shape: %s\n" (noun_shape ~max_depth:3 event);
+ Printf.printf " Is atom: %b\n" (Noun.is_atom event);
+ Printf.printf " Is cell: %b\n" (Noun.is_cell event);
+
+ if Noun.is_cell event then begin
+ let head = Noun.head event in
+ let tail = Noun.tail event in
+ Printf.printf " Head shape: %s\n" (noun_shape ~max_depth:2 head);
+ Printf.printf " Tail shape: %s\n" (noun_shape ~max_depth:2 tail);
+
+ (* Check if it could be a formula (common formula patterns) *)
+ match head with
+ | Noun.Atom z ->
+ let n = Z.to_int z in
+ if n >= 0 && n <= 11 then
+ Printf.printf " Head is opcode %d!\n" n
+ | _ -> ()
+ end;
+
+ Printf.printf "\n";
+ ) bot_list;
+
+ Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n";
+ Printf.printf "║ Analysis Complete ║\n";
+ Printf.printf "╚═══════════════════════════════════════════════════════╝\n"