Skip to content

Commit

Permalink
Added support for whitespace in completion
Browse files Browse the repository at this point in the history
The solution here is to change all whitespace to spaces for ease of regex matching(all whitespace is equivelent semantically) and then remove all spaces from the prefix that's passed to merlin.
  • Loading branch information
faldor20 committed Sep 18, 2023
1 parent 96376d1 commit 9bb112a
Show file tree
Hide file tree
Showing 6 changed files with 248 additions and 21 deletions.
22 changes: 18 additions & 4 deletions ocaml-lsp-server/bench/ocaml_lsp_bench.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,16 +5,30 @@ open Ocaml_lsp_server.Testing
let () =
let document =
"let mem = ListLabels.mem\n\nlet _ = mem ~se" |> Merlin_kernel.Msource.make
in
let long_document =
"
arosietnaorisetnoarisent
arsotienarositen
arsotinarsotienarst
ast. rienrst .rst
!@#&984@#$ <><|||>>
aoris noarisetnaoiresnt aorisent aoierns
let b a= 5234 n oienar. rsoien . iri i... r
let mem = ListLabels.mem\n\nlet _ = mem ~se" |> Merlin_kernel.Msource.make
in

let position = `Logical (3, 15) in
Command_unix.run
Command_unix.run
(Bench.make_command
[ Bench.Test.create ~name:"non-regex" (fun _ ->
[ Bench.Test.create ~name:"regex" (fun _ ->
Compl.prefix_of_position ~short_path:false document position
|> ignore)
; Bench.Test.create ~name:"regex" (fun _ ->
Compl.prefix_of_position_regex ~short_path:false document position
; Bench.Test.create ~name:"parser" (fun _ ->
Compl.prefix_of_position_parser ~short_path:false document position
|> ignore)
; Bench.Test.create ~name:"regex_long" (fun _ ->
Compl.prefix_of_position ~short_path:false long_document position
|> ignore)
; Bench.Test.create ~name:"old" (fun _ ->
Compl.prefix_of_position_old ~short_path:false document position
Expand Down
20 changes: 17 additions & 3 deletions ocaml-lsp-server/bench/run_bench.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,16 +5,30 @@ open Ocaml_lsp_server.Testing
let () =
let document =
"let mem = ListLabels.mem\n\nlet _ = mem ~se" |> Merlin_kernel.Msource.make
in
let long_document =
"
arosietnaorisetnoarisent
arsotienarositen
arsotinarsotienarst
ast. rienrst .rst
!@#&984@#$ <><|||>>
aoris noarisetnaoiresnt aorisent aoierns
let b a= 5234 n oienar. rsoien . iri i... r
let mem = ListLabels.mem\n\nlet _ = mem ~se" |> Merlin_kernel.Msource.make
in

let position = `Logical (3, 15) in
Command.summary
(Bench.make_command
[ Bench.Test.create ~name:"non-regex" (fun _ ->
[ Bench.Test.create ~name:"regex" (fun _ ->
Compl.prefix_of_position ~short_path:false document position
|> ignore)
; Bench.Test.create ~name:"regex" (fun _ ->
Compl.prefix_of_position_regex ~short_path:false document position
; Bench.Test.create ~name:"parser" (fun _ ->
Compl.prefix_of_position_parser ~short_path:false document position
|> ignore)
; Bench.Test.create ~name:"regex_long" (fun _ ->
Compl.prefix_of_position ~short_path:false long_document position
|> ignore)
; Bench.Test.create ~name:"old" (fun _ ->
Compl.prefix_of_position_old ~short_path:false document position
Expand Down
21 changes: 12 additions & 9 deletions ocaml-lsp-server/src/compl.ml
Original file line number Diff line number Diff line change
Expand Up @@ -138,13 +138,12 @@ let prefix_of_position_parser ~short_path source position =
let pos = end_of_prefix - len + 1 in
let reconstructed_prefix = String.sub text ~pos ~len in
if short_path then
match String.split_on_char reconstructed_prefix ~sep:'.'|> List.last with
| Some (s) -> s
match String.split_on_char reconstructed_prefix ~sep:'.' |> List.last with
| Some s -> s
| None -> reconstructed_prefix
else reconstructed_prefix

let prefix_of_position ~short_path source position =

let open Prefix_parser in
match Msource.text source with
| "" -> ""
Expand All @@ -159,21 +158,25 @@ let prefix_of_position ~short_path source position =
parser the fact that whitespace doesn't really matter in certain cases
like "List. map"*)
let pos =
text
|> String.rfindi ~from:end_of_prefix ~f:(( = ) '\n')
|> Option.value ~default:0
(* text |> String.rfindi ~from:end_of_prefix ~f:(( = ) '\n') |>
Option.value ~default:0 *)

(*clamp the length of a line to process at 500 chars*)
max 0 (end_of_prefix - 500)
in
String.sub text ~pos ~len:(end_of_prefix + 1 - pos)
|> String.map ~f:(fun x -> if x = '\n'||x='\t' then ' ' else x)
in

(*Printf.printf "trying to parse text `%s`\n"
(prefix_text|>String.of_list);*)
let reconstructed_prefix =
try_parse_regex prefix_text |> Option.value ~default:""
try_parse_regex prefix_text |> Option.value ~default:"" |>String.filter_map ~f:(fun x-> if x=' ' then None else Some x )

in
if short_path then
match String.split_on_char reconstructed_prefix ~sep:'.'|> List.last with
| Some (s) -> s
match String.split_on_char reconstructed_prefix ~sep:'.' |> List.last with
| Some s -> s
| None -> reconstructed_prefix
else reconstructed_prefix

Expand Down
9 changes: 5 additions & 4 deletions ocaml-lsp-server/src/prefix_parser.ml
Original file line number Diff line number Diff line change
Expand Up @@ -86,14 +86,16 @@ let rec try_parse parsers str =
| Some l -> Some l
| None -> str |> try_parse tail)
| [] -> None

open Re

(*Regex based parser*)

let name_or_label_regex =
Re.compile @@ Re.Posix.re {|([~?`])?([a-zA-Z0-9_']|[a-zA-Z0-9_']\.)+$|}
Re.compile @@ Re.
Posix. re {|([~?`])?([a-zA-Z0-9_']|[a-zA-Z0-9_']\.( )*)+$|}

let infixRegex =Re.compile @@ Re.Posix.re {|[~?:!$&*+\-\/=><@^|%<.#]+$|}
let infixRegex = Re.compile @@ Re.Posix.re {|[~?:!$&*+\-\/=><@^|%<.#]+$|}

open Import

Expand All @@ -107,9 +109,8 @@ module Option = struct
end

let try_parse_regex text =

let matched =
Re.exec_opt name_or_label_regex text
|> Option.none_bind (fun () -> Re.exec_opt infixRegex text)
in
matched |>Option.map ~f:(fun x->Group.get x 0)
matched |> Option.map ~f:(fun x -> Group.get x 0)
183 changes: 182 additions & 1 deletion ocaml-lsp-server/test/e2e/__tests__/textDocument-completion.test.ts
Original file line number Diff line number Diff line change
Expand Up @@ -270,6 +270,187 @@ describe_opt("textDocument/completion", () => {
]
`);
});


it("can start completion in dot chain with newline", async () => {
openDocument(outdent`
[1;2] |> List.
ma
`);

let items = await queryCompletion(Types.Position.create(1, 2));
expect(items).toMatchInlineSnapshot(`
Array [
Object {
"label": "map",
"textEdit": Object {
"newText": "map",
"range": Object {
"end": Object {
"character": 2,
"line": 1,
},
"start": Object {
"character": 0,
"line": 1,
},
},
},
},
Object {
"label": "mapi",
"textEdit": Object {
"newText": "mapi",
"range": Object {
"end": Object {
"character": 2,
"line": 1,
},
"start": Object {
"character": 0,
"line": 1,
},
},
},
},
Object {
"label": "map2",
"textEdit": Object {
"newText": "map2",
"range": Object {
"end": Object {
"character": 2,
"line": 1,
},
"start": Object {
"character": 0,
"line": 1,
},
},
},
},
]
`);
});
it("can start completion in dot chain with tab", async () => {
openDocument(outdent`
[1;2] |> List. ma
`);

let items = await queryCompletion(Types.Position.create(0, 17));
expect(items).toMatchInlineSnapshot(`
Array [
Object {
"label": "map",
"textEdit": Object {
"newText": "map",
"range": Object {
"end": Object {
"character": 17,
"line": 0,
},
"start": Object {
"character": 15,
"line": 0,
},
},
},
},
Object {
"label": "mapi",
"textEdit": Object {
"newText": "mapi",
"range": Object {
"end": Object {
"character": 17,
"line": 0,
},
"start": Object {
"character": 15,
"line": 0,
},
},
},
},
Object {
"label": "map2",
"textEdit": Object {
"newText": "map2",
"range": Object {
"end": Object {
"character": 17,
"line": 0,
},
"start": Object {
"character": 15,
"line": 0,
},
},
},
},
]
`);
});
it("can start completion in dot chain with space", async () => {
openDocument(outdent`
[1;2] |> List. ma
`);

let items = await queryCompletion(Types.Position.create(0, 17));
expect(items).toMatchInlineSnapshot(`
Array [
Object {
"label": "map",
"textEdit": Object {
"newText": "map",
"range": Object {
"end": Object {
"character": 17,
"line": 0,
},
"start": Object {
"character": 15,
"line": 0,
},
},
},
},
Object {
"label": "mapi",
"textEdit": Object {
"newText": "mapi",
"range": Object {
"end": Object {
"character": 17,
"line": 0,
},
"start": Object {
"character": 15,
"line": 0,
},
},
},
},
Object {
"label": "map2",
"textEdit": Object {
"newText": "map2",
"range": Object {
"end": Object {
"character": 17,
"line": 0,
},
"start": Object {
"character": 15,
"line": 0,
},
},
},
},
]
`);
});

it("can start completion after dereference", async () => {
openDocument(outdent`
let apple=ref 10 in
Expand Down Expand Up @@ -299,7 +480,7 @@ let apple=ref 10 in
`);

});
it("can complete symbol passed as a named argument", async () => {
it("can complete symbol passed as a named argument", async () => {
openDocument(outdent`
let g ~f = f 0 in
g ~f:ig
Expand Down
14 changes: 14 additions & 0 deletions ocaml-lsp-server/test/position_prefix_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -101,3 +101,17 @@ let%expect_test "short path prefix" =
print_endline prefix;
[%expect "ma"]

let%expect_test "Space in dot chain" =
let document = "[1;2] |> Core. List. ma\n" |> Testing.Merlin_kernel.Msource.make in
let position = `Logical (1, 23) in
let prefix = Compl.prefix_of_position ~short_path:false document position in
print_endline prefix;
[%expect "Core.List.ma"]

let%expect_test "newline in dot chain" =
let document = "[1;2] |> Core.\nList.\nma\n" |> Testing.Merlin_kernel.Msource.make in
let position = `Logical (3, 2) in
let prefix = Compl.prefix_of_position ~short_path:false document position in
print_endline prefix;
[%expect "Core.List.ma"]

0 comments on commit 9bb112a

Please sign in to comment.