summaryrefslogtreecommitdiff
path: root/ocaml/bin/neovere_live.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/bin/neovere_live.ml')
-rw-r--r--ocaml/bin/neovere_live.ml146
1 files changed, 146 insertions, 0 deletions
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