Skip to content

Commit

Permalink
Fix prefix parsing to start method completion when typing # (#1363)
Browse files Browse the repository at this point in the history
* Add a test illustrating issue #1358

Object methods are not completed

* Fix prefix parsing for method call

When completing module paths or record fields Merlin expects the
    beginning of the path and the `.` to be part of the prefix. But when
    accessing an object's methods, the prefix should not contain the `#`
    sign. We use a sub-matching group to that effect.

    - Prefix for [my_record.|] is ["my_record."] (handled by [name_or_label])
    - Prefix for [my_object#|] is [""] (handled by [method_call])

* Changelog entry for #1363

Fixes #1358
  • Loading branch information
voodoos authored Aug 26, 2024
1 parent 1509ff4 commit 51e16ea
Show file tree
Hide file tree
Showing 3 changed files with 72 additions and 3 deletions.
1 change: 1 addition & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
## Fixes

- Fix fd leak in running external processes for preprocessing (#1349)
- Fix prefix parsing for completion of object methods (#1363, fixes #1358)

# 1.19.0

Expand Down
18 changes: 15 additions & 3 deletions ocaml-lsp-server/src/prefix_parser.ml
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,15 @@ include struct
])
;;

(* When completing module paths or record fields Merlin expects the
beginning of the path and the `.` to be part of the prefix. But when
accessing an object's methods, the prefix should not contain the `#`
sign. We use a sub-matching group to that effect.
- Prefix for [my_record.|] is ["my_record."] (handled by [name_or_label])
- Prefix for [my_object#|] is [""] (handled by [method_call]) *)
let method_call = compile (seq [ char '#'; Re.group (rep name_char); stop ])

(** matches let%lwt and let* style expressions. See
here:https://v2.ocaml.org/manual/bindingops.html *)
let monadic_bind =
Expand All @@ -42,8 +51,11 @@ let parse ~pos ~len text =
(*Attempt to match each of our possible prefix types, the order is important
because there is some overlap between the regexs*)
let matched =
List.find_map [ name_or_label; monadic_bind; infix_operator ] ~f:(fun regex ->
Re.exec_opt ~pos ~len regex text)
List.find_map
[ name_or_label; method_call; monadic_bind; infix_operator ]
~f:(fun regex -> Re.exec_opt ~pos ~len regex text)
in
matched |> Option.map ~f:(fun x -> Re.Group.get x 0)
matched
|> Option.map ~f:(fun x ->
if Re.Group.test x 1 then Re.Group.get x 1 else Re.Group.get x 0)
;;
56 changes: 56 additions & 0 deletions ocaml-lsp-server/test/e2e-new/completion.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1243,3 +1243,59 @@ let foo param1 =
}
............. |}]
;;
(* Test case was taken from issue #1358 *)
let%expect_test "completion for object methods" =
let source = {ocaml|let f (x : < a_method : 'a >) = x#|ocaml} in
let position = Position.create ~line:0 ~character:34 in
print_completions ~limit:3 source position;
[%expect
{|
Completions:
{
"kind": 14,
"label": "in",
"textEdit": {
"newText": "in",
"range": {
"end": { "character": 34, "line": 0 },
"start": { "character": 34, "line": 0 }
}
}
}
{
"detail": "'a",
"kind": 2,
"label": "a_method",
"sortText": "0000",
"textEdit": {
"newText": "a_method",
"range": {
"end": { "character": 34, "line": 0 },
"start": { "character": 34, "line": 0 }
}
}
} |}]
;;
let%expect_test "completion for object methods" =
let source = {ocaml|let f (x : < a_method : 'a; ab_m : 'b >) = x#ab|ocaml} in
let position = Position.create ~line:0 ~character:49 in
print_completions ~limit:3 source position;
[%expect
{|
Completions:
{
"detail": "'b",
"kind": 2,
"label": "ab_m",
"sortText": "0000",
"textEdit": {
"newText": "ab_m",
"range": {
"end": { "character": 49, "line": 0 },
"start": { "character": 47, "line": 0 }
}
}
} |}]
;;

0 comments on commit 51e16ea

Please sign in to comment.