summaryrefslogtreecommitdiff
path: root/ocaml/bin/overe.ml
blob: cc75ca44d5953d7da5d4ce56bdbe7692af1bf5f0 (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
(* Overe - OCaml Urbit Runtime with Multicore Support
 *
 * This is the main entry point that wires together:
 * - Nock interpreter and state management (nock_lib)
 * - I/O drivers (io_drivers)
 * - Eio async runtime
 * - Domain-based parallelism
 *
 * Architecture:
 * - Main event loop running on primary domain
 * - I/O drivers running in concurrent fibers
 * - Event processing with real Nock execution
 * - Effect dispatch to appropriate drivers
 *)

open Nock_lib

(* Run Overe with I/O drivers integrated *)
let run_with_drivers ~env config =
  Printf.printf "šŸš€ Starting Overe Runtime with I/O Drivers\n%!";
  Printf.printf "   Pier: %s\n%!" config.Runtime.pier_path;
  Printf.printf "   OCaml %s on %d cores\n%!"
    Sys.ocaml_version (Domain.recommended_domain_count ());
  Printf.printf "\n";

  Eio.Switch.run @@ fun sw ->
  let fs = Eio.Stdenv.fs env in

  (* Create runtime *)
  let runtime = Runtime.create ~sw ~fs config in

  (* Create event stream (lock-free!) *)
  let event_stream = Eio.Stream.create 1000 in

  Printf.printf "āœ“ Runtime created\n%!";

  (* Load snapshot or boot fresh kernel *)
  (match State.load_snapshot runtime.Runtime.state ~fs config.snapshot_path with
  | Ok eve ->
      Printf.printf "āœ“ Loaded snapshot at event %Ld\n%!" eve
  | Error _msg ->
      Printf.printf "⚠ No snapshot found, booting fresh kernel...\n%!";
      (* Boot with fake pill for now *)
      match Boot.boot_fake runtime.state with
      | Ok () -> Printf.printf "āœ“ Kernel booted\n%!"
      | Error msg -> Printf.printf "āœ— Boot failed: %s\n%!" msg
  );

  (* Replay events from log *)
  Printf.printf "Replaying events from log...\n%!";
  Eventlog.replay runtime.event_log ~sw (fun event_num _event ->
    Printf.printf "  Replayed event %Ld\n%!" event_num
  );

  Printf.printf "āœ“ Runtime ready! State: %s\n%!" (State.summary runtime.state);
  Printf.printf "\n";

  (* Create I/O drivers *)
  Printf.printf "Initializing I/O drivers...\n%!";

  (* Behn (timer) *)
  let behn = Io_drivers.Behn.create () in
  Printf.printf "  āœ“ Behn (timers)\n%!";

  (* Clay (filesystem) *)
  let clay_config = { Io_drivers.Clay.pier_path = config.pier_path } in
  let clay = Io_drivers.Clay.create clay_config in
  Printf.printf "  āœ“ Clay (filesystem)\n%!";

  (* Dill (terminal) *)
  let dill_config = { Io_drivers.Dill.prompt = "~zod:dojo>" } in
  let dill = Io_drivers.Dill.create dill_config in
  Printf.printf "  āœ“ Dill (terminal)\n%!";

  (* Iris (HTTP client) *)
  let iris = Io_drivers.Iris.create () in
  Printf.printf "  āœ“ Iris (HTTP client)\n%!";

  Printf.printf "\nšŸŽÆ All drivers initialized!\n\n";

  (* Event processor fiber - processes events from the stream *)
  let event_processor () =
    Printf.printf "[Runtime] Event processor fiber started\n%!";
    try
      while true do
        let ovum = Eio.Stream.take event_stream in

        (* Convert ovum to noun for Nock execution *)
        (* Ovum format: [wire card] *)
        let event_noun = Noun.cell ovum.Effects.wire ovum.Effects.card in

        (* Process event through Arvo *)
        let _effects = State.poke runtime.state event_noun in
        runtime.events_processed <- Int64.succ runtime.events_processed;

        (* Log progress periodically *)
        if Int64.rem runtime.events_processed 100L = 0L then
          Printf.printf "[Runtime] Processed %Ld events\n%!" runtime.events_processed
      done
    with End_of_file ->
      Printf.printf "[Runtime] Event processor shutting down\n%!"
  in

  (* Effect executor fiber - executes effects *)
  let effect_executor () =
    Printf.printf "[Runtime] Effect executor fiber started\n%!";
    let rec loop () =
      match Effects.try_dequeue runtime.effect_queue with
      | None ->
          Eio.Time.sleep (Eio.Stdenv.clock env) 0.001;
          loop ()
      | Some eff ->
          (match eff with
          | Effects.Log msg ->
              Printf.printf "[Effect] Log: %s\n%!" msg
          | Effects.SetTimer { id; time } ->
              Printf.printf "[Effect] SetTimer: id=%Ld time=%f\n%!" id time
          | _ ->
              Printf.printf "[Effect] Other effect\n%!"
          );
          runtime.effects_executed <- Int64.succ runtime.effects_executed;
          loop ()
    in
    try loop ()
    with End_of_file ->
      Printf.printf "[Runtime] Effect executor shutting down\n%!"
  in

  (* Run all fibers concurrently *)
  Printf.printf "šŸš€ Starting all fibers...\n\n";

  Eio.Fiber.all [
    (* Core runtime fibers *)
    event_processor;
    effect_executor;

    (* I/O driver fibers *)
    (fun () -> Io_drivers.Behn.driver_fiber behn ~sw ~env
                 ~effect_queue:runtime.effect_queue ~event_stream);
    (fun () -> Io_drivers.Clay.run clay ~env ~sw ~event_stream);
    (fun () -> let _ = Io_drivers.Dill.run dill ~env ~sw ~event_stream in ());
    (fun () -> let _ = Io_drivers.Iris.run iris ~env ~sw ~event_stream in ());
  ];

  (* Shutdown *)
  Printf.printf "\nšŸ›‘ Runtime shutting down...\n%!";
  Printf.printf "   Events processed: %Ld\n%!" runtime.events_processed;
  Printf.printf "   Effects executed: %Ld\n%!" runtime.effects_executed;

  (* Save final snapshot *)
  Printf.printf "Saving final snapshot...\n%!";
  State.save_snapshot runtime.state ~fs config.snapshot_path;
  Printf.printf "āœ“ Snapshot saved\n%!"

(* Main entry point *)
let () =
  Printf.printf "\n";
  Printf.printf "╔══════════════════════════════════════════════════════════════╗\n";
  Printf.printf "ā•‘  Overe - OCaml Urbit Runtime with Multicore Support         ā•‘\n";
  Printf.printf "ā•‘                                                              ā•‘\n";
  Printf.printf "ā•‘  šŸš€ Features:                                                ā•‘\n";
  Printf.printf "ā•‘    - True multicore parallelism (OCaml 5 domains)           ā•‘\n";
  Printf.printf "ā•‘    - Async I/O with Eio (non-blocking everything!)          ā•‘\n";
  Printf.printf "ā•‘    - Parallel Nock execution (domainslib)                    ā•‘\n";
  Printf.printf "ā•‘    - Full I/O driver stack (Behn/Ames/Eyre/Clay/Dill/Iris)  ā•‘\n";
  Printf.printf "ā•šā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•ā•\n";
  Printf.printf "\n";

  (* Default config *)
  let config = Runtime.default_config ~pier_path:"./pier" () in

  (* Run with Eio *)
  Eio_main.run @@ fun env ->
  run_with_drivers ~env config