@@ -5,14 +5,14 @@ let meth = "ocamllsp/merlinCallCompatible"
55
66module 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 }
14+ let create ~uri ~result_as_sexp ~command ~args =
15+ { uri ; result_as_sexp; command; args }
1616 ;;
1717
1818 let stringish_of_yojson
@@ -70,18 +70,16 @@ module Request_params = struct
7070 let result_as_sexp = json |> member " resultAsSexp" |> to_bool in
7171 let command = json |> member " command" |> to_string in
7272 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 }
73+ let uri = json |> member " uri " |> Uri . t_of_yojson in
74+ { uri ; result_as_sexp; command; args }
7575 ;;
7676
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
77+ let yojson_of_t { uri; result_as_sexp; command; args } =
78+ let result_as_sexp = " resultAsSexp" , `Bool result_as_sexp in
79+ let command = " command" , `String command in
80+ let args = " args" , `List (List. map ~f: (fun x -> `String x) args) in
81+ let uri = " uri" , Uri. yojson_of_t uri in
82+ `Assoc (result_as_sexp :: command :: args :: uri :: [] )
8583 ;;
8684end
8785
@@ -142,13 +140,12 @@ let perform_query action params pipeline =
142140let on_request ~params state =
143141 Fiber. of_thunk (fun () ->
144142 let params = (Option. value ~default: (`Assoc [] ) params :> Json. t) in
145- let Request_params. { result_as_sexp; command; args; text_document } =
143+ let Request_params. { result_as_sexp; command; args; uri } =
146144 Request_params. t_of_yojson params
147145 in
148146 match Merlin_commands.New_commands. (find_command command all_commands) with
149147 | Merlin_commands.New_commands. Command (_name , _doc , specs , params , action ) ->
150148 let open Fiber.O in
151- let uri = text_document.uri in
152149 let + json = with_pipeline state uri specs args params @@ perform_query action in
153150 let result =
154151 if result_as_sexp
0 commit comments