Skip to content

Commit

Permalink
fix encoding bug
Browse files Browse the repository at this point in the history
  • Loading branch information
PizieDust committed Oct 22, 2024
1 parent 9c17c78 commit 6e5d291
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 12 deletions.
19 changes: 9 additions & 10 deletions ocaml-lsp-server/src/custom_requests/req_type_search.ml
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
open Import
module TextDocumentPositionParams = Lsp.Types.TextDocumentPositionParams

let meth = "ocamllsp/typeSearch"
let capability = "handleTypeSearch", `Bool true
Expand All @@ -15,21 +14,19 @@ module TypeSearchParams = struct

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
{ position = textDocumentPosition.position
; text_document = textDocumentPosition.textDocument
; query
; limit
; with_doc
}
let position = json |> member "position" |> Position.t_of_yojson in
let text_document =
json |> member "text_document" |> TextDocumentIdentifier.t_of_yojson
in
{ text_document; position; query; limit; with_doc }
;;

let yojson_of_t { text_document; position; query; limit; with_doc } =
`Assoc
(("textDocument", TextDocumentIdentifier.yojson_of_t text_document)
(("text_document", TextDocumentIdentifier.yojson_of_t text_document)
:: ("position", Position.yojson_of_t position)
:: ("limit", `Int limit)
:: ("with_doc", `Bool with_doc)
Expand Down Expand Up @@ -65,7 +62,7 @@ module Request_params = struct

let yojson_of_t t = TypeSearchParams.yojson_of_t t

let create text_document position limit query with_doc : t =
let create ~text_document ~position ?(limit = 20) ~query ?(with_doc = true) () : t =
{ text_document; position; limit; query; with_doc }
;;
end
Expand All @@ -82,6 +79,8 @@ 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 } =
let json_str = Yojson.Safe.pretty_to_string params in
Format.printf "%s@." json_str;
TypeSearchParams.t_of_yojson params
in
let uri = text_document.uri in
Expand Down
10 changes: 9 additions & 1 deletion ocaml-lsp-server/src/custom_requests/req_type_search.mli
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,15 @@ module Request_params : sig
type t

val yojson_of_t : t -> Json.t
val create : TextDocumentIdentifier.t -> Position.t -> int -> string -> bool -> t

val create
: text_document:TextDocumentIdentifier.t
-> position:Position.t
-> ?limit:int
-> query:string
-> ?with_doc:bool
-> unit
-> t
end

type t
Expand Down
2 changes: 1 addition & 1 deletion ocaml-lsp-server/test/e2e-new/type_search.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module Util = struct
let uri = DocumentUri.of_path "test.ml" in
let text_document = TextDocumentIdentifier.create ~uri in
let params =
Req.Request_params.create text_document position 3 query with_doc
Req.Request_params.create ~text_document ~position ~limit:3 ~query ~with_doc ()
|> Req.Request_params.yojson_of_t
|> Jsonrpc.Structured.t_of_yojson
|> Option.some
Expand Down

0 comments on commit 6e5d291

Please sign in to comment.