11open Import
2- module TextDocumentPositionParams = Lsp.Types. TextDocumentPositionParams
32
43let meth = " ocamllsp/typeSearch"
54let capability = " handleTypeSearch" , `Bool true
@@ -15,21 +14,19 @@ module TypeSearchParams = struct
1514
1615 let t_of_yojson json =
1716 let open Yojson.Safe.Util in
18- let textDocumentPosition = Lsp.Types.TextDocumentPositionParams. t_of_yojson json in
1917 let query = json |> member " query" |> to_string in
2018 let limit = json |> member " limit" |> to_int in
2119 let with_doc = json |> member " with_doc" |> to_bool in
22- { position = textDocumentPosition.position
23- ; text_document = textDocumentPosition.textDocument
24- ; query
25- ; limit
26- ; with_doc
27- }
20+ let position = json |> member " position" |> Position. t_of_yojson in
21+ let text_document =
22+ json |> member " text_document" |> TextDocumentIdentifier. t_of_yojson
23+ in
24+ { text_document; position; query; limit; with_doc }
2825 ;;
2926
3027 let yojson_of_t { text_document; position; query; limit; with_doc } =
3128 `Assoc
32- ((" textDocument " , TextDocumentIdentifier. yojson_of_t text_document)
29+ ((" text_document " , TextDocumentIdentifier. yojson_of_t text_document)
3330 :: (" position" , Position. yojson_of_t position)
3431 :: (" limit" , `Int limit)
3532 :: (" with_doc" , `Bool with_doc)
@@ -65,7 +62,7 @@ module Request_params = struct
6562
6663 let yojson_of_t t = TypeSearchParams. yojson_of_t t
6764
68- let create text_document position limit query with_doc : t =
65+ let create ~ text_document ~ position ?( limit = 20 ) ~ query ?( with_doc = true ) () : t =
6966 { text_document; position; limit; query; with_doc }
7067 ;;
7168end
@@ -82,6 +79,8 @@ let on_request ~params state =
8279 Fiber. of_thunk (fun () ->
8380 let params = (Option. value ~default: (`Assoc [] ) params :> Yojson.Safe. t) in
8481 let TypeSearchParams. { text_document; position; limit; query; with_doc } =
82+ let json_str = Yojson.Safe. pretty_to_string params in
83+ Format. printf " %s@." json_str;
8584 TypeSearchParams. t_of_yojson params
8685 in
8786 let uri = text_document.uri in
0 commit comments