Skip to content

Commit

Permalink
Some tweaking on the request
Browse files Browse the repository at this point in the history
  • Loading branch information
xvw committed Jun 24, 2024
1 parent 425f6e0 commit 5516d73
Show file tree
Hide file tree
Showing 3 changed files with 47 additions and 31 deletions.
2 changes: 1 addition & 1 deletion ocaml-lsp-server/docs/ocamllsp/typeEnclosing-spec.md
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ There is no client capability relative to this request.
"textDocument": TextDocumentIdentifier,
"position": Position,
"index": uinteger,
"verbosity": uinteger,
"verbosity?": uinteger,
"rangeEnd?": Position
}
```
Expand Down
37 changes: 23 additions & 14 deletions ocaml-lsp-server/src/custom_requests/req_type_enclosing.ml
Original file line number Diff line number Diff line change
Expand Up @@ -119,24 +119,33 @@ let get_logical_position tdp =
let p = tdp.Lsp.Types.TextDocumentPositionParams.position in
Position.logical p

let get_first_enclosing_index range_end enclosings =
let rec aux i = function
| (loc, _, _) :: xs ->
let range = Range.of_loc loc in
if overlap_with_range_end range range_end then Some i else aux (succ i) xs
| _ -> None
in
aux 0 enclosings

let dispatch_type_enclosing text_document_position index range_end pipeline =
let position = get_logical_position text_document_position in
let dummy_command = make_enclosing_command position (-1) in
let command = make_enclosing_command position index in
let enclosings = Query_commands.dispatch pipeline dummy_command in
match Query_commands.dispatch pipeline command with
| (_, `String typ, _) :: _ ->
Some
( typ
, enclosings
|> List.filter_map ~f:(fun (loc, _, _) ->
let range = Range.of_loc loc in
if overlap_with_range_end range range_end then Some range
else None)
|> Merlin_utils.Std.List.merge_cons ~f:(fun a_range b_range ->
if Range.compare a_range b_range = Eq then Some b_range else None)
)
| _ -> None
Option.bind
(get_first_enclosing_index range_end enclosings)
~f:(fun first_index ->
let command = make_enclosing_command position (first_index + index) in
match Query_commands.dispatch pipeline command with
| (_, `String typ, _) :: enclosings ->
Some
( typ
, enclosings
|> List.map ~f:(fun (loc, _, _) -> Range.of_loc loc)
|> Merlin_utils.Std.List.merge_cons ~f:(fun a_range b_range ->
if Range.compare a_range b_range = Eq then Some b_range
else None) )
| _ -> None)

let on_request ~params state =
Fiber.of_thunk (fun () ->
Expand Down
39 changes: 23 additions & 16 deletions ocaml-lsp-server/test/e2e-new/type_enclosing.ml
Original file line number Diff line number Diff line change
Expand Up @@ -40,10 +40,6 @@ let%expect_test "type enclosing on simple example" =
{
"index": 0,
"enclosings": [
{
"end": { "character": 26, "line": 0 },
"start": { "character": 22, "line": 0 }
},
{
"end": { "character": 26, "line": 0 },
"start": { "character": 8, "line": 0 }
Expand Down Expand Up @@ -73,10 +69,6 @@ let a = Foo 3|}
{
"index": 0,
"enclosings": [
{
"end": { "character": 11, "line": 4 },
"start": { "character": 8, "line": 4 }
},
{
"end": { "character": 13, "line": 4 },
"start": { "character": 8, "line": 4 }
Expand All @@ -85,6 +77,29 @@ let a = Foo 3|}
"type": "int -> t"
} |}]

let%expect_test "type enclosing on simple example - 3" =
let source = {|let x = string_of_int 2002|} in
let request client =
let open Fiber.O in
let position = Position.create ~line:0 ~character:23 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": [
{
"end": { "character": 26, "line": 0 },
"start": { "character": 8, "line": 0 }
}
],
"type": "int"
} |}]

let%expect_test "type enclosing on simple example with rangeEnd" =
let source =
{|module Foo = struct
Expand Down Expand Up @@ -213,10 +228,6 @@ let%expect_test "type enclosing constructors_and_path - 3" =
{
"index": 0,
"enclosings": [
{
"end": { "character": 9, "line": 16 },
"start": { "character": 8, "line": 16 }
},
{
"end": { "character": 11, "line": 16 },
"start": { "character": 8, "line": 16 }
Expand All @@ -240,10 +251,6 @@ let%expect_test "type enclosing constructors_and_path with reconstruction - 4" =
{
"index": 0,
"enclosings": [
{
"end": { "character": 15, "line": 23 },
"start": { "character": 14, "line": 23 }
},
{
"end": { "character": 20, "line": 23 },
"start": { "character": 13, "line": 23 }
Expand Down

0 comments on commit 5516d73

Please sign in to comment.