Skip to content

Commit e485128

Browse files
authored
test: add tests for exit and shutdown notifications (#1241)
* test: add tests for exit and shutdown notifications Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
1 parent 2fa2e84 commit e485128

File tree

3 files changed

+82
-12
lines changed

3 files changed

+82
-12
lines changed

ocaml-lsp-server/test/e2e-new/dune

+1
Original file line numberDiff line numberDiff line change
@@ -50,6 +50,7 @@
5050
completion
5151
doc_to_md
5252
document_flow
53+
exit_notification
5354
for_ppx
5455
hover_extended
5556
inlay_hints
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,56 @@
1+
open Test.Import
2+
3+
let client_capabilities = ClientCapabilities.create ()
4+
5+
module T : sig
6+
val run : (unit Client.t -> 'a Fiber.t) -> 'a
7+
end = struct
8+
let run f =
9+
let status, a = Test.run_with_status f in
10+
let () =
11+
match status with
12+
| WEXITED n -> Format.eprintf "ocamllsp finished with code = %d@.%!" n
13+
| WSIGNALED s -> Format.eprintf "ocamllsp killed with signal = %d@.%!" s
14+
| WSTOPPED s -> Format.eprintf "ocamllsp stopped with signal = %d@.%!" s
15+
in
16+
a
17+
end
18+
19+
let test run =
20+
T.run (fun client ->
21+
let run_client () =
22+
Client.start
23+
client
24+
(InitializeParams.create ~capabilities:client_capabilities ())
25+
in
26+
Fiber.fork_and_join_unit run_client (run client))
27+
28+
let%expect_test "ocamllsp process exits with code 0 after Shutdown and Exit \
29+
notifications are sent" =
30+
let run client () =
31+
let* (_ : InitializeResult.t) = Client.initialized client in
32+
let* () = Client.request client Shutdown in
33+
Client.notification client Exit
34+
in
35+
test run;
36+
[%expect {|
37+
ocamllsp finished with code = 0 |}]
38+
39+
let%expect_test "ocamllsp does not exit if only Shutdown notification is sent" =
40+
let run client () =
41+
let* (_ : InitializeResult.t) = Client.initialized client in
42+
Client.request client Shutdown
43+
in
44+
test run;
45+
[%expect {|
46+
ocamllsp killed with signal = -7 |}]
47+
48+
let%expect_test "ocamllsp process exits with code 0 after Exit notification is \
49+
sent (should be 1)" =
50+
let run client () =
51+
let* (_ : InitializeResult.t) = Client.initialized client in
52+
Client.notification client Exit
53+
in
54+
test run;
55+
[%expect {|
56+
ocamllsp finished with code = 0 |}]

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

+25-12
Original file line numberDiff line numberDiff line change
@@ -70,6 +70,12 @@ end
7070
open Import
7171

7272
module T : sig
73+
val run_with_status :
74+
?extra_env:string list
75+
-> ?handler:unit Client.Handler.t
76+
-> (unit Client.t -> 'a Fiber.t)
77+
-> Unix.process_status * 'a
78+
7379
val run :
7480
?extra_env:string list
7581
-> ?handler:unit Client.Handler.t
@@ -82,7 +88,7 @@ end = struct
8288
let bin =
8389
Bin.which "ocamllsp" ~path:_PATH |> Option.value_exn |> Path.to_string
8490

85-
let run ?(extra_env = []) ?handler f =
91+
let run_with_status ?(extra_env = []) ?handler f =
8692
let stdin_i, stdin_o = Unix.pipe ~cloexec:true () in
8793
let stdout_i, stdout_o = Unix.pipe ~cloexec:true () in
8894
let pid =
@@ -131,26 +137,33 @@ end = struct
131137
let cancelled = ref false in
132138
Fiber.fork_and_join_unit
133139
(fun () ->
134-
let+ timeout = Lev_fiber.Timer.Wheel.await timeout in
135-
match timeout with
140+
Lev_fiber.Timer.Wheel.await timeout >>| function
141+
| `Cancelled -> ()
136142
| `Ok ->
137143
Unix.kill pid Sys.sigkill;
138-
cancelled := true
139-
| `Cancelled -> ())
144+
cancelled := true)
140145
(fun () ->
141-
let* (_ : Unix.process_status) = Lev_fiber.waitpid ~pid in
142-
if !cancelled then Fiber.return ()
143-
else Lev_fiber.Timer.Wheel.cancel timeout)
146+
let* (server_exit_status : Unix.process_status) =
147+
Lev_fiber.waitpid ~pid
148+
in
149+
let+ () =
150+
if !cancelled then Fiber.return ()
151+
else Lev_fiber.Timer.Wheel.cancel timeout
152+
in
153+
server_exit_status)
144154
in
145155
Lev_fiber.run (fun () ->
146156
let* wheel = Lev_fiber.Timer.Wheel.create ~delay:3.0 in
147157
let+ res = init
148-
and+ () =
149-
Fiber.all_concurrently_unit
150-
[ waitpid wheel; Lev_fiber.Timer.Wheel.run wheel ]
158+
and+ status =
159+
Fiber.fork_and_join_unit
160+
(fun () -> Lev_fiber.Timer.Wheel.run wheel)
161+
(fun () -> waitpid wheel)
151162
in
152-
res)
163+
(status, res))
153164
|> Lev_fiber.Error.ok_exn
165+
166+
let run ?extra_env ?handler f = snd @@ run_with_status ?extra_env ?handler f
154167
end
155168

156169
include T

0 commit comments

Comments
 (0)