Skip to content

Commit

Permalink
Add Bytes.{starts,ends}_with
Browse files Browse the repository at this point in the history
  • Loading branch information
dra27 committed Mar 1, 2021
1 parent 3e7d6e0 commit 6bd29a0
Show file tree
Hide file tree
Showing 4 changed files with 49 additions and 0 deletions.
21 changes: 21 additions & 0 deletions stdlib/bytes.ml
Original file line number Diff line number Diff line change
Expand Up @@ -236,6 +236,27 @@ let apply1 f s =
let capitalize_ascii s = apply1 Char.uppercase_ascii s
let uncapitalize_ascii s = apply1 Char.lowercase_ascii s

(* duplicated in string.ml *)
let starts_with ~prefix s =
let len_s = length s
and len_pre = length prefix in
let rec aux i =
if i = len_pre then true
else if unsafe_get s i <> unsafe_get prefix i then false
else aux (i + 1)
in len_s >= len_pre && aux 0

(* duplicated in string.ml *)
let ends_with ~suffix s =
let len_s = length s
and len_suf = length suffix in
let diff = len_s - len_suf in
let rec aux i =
if i = len_suf then true
else if unsafe_get s (diff + i) <> unsafe_get suffix i then false
else aux (i + 1)
in diff >= 0 && aux 0

(* duplicated in string.ml *)
let rec index_rec s lim i c =
if i >= lim then raise Not_found else
Expand Down
13 changes: 13 additions & 0 deletions stdlib/bytes.mli
Original file line number Diff line number Diff line change
Expand Up @@ -323,6 +323,19 @@ val equal: t -> t -> bool
(** The equality function for byte sequences.
@since 4.03.0 (4.05.0 in BytesLabels) *)

val starts_with :
prefix (* comment thwarts tools/sync_stdlib_docs *) :bytes -> bytes -> bool
(** [starts_with ][~][prefix s] is [true] if and only if [s] starts with
[prefix].
@since 4.13.0 *)

val ends_with :
suffix (* comment thwarts tools/sync_stdlib_docs *) :bytes -> bytes -> bool
(** [ends_with suffix s] is [true] if and only if [s] ends with [suffix].
@since 4.13.0 *)

(** {1:unsafe Unsafe conversions (for advanced users)}
This section describes unsafe, low-level conversion functions
Expand Down
13 changes: 13 additions & 0 deletions stdlib/bytesLabels.mli
Original file line number Diff line number Diff line change
Expand Up @@ -323,6 +323,19 @@ val equal: t -> t -> bool
(** The equality function for byte sequences.
@since 4.03.0 (4.05.0 in BytesLabels) *)

val starts_with :
prefix (* comment thwarts tools/sync_stdlib_docs *) :bytes -> bytes -> bool
(** [starts_with ][~][prefix s] is [true] if and only if [s] starts with
[prefix].
@since 4.13.0 *)

val ends_with :
suffix (* comment thwarts tools/sync_stdlib_docs *) :bytes -> bytes -> bool
(** [ends_with suffix s] is [true] if and only if [s] ends with [suffix].
@since 4.13.0 *)

(** {1:unsafe Unsafe conversions (for advanced users)}
This section describes unsafe, low-level conversion functions
Expand Down
2 changes: 2 additions & 0 deletions stdlib/string.ml
Original file line number Diff line number Diff line change
Expand Up @@ -202,6 +202,7 @@ let capitalize_ascii s =
let uncapitalize_ascii s =
B.uncapitalize_ascii (bos s) |> bts

(* duplicated in bytes.ml *)
let starts_with ~prefix s =
let len_s = length s
and len_pre = length prefix in
Expand All @@ -211,6 +212,7 @@ let starts_with ~prefix s =
else aux (i + 1)
in len_s >= len_pre && aux 0

(* duplicated in bytes.ml *)
let ends_with ~suffix s =
let len_s = length s
and len_suf = length suffix in
Expand Down

0 comments on commit 6bd29a0

Please sign in to comment.