-
Notifications
You must be signed in to change notification settings - Fork 121
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
* Tests passing * Added support for whitespace in completion 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. Co-authored-by: faldor20 <eli.jambu@gmail.com> Co-authored-by: faldor20 <eli.jambu@yahoo.com>
- Loading branch information
1 parent
3b3b9bc
commit 73bf594
Showing
21 changed files
with
1,564 additions
and
814 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
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
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,98 @@ | ||
let document = | ||
"let mem = ListLabels.mem\n\nlet _ = mem ~se" |> Merlin_kernel.Msource.make | ||
|
||
let long_document_text = | ||
{|let prefix_of_position ~short_path source position = | ||
let open Prefix_parser in | ||
match Msource.text source with | ||
| "" -> "" | ||
| text -> | ||
let end_of_prefix = | ||
let (`Offset index) = Msource.get_offset source position in | ||
min (String.length text - 1) (index - 1) | ||
in | ||
let prefix_text = | ||
let pos = | ||
(*clamp the length of a line to process at 500 chars, this is just a | ||
reasonable limit for regex performance*) | ||
max 0 (end_of_prefix - 500) | ||
in | ||
String.sub text ~pos ~len:(end_of_prefix + 1 - pos) | ||
(*because all whitespace is semantically the same we convert it all to | ||
spaces for easier regex matching*) | ||
|> String.rev_map ~f:(fun x -> if x = '\n' || x = '\t' then ' ' else x) | ||
in | ||
|
||
let reconstructed_prefix = | ||
try_parse_with_regex prefix_text | ||
|> Option.value ~default:"" | ||
|> String.rev_filter ~f:(fun x -> x <> ' ') | ||
in | ||
|
||
if short_path then | ||
match String.split_on_char reconstructed_prefix ~sep:'.' |> List.last with | ||
| Some s -> s | ||
| None -> reconstructed_prefix | ||
else reconstructed_prefix | ||
|
||
let suffix_of_position source position = | ||
match Msource.text source with | ||
| "" -> "" | ||
| text -> | ||
let (`Offset index) = Msource.get_offset source position in | ||
let len = String.length text in | ||
if index >= len then "" | ||
else | ||
let from = index in | ||
let len = | ||
let ident_char = function | ||
| 'a' .. 'z' | 'A' .. 'Z' | '0' .. '9' | '\'' | '_' -> true | ||
| _ -> false | ||
in | ||
let until = | ||
String.findi ~from text ~f:(fun c -> not (ident_char c)) | ||
|> Option.value ~default:len | ||
in | ||
until - from | ||
in | ||
String.sub text ~pos:from ~len | ||
|
||
let reconstruct_ident source position = | ||
let prefix = prefix_of_position ~short_path:false source position in | ||
let suffix = suffix_of_position source position in | ||
let ident = prefix ^ suffix in | ||
Option.some_if (ident <> "") ident | ||
|
||
let range_prefix (lsp_position : Position.t) prefix : Range.t = | ||
let start = | ||
let len = String.length prefix in | ||
let character = lsp_position.character - len in | ||
{ lsp_position with character } | ||
in | ||
{ Range.start; end_ = lsp_position } | ||
|
||
let sortText_of_index idx = Printf.sprintf "%04d" idx | ||
|
||
module Complete_by_prefix = struct | ||
let completionItem_of_completion_entry idx | ||
(entry : Query_protocol.Compl.entry) ~compl_params ~range ~deprecated = | ||
let kind = completion_kind entry.kind in | ||
let textEdit = `TextEdit { TextEdit.range; newText = entry.name } in | ||
CompletionItem.create | ||
~label:entry.name | ||
?kind | ||
~detail:entry.desc | ||
?deprecated:(Option.some_if deprecated entry.deprecated) | ||
(* Without this field the client is not forced to respect the order | ||
provided by merlin. *) | ||
~sortText:(sortText_of_index idx) | ||
?data:compl_params | ||
~textEdit | ||
() | ||
|
||
let dispatch_cmd ~prefix position pipeline = | ||
let complete = | ||
Query_protocol.Complete_prefix (prefix, position, [], false, true) | ||
in | ||
Query_commands.dispatch pipeline comp | ||
|} |
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,13 @@ | ||
(executables | ||
(names ocaml_lsp_bench) | ||
(enabled_if | ||
(= %{profile} bench)) | ||
(libraries | ||
ocaml_lsp_server | ||
core_unix.command_unix | ||
merlin-lib.kernel | ||
base | ||
core | ||
core_bench) | ||
(preprocess | ||
(pps ppx_bench))) |
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,27 @@ | ||
open Ocaml_lsp_server | ||
open Core | ||
open Core_bench | ||
|
||
let () = | ||
let open Documents in | ||
let long_document = long_document_text |> Merlin_kernel.Msource.make in | ||
let position = `Logical (3, 15) in | ||
let long_position = `Logical (92, 41) in | ||
Command_unix.run | ||
(Bench.make_command | ||
[ Bench.Test.create ~name:"get_prefix" (fun _ -> | ||
Testing.Compl.prefix_of_position | ||
~short_path:false | ||
document | ||
position | ||
|> ignore) | ||
; Bench.Test.create ~name:"get_prefix_long" (fun _ -> | ||
Testing.Compl.prefix_of_position | ||
~short_path:false | ||
long_document | ||
long_position | ||
|> ignore) | ||
; Bench.Test.create ~name:"get_offset_long" (fun _ -> | ||
Merlin_kernel.Msource.get_offset long_document long_position | ||
|> ignore) | ||
]) |
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
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
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
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
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
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,50 @@ | ||
open Import | ||
|
||
include struct | ||
open Re | ||
|
||
(* Regex based parser *) | ||
let white_space = set "\n\t " | ||
|
||
let name_char = | ||
Re.alt [ rg 'a' 'z'; rg 'A' 'Z'; rg '0' '9'; char '_'; char '\'' ] | ||
|
||
let name_with_dot = | ||
Re.seq [ name_char; white_space |> rep; char '.'; white_space |> rep ] | ||
|
||
let core_operator_str = {|$&*+-/=>@^||} | ||
|
||
let operator = core_operator_str ^ {|~!?%<:.|} | ||
|
||
let infix = set (operator ^ "#") | ||
|
||
let name_or_label = | ||
compile | ||
(seq | ||
[ alt [ set "~?``"; str "let%"; str "and%" ] |> opt | ||
; alt [ name_char; name_with_dot ] |> rep1 | ||
; stop | ||
]) | ||
|
||
(** matches let%lwt and let* style expressions. See | ||
here:https://v2.ocaml.org/manual/bindingops.html *) | ||
let monadic_bind = | ||
compile | ||
(seq | ||
[ alt [ str "let"; str "and" ] | ||
; alt [ infix |> rep1; seq [ name_char |> rep1; char '%' ] ] | ||
; stop | ||
]) | ||
|
||
let infix_operator = compile (seq [ infix |> rep1; stop ]) | ||
end | ||
|
||
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) | ||
in | ||
matched |> Option.map ~f:(fun x -> Re.Group.get x 0) |
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,4 @@ | ||
(** Tries the parse the incoming string for a prefix. The string should be the | ||
source code ending at the prefix position. pos and len set the range for the | ||
regex to operate on *) | ||
val parse : pos:int -> len:int -> string -> string option |
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,5 @@ | ||
(**WARNING: This is for internal use in testing only *) | ||
|
||
module Compl = Compl | ||
module Merlin_kernel = Merlin_kernel | ||
module Prefix_parser = Prefix_parser |
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
Oops, something went wrong.