summaryrefslogtreecommitdiff
path: root/ocaml/bin/neovere.ml
blob: 0d40ce01fecd601fb76d895aae2935417a1ff8c8 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
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