Skip to content

Commit

Permalink
test: add repetition of sequence (#520)
Browse files Browse the repository at this point in the history
  • Loading branch information
rgrinberg authored Oct 4, 2024
1 parent 0c885e5 commit 4db72ce
Show file tree
Hide file tree
Showing 2 changed files with 29 additions and 0 deletions.
10 changes: 10 additions & 0 deletions benchmarks/benchmark.ml
Original file line number Diff line number Diff line change
Expand Up @@ -89,6 +89,15 @@ let compile_clean_star =
test ~name:"kleene star compilation" re (fun re -> ignore (Re.execp (re ()) s))
;;

let repeated_sequence =
let s = String.init 256 ~f:Char.of_int_exn in
let re () = Re.repn (Re.str s) 50 (Some 50) |> Re.compile in
let s = List.init 50 ~f:(fun _ -> s) |> String.concat ~sep:"" in
test ~name:"repeated sequence re" re (fun re ->
let re = re () in
ignore (Re.execp re s))
;;

let benchmarks =
let benches =
List.map benchmarks ~f:(fun (name, re, cases) ->
Expand Down Expand Up @@ -134,6 +143,7 @@ let benchmarks =
@ string_traversal
@ compile_clean_star
@ Memory.benchmarks
@ repeated_sequence
;;

let () =
Expand Down
19 changes: 19 additions & 0 deletions lib_test/expect/test_repn.ml
Original file line number Diff line number Diff line change
Expand Up @@ -57,3 +57,22 @@ let%expect_test "opt" =
test_re (opt (char 'a')) "a";
[%expect {| [| (0, 1) |] |}]
;;

let copy s n =
let len = String.length s in
let b = Bytes.make (len * n) '\000' in
for i = 0 to n - 1 do
Bytes.blit_string s 0 b (i * len) len
done;
Bytes.to_string b
;;

let%expect_test "repeat sequence" =
let s = "abcde" in
let re = str s |> rep |> whole_string |> compile in
for i = 0 to 3 do
let r = copy s i in
assert (Re.execp re r)
done;
[%expect {||}]
;;

0 comments on commit 4db72ce

Please sign in to comment.