Skip to content

Commit

Permalink
Add back previously removed functions
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Apr 6, 2019
1 parent 85f9d2f commit 42c7f88
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 0 deletions.
6 changes: 6 additions & 0 deletions lib/core.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1177,6 +1177,7 @@ let witness t =
| End_of_str -> "" in
witness (handle_case false t)

type 'a seq = 'a Seq.t
module Seq = Rseq
module List = Rlist
module Group = Group
Expand All @@ -1189,6 +1190,11 @@ let matches_gen = Gen.matches
let split_gen = Gen.split
let split_full_gen = Gen.split_full

let all_seq = Seq.all
let matches_seq = Seq.matches
let split_seq = Seq.split
let split_full_seq = Seq.split_full


type substrings = Group.t

Expand Down
14 changes: 14 additions & 0 deletions lib/core.mli
Original file line number Diff line number Diff line change
Expand Up @@ -125,6 +125,8 @@ type split_token =
| `Delim of Group.t (** Delimiter *)
]

type 'a seq = 'a Seq.t

module Seq : sig
val all :
?pos:int -> (** Default: 0 *)
Expand Down Expand Up @@ -162,13 +164,19 @@ type 'a gen = unit -> 'a option
val all_gen : ?pos:int -> ?len:int -> re -> string -> Group.t gen
[@@ocaml.deprecated "Use Seq.all"]

val all_seq : ?pos:int -> ?len:int -> re -> string -> Group.t seq
[@@ocaml.deprecated "Use Seq.all"]

val matches : ?pos:int -> ?len:int -> re -> string -> string list
(** Same as {!all}, but extracts the matched substring rather than returning
the whole group. This basically iterates over matched strings *)

val matches_gen : ?pos:int -> ?len:int -> re -> string -> string gen
[@@ocaml.deprecated "Use Seq.matches"]

val matches_seq : ?pos:int -> ?len:int -> re -> string -> string seq
[@@ocaml.deprecated "Use Seq.matches"]

val split : ?pos:int -> ?len:int -> re -> string -> string list
(** [split re s] splits [s] into chunks separated by [re]. It yields the chunks
themselves, not the separator. For instance this can be used with a
Expand All @@ -177,6 +185,9 @@ val split : ?pos:int -> ?len:int -> re -> string -> string list
val split_gen : ?pos:int -> ?len:int -> re -> string -> string gen
[@@ocaml.deprecated "Use Seq.split"]

val split_seq : ?pos:int -> ?len:int -> re -> string -> string seq
[@@ocaml.deprecated "Use Seq.split"]

val split_full : ?pos:int -> ?len:int -> re -> string -> split_token list
(** [split re s] splits [s] into chunks separated by [re]. It yields the chunks
along with the separators. For instance this can be used with a
Expand All @@ -185,6 +196,9 @@ val split_full : ?pos:int -> ?len:int -> re -> string -> split_token list
val split_full_gen : ?pos:int -> ?len:int -> re -> string -> split_token gen
[@@ocaml.deprecated "Use Seq.split_full"]

val split_full_seq : ?pos:int -> ?len:int -> re -> string -> split_token seq
[@@ocaml.deprecated "Use Seq.split_full"]

val replace :
?pos:int -> (** Default: 0 *)
?len:int ->
Expand Down

0 comments on commit 42c7f88

Please sign in to comment.