summaryrefslogtreecommitdiff
path: root/ocaml/lib/io
diff options
context:
space:
mode:
Diffstat (limited to 'ocaml/lib/io')
-rw-r--r--ocaml/lib/io/ames.ml172
-rw-r--r--ocaml/lib/io/dune2
2 files changed, 173 insertions, 1 deletions
diff --git a/ocaml/lib/io/ames.ml b/ocaml/lib/io/ames.ml
new file mode 100644
index 0000000..cb24768
--- /dev/null
+++ b/ocaml/lib/io/ames.ml
@@ -0,0 +1,172 @@
+(* Ames - UDP Networking Driver with Eio
+ *
+ * This is the networking backbone for ship-to-ship communication.
+ * Uses Eio.Net for async UDP I/O - can handle thousands of concurrent ships!
+ *
+ * Key innovation vs C Vere:
+ * - C Vere: Blocking UDP, single-threaded packet processing
+ * - Overe: Async UDP with Eio, concurrent packet handling across fibers
+ *)
+
+(* Ames configuration *)
+type config = {
+ port: int; (* UDP port to bind to *)
+ our_ship: string; (* Our ship name *)
+ galaxy_table: (string * string * int) list; (* (ship, ip, port) *)
+}
+
+(* Ames driver state *)
+type 'a t = {
+ config: config;
+ socket: 'a Eio.Net.datagram_socket;
+ mutable stats: stats;
+}
+
+and stats = {
+ mutable packets_sent: int64;
+ mutable packets_recv: int64;
+ mutable bytes_sent: int64;
+ mutable bytes_recv: int64;
+}
+
+(* Ames packet header - simplified for now *)
+type packet_header = {
+ version: int; (* Protocol version *)
+ sender: string; (* Sender ship *)
+ receiver: string; (* Receiver ship *)
+ sequence: int64; (* Packet sequence number *)
+}
+
+(* Ames packet *)
+type packet = {
+ header: packet_header;
+ payload: bytes;
+}
+
+(* Create Ames driver *)
+let create ~env ~sw config =
+ Printf.printf "[Ames] Starting on port %d for ship %s\n%!"
+ config.port config.our_ship;
+
+ (* Bind UDP socket *)
+ let net = Eio.Stdenv.net env in
+ let addr = `Udp (Eio.Net.Ipaddr.V4.any, config.port) in
+
+ let socket = Eio.Net.datagram_socket ~sw net addr in
+
+ Printf.printf "[Ames] Bound to UDP port %d\n%!" config.port;
+
+ {
+ config;
+ socket;
+ stats = {
+ packets_sent = 0L;
+ packets_recv = 0L;
+ bytes_sent = 0L;
+ bytes_recv = 0L;
+ };
+ }
+
+(* Parse packet header - simplified *)
+let parse_header bytes =
+ if Bytes.length bytes < 16 then
+ Error "Packet too short"
+ else
+ let version = int_of_char (Bytes.get bytes 0) in
+ (* For now, just extract version and create dummy header *)
+ Ok {
+ version;
+ sender = "~zod";
+ receiver = "~zod";
+ sequence = 0L;
+ }
+
+(* Encode packet header - simplified *)
+let encode_header header =
+ let buf = Bytes.create 16 in
+ Bytes.set buf 0 (char_of_int header.version);
+ (* TODO: Encode ship addresses and sequence *)
+ buf
+
+(* Send packet *)
+let send_packet ames dest_addr packet =
+ let header_bytes = encode_header packet.header in
+ let total_len = Bytes.length header_bytes + Bytes.length packet.payload in
+ let wire_packet = Bytes.create total_len in
+
+ Bytes.blit header_bytes 0 wire_packet 0 (Bytes.length header_bytes);
+ Bytes.blit packet.payload 0 wire_packet (Bytes.length header_bytes) (Bytes.length packet.payload);
+
+ (* Async send *)
+ Eio.Net.send ames.socket ~dst:dest_addr [Cstruct.of_bytes wire_packet];
+
+ (* Update stats *)
+ ames.stats.packets_sent <- Int64.succ ames.stats.packets_sent;
+ ames.stats.bytes_sent <- Int64.add ames.stats.bytes_sent (Int64.of_int total_len);
+
+ Printf.printf "[Ames] Sent %d bytes to %s\n%!" total_len
+ (match dest_addr with
+ | `Udp (ip, port) -> Printf.sprintf "%s:%d" (Format.asprintf "%a" Eio.Net.Ipaddr.pp ip) port
+ | _ -> "unknown")
+
+(* Receive fiber - continuously receives UDP packets *)
+let receive_fiber ames ~sw:_ ~event_stream =
+ Printf.printf "[Ames] Receive fiber started\n%!";
+
+ let buf = Cstruct.create 4096 in (* 4KB buffer per packet *)
+
+ let rec loop () =
+ try
+ (* Async receive - blocks this fiber but not others! *)
+ let addr, recv_len = Eio.Net.recv ames.socket buf in
+ let packet_bytes = Cstruct.to_bytes (Cstruct.sub buf 0 recv_len) in
+
+ (* Update stats *)
+ ames.stats.packets_recv <- Int64.succ ames.stats.packets_recv;
+ ames.stats.bytes_recv <- Int64.add ames.stats.bytes_recv (Int64.of_int recv_len);
+
+ (* Parse packet *)
+ (match parse_header packet_bytes with
+ | Ok header ->
+ Printf.printf "[Ames] Received %d bytes from %s (v%d)\n%!"
+ recv_len
+ (match addr with
+ | `Udp (ip, port) -> Printf.sprintf "%s:%d" (Format.asprintf "%a" Eio.Net.Ipaddr.pp ip) port
+ | _ -> "unknown")
+ header.version;
+
+ (* Create event for runtime *)
+ let ovum = Nock_lib.Effects.ames_packet
+ ~from:header.sender
+ ~data:packet_bytes
+ in
+
+ (* Send to runtime event queue *)
+ Eio.Stream.add event_stream ovum
+
+ | Error err ->
+ Printf.printf "[Ames] Failed to parse packet: %s\n%!" err
+ );
+
+ (* Loop forever *)
+ loop ()
+ with
+ | End_of_file -> Printf.printf "[Ames] Receive fiber closed\n%!"
+ | Eio.Cancel.Cancelled _ -> Printf.printf "[Ames] Receive fiber cancelled\n%!"
+ in
+
+ loop ()
+
+(* Get statistics *)
+let get_stats ames = ames.stats
+
+(* Run Ames driver - spawns receive fiber *)
+let run ames ~sw ~event_stream =
+ Printf.printf "[Ames] Running Ames driver...\n%!";
+
+ (* Spawn receive fiber *)
+ Eio.Fiber.fork ~sw (fun () ->
+ receive_fiber ames ~sw ~event_stream
+ );
+
+ Printf.printf "[Ames] Ames driver running!\n%!"
diff --git a/ocaml/lib/io/dune b/ocaml/lib/io/dune
index 699df2e..db1abbb 100644
--- a/ocaml/lib/io/dune
+++ b/ocaml/lib/io/dune
@@ -1,4 +1,4 @@
(library
(name io_drivers)
- (modules behn)
+ (modules behn ames)
(libraries nock_lib zarith eio eio.unix))