Skip to content

Commit

Permalink
feature(pcre): get_named_substring_opt
Browse files Browse the repository at this point in the history
  • Loading branch information
rgrinberg committed Oct 12, 2024
1 parent 83d0f60 commit 447d4d3
Show file tree
Hide file tree
Showing 3 changed files with 24 additions and 6 deletions.
6 changes: 6 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,9 @@
Unreleased
----------

* Introduce [Re.Pcre.get_named_substring_opt]. A non raising version of
[Re.Pcre.get_named_substring] (#525)

1.13.1 (30-Sep-2024)
--------------------

Expand Down
18 changes: 13 additions & 5 deletions lib/pcre.ml
Original file line number Diff line number Diff line change
Expand Up @@ -36,15 +36,15 @@ let re ?(flags = []) pat =
let regexp ?flags pat = Re.compile (re ?flags pat)
let extract ~rex s = Re.Group.all (Re.exec rex s)
let exec ~rex ?pos s = Re.exec rex ?pos s
let get_substring s i = Re.Group.get s i
let names rex = Re.group_names rex |> List.map fst |> Array.of_list

let get_named_substring rex name s =
let get_named_substring_opt rex name s =
let rec loop = function
| [] -> raise Not_found
| [] -> None
| (n, i) :: rem when n = name ->
(try get_substring s i with
| Not_found -> loop rem)
(match Re.Group.get_opt s i with
| None -> loop rem
| Some _ as s -> s)
| _ :: rem -> loop rem
in
loop (Re.group_names rex)
Expand Down Expand Up @@ -169,3 +169,11 @@ let full_split ?(max = 0) ~rex s =
;;

type substrings = Group.t

let get_substring s i = Re.Group.get s i

let get_named_substring rex name s =
match get_named_substring_opt rex name s with
| None -> raise Not_found
| Some s -> s
;;
6 changes: 5 additions & 1 deletion lib/pcre.mli
Original file line number Diff line number Diff line change
Expand Up @@ -39,9 +39,13 @@ val get_substring : groups -> int -> string
(** Return the names of named groups. *)
val names : regexp -> string array

(** Return the first matched named group, or raise [Not_found]. *)
(** Return the first matched named group, or raise [Not_found]. Prefer to use
the non-raising version [get_named_substring_opt] *)
val get_named_substring : regexp -> string -> groups -> string

(** Return the first matched named group, or raise [Not_found]. *)
val get_named_substring_opt : regexp -> string -> groups -> string option

(** Equivalent to {!Core.Group.offset}. *)
val get_substring_ofs : groups -> int -> int * int

Expand Down

0 comments on commit 447d4d3

Please sign in to comment.