Skip to content

Commit 556da72

Browse files
authored
Type search custom request (#1369)
This custom request allows clients to perform a type search at a specific position within a text document based on finding functions or types that match a specific query pattern. Result can include documentation in ocaml-doc or markdown format.
1 parent 8b47925 commit 556da72

File tree

11 files changed

+441
-2
lines changed

11 files changed

+441
-2
lines changed

.github/workflows/build-and-test.yml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -54,7 +54,7 @@ jobs:
5454

5555
# Remove this pin once a compatible version of Merlin has been released
5656
# - name: Pin dev Merlin
57-
# run: opam pin https://github.com/ocaml/merlin.git#master
57+
# run: opam pin https://github.com/ocaml/merlin.git#main
5858

5959
- name: Build and install dependencies
6060
run: opam install .

CHANGES.md

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,8 @@
11
# Unreleased
22

3+
- Add custom
4+
[`ocamllsp/typeSearch`](/ocaml-lsp-server/docs/ocamllsp/typeSearch-spec.md) request (#1369)
5+
36
- Make MerlinJump code action configurable (#1376)
47

58
## Fixes
Lines changed: 55 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,55 @@
1+
# TypeSearch Request
2+
3+
## Description
4+
5+
This custom request allows clients to perform a type search at a specific position within a text document based on finding functions or types that match a specific query pattern.
6+
7+
## Server capability
8+
9+
- property name: `handleTypeSearch`
10+
- property type: `boolean`
11+
12+
## Request
13+
14+
```js
15+
export interface TypeSearchParams extends TexDocumentPositionParams
16+
{
17+
query: string;
18+
limit: int;
19+
with_doc: bool;
20+
doc_format: string;
21+
}
22+
```
23+
- method: `ocamllsp/typeSearch`
24+
- params:
25+
- `TextDocumentPositionParams`: This is an existing interface that includes:
26+
- `TextDocumentIdentifier`: Specifies the document uri for which the request is sent.
27+
- `Position`: Specifies the cursor position.
28+
More details can be found in the [TextDocumentPositionParams - LSP Specification](https://microsoft.github.io/language-server-protocol/specifications/lsp/3.17/specification/#textDocumentPositionParams).
29+
- `query`: The search pattern.
30+
- `limit`: The number of results to return
31+
- `with_doc`: If to return documentation information or not
32+
33+
## Response
34+
```json
35+
{
36+
[
37+
"name": string,
38+
"typ": string,
39+
"loc": Range,
40+
"doc": {
41+
"value": string,
42+
"kind": string
43+
},
44+
"cost": int,
45+
"constructible" : string
46+
]
47+
}
48+
```
49+
- name: The fully qualified name of this result.,
50+
- typ: The signature of this result,
51+
- loc: The location of the definition of this result in the source code.,
52+
- doc: Optional documentation associated with this result.,
53+
- cost: A numeric value representing the "cost" or distance between this result and the query.
54+
- constructible: A constructible form or template that can be used to invoke this result
55+
- A response with null result is returned if no entries are found.

ocaml-lsp-server/src/custom_requests/custom_request.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,3 +7,4 @@ module Typed_holes = Req_typed_holes
77
module Type_enclosing = Req_type_enclosing
88
module Wrapping_ast_node = Req_wrapping_ast_node
99
module Get_documentation = Req_get_documentation
10+
module Type_search = Req_type_search

ocaml-lsp-server/src/custom_requests/custom_request.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,3 +9,4 @@ module Typed_holes = Req_typed_holes
99
module Type_enclosing = Req_type_enclosing
1010
module Wrapping_ast_node = Req_wrapping_ast_node
1111
module Get_documentation = Req_get_documentation
12+
module Type_search = Req_type_search
Lines changed: 119 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,119 @@
1+
open Import
2+
module TextDocumentPositionParams = Lsp.Types.TextDocumentPositionParams
3+
4+
let meth = "ocamllsp/typeSearch"
5+
let capability = "handleTypeSearch", `Bool true
6+
7+
module TypeSearchParams = struct
8+
type t =
9+
{ text_document : TextDocumentIdentifier.t
10+
; position : Position.t
11+
; limit : int
12+
; query : string
13+
; with_doc : bool
14+
; doc_format : MarkupKind.t option
15+
}
16+
17+
let t_of_yojson json =
18+
let open Yojson.Safe.Util in
19+
let textDocumentPosition = Lsp.Types.TextDocumentPositionParams.t_of_yojson json in
20+
let query = json |> member "query" |> to_string in
21+
let limit = json |> member "limit" |> to_int in
22+
let with_doc = json |> member "with_doc" |> to_bool in
23+
let doc_format = json |> member "doc_format" |> to_option MarkupKind.t_of_yojson in
24+
{ position = textDocumentPosition.position
25+
; text_document = textDocumentPosition.textDocument
26+
; query
27+
; limit
28+
; with_doc
29+
; doc_format
30+
}
31+
;;
32+
33+
let yojson_of_t { text_document; position; query; limit; with_doc; doc_format } =
34+
let doc_format =
35+
match doc_format with
36+
| Some format -> [ "doc_format", MarkupKind.yojson_of_t format ]
37+
| None -> []
38+
in
39+
`Assoc
40+
(("textDocument", TextDocumentIdentifier.yojson_of_t text_document)
41+
:: ("position", Position.yojson_of_t position)
42+
:: ("limit", `Int limit)
43+
:: ("with_doc", `Bool with_doc)
44+
:: ("query", `String query)
45+
:: doc_format)
46+
;;
47+
end
48+
49+
module TypeSearch = struct
50+
type t = string Query_protocol.type_search_result list
51+
52+
let doc_to_markupContent ~kind ~value =
53+
let v =
54+
match kind with
55+
| MarkupKind.Markdown ->
56+
(match Doc_to_md.translate value with
57+
| Raw d -> d
58+
| Markdown d -> d)
59+
| MarkupKind.PlainText -> value
60+
in
61+
MarkupContent.create ~kind ~value:v
62+
;;
63+
64+
let yojson_of_t (t : t) doc_format =
65+
let format =
66+
match doc_format with
67+
| Some format -> format
68+
| None -> MarkupKind.PlainText
69+
in
70+
let yojson_of_type_search_result (res : string Query_protocol.type_search_result) =
71+
`Assoc
72+
[ "name", `String res.name
73+
; "typ", `String res.typ
74+
; "loc", Range.yojson_of_t (Range.of_loc res.loc)
75+
; ( "doc"
76+
, match res.doc with
77+
| Some value ->
78+
doc_to_markupContent ~kind:format ~value |> MarkupContent.yojson_of_t
79+
| None -> `Null )
80+
; "cost", `Int res.cost
81+
; "constructible", `String res.constructible
82+
]
83+
in
84+
`List (List.map ~f:yojson_of_type_search_result t)
85+
;;
86+
end
87+
88+
type t = TypeSearch.t
89+
90+
module Request_params = struct
91+
type t = TypeSearchParams.t
92+
93+
let yojson_of_t t = TypeSearchParams.yojson_of_t t
94+
95+
let create text_document position limit query with_doc doc_format : t =
96+
{ text_document; position; limit; query; with_doc; doc_format }
97+
;;
98+
end
99+
100+
let dispatch merlin position limit query with_doc doc_format =
101+
Document.Merlin.with_pipeline_exn merlin (fun pipeline ->
102+
let position = Position.logical position in
103+
let query = Query_protocol.Type_search (query, position, limit, with_doc) in
104+
let results = Query_commands.dispatch pipeline query in
105+
TypeSearch.yojson_of_t results doc_format)
106+
;;
107+
108+
let on_request ~params state =
109+
Fiber.of_thunk (fun () ->
110+
let params = (Option.value ~default:(`Assoc []) params :> Yojson.Safe.t) in
111+
let TypeSearchParams.{ text_document; position; limit; query; with_doc; doc_format } =
112+
TypeSearchParams.t_of_yojson params
113+
in
114+
let uri = text_document.uri in
115+
let doc = Document_store.get state.State.store uri in
116+
match Document.kind doc with
117+
| `Other -> Fiber.return `Null
118+
| `Merlin merlin -> dispatch merlin position limit query with_doc doc_format)
119+
;;
Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
open Import
2+
3+
module Request_params : sig
4+
type t
5+
6+
val yojson_of_t : t -> Json.t
7+
8+
val create
9+
: TextDocumentIdentifier.t
10+
-> Position.t
11+
-> int
12+
-> string
13+
-> bool
14+
-> MarkupKind.t option
15+
-> t
16+
end
17+
18+
type t
19+
20+
val meth : string
21+
val capability : string * [> `Bool of bool ]
22+
val on_request : params:Jsonrpc.Structured.t option -> State.t -> Json.t Fiber.t

ocaml-lsp-server/src/ocaml_lsp_server.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -96,6 +96,7 @@ let initialize_info (client_capabilities : ClientCapabilities.t) : InitializeRes
9696
; Req_type_enclosing.capability
9797
; Req_get_documentation.capability
9898
; Req_construct.capability
99+
; Req_type_search.capability
99100
] )
100101
]
101102
in
@@ -526,6 +527,7 @@ let on_request
526527
; Req_type_enclosing.meth, Req_type_enclosing.on_request
527528
; Req_get_documentation.meth, Req_get_documentation.on_request
528529
; Req_wrapping_ast_node.meth, Req_wrapping_ast_node.on_request
530+
; Req_type_search.meth, Req_type_search.on_request
529531
; Req_construct.meth, Req_construct.on_request
530532
; ( Semantic_highlighting.Debug.meth_request_full
531533
, 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
@@ -63,6 +63,7 @@
6363
test
6464
type_enclosing
6565
documentation
66+
type_search
6667
with_pp
6768
with_ppx
6869
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
@@ -93,7 +93,8 @@ let%expect_test "start/stop" =
9393
"handleMerlinCallCompatible": true,
9494
"handleTypeEnclosing": true,
9595
"handleGetDocumentation": true,
96-
"handleConstruct": true
96+
"handleConstruct": true,
97+
"handleTypeSearch": true
9798
}
9899
},
99100
"foldingRangeProvider": true,

0 commit comments

Comments
 (0)