Skip to content

Commit

Permalink
_
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed Nov 26, 2023
1 parent 55e80af commit f1edd2c
Show file tree
Hide file tree
Showing 4 changed files with 6 additions and 8 deletions.
3 changes: 1 addition & 2 deletions ocaml-lsp-server/bench/documents.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,6 @@ let document =

let long_document_text =
{|let prefix_of_position ~short_path source position =
let open Prefix_parser in
match Msource.text source with
| "" -> ""
| text ->
Expand All @@ -24,7 +23,7 @@ let long_document_text =
in

let reconstructed_prefix =
try_parse_with_regex prefix_text
Prefix_parser.parse prefix_text
|> Option.value ~default:""
|> String.rev_filter ~f:(fun x -> x <> ' ')
in
Expand Down
7 changes: 3 additions & 4 deletions ocaml-lsp-server/src/compl.ml
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,6 @@ let completion_kind kind : CompletionItemKind.t option =
| `Type -> Some TypeParameter

let prefix_of_position ~short_path source position =
let open Prefix_parser in
match Msource.text source with
| "" -> ""
| text ->
Expand All @@ -42,10 +41,10 @@ let prefix_of_position ~short_path source position =
in

let reconstructed_prefix =
try_parse_with_regex ~pos ~len:(end_of_prefix + 1 - pos) text
Prefix_parser.parse ~pos ~len:(end_of_prefix + 1 - pos) text
|> Option.value ~default:""
(*We remove the whitespace because merlin expects no whitespace and it's
semantically meaningless*)
(* We remove the whitespace because merlin expects no whitespace and it's
semantically meaningless *)
|> String.filter (fun x -> not (x = ' ' || x = '\n' || x = '\t'))
in

Expand Down
2 changes: 1 addition & 1 deletion ocaml-lsp-server/src/prefix_parser.ml
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ include struct
let infix_operator = compile (seq [ infix |> rep1; stop ])
end

let try_parse_with_regex ~pos ~len text =
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 =
Expand Down
2 changes: 1 addition & 1 deletion ocaml-lsp-server/src/prefix_parser.mli
Original file line number Diff line number Diff line change
@@ -1,4 +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 try_parse_with_regex : pos:int -> len:int -> string -> string option
val parse : pos:int -> len:int -> string -> string option

0 comments on commit f1edd2c

Please sign in to comment.