diff --git a/lib/dyn.ml b/lib/dyn.ml index 8ba97350..a9029d31 100644 --- a/lib/dyn.ml +++ b/lib/dyn.ml @@ -14,3 +14,13 @@ let pair x y = Tuple [ x; y ] let record fields = Record fields let enum x = Enum x let string s = String s + +let result ok err = function + | Ok s -> variant "Ok" [ ok s ] + | Error e -> variant "Error" [ err e ] +;; + +let option f = function + | None -> enum "None" + | Some s -> variant "Some" [ f s ] +;; diff --git a/lib/fmt.ml b/lib/fmt.ml index 51cade84..a0d67483 100644 --- a/lib/fmt.ml +++ b/lib/fmt.ml @@ -37,18 +37,8 @@ let optint fmt = function | Some i -> fprintf fmt "@ %d" i ;; -let quote fmt s = Format.fprintf fmt "\"%s\"" s - -let pp_olist pp_elem fmt = - Format.fprintf - fmt - "@[<3>[@ %a@ ]@]" - (pp_print_list ~pp_sep:(fun fmt () -> fprintf fmt ";@ ") pp_elem) -;; - let char fmt c = Format.fprintf fmt "%c" c let bool = Format.pp_print_bool -let pp_str_list = pp_olist quote let lit s fmt () = pp_print_string fmt s let to_to_string pp x = diff --git a/lib/fmt.mli b/lib/fmt.mli index f4b8e54f..3dbadf46 100644 --- a/lib/fmt.mli +++ b/lib/fmt.mli @@ -1,7 +1,6 @@ type formatter := Format.formatter type 'a t = formatter -> 'a -> unit -val pp_str_list : string list t val sexp : formatter -> string -> 'a t -> 'a -> unit val str : string t val optint : int option t diff --git a/lib_test/expect/dune b/lib_test/expect/dune index 6edf846a..159b17b4 100644 --- a/lib_test/expect/dune +++ b/lib_test/expect/dune @@ -8,6 +8,7 @@ ppx_expect.config_types ppx_expect base + str ppx_inline_test.config) (inline_tests (modes native js)) diff --git a/lib_test/expect/import.ml b/lib_test/expect/import.ml index 60fb6ed9..31e7aef3 100644 --- a/lib_test/expect/import.ml +++ b/lib_test/expect/import.ml @@ -1,6 +1,7 @@ module Re = Re_private.Re include Re_private.Import module Fmt = Re_private.Fmt +module Dyn = Re_private.Dyn let printf = Printf.printf diff --git a/lib_test/expect/test_str.ml b/lib_test/expect/test_str.ml new file mode 100644 index 00000000..720def31 --- /dev/null +++ b/lib_test/expect/test_str.ml @@ -0,0 +1,325 @@ +open Import + +module type Str_intf = module type of Str + +module Test_matches (R : Str_intf) = struct + let groups () = + let group i = + try `Found (R.group_beginning i) with + | Not_found -> `Not_found + | Invalid_argument _ -> `Not_exists + in + let rec loop acc i = + match group i with + | `Found p -> loop ((p, R.group_end i) :: acc) (i + 1) + | `Not_found -> loop ((-1, -1) :: acc) (i + 1) + | `Not_exists -> List.rev acc + in + loop [] 0 + ;; + + let eq_match ?(pos = 0) ?(case = true) r s = + let pat = if case then R.regexp r else R.regexp_case_fold r in + try + ignore (R.search_forward pat s pos); + Some (groups ()) + with + | Not_found -> None + ;; + + let eq_match' ?(pos = 0) ?(case = true) r s = + let pat = if case then R.regexp r else R.regexp_case_fold r in + try + ignore (R.string_match pat s pos); + Some (groups ()) + with + | Not_found -> None + ;; +end + +module T_str = Test_matches (Str) +module T_re = Test_matches (Re.Str) + +let test dyn_of_ok str re args = + let run f = + match f () with + | s -> Ok s + | exception exn -> Error exn + in + let str = run (fun () -> str args) in + let re = run (fun () -> re args) in + if not (Poly.equal str re) + then ( + let printer x = + let dyn = + let open Dyn in + result dyn_of_ok (fun x -> string (Printexc.to_string x)) x + in + sexp_of_dyn dyn |> Base.Sexp.to_string_hum + in + Printf.printf "str: %s\n" (printer str); + Printf.printf "re: %s\n" (printer re)) +;; + +let dyn_of_pairs x = + Dyn.option + (fun x -> + List.map x ~f:(fun (start, stop) -> + let open Dyn in + pair (int start) (int stop)) + |> Dyn.list) + x +;; + +let split_result_conv = + List.map ~f:(function + | Str.Delim x -> Re.Str.Delim x + | Str.Text x -> Re.Str.Text x) +;; + +let dyn_split_result_list list = + List.map + list + ~f: + (let open Dyn in + function + | Re.Str.Delim x -> variant "Delim" [ string x ] + | Text s -> variant "Text" [ string s ]) + |> Dyn.list +;; + +type ('a, 'b) test = + { name : string + ; dyn_of_ok : 'b -> Dyn.t + ; re_str : Re.Str.regexp -> 'a -> 'b + ; str : Str.regexp -> 'a -> 'b + } + +let bounded_split_t = + { name = "bounded_split" + ; dyn_of_ok = (fun x -> Dyn.list (List.map x ~f:Dyn.string)) + ; re_str = (fun re (s, n) -> Re.Str.bounded_split re s n) + ; str = (fun re (s, n) -> Str.bounded_split re s n) + } +;; + +let bounded_full_split_t = + { name = "bounded_full_split" + ; dyn_of_ok = dyn_split_result_list + ; re_str = (fun re (s, n) -> Re.Str.bounded_full_split re s n) + ; str = (fun re (s, n) -> split_result_conv (Str.bounded_full_split re s n)) + } +;; + +let full_split_t = + { bounded_full_split_t with + name = "full_split" + ; re_str = (fun re s -> Re.Str.full_split re s) + ; str = (fun re s -> split_result_conv (Str.full_split re s)) + } +;; + +let split_delim_t = + { name = "split_delim" + ; dyn_of_ok = (fun x -> Dyn.list (List.map x ~f:Dyn.string)) + ; re_str = Re.Str.split_delim + ; str = Str.split_delim + } +;; + +let split_t = + { name = "split" + ; dyn_of_ok = (fun x -> Dyn.list (List.map x ~f:Dyn.string)) + ; re_str = Re.Str.split + ; str = Str.split + } +;; + +let global_replace_t = + { name = "global_replace" + ; dyn_of_ok = Dyn.string + ; re_str = (fun re (r, s) -> Re.Str.global_replace re r s) + ; str = (fun re (r, s) -> Str.global_replace re r s) + } +;; + +let eq_match ?pos ?case re = + test dyn_of_pairs (T_str.eq_match ?pos ?case re) (T_re.eq_match ?pos ?case re) +;; + +let eq_match' ?pos ?case re = + test dyn_of_pairs (T_str.eq_match' ?pos ?case re) (T_re.eq_match' ?pos ?case re) +;; + +let test t re args = + test t.dyn_of_ok (t.re_str (Re.Str.regexp re)) (t.str (Str.regexp re)) args +;; + +let split_delim re s = test split_delim_t re s +let split re s = test split_t re s +let full_split re s = test full_split_t re s +let bounded_split re s n = test bounded_split_t re (s, n) +let bounded_full_split re s n = test bounded_full_split_t re (s, n) +let global_replace re r s = test global_replace_t re (r, s) + +let%expect_test "literal match" = + eq_match "a" "a"; + eq_match "a" "b"; + [%expect {||}] +;; + +let%expect_test "alt" = + eq_match "a\\|b" "a"; + eq_match "a\\|b" "b"; + eq_match "a\\|b" "c"; + [%expect {||}] +;; + +let%expect_test "seq" = + eq_match "ab" "ab"; + eq_match "ab" "ac"; + [%expect {||}] +;; + +let%expect_test "epsilon" = + eq_match "" ""; + eq_match "" "a"; + [%expect {||}] +;; + +let%expect_test "rep" = + eq_match "a*" ""; + eq_match "a*" "a"; + eq_match "a*" "aa"; + eq_match "a*" "b"; + [%expect {||}] +;; + +let%expect_test "rep1" = + eq_match "a+" "a"; + eq_match "a+" "aa"; + eq_match "a+" ""; + eq_match "a+" "b"; + [%expect {| |}] +;; + +let%expect_test "opt" = + eq_match "a?" ""; + eq_match "a?" "a"; + [%expect {| |}] +;; + +let%expect_test "bol" = + eq_match "^a" "ab"; + eq_match "^a" "b\na"; + eq_match "^a" "ba"; + [%expect {| |}] +;; + +let%expect_test "eol" = + eq_match "a$" "ba"; + eq_match "a$" "a\nb"; + eq_match "a$" "ba\n"; + eq_match "a$" "ab"; + [%expect {| |}] +;; + +let%expect_test "start" = + eq_match ~pos:1 "Za" "xab"; + eq_match ~pos:1 "Za" "xb\na"; + eq_match ~pos:1 "Za" "xba"; + [%expect {||}] +;; + +let%expect_test "match semantics" = + eq_match "\\(a\\|b\\)*b" "aabaab"; + eq_match "aa\\|aaa" "aaaa"; + eq_match "aaa\\|aa" "aaaa"; + [%expect {||}] +;; + +let%expect_test "Group (or submatch)" = + eq_match "\\(a\\)\\(a\\)?\\(b\\)" "ab"; + [%expect {| |}] +;; + +let%expect_test "Character set" = + eq_match "[0-9]+" "0123456789"; + eq_match "[0-9]+" "a"; + eq_match "[9-0]+" "2"; + eq_match "[5-5]" "5"; + eq_match "[5-4]" "1"; + eq_match' "[]]" "]"; + eq_match' "[a-]" "-"; + eq_match' "[-a]" "-"; + eq_match' "]" "]"; + eq_match' "[^b-f]" "z"; + eq_match' "[^b-f]" "a"; + [%expect {||}]; + (* These errors aren't correct *) + eq_match' "[]" "x"; + eq_match' "[" "["; + [%expect + {| + str: (Error "Failure(\"[ class not closed by ]\")") + re: (Error Re_private.Emacs.Parse_error) + str: (Error "Failure(\"[ class not closed by ]\")") + re: (Error Re_private.Emacs.Parse_error) + |}] +;; + +let%expect_test "compl" = + eq_match "[^0-9a-z]+" "A:Z+"; + eq_match "[^0-9a-z]+" "0"; + eq_match "[^0-9a-z]+" "a"; + [%expect {||}] +;; + +let%expect_test "Word modifiers" = + eq_match' "\\bfoo" "foo"; + eq_match' "\\" "foo"; + eq_match' "z\\Bfoo" "zfoo"; + eq_match' "\\`foo" "foo"; + eq_match' "foo\\'" "foo"; + [%expect {||}] +;; + +let%expect_test "Case modifiers" = + eq_match ~case:false "abc" "abc"; + eq_match ~case:false "abc" "ABC"; + [%expect {| |}] +;; + +let%expect_test "global_replace" = + global_replace "needle" "test" "needlehaystack"; + global_replace "needle" "" ""; + global_replace "needle" "" "needle"; + global_replace "xxx" "yyy" "zzz"; + global_replace "test\\([0-9]*\\)" "\\1-foo-\\1" "test100 test200 test"; + global_replace "test\\([0-9]*\\)" "'\\-0'" "test100 test200 test"; + (* Regrssion test for #129 *) + global_replace "\\(X+\\)" "A\\1YY" "XXXXXXZZZZ"; + [%expect {||}] +;; + +let%expect_test "bounded_split, bounded_full_split" = + [ ",", "foo,bar,baz", 5 + ; ",", "foo,bar,baz", 1 + ; ",", "foo,bar,baz", 0 + ; ",\\|", "foo,bar|baz", 4 + ] + |> List.iter ~f:(fun (re, s, n) -> + bounded_full_split re s n; + bounded_split re s n); + [%expect {||}] +;; + +let%expect_test "split, full_split, split_delim" = + [ "re", ""; " ", "foo bar"; "\b", "one-two three"; "[0-9]", "One3TwoFive" ] + |> List.iter ~f:(fun (re, s) -> + split re s; + full_split re s; + split_delim re s); + [%expect {||}] +;; diff --git a/lib_test/fort_unit/dune b/lib_test/fort_unit/dune deleted file mode 100644 index 464e280c..00000000 --- a/lib_test/fort_unit/dune +++ /dev/null @@ -1,7 +0,0 @@ -(rule - (copy %{project_root}/lib/fmt.ml fmt.ml)) - -(library - (name fort_unit) - (wrapped false) - (libraries re ounit2)) diff --git a/lib_test/fort_unit/fort_unit.ml b/lib_test/fort_unit/fort_unit.ml deleted file mode 100644 index c29f2912..00000000 --- a/lib_test/fort_unit/fort_unit.ml +++ /dev/null @@ -1,76 +0,0 @@ -(* ounit compatibility layer for fort tests *) -open OUnit2 - -type ('a, 'b) either = - | Left of 'a - | Right of 'b - -let str_of_either f g = function - | Left a -> f a - | Right b -> g b -;; - -let try_with f = - try Right (f ()) with - | exn -> Left exn -;; - -let expect_equal_app ?printer ?msg f x g y = - let fx = try_with (fun () -> f x) in - let gy = try_with (fun () -> g y) in - let printer = - let right x = - match printer with - | None -> "" - | Some p -> p x - in - str_of_either Printexc.to_string right - in - assert_equal ~printer ?msg fx gy -;; - -let collected_tests = ref [] -let id x = x -let not_found () = raise Not_found -let bool_printer i = Printf.sprintf "%b" i -let int_printer i = Printf.sprintf "%d" i -let str_printer s = "\"" ^ String.escaped s ^ "\"" -let ofs_printer (i0, i1) = Printf.sprintf "(%d,%d)" i0 i1 -let list_printer f l = "[" ^ String.concat "; " (List.map f l) ^ "]" -let arr_printer f a = "[|" ^ String.concat "; " (List.map f (Array.to_list a)) ^ "|]" - -let opt_printer f = function - | None -> "" - | Some s -> "Some (" ^ f s ^ ")" -;; - -let arr_str_printer = arr_printer str_printer -let arr_ofs_printer = arr_printer ofs_printer -let list_ofs_printer = list_printer ofs_printer -let fail = assert_failure -let expect_eq_bool ?msg f x g y = expect_equal_app ?msg ~printer:string_of_bool f x g y -let expect_eq_str ?msg f x g y = expect_equal_app ?msg ~printer:str_printer f x g y - -let expect_eq_str_opt ?msg f x g y = - expect_equal_app ?msg ~printer:(opt_printer str_printer) f x g y -;; - -let expect_eq_ofs ?msg f x g y = expect_equal_app ?msg ~printer:ofs_printer f x g y - -let expect_eq_arr_str ?msg f x g y = - expect_equal_app ?msg ~printer:arr_str_printer f x g y -;; - -let expect_eq_arr_ofs ?msg f x g y = - expect_equal_app ?msg ~printer:arr_ofs_printer f x g y -;; - -let expect_eq_list_str ?msg f x g y = - expect_equal_app ?msg ~printer:(list_printer str_printer) f x g y -;; - -let expect_pass name run = - collected_tests := (name >:: fun _ -> run ()) :: !collected_tests -;; - -let run_test_suite suite_name = run_test_tt_main (suite_name >::: !collected_tests) diff --git a/lib_test/str/dune b/lib_test/str/dune deleted file mode 100644 index a9745237..00000000 --- a/lib_test/str/dune +++ /dev/null @@ -1,3 +0,0 @@ -(test - (libraries re fort_unit str ounit2) - (name test_str)) diff --git a/lib_test/str/test_str.ml b/lib_test/str/test_str.ml deleted file mode 100644 index 3700fd0c..00000000 --- a/lib_test/str/test_str.ml +++ /dev/null @@ -1,276 +0,0 @@ -open Fort_unit -open OUnit2 - -module type Str_intf = module type of Str - -module Test_matches (R : Str_intf) = struct - let groups () = - let group i = - try `Found (R.group_beginning i) with - | Not_found -> `Not_found - | Invalid_argument _ -> `Not_exists - in - let rec loop acc i = - match group i with - | `Found p -> loop ((p, R.group_end i) :: acc) (i + 1) - | `Not_found -> loop ((-1, -1) :: acc) (i + 1) - | `Not_exists -> List.rev acc - in - loop [] 0 - ;; - - let eq_match ?(pos = 0) ?(case = true) r s = - let pat = if case then R.regexp r else R.regexp_case_fold r in - try - ignore (R.search_forward pat s pos); - Some (groups ()) - with - | Not_found -> None - ;; - - let eq_match' ?(pos = 0) ?(case = true) r s = - let pat = if case then R.regexp r else R.regexp_case_fold r in - try - ignore (R.string_match pat s pos); - Some (groups ()) - with - | Not_found -> None - ;; -end - -module T_str = Test_matches (Str) -module T_re = Test_matches (Re.Str) - -let eq_match ?pos ?case r s = - expect_equal_app - ~msg:(str_printer s) - ~printer:(opt_printer (list_printer ofs_printer)) - (fun () -> T_str.eq_match ?pos ?case r s) - () - (fun () -> T_re.eq_match ?pos ?case r s) - () -;; - -let eq_match' ?pos ?case r s = - expect_equal_app - ~msg:(str_printer s) - ~printer:(opt_printer (list_printer ofs_printer)) - (fun () -> T_str.eq_match' ?pos ?case r s) - () - (fun () -> T_re.eq_match' ?pos ?case r s) - () -;; - -let split_result_conv = - List.map (function - | Str.Delim x -> Re.Str.Delim x - | Str.Text x -> Re.Str.Text x) -;; - -let pp_split_result_list = - Fmt.pp_olist (fun fmt x -> - let tag, arg = - match x with - | Re.Str.Delim x -> "Delim", x - | Re.Str.Text x -> "Text", x - in - Fmt.fprintf fmt "%s@ (\"%s\")" tag arg) -;; - -let pp_fs pp_args pp_out fmt (name, re, args, ex, res) = - let f fmt (mod_, r) = - Fmt.fprintf fmt "%s.%s %a %a = %a" mod_ name Fmt.quote re pp_args args pp_out r - in - Fmt.fprintf fmt "@.%a@.%a" f ("Str", ex) f ("Re.Str", res) -;; - -type ('a, 'b) test = - { name : string - ; pp_args : 'a Fmt.t - ; pp_out : 'b Fmt.t - ; re_str : Re.Str.regexp -> 'a -> 'b - ; str : Str.regexp -> 'a -> 'b - } - -let bounded_split_t = - { name = "bounded_split" - ; pp_args = (fun fmt (s, n) -> Fmt.fprintf fmt "%a %d" Fmt.quote s n) - ; pp_out = Fmt.pp_str_list - ; re_str = (fun re (s, n) -> Re.Str.bounded_split re s n) - ; str = (fun re (s, n) -> Str.bounded_split re s n) - } -;; - -let bounded_full_split_t = - { bounded_split_t with - name = "bounded_full_split" - ; pp_out = pp_split_result_list - ; re_str = (fun re (s, n) -> Re.Str.bounded_full_split re s n) - ; str = (fun re (s, n) -> split_result_conv (Str.bounded_full_split re s n)) - } -;; - -let full_split_t = - { bounded_full_split_t with - name = "full_split" - ; pp_args = (fun fmt s -> Fmt.fprintf fmt "%a" Fmt.quote s) - ; re_str = (fun re s -> Re.Str.full_split re s) - ; str = (fun re s -> split_result_conv (Str.full_split re s)) - } -;; - -let split_delim_t = - { full_split_t with - name = "split_delim" - ; pp_out = Fmt.pp_str_list - ; re_str = (fun re s -> Re.Str.split_delim re s) - ; str = (fun re s -> Str.split_delim re s) - } -;; - -let split_t = - { name = "split" - ; pp_out = Fmt.pp_str_list - ; pp_args = full_split_t.pp_args - ; re_str = (fun re s -> Re.Str.split re s) - ; str = (fun re s -> Str.split re s) - } -;; - -let global_replace_t = - { name = "global_replace" - ; pp_out = Fmt.pp_print_string - ; pp_args = (fun fmt (r, s) -> Fmt.fprintf fmt "%a %a" Fmt.quote r Fmt.quote s) - ; re_str = (fun re (r, s) -> Re.Str.global_replace re r s) - ; str = (fun re (r, s) -> Str.global_replace re r s) - } -;; - -let test t re args = - assert_equal - ~pp_diff:(fun fmt (ex, act) -> - pp_fs t.pp_args t.pp_out fmt (t.name, re, args, ex, act)) - ~printer:(Fmt.to_to_string t.pp_out) - (t.re_str (Re.Str.regexp re) args) - (t.str (Str.regexp re) args) -;; - -let split_delim re s = test split_delim_t re s -let split re s = test split_t re s -let full_split re s = test full_split_t re s -let bounded_split re s n = test bounded_split_t re (s, n) -let bounded_full_split re s n = test bounded_full_split_t re (s, n) -let global_replace re r s = test global_replace_t re (r, s) - -let _ = - (* Literal Match *) - expect_pass "str" (fun () -> - eq_match "a" "a"; - eq_match "a" "b"); - (* Basic Operations *) - expect_pass "alt" (fun () -> - eq_match "a\\|b" "a"; - eq_match "a\\|b" "b"; - eq_match "a\\|b" "c"); - expect_pass "seq" (fun () -> - eq_match "ab" "ab"; - eq_match "ab" "ac"); - expect_pass "epsilon" (fun () -> - eq_match "" ""; - eq_match "" "a"); - expect_pass "rep" (fun () -> - eq_match "a*" ""; - eq_match "a*" "a"; - eq_match "a*" "aa"; - eq_match "a*" "b"); - expect_pass "rep1" (fun () -> - eq_match "a+" "a"; - eq_match "a+" "aa"; - eq_match "a+" ""; - eq_match "a+" "b"); - expect_pass "opt" (fun () -> - eq_match "a?" ""; - eq_match "a?" "a"); - (* String, line, word *) - expect_pass "bol" (fun () -> - eq_match "^a" "ab"; - eq_match "^a" "b\na"; - eq_match "^a" "ba"); - expect_pass "eol" (fun () -> - eq_match "a$" "ba"; - eq_match "a$" "a\nb"; - eq_match "a$" "ba\n"; - eq_match "a$" "ab"); - expect_pass "start" (fun () -> - eq_match ~pos:1 "Za" "xab"; - eq_match ~pos:1 "Za" "xb\na"; - eq_match ~pos:1 "Za" "xba"); - (* Match semantics *) - expect_pass "match semantics" (fun () -> - eq_match "\\(a\\|b\\)*b" "aabaab"; - eq_match "aa\\|aaa" "aaaa"; - eq_match "aaa\\|aa" "aaaa"); - (* Group (or submatch) *) - - (* TODO: infinite loop *) - expect_pass "group" (fun () -> eq_match "\\(a\\)\\(a\\)?\\(b\\)" "ab"); - (* Character set *) - expect_pass "rg" (fun () -> - eq_match "[0-9]+" "0123456789"; - eq_match "[0-9]+" "a"; - eq_match "[9-0]+" "2"; - eq_match "[5-5]" "5"; - eq_match "[5-4]" "1"; - eq_match' "[]]" "]"; - eq_match' "[a-]" "-"; - eq_match' "[-a]" "-"; - eq_match' "]" "]"; - eq_match' "[^b-f]" "z"; - eq_match' "[^b-f]" "a" - (* These errors aren't correct *) - (* eq_match' "[]" "x" *) - (* eq_match' "[" "[" *)); - expect_pass "compl" (fun () -> - eq_match "[^0-9a-z]+" "A:Z+"; - eq_match "[^0-9a-z]+" "0"; - eq_match "[^0-9a-z]+" "a"); - (* Word modifiers *) - expect_pass "word boundaries" (fun () -> - eq_match' "\\bfoo" "foo"; - eq_match' "\\" "foo"; - eq_match' "z\\Bfoo" "zfoo"; - eq_match' "\\`foo" "foo"; - eq_match' "foo\\'" "foo"); - (* Case modifiers *) - expect_pass "no_case" (fun () -> - eq_match ~case:false "abc" "abc"; - eq_match ~case:false "abc" "ABC"); - expect_pass "global_replace" (fun () -> - global_replace "needle" "test" "needlehaystack"; - global_replace "needle" "" ""; - global_replace "needle" "" "needle"; - global_replace "xxx" "yyy" "zzz"; - global_replace "test\\([0-9]*\\)" "\\1-foo-\\1" "test100 test200 test"; - global_replace "test\\([0-9]*\\)" "'\\-0'" "test100 test200 test"; - (* Regrssion test for #129 *) - global_replace "\\(X+\\)" "A\\1YY" "XXXXXXZZZZ"); - expect_pass "bounded_split, bounded_full_split" (fun () -> - List.iter - (fun (re, s, n) -> - bounded_full_split re s n; - bounded_split re s n) - [ ",", "foo,bar,baz", 5 - ; ",", "foo,bar,baz", 1 - ; ",", "foo,bar,baz", 0 - ; ",\\|", "foo,bar|baz", 4 - ]); - expect_pass "split, full_split, split_delim" (fun () -> - List.iter - (fun (re, s) -> - split re s; - full_split re s; - split_delim re s) - [ "re", ""; " ", "foo bar"; "\b", "one-two three"; "[0-9]", "One3TwoFive" ]); - run_test_suite "test_str" -;;