Skip to content

Commit

Permalink
fix(lsp): make write take list of strings (#1085)
Browse files Browse the repository at this point in the history
So that we don't have to assume that writes aren't interleaved

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg authored May 12, 2023
1 parent e309486 commit 62f8c4e
Show file tree
Hide file tree
Showing 3 changed files with 5 additions and 6 deletions.
4 changes: 2 additions & 2 deletions lsp-fiber/src/fiber_io.ml
Original file line number Diff line number Diff line change
Expand Up @@ -28,9 +28,9 @@ module Io =
| Ok s -> Some s
| Error (`Partial_eof _) -> None

let write oc s =
let write oc strings =
Fiber.of_thunk (fun () ->
Lio.Writer.add_string oc s;
List.iter strings ~f:(Lio.Writer.add_string oc);
Fiber.return ())
end)

Expand Down
5 changes: 2 additions & 3 deletions lsp/src/io.ml
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,7 @@ end) (Chan : sig

val read_exactly : input -> int -> string option Io.t

val write : output -> string -> unit Io.t
val write : output -> string list -> unit Io.t
end) =
struct
open Io.O
Expand Down Expand Up @@ -112,6 +112,5 @@ struct
let data = Json.to_string json in
let content_length = String.length data in
let header = Header.create ~content_length () in
let* () = Chan.write chan (Header.to_string header) in
Chan.write chan data
Chan.write chan [ Header.to_string header; data ]
end
2 changes: 1 addition & 1 deletion lsp/src/io.mli
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ end) (Chan : sig

val read_exactly : input -> int -> string option Io.t

val write : output -> string -> unit Io.t
val write : output -> string list -> unit Io.t
end) : sig
val read : Chan.input -> Jsonrpc.Packet.t option Io.t

Expand Down

0 comments on commit 62f8c4e

Please sign in to comment.