-
Notifications
You must be signed in to change notification settings - Fork 123
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Co-authored-by: Ulysse Gérard <[email protected]>
- Loading branch information
Showing
10 changed files
with
319 additions
and
1 deletion.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,54 @@ | ||
# Merlin Jump Request | ||
|
||
## Description | ||
|
||
This custom request allows Merlin-type code navigation in a source buffer. | ||
|
||
## Server capability | ||
|
||
- propert name: `handleJump` | ||
- property type: `boolean` | ||
|
||
## Request | ||
|
||
- method: `ocamllsp/jump` | ||
- params: `JumpParams` extends [TextDocumentPositionParams](https://microsoft.github.io/language-server-protocol/specifications/lsp/3.17/specification/#textDocumentPositionParams) and is defined as follows: | ||
|
||
```js | ||
export interface JumpParams extends TextDocumentPositionParams | ||
{ | ||
/** | ||
* The requested target of the jump, one of `fun`, `let`, `module`, | ||
* `module-type`, `match`, `match-next-case`, `match-prev-case`. | ||
* | ||
* If omitted, all valid targets will be considered. | ||
*/ | ||
target?: string; | ||
} | ||
``` | ||
|
||
## Response | ||
|
||
- result: `Jump` | ||
|
||
```js | ||
|
||
export interface TargetPosition { | ||
/** | ||
* The target's kind. | ||
*/ | ||
target: string; | ||
|
||
/** | ||
* The corresponding position in the request's document. | ||
*/ | ||
position: Position; | ||
} | ||
|
||
export interface Jump { | ||
/** | ||
* The list of possible targets to jump-to. | ||
*/ | ||
jumps: TargetPosition[] | ||
} | ||
``` |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
104 changes: 104 additions & 0 deletions
104
ocaml-lsp-server/src/custom_requests/req_merlin_jump.ml
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,104 @@ | ||
open Import | ||
module TextDocumentPositionParams = Lsp.Types.TextDocumentPositionParams | ||
|
||
let meth = "ocamllsp/jump" | ||
let capability = "handleJump", `Bool true | ||
|
||
module JumpParams = struct | ||
let targets = | ||
[ "fun" | ||
; "match" | ||
; "let" | ||
; "module" | ||
; "module-type" | ||
; "match-next-case" | ||
; "match-prev-case" | ||
] | ||
;; | ||
|
||
type t = | ||
{ textDocument : TextDocumentIdentifier.t | ||
; position : Position.t | ||
; target : string option | ||
} | ||
|
||
let t_of_yojson json = | ||
let open Yojson.Safe.Util in | ||
{ textDocument = json |> member "textDocument" |> TextDocumentIdentifier.t_of_yojson | ||
; position = json |> member "position" |> Position.t_of_yojson | ||
; target = json |> member "target" |> to_string_option | ||
} | ||
;; | ||
|
||
let yojson_of_t { textDocument; position; target } = | ||
let target = | ||
Option.value_map target ~default:[] ~f:(fun v -> [ "target", `String v ]) | ||
in | ||
`Assoc | ||
(("textDocument", TextDocumentIdentifier.yojson_of_t textDocument) | ||
:: ("position", Position.yojson_of_t position) | ||
:: target) | ||
;; | ||
end | ||
|
||
module Jump = struct | ||
type t = (string * Position.t) list | ||
|
||
let yojson_of_t (lst : t) : Yojson.Safe.t = | ||
let jumps = | ||
List.map | ||
~f:(fun (target, position) -> | ||
`Assoc [ "target", `String target; "position", Position.yojson_of_t position ]) | ||
lst | ||
in | ||
`Assoc [ "jumps", `List jumps ] | ||
;; | ||
end | ||
|
||
type t = Jump.t | ||
|
||
module Request_params = struct | ||
type t = JumpParams.t | ||
|
||
let yojson_of_t t = JumpParams.yojson_of_t t | ||
|
||
let create ~uri ~position ~target = | ||
{ JumpParams.textDocument = TextDocumentIdentifier.create ~uri; position; target } | ||
;; | ||
end | ||
|
||
let dispatch ~merlin ~position ~target = | ||
Document.Merlin.with_pipeline_exn merlin (fun pipeline -> | ||
let pposition = Position.logical position in | ||
let query = Query_protocol.Jump (target, pposition) in | ||
Query_commands.dispatch pipeline query) | ||
;; | ||
|
||
let on_request ~params state = | ||
let open Fiber.O in | ||
Fiber.of_thunk (fun () -> | ||
let params = (Option.value ~default:(`Assoc []) params :> Yojson.Safe.t) in | ||
let params = JumpParams.t_of_yojson params in | ||
let uri = params.textDocument.uri in | ||
let position = params.position in | ||
let doc = Document_store.get state.State.store uri in | ||
match Document.kind doc with | ||
| `Other -> Fiber.return `Null | ||
| `Merlin merlin -> | ||
let targets = | ||
match params.target with | ||
| None -> JumpParams.targets | ||
| Some target -> [ target ] | ||
in | ||
let+ results = | ||
Fiber.parallel_map targets ~f:(fun target -> | ||
dispatch ~merlin ~position ~target | ||
|> Fiber.map ~f:(function | ||
| `Error _ -> None | ||
| `Found pos -> | ||
(match Position.of_lexical_position pos with | ||
| None -> None | ||
| Some position -> Some (target, position)))) | ||
in | ||
Jump.yojson_of_t (List.filter_map results ~f:Fun.id)) | ||
;; |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,14 @@ | ||
open Import | ||
|
||
module Request_params : sig | ||
type t | ||
|
||
val yojson_of_t : t -> Json.t | ||
val create : uri:DocumentUri.t -> position:Position.t -> target:string option -> t | ||
end | ||
|
||
type t | ||
|
||
val meth : string | ||
val capability : string * [> `Bool of bool ] | ||
val on_request : params:Jsonrpc.Structured.t option -> State.t -> Json.t Fiber.t |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -63,6 +63,7 @@ | |
test | ||
type_enclosing | ||
documentation | ||
merlin_jump | ||
type_search | ||
with_pp | ||
with_ppx | ||
|
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,138 @@ | ||
open Test.Import | ||
module Req = Ocaml_lsp_server.Custom_request.Merlin_jump | ||
|
||
module Util = struct | ||
let call_jump position ?target client = | ||
let uri = DocumentUri.of_path "test.ml" in | ||
let params = | ||
Req.Request_params.create ~uri ~position ~target | ||
|> Req.Request_params.yojson_of_t | ||
|> Jsonrpc.Structured.t_of_yojson | ||
|> Option.some | ||
in | ||
let req = Lsp.Client_request.UnknownRequest { meth = "ocamllsp/jump"; params } in | ||
Client.request client req | ||
;; | ||
|
||
let test ~line ~character ~source ?target () = | ||
let position = Position.create ~character ~line in | ||
let request client = | ||
let open Fiber.O in | ||
let+ response = call_jump position client ?target in | ||
Test.print_result response | ||
in | ||
Helpers.test source request | ||
;; | ||
end | ||
|
||
let%expect_test "Get all jumps including the next match case" = | ||
let source = | ||
{| | ||
let find_vowel x = | ||
match x with | ||
| 'A' -> true | ||
| 'E' -> true | ||
| 'I' -> true | ||
| 'O' -> true | ||
| 'U' -> true | ||
| _ -> false | ||
|} | ||
in | ||
let line = 3 in | ||
let character = 2 in | ||
Util.test ~line ~character ~source (); | ||
[%expect | ||
{| | ||
{ | ||
"jumps": [ | ||
{ "target": "fun", "position": { "character": 0, "line": 1 } }, | ||
{ "target": "match", "position": { "character": 0, "line": 2 } }, | ||
{ "target": "let", "position": { "character": 0, "line": 1 } }, | ||
{ | ||
"target": "match-next-case", | ||
"position": { "character": 2, "line": 4 } | ||
} | ||
] | ||
} |}] | ||
;; | ||
|
||
let%expect_test "Get location of the next match case" = | ||
let source = | ||
{| | ||
let find_vowel x = | ||
match x with | ||
| 'A' -> true | ||
| 'E' -> true | ||
| 'I' -> true | ||
| 'O' -> true | ||
| 'U' -> true | ||
| _ -> false | ||
|} | ||
in | ||
let line = 3 in | ||
let character = 2 in | ||
Util.test ~line ~character ~source ~target:"match-next-case" (); | ||
[%expect | ||
{| | ||
{ | ||
"jumps": [ | ||
{ | ||
"target": "match-next-case", | ||
"position": { "character": 2, "line": 4 } | ||
} | ||
] | ||
} | ||
|}] | ||
;; | ||
|
||
let%expect_test "Get location of a the module" = | ||
let source = | ||
{|type a = Foo | Bar | ||
|
||
module A = struct | ||
let f () = 10 | ||
let g = Bar | ||
let h x = x | ||
|
||
module B = struct | ||
type b = Baz | ||
|
||
let x = (Baz, 10) | ||
let y = (Bar, Foo) | ||
end | ||
|
||
type t = { a : string; b : float } | ||
|
||
let z = { a = "Hello"; b = 1.0 } | ||
end|} | ||
in | ||
let line = 10 in | ||
let character = 3 in | ||
Util.test ~line ~character ~source (); | ||
[%expect | ||
{| | ||
{ | ||
"jumps": [ | ||
{ "target": "module", "position": { "character": 2, "line": 7 } } | ||
] | ||
} |}] | ||
;; | ||
|
||
let%expect_test "Same line should output no locations" = | ||
let source = {|let x = 5 |} in | ||
let line = 1 in | ||
let character = 5 in | ||
Util.test ~line ~character ~source (); | ||
[%expect {| { "jumps": [] } |}] | ||
;; | ||
|
||
let%expect_test "Ask for a non-existing target" = | ||
let source = {| | ||
let find_vowel x = () | ||
|} in | ||
let line = 1 in | ||
let character = 2 in | ||
Util.test ~line ~character ~source ~target:"notatarget" (); | ||
[%expect | ||
{| { "jumps": [] } |}] | ||
;; |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters