Skip to content

Commit 2d9b1f8

Browse files
committed
feature: open related code actions
We can now open documents on the lsp side, which means that we can implement ml/mli toggling entirely in LSP ps-id: e8a3b313-bfc9-4f75-af26-48228f3e999a
1 parent b26c087 commit 2d9b1f8

File tree

9 files changed

+196
-9
lines changed

9 files changed

+196
-9
lines changed

CHANGES.md

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,9 @@
1+
# Unreleased
2+
3+
## Features
4+
5+
- Code actions for jumping to related files (`.ml`, `.mli`, etc.) (#795)
6+
17
# 1.12.4
28

39
- Allow cancellation of workspace symbols requests (#777)

ocaml-lsp-server/src/code_actions.ml

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -26,8 +26,8 @@ end
2626

2727
let compute server (params : CodeActionParams.t) =
2828
let state : State.t = Server.state server in
29+
let uri = params.textDocument.uri in
2930
let doc =
30-
let uri = params.textDocument.uri in
3131
let store = state.store in
3232
Document_store.get_opt store uri
3333
in
@@ -41,10 +41,11 @@ let compute server (params : CodeActionParams.t) =
4141
match doc with
4242
| None -> Fiber.return (Reply.now (actions dune_actions), state)
4343
| Some doc -> (
44+
let open_related = Action_open_related.for_uri uri in
4445
match Document.syntax doc with
4546
| Ocamllex | Menhir | Cram | Dune ->
4647
let state : State.t = Server.state server in
47-
Fiber.return (Reply.now (actions dune_actions), state)
48+
Fiber.return (Reply.now (actions (dune_actions @ open_related)), state)
4849
| Ocaml | Reason ->
4950
let reply () =
5051
let code_action (ca : Code_action.t) =
@@ -83,8 +84,9 @@ let compute server (params : CodeActionParams.t) =
8384
; Action_mark_remove_unused.remove
8485
]
8586
in
86-
List.filter_opt code_action_results
87-
|> List.append dune_actions |> actions
87+
List.concat
88+
[ List.filter_opt code_action_results; dune_actions; open_related ]
89+
|> actions
8890
in
8991
let later f =
9092
Fiber.return
Lines changed: 48 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,48 @@
1+
open Import
2+
open Fiber.O
3+
4+
let command_name = "ocamllsp/open-related-source"
5+
6+
let command_run server (params : ExecuteCommandParams.t) =
7+
let uri =
8+
match params.arguments with
9+
| Some [ json ] -> DocumentUri.t_of_yojson json
10+
| None | Some _ ->
11+
Jsonrpc.Response.Error.raise
12+
@@ Jsonrpc.Response.Error.make
13+
~code:Jsonrpc.Response.Error.Code.InvalidParams
14+
~message:"takes a single uri as input" ()
15+
in
16+
let uri = Uri.to_string uri in
17+
let+ { ShowDocumentResult.success } =
18+
let req = ShowDocumentParams.create ~uri ~takeFocus:true () in
19+
Server.request server (Server_request.ShowDocumentRequest req)
20+
in
21+
if not success then Format.eprintf "failed to open %s@." uri;
22+
`Null
23+
24+
let for_uri uri =
25+
Document.get_impl_intf_counterparts uri
26+
|> List.map ~f:(fun uri ->
27+
let path = Uri.to_path uri in
28+
let exists = Sys.file_exists path in
29+
let title =
30+
sprintf "%s %s"
31+
(if exists then "Open" else "Create")
32+
(Filename.basename path)
33+
in
34+
let command =
35+
let arguments = [ DocumentUri.yojson_of_t uri ] in
36+
Command.create ~title ~command:command_name ~arguments ()
37+
in
38+
let edit =
39+
match exists with
40+
| true -> None
41+
| false ->
42+
let documentChanges =
43+
[ `CreateFile (CreateFile.create ~uri ()) ]
44+
in
45+
Some (WorkspaceEdit.create ~documentChanges ())
46+
in
47+
CodeAction.create ?edit ~title ~kind:(CodeActionKind.Other "switch")
48+
~command ())
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
open Import
2+
3+
val command_name : string
4+
5+
val command_run : _ Server.t -> ExecuteCommandParams.t -> Json.t Fiber.t
6+
7+
val for_uri : DocumentUri.t -> CodeAction.t list

ocaml-lsp-server/src/import.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -149,6 +149,7 @@ include struct
149149
module CompletionOptions = CompletionOptions
150150
module CompletionParams = CompletionParams
151151
module ConfigurationParams = ConfigurationParams
152+
module CreateFile = CreateFile
152153
module Diagnostic = Diagnostic
153154
module DiagnosticRelatedInformation = DiagnosticRelatedInformation
154155
module DiagnosticSeverity = DiagnosticSeverity

ocaml-lsp-server/src/ocaml_lsp_server.ml

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -83,7 +83,9 @@ let initialize_info : InitializeResult.t =
8383
in
8484
let executeCommandProvider =
8585
ExecuteCommandOptions.create
86-
~commands:(view_metrics_command_name :: Dune.commands)
86+
~commands:
87+
(view_metrics_command_name :: Action_open_related.command_name
88+
:: Dune.commands)
8789
()
8890
in
8991
ServerCapabilities.create ~textDocumentSync ~hoverProvider:(`Bool true)
@@ -800,6 +802,10 @@ let on_request :
800802
| ExecuteCommand command ->
801803
if String.equal command.command view_metrics_command_name then
802804
later (fun _state server -> view_metrics server) server
805+
else if String.equal command.command Action_open_related.command_name then
806+
later
807+
(fun _state server -> Action_open_related.command_run server command)
808+
server
803809
else
804810
later
805811
(fun state () ->

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

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,8 @@ let foo = 123
5050
in
5151
Fiber.fork_and_join_unit run_client (fun () -> run >>> Client.stop client)
5252
);
53-
[%expect {|
53+
[%expect
54+
{|
5455
Code actions:
5556
{
5657
"title": "Type-annotate",
@@ -72,4 +73,16 @@ let foo = 123
7273
}
7374
]
7475
}
76+
}
77+
{
78+
"title": "Create foo.mli",
79+
"kind": "switch",
80+
"edit": {
81+
"documentChanges": [ { "kind": "create", "uri": "file:///foo.mli" } ]
82+
},
83+
"command": {
84+
"title": "Create foo.mli",
85+
"command": "ocamllsp/open-related-source",
86+
"arguments": [ "file:///foo.mli" ]
87+
}
7588
} |}]

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

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,10 @@ let%expect_test "start/stop" =
5858
"renameProvider": { "prepareProvider": true },
5959
"foldingRangeProvider": true,
6060
"executeCommandProvider": {
61-
"commands": [ "ocamllsp/view-metrics", "dune/promote" ]
61+
"commands": [
62+
"ocamllsp/view-metrics", "ocamllsp/open-related-source",
63+
"dune/promote"
64+
]
6265
},
6366
"selectionRangeProvider": true,
6467
"workspaceSymbolProvider": true,

ocaml-lsp-server/test/e2e/__tests__/textDocument-codeAction.test.ts

Lines changed: 103 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -182,6 +182,25 @@ let f (x : t) = x
182182
"kind": "type-annotate",
183183
"title": "Type-annotate",
184184
},
185+
Object {
186+
"command": Object {
187+
"arguments": Array [
188+
"file:///test.mli",
189+
],
190+
"command": "ocamllsp/open-related-source",
191+
"title": "Create test.mli",
192+
},
193+
"edit": Object {
194+
"documentChanges": Array [
195+
Object {
196+
"kind": "create",
197+
"uri": "file:///test.mli",
198+
},
199+
],
200+
},
201+
"kind": "switch",
202+
"title": "Create test.mli",
203+
},
185204
]
186205
`);
187206
});
@@ -464,7 +483,29 @@ type x =
464483
let start = Types.Position.create(2, 5);
465484
let end = Types.Position.create(2, 6);
466485
let actions = await codeAction("file:///test.ml", start, end);
467-
expect(actions).toBeNull();
486+
expect(actions).toMatchInlineSnapshot(`
487+
Array [
488+
Object {
489+
"command": Object {
490+
"arguments": Array [
491+
"file:///test.mli",
492+
],
493+
"command": "ocamllsp/open-related-source",
494+
"title": "Create test.mli",
495+
},
496+
"edit": Object {
497+
"documentChanges": Array [
498+
Object {
499+
"kind": "create",
500+
"uri": "file:///test.mli",
501+
},
502+
],
503+
},
504+
"kind": "switch",
505+
"title": "Create test.mli",
506+
},
507+
]
508+
`);
468509
});
469510

470511
it("offers `Construct an expression` code action", async () => {
@@ -480,7 +521,67 @@ let x = _
480521
(await codeAction(uri, Position.create(0, 8), Position.create(0, 9))) ??
481522
[];
482523

483-
expect(actions).not.toBeNull();
524+
expect(actions).toMatchInlineSnapshot(`
525+
Array [
526+
Object {
527+
"edit": Object {
528+
"documentChanges": Array [
529+
Object {
530+
"edits": Array [
531+
Object {
532+
"newText": "(_ : 'a)",
533+
"range": Object {
534+
"end": Object {
535+
"character": 9,
536+
"line": 0,
537+
},
538+
"start": Object {
539+
"character": 8,
540+
"line": 0,
541+
},
542+
},
543+
},
544+
],
545+
"textDocument": Object {
546+
"uri": "file:///test.ml",
547+
"version": 0,
548+
},
549+
},
550+
],
551+
},
552+
"isPreferred": false,
553+
"kind": "type-annotate",
554+
"title": "Type-annotate",
555+
},
556+
Object {
557+
"command": Object {
558+
"command": "editor.action.triggerSuggest",
559+
"title": "Trigger Suggest",
560+
},
561+
"kind": "construct",
562+
"title": "Construct an expression",
563+
},
564+
Object {
565+
"command": Object {
566+
"arguments": Array [
567+
"file:///test.mli",
568+
],
569+
"command": "ocamllsp/open-related-source",
570+
"title": "Create test.mli",
571+
},
572+
"edit": Object {
573+
"documentChanges": Array [
574+
Object {
575+
"kind": "create",
576+
"uri": "file:///test.mli",
577+
},
578+
],
579+
},
580+
"kind": "switch",
581+
"title": "Create test.mli",
582+
},
583+
]
584+
`);
484585

485586
let construct_actions = actions.find(
486587
(codeAction: Types.CodeAction) =>

0 commit comments

Comments
 (0)