Skip to content

Commit 3dc1a66

Browse files
authored
Merlins Jump in Ocaml-LSP (#1364)
Add code actions for merlin jumps
1 parent 51e16ea commit 3dc1a66

File tree

7 files changed

+210
-3
lines changed

7 files changed

+210
-3
lines changed

CHANGES.md

+2
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,8 @@
1313

1414
- Add support for OCaml 5.2 (#1233)
1515

16+
- Add a code-action for syntactic and semantic movement shortcuts based on Merlin's Jump command (#1364)
17+
1618
## Fixes
1719

1820
- Kill unnecessary ocamlformat processes with sigterm rather than sigint or

ocaml-lsp-server/src/code_actions.ml

+10-1
Original file line numberDiff line numberDiff line change
@@ -118,13 +118,22 @@ let compute server (params : CodeActionParams.t) =
118118
in
119119
Action_open_related.for_uri capabilities doc
120120
in
121+
let* merlin_jumps =
122+
let capabilities =
123+
let open Option.O in
124+
let* window = (State.client_capabilities state).window in
125+
window.showDocument
126+
in
127+
Action_jump.code_actions doc params capabilities
128+
in
121129
(match Document.syntax doc with
122130
| Ocamllex | Menhir | Cram | Dune ->
123131
Fiber.return (Reply.now (actions (dune_actions @ open_related)), state)
124132
| Ocaml | Reason ->
125133
let reply () =
126134
let+ code_action_results = compute_ocaml_code_actions params state doc in
127-
List.concat [ code_action_results; dune_actions; open_related ] |> actions
135+
List.concat [ code_action_results; dune_actions; open_related; merlin_jumps ]
136+
|> actions
128137
in
129138
let later f =
130139
Fiber.return
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,83 @@
1+
open Import
2+
open Fiber.O
3+
open Stdune
4+
5+
let command_name = "ocamllsp/merlin-jump-to-target"
6+
7+
let targets =
8+
[ "fun"; "match"; "let"; "module"; "module-type"; "match-next-case"; "match-prev-case" ]
9+
;;
10+
11+
let available (capabilities : ShowDocumentClientCapabilities.t option) =
12+
match capabilities with
13+
| Some { support } -> support
14+
| None -> false
15+
;;
16+
17+
let error message =
18+
Jsonrpc.Response.Error.raise
19+
@@ Jsonrpc.Response.Error.make
20+
~code:Jsonrpc.Response.Error.Code.InvalidParams
21+
~message
22+
()
23+
;;
24+
25+
let command_run server (params : ExecuteCommandParams.t) =
26+
let uri, range =
27+
match params.arguments with
28+
| Some [ json_uri; json_range ] ->
29+
let uri = DocumentUri.t_of_yojson json_uri in
30+
let range = Range.t_of_yojson json_range in
31+
uri, range
32+
| None | Some _ -> error "takes a URI and a range as input"
33+
in
34+
let+ { ShowDocumentResult.success } =
35+
let req = ShowDocumentParams.create ~uri ~selection:range ~takeFocus:true () in
36+
Server.request server (Server_request.ShowDocumentRequest req)
37+
in
38+
if not success
39+
then (
40+
let uri = Uri.to_string uri in
41+
Format.eprintf "failed to open %s@." uri);
42+
`Null
43+
;;
44+
45+
(* Dispatch the jump request to Merlin and get the result *)
46+
let process_jump_request ~merlin ~position ~target =
47+
let+ results =
48+
Document.Merlin.with_pipeline_exn merlin (fun pipeline ->
49+
let pposition = Position.logical position in
50+
let query = Query_protocol.Jump (target, pposition) in
51+
Query_commands.dispatch pipeline query)
52+
in
53+
match results with
54+
| `Error _ -> None
55+
| `Found pos -> Some pos
56+
;;
57+
58+
let code_actions
59+
(doc : Document.t)
60+
(params : CodeActionParams.t)
61+
(capabilities : ShowDocumentClientCapabilities.t option)
62+
=
63+
match Document.kind doc with
64+
| `Merlin merlin when available capabilities ->
65+
let+ actions =
66+
(* TODO: Merlin Jump command that returns all available jump locations for a source code buffer. *)
67+
Fiber.parallel_map targets ~f:(fun target ->
68+
let+ res = process_jump_request ~merlin ~position:params.range.start ~target in
69+
let open Option.O in
70+
let* lexing_pos = res in
71+
let+ position = Position.of_lexical_position lexing_pos in
72+
let uri = Document.uri doc in
73+
let range = { Range.start = position; end_ = position } in
74+
let title = sprintf "Jump to %s" target in
75+
let command =
76+
let arguments = [ DocumentUri.yojson_of_t uri; Range.yojson_of_t range ] in
77+
Command.create ~title ~command:command_name ~arguments ()
78+
in
79+
CodeAction.create ~title ~kind:(CodeActionKind.Other "merlin-jump") ~command ())
80+
in
81+
List.filter_opt actions
82+
| _ -> Fiber.return []
83+
;;
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
open Import
2+
3+
val command_name : string
4+
val available : ShowDocumentClientCapabilities.t option -> bool
5+
val command_run : 'a Server.t -> ExecuteCommandParams.t -> Json.t Fiber.t
6+
7+
val code_actions
8+
: Document.t
9+
-> CodeActionParams.t
10+
-> ShowDocumentClientCapabilities.t option
11+
-> CodeAction.t list Fiber.t

ocaml-lsp-server/src/ocaml_lsp_server.ml

+3
Original file line numberDiff line numberDiff line change
@@ -107,6 +107,7 @@ let initialize_info (client_capabilities : ClientCapabilities.t) : InitializeRes
107107
then
108108
view_metrics_command_name
109109
:: Action_open_related.command_name
110+
:: Action_jump.command_name
110111
:: Document_text_command.command_name
111112
:: Merlin_config_command.command_name
112113
:: Dune.commands
@@ -592,6 +593,8 @@ let on_request
592593
else if String.equal command.command Action_open_related.command_name
593594
then
594595
later (fun _state server -> Action_open_related.command_run server command) server
596+
else if String.equal command.command Action_jump.command_name
597+
then later (fun _state server -> Action_jump.command_run server command) server
595598
else
596599
later
597600
(fun state () ->

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

+99
Original file line numberDiff line numberDiff line change
@@ -1272,6 +1272,105 @@ module M : sig type t = I of int | B of bool end
12721272
|}]
12731273
;;
12741274
1275+
let%expect_test "can jump to target" =
1276+
let source =
1277+
{ocaml|
1278+
type t = Foo of int | Bar of bool
1279+
let square x = x * x
1280+
let f (x : t) (d : bool) =
1281+
match x with
1282+
|Bar x -> x
1283+
|Foo _ -> d
1284+
|ocaml}
1285+
in
1286+
let range =
1287+
let start = Position.create ~line:5 ~character:5 in
1288+
let end_ = Position.create ~line:5 ~character:5 in
1289+
Range.create ~start ~end_
1290+
in
1291+
print_code_actions source range ~filter:(find_action "merlin-jump");
1292+
[%expect
1293+
{|
1294+
Code actions:
1295+
{
1296+
"command": {
1297+
"arguments": [
1298+
"file:///foo.ml",
1299+
{
1300+
"end": { "character": 0, "line": 3 },
1301+
"start": { "character": 0, "line": 3 }
1302+
}
1303+
],
1304+
"command": "ocamllsp/merlin-jump-to-target",
1305+
"title": "Jump to fun"
1306+
},
1307+
"kind": "merlin-jump",
1308+
"title": "Jump to fun"
1309+
}
1310+
{
1311+
"command": {
1312+
"arguments": [
1313+
"file:///foo.ml",
1314+
{
1315+
"end": { "character": 2, "line": 4 },
1316+
"start": { "character": 2, "line": 4 }
1317+
}
1318+
],
1319+
"command": "ocamllsp/merlin-jump-to-target",
1320+
"title": "Jump to match"
1321+
},
1322+
"kind": "merlin-jump",
1323+
"title": "Jump to match"
1324+
}
1325+
{
1326+
"command": {
1327+
"arguments": [
1328+
"file:///foo.ml",
1329+
{
1330+
"end": { "character": 0, "line": 3 },
1331+
"start": { "character": 0, "line": 3 }
1332+
}
1333+
],
1334+
"command": "ocamllsp/merlin-jump-to-target",
1335+
"title": "Jump to let"
1336+
},
1337+
"kind": "merlin-jump",
1338+
"title": "Jump to let"
1339+
}
1340+
{
1341+
"command": {
1342+
"arguments": [
1343+
"file:///foo.ml",
1344+
{
1345+
"end": { "character": 3, "line": 6 },
1346+
"start": { "character": 3, "line": 6 }
1347+
}
1348+
],
1349+
"command": "ocamllsp/merlin-jump-to-target",
1350+
"title": "Jump to match-next-case"
1351+
},
1352+
"kind": "merlin-jump",
1353+
"title": "Jump to match-next-case"
1354+
}
1355+
{
1356+
"command": {
1357+
"arguments": [
1358+
"file:///foo.ml",
1359+
{
1360+
"end": { "character": 3, "line": 5 },
1361+
"start": { "character": 3, "line": 5 }
1362+
}
1363+
],
1364+
"command": "ocamllsp/merlin-jump-to-target",
1365+
"title": "Jump to match-prev-case"
1366+
},
1367+
"kind": "merlin-jump",
1368+
"title": "Jump to match-prev-case"
1369+
}
1370+
1371+
|}]
1372+
;;
1373+
12751374
let position_of_offset src x =
12761375
assert (0 <= x && x < String.length src);
12771376
let cnum = ref 0

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

+2-2
Original file line numberDiff line numberDiff line change
@@ -77,8 +77,8 @@ let%expect_test "start/stop" =
7777
"executeCommandProvider": {
7878
"commands": [
7979
"ocamllsp/view-metrics", "ocamllsp/open-related-source",
80-
"ocamllsp/show-document-text", "ocamllsp/show-merlin-config",
81-
"dune/promote"
80+
"ocamllsp/merlin-jump-to-target", "ocamllsp/show-document-text",
81+
"ocamllsp/show-merlin-config", "dune/promote"
8282
]
8383
},
8484
"experimental": {

0 commit comments

Comments
 (0)