diff options
Diffstat (limited to 'ocaml/lib/io')
-rw-r--r-- | ocaml/lib/io/dill.ml | 167 | ||||
-rw-r--r-- | ocaml/lib/io/dune | 2 | ||||
-rw-r--r-- | ocaml/lib/io/iris.ml | 219 |
3 files changed, 387 insertions, 1 deletions
diff --git a/ocaml/lib/io/dill.ml b/ocaml/lib/io/dill.ml new file mode 100644 index 0000000..8677732 --- /dev/null +++ b/ocaml/lib/io/dill.ml @@ -0,0 +1,167 @@ +(* Dill - Terminal I/O Driver with Eio + * + * This is the terminal driver for ship console interaction. + * Uses Eio for async terminal I/O - non-blocking console operations! + * + * Key innovation vs C Vere: + * - C Vere: Blocking terminal I/O, single-threaded input processing + * - Overe: Async terminal I/O with Eio, concurrent input/output handling + *) + +(* Dill configuration *) +type config = { + prompt: string; (* Command prompt to display *) +} + +(* Dill driver state *) +type t = { + config: config; + mutable stats: stats; +} + +and stats = { + mutable lines_read: int64; + mutable lines_written: int64; + mutable bytes_read: int64; + mutable bytes_written: int64; +} + +(* Create Dill driver *) +let create config = { + config; + stats = { + lines_read = 0L; + lines_written = 0L; + bytes_read = 0L; + bytes_written = 0L; + }; +} + +(* Write output to terminal *) +let write_output dill ~env text = + let stdout = Eio.Stdenv.stdout env in + + (* Async write - doesn't block! *) + Eio.Flow.copy_string text stdout; + + dill.stats.lines_written <- Int64.succ dill.stats.lines_written; + dill.stats.bytes_written <- Int64.add dill.stats.bytes_written + (Int64.of_int (String.length text)) + +(* Write prompt *) +let write_prompt dill ~env = + write_output dill ~env (dill.config.prompt ^ " ") + +(* Read input line from terminal *) +let read_input dill ~env = + let stdin = Eio.Stdenv.stdin env in + + (* Read line - async, doesn't block other operations! *) + let buf = Buffer.create 256 in + let chunk = Cstruct.create 1 in + + let rec read_until_newline () = + match Eio.Flow.single_read stdin chunk with + | 0 -> None (* EOF *) + | _ -> + let char = Cstruct.get_char chunk 0 in + if char = '\n' then + Some (Buffer.contents buf) + else begin + Buffer.add_char buf char; + read_until_newline () + end + in + + match read_until_newline () with + | Some line -> + dill.stats.lines_read <- Int64.succ dill.stats.lines_read; + dill.stats.bytes_read <- Int64.add dill.stats.bytes_read + (Int64.of_int (String.length line)); + Some line + | None -> None + +(* Input fiber - continuously reads terminal input *) +let input_fiber dill ~env ~sw:_ ~event_stream = + Printf.printf "[Dill] Input fiber started\n%!"; + + let rec loop () = + try + (* Show prompt *) + write_prompt dill ~env; + + (* Read input line - async! *) + (match read_input dill ~env with + | Some line -> + Printf.printf "[Dill] Read input: %s\n%!" line; + + (* Create ovum for runtime *) + let ovum = Nock_lib.Effects.make_ovum + ~wire:(Nock_lib.Noun.atom 0) + ~card:(Nock_lib.Noun.cell + (Nock_lib.Noun.atom 4) (* dill tag *) + (Nock_lib.Noun.atom 0)) (* simplified - would be parsed command *) + in + + (* Send to runtime event queue *) + Eio.Stream.add event_stream ovum; + + loop () + + | None -> + Printf.printf "[Dill] EOF on input\n%!" + ) + with + | End_of_file -> + Printf.printf "[Dill] Input fiber closed\n%!" + | Eio.Cancel.Cancelled _ -> + Printf.printf "[Dill] Input fiber cancelled\n%!" + in + + loop () + +(* Output fiber - handles terminal output *) +let output_fiber dill ~env ~sw:_ output_stream = + Printf.printf "[Dill] Output fiber started\n%!"; + + let rec loop () = + try + (* Wait for output from runtime *) + let text = Eio.Stream.take output_stream in + + (* Write to terminal - async! *) + write_output dill ~env text; + + loop () + with + | End_of_file -> + Printf.printf "[Dill] Output fiber closed\n%!" + | Eio.Cancel.Cancelled _ -> + Printf.printf "[Dill] Output fiber cancelled\n%!" + in + + loop () + +(* Run Dill driver - spawns input and output fibers *) +let run dill ~env ~sw ~event_stream = + Printf.printf "[Dill] Starting terminal driver\n%!"; + + (* Create output stream for terminal output *) + let output_stream = Eio.Stream.create 100 in + + (* Spawn input fiber *) + Eio.Fiber.fork ~sw (fun () -> + input_fiber dill ~env ~sw ~event_stream + ); + + (* Spawn output fiber *) + Eio.Fiber.fork ~sw (fun () -> + output_fiber dill ~env ~sw output_stream + ); + + Printf.printf "[Dill] Terminal driver running!\n%!"; + + output_stream (* Return output stream so runtime can send output *) + +(* Get statistics *) +let get_stats dill = dill.stats diff --git a/ocaml/lib/io/dune b/ocaml/lib/io/dune index 0c63f23..973d93a 100644 --- a/ocaml/lib/io/dune +++ b/ocaml/lib/io/dune @@ -1,4 +1,4 @@ (library (name io_drivers) - (modules behn ames http clay) + (modules behn ames http clay dill iris) (libraries nock_lib zarith eio eio.unix)) diff --git a/ocaml/lib/io/iris.ml b/ocaml/lib/io/iris.ml new file mode 100644 index 0000000..e1acc75 --- /dev/null +++ b/ocaml/lib/io/iris.ml @@ -0,0 +1,219 @@ +(* Iris - HTTP Client Driver with Eio + * + * This is the HTTP client for making outbound HTTP requests. + * Uses Eio.Net for async HTTP - non-blocking HTTP client operations! + * + * Key innovation vs C Vere: + * - C Vere: Blocking HTTP with libcurl, sequential request processing + * - Overe: Async HTTP with Eio.Net, concurrent request handling + *) + +(* HTTP request *) +type http_request = { + method_: string; (* GET, POST, etc *) + url: string; + headers: (string * string) list; + body: bytes option; +} + +(* HTTP response *) +type http_response = { + status: int; + headers: (string * string) list; + body: bytes; +} + +(* Request result *) +type request_result = + | Success of http_response + | Error of string + +(* Iris driver state *) +type t = { + mutable stats: stats; +} + +and stats = { + mutable requests_total: int64; + mutable requests_active: int; + mutable bytes_sent: int64; + mutable bytes_recv: int64; +} + +(* Create Iris driver *) +let create () = { + stats = { + requests_total = 0L; + requests_active = 0; + bytes_sent = 0L; + bytes_recv = 0L; + }; +} + +(* Parse URL into host and path *) +let parse_url url = + (* Very simplified URL parsing *) + let without_scheme = + if String.starts_with ~prefix:"http://" url then + String.sub url 7 (String.length url - 7) + else if String.starts_with ~prefix:"https://" url then + String.sub url 8 (String.length url - 8) + else + url + in + + match String.index_opt without_scheme '/' with + | Some idx -> + let host = String.sub without_scheme 0 idx in + let path = String.sub without_scheme idx (String.length without_scheme - idx) in + (host, path) + | None -> + (without_scheme, "/") + +(* Parse HTTP response *) +let parse_response response_text = + let lines = String.split_on_char '\n' response_text in + match lines with + | [] -> Error "Empty response" + | status_line :: rest -> + (* Parse status line: HTTP/1.1 200 OK *) + let status = + try + let parts = String.split_on_char ' ' status_line in + if List.length parts >= 2 then + int_of_string (List.nth parts 1) + else + 0 + with _ -> 0 + in + + (* Parse headers until blank line *) + let rec parse_headers acc = function + | [] -> (List.rev acc, "") + | "" :: rest | "\r" :: rest -> + (List.rev acc, String.concat "\n" rest) + | line :: rest -> + (match String.index_opt line ':' with + | Some idx -> + let key = String.sub line 0 idx |> String.trim in + let value = String.sub line (idx + 1) (String.length line - idx - 1) |> String.trim in + parse_headers ((key, value) :: acc) rest + | None -> + parse_headers acc rest) + in + + let headers, body = parse_headers [] rest in + Success { + status; + headers; + body = Bytes.of_string body; + } + +(* Make HTTP request *) +let make_request iris ~env ~sw request = + try + iris.stats.requests_active <- iris.stats.requests_active + 1; + iris.stats.requests_total <- Int64.succ iris.stats.requests_total; + + let (host, path) = parse_url request.url in + + Printf.printf "[Iris] %s %s (host: %s, path: %s)\n%!" + request.method_ request.url host path; + + (* Connect to server *) + let net = Eio.Stdenv.net env in + + (* Simple DNS lookup - just use host as-is for now *) + (* In production, would use Eio.Net.getaddrinfo *) + let port = 80 in (* TODO: Parse port from URL *) + let addr = `Tcp (Eio.Net.Ipaddr.V4.loopback, port) in (* TODO: Resolve hostname *) + + let flow = Eio.Net.connect ~sw net addr in + + (* Build HTTP request *) + let request_line = Printf.sprintf "%s %s HTTP/1.1\r\n" request.method_ path in + let host_header = Printf.sprintf "Host: %s\r\n" host in + let headers_str = List.map (fun (k, v) -> + Printf.sprintf "%s: %s\r\n" k v + ) request.headers |> String.concat "" in + + let request_text = request_line ^ host_header ^ headers_str ^ "\r\n" in + let request_bytes = Bytes.of_string request_text in + + (* Add body if present *) + let full_request = + match request.body with + | Some body -> + let total_len = Bytes.length request_bytes + Bytes.length body in + let combined = Bytes.create total_len in + Bytes.blit request_bytes 0 combined 0 (Bytes.length request_bytes); + Bytes.blit body 0 combined (Bytes.length request_bytes) (Bytes.length body); + combined + | None -> + request_bytes + in + + iris.stats.bytes_sent <- Int64.add iris.stats.bytes_sent + (Int64.of_int (Bytes.length full_request)); + + (* Send request - async! *) + Eio.Flow.write flow [Cstruct.of_bytes full_request]; + + (* Read response - async! *) + let buf = Cstruct.create 16384 in + let recv_len = Eio.Flow.single_read flow buf in + let response_text = Cstruct.to_string (Cstruct.sub buf 0 recv_len) in + + iris.stats.bytes_recv <- Int64.add iris.stats.bytes_recv + (Int64.of_int recv_len); + + iris.stats.requests_active <- iris.stats.requests_active - 1; + + Printf.printf "[Iris] Received %d bytes\n%!" recv_len; + + parse_response response_text + + with + | e -> + iris.stats.requests_active <- iris.stats.requests_active - 1; + Error (Printf.sprintf "Request failed: %s" (Printexc.to_string e)) + +(* Make multiple requests in parallel *) +let parallel_requests iris ~env ~sw requests = + Printf.printf "[Iris] Making %d requests in parallel...\n%!" (List.length requests); + + let start = Unix.gettimeofday () in + + (* Launch requests in parallel fibers *) + let results = List.map (fun req -> + let promise = ref None in + Eio.Fiber.fork ~sw (fun () -> + let result = make_request iris ~env ~sw req in + promise := Some (req.url, result) + ); + promise + ) requests in + + (* Wait for completion *) + Eio.Time.sleep (Eio.Stdenv.clock env) 0.1; + + (* Collect results *) + let collected = List.filter_map (fun promise -> + match !promise with + | Some result -> Some result + | None -> None + ) results in + + let elapsed = Unix.gettimeofday () -. start in + Printf.printf "[Iris] Completed %d/%d requests in %.4fs\n%!" + (List.length collected) (List.length requests) elapsed; + + collected + +(* Run Iris driver *) +let run iris ~env:_ ~sw:_ ~event_stream:_ = + Printf.printf "[Iris] HTTP client driver running!\n%!"; + iris + +(* Get statistics *) +let get_stats iris = iris.stats |