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 briefly *) let rec noun_shape = function | Noun.Atom z -> if Z.equal z Z.zero then "0" else Printf.sprintf "atom(%d bits)" (Z.numbits z) | Noun.Cell (h, t) -> Printf.sprintf "[%s %s]" (noun_shape h) (noun_shape t) (* Count the length of a noun list *) let rec list_length = function | Noun.Atom z when Z.equal z Z.zero -> 0 | Noun.Cell (_, t) -> 1 + list_length t | _ -> 0 let () = Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n"; Printf.printf "║ Boot Effects Analysis ║\n"; Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n"; let pier_path = Filename.concat project_root "test-pier-effects" 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...\n%!"; let state = State.create ~pier_path () in Printf.printf "\n[2] Booting ivory.pill...\n%!"; let ivory_path = Filename.concat project_root "pills/ivory.pill" in begin match Boot.boot_ivory state ivory_path with | Error (Boot.Invalid_pill msg) -> Printf.printf "✗ Ivory boot failed: %s\n%!" msg; exit 1 | Error (Boot.Unsupported msg) -> Printf.printf "✗ Unsupported: %s\n%!" msg; exit 1 | Ok () -> Printf.printf "✓ Ivory kernel loaded\n\n%!"; end; Printf.printf "[3] Processing solid.pill events and capturing effects...\n%!"; let solid_path = Filename.concat project_root "pills/solid.pill" in (* Track effects returned from each event *) let event_count = ref 0 in let effects_summary = ref [] in (* Custom apply function that wraps State.poke and logs effects *) let apply_with_logging state event = incr event_count; let effects = State.poke state event in let effect_count = list_length effects in (* Log every event, or just milestone events *) if !event_count <= 20 || !event_count mod 50 = 0 then begin Printf.printf " Event %d: %d effects returned\n%!" !event_count effect_count; end; (* Always log when we see effects! *) if effect_count > 0 then begin Printf.printf " *** EFFECTS FOUND! Event %d has %d effects ***\n%!" !event_count effect_count; Printf.printf " Effects shape: %s\n%!" (noun_shape effects); end; effects_summary := (!event_count, effect_count) :: !effects_summary; effects in (* Boot solid WITHOUT limit, capturing all effects *) begin match Boot.boot_solid ~apply:apply_with_logging state solid_path with | Error (Boot.Invalid_pill msg) -> Printf.printf "✗ Solid boot failed: %s\n%!" msg; exit 1 | Error (Boot.Unsupported msg) -> Printf.printf "✗ Unsupported: %s\n%!" msg; exit 1 | Ok () -> let eve = State.event_number state in Printf.printf "\n✓ Solid boot completed!\n%!"; Printf.printf " Total events processed: %Ld\n\n%!" eve; end; Printf.printf "[4] Effects Summary:\n%!"; let total_effects = List.fold_left (fun acc (_, count) -> acc + count) 0 !effects_summary in Printf.printf " Total effects returned: %d\n%!" total_effects; Printf.printf " Average effects per event: %.2f\n%!" (float_of_int total_effects /. float_of_int !event_count); (* Show which events had effects *) let with_effects = List.filter (fun (_, count) -> count > 0) !effects_summary in Printf.printf " Events with effects: %d/%d\n%!" (List.length with_effects) !event_count; if List.length with_effects > 0 then begin Printf.printf " First 10 events with effects:\n"; List.iter (fun (evt_num, count) -> Printf.printf " Event %d: %d effects\n" evt_num count ) (List.rev with_effects |> (fun l -> if List.length l > 10 then List.filteri (fun i _ -> i < 10) l else l)); end; State.close_eventlog state; Printf.printf "\n╔═══════════════════════════════════════════════════════╗\n"; Printf.printf "║ Boot Effects Analysis Complete! 🎉 ║\n"; Printf.printf "╚═══════════════════════════════════════════════════════╝\n\n"