Skip to content

Commit

Permalink
Type search custom request (#1369)
Browse files Browse the repository at this point in the history
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.
  • Loading branch information
PizieDust authored Nov 14, 2024
1 parent 8b47925 commit 556da72
Show file tree
Hide file tree
Showing 11 changed files with 441 additions and 2 deletions.
2 changes: 1 addition & 1 deletion .github/workflows/build-and-test.yml
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,7 @@ jobs:

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

- name: Build and install dependencies
run: opam install .
Expand Down
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,8 @@
# Unreleased

- Add custom
[`ocamllsp/typeSearch`](/ocaml-lsp-server/docs/ocamllsp/typeSearch-spec.md) request (#1369)

- Make MerlinJump code action configurable (#1376)

## Fixes
Expand Down
55 changes: 55 additions & 0 deletions ocaml-lsp-server/docs/ocamllsp/typeSearch-spec.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,55 @@
# TypeSearch Request

## Description

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.

## Server capability

- property name: `handleTypeSearch`
- property type: `boolean`

## Request

```js
export interface TypeSearchParams extends TexDocumentPositionParams
{
query: string;
limit: int;
with_doc: bool;
doc_format: string;
}
```
- method: `ocamllsp/typeSearch`
- params:
- `TextDocumentPositionParams`: This is an existing interface that includes:
- `TextDocumentIdentifier`: Specifies the document uri for which the request is sent.
- `Position`: Specifies the cursor position.
More details can be found in the [TextDocumentPositionParams - LSP Specification](https://microsoft.github.io/language-server-protocol/specifications/lsp/3.17/specification/#textDocumentPositionParams).
- `query`: The search pattern.
- `limit`: The number of results to return
- `with_doc`: If to return documentation information or not

## Response
```json
{
[
"name": string,
"typ": string,
"loc": Range,
"doc": {
"value": string,
"kind": string
},
"cost": int,
"constructible" : string
]
}
```
- name: The fully qualified name of this result.,
- typ: The signature of this result,
- loc: The location of the definition of this result in the source code.,
- doc: Optional documentation associated with this result.,
- cost: A numeric value representing the "cost" or distance between this result and the query.
- constructible: A constructible form or template that can be used to invoke this result
- A response with null result is returned if no entries are found.
1 change: 1 addition & 0 deletions ocaml-lsp-server/src/custom_requests/custom_request.ml
Original file line number Diff line number Diff line change
Expand Up @@ -7,3 +7,4 @@ module Typed_holes = Req_typed_holes
module Type_enclosing = Req_type_enclosing
module Wrapping_ast_node = Req_wrapping_ast_node
module Get_documentation = Req_get_documentation
module Type_search = Req_type_search
1 change: 1 addition & 0 deletions ocaml-lsp-server/src/custom_requests/custom_request.mli
Original file line number Diff line number Diff line change
Expand Up @@ -9,3 +9,4 @@ module Typed_holes = Req_typed_holes
module Type_enclosing = Req_type_enclosing
module Wrapping_ast_node = Req_wrapping_ast_node
module Get_documentation = Req_get_documentation
module Type_search = Req_type_search
119 changes: 119 additions & 0 deletions ocaml-lsp-server/src/custom_requests/req_type_search.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,119 @@
open Import
module TextDocumentPositionParams = Lsp.Types.TextDocumentPositionParams

let meth = "ocamllsp/typeSearch"
let capability = "handleTypeSearch", `Bool true

module TypeSearchParams = struct
type t =
{ text_document : TextDocumentIdentifier.t
; position : Position.t
; limit : int
; query : string
; with_doc : bool
; doc_format : MarkupKind.t option
}

let t_of_yojson json =
let open Yojson.Safe.Util in
let textDocumentPosition = Lsp.Types.TextDocumentPositionParams.t_of_yojson json in
let query = json |> member "query" |> to_string in
let limit = json |> member "limit" |> to_int in
let with_doc = json |> member "with_doc" |> to_bool in
let doc_format = json |> member "doc_format" |> to_option MarkupKind.t_of_yojson in
{ position = textDocumentPosition.position
; text_document = textDocumentPosition.textDocument
; query
; limit
; with_doc
; doc_format
}
;;

let yojson_of_t { text_document; position; query; limit; with_doc; doc_format } =
let doc_format =
match doc_format with
| Some format -> [ "doc_format", MarkupKind.yojson_of_t format ]
| None -> []
in
`Assoc
(("textDocument", TextDocumentIdentifier.yojson_of_t text_document)
:: ("position", Position.yojson_of_t position)
:: ("limit", `Int limit)
:: ("with_doc", `Bool with_doc)
:: ("query", `String query)
:: doc_format)
;;
end

module TypeSearch = struct
type t = string Query_protocol.type_search_result list

let doc_to_markupContent ~kind ~value =
let v =
match kind with
| MarkupKind.Markdown ->
(match Doc_to_md.translate value with
| Raw d -> d
| Markdown d -> d)
| MarkupKind.PlainText -> value
in
MarkupContent.create ~kind ~value:v
;;

let yojson_of_t (t : t) doc_format =
let format =
match doc_format with
| Some format -> format
| None -> MarkupKind.PlainText
in
let yojson_of_type_search_result (res : string Query_protocol.type_search_result) =
`Assoc
[ "name", `String res.name
; "typ", `String res.typ
; "loc", Range.yojson_of_t (Range.of_loc res.loc)
; ( "doc"
, match res.doc with
| Some value ->
doc_to_markupContent ~kind:format ~value |> MarkupContent.yojson_of_t
| None -> `Null )
; "cost", `Int res.cost
; "constructible", `String res.constructible
]
in
`List (List.map ~f:yojson_of_type_search_result t)
;;
end

type t = TypeSearch.t

module Request_params = struct
type t = TypeSearchParams.t

let yojson_of_t t = TypeSearchParams.yojson_of_t t

let create text_document position limit query with_doc doc_format : t =
{ text_document; position; limit; query; with_doc; doc_format }
;;
end

let dispatch merlin position limit query with_doc doc_format =
Document.Merlin.with_pipeline_exn merlin (fun pipeline ->
let position = Position.logical position in
let query = Query_protocol.Type_search (query, position, limit, with_doc) in
let results = Query_commands.dispatch pipeline query in
TypeSearch.yojson_of_t results doc_format)
;;

let on_request ~params state =
Fiber.of_thunk (fun () ->
let params = (Option.value ~default:(`Assoc []) params :> Yojson.Safe.t) in
let TypeSearchParams.{ text_document; position; limit; query; with_doc; doc_format } =
TypeSearchParams.t_of_yojson params
in
let uri = text_document.uri in
let doc = Document_store.get state.State.store uri in
match Document.kind doc with
| `Other -> Fiber.return `Null
| `Merlin merlin -> dispatch merlin position limit query with_doc doc_format)
;;
22 changes: 22 additions & 0 deletions ocaml-lsp-server/src/custom_requests/req_type_search.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
open Import

module Request_params : sig
type t

val yojson_of_t : t -> Json.t

val create
: TextDocumentIdentifier.t
-> Position.t
-> int
-> string
-> bool
-> MarkupKind.t 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
2 changes: 2 additions & 0 deletions ocaml-lsp-server/src/ocaml_lsp_server.ml
Original file line number Diff line number Diff line change
Expand Up @@ -96,6 +96,7 @@ let initialize_info (client_capabilities : ClientCapabilities.t) : InitializeRes
; Req_type_enclosing.capability
; Req_get_documentation.capability
; Req_construct.capability
; Req_type_search.capability
] )
]
in
Expand Down Expand Up @@ -526,6 +527,7 @@ let on_request
; Req_type_enclosing.meth, Req_type_enclosing.on_request
; Req_get_documentation.meth, Req_get_documentation.on_request
; Req_wrapping_ast_node.meth, Req_wrapping_ast_node.on_request
; Req_type_search.meth, Req_type_search.on_request
; Req_construct.meth, Req_construct.on_request
; ( Semantic_highlighting.Debug.meth_request_full
, Semantic_highlighting.Debug.on_request_full )
Expand Down
1 change: 1 addition & 0 deletions ocaml-lsp-server/test/e2e-new/dune
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,7 @@
test
type_enclosing
documentation
type_search
with_pp
with_ppx
workspace_change_config))))
3 changes: 2 additions & 1 deletion ocaml-lsp-server/test/e2e-new/start_stop.ml
Original file line number Diff line number Diff line change
Expand Up @@ -93,7 +93,8 @@ let%expect_test "start/stop" =
"handleMerlinCallCompatible": true,
"handleTypeEnclosing": true,
"handleGetDocumentation": true,
"handleConstruct": true
"handleConstruct": true,
"handleTypeSearch": true
}
},
"foldingRangeProvider": true,
Expand Down
Loading

0 comments on commit 556da72

Please sign in to comment.