Skip to content

Commit

Permalink
fix(ocamllsp): respect client capabilites
Browse files Browse the repository at this point in the history
do not display code actions that aren't available to clients without
showDocument support

ps-id: 09AE75CD-265B-4AD4-B1E9-FF5E4451559B
  • Loading branch information
rgrinberg committed Aug 17, 2022
1 parent 6c2b11a commit c49c6bc
Show file tree
Hide file tree
Showing 5 changed files with 39 additions and 39 deletions.
9 changes: 8 additions & 1 deletion ocaml-lsp-server/src/code_actions.ml
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,14 @@ let compute server (params : CodeActionParams.t) =
match doc with
| None -> Fiber.return (Reply.now (actions dune_actions), state)
| Some doc -> (
let open_related = Action_open_related.for_uri uri in
let open_related =
let capabilities =
let open Option.O in
let* window = (State.client_capabilities state).window in
window.showDocument
in
Action_open_related.for_uri capabilities uri
in
match Document.syntax doc with
| Ocamllex | Menhir | Cram | Dune ->
let state : State.t = Server.state server in
Expand Down
53 changes: 28 additions & 25 deletions ocaml-lsp-server/src/code_actions/action_open_related.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,28 +22,31 @@ let command_run server (params : ExecuteCommandParams.t) =
Format.eprintf "failed to open %s@." uri);
`Null

let for_uri uri =
Document.get_impl_intf_counterparts uri
|> List.map ~f:(fun uri ->
let path = Uri.to_path uri in
let exists = Sys.file_exists path in
let title =
sprintf "%s %s"
(if exists then "Open" else "Create")
(Filename.basename path)
in
let command =
let arguments = [ DocumentUri.yojson_of_t uri ] in
Command.create ~title ~command:command_name ~arguments ()
in
let edit =
match exists with
| true -> None
| false ->
let documentChanges =
[ `CreateFile (CreateFile.create ~uri ()) ]
in
Some (WorkspaceEdit.create ~documentChanges ())
in
CodeAction.create ?edit ~title ~kind:(CodeActionKind.Other "switch")
~command ())
let for_uri (capabilities : ShowDocumentClientCapabilities.t option) uri =
match capabilities with
| None | Some { support = false } -> []
| Some { support = true } ->
Document.get_impl_intf_counterparts uri
|> List.map ~f:(fun uri ->
let path = Uri.to_path uri in
let exists = Sys.file_exists path in
let title =
sprintf "%s %s"
(if exists then "Open" else "Create")
(Filename.basename path)
in
let command =
let arguments = [ DocumentUri.yojson_of_t uri ] in
Command.create ~title ~command:command_name ~arguments ()
in
let edit =
match exists with
| true -> None
| false ->
let documentChanges =
[ `CreateFile (CreateFile.create ~uri ()) ]
in
Some (WorkspaceEdit.create ~documentChanges ())
in
CodeAction.create ?edit ~title ~kind:(CodeActionKind.Other "switch")
~command ())
3 changes: 2 additions & 1 deletion ocaml-lsp-server/src/code_actions/action_open_related.mli
Original file line number Diff line number Diff line change
Expand Up @@ -4,4 +4,5 @@ val command_name : string

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

val for_uri : DocumentUri.t -> CodeAction.t list
val for_uri :
ShowDocumentClientCapabilities.t option -> DocumentUri.t -> CodeAction.t list
1 change: 1 addition & 0 deletions ocaml-lsp-server/src/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -226,6 +226,7 @@ include struct
module ServerCapabilities = ServerCapabilities
module Server_notification = Lsp.Server_notification
module SetTraceParams = SetTraceParams
module ShowDocumentClientCapabilities = ShowDocumentClientCapabilities
module ShowDocumentParams = ShowDocumentParams
module ShowDocumentResult = ShowDocumentResult
module ShowMessageParams = ShowMessageParams
Expand Down
12 changes: 0 additions & 12 deletions ocaml-lsp-server/test/e2e-new/code_actions.ml
Original file line number Diff line number Diff line change
Expand Up @@ -73,16 +73,4 @@ let foo = 123
"isPreferred": false,
"kind": "type-annotate",
"title": "Type-annotate"
}
{
"command": {
"arguments": [ "file:///foo.mli" ],
"command": "ocamllsp/open-related-source",
"title": "Create foo.mli"
},
"edit": {
"documentChanges": [ { "kind": "create", "uri": "file:///foo.mli" } ]
},
"kind": "switch",
"title": "Create foo.mli"
} |}]

0 comments on commit c49c6bc

Please sign in to comment.