Skip to content

Commit 7bb7fb9

Browse files
committed
Requests: Refactor implIntf and inferIntf parameters
Currently implIntf and inferIntf accept a DocumentUri while typedHoles accepts ``` { uri: DocumentUri } ``` When looking at how vscode-ocaml-platform handles it: - For implIntf and inferIntf: ``` let source_uri = Uri.toString (TextDocument.uri document) () in ``` - For typedHoles ``` let uri = TextDocument.uri doc in ``` I don't see any reason to not have the three requests have the same type of parameter
1 parent dba52c2 commit 7bb7fb9

File tree

8 files changed

+86
-106
lines changed

8 files changed

+86
-106
lines changed

ocaml-lsp-server/docs/ocamllsp/inferIntf-spec.md

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,14 @@ property type: `boolean`
2222
## Request
2323

2424
- method: `ocamllsp/inferIntf`
25-
- params: `DocumentUri` (see [`DocumentUri`](https://microsoft.github.io/language-server-protocol/specifications/specification-current/#uri) in LSP specification)
25+
- params:
26+
27+
```json
28+
{
29+
"uri": DocumentUri,
30+
}
31+
```
32+
(see [`DocumentUri`](https://microsoft.github.io/language-server-protocol/specifications/specification-current/#uri) in LSP specification)
2633

2734
## Response
2835

ocaml-lsp-server/docs/ocamllsp/switchImplIntf-spec.md

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -25,11 +25,16 @@ property type: `boolean`
2525
## Request
2626

2727
- method: `ocamllsp/switchImplIntf`
28-
- params: `DocumentUri` (see [`DocumentUri`](https://microsoft.github.io/language-server-protocol/specifications/specification-current/#uri) in LSP specification)
28+
- params:
29+
30+
```json
31+
{
32+
"uri": DocumentUri,
33+
}
34+
```
35+
(see [`DocumentUri`](https://microsoft.github.io/language-server-protocol/specifications/specification-current/#uri) in LSP specification)
2936

3037
## Response
3138

3239
- result: DocumentUri[] (non-empty)
3340
- error: code and message set in case an exception happens during the `ocamllsp/switchImplIntf` request.
34-
35-

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

Lines changed: 11 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -6,32 +6,18 @@ let meth = "ocamllsp/inferIntf"
66

77
let on_request ~(params : Jsonrpc.Structured.t option) (state : State.t) =
88
Fiber.of_thunk (fun () ->
9-
match params with
10-
| Some (`List [ json_uri ]) ->
11-
let json_uri = DocumentUri.t_of_yojson json_uri in
12-
(match Document_store.get_opt state.store json_uri with
13-
| None ->
14-
Jsonrpc.Response.Error.raise
15-
(Jsonrpc.Response.Error.make
16-
~code:InvalidParams
17-
~message:
18-
"ocamllsp/inferIntf received a URI for an unloaded file. Load the file \
19-
first."
20-
())
21-
| Some impl ->
22-
let+ intf = Inference.infer_intf_for_impl impl in
23-
Json.t_of_yojson (`String intf))
24-
| Some json ->
25-
Jsonrpc.Response.Error.raise
26-
(Jsonrpc.Response.Error.make
27-
~code:InvalidRequest
28-
~message:"The input parameter for ocamllsp/inferIntf is invalid"
29-
~data:(`Assoc [ "param", (json :> Json.t) ])
30-
())
9+
let uri = Request_uri_params.parse_exn params in
10+
let doc = Document_store.get_opt state.store uri in
11+
match doc with
3112
| None ->
3213
Jsonrpc.Response.Error.raise
3314
(Jsonrpc.Response.Error.make
34-
~code:InvalidRequest
35-
~message:"ocamllsp/inferIntf must receive param: DocumentUri.t"
36-
()))
15+
~code:InvalidParams
16+
~message:
17+
"ocamllsp/inferIntf received a URI for an unloaded file. Load the file \
18+
first."
19+
())
20+
| Some impl ->
21+
let+ intf = Inference.infer_intf_for_impl impl in
22+
Json.t_of_yojson (`String intf))
3723
;;

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

Lines changed: 14 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -10,33 +10,18 @@ let switch merlin_doc (param : DocumentUri.t) : Json.t =
1010
;;
1111

1212
let on_request ~(params : Jsonrpc.Structured.t option) (state : State.t) =
13-
match params with
14-
| Some (`List [ json_uri ]) ->
15-
let uri = DocumentUri.t_of_yojson json_uri in
16-
(match Document_store.get_opt state.store uri with
17-
| Some doc ->
18-
(match Document.kind doc with
19-
| `Merlin merlin_doc -> switch (Some merlin_doc) uri
20-
| `Other ->
21-
Jsonrpc.Response.Error.raise
22-
(Jsonrpc.Response.Error.make
23-
~code:InvalidRequest
24-
~message:
25-
"Document with this URI is not supported by ocamllsp/switchImplIntf"
26-
~data:(`Assoc [ "param", (json_uri :> Json.t) ])
27-
()))
28-
| None -> switch None uri)
29-
| Some json ->
30-
Jsonrpc.Response.Error.raise
31-
(Jsonrpc.Response.Error.make
32-
~code:InvalidRequest
33-
~message:"The input parameter for ocamllsp/switchImplIntf is invalid"
34-
~data:(`Assoc [ "param", (json :> Json.t) ])
35-
())
36-
| None ->
37-
Jsonrpc.Response.Error.raise
38-
(Jsonrpc.Response.Error.make
39-
~code:InvalidRequest
40-
~message:"ocamllsp/switchImplIntf must receive param: DocumentUri.t"
41-
())
13+
let uri = Request_uri_params.parse_exn params in
14+
let doc = Document_store.get_opt state.store uri in
15+
match doc with
16+
| Some doc ->
17+
(match Document.kind doc with
18+
| `Merlin merlin_doc -> switch (Some merlin_doc) uri
19+
| `Other ->
20+
Jsonrpc.Response.Error.raise
21+
(Jsonrpc.Response.Error.make
22+
~code:InvalidRequest
23+
~message:"Document with this URI is not supported by ocamllsp/switchImplIntf"
24+
~data:(Uri.yojson_of_t uri)
25+
()))
26+
| None -> switch None uri
4227
;;

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

Lines changed: 1 addition & 41 deletions
Original file line numberDiff line numberDiff line change
@@ -4,46 +4,6 @@ open Fiber.O
44
let capability = "handleTypedHoles", `Bool true
55
let meth = "ocamllsp/typedHoles"
66

7-
module Request_params = struct
8-
type t = Uri.t
9-
10-
(* Request params must have the form as in the given string. *)
11-
let expected_params = `Assoc [ "uri", `String "<DocumentUri>" ]
12-
let create uri = uri
13-
14-
let t_of_structured_json params : t option =
15-
match params with
16-
| `Assoc [ ("uri", uri) ] ->
17-
let uri = Uri.t_of_yojson uri in
18-
Some uri
19-
| _ -> None
20-
;;
21-
22-
let parse_exn (params : Jsonrpc.Structured.t option) : t =
23-
let raise_invalid_params ?data ~message () =
24-
Jsonrpc.Response.Error.raise
25-
@@ Jsonrpc.Response.Error.make
26-
?data
27-
~code:Jsonrpc.Response.Error.Code.InvalidParams
28-
~message
29-
()
30-
in
31-
match params with
32-
| None -> raise_invalid_params ~message:"Expected params but received none" ()
33-
| Some params ->
34-
(match t_of_structured_json params with
35-
| Some uri -> uri
36-
| None ->
37-
let error_json =
38-
`Assoc
39-
[ "params_expected", expected_params; "params_received", (params :> Json.t) ]
40-
in
41-
raise_invalid_params ~message:"Unxpected parameter format" ~data:error_json ())
42-
;;
43-
44-
let yojson_of_t = Uri.yojson_of_t
45-
end
46-
477
type t = Range.t list
488

499
let yojson_of_t holes =
@@ -57,7 +17,7 @@ let t_of_yojson list =
5717

5818
let on_request ~(params : Jsonrpc.Structured.t option) (state : State.t) =
5919
Fiber.of_thunk (fun () ->
60-
let uri = Request_params.parse_exn params in
20+
let uri = Request_uri_params.parse_exn params in
6121
let store = state.store in
6222
let doc = Document_store.get_opt store uri in
6323
match doc with

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

Lines changed: 0 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,5 @@
11
open Import
22

3-
module Request_params : sig
4-
type t
5-
6-
val create : Uri.t -> t
7-
val yojson_of_t : t -> Json.t
8-
end
9-
103
type t
114

125
val t_of_yojson : Json.t -> t
Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,38 @@
1+
open Import
2+
3+
type t = Uri.t
4+
5+
(* Request params must have the form as in the given string. *)
6+
let expected_params = `Assoc [ "uri", `String "<DocumentUri>" ]
7+
8+
let t_of_structured_json params : t option =
9+
match params with
10+
| `Assoc [ ("uri", uri) ] ->
11+
let uri = Uri.t_of_yojson uri in
12+
Some uri
13+
| _ -> None
14+
;;
15+
16+
let parse_exn (params : Jsonrpc.Structured.t option) : t =
17+
let raise_invalid_params ?data ~message () =
18+
Jsonrpc.Response.Error.raise
19+
@@ Jsonrpc.Response.Error.make
20+
?data
21+
~code:Jsonrpc.Response.Error.Code.InvalidParams
22+
~message
23+
()
24+
in
25+
match params with
26+
| None -> raise_invalid_params ~message:"Expected params but received none" ()
27+
| Some params ->
28+
(match t_of_structured_json params with
29+
| Some uri -> uri
30+
| None ->
31+
let error_json =
32+
`Assoc
33+
[ "params_expected", expected_params; "params_received", (params :> Json.t) ]
34+
in
35+
raise_invalid_params ~message:"Unexpected parameter format" ~data:error_json ())
36+
;;
37+
38+
let yojson_of_t = Uri.yojson_of_t
Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
open Import
2+
3+
type t = Uri.t
4+
5+
val yojson_of_t : t -> Json.t
6+
val parse_exn : Jsonrpc.Structured.t option -> t

0 commit comments

Comments
 (0)