From beaf5de931257451ab9ad19e0c2cec755b017647 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= <thevoodoos@gmail.com>
Date: Fri, 20 Dec 2024 10:54:43 +0100
Subject: [PATCH] Use DocumentUri converter directly.

This makes the intent clearer.
---
 .../req_merlin_call_compatible.ml             | 27 ++++++++-----------
 .../req_merlin_call_compatible.mli            |  8 +-----
 .../test/e2e-new/merlin_call_compatible.ml    |  3 +--
 3 files changed, 13 insertions(+), 25 deletions(-)

diff --git a/ocaml-lsp-server/src/custom_requests/req_merlin_call_compatible.ml b/ocaml-lsp-server/src/custom_requests/req_merlin_call_compatible.ml
index 41ec7633c..9971548a7 100644
--- a/ocaml-lsp-server/src/custom_requests/req_merlin_call_compatible.ml
+++ b/ocaml-lsp-server/src/custom_requests/req_merlin_call_compatible.ml
@@ -5,15 +5,13 @@ let meth = "ocamllsp/merlinCallCompatible"
 
 module Request_params = struct
   type t =
-    { text_document : TextDocumentIdentifier.t
+    { uri : Uri.t
     ; result_as_sexp : bool
     ; command : string
     ; args : string list
     }
 
-  let create ~text_document ~result_as_sexp ~command ~args =
-    { text_document; result_as_sexp; command; args }
-  ;;
+  let create ~uri ~result_as_sexp ~command ~args = { uri; result_as_sexp; command; args }
 
   let stringish_of_yojson
     =
@@ -70,18 +68,16 @@ module Request_params = struct
     let result_as_sexp = json |> member "resultAsSexp" |> to_bool in
     let command = json |> member "command" |> to_string in
     let args = args_of_yojson json in
-    let text_document = TextDocumentIdentifier.t_of_yojson json in
-    { text_document; result_as_sexp; command; args }
+    let uri = json |> member "uri" |> Uri.t_of_yojson in
+    { uri; result_as_sexp; command; args }
   ;;
 
-  let yojson_of_t { text_document; result_as_sexp; command; args } =
-    match TextDocumentIdentifier.yojson_of_t text_document with
-    | `Assoc assoc ->
-      let result_as_sexp = "resultAsSexp", `Bool result_as_sexp in
-      let command = "command", `String command in
-      let args = "args", `List (List.map ~f:(fun x -> `String x) args) in
-      `Assoc (result_as_sexp :: command :: args :: assoc)
-    | _ -> (* unreachable *) assert false
+  let yojson_of_t { uri; result_as_sexp; command; args } =
+    let result_as_sexp = "resultAsSexp", `Bool result_as_sexp in
+    let command = "command", `String command in
+    let args = "args", `List (List.map ~f:(fun x -> `String x) args) in
+    let uri = "uri", Uri.yojson_of_t uri in
+    `Assoc [ result_as_sexp; command; args; uri ]
   ;;
 end
 
@@ -142,13 +138,12 @@ let perform_query action params pipeline =
 let on_request ~params state =
   Fiber.of_thunk (fun () ->
     let params = (Option.value ~default:(`Assoc []) params :> Json.t) in
-    let Request_params.{ result_as_sexp; command; args; text_document } =
+    let Request_params.{ result_as_sexp; command; args; uri } =
       Request_params.t_of_yojson params
     in
     match Merlin_commands.New_commands.(find_command command all_commands) with
     | Merlin_commands.New_commands.Command (_name, _doc, specs, params, action) ->
       let open Fiber.O in
-      let uri = text_document.uri in
       let+ json = with_pipeline state uri specs args params @@ perform_query action in
       let result =
         if result_as_sexp
diff --git a/ocaml-lsp-server/src/custom_requests/req_merlin_call_compatible.mli b/ocaml-lsp-server/src/custom_requests/req_merlin_call_compatible.mli
index fa6a0c1ea..024352013 100644
--- a/ocaml-lsp-server/src/custom_requests/req_merlin_call_compatible.mli
+++ b/ocaml-lsp-server/src/custom_requests/req_merlin_call_compatible.mli
@@ -3,13 +3,7 @@ open Import
 module Request_params : sig
   type t
 
-  val create
-    :  text_document:TextDocumentIdentifier.t
-    -> result_as_sexp:bool
-    -> command:string
-    -> args:string list
-    -> t
-
+  val create : uri:Uri.t -> result_as_sexp:bool -> command:string -> args:string list -> t
   val yojson_of_t : t -> Json.t
 end
 
diff --git a/ocaml-lsp-server/test/e2e-new/merlin_call_compatible.ml b/ocaml-lsp-server/test/e2e-new/merlin_call_compatible.ml
index 80e77d2cc..f743262ea 100644
--- a/ocaml-lsp-server/test/e2e-new/merlin_call_compatible.ml
+++ b/ocaml-lsp-server/test/e2e-new/merlin_call_compatible.ml
@@ -3,9 +3,8 @@ module Req = Ocaml_lsp_server.Custom_request.Merlin_call_compatible
 
 let call_merlin_compatible client command args result_as_sexp =
   let uri = DocumentUri.of_path "test.ml" in
-  let text_document = TextDocumentIdentifier.create ~uri in
   let params =
-    Req.Request_params.create ~text_document ~result_as_sexp ~command ~args
+    Req.Request_params.create ~uri ~result_as_sexp ~command ~args
     |> Req.Request_params.yojson_of_t
     |> Jsonrpc.Structured.t_of_yojson
     |> Option.some