Skip to content

Commit

Permalink
fix: update DocumentSelector definition (#1068)
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed Apr 25, 2023
1 parent 829f1b2 commit 07ba12b
Show file tree
Hide file tree
Showing 6 changed files with 12 additions and 87 deletions.
2 changes: 2 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,8 @@
([#1049](https://github.com/ocaml/ocaml-lsp/pull/1049), fixes
[#1034](https://github.com/ocaml/ocaml-lsp/issues/1034))

- Fix the type of DocumentSelector in cram document registration (#1068)

## Features
- Add "Remove type annotation" code action. (#1039)

Expand Down
13 changes: 2 additions & 11 deletions lsp/bin/metamodel/metaModel.json
Original file line number Diff line number Diff line change
Expand Up @@ -13917,17 +13917,8 @@
"type": {
"kind": "array",
"element": {
"kind": "or",
"items": [
{
"kind": "base",
"name": "string"
},
{
"kind": "reference",
"name": "DocumentFilter"
}
]
"kind": "reference",
"name": "DocumentFilter"
}
},
"documentation": "A document selector is the combination of one or many document filters.\n\n@sample `let sel:DocumentSelector = [{ language: 'typescript' }, { language: 'json', pattern: '**∕tsconfig.json' }]`;\n\nThe use of a string as a document filter is deprecated @since 3.16.0.",
Expand Down
72 changes: 3 additions & 69 deletions lsp/src/types.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4878,85 +4878,19 @@ module DocumentFilter = struct
end

module DocumentSelector = struct
type t = [ `String of string | `DocumentFilter of DocumentFilter.t ] list
[@@deriving_inline yojson]
type t = DocumentFilter.t list [@@deriving_inline yojson]

let _ = fun (_ : t) -> ()

let t_of_yojson =
(let _tp_loc = "lsp/src/types.ml.DocumentSelector.t" in
fun t ->
list_of_yojson
(fun yojson ->
try
match yojson with
| `List [ `String atom ] as _yojson -> (
match atom with
| "String" ->
Ppx_yojson_conv_lib.Yojson_conv_error.ptag_takes_args
_tp_loc
_yojson
| "DocumentFilter" ->
Ppx_yojson_conv_lib.Yojson_conv_error.ptag_takes_args
_tp_loc
_yojson
| _ -> Ppx_yojson_conv_lib.Yojson_conv_error.no_variant_match ())
| `List (`String atom :: yojson_args) as _yojson -> (
match atom with
| "String" as _tag -> (
match yojson_args with
| [ v0 ] ->
let v0 = string_of_yojson v0 in
`String v0
| _ ->
Ppx_yojson_conv_lib.Yojson_conv_error.ptag_incorrect_n_args
_tp_loc
_tag
_yojson)
| "DocumentFilter" as _tag -> (
match yojson_args with
| [ v0 ] ->
let v0 = DocumentFilter.t_of_yojson v0 in
`DocumentFilter v0
| _ ->
Ppx_yojson_conv_lib.Yojson_conv_error.ptag_incorrect_n_args
_tp_loc
_tag
_yojson)
| _ -> Ppx_yojson_conv_lib.Yojson_conv_error.no_variant_match ())
| `List (`List _ :: _) as yojson ->
Ppx_yojson_conv_lib.Yojson_conv_error
.nested_list_invalid_poly_var
_tp_loc
yojson
| `List [] as yojson ->
Ppx_yojson_conv_lib.Yojson_conv_error.empty_list_invalid_poly_var
_tp_loc
yojson
| _ as yojson ->
Ppx_yojson_conv_lib.Yojson_conv_error.unexpected_stag
_tp_loc
yojson
with Ppx_yojson_conv_lib.Yojson_conv_error.No_variant_match ->
Ppx_yojson_conv_lib.Yojson_conv_error.no_matching_variant_found
_tp_loc
yojson)
t
fun t -> list_of_yojson DocumentFilter.t_of_yojson t
: Ppx_yojson_conv_lib.Yojson.Safe.t -> t)

let _ = t_of_yojson

let yojson_of_t =
(fun v ->
yojson_of_list
(function
| `String v0 ->
let v0 = yojson_of_string v0 in
`List [ `String "String"; v0 ]
| `DocumentFilter v0 ->
let v0 = DocumentFilter.yojson_of_t v0 in
`List [ `String "DocumentFilter"; v0 ])
v
(fun v -> yojson_of_list DocumentFilter.yojson_of_t v
: t -> Ppx_yojson_conv_lib.Yojson.Safe.t)

let _ = yojson_of_t
Expand Down
2 changes: 1 addition & 1 deletion lsp/src/types.mli
Original file line number Diff line number Diff line change
Expand Up @@ -839,7 +839,7 @@ module DocumentFilter : sig
end

module DocumentSelector : sig
type t = [ `String of string | `DocumentFilter of DocumentFilter.t ] list
type t = DocumentFilter.t list

include Json.Jsonable.S with type t := t
end
Expand Down
5 changes: 2 additions & 3 deletions ocaml-lsp-server/src/document_store.ml
Original file line number Diff line number Diff line change
Expand Up @@ -75,9 +75,8 @@ let register_request t uris =
let id = code_action_id uri in
let registerOptions =
let documentSelector =
[ `DocumentFilter
(`TextDocumentFilter
(TextDocumentFilter.create ~pattern:(Uri.to_path uri) ()))
[ `TextDocumentFilter
(TextDocumentFilter.create ~pattern:(Uri.to_path uri) ())
]
in
CodeActionRegistrationOptions.create
Expand Down
5 changes: 2 additions & 3 deletions ocaml-lsp-server/src/ocaml_lsp_server.ml
Original file line number Diff line number Diff line change
Expand Up @@ -288,9 +288,8 @@ let on_initialize server (ip : InitializeParams.t) =
let documentSelector =
[ "cram"; "dune"; "dune-project"; "dune-workspace" ]
|> List.map ~f:(fun language ->
`DocumentFilter
(`TextDocumentFilter
(TextDocumentFilter.create ~language ())))
`TextDocumentFilter
(TextDocumentFilter.create ~language ()))
in
TextDocumentRegistrationOptions.create ~documentSelector ()
|> TextDocumentRegistrationOptions.yojson_of_t
Expand Down

0 comments on commit 07ba12b

Please sign in to comment.