summaryrefslogtreecommitdiff
path: root/ocaml/scripts/boot_pill.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/scripts/boot_pill.ml')
-rw-r--r--ocaml/scripts/boot_pill.ml55
1 files changed, 55 insertions, 0 deletions
diff --git a/ocaml/scripts/boot_pill.ml b/ocaml/scripts/boot_pill.ml
new file mode 100644
index 0000000..4662c47
--- /dev/null
+++ b/ocaml/scripts/boot_pill.ml
@@ -0,0 +1,55 @@
+open Nock_lib
+
+let digest noun =
+ (* Use jam to mirror Vere's hashing pathway and avoid quadratic marshaling. *)
+ Serial.jam noun
+ |> Bytes.unsafe_to_string
+ |> Digest.string
+ |> Digest.to_hex
+
+let ensure_debug_logging () =
+ match Sys.getenv_opt "NEOVERE_BOOT_DEBUG" with
+ | Some _ -> ()
+ | None -> Unix.putenv "NEOVERE_BOOT_DEBUG" "1"
+
+let file_size path =
+ let ic = open_in_bin path in
+ let len = in_channel_length ic in
+ close_in ic;
+ len
+
+let run_ivory path =
+ ensure_debug_logging ();
+ Printf.printf "[boot_pill] ivory path=%s\n%!" path;
+ (try
+ let size = file_size path in
+ Printf.printf "[boot_pill] pill size=%d bytes\n%!" size
+ with Sys_error msg ->
+ Printf.printf "[boot_pill] warning: %s\n%!" msg);
+ let state = State.create () in
+ let start = Sys.time () in
+ match Boot.boot_ivory state path with
+ | Error err ->
+ let msg = match err with
+ | Boot.Invalid_pill s
+ | Boot.Unsupported s -> s
+ in
+ Printf.printf "boot_ivory error: %s\n%!" msg
+ | Ok () ->
+ let elapsed = Sys.time () -. start in
+ Printf.printf "[boot_pill] boot complete in %.3fs\n%!" elapsed;
+ let core = State.arvo_core state in
+ Printf.printf "[boot_pill] computing digest...\n%!";
+ let dig = digest core in
+ Printf.printf "[boot_pill] digest ready\n%!";
+ Printf.printf "ivory core digest=%s\n%!" dig
+
+let () =
+ if Array.length Sys.argv < 2 then begin
+ prerr_endline "usage: boot_pill path";
+ exit 1
+ end;
+ let path = Sys.argv.(1) in
+ let start = Sys.time () in
+ run_ivory path;
+ Printf.printf "elapsed=%.2fs\n%!" (Sys.time () -. start)