Skip to content

Commit

Permalink
fix(ocamllsp): check capabilities before offering commands
Browse files Browse the repository at this point in the history
  • Loading branch information
rgrinberg committed Aug 17, 2022
1 parent c49c6bc commit eafac5e
Show file tree
Hide file tree
Showing 5 changed files with 34 additions and 17 deletions.
7 changes: 7 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,10 @@
# Unreleased

## Fixes

- Respect `showDocument` capabilities. Do not offer commands or code actions
that rely on this request without client support. (#836)

# 1.13.1

## Fixes
Expand Down
11 changes: 8 additions & 3 deletions ocaml-lsp-server/src/code_actions/action_open_related.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,10 +22,15 @@ let command_run server (params : ExecuteCommandParams.t) =
Format.eprintf "failed to open %s@." uri);
`Null

let for_uri (capabilities : ShowDocumentClientCapabilities.t option) uri =
let available (capabilities : ShowDocumentClientCapabilities.t option) =
match capabilities with
| None | Some { support = false } -> []
| Some { support = true } ->
| None | Some { support = false } -> false
| Some { support = true } -> true

let for_uri (capabilities : ShowDocumentClientCapabilities.t option) uri =
match available capabilities with
| false -> []
| true ->
Document.get_impl_intf_counterparts uri
|> List.map ~f:(fun uri ->
let path = Uri.to_path uri in
Expand Down
2 changes: 2 additions & 0 deletions ocaml-lsp-server/src/code_actions/action_open_related.mli
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@ open Import

val command_name : string

val available : ShowDocumentClientCapabilities.t option -> bool

val command_run : _ Server.t -> ExecuteCommandParams.t -> Json.t Fiber.t

val for_uri :
Expand Down
24 changes: 16 additions & 8 deletions ocaml-lsp-server/src/ocaml_lsp_server.ml
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,8 @@ let view_metrics server =
let+ { ShowDocumentResult.success = _ } = Server.request server req in
`Null

let initialize_info : InitializeResult.t =
let initialize_info (client_capabilities : ClientCapabilities.t) :
InitializeResult.t =
let codeActionProvider =
let codeActionKinds =
Action_inferred_intf.kind :: Action_destruct.kind
Expand Down Expand Up @@ -83,11 +84,18 @@ let initialize_info : InitializeResult.t =
]
in
let executeCommandProvider =
ExecuteCommandOptions.create
~commands:
(view_metrics_command_name :: Action_open_related.command_name
:: Dune.commands)
()
let commands =
if
Action_open_related.available
(let open Option.O in
let* window = client_capabilities.window in
window.showDocument)
then
view_metrics_command_name :: Action_open_related.command_name
:: Dune.commands
else Dune.commands
in
ExecuteCommandOptions.create ~commands ()
in
let semanticTokensProvider =
Option.map (Sys.getenv_opt "OCAMLLSP_SEMANTIC_HIGHLIGHTING") ~f:(fun v ->
Expand Down Expand Up @@ -322,7 +330,7 @@ let on_initialize server (ip : InitializeParams.t) =
; _
} ->
Reply.later (fun send ->
let* () = send initialize_info in
let* () = send (initialize_info ip.capabilities) in
let register =
RegistrationParams.create
~registrations:
Expand All @@ -346,7 +354,7 @@ let on_initialize server (ip : InitializeParams.t) =
in
Server.request server
(Server_request.ClientRegisterCapability register))
| _ -> Reply.now initialize_info
| _ -> Reply.now (initialize_info ip.capabilities)
in
(resp, state)

Expand Down
7 changes: 1 addition & 6 deletions ocaml-lsp-server/test/e2e-new/start_stop.ml
Original file line number Diff line number Diff line change
Expand Up @@ -42,12 +42,7 @@ let%expect_test "start/stop" =
"documentFormattingProvider": true,
"documentHighlightProvider": true,
"documentSymbolProvider": true,
"executeCommandProvider": {
"commands": [
"ocamllsp/view-metrics", "ocamllsp/open-related-source",
"dune/promote"
]
},
"executeCommandProvider": { "commands": [ "dune/promote" ] },
"experimental": {
"ocamllsp": {
"interfaceSpecificLangId": true,
Expand Down

0 comments on commit eafac5e

Please sign in to comment.