Skip to content

Commit

Permalink
Revert "move string functions to std"
Browse files Browse the repository at this point in the history
This reverts commit 77853db.
  • Loading branch information
3Rafal committed Jan 6, 2024
1 parent a87c025 commit 97c99ed
Show file tree
Hide file tree
Showing 2 changed files with 36 additions and 28 deletions.
38 changes: 36 additions & 2 deletions src/analysis/signature_help.ml
Original file line number Diff line number Diff line change
Expand Up @@ -155,6 +155,40 @@ let application_signature ~prefix = function
Some { result with active_param }
| _ -> None

module String = struct
include String
let rfindi =
let rec loop s ~f i =
if i < 0 then None
else if f (String.unsafe_get s i) then Some i
else loop s ~f (i - 1)
in
fun ?from s ~f ->
let from =
let len = String.length s in
match from with
| None -> len - 1
| Some i ->
if i > len - 1 then failwith "rfindi: invalid from"
else i
in
loop s ~f from

let rec check_prefix s ~prefix len i =
i = len || (s.[i] = prefix.[i] && check_prefix s ~prefix len (i + 1))

let lsplit2 s ~on =
match String.index_opt s on with
| None -> None
| Some i ->
Some (sub s ~pos:0 ~len:i, sub s ~pos:(i + 1) ~len:(length s - i - 1))

let is_prefix s ~prefix =
let len = length s in
let prefix_len = length prefix in
len >= prefix_len && check_prefix s ~prefix prefix_len 0
end

(** @see <https://ocaml.org/manual/lex.html> reference *)
let prefix_of_position ~short_path source position =
match Msource.text source with
Expand Down Expand Up @@ -216,8 +250,8 @@ let prefix_of_position ~short_path source position =
(* if we reconstructed [~f:ignore] or [?f:ignore], we should take only
[ignore], so: *)
if
String.is_prefixed reconstructed_prefix ~by:"~"
|| String.is_prefixed reconstructed_prefix ~by:"?"
String.is_prefix reconstructed_prefix ~prefix:"~"
|| String.is_prefix reconstructed_prefix ~prefix:"?"
then
match String.lsplit2 reconstructed_prefix ~on:':' with
| Some (_, s) -> s
Expand Down
26 changes: 0 additions & 26 deletions src/utils/std.ml
Original file line number Diff line number Diff line change
Expand Up @@ -393,32 +393,6 @@ module String = struct
(* Drop characters from beginning of string *)
let drop n s = sub s ~pos:n ~len:(length s - n)

let rfindi =
let rec loop s ~f i =
if i < 0 then None
else if f (String.unsafe_get s i) then Some i
else loop s ~f (i - 1)
in
fun ?from s ~f ->
let from =
let len = String.length s in
match from with
| None -> len - 1
| Some i ->
if i > len - 1 then failwith "rfindi: invalid from"
else i
in
loop s ~f from

let rec check_prefix s ~prefix len i =
i = len || (s.[i] = prefix.[i] && check_prefix s ~prefix len (i + 1))

let lsplit2 s ~on =
match String.index_opt s on with
| None -> None
| Some i ->
Some (sub s ~pos:0 ~len:i, sub s ~pos:(i + 1) ~len:(length s - i - 1))

module Set = struct
include MoreLabels.Set.Make (struct type t = string let compare = compare end)
let of_list l = List.fold_left ~f:(fun s elt -> add elt s) l ~init:empty
Expand Down

0 comments on commit 97c99ed

Please sign in to comment.