Skip to content

Commit beaf5de

Browse files
committed
Use DocumentUri converter directly.
This makes the intent clearer.
1 parent 1628871 commit beaf5de

File tree

3 files changed

+13
-25
lines changed

3 files changed

+13
-25
lines changed

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

Lines changed: 11 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -5,15 +5,13 @@ let meth = "ocamllsp/merlinCallCompatible"
55

66
module Request_params = struct
77
type t =
8-
{ text_document : TextDocumentIdentifier.t
8+
{ uri : Uri.t
99
; result_as_sexp : bool
1010
; command : string
1111
; args : string list
1212
}
1313

14-
let create ~text_document ~result_as_sexp ~command ~args =
15-
{ text_document; result_as_sexp; command; args }
16-
;;
14+
let create ~uri ~result_as_sexp ~command ~args = { uri; result_as_sexp; command; args }
1715

1816
let stringish_of_yojson
1917
=
@@ -70,18 +68,16 @@ module Request_params = struct
7068
let result_as_sexp = json |> member "resultAsSexp" |> to_bool in
7169
let command = json |> member "command" |> to_string in
7270
let args = args_of_yojson json in
73-
let text_document = TextDocumentIdentifier.t_of_yojson json in
74-
{ text_document; result_as_sexp; command; args }
71+
let uri = json |> member "uri" |> Uri.t_of_yojson in
72+
{ uri; result_as_sexp; command; args }
7573
;;
7674

77-
let yojson_of_t { text_document; result_as_sexp; command; args } =
78-
match TextDocumentIdentifier.yojson_of_t text_document with
79-
| `Assoc assoc ->
80-
let result_as_sexp = "resultAsSexp", `Bool result_as_sexp in
81-
let command = "command", `String command in
82-
let args = "args", `List (List.map ~f:(fun x -> `String x) args) in
83-
`Assoc (result_as_sexp :: command :: args :: assoc)
84-
| _ -> (* unreachable *) assert false
75+
let yojson_of_t { uri; result_as_sexp; command; args } =
76+
let result_as_sexp = "resultAsSexp", `Bool result_as_sexp in
77+
let command = "command", `String command in
78+
let args = "args", `List (List.map ~f:(fun x -> `String x) args) in
79+
let uri = "uri", Uri.yojson_of_t uri in
80+
`Assoc [ result_as_sexp; command; args; uri ]
8581
;;
8682
end
8783

@@ -142,13 +138,12 @@ let perform_query action params pipeline =
142138
let on_request ~params state =
143139
Fiber.of_thunk (fun () ->
144140
let params = (Option.value ~default:(`Assoc []) params :> Json.t) in
145-
let Request_params.{ result_as_sexp; command; args; text_document } =
141+
let Request_params.{ result_as_sexp; command; args; uri } =
146142
Request_params.t_of_yojson params
147143
in
148144
match Merlin_commands.New_commands.(find_command command all_commands) with
149145
| Merlin_commands.New_commands.Command (_name, _doc, specs, params, action) ->
150146
let open Fiber.O in
151-
let uri = text_document.uri in
152147
let+ json = with_pipeline state uri specs args params @@ perform_query action in
153148
let result =
154149
if result_as_sexp

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

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -3,13 +3,7 @@ open Import
33
module Request_params : sig
44
type t
55

6-
val create
7-
: text_document:TextDocumentIdentifier.t
8-
-> result_as_sexp:bool
9-
-> command:string
10-
-> args:string list
11-
-> t
12-
6+
val create : uri:Uri.t -> result_as_sexp:bool -> command:string -> args:string list -> t
137
val yojson_of_t : t -> Json.t
148
end
159

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

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,9 +3,8 @@ module Req = Ocaml_lsp_server.Custom_request.Merlin_call_compatible
33

44
let call_merlin_compatible client command args result_as_sexp =
55
let uri = DocumentUri.of_path "test.ml" in
6-
let text_document = TextDocumentIdentifier.create ~uri in
76
let params =
8-
Req.Request_params.create ~text_document ~result_as_sexp ~command ~args
7+
Req.Request_params.create ~uri ~result_as_sexp ~command ~args
98
|> Req.Request_params.yojson_of_t
109
|> Jsonrpc.Structured.t_of_yojson
1110
|> Option.some

0 commit comments

Comments
 (0)