Skip to content

Commit d44b27d

Browse files
authored
Fix hover on method calls (#1553)
* Reproduce issue #1552 * Add missing Pexp_send case in hover filtering Fixes #1552 Now object method types are correctly shown * Add changelog entry
1 parent 2c62a1c commit d44b27d

File tree

4 files changed

+54
-2
lines changed

4 files changed

+54
-2
lines changed

CHANGES.md

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,9 @@
1+
# unreleased
2+
3+
## Fixes
4+
5+
- Fix hover on method calls not showing the type. (#1553, fixes #1552)
6+
17
# 1.23.0
28

39
## Features

ocaml-lsp-server/src/hover_req.ml

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -58,8 +58,10 @@ let hover_at_cursor parsetree (`Logical (cursor_line, cursor_col)) =
5858
then (
5959
match expr.pexp_desc with
6060
| Pexp_constant _ | Pexp_variant _ | Pexp_pack _ -> result := Some `Type_enclosing
61-
| Pexp_ident { loc; _ } | Pexp_construct ({ loc; _ }, _) | Pexp_field (_, { loc; _ })
62-
->
61+
| Pexp_ident { loc; _ }
62+
| Pexp_construct ({ loc; _ }, _)
63+
| Pexp_field (_, { loc; _ })
64+
| Pexp_send (_, { loc; _ }) ->
6365
if is_at_cursor loc
6466
then result := Some `Type_enclosing
6567
else Ast_iterator.default_iterator.expr self expr

ocaml-lsp-server/test/e2e-new/dune

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,7 @@
5151
document_flow
5252
exit_notification
5353
for_ppx
54+
hover
5455
hover_extended
5556
inlay_hints
5657
jump_to_typed_hole
Lines changed: 43 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,43 @@
1+
open Test.Import
2+
3+
let print_hover hover =
4+
match hover with
5+
| None -> print_endline "no hover response"
6+
| Some hover ->
7+
hover |> Hover.yojson_of_t |> Yojson.Safe.pretty_to_string ~std:false |> print_endline
8+
;;
9+
10+
let hover client position =
11+
Client.request
12+
client
13+
(TextDocumentHover
14+
{ HoverParams.position
15+
; textDocument = TextDocumentIdentifier.create ~uri:Helpers.uri
16+
; workDoneToken = None
17+
})
18+
;;
19+
20+
let%expect_test "object method call" =
21+
let source =
22+
{ocaml|
23+
let f (o : < g : int -> unit >) = o#g 4
24+
|ocaml}
25+
in
26+
let position = Position.create ~line:1 ~character:38 in
27+
let req client =
28+
let* resp = hover client position in
29+
let () = print_hover resp in
30+
Fiber.return ()
31+
in
32+
Helpers.test source req;
33+
[%expect
34+
{|
35+
{
36+
"contents": { "kind": "plaintext", "value": "int -> unit" },
37+
"range": {
38+
"end": { "character": 38, "line": 1 },
39+
"start": { "character": 35, "line": 1 }
40+
}
41+
}
42+
|}]
43+
;;

0 commit comments

Comments
 (0)