Skip to content

Commit

Permalink
fix: allow opening the same document twice
Browse files Browse the repository at this point in the history
this is done to accommodate neovim's lsp client

Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed Apr 25, 2023
1 parent 6593231 commit 829f1b2
Show file tree
Hide file tree
Showing 4 changed files with 25 additions and 34 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,9 @@

## Fixes

- Allow opening documents that were already open. This is a workaround for
neovim's lsp client (#1067)

- Disable type annotation for functions (#1054)

- Respect codeActionLiteralSupport capability (#1046)
Expand Down
8 changes: 6 additions & 2 deletions ocaml-lsp-server/src/document_store.ml
Original file line number Diff line number Diff line change
Expand Up @@ -106,9 +106,13 @@ let open_document t doc =
{ document = Some doc; promotions = 0; semantic_tokens_cache = None });
Fiber.return ()
| Some d ->
assert (!d.document = None);
(* if there's no document, then we just opened it to track promotions.
if there's a document already, we're doing a double open and there's no
need to unregister. *)
let unregister = !d.document = None in
d := { !d with document = Some doc };
unregister_request t [ key ]
if unregister then unregister_request t [ key ] else Fiber.return ()

let get_opt t uri = Table.find t.db uri |> Option.bind ~f:(fun d -> !d.document)

Expand Down
1 change: 0 additions & 1 deletion ocaml-lsp-server/src/ocaml_lsp_server.ml
Original file line number Diff line number Diff line change
Expand Up @@ -683,7 +683,6 @@ let on_notification server (notification : Client_notification.t) :
state.merlin
params
in
assert (Document_store.get_opt store params.textDocument.uri = None);
let* () = Document_store.open_document store doc in
let+ () = set_diagnostics state.detached (State.diagnostics state) doc in
state
Expand Down
47 changes: 16 additions & 31 deletions ocaml-lsp-server/test/e2e-new/document_flow.ml
Original file line number Diff line number Diff line change
@@ -1,13 +1,24 @@
open Test.Import

let%expect_test "it should allow double opening the same document" =
let diagnostics = Fiber.Ivar.create () in
let diagnostics = Fiber.Mvar.create () in
let drain_diagnostics () = Fiber.Mvar.read diagnostics in
let handler =
let on_request (type resp state) (client : state Client.t)
(req : resp Lsp.Server_request.t) :
(resp Lsp_fiber.Rpc.Reply.t * state) Fiber.t =
match req with
| Lsp.Server_request.ClientUnregisterCapability _ ->
let state = Client.state client in
Fiber.return (Lsp_fiber.Rpc.Reply.now (), state)
| _ -> assert false
in
Client.Handler.make
~on_notification:
(fun _ -> function
| PublishDiagnostics _ -> Fiber.Ivar.fill diagnostics ()
| PublishDiagnostics _ -> Fiber.Mvar.write diagnostics ()
| _ -> Fiber.return ())
~on_request:{ Client.Handler.on_request }
()
in
( Test.run ~handler @@ fun client ->
Expand Down Expand Up @@ -35,36 +46,10 @@ let%expect_test "it should allow double opening the same document" =
(TextDocumentDidOpen (DidOpenTextDocumentParams.create ~textDocument))
in
let* () = open_ "text 1" in
let* () = drain_diagnostics () in
let+ () = open_ "text 2" in
()
in
Fiber.fork_and_join_unit run_client (fun () ->
run >>> Fiber.Ivar.read diagnostics >>> Client.stop client) );
[%expect
{|
(* CR expect_test_collector: This test expectation appears to contain a backtrace.
This is strongly discouraged as backtraces are fragile.
Please change this test to not include a backtrace. *)

Uncaught error when handling notification:
{
"params": {
"textDocument": {
"languageId": "ocaml",
"text": "text 2",
"uri": "file:///foo.ml",
"version": 0
}
},
"method": "textDocument/didOpen",
"jsonrpc": "2.0"
}
Error:
[ { exn =
"File \"ocaml-lsp-server/src/ocaml_lsp_server.ml\", line 686, characters 4-10: Assertion failed"
; backtrace =
"Raised at Ocaml_lsp_server.on_notification in file \"ocaml-lsp-server/src/ocaml_lsp_server.ml\", line 686, characters 4-72\n\
Called from Fiber__Scheduler.exec in file \"fiber/src/scheduler.ml\", line 73, characters 8-11\n\
"
}
] |}]
run >>> drain_diagnostics () >>> Client.stop client) );
[%expect {| |}]

0 comments on commit 829f1b2

Please sign in to comment.