summaryrefslogtreecommitdiff
path: root/ocaml/lib/io/dill.ml
blob: 86777321af33c3595856fa2a809877f42e2f7c85 (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
(* 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