summaryrefslogtreecommitdiff
path: root/ocaml/lib/io/iris.ml
blob: e1acc75a1b7dcb150037105240128add66e76ff9 (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
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
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