-
Notifications
You must be signed in to change notification settings - Fork 124
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Loading branch information
Showing
2 changed files
with
272 additions
and
0 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -60,6 +60,7 @@ | |
start_stop | ||
syntax_doc_tests | ||
test | ||
type_enclosing | ||
with_pp | ||
with_ppx | ||
workspace_change_config)))) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,271 @@ | ||
open Test.Import | ||
|
||
let call_type_enclosing ?(verbosity = 0) ?range_end client position index = | ||
let uri = DocumentUri.of_path "test.ml" in | ||
let text_document = TextDocumentIdentifier.create ~uri in | ||
let params = | ||
`Assoc | ||
([ ("textDocument", TextDocumentIdentifier.yojson_of_t text_document) | ||
; ("position", Position.yojson_of_t position) | ||
; ("index", `Int index) | ||
; ("verbosity", `Int verbosity) | ||
] | ||
@ | ||
match range_end with | ||
| None -> [] | ||
| Some x -> [ ("rangeEnd", Position.yojson_of_t x) ]) | ||
in | ||
let params = Some (Jsonrpc.Structured.t_of_yojson params) in | ||
let req = | ||
Lsp.Client_request.UnknownRequest | ||
{ meth = "ocamllsp/typeEnclosing"; params } | ||
in | ||
Client.request client req | ||
|
||
let print_type_enclosing result = | ||
result |> Yojson.Safe.pretty_to_string ~std:false |> print_endline | ||
|
||
let%expect_test "type enclosing on simple example" = | ||
let source = {|let x = string_of_int 2002|} in | ||
let request client = | ||
let open Fiber.O in | ||
let position = Position.create ~line:0 ~character:22 in | ||
let index = 0 in | ||
let+ response = call_type_enclosing client position index in | ||
print_type_enclosing response | ||
in | ||
Helpers.test source request; | ||
[%expect | ||
{| | ||
{ | ||
"index": 0, | ||
"enclosings": [ | ||
{ | ||
"start": { "character": 22, "line": 0 }, | ||
"end_": { "character": 26, "line": 0 }, | ||
"type": "int" | ||
}, | ||
{ | ||
"start": { "character": 8, "line": 0 }, | ||
"end_": { "character": 26, "line": 0 }, | ||
"type": "string" | ||
} | ||
], | ||
"type": "int" | ||
} |}] | ||
|
||
let%expect_test "type enclosing on simple example 2" = | ||
let source = | ||
{|module Foo = struct | ||
let bar = 42 | ||
end | ||
type t = Foo of int | ||
let a = Foo 3|} | ||
in | ||
let request client = | ||
let open Fiber.O in | ||
let position = Position.create ~line:4 ~character:8 in | ||
let index = 0 in | ||
let+ response = call_type_enclosing client position index in | ||
print_type_enclosing response | ||
in | ||
Helpers.test source request; | ||
[%expect | ||
{| | ||
{ | ||
"index": 0, | ||
"enclosings": [ | ||
{ | ||
"start": { "character": 8, "line": 4 }, | ||
"end_": { "character": 11, "line": 4 }, | ||
"type": "int -> t" | ||
}, | ||
{ | ||
"start": { "character": 8, "line": 4 }, | ||
"end_": { "character": 13, "line": 4 }, | ||
"type": "t" | ||
} | ||
], | ||
"type": "int -> t" | ||
} |}] | ||
|
||
let%expect_test "type enclosing on simple example with rangeEnd" = | ||
let source = | ||
{|module Foo = struct | ||
let bar = 42 | ||
end | ||
type t = Foo of int | ||
let a = Foo 3|} | ||
in | ||
let request client = | ||
let open Fiber.O in | ||
let position = Position.create ~line:4 ~character:8 in | ||
let range_end = Position.create ~line:4 ~character:11 in | ||
let index = 0 in | ||
let+ response = call_type_enclosing ~range_end client position index in | ||
print_type_enclosing response | ||
in | ||
Helpers.test source request; | ||
[%expect | ||
{| | ||
{ | ||
"index": 0, | ||
"enclosings": [ | ||
{ | ||
"start": { "character": 8, "line": 4 }, | ||
"end_": { "character": 13, "line": 4 }, | ||
"type": "t" | ||
} | ||
], | ||
"type": "t" | ||
} |}] | ||
|
||
let cons_ml = | ||
{|type t = U | ||
type t' = U | ||
|
||
let f : t = U | ||
|
||
let g (x : t) = | ||
match x with | ||
| U -> () | ||
|
||
module M = struct | ||
type t = A | ||
type u = A | B | ||
end | ||
|
||
let f () = (M.A : M.t) | ||
|
||
let _ = M.A | ||
|
||
module N = struct | ||
type t = A of int | ||
let x = 3 | ||
end | ||
|
||
let _ = Some (N.A 3) | ||
|
||
let _ = N.x | ||
|} | ||
|
||
let%expect_test "type enclosing constructors_and_path - 1" = | ||
let source = cons_ml in | ||
let request client = | ||
let open Fiber.O in | ||
let position = Position.create ~line:3 ~character:13 in | ||
let index = 0 in | ||
let+ response = call_type_enclosing client position index in | ||
print_type_enclosing response | ||
in | ||
Helpers.test source request; | ||
[%expect | ||
{| | ||
{ | ||
"index": 0, | ||
"enclosings": [ | ||
{ | ||
"start": { "character": 13, "line": 3 }, | ||
"end_": { "character": 14, "line": 3 }, | ||
"type": "t" | ||
} | ||
], | ||
"type": "t" | ||
} |}] | ||
|
||
let%expect_test "type enclosing constructors_and_path - 2" = | ||
let source = cons_ml in | ||
let request client = | ||
let open Fiber.O in | ||
let position = Position.create ~line:7 ~character:4 in | ||
let index = 0 in | ||
let+ response = call_type_enclosing client position index in | ||
print_type_enclosing response | ||
in | ||
Helpers.test source request; | ||
[%expect | ||
{| | ||
{ | ||
"index": 0, | ||
"enclosings": [ | ||
{ | ||
"start": { "character": 4, "line": 7 }, | ||
"end_": { "character": 5, "line": 7 }, | ||
"type": "t" | ||
}, | ||
{ | ||
"start": { "character": 2, "line": 6 }, | ||
"end_": { "character": 11, "line": 7 }, | ||
"type": "unit" | ||
}, | ||
{ | ||
"start": { "character": 6, "line": 5 }, | ||
"end_": { "character": 11, "line": 7 }, | ||
"type": "t -> unit" | ||
} | ||
], | ||
"type": "t" | ||
} |}] | ||
|
||
let%expect_test "type enclosing constructors_and_path - 3" = | ||
let source = cons_ml in | ||
let request client = | ||
let open Fiber.O in | ||
let position = Position.create ~line:16 ~character:8 in | ||
let index = 0 in | ||
let+ response = call_type_enclosing client position index in | ||
print_type_enclosing response | ||
in | ||
Helpers.test source request; | ||
[%expect | ||
{| | ||
{ | ||
"index": 0, | ||
"enclosings": [ | ||
{ | ||
"start": { "character": 8, "line": 16 }, | ||
"end_": { "character": 9, "line": 16 }, | ||
"type": "sig type t = A type u = A | B end" | ||
}, | ||
{ | ||
"start": { "character": 8, "line": 16 }, | ||
"end_": { "character": 11, "line": 16 }, | ||
"type": "M.u" | ||
} | ||
], | ||
"type": "sig type t = A type u = A | B end" | ||
} |}] | ||
|
||
let%expect_test "type enclosing constructors_and_path with reconstruction - 4" = | ||
let source = cons_ml in | ||
let request client = | ||
let open Fiber.O in | ||
let position = Position.create ~line:23 ~character:14 in | ||
let index = 0 in | ||
let+ response = call_type_enclosing client position index in | ||
print_type_enclosing response | ||
in | ||
Helpers.test source request; | ||
[%expect | ||
{| | ||
{ | ||
"index": 0, | ||
"enclosings": [ | ||
{ | ||
"start": { "character": 14, "line": 23 }, | ||
"end_": { "character": 15, "line": 23 }, | ||
"type": "sig type t = A of int val x : int end" | ||
}, | ||
{ | ||
"start": { "character": 13, "line": 23 }, | ||
"end_": { "character": 20, "line": 23 }, | ||
"type": "N.t" | ||
}, | ||
{ | ||
"start": { "character": 8, "line": 23 }, | ||
"end_": { "character": 20, "line": 23 }, | ||
"type": "N.t option" | ||
} | ||
], | ||
"type": "sig type t = A of int val x : int end" | ||
} |}] |