Skip to content

Commit

Permalink
feature: add some re parser that don't raise (#542)
Browse files Browse the repository at this point in the history
  • Loading branch information
rgrinberg authored Oct 25, 2024
1 parent de9bd96 commit 9d58581
Show file tree
Hide file tree
Showing 9 changed files with 62 additions and 0 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,9 @@ Unreleased
* Introduce [Re.Pcre.get_named_substring_opt]. A non raising version of
[Re.Pcre.get_named_substring] (#525)

* Introduce parsing functions in `Re.{Perl,Pcre,Emacs,Glob}` that return a
result instead of raising. (#542)

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

Expand Down
7 changes: 7 additions & 0 deletions lib/emacs.ml
Original file line number Diff line number Diff line change
Expand Up @@ -121,5 +121,12 @@ let re ?(case = true) s =
if case then r else Re.no_case r
;;

let re_result ?case s =
match re ?case s with
| s -> Ok s
| exception Not_supported -> Error `Not_supported
| exception Parse_error -> Error `Parse_error
;;

let compile = Re.compile
let compile_pat ?(case = true) s = compile (re ~case s)
2 changes: 2 additions & 0 deletions lib/emacs.mli
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,8 @@ exception Not_supported
(** Parsing of an Emacs-style regular expression *)
val re : ?case:bool -> string -> Core.t

val re_result : ?case:bool -> string -> (Core.t, [ `Not_supported | `Parse_error ]) result

(** Regular expression compilation *)
val compile : Core.t -> Core.re

Expand Down
16 changes: 16 additions & 0 deletions lib/glob.ml
Original file line number Diff line number Diff line change
Expand Up @@ -316,6 +316,22 @@ let glob
if expand_braces then Re.alt (List.map to_re (explode s)) else to_re s
;;

let glob_result
?anchored
?pathname
?match_backslashes
?period
?expand_braces
?double_asterisk
s
=
match
glob ?anchored ?pathname ?match_backslashes ?period ?expand_braces ?double_asterisk s
with
| re -> Ok re
| exception Parse_error -> Error `Parse_error
;;

let glob' ?anchored period s = glob ?anchored ~period s
let globx ?anchored s = glob ?anchored ~expand_braces:true s
let globx' ?anchored period s = glob ?anchored ~expand_braces:true ~period s
10 changes: 10 additions & 0 deletions lib/glob.mli
Original file line number Diff line number Diff line change
Expand Up @@ -68,6 +68,16 @@ val glob
-> string
-> Core.t

val glob_result
: ?anchored:bool
-> ?pathname:bool
-> ?match_backslashes:bool
-> ?period:bool
-> ?expand_braces:bool
-> ?double_asterisk:bool
-> string
-> (Core.t, [ `Parse_error ]) result

(** Same, but allows to choose whether dots at the beginning of a
file name need to be explicitly matched (true) or not (false)
Expand Down
7 changes: 7 additions & 0 deletions lib/pcre.ml
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,13 @@ let re ?(flags = []) pat =
Perl.re ~opts pat
;;

let re_result ?flags s =
match re ?flags s with
| s -> Ok s
| exception Not_supported -> Error `Not_supported
| exception Parse_error -> Error `Parse_error
;;

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
Expand Down
5 changes: 5 additions & 0 deletions lib/pcre.mli
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,11 @@ type split_result =
(** [re ~flags s] creates the regexp [s] using the pcre syntax. *)
val re : ?flags:flag list -> string -> Core.t

val re_result
: ?flags:flag list
-> string
-> (Core.t, [ `Not_supported | `Parse_error ]) result

(** [re ~flags s] compiles the regexp [s] using the pcre syntax. *)
val regexp : ?flags:flag list -> string -> regexp

Expand Down
7 changes: 7 additions & 0 deletions lib/perl.ml
Original file line number Diff line number Diff line change
Expand Up @@ -338,3 +338,10 @@ let re ?(opts = []) s =

let compile = Re.compile
let compile_pat ?(opts = []) s = compile (re ~opts s)

let re_result ?opts s =
match re ?opts s with
| s -> Ok s
| exception Not_supported -> Error `Not_supported
| exception Parse_error -> Error `Parse_error
;;
5 changes: 5 additions & 0 deletions lib/perl.mli
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,11 @@ type opt =
(** Parsing of a Perl-style regular expression *)
val re : ?opts:opt list -> string -> Core.t

val re_result
: ?opts:opt list
-> string
-> (Core.t, [ `Not_supported | `Parse_error ]) result

(** (Same as [Re.compile]) *)
val compile : Core.t -> Core.re

Expand Down

0 comments on commit 9d58581

Please sign in to comment.