summaryrefslogtreecommitdiff
path: root/ocaml/bin
diff options
context:
space:
mode:
authorpolwex <polwex@sortug.com>2025-10-20 13:13:39 +0700
committerpolwex <polwex@sortug.com>2025-10-20 13:13:39 +0700
commitd21900836f89b2bf9cd55ff1708a4619c8b89656 (patch)
treebb3a5842ae408ffa465814c6bbf27a5002866252 /ocaml/bin
neoinityes
Diffstat (limited to 'ocaml/bin')
-rw-r--r--ocaml/bin/dune9
-rw-r--r--ocaml/bin/neovere.ml190
-rw-r--r--ocaml/bin/neovere_live.ml146
3 files changed, 345 insertions, 0 deletions
diff --git a/ocaml/bin/dune b/ocaml/bin/dune
new file mode 100644
index 0000000..79dda7c
--- /dev/null
+++ b/ocaml/bin/dune
@@ -0,0 +1,9 @@
+(executable
+ (name neovere)
+ (public_name neovere)
+ (libraries overe.nock unix))
+
+(executable
+ (name neovere_live)
+ (public_name neovere-live)
+ (libraries overe.nock unix eio eio_main))
diff --git a/ocaml/bin/neovere.ml b/ocaml/bin/neovere.ml
new file mode 100644
index 0000000..0d40ce0
--- /dev/null
+++ b/ocaml/bin/neovere.ml
@@ -0,0 +1,190 @@
+(** Neovere - OCaml Urbit Runtime
+ *
+ * Boot a new ship with Urbit-style boot screen
+ *)
+
+open Nock_lib
+
+let version = "0.1.0"
+
+let project_root =
+ match Sys.getenv_opt "NEOVERE_ROOT" with
+ | Some root -> root
+ | None ->
+ let exe_dir = Filename.dirname Sys.executable_name in
+ let rec find_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_root parent
+ in
+ find_root exe_dir
+
+(* Ship name helper *)
+let ship_name = "zod"
+let ship_sigil = "~zod"
+
+(* Urbit-style boot messages *)
+let print_header () =
+ Printf.printf "urbit %s\n" version;
+ Printf.printf "boot: home is %s\n" ship_name;
+ Printf.printf "loom: mapped 2048MB\n";
+ Printf.printf "%!"
+
+let print_boot_start pill_path =
+ Printf.printf "boot: loading pill %s\n%!" pill_path
+
+let print_pill_info bot_count mod_count use_count =
+ let total = bot_count + mod_count + use_count in
+ Printf.printf "boot: %%solid pill\n";
+ Printf.printf "boot: protected loom\n";
+ Printf.printf "live: logical boot\n";
+ Printf.printf "boot: installed 0 jets\n";
+ Printf.printf "---------------- playback starting ----------------\n";
+ Printf.printf "pier: replaying events 1-%d\n%!" total
+
+let print_lifecycle_start () =
+ Printf.printf "arvo: metamorphosis\n%!"
+
+let print_playback_done event_count =
+ Printf.printf "pier: (%d): play: done\n" event_count;
+ Printf.printf "---------------- playback complete ----------------\n%!"
+
+let print_network_info () =
+ Printf.printf "ames: live on 0 (localhost only)\n";
+ Printf.printf "http: web interface live on http://localhost:8080\n";
+ Printf.printf "http: loopback live on http://localhost:12321\n%!"
+
+let print_ready event_count =
+ Printf.printf "pier (%d): live\n" event_count;
+ Printf.printf "%s:dojo> %!" ship_sigil
+
+(* Count events in noun list *)
+let rec count_noun_list = function
+ | Noun.Atom z when Z.equal z Z.zero -> 0
+ | Noun.Cell (_, t) -> 1 + count_noun_list t
+ | _ -> 0
+
+(* Boot from pill *)
+let boot_ship pier_name =
+ print_header ();
+
+ (* Create pier directory *)
+ let pier_path = Filename.concat project_root pier_name in
+ if Sys.file_exists pier_path then begin
+ Printf.eprintf "Error: Pier directory %s already exists\n" pier_path;
+ Printf.eprintf "Hint: Remove it first (rm -rf %s)\n" pier_path;
+ exit 1
+ end;
+
+ Unix.mkdir pier_path 0o755;
+
+ (* Boot from pills *)
+ let ivory_path = Filename.concat project_root "pills/ivory.pill" in
+ let solid_path = Filename.concat project_root "pills/solid.pill" in
+
+ (* Create state *)
+ let state = State.create ~pier_path () in
+
+ (* Load ivory first (silently) *)
+ let () = match Boot.boot_ivory state ivory_path with
+ | Error (Boot.Invalid_pill msg) ->
+ Printf.eprintf "✗ Ivory boot failed: %s\n" msg;
+ exit 1
+ | Error (Boot.Unsupported msg) ->
+ Printf.eprintf "✗ Unsupported: %s\n" msg;
+ exit 1
+ | Ok () -> ()
+ in
+
+ (* Now load solid with progress *)
+ print_boot_start solid_path;
+
+ (* Parse pill to get event counts *)
+ let pill = Boot.cue_file solid_path in
+ let (bot, mod_, use_) = match Boot.parse_solid pill with
+ | Error _ ->
+ Printf.eprintf "Error: Failed to parse solid pill\n";
+ exit 1
+ | Ok result -> result
+ in
+
+ let bot_count = count_noun_list bot in
+ let mod_count = count_noun_list mod_ in
+ let use_count = count_noun_list use_ in
+
+ (* Add the 4 system events and 1 boot event we'll inject *)
+ print_pill_info bot_count (mod_count + 4) (use_count + 1);
+
+ (* Run lifecycle boot *)
+ print_lifecycle_start ();
+
+ let boot_start = Sys.time () in
+ let () = match Boot.boot_solid_lifecycle state solid_path with
+ | Error (Boot.Invalid_pill msg) ->
+ Printf.eprintf "✗ Boot failed: %s\n" msg;
+ exit 1
+ | Error (Boot.Unsupported msg) ->
+ Printf.eprintf "✗ Unsupported: %s\n" msg;
+ exit 1
+ | Ok () -> ()
+ in
+ let boot_elapsed = Sys.time () -. boot_start in
+
+ Printf.printf "clay: kernel updated to solid\n";
+
+ let eve = State.event_number state in
+ print_playback_done (Int64.to_int eve);
+
+ (* Show boot time *)
+ Printf.printf "boot: complete in %.2fs\n" boot_elapsed;
+ Printf.printf "\n";
+
+ (* Network info *)
+ print_network_info ();
+
+ (* Ready! *)
+ print_ready (Int64.to_int eve);
+
+ (* Close eventlog *)
+ State.close_eventlog state;
+
+ (* Show status *)
+ Printf.printf "\n\n";
+ Printf.printf "╔═══════════════════════════════════════════════════════╗\n";
+ Printf.printf "║ Neovere Boot Complete! 🎉 ║\n";
+ Printf.printf "╚═══════════════════════════════════════════════════════╝\n";
+ Printf.printf "\n";
+ Printf.printf "Pier: %s\n" pier_path;
+ Printf.printf "Events: %Ld\n" eve;
+ Printf.printf "Kernel: %s\n" (if Noun.is_cell (State.arvo_core state) then "valid" else "invalid");
+ Printf.printf "\n";
+ Printf.printf "Next steps:\n";
+ Printf.printf " - Event loop and I/O drivers (Dill, Ames, Eyre)\n";
+ Printf.printf " - Effects processing\n";
+ Printf.printf " - Interactive dojo\n";
+ Printf.printf "\n"
+
+(* Main *)
+let () =
+ let pier_name =
+ if Array.length Sys.argv > 1 then Sys.argv.(1)
+ else "zod"
+ in
+
+ try
+ boot_ship pier_name
+ with
+ | Sys_error msg ->
+ Printf.eprintf "\nSystem error: %s\n" msg;
+ exit 1
+ | Failure msg ->
+ Printf.eprintf "\nError: %s\n" msg;
+ exit 1
+ | e ->
+ Printf.eprintf "\nFatal error: %s\n" (Printexc.to_string e);
+ Printexc.print_backtrace stderr;
+ exit 1
diff --git a/ocaml/bin/neovere_live.ml b/ocaml/bin/neovere_live.ml
new file mode 100644
index 0000000..5707e46
--- /dev/null
+++ b/ocaml/bin/neovere_live.ml
@@ -0,0 +1,146 @@
+(** Neovere Live - Interactive Urbit runtime with Eio *)
+
+open Eio.Std
+open Nock_lib
+
+let version = "0.1.0"
+
+let project_root =
+ match Sys.getenv_opt "NEOVERE_ROOT" with
+ | Some root -> root
+ | None ->
+ let exe_dir = Filename.dirname Sys.executable_name in
+ let rec find_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_root parent
+ in
+ find_root exe_dir
+
+(** Boot the ship *)
+let boot_ship pier_name =
+ traceln "Booting ship: %s" pier_name;
+
+ let pier_path = Filename.concat project_root pier_name in
+ if Sys.file_exists pier_path then begin
+ traceln "Error: Pier %s already exists" pier_path;
+ exit 1
+ end;
+
+ Unix.mkdir pier_path 0o755;
+
+ 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 _ -> traceln "Ivory boot failed"; exit 1
+ | Ok () -> traceln "✓ Ivory kernel loaded"
+ 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 _ -> traceln "Solid boot failed"; exit 1
+ | Ok () ->
+ traceln "✓ Solid boot complete (events: %Ld)" (State.event_number state)
+ end;
+
+ state
+
+(** Main event loop using Eio's structured concurrency *)
+let run_event_loop env state =
+ let stdin = Eio.Stdenv.stdin env in
+ let stdout = Eio.Stdenv.stdout env in
+ let clock = Eio.Stdenv.clock env in
+
+ traceln "\n~zod:dojo> ";
+ Eio.Flow.copy_string "~zod:dojo> " stdout;
+
+ (* Create Dill wire for terminal 1 *)
+ let dill_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
+
+ (* Process effects helper *)
+ let process_effects result =
+ match result with
+ | Noun.Cell (effects, _new_core) ->
+ Nock_lib.Dill.render_effects ~stdout effects
+ | _ ->
+ traceln "Warning: poke returned unexpected structure"
+ in
+
+ (* Run concurrent fibers *)
+ Switch.run @@ fun _sw ->
+ Fiber.all [
+ (* Terminal input fiber *)
+ (fun () ->
+ traceln "[Input fiber started]";
+ Nock_lib.Dill.input_loop ~stdin ~state ~wire:dill_wire process_effects
+ );
+
+ (* Timer fiber (placeholder) *)
+ (fun () ->
+ traceln "[Timer fiber started]";
+ while true do
+ Eio.Time.sleep clock 10.0;
+ traceln "[Timer tick]"
+ done
+ );
+
+ (* Status fiber (placeholder) *)
+ (fun () ->
+ traceln "[Status fiber started]";
+ Eio.Time.sleep clock 5.0;
+ let eve = State.event_number state in
+ traceln "[Status] Events: %Ld" eve;
+ );
+ ]
+
+(** Main entry point *)
+let main env =
+ let pier_name =
+ if Array.length Sys.argv > 1 then Sys.argv.(1)
+ else "zod-live"
+ in
+
+ traceln "╔═══════════════════════════════════════════════════════╗";
+ traceln "║ Neovere Live v%s ║" version;
+ traceln "╚═══════════════════════════════════════════════════════╝";
+ traceln "";
+
+ (* Boot ship *)
+ let state = boot_ship pier_name in
+
+ traceln "";
+ traceln "Ship booted successfully!";
+ traceln "Starting event loop with Eio structured concurrency...";
+ traceln "";
+
+ (* Run event loop *)
+ run_event_loop env state;
+
+ (* Cleanup *)
+ State.close_eventlog state;
+ traceln "Shutdown complete"
+
+let () =
+ Eio_main.run @@ fun env ->
+ try
+ main env
+ with
+ | Sys_error msg ->
+ traceln "System error: %s" msg;
+ exit 1
+ | e ->
+ traceln "Fatal error: %s" (Printexc.to_string e);
+ Printexc.print_backtrace stderr;
+ exit 1