Skip to content

Commit b73d822

Browse files
authored
Type enclosing query (#1304)
Add `typeEnclosing` customRequest
1 parent 9601581 commit b73d822

File tree

9 files changed

+772
-1
lines changed

9 files changed

+772
-1
lines changed

CHANGES.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,8 @@
4242
[`ocamllsp/merlinCallCompatible`](https://github.com/ocaml/ocaml-lsp/blob/e165f6a3962c356adc7364b9ca71788e93489dd0/ocaml-lsp-server/docs/ocamllsp/merlinCallCompatible-spec.md)
4343
request (#1265)
4444

45+
- Add custom [`ocamllsp/typeEnclosing`](https://github.com/ocaml/ocaml-lsp/blob/109801e56f2060caf4487427bede28b824f4f1fe/ocaml-lsp-server/docs/ocamllsp/typeEnclosing-spec.md) request (#1304)
46+
4547

4648
## Fixes
4749

Lines changed: 59 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,59 @@
1+
# Type Enclosing Request
2+
3+
## Description
4+
5+
Merlin has a concept of `type enclosing` that gets the type of ident under the
6+
cursor. It will highlight the ident and display its type. You can climb the
7+
typed-tree and display the type of bigger expressions surrounding the cursor. In
8+
order to keep the request stateless, the manipulation related to growing or
9+
shrinking enclosings is delegated to the client. This request allows to request
10+
type enclosing under the cursor and then its surrounding enclosings.
11+
12+
## Client capability
13+
14+
There is no client capability relative to this request.
15+
16+
## Server capability
17+
18+
- property name: `handleTypeEnclosing`
19+
- property type: `boolean`
20+
21+
## Request
22+
23+
- method: `ocamllsp/typeEnclosing`
24+
- params:
25+
26+
```json
27+
{
28+
"uri": TextDocumentIdentifier,
29+
"at": (Position | Range),
30+
"index": uinteger,
31+
"verbosity?": uinteger,
32+
}
33+
```
34+
35+
- `index` can be used to print only one type information. This is useful to query
36+
the types lazily: normally, Merlin would return the signature of all enclosing
37+
modules, which can be very expensive.
38+
- `verbosity` determines the number of expansions of aliases in answers.
39+
- `at` :
40+
- if a `Position` is given, it will returns all enclosing around the position
41+
- if a `Range` is given, only enclosings that contain the range
42+
`[range.start; range.end]` will be included in the answer
43+
44+
45+
## Response
46+
47+
```json
48+
{
49+
"enclosings": Range[],
50+
"index": uinteger,
51+
"type": string
52+
}
53+
```
54+
55+
- `enclosings`: The surrounding enclosings
56+
- `index` The index of the provided type result: the index corresponds to a
57+
zero-indexed enclosing in the `enclosings`' array. It is the same value as the
58+
one provided in this request's `TypeEnclosingParams`
59+
- `type`: The type of the enclosing `enclosings[index]` as a raw string
Lines changed: 182 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,182 @@
1+
open Import
2+
module TextDocumentPositionParams = Lsp.Types.TextDocumentPositionParams
3+
4+
let capability = ("handleTypeEnclosing", `Bool true)
5+
6+
let meth = "ocamllsp/typeEnclosing"
7+
8+
module Request_params = struct
9+
type t =
10+
{ text_document : TextDocumentIdentifier.t
11+
; at : [ `Range of Range.t | `Position of Position.t ]
12+
; index : int
13+
; verbosity : int
14+
}
15+
16+
let yojson_of_at = function
17+
| `Range r -> Range.yojson_of_t r
18+
| `Position p -> Position.yojson_of_t p
19+
20+
let yojson_of_t { text_document; index; at; verbosity } =
21+
match TextDocumentIdentifier.yojson_of_t text_document with
22+
| `Assoc assoc ->
23+
let index = ("index", `Int index) in
24+
let range_end = ("at", yojson_of_at at) in
25+
let verbosity = ("verbosity", `Int verbosity) in
26+
`Assoc (index :: range_end :: verbosity :: assoc)
27+
| _ -> (* unreachable *) assert false
28+
29+
let create ?(verbosity = 0) ~text_document ~at ~index () =
30+
{ text_document; index; at; verbosity }
31+
32+
let json_error json =
33+
Json.error "invalid Req_type_enclosing.Request_params" json
34+
35+
let index_of_yojson json params =
36+
match List.assoc_opt "index" params with
37+
| Some (`Int index) -> index
38+
| _ ->
39+
(* If the parameter is incorrectly formatted or missing, we refuse to build
40+
the parameter, [index] is mandatory. *)
41+
json_error json
42+
43+
let verbosity_of_yojson params =
44+
match List.assoc_opt "verbosity" params with
45+
| Some (`Int verbosity) -> verbosity
46+
| _ ->
47+
(* If the parameter is incorrectly formatted or missing, it is assumed that
48+
the we ask for a verbosity level set to 0. *)
49+
0
50+
51+
let at_of_yojson json params =
52+
match List.assoc_opt "at" params with
53+
| Some at -> (
54+
try `Position (Position.t_of_yojson at)
55+
with _ -> `Range (Range.t_of_yojson at))
56+
| _ ->
57+
(* If the parameter is incorrectly formatted or missing, we refuse to build
58+
the parameter, [at] is mandatory. *)
59+
json_error json
60+
61+
let t_of_yojson = function
62+
| `Assoc params as json ->
63+
let verbosity = verbosity_of_yojson params in
64+
let at = at_of_yojson json params in
65+
let index = index_of_yojson json params in
66+
let text_document = TextDocumentIdentifier.t_of_yojson json in
67+
{ index; at; verbosity; text_document }
68+
| json -> json_error json
69+
end
70+
71+
type t =
72+
{ index : int
73+
; type_ : string
74+
; enclosings : Range.t list
75+
}
76+
77+
let yojson_of_t { index; type_; enclosings } =
78+
`Assoc
79+
[ ("index", `Int index)
80+
; ("enclosings", `List (List.map ~f:Range.yojson_of_t enclosings))
81+
; ("type", `String type_)
82+
]
83+
84+
let config_with_given_verbosity config verbosity =
85+
let open Mconfig in
86+
{ config with query = { config.query with verbosity } }
87+
88+
let with_pipeline state uri verbosity with_pipeline =
89+
let doc = Document_store.get state.State.store uri in
90+
match Document.kind doc with
91+
| `Other -> Fiber.return `Null
92+
| `Merlin merlin ->
93+
let open Fiber.O in
94+
let* config = Document.Merlin.mconfig merlin in
95+
Document.Merlin.with_configurable_pipeline_exn
96+
~config:(config_with_given_verbosity config verbosity)
97+
merlin
98+
with_pipeline
99+
100+
let make_enclosing_command position index =
101+
Query_protocol.Type_enclosing (None, position, Some index)
102+
103+
let get_first_enclosing_index range_end enclosings =
104+
List.find_mapi enclosings ~f:(fun i (loc, _, _) ->
105+
let range = Range.of_loc loc in
106+
match Position.compare range_end range.end_ with
107+
| Ordering.Lt | Ordering.Eq -> Some i
108+
| Ordering.Gt -> None)
109+
110+
let dispatch_command pipeline command first_index index =
111+
let rec aux i acc = function
112+
| (_, `String typ, _) :: _ as enclosings when i = index ->
113+
Some
114+
( typ
115+
, List.map
116+
~f:(fun (loc, _, _) -> Range.of_loc loc)
117+
(List.rev_append acc enclosings) )
118+
| curr :: enclosings -> aux (succ i) (curr :: acc) enclosings
119+
| [] -> None
120+
in
121+
let result =
122+
List.drop (Query_commands.dispatch pipeline command) first_index
123+
in
124+
aux 0 [] result
125+
126+
let dispatch_with_range_end pipeline position index range_end =
127+
(* merlin's `type-enclosing` command takes a position and returns a list of
128+
increasing enclosures around that position. If it is given the [index]
129+
parameter, it annotates the corresponding enclosing with its type.
130+
131+
As the request would like to allow the target of an interval, we want to
132+
truncate the list of enclosures that include the interval. Something merlin
133+
cannot do.
134+
135+
We use a little hack where we use the `type-enclosing` command (with a
136+
negative index, so as not to make unnecessary computations) to calculate
137+
the enclosings around the given position. Then, we look for the index
138+
corresponding to the first enclosing included in the range which will act
139+
as an offset to calculate the real index, relative to the range *)
140+
let dummy_command = make_enclosing_command position (-1) in
141+
let enclosings = Query_commands.dispatch pipeline dummy_command in
142+
Option.bind
143+
(get_first_enclosing_index range_end enclosings)
144+
~f:(fun first_index ->
145+
let real_index = first_index + index in
146+
let command = make_enclosing_command position real_index in
147+
dispatch_command pipeline command first_index index)
148+
149+
let dispatch_without_range_end pipeline position index =
150+
let command = make_enclosing_command position index in
151+
dispatch_command pipeline command 0 index
152+
153+
let dispatch_type_enclosing position index range_end pipeline =
154+
let position = Position.logical position in
155+
let result =
156+
match range_end with
157+
| None -> dispatch_without_range_end pipeline position index
158+
| Some range_end ->
159+
dispatch_with_range_end pipeline position index range_end
160+
in
161+
let type_, enclosings =
162+
match result with
163+
| None -> ("<no information>", [])
164+
| Some (typ, enclosings) -> (typ, enclosings)
165+
in
166+
yojson_of_t { index; type_; enclosings }
167+
168+
let on_request ~params state =
169+
Fiber.of_thunk (fun () ->
170+
let params = (Option.value ~default:(`Assoc []) params :> Json.t) in
171+
let Request_params.{ index; verbosity; text_document; at } =
172+
Request_params.t_of_yojson params
173+
in
174+
let position, range_end =
175+
match at with
176+
| `Position p -> (p, None)
177+
| `Range r -> (r.start, Some r.end_)
178+
in
179+
let uri = text_document.uri in
180+
let verbosity = Mconfig.Verbosity.Lvl verbosity in
181+
with_pipeline state uri verbosity
182+
@@ dispatch_type_enclosing position index range_end)
Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,23 @@
1+
open Import
2+
3+
module Request_params : sig
4+
type t
5+
6+
val create :
7+
?verbosity:int
8+
-> text_document:Lsp.Types.TextDocumentIdentifier.t
9+
-> at:[ `Position of Position.t | `Range of Range.t ]
10+
-> index:int
11+
-> unit
12+
-> t
13+
14+
val yojson_of_t : t -> Json.t
15+
end
16+
17+
type t
18+
19+
val capability : string * Json.t
20+
21+
val meth : string
22+
23+
val on_request : params:Jsonrpc.Structured.t option -> State.t -> Json.t Fiber.t

ocaml-lsp-server/src/import.ml

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,8 @@ include struct
2828

2929
let findi xs ~f = List.findi xs ~f
3030

31+
let find_mapi xs ~f = List.find_mapi xs ~f
32+
3133
let sub xs ~pos ~len = List.sub xs ~pos ~len
3234

3335
let hd_exn t = List.hd_exn t
@@ -39,6 +41,8 @@ include struct
3941
let filter t ~f = List.filter t ~f
4042

4143
let tl t = List.tl t
44+
45+
let drop xs i = List.drop xs i
4246
end
4347

4448
module Map = Map

ocaml-lsp-server/src/ocaml_lsp_server.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -99,6 +99,7 @@ let initialize_info (client_capabilities : ClientCapabilities.t) :
9999
; Dune.view_promotion_capability
100100
; Req_hover_extended.capability
101101
; Req_merlin_call_compatible.capability
102+
; Req_type_enclosing.capability
102103
] )
103104
]
104105
in
@@ -521,6 +522,7 @@ let on_request :
521522
; (Req_infer_intf.meth, Req_infer_intf.on_request)
522523
; (Req_typed_holes.meth, Req_typed_holes.on_request)
523524
; (Req_merlin_call_compatible.meth, Req_merlin_call_compatible.on_request)
525+
; (Req_type_enclosing.meth, Req_type_enclosing.on_request)
524526
; (Req_wrapping_ast_node.meth, Req_wrapping_ast_node.on_request)
525527
; ( Semantic_highlighting.Debug.meth_request_full
526528
, Semantic_highlighting.Debug.on_request_full )

ocaml-lsp-server/test/e2e-new/dune

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -60,6 +60,7 @@
6060
start_stop
6161
syntax_doc_tests
6262
test
63+
type_enclosing
6364
with_pp
6465
with_ppx
6566
workspace_change_config))))

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

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -92,7 +92,8 @@ let%expect_test "start/stop" =
9292
"handleWrappingAstNode": true,
9393
"diagnostic_promotions": true,
9494
"handleHoverExtended": true,
95-
"handleMerlinCallCompatible": true
95+
"handleMerlinCallCompatible": true,
96+
"handleTypeEnclosing": true
9697
}
9798
},
9899
"foldingRangeProvider": true,

0 commit comments

Comments
 (0)