Skip to content

Commit c36cab7

Browse files
committed
test(ocamllsp): extract e2e-new helpers
to make it easy to write them in OCaml Signed-off-by: Rudi Grinberg <[email protected]> ps-id: e2a40a58-1e8b-451f-9637-a8400cad373c
1 parent 431ecb5 commit c36cab7

File tree

2 files changed

+59
-42
lines changed

2 files changed

+59
-42
lines changed

ocaml-lsp-server/test/e2e-new/start_stop.ml

Lines changed: 3 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -1,41 +1,7 @@
1-
open Stdune
2-
open Fiber.O
3-
4-
let _PATH =
5-
Bin.parse_path (Option.value ~default:"" @@ Env.get Env.initial "PATH")
6-
7-
let bin = Bin.which "ocamllsp" ~path:_PATH |> Option.value_exn |> Path.to_string
8-
9-
let env = Spawn.Env.of_list [ "OCAMLLSP_TEST=true" ]
10-
11-
module Client = Lsp_fiber.Client
12-
open Lsp.Types
1+
open Test.Import
132

143
let%expect_test "start/stop" =
15-
let stdin_i, stdin_o = Unix.pipe ~cloexec:true () in
16-
let stdout_i, stdout_o = Unix.pipe ~cloexec:true () in
17-
let pid =
18-
Spawn.spawn ~env ~prog:bin ~argv:[ bin ] ~stdin:stdin_i ~stdout:stdout_o ()
19-
in
20-
Unix.close stdin_i;
21-
Unix.close stdout_o;
22-
let handler = Client.Handler.make () in
23-
let init =
24-
let blockity =
25-
if Sys.win32 then `Blocking
26-
else (
27-
Unix.set_nonblock stdout_i;
28-
Unix.set_nonblock stdin_o;
29-
`Non_blocking true)
30-
in
31-
let make fd what =
32-
let fd = Lev_fiber.Fd.create fd blockity in
33-
Lev_fiber.Io.create fd what
34-
in
35-
let* in_ = make stdout_i Input in
36-
let* out = make stdin_o Output in
37-
let io = Lsp_fiber.Fiber_io.make in_ out in
38-
let client = Client.make handler io () in
4+
( Test.run @@ fun client ->
395
let run_client () =
406
let capabilities = ClientCapabilities.create () in
417
Client.start client (InitializeParams.create ~capabilities ())
@@ -53,12 +19,7 @@ let%expect_test "start/stop" =
5319
Client.request client Shutdown
5420
in
5521
Fiber.fork_and_join_unit run_client (fun () -> run >>> Client.stop client)
56-
in
57-
let waitpid =
58-
let+ (_ : Unix.process_status) = Lev_fiber.waitpid ~pid in
59-
()
60-
in
61-
Lev_fiber.run (fun () -> Fiber.all_concurrently_unit [ init; waitpid ]);
22+
);
6223
[%expect
6324
{|
6425
client: server initialized with:
Lines changed: 56 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,56 @@
1+
module Import = struct
2+
include Stdune
3+
include Fiber.O
4+
module Client = Lsp_fiber.Client
5+
include Lsp.Types
6+
end
7+
8+
open Import
9+
10+
module T : sig
11+
val run : (unit Client.t -> unit Fiber.t) -> unit
12+
end = struct
13+
let _PATH =
14+
Bin.parse_path (Option.value ~default:"" @@ Env.get Env.initial "PATH")
15+
16+
let bin =
17+
Bin.which "ocamllsp" ~path:_PATH |> Option.value_exn |> Path.to_string
18+
19+
let env = Spawn.Env.of_list [ "OCAMLLSP_TEST=true" ]
20+
21+
let run f =
22+
let stdin_i, stdin_o = Unix.pipe ~cloexec:true () in
23+
let stdout_i, stdout_o = Unix.pipe ~cloexec:true () in
24+
let pid =
25+
Spawn.spawn ~env ~prog:bin ~argv:[ bin ] ~stdin:stdin_i ~stdout:stdout_o
26+
()
27+
in
28+
Unix.close stdin_i;
29+
Unix.close stdout_o;
30+
let handler = Client.Handler.make () in
31+
let init =
32+
let blockity =
33+
if Sys.win32 then `Blocking
34+
else (
35+
Unix.set_nonblock stdout_i;
36+
Unix.set_nonblock stdin_o;
37+
`Non_blocking true)
38+
in
39+
let make fd what =
40+
let fd = Lev_fiber.Fd.create fd blockity in
41+
Lev_fiber.Io.create fd what
42+
in
43+
let* in_ = make stdout_i Input in
44+
let* out = make stdin_o Output in
45+
let io = Lsp_fiber.Fiber_io.make in_ out in
46+
let client = Client.make handler io () in
47+
f client
48+
in
49+
let waitpid =
50+
let+ (_ : Unix.process_status) = Lev_fiber.waitpid ~pid in
51+
()
52+
in
53+
Lev_fiber.run (fun () -> Fiber.all_concurrently_unit [ init; waitpid ])
54+
end
55+
56+
include T

0 commit comments

Comments
 (0)