summaryrefslogtreecommitdiff
path: root/ocaml/lib/io/dill.ml
diff options
context:
space:
mode:
authorpolwex <polwex@sortug.com>2025-10-06 05:08:28 +0700
committerpolwex <polwex@sortug.com>2025-10-06 05:08:28 +0700
commit9fd3f41bf9a3326c5f0866f39f2ed151adc21565 (patch)
tree73e5d9277a34f14e0368e18352593040509ef89f /ocaml/lib/io/dill.ml
parent49ba06ba00468c24767fff0222fbc3c776b14881 (diff)
iris and dill
Diffstat (limited to 'ocaml/lib/io/dill.ml')
-rw-r--r--ocaml/lib/io/dill.ml167
1 files changed, 167 insertions, 0 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