summaryrefslogtreecommitdiff
path: root/ocaml/test/old/test_runtime.ml
blob: ff0514ca67c02fc0aae90456f0bd8bd0ac171f2b (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
(* Runtime Tests - Testing the Eio-based Urbit runtime
 *
 * Tests:
 * 1. Basic runtime creation
 * 2. Event processing
 * 3. Effect execution
 * 4. Timer driver (Behn)
 * 5. Concurrent event processing
 *)

open Nock_lib

let test_runtime_creation env =
  Printf.printf "Test: Runtime creation...\n";

  (* Create pier directory *)
  (try Unix.mkdir "tmp/test_pier" 0o755 with _ -> ());

  let config = Runtime.default_config ~pier_path:"tmp/test_pier" () in
  let events = [
    Noun.atom 1;
    Noun.atom 2;
    Noun.atom 3;
  ] in

  let runtime = Runtime.run_simple ~env config events in
  let stats = Runtime.get_stats runtime in

  Printf.printf "  Events processed: %Ld\n" stats.events_processed;
  Printf.printf "  State: %s\n" stats.state_summary;

  assert (stats.events_processed = 3L);

  Printf.printf "  ✓ Runtime created and processed events!\n\n"

let test_effect_queue _env =
  Printf.printf "Test: Effect queue...\n";

  let queue = Nock_lib.Effects.create_queue () in

  (* Add some effects *)
  Nock_lib.Effects.enqueue queue (Nock_lib.Effects.Log "Test message 1");
  Nock_lib.Effects.enqueue queue (Nock_lib.Effects.SetTimer { id = 1L; time = 123.0 });
  Nock_lib.Effects.enqueue queue (Nock_lib.Effects.Log "Test message 2");

  Printf.printf "  Queue length: %d\n" (Nock_lib.Effects.queue_length queue);
  assert (Nock_lib.Effects.queue_length queue = 3);

  (* Dequeue *)
  let eff1 = Nock_lib.Effects.dequeue queue in
  (match eff1 with
  | Nock_lib.Effects.Log msg -> Printf.printf "  Dequeued: Log(%s)\n" msg
  | _ -> failwith "Wrong effect type"
  );

  assert (Nock_lib.Effects.queue_length queue = 2);

  Printf.printf "  ✓ Effect queue works!\n\n"

let test_behn_driver env =
  Printf.printf "Test: Behn timer driver...\n";

  Eio.Switch.run @@ fun _sw ->

  let behn = Io_drivers.Behn.create () in
  let now = Unix.gettimeofday () in

  (* Set a timer for 0.1 seconds from now *)
  Io_drivers.Behn.set_timer behn ~id:1L ~fire_time:(now +. 0.1);

  Printf.printf "  Active timers: %d\n" (Io_drivers.Behn.active_timers behn);
  assert (Io_drivers.Behn.active_timers behn = 1);

  (* Sleep to let timer fire *)
  Eio.Time.sleep (Eio.Stdenv.clock env) 0.2;

  Printf.printf "  Active timers after fire: %d\n" (Io_drivers.Behn.active_timers behn);

  Printf.printf "  ✓ Behn driver works!\n\n"

let test_timer_cancellation env =
  Printf.printf "Test: Timer cancellation...\n";

  Eio.Switch.run @@ fun _sw ->

  let behn = Io_drivers.Behn.create () in
  let now = Unix.gettimeofday () in

  (* Set a timer *)
  Io_drivers.Behn.set_timer behn ~id:1L ~fire_time:(now +. 1.0);
  assert (Io_drivers.Behn.active_timers behn = 1);

  (* Cancel it immediately *)
  Io_drivers.Behn.cancel_timer behn ~id:1L;

  (* Sleep *)
  Eio.Time.sleep (Eio.Stdenv.clock env) 0.1;

  Printf.printf "  ✓ Timer cancelled successfully!\n\n"

let test_concurrent_timers env =
  Printf.printf "Test: Concurrent timers...\n";

  Eio.Switch.run @@ fun sw ->

  let behn = Io_drivers.Behn.create () in
  let effect_queue = Nock_lib.Effects.create_queue () in
  let event_stream = Eio.Stream.create 100 in

  let now = Unix.gettimeofday () in

  (* Set multiple timers with different delays *)
  let timer_ids = [1L; 2L; 3L; 4L; 5L] in
  List.iteri (fun i id ->
    let delay = 0.05 *. float_of_int (i + 1) in
    Nock_lib.Effects.enqueue effect_queue (Nock_lib.Effects.SetTimer {
      id;
      time = now +. delay;
    })
  ) timer_ids;

  Printf.printf "  Set %d timers\n" (List.length timer_ids);

  (* Run behn driver fiber with timeout *)
  Eio.Fiber.fork ~sw (fun () ->
    (* Run for limited time *)
    let start = Unix.gettimeofday () in
    let rec loop () =
      if Unix.gettimeofday () -. start < 0.5 then begin
        match Nock_lib.Effects.try_dequeue effect_queue with
        | Some (Nock_lib.Effects.SetTimer { id; time }) ->
            Io_drivers.Behn.set_timer behn ~id ~fire_time:time;
            let timer = Hashtbl.find behn.timers id in
            Eio.Fiber.fork ~sw (fun () ->
              Io_drivers.Behn.timer_fiber behn ~env ~event_stream timer
            );
            loop ()
        | _ ->
            Eio.Time.sleep (Eio.Stdenv.clock env) 0.01;
            loop ()
      end
    in
    loop ()
  );

  (* Sleep to allow driver to run *)
  Eio.Time.sleep (Eio.Stdenv.clock env) 0.6;

  (* Count events produced *)
  let event_count = ref 0 in
  while Eio.Stream.length event_stream > 0 do
    let _ = Eio.Stream.take event_stream in
    event_count := !event_count + 1
  done;

  Printf.printf "  Events produced: %d\n" !event_count;
  Printf.printf "  ✓ Concurrent timers work!\n\n"

let () =
  Eio_main.run @@ fun env ->
  Printf.printf "\n🚀 === EIO RUNTIME TESTS === 🚀\n\n";

  (* Clean up test directories *)
  (try Unix.system "rm -rf tmp/test_pier*" |> ignore with _ -> ());

  test_runtime_creation env;
  test_effect_queue env;
  test_behn_driver env;
  test_timer_cancellation env;
  test_concurrent_timers env;

  Printf.printf "🎉 === ALL RUNTIME TESTS PASSED! === 🎉\n";
  Printf.printf "\nThe Eio runtime is working!\n";
  Printf.printf "- Event processing ✓\n";
  Printf.printf "- Effect execution ✓\n";
  Printf.printf "- Timer driver (Behn) ✓\n";
  Printf.printf "- Concurrent fibers ✓\n\n";
  Printf.printf "Ready for a full runtime with all I/O drivers!\n"