Skip to content

Commit 6100599

Browse files
committed
add doc format
1 parent 26fdb8a commit 6100599

File tree

3 files changed

+92
-31
lines changed

3 files changed

+92
-31
lines changed

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

Lines changed: 40 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ module TypeSearchParams = struct
1111
; limit : int
1212
; query : string
1313
; with_doc : bool
14+
; doc_format : MarkupKind.t option
1415
}
1516

1617
let t_of_yojson json =
@@ -19,36 +20,61 @@ module TypeSearchParams = struct
1920
let query = json |> member "query" |> to_string in
2021
let limit = json |> member "limit" |> to_int in
2122
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
2224
{ position = textDocumentPosition.position
2325
; text_document = textDocumentPosition.textDocument
2426
; query
2527
; limit
2628
; with_doc
29+
; doc_format
2730
}
2831
;;
2932

30-
let yojson_of_t { text_document; position; query; limit; with_doc } =
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
3139
`Assoc
32-
(("textDocument", TextDocumentIdentifier.yojson_of_t text_document)
33-
:: ("position", Position.yojson_of_t position)
34-
:: ("limit", `Int limit)
35-
:: ("with_doc", `Bool with_doc)
36-
:: [ "query", `String query ])
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)
3746
;;
3847
end
3948

4049
module TypeSearch = struct
4150
type t = string Query_protocol.type_search_result list
4251

43-
let yojson_of_t (t : t) =
52+
let create ~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
4470
let yojson_of_type_search_result (res : string Query_protocol.type_search_result) =
4571
`Assoc
4672
[ "name", `String res.name
4773
; "typ", `String res.typ
4874
; "loc", Range.yojson_of_t (Range.of_loc res.loc)
4975
; ( "doc"
5076
, match res.doc with
51-
| Some d -> `String d
77+
| Some value -> create ~kind:format ~value |> MarkupContent.yojson_of_t
5278
| None -> `Null )
5379
; "cost", `Int res.cost
5480
; "constructible", `String res.constructible
@@ -65,28 +91,28 @@ module Request_params = struct
6591

6692
let yojson_of_t t = TypeSearchParams.yojson_of_t t
6793

68-
let create text_document position limit query with_doc : t =
69-
{ text_document; position; limit; query; with_doc }
94+
let create text_document position limit query with_doc doc_format : t =
95+
{ text_document; position; limit; query; with_doc; doc_format }
7096
;;
7197
end
7298

73-
let dispatch merlin position limit query with_doc =
99+
let dispatch merlin position limit query with_doc doc_format =
74100
Document.Merlin.with_pipeline_exn merlin (fun pipeline ->
75101
let position = Position.logical position in
76102
let query = Query_protocol.Type_search (query, position, limit, with_doc) in
77103
let results = Query_commands.dispatch pipeline query in
78-
TypeSearch.yojson_of_t results)
104+
TypeSearch.yojson_of_t results doc_format)
79105
;;
80106

81107
let on_request ~params state =
82108
Fiber.of_thunk (fun () ->
83109
let params = (Option.value ~default:(`Assoc []) params :> Yojson.Safe.t) in
84-
let TypeSearchParams.{ text_document; position; limit; query; with_doc } =
110+
let TypeSearchParams.{ text_document; position; limit; query; with_doc; doc_format } =
85111
TypeSearchParams.t_of_yojson params
86112
in
87113
let uri = text_document.uri in
88114
let doc = Document_store.get state.State.store uri in
89115
match Document.kind doc with
90116
| `Other -> Fiber.return `Null
91-
| `Merlin merlin -> dispatch merlin position limit query with_doc)
117+
| `Merlin merlin -> dispatch merlin position limit query with_doc doc_format)
92118
;;

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

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,15 @@ module Request_params : sig
44
type t
55

66
val yojson_of_t : t -> Json.t
7-
val create : TextDocumentIdentifier.t -> Position.t -> int -> string -> bool -> t
7+
8+
val create
9+
: TextDocumentIdentifier.t
10+
-> Position.t
11+
-> int
12+
-> string
13+
-> bool
14+
-> MarkupKind.t option
15+
-> t
816
end
917

1018
type t

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

Lines changed: 43 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -2,11 +2,11 @@ open Test.Import
22
module Req = Ocaml_lsp_server.Custom_request.Type_search
33

44
module Util = struct
5-
let call_search position query with_doc client =
5+
let call_search position query with_doc doc_format client =
66
let uri = DocumentUri.of_path "test.ml" in
77
let text_document = TextDocumentIdentifier.create ~uri in
88
let params =
9-
Req.Request_params.create text_document position 3 query with_doc
9+
Req.Request_params.create text_document position 3 query with_doc doc_format
1010
|> Req.Request_params.yojson_of_t
1111
|> Jsonrpc.Structured.t_of_yojson
1212
|> Option.some
@@ -17,11 +17,11 @@ module Util = struct
1717
Client.request client req
1818
;;
1919

20-
let test ~line ~character ~query source ~with_doc =
20+
let test ~line ~character ~query source ~with_doc ?(doc_format = None) () =
2121
let position = Position.create ~character ~line in
2222
let request client =
2323
let open Fiber.O in
24-
let+ response = call_search position query with_doc client in
24+
let+ response = call_search position query with_doc doc_format client in
2525
Test.print_result response
2626
in
2727
Helpers.test source request
@@ -34,7 +34,8 @@ let%expect_test "Polarity Search for a simple query that takes an int and return
3434
let source = "" in
3535
let line = 1 in
3636
let character = 0 in
37-
Util.test ~line ~character ~query:"-int +string" source ~with_doc:true;
37+
let doc_format = Some MarkupKind.Markdown in
38+
Util.test ~line ~character ~query:"-int +string" source ~with_doc:true ~doc_format ();
3839
[%expect
3940
{|
4041
[
@@ -45,7 +46,10 @@ let%expect_test "Polarity Search for a simple query that takes an int and return
4546
"end": { "character": 29, "line": 152 },
4647
"start": { "character": 0, "line": 152 }
4748
},
48-
"doc": "[to_string x] is the written representation of [x] in decimal.",
49+
"doc": {
50+
"kind": "markdown",
51+
"value": "`to_string x` is the written representation of `x` in decimal."
52+
},
4953
"cost": 4,
5054
"constructible": "Int.to_string _"
5155
},
@@ -56,7 +60,10 @@ let%expect_test "Polarity Search for a simple query that takes an int and return
5660
"end": { "character": 33, "line": 740 },
5761
"start": { "character": 0, "line": 740 }
5862
},
59-
"doc": "Return the string representation of an integer, in decimal.",
63+
"doc": {
64+
"kind": "markdown",
65+
"value": "Return the string representation of an integer, in decimal."
66+
},
6067
"cost": 4,
6168
"constructible": "string_of_int _"
6269
},
@@ -67,11 +74,15 @@ let%expect_test "Polarity Search for a simple query that takes an int and return
6774
"end": { "character": 33, "line": 740 },
6875
"start": { "character": 0, "line": 740 }
6976
},
70-
"doc": "Return the string representation of an integer, in decimal.",
77+
"doc": {
78+
"kind": "markdown",
79+
"value": "Return the string representation of an integer, in decimal."
80+
},
7181
"cost": 4,
7282
"constructible": "string_of_int _"
7383
}
74-
] |}]
84+
]
85+
|}]
7586
;;
7687

7788
let%expect_test "Polarity Search for a simple query that takes an int and returns a \
@@ -80,7 +91,7 @@ let%expect_test "Polarity Search for a simple query that takes an int and return
8091
let source = "" in
8192
let line = 1 in
8293
let character = 0 in
83-
Util.test ~line ~character ~query:"-int +string" source ~with_doc:false;
94+
Util.test ~line ~character ~query:"-int +string" source ~with_doc:false ();
8495
[%expect
8596
{|
8697
[
@@ -126,7 +137,13 @@ let%expect_test "Type Search for a simple query that takes an int and returns a
126137
let source = "" in
127138
let line = 1 in
128139
let character = 0 in
129-
Util.test ~line ~character ~query:"int -> string" source ~with_doc:false;
140+
Util.test
141+
~line
142+
~character
143+
~query:"int -> string"
144+
source
145+
~with_doc:false
146+
();
130147
[%expect
131148
{|
132149
[
@@ -172,7 +189,7 @@ let%expect_test "Type Search for a simple query that takes an int and returns a
172189
let source = "" in
173190
let line = 1 in
174191
let character = 0 in
175-
Util.test ~line ~character ~query:"int -> string" source ~with_doc:true;
192+
Util.test ~line ~character ~query:"int -> string" source ~with_doc:true ();
176193
[%expect
177194
{|
178195
[
@@ -183,7 +200,10 @@ let%expect_test "Type Search for a simple query that takes an int and returns a
183200
"end": { "character": 29, "line": 152 },
184201
"start": { "character": 0, "line": 152 }
185202
},
186-
"doc": "[to_string x] is the written representation of [x] in decimal.",
203+
"doc": {
204+
"kind": "plaintext",
205+
"value": "[to_string x] is the written representation of [x] in decimal."
206+
},
187207
"cost": 0,
188208
"constructible": "Int.to_string _"
189209
},
@@ -194,7 +214,10 @@ let%expect_test "Type Search for a simple query that takes an int and returns a
194214
"end": { "character": 33, "line": 740 },
195215
"start": { "character": 0, "line": 740 }
196216
},
197-
"doc": "Return the string representation of an integer, in decimal.",
217+
"doc": {
218+
"kind": "plaintext",
219+
"value": "Return the string representation of an integer, in decimal."
220+
},
198221
"cost": 0,
199222
"constructible": "string_of_int _"
200223
},
@@ -205,9 +228,13 @@ let%expect_test "Type Search for a simple query that takes an int and returns a
205228
"end": { "character": 33, "line": 740 },
206229
"start": { "character": 0, "line": 740 }
207230
},
208-
"doc": "Return the string representation of an integer, in decimal.",
231+
"doc": {
232+
"kind": "plaintext",
233+
"value": "Return the string representation of an integer, in decimal."
234+
},
209235
"cost": 0,
210236
"constructible": "string_of_int _"
211237
}
212-
] |}]
238+
]
239+
|}]
213240
;;

0 commit comments

Comments
 (0)