Skip to content

Commit

Permalink
Fix stackoverflow in Re_str.split
Browse files Browse the repository at this point in the history
Make sure that searching in a string always does progress. Also add
general + regression split tests.

Fix #90
  • Loading branch information
rgrinberg committed Aug 14, 2016
1 parent 8e272b4 commit c5531af
Show file tree
Hide file tree
Showing 2 changed files with 39 additions and 3 deletions.
12 changes: 9 additions & 3 deletions lib/re_str.ml
Expand Up @@ -235,14 +235,20 @@ let global_replace expr repl text =
and replace_first expr repl text =
substitute_first expr (replacement_text repl) text

let search_forward_progress re s p =
let pos = search_forward re s p in
if match_end () > p then pos
else if p < String.length s then search_forward re s (p + 1)
else raise Not_found

let bounded_split expr text num =
let start =
if string_match expr text 0 then match_end() else 0 in
let rec split start n =
if start >= String.length text then [] else
if n = 1 then [string_after text start] else
try
let pos = search_forward expr text start in
let pos = search_forward_progress expr text start in
String.sub text start (pos-start) :: split (match_end()) (n-1)
with Not_found ->
[string_after text start] in
Expand All @@ -255,7 +261,7 @@ let bounded_split_delim expr text num =
if start > String.length text then [] else
if n = 1 then [string_after text start] else
try
let pos = search_forward expr text start in
let pos = search_forward_progress expr text start in
String.sub text start (pos-start) :: split (match_end()) (n-1)
with Not_found ->
[string_after text start] in
Expand All @@ -270,7 +276,7 @@ let bounded_full_split expr text num =
if start >= String.length text then [] else
if n = 1 then [Text(string_after text start)] else
try
let pos = search_forward expr text start in
let pos = search_forward_progress expr text start in
let s = matched_string text in
if pos > start then
Text(String.sub text start (pos-start)) ::
Expand Down
30 changes: 30 additions & 0 deletions lib_test/test_str.ml
@@ -1,4 +1,5 @@
open Fort_unit
open OUnit2

module type Str_intf = module type of Str

Expand Down Expand Up @@ -27,6 +28,10 @@ end
module T_str = Test_matches(Str)
module T_re = Test_matches(Re_str)

let split_convert = List.map (function
| Str.Text s -> Re_str.Text s
| Str.Delim s -> Re_str.Delim s)

let eq_match ?pos ?case r s =
expect_equal_app
~msg:(str_printer s)
Expand Down Expand Up @@ -135,4 +140,29 @@ let _ =
eq_match ~case:false "abc" "ABC";
);

expect_pass "split tests" (fun () ->
let printer = list_printer (fun x -> x) in
let split_printer =
list_printer (function
| Re_str.Delim s -> "Delim " ^ s
| Re_str.Text s -> "Text " ^ s) in
List.iter (fun (re, s) ->
let re1 = Str.regexp re in
let re2 = Re_str.regexp re in
assert_equal ~printer:split_printer
(split_convert (Str.full_split re1 s))
(Re_str.full_split re2 s);
assert_equal ~printer
(Str.split_delim re1 s)
(Re_str.split_delim re2 s);
assert_equal ~printer
(Str.split re1 s)
(Re_str.split re2 s)
)
[ "re", ""
; " ", "foo bar"
; "\b", "one-two three"
; "[0-9]", "One3TwoFive"]
);

run_test_suite "test_str"

0 comments on commit c5531af

Please sign in to comment.