aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/Makefile8
-rw-r--r--lib/stdlib/test/beam_lib_SUITE.erl68
-rw-r--r--lib/stdlib/test/binary_module_SUITE.erl5
-rw-r--r--lib/stdlib/test/epp_SUITE.erl2
-rw-r--r--lib/stdlib/test/erl_eval_SUITE.erl12
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl115
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl110
-rw-r--r--lib/stdlib/test/ets_SUITE.erl2400
-rw-r--r--lib/stdlib/test/ets_SUITE_data/visualize_throughput.html253
-rw-r--r--lib/stdlib/test/gen_fsm_SUITE.erl12
-rw-r--r--lib/stdlib/test/gen_statem_SUITE.erl114
-rw-r--r--lib/stdlib/test/io_SUITE.erl46
-rw-r--r--lib/stdlib/test/lists_SUITE.erl27
-rw-r--r--lib/stdlib/test/qlc_SUITE.erl76
-rw-r--r--lib/stdlib/test/rand_SUITE.erl436
-rw-r--r--lib/stdlib/test/rand_Xoroshiro928ss_dev.txt343
-rw-r--r--lib/stdlib/test/re_SUITE.erl57
-rw-r--r--lib/stdlib/test/re_SUITE_data/testoutput124
-rw-r--r--lib/stdlib/test/re_SUITE_data/testoutput24
-rw-r--r--lib/stdlib/test/re_SUITE_data/testoutput44
-rw-r--r--lib/stdlib/test/re_testoutput1_replacement_test.erl29
-rw-r--r--lib/stdlib/test/re_testoutput1_split_test.erl13779
-rw-r--r--lib/stdlib/test/shell_SUITE.erl6
-rw-r--r--lib/stdlib/test/stdlib.spec5
-rw-r--r--lib/stdlib/test/stdlib_bench.spec1
-rw-r--r--lib/stdlib/test/stdlib_bench_SUITE.erl130
-rw-r--r--lib/stdlib/test/stdlib_bench_SUITE_data/generic_fsm.erl2
-rw-r--r--lib/stdlib/test/stdlib_bench_SUITE_data/generic_server.erl4
-rw-r--r--lib/stdlib/test/stdlib_bench_SUITE_data/generic_statem.erl10
-rw-r--r--lib/stdlib/test/string_SUITE.erl108
-rw-r--r--lib/stdlib/test/unicode_util_SUITE.erl10
-rw-r--r--lib/stdlib/test/unicode_util_SUITE_data/GraphemeBreakTest.txt1148
-rw-r--r--lib/stdlib/test/unicode_util_SUITE_data/LineBreakTest.txt246
-rw-r--r--lib/stdlib/test/unicode_util_SUITE_data/NormalizationTest.txt52
-rw-r--r--lib/stdlib/test/uri_string_SUITE.erl10
35 files changed, 11206 insertions, 8450 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index bbe3cefa42..712b1b92fb 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -99,11 +99,9 @@ MODULES= \
maps_SUITE \
zzz_SUITE
-ERL_FILES= $(MODULES:%=%.erl)
+ERTS_MODULES= erts_test_utils
-TARGET_FILES= $(MODULES:%=$(EBIN)/%.$(EMULATOR))
-
-INSTALL_PROGS= $(TARGET_FILES)
+ERL_FILES= $(MODULES:%=%.erl) $(ERTS_MODULES:%=$(ERL_TOP)/erts/emulator/test/%.erl)
# ----------------------------------------------------
# Release directory specification
@@ -128,7 +126,7 @@ COVERFILE=stdlib.cover
# ----------------------------------------------------
make_emakefile:
- $(ERL_TOP)/make/make_emakefile $(ERL_COMPILE_FLAGS) -o$(EBIN) $(MODULES) \
+ $(ERL_TOP)/make/make_emakefile $(ERL_COMPILE_FLAGS) -o$(EBIN) $(MODULES) $(ERTS_MODULES) \
> $(EMAKEFILE)
tests debug opt: make_emakefile
diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl
index 6418dc7eb6..4b2694320e 100644
--- a/lib/stdlib/test/beam_lib_SUITE.erl
+++ b/lib/stdlib/test/beam_lib_SUITE.erl
@@ -35,7 +35,7 @@
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2,end_per_group/2,
- normal/1, error/1, cmp/1, cmp_literals/1, strip/1, otp_6711/1,
+ normal/1, error/1, cmp/1, cmp_literals/1, strip/1, strip_add_chunks/1, otp_6711/1,
building/1, md5/1, encrypted_abstr/1, encrypted_abstr_file/1]).
-export([init_per_testcase/2, end_per_testcase/2]).
@@ -45,7 +45,7 @@ suite() ->
{timetrap,{minutes,2}}].
all() ->
- [error, normal, cmp, cmp_literals, strip, otp_6711,
+ [error, normal, cmp, cmp_literals, strip, strip_add_chunks, otp_6711,
building, md5, encrypted_abstr, encrypted_abstr_file].
groups() ->
@@ -401,6 +401,69 @@ strip(Conf) when is_list(Conf) ->
Source5D1, BeamFile5D1]),
ok.
+strip_add_chunks(Conf) when is_list(Conf) ->
+ PrivDir = ?privdir,
+ {SourceD1, BeamFileD1} = make_beam(PrivDir, simple, member),
+ {Source2D1, BeamFile2D1} = make_beam(PrivDir, simple2, concat),
+ {Source3D1, BeamFile3D1} = make_beam(PrivDir, make_fun, make_fun),
+ {Source4D1, BeamFile4D1} = make_beam(PrivDir, constant, constant),
+ {Source5D1, BeamFile5D1} = make_beam(PrivDir, lines, lines),
+
+ NoOfTables = erlang:system_info(ets_count),
+ P0 = pps(),
+
+ %% strip binary
+ verify(not_a_beam_file, beam_lib:strip(<<>>)),
+ {ok, B1} = file:read_file(BeamFileD1),
+ {ok, {simple, NB1}} = beam_lib:strip(B1),
+
+ BId1 = chunk_ids(B1),
+ NBId1 = chunk_ids(NB1),
+ true = length(BId1) > length(NBId1),
+ compare_chunks(B1, NB1, NBId1),
+
+ %% Keep all the extra chunks
+ ExtraChunks = ["Abst" , "Dbgi" , "Attr" , "CInf" , "LocT" , "Atom" ],
+ {ok, {simple, AB1}} = beam_lib:strip(B1, ExtraChunks),
+ ABId1 = chunk_ids(AB1),
+ true = length(BId1) == length(ABId1),
+ compare_chunks(B1, AB1, ABId1),
+
+ %% strip file - Keep extra chunks
+ verify(file_error, beam_lib:strip(foo)),
+ {ok, {simple, _}} = beam_lib:strip(BeamFileD1, ExtraChunks),
+ compare_chunks(B1, BeamFileD1, ABId1),
+
+ %% strip_files
+ {ok, B2} = file:read_file(BeamFile2D1),
+ {ok, [{simple,_},{simple2,_}]} = beam_lib:strip_files([B1, B2], ExtraChunks),
+ {ok, [{simple,_},{simple2,_},{make_fun,_},{constant,_}]} =
+ beam_lib:strip_files([BeamFileD1, BeamFile2D1, BeamFile3D1, BeamFile4D1], ExtraChunks),
+
+ %% check that each module can be loaded.
+ {module, simple} = code:load_abs(filename:rootname(BeamFileD1)),
+ {module, simple2} = code:load_abs(filename:rootname(BeamFile2D1)),
+ {module, make_fun} = code:load_abs(filename:rootname(BeamFile3D1)),
+ {module, constant} = code:load_abs(filename:rootname(BeamFile4D1)),
+
+ %% check that line number information is still present after stripping
+ {module, lines} = code:load_abs(filename:rootname(BeamFile5D1)),
+ {'EXIT',{badarith,[{lines,t,1,Info}|_]}} = (catch lines:t(atom)),
+ false = code:purge(lines),
+ true = code:delete(lines),
+ {ok, {lines,BeamFile5D1}} = beam_lib:strip(BeamFile5D1),
+ {module, lines} = code:load_abs(filename:rootname(BeamFile5D1)),
+ {'EXIT',{badarith,[{lines,t,1,Info}|_]}} = (catch lines:t(atom)),
+
+ true = (P0 == pps()),
+ NoOfTables = erlang:system_info(ets_count),
+
+ delete_files([SourceD1, BeamFileD1,
+ Source2D1, BeamFile2D1,
+ Source3D1, BeamFile3D1,
+ Source4D1, BeamFile4D1,
+ Source5D1, BeamFile5D1]),
+ ok.
otp_6711(Conf) when is_list(Conf) ->
{'EXIT',{function_clause,_}} = (catch {a, beam_lib:info(3)}),
@@ -729,6 +792,7 @@ make_beam(Dir, Module, F) ->
FileBase = filename:join(Dir, atom_to_list(Module)),
Source = FileBase ++ ".erl",
BeamFile = FileBase ++ ".beam",
+ file:delete(BeamFile),
simple_file(Source, Module, F),
{ok, _} = compile:file(Source, [{outdir,Dir}, debug_info, report]),
{Source, BeamFile}.
diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl
index e0811f19cf..9b2033ec4a 100644
--- a/lib/stdlib/test/binary_module_SUITE.erl
+++ b/lib/stdlib/test/binary_module_SUITE.erl
@@ -755,8 +755,9 @@ list_to_bin(Config) when is_list(Config) ->
copy(Config) when is_list(Config) ->
<<1,2,3>> = binary:copy(<<1,2,3>>),
RS = random_string({1,10000}),
- RS = RS2 = binary:copy(RS),
- false = erts_debug:same(RS,RS2),
+ RS2 = binary:copy(RS),
+ true = RS =:= RS2,
+ false = erts_debug:same(RS, RS2),
<<>> = ?MASK_ERROR(binary:copy(<<1,2,3>>,0)),
badarg = ?MASK_ERROR(binary:copy(<<1,2,3:3>>,2)),
badarg = ?MASK_ERROR(binary:copy([],0)),
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index 0ac99ad03a..a90beed4f3 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -1372,7 +1372,7 @@ otp_8562(Config) when is_list(Config) ->
otp_8911(Config) when is_list(Config) ->
case test_server:is_cover() of
true ->
- {skip, "Testing cover, so can not run when cover is already running"};
+ {skip, "Testing cover, so cannot run when cover is already running"};
false ->
do_otp_8911(Config)
end.
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index f4019d477b..2436c8091c 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -1156,7 +1156,17 @@ simple() ->
{A}.
simple1() ->
- erlang:error(simple).
+ %% If the compiler could see that this function would always
+ %% throw an error exception, it would rewrite simple() like this:
+ %%
+ %% simple() -> simple1().
+ %%
+ %% That would change the stacktrace. To prevent the compiler from
+ %% doing that optimization, we must obfuscate the code.
+ case get(a_key_that_is_not_defined) of
+ undefined -> erlang:error(simple);
+ WillNeverHappen -> WillNeverHappen
+ end.
%% Simple cases, just to cover some code.
funs(Config) when is_list(Config) ->
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index d18c7c255c..e7882e0daf 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2018. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2019. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -68,7 +68,7 @@
non_latin1_module/1, otp_14323/1,
stacktrace_syntax/1,
otp_14285/1, otp_14378/1,
- external_funs/1]).
+ external_funs/1,otp_15456/1,otp_15563/1]).
suite() ->
[{ct_hooks,[ts_install_cth]},
@@ -89,7 +89,8 @@ all() ->
maps, maps_type, maps_parallel_match,
otp_11851, otp_11879, otp_13230,
record_errors, otp_11879_cont, non_latin1_module, otp_14323,
- stacktrace_syntax, otp_14285, otp_14378, external_funs].
+ stacktrace_syntax, otp_14285, otp_14378, external_funs,
+ otp_15456, otp_15563].
groups() ->
[{unused_vars_warn, [],
@@ -2108,17 +2109,93 @@ otp_5362(Config) when is_list(Config) ->
{calendar,local_time_to_universal_time_dst,1}, "a future release"}}]}},
{call_removed_function,
- <<"t(X) -> regexp:match(X).">>,
+ <<"t(X) -> erlang:hash(X, 10000).">>,
[],
{warnings,
- [{1,erl_lint,{removed,{regexp,match,1},
- "removed in R15; use the re module instead"}}]}}
+ [{1,erl_lint,{removed,{erlang,hash,2},{erlang,phash2,2},"20.0"}}]}},
+
+ {nowarn_call_removed_function_1,
+ <<"t(X) -> erlang:hash(X, 10000).">>,
+ [{nowarn_removed,{erlang,hash,2}}],
+ []},
+
+ {nowarn_call_removed_function_2,
+ <<"t(X) -> os_mon_mib:any_function_really(erlang:hash(X, 10000)).">>,
+ [nowarn_removed],
+ []},
+
+ {call_removed_module,
+ <<"t(X) -> os_mon_mib:any_function_really(X).">>,
+ [],
+ {warnings,[{1,erl_lint,
+ {removed,{os_mon_mib,any_function_really,1},
+ "was removed in 22.0"}}]}},
+
+ {nowarn_call_removed_module,
+ <<"t(X) -> os_mon_mib:any_function_really(X).">>,
+ [{nowarn_removed,os_mon_mib}],
+ []}
],
[] = run(Config, Ts),
ok.
+%% OTP-15456. All compiler options can now be given in the option list
+%% (as opposed to only in files).
+otp_15456(Config) when is_list(Config) ->
+ Ts = [
+ %% {nowarn_deprecated_function,[{M,F,A}]} can now be given
+ %% in the option list as well as in an attribute.
+ %% Wherever it occurs, it is not affected by
+ %% warn_deprecated_function.
+ {otp_15456_1,
+ <<"-compile({nowarn_deprecated_function,{erlang,now,0}}).
+ -export([foo/0]).
+
+ foo() ->
+ {erlang:now(), random:seed0(), random:seed(1, 2, 3),
+ random:uniform(), random:uniform(42)}.
+ ">>,
+ {[{nowarn_deprecated_function,{random,seed0,0}},
+ {nowarn_deprecated_function,[{random,uniform,0},
+ {random,uniform,1}]},
+ %% There should be no warnings when attempting to
+ %% turn of warnings for functions that are not
+ %% deprecated or not used in the module.
+ {nowarn_deprecated_function,{random,uniform_s,1}},
+ {nowarn_deprecated_function,{erlang,abs,1}},
+ warn_deprecated_function]},
+ {warnings,[{5,erl_lint,
+ {deprecated,{random,seed,3},
+ "the 'random' module is deprecated; "
+ "use the 'rand' module instead"}}]}},
+
+ %% {nowarn_unused_function,[{M,F,A}]} can be given
+ %% in the option list as well as in an attribute.
+ %% It was incorrectly documented to only work when
+ %% given in an attribute.
+ {otp_15456_2,
+ <<"-compile({nowarn_unused_function,foo/0}).
+ foo() -> ok.
+ bar() -> ok.
+ foobar() -> ok.
+ barf(_) -> ok.
+ other() -> ok.
+ ">>,
+ {[{nowarn_unused_function,[{bar,0},{foobar,0}]},
+ {nowarn_unused_function,{barf,1}},
+ %% There should be no warnings when attempting to
+ %% turn of warnings for unused functions that are not
+ %% defined in the module.
+ {nowarn_unused_function,{not_defined_in_module,1}},
+ warn_unused_function]},
+ {warnings,[{6,erl_lint,{unused_function,{other,0}}}]}
+ }],
+
+ [] = run(Config, Ts),
+ ok.
+
%% OTP-5371. Aliases for bit syntax expressions are no longer allowed.
otp_5371(Config) when is_list(Config) ->
Ts = [{otp_5371_1,
@@ -2731,7 +2808,7 @@ bif_clash(Config) when is_list(Config) ->
[],
{errors,[{2,erl_lint,{call_to_redefined_old_bif,{size,1}}}],[]}},
- %% Verify that warnings can not be turned off in the old way.
+ %% Verify that warnings cannot be turned off in the old way.
{clash2,
<<"-export([t/1,size/1]).
t(X) ->
@@ -3499,10 +3576,12 @@ basic_errors(Config) ->
{illegal_record_info,
<<"f1() -> record_info(42, record).
- f2() -> record_info(shoe_size, record).">>,
+ f2() -> record_info(shoe_size, record).
+ f3() -> fun record_info/2.">>,
[],
{errors,[{1,erl_lint,illegal_record_info},
- {2,erl_lint,illegal_record_info}],[]}},
+ {2,erl_lint,illegal_record_info},
+ {3,erl_lint,illegal_record_info}],[]}},
{illegal_expr,
<<"f() -> a:b.">>,
@@ -3931,6 +4010,8 @@ non_latin1_module(Config) ->
format_error(non_latin1_module_unsupported),
BadCallback =
{bad_callback,{'кирилли́ческий атом','кирилли́ческий атом',0}},
+ BadModule =
+ {bad_module,{'кирилли́ческий атом','кирилли́ческий атом',0}},
"explicit module not allowed for callback "
"'кирилли́ческий атом':'кирилли́ческий атом'/0" =
format_error(BadCallback),
@@ -3973,6 +4054,7 @@ non_latin1_module(Config) ->
{11,erl_lint,illegal_guard_expr},
{15,erl_lint,non_latin1_module_unsupported},
{17,erl_lint,non_latin1_module_unsupported},
+ {17,erl_lint,BadModule},
{20,erl_lint,non_latin1_module_unsupported},
{23,erl_lint,non_latin1_module_unsupported},
{25,erl_lint,non_latin1_module_unsupported}],
@@ -4150,6 +4232,21 @@ external_funs(Config) when is_list(Config) ->
run(Config, Ts),
ok.
+otp_15563(Config) when is_list(Config) ->
+ Ts = [{otp_15563,
+ <<"-type deep_list(A) :: [A | deep_list(A)].
+ -spec lists:flatten(deep_list(A)) -> [A].
+ -callback lists:concat([_]) -> string().
+ -spec ?MODULE:foo() -> any().
+ foo() -> a.
+ ">>,
+ [warn_unused_vars],
+ {errors,[{2,erl_lint,{bad_module,{lists,flatten,1}}},
+ {3,erl_lint,{bad_callback,{lists,concat,1}}}],
+ []}}],
+ [] = run(Config, Ts),
+ ok.
+
format_error(E) ->
lists:flatten(erl_lint:format_error(E)).
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index f5d80e7e68..c0cfd26925 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -47,11 +47,12 @@
hook/1,
neg_indent/1,
maps_syntax/1,
+ quoted_atom_types/1,
otp_6321/1, otp_6911/1, otp_6914/1, otp_8150/1, otp_8238/1,
otp_8473/1, otp_8522/1, otp_8567/1, otp_8664/1, otp_9147/1,
otp_10302/1, otp_10820/1, otp_11100/1, otp_11861/1, pr_1014/1,
- otp_13662/1, otp_14285/1, otp_15592/1]).
+ otp_13662/1, otp_14285/1, otp_15592/1, otp_15751/1, otp_15755/1]).
%% Internal export.
-export([ehook/6]).
@@ -74,14 +75,14 @@ groups() ->
[{expr, [],
[func, call, recs, try_catch, if_then, receive_after,
bits, head_tail, cond1, block, case1, ops,
- messages, maps_syntax
+ messages, maps_syntax, quoted_atom_types
]},
{attributes, [], [misc_attrs, import_export, dialyzer_attrs]},
{tickets, [],
[otp_6321, otp_6911, otp_6914, otp_8150, otp_8238,
otp_8473, otp_8522, otp_8567, otp_8664, otp_9147,
otp_10302, otp_10820, otp_11100, otp_11861, pr_1014, otp_13662,
- otp_14285, otp_15592]}].
+ otp_14285, otp_15592, otp_15751, otp_15755]}].
init_per_suite(Config) ->
Config.
@@ -473,10 +474,10 @@ cond1(Config) when is_list(Config) ->
[{tuple,5,[{atom,5,x},{atom,5,y}]}]}]},
CChars = flat_expr1(C),
"cond\n"
- " {foo,bar} ->\n"
- " [a,b];\n"
+ " {foo, bar} ->\n"
+ " [a, b];\n"
" true ->\n"
- " {x,y}\n"
+ " {x, y}\n"
"end" = CChars,
ok.
@@ -711,7 +712,7 @@ otp_6321(Config) when is_list(Config) ->
Str = "S = hopp, {hej, S}. ",
{done, {ok, Tokens, _EndLine}, ""} = erl_scan:tokens("", Str, _L=1),
{ok, Exprs} = erl_parse:parse_exprs(Tokens),
- "S = hopp, {hej,S}" = lists:flatten(erl_pp:exprs(Exprs)),
+ "S = hopp, {hej, S}" = lists:flatten(erl_pp:exprs(Exprs)),
ok.
%% OTP_6911. More newlines.
@@ -828,7 +829,7 @@ type_examples() ->
"(t24()) -> D when is_subtype(D, atom()),"
" is_subtype(D, t14()),"
" is_subtype(D, '\\'t::4'()).">>},
- {ex32,<<"-spec mod:t2() -> any(). ">>},
+ {ex32,<<"-spec erl_pp_test:t2() -> any(). ">>},
{ex33,<<"-opaque attributes_data() :: "
"[{'column', column()} | {'line', info_line()} |"
" {'text', string()}] | {line(),column()}. ">>},
@@ -912,6 +913,21 @@ maps_syntax(Config) when is_list(Config) ->
ok = pp_forms(F),
ok.
+quoted_atom_types(Config) when is_list(Config) ->
+ Q = [{quote_singleton_atom_types, true}],
+ U = [{encoding,unicode}],
+ L = [{encoding,latin1}],
+ F = "-type t() :: a | a().",
+ "-type t() :: 'a' | a().\n" =
+ lists:flatten(parse_and_pp_forms(F, Q ++ L)),
+ "-type t() :: 'a' | a().\n" =
+ lists:flatten(parse_and_pp_forms(F, Q ++ U)),
+ UF = "-type t() :: '\x{400}' | '\x{400}'().",
+ "-type t() :: '\\x{400}' | '\\x{400}'().\n" =
+ lists:flatten(parse_and_pp_forms(UF, Q ++ L)),
+ "-type t() :: '\x{400}' | '\x{400}'().\n" =
+ lists:flatten(parse_and_pp_forms(UF, Q ++ U)),
+ ok.
%% OTP_8567. Avoid duplicated 'undefined' in record field types.
otp_8567(Config) when is_list(Config) ->
@@ -1096,7 +1112,7 @@ otp_11861(Config) when is_list(Config) ->
A3 = erl_anno:new(3),
"-optional_callbacks([bar/0]).\n" =
pf({attribute,A3,optional_callbacks,[{bar,0}]}),
- "-optional_callbacks([{bar,1,bad}]).\n" =
+ "-optional_callbacks([{bar, 1, bad}]).\n" =
pf({attribute,A3,optional_callbacks,[{bar,1,bad}]}),
ok.
@@ -1172,6 +1188,79 @@ otp_15592(_Config) ->
"56789012345678901234:f(<<>>)">>),
ok.
+otp_15751(_Config) ->
+ ok = pp_expr(<<"try foo:bar()
+ catch
+ Reason : Stacktrace ->
+ {Reason, Stacktrace}
+ end">>),
+ ok = pp_expr(<<"try foo:bar()
+ catch
+ throw: Reason : Stacktrace ->
+ {Reason, Stacktrace}
+ end">>),
+ ok = pp_expr(<<"try foo:bar()
+ catch
+ Reason : _ ->
+ Reason
+ end">>),
+ ok = pp_expr(<<"try foo:bar()
+ catch
+ throw: Reason : _ ->
+ Reason
+ end">>),
+ ok = pp_expr(<<"try foo:bar()
+ catch
+ Reason ->
+ Reason
+ end">>),
+ ok = pp_expr(<<"try foo:bar()
+ catch
+ throw: Reason ->
+ Reason
+ end">>),
+ ok.
+
+otp_15755(_Config) ->
+ "[{a, b}, c, {d, e} | t]" =
+ flat_parse_and_pp_expr("[{a, b}, c, {d, e} | t]", 0, []),
+ "[{a, b},\n c, d,\n {d, e},\n 1, 2.0,\n {d, e},\n <<>>, {},\n {d, e},\n"
+ " [], [],\n {d, e} |\n t]" =
+ flat_parse_and_pp_expr("[{a,b},c,d,{d,e},1,2.0,{d,e},<<>>,"
+ "{},{d,e},[],[],{d,e}|t]", 0, []),
+ "[{a, b},\n c, d,\n {d, e},\n 1, 2.0,\n {d, e},\n <<>>, {},\n {d, e},\n"
+ " [], [], d, e | t]" =
+ flat_parse_and_pp_expr("[{a,b},c,d,{d,e},1,2.0,{d,e},<<>>,"
+ "{},{d,e},[],[],d,e|t]", 0, []),
+
+ "-type t() ::
+ a | b | c | a | b | a | b | a | b | a | b | a | b | a | b |
+ a | b | a | b | a | b.\n" =
+ lists:flatten(parse_and_pp_forms(
+ "-type t() :: a | b | c| a | b | a | b | a | b | a |"
+ " b | a | b | a | b | a | b | a | b |a | b.", [])),
+
+ "-type t() ::
+ {dict, 0, 16, 16, 8, 80, 48,
+ {[], [], [], [], [], [], [], [], [], [], [], [], [], [], [],
+ []},
+ {{[], [], [], [], [], [], [], [], [], [], [], [], [], [], []}}}.\n" =
+ lists:flatten(parse_and_pp_forms(
+ "-type t() :: {dict,0,16,16,8,80,48,"
+ "{[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]},"
+ "{{[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]}}}.", [])),
+
+ "-type t() ::
+ {{a},
+ 0, 16,
+ {16},
+ 8, 80, 48, a, b, e, f, 'sf s sdf', [], {},
+ {[]}}.\n" =
+ lists:flatten(parse_and_pp_forms(
+ "-type t() :: {{a}, 0, 16, {16}, 8, 80, 48, a, b, e, f,"
+ " 'sf s sdf', [], {}, {[]}}.", [])),
+ ok.
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
compile(Config, Tests) ->
@@ -1303,6 +1392,9 @@ pp_expr(List, Options) when is_list(List) ->
not_ok
end.
+flat_parse_and_pp_expr(String, Indent, Options) ->
+ lists:flatten(parse_and_pp_expr(String, Indent, Options)).
+
parse_and_pp_expr(String, Indent, Options) ->
StringDot = lists:flatten(String) ++ ".",
erl_pp:expr(parse_expr(StringDot), Indent, Options).
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 433b812fd5..09238ae2b4 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -24,7 +24,7 @@
-export([default/1,setbag/1,badnew/1,verybadnew/1,named/1,keypos2/1,
privacy/1]).
-export([empty/1,badinsert/1]).
--export([time_lookup/1,badlookup/1,lookup_order/1]).
+-export([badlookup/1,lookup_order/1]).
-export([delete_elem/1,delete_tab/1,delete_large_tab/1,
delete_large_named_table/1,
evil_delete/1,baddelete/1,match_delete/1,table_leak/1]).
@@ -42,6 +42,8 @@
select_bound_chunk/1,
t_delete_all_objects/1, t_insert_list/1, t_test_ms/1,
t_select_delete/1,t_select_replace/1,t_select_replace_next_bug/1,t_ets_dets/1]).
+-export([test_table_size_concurrency/1,test_table_memory_concurrency/1,
+ test_delete_table_while_size_snapshot/1, test_delete_table_while_size_snapshot_helper/0]).
-export([ordered/1, ordered_match/1, interface_equality/1,
fixtable_next/1, fixtable_insert/1, rename/1, rename_unnamed/1, evil_rename/1,
@@ -56,6 +58,7 @@
-export([t_match_spec_run/1]).
-export([t_bucket_disappears/1]).
-export([t_named_select/1]).
+-export([select_fixtab_owner_change/1]).
-export([otp_5340/1]).
-export([otp_6338/1]).
-export([otp_6842_select_1000/1]).
@@ -67,7 +70,13 @@
meta_lookup_named_read/1, meta_lookup_named_write/1,
meta_newdel_unnamed/1, meta_newdel_named/1]).
-export([smp_insert/1, smp_fixed_delete/1, smp_unfix_fix/1, smp_select_delete/1,
+ smp_ordered_iteration/1,
smp_select_replace/1, otp_8166/1, otp_8732/1, delete_unfix_race/1]).
+-export([throughput_benchmark/0,
+ throughput_benchmark/1,
+ test_throughput_benchmark/1,
+ long_throughput_benchmark/1,
+ lookup_catree_par_vs_seq_init_benchmark/0]).
-export([exit_large_table_owner/1,
exit_many_large_table_owner/1,
exit_many_tables_owner/1,
@@ -90,6 +99,7 @@
-include_lib("stdlib/include/ms_transform.hrl"). % ets:fun2ms
-include_lib("common_test/include/ct.hrl").
+-include_lib("common_test/include/ct_event.hrl").
-define(m(A,B), assert_eq(A,B)).
-define(heap_binary_size, 64).
@@ -128,13 +138,14 @@ all() ->
t_insert_list, t_test_ms, t_select_delete, t_select_replace,
t_select_replace_next_bug,
t_ets_dets, memory, t_select_reverse, t_bucket_disappears,
- t_named_select,
+ t_named_select, select_fixtab_owner_change,
select_fail, t_insert_new, t_repair_continuation,
otp_5340, otp_6338, otp_6842_select_1000, otp_7665,
select_mbuf_trapping,
otp_8732, meta_wb, grow_shrink, grow_pseudo_deleted,
shrink_pseudo_deleted, {group, meta_smp}, smp_insert,
- smp_fixed_delete, smp_unfix_fix, smp_select_replace,
+ smp_fixed_delete, smp_unfix_fix, smp_select_replace,
+ smp_ordered_iteration,
smp_select_delete, otp_8166, exit_large_table_owner,
exit_many_large_table_owner, exit_many_tables_owner,
exit_many_many_tables_owner, write_concurrency, heir,
@@ -146,14 +157,20 @@ all() ->
massive_ets_all,
take,
whereis_table,
- delete_unfix_race].
+ delete_unfix_race,
+ test_throughput_benchmark,
+ {group, benchmark},
+ test_table_size_concurrency,
+ test_table_memory_concurrency,
+ test_delete_table_while_size_snapshot].
+
groups() ->
[{new, [],
[default, setbag, badnew, verybadnew, named, keypos2,
privacy]},
{insert, [], [empty, badinsert]},
- {lookup, [], [time_lookup, badlookup, lookup_order]},
+ {lookup, [], [badlookup, lookup_order]},
{lookup_element, [], [lookup_element_mult]},
{delete, [],
[delete_elem, delete_tab, delete_large_tab,
@@ -174,7 +191,9 @@ groups() ->
{meta_smp, [],
[meta_lookup_unnamed_read, meta_lookup_unnamed_write,
meta_lookup_named_read, meta_lookup_named_write,
- meta_newdel_unnamed, meta_newdel_named]}].
+ meta_newdel_unnamed, meta_newdel_named]},
+ {benchmark, [],
+ [long_throughput_benchmark]}].
init_per_suite(Config) ->
erts_debug:set_internal_state(available_internal_state, true),
@@ -187,9 +206,61 @@ end_per_suite(_Config) ->
catch erts_debug:set_internal_state(available_internal_state, false),
ok.
+init_per_group(benchmark, Config) ->
+ P = self(),
+ %% Spawn owner of ETS table that is alive until end_per_group is run
+ EtsProcess =
+ spawn(
+ fun()->
+ Tab = ets:new(ets_benchmark_result_summary_tab, [public]),
+ P ! {the_table, Tab},
+ receive
+ kill -> ok
+ end
+ end),
+ Tab = receive {the_table, T} -> T end,
+ CounterNames = [nr_of_benchmarks,
+ total_throughput,
+ nr_of_set_benchmarks,
+ total_throughput_set,
+ nr_of_ordered_set_benchmarks,
+ total_throughput_ordered_set],
+ lists:foreach(fun(CtrName) ->
+ ets:insert(Tab, {CtrName, 0.0})
+ end,
+ CounterNames),
+ [{ets_benchmark_result_summary_tab, Tab},
+ {ets_benchmark_result_summary_tab_process, EtsProcess} | Config];
init_per_group(_GroupName, Config) ->
Config.
+end_per_group(benchmark, Config) ->
+ T = proplists:get_value(ets_benchmark_result_summary_tab, Config),
+ EtsProcess = proplists:get_value(ets_benchmark_result_summary_tab_process, Config),
+ Report =
+ fun(NOfBenchmarksCtr, TotThroughoutCtr, Name) ->
+ Average =
+ ets:lookup_element(T, TotThroughoutCtr, 2) /
+ ets:lookup_element(T, NOfBenchmarksCtr, 2),
+ io:format("~p ~p~n", [Name, Average]),
+ ct_event:notify(
+ #event{name = benchmark_data,
+ data = [{suite,"ets_bench"},
+ {name, Name},
+ {value, Average}]})
+ end,
+ Report(nr_of_benchmarks,
+ total_throughput,
+ "Average Throughput"),
+ Report(nr_of_set_benchmarks,
+ total_throughput_set,
+ "Average Throughput Set"),
+ Report(nr_of_ordered_set_benchmarks,
+ total_throughput_ordered_set,
+ "Average Throughput Ordered Set"),
+ ets:delete(T),
+ EtsProcess ! kill,
+ Config;
end_per_group(_GroupName, Config) ->
Config.
@@ -245,7 +316,64 @@ t_named_select_do(Opts) ->
verify_etsmem(EtsMem).
+%% Verify select and friends release fixtab as they should
+%% even when owneship is changed between traps.
+select_fixtab_owner_change(_Config) ->
+ T = ets:new(xxx, [protected]),
+ NKeys = 2000,
+ [ets:insert(T,{K,K band 7}) || K <- lists:seq(1,NKeys)],
+
+ %% Buddy and Papa will ping-pong table ownership between them
+ %% and the aim is to give Buddy the table when he is
+ %% in the middle of a yielding select* call.
+ {Buddy,_} = spawn_opt(fun() -> sfoc_buddy_loop(T, 1, undefined) end,
+ [link,monitor]),
+
+ sfoc_papa_loop(T, Buddy),
+
+ receive {'DOWN', _, process, Buddy, _} -> ok end,
+ ets:delete(T),
+ ok.
+
+sfoc_buddy_loop(T, I, State0) ->
+ receive
+ {'ETS-TRANSFER', T, Papa, _} ->
+ ets:give_away(T, Papa, State0),
+ case State0 of
+ done ->
+ ok;
+ _ ->
+ State1 = sfoc_traverse(T, I, State0),
+ %% Verify no fixation left
+ {I, false} = {I, ets:info(T, safe_fixed_monotonic_time)},
+ sfoc_buddy_loop(T, I+1, State1)
+ end
+ end.
+
+sfoc_papa_loop(T, Buddy) ->
+ ets:give_away(T, Buddy, "Catch!"),
+ receive
+ {'ETS-TRANSFER', T, Buddy, State} ->
+ case State of
+ done ->
+ ok;
+ _ ->
+ sfoc_papa_loop(T, Buddy)
+ end
+ end.
+sfoc_traverse(T, 1, S) ->
+ ets:select(T, [{{'$1',7}, [], ['$1']}]), S;
+sfoc_traverse(T, 2, S) ->
+ 0 = ets:select_count(T, [{{'$1',7}, [], [false]}]), S;
+sfoc_traverse(T, 3, _) ->
+ Limit = ets:info(T, size) div 2,
+ {_, Continuation} = ets:select(T, [{{'$1',7}, [], ['$1']}],
+ Limit),
+ Continuation;
+sfoc_traverse(_T, 4, Continuation) ->
+ _ = ets:select(Continuation),
+ done.
%% Check ets:match_spec_run/2.
t_match_spec_run(Config) when is_list(Config) ->
@@ -707,7 +835,11 @@ adjust_xmem([_T1,_T2,_T3,_T4], {A0,B0,C0,D0} = _Mem0, EstCnt) ->
{TabSz, EstSz} = erts_debug:get_internal_state('DbTable_words'),
HTabSz = TabSz + EstCnt*EstSz,
- {A0+TabSz, B0+HTabSz, C0+HTabSz, D0+HTabSz}.
+ OrdSetExtra = case erlang:system_info(wordsize) of
+ 8 -> 40; % larger stack on 64 bit architectures
+ _ -> 0
+ end,
+ {A0+TabSz+OrdSetExtra, B0+HTabSz, C0+HTabSz, D0+HTabSz}.
%% Misc. whitebox tests
t_whitebox(Config) when is_list(Config) ->
@@ -745,7 +877,7 @@ select_bound_chunk(_Config) ->
repeat_for_opts(fun select_bound_chunk_do/1, [all_types]).
select_bound_chunk_do(Opts) ->
- T = ets:new(x, Opts),
+ T = ets_new(x, Opts),
ets:insert(T, [{key, 1}]),
{[{key, 1}], '$end_of_table'} = ets:select(T, [{{key,1},[],['$_']}], 100000),
ok.
@@ -791,38 +923,42 @@ check_badarg({'EXIT', {badarg, [{M,F,A,_} | _]}}, M, F, Args) ->
%% Test ets:delete_all_objects/1.
t_delete_all_objects(Config) when is_list(Config) ->
EtsMem = etsmem(),
- repeat_for_opts(fun t_delete_all_objects_do/1),
+ repeat_for_opts_all_set_table_types(fun t_delete_all_objects_do/1),
verify_etsmem(EtsMem).
get_kept_objects(T) ->
case ets:info(T,stats) of
- false ->
- 0;
{_,_,_,_,_,_,KO} ->
- KO
+ KO;
+ _ ->
+ 0
end.
t_delete_all_objects_do(Opts) ->
- T=ets_new(x,Opts),
- filltabint(T,4000),
+ KeyRange = 4000,
+ T=ets_new(x, Opts, KeyRange),
+ filltabint(T,KeyRange),
O=ets:first(T),
ets:next(T,O),
ets:safe_fixtable(T,true),
true = ets:delete_all_objects(T),
'$end_of_table' = ets:next(T,O),
0 = ets:info(T,size),
- 4000 = get_kept_objects(T),
+ case ets:info(T,type) of
+ ordered_set -> ok;
+ _ -> KeyRange = get_kept_objects(T)
+ end,
ets:safe_fixtable(T,false),
0 = ets:info(T,size),
0 = get_kept_objects(T),
- filltabint(T,4000),
- 4000 = ets:info(T,size),
+ filltabint(T, KeyRange),
+ KeyRange = ets:info(T,size),
true = ets:delete_all_objects(T),
0 = ets:info(T,size),
ets:delete(T),
%% Test delete_all_objects is atomic
- T2 = ets:new(t_delete_all_objects, [public | Opts]),
+ T2 = ets_new(t_delete_all_objects, [public | Opts]),
Self = self(),
Inserters = [spawn_link(fun() -> inserter(T2, 100*1000, 1, Self) end) || _ <- [1,2,3,4]],
[receive {Ipid, running} -> ok end || Ipid <- Inserters],
@@ -2374,17 +2510,29 @@ write_concurrency(Config) when is_list(Config) ->
Yes6 = ets_new(foo,[duplicate_bag,protected,{write_concurrency,true}]),
No3 = ets_new(foo,[duplicate_bag,private,{write_concurrency,true}]),
- No4 = ets_new(foo,[ordered_set,public,{write_concurrency,true}]),
- No5 = ets_new(foo,[ordered_set,protected,{write_concurrency,true}]),
- No6 = ets_new(foo,[ordered_set,private,{write_concurrency,true}]),
-
- No7 = ets_new(foo,[public,{write_concurrency,false}]),
- No8 = ets_new(foo,[protected,{write_concurrency,false}]),
+ Yes7 = ets_new(foo,[ordered_set,public,{write_concurrency,true}]),
+ Yes8 = ets_new(foo,[ordered_set,protected,{write_concurrency,true}]),
+ Yes9 = ets_new(foo,[ordered_set,{write_concurrency,true}]),
+ Yes10 = ets_new(foo,[{write_concurrency,true},ordered_set,public]),
+ Yes11 = ets_new(foo,[{write_concurrency,true},ordered_set,protected]),
+ Yes12 = ets_new(foo,[set,{write_concurrency,false},
+ {write_concurrency,true},ordered_set,public]),
+ Yes13 = ets_new(foo,[private,public,set,{write_concurrency,false},
+ {write_concurrency,true},ordered_set]),
+ No4 = ets_new(foo,[ordered_set,private,{write_concurrency,true}]),
+ No5 = ets_new(foo,[ordered_set,public,{write_concurrency,false}]),
+ No6 = ets_new(foo,[ordered_set,protected,{write_concurrency,false}]),
+ No7 = ets_new(foo,[ordered_set,private,{write_concurrency,false}]),
+
+ No8 = ets_new(foo,[public,{write_concurrency,false}]),
+ No9 = ets_new(foo,[protected,{write_concurrency,false}]),
YesMem = ets:info(Yes1,memory),
NoHashMem = ets:info(No1,memory),
+ YesTreeMem = ets:info(Yes7,memory),
NoTreeMem = ets:info(No4,memory),
- io:format("YesMem=~p NoHashMem=~p NoTreeMem=~p\n",[YesMem,NoHashMem,NoTreeMem]),
+ io:format("YesMem=~p NoHashMem=~p NoTreeMem=~p YesTreeMem=~p\n",[YesMem,NoHashMem,
+ NoTreeMem,YesTreeMem]),
YesMem = ets:info(Yes2,memory),
YesMem = ets:info(Yes3,memory),
@@ -2393,13 +2541,24 @@ write_concurrency(Config) when is_list(Config) ->
YesMem = ets:info(Yes6,memory),
NoHashMem = ets:info(No2,memory),
NoHashMem = ets:info(No3,memory),
+ YesTreeMem = ets:info(Yes7,memory),
+ YesTreeMem = ets:info(Yes8,memory),
+ YesTreeMem = ets:info(Yes9,memory),
+ YesTreeMem = ets:info(Yes10,memory),
+ YesTreeMem = ets:info(Yes11,memory),
+ YesTreeMem = ets:info(Yes12,memory),
+ YesTreeMem = ets:info(Yes13,memory),
+ NoTreeMem = ets:info(No4,memory),
NoTreeMem = ets:info(No5,memory),
NoTreeMem = ets:info(No6,memory),
- NoHashMem = ets:info(No7,memory),
+ NoTreeMem = ets:info(No7,memory),
NoHashMem = ets:info(No8,memory),
+ NoHashMem = ets:info(No9,memory),
true = YesMem > NoHashMem,
true = YesMem > NoTreeMem,
+ true = YesMem > YesTreeMem,
+ true = YesTreeMem < NoTreeMem,
{'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency,foo}])),
{'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency}])),
@@ -2407,8 +2566,8 @@ write_concurrency(Config) when is_list(Config) ->
{'EXIT',{badarg,_}} = (catch ets_new(foo,[public,write_concurrency])),
lists:foreach(fun(T) -> ets:delete(T) end,
- [Yes1,Yes2,Yes3,Yes4,Yes5,Yes6,
- No1,No2,No3,No4,No5,No6,No7,No8]),
+ [Yes1,Yes2,Yes3,Yes4,Yes5,Yes6,Yes7,Yes8,Yes9,Yes10,Yes11,Yes12,Yes13,
+ No1,No2,No3,No4,No5,No6,No7,No8,No9]),
verify_etsmem(EtsMem),
ok.
@@ -3053,41 +3212,43 @@ pick_all_backwards(T) ->
%% Small test case for both set and bag type ets tables.
setbag(Config) when is_list(Config) ->
EtsMem = etsmem(),
- Set = ets_new(set,[set]),
- Bag = ets_new(bag,[bag]),
- Key = {foo,bar},
-
- %% insert some value
- ets:insert(Set,{Key,val1}),
- ets:insert(Bag,{Key,val1}),
-
- %% insert new value for same key again
- ets:insert(Set,{Key,val2}),
- ets:insert(Bag,{Key,val2}),
-
- %% check
- [{Key,val2}] = ets:lookup(Set,Key),
- [{Key,val1},{Key,val2}] = ets:lookup(Bag,Key),
-
- true = ets:delete(Set),
- true = ets:delete(Bag),
+ lists:foreach(fun(SetType) ->
+ Set = ets_new(SetType,[SetType]),
+ Bag = ets_new(bag,[bag]),
+ Key = {foo,bar},
+
+ %% insert some value
+ ets:insert(Set,{Key,val1}),
+ ets:insert(Bag,{Key,val1}),
+
+ %% insert new value for same key again
+ ets:insert(Set,{Key,val2}),
+ ets:insert(Bag,{Key,val2}),
+
+ %% check
+ [{Key,val2}] = ets:lookup(Set,Key),
+ [{Key,val1},{Key,val2}] = ets:lookup(Bag,Key),
+
+ true = ets:delete(Set),
+ true = ets:delete(Bag)
+ end, [set, cat_ord_set,stim_cat_ord_set,ordered_set]),
verify_etsmem(EtsMem).
%% Test case to check proper return values for illegal ets_new() calls.
badnew(Config) when is_list(Config) ->
EtsMem = etsmem(),
- {'EXIT',{badarg,_}} = (catch ets_new(12,[])),
- {'EXIT',{badarg,_}} = (catch ets_new({a,b},[])),
- {'EXIT',{badarg,_}} = (catch ets_new(name,[foo])),
- {'EXIT',{badarg,_}} = (catch ets_new(name,{bag})),
- {'EXIT',{badarg,_}} = (catch ets_new(name,bag)),
+ {'EXIT',{badarg,_}} = (catch ets:new(12,[])),
+ {'EXIT',{badarg,_}} = (catch ets:new({a,b},[])),
+ {'EXIT',{badarg,_}} = (catch ets:new(name,[foo])),
+ {'EXIT',{badarg,_}} = (catch ets:new(name,{bag})),
+ {'EXIT',{badarg,_}} = (catch ets:new(name,bag)),
verify_etsmem(EtsMem).
%% OTP-2314. Test case to check that a non-proper list does not
%% crash the emulator.
verybadnew(Config) when is_list(Config) ->
EtsMem = etsmem(),
- {'EXIT',{badarg,_}} = (catch ets_new(verybad,[set|protected])),
+ {'EXIT',{badarg,_}} = (catch ets:new(verybad,[set|protected])),
verify_etsmem(EtsMem).
%% Small check to see if named tables work.
@@ -3103,11 +3264,13 @@ named(Config) when is_list(Config) ->
%% Test case to check if specified keypos works.
keypos2(Config) when is_list(Config) ->
EtsMem = etsmem(),
- Tab = make_table(foo,
- [set,{keypos,2}],
- [{val,key}, {val2,key}]),
- [{val2,key}] = ets:lookup(Tab,key),
- true = ets:delete(Tab),
+ lists:foreach(fun(SetType) ->
+ Tab = make_table(foo,
+ [SetType,{keypos,2}],
+ [{val,key}, {val2,key}]),
+ [{val2,key}] = ets:lookup(Tab,key),
+ true = ets:delete(Tab)
+ end, [set, cat_ord_set,stim_cat_ord_set,ordered_set]),
verify_etsmem(EtsMem).
%% Privacy check. Check that a named(public/private/protected) table
@@ -3199,7 +3362,7 @@ rotate_tuple(Tuple, N) ->
%% Check lookup in an empty table and lookup of a non-existing key.
empty(Config) when is_list(Config) ->
- repeat_for_opts(fun empty_do/1).
+ repeat_for_opts_all_table_types(fun empty_do/1).
empty_do(Opts) ->
EtsMem = etsmem(),
@@ -3212,7 +3375,7 @@ empty_do(Opts) ->
%% Check proper return values for illegal insert operations.
badinsert(Config) when is_list(Config) ->
- repeat_for_opts(fun badinsert_do/1).
+ repeat_for_opts_all_table_types(fun badinsert_do/1).
badinsert_do(Opts) ->
EtsMem = etsmem(),
@@ -3232,31 +3395,6 @@ badinsert_do(Opts) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% Test lookup timing.
-time_lookup(Config) when is_list(Config) ->
- %% just for timing, really
- EtsMem = etsmem(),
- Values = repeat_for_opts(fun time_lookup_do/1),
- verify_etsmem(EtsMem),
- {comment,lists:flatten(io_lib:format(
- "~p ets lookups/s",[Values]))}.
-
-time_lookup_do(Opts) ->
- Tab = ets_new(foo,Opts),
- fill_tab(Tab,foo),
- ets:insert(Tab,{{a,key},foo}),
- N = 100000,
- {Time,_} = timer:tc(fun() -> time_lookup_many(N, Tab) end),
- Seconds = Time / 1000000,
- true = ets:delete(Tab),
- round(N / Seconds). % lookups/s
-
-time_lookup_many(0, _Tab) ->
- ok;
-time_lookup_many(N, Tab) ->
- ets:lookup(Tab, {a,key}),
- time_lookup_many(N-1, Tab).
-
%% Check proper return values from bad lookups in existing/non existing
%% ets tables.
badlookup(Config) when is_list(Config) ->
@@ -3433,19 +3571,29 @@ delete_tab_do(Opts) ->
%% Check that ets:delete/1 works and that other processes can run.
delete_large_tab(Config) when is_list(Config) ->
- ct:timetrap({minutes,30}), %% valgrind needs a lot
- Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)],
+ ct:timetrap({minutes,60}), %% valgrind needs a lot
+ KeyRange = 16#ffffff,
+ Data = [{erlang:phash2(I, KeyRange),I} || I <- lists:seq(1, 200000)],
EtsMem = etsmem(),
- repeat_for_opts(fun(Opts) -> delete_large_tab_do(Opts,Data) end),
+ repeat_for_opts(fun(Opts) -> delete_large_tab_do(key_range(Opts,KeyRange),
+ Data) end),
verify_etsmem(EtsMem).
delete_large_tab_do(Opts,Data) ->
delete_large_tab_1(foo_hash, Opts, Data, false),
delete_large_tab_1(foo_tree, [ordered_set | Opts], Data, false),
- delete_large_tab_1(foo_hash, Opts, Data, true).
+ delete_large_tab_1(foo_tree, [stim_cat_ord_set | Opts], Data, false),
+ delete_large_tab_1(foo_hash_fix, Opts, Data, true).
delete_large_tab_1(Name, Flags, Data, Fix) ->
+ case is_redundant_opts_combo(Flags) of
+ true -> skip;
+ false ->
+ delete_large_tab_2(Name, Flags, Data, Fix)
+ end.
+
+delete_large_tab_2(Name, Flags, Data, Fix) ->
Tab = ets_new(Name, Flags),
ets:insert(Tab, Data),
@@ -3504,18 +3652,30 @@ delete_large_tab_1(Name, Flags, Data, Fix) ->
%% Delete a large name table and try to create a new table with
%% the same name in another process.
delete_large_named_table(Config) when is_list(Config) ->
- Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)],
+ KeyRange = 16#ffffff,
+ Data = [{erlang:phash2(I, KeyRange),I} || I <- lists:seq(1, 200000)],
EtsMem = etsmem(),
- repeat_for_opts(fun(Opts) -> delete_large_named_table_do(Opts,Data) end),
+ repeat_for_opts(fun(Opts) ->
+ delete_large_named_table_do(key_range(Opts,KeyRange),
+ Data)
+ end),
verify_etsmem(EtsMem),
ok.
delete_large_named_table_do(Opts,Data) ->
delete_large_named_table_1(foo_hash, [named_table | Opts], Data, false),
delete_large_named_table_1(foo_tree, [ordered_set,named_table | Opts], Data, false),
+ delete_large_named_table_1(foo_tree, [stim_cat_ord_set,named_table | Opts], Data, false),
delete_large_named_table_1(foo_hash, [named_table | Opts], Data, true).
delete_large_named_table_1(Name, Flags, Data, Fix) ->
+ case is_redundant_opts_combo(Flags) of
+ true -> skip;
+ false ->
+ delete_large_named_table_2(Name, Flags, Data, Fix)
+ end.
+
+delete_large_named_table_2(Name, Flags, Data, Fix) ->
Tab = ets_new(Name, Flags),
ets:insert(Tab, Data),
@@ -3539,8 +3699,12 @@ delete_large_named_table_1(Name, Flags, Data, Fix) ->
%% Delete a large table, and kill the process during the delete.
evil_delete(Config) when is_list(Config) ->
- Data = [{I,I*I} || I <- lists:seq(1, 100000)],
- repeat_for_opts(fun(Opts) -> evil_delete_do(Opts,Data) end).
+ KeyRange = 100000,
+ Data = [{I,I*I} || I <- lists:seq(1, KeyRange)],
+ repeat_for_opts(fun(Opts) ->
+ evil_delete_do(key_range(Opts,KeyRange),
+ Data)
+ end).
evil_delete_do(Opts,Data) ->
EtsMem = etsmem(),
@@ -3550,16 +3714,27 @@ evil_delete_do(Opts,Data) ->
verify_etsmem(EtsMem),
evil_delete_owner(foo_tree, [ordered_set | Opts], Data, false),
verify_etsmem(EtsMem),
+ evil_delete_owner(foo_catree, [stim_cat_ord_set | Opts], Data, false),
+ verify_etsmem(EtsMem),
TabA = evil_delete_not_owner(foo_hash, Opts, Data, false),
verify_etsmem(EtsMem),
TabB = evil_delete_not_owner(foo_hash, Opts, Data, true),
verify_etsmem(EtsMem),
TabC = evil_delete_not_owner(foo_tree, [ordered_set | Opts], Data, false),
verify_etsmem(EtsMem),
+ TabD = evil_delete_not_owner(foo_catree, [stim_cat_ord_set | Opts], Data, false),
+ verify_etsmem(EtsMem),
lists:foreach(fun(T) -> undefined = ets:info(T) end,
- [TabA,TabB,TabC]).
+ [TabA,TabB,TabC,TabD]).
evil_delete_not_owner(Name, Flags, Data, Fix) ->
+ case is_redundant_opts_combo(Flags) of
+ true -> skip;
+ false ->
+ evil_delete_not_owner_1(Name, Flags, Data, Fix)
+ end.
+
+evil_delete_not_owner_1(Name, Flags, Data, Fix) ->
io:format("Not owner: ~p, fix = ~p", [Name,Fix]),
Tab = ets_new(Name, [public|Flags]),
ets:insert(Tab, Data),
@@ -3585,6 +3760,13 @@ evil_delete_not_owner(Name, Flags, Data, Fix) ->
Tab.
evil_delete_owner(Name, Flags, Data, Fix) ->
+ case is_redundant_opts_combo(Flags) of
+ true -> skip;
+ false ->
+ evil_delete_owner_1(Name, Flags, Data, Fix)
+ end.
+
+evil_delete_owner_1(Name, Flags, Data, Fix) ->
Fun = fun() ->
Tab = ets_new(Name, [public|Flags]),
ets:insert(Tab, Data),
@@ -3772,7 +3954,7 @@ verify_rescheduling_exit(Config, ForEachData, Flags, Fix, NOTabs, NOProcs) ->
%% Make sure that slots for ets tables are cleared properly.
table_leak(Config) when is_list(Config) ->
- repeat_for_opts(fun(Opts) -> table_leak_1(Opts,20000) end).
+ repeat_for_opts_all_non_stim_table_types(fun(Opts) -> table_leak_1(Opts,20000) end).
table_leak_1(_,0) -> ok;
table_leak_1(Opts,N) ->
@@ -3835,7 +4017,7 @@ match_delete3_do(Opts) ->
%% Test ets:first/1 & ets:next/2.
firstnext(Config) when is_list(Config) ->
- repeat_for_opts(fun firstnext_do/1).
+ repeat_for_opts_all_set_table_types(fun firstnext_do/1).
firstnext_do(Opts) ->
EtsMem = etsmem(),
@@ -3857,15 +4039,20 @@ firstnext_collect(Tab,Key,List) ->
%% Tests ets:first/1 & ets:next/2.
firstnext_concurrent(Config) when is_list(Config) ->
- register(master, self()),
- ets_init(?MODULE, 20),
- [dynamic_go() || _ <- lists:seq(1, 2)],
- receive
- after 5000 -> ok
- end.
+ lists:foreach(
+ fun(TableType) ->
+ register(master, self()),
+ TableName = list_to_atom(atom_to_list(?MODULE) ++ atom_to_list(TableType)),
+ ets_init(TableName, 20, TableType),
+ [dynamic_go(TableName) || _ <- lists:seq(1, 2)],
+ receive
+ after 5000 -> ok
+ end,
+ unregister(master)
+ end, repeat_for_opts_atom2list(ord_set_types)).
-ets_init(Tab, N) ->
- ets_new(Tab, [named_table,public,ordered_set]),
+ets_init(Tab, N, TableType) ->
+ ets_new(Tab, [named_table,public,TableType]),
cycle(Tab, lists:seq(1,N+1)).
cycle(_Tab, [H|T]) when H > length(T)-> ok;
@@ -3873,9 +4060,9 @@ cycle(Tab, L) ->
ets:insert(Tab,list_to_tuple(L)),
cycle(Tab, tl(L)++[hd(L)]).
-dynamic_go() -> my_spawn_link(fun dynamic_init/0).
+dynamic_go(TableName) -> my_spawn_link(fun() -> dynamic_init(TableName) end).
-dynamic_init() -> [dyn_lookup(?MODULE) || _ <- lists:seq(1, 10)].
+dynamic_init(TableName) -> [dyn_lookup(TableName) || _ <- lists:seq(1, 10)].
dyn_lookup(T) -> dyn_lookup(T, ets:first(T)).
@@ -3893,7 +4080,7 @@ dyn_lookup(T, K) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
slot(Config) when is_list(Config) ->
- repeat_for_opts(fun slot_do/1).
+ repeat_for_opts_all_set_table_types(fun slot_do/1).
slot_do(Opts) ->
EtsMem = etsmem(),
@@ -3901,6 +4088,11 @@ slot_do(Opts) ->
fill_tab(Tab,foo),
Elts = ets:info(Tab,size),
Elts = slot_loop(Tab,0,0),
+ case ets:info(Tab, type) of
+ ordered_set ->
+ '$end_of_table' = ets:slot(Tab,Elts);
+ _ -> ok
+ end,
true = ets:delete(Tab),
verify_etsmem(EtsMem).
@@ -3918,7 +4110,7 @@ slot_loop(Tab,SlotNo,EltsSoFar) ->
match1(Config) when is_list(Config) ->
- repeat_for_opts(fun match1_do/1).
+ repeat_for_opts_all_set_table_types(fun match1_do/1).
match1_do(Opts) ->
EtsMem = etsmem(),
@@ -3981,7 +4173,7 @@ match2_do(Opts) ->
%% Some ets:match_object tests.
match_object(Config) when is_list(Config) ->
- repeat_for_opts(fun match_object_do/1).
+ repeat_for_opts_all_set_table_types(fun match_object_do/1).
match_object_do(Opts) ->
EtsMem = etsmem(),
@@ -4081,23 +4273,16 @@ match_object_do(Opts) ->
%% Tests that db_match_object does not generate a `badarg' when
%% resuming a search with no previous matches.
match_object2(Config) when is_list(Config) ->
- repeat_for_opts(fun match_object2_do/1).
+ repeat_for_opts_all_table_types(fun match_object2_do/1).
match_object2_do(Opts) ->
EtsMem = etsmem(),
- Tab = ets_new(foo, [bag, {keypos, 2} | Opts]),
- fill_tab2(Tab, 0, 13005), % match_db_object does 1000
+ KeyRange = 13005,
+ Tab = ets_new(foo, [{keypos, 2} | Opts], KeyRange),
+ fill_tab2(Tab, 0, KeyRange), % match_db_object does 1000
% elements per pass, might
% change in the future.
- case catch ets:match_object(Tab, {hej, '$1'}) of
- {'EXIT', _} ->
- ets:delete(Tab),
- ct:fail("match_object EXIT:ed");
- [] ->
- io:format("Nothing matched.");
- List ->
- io:format("Matched:~p~n",[List])
- end,
+ [] = ets:match_object(Tab, {hej, '$1'}),
ets:delete(Tab),
verify_etsmem(EtsMem).
@@ -4106,18 +4291,21 @@ match_object2_do(Opts) ->
%% OTP-3319. Test tab2list.
tab2list(Config) when is_list(Config) ->
- EtsMem = etsmem(),
- Tab = make_table(foo,
- [ordered_set],
- [{a,b}, {c,b}, {b,b}, {a,c}]),
- [{a,c},{b,b},{c,b}] = ets:tab2list(Tab),
- true = ets:delete(Tab),
- verify_etsmem(EtsMem).
+ repeat_for_all_ord_set_table_types(
+ fun(Opts) ->
+ EtsMem = etsmem(),
+ Tab = make_table(foo,
+ Opts,
+ [{a,b}, {c,b}, {b,b}, {a,c}]),
+ [{a,c},{b,b},{c,b}] = ets:tab2list(Tab),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem)
+ end).
%% Simple general small test. If this fails, ets is in really bad
%% shape.
misc1(Config) when is_list(Config) ->
- repeat_for_opts(fun misc1_do/1).
+ repeat_for_opts_all_table_types(fun misc1_do/1).
misc1_do(Opts) ->
EtsMem = etsmem(),
@@ -4135,7 +4323,7 @@ misc1_do(Opts) ->
%% Check the safe_fixtable function.
safe_fixtable(Config) when is_list(Config) ->
- repeat_for_opts(fun safe_fixtable_do/1).
+ repeat_for_opts_all_table_types(fun safe_fixtable_do/1).
safe_fixtable_do(Opts) ->
EtsMem = etsmem(),
@@ -4193,10 +4381,42 @@ safe_fixtable_do(Opts) ->
%% Tests ets:info result for required tuples.
info(Config) when is_list(Config) ->
- repeat_for_opts(fun info_do/1).
+ repeat_for_opts_all_table_types(fun info_do/1).
info_do(Opts) ->
EtsMem = etsmem(),
+ TableType = lists:foldl(
+ fun(Item, Curr) ->
+ case Item of
+ set -> set;
+ ordered_set -> ordered_set;
+ cat_ord_set -> ordered_set;
+ stim_cat_ord_set -> ordered_set;
+ bag -> bag;
+ duplicate_bag -> duplicate_bag;
+ _ -> Curr
+ end
+ end, set, Opts),
+ PublicOrCurr =
+ fun(Curr) ->
+ case lists:member({write_concurrency, false}, Opts) or
+ lists:member(private, Opts) or
+ lists:member(protected, Opts) of
+ true -> Curr;
+ false -> public
+ end
+ end,
+ Protection = lists:foldl(
+ fun(Item, Curr) ->
+ case Item of
+ public -> public;
+ protected -> protected;
+ private -> private;
+ cat_ord_set -> PublicOrCurr(Curr); %% Special items
+ stim_cat_ord_set -> PublicOrCurr(Curr);
+ _ -> Curr
+ end
+ end, protected, Opts),
MeMyselfI=self(),
ThisNode=node(),
Tab = ets_new(foobar, [{keypos, 2} | Opts]),
@@ -4210,9 +4430,9 @@ info_do(Opts) ->
{value, {size, 0}} = lists:keysearch(size, 1, Res),
{value, {node, ThisNode}} = lists:keysearch(node, 1, Res),
{value, {named_table, false}} = lists:keysearch(named_table, 1, Res),
- {value, {type, set}} = lists:keysearch(type, 1, Res),
+ {value, {type, TableType}} = lists:keysearch(type, 1, Res),
{value, {keypos, 2}} = lists:keysearch(keypos, 1, Res),
- {value, {protection, protected}} =
+ {value, {protection, Protection}} =
lists:keysearch(protection, 1, Res),
{value, {id, Tab}} = lists:keysearch(id, 1, Res),
true = ets:delete(Tab),
@@ -4224,6 +4444,131 @@ info_do(Opts) ->
undefined = ets:info(non_existing_table_xxyy,safe_fixed),
verify_etsmem(EtsMem).
+size_loop(_T, 0, _, _) ->
+ ok;
+size_loop(T, I, PrevSize, WhatToTest) ->
+ Size = ets:info(T, WhatToTest),
+ case Size < PrevSize of
+ true -> ct:fail("Bad ets:info/2");
+ _ -> ok
+ end,
+ size_loop(T, I -1, Size, WhatToTest).
+
+add_loop(_T, 0) ->
+ ok;
+add_loop(T, I) ->
+ ets:insert(T, {I}),
+ add_loop(T, I -1).
+
+
+test_table_counter_concurrency(WhatToTest) ->
+ IntStatePrevOn =
+ erts_debug:set_internal_state(available_internal_state, true),
+ ItemsToAdd = 1000000,
+ SizeLoopSize = 1000,
+ T = ets:new(k, [public, ordered_set, {write_concurrency, true}]),
+ erts_debug:set_internal_state(ets_debug_random_split_join, {T, false}),
+ 0 = ets:info(T, size),
+ P = self(),
+ SpawnedSizeProcs =
+ [spawn_link(fun() ->
+ size_loop(T, SizeLoopSize, 0, WhatToTest),
+ P ! done
+ end)
+ || _ <- lists:seq(1, 6)],
+ spawn_link(fun() ->
+ add_loop(T, ItemsToAdd),
+ P ! done_add
+ end),
+ [receive
+ done -> ok;
+ done_add -> ok
+ end
+ || _ <- [ok|SpawnedSizeProcs]],
+ case WhatToTest =:= size of
+ true ->
+ ItemsToAdd = ets:info(T, size);
+ _ ->
+ ok
+ end,
+ erts_debug:set_internal_state(available_internal_state, IntStatePrevOn),
+ ok.
+
+test_table_size_concurrency(Config) when is_list(Config) ->
+ test_table_counter_concurrency(size).
+
+test_table_memory_concurrency(Config) when is_list(Config) ->
+ test_table_counter_concurrency(memory).
+
+%% Tests that calling the ets:delete operation on a table T with
+%% decentralized counters works while ets:info(T, size) operations are
+%% active
+test_delete_table_while_size_snapshot(Config) when is_list(Config) ->
+ %% Run test case in a slave node as other test suites in stdlib
+ %% depend on that pids are ordered in creation order which is no
+ %% longer the case when many processes have been started before
+ Node = start_slave(),
+ ok = rpc:call(Node, ?MODULE, test_delete_table_while_size_snapshot_helper, []),
+ test_server:stop_node(Node),
+ ok.
+
+test_delete_table_while_size_snapshot_helper()->
+ TopParent = self(),
+ repeat_par(
+ fun() ->
+ Table = ets:new(t, [public, ordered_set,
+ {write_concurrency, true}]),
+ Parent = self(),
+ NrOfSizeProcs = 100,
+ Pids = [ spawn(fun()-> size_process(Table, Parent) end)
+ || _ <- lists:seq(1, NrOfSizeProcs)],
+ timer:sleep(1),
+ ets:delete(Table),
+ [receive
+ table_gone -> ok;
+ Problem -> TopParent ! Problem
+ end || _ <- Pids]
+ end,
+ 15000),
+ receive
+ Problem -> throw(Problem)
+ after 0 -> ok
+ end.
+
+size_process(Table, Parent) ->
+ try ets:info(Table, size) of
+ N when is_integer(N) ->
+ size_process(Table, Parent);
+ undefined -> Parent ! table_gone;
+ E -> Parent ! {got_unexpected, E}
+ catch
+ E -> Parent ! {got_unexpected_exception, E}
+ end.
+
+start_slave() ->
+ MicroSecs = erlang:monotonic_time(),
+ Name = "ets_" ++ integer_to_list(MicroSecs),
+ Pa = filename:dirname(code:which(?MODULE)),
+ {ok, Node} = test_server:start_node(list_to_atom(Name), slave, [{args, "-pa " ++ Pa}]),
+ Node.
+
+repeat_par(FunToRepeat, NrOfTimes) ->
+ repeat_par_help(FunToRepeat, NrOfTimes, NrOfTimes).
+
+repeat_par_help(_FunToRepeat, 0, OrgNrOfTimes) ->
+ repeat(fun()-> receive done -> ok end end, OrgNrOfTimes);
+repeat_par_help(FunToRepeat, NrOfTimes, OrgNrOfTimes) ->
+ Parent = self(),
+ case NrOfTimes rem 5 of
+ 0 -> timer:sleep(1);
+ _ -> ok
+ end,
+ spawn(fun()->
+ FunToRepeat(),
+ Parent ! done
+ end),
+ repeat_par_help(FunToRepeat, NrOfTimes-1, OrgNrOfTimes).
+
%% Test various duplicate_bags stuff.
dups(Config) when is_list(Config) ->
repeat_for_opts(fun dups_do/1).
@@ -4257,20 +4602,29 @@ dups_do(Opts) ->
%% Test the ets:tab2file function on an empty ets table.
tab2file(Config) when is_list(Config) ->
FName = filename:join([proplists:get_value(priv_dir, Config),"tab2file_case"]),
- tab2file_do(FName, []),
- tab2file_do(FName, [{sync,true}]),
- tab2file_do(FName, [{sync,false}]),
- {'EXIT',{{badmatch,{error,_}},_}} = (catch tab2file_do(FName, [{sync,yes}])),
- {'EXIT',{{badmatch,{error,_}},_}} = (catch tab2file_do(FName, [sync])),
+ tab2file_do(FName, [], set),
+ tab2file_do(FName, [], ordered_set),
+ tab2file_do(FName, [], cat_ord_set),
+ tab2file_do(FName, [], stim_cat_ord_set),
+ tab2file_do(FName, [{sync,true}], set),
+ tab2file_do(FName, [{sync,false}], set),
+ {'EXIT',{{badmatch,{error,_}},_}} = (catch tab2file_do(FName, [{sync,yes}], set)),
+ {'EXIT',{{badmatch,{error,_}},_}} = (catch tab2file_do(FName, [sync], set)),
ok.
-tab2file_do(FName, Opts) ->
+tab2file_do(FName, Opts, TableType) ->
%% Write an empty ets table to a file, read back and check properties.
- Tab = ets_new(ets_SUITE_foo_tab, [named_table, set, public,
+ Tab = ets_new(ets_SUITE_foo_tab, [named_table, TableType, public,
{keypos, 2},
compressed,
{write_concurrency,true},
{read_concurrency,true}]),
+ ActualTableType =
+ case TableType of
+ cat_ord_set -> ordered_set;
+ stim_cat_ord_set -> ordered_set;
+ _ -> TableType
+ end,
catch file:delete(FName),
Res = ets:tab2file(Tab, FName, Opts),
true = ets:delete(Tab),
@@ -4281,7 +4635,7 @@ tab2file_do(FName, Opts) ->
public = ets:info(Tab2, protection),
true = ets:info(Tab2, named_table),
2 = ets:info(Tab2, keypos),
- set = ets:info(Tab2, type),
+ ActualTableType = ets:info(Tab2, type),
true = ets:info(Tab2, compressed),
Smp = erlang:system_info(smp_support),
Smp = ets:info(Tab2, read_concurrency),
@@ -4294,14 +4648,15 @@ tab2file_do(FName, Opts) ->
tab2file2(Config) when is_list(Config) ->
repeat_for_opts(fun(Opts) ->
tab2file2_do(Opts, Config)
- end, [[set,bag],compressed]).
+ end, [[stim_cat_ord_set,cat_ord_set,set,bag],compressed]).
tab2file2_do(Opts, Config) ->
EtsMem = etsmem(),
- Tab = ets_new(ets_SUITE_foo_tab, [named_table, private,
- {keypos, 2} | Opts]),
+ KeyRange = 10000,
+ Tab = ets_new(ets_SUITE_foo_tab, [named_table, private, {keypos, 2} | Opts],
+ KeyRange),
FName = filename:join([proplists:get_value(priv_dir, Config),"tab2file2_case"]),
- ok = fill_tab2(Tab, 0, 10000), % Fill up the table (grucho mucho!)
+ ok = fill_tab2(Tab, 0, KeyRange), % Fill up the table (grucho mucho!)
Len = length(ets:tab2list(Tab)),
Mem = ets:info(Tab, memory),
Type = ets:info(Tab, type),
@@ -4355,13 +4710,14 @@ fill_tab2(Tab, Val, Num) ->
%% Test verification of tables with object count extended_info.
tabfile_ext1(Config) when is_list(Config) ->
- repeat_for_opts(fun(Opts) -> tabfile_ext1_do(Opts, Config) end).
+ repeat_for_opts_all_set_table_types(fun(Opts) -> tabfile_ext1_do(Opts, Config) end).
tabfile_ext1_do(Opts,Config) ->
FName = filename:join([proplists:get_value(priv_dir, Config),"nisse.dat"]),
FName2 = filename:join([proplists:get_value(priv_dir, Config),"countflip.dat"]),
- L = lists:seq(1,10),
- T = ets_new(x,Opts),
+ KeyRange = 10,
+ L = lists:seq(1,KeyRange),
+ T = ets_new(x,Opts,KeyRange),
Name = make_ref(),
[ets:insert(T,{X,integer_to_list(X)}) || X <- L],
ok = ets:tab2file(T,FName,[{extended_info,[object_count]}]),
@@ -4393,13 +4749,14 @@ tabfile_ext1_do(Opts,Config) ->
%% Test verification of tables with md5sum extended_info.
tabfile_ext2(Config) when is_list(Config) ->
- repeat_for_opts(fun(Opts) -> tabfile_ext2_do(Opts,Config) end).
+ repeat_for_opts_all_set_table_types(fun(Opts) -> tabfile_ext2_do(Opts,Config) end).
tabfile_ext2_do(Opts,Config) ->
FName = filename:join([proplists:get_value(priv_dir, Config),"olle.dat"]),
FName2 = filename:join([proplists:get_value(priv_dir, Config),"bitflip.dat"]),
- L = lists:seq(1,10),
- T = ets_new(x,Opts),
+ KeyRange = 10,
+ L = lists:seq(1, KeyRange),
+ T = ets_new(x, Opts, KeyRange),
Name = make_ref(),
[ets:insert(T,{X,integer_to_list(X)}) || X <- L],
ok = ets:tab2file(T,FName,[{extended_info,[md5sum]}]),
@@ -4430,71 +4787,77 @@ tabfile_ext2_do(Opts,Config) ->
%% Test verification of (named) tables without extended info.
tabfile_ext3(Config) when is_list(Config) ->
- FName = filename:join([proplists:get_value(priv_dir, Config),"namn.dat"]),
- FName2 = filename:join([proplists:get_value(priv_dir, Config),"ncountflip.dat"]),
- L = lists:seq(1,10),
- Name = make_ref(),
- ?MODULE = ets_new(?MODULE,[named_table]),
- [ets:insert(?MODULE,{X,integer_to_list(X)}) || X <- L],
- ets:tab2file(?MODULE,FName),
- {error,cannot_create_table} = ets:file2tab(FName),
- true = ets:delete(?MODULE),
- {ok,?MODULE} = ets:file2tab(FName),
- true = ets:delete(?MODULE),
- disk_log:open([{name,Name},{file,FName}]),
- {_,[H2|T2]} = disk_log:chunk(Name,start),
- disk_log:close(Name),
- NewT2=lists:keydelete(8,1,T2),
- file:delete(FName2),
- disk_log:open([{name,Name},{file,FName2},{mode,read_write}]),
- disk_log:log_terms(Name,[H2|NewT2]),
- disk_log:close(Name),
- 9 = length(ets:tab2list(element(2,ets:file2tab(FName2)))),
- true = ets:delete(?MODULE),
- {error,invalid_object_count} = ets:file2tab(FName2,[{verify,true}]),
- {'EXIT',_} = (catch ets:delete(?MODULE)),
- {ok,_} = ets:tabfile_info(FName2),
- {ok,_} = ets:tabfile_info(FName),
- file:delete(FName),
- file:delete(FName2),
+ repeat_for_all_set_table_types(
+ fun(Opts) ->
+ FName = filename:join([proplists:get_value(priv_dir, Config),"namn.dat"]),
+ FName2 = filename:join([proplists:get_value(priv_dir, Config),"ncountflip.dat"]),
+ L = lists:seq(1,10),
+ Name = make_ref(),
+ ?MODULE = ets_new(?MODULE,[named_table|Opts]),
+ [ets:insert(?MODULE,{X,integer_to_list(X)}) || X <- L],
+ ets:tab2file(?MODULE,FName),
+ {error,cannot_create_table} = ets:file2tab(FName),
+ true = ets:delete(?MODULE),
+ {ok,?MODULE} = ets:file2tab(FName),
+ true = ets:delete(?MODULE),
+ disk_log:open([{name,Name},{file,FName}]),
+ {_,[H2|T2]} = disk_log:chunk(Name,start),
+ disk_log:close(Name),
+ NewT2=lists:keydelete(8,1,T2),
+ file:delete(FName2),
+ disk_log:open([{name,Name},{file,FName2},{mode,read_write}]),
+ disk_log:log_terms(Name,[H2|NewT2]),
+ disk_log:close(Name),
+ 9 = length(ets:tab2list(element(2,ets:file2tab(FName2)))),
+ true = ets:delete(?MODULE),
+ {error,invalid_object_count} = ets:file2tab(FName2,[{verify,true}]),
+ {'EXIT',_} = (catch ets:delete(?MODULE)),
+ {ok,_} = ets:tabfile_info(FName2),
+ {ok,_} = ets:tabfile_info(FName),
+ file:delete(FName),
+ file:delete(FName2)
+ end),
ok.
%% Tests verification of large table with md5 sum.
tabfile_ext4(Config) when is_list(Config) ->
- FName = filename:join([proplists:get_value(priv_dir, Config),"bauta.dat"]),
- LL = lists:seq(1,10000),
- TL = ets_new(x,[]),
- Name2 = make_ref(),
- [ets:insert(TL,{X,integer_to_list(X)}) || X <- LL],
- ok = ets:tab2file(TL,FName,[{extended_info,[md5sum]}]),
- {ok, Name2} = disk_log:open([{name, Name2}, {file, FName},
- {mode, read_only}]),
- {C,[_|_]} = disk_log:chunk(Name2,start),
- {_,[_|_]} = disk_log:chunk(Name2,C),
- disk_log:close(Name2),
- true = lists:sort(ets:tab2list(TL)) =:=
- lists:sort(ets:tab2list(element(2,ets:file2tab(FName)))),
- Res = [begin
- {ok,FD} = file:open(FName,[binary,read,write]),
- {ok, Bin} = file:pread(FD,0,1000),
- <<B1:N/binary,Ch:8,B2/binary>> = Bin,
- Ch2 = (Ch + 1) rem 255,
- Bin2 = <<B1/binary,Ch2:8,B2/binary>>,
- ok = file:pwrite(FD,0,Bin2),
- ok = file:close(FD),
- X = case ets:file2tab(FName) of
- {ok,TL2} ->
- true = lists:sort(ets:tab2list(TL)) =/=
- lists:sort(ets:tab2list(TL2));
- _ ->
- totally_broken
- end,
- {error,Y} = ets:file2tab(FName,[{verify,true}]),
- ets:tab2file(TL,FName,[{extended_info,[md5sum]}]),
- {X,Y}
- end || N <- lists:seq(500,600)],
- io:format("~p~n",[Res]),
- file:delete(FName),
+ repeat_for_all_set_table_types(
+ fun(Opts) ->
+ FName = filename:join([proplists:get_value(priv_dir, Config),"bauta.dat"]),
+ LL = lists:seq(1,10000),
+ TL = ets_new(x,Opts),
+ Name2 = make_ref(),
+ [ets:insert(TL,{X,integer_to_list(X)}) || X <- LL],
+ ok = ets:tab2file(TL,FName,[{extended_info,[md5sum]}]),
+ {ok, Name2} = disk_log:open([{name, Name2}, {file, FName},
+ {mode, read_only}]),
+ {C,[_|_]} = disk_log:chunk(Name2,start),
+ {_,[_|_]} = disk_log:chunk(Name2,C),
+ disk_log:close(Name2),
+ true = lists:sort(ets:tab2list(TL)) =:=
+ lists:sort(ets:tab2list(element(2,ets:file2tab(FName)))),
+ Res = [begin
+ {ok,FD} = file:open(FName,[binary,read,write]),
+ {ok, Bin} = file:pread(FD,0,1000),
+ <<B1:N/binary,Ch:8,B2/binary>> = Bin,
+ Ch2 = (Ch + 1) rem 255,
+ Bin2 = <<B1/binary,Ch2:8,B2/binary>>,
+ ok = file:pwrite(FD,0,Bin2),
+ ok = file:close(FD),
+ X = case ets:file2tab(FName) of
+ {ok,TL2} ->
+ true = lists:sort(ets:tab2list(TL)) =/=
+ lists:sort(ets:tab2list(TL2));
+ _ ->
+ totally_broken
+ end,
+ {error,Y} = ets:file2tab(FName,[{verify,true}]),
+ ets:tab2file(TL,FName,[{extended_info,[md5sum]}]),
+ {X,Y}
+ end || N <- lists:seq(500,600)],
+ io:format("~p~n",[Res]),
+ file:delete(FName)
+ end),
ok.
%% Test that no disk_log is left open when file has been corrupted.
@@ -4558,13 +4921,14 @@ make_sub_binary(List, Num) when is_list(List) ->
%% Perform multiple lookups for every key in a large table.
heavy_lookup(Config) when is_list(Config) ->
- repeat_for_opts(fun heavy_lookup_do/1).
+ repeat_for_opts_all_set_table_types(fun heavy_lookup_do/1).
heavy_lookup_do(Opts) ->
EtsMem = etsmem(),
- Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]),
- ok = fill_tab2(Tab, 0, 7000),
- _ = [do_lookup(Tab, 6999) || _ <- lists:seq(1, 50)],
+ KeyRange = 7000,
+ Tab = ets_new(foobar_table, [{keypos, 2} | Opts], KeyRange),
+ ok = fill_tab2(Tab, 0, KeyRange),
+ _ = [do_lookup(Tab, KeyRange-1) || _ <- lists:seq(1, 50)],
true = ets:delete(Tab),
verify_etsmem(EtsMem).
@@ -4581,15 +4945,16 @@ do_lookup(Tab, N) ->
%% Perform multiple lookups for every element in a large table.
heavy_lookup_element(Config) when is_list(Config) ->
- repeat_for_opts(fun heavy_lookup_element_do/1).
+ repeat_for_opts_all_set_table_types(fun heavy_lookup_element_do/1).
heavy_lookup_element_do(Opts) ->
EtsMem = etsmem(),
- Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]),
- ok = fill_tab2(Tab, 0, 7000),
+ KeyRange = 7000,
+ Tab = ets_new(foobar_table, [{keypos, 2} | Opts], KeyRange),
+ ok = fill_tab2(Tab, 0, KeyRange),
%% lookup ALL elements 50 times
Laps = 50 div syrup_factor(),
- _ = [do_lookup_element(Tab, 6999, 1) || _ <- lists:seq(1, Laps)],
+ _ = [do_lookup_element(Tab, KeyRange-1, 1) || _ <- lists:seq(1, Laps)],
true = ets:delete(Tab),
verify_etsmem(EtsMem).
@@ -4608,15 +4973,15 @@ do_lookup_element(Tab, N, M) ->
heavy_concurrent(Config) when is_list(Config) ->
- ct:timetrap({minutes,30}), %% valgrind needs a lot of time
- repeat_for_opts(fun do_heavy_concurrent/1).
+ ct:timetrap({minutes,120}), %% valgrind needs a lot of time
+ repeat_for_opts_all_set_table_types(fun do_heavy_concurrent/1).
do_heavy_concurrent(Opts) ->
- Size = 10000,
+ KeyRange = 10000,
Laps = 10000 div syrup_factor(),
EtsMem = etsmem(),
- Tab = ets_new(blupp, [set, public, {keypos, 2} | Opts]),
- ok = fill_tab2(Tab, 0, Size),
+ Tab = ets_new(blupp, [public, {keypos, 2} | Opts], KeyRange),
+ ok = fill_tab2(Tab, 0, KeyRange),
Procs = lists:map(
fun (N) ->
my_spawn_link(
@@ -4649,48 +5014,68 @@ do_heavy_concurrent_proc(Tab, N, Offs) ->
fold_empty(Config) when is_list(Config) ->
- EtsMem = etsmem(),
- Tab = make_table(a, [], []),
- [] = ets:foldl(fun(_X) -> exit(hej) end, [], Tab),
- [] = ets:foldr(fun(_X) -> exit(hej) end, [], Tab),
- true = ets:delete(Tab),
- verify_etsmem(EtsMem).
+ repeat_for_opts_all_set_table_types(
+ fun(Opts) ->
+ EtsMem = etsmem(),
+ Tab = make_table(a, Opts, []),
+ [] = ets:foldl(fun(_X) -> exit(hej) end, [], Tab),
+ [] = ets:foldr(fun(_X) -> exit(hej) end, [], Tab),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem)
+ end),
+ ok.
foldl(Config) when is_list(Config) ->
- EtsMem = etsmem(),
- L = [{a,1}, {c,3}, {b,2}],
- LS = lists:sort(L),
- Tab = make_table(a, [bag], L),
- LS = lists:sort(ets:foldl(fun(E,A) -> [E|A] end, [], Tab)),
- true = ets:delete(Tab),
- verify_etsmem(EtsMem).
+ repeat_for_opts_all_table_types(
+ fun(Opts) ->
+ EtsMem = etsmem(),
+ L = [{a,1}, {c,3}, {b,2}],
+ LS = lists:sort(L),
+ Tab = make_table(a, Opts, L),
+ LS = lists:sort(ets:foldl(fun(E,A) -> [E|A] end, [], Tab)),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem)
+ end),
+ ok.
foldr(Config) when is_list(Config) ->
- EtsMem = etsmem(),
- L = [{a,1}, {c,3}, {b,2}],
- LS = lists:sort(L),
- Tab = make_table(a, [bag], L),
- LS = lists:sort(ets:foldr(fun(E,A) -> [E|A] end, [], Tab)),
- true = ets:delete(Tab),
- verify_etsmem(EtsMem).
+ repeat_for_opts_all_table_types(
+ fun(Opts) ->
+ EtsMem = etsmem(),
+ L = [{a,1}, {c,3}, {b,2}],
+ LS = lists:sort(L),
+ Tab = make_table(a, Opts, L),
+ LS = lists:sort(ets:foldr(fun(E,A) -> [E|A] end, [], Tab)),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem)
+ end),
+ ok.
foldl_ordered(Config) when is_list(Config) ->
- EtsMem = etsmem(),
- L = [{a,1}, {c,3}, {b,2}],
- LS = lists:sort(L),
- Tab = make_table(a, [ordered_set], L),
- LS = lists:reverse(ets:foldl(fun(E,A) -> [E|A] end, [], Tab)),
- true = ets:delete(Tab),
- verify_etsmem(EtsMem).
+ repeat_for_opts_all_ord_set_table_types(
+ fun(Opts) ->
+ EtsMem = etsmem(),
+ L = [{a,1}, {c,3}, {b,2}],
+ LS = lists:sort(L),
+ Tab = make_table(a, Opts, L),
+ LS = lists:reverse(ets:foldl(fun(E,A) -> [E|A] end, [], Tab)),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem)
+ end),
+ ok.
foldr_ordered(Config) when is_list(Config) ->
- EtsMem = etsmem(),
- L = [{a,1}, {c,3}, {b,2}],
- LS = lists:sort(L),
- Tab = make_table(a, [ordered_set], L),
- LS = ets:foldr(fun(E,A) -> [E|A] end, [], Tab),
- true = ets:delete(Tab),
- verify_etsmem(EtsMem).
+ repeat_for_opts_all_ord_set_table_types(
+ fun(Opts) ->
+ EtsMem = etsmem(),
+ L = [{a,1}, {c,3}, {b,2}],
+ LS = lists:sort(L),
+ Tab = make_table(a, Opts, L),
+ LS = ets:foldr(fun(E,A) -> [E|A] end, [], Tab),
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem)
+ end),
+ ok.
%% Test ets:member BIF.
member(Config) when is_list(Config) ->
@@ -4875,6 +5260,7 @@ filltabint(Tab,0) ->
filltabint(Tab,N) ->
ets:insert(Tab,{N,integer_to_list(N)}),
filltabint(Tab,N-1).
+
filltabint2(Tab,0) ->
Tab;
filltabint2(Tab,N) ->
@@ -5089,27 +5475,31 @@ gen_dets_filename(Config,N) ->
"testdets_" ++ integer_to_list(N) ++ ".dets").
otp_6842_select_1000(Config) when is_list(Config) ->
- Tab = ets_new(xxx,[ordered_set]),
- [ets:insert(Tab,{X,X}) || X <- lists:seq(1,10000)],
- AllTrue = lists:duplicate(10,true),
- AllTrue =
- [ length(
- element(1,
- ets:select(Tab,[{'_',[],['$_']}],X*1000))) =:=
- X*1000 || X <- lists:seq(1,10) ],
- Sequences = [[1000,1000,1000,1000,1000,1000,1000,1000,1000,1000],
- [2000,2000,2000,2000,2000],
- [3000,3000,3000,1000],
- [4000,4000,2000],
- [5000,5000],
- [6000,4000],
- [7000,3000],
- [8000,2000],
- [9000,1000],
- [10000]],
- AllTrue = [ check_seq(Tab, ets:select(Tab,[{'_',[],['$_']}],hd(L)),L) ||
- L <- Sequences ],
- ets:delete(Tab),
+ repeat_for_opts_all_ord_set_table_types(
+ fun(Opts) ->
+ KeyRange = 10000,
+ Tab = ets_new(xxx, Opts, KeyRange),
+ [ets:insert(Tab,{X,X}) || X <- lists:seq(1,KeyRange)],
+ AllTrue = lists:duplicate(10,true),
+ AllTrue =
+ [ length(
+ element(1,
+ ets:select(Tab,[{'_',[],['$_']}],X*1000))) =:=
+ X*1000 || X <- lists:seq(1,10) ],
+ Sequences = [[1000,1000,1000,1000,1000,1000,1000,1000,1000,1000],
+ [2000,2000,2000,2000,2000],
+ [3000,3000,3000,1000],
+ [4000,4000,2000],
+ [5000,5000],
+ [6000,4000],
+ [7000,3000],
+ [8000,2000],
+ [9000,1000],
+ [10000]],
+ AllTrue = [ check_seq(Tab, ets:select(Tab,[{'_',[],['$_']}],hd(L)),L) ||
+ L <- Sequences ],
+ ets:delete(Tab)
+ end),
ok.
check_seq(_,'$end_of_table',[]) ->
@@ -5121,17 +5511,21 @@ check_seq(A,B,C) ->
false.
otp_6338(Config) when is_list(Config) ->
- L = binary_to_term(<<131,108,0,0,0,2,104,2,108,0,0,0,2,103,100,0,19,112,112,
- 98,49,95,98,115,49,50,64,98,108,97,100,101,95,48,95,53,
- 0,0,33,50,0,0,0,4,1,98,0,0,23,226,106,100,0,4,101,120,
- 105,116,104,2,108,0,0,0,2,104,2,100,0,3,115,98,109,100,
- 0,19,112,112,98,50,95,98,115,49,50,64,98,108,97,100,
- 101,95,48,95,56,98,0,0,18,231,106,100,0,4,114,101,99,
- 118,106>>),
- T = ets_new(xxx,[ordered_set]),
- lists:foreach(fun(X) -> ets:insert(T,X) end,L),
- [[4839,recv]] = ets:match(T,{[{sbm,ppb2_bs12@blade_0_8},'$1'],'$2'}),
- ets:delete(T).
+ repeat_for_opts_all_ord_set_table_types(
+ fun(Opts) ->
+ L = binary_to_term(<<131,108,0,0,0,2,104,2,108,0,0,0,2,103,100,0,19,112,112,
+ 98,49,95,98,115,49,50,64,98,108,97,100,101,95,48,95,53,
+ 0,0,33,50,0,0,0,4,1,98,0,0,23,226,106,100,0,4,101,120,
+ 105,116,104,2,108,0,0,0,2,104,2,100,0,3,115,98,109,100,
+ 0,19,112,112,98,50,95,98,115,49,50,64,98,108,97,100,
+ 101,95,48,95,56,98,0,0,18,231,106,100,0,4,114,101,99,
+ 118,106>>),
+ T = ets_new(xxx,Opts),
+ lists:foreach(fun(X) -> ets:insert(T,X) end,L),
+ [[4839,recv]] = ets:match(T,{[{sbm,ppb2_bs12@blade_0_8},'$1'],'$2'}),
+ ets:delete(T)
+ end),
+ ok.
%% OTP-15660: Verify select not doing excessive trapping
%% when process have mbuf heap fragments.
@@ -5256,7 +5650,7 @@ otp_7665_act(Tab,Min,Max,DelNr) ->
%% Whitebox testing of meta name table hashing.
meta_wb(Config) when is_list(Config) ->
EtsMem = etsmem(),
- repeat_for_opts(fun meta_wb_do/1),
+ repeat_for_opts_all_non_stim_table_types(fun meta_wb_do/1),
verify_etsmem(EtsMem).
@@ -5325,13 +5719,16 @@ colliding_names(Name) ->
%% OTP_6913: Grow and shrink.
grow_shrink(Config) when is_list(Config) ->
- EtsMem = etsmem(),
-
- Set = ets_new(a, [set]),
- grow_shrink_0(0, 3071, 3000, 5000, Set),
- ets:delete(Set),
-
- verify_etsmem(EtsMem).
+ repeat_for_all_set_table_types(
+ fun(Opts) ->
+ EtsMem = etsmem(),
+
+ Set = ets_new(a, Opts, 5000),
+ grow_shrink_0(0, 3071, 3000, 5000, Set),
+ ets:delete(Set),
+
+ verify_etsmem(EtsMem)
+ end).
grow_shrink_0(N, _, _, Max, _) when N >= Max ->
ok;
@@ -5355,7 +5752,7 @@ grow_shrink_3(N, ShrinkTo, T) ->
true = ets:delete(T, N),
grow_shrink_3(N-1, ShrinkTo, T).
-%% Grow a table that still contains pseudo-deleted objects.
+%% Grow a hash table that still contains pseudo-deleted objects.
grow_pseudo_deleted(Config) when is_list(Config) ->
only_if_smp(fun() -> grow_pseudo_deleted_do() end).
@@ -5408,7 +5805,7 @@ grow_pseudo_deleted_do(Type) ->
ets:delete(T),
process_flag(scheduler,0).
-%% Shrink a table that still contains pseudo-deleted objects.
+%% Shrink a hash table that still contains pseudo-deleted objects.
shrink_pseudo_deleted(Config) when is_list(Config) ->
only_if_smp(fun()->shrink_pseudo_deleted_do() end).
@@ -5528,10 +5925,16 @@ meta_newdel_named(Config) when is_list(Config) ->
%% Concurrent insert's on same table.
smp_insert(Config) when is_list(Config) ->
- ets_new(smp_insert,[named_table,public,{write_concurrency,true}]),
+ repeat_for_opts(fun smp_insert_do/1,
+ [[set,ordered_set,stim_cat_ord_set]]).
+
+smp_insert_do(Opts) ->
+ KeyRange = 10000,
+ ets_new(smp_insert,[named_table,public,{write_concurrency,true}|Opts],
+ KeyRange),
InitF = fun(_) -> ok end,
- ExecF = fun(_) -> true = ets:insert(smp_insert,{rand:uniform(10000)})
- end,
+ ExecF = fun(_) -> true = ets:insert(smp_insert,{rand:uniform(KeyRange)})
+ end,
FiniF = fun(_) -> ok end,
run_smp_workers(InitF,ExecF,FiniF,100000),
verify_table_load(smp_insert),
@@ -5539,7 +5942,7 @@ smp_insert(Config) when is_list(Config) ->
%% Concurrent deletes on same fixated table.
smp_fixed_delete(Config) when is_list(Config) ->
- only_if_smp(fun()->smp_fixed_delete_do() end).
+ only_if_smp(fun() -> smp_fixed_delete_do() end).
smp_fixed_delete_do() ->
T = ets_new(foo,[public,{write_concurrency,true}]),
@@ -5550,17 +5953,20 @@ smp_fixed_delete_do() ->
Buckets = num_of_buckets(T),
InitF = fun([ProcN,NumOfProcs|_]) -> {ProcN,NumOfProcs} end,
ExecF = fun({Key,_}) when Key > NumOfObjs ->
- [end_of_work];
- ({Key,Increment}) ->
- true = ets:delete(T,Key),
- {Key+Increment,Increment}
- end,
+ [end_of_work];
+ ({Key,Increment}) ->
+ true = ets:delete(T,Key),
+ {Key+Increment,Increment}
+ end,
FiniF = fun(_) -> ok end,
run_sched_workers(InitF,ExecF,FiniF,NumOfObjs),
0 = ets:info(T,size),
true = ets:info(T,fixed),
Buckets = num_of_buckets(T),
- NumOfObjs = get_kept_objects(T),
+ case ets:info(T,type) of
+ set -> NumOfObjs = get_kept_objects(T);
+ _ -> ok
+ end,
ets:safe_fixtable(T,false),
%% Will fail as unfix does not shrink the table:
%%Mem = ets:info(T,memory),
@@ -5608,7 +6014,12 @@ delete_unfix_race(Config) when is_list(Config) ->
verify_etsmem(EtsMem).
num_of_buckets(T) ->
- element(1,ets:info(T,stats)).
+ case ets:info(T,type) of
+ set -> element(1,ets:info(T,stats));
+ bag -> element(1,ets:info(T,stats));
+ duplicate_bag -> element(1,ets:info(T,stats));
+ _ -> ok
+ end.
%% Fixate hash table while other process is busy doing unfix.
smp_unfix_fix(Config) when is_list(Config) ->
@@ -5773,106 +6184,126 @@ otp_8166_zombie_creator(T,Deleted) ->
verify_table_load(T) ->
- Stats = ets:info(T,stats),
- {Buckets,AvgLen,StdDev,ExpSD,_MinLen,_MaxLen,_} = Stats,
- ok = if
- AvgLen > 1.2 ->
- io:format("Table overloaded: Stats=~p\n~p\n",
- [Stats, ets:info(T)]),
- false;
-
- Buckets>256, AvgLen < 0.47 ->
- io:format("Table underloaded: Stats=~p\n~p\n",
- [Stats, ets:info(T)]),
- false;
-
- StdDev > ExpSD*2 ->
- io:format("Too large standard deviation (poor hashing?),"
- " stats=~p\n~p\n",[Stats, ets:info(T)]),
- false;
-
- true ->
- io:format("Stats = ~p\n",[Stats]),
- ok
- end.
+ case ets:info(T,type) of
+ ordered_set -> ok;
+ _ ->
+ Stats = ets:info(T,stats),
+ {Buckets,AvgLen,StdDev,ExpSD,_MinLen,_MaxLen,_} = Stats,
+ ok = if
+ AvgLen > 1.2 ->
+ io:format("Table overloaded: Stats=~p\n~p\n",
+ [Stats, ets:info(T)]),
+ false;
+
+ Buckets>256, AvgLen < 0.47 ->
+ io:format("Table underloaded: Stats=~p\n~p\n",
+ [Stats, ets:info(T)]),
+ false;
+
+ StdDev > ExpSD*2 ->
+ io:format("Too large standard deviation (poor hashing?),"
+ " stats=~p\n~p\n",[Stats, ets:info(T)]),
+ false;
+
+ true ->
+ io:format("Stats = ~p\n",[Stats]),
+ ok
+ end
+ end.
%% ets:select on a tree with NIL key object.
otp_8732(Config) when is_list(Config) ->
- Tab = ets_new(noname,[ordered_set]),
- filltabstr(Tab,999),
- ets:insert(Tab,{[],"nasty NIL object"}),
- [] = ets:match(Tab,{'_',nomatch}), %% Will hang if bug not fixed
+ repeat_for_all_ord_set_table_types(
+ fun(Opts) ->
+ KeyRange = 999,
+ KeyFun = fun(K) -> integer_to_list(K) end,
+ Tab = ets_new(noname,Opts, KeyRange, KeyFun),
+ filltabstr(Tab, KeyRange),
+ ets:insert(Tab,{[],"nasty NIL object"}),
+ [] = ets:match(Tab,{'_',nomatch}) %% Will hang if bug not fixed
+ end),
ok.
%% Run concurrent select_delete (and inserts) on same table.
smp_select_delete(Config) when is_list(Config) ->
- T = ets_new(smp_select_delete,[named_table,public,{write_concurrency,true}]),
- Mod = 17,
- Zeros = erlang:make_tuple(Mod,0),
- InitF = fun(_) -> Zeros end,
- ExecF = fun(Diffs0) ->
- case rand:uniform(20) of
- 1 ->
- Mod = 17,
- Eq = rand:uniform(Mod) - 1,
- Deleted = ets:select_delete(T,
- [{{'_', '$1'},
- [{'=:=', {'rem', '$1', Mod}, Eq}],
- [true]}]),
- Diffs1 = setelement(Eq+1, Diffs0,
- element(Eq+1,Diffs0) - Deleted),
- Diffs1;
- _ ->
- Key = rand:uniform(10000),
- Eq = Key rem Mod,
- case ets:insert_new(T,{Key,Key}) of
- true ->
- Diffs1 = setelement(Eq+1, Diffs0,
- element(Eq+1,Diffs0)+1),
- Diffs1;
- false -> Diffs0
- end
- end
- end,
- FiniF = fun(Result) -> Result end,
- Results = run_sched_workers(InitF,ExecF,FiniF,20000),
- TotCnts = lists:foldl(fun(Diffs, Sum) -> add_lists(Sum,tuple_to_list(Diffs)) end,
- lists:duplicate(Mod, 0), Results),
- io:format("TotCnts = ~p\n",[TotCnts]),
- LeftInTab = lists:foldl(fun(N,Sum) -> Sum+N end,
- 0, TotCnts),
- io:format("LeftInTab = ~p\n",[LeftInTab]),
- LeftInTab = ets:info(T,size),
- lists:foldl(fun(Cnt,Eq) ->
- WasCnt = ets:select_count(T,
- [{{'_', '$1'},
- [{'=:=', {'rem', '$1', Mod}, Eq}],
- [true]}]),
- io:format("~p: ~p =?= ~p\n",[Eq,Cnt,WasCnt]),
- Cnt = WasCnt,
- Eq+1
- end,
- 0, TotCnts),
- %% May fail as select_delete does not shrink table (enough)
- %%verify_table_load(T),
- LeftInTab = ets:select_delete(T, [{{'$1','$1'}, [], [true]}]),
- 0 = ets:info(T,size),
- false = ets:info(T,fixed),
- ets:delete(T).
+ repeat_for_opts(fun smp_select_delete_do/1,
+ [[set,ordered_set,stim_cat_ord_set],
+ read_concurrency, compressed]).
+
+smp_select_delete_do(Opts) ->
+ KeyRange = 10000,
+ begin % indentation
+ T = ets_new(smp_select_delete,[named_table,public,{write_concurrency,true}|Opts],
+ KeyRange),
+ Mod = 17,
+ Zeros = erlang:make_tuple(Mod,0),
+ InitF = fun(_) -> Zeros end,
+ ExecF = fun(Diffs0) ->
+ case rand:uniform(20) of
+ 1 ->
+ Mod = 17,
+ Eq = rand:uniform(Mod) - 1,
+ Deleted = ets:select_delete(T,
+ [{{'_', '$1'},
+ [{'=:=', {'rem', '$1', Mod}, Eq}],
+ [true]}]),
+ Diffs1 = setelement(Eq+1, Diffs0,
+ element(Eq+1,Diffs0) - Deleted),
+ Diffs1;
+ _ ->
+ Key = rand:uniform(KeyRange),
+ Eq = Key rem Mod,
+ case ets:insert_new(T,{Key,Key}) of
+ true ->
+ Diffs1 = setelement(Eq+1, Diffs0,
+ element(Eq+1,Diffs0)+1),
+ Diffs1;
+ false -> Diffs0
+ end
+ end
+ end,
+ FiniF = fun(Result) -> Result end,
+ Results = run_sched_workers(InitF,ExecF,FiniF,20000),
+ TotCnts = lists:foldl(fun(Diffs, Sum) -> add_lists(Sum,tuple_to_list(Diffs)) end,
+ lists:duplicate(Mod, 0), Results),
+ io:format("TotCnts = ~p\n",[TotCnts]),
+ LeftInTab = lists:foldl(fun(N,Sum) -> Sum+N end,
+ 0, TotCnts),
+ io:format("LeftInTab = ~p\n",[LeftInTab]),
+ LeftInTab = ets:info(T,size),
+ lists:foldl(fun(Cnt,Eq) ->
+ WasCnt = ets:select_count(T,
+ [{{'_', '$1'},
+ [{'=:=', {'rem', '$1', Mod}, Eq}],
+ [true]}]),
+ io:format("~p: ~p =?= ~p\n",[Eq,Cnt,WasCnt]),
+ Cnt = WasCnt,
+ Eq+1
+ end,
+ 0, TotCnts),
+ %% May fail as select_delete does not shrink table (enough)
+ %%verify_table_load(T),
+ LeftInTab = ets:select_delete(T, [{{'$1','$1'}, [], [true]}]),
+ 0 = ets:info(T,size),
+ false = ets:info(T,fixed),
+ ets:delete(T)
+ end, % indentation
+ ok.
smp_select_replace(Config) when is_list(Config) ->
repeat_for_opts(fun smp_select_replace_do/1,
- [[set,ordered_set,duplicate_bag]]).
+ [[set,ordered_set,stim_cat_ord_set,duplicate_bag]]).
smp_select_replace_do(Opts) ->
+ KeyRange = 20,
T = ets_new(smp_select_replace,
- [public, {write_concurrency, true} | Opts]),
- ObjCount = 20,
+ [public, {write_concurrency, true} | Opts],
+ KeyRange),
InitF = fun (_) -> 0 end,
ExecF = fun (Cnt0) ->
- CounterId = rand:uniform(ObjCount),
+ CounterId = rand:uniform(KeyRange),
Match = [{{'$1', '$2'},
[{'=:=', '$1', CounterId}],
[{{'$1', {'+', '$2', 1}}}]}],
@@ -5896,15 +6327,143 @@ smp_select_replace_do(Opts) ->
FinalCounts = ets:select(T, [{{'_', '$1'}, [], ['$1']}]),
Total = lists:sum(FinalCounts),
Total = lists:sum(Results),
- ObjCount = ets:select_delete(T, [{{'_', '_'}, [], [true]}]),
+ KeyRange = ets:select_delete(T, [{{'_', '_'}, [], [true]}]),
0 = ets:info(T, size),
true = ets:delete(T),
ok.
+%% Iterate ordered_set with write_concurrency
+%% and make sure we hit all "stable" long lived keys
+%% while "volatile" objects are randomly inserted and deleted.
+smp_ordered_iteration(Config) when is_list(Config) ->
+ repeat_for_opts(fun smp_ordered_iteration_do/1,
+ [[cat_ord_set,stim_cat_ord_set]]).
+
+
+smp_ordered_iteration_do(Opts) ->
+ KeyRange = 1000,
+ OffHeap = erts_test_utils:mk_ext_pid({a@b,1}, 4711, 1),
+ KeyFun = fun(K, Type) ->
+ {K div 10, K rem 10, Type, OffHeap}
+ end,
+ StimKeyFun = fun(K) ->
+ KeyFun(K, element(rand:uniform(3),
+ {stable, other, volatile}))
+ end,
+ T = ets_new(smp_ordered_iteration, [public, {write_concurrency,true} | Opts],
+ KeyRange, StimKeyFun),
+ NStable = KeyRange div 4,
+ prefill_table(T, KeyRange, NStable, fun(K) -> {KeyFun(K, stable), 0} end),
+ NStable = ets:info(T, size),
+ NVolatile = KeyRange div 2,
+ prefill_table(T, KeyRange, NVolatile, fun(K) -> {KeyFun(K, volatile), 0} end),
+
+ InitF = fun (_) -> #{insert => 0, delete => 0,
+ select_delete_bk => 0, select_delete_pbk => 0,
+ select_replace_bk => 0, select_replace_pbk => 0}
+ end,
+ ExecF = fun (Counters) ->
+ K = rand:uniform(KeyRange),
+ Key = KeyFun(K, volatile),
+ Acc = case rand:uniform(22) of
+ R when R =< 10 ->
+ ets:insert(T, {Key}),
+ incr_counter(insert, Counters);
+ R when R =< 15 ->
+ ets:delete(T, Key),
+ incr_counter(delete, Counters);
+ R when R =< 19 ->
+ %% Delete bound key
+ ets:select_delete(T, [{{Key, '_'}, [], [true]}]),
+ incr_counter(select_delete_bk, Counters);
+ R when R =< 20 ->
+ %% Delete partially bound key
+ ets:select_delete(T, [{{{K div 10, '_', volatile, '_'}, '_'}, [], [true]}]),
+ incr_counter(select_delete_pbk, Counters);
+ R when R =< 21 ->
+ %% Replace bound key
+ ets:select_replace(T, [{{Key, '$1'}, [],
+ [{{{const,Key}, {'+','$1',1}}}]}]),
+ incr_counter(select_replace_bk, Counters);
+ _ ->
+ %% Replace partially bound key
+ ets:select_replace(T, [{{{K div 10, '_', volatile, '_'}, '$1'}, [],
+ [{{{element,1,'$_'}, {'+','$1',1}}}]}]),
+ incr_counter(select_replace_pbk, Counters)
+ end,
+ receive stop ->
+ [end_of_work | Acc]
+ after 0 ->
+ Acc
+ end
+ end,
+ FiniF = fun (Acc) -> Acc end,
+ Pids = run_sched_workers(InitF, ExecF, FiniF, infinite),
+ timer:send_after(1000, stop),
+
+ Log2ChunkMax = math:log2(NStable*2),
+ Rounds = fun Loop(N) ->
+ MS = [{{{'_', '_', stable, '_'}, '_'}, [], [true]}],
+ NStable = ets:select_count(T, MS),
+ NStable = count_stable(T, next, ets:first(T), 0),
+ NStable = count_stable(T, prev, ets:last(T), 0),
+ NStable = length(ets:select(T, MS)),
+ NStable = length(ets:select_reverse(T, MS)),
+ Chunk = round(math:pow(2, rand:uniform()*Log2ChunkMax)),
+ NStable = ets_select_chunks_count(T, MS, Chunk),
+ receive stop -> N
+ after 0 -> Loop(N+1)
+ end
+ end (1),
+ [P ! stop || P <- Pids],
+ Results = wait_pids(Pids),
+ io:format("Ops = ~p\n", [maps_sum(Results)]),
+ io:format("Diff = ~p\n", [ets:info(T,size) - NStable - NVolatile]),
+ io:format("Stats = ~p\n", [ets:info(T,stats)]),
+ io:format("Rounds = ~p\n", [Rounds]),
+ true = ets:delete(T),
+
+ %% Verify no leakage of offheap key data
+ ok = erts_test_utils:check_node_dist(),
+ ok.
+
+incr_counter(Name, Counters) ->
+ Counters#{Name => maps:get(Name, Counters, 0) + 1}.
+
+count_stable(T, Next, {_, _, stable, _}=Key, N) ->
+ count_stable(T, Next, ets:Next(T, Key), N+1);
+count_stable(T, Next, {_, _, volatile, _}=Key, N) ->
+ count_stable(T, Next, ets:Next(T, Key), N);
+count_stable(_, _, '$end_of_table', N) ->
+ N.
+
+ets_select_chunks_count(T, MS, Chunk) ->
+ ets_select_chunks_count(ets:select(T, MS, Chunk), 0).
+
+ets_select_chunks_count('$end_of_table', N) ->
+ N;
+ets_select_chunks_count({List, Continuation}, N) ->
+ ets_select_chunks_count(ets:select(Continuation),
+ length(List) + N).
+
+maps_sum([Ma | Tail]) when is_map(Ma) ->
+ maps_sum([lists:sort(maps:to_list(Ma)) | Tail]);
+maps_sum([La, Mb | Tail]) ->
+ Lab = lists:zipwith(fun({K,Va}, {K,Vb}) -> {K,Va+Vb} end,
+ La,
+ lists:sort(maps:to_list(Mb))),
+ maps_sum([Lab | Tail]);
+maps_sum([L]) ->
+ L.
+
+
+
+
%% Test different types.
types(Config) when is_list(Config) ->
init_externals(),
- repeat_for_opts(fun types_do/1, [[set,ordered_set],compressed]).
+ repeat_for_opts(fun types_do/1, [repeat_for_opts_atom2list(set_types),
+ compressed]).
types_do(Opts) ->
EtsMem = etsmem(),
@@ -5931,7 +6490,7 @@ types_do(Opts) ->
%% OTP-9932: Memory overwrite when inserting large integers in compressed bag.
%% Will crash with segv on 64-bit opt if not fixed.
otp_9932(Config) when is_list(Config) ->
- T = ets:new(xxx, [bag, compressed]),
+ T = ets_new(xxx, [bag, compressed]),
Fun = fun(N) ->
Key = {1316110174588445 bsl N,1316110174588583 bsl N},
S = {Key, Key},
@@ -5947,48 +6506,56 @@ otp_9932(Config) when is_list(Config) ->
%% vm-deadlock caused by race between ets:delete and others on
%% write_concurrency table.
otp_9423(Config) when is_list(Config) ->
- InitF = fun(_) -> {0,0} end,
- ExecF = fun({S,F}) ->
- receive
- stop ->
- io:format("~p got stop\n", [self()]),
- [end_of_work | {"Succeded=",S,"Failed=",F}]
- after 0 ->
- %%io:format("~p (~p) doing lookup\n", [self(), {S,F}]),
- try ets:lookup(otp_9423, key) of
- [] -> {S+1,F}
- catch
- error:badarg -> {S,F+1}
- end
- end
- end,
- FiniF = fun(R) -> R end,
- case run_smp_workers(InitF, ExecF, FiniF, infinite, 1) of
- Pids when is_list(Pids) ->
- %%[P ! start || P <- Pids],
- repeat(fun() -> ets:new(otp_9423, [named_table, public, {write_concurrency,true}]),
- ets:delete(otp_9423)
- end, 10000),
- [P ! stop || P <- Pids],
- wait_pids(Pids),
- ok;
+ repeat_for_all_non_stim_set_table_types(
+ fun(Opts) ->
+ InitF = fun(_) -> {0,0} end,
+ ExecF = fun({S,F}) ->
+ receive
+ stop ->
+ io:format("~p got stop\n", [self()]),
+ [end_of_work | {"Succeded=",S,"Failed=",F}]
+ after 0 ->
+ %%io:format("~p (~p) doing lookup\n", [self(), {S,F}]),
+ try ets:lookup(otp_9423, key) of
+ [] -> {S+1,F}
+ catch
+ error:badarg -> {S,F+1}
+ end
+ end
+ end,
+ FiniF = fun(R) -> R end,
+ case run_smp_workers(InitF, ExecF, FiniF, infinite, 1) of
+ Pids when is_list(Pids) ->
+ %%[P ! start || P <- Pids],
+ repeat(fun() -> ets_new(otp_9423, [named_table, public,
+ {write_concurrency,true}|Opts]),
+ ets:delete(otp_9423)
+ end, 10000),
+ [P ! stop || P <- Pids],
+ wait_pids(Pids),
+ ok;
+
+ Skipped -> Skipped
+ end
+ end).
- Skipped -> Skipped
- end.
%% Corrupted binary in compressed table
otp_10182(Config) when is_list(Config) ->
- Bin = <<"aHR0cDovL2hvb3RzdWl0ZS5jb20vYy9wcm8tYWRyb2xsLWFi">>,
- Key = {test, Bin},
- Value = base64:decode(Bin),
- In = {Key,Value},
- Db = ets:new(undefined, [set, protected, {read_concurrency, true}, compressed]),
- ets:insert(Db, In),
- [Out] = ets:lookup(Db, Key),
- io:format("In : ~p\nOut: ~p\n", [In,Out]),
- ets:delete(Db),
- In = Out.
+ repeat_for_opts_all_table_types(
+ fun(Opts) ->
+ Bin = <<"aHR0cDovL2hvb3RzdWl0ZS5jb20vYy9wcm8tYWRyb2xsLWFi">>,
+ Key = {test, Bin},
+ Value = base64:decode(Bin),
+ In = {Key,Value},
+ Db = ets_new(undefined, Opts),
+ ets:insert(Db, In),
+ [Out] = ets:lookup(Db, Key),
+ io:format("In : ~p\nOut: ~p\n", [In,Out]),
+ ets:delete(Db),
+ In = Out
+ end).
%% Test that ets:all include/exclude tables that we know are created/deleted
ets_all(Config) when is_list(Config) ->
@@ -6079,19 +6646,23 @@ take(Config) when is_list(Config) ->
ets:insert(T1, {{'not',<<"immediate">>},ok}),
[{{'not',<<"immediate">>},ok}] = ets:take(T1, {'not',<<"immediate">>}),
%% Same with ordered tables.
- T2 = ets_new(b, [ordered_set]),
- [] = ets:take(T2, foo),
- ets:insert(T2, {foo,bar}),
- [] = ets:take(T2, bar),
- [{foo,bar}] = ets:take(T2, foo),
- [] = ets:tab2list(T2),
- ets:insert(T2, {{'not',<<"immediate">>},ok}),
- [{{'not',<<"immediate">>},ok}] = ets:take(T2, {'not',<<"immediate">>}),
- %% Arithmetically-equal keys.
- ets:insert(T2, [{1.0,float},{2,integer}]),
- [{1.0,float}] = ets:take(T2, 1),
- [{2,integer}] = ets:take(T2, 2.0),
- [] = ets:tab2list(T2),
+ repeat_for_all_ord_set_table_types(
+ fun(Opts) ->
+ T2 = ets_new(b, Opts),
+ [] = ets:take(T2, foo),
+ ets:insert(T2, {foo,bar}),
+ [] = ets:take(T2, bar),
+ [{foo,bar}] = ets:take(T2, foo),
+ [] = ets:tab2list(T2),
+ ets:insert(T2, {{'not',<<"immediate">>},ok}),
+ [{{'not',<<"immediate">>},ok}] = ets:take(T2, {'not',<<"immediate">>}),
+ %% Arithmetically-equal keys.
+ ets:insert(T2, [{1.0,float},{2,integer}]),
+ [{1.0,float}] = ets:take(T2, 1),
+ [{2,integer}] = ets:take(T2, 2.0),
+ [] = ets:tab2list(T2),
+ ets:delete(T2)
+ end),
%% Same with bag.
T3 = ets_new(c, [bag]),
ets:insert(T3, [{1,1},{1,2},{3,3}]),
@@ -6099,7 +6670,6 @@ take(Config) when is_list(Config) ->
[{3,3}] = ets:take(T3, 3),
[] = ets:tab2list(T3),
ets:delete(T1),
- ets:delete(T2),
ets:delete(T3),
ok.
@@ -6134,9 +6704,650 @@ whereis_table(Config) when is_list(Config) ->
ok.
+
+%% The following help functions are used by
+%% throughput_benchmark. They are declared on the top level beacuse
+%% declaring them as function local funs cause a scalability issue.
+get_op([{_,O}], _RandNum) ->
+ O;
+get_op([{Prob,O}|Rest], RandNum) ->
+ case RandNum < Prob of
+ true -> O;
+ false -> get_op(Rest, RandNum)
+ end.
+do_op(Table, ProbHelpTab, Range, Operations) ->
+ RandNum = rand:uniform(),
+ Op = get_op(ProbHelpTab, RandNum),
+ #{ Op := TheOp} = Operations,
+ TheOp(Table, Range).
+do_work(WorksDoneSoFar, Table, ProbHelpTab, Range, Operations) ->
+ receive
+ stop -> WorksDoneSoFar
+ after
+ 0 -> do_op(Table, ProbHelpTab, Range, Operations),
+ do_work(WorksDoneSoFar + 1, Table, ProbHelpTab, Range, Operations)
+ end.
+
+prefill_table(T, KeyRange, Num, ObjFun) ->
+ Parent = self(),
+ spawn_link(fun() ->
+ prefill_table_helper(T, KeyRange, Num, ObjFun),
+ Parent ! done
+ end),
+ receive done -> ok end.
+
+prefill_table_helper(T, KeyRange, Num, ObjFun) ->
+ Seed = rand:uniform(KeyRange),
+ %%io:format("prefill_table: Seed = ~p\n", [Seed]),
+ RState = unique_rand_start(KeyRange, Seed),
+ prefill_table_loop(T, RState, Num, ObjFun).
+
+prefill_table_loop(_, _, 0, _) ->
+ ok;
+prefill_table_loop(T, RS0, N, ObjFun) ->
+ {Key, RS1} = unique_rand_next(RS0),
+ ets:insert(T, ObjFun(Key)),
+ prefill_table_loop(T, RS1, N-1, ObjFun).
+
+inserter_proc_starter(T, ToInsert, Parent) ->
+ receive
+ start -> ok
+ end,
+ inserter_proc(T, ToInsert, [], Parent, false).
+
+inserter_proc(T, [], Inserted, Parent, _) ->
+ inserter_proc(T, Inserted, [], Parent, true);
+inserter_proc(T, [I | ToInsert], Inserted, Parent, CanStop) ->
+ Stop =
+ case CanStop of
+ true ->
+ receive
+ stop -> Parent ! stopped
+ after 0 -> no_stop
+ end;
+ false -> no_stop
+ end,
+ case Stop of
+ no_stop ->
+ ets:insert(T, I),
+ inserter_proc(T, ToInsert, [I | Inserted], Parent, CanStop);
+ _ -> ok
+ end.
+
+prefill_table_parallel(T, KeyRange, Num, ObjFun) ->
+ Parent = self(),
+ spawn_link(fun() ->
+ prefill_table_parallel_helper(T, KeyRange, Num, ObjFun),
+ Parent ! done
+ end),
+ receive done -> ok end.
+
+prefill_table_parallel_helper(T, KeyRange, Num, ObjFun) ->
+ NrOfSchedulers = erlang:system_info(schedulers),
+ Seed = rand:uniform(KeyRange),
+ %%io:format("prefill_table: Seed = ~p\n", [Seed]),
+ RState = unique_rand_start(KeyRange, Seed),
+ InsertMap = prefill_insert_map_loop(T, RState, Num, ObjFun, #{}, NrOfSchedulers),
+ Self = self(),
+ Pids = [
+ begin
+ InserterFun =
+ fun() ->
+ inserter_proc_starter(T, ToInsert, Self)
+ end,
+ spawn_link(InserterFun)
+ end
+ || ToInsert <- maps:values(InsertMap)],
+ [Pid ! start || Pid <- Pids],
+ timer:sleep(1000),
+ [Pid ! stop || Pid <- Pids],
+ [receive stopped -> ok end || _Pid <- Pids].
+
+prefill_insert_map_loop(_, _, 0, _, InsertMap, _NrOfSchedulers) ->
+ InsertMap;
+prefill_insert_map_loop(T, RS0, N, ObjFun, InsertMap, NrOfSchedulers) ->
+ {Key, RS1} = unique_rand_next(RS0),
+ Sched = N rem NrOfSchedulers,
+ PrevInserts = maps:get(Sched, InsertMap, []),
+ NewPrevInserts = [ObjFun(Key) | PrevInserts],
+ NewInsertMap = maps:put(Sched, NewPrevInserts, InsertMap),
+ prefill_insert_map_loop(T, RS1, N-1, ObjFun, NewInsertMap, NrOfSchedulers).
+
+-record(ets_throughput_bench_config,
+ {benchmark_duration_ms = 3000,
+ recover_time_ms = 1000,
+ thread_counts = not_set,
+ key_ranges = [1000000],
+ init_functions = [fun prefill_table/4],
+ nr_of_repeats = 1,
+ scenarios =
+ [
+ [
+ {0.5, insert},
+ {0.5, delete}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.8, lookup}
+ ],
+ [
+ {0.01, insert},
+ {0.01, delete},
+ {0.98, lookup}
+ ],
+ [
+ {1.0, lookup}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.4, lookup},
+ {0.4, nextseq10}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.4, lookup},
+ {0.4, nextseq100}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.4, lookup},
+ {0.4, nextseq1000}
+ ],
+ [
+ {1.0, nextseq1000}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.79, lookup},
+ {0.01, selectAll}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.7999, lookup},
+ {0.0001, selectAll}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.799999, lookup},
+ {0.000001, selectAll}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.79, lookup},
+ {0.01, partial_select1000}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.7999, lookup},
+ {0.0001, partial_select1000}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.799999, lookup},
+ {0.000001, partial_select1000}
+ ]
+ ],
+ table_types =
+ [
+ [ordered_set, public],
+ [ordered_set, public, {write_concurrency, true}],
+ [ordered_set, public, {read_concurrency, true}],
+ [ordered_set, public, {write_concurrency, true}, {read_concurrency, true}],
+ [set, public],
+ [set, public, {write_concurrency, true}],
+ [set, public, {read_concurrency, true}],
+ [set, public, {write_concurrency, true}, {read_concurrency, true}]
+ ],
+ etsmem_fun = fun() -> ok end,
+ verify_etsmem_fun = fun(_) -> true end,
+ notify_res_fun = fun(_Name, _Throughput) -> ok end,
+ print_result_paths_fun =
+ fun(ResultPath, _LatestResultPath) ->
+ Comment =
+ io_lib:format("<a href=\"file:///~s\">Result visualization</a>",[ResultPath]),
+ {comment, Comment}
+ end
+ }).
+
+stdout_notify_res(ResultPath, LatestResultPath) ->
+ io:format("Result Location: /~s~n", [ResultPath]),
+ io:format("Latest Result Location: ~s~n", [LatestResultPath]).
+
+throughput_benchmark() ->
+ throughput_benchmark(
+ #ets_throughput_bench_config{
+ print_result_paths_fun = fun stdout_notify_res/2}).
+
+throughput_benchmark(
+ #ets_throughput_bench_config{
+ benchmark_duration_ms = BenchmarkDurationMs,
+ recover_time_ms = RecoverTimeMs,
+ thread_counts = ThreadCountsOpt,
+ key_ranges = KeyRanges,
+ init_functions = InitFuns,
+ nr_of_repeats = NrOfRepeats,
+ scenarios = Scenarios,
+ table_types = TableTypes,
+ etsmem_fun = ETSMemFun,
+ verify_etsmem_fun = VerifyETSMemFun,
+ notify_res_fun = NotifyResFun,
+ print_result_paths_fun = PrintResultPathsFun}) ->
+ NrOfSchedulers = erlang:system_info(schedulers),
+ %% Definitions of operations that are supported by the benchmark
+ NextSeqOp =
+ fun (T, KeyRange, SeqSize) ->
+ Start = rand:uniform(KeyRange),
+ Last =
+ lists:foldl(
+ fun(_, Prev) ->
+ case Prev of
+ '$end_of_table'-> ok;
+ _ ->
+ try ets:next(T, Prev) of
+ Normal -> Normal
+ catch
+ error:badarg ->
+ % sets (not ordered_sets) cannot handle when the argument
+ % to next is not in the set
+ rand:uniform(KeyRange)
+ end
+ end
+ end,
+ Start,
+ lists:seq(1, SeqSize)),
+ case Last =:= -1 of
+ true -> io:format("Will never be printed");
+ false -> ok
+ end
+ end,
+ PartialSelectOp =
+ fun (T, KeyRange, SeqSize) ->
+ Start = rand:uniform(KeyRange),
+ Last = Start + SeqSize,
+ case -1 =:= ets:select_count(T,
+ ets:fun2ms(fun({X}) when X > Start andalso X =< Last -> true end)) of
+ true -> io:format("Will never be printed");
+ false -> ok
+ end
+
+ end,
+ %% Mapping benchmark operation names to their corresponding functions that do them
+ Operations =
+ #{insert =>
+ fun(T,KeyRange) ->
+ Num = rand:uniform(KeyRange),
+ ets:insert(T, {Num})
+ end,
+ delete =>
+ fun(T,KeyRange) ->
+ Num = rand:uniform(KeyRange),
+ ets:delete(T, Num)
+ end,
+ lookup =>
+ fun(T,KeyRange) ->
+ Num = rand:uniform(KeyRange),
+ ets:lookup(T, Num)
+ end,
+ nextseq10 =>
+ fun(T,KeyRange) -> NextSeqOp(T,KeyRange,10) end,
+ nextseq100 =>
+ fun(T,KeyRange) -> NextSeqOp(T,KeyRange,100) end,
+ nextseq1000 =>
+ fun(T,KeyRange) -> NextSeqOp(T,KeyRange,1000) end,
+ selectAll =>
+ fun(T,_KeyRange) ->
+ case -1 =:= ets:select_count(T, ets:fun2ms(fun(_X) -> true end)) of
+ true -> io:format("Will never be printed");
+ false -> ok
+ end
+ end,
+ partial_select1000 =>
+ fun(T,KeyRange) -> PartialSelectOp(T,KeyRange,1000) end
+ },
+ %% Helper functions
+ CalculateThreadCounts = fun Calculate([Count|Rest]) ->
+ case Count > NrOfSchedulers of
+ true -> lists:reverse(Rest);
+ false -> Calculate([Count*2,Count|Rest])
+ end
+ end,
+ CalculateOpsProbHelpTab =
+ fun Calculate([{_, OpName}], _) ->
+ [{1.0, OpName}];
+ Calculate([{OpPropability, OpName}|Res], Current) ->
+ NewCurrent = Current + OpPropability,
+ [{NewCurrent, OpName}| Calculate(Res, NewCurrent)]
+ end,
+ RenderScenario =
+ fun R([], StringSoFar) ->
+ StringSoFar;
+ R([{Fraction, Operation}], StringSoFar) ->
+ io_lib:format("~s ~f% ~p",[StringSoFar, Fraction * 100.0, Operation]);
+ R([{Fraction, Operation}|Rest], StringSoFar) ->
+ R(Rest,
+ io_lib:format("~s ~f% ~p, ",[StringSoFar, Fraction * 100.0, Operation]))
+ end,
+ SafeFixTableIfRequired =
+ fun(Table, Scenario, On) ->
+ case set =:= ets:info(Table, type) of
+ true ->
+ HasNotRequiringOp =
+ lists:search(
+ fun({_,nextseq10}) -> true;
+ ({_,nextseq100}) -> true;
+ ({_,nextseq1000}) -> true;
+ (_) -> false
+ end, Scenario),
+ case HasNotRequiringOp of
+ false -> ok;
+ _ -> ets:safe_fixtable(Table, On)
+ end;
+ false -> ok
+ end
+ end,
+ DataHolder =
+ fun DataHolderFun(Data)->
+ receive
+ {get_data, Pid} -> Pid ! {ets_bench_data, Data};
+ D -> DataHolderFun([Data,D])
+ end
+ end,
+ DataHolderPid = spawn_link(fun()-> DataHolder([]) end),
+ PrintData =
+ fun (Str, List) ->
+ io:format(Str, List),
+ DataHolderPid ! io_lib:format(Str, List)
+ end,
+ GetData =
+ fun () ->
+ DataHolderPid ! {get_data, self()},
+ receive {ets_bench_data, Data} -> Data end
+ end,
+ %% Function that runs a benchmark instance and returns the number
+ %% of operations that were performed
+ RunBenchmark =
+ fun({NrOfProcs, TableConfig, Scenario, Range, Duration, InitFun}) ->
+ ProbHelpTab = CalculateOpsProbHelpTab(Scenario, 0),
+ Table = ets:new(t, TableConfig),
+ Nobj = Range div 2,
+ case InitFun of
+ not_set -> prefill_table(Table, Range, Nobj, fun(K) -> {K} end);
+ _ -> InitFun(Table, Range, Nobj, fun(K) -> {K} end)
+ end,
+ Nobj = ets:info(Table, size),
+ SafeFixTableIfRequired(Table, Scenario, true),
+ ParentPid = self(),
+ Worker =
+ fun() ->
+ receive start -> ok end,
+ WorksDone =
+ do_work(0, Table, ProbHelpTab, Range, Operations),
+ ParentPid ! WorksDone
+ end,
+ ChildPids =
+ lists:map(fun(_N) ->spawn_link(Worker)end, lists:seq(1, NrOfProcs)),
+ erlang:garbage_collect(),
+ timer:sleep(RecoverTimeMs),
+ lists:foreach(fun(Pid) -> Pid ! start end, ChildPids),
+ timer:sleep(Duration),
+ lists:foreach(fun(Pid) -> Pid ! stop end, ChildPids),
+ TotalWorksDone = lists:foldl(
+ fun(_, Sum) ->
+ receive
+ Count -> Sum + Count
+ end
+ end, 0, ChildPids),
+ SafeFixTableIfRequired(Table, Scenario, false),
+ ets:delete(Table),
+ TotalWorksDone
+ end,
+ RunBenchmarkInSepProcess =
+ fun(ParameterTuple) ->
+ P = self(),
+ Results =
+ [begin
+ spawn_link(fun()-> P ! {bench_result, RunBenchmark(ParameterTuple)} end),
+ receive {bench_result, Res} -> Res end
+ end || _ <- lists:seq(1, NrOfRepeats)],
+ lists:sum(Results) / NrOfRepeats
+ end,
+ RunBenchmarkAndReport =
+ fun(ThreadCount,
+ TableType,
+ Scenario,
+ KeyRange,
+ Duration,
+ InitFunName,
+ InitFun) ->
+ Result = RunBenchmarkInSepProcess({ThreadCount,
+ TableType,
+ Scenario,
+ KeyRange,
+ Duration,
+ InitFun}),
+ Throughput = Result/(Duration/1000.0),
+ PrintData("; ~f",[Throughput]),
+ Name = io_lib:format("Scenario: ~s, ~w, Key Range Size: ~w, "
+ "# of Processes: ~w, Table Type: ~w",
+ [InitFunName, Scenario, KeyRange, ThreadCount, TableType]),
+ NotifyResFun(Name, Throughput)
+ end,
+ ThreadCounts =
+ case ThreadCountsOpt of
+ not_set ->
+ CalculateThreadCounts([1]);
+ _ -> ThreadCountsOpt
+ end,
+ %% Run the benchmark
+ PrintData("# Each instance of the benchmark runs for ~w seconds:~n", [BenchmarkDurationMs/1000]),
+ PrintData("# The result of a benchmark instance is presented as a number representing~n",[]),
+ PrintData("# the number of operations performed per second:~n~n~n",[]),
+ PrintData("# To plot graphs for the results below:~n",[]),
+ PrintData("# 1. Open \"$ERL_TOP/lib/stdlib/test/ets_SUITE_data/visualize_throughput.html\" in a web browser~n",[]),
+ PrintData("# 2. Copy the lines between \"#BENCHMARK STARTED$\" and \"#BENCHMARK ENDED$\" below~n",[]),
+ PrintData("# 3. Paste the lines copied in step 2 to the text box in the browser window opened in~n",[]),
+ PrintData("# step 1 and press the Render button~n~n",[]),
+ PrintData("#BENCHMARK STARTED$~n",[]),
+ EtsMem = ETSMemFun(),
+ %% The following loop runs all benchmark scenarios and prints the results (i.e, operations/second)
+ lists:foreach(
+ fun(KeyRange) ->
+ lists:foreach(
+ fun(Scenario) ->
+ PrintData("Scenario: ~s | Key Range Size: ~w$~n",
+ [RenderScenario(Scenario, ""), KeyRange]),
+ lists:foreach(
+ fun(ThreadCount) ->
+ PrintData("; ~w",[ThreadCount])
+ end,
+ ThreadCounts),
+ PrintData("$~n",[]),
+ lists:foreach(
+ fun(TableType) ->
+ lists:foreach(
+ fun(InitFunArg) ->
+ {InitFunName, InitFun} =
+ case InitFunArg of
+ {FunName, Fun} -> {FunName, Fun};
+ Fun -> {"", Fun}
+ end,
+ PrintData("~s,~w ",[InitFunName,TableType]),
+ lists:foreach(
+ fun(ThreadCount) ->
+ RunBenchmarkAndReport(ThreadCount,
+ TableType,
+ Scenario,
+ KeyRange,
+ BenchmarkDurationMs,
+ InitFunName,
+ InitFun)
+ end,
+ ThreadCounts),
+ PrintData("$~n",[])
+ end,
+ InitFuns)
+
+ end,
+ TableTypes)
+ end,
+ Scenarios)
+ end,
+ KeyRanges),
+ PrintData("~n#BENCHMARK ENDED$~n~n",[]),
+ VerifyETSMemFun(EtsMem),
+ DataDir = filename:join(filename:dirname(code:which(?MODULE)), "ets_SUITE_data"),
+ TemplatePath = filename:join(DataDir, "visualize_throughput.html"),
+ {ok, Template} = file:read_file(TemplatePath),
+ OutputData = string:replace(Template, "#bench_data_placeholder", GetData()),
+ OutputPath1 = filename:join(DataDir, "ets_bench_result.html"),
+ {{Year, Month, Day}, {Hour, Minute, Second}} = calendar:now_to_datetime(erlang:timestamp()),
+ StrTime = lists:flatten(io_lib:format("~4..0w-~2..0w-~2..0wT~2..0w:~2..0w:~2..0w",[Year,Month,Day,Hour,Minute,Second])),
+ OutputPath2 = filename:join(DataDir, io_lib:format("ets_bench_result_~s.html", [StrTime])),
+ file:write_file(OutputPath1, OutputData),
+ file:write_file(OutputPath2, OutputData),
+ PrintResultPathsFun(OutputPath2, OutputPath1).
+
+test_throughput_benchmark(Config) when is_list(Config) ->
+ throughput_benchmark(
+ #ets_throughput_bench_config{
+ benchmark_duration_ms = 100,
+ recover_time_ms = 0,
+ thread_counts = [1, erlang:system_info(schedulers)],
+ key_ranges = [50000],
+ etsmem_fun = fun etsmem/0,
+ verify_etsmem_fun = fun verify_etsmem/1}).
+
+long_throughput_benchmark(Config) when is_list(Config) ->
+ N = erlang:system_info(schedulers),
+ throughput_benchmark(
+ #ets_throughput_bench_config{
+ benchmark_duration_ms = 3000,
+ recover_time_ms = 1000,
+ thread_counts = [1, N div 2, N],
+ key_ranges = [1000000],
+ scenarios =
+ [
+ [
+ {0.5, insert},
+ {0.5, delete}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.8, lookup}
+ ],
+ [
+ {0.01, insert},
+ {0.01, delete},
+ {0.98, lookup}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.4, lookup},
+ {0.4, nextseq100}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.79, lookup},
+ {0.01, selectAll}
+ ],
+ [
+ {0.1, insert},
+ {0.1, delete},
+ {0.79, lookup},
+ {0.01, partial_select1000}
+ ]
+ ],
+ table_types =
+ [
+ [ordered_set, public, {write_concurrency, true}, {read_concurrency, true}],
+ [set, public, {write_concurrency, true}, {read_concurrency, true}]
+ ],
+ etsmem_fun = fun etsmem/0,
+ verify_etsmem_fun = fun verify_etsmem/1,
+ notify_res_fun =
+ fun(Name, Throughput) ->
+ SummaryTable =
+ proplists:get_value(ets_benchmark_result_summary_tab, Config),
+ AddToSummaryCounter =
+ case SummaryTable of
+ undefined ->
+ fun(_, _) ->
+ ok
+ end;
+ Tab ->
+ fun(CounterName, ToAdd) ->
+ OldVal = ets:lookup_element(Tab, CounterName, 2),
+ NewVal = OldVal + ToAdd,
+ ets:insert(Tab, {CounterName, NewVal})
+ end
+ end,
+ Record =
+ fun(NoOfBenchsCtr, TotThrputCtr) ->
+ AddToSummaryCounter(NoOfBenchsCtr, 1),
+ AddToSummaryCounter(TotThrputCtr, Throughput)
+ end,
+ Record(nr_of_benchmarks, total_throughput),
+ case string:find(Name, "ordered_set") of
+ nomatch ->
+ Record(nr_of_set_benchmarks, total_throughput_set);
+ _ ->
+ Record(nr_of_ordered_set_benchmarks,
+ total_throughput_ordered_set)
+ end,
+ ct_event:notify(
+ #event{name = benchmark_data,
+ data = [{suite,"ets_bench"},
+ {name, Name},
+ {value,Throughput}]})
+ end
+ }).
+
+%% This function compares the lookup operation's performance for
+%% ordered_set ETS tables with and without write_concurrency enabled
+%% when the data structures have been populated in parallel and
+%% sequentially.
%%
-%% Utility functions:
-%%
+%% The main purpose of this function is to check that the
+%% implementation of ordered_set with write_concurrency (CA tree)
+%% adapts its structure to contention even when only lookup operations
+%% are used.
+lookup_catree_par_vs_seq_init_benchmark() ->
+ N = erlang:system_info(schedulers),
+ throughput_benchmark(
+ #ets_throughput_bench_config{
+ benchmark_duration_ms = 600000,
+ recover_time_ms = 1000,
+ thread_counts = [1, N div 2, N],
+ key_ranges = [1000000],
+ init_functions = [{"seq_init", fun prefill_table/4},
+ {"par_init", fun prefill_table_parallel/4}],
+ nr_of_repeats = 1,
+ scenarios =
+ [
+ [
+ {1.0, lookup}
+ ]
+ ],
+ table_types =
+ [
+ [ordered_set, public, {write_concurrency, true}],
+ [ordered_set, public]
+ ],
+ print_result_paths_fun = fun stdout_notify_res/2
+ }).
add_lists(L1,L2) ->
add_lists(L1,L2,[]).
@@ -6197,8 +7408,11 @@ wait_pids(Pids, Acc) ->
{Pid,Result} ->
true = lists:member(Pid,Pids),
Others = lists:delete(Pid,Pids),
- io:format("wait_pid got ~p from ~p, still waiting for ~p\n",[Result,Pid,Others]),
+ %%io:format("wait_pid got ~p from ~p\n",[Result,Pid]),
wait_pids(Others,[Result | Acc])
+ after 60*1000 ->
+ io:format("Still waiting for workers ~p\n",[Pids]),
+ wait_pids(Pids, Acc)
end.
@@ -6222,48 +7436,25 @@ wait_for_memory_deallocations() ->
wait_for_memory_deallocations()
end.
-
etsmem() ->
- wait_for_memory_deallocations(),
-
- AllTabs = lists:map(fun(T) -> {T,ets:info(T,name),ets:info(T,size),
- ets:info(T,memory),ets:info(T,type)}
- end, ets:all()),
-
- EtsAllocInfo = erlang:system_info({allocator,ets_alloc}),
- ErlangMemoryEts = try erlang:memory(ets) catch error:notsup -> notsup end,
-
- Mem =
- {ErlangMemoryEts,
- case EtsAllocInfo of
- false -> undefined;
- MemInfo ->
- CS = lists:foldl(
- fun ({instance, _, L}, Acc) ->
- {value,{mbcs,MBCS}} = lists:keysearch(mbcs, 1, L),
- {value,{sbcs,SBCS}} = lists:keysearch(sbcs, 1, L),
- NewAcc = [MBCS, SBCS | Acc],
- case lists:keysearch(mbcs_pool, 1, L) of
- {value,{mbcs_pool, MBCS_POOL}} ->
- [MBCS_POOL|NewAcc];
- _ -> NewAcc
- end
- end,
- [],
- MemInfo),
- lists:foldl(
- fun(L, {Bl0,BlSz0}) ->
- {value,BlTup} = lists:keysearch(blocks, 1, L),
- blocks = element(1, BlTup),
- Bl = element(2, BlTup),
- {value,BlSzTup} = lists:keysearch(blocks_size, 1, L),
- blocks_size = element(1, BlSzTup),
- BlSz = element(2, BlSzTup),
- {Bl0+Bl,BlSz0+BlSz}
- end, {0,0}, CS)
- end},
- {Mem,AllTabs}.
+ % The following is done twice to avoid an inconsistent memory
+ % "snapshot" (see verify_etsmem/2).
+ lists:foldl(
+ fun(_,_) ->
+ wait_for_memory_deallocations(),
+
+ AllTabs = lists:map(fun(T) -> {T,ets:info(T,name),ets:info(T,size),
+ ets:info(T,memory),ets:info(T,type)}
+ end, ets:all()),
+ EtsAllocSize = erts_debug:alloc_blocks_size(ets_alloc),
+ ErlangMemoryEts = try erlang:memory(ets) catch error:notsup -> notsup end,
+
+ Mem = {ErlangMemoryEts, EtsAllocSize},
+ {Mem, AllTabs}
+ end,
+ not_used,
+ lists:seq(1,2)).
verify_etsmem(MI) ->
wait_for_test_procs(),
@@ -6284,15 +7475,15 @@ verify_etsmem({MemInfo,AllTabs}, Try) ->
end;
{MemInfo2, AllTabs2} ->
- io:format("Expected: ~p", [MemInfo]),
- io:format("Actual: ~p", [MemInfo2]),
- io:format("Changed tables before: ~p\n",[AllTabs -- AllTabs2]),
- io:format("Changed tables after: ~p\n", [AllTabs2 -- AllTabs]),
+ io:format("#Expected: ~p", [MemInfo]),
+ io:format("#Actual: ~p", [MemInfo2]),
+ io:format("#Changed tables before: ~p\n",[AllTabs -- AllTabs2]),
+ io:format("#Changed tables after: ~p\n", [AllTabs2 -- AllTabs]),
case Try < 2 of
true ->
- io:format("\nThis discrepancy could be caused by an "
+ io:format("\n#This discrepancy could be caused by an "
"inconsistent memory \"snapshot\""
- "\nTry again...\n", []),
+ "\n#Try again...\n", []),
verify_etsmem({MemInfo, AllTabs}, Try+1);
false ->
ct:fail("Failed memory check")
@@ -6766,22 +7957,49 @@ make_unaligned_sub_binary(List) ->
repeat_for_opts(F) ->
repeat_for_opts(F, [write_concurrency, read_concurrency, compressed]).
+repeat_for_opts_all_table_types(F) ->
+ repeat_for_opts(F, [all_types, write_concurrency, read_concurrency, compressed]).
+
+repeat_for_opts_all_non_stim_table_types(F) ->
+ repeat_for_opts(F, [all_non_stim_types, write_concurrency, read_concurrency, compressed]).
+
+repeat_for_opts_all_set_table_types(F) ->
+ repeat_for_opts(F, [set_types, write_concurrency, read_concurrency, compressed]).
+
+repeat_for_all_set_table_types(F) ->
+ repeat_for_opts(F, [set_types]).
+
+repeat_for_all_ord_set_table_types(F) ->
+ repeat_for_opts(F, [ord_set_types]).
+
+repeat_for_all_non_stim_set_table_types(F) ->
+ repeat_for_opts(F, [all_non_stim_set_types]).
+
+repeat_for_opts_all_ord_set_table_types(F) ->
+ repeat_for_opts(F, [ord_set_types, write_concurrency, read_concurrency, compressed]).
+
repeat_for_opts(F, OptGenList) when is_function(F, 1) ->
repeat_for_opts(F, OptGenList, []).
repeat_for_opts(F, [], Acc) ->
lists:foldl(fun(Opts, RV_Acc) ->
OptList = lists:filter(fun(E) -> E =/= void end, Opts),
- io:format("Calling with options ~p\n",[OptList]),
- RV = F(OptList),
- case RV_Acc of
- {comment,_} -> RV_Acc;
- _ -> case RV of
- {comment,_} -> RV;
- _ -> [RV | RV_Acc]
- end
- end
- end, [], Acc);
+ case is_redundant_opts_combo(OptList) of
+ true ->
+ %%io:format("Ignoring redundant options ~p\n",[OptList]),
+ ok;
+ false ->
+ io:format("Calling with options ~p\n",[OptList]),
+ RV = F(OptList),
+ case RV_Acc of
+ {comment,_} -> RV_Acc;
+ _ -> case RV of
+ {comment,_} -> RV;
+ _ -> [RV | RV_Acc]
+ end
+ end
+ end
+ end, [], Acc);
repeat_for_opts(F, [OptList | Tail], []) when is_list(OptList) ->
repeat_for_opts(F, Tail, [[Opt] || Opt <- OptList]);
repeat_for_opts(F, [OptList | Tail], AccList) when is_list(OptList) ->
@@ -6789,14 +8007,127 @@ repeat_for_opts(F, [OptList | Tail], AccList) when is_list(OptList) ->
repeat_for_opts(F, [Atom | Tail], AccList) when is_atom(Atom) ->
repeat_for_opts(F, [repeat_for_opts_atom2list(Atom) | Tail ], AccList).
-repeat_for_opts_atom2list(all_types) -> [set,ordered_set,bag,duplicate_bag];
+repeat_for_opts_atom2list(set_types) -> [set,ordered_set,stim_cat_ord_set,cat_ord_set];
+repeat_for_opts_atom2list(ord_set_types) -> [ordered_set,stim_cat_ord_set,cat_ord_set];
+repeat_for_opts_atom2list(all_types) -> [set,ordered_set,stim_cat_ord_set,cat_ord_set,bag,duplicate_bag];
+repeat_for_opts_atom2list(all_non_stim_types) -> [set,ordered_set,cat_ord_set,bag,duplicate_bag];
+repeat_for_opts_atom2list(all_non_stim_set_types) -> [set,ordered_set,cat_ord_set];
repeat_for_opts_atom2list(write_concurrency) -> [{write_concurrency,false},{write_concurrency,true}];
repeat_for_opts_atom2list(read_concurrency) -> [{read_concurrency,false},{read_concurrency,true}];
repeat_for_opts_atom2list(compressed) -> [compressed,void].
-ets_new(Name, Opts) ->
- %%ets:new(Name, [compressed | Opts]).
- ets:new(Name, Opts).
+is_redundant_opts_combo(Opts) ->
+ (lists:member(stim_cat_ord_set, Opts) orelse
+ lists:member(cat_ord_set, Opts))
+ andalso
+ (lists:member({write_concurrency, false}, Opts) orelse
+ lists:member(private, Opts) orelse
+ lists:member(protected, Opts)).
+
+%% Add fake table option with info about key range.
+%% Will be consumed by ets_new and used for stim_cat_ord_set.
+key_range(Opts, KeyRange) ->
+ [{key_range, KeyRange} | Opts].
+
+ets_new(Name, Opts0) ->
+ {KeyRange, Opts1} = case lists:keytake(key_range, 1, Opts0) of
+ {value, {key_range, KR}, Rest1} ->
+ {KR, Rest1};
+ false ->
+ {1000*1000, Opts0}
+ end,
+ ets_new(Name, Opts1, KeyRange).
+
+ets_new(Name, Opts, KeyRange) ->
+ ets_new(Name, Opts, KeyRange, fun id/1).
+
+ets_new(Name, Opts0, KeyRange, KeyFun) ->
+ {CATree, Stimulate, RevOpts} =
+ lists:foldl(fun(cat_ord_set, {false, false, Lacc}) ->
+ {true, false, [ordered_set | Lacc]};
+ (stim_cat_ord_set, {false, false, Lacc}) ->
+ {true, true, [ordered_set | Lacc]};
+ (Other, {CAT, STIM, Lacc}) ->
+ {CAT, STIM, [Other | Lacc]}
+ end,
+ {false, false, []},
+ Opts0),
+ Opts = lists:reverse(RevOpts),
+ EtsNewHelper =
+ fun (UseOpts) ->
+ case get(ets_new_opts) of
+ UseOpts ->
+ silence; %% suppress identical table opts spam
+ _ ->
+ put(ets_new_opts, UseOpts),
+ io:format("ets:new(~p, ~p)~n", [Name, UseOpts])
+ end,
+ ets:new(Name, UseOpts)
+ end,
+ case CATree andalso
+ (not lists:member({write_concurrency, false}, Opts)) andalso
+ (not lists:member(private, Opts)) andalso
+ (not lists:member(protected, Opts)) of
+ true ->
+ NewOpts1 =
+ case lists:member({write_concurrency, true}, Opts) of
+ true -> Opts;
+ false -> [{write_concurrency, true}|Opts]
+ end,
+ NewOpts2 =
+ case lists:member(public, NewOpts1) of
+ true -> NewOpts1;
+ false -> [public|NewOpts1]
+ end,
+ T = EtsNewHelper(NewOpts2),
+ case Stimulate of
+ false -> ok;
+ true -> stimulate_contention(T, KeyRange, KeyFun)
+ end,
+ T;
+ false ->
+ EtsNewHelper(Opts)
+ end.
+
+% The purpose of this function is to stimulate fine grained locking in
+% tables of types ordered_set with the write_concurrency options
+% turned on. The erts_debug feature 'ets_force_split' is used to easier
+% generate a routing tree with fine grained locking without having to
+% provoke lots of actual lock contentions.
+stimulate_contention(Tid, KeyRange, KeyFun) ->
+ T = case Tid of
+ A when is_atom(A) -> ets:whereis(A);
+ _ -> Tid
+ end,
+ erts_debug:set_internal_state(ets_force_split, {T, true}),
+ Num = case KeyRange > 50 of
+ true -> 50;
+ false -> KeyRange
+ end,
+ Seed = rand:uniform(KeyRange),
+ %%io:format("prefill_table: Seed = ~p\n", [Seed]),
+ RState = unique_rand_start(KeyRange, Seed),
+ stim_inserter_loop(T, RState, Num, KeyFun),
+ Num = ets:info(T, size),
+ ets:match_delete(T, {'$1','$1','$1'}),
+ 0 = ets:info(T, size),
+ erts_debug:set_internal_state(ets_force_split, {T, false}),
+ case ets:info(T,stats) of
+ {0, _, _} ->
+ io:format("No routing nodes in table?\n"
+ "Debug feature 'ets_force_split' does not seem to work.\n", []),
+ ct:fail("No ets_force_split?");
+ Stats ->
+ io:format("stimulated ordered_set: ~p\n", [Stats])
+ end.
+
+stim_inserter_loop(_, _, 0, _) ->
+ ok;
+stim_inserter_loop(T, RS0, N, KeyFun) ->
+ {K, RS1} = unique_rand_next(RS0),
+ Key = KeyFun(K),
+ ets:insert(T, {Key, Key, Key}),
+ stim_inserter_loop(T, RS1, N-1, KeyFun).
do_tc(Do, Report) ->
T1 = erlang:monotonic_time(),
@@ -6810,3 +8141,50 @@ syrup_factor() ->
valgrind -> 20;
_ -> 1
end.
+
+
+%%
+%% This is a pseudo random number generator for UNIQUE integers.
+%% All integers between 1 and Max will be generated before it repeat itself.
+%% It's a variant of this one using quadratic residues by Jeff Preshing:
+%% http://preshing.com/20121224/how-to-generate-a-sequence-of-unique-random-integers/
+%%
+unique_rand_start(Max, Seed) ->
+ L = lists:dropwhile(fun(P) -> P < Max end,
+ primes_3mod4()),
+ [P | _] = case L of
+ [] ->
+ error("Random range too large");
+ _ ->
+ L
+ end,
+ 3 = P rem 4,
+ {0, {Max, P, Seed}}.
+
+unique_rand_next({N, {Max, P, Seed}=Const}) ->
+ case dquad(P, N, Seed) + 1 of
+ RND when RND > Max -> % Too large, skip
+ unique_rand_next({N+1, Const});
+ RND ->
+ {RND, {N+1, Const}}
+ end.
+
+%% A one-to-one relation between all integers 0 =< X < Prime
+%% if Prime rem 4 == 3.
+quad(Prime, X) ->
+ Rem = X*X rem Prime,
+ case 2*X < Prime of
+ true ->
+ Rem;
+ false ->
+ Prime - Rem
+ end.
+
+dquad(Prime, X, Seed) ->
+ quad(Prime, (quad(Prime, X) + Seed) rem Prime).
+
+%% Primes where P rem 4 == 3.
+primes_3mod4() ->
+ [103, 211, 503, 1019, 2003, 5003, 10007, 20011, 50023,
+ 100003, 200003, 500083, 1000003, 2000003, 5000011,
+ 10000019, 20000003, 50000047, 100000007].
diff --git a/lib/stdlib/test/ets_SUITE_data/visualize_throughput.html b/lib/stdlib/test/ets_SUITE_data/visualize_throughput.html
new file mode 100644
index 0000000000..27d6849c60
--- /dev/null
+++ b/lib/stdlib/test/ets_SUITE_data/visualize_throughput.html
@@ -0,0 +1,253 @@
+<!doctype html>
+<html lang="en">
+
+<!-- %% -->
+<!-- %% %CopyrightBegin% -->
+<!-- %% -->
+<!-- %% Copyright Ericsson AB and Kjell Winblad 1996-2018. All Rights Reserved. -->
+<!-- %% -->
+<!-- %% Licensed under the Apache License, Version 2.0 (the "License"); -->
+<!-- %% you may not use this file except in compliance with the License. -->
+<!-- %% You may obtain a copy of the License at -->
+<!-- %% -->
+<!-- %% http://www.apache.org/licenses/LICENSE-2.0 -->
+<!-- %% -->
+<!-- %% Unless required by applicable law or agreed to in writing, software -->
+<!-- %% distributed under the License is distributed on an "AS IS" BASIS, -->
+<!-- %% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. -->
+<!-- %% See the License for the specific language governing permissions and -->
+<!-- %% limitations under the License. -->
+<!-- %% -->
+<!-- %% %CopyrightEnd% -->
+<!-- %% -->
+<!-- %% Author: Kjell Winblad -->
+<!-- %% -->
+
+ <head>
+ <meta charset="utf-8">
+ <title>ETS Benchmark Result Viewer</title>
+ </head>
+
+ <body>
+ <div id="insertPlaceholder"></div>
+ <h1>ETS Benchmark Result Viewer</h1>
+ <p>
+ This page generates graphs from data produced by the ETS benchmark which is defined in the function <code>ets_SUITE:throughput_benchmark/0</code> (see "<code>$ERL_TOP/lib/stdlib/test/ets_SUITE.erl</code>").
+ </p>
+ <p>
+ Note that one can paste results from several benchmark runs into the field below. Results from the same scenario but from different benchmark runs will be relabeled and ploted in the same graph automatically. This makes comparisons of different ETS versions easy.
+ </p>
+ <p>
+ Note also that that lines can be hidden by clicking on the corresponding label.
+ </p>
+ Paste the generated data in the field below and press the Render button:
+ <br>
+ <textarea id="dataField" rows="4" cols="50">#bench_data_placeholder</textarea>
+ <br>
+ <input type="checkbox" id="barPlot"> Bar Plot
+ <br>
+ <input type="checkbox" id="sameSpacing" checked> Same X Spacing Between Points
+ <br>
+ <input type="checkbox" class="showCheck" value="[ordered_set,public]" checked> Show <code>[ordered_set,public]</code>
+ <br>
+ <input type="checkbox" class="showCheck" value="[ordered_set,public,{write_concurrency,true}]" checked> Show <code>[ordered_set,public,{write_concurrency,true}]</code>
+ <br>
+ <input type="checkbox" class="showCheck" value="[ordered_set,public,{read_concurrency,true}]" checked> Show <code>[ordered_set,public,{read_concurrency,true}]</code>
+ <br>
+ <input type="checkbox" class="showCheck" value="[ordered_set,public,{write_concurrency,true},{read_concurrency,true}]" checked> Show <code>[ordered_set,public,{write_concurrency,true},{read_concurrency,true}]</code>
+ <br>
+ <input type="checkbox" class="showCheck" value="[set,public]" checked> Show <code>[set,public]</code>
+ <br>
+ <input type="checkbox" class="showCheck" value="[set,public,{write_concurrency,true}]" checked> Show <code>[set,public,{write_concurrency,true}]</code>
+ <br>
+ <input type="checkbox" class="showCheck" value="[set,public,{read_concurrency,true}]" checked> Show <code>[set,public,{read_concurrency,true}]</code>
+ <br>
+ <input type="checkbox" class="showCheck" value="[set,public,{write_concurrency,true},{read_concurrency,true}]" checked> Show <code>[set,public,{write_concurrency,true},{read_concurrency,true}]</code>
+ <br>
+ <button id="renderButton" type="button">Render</button>
+
+ <script src="https://code.jquery.com/jquery-3.3.1.slim.min.js"
+ integrity="sha256-3edrmyuQ0w65f8gfBsqowzjJe2iM6n0nKciPUp8y+7E="
+ crossorigin="anonymous"></script>
+ <script>
+ var loading = false;
+ function toggleLoadingScreen(){
+ if(loading){
+ $("#loading").remove();
+ loading = false;
+ }else{
+ $('<div id="loading">'+
+ '<span style="position: fixed; top: 50%;left: 50%;color: white;"><b>Loading...</b></span>'+
+ '</div>')
+ .css({position: "fixed",
+ top: 0,
+ left: 0,
+ width: "100%",
+ height: "100%",
+ 'background-color': "#000",
+ filter:"alpha(opacity=50)",
+ '-moz-opacity':"0.5",
+ '-khtml-opacity': "0.5",
+ opacity: "0.5",
+ 'z-index': "10000"})
+ .appendTo(document.body);
+ loading = true;
+
+ }
+ }
+ //Start loading screen before downloading plotly which is quite large
+ toggleLoadingScreen();
+ </script>
+ <script src="https://cdn.plot.ly/plotly-1.5.0.min.js"></script>
+ <script>
+ String.prototype.replaceAll = function(search, replacement) {
+ var target = this;
+ return target.split(search).join(replacement);
+ };
+ String.prototype.myTrim = function() {
+ var target = this;
+ return target.replace(/^\s+|\s+$/g, '');
+ };
+ function plotGraph(lines, sameSpacing, barPlot, prefix) {
+ var xvals = null;
+ var data = [];
+ while(lines.length > 0 &&
+ (lines[0].myTrim() == "" ||
+ lines[0].myTrim().indexOf(";") !== -1)){
+ var line = lines.shift().myTrim();
+ if(line == "" || line.startsWith("#")){
+ continue;
+ } else if(line.startsWith(";")) {
+ xvals = line.split(";")
+ xvals.shift(); // Remove first
+ xvals = $.map(xvals, function (i){
+ if(sameSpacing){
+ return "_"+i.myTrim();
+ }else{
+ return parseInt(i.myTrim(), 10);
+ }
+ });
+ }else{
+ line = line.split(";")
+ var label = prefix + line.shift().myTrim();
+ var yvals = $.map(line, function (i){
+ return parseFloat(i.myTrim(), 10);
+ });
+ var trace = {
+ x: xvals,
+ y: yvals,
+ mode: 'lines+markers',
+ name: label
+ };
+ if(barPlot){
+ trace['type'] = "bar";
+ }
+ data.push(trace);
+ }
+
+ }
+ return data;
+ }
+ function plotGraphs(){
+ var insertPlaceholder = $("#insertPlaceholder");
+ var sameSpacing = $('#sameSpacing').is(":checked");
+ var barPlot = $('#barPlot').is(":checked");
+ var lines = $("#dataField").val();
+ $('.showCheck').each(function() {
+ var item = $(this);
+ if(!item.is(":checked")){
+ lines = lines.replaceAll(item.val(), "#"+item.val())
+ }
+ });
+ lines = lines.split("$");
+ var nrOfGraphs = 0;
+ var scenarioDataMap = {};
+ var scenarioNrOfVersionsMap = {};
+ var scenarioList = [];
+ while(lines.length > 0){
+ var line = lines.shift().myTrim();
+ if(line == ""){
+ continue;
+ } else if(line.startsWith("Scenario:")) {
+ nrOfGraphs = nrOfGraphs + 1;
+ var name = line;
+ if(scenarioDataMap[name] === undefined){
+ scenarioDataMap[name] = [];
+ scenarioNrOfVersionsMap[name] = 0;
+ scenarioList.push(line);
+ }
+ scenarioNrOfVersionsMap[name] = scenarioNrOfVersionsMap[name] + 1;
+ var prefix = undefined;
+ if(scenarioNrOfVersionsMap[name] === 1){
+ prefix = "";
+ }else{
+ prefix = "Ver: " + scenarioNrOfVersionsMap[name] + " ";
+ }
+ scenarioDataMap[name] =
+ scenarioDataMap[name].concat(
+ plotGraph(lines, sameSpacing, barPlot, prefix));
+ }
+ }
+ $.each(scenarioList,
+ function( index, name ) {
+ var nrOfGraphs = index + 1;
+ var data = scenarioDataMap[name];
+ $( "<div class='added' id='graph"+nrOfGraphs+"'>")
+ .insertBefore( insertPlaceholder );
+ $( "<button type='button' class='added' id='fullscreenButton"+nrOfGraphs+"'>Fill screen</button>")
+ .insertBefore( insertPlaceholder );
+ $( "<span class='added'><br><hr><br></span>")
+ .insertBefore( insertPlaceholder );
+ var layout = {
+ title:name,
+ xaxis: {
+ title: '# of Processes'
+ },
+ yaxis: {
+ title: 'Operations/Second'
+ }
+
+ };
+
+ $("#fullscreenButton"+nrOfGraphs).click(
+ function(){
+ $('#graph'+nrOfGraphs).replaceWith(
+ $("<div class='added' id='graph"+nrOfGraphs+"'>"));
+ layout = $.extend({}, layout, {
+ width:$(window).width()-40,
+ height:$(window).height()-40
+ });
+ Plotly.newPlot('graph'+nrOfGraphs, data, layout);
+ });
+ Plotly.newPlot('graph'+nrOfGraphs, data, layout);
+
+ });
+
+
+ }
+ $(document).ready(function(){
+ $('#renderButton').click(
+ function(){
+ toggleLoadingScreen();
+ setTimeout(function(){
+ try {
+ $( ".added" ).remove();
+ plotGraphs();
+ toggleLoadingScreen();
+ } catch(e){
+ toggleLoadingScreen();
+ console.log(e);
+ alert("Error happened when parsing data.\n" +
+ "See console for more info");
+ }
+ }, 10);
+ });
+ setTimeout(function(){
+ $( ".added" ).remove();
+ plotGraphs();
+ toggleLoadingScreen();
+ }, 10);
+ });
+ </script>
+ </body>
+</html>
diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl
index a8264e5a84..62d9d0e0ae 100644
--- a/lib/stdlib/test/gen_fsm_SUITE.erl
+++ b/lib/stdlib/test/gen_fsm_SUITE.erl
@@ -521,14 +521,16 @@ error_format_status(Config) when is_list(Config) ->
error_logger_forwarder:register(),
OldFl = process_flag(trap_exit, true),
StateData = "called format_status",
+ Parent = self(),
{ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []),
%% bad return value in the gen_fsm loop
{'EXIT',{{bad_return_value, badreturn},_}} =
(catch gen_fsm:sync_send_event(Pid, badreturn)),
receive
{error,_GroupLeader,{Pid,
- "** State machine"++_,
- [Pid,{_,_,badreturn},idle,{formatted,StateData},_]}} ->
+ "** State machine "++_,
+ [Pid,badreturn,Parent,idle,{formatted,StateData},
+ {bad_return_value,badreturn}|_]}} ->
ok;
Other ->
io:format("Unexpected: ~p", [Other]),
@@ -541,12 +543,14 @@ terminate_crash_format(Config) when is_list(Config) ->
error_logger_forwarder:register(),
OldFl = process_flag(trap_exit, true),
StateData = crash_terminate,
+ Parent = self(),
{ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []),
stop_it(Pid),
receive
{error,_GroupLeader,{Pid,
- "** State machine"++_,
- [Pid,{_,_,_},idle,{formatted, StateData},_]}} ->
+ "** State machine "++_,
+ [Pid,stop,Parent,idle,{formatted, StateData},
+ {crash,terminate}|_]}} ->
ok;
Other ->
io:format("Unexpected: ~p", [Other]),
diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl
index 053233df9b..16cf8f43f9 100644
--- a/lib/stdlib/test/gen_statem_SUITE.erl
+++ b/lib/stdlib/test/gen_statem_SUITE.erl
@@ -121,7 +121,8 @@ end_per_testcase(_CaseName, Config) ->
start1(Config) ->
%%OldFl = process_flag(trap_exit, true),
- {ok,Pid0} = gen_statem:start_link(?MODULE, start_arg(Config, []), []),
+ {ok,Pid0} =
+ gen_statem:start_link(?MODULE, start_arg(Config, []), [{debug,[trace]}]),
ok = do_func_test(Pid0),
ok = do_sync_func_test(Pid0),
stop_it(Pid0),
@@ -135,7 +136,8 @@ start1(Config) ->
%% anonymous w. shutdown
start2(Config) ->
%% Dont link when shutdown
- {ok,Pid0} = gen_statem:start(?MODULE, start_arg(Config, []), []),
+ {ok,Pid0} =
+ gen_statem:start(?MODULE, start_arg(Config, []), []),
ok = do_func_test(Pid0),
ok = do_sync_func_test(Pid0),
stopped = gen_statem:call(Pid0, {stop,shutdown}),
@@ -511,7 +513,9 @@ abnormal1dirty(Config) ->
%% trap exit since we must link to get the real bad_return_ error
abnormal2(Config) ->
OldFl = process_flag(trap_exit, true),
- {ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []),
+ {ok,Pid} =
+ gen_statem:start_link(
+ ?MODULE, start_arg(Config, []), [{debug,[log]}]),
%% bad return value in the gen_statem loop
{{{bad_return_from_state_function,badreturn},_},_} =
@@ -529,7 +533,9 @@ abnormal2(Config) ->
%% trap exit since we must link to get the real bad_return_ error
abnormal3(Config) ->
OldFl = process_flag(trap_exit, true),
- {ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []),
+ {ok,Pid} =
+ gen_statem:start_link(
+ ?MODULE, start_arg(Config, []), [{debug,[log]}]),
%% bad return value in the gen_statem loop
{{{bad_action_from_state_function,badaction},_},_} =
@@ -547,7 +553,9 @@ abnormal3(Config) ->
%% trap exit since we must link to get the real bad_return_ error
abnormal4(Config) ->
OldFl = process_flag(trap_exit, true),
- {ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []),
+ {ok,Pid} =
+ gen_statem:start_link(
+ ?MODULE, start_arg(Config, []), [{debug,[log]}]),
%% bad return value in the gen_statem loop
BadTimeout = {badtimeout,4711,ouch},
@@ -641,51 +649,80 @@ state_enter(_Config) ->
end,
start =>
fun (enter, Prev, N) ->
- Self ! {enter,start,Prev,N},
+ Self ! {N,enter,start,Prev},
{keep_state,N + 1};
(internal, Prev, N) ->
- Self ! {internal,start,Prev,N},
+ Self ! {N,internal,start,Prev},
{keep_state,N + 1};
+ (timeout, M, N) ->
+ {keep_state, N + 1,
+ {reply, {Self,N}, {timeout,M}}};
({call,From}, repeat, N) ->
{repeat_state,N + 1,
- [{reply,From,{repeat,start,N}}]};
+ [{reply,From,{N,repeat,start}}]};
({call,From}, echo, N) ->
{next_state,wait,N + 1,
- {reply,From,{echo,start,N}}};
+ [{reply,From,{N,echo,start}},{timeout,0,N}]};
({call,From}, {stop,Reason}, N) ->
{stop_and_reply,Reason,
- [{reply,From,{stop,N}}],N + 1}
+ [{reply,From,{N,stop}}],N + 1}
end,
wait =>
fun (enter, Prev, N) when N < 5 ->
{repeat_state,N + 1,
- {reply,{Self,N},{enter,Prev}}};
+ [{reply,{Self,N},{enter,Prev}},
+ {timeout,0,N},
+ {state_timeout,0,N}]};
(enter, Prev, N) ->
- Self ! {enter,wait,Prev,N},
- {keep_state,N + 1};
+ Self ! {N,enter,wait,Prev},
+ {keep_state,N + 1,
+ [{timeout,0,N},
+ {state_timeout,0,N}]};
+ (timeout, M, N) ->
+ {keep_state, N + 1,
+ {reply, {Self,N}, {timeout,M}}};
+ (state_timeout, M, N) ->
+ {keep_state, N + 1,
+ {reply, {Self,N}, {state_timeout,M}}};
({call,From}, repeat, N) ->
{repeat_state_and_data,
- [{reply,From,{repeat,wait,N}}]};
+ [{reply,From,{N,repeat,wait}},
+ {timeout,0,N}]};
({call,From}, echo, N) ->
{next_state,start,N + 1,
[{next_event,internal,wait},
- {reply,From,{echo,wait,N}}]}
+ {reply,From,{N,echo,wait}}]}
end},
{ok,STM} =
gen_statem:start_link(
- ?MODULE, {map_statem,Machine,[state_enter]}, []),
-
- [{enter,start,start,1}] = flush(),
- {echo,start,2} = gen_statem:call(STM, echo),
- [{3,{enter,start}},{4,{enter,start}},{enter,wait,start,5}] = flush(),
- {wait,[6|_]} = sys:get_state(STM),
- {repeat,wait,6} = gen_statem:call(STM, repeat),
- [{enter,wait,wait,6}] = flush(),
- {echo,wait,7} = gen_statem:call(STM, echo),
- [{enter,start,wait,8},{internal,start,wait,9}] = flush(),
- {repeat,start,10} = gen_statem:call(STM, repeat),
- [{enter,start,start,11}] = flush(),
- {stop,12} = gen_statem:call(STM, {stop,bye}),
+ ?MODULE, {map_statem,Machine,[state_enter]},
+ [{debug,[trace,{log,17}]}]),
+ ok = sys:log(STM, false),
+ ok = sys:log(STM, true),
+
+ [{1,enter,start,start}] = flush(),
+ {2,echo,start} = gen_statem:call(STM, echo),
+ [{3,{enter,start}},
+ {4,{enter,start}},
+ {5,enter,wait,start},
+ {6,{timeout,5}},
+ {7,{state_timeout,5}}] = flush(),
+ {wait,[8|_]} = sys:get_state(STM),
+ {8,repeat,wait} = gen_statem:call(STM, repeat),
+ [{8,enter,wait,wait},
+ {9,{timeout,8}},
+ {10,{state_timeout,8}}] = flush(),
+ {11,echo,wait} = gen_statem:call(STM, echo),
+ [{12,enter,start,wait},
+ {13,internal,start,wait}] = flush(),
+ {14,repeat,start} = gen_statem:call(STM, repeat),
+ [{15,enter,start,start}] = flush(),
+
+ {ok,Log} = sys:log(STM, get),
+ io:format("sys:log ~p~n", [Log]),
+ ok = sys:log(STM, print),
+
+ {16,stop} = gen_statem:call(STM, {stop,bye}),
[{'EXIT',STM,bye}] = flush(),
{noproc,_} =
@@ -1447,7 +1484,8 @@ enter_loop(_Config) ->
%% Locally registered process + {local,Name}
{ok,Pid1a} =
- proc_lib:start_link(?MODULE, enter_loop, [local,local]),
+ proc_lib:start_link(
+ ?MODULE, enter_loop, [local,local,[{debug,[{log,7}]}]]),
yes = gen_statem:call(Pid1a, 'alive?'),
stopped = gen_statem:call(Pid1a, stop),
receive
@@ -1459,7 +1497,8 @@ enter_loop(_Config) ->
%% Unregistered process + {local,Name}
{ok,Pid1b} =
- proc_lib:start_link(?MODULE, enter_loop, [anon,local]),
+ proc_lib:start_link(
+ ?MODULE, enter_loop, [anon,local,[{debug,[log]}]]),
receive
{'EXIT',Pid1b,process_not_registered} ->
ok
@@ -1568,6 +1607,9 @@ enter_loop(_Config) ->
ok = verify_empty_msgq().
enter_loop(Reg1, Reg2) ->
+ enter_loop(Reg1, Reg2, []).
+%%
+enter_loop(Reg1, Reg2, Opts) ->
process_flag(trap_exit, true),
case Reg1 of
local -> register(armitage, self());
@@ -1579,15 +1621,15 @@ enter_loop(Reg1, Reg2) ->
case Reg2 of
local ->
gen_statem:enter_loop(
- ?MODULE, [], state0, [], {local,armitage});
+ ?MODULE, Opts, state0, [], {local,armitage});
global ->
gen_statem:enter_loop(
- ?MODULE, [], state0, [], {global,armitage});
+ ?MODULE, Opts, state0, [], {global,armitage});
via ->
gen_statem:enter_loop(
- ?MODULE, [], state0, [], {via, dummy_via, armitage});
+ ?MODULE, Opts, state0, [], {via, dummy_via, armitage});
anon ->
- gen_statem:enter_loop(?MODULE, [], state0, [])
+ gen_statem:enter_loop(?MODULE, Opts, state0, [])
end.
undef_code_change(_Config) ->
@@ -1619,7 +1661,9 @@ undef_terminate2(_Config) ->
undef_in_terminate(_Config) ->
Data = {undef_in_terminate, {?MODULE, terminate}},
- {ok, Statem} = gen_statem:start(?MODULE, {data, Data}, []),
+ {ok, Statem} =
+ gen_statem:start(
+ ?MODULE, {data, Data}, [{debug,[log]}]),
try
gen_statem:stop(Statem),
ct:fail(should_crash)
diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl
index 824f5d19f2..4eb5b1772c 100644
--- a/lib/stdlib/test/io_SUITE.erl
+++ b/lib/stdlib/test/io_SUITE.erl
@@ -32,7 +32,7 @@
io_with_huge_message_queue/1, format_string/1,
maps/1, coverage/1, otp_14178_unicode_atoms/1, otp_14175/1,
otp_14285/1, limit_term/1, otp_14983/1, otp_15103/1, otp_15076/1,
- otp_15159/1, otp_15639/1]).
+ otp_15159/1, otp_15639/1, otp_15705/1, otp_15847/1, otp_15875/1]).
-export([pretty/2, trf/3]).
@@ -65,7 +65,7 @@ all() ->
io_lib_width_too_small, io_with_huge_message_queue,
format_string, maps, coverage, otp_14178_unicode_atoms, otp_14175,
otp_14285, limit_term, otp_14983, otp_15103, otp_15076, otp_15159,
- otp_15639].
+ otp_15639, otp_15705, otp_15847, otp_15875].
%% Error cases for output.
error_1(Config) when is_list(Config) ->
@@ -2504,9 +2504,11 @@ otp_14983(_Config) ->
trunc_string() ->
"str " = trf("str ", [], 10),
- "str ..." = trf("str ~s", ["str"], 6),
+ "str str" = trf("str ~s", ["str"], 6),
+ "str ..." = trf("str ~s", ["str1"], 6),
"str str" = trf("str ~s", ["str"], 7),
- "str ..." = trf("str ~8s", ["str"], 6),
+ "str str" = trf("str ~8s", ["str"], 6),
+ "str ..." = trf("str ~8s", ["str1"], 6),
Pa = filename:dirname(code:which(?MODULE)),
{ok, UNode} = test_server:start_node(printable_range_unicode, slave,
[{args, " +pc unicode -pa " ++ Pa}]),
@@ -2680,3 +2682,39 @@ otp_15639(_Config) ->
"\"12345678\"..." = pretty("123456789"++[x], UOpts),
"[[...]|...]" = pretty(["1","2","3","4","5","6","7","8"], UOpts),
ok.
+
+otp_15705(_Config) ->
+ L = [<<"an">>,["at"],[["om"]]],
+ "..." = trf("~s", [L], 0),
+ "..." = trf("~s", [L], 1),
+ "..." = trf("~s", [L], 2),
+ "..." = trf("~s", [L], 3),
+ "a..." = trf("~s", [L], 4),
+ "an..." = trf("~s", [L], 5),
+ "anatom" = trf("~s", [L], 6),
+ L2 = ["a",[<<"na">>],[["tom"]]],
+ "..." = trf("~s", [L2], 3),
+ "a..." = trf("~s", [L2], 4),
+ "an..." = trf("~s", [L2], 5),
+ "anatom" = trf("~s", [L2], 6),
+
+ A = [[<<"äpple"/utf8>>, "plus", <<"äpple">>]],
+ "äp..." = trf("~ts", [A], 5),
+ "äppleplusäpple" = trf("~ts", [A], 14),
+ U = [["ки"],"рилл","и́ческий атом"],
+ "ки..." = trf("~ts", [U], 5),
+ "кирилли́ческий..." = trf("~ts", [U], 16),
+ "кирилли́ческий атом" = trf("~ts", [U], 20),
+
+ "|кирилли́чес|" = trf("|~10ts|", [U], -1),
+ ok.
+
+otp_15847(_Config) ->
+ T = {someRecord,<<"1234567890">>,some,more},
+ "{someRecord,<<...>>,...}" =
+ pretty(T, [{chars_limit,20}, {encoding,latin1}]),
+ ok.
+
+otp_15875(_Config) ->
+ S = io_lib:format("~tp", [[{0, [<<"00">>]}]], [{chars_limit, 18}]),
+ "[{0,[<<48,...>>]}]" = lists:flatten(S).
diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl
index 984b51e7ae..c3c54710eb 100644
--- a/lib/stdlib/test/lists_SUITE.erl
+++ b/lib/stdlib/test/lists_SUITE.erl
@@ -158,6 +158,20 @@ append_2(Config) when is_list(Config) ->
"abcdef"=lists:append("abc", "def"),
[hej, du]=lists:append([hej], [du]),
[10, [elem]]=lists:append([10], [[elem]]),
+
+ %% Trapping, both crashing and otherwise.
+ [append_trapping_1(N) || N <- lists:seq(0, 20)],
+
+ ok.
+
+append_trapping_1(N) ->
+ List = lists:duplicate(N + (1 bsl N), gurka),
+ ImproperList = List ++ crash,
+
+ {'EXIT',_} = (catch (ImproperList ++ [])),
+
+ [3, 2, 1 | List] = lists:reverse(List ++ [1, 2, 3]),
+
ok.
%% Tests the lists:reverse() implementation. The function is
@@ -1679,7 +1693,7 @@ make_fun() ->
receive {Pid, Fun} -> Fun end.
make_fun(Pid) ->
- Pid ! {self(), fun make_fun/1}.
+ Pid ! {self(), fun (X) -> {X, Pid} end}.
fun_pid(Fun) ->
erlang:fun_info(Fun, pid).
@@ -2586,6 +2600,15 @@ subtract(Config) when is_list(Config) ->
[1,2,3,4,5,6,7,8,9,9999,10000,20,21,22] =
sub(lists:seq(1, 10000)++[20,21,22], lists:seq(10, 9998)),
+ %% ERL-986; an integer overflow relating to term comparison
+ %% caused subtraction to be inconsistent.
+ Ids = [2985095936,47540628,135460048,1266126295,240535295,
+ 115724671,161800351,4187206564,4178142725,234897063,
+ 14773162,6662515191,133150693,378034895,1874402262,
+ 3507611978,22850922,415521280,253360400,71683243],
+
+ [] = id(Ids) -- id(Ids),
+
%% Floats/integers.
[42.0,42.0] = sub([42.0,42,42.0], [42,42,42]),
[1,2,3,4,43.0] = sub([1,2,3,4,5,42.0,43.0], [42.0,5]),
@@ -2613,6 +2636,8 @@ subtract(Config) when is_list(Config) ->
ok.
+id(I) -> I.
+
sub_non_matching(A, B) ->
A = sub(A, B).
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index d7354438f9..8a43f15d2c 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2004-2018. All Rights Reserved.
+%% Copyright Ericsson AB 2004-2019. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -2436,7 +2436,7 @@ info(Config) when is_list(Config) ->
<<"{'EXIT', {badarg, _}} =
(catch qlc:info([X || {X} <- []], {n_elements, 0})),
L = lists:seq(1, 1000),
- \"[1,2,3,4,5,6,7,8,9,10|'...']\" = qlc:info(L, {n_elements, 10}),
+ \"[1, 2, 3, 4, 5, 6, 7, 8, 9, 10 | '...']\" = qlc:info(L, {n_elements, 10}),
{cons,A1,{integer,A2,1},{atom,A3,'...'}} =
qlc:info(L, [{n_elements, 1},{format,abstract_code}]),
1 = erl_anno:line(A1),
@@ -2447,8 +2447,8 @@ info(Config) when is_list(Config) ->
{atom,_,'...'}}}},
{call,_,_,_}]} =
qlc:info(Q, [{n_elements, 3},{format,abstract_code}]),
- \"ets:match_spec_run([a,b,c,d,e,f],\n\"
- \" ets:match_spec_compile([{'$1',[true],\"
+ \"ets:match_spec_run([a, b, c, d, e, f],\n\"
+ \" ets:match_spec_compile([{'$1', [true], \"
\"[{{'$1'}}]}]))\" =
qlc:info(Q, [{n_elements, infinity}])">>,
@@ -3163,19 +3163,13 @@ lookup2(Config) when is_list(Config) ->
[a] = lookup_keys(Q)
end, [{a},{b},{c}])">>,
- {cres,
- <<"etsc(fun(E) ->
+ <<"etsc(fun(E) ->
Q = qlc:q([X || {X}=Y <- ets:table(E),
element(2, Y) == b,
X =:= 1]),
[] = qlc:e(Q),
false = lookup_keys(Q)
- end, [{1,b},{2,3}])">>,
- %% {warnings,[{2,sys_core_fold,nomatch_guard},
- %% {3,qlc,nomatch_filter},
- %% {3,sys_core_fold,{eval_failure,badarg}}]}},
- {warnings,[{2,sys_core_fold,nomatch_guard},
- {3,sys_core_fold,{eval_failure,badarg}}]}},
+ end, [{1,b},{2,3}])">>,
<<"etsc(fun(E) ->
Q = qlc:q([X || {X} <- ets:table(E), element(1,{X}) =:= 1]),
@@ -6553,7 +6547,7 @@ otp_7114(Config) when is_list(Config) ->
otp_7232(Config) when is_list(Config) ->
Ts = [<<"L = [fun math:sqrt/1, list_to_pid(\"<0.4.1>\"),
erlang:make_ref()],
- \"[fun math:sqrt/1,<0.4.1>,#Ref<\" ++ _ = qlc:info(L),
+ \"[fun math:sqrt/1, <0.4.1>, #Ref<\" ++ _ = qlc:info(L),
{call,_,
{remote,_,{atom,_,qlc},{atom,_,sort}},
[{cons,_,
@@ -6569,7 +6563,7 @@ otp_7232(Config) when is_list(Config) ->
\"qlc:sort([55296,56296],[{order,fun'-function/0-fun-2-'/2}])\" =
format_info(Q, true),
AC = qlc:info(Q, {format, abstract_code}),
- \"qlc:sort([55296,56296], [{order,fun '-function/0-fun-2-'/2}])\" =
+ \"qlc:sort([55296, 56296], [{order, fun '-function/0-fun-2-'/2}])\" =
binary_to_list(iolist_to_binary(erl_pp:expr(AC)))">>,
%% OTP-7234. erl_parse:abstract() handles bit strings
@@ -7094,21 +7088,21 @@ manpage(Config) when is_list(Config) ->
\" V1 =\n\"
\" qlc:q([ \n\"
\" SQV ||\n\"
- \" SQV <- [x,y]\n\"
+ \" SQV <- [x, y]\n\"
\" ],\n\"
- \" [{unique,true}]),\n\"
+ \" [{unique, true}]),\n\"
\" V2 =\n\"
\" qlc:q([ \n\"
\" SQV ||\n\"
- \" SQV <- [a,b]\n\"
+ \" SQV <- [a, b]\n\"
\" ],\n\"
- \" [{unique,true}]),\n\"
+ \" [{unique, true}]),\n\"
\" qlc:q([ \n\"
- \" {X,Y} ||\n\"
+ \" {X, Y} ||\n\"
\" X <- V1,\n\"
\" Y <- V2\n\"
\" ],\n\"
- \" [{unique,true}])\n\"
+ \" [{unique, true}])\n\"
\"end\",
true = B =:= qlc:info(QH, unique_all)">>,
@@ -7124,19 +7118,19 @@ manpage(Config) when is_list(Config) ->
\" V1 =\n\"
\" qlc:q([ \n\"
\" P0 ||\n\"
- \" P0 = {W,Y} <- ets:table(_)\n\"
+ \" P0 = {W, Y} <- ets:table(_)\n\"
\" ]),\n\"
\" V2 =\n\"
\" qlc:q([ \n\"
- \" [G1|G2] ||\n\"
+ \" [G1 | G2] ||\n\"
\" G2 <- V1,\n\"
\" G1 <- ets:table(_),\n\"
\" element(2, G1) =:= element(1, G2)\n\"
\" ],\n\"
- \" [{join,lookup}]),\n\"
+ \" [{join, lookup}]),\n\"
\" qlc:q([ \n\"
- \" {X,Z,W} ||\n\"
- \" [{X,Z}|{W,Y}] <- V2\n\"
+ \" {X, Z, W} ||\n\"
+ \" [{X, Z} | {W, Y}] <- V2\n\"
\" ])\n\"
\"end\",
Info1 =
@@ -7161,25 +7155,28 @@ manpage(Config) when is_list(Config) ->
\" V1 =\n\"
\" qlc:q([ \n\"
\" P0 ||\n\"
- \" P0 = {X,Z} <- qlc:keysort(1, [{a,1},{b,4},{c,6}], [])\n\"
+ \" P0 = {X, Z} <-\n\"
+ \" qlc:keysort(1, [{a, 1}, {b, 4}, {c, 6}], [])\n\"
\" ]),\n\"
\" V2 =\n\"
\" qlc:q([ \n\"
\" P0 ||\n\"
- \" P0 = {W,Y} <- qlc:keysort(2, [{2,a},{3,b},{4,c}], [])\n\"
+ \" P0 = {W, Y} <-\n\"
+ \" qlc:keysort(2, [{2, a}, {3, b}, {4, c}], [])\n\"
+
\" ]),\n\"
\" V3 =\n\"
\" qlc:q([ \n\"
- \" [G1|G2] ||\n\"
+ \" [G1 | G2] ||\n\"
\" G1 <- V1,\n\"
\" G2 <- V2,\n\"
\" element(1, G1) == element(2, G2)\n\"
\" ],\n\"
- \" [{join,merge},{cache,list}]),\n\"
+ \" [{join, merge}, {cache, list}]),\n\"
\" qlc:q([ \n\"
- \" {A,X,Z,W} ||\n\"
- \" A <- [a,b,c],\n\"
- \" [{X,Z}|{W,Y}] <- V3,\n\"
+ \" {A, X, Z, W} ||\n\"
+ \" A <- [a, b, c],\n\"
+ \" [{X, Z} | {W, Y}] <- V3,\n\"
\" X =:= Y\n\"
\" ])\n\"
\"end\",
@@ -7221,14 +7218,21 @@ manpage(Config) when is_list(Config) ->
gb_trees:lookup(K,
gb_trees:from_orddict([]))
of
- {value,V} ->
- [{K,V}];
+ {value, V} ->
+ [{K, V}];
none ->
[]
end
end,
- [{1,a},{1,b},{1,c},{2,a},{2,b},{2,c}]),
- ets:match_spec_compile([{{{'$1','$2'},'_'},[],['$1']}]))\",
+ [{1, a},
+ {1, b},
+ {1, c},
+ {2, a},
+ {2, b},
+ {2, c}]),
+ ets:match_spec_compile([{{{'$1', '$2'}, '_'},
+ [],
+ ['$1']}]))\",
L = qlc:info(QH)">>
],
run(Config, Ts),
diff --git a/lib/stdlib/test/rand_SUITE.erl b/lib/stdlib/test/rand_SUITE.erl
index b76c9f5341..7685c17967 100644
--- a/lib/stdlib/test/rand_SUITE.erl
+++ b/lib/stdlib/test/rand_SUITE.erl
@@ -21,24 +21,7 @@
-compile({nowarn_deprecated_function,[{random,seed,1},
{random,uniform_s,1},
{random,uniform_s,2}]}).
-
--export([all/0, suite/0, groups/0, group/1]).
-
--export([interval_int/1, interval_float/1, seed/1,
- api_eq/1, reference/1,
- basic_stats_uniform_1/1, basic_stats_uniform_2/1,
- basic_stats_standard_normal/1,
- basic_stats_normal/1,
- stats_standard_normal_box_muller/1,
- stats_standard_normal_box_muller_2/1,
- stats_standard_normal/1,
- uniform_real_conv/1,
- plugin/1, measure/1,
- reference_jump_state/1, reference_jump_procdict/1]).
-
--export([test/0, gen/1]).
-
--export([uniform_real_gen/1, uniform_gen/2]).
+-compile([export_all, nowarn_export_all]).
-include_lib("common_test/include/ct.hrl").
@@ -56,7 +39,8 @@ all() ->
{group, distr_stats},
uniform_real_conv,
plugin, measure,
- {group, reference_jump}
+ {group, reference_jump},
+ short_jump
].
groups() ->
@@ -95,7 +79,7 @@ test() ->
end, Tests).
algs() ->
- [exrop, exsp, exs1024s, exs64, exsplus, exs1024].
+ [exsss, exrop, exsp, exs1024s, exs64, exsplus, exs1024, exro928ss].
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -125,7 +109,7 @@ seed_1(Alg) ->
S0 = get(rand_seed),
S0 = rand:seed_s(Alg, {0, 0, 0}),
%% Check that process_dict should not be used for seed_s functionality
- _ = rand:seed_s(Alg, {1, 0, 0}),
+ _ = rand:seed_s(Alg, 4711),
S0 = get(rand_seed),
%% Test export
ES0 = rand:export_seed(),
@@ -262,31 +246,43 @@ reference(Config) when is_list(Config) ->
ok.
reference_1(Alg) ->
- Refval = reference_val(Alg),
- Testval = gen(Alg),
- case Refval =:= Testval of
- true -> ok;
- false when Refval =:= not_implemented ->
- exit({not_implemented,Alg});
- false ->
- io:format("Failed: ~p~n",[Alg]),
- io:format("Length ~p ~p~n",[length(Refval), length(Testval)]),
- io:format("Head ~p ~p~n",[hd(Refval), hd(Testval)]),
- exit(wrong_value)
+ Refval = reference_val(Alg),
+ if
+ Refval =:= not_implemented -> Refval;
+ true ->
+ case gen(Alg) of
+ Refval ->
+ io:format("Ok: ~p~n",[Alg]),
+ ok;
+ Testval ->
+ io:format("Failed: ~p~n",[Alg]),
+ io:format("Length ~p ~p~n",[length(Refval), length(Testval)]),
+ io:format("Head ~p ~p~n",[hd(Refval), hd(Testval)]),
+ show_wrong(Refval, Testval),
+ exit(wrong_value)
+ end
end.
+show_wrong([], []) ->
+ ok;
+show_wrong([H|T1], [H|T2]) ->
+ show_wrong(T1, T2);
+show_wrong([H1|_], [H2|_]) ->
+ io:format("Wrong ~p ~p~n",[H1,H2]).
+
+
gen(Algo) ->
State =
- case Algo of
- exs64 -> %% Printed with orig 'C' code and this seed
- rand:seed_s({exs64, 12345678});
- _ when Algo =:= exsplus; Algo =:= exsp; Algo =:= exrop ->
+ if
+ Algo =:= exs64 -> %% Printed with orig 'C' code and this seed
+ rand:seed_s(exs64, [12345678]);
+ Algo =:= exsplus; Algo =:= exsp; Algo =:= exrop; Algo =:= exsss ->
%% Printed with orig 'C' code and this seed
- rand:seed_s({Algo, [12345678|12345678]});
- _ when Algo =:= exs1024; Algo =:= exs1024s ->
+ rand:seed_s(Algo, [12345678,12345678]);
+ Algo =:= exs1024; Algo =:= exs1024s; Algo =:= exro928ss ->
%% Printed with orig 'C' code and this seed
- rand:seed_s({Algo, {lists:duplicate(16, 12345678), []}});
- _ ->
+ rand:seed_s(Algo, lists:duplicate(16, 12345678));
+ true ->
rand:seed(Algo, {100, 200, 300})
end,
Max = range(State),
@@ -442,7 +438,7 @@ stats_standard_normal_box_muller(Config) when is_list(Config) ->
([S|Z]) ->
{Z, [S]}
end,
- State = [rand:seed(exrop)],
+ State = [rand:seed(exsss)],
stats_standard_normal(NormalS, State, 3)
catch error:_ ->
{skip, "math:erfc/1 not supported"}
@@ -467,7 +463,7 @@ stats_standard_normal_box_muller_2(Config) when is_list(Config) ->
([S|Z]) ->
{Z, [S]}
end,
- State = [rand:seed(exrop)],
+ State = [rand:seed(exsss)],
stats_standard_normal(NormalS, State, 3)
catch error:_ ->
{skip, "math:erfc/1 not supported"}
@@ -479,7 +475,7 @@ stats_standard_normal(Config) when is_list(Config) ->
try math:erfc(1.0) of
_ ->
stats_standard_normal(
- fun rand:normal_s/1, rand:seed_s(exrop), Retries)
+ fun rand:normal_s/1, rand:seed_s(exsss), Retries)
catch error:_ ->
{skip, "math:erfc/1 not supported"}
end.
@@ -853,7 +849,8 @@ do_measure(_Config) ->
Algs =
algs() ++
try crypto:strong_rand_bytes(1) of
- <<_>> -> [crypto64, crypto_cache, crypto]
+ <<_>> ->
+ [crypto64, crypto_cache, crypto_aes, crypto]
catch
error:low_entropy -> [];
error:undef -> []
@@ -1074,7 +1071,7 @@ do_measure(_Config) ->
end,
State)
end,
- exrop, TMarkNormalFloat),
+ exsss, TMarkNormalFloat),
ok.
-define(LOOP_MEASURE, (?LOOP div 5)).
@@ -1102,6 +1099,10 @@ measure_1(RangeFun, Fun, Alg, TMark) ->
{rand, crypto:rand_seed_alg(crypto_cache)};
crypto ->
{rand, crypto:rand_seed_s()};
+ crypto_aes ->
+ {rand,
+ crypto:rand_seed_alg(
+ crypto_aes, crypto:strong_rand_bytes(256))};
random ->
{random, random:seed(os:timestamp()), get(random_seed)};
_ ->
@@ -1117,7 +1118,7 @@ measure_1(RangeFun, Fun, Alg, TMark) ->
_ -> (Time * 100 + 50) div TMark
end,
io:format(
- "~.12w: ~p ns ~p% [16#~.16b]~n",
+ "~.20w: ~p ns ~p% [16#~.16b]~n",
[Alg, (Time * 1000 + 500) div ?LOOP_MEASURE,
Percent, Range]),
Parent ! {self(), Time},
@@ -1142,104 +1143,156 @@ reference_jump_state(Config) when is_list(Config) ->
ok.
reference_jump_1(Alg) ->
- Refval = reference_jump_val(Alg),
- Testval = gen_jump_1(Alg),
- case Refval =:= Testval of
- true -> ok;
- false ->
- io:format("Failed: ~p~n",[Alg]),
- io:format("Length ~p ~p~n",[length(Refval), length(Testval)]),
- io:format("Head ~p ~p~n",[hd(Refval), hd(Testval)]),
- io:format("Vals ~p ~p~n",[Refval, Testval]),
- exit(wrong_value)
+ Refval = reference_jump_val(Alg),
+ if
+ Refval =:= not_implemented -> Refval;
+ true ->
+ case gen_jump_1(Alg) of
+ Refval -> ok;
+ Testval ->
+ io:format(
+ "Failed: ~p~n",[Alg]),
+ io:format(
+ "Length ~p ~p~n",
+ [length(Refval), length(Testval)]),
+ io:format(
+ "Head ~p ~p~n",[hd(Refval), hd(Testval)]),
+ io:format(
+ "Vals ~p ~p~n",[Refval, Testval]),
+ exit(wrong_value)
+ end
end.
gen_jump_1(Algo) ->
- State =
- case Algo of
- exs64 -> %% Test exception of not_implemented notice
- try rand:jump(rand:seed_s(exs64))
- catch
- error:not_implemented -> not_implemented
- end;
- _ when Algo =:= exsplus; Algo =:= exsp; Algo =:= exrop ->
- %% Printed with orig 'C' code and this seed
- rand:seed_s({Algo, [12345678|12345678]});
- _ when Algo =:= exs1024; Algo =:= exs1024s ->
- %% Printed with orig 'C' code and this seed
- rand:seed_s({Algo, {lists:duplicate(16, 12345678), []}});
- _ -> % unimplemented
- not_implemented
- end,
- case State of
- not_implemented -> [not_implemented];
- _ ->
- Max = range(State),
- gen_jump_1(?LOOP_JUMP, State, Max, [])
+ case Algo of
+ exs64 -> %% Test exception of not_implemented notice
+ try rand:jump(rand:seed_s(exs64))
+ catch
+ error:not_implemented -> [error_not_implemented]
+ end;
+ _ when Algo =:= exsplus; Algo =:= exsp; Algo =:= exrop; Algo =:= exsss ->
+ %% Printed with orig 'C' code and this seed
+ gen_jump_2(
+ rand:seed_s(Algo, [12345678,12345678]));
+ _ when Algo =:= exs1024; Algo =:= exs1024s; Algo =:= exro928ss ->
+ %% Printed with orig 'C' code and this seed
+ gen_jump_2(
+ rand:seed_s(Algo, lists:duplicate(16, 12345678)))
end.
-gen_jump_1(N, State0, Max, Acc) when N > 0 ->
+gen_jump_2(State) ->
+ Max = range(State),
+ gen_jump_3(?LOOP_JUMP, State, Max, []).
+
+gen_jump_3(N, State0, Max, Acc) when N > 0 ->
{_, State1} = rand:uniform_s(Max, State0),
{Random, State2} = rand:uniform_s(Max, rand:jump(State1)),
case N rem (?LOOP_JUMP div 100) of
- 0 -> gen_jump_1(N-1, State2, Max, [Random|Acc]);
- _ -> gen_jump_1(N-1, State2, Max, Acc)
+ 0 -> gen_jump_3(N-1, State2, Max, [Random|Acc]);
+ _ -> gen_jump_3(N-1, State2, Max, Acc)
end;
-gen_jump_1(_, _, _, Acc) -> lists:reverse(Acc).
+gen_jump_3(_, _, _, Acc) -> lists:reverse(Acc).
%% Check if each algorithm generates the proper jump sequence
%% with the internal state in the process dictionary.
reference_jump_procdict(Config) when is_list(Config) ->
- [reference_jump_0(Alg) || Alg <- algs()],
+ [reference_jump_p1(Alg) || Alg <- algs()],
ok.
-reference_jump_0(Alg) ->
+reference_jump_p1(Alg) ->
Refval = reference_jump_val(Alg),
- Testval = gen_jump_0(Alg),
- case Refval =:= Testval of
- true -> ok;
- false ->
- io:format("Failed: ~p~n",[Alg]),
- io:format("Length ~p ~p~n",[length(Refval), length(Testval)]),
- io:format("Head ~p ~p~n",[hd(Refval), hd(Testval)]),
- exit(wrong_value)
+ if
+ Refval =:= not_implemented -> Refval;
+ true ->
+ case gen_jump_p1(Alg) of
+ Refval -> ok;
+ Testval ->
+ io:format("Failed: ~p~n",[Alg]),
+ io:format("Length ~p ~p~n",[length(Refval), length(Testval)]),
+ io:format("Head ~p ~p~n",[hd(Refval), hd(Testval)]),
+ exit(wrong_value)
+ end
end.
-gen_jump_0(Algo) ->
- Seed = case Algo of
- exs64 -> %% Test exception of not_implemented notice
- try
- _ = rand:seed(exs64),
- rand:jump()
- catch
- error:not_implemented -> not_implemented
- end;
- _ when Algo =:= exsplus; Algo =:= exsp; Algo =:= exrop ->
- %% Printed with orig 'C' code and this seed
- rand:seed({Algo, [12345678|12345678]});
- _ when Algo =:= exs1024; Algo =:= exs1024s ->
- %% Printed with orig 'C' code and this seed
- rand:seed({Algo, {lists:duplicate(16, 12345678), []}});
- _ -> % unimplemented
- not_implemented
- end,
- case Seed of
- not_implemented -> [not_implemented];
- _ ->
- Max = range(Seed),
- gen_jump_0(?LOOP_JUMP, Max, [])
+gen_jump_p1(Algo) ->
+ case Algo of
+ exs64 -> %% Test exception of not_implemented notice
+ try
+ _ = rand:seed(exs64),
+ rand:jump()
+ catch
+ error:not_implemented -> [error_not_implemented]
+ end;
+ _ when Algo =:= exsplus; Algo =:= exsp; Algo =:= exrop; Algo =:= exsss ->
+ %% Printed with orig 'C' code and this seed
+ gen_jump_p2(
+ rand:seed(Algo, [12345678,12345678]));
+ _ when Algo =:= exs1024; Algo =:= exs1024s; Algo =:= exro928ss ->
+ %% Printed with orig 'C' code and this seed
+ gen_jump_p2(
+ rand:seed(Algo, lists:duplicate(16, 12345678)))
end.
-gen_jump_0(N, Max, Acc) when N > 0 ->
+gen_jump_p2(Seed) ->
+ Max = range(Seed),
+ gen_jump_p3(?LOOP_JUMP, Max, []).
+
+gen_jump_p3(N, Max, Acc) when N > 0 ->
_ = rand:uniform(Max),
_ = rand:jump(),
Random = rand:uniform(Max),
case N rem (?LOOP_JUMP div 100) of
- 0 -> gen_jump_0(N-1, Max, [Random|Acc]);
- _ -> gen_jump_0(N-1, Max, Acc)
+ 0 -> gen_jump_p3(N-1, Max, [Random|Acc]);
+ _ -> gen_jump_p3(N-1, Max, Acc)
end;
-gen_jump_0(_, _, Acc) -> lists:reverse(Acc).
+gen_jump_p3(_, _, Acc) -> lists:reverse(Acc).
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+short_jump(Config) when is_list(Config) ->
+ Seed = erlang:system_time(),
+ short_jump(
+ rand:seed_s(exro928ss, Seed),
+ fun ({Alg,AlgState}) ->
+ {Alg,rand:exro928_jump_2pow20(AlgState)}
+ end),
+ short_jump(
+ crypto:rand_seed_alg_s(crypto_aes, integer_to_list(Seed)),
+ fun ({Alg,AlgState}) ->
+ {Alg,crypto:rand_plugin_aes_jump_2pow20(AlgState)}
+ end),
+ ok.
+
+short_jump({#{bits := Bits},_} = State_0, Jump2Pow20) ->
+ Range = 1 bsl Bits,
+ State_1 = repeat(7, Range, State_0),
+ %%
+ State_2a = repeat(1 bsl 20, Range, State_1),
+ State_2b = Jump2Pow20(State_1),
+ check(17, Range, State_2a, State_2b),
+ %%
+ {_,State_3a} = rand:uniform_s(Range, State_2a),
+ State_4a = Jump2Pow20(State_3a),
+ State_4b = repeat((1 bsl 20) + 1, Range, State_2b),
+ check(17, Range, State_4a, State_4b).
+
+repeat(0, _Range, State) ->
+ State;
+repeat(N, Range, State) ->
+ {_, NewState} = rand:uniform_s(Range, State),
+ repeat(N - 1, Range, NewState).
+
+check(0, _Range, _StateA, _StateB) ->
+ ok;
+check(N, Range, StateA, StateB) ->
+ {V,NewStateA} = rand:uniform_s(Range, StateA),
+ case rand:uniform_s(Range, StateB) of
+ {V,NewStateB} ->
+ check(N - 1, Range, NewStateA, NewStateB);
+ {Wrong,_} ->
+ ct:fail({Wrong,neq,V,for,N})
+ end.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%% Data
@@ -1324,6 +1377,34 @@ reference_val(exsplus) ->
16#3dd493b8012970f,16#be13bed1e00e5c,16#ceef033b74ae10,16#3da38c6a50abe03,
16#15cbd1a421c7a8c,16#22794e3ec6ef3b1,16#26154d26e7ea99f,16#3a66681359a6ab6];
+reference_val(exsss) ->
+ [16#108e8d5b01,16#33b72092117209a,16#224d4d2961a2d0a,16#2c4c81aac3da48d,
+ 16#2f4bc39bfc36f3a,16#41826d4c4d243a,16#19871b8bb4e23ee,16#3e2112cdf9384b1,
+ 16#69801943bf91ab,16#2de1a603c31ec45,16#a90ca1991b831e,16#51ca29571a69a7,
+ 16#93ce3e511906cf,16#93ebc5768aef75,16#2412f284b902ae7,16#1ac10e758410c52,
+ 16#3f32494560368f6,16#39a5e82dcf0de95,16#3f4b14d59cc6a21,16#3174668db0b36ae,
+ 16#1449812fb8bd54e,16#eaca1f8ece51e1,16#2564b2545fd23c1,16#3cf3a2d2217e0d7,
+ 16#226f4164ba1d054,16#10dac9ae207ceef,16#17f2c4b2d40fcb9,16#1c1b282d386fdcb,
+ 16#a264f450ba2912,16#2a0a1dd67e52666,16#2be84eb835cb1e1,16#2a1cd9aa16ccc37,
+ 16#7dd5e8c2b3f490,16#254a3db4976c05b,16#2a0a67971ec1e63,16#13a0cbf7c0eed8a,
+ 16#3192d7edc0a20bc,16#2705ad756292e84,16#3ec429a18119c81,16#25944b38baa975b,
+ 16#291dcc43e3256f4,16#30d10b759237db,16#c1522a652058a,16#8ef1e9378381e6,
+ 16#1f442f33c2439f4,16#186087710a73818,16#12887f94b2b8387,16#3e42e8b1f3c9b4b,
+ 16#e462859d55f9d8,16#2356ae85be908de,16#15e96a927b3bc52,16#35c6dc52511ce46,
+ 16#7bc0624ce66e01,16#33ab7d95b738322,16#26f01effc182aa0,16#1b66ae7eaafea88,
+ 16#278f3dc14943b90,16#22178bc8d8faf28,16#396c37d53c11985,16#5e0d79d0b10f18,
+ 16#1be3de3b5675ec,16#d4db298f1f4b50,16#2da6cb99bb5c7b1,16#130b2dc17d03be8,
+ 16#f1847e7e059e9f,16#2da6591788326e7,16#222e4a18c24211c,16#949213ca49baab,
+ 16#b5129fec56f6a2,16#30f25f1e926f43e,16#1ddd8d04445fb4d,16#15995b542514150,
+ 16#1595fe879296296,16#e2f237a488453b,16#23e5cd2d6047890,16#3a5dc88fc954666,
+ 16#89bca9969b103,16#5e6893cd35dc63,16#1fed534feeeef5a,16#26f40e2147ee558,
+ 16#30c131a00625837,16#2618a7e617422e9,16#23630b297e45e7,16#1143b17502f3219,
+ 16#15607dac41168da,16#2886bdc314b3fb8,16#465d1cc1536546,16#30b09123e3a02e4,
+ 16#245a375f810be52,16#6a1b0792376a03,16#221425f59f2470f,16#867ce16dfac81c,
+ 16#9c62d95fae9b58,16#380381db1394426,16#34908dedc01c324,16#1f0ff517089b561,
+ 16#1571366dd873d32,16#3ee353dc56e192,16#15a1dee8d889b11,16#41036ad76d9888
+ ];
+
reference_val(exsp) ->
reference_val(exsplus);
reference_val(exs1024s) ->
@@ -1390,7 +1471,50 @@ reference_val(exrop) ->
250789092615679985,78848633178610658,72059442721196128,
98223942961505519,191144652663779840,
102425686803727694,89058927716079076,80721467542933080,
- 8462479817391645,2774921106204163].
+ 8462479817391645,2774921106204163];
+
+reference_val(exro928ss) ->
+%% Same as for exrop, but this state init:
+%% for (n = 0; n < 16; n++) {
+%% s[n] = 12345678;
+ [16#000000108e8d5b01,16#03604028f2769dff,16#007f92f60bc7170c,
+ 16#035ea81a9898a5e2,16#0104c90c5a0c8178,16#0313514025cca717,
+ 16#03c5506b2a2e98cf,16#0098a5405961552e,16#004ad29eabb785a0,
+ 16#033ea8ec4efb8058,16#00b21545e62bef1c,16#0333fc5320703482,
+ 16#02c3c650e51a8d47,16#03a3b7fc848c9cda,16#03775adea6cddff5,
+ 16#01ae5499c9049973,16#03d3c90e5504e16b,16#0383cd6b6cb852e6,
+ 16#009c8d0996ef543a,16#0059cf671371af60,16#03dfd68ed980b719,
+ 16#0290f2a0acf2c5b0,16#029061df18d63b55,16#02e702ea4b45137b,
+ 16#029a0ccca604d848,16#01664c7cd31f0fa6,16#00dced83e60ccddc,
+ 16#008764d2c9a05f3e,16#02b9ca5f6a80c4ba,16#02daf93d2c566750,
+ 16#0147d326ead18ace,16#014b452efc19297f,16#0242d3f7a7237eca,
+ 16#0141bb68c2abce39,16#02d798e1230baf45,16#0216bf8f25c1ec2d,
+ 16#003a43ea733f1e1f,16#036c75390db736f3,16#028cca5f5f48c6f9,
+ 16#0186e4a17174d6cf,16#02152679dfa4c25c,16#01429b9f15e3b9d6,
+ 16#0134a61411d22bb0,16#01593f7d970d1c94,16#0205a7d8a305490f,
+ 16#01dd092272595a9c,16#0028c95208aad2d4,16#016347c25cc24162,
+ 16#025306acfb891309,16#0207a07e2bebef2f,16#024ee78d86ff5288,
+ 16#030b53192db97613,16#03f765cb9e98e611,16#025ec35a1e237377,
+ 16#03d81fd73102ef6f,16#0242dc8fea9a68b2,16#00abb876c1d4ea1b,
+ 16#00871ffd2b7e45fb,16#03593ff73c9be08d,16#00b96b2b8aca3688,
+ 16#0174aba957b7cf7b,16#012b7a5d4cf4a5b7,16#032a5260f2123db8,
+ 16#00f9374d88ee0080,16#030df39bec2ad657,16#00dce0cb81d006c4,
+ 16#038213b806303c76,16#03940aafdbfabf84,16#0398dbb26aeba037,
+ 16#01eb28d61951587f,16#00fed3d2aacfeef4,16#03499587547d6e40,
+ 16#01b192fe6e979e3c,16#00e974bf5f0a26d0,16#012ed94f76459c83,
+ 16#02d76859e7a82587,16#00d1d2c7b791f51b,16#03988058017a031b,
+ 16#00bbcf4b59d8e86d,16#015ed8b73a1b767c,16#0277283ea6a5ee74,
+ 16#002211460dd6d422,16#001ad62761ee9fbd,16#037311b44518b067,
+ 16#02b5ed61bf70904e,16#011862a05c1929fa,16#014be68683c3bab4,
+ 16#025c29aa5c508b07,16#00895c6106f97378,16#026ce91a3d671c7f,
+ 16#02591f4c74784293,16#02f0ed2a70bc1853,16#00a2762ff614bfbc,
+ 16#008f4e354f0c20d4,16#038b66fb587ed430,16#00636296e188de89,
+ 16#0278fadd143e74f5,16#029697ccf1b3a4c2,16#011eccb273404458,
+ 16#03f204064a9fe0c0];
+
+reference_val(_) ->
+ not_implemented.
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -1421,6 +1545,33 @@ reference_jump_val(exsplus) ->
12504080415362731, 45083100453836317, 270968267812126657, 93505647407734103,
252852934678537969, 258758309277167202, 74250882143432077, 141629095984552833];
+reference_jump_val(exsss) ->
+ [16#304ae783d40db2b,16#1dfb196b3a5600a,16#2a24116effc6a0d,16#1f138d68c56725,
+ 16#9360a445e2f989,16#32ed8080390e242,16#294ca85a270cff6,16#1418e6296a88bf,
+ 16#114fae3dc578ba7,16#479c42c760eb72,16#334a40655df22d6,16#e7a85dd4d37d72,
+ 16#181db16c8925c77,16#1b8a5a8afd16cbd,16#329107bf9777a39,16#2fc915c08535e42,
+ 16#16696d142c6078,16#2e2a2601c919448,16#2246150d1000568,16#26109007cb3dd44,
+ 16#3761360723e3175,16#169abd352db74de,16#1c97d520983684f,16#12455f0adee8c66,
+ 16#46719cff00622d,16#1fc92792ed4e437,16#18e2edae21affb5,16#3a67fa9e3e7d46e,
+ 16#1313fdc2728aa74,16#1c1a2b577581db8,16#db49357ea196b1,16#10e219a21d93fc7,
+ 16#3c43abede083666,16#3eef5055a58bbf9,16#1975056f95d90e3,16#3916c133ab16d87,
+ 16#2bc0bea891c26f1,16#391e4b369fc6b36,16#183f83155a359f6,16#1d9f137e9d2e488,
+ 16#ef084de5f4cd3c,16#36a9cf7e29e55d3,16#19eca704e0409a7,16#1bdb99902896c69,
+ 16#21777e2ad128203,16#5d0369ec0563e4,16#36db40b863bd74a,16#33feb71b7515159,
+ 16#208d923ce26f257,16#3841b32891c082d,16#2748f224c2ba226,16#2fcd93b2daf79bb,
+ 16#2c8e6cacad58ec4,16#39850131a1a85f,16#134648d6eea624d,16#2e102e197d5725c,
+ 16#12ac280fa744758,16#1c18266c7442d16,16#22b5f91b15fe17e,16#316740ca870f7c8,
+ 16#720ed4836c426,16#1aac0f738d04f8c,16#34fcd2a647b462c,16#3d430ac755114a3,
+ 16#3692e3670fdf2a,16#265279ab0fc0a15,16#10bd883dee80945,16#10e7843413175e4,
+ 16#b291deba08cee2,16#3915a8234caf11,16#34b911b96707dbd,16#ae63fcda15fde6,
+ 16#b13b9091e82e41,16#29de1b6d70dc04f,16#23fbcbc409617e8,16#1389a0738061066,
+ 16#360f39af790f5d1,16#f436da2a7d12f5,16#2d06ba8da21e08,16#3601a6492b887d,
+ 16#2b2590b8c6cc186,16#f8d613b6904464,16#e5456786e46b78,16#201b8b1f96ed80c,
+ 16#1b75b86d9b843f2,16#2e8bfaa7243a630,16#125ff068a78c3b4,16#3875a28c48bd26e,
+ 16#f09a06941fc9d7,16#107c4de8ca77744,16#357c34144bb9ed6,16#3ccc55d3ebb3378,
+ 16#28db7cea7d3fdee,16#3197fd0b49f6370,16#11af6fedb708ea6,16#2bde0382e37469e,
+ 16#10666171abddb3f,16#1a8876c1f4e78a8,16#169c0efd4422043,16#1501c49abf0440f];
+
reference_jump_val(exs1024) ->
[2655961906500790629, 17003395417078685063, 10466831598958356428, 7603399148503548021,
1650550950190587188, 12294992315080723704, 15743995773860389219, 5492181000145247327,
@@ -1452,7 +1603,7 @@ reference_jump_val(exsp) ->
reference_jump_val(exsplus);
reference_jump_val(exs1024s) ->
reference_jump_val(exs1024);
-reference_jump_val(exs64) -> [not_implemented];
+reference_jump_val(exs64) -> [error_not_implemented];
reference_jump_val(exrop) ->
%% #include <stdint.h>
%% #include <stdio.h>
@@ -1517,7 +1668,50 @@ reference_jump_val(exrop) ->
250227633882474729,171181147785250210,55437891969696407,
241227318715885854,77323084015890802,
1663590009695191,234064400749487599,222983191707424780,
- 254956809144783896,203898972156838252].
+ 254956809144783896,203898972156838252];
+
+reference_jump_val(exro928ss) ->
+%% Same as for exrop, but this state init:
+%% for (n = 0; n < 16; n++) {
+%% s[n] = 12345678;
+ [16#031ee449e53b6689,16#001afeee12813137,16#005e2172711df36b,
+ 16#02850aea3a595d36,16#0029705187e891c7,16#001794badd489667,
+ 16#00ab621be15be56c,16#024b663a6924786b,16#03cab70b8ab854bf,
+ 16#01daa37601285320,16#02db955a53c40e89,16#01fbef51d5c65891,
+ 16#02fecf4116ed5f77,16#0349c2057246ac5d,16#01217f257c4fa148,
+ 16#0367ee84d020697d,16#01d5cf647fe23335,16#020941838adfb750,
+ 16#02c2da26b1d7b3e5,16#00d1583d34cea6c0,16#038be9cb5b527f50,
+ 16#00bfa93c1d7f4864,16#03778912a4f56b14,16#037fcabc483fa5c5,
+ 16#00a3c9de6aaf5fc7,16#03600b883b2f2b42,16#03797a99ffddfdfb,
+ 16#0189fead429945b7,16#0103ac90cd912508,16#03e3d872fd950d64,
+ 16#0214fc3e77dc2f02,16#02a084f4f0e580ca,16#035d2fe72266a7f3,
+ 16#02887c49ae7e41a4,16#0011dc026af83c51,16#02d28bfd32c2c517,
+ 16#022e4165c33ad4f3,16#01f053cf0687b052,16#035315e6e53c8918,
+ 16#01255312da07b572,16#0237f1da11ec9221,16#02faf2e282fb1fb1,
+ 16#0227423ec1787ebc,16#011fa5eb1505571c,16#0275ff9eaaa1abdd,
+ 16#03e2d032c3981cb4,16#0181bb32d51d3072,16#01b1d3939b9f16ec,
+ 16#0259f09f55d1112f,16#0396464a2767e428,16#039777c0368bdb9e,
+ 16#0320925f35f36c5f,16#02a35289e0af1248,16#02e80bd4bc72254b,
+ 16#00a8b11af1674d68,16#027735036100a69e,16#03c8c268ded7f254,
+ 16#03de80aa57c65217,16#00f2247754d24000,16#005582a42b467f89,
+ 16#0031906569729477,16#00fd523f2ca4fefe,16#00ad223113d1e336,
+ 16#0238ddf026cbfca9,16#028b98211cfed876,16#0354353ebcc0de9a,
+ 16#009ee370c1e154f4,16#033131af3b8a7f88,16#032291baa45801e3,
+ 16#00941fc2b45eb217,16#035d6a61fa101647,16#03fdb51f736f1bbc,
+ 16#0232f7b98539faa0,16#0311b35319e3a61e,16#0048356b17860eb5,
+ 16#01a205b2554ce71e,16#03f873ea136e29d6,16#003c67d5c3df5ffd,
+ 16#00cd19e7a8641648,16#0149a8c54e4ba45e,16#0329498d134d2f6a,
+ 16#03b69421ae65ee2b,16#01a8d20b59447429,16#006b2292571032a2,
+ 16#00c193b17da22ba5,16#01faa7ab62181249,16#00acd401cd596a00,
+ 16#005b5086c3531402,16#0259113d5d3d058d,16#00bef3f3ce4a43b2,
+ 16#014837a4070b893c,16#00460a26ac2eeec1,16#026219a8b8c63d7e,
+ 16#03c7b8ed032cf5a6,16#004da912a1fff131,16#0297de3716215741,
+ 16#0079fb9b4c715466,16#00a73bad4ae5a356,16#0072e606c0d4ab86,
+ 16#02374382d5f9bd2e];
+
+reference_jump_val(_) ->
+ not_implemented.
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
diff --git a/lib/stdlib/test/rand_Xoroshiro928ss_dev.txt b/lib/stdlib/test/rand_Xoroshiro928ss_dev.txt
new file mode 100644
index 0000000000..150f37fcfa
--- /dev/null
+++ b/lib/stdlib/test/rand_Xoroshiro928ss_dev.txt
@@ -0,0 +1,343 @@
+%CopyrightBegin%
+
+Copyright Ericsson AB 2015-2017. All Rights Reserved.
+
+Licensed under the Apache License, Version 2.0 (the "License");
+you may not use this file except in compliance with the License.
+You may obtain a copy of the License at
+
+ http://www.apache.org/licenses/LICENSE-2.0
+
+Unless required by applicable law or agreed to in writing, software
+distributed under the License is distributed on an "AS IS" BASIS,
+WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+See the License for the specific language governing permissions and
+limitations under the License.
+
+%CopyrightEnd%
+
+
+Memorable facts from designing the Xoroshiro928** generator
+===========================================================
+AKA: exro928ss in the rand module
+
+Author: Raimo Niskanen, for the Erlang/OTP team @ Ericsson.
+
+Reference URL: http://vigna.di.unimi.it/ftp/papers/ScrambledLinear.pdf
+i.e the Xoroshiro1024 generator with ** scrambler:
+
+ int p;
+ uint64_t s[16];
+
+ const int q = p;
+ const uint64_t s0 = s[p = (p + 1) & 15];
+
+ uint64_t s15 = s[q];
+
+ const uint64_t result_starstar = rotl(s0 * S, R) * T;
+
+ s15 ^= s0;
+ s[q] = rotl(s0, A) ^ s15 ^ (s15 << B);
+ s[p] = rotl(s15, C);
+
+Where {S, R, T} = {5, 7, 9} as recommended in the paper.
+
+We want to scale down to 58 bit words (16 of them)
+so we get a generator with period 2^928 - 1.
+
+{A, B, C} were deduced as follows
+---------------------------------
+
+First, to find which triplets that give a full period generator
+one have to factor 2^928 - 1.
+
+https://www.alpertron.com.ar/ECM.HTM actually could do that
+and gave the result:
+
+ Value
+ 2^928 - 1
+
+ 2269 007733 883335 972287 082669 296112 915239 349672 942191 252221 331572
+ 442536 403137 824056 312817 862695 551072 066953 619064 625508 194663
+ 368599 769448 406663 254670 871573 830845 597595 897613 333042 429214
+ 224697 474472 410882 236254 024057 110212 260250 671521 235807 709272
+ 244389 361641 091086 035023 229622 419455 (280 digits) = 3 × 5 × 17 × 59 ×
+ 233 × 257 × 929 × 1103 × 2089 × 5569 × 8353 × 59393 × 65537 × 3 033169 ×
+ 39 594977 × 107 367629 × 536 903681 × 748 264961 × 2245 984577 × 239
+ 686663 718401 × 15 929619 591127 520827 829953 × 82280 195167 144119
+ 832390 568177 × 6033 312171 721035 031651 315652 130497 (34 digits) × 18
+ 774318 450142 955120 650303 957350 521748 903233 (44 digits) × 15 694604
+ 006012 505869 851221 169365 594050 637743 819041 (50 digits)
+
+Sebastiano Vigna from that calculated all full period triplets, at the
+end of this document, and the ones with the highest degree were:
+
+ 23-25-12 411
+ 36-2-35 411
+ 55-5-54 411
+ 14-19-11 415
+ 34-37-5 415
+ 37-3-56 415
+ 55-11-54 417
+ 30-3-41 419
+ 11-45-50 423
+ 50-19-47 423
+ 52-27-13 427
+ 54-9-25 433
+ 56-43-35 433
+ 44-9-45 441
+
+All these candidates were tested with TestU01-1.2.3:
+
+ http://simul.iro.umontreal.ca/testu01/tu01.html
+
+A plugin was created with parameters for {A, B, C} and, since
+TestU01 is a 32-bit test tool, with parameters to reverse
+the generated bits or not, and to take the 32 highest or lowest
+bits from the reversed or non-reversed 58 bit output.
+
+The generators were seeded with a SplitMix64 generator like the
+one used for seeding this generator in the rand module,
+taking the 58 lowest bits and wasting all zero values.
+
+3 runs were made with all candidates and all four bit selection variants.
+For these runs the seeder was initialized with 12345678, 876543212345678
+and 1234567890.
+
+After all these runs the candidate with the highest degree: 44-9-45
+had not gotten any suspicious p-value at all. All the other
+got p-values around 5.0e-4 worst 9.8e-6 suggesting only random
+failures, so they would probably have worked about as well.
+
+Finally 44-9-45 was run through PractRand-0.93:
+
+ http://pracrand.sourceforge.net/
+
+Again, all 4 bit selection variants of 32 bits were run.
+Random failures with p-values around e-3..e-4 for the "smaller"
+tests, but for 8, 16 and 32 TB tests no anomalies were found
+(with the internal seeder masked to 58 bits):
+
+ Xoroshiro928High seed: 0x3178ec5d
+ Xoroshiro928Low seed: 0xa9a04fb9
+ Xoroshiro928ReverseHigh seed: 0xfa0bdbab
+ Xoroshiro928ReverseLow seed: 0xada51705
+
+
+Then, S. Vigna calculated the 2^512 jump coefficient as well
+as a 2^20 jump coefficient (for testing purposes) for 44-9-45.
+
+2^512:
+ { 0x44085302f77130ca, 0xba05381fdfd14902, 0x10a1de1d7d6813d2,
+ 0xb83fe51a1eb3be19, 0xa81b0090567fd9f0, 0x5ac26d5d20f9b49f,
+ 0x4ddd98ee4be41e01, 0x0657e19f00d4b358, 0xf02f778573cf0f0a,
+ 0xb45a3a8a3cef3cc0, 0x6e62a33cc2323831, 0xbcb3b7c4cc049c53,
+ 0x83f240c6007e76ce, 0xe19f5fc1a1504acd, 0x00000000b10773cb }
+
+2^20:
+ { 0xbdb966a3daf905e6, 0x644807a56270cf78, 0xda90f4a806c17e9e,
+ 0x4a426866bfad3c77, 0xaf699c306d8e7566, 0x8ebc73c700b8b091,
+ 0xc081a7bf148531fb, 0xdc4d3af15f8a4dfd, 0x90627c014098f4b6,
+ 0x06df2eb1feaf0fb6, 0x5bdeb1a5a90f2e6b, 0xa480c5878c3549bd,
+ 0xff45ef33c82f3d48, 0xa30bebc15fefcc78, 0x00000000cb3d181c }
+
+Standard jump function pseudocode:
+
+ Jump constant j = 0xb10773cb...44085302f77130ca
+ Generator state: s
+ New generator state: t = 0
+ foreach bit in j, low to high:
+ if the bit is one:
+ t ^= s
+ next s
+ s = t
+
+
+The complete list of full period constants
+------------------------------------------
+
+29-48-54 27 x^928 + x^874 + x^870 + x^840 + x^814 + x^784 + x^759 + x^750 + x^724 + x^720 + x^634 + x^630 + x^600 + x^574 + x^544 + x^519 + x^510 + x^484 + x^480 + x^390 + x^360 + x^270 + x^240 + x^150 + x^120 + x^30 + 1
+
+29-18-56 65 x^928 + x^870 + x^850 + x^840 + x^832 + x^821 + x^802 + x^791 + x^761 + x^750 + x^734 + x^731 + x^720 + x^712 + x^701 + x^686 + x^674 + x^671 + x^663 + x^641 + x^630 + x^611 + x^610 + x^603 + x^600 + x^596 + x^577 + x^566 + x^547 + x^524 + x^517 + x^510 + x^487 + x^480 + x^476 + x^464 + x^457 + x^446 + x^427 + x^423 + x^397 + x^390 + x^367 + x^363 + x^360 + x^356 + x^352 + x^341 + x^326 + x^322 + x^311 + x^281 + x^270 + x^251 + x^240 + x^236 + x^232 + x^221 + x^191 + x^161 + x^150 + x^131 + x^120 + x^30 + 1
+
+29-32-36 81 x^928 + x^874 + x^870 + x^840 + x^820 + x^819 + x^794 + x^790 + x^770 + x^765 + x^764 + x^760 + x^754 + x^750 + x^740 + x^739 + x^735 + x^734 + x^730 + x^709 + x^704 + x^674 + x^670 + x^665 + x^660 + x^650 + x^649 + x^635 + x^634 + x^619 + x^614 + x^605 + x^595 + x^585 + x^584 + x^579 + x^564 + x^555 + x^545 + x^540 + x^524 + x^515 + x^514 + x^495 + x^490 + x^485 + x^460 + x^455 + x^435 + x^425 + x^400 + x^395 + x^375 + x^370 + x^365 + x^340 + x^315 + x^310 + x^305 + x^300 + x^290 + x^285 + x^275 + x^260 + x^250 + x^245 + x^240 + x^215 + x^190 + x^180 + x^170 + x^150 + x^130 + x^120 + x^115 + x^105 + x^100 + x^75 + x^40 + x^30 + 1
+
+39-10-20 105 x^928 + x^898 + x^870 + x^841 + x^840 + x^808 + x^783 + x^782 + x^781 + x^780 + x^778 + x^754 + x^752 + x^724 + x^721 + x^720 + x^696 + x^692 + x^688 + x^667 + x^666 + x^661 + x^660 + x^658 + x^638 + x^636 + x^632 + x^609 + x^607 + x^606 + x^605 + x^604 + x^601 + x^600 + x^580 + x^578 + x^576 + x^572 + x^568 + x^549 + x^548 + x^541 + x^540 + x^538 + x^516 + x^512 + x^489 + x^485 + x^484 + x^481 + x^480 + x^456 + x^452 + x^448 + x^429 + x^428 + x^421 + x^420 + x^418 + x^400 + x^398 + x^396 + x^392 + x^368 + x^365 + x^364 + x^336 + x^328 + x^319 + x^318 + x^315 + x^314 + x^298 + x^286 + x^278 + x^276 + x^274 + x^255 + x^254 + x^249 + x^245 + x^228 + x^226 + x^220 + x^208 + x^199 + x^198 + x^189 + x^188 + x^178 + x^168 + x^166 + x^160 + x^129 + x^128 + x^108 + x^100 + x^88 + x^79 + x^78 + x^69 + x^68 + x^58 + x^40 + 1
+
+4-4-9 149 x^928 + x^898 + x^886 + x^870 + x^856 + x^826 + x^823 + x^808 + x^796 + x^793 + x^784 + x^778 + x^772 + x^766 + x^760 + x^754 + x^751 + x^742 + x^736 + x^734 + x^724 + x^713 + x^709 + x^706 + x^703 + x^694 + x^691 + x^688 + x^676 + x^674 + x^673 + x^664 + x^662 + x^658 + x^653 + x^641 + x^640 + x^634 + x^632 + x^631 + x^620 + x^614 + x^611 + x^608 + x^604 + x^602 + x^599 + x^590 + x^583 + x^581 + x^578 + x^574 + x^572 + x^571 + x^569 + x^568 + x^561 + x^554 + x^553 + x^551 + x^544 + x^542 + x^540 + x^538 + x^532 + x^531 + x^518 + x^514 + x^512 + x^502 + x^498 + x^489 + x^488 + x^484 + x^482 + x^480 + x^479 + x^468 + x^463 + x^456 + x^454 + x^452 + x^449 + x^448 + x^438 + x^433 + x^429 + x^424 + x^422 + x^420 + x^418 + x^408 + x^406 + x^401 + x^396 + x^394 + x^392 + x^380 + x^378 + x^376 + x^371 + x^367 + x^364 + x^362 + x^360 + x^350 + x^348 + x^346 + x^341 + x^334 + x^332 + x^328 + x^318 + x^311 + x^307 + x^304 + x^302 + x^300 + x^298 + x^288 + x^274 + x^272 + x^254 + x^249 + x^242 + x^240 + x^233 + x^212 + x^208 + x^189 + x^180 + x^178 + x^166 + x^152 + x^143 + x^136 + x^127 + x^122 + x^120 + x^113 + x^106 + x^88 + x^83 + x^81 + x^67 + x^58 + x^51 + x^14 + 1
+
+44-44-45 157 x^928 + x^898 + x^870 + x^850 + x^830 + x^820 + x^808 + x^800 + x^790 + x^782 + x^778 + x^777 + x^760 + x^757 + x^752 + x^747 + x^742 + x^727 + x^702 + x^694 + x^689 + x^688 + x^679 + x^674 + x^659 + x^658 + x^657 + x^644 + x^642 + x^637 + x^634 + x^627 + x^619 + x^612 + x^607 + x^606 + x^601 + x^596 + x^594 + x^591 + x^590 + x^584 + x^576 + x^568 + x^566 + x^561 + x^560 + x^556 + x^554 + x^546 + x^541 + x^539 + x^538 + x^518 + x^516 + x^511 + x^509 + x^503 + x^502 + x^499 + x^496 + x^488 + x^476 + x^471 + x^468 + x^466 + x^464 + x^448 + x^446 + x^441 + x^436 + x^421 + x^420 + x^415 + x^411 + x^408 + x^404 + x^400 + x^388 + x^383 + x^381 + x^379 + x^376 + x^363 + x^358 + x^356 + x^354 + x^346 + x^344 + x^340 + x^333 + x^330 + x^328 + x^325 + x^316 + x^312 + x^307 + x^305 + x^302 + x^284 + x^282 + x^277 + x^270 + x^268 + x^267 + x^256 + x^252 + x^249 + x^245 + x^244 + x^239 + x^238 + x^236 + x^231 + x^228 + x^226 + x^224 + x^222 + x^215 + x^208 + x^207 + x^205 + x^203 + x^201 + x^199 + x^196 + x^194 + x^192 + x^189 + x^185 + x^184 + x^182 + x^180 + x^175 + x^171 + x^168 + x^166 + x^162 + x^161 + x^155 + x^152 + x^150 + x^141 + x^134 + x^132 + x^131 + x^127 + x^122 + x^111 + x^104 + x^92 + x^90 + x^83 + x^81 + x^58 + x^37 + 1
+
+40-40-7 167 x^928 + x^898 + x^870 + x^866 + x^838 + x^836 + x^807 + x^806 + x^804 + x^778 + x^777 + x^774 + x^745 + x^744 + x^742 + x^718 + x^714 + x^713 + x^712 + x^687 + x^658 + x^657 + x^656 + x^655 + x^654 + x^626 + x^620 + x^619 + x^598 + x^596 + x^592 + x^591 + x^589 + x^566 + x^564 + x^563 + x^562 + x^560 + x^558 + x^538 + x^534 + x^530 + x^529 + x^504 + x^503 + x^502 + x^500 + x^499 + x^498 + x^496 + x^478 + x^474 + x^470 + x^469 + x^443 + x^442 + x^441 + x^439 + x^438 + x^436 + x^434 + x^432 + x^418 + x^416 + x^414 + x^410 + x^409 + x^407 + x^406 + x^405 + x^402 + x^386 + x^383 + x^380 + x^374 + x^373 + x^372 + x^370 + x^356 + x^350 + x^349 + x^348 + x^347 + x^346 + x^345 + x^340 + x^328 + x^326 + x^324 + x^323 + x^321 + x^316 + x^314 + x^308 + x^298 + x^296 + x^294 + x^289 + x^285 + x^283 + x^282 + x^281 + x^280 + x^278 + x^263 + x^262 + x^259 + x^257 + x^255 + x^251 + x^249 + x^248 + x^246 + x^233 + x^232 + x^229 + x^220 + x^218 + x^217 + x^216 + x^208 + x^202 + x^201 + x^199 + x^195 + x^190 + x^188 + x^187 + x^186 + x^178 + x^172 + x^169 + x^167 + x^162 + x^161 + x^159 + x^158 + x^157 + x^146 + x^142 + x^139 + x^135 + x^125 + x^123 + x^116 + x^112 + x^107 + x^105 + x^94 + x^93 + x^88 + x^86 + x^84 + x^82 + x^75 + x^73 + x^69 + x^64 + x^58 + x^56 + x^54 + x^52 + x^43 + x^41 + x^39 + x^32 + 1
+
+47-47-18 217 x^928 + x^898 + x^871 + x^870 + x^843 + x^842 + x^841 + x^813 + x^812 + x^811 + x^808 + x^787 + x^786 + x^785 + x^783 + x^781 + x^778 + x^759 + x^757 + x^754 + x^753 + x^751 + x^729 + x^727 + x^726 + x^723 + x^721 + x^701 + x^700 + x^699 + x^697 + x^693 + x^691 + x^688 + x^673 + x^672 + x^670 + x^667 + x^663 + x^661 + x^658 + x^647 + x^644 + x^641 + x^637 + x^633 + x^631 + x^618 + x^617 + x^614 + x^613 + x^612 + x^611 + x^610 + x^607 + x^603 + x^601 + x^586 + x^585 + x^582 + x^581 + x^580 + x^577 + x^573 + x^571 + x^568 + x^562 + x^560 + x^556 + x^555 + x^554 + x^553 + x^551 + x^547 + x^543 + x^541 + x^538 + x^532 + x^530 + x^528 + x^524 + x^522 + x^521 + x^517 + x^513 + x^511 + x^506 + x^504 + x^502 + x^500 + x^497 + x^495 + x^491 + x^487 + x^483 + x^481 + x^478 + x^474 + x^472 + x^467 + x^466 + x^465 + x^461 + x^457 + x^453 + x^451 + x^444 + x^438 + x^437 + x^436 + x^435 + x^431 + x^427 + x^423 + x^412 + x^408 + x^407 + x^405 + x^401 + x^397 + x^390 + x^384 + x^377 + x^375 + x^371 + x^367 + x^366 + x^365 + x^363 + x^362 + x^360 + x^358 + x^356 + x^352 + x^350 + x^347 + x^345 + x^341 + x^337 + x^336 + x^334 + x^332 + x^324 + x^317 + x^315 + x^311 + x^307 + x^306 + x^305 + x^304 + x^302 + x^300 + x^298 + x^296 + x^287 + x^285 + x^281 + x^279 + x^277 + x^276 + x^274 + x^268 + x^266 + x^257 + x^255 + x^247 + x^244 + x^242 + x^240 + x^238 + x^234 + x^227 + x^221 + x^219 + x^216 + x^214 + x^206 + x^197 + x^195 + x^193 + x^182 + x^176 + x^161 + x^156 + x^152 + x^146 + x^139 + x^133 + x^116 + x^111 + x^109 + x^107 + x^96 + x^94 + x^92 + x^90 + x^88 + x^85 + x^81 + x^79 + x^77 + x^73 + x^66 + x^64 + x^62 + x^60 + x^53 + x^51 + x^47 + x^45 + x^36 + x^34 + x^32 + x^19 + x^17 + x^15 + 1
+
+31-52-54 249 x^928 + x^898 + x^872 + x^870 + x^842 + x^841 + x^838 + x^836 + x^812 + x^810 + x^782 + x^781 + x^779 + x^778 + x^774 + x^753 + x^752 + x^750 + x^748 + x^723 + x^722 + x^721 + x^719 + x^717 + x^714 + x^712 + x^694 + x^690 + x^689 + x^688 + x^686 + x^684 + x^664 + x^663 + x^662 + x^661 + x^660 + x^658 + x^657 + x^656 + x^655 + x^654 + x^653 + x^652 + x^650 + x^634 + x^633 + x^631 + x^630 + x^629 + x^628 + x^622 + x^604 + x^599 + x^597 + x^596 + x^593 + x^592 + x^590 + x^588 + x^570 + x^567 + x^566 + x^562 + x^560 + x^536 + x^534 + x^533 + x^531 + x^530 + x^526 + x^513 + x^512 + x^510 + x^509 + x^508 + x^507 + x^506 + x^505 + x^504 + x^502 + x^498 + x^483 + x^482 + x^481 + x^479 + x^478 + x^476 + x^466 + x^464 + x^454 + x^445 + x^438 + x^424 + x^423 + x^422 + x^421 + x^419 + x^418 + x^411 + x^404 + x^402 + x^394 + x^393 + x^392 + x^391 + x^390 + x^387 + x^386 + x^383 + x^380 + x^379 + x^378 + x^377 + x^376 + x^374 + x^364 + x^362 + x^361 + x^359 + x^357 + x^356 + x^355 + x^354 + x^351 + x^349 + x^348 + x^347 + x^345 + x^342 + x^340 + x^332 + x^330 + x^329 + x^328 + x^327 + x^325 + x^324 + x^323 + x^321 + x^319 + x^318 + x^316 + x^314 + x^312 + x^302 + x^301 + x^300 + x^296 + x^295 + x^294 + x^291 + x^289 + x^287 + x^286 + x^283 + x^278 + x^266 + x^265 + x^264 + x^263 + x^262 + x^260 + x^259 + x^255 + x^250 + x^234 + x^232 + x^229 + x^227 + x^226 + x^225 + x^222 + x^218 + x^216 + x^208 + x^204 + x^200 + x^198 + x^197 + x^195 + x^194 + x^193 + x^190 + x^188 + x^178 + x^174 + x^173 + x^172 + x^171 + x^170 + x^169 + x^168 + x^166 + x^165 + x^164 + x^162 + x^161 + x^160 + x^159 + x^158 + x^157 + x^156 + x^154 + x^142 + x^141 + x^139 + x^138 + x^135 + x^131 + x^128 + x^126 + x^116 + x^112 + x^110 + x^107 + x^106 + x^105 + x^104 + x^102 + x^100 + x^98 + x^96 + x^95 + x^94 + x^92 + x^88 + x^80 + x^79 + x^76 + x^74 + x^73 + x^71 + x^70 + x^69 + x^66 + x^65 + x^64 + x^56 + x^54 + x^48 + x^46 + x^45 + x^43 + x^38 + x^35 + x^33 + x^30 + 1
+
+57-54-32 249 x^928 + x^898 + x^870 + x^855 + x^848 + x^834 + x^826 + x^825 + x^808 + x^806 + x^805 + x^804 + x^798 + x^796 + x^788 + x^778 + x^776 + x^775 + x^766 + x^763 + x^756 + x^752 + x^745 + x^742 + x^736 + x^735 + x^734 + x^731 + x^715 + x^714 + x^713 + x^705 + x^703 + x^694 + x^688 + x^684 + x^682 + x^671 + x^660 + x^658 + x^652 + x^642 + x^641 + x^639 + x^634 + x^630 + x^621 + x^620 + x^616 + x^612 + x^609 + x^604 + x^602 + x^593 + x^591 + x^584 + x^579 + x^570 + x^568 + x^566 + x^565 + x^562 + x^558 + x^554 + x^550 + x^544 + x^536 + x^535 + x^533 + x^530 + x^529 + x^528 + x^524 + x^522 + x^517 + x^512 + x^505 + x^496 + x^494 + x^492 + x^491 + x^489 + x^480 + x^478 + x^475 + x^471 + x^464 + x^461 + x^454 + x^452 + x^450 + x^446 + x^445 + x^441 + x^438 + x^437 + x^436 + x^434 + x^430 + x^429 + x^427 + x^425 + x^420 + x^418 + x^416 + x^415 + x^413 + x^411 + x^409 + x^402 + x^397 + x^394 + x^392 + x^388 + x^386 + x^384 + x^377 + x^375 + x^371 + x^368 + x^367 + x^365 + x^364 + x^363 + x^362 + x^360 + x^358 + x^356 + x^353 + x^351 + x^346 + x^342 + x^341 + x^338 + x^335 + x^333 + x^330 + x^328 + x^326 + x^325 + x^317 + x^307 + x^304 + x^300 + x^296 + x^295 + x^293 + x^292 + x^288 + x^286 + x^285 + x^284 + x^283 + x^278 + x^277 + x^276 + x^273 + x^271 + x^270 + x^262 + x^261 + x^255 + x^253 + x^249 + x^248 + x^246 + x^245 + x^240 + x^236 + x^232 + x^231 + x^227 + x^224 + x^223 + x^221 + x^220 + x^217 + x^216 + x^212 + x^208 + x^205 + x^204 + x^198 + x^196 + x^192 + x^191 + x^190 + x^189 + x^187 + x^186 + x^178 + x^176 + x^175 + x^171 + x^169 + x^165 + x^160 + x^159 + x^158 + x^154 + x^152 + x^150 + x^148 + x^146 + x^144 + x^141 + x^134 + x^132 + x^131 + x^129 + x^127 + x^125 + x^123 + x^120 + x^118 + x^114 + x^113 + x^111 + x^106 + x^104 + x^103 + x^102 + x^101 + x^100 + x^99 + x^97 + x^95 + x^93 + x^88 + x^85 + x^77 + x^67 + x^62 + x^60 + x^55 + x^54 + x^53 + x^52 + x^51 + x^50 + x^48 + x^46 + x^40 + x^37 + x^33 + x^28 + x^27 + x^24 + 1
+
+1-38-28 251 x^928 + x^898 + x^870 + x^866 + x^836 + x^834 + x^832 + x^818 + x^808 + x^806 + x^804 + x^797 + x^788 + x^778 + x^776 + x^770 + x^767 + x^765 + x^738 + x^736 + x^733 + x^724 + x^717 + x^708 + x^706 + x^703 + x^701 + x^690 + x^688 + x^685 + x^678 + x^677 + x^676 + x^674 + x^672 + x^664 + x^658 + x^656 + x^652 + x^647 + x^645 + x^640 + x^626 + x^624 + x^621 + x^620 + x^616 + x^610 + x^608 + x^604 + x^600 + x^594 + x^593 + x^592 + x^590 + x^580 + x^578 + x^576 + x^575 + x^574 + x^572 + x^568 + x^566 + x^565 + x^564 + x^562 + x^560 + x^558 + x^552 + x^550 + x^549 + x^548 + x^544 + x^541 + x^538 + x^536 + x^533 + x^532 + x^529 + x^526 + x^522 + x^520 + x^519 + x^517 + x^514 + x^513 + x^509 + x^508 + x^504 + x^501 + x^494 + x^493 + x^484 + x^482 + x^469 + x^468 + x^466 + x^461 + x^453 + x^452 + x^448 + x^447 + x^436 + x^428 + x^424 + x^422 + x^420 + x^416 + x^414 + x^413 + x^412 + x^409 + x^408 + x^406 + x^405 + x^404 + x^400 + x^399 + x^397 + x^393 + x^391 + x^388 + x^385 + x^382 + x^381 + x^376 + x^374 + x^372 + x^370 + x^368 + x^366 + x^365 + x^360 + x^350 + x^349 + x^344 + x^341 + x^340 + x^336 + x^335 + x^334 + x^333 + x^332 + x^328 + x^326 + x^322 + x^319 + x^318 + x^308 + x^304 + x^300 + x^298 + x^293 + x^292 + x^290 + x^289 + x^287 + x^284 + x^281 + x^279 + x^278 + x^272 + x^271 + x^269 + x^264 + x^263 + x^261 + x^256 + x^254 + x^253 + x^250 + x^240 + x^238 + x^234 + x^229 + x^228 + x^226 + x^223 + x^221 + x^218 + x^213 + x^210 + x^208 + x^204 + x^198 + x^197 + x^196 + x^194 + x^191 + x^188 + x^186 + x^180 + x^176 + x^174 + x^172 + x^170 + x^169 + x^167 + x^165 + x^161 + x^159 + x^157 + x^153 + x^150 + x^149 + x^148 + x^145 + x^136 + x^135 + x^134 + x^133 + x^132 + x^130 + x^128 + x^127 + x^125 + x^122 + x^120 + x^118 + x^113 + x^110 + x^109 + x^108 + x^100 + x^96 + x^94 + x^92 + x^90 + x^88 + x^86 + x^85 + x^84 + x^81 + x^80 + x^72 + x^70 + x^66 + x^58 + x^53 + x^45 + x^36 + x^34 + x^32 + x^30 + x^24 + x^20 + x^16 + x^12 + x^8 + x^2 + 1
+
+47-57-20 279 x^928 + x^898 + x^880 + x^870 + x^864 + x^851 + x^850 + x^846 + x^830 + x^821 + x^820 + x^817 + x^812 + x^808 + x^807 + x^804 + x^796 + x^790 + x^783 + x^782 + x^777 + x^773 + x^762 + x^757 + x^753 + x^744 + x^743 + x^739 + x^731 + x^728 + x^714 + x^713 + x^710 + x^709 + x^705 + x^701 + x^694 + x^692 + x^688 + x^684 + x^683 + x^675 + x^672 + x^671 + x^668 + x^662 + x^660 + x^654 + x^653 + x^646 + x^642 + x^641 + x^637 + x^626 + x^624 + x^623 + x^608 + x^607 + x^603 + x^598 + x^593 + x^592 + x^590 + x^585 + x^578 + x^577 + x^574 + x^573 + x^572 + x^569 + x^568 + x^567 + x^563 + x^559 + x^558 + x^555 + x^551 + x^548 + x^547 + x^542 + x^539 + x^538 + x^537 + x^536 + x^535 + x^532 + x^530 + x^529 + x^525 + x^524 + x^521 + x^518 + x^517 + x^506 + x^505 + x^501 + x^496 + x^491 + x^490 + x^487 + x^471 + x^467 + x^462 + x^456 + x^452 + x^448 + x^446 + x^441 + x^440 + x^437 + x^433 + x^428 + x^420 + x^412 + x^411 + x^404 + x^403 + x^402 + x^401 + x^399 + x^398 + x^396 + x^394 + x^381 + x^378 + x^376 + x^371 + x^370 + x^366 + x^365 + x^360 + x^355 + x^354 + x^351 + x^348 + x^346 + x^344 + x^342 + x^340 + x^339 + x^337 + x^335 + x^333 + x^331 + x^330 + x^329 + x^328 + x^327 + x^320 + x^318 + x^313 + x^307 + x^299 + x^298 + x^297 + x^296 + x^295 + x^294 + x^293 + x^291 + x^283 + x^282 + x^281 + x^280 + x^279 + x^277 + x^276 + x^266 + x^265 + x^264 + x^263 + x^262 + x^261 + x^259 + x^258 + x^257 + x^256 + x^251 + x^248 + x^247 + x^242 + x^240 + x^235 + x^234 + x^233 + x^231 + x^230 + x^229 + x^227 + x^225 + x^224 + x^219 + x^214 + x^212 + x^210 + x^206 + x^204 + x^203 + x^200 + x^196 + x^195 + x^194 + x^192 + x^191 + x^190 + x^188 + x^185 + x^182 + x^178 + x^176 + x^173 + x^159 + x^158 + x^157 + x^156 + x^151 + x^146 + x^144 + x^143 + x^142 + x^140 + x^138 + x^136 + x^131 + x^130 + x^128 + x^127 + x^126 + x^123 + x^122 + x^118 + x^117 + x^115 + x^114 + x^113 + x^108 + x^105 + x^99 + x^98 + x^94 + x^90 + x^88 + x^87 + x^86 + x^84 + x^82 + x^81 + x^80 + x^79 + x^78 + x^75 + x^74 + x^72 + x^71 + x^70 + x^65 + x^64 + x^58 + x^57 + x^56 + x^55 + x^52 + x^50 + x^48 + x^47 + x^46 + x^45 + x^42 + x^39 + x^26 + x^24 + x^23 + x^22 + x^20 + x^18 + x^15 + x^8 + x^4 + 1
+
+3-16-56 281 x^928 + x^898 + x^882 + x^870 + x^836 + x^820 + x^816 + x^808 + x^803 + x^802 + x^799 + x^778 + x^773 + x^770 + x^762 + x^757 + x^754 + x^753 + x^750 + x^737 + x^733 + x^720 + x^717 + x^713 + x^700 + x^688 + x^683 + x^680 + x^679 + x^674 + x^660 + x^658 + x^656 + x^654 + x^653 + x^650 + x^646 + x^644 + x^641 + x^640 + x^637 + x^634 + x^633 + x^623 + x^618 + x^617 + x^616 + x^613 + x^597 + x^590 + x^585 + x^584 + x^581 + x^577 + x^574 + x^572 + x^563 + x^562 + x^560 + x^555 + x^554 + x^553 + x^551 + x^547 + x^544 + x^537 + x^536 + x^533 + x^525 + x^521 + x^520 + x^519 + x^517 + x^515 + x^513 + x^510 + x^508 + x^505 + x^502 + x^501 + x^498 + x^493 + x^490 + x^485 + x^480 + x^477 + x^476 + x^475 + x^472 + x^469 + x^461 + x^458 + x^453 + x^449 + x^448 + x^445 + x^444 + x^442 + x^435 + x^433 + x^432 + x^431 + x^426 + x^425 + x^422 + x^420 + x^418 + x^412 + x^411 + x^409 + x^405 + x^403 + x^401 + x^400 + x^397 + x^393 + x^385 + x^381 + x^368 + x^366 + x^365 + x^362 + x^361 + x^359 + x^356 + x^353 + x^350 + x^346 + x^341 + x^338 + x^335 + x^334 + x^333 + x^332 + x^328 + x^326 + x^325 + x^323 + x^322 + x^320 + x^319 + x^317 + x^316 + x^315 + x^313 + x^312 + x^310 + x^309 + x^307 + x^305 + x^300 + x^295 + x^293 + x^291 + x^290 + x^289 + x^288 + x^286 + x^285 + x^282 + x^277 + x^274 + x^273 + x^266 + x^265 + x^263 + x^261 + x^259 + x^255 + x^253 + x^251 + x^248 + x^247 + x^246 + x^242 + x^241 + x^239 + x^234 + x^233 + x^232 + x^230 + x^229 + x^228 + x^226 + x^225 + x^224 + x^222 + x^218 + x^217 + x^215 + x^212 + x^210 + x^208 + x^206 + x^205 + x^203 + x^201 + x^200 + x^194 + x^193 + x^191 + x^189 + x^183 + x^181 + x^180 + x^178 + x^177 + x^176 + x^174 + x^172 + x^171 + x^169 + x^167 + x^166 + x^163 + x^162 + x^159 + x^157 + x^155 + x^151 + x^150 + x^149 + x^147 + x^140 + x^139 + x^138 + x^137 + x^136 + x^134 + x^131 + x^128 + x^127 + x^126 + x^121 + x^119 + x^118 + x^117 + x^111 + x^106 + x^104 + x^102 + x^101 + x^99 + x^98 + x^91 + x^90 + x^88 + x^86 + x^85 + x^81 + x^79 + x^75 + x^74 + x^73 + x^72 + x^71 + x^69 + x^68 + x^65 + x^64 + x^63 + x^62 + x^61 + x^58 + x^57 + x^56 + x^55 + x^51 + x^50 + x^49 + x^41 + x^38 + x^36 + x^34 + x^33 + x^32 + x^24 + x^21 + x^9 + x^6 + 1
+
+10-38-9 285 x^928 + x^898 + x^870 + x^841 + x^840 + x^838 + x^836 + x^811 + x^810 + x^781 + x^777 + x^774 + x^751 + x^748 + x^723 + x^721 + x^720 + x^719 + x^718 + x^717 + x^716 + x^714 + x^712 + x^694 + x^692 + x^691 + x^688 + x^686 + x^664 + x^663 + x^661 + x^660 + x^659 + x^657 + x^652 + x^650 + x^632 + x^631 + x^630 + x^628 + x^627 + x^625 + x^624 + x^623 + x^605 + x^604 + x^603 + x^599 + x^597 + x^594 + x^593 + x^591 + x^590 + x^588 + x^576 + x^575 + x^574 + x^572 + x^571 + x^570 + x^569 + x^567 + x^565 + x^560 + x^544 + x^543 + x^542 + x^540 + x^539 + x^537 + x^535 + x^531 + x^526 + x^514 + x^510 + x^509 + x^507 + x^506 + x^505 + x^504 + x^503 + x^502 + x^498 + x^485 + x^484 + x^478 + x^474 + x^471 + x^470 + x^468 + x^466 + x^464 + x^458 + x^455 + x^452 + x^450 + x^449 + x^448 + x^445 + x^441 + x^439 + x^428 + x^419 + x^416 + x^415 + x^411 + x^407 + x^406 + x^405 + x^404 + x^402 + x^398 + x^392 + x^388 + x^385 + x^384 + x^383 + x^382 + x^381 + x^380 + x^379 + x^376 + x^374 + x^364 + x^359 + x^357 + x^356 + x^355 + x^354 + x^353 + x^351 + x^349 + x^346 + x^345 + x^343 + x^340 + x^338 + x^334 + x^328 + x^326 + x^325 + x^324 + x^321 + x^320 + x^319 + x^318 + x^315 + x^314 + x^312 + x^306 + x^298 + x^297 + x^295 + x^294 + x^293 + x^291 + x^288 + x^287 + x^286 + x^285 + x^283 + x^282 + x^281 + x^278 + x^276 + x^274 + x^270 + x^269 + x^268 + x^263 + x^261 + x^256 + x^255 + x^254 + x^244 + x^242 + x^237 + x^236 + x^235 + x^234 + x^233 + x^232 + x^229 + x^225 + x^222 + x^219 + x^216 + x^214 + x^212 + x^210 + x^209 + x^208 + x^207 + x^206 + x^202 + x^198 + x^194 + x^193 + x^192 + x^191 + x^190 + x^184 + x^182 + x^178 + x^176 + x^175 + x^174 + x^173 + x^168 + x^166 + x^164 + x^160 + x^159 + x^157 + x^154 + x^152 + x^151 + x^150 + x^145 + x^144 + x^142 + x^136 + x^135 + x^134 + x^129 + x^128 + x^122 + x^121 + x^119 + x^118 + x^116 + x^114 + x^113 + x^112 + x^111 + x^108 + x^105 + x^103 + x^100 + x^98 + x^97 + x^95 + x^94 + x^92 + x^89 + x^88 + x^87 + x^85 + x^84 + x^83 + x^78 + x^76 + x^74 + x^73 + x^71 + x^70 + x^69 + x^67 + x^66 + x^64 + x^61 + x^59 + x^57 + x^56 + x^54 + x^53 + x^51 + x^49 + x^48 + x^46 + x^45 + x^43 + x^42 + x^41 + x^40 + x^38 + x^37 + x^36 + x^35 + x^34 + x^33 + x^32 + x^30 + x^4 + 1
+
+15-22-28 289 x^928 + x^898 + x^870 + x^838 + x^821 + x^806 + x^805 + x^792 + x^790 + x^778 + x^774 + x^762 + x^745 + x^744 + x^718 + x^697 + x^682 + x^672 + x^670 + x^667 + x^666 + x^658 + x^656 + x^653 + x^652 + x^651 + x^650 + x^642 + x^641 + x^638 + x^637 + x^623 + x^608 + x^607 + x^598 + x^594 + x^588 + x^575 + x^574 + x^573 + x^566 + x^565 + x^564 + x^563 + x^562 + x^557 + x^548 + x^547 + x^542 + x^538 + x^533 + x^531 + x^529 + x^526 + x^517 + x^516 + x^514 + x^513 + x^505 + x^504 + x^503 + x^502 + x^501 + x^499 + x^498 + x^497 + x^488 + x^487 + x^484 + x^483 + x^482 + x^474 + x^470 + x^468 + x^467 + x^466 + x^464 + x^457 + x^454 + x^453 + x^449 + x^447 + x^444 + x^443 + x^442 + x^441 + x^440 + x^439 + x^437 + x^436 + x^435 + x^428 + x^427 + x^426 + x^425 + x^422 + x^418 + x^417 + x^414 + x^409 + x^406 + x^405 + x^392 + x^391 + x^389 + x^388 + x^387 + x^386 + x^379 + x^378 + x^374 + x^372 + x^371 + x^368 + x^367 + x^362 + x^361 + x^358 + x^357 + x^354 + x^350 + x^349 + x^347 + x^342 + x^341 + x^340 + x^334 + x^333 + x^332 + x^331 + x^330 + x^329 + x^328 + x^327 + x^324 + x^323 + x^320 + x^319 + x^313 + x^308 + x^307 + x^305 + x^303 + x^302 + x^301 + x^300 + x^299 + x^298 + x^297 + x^296 + x^295 + x^294 + x^293 + x^292 + x^288 + x^287 + x^286 + x^283 + x^282 + x^280 + x^279 + x^278 + x^277 + x^276 + x^271 + x^269 + x^268 + x^267 + x^266 + x^265 + x^255 + x^254 + x^253 + x^249 + x^247 + x^241 + x^238 + x^237 + x^236 + x^235 + x^226 + x^225 + x^224 + x^223 + x^220 + x^219 + x^215 + x^214 + x^212 + x^210 + x^209 + x^205 + x^202 + x^201 + x^200 + x^199 + x^197 + x^190 + x^186 + x^182 + x^181 + x^180 + x^177 + x^174 + x^173 + x^172 + x^171 + x^170 + x^169 + x^168 + x^165 + x^163 + x^161 + x^160 + x^158 + x^155 + x^153 + x^151 + x^150 + x^146 + x^143 + x^142 + x^137 + x^136 + x^135 + x^131 + x^130 + x^128 + x^127 + x^126 + x^125 + x^124 + x^123 + x^122 + x^120 + x^119 + x^117 + x^114 + x^113 + x^111 + x^105 + x^104 + x^103 + x^102 + x^101 + x^99 + x^97 + x^93 + x^90 + x^89 + x^88 + x^87 + x^86 + x^84 + x^83 + x^82 + x^81 + x^80 + x^79 + x^77 + x^75 + x^72 + x^71 + x^70 + x^69 + x^68 + x^65 + x^60 + x^59 + x^58 + x^55 + x^54 + x^52 + x^51 + x^50 + x^48 + x^43 + x^42 + x^40 + x^39 + x^30 + x^28 + x^27 + x^24 + x^23 + x^19 + x^16 + x^15 + 1
+
+12-41-35 291 x^928 + x^898 + x^886 + x^873 + x^870 + x^860 + x^856 + x^847 + x^844 + x^834 + x^830 + x^826 + x^818 + x^817 + x^805 + x^804 + x^796 + x^795 + x^791 + x^784 + x^782 + x^779 + x^769 + x^765 + x^762 + x^758 + x^756 + x^753 + x^752 + x^743 + x^739 + x^736 + x^735 + x^732 + x^731 + x^730 + x^727 + x^726 + x^723 + x^722 + x^717 + x^713 + x^710 + x^705 + x^701 + x^700 + x^692 + x^685 + x^683 + x^680 + x^676 + x^671 + x^663 + x^659 + x^657 + x^654 + x^653 + x^645 + x^642 + x^637 + x^632 + x^628 + x^624 + x^623 + x^619 + x^616 + x^615 + x^612 + x^610 + x^607 + x^606 + x^603 + x^598 + x^597 + x^594 + x^593 + x^590 + x^589 + x^585 + x^580 + x^577 + x^576 + x^572 + x^567 + x^564 + x^560 + x^559 + x^556 + x^550 + x^545 + x^543 + x^538 + x^537 + x^534 + x^533 + x^532 + x^528 + x^520 + x^516 + x^513 + x^508 + x^507 + x^506 + x^504 + x^499 + x^496 + x^491 + x^490 + x^487 + x^486 + x^485 + x^481 + x^477 + x^474 + x^466 + x^465 + x^457 + x^452 + x^448 + x^447 + x^446 + x^438 + x^436 + x^435 + x^434 + x^430 + x^425 + x^422 + x^421 + x^417 + x^413 + x^409 + x^404 + x^395 + x^393 + x^392 + x^388 + x^387 + x^386 + x^384 + x^382 + x^380 + x^379 + x^374 + x^373 + x^370 + x^367 + x^366 + x^362 + x^361 + x^358 + x^357 + x^354 + x^353 + x^352 + x^350 + x^349 + x^345 + x^344 + x^343 + x^340 + x^337 + x^336 + x^332 + x^331 + x^328 + x^324 + x^323 + x^317 + x^315 + x^314 + x^313 + x^311 + x^305 + x^302 + x^298 + x^297 + x^296 + x^295 + x^292 + x^291 + x^288 + x^283 + x^280 + x^276 + x^275 + x^272 + x^268 + x^266 + x^262 + x^259 + x^258 + x^255 + x^251 + x^250 + x^242 + x^241 + x^240 + x^232 + x^227 + x^225 + x^224 + x^223 + x^216 + x^214 + x^212 + x^211 + x^210 + x^206 + x^203 + x^198 + x^189 + x^188 + x^177 + x^176 + x^175 + x^173 + x^168 + x^164 + x^162 + x^160 + x^159 + x^156 + x^155 + x^154 + x^152 + x^149 + x^147 + x^146 + x^145 + x^142 + x^139 + x^138 + x^137 + x^134 + x^132 + x^130 + x^124 + x^123 + x^122 + x^115 + x^113 + x^112 + x^111 + x^110 + x^108 + x^106 + x^103 + x^102 + x^98 + x^97 + x^96 + x^95 + x^94 + x^92 + x^91 + x^90 + x^88 + x^85 + x^80 + x^78 + x^77 + x^76 + x^73 + x^71 + x^70 + x^69 + x^68 + x^67 + x^65 + x^64 + x^63 + x^54 + x^53 + x^52 + x^51 + x^50 + x^49 + x^48 + x^47 + x^44 + x^43 + x^42 + x^40 + x^39 + x^31 + x^30 + x^29 + x^21 + x^13 + 1
+
+35-54-56 293 x^928 + x^898 + x^870 + x^862 + x^832 + x^826 + x^808 + x^796 + x^794 + x^790 + x^778 + x^765 + x^758 + x^754 + x^734 + x^729 + x^728 + x^722 + x^718 + x^715 + x^706 + x^700 + x^699 + x^698 + x^693 + x^686 + x^682 + x^676 + x^673 + x^672 + x^669 + x^668 + x^662 + x^658 + x^656 + x^655 + x^652 + x^650 + x^649 + x^646 + x^645 + x^642 + x^639 + x^638 + x^636 + x^630 + x^622 + x^614 + x^613 + x^612 + x^610 + x^608 + x^607 + x^600 + x^596 + x^595 + x^592 + x^590 + x^589 + x^587 + x^582 + x^574 + x^571 + x^568 + x^566 + x^560 + x^558 + x^554 + x^553 + x^552 + x^548 + x^544 + x^542 + x^538 + x^536 + x^534 + x^530 + x^528 + x^527 + x^524 + x^523 + x^522 + x^520 + x^518 + x^516 + x^515 + x^511 + x^506 + x^499 + x^497 + x^493 + x^492 + x^490 + x^487 + x^482 + x^478 + x^474 + x^467 + x^462 + x^461 + x^452 + x^445 + x^442 + x^439 + x^437 + x^436 + x^433 + x^428 + x^427 + x^422 + x^418 + x^413 + x^412 + x^410 + x^409 + x^407 + x^406 + x^403 + x^401 + x^398 + x^396 + x^392 + x^390 + x^386 + x^384 + x^383 + x^382 + x^380 + x^378 + x^377 + x^373 + x^372 + x^371 + x^366 + x^365 + x^362 + x^353 + x^352 + x^350 + x^348 + x^346 + x^344 + x^342 + x^340 + x^338 + x^336 + x^335 + x^334 + x^332 + x^331 + x^328 + x^326 + x^320 + x^318 + x^317 + x^316 + x^313 + x^312 + x^311 + x^310 + x^308 + x^304 + x^300 + x^299 + x^298 + x^296 + x^295 + x^293 + x^290 + x^288 + x^284 + x^282 + x^275 + x^271 + x^269 + x^268 + x^266 + x^265 + x^264 + x^263 + x^262 + x^260 + x^259 + x^253 + x^250 + x^247 + x^246 + x^244 + x^242 + x^240 + x^239 + x^238 + x^235 + x^233 + x^232 + x^228 + x^227 + x^226 + x^224 + x^221 + x^220 + x^218 + x^216 + x^214 + x^212 + x^208 + x^203 + x^199 + x^198 + x^196 + x^195 + x^194 + x^193 + x^192 + x^189 + x^187 + x^182 + x^178 + x^176 + x^175 + x^173 + x^168 + x^167 + x^166 + x^163 + x^161 + x^160 + x^156 + x^152 + x^150 + x^148 + x^146 + x^140 + x^138 + x^135 + x^133 + x^131 + x^130 + x^129 + x^128 + x^127 + x^126 + x^125 + x^123 + x^122 + x^120 + x^118 + x^116 + x^115 + x^113 + x^112 + x^109 + x^106 + x^105 + x^104 + x^103 + x^101 + x^100 + x^95 + x^94 + x^92 + x^84 + x^82 + x^80 + x^79 + x^77 + x^76 + x^74 + x^71 + x^69 + x^68 + x^66 + x^65 + x^64 + x^63 + x^55 + x^54 + x^53 + x^49 + x^48 + x^46 + x^45 + x^43 + x^42 + x^41 + x^40 + x^38 + x^36 + x^34 + x^24 + x^18 + x^6 + 1
+
+44-42-5 307 x^928 + x^898 + x^880 + x^870 + x^856 + x^850 + x^839 + x^832 + x^826 + x^820 + x^816 + x^815 + x^808 + x^792 + x^791 + x^790 + x^784 + x^779 + x^778 + x^768 + x^762 + x^760 + x^756 + x^754 + x^753 + x^747 + x^744 + x^738 + x^737 + x^736 + x^731 + x^726 + x^723 + x^720 + x^719 + x^717 + x^713 + x^707 + x^696 + x^693 + x^689 + x^688 + x^682 + x^678 + x^677 + x^670 + x^666 + x^665 + x^663 + x^660 + x^658 + x^657 + x^653 + x^646 + x^633 + x^630 + x^628 + x^624 + x^617 + x^616 + x^612 + x^611 + x^606 + x^605 + x^604 + x^603 + x^600 + x^599 + x^597 + x^594 + x^592 + x^588 + x^587 + x^586 + x^582 + x^580 + x^576 + x^575 + x^568 + x^563 + x^556 + x^552 + x^546 + x^544 + x^542 + x^540 + x^539 + x^537 + x^534 + x^533 + x^526 + x^522 + x^521 + x^520 + x^518 + x^517 + x^516 + x^514 + x^511 + x^510 + x^508 + x^505 + x^503 + x^494 + x^492 + x^488 + x^485 + x^481 + x^475 + x^474 + x^470 + x^467 + x^464 + x^463 + x^462 + x^454 + x^452 + x^449 + x^447 + x^446 + x^444 + x^443 + x^442 + x^439 + x^438 + x^437 + x^432 + x^431 + x^430 + x^427 + x^426 + x^424 + x^422 + x^419 + x^418 + x^413 + x^410 + x^409 + x^406 + x^404 + x^401 + x^398 + x^396 + x^393 + x^392 + x^391 + x^390 + x^389 + x^385 + x^383 + x^380 + x^379 + x^376 + x^374 + x^372 + x^370 + x^368 + x^367 + x^366 + x^365 + x^364 + x^363 + x^361 + x^358 + x^355 + x^354 + x^353 + x^349 + x^348 + x^347 + x^344 + x^343 + x^342 + x^341 + x^338 + x^337 + x^336 + x^334 + x^332 + x^329 + x^328 + x^318 + x^317 + x^312 + x^310 + x^308 + x^307 + x^306 + x^305 + x^304 + x^299 + x^296 + x^294 + x^293 + x^291 + x^289 + x^281 + x^280 + x^278 + x^277 + x^276 + x^274 + x^272 + x^270 + x^267 + x^265 + x^264 + x^263 + x^260 + x^253 + x^252 + x^251 + x^250 + x^247 + x^242 + x^241 + x^239 + x^234 + x^233 + x^231 + x^230 + x^229 + x^224 + x^223 + x^222 + x^217 + x^214 + x^212 + x^210 + x^209 + x^208 + x^203 + x^200 + x^199 + x^198 + x^196 + x^195 + x^192 + x^191 + x^186 + x^185 + x^184 + x^181 + x^180 + x^179 + x^178 + x^177 + x^176 + x^175 + x^172 + x^171 + x^170 + x^169 + x^168 + x^166 + x^165 + x^161 + x^160 + x^159 + x^151 + x^146 + x^144 + x^143 + x^142 + x^141 + x^139 + x^137 + x^136 + x^135 + x^133 + x^131 + x^130 + x^120 + x^116 + x^114 + x^113 + x^108 + x^107 + x^106 + x^104 + x^101 + x^98 + x^97 + x^96 + x^91 + x^90 + x^89 + x^87 + x^82 + x^80 + x^78 + x^73 + x^72 + x^67 + x^62 + x^58 + x^56 + x^55 + x^53 + x^49 + x^46 + x^44 + x^39 + x^32 + x^26 + x^17 + 1
+
+18-7-29 311 x^928 + x^926 + x^920 + x^918 + x^912 + x^910 + x^904 + x^902 + x^898 + x^896 + x^894 + x^890 + x^888 + x^886 + x^882 + x^880 + x^878 + x^874 + x^872 + x^870 + x^866 + x^858 + x^850 + x^842 + x^808 + x^806 + x^792 + x^790 + x^778 + x^776 + x^774 + x^762 + x^760 + x^758 + x^746 + x^730 + x^688 + x^686 + x^680 + x^678 + x^669 + x^667 + x^661 + x^659 + x^658 + x^656 + x^655 + x^654 + x^651 + x^650 + x^648 + x^647 + x^646 + x^643 + x^626 + x^618 + x^611 + x^605 + x^595 + x^589 + x^587 + x^575 + x^569 + x^568 + x^566 + x^561 + x^553 + x^541 + x^539 + x^538 + x^537 + x^536 + x^534 + x^533 + x^515 + x^511 + x^509 + x^507 + x^506 + x^503 + x^501 + x^497 + x^495 + x^493 + x^489 + x^485 + x^483 + x^481 + x^479 + x^475 + x^473 + x^471 + x^469 + x^457 + x^455 + x^453 + x^451 + x^449 + x^448 + x^447 + x^446 + x^443 + x^440 + x^439 + x^438 + x^437 + x^435 + x^433 + x^432 + x^431 + x^429 + x^426 + x^425 + x^424 + x^421 + x^418 + x^417 + x^416 + x^415 + x^414 + x^412 + x^409 + x^408 + x^406 + x^405 + x^404 + x^401 + x^398 + x^396 + x^395 + x^393 + x^392 + x^390 + x^388 + x^387 + x^380 + x^379 + x^377 + x^376 + x^372 + x^371 + x^370 + x^369 + x^367 + x^364 + x^363 + x^362 + x^361 + x^359 + x^358 + x^354 + x^352 + x^350 + x^349 + x^348 + x^341 + x^340 + x^337 + x^336 + x^335 + x^331 + x^330 + x^328 + x^326 + x^320 + x^319 + x^318 + x^317 + x^315 + x^314 + x^313 + x^312 + x^310 + x^308 + x^307 + x^302 + x^301 + x^299 + x^297 + x^295 + x^293 + x^291 + x^287 + x^284 + x^283 + x^282 + x^281 + x^280 + x^279 + x^278 + x^274 + x^271 + x^267 + x^266 + x^264 + x^263 + x^257 + x^256 + x^255 + x^252 + x^251 + x^250 + x^246 + x^241 + x^240 + x^239 + x^234 + x^233 + x^231 + x^230 + x^229 + x^226 + x^225 + x^224 + x^223 + x^222 + x^218 + x^216 + x^214 + x^212 + x^211 + x^206 + x^203 + x^202 + x^199 + x^198 + x^197 + x^193 + x^191 + x^190 + x^188 + x^185 + x^183 + x^181 + x^180 + x^179 + x^176 + x^171 + x^169 + x^167 + x^158 + x^156 + x^155 + x^154 + x^153 + x^151 + x^150 + x^148 + x^145 + x^143 + x^142 + x^141 + x^138 + x^133 + x^132 + x^130 + x^127 + x^125 + x^123 + x^121 + x^118 + x^109 + x^108 + x^105 + x^104 + x^103 + x^102 + x^100 + x^97 + x^95 + x^94 + x^92 + x^90 + x^85 + x^84 + x^82 + x^80 + x^76 + x^74 + x^73 + x^71 + x^70 + x^68 + x^67 + x^66 + x^65 + x^64 + x^61 + x^59 + x^57 + x^55 + x^53 + x^52 + x^48 + x^47 + x^45 + x^41 + x^38 + x^36 + x^34 + x^31 + x^28 + x^26 + x^24 + x^22 + x^18 + x^16 + x^12 + x^10 + x^2 + 1
+
+48-55-49 313 x^928 + x^898 + x^894 + x^893 + x^870 + x^864 + x^860 + x^858 + x^838 + x^836 + x^832 + x^831 + x^830 + x^828 + x^804 + x^802 + x^796 + x^794 + x^778 + x^774 + x^773 + x^770 + x^769 + x^768 + x^741 + x^740 + x^737 + x^736 + x^734 + x^732 + x^731 + x^718 + x^712 + x^711 + x^706 + x^704 + x^702 + x^701 + x^684 + x^681 + x^679 + x^678 + x^676 + x^675 + x^672 + x^671 + x^669 + x^658 + x^656 + x^654 + x^653 + x^652 + x^651 + x^647 + x^646 + x^645 + x^621 + x^618 + x^617 + x^616 + x^615 + x^614 + x^611 + x^610 + x^609 + x^598 + x^596 + x^592 + x^590 + x^589 + x^583 + x^582 + x^580 + x^579 + x^576 + x^561 + x^559 + x^558 + x^557 + x^554 + x^548 + x^547 + x^545 + x^538 + x^534 + x^533 + x^531 + x^529 + x^527 + x^526 + x^524 + x^522 + x^521 + x^515 + x^512 + x^500 + x^497 + x^486 + x^484 + x^478 + x^474 + x^470 + x^469 + x^468 + x^467 + x^466 + x^465 + x^464 + x^462 + x^460 + x^458 + x^456 + x^454 + x^453 + x^450 + x^444 + x^438 + x^436 + x^435 + x^434 + x^433 + x^432 + x^429 + x^424 + x^422 + x^421 + x^418 + x^416 + x^413 + x^412 + x^407 + x^406 + x^405 + x^404 + x^402 + x^399 + x^398 + x^397 + x^396 + x^394 + x^392 + x^391 + x^388 + x^384 + x^380 + x^378 + x^377 + x^375 + x^373 + x^372 + x^371 + x^364 + x^359 + x^356 + x^354 + x^353 + x^352 + x^351 + x^350 + x^347 + x^343 + x^342 + x^340 + x^339 + x^334 + x^331 + x^328 + x^327 + x^325 + x^324 + x^322 + x^316 + x^312 + x^311 + x^310 + x^308 + x^306 + x^305 + x^304 + x^302 + x^301 + x^300 + x^298 + x^297 + x^295 + x^294 + x^292 + x^291 + x^290 + x^289 + x^288 + x^282 + x^280 + x^279 + x^278 + x^277 + x^276 + x^275 + x^273 + x^271 + x^268 + x^264 + x^261 + x^258 + x^256 + x^254 + x^253 + x^251 + x^249 + x^248 + x^246 + x^245 + x^244 + x^242 + x^241 + x^240 + x^239 + x^237 + x^236 + x^232 + x^231 + x^229 + x^228 + x^227 + x^226 + x^224 + x^223 + x^219 + x^216 + x^215 + x^211 + x^210 + x^207 + x^206 + x^204 + x^203 + x^199 + x^198 + x^194 + x^188 + x^187 + x^186 + x^182 + x^181 + x^180 + x^174 + x^171 + x^170 + x^168 + x^165 + x^164 + x^160 + x^152 + x^151 + x^150 + x^149 + x^148 + x^147 + x^144 + x^143 + x^142 + x^141 + x^139 + x^134 + x^129 + x^127 + x^124 + x^121 + x^119 + x^115 + x^108 + x^107 + x^105 + x^104 + x^103 + x^102 + x^95 + x^94 + x^90 + x^89 + x^88 + x^86 + x^84 + x^79 + x^77 + x^73 + x^72 + x^69 + x^66 + x^64 + x^63 + x^62 + x^60 + x^57 + x^56 + x^55 + x^54 + x^53 + x^52 + x^50 + x^49 + x^48 + x^46 + x^45 + x^41 + x^36 + x^34 + x^31 + x^29 + x^28 + x^26 + x^25 + 1
+
+40-44-57 319 x^928 + x^898 + x^870 + x^846 + x^822 + x^819 + x^808 + x^800 + x^794 + x^792 + x^786 + x^778 + x^770 + x^764 + x^759 + x^748 + x^746 + x^740 + x^732 + x^716 + x^713 + x^697 + x^696 + x^691 + x^686 + x^674 + x^664 + x^661 + x^658 + x^650 + x^648 + x^645 + x^644 + x^636 + x^629 + x^626 + x^624 + x^623 + x^621 + x^620 + x^618 + x^615 + x^594 + x^593 + x^591 + x^590 + x^586 + x^583 + x^580 + x^579 + x^577 + x^575 + x^574 + x^572 + x^571 + x^568 + x^564 + x^563 + x^561 + x^558 + x^556 + x^555 + x^553 + x^550 + x^547 + x^545 + x^544 + x^542 + x^541 + x^538 + x^536 + x^533 + x^528 + x^526 + x^525 + x^522 + x^519 + x^513 + x^512 + x^510 + x^509 + x^508 + x^507 + x^504 + x^503 + x^501 + x^495 + x^488 + x^487 + x^485 + x^484 + x^483 + x^482 + x^480 + x^479 + x^474 + x^473 + x^471 + x^470 + x^466 + x^463 + x^460 + x^458 + x^457 + x^454 + x^453 + x^450 + x^449 + x^446 + x^444 + x^443 + x^441 + x^440 + x^439 + x^436 + x^434 + x^433 + x^432 + x^431 + x^430 + x^427 + x^425 + x^424 + x^422 + x^420 + x^417 + x^416 + x^415 + x^413 + x^412 + x^411 + x^410 + x^409 + x^408 + x^407 + x^406 + x^405 + x^403 + x^398 + x^397 + x^395 + x^392 + x^390 + x^387 + x^386 + x^385 + x^383 + x^375 + x^370 + x^369 + x^368 + x^367 + x^365 + x^364 + x^363 + x^360 + x^359 + x^357 + x^356 + x^353 + x^351 + x^349 + x^342 + x^340 + x^339 + x^336 + x^335 + x^329 + x^327 + x^326 + x^324 + x^323 + x^320 + x^319 + x^318 + x^317 + x^316 + x^315 + x^312 + x^311 + x^307 + x^306 + x^302 + x^299 + x^298 + x^297 + x^295 + x^294 + x^293 + x^291 + x^290 + x^287 + x^285 + x^284 + x^283 + x^282 + x^281 + x^279 + x^277 + x^276 + x^275 + x^272 + x^271 + x^268 + x^266 + x^263 + x^262 + x^261 + x^255 + x^251 + x^249 + x^248 + x^245 + x^244 + x^243 + x^240 + x^239 + x^238 + x^236 + x^235 + x^234 + x^230 + x^229 + x^228 + x^227 + x^226 + x^224 + x^221 + x^217 + x^214 + x^212 + x^209 + x^208 + x^204 + x^202 + x^201 + x^197 + x^194 + x^193 + x^192 + x^191 + x^189 + x^188 + x^185 + x^184 + x^182 + x^181 + x^178 + x^176 + x^173 + x^172 + x^171 + x^169 + x^166 + x^163 + x^161 + x^160 + x^158 + x^156 + x^155 + x^154 + x^152 + x^151 + x^149 + x^148 + x^146 + x^145 + x^144 + x^142 + x^141 + x^134 + x^132 + x^129 + x^122 + x^121 + x^119 + x^117 + x^116 + x^113 + x^112 + x^110 + x^109 + x^103 + x^102 + x^101 + x^100 + x^97 + x^95 + x^94 + x^93 + x^92 + x^91 + x^87 + x^86 + x^85 + x^84 + x^81 + x^80 + x^75 + x^74 + x^71 + x^70 + x^68 + x^66 + x^63 + x^52 + x^51 + x^50 + x^47 + x^45 + x^44 + x^43 + x^39 + x^38 + x^34 + x^24 + x^16 + x^8 + 1
+
+21-52-12 321 x^928 + x^898 + x^870 + x^868 + x^856 + x^838 + x^828 + x^826 + x^816 + x^815 + x^808 + x^804 + x^786 + x^784 + x^778 + x^748 + x^744 + x^736 + x^734 + x^733 + x^732 + x^731 + x^726 + x^722 + x^718 + x^710 + x^706 + x^704 + x^703 + x^694 + x^692 + x^691 + x^688 + x^683 + x^680 + x^679 + x^678 + x^674 + x^672 + x^668 + x^664 + x^660 + x^658 + x^656 + x^653 + x^649 + x^648 + x^644 + x^643 + x^638 + x^632 + x^630 + x^625 + x^623 + x^619 + x^618 + x^616 + x^615 + x^613 + x^610 + x^607 + x^606 + x^602 + x^601 + x^600 + x^595 + x^593 + x^589 + x^588 + x^586 + x^585 + x^580 + x^579 + x^578 + x^571 + x^570 + x^566 + x^565 + x^564 + x^563 + x^560 + x^559 + x^555 + x^554 + x^550 + x^548 + x^547 + x^546 + x^544 + x^543 + x^541 + x^539 + x^538 + x^537 + x^535 + x^531 + x^530 + x^529 + x^522 + x^520 + x^514 + x^513 + x^509 + x^507 + x^504 + x^501 + x^500 + x^499 + x^498 + x^496 + x^495 + x^494 + x^492 + x^491 + x^490 + x^486 + x^483 + x^480 + x^479 + x^476 + x^473 + x^469 + x^466 + x^463 + x^460 + x^459 + x^457 + x^451 + x^449 + x^443 + x^441 + x^440 + x^436 + x^433 + x^432 + x^431 + x^424 + x^420 + x^418 + x^416 + x^414 + x^411 + x^410 + x^409 + x^408 + x^406 + x^404 + x^403 + x^401 + x^400 + x^398 + x^393 + x^390 + x^388 + x^385 + x^384 + x^381 + x^375 + x^372 + x^366 + x^365 + x^361 + x^358 + x^356 + x^354 + x^352 + x^347 + x^346 + x^341 + x^340 + x^338 + x^335 + x^334 + x^333 + x^331 + x^330 + x^326 + x^323 + x^320 + x^319 + x^318 + x^317 + x^315 + x^312 + x^311 + x^309 + x^305 + x^303 + x^301 + x^299 + x^297 + x^296 + x^295 + x^290 + x^289 + x^283 + x^282 + x^277 + x^276 + x^273 + x^268 + x^267 + x^266 + x^264 + x^262 + x^261 + x^260 + x^256 + x^254 + x^251 + x^250 + x^247 + x^245 + x^244 + x^243 + x^240 + x^238 + x^235 + x^234 + x^233 + x^231 + x^229 + x^225 + x^224 + x^217 + x^212 + x^211 + x^209 + x^208 + x^205 + x^204 + x^202 + x^200 + x^198 + x^196 + x^195 + x^191 + x^190 + x^188 + x^187 + x^186 + x^182 + x^181 + x^180 + x^175 + x^174 + x^172 + x^171 + x^170 + x^169 + x^166 + x^164 + x^158 + x^154 + x^153 + x^152 + x^149 + x^148 + x^147 + x^146 + x^144 + x^142 + x^141 + x^140 + x^138 + x^137 + x^136 + x^135 + x^133 + x^131 + x^127 + x^125 + x^123 + x^122 + x^121 + x^120 + x^119 + x^115 + x^113 + x^112 + x^111 + x^106 + x^102 + x^101 + x^100 + x^98 + x^96 + x^95 + x^93 + x^92 + x^91 + x^90 + x^89 + x^88 + x^87 + x^81 + x^79 + x^76 + x^72 + x^71 + x^70 + x^64 + x^60 + x^57 + x^56 + x^55 + x^54 + x^50 + x^49 + x^48 + x^47 + x^43 + x^39 + x^38 + x^30 + x^29 + x^26 + x^25 + x^14 + x^10 + 1
+
+25-44-4 331 x^928 + x^898 + x^870 + x^866 + x^862 + x^859 + x^836 + x^834 + x^829 + x^822 + x^808 + x^806 + x^804 + x^800 + x^799 + x^798 + x^797 + x^795 + x^778 + x^776 + x^770 + x^769 + x^767 + x^762 + x^753 + x^739 + x^735 + x^734 + x^731 + x^721 + x^713 + x^709 + x^708 + x^706 + x^705 + x^703 + x^701 + x^698 + x^688 + x^679 + x^677 + x^676 + x^674 + x^670 + x^669 + x^667 + x^666 + x^661 + x^659 + x^658 + x^649 + x^647 + x^645 + x^643 + x^642 + x^638 + x^635 + x^633 + x^629 + x^626 + x^624 + x^620 + x^618 + x^617 + x^614 + x^611 + x^605 + x^603 + x^598 + x^596 + x^594 + x^593 + x^590 + x^587 + x^581 + x^580 + x^579 + x^571 + x^570 + x^568 + x^566 + x^562 + x^558 + x^557 + x^551 + x^550 + x^548 + x^547 + x^546 + x^544 + x^542 + x^541 + x^539 + x^536 + x^533 + x^532 + x^530 + x^527 + x^526 + x^525 + x^524 + x^523 + x^521 + x^520 + x^519 + x^518 + x^517 + x^515 + x^514 + x^513 + x^507 + x^506 + x^504 + x^501 + x^497 + x^493 + x^492 + x^490 + x^488 + x^483 + x^482 + x^481 + x^478 + x^477 + x^476 + x^475 + x^473 + x^467 + x^466 + x^465 + x^463 + x^462 + x^461 + x^460 + x^456 + x^454 + x^453 + x^452 + x^450 + x^448 + x^446 + x^444 + x^443 + x^442 + x^433 + x^426 + x^423 + x^422 + x^420 + x^419 + x^416 + x^413 + x^412 + x^411 + x^410 + x^406 + x^404 + x^403 + x^402 + x^401 + x^400 + x^398 + x^396 + x^395 + x^392 + x^391 + x^389 + x^387 + x^386 + x^385 + x^380 + x^372 + x^366 + x^365 + x^363 + x^362 + x^359 + x^357 + x^354 + x^353 + x^352 + x^348 + x^346 + x^345 + x^342 + x^340 + x^338 + x^335 + x^334 + x^333 + x^332 + x^325 + x^324 + x^323 + x^320 + x^319 + x^318 + x^314 + x^312 + x^309 + x^308 + x^303 + x^302 + x^301 + x^299 + x^295 + x^294 + x^292 + x^291 + x^290 + x^289 + x^286 + x^284 + x^279 + x^278 + x^274 + x^273 + x^268 + x^266 + x^265 + x^263 + x^261 + x^257 + x^256 + x^255 + x^254 + x^253 + x^248 + x^245 + x^244 + x^241 + x^240 + x^237 + x^235 + x^234 + x^233 + x^232 + x^230 + x^229 + x^228 + x^226 + x^223 + x^222 + x^220 + x^218 + x^214 + x^212 + x^211 + x^209 + x^207 + x^206 + x^203 + x^202 + x^201 + x^200 + x^199 + x^198 + x^196 + x^191 + x^189 + x^184 + x^178 + x^177 + x^176 + x^175 + x^172 + x^171 + x^169 + x^166 + x^165 + x^162 + x^161 + x^159 + x^157 + x^156 + x^155 + x^150 + x^149 + x^148 + x^147 + x^143 + x^142 + x^141 + x^140 + x^137 + x^136 + x^135 + x^133 + x^131 + x^130 + x^129 + x^127 + x^126 + x^125 + x^124 + x^123 + x^120 + x^113 + x^112 + x^108 + x^105 + x^104 + x^98 + x^96 + x^92 + x^90 + x^82 + x^81 + x^80 + x^78 + x^76 + x^74 + x^73 + x^68 + x^66 + x^64 + x^62 + x^60 + x^58 + x^54 + x^42 + x^38 + x^36 + x^32 + x^26 + x^18 + x^16 + x^10 + x^8 + x^2 + 1
+
+16-8-37 341 x^928 + x^898 + x^870 + x^842 + x^814 + x^808 + x^788 + x^786 + x^784 + x^778 + x^777 + x^775 + x^773 + x^762 + x^756 + x^751 + x^745 + x^736 + x^723 + x^721 + x^717 + x^715 + x^713 + x^710 + x^700 + x^697 + x^693 + x^691 + x^688 + x^685 + x^678 + x^674 + x^673 + x^672 + x^667 + x^654 + x^650 + x^647 + x^645 + x^644 + x^643 + x^642 + x^641 + x^635 + x^634 + x^632 + x^631 + x^630 + x^622 + x^621 + x^618 + x^615 + x^614 + x^612 + x^608 + x^605 + x^604 + x^603 + x^601 + x^596 + x^595 + x^592 + x^590 + x^589 + x^588 + x^587 + x^586 + x^585 + x^584 + x^583 + x^581 + x^579 + x^578 + x^576 + x^575 + x^573 + x^571 + x^569 + x^565 + x^564 + x^561 + x^560 + x^557 + x^556 + x^555 + x^554 + x^552 + x^544 + x^543 + x^540 + x^535 + x^533 + x^530 + x^528 + x^527 + x^524 + x^522 + x^520 + x^519 + x^517 + x^516 + x^515 + x^514 + x^513 + x^510 + x^509 + x^508 + x^507 + x^503 + x^502 + x^500 + x^497 + x^496 + x^493 + x^491 + x^490 + x^486 + x^480 + x^477 + x^476 + x^475 + x^474 + x^473 + x^472 + x^471 + x^467 + x^464 + x^463 + x^461 + x^458 + x^457 + x^453 + x^446 + x^444 + x^441 + x^439 + x^436 + x^434 + x^433 + x^432 + x^430 + x^427 + x^426 + x^422 + x^418 + x^417 + x^416 + x^414 + x^412 + x^411 + x^410 + x^405 + x^404 + x^401 + x^399 + x^396 + x^395 + x^392 + x^391 + x^390 + x^388 + x^387 + x^386 + x^385 + x^384 + x^383 + x^378 + x^377 + x^375 + x^373 + x^372 + x^371 + x^366 + x^364 + x^358 + x^357 + x^356 + x^352 + x^348 + x^345 + x^342 + x^340 + x^339 + x^338 + x^336 + x^335 + x^331 + x^330 + x^329 + x^327 + x^324 + x^323 + x^322 + x^321 + x^320 + x^317 + x^316 + x^315 + x^314 + x^310 + x^307 + x^306 + x^303 + x^297 + x^295 + x^294 + x^293 + x^292 + x^291 + x^290 + x^288 + x^286 + x^284 + x^283 + x^282 + x^278 + x^276 + x^275 + x^274 + x^269 + x^268 + x^267 + x^263 + x^262 + x^261 + x^260 + x^259 + x^258 + x^256 + x^251 + x^249 + x^248 + x^247 + x^245 + x^242 + x^241 + x^239 + x^238 + x^236 + x^235 + x^234 + x^233 + x^232 + x^230 + x^229 + x^225 + x^224 + x^223 + x^222 + x^220 + x^218 + x^216 + x^214 + x^213 + x^212 + x^211 + x^209 + x^206 + x^201 + x^200 + x^199 + x^197 + x^196 + x^194 + x^193 + x^190 + x^186 + x^184 + x^181 + x^180 + x^179 + x^178 + x^177 + x^176 + x^175 + x^169 + x^168 + x^166 + x^164 + x^160 + x^158 + x^157 + x^156 + x^153 + x^152 + x^147 + x^146 + x^136 + x^134 + x^132 + x^129 + x^126 + x^125 + x^124 + x^123 + x^122 + x^120 + x^119 + x^116 + x^114 + x^112 + x^108 + x^107 + x^106 + x^104 + x^102 + x^98 + x^95 + x^91 + x^85 + x^84 + x^82 + x^81 + x^80 + x^79 + x^77 + x^76 + x^73 + x^72 + x^70 + x^62 + x^60 + x^59 + x^58 + x^56 + x^55 + x^53 + x^49 + x^44 + x^42 + x^41 + x^39 + x^38 + x^35 + x^34 + x^32 + x^28 + x^26 + x^24 + x^22 + 1
+
+17-12-36 341 x^928 + x^898 + x^870 + x^868 + x^860 + x^848 + x^838 + x^830 + x^829 + x^806 + x^798 + x^797 + x^789 + x^788 + x^772 + x^770 + x^767 + x^762 + x^761 + x^756 + x^751 + x^749 + x^748 + x^746 + x^742 + x^740 + x^738 + x^730 + x^726 + x^721 + x^718 + x^716 + x^714 + x^710 + x^709 + x^707 + x^706 + x^705 + x^696 + x^688 + x^684 + x^681 + x^677 + x^676 + x^674 + x^669 + x^666 + x^664 + x^659 + x^658 + x^657 + x^656 + x^655 + x^654 + x^651 + x^650 + x^647 + x^645 + x^639 + x^637 + x^636 + x^634 + x^631 + x^627 + x^625 + x^624 + x^622 + x^621 + x^619 + x^615 + x^614 + x^608 + x^605 + x^601 + x^599 + x^597 + x^596 + x^594 + x^593 + x^592 + x^591 + x^588 + x^587 + x^586 + x^585 + x^583 + x^582 + x^580 + x^578 + x^577 + x^576 + x^575 + x^574 + x^573 + x^572 + x^569 + x^568 + x^567 + x^565 + x^564 + x^561 + x^560 + x^559 + x^558 + x^557 + x^554 + x^553 + x^546 + x^545 + x^543 + x^542 + x^541 + x^539 + x^538 + x^536 + x^533 + x^530 + x^529 + x^527 + x^526 + x^525 + x^521 + x^520 + x^513 + x^509 + x^508 + x^504 + x^501 + x^500 + x^499 + x^498 + x^497 + x^496 + x^494 + x^488 + x^486 + x^484 + x^480 + x^479 + x^478 + x^475 + x^471 + x^469 + x^466 + x^463 + x^458 + x^456 + x^455 + x^452 + x^450 + x^449 + x^445 + x^437 + x^436 + x^433 + x^432 + x^430 + x^428 + x^426 + x^425 + x^423 + x^417 + x^416 + x^415 + x^413 + x^401 + x^400 + x^395 + x^394 + x^392 + x^391 + x^387 + x^386 + x^385 + x^384 + x^383 + x^379 + x^375 + x^373 + x^372 + x^371 + x^368 + x^366 + x^361 + x^360 + x^359 + x^358 + x^357 + x^354 + x^352 + x^350 + x^349 + x^348 + x^347 + x^345 + x^344 + x^343 + x^340 + x^334 + x^332 + x^330 + x^328 + x^327 + x^325 + x^323 + x^321 + x^318 + x^317 + x^316 + x^315 + x^314 + x^311 + x^310 + x^309 + x^308 + x^307 + x^306 + x^304 + x^299 + x^298 + x^296 + x^295 + x^294 + x^292 + x^291 + x^288 + x^287 + x^286 + x^282 + x^281 + x^280 + x^272 + x^271 + x^268 + x^267 + x^262 + x^256 + x^253 + x^252 + x^250 + x^244 + x^242 + x^241 + x^240 + x^238 + x^234 + x^233 + x^232 + x^231 + x^229 + x^228 + x^227 + x^226 + x^223 + x^222 + x^221 + x^220 + x^219 + x^218 + x^217 + x^215 + x^214 + x^212 + x^211 + x^208 + x^206 + x^203 + x^201 + x^199 + x^198 + x^195 + x^194 + x^193 + x^192 + x^189 + x^185 + x^182 + x^180 + x^179 + x^177 + x^176 + x^173 + x^172 + x^170 + x^164 + x^163 + x^160 + x^157 + x^155 + x^153 + x^152 + x^150 + x^147 + x^146 + x^139 + x^137 + x^132 + x^131 + x^127 + x^126 + x^125 + x^123 + x^122 + x^120 + x^115 + x^113 + x^111 + x^109 + x^107 + x^106 + x^104 + x^103 + x^101 + x^100 + x^99 + x^98 + x^97 + x^94 + x^88 + x^85 + x^78 + x^77 + x^76 + x^71 + x^68 + x^66 + x^64 + x^51 + x^47 + x^45 + x^39 + x^38 + x^36 + x^31 + x^30 + x^26 + x^24 + x^22 + x^20 + x^15 + 1
+
+2-30-27 343 x^928 + x^898 + x^881 + x^870 + x^868 + x^866 + x^851 + x^838 + x^819 + x^817 + x^808 + x^806 + x^804 + x^778 + x^776 + x^774 + x^772 + x^761 + x^759 + x^755 + x^753 + x^748 + x^742 + x^740 + x^731 + x^725 + x^718 + x^716 + x^712 + x^710 + x^706 + x^695 + x^693 + x^691 + x^689 + x^688 + x^682 + x^678 + x^674 + x^665 + x^663 + x^661 + x^658 + x^657 + x^652 + x^646 + x^644 + x^642 + x^641 + x^637 + x^629 + x^628 + x^627 + x^626 + x^625 + x^618 + x^616 + x^614 + x^612 + x^611 + x^610 + x^607 + x^601 + x^598 + x^597 + x^593 + x^592 + x^588 + x^580 + x^579 + x^577 + x^575 + x^573 + x^571 + x^569 + x^568 + x^566 + x^564 + x^563 + x^562 + x^561 + x^560 + x^554 + x^552 + x^550 + x^548 + x^543 + x^539 + x^538 + x^536 + x^534 + x^531 + x^530 + x^529 + x^528 + x^524 + x^521 + x^519 + x^517 + x^515 + x^513 + x^509 + x^508 + x^507 + x^505 + x^502 + x^500 + x^499 + x^498 + x^497 + x^492 + x^491 + x^487 + x^486 + x^484 + x^479 + x^478 + x^477 + x^476 + x^473 + x^470 + x^468 + x^466 + x^465 + x^464 + x^458 + x^454 + x^450 + x^448 + x^447 + x^446 + x^445 + x^439 + x^436 + x^435 + x^434 + x^433 + x^432 + x^428 + x^426 + x^422 + x^420 + x^416 + x^415 + x^413 + x^411 + x^409 + x^407 + x^406 + x^404 + x^399 + x^396 + x^392 + x^389 + x^384 + x^383 + x^382 + x^381 + x^379 + x^377 + x^376 + x^374 + x^372 + x^370 + x^367 + x^359 + x^355 + x^352 + x^347 + x^346 + x^344 + x^342 + x^341 + x^339 + x^338 + x^336 + x^335 + x^334 + x^328 + x^327 + x^324 + x^320 + x^318 + x^316 + x^314 + x^313 + x^309 + x^308 + x^304 + x^303 + x^300 + x^298 + x^297 + x^296 + x^294 + x^292 + x^287 + x^286 + x^284 + x^283 + x^282 + x^278 + x^276 + x^272 + x^269 + x^266 + x^265 + x^264 + x^261 + x^256 + x^252 + x^250 + x^248 + x^247 + x^245 + x^244 + x^243 + x^242 + x^239 + x^238 + x^237 + x^236 + x^235 + x^234 + x^233 + x^231 + x^229 + x^226 + x^225 + x^224 + x^220 + x^219 + x^216 + x^213 + x^212 + x^210 + x^205 + x^204 + x^203 + x^201 + x^199 + x^197 + x^194 + x^192 + x^191 + x^190 + x^189 + x^188 + x^186 + x^184 + x^183 + x^182 + x^178 + x^177 + x^176 + x^175 + x^173 + x^171 + x^170 + x^169 + x^166 + x^165 + x^163 + x^162 + x^161 + x^157 + x^156 + x^155 + x^153 + x^152 + x^150 + x^148 + x^147 + x^146 + x^144 + x^143 + x^141 + x^139 + x^137 + x^134 + x^133 + x^129 + x^128 + x^127 + x^126 + x^125 + x^123 + x^119 + x^117 + x^116 + x^115 + x^114 + x^113 + x^111 + x^110 + x^102 + x^101 + x^100 + x^99 + x^97 + x^96 + x^94 + x^93 + x^89 + x^88 + x^84 + x^83 + x^81 + x^78 + x^74 + x^72 + x^71 + x^69 + x^67 + x^62 + x^61 + x^59 + x^57 + x^56 + x^55 + x^53 + x^51 + x^47 + x^44 + x^42 + x^39 + x^37 + x^36 + x^35 + x^33 + x^30 + x^26 + x^24 + x^23 + x^21 + x^19 + x^18 + x^17 + x^16 + x^10 + x^8 + x^2 + 1
+
+26-55-39 345 x^928 + x^904 + x^898 + x^870 + x^861 + x^856 + x^851 + x^850 + x^831 + x^821 + x^820 + x^818 + x^813 + x^802 + x^796 + x^794 + x^790 + x^788 + x^783 + x^778 + x^775 + x^772 + x^770 + x^765 + x^760 + x^754 + x^746 + x^745 + x^741 + x^740 + x^736 + x^735 + x^734 + x^732 + x^731 + x^729 + x^727 + x^723 + x^722 + x^721 + x^716 + x^715 + x^710 + x^708 + x^705 + x^701 + x^699 + x^686 + x^685 + x^684 + x^681 + x^679 + x^678 + x^676 + x^674 + x^673 + x^672 + x^668 + x^664 + x^663 + x^661 + x^660 + x^658 + x^656 + x^650 + x^648 + x^645 + x^643 + x^641 + x^638 + x^637 + x^636 + x^632 + x^622 + x^621 + x^618 + x^616 + x^615 + x^614 + x^612 + x^608 + x^603 + x^600 + x^598 + x^595 + x^594 + x^593 + x^591 + x^590 + x^589 + x^588 + x^585 + x^582 + x^581 + x^576 + x^574 + x^571 + x^569 + x^568 + x^564 + x^562 + x^557 + x^556 + x^553 + x^550 + x^549 + x^548 + x^547 + x^546 + x^545 + x^544 + x^543 + x^538 + x^535 + x^530 + x^525 + x^520 + x^517 + x^515 + x^514 + x^510 + x^509 + x^506 + x^501 + x^497 + x^495 + x^489 + x^486 + x^484 + x^483 + x^482 + x^480 + x^479 + x^476 + x^474 + x^473 + x^471 + x^470 + x^469 + x^467 + x^464 + x^462 + x^460 + x^453 + x^452 + x^450 + x^449 + x^448 + x^446 + x^444 + x^443 + x^441 + x^436 + x^435 + x^434 + x^433 + x^432 + x^429 + x^428 + x^427 + x^424 + x^419 + x^418 + x^417 + x^416 + x^413 + x^412 + x^410 + x^407 + x^404 + x^403 + x^401 + x^399 + x^398 + x^397 + x^396 + x^394 + x^393 + x^392 + x^390 + x^386 + x^385 + x^383 + x^379 + x^378 + x^377 + x^376 + x^375 + x^373 + x^372 + x^366 + x^362 + x^359 + x^357 + x^355 + x^354 + x^351 + x^350 + x^347 + x^346 + x^344 + x^340 + x^339 + x^338 + x^337 + x^333 + x^332 + x^331 + x^330 + x^328 + x^326 + x^325 + x^323 + x^319 + x^315 + x^314 + x^313 + x^311 + x^310 + x^308 + x^307 + x^306 + x^304 + x^301 + x^300 + x^298 + x^296 + x^294 + x^293 + x^292 + x^291 + x^290 + x^286 + x^283 + x^280 + x^277 + x^274 + x^272 + x^265 + x^264 + x^263 + x^261 + x^260 + x^258 + x^255 + x^252 + x^251 + x^250 + x^249 + x^247 + x^245 + x^244 + x^241 + x^238 + x^235 + x^234 + x^230 + x^228 + x^225 + x^221 + x^218 + x^212 + x^211 + x^210 + x^208 + x^206 + x^204 + x^203 + x^202 + x^199 + x^198 + x^196 + x^195 + x^193 + x^188 + x^186 + x^184 + x^183 + x^177 + x^176 + x^167 + x^166 + x^165 + x^163 + x^161 + x^160 + x^158 + x^156 + x^153 + x^151 + x^146 + x^144 + x^141 + x^140 + x^134 + x^133 + x^129 + x^128 + x^127 + x^124 + x^123 + x^121 + x^119 + x^117 + x^115 + x^114 + x^113 + x^112 + x^111 + x^110 + x^109 + x^105 + x^104 + x^103 + x^100 + x^99 + x^93 + x^92 + x^91 + x^86 + x^84 + x^81 + x^80 + x^77 + x^75 + x^72 + x^71 + x^70 + x^68 + x^66 + x^65 + x^64 + x^61 + x^54 + x^53 + x^47 + x^45 + x^36 + x^35 + x^34 + x^32 + x^29 + x^18 + x^7 + 1
+
+40-36-23 345 x^928 + x^898 + x^886 + x^870 + x^862 + x^844 + x^838 + x^826 + x^820 + x^816 + x^814 + x^808 + x^797 + x^792 + x^791 + x^790 + x^784 + x^778 + x^777 + x^772 + x^768 + x^767 + x^766 + x^762 + x^761 + x^756 + x^753 + x^749 + x^747 + x^744 + x^742 + x^738 + x^735 + x^734 + x^726 + x^724 + x^723 + x^720 + x^712 + x^702 + x^701 + x^695 + x^689 + x^684 + x^683 + x^681 + x^677 + x^675 + x^670 + x^669 + x^664 + x^663 + x^660 + x^659 + x^658 + x^653 + x^648 + x^646 + x^644 + x^634 + x^629 + x^628 + x^627 + x^626 + x^625 + x^622 + x^621 + x^617 + x^616 + x^611 + x^609 + x^605 + x^604 + x^603 + x^602 + x^597 + x^595 + x^594 + x^593 + x^592 + x^586 + x^585 + x^584 + x^578 + x^575 + x^574 + x^573 + x^572 + x^571 + x^569 + x^565 + x^563 + x^561 + x^559 + x^557 + x^555 + x^554 + x^547 + x^545 + x^543 + x^539 + x^537 + x^536 + x^535 + x^534 + x^529 + x^528 + x^527 + x^525 + x^524 + x^521 + x^520 + x^519 + x^518 + x^517 + x^515 + x^514 + x^512 + x^510 + x^509 + x^508 + x^507 + x^506 + x^504 + x^503 + x^501 + x^499 + x^496 + x^494 + x^490 + x^489 + x^487 + x^485 + x^484 + x^482 + x^481 + x^480 + x^479 + x^478 + x^477 + x^475 + x^473 + x^470 + x^466 + x^465 + x^464 + x^463 + x^460 + x^457 + x^456 + x^454 + x^453 + x^452 + x^447 + x^446 + x^442 + x^441 + x^439 + x^436 + x^434 + x^432 + x^430 + x^428 + x^427 + x^423 + x^421 + x^416 + x^415 + x^414 + x^413 + x^411 + x^408 + x^405 + x^402 + x^401 + x^399 + x^396 + x^394 + x^393 + x^391 + x^390 + x^389 + x^388 + x^387 + x^386 + x^384 + x^381 + x^379 + x^378 + x^377 + x^375 + x^374 + x^372 + x^369 + x^367 + x^366 + x^364 + x^363 + x^361 + x^360 + x^359 + x^358 + x^356 + x^355 + x^354 + x^353 + x^352 + x^349 + x^345 + x^343 + x^342 + x^338 + x^336 + x^335 + x^334 + x^333 + x^331 + x^329 + x^328 + x^327 + x^320 + x^318 + x^317 + x^316 + x^312 + x^307 + x^304 + x^303 + x^300 + x^298 + x^296 + x^295 + x^294 + x^293 + x^291 + x^290 + x^288 + x^287 + x^286 + x^285 + x^284 + x^276 + x^275 + x^274 + x^273 + x^272 + x^271 + x^269 + x^268 + x^266 + x^263 + x^262 + x^259 + x^257 + x^255 + x^254 + x^251 + x^248 + x^246 + x^244 + x^240 + x^238 + x^237 + x^235 + x^234 + x^232 + x^228 + x^226 + x^225 + x^224 + x^222 + x^220 + x^217 + x^213 + x^212 + x^211 + x^209 + x^208 + x^207 + x^202 + x^200 + x^199 + x^198 + x^192 + x^190 + x^187 + x^183 + x^182 + x^180 + x^175 + x^172 + x^171 + x^170 + x^169 + x^167 + x^166 + x^165 + x^164 + x^163 + x^160 + x^157 + x^154 + x^153 + x^152 + x^150 + x^149 + x^148 + x^147 + x^146 + x^144 + x^142 + x^140 + x^137 + x^136 + x^134 + x^132 + x^129 + x^128 + x^124 + x^119 + x^117 + x^116 + x^115 + x^110 + x^108 + x^106 + x^103 + x^98 + x^88 + x^82 + x^76 + x^75 + x^74 + x^69 + x^68 + x^64 + x^62 + x^51 + x^47 + x^46 + x^39 + x^32 + x^23 + x^22 + 1
+
+24-36-37 347 x^928 + x^898 + x^878 + x^870 + x^854 + x^830 + x^824 + x^821 + x^818 + x^816 + x^813 + x^808 + x^806 + x^800 + x^792 + x^791 + x^789 + x^783 + x^780 + x^778 + x^776 + x^768 + x^765 + x^759 + x^753 + x^750 + x^747 + x^745 + x^744 + x^741 + x^740 + x^736 + x^734 + x^729 + x^721 + x^717 + x^715 + x^714 + x^708 + x^705 + x^704 + x^702 + x^699 + x^694 + x^690 + x^688 + x^684 + x^682 + x^681 + x^680 + x^679 + x^670 + x^669 + x^666 + x^664 + x^663 + x^660 + x^652 + x^649 + x^646 + x^645 + x^643 + x^639 + x^636 + x^634 + x^633 + x^631 + x^629 + x^627 + x^622 + x^621 + x^620 + x^614 + x^613 + x^612 + x^611 + x^610 + x^609 + x^605 + x^603 + x^601 + x^600 + x^599 + x^596 + x^593 + x^590 + x^587 + x^586 + x^585 + x^584 + x^583 + x^582 + x^581 + x^579 + x^577 + x^573 + x^565 + x^564 + x^563 + x^562 + x^561 + x^560 + x^559 + x^558 + x^557 + x^554 + x^550 + x^549 + x^546 + x^545 + x^544 + x^543 + x^542 + x^539 + x^538 + x^536 + x^535 + x^534 + x^529 + x^527 + x^525 + x^524 + x^523 + x^521 + x^519 + x^518 + x^516 + x^515 + x^512 + x^510 + x^505 + x^504 + x^503 + x^501 + x^500 + x^499 + x^493 + x^492 + x^488 + x^484 + x^483 + x^479 + x^474 + x^472 + x^470 + x^465 + x^464 + x^459 + x^457 + x^455 + x^454 + x^450 + x^440 + x^435 + x^434 + x^433 + x^427 + x^426 + x^424 + x^421 + x^420 + x^419 + x^414 + x^413 + x^412 + x^409 + x^407 + x^406 + x^405 + x^403 + x^401 + x^400 + x^399 + x^398 + x^395 + x^393 + x^391 + x^390 + x^388 + x^383 + x^381 + x^376 + x^374 + x^370 + x^367 + x^365 + x^363 + x^359 + x^356 + x^355 + x^353 + x^352 + x^348 + x^347 + x^346 + x^345 + x^344 + x^343 + x^342 + x^339 + x^336 + x^330 + x^327 + x^326 + x^325 + x^324 + x^323 + x^321 + x^318 + x^316 + x^315 + x^314 + x^312 + x^311 + x^310 + x^302 + x^300 + x^298 + x^295 + x^294 + x^292 + x^284 + x^282 + x^279 + x^278 + x^277 + x^276 + x^271 + x^268 + x^267 + x^266 + x^265 + x^264 + x^262 + x^260 + x^256 + x^253 + x^250 + x^249 + x^248 + x^244 + x^243 + x^242 + x^239 + x^236 + x^235 + x^232 + x^231 + x^229 + x^227 + x^226 + x^222 + x^220 + x^219 + x^216 + x^215 + x^214 + x^213 + x^211 + x^209 + x^208 + x^204 + x^202 + x^200 + x^199 + x^198 + x^196 + x^193 + x^191 + x^190 + x^189 + x^188 + x^187 + x^186 + x^179 + x^178 + x^177 + x^176 + x^175 + x^174 + x^170 + x^169 + x^167 + x^163 + x^162 + x^161 + x^160 + x^153 + x^150 + x^149 + x^147 + x^145 + x^140 + x^138 + x^136 + x^135 + x^133 + x^131 + x^130 + x^128 + x^127 + x^119 + x^117 + x^113 + x^111 + x^110 + x^108 + x^104 + x^103 + x^102 + x^101 + x^100 + x^99 + x^97 + x^96 + x^93 + x^88 + x^87 + x^86 + x^85 + x^84 + x^83 + x^82 + x^80 + x^78 + x^77 + x^72 + x^71 + x^70 + x^67 + x^66 + x^64 + x^63 + x^62 + x^61 + x^59 + x^58 + x^56 + x^54 + x^53 + x^50 + x^47 + x^46 + x^38 + x^24 + x^16 + 1
+
+26-38-9 353 x^928 + x^898 + x^875 + x^870 + x^848 + x^822 + x^808 + x^806 + x^800 + x^798 + x^797 + x^795 + x^792 + x^788 + x^778 + x^776 + x^769 + x^767 + x^765 + x^762 + x^758 + x^756 + x^747 + x^741 + x^732 + x^730 + x^728 + x^727 + x^723 + x^719 + x^714 + x^712 + x^711 + x^709 + x^706 + x^703 + x^700 + x^697 + x^695 + x^689 + x^688 + x^686 + x^684 + x^682 + x^680 + x^678 + x^676 + x^674 + x^673 + x^667 + x^666 + x^664 + x^661 + x^658 + x^653 + x^652 + x^649 + x^648 + x^646 + x^645 + x^635 + x^634 + x^633 + x^629 + x^626 + x^625 + x^620 + x^616 + x^614 + x^612 + x^611 + x^610 + x^607 + x^606 + x^604 + x^603 + x^599 + x^595 + x^594 + x^591 + x^583 + x^580 + x^578 + x^577 + x^572 + x^569 + x^568 + x^567 + x^566 + x^564 + x^559 + x^558 + x^555 + x^554 + x^550 + x^549 + x^548 + x^543 + x^542 + x^541 + x^539 + x^533 + x^532 + x^531 + x^528 + x^527 + x^526 + x^523 + x^519 + x^518 + x^515 + x^514 + x^513 + x^512 + x^511 + x^510 + x^509 + x^508 + x^507 + x^506 + x^502 + x^497 + x^495 + x^491 + x^488 + x^487 + x^485 + x^483 + x^482 + x^481 + x^478 + x^477 + x^476 + x^475 + x^473 + x^469 + x^466 + x^463 + x^462 + x^460 + x^458 + x^457 + x^456 + x^451 + x^447 + x^444 + x^443 + x^442 + x^440 + x^438 + x^437 + x^435 + x^433 + x^432 + x^430 + x^427 + x^424 + x^418 + x^417 + x^416 + x^414 + x^410 + x^409 + x^403 + x^401 + x^398 + x^397 + x^396 + x^394 + x^393 + x^391 + x^389 + x^388 + x^386 + x^385 + x^384 + x^382 + x^381 + x^380 + x^375 + x^374 + x^368 + x^364 + x^363 + x^359 + x^358 + x^357 + x^356 + x^354 + x^350 + x^349 + x^347 + x^346 + x^339 + x^337 + x^336 + x^334 + x^332 + x^330 + x^329 + x^328 + x^327 + x^326 + x^325 + x^324 + x^320 + x^318 + x^317 + x^315 + x^313 + x^309 + x^307 + x^305 + x^304 + x^303 + x^300 + x^299 + x^295 + x^293 + x^290 + x^288 + x^286 + x^285 + x^281 + x^279 + x^277 + x^274 + x^273 + x^269 + x^267 + x^266 + x^265 + x^263 + x^262 + x^257 + x^256 + x^255 + x^251 + x^249 + x^247 + x^246 + x^243 + x^241 + x^237 + x^236 + x^233 + x^230 + x^228 + x^227 + x^226 + x^225 + x^224 + x^223 + x^222 + x^221 + x^220 + x^212 + x^211 + x^210 + x^209 + x^208 + x^205 + x^204 + x^202 + x^201 + x^200 + x^197 + x^192 + x^191 + x^186 + x^184 + x^183 + x^181 + x^177 + x^175 + x^174 + x^170 + x^167 + x^165 + x^164 + x^162 + x^156 + x^154 + x^149 + x^148 + x^147 + x^144 + x^143 + x^142 + x^141 + x^139 + x^138 + x^137 + x^133 + x^131 + x^130 + x^128 + x^127 + x^126 + x^120 + x^116 + x^115 + x^113 + x^111 + x^108 + x^107 + x^105 + x^101 + x^99 + x^97 + x^95 + x^91 + x^90 + x^88 + x^87 + x^85 + x^81 + x^79 + x^78 + x^75 + x^72 + x^71 + x^70 + x^69 + x^66 + x^65 + x^63 + x^59 + x^57 + x^55 + x^54 + x^52 + x^51 + x^50 + x^49 + x^46 + x^44 + x^43 + x^39 + x^36 + x^34 + x^33 + x^32 + x^31 + x^30 + x^26 + x^24 + x^22 + x^16 + x^14 + x^8 + x^6 + 1
+
+31-6-30 353 x^928 + x^898 + x^870 + x^834 + x^814 + x^796 + x^790 + x^788 + x^784 + x^774 + x^772 + x^770 + x^762 + x^760 + x^756 + x^748 + x^740 + x^734 + x^732 + x^728 + x^727 + x^726 + x^718 + x^716 + x^712 + x^707 + x^701 + x^700 + x^697 + x^692 + x^688 + x^686 + x^684 + x^682 + x^681 + x^678 + x^677 + x^676 + x^674 + x^671 + x^670 + x^668 + x^665 + x^660 + x^658 + x^655 + x^652 + x^651 + x^650 + x^649 + x^646 + x^642 + x^641 + x^639 + x^638 + x^637 + x^636 + x^635 + x^630 + x^625 + x^624 + x^623 + x^622 + x^621 + x^620 + x^619 + x^617 + x^612 + x^611 + x^610 + x^609 + x^608 + x^607 + x^606 + x^604 + x^601 + x^598 + x^597 + x^593 + x^592 + x^591 + x^590 + x^582 + x^579 + x^578 + x^572 + x^570 + x^567 + x^566 + x^565 + x^563 + x^561 + x^559 + x^558 + x^555 + x^554 + x^544 + x^543 + x^542 + x^540 + x^539 + x^536 + x^533 + x^529 + x^528 + x^525 + x^522 + x^517 + x^516 + x^512 + x^511 + x^510 + x^507 + x^505 + x^502 + x^501 + x^499 + x^494 + x^492 + x^491 + x^489 + x^488 + x^487 + x^486 + x^484 + x^483 + x^481 + x^480 + x^476 + x^473 + x^469 + x^468 + x^466 + x^465 + x^464 + x^457 + x^451 + x^449 + x^448 + x^445 + x^444 + x^441 + x^440 + x^438 + x^436 + x^435 + x^433 + x^432 + x^431 + x^428 + x^425 + x^422 + x^420 + x^418 + x^414 + x^413 + x^412 + x^411 + x^410 + x^406 + x^405 + x^402 + x^401 + x^400 + x^394 + x^390 + x^389 + x^387 + x^384 + x^382 + x^380 + x^376 + x^375 + x^372 + x^371 + x^370 + x^369 + x^366 + x^363 + x^362 + x^361 + x^359 + x^357 + x^356 + x^354 + x^352 + x^351 + x^349 + x^347 + x^346 + x^344 + x^343 + x^342 + x^341 + x^340 + x^338 + x^337 + x^336 + x^334 + x^333 + x^331 + x^328 + x^323 + x^322 + x^318 + x^315 + x^313 + x^312 + x^310 + x^309 + x^308 + x^307 + x^301 + x^300 + x^298 + x^296 + x^295 + x^294 + x^292 + x^287 + x^285 + x^284 + x^283 + x^282 + x^279 + x^276 + x^275 + x^272 + x^270 + x^269 + x^268 + x^267 + x^263 + x^261 + x^259 + x^258 + x^256 + x^250 + x^248 + x^247 + x^246 + x^245 + x^244 + x^240 + x^239 + x^238 + x^237 + x^236 + x^235 + x^232 + x^231 + x^230 + x^229 + x^226 + x^223 + x^220 + x^217 + x^216 + x^213 + x^212 + x^210 + x^208 + x^205 + x^204 + x^201 + x^195 + x^194 + x^192 + x^191 + x^189 + x^188 + x^182 + x^181 + x^177 + x^175 + x^174 + x^173 + x^171 + x^169 + x^167 + x^162 + x^161 + x^159 + x^158 + x^154 + x^153 + x^148 + x^146 + x^145 + x^144 + x^143 + x^142 + x^141 + x^140 + x^139 + x^138 + x^135 + x^134 + x^133 + x^122 + x^119 + x^118 + x^115 + x^111 + x^110 + x^108 + x^107 + x^106 + x^105 + x^101 + x^99 + x^97 + x^96 + x^95 + x^94 + x^93 + x^92 + x^90 + x^87 + x^84 + x^83 + x^80 + x^74 + x^73 + x^71 + x^70 + x^67 + x^66 + x^63 + x^55 + x^53 + x^52 + x^51 + x^49 + x^45 + x^44 + x^43 + x^40 + x^35 + x^34 + x^33 + x^32 + x^27 + x^25 + x^24 + x^22 + x^21 + x^20 + x^17 + x^16 + x^11 + x^4 + 1
+
+54-21-7 353 x^928 + x^898 + x^870 + x^861 + x^860 + x^859 + x^858 + x^846 + x^842 + x^837 + x^836 + x^835 + x^831 + x^830 + x^829 + x^828 + x^822 + x^818 + x^811 + x^810 + x^808 + x^807 + x^804 + x^798 + x^792 + x^788 + x^781 + x^778 + x^758 + x^756 + x^751 + x^750 + x^746 + x^745 + x^740 + x^739 + x^738 + x^722 + x^720 + x^716 + x^703 + x^701 + x^696 + x^695 + x^688 + x^686 + x^674 + x^666 + x^659 + x^658 + x^656 + x^655 + x^654 + x^649 + x^644 + x^643 + x^641 + x^637 + x^632 + x^630 + x^629 + x^626 + x^623 + x^621 + x^620 + x^618 + x^614 + x^613 + x^606 + x^601 + x^599 + x^597 + x^595 + x^592 + x^591 + x^589 + x^588 + x^586 + x^584 + x^582 + x^577 + x^576 + x^575 + x^568 + x^567 + x^565 + x^564 + x^562 + x^558 + x^556 + x^553 + x^551 + x^550 + x^548 + x^547 + x^541 + x^540 + x^535 + x^534 + x^528 + x^527 + x^526 + x^522 + x^521 + x^520 + x^517 + x^514 + x^512 + x^510 + x^504 + x^503 + x^502 + x^498 + x^497 + x^496 + x^487 + x^482 + x^474 + x^473 + x^469 + x^468 + x^466 + x^463 + x^462 + x^459 + x^454 + x^453 + x^452 + x^451 + x^447 + x^442 + x^441 + x^433 + x^431 + x^430 + x^429 + x^426 + x^424 + x^423 + x^422 + x^421 + x^419 + x^417 + x^415 + x^412 + x^411 + x^409 + x^405 + x^402 + x^397 + x^396 + x^393 + x^392 + x^391 + x^385 + x^384 + x^382 + x^381 + x^380 + x^370 + x^369 + x^367 + x^365 + x^364 + x^361 + x^359 + x^356 + x^355 + x^351 + x^350 + x^349 + x^343 + x^342 + x^341 + x^340 + x^339 + x^338 + x^336 + x^335 + x^333 + x^332 + x^331 + x^330 + x^326 + x^325 + x^324 + x^323 + x^318 + x^317 + x^315 + x^313 + x^310 + x^309 + x^306 + x^301 + x^300 + x^298 + x^295 + x^294 + x^293 + x^292 + x^291 + x^290 + x^289 + x^288 + x^282 + x^281 + x^278 + x^277 + x^276 + x^275 + x^273 + x^271 + x^268 + x^266 + x^265 + x^263 + x^261 + x^260 + x^259 + x^257 + x^252 + x^249 + x^247 + x^244 + x^243 + x^238 + x^236 + x^232 + x^231 + x^229 + x^228 + x^227 + x^226 + x^225 + x^224 + x^221 + x^220 + x^219 + x^215 + x^214 + x^211 + x^209 + x^207 + x^204 + x^201 + x^198 + x^196 + x^195 + x^194 + x^193 + x^191 + x^189 + x^186 + x^185 + x^182 + x^181 + x^179 + x^178 + x^174 + x^173 + x^172 + x^170 + x^168 + x^166 + x^164 + x^162 + x^160 + x^159 + x^156 + x^155 + x^154 + x^152 + x^151 + x^149 + x^148 + x^147 + x^146 + x^145 + x^143 + x^140 + x^134 + x^133 + x^130 + x^129 + x^128 + x^126 + x^124 + x^123 + x^122 + x^121 + x^119 + x^118 + x^117 + x^116 + x^115 + x^113 + x^110 + x^107 + x^106 + x^105 + x^104 + x^103 + x^102 + x^101 + x^99 + x^97 + x^96 + x^95 + x^94 + x^93 + x^92 + x^91 + x^90 + x^89 + x^86 + x^85 + x^82 + x^81 + x^80 + x^79 + x^78 + x^76 + x^73 + x^71 + x^69 + x^65 + x^63 + x^60 + x^58 + x^57 + x^56 + x^55 + x^54 + x^52 + x^49 + x^47 + x^46 + x^45 + x^43 + x^42 + x^40 + x^39 + x^38 + x^36 + x^33 + x^32 + x^28 + x^25 + x^19 + x^18 + x^7 + 1
+
+8-36-47 355 x^928 + x^898 + x^870 + x^860 + x^856 + x^830 + x^818 + x^814 + x^813 + x^808 + x^800 + x^797 + x^796 + x^792 + x^788 + x^783 + x^778 + x^776 + x^772 + x^771 + x^770 + x^767 + x^766 + x^762 + x^755 + x^750 + x^740 + x^737 + x^736 + x^734 + x^730 + x^729 + x^724 + x^719 + x^711 + x^710 + x^707 + x^706 + x^698 + x^693 + x^692 + x^690 + x^688 + x^687 + x^680 + x^676 + x^674 + x^673 + x^672 + x^669 + x^665 + x^663 + x^662 + x^658 + x^657 + x^656 + x^653 + x^651 + x^650 + x^648 + x^647 + x^642 + x^635 + x^632 + x^631 + x^630 + x^627 + x^625 + x^624 + x^623 + x^622 + x^620 + x^619 + x^618 + x^609 + x^600 + x^595 + x^593 + x^592 + x^591 + x^589 + x^587 + x^583 + x^582 + x^579 + x^578 + x^577 + x^574 + x^570 + x^566 + x^565 + x^561 + x^559 + x^558 + x^557 + x^556 + x^555 + x^552 + x^550 + x^548 + x^544 + x^542 + x^541 + x^540 + x^537 + x^536 + x^534 + x^533 + x^532 + x^531 + x^528 + x^527 + x^525 + x^524 + x^521 + x^519 + x^518 + x^517 + x^516 + x^515 + x^514 + x^513 + x^512 + x^511 + x^509 + x^507 + x^505 + x^504 + x^502 + x^501 + x^497 + x^496 + x^493 + x^492 + x^491 + x^490 + x^488 + x^486 + x^485 + x^480 + x^478 + x^476 + x^475 + x^473 + x^469 + x^468 + x^467 + x^466 + x^463 + x^462 + x^453 + x^452 + x^451 + x^449 + x^447 + x^446 + x^445 + x^444 + x^443 + x^440 + x^438 + x^437 + x^436 + x^435 + x^427 + x^426 + x^423 + x^421 + x^419 + x^416 + x^411 + x^410 + x^409 + x^408 + x^406 + x^405 + x^404 + x^403 + x^402 + x^400 + x^398 + x^397 + x^395 + x^391 + x^390 + x^389 + x^385 + x^384 + x^380 + x^378 + x^377 + x^374 + x^373 + x^372 + x^370 + x^367 + x^366 + x^365 + x^363 + x^361 + x^360 + x^354 + x^352 + x^351 + x^350 + x^347 + x^342 + x^339 + x^337 + x^334 + x^333 + x^330 + x^328 + x^326 + x^324 + x^323 + x^315 + x^314 + x^309 + x^306 + x^304 + x^302 + x^298 + x^297 + x^296 + x^295 + x^293 + x^291 + x^289 + x^284 + x^282 + x^281 + x^279 + x^275 + x^274 + x^273 + x^269 + x^267 + x^265 + x^263 + x^261 + x^260 + x^259 + x^257 + x^256 + x^254 + x^252 + x^248 + x^247 + x^246 + x^244 + x^243 + x^242 + x^241 + x^238 + x^235 + x^234 + x^232 + x^229 + x^227 + x^225 + x^224 + x^223 + x^219 + x^217 + x^215 + x^211 + x^208 + x^206 + x^205 + x^203 + x^200 + x^197 + x^195 + x^190 + x^189 + x^187 + x^185 + x^176 + x^174 + x^172 + x^169 + x^165 + x^160 + x^159 + x^158 + x^156 + x^155 + x^154 + x^153 + x^152 + x^150 + x^146 + x^141 + x^139 + x^137 + x^135 + x^132 + x^131 + x^130 + x^127 + x^124 + x^120 + x^119 + x^116 + x^114 + x^111 + x^110 + x^109 + x^108 + x^105 + x^102 + x^99 + x^98 + x^95 + x^94 + x^93 + x^92 + x^90 + x^87 + x^86 + x^76 + x^75 + x^74 + x^72 + x^70 + x^68 + x^67 + x^65 + x^64 + x^63 + x^60 + x^59 + x^58 + x^57 + x^54 + x^51 + x^50 + x^48 + x^46 + x^45 + x^44 + x^43 + x^41 + x^39 + x^38 + x^36 + x^30 + x^27 + x^26 + x^24 + x^18 + x^14 + x^12 + 1
+
+44-14-41 357 x^928 + x^898 + x^870 + x^856 + x^852 + x^847 + x^831 + x^822 + x^817 + x^814 + x^808 + x^796 + x^795 + x^792 + x^784 + x^778 + x^777 + x^775 + x^772 + x^771 + x^766 + x^763 + x^756 + x^754 + x^747 + x^746 + x^745 + x^744 + x^742 + x^736 + x^733 + x^732 + x^730 + x^727 + x^726 + x^724 + x^721 + x^717 + x^716 + x^715 + x^714 + x^711 + x^705 + x^704 + x^694 + x^693 + x^691 + x^684 + x^682 + x^678 + x^674 + x^670 + x^664 + x^662 + x^655 + x^653 + x^647 + x^645 + x^644 + x^643 + x^637 + x^636 + x^635 + x^633 + x^631 + x^627 + x^626 + x^625 + x^624 + x^620 + x^618 + x^605 + x^604 + x^603 + x^601 + x^597 + x^588 + x^585 + x^583 + x^578 + x^575 + x^574 + x^569 + x^568 + x^567 + x^566 + x^565 + x^563 + x^558 + x^556 + x^554 + x^553 + x^552 + x^551 + x^550 + x^548 + x^544 + x^543 + x^542 + x^539 + x^538 + x^537 + x^535 + x^533 + x^532 + x^530 + x^528 + x^525 + x^523 + x^521 + x^520 + x^516 + x^515 + x^514 + x^513 + x^510 + x^509 + x^506 + x^504 + x^502 + x^497 + x^496 + x^491 + x^487 + x^485 + x^484 + x^482 + x^481 + x^480 + x^473 + x^471 + x^470 + x^468 + x^466 + x^464 + x^463 + x^462 + x^461 + x^459 + x^458 + x^455 + x^452 + x^450 + x^449 + x^447 + x^446 + x^443 + x^442 + x^440 + x^438 + x^436 + x^435 + x^432 + x^429 + x^428 + x^423 + x^420 + x^418 + x^417 + x^416 + x^413 + x^412 + x^411 + x^410 + x^407 + x^406 + x^405 + x^403 + x^402 + x^401 + x^400 + x^397 + x^396 + x^393 + x^392 + x^391 + x^390 + x^389 + x^386 + x^385 + x^384 + x^382 + x^380 + x^378 + x^376 + x^371 + x^370 + x^369 + x^368 + x^365 + x^364 + x^363 + x^359 + x^358 + x^357 + x^356 + x^353 + x^351 + x^350 + x^349 + x^348 + x^346 + x^345 + x^343 + x^342 + x^340 + x^339 + x^338 + x^335 + x^333 + x^332 + x^327 + x^324 + x^322 + x^317 + x^316 + x^315 + x^313 + x^311 + x^308 + x^307 + x^306 + x^304 + x^303 + x^301 + x^300 + x^299 + x^296 + x^294 + x^293 + x^292 + x^291 + x^290 + x^289 + x^284 + x^281 + x^279 + x^278 + x^276 + x^275 + x^273 + x^272 + x^271 + x^269 + x^266 + x^264 + x^260 + x^258 + x^256 + x^255 + x^251 + x^250 + x^248 + x^247 + x^244 + x^243 + x^241 + x^240 + x^239 + x^236 + x^235 + x^233 + x^232 + x^230 + x^226 + x^224 + x^223 + x^221 + x^220 + x^218 + x^217 + x^216 + x^215 + x^211 + x^210 + x^209 + x^208 + x^206 + x^204 + x^201 + x^200 + x^197 + x^196 + x^192 + x^187 + x^185 + x^183 + x^182 + x^181 + x^179 + x^178 + x^177 + x^175 + x^173 + x^170 + x^169 + x^168 + x^166 + x^159 + x^158 + x^157 + x^155 + x^154 + x^150 + x^149 + x^146 + x^144 + x^139 + x^138 + x^134 + x^132 + x^131 + x^128 + x^125 + x^123 + x^122 + x^120 + x^119 + x^116 + x^115 + x^111 + x^110 + x^109 + x^108 + x^101 + x^100 + x^99 + x^97 + x^96 + x^93 + x^92 + x^90 + x^87 + x^77 + x^74 + x^71 + x^70 + x^63 + x^58 + x^56 + x^54 + x^53 + x^52 + x^51 + x^50 + x^46 + x^42 + x^40 + x^38 + x^37 + x^36 + x^30 + x^28 + x^26 + x^14 + x^12 + 1
+
+22-40-11 359 x^928 + x^898 + x^870 + x^829 + x^816 + x^814 + x^808 + x^803 + x^799 + x^786 + x^784 + x^778 + x^777 + x^773 + x^764 + x^762 + x^743 + x^738 + x^736 + x^734 + x^725 + x^723 + x^719 + x^713 + x^710 + x^708 + x^699 + x^691 + x^688 + x^686 + x^684 + x^682 + x^673 + x^672 + x^665 + x^661 + x^657 + x^656 + x^654 + x^652 + x^650 + x^648 + x^645 + x^644 + x^642 + x^639 + x^637 + x^633 + x^631 + x^630 + x^626 + x^624 + x^622 + x^621 + x^620 + x^619 + x^618 + x^615 + x^614 + x^612 + x^611 + x^609 + x^606 + x^605 + x^604 + x^603 + x^601 + x^600 + x^599 + x^598 + x^594 + x^591 + x^587 + x^586 + x^585 + x^582 + x^580 + x^578 + x^577 + x^576 + x^572 + x^562 + x^561 + x^559 + x^558 + x^557 + x^556 + x^554 + x^553 + x^552 + x^550 + x^549 + x^548 + x^545 + x^543 + x^541 + x^540 + x^537 + x^535 + x^534 + x^533 + x^531 + x^530 + x^528 + x^527 + x^526 + x^522 + x^521 + x^518 + x^517 + x^516 + x^515 + x^514 + x^512 + x^511 + x^510 + x^509 + x^508 + x^507 + x^501 + x^499 + x^494 + x^491 + x^490 + x^489 + x^488 + x^486 + x^484 + x^483 + x^481 + x^480 + x^479 + x^478 + x^476 + x^475 + x^474 + x^472 + x^471 + x^469 + x^468 + x^466 + x^465 + x^464 + x^463 + x^461 + x^459 + x^457 + x^450 + x^449 + x^448 + x^446 + x^445 + x^439 + x^438 + x^437 + x^436 + x^435 + x^433 + x^431 + x^430 + x^429 + x^427 + x^426 + x^423 + x^418 + x^417 + x^415 + x^413 + x^403 + x^402 + x^401 + x^399 + x^398 + x^397 + x^395 + x^394 + x^393 + x^386 + x^382 + x^379 + x^378 + x^377 + x^368 + x^367 + x^366 + x^364 + x^363 + x^362 + x^360 + x^359 + x^356 + x^354 + x^352 + x^344 + x^343 + x^342 + x^341 + x^340 + x^337 + x^336 + x^331 + x^330 + x^325 + x^323 + x^321 + x^320 + x^319 + x^318 + x^315 + x^313 + x^311 + x^310 + x^308 + x^306 + x^303 + x^302 + x^300 + x^298 + x^297 + x^296 + x^294 + x^293 + x^292 + x^291 + x^290 + x^288 + x^286 + x^285 + x^283 + x^278 + x^277 + x^275 + x^274 + x^273 + x^271 + x^269 + x^268 + x^267 + x^265 + x^261 + x^260 + x^259 + x^257 + x^256 + x^255 + x^254 + x^251 + x^249 + x^248 + x^245 + x^244 + x^242 + x^240 + x^238 + x^237 + x^236 + x^231 + x^229 + x^227 + x^225 + x^224 + x^223 + x^222 + x^221 + x^216 + x^215 + x^213 + x^211 + x^205 + x^202 + x^196 + x^194 + x^193 + x^192 + x^191 + x^190 + x^184 + x^180 + x^179 + x^178 + x^177 + x^176 + x^175 + x^174 + x^171 + x^169 + x^164 + x^162 + x^161 + x^160 + x^155 + x^153 + x^149 + x^143 + x^142 + x^139 + x^138 + x^135 + x^134 + x^133 + x^132 + x^130 + x^128 + x^127 + x^126 + x^124 + x^123 + x^120 + x^118 + x^117 + x^115 + x^114 + x^113 + x^112 + x^111 + x^109 + x^108 + x^107 + x^104 + x^103 + x^101 + x^98 + x^95 + x^93 + x^92 + x^89 + x^88 + x^86 + x^82 + x^80 + x^76 + x^75 + x^69 + x^67 + x^65 + x^64 + x^60 + x^58 + x^57 + x^55 + x^53 + x^50 + x^49 + x^47 + x^46 + x^45 + x^44 + x^43 + x^42 + x^39 + x^37 + x^36 + x^35 + x^34 + x^32 + x^24 + x^22 + x^20 + 1
+
+33-20-8 359 x^928 + x^898 + x^874 + x^870 + x^845 + x^840 + x^824 + x^808 + x^794 + x^790 + x^787 + x^786 + x^780 + x^778 + x^764 + x^762 + x^761 + x^760 + x^756 + x^752 + x^741 + x^737 + x^736 + x^734 + x^731 + x^729 + x^728 + x^726 + x^720 + x^716 + x^712 + x^710 + x^707 + x^706 + x^703 + x^700 + x^697 + x^696 + x^688 + x^686 + x^683 + x^682 + x^681 + x^675 + x^671 + x^669 + x^667 + x^666 + x^660 + x^658 + x^657 + x^654 + x^653 + x^652 + x^649 + x^647 + x^646 + x^640 + x^639 + x^637 + x^636 + x^634 + x^629 + x^628 + x^627 + x^625 + x^624 + x^618 + x^613 + x^609 + x^608 + x^607 + x^600 + x^598 + x^597 + x^596 + x^595 + x^594 + x^593 + x^592 + x^591 + x^589 + x^587 + x^586 + x^585 + x^583 + x^582 + x^581 + x^580 + x^579 + x^577 + x^570 + x^567 + x^562 + x^554 + x^553 + x^550 + x^549 + x^548 + x^547 + x^546 + x^545 + x^544 + x^542 + x^539 + x^537 + x^535 + x^533 + x^531 + x^530 + x^524 + x^523 + x^521 + x^520 + x^517 + x^516 + x^512 + x^511 + x^504 + x^503 + x^502 + x^501 + x^497 + x^494 + x^492 + x^490 + x^489 + x^486 + x^480 + x^478 + x^477 + x^476 + x^475 + x^472 + x^467 + x^465 + x^463 + x^462 + x^461 + x^460 + x^459 + x^458 + x^456 + x^452 + x^449 + x^447 + x^446 + x^442 + x^440 + x^439 + x^438 + x^437 + x^436 + x^435 + x^434 + x^433 + x^432 + x^431 + x^430 + x^429 + x^426 + x^425 + x^423 + x^422 + x^421 + x^420 + x^415 + x^414 + x^413 + x^412 + x^411 + x^410 + x^408 + x^404 + x^402 + x^400 + x^399 + x^398 + x^395 + x^394 + x^392 + x^390 + x^387 + x^386 + x^385 + x^383 + x^379 + x^377 + x^376 + x^374 + x^373 + x^372 + x^371 + x^368 + x^366 + x^365 + x^362 + x^361 + x^360 + x^359 + x^358 + x^350 + x^347 + x^342 + x^341 + x^338 + x^337 + x^335 + x^331 + x^330 + x^326 + x^325 + x^322 + x^321 + x^320 + x^319 + x^318 + x^317 + x^312 + x^311 + x^308 + x^307 + x^305 + x^303 + x^301 + x^298 + x^295 + x^292 + x^289 + x^286 + x^282 + x^280 + x^277 + x^273 + x^271 + x^270 + x^265 + x^263 + x^262 + x^261 + x^260 + x^257 + x^253 + x^252 + x^251 + x^249 + x^248 + x^247 + x^246 + x^245 + x^243 + x^240 + x^239 + x^236 + x^234 + x^230 + x^228 + x^226 + x^225 + x^224 + x^222 + x^220 + x^219 + x^218 + x^215 + x^214 + x^213 + x^210 + x^205 + x^203 + x^201 + x^195 + x^194 + x^192 + x^191 + x^187 + x^185 + x^184 + x^183 + x^181 + x^178 + x^176 + x^174 + x^173 + x^172 + x^171 + x^170 + x^168 + x^165 + x^164 + x^163 + x^160 + x^157 + x^155 + x^154 + x^153 + x^152 + x^151 + x^150 + x^149 + x^148 + x^139 + x^138 + x^135 + x^134 + x^132 + x^131 + x^129 + x^128 + x^127 + x^126 + x^125 + x^122 + x^121 + x^119 + x^118 + x^115 + x^114 + x^111 + x^110 + x^106 + x^103 + x^101 + x^99 + x^98 + x^95 + x^91 + x^90 + x^89 + x^83 + x^78 + x^77 + x^75 + x^74 + x^70 + x^65 + x^64 + x^61 + x^56 + x^55 + x^52 + x^51 + x^49 + x^46 + x^41 + x^38 + x^36 + x^35 + x^34 + x^32 + x^29 + x^28 + x^27 + x^23 + x^16 + x^12 + x^8 + x^4 + 1
+
+6-42-43 359 x^928 + x^898 + x^877 + x^870 + x^847 + x^846 + x^844 + x^822 + x^808 + x^799 + x^794 + x^793 + x^790 + x^786 + x^778 + x^775 + x^774 + x^772 + x^771 + x^769 + x^766 + x^764 + x^750 + x^749 + x^748 + x^747 + x^744 + x^743 + x^742 + x^739 + x^736 + x^724 + x^721 + x^718 + x^715 + x^712 + x^710 + x^706 + x^702 + x^699 + x^695 + x^693 + x^692 + x^689 + x^687 + x^685 + x^684 + x^683 + x^682 + x^679 + x^674 + x^671 + x^670 + x^668 + x^667 + x^664 + x^662 + x^653 + x^652 + x^650 + x^649 + x^645 + x^644 + x^642 + x^639 + x^638 + x^637 + x^634 + x^633 + x^630 + x^624 + x^622 + x^619 + x^618 + x^616 + x^614 + x^613 + x^611 + x^610 + x^609 + x^608 + x^603 + x^601 + x^598 + x^595 + x^592 + x^589 + x^587 + x^586 + x^585 + x^584 + x^583 + x^582 + x^578 + x^574 + x^572 + x^568 + x^567 + x^565 + x^562 + x^561 + x^559 + x^558 + x^557 + x^555 + x^554 + x^550 + x^549 + x^547 + x^545 + x^541 + x^534 + x^528 + x^527 + x^523 + x^520 + x^518 + x^515 + x^510 + x^503 + x^502 + x^501 + x^500 + x^499 + x^498 + x^497 + x^496 + x^495 + x^494 + x^492 + x^489 + x^486 + x^483 + x^482 + x^479 + x^476 + x^475 + x^473 + x^472 + x^468 + x^467 + x^465 + x^464 + x^463 + x^461 + x^459 + x^458 + x^455 + x^452 + x^451 + x^450 + x^449 + x^448 + x^446 + x^445 + x^444 + x^443 + x^441 + x^440 + x^437 + x^434 + x^431 + x^430 + x^429 + x^425 + x^423 + x^422 + x^421 + x^419 + x^418 + x^417 + x^411 + x^408 + x^406 + x^405 + x^403 + x^401 + x^398 + x^397 + x^396 + x^393 + x^390 + x^382 + x^378 + x^376 + x^373 + x^372 + x^370 + x^369 + x^366 + x^361 + x^359 + x^358 + x^356 + x^354 + x^352 + x^351 + x^350 + x^349 + x^348 + x^347 + x^344 + x^340 + x^339 + x^336 + x^335 + x^333 + x^332 + x^329 + x^325 + x^324 + x^322 + x^321 + x^317 + x^316 + x^311 + x^310 + x^309 + x^303 + x^302 + x^301 + x^299 + x^298 + x^295 + x^294 + x^290 + x^289 + x^288 + x^287 + x^283 + x^282 + x^280 + x^279 + x^278 + x^277 + x^272 + x^271 + x^270 + x^268 + x^263 + x^261 + x^260 + x^259 + x^257 + x^256 + x^254 + x^250 + x^248 + x^247 + x^245 + x^244 + x^243 + x^241 + x^239 + x^238 + x^237 + x^235 + x^231 + x^230 + x^229 + x^228 + x^226 + x^225 + x^224 + x^221 + x^219 + x^217 + x^214 + x^210 + x^209 + x^208 + x^205 + x^204 + x^202 + x^199 + x^196 + x^191 + x^190 + x^189 + x^186 + x^184 + x^183 + x^180 + x^179 + x^178 + x^177 + x^175 + x^174 + x^170 + x^168 + x^167 + x^166 + x^165 + x^164 + x^162 + x^161 + x^160 + x^159 + x^157 + x^154 + x^153 + x^151 + x^143 + x^137 + x^135 + x^134 + x^129 + x^127 + x^126 + x^122 + x^121 + x^119 + x^118 + x^113 + x^111 + x^106 + x^104 + x^101 + x^100 + x^99 + x^98 + x^96 + x^92 + x^91 + x^90 + x^83 + x^82 + x^81 + x^79 + x^75 + x^74 + x^72 + x^71 + x^68 + x^64 + x^63 + x^60 + x^57 + x^56 + x^54 + x^52 + x^51 + x^49 + x^48 + x^46 + x^45 + x^43 + x^42 + x^39 + x^38 + x^37 + x^36 + x^32 + x^28 + x^26 + x^24 + x^16 + x^14 + 1
+
+33-22-4 361 x^928 + x^898 + x^870 + x^832 + x^822 + x^812 + x^808 + x^805 + x^802 + x^792 + x^784 + x^778 + x^775 + x^774 + x^762 + x^757 + x^756 + x^754 + x^746 + x^744 + x^740 + x^738 + x^736 + x^732 + x^728 + x^726 + x^720 + x^716 + x^711 + x^701 + x^697 + x^692 + x^684 + x^682 + x^680 + x^678 + x^673 + x^672 + x^671 + x^670 + x^658 + x^655 + x^653 + x^652 + x^651 + x^644 + x^637 + x^636 + x^630 + x^626 + x^622 + x^615 + x^613 + x^612 + x^611 + x^610 + x^608 + x^607 + x^606 + x^600 + x^599 + x^594 + x^593 + x^592 + x^590 + x^589 + x^588 + x^587 + x^586 + x^585 + x^583 + x^580 + x^578 + x^577 + x^574 + x^569 + x^567 + x^564 + x^562 + x^561 + x^559 + x^554 + x^553 + x^552 + x^549 + x^548 + x^544 + x^543 + x^538 + x^537 + x^536 + x^535 + x^533 + x^530 + x^525 + x^524 + x^523 + x^522 + x^521 + x^519 + x^517 + x^516 + x^515 + x^514 + x^511 + x^507 + x^506 + x^500 + x^499 + x^498 + x^496 + x^494 + x^487 + x^486 + x^485 + x^483 + x^480 + x^473 + x^468 + x^466 + x^465 + x^464 + x^463 + x^461 + x^460 + x^454 + x^452 + x^448 + x^447 + x^445 + x^441 + x^440 + x^439 + x^438 + x^436 + x^435 + x^434 + x^433 + x^429 + x^427 + x^425 + x^423 + x^421 + x^420 + x^418 + x^416 + x^415 + x^413 + x^411 + x^410 + x^409 + x^408 + x^404 + x^402 + x^401 + x^399 + x^397 + x^396 + x^393 + x^391 + x^390 + x^388 + x^387 + x^386 + x^383 + x^381 + x^380 + x^379 + x^376 + x^375 + x^374 + x^371 + x^370 + x^369 + x^368 + x^366 + x^364 + x^363 + x^361 + x^359 + x^356 + x^355 + x^354 + x^353 + x^350 + x^349 + x^344 + x^341 + x^338 + x^337 + x^336 + x^335 + x^332 + x^330 + x^329 + x^328 + x^327 + x^323 + x^322 + x^319 + x^318 + x^315 + x^314 + x^313 + x^309 + x^308 + x^307 + x^306 + x^304 + x^303 + x^301 + x^300 + x^298 + x^296 + x^295 + x^294 + x^292 + x^290 + x^289 + x^288 + x^286 + x^284 + x^282 + x^280 + x^279 + x^278 + x^275 + x^273 + x^271 + x^268 + x^266 + x^262 + x^261 + x^259 + x^258 + x^256 + x^255 + x^254 + x^253 + x^250 + x^245 + x^241 + x^240 + x^239 + x^237 + x^235 + x^234 + x^232 + x^231 + x^229 + x^226 + x^225 + x^221 + x^220 + x^218 + x^217 + x^215 + x^213 + x^211 + x^209 + x^206 + x^205 + x^201 + x^200 + x^196 + x^195 + x^192 + x^189 + x^188 + x^187 + x^186 + x^184 + x^183 + x^181 + x^180 + x^178 + x^177 + x^176 + x^175 + x^174 + x^172 + x^171 + x^169 + x^166 + x^165 + x^162 + x^160 + x^157 + x^154 + x^152 + x^150 + x^149 + x^145 + x^141 + x^138 + x^137 + x^133 + x^131 + x^129 + x^127 + x^125 + x^124 + x^123 + x^120 + x^118 + x^117 + x^115 + x^114 + x^112 + x^109 + x^108 + x^105 + x^102 + x^100 + x^99 + x^97 + x^96 + x^91 + x^90 + x^88 + x^87 + x^86 + x^85 + x^82 + x^80 + x^79 + x^77 + x^75 + x^74 + x^70 + x^66 + x^65 + x^63 + x^62 + x^61 + x^60 + x^59 + x^54 + x^52 + x^50 + x^49 + x^46 + x^42 + x^41 + x^40 + x^39 + x^38 + x^37 + x^36 + x^35 + x^33 + x^31 + x^27 + x^26 + x^22 + x^21 + x^19 + x^16 + x^14 + x^12 + 1
+
+46-48-7 361 x^928 + x^898 + x^870 + x^862 + x^848 + x^837 + x^829 + x^820 + x^815 + x^808 + x^807 + x^806 + x^802 + x^799 + x^798 + x^795 + x^790 + x^788 + x^787 + x^785 + x^776 + x^769 + x^765 + x^762 + x^760 + x^756 + x^755 + x^740 + x^739 + x^737 + x^732 + x^730 + x^727 + x^725 + x^717 + x^715 + x^714 + x^710 + x^709 + x^706 + x^704 + x^695 + x^688 + x^687 + x^686 + x^684 + x^682 + x^680 + x^679 + x^678 + x^676 + x^675 + x^667 + x^664 + x^661 + x^658 + x^657 + x^655 + x^654 + x^653 + x^652 + x^650 + x^649 + x^647 + x^646 + x^644 + x^643 + x^638 + x^637 + x^636 + x^634 + x^633 + x^627 + x^624 + x^623 + x^622 + x^620 + x^619 + x^618 + x^615 + x^612 + x^611 + x^606 + x^604 + x^601 + x^594 + x^591 + x^590 + x^589 + x^588 + x^587 + x^585 + x^583 + x^580 + x^575 + x^574 + x^572 + x^571 + x^569 + x^568 + x^567 + x^564 + x^563 + x^558 + x^557 + x^556 + x^552 + x^551 + x^546 + x^544 + x^542 + x^541 + x^535 + x^534 + x^532 + x^531 + x^530 + x^529 + x^528 + x^526 + x^525 + x^523 + x^521 + x^519 + x^518 + x^516 + x^514 + x^513 + x^506 + x^505 + x^504 + x^499 + x^498 + x^497 + x^496 + x^495 + x^493 + x^491 + x^490 + x^488 + x^487 + x^486 + x^485 + x^484 + x^481 + x^480 + x^477 + x^476 + x^473 + x^472 + x^471 + x^466 + x^465 + x^463 + x^462 + x^461 + x^460 + x^459 + x^455 + x^451 + x^449 + x^448 + x^447 + x^446 + x^444 + x^443 + x^441 + x^440 + x^439 + x^437 + x^431 + x^429 + x^428 + x^426 + x^424 + x^421 + x^420 + x^419 + x^418 + x^417 + x^416 + x^414 + x^411 + x^410 + x^408 + x^407 + x^406 + x^405 + x^403 + x^402 + x^401 + x^400 + x^397 + x^394 + x^392 + x^390 + x^388 + x^382 + x^381 + x^379 + x^378 + x^377 + x^376 + x^374 + x^367 + x^364 + x^363 + x^360 + x^357 + x^356 + x^354 + x^353 + x^352 + x^351 + x^350 + x^348 + x^343 + x^342 + x^341 + x^337 + x^334 + x^333 + x^330 + x^326 + x^316 + x^313 + x^309 + x^306 + x^305 + x^300 + x^299 + x^296 + x^294 + x^293 + x^292 + x^287 + x^285 + x^282 + x^281 + x^278 + x^276 + x^275 + x^271 + x^269 + x^267 + x^263 + x^262 + x^261 + x^260 + x^257 + x^256 + x^255 + x^253 + x^249 + x^248 + x^244 + x^243 + x^242 + x^240 + x^239 + x^238 + x^236 + x^235 + x^234 + x^231 + x^226 + x^224 + x^221 + x^217 + x^216 + x^214 + x^211 + x^210 + x^209 + x^208 + x^206 + x^205 + x^202 + x^200 + x^197 + x^196 + x^195 + x^190 + x^186 + x^184 + x^183 + x^181 + x^176 + x^172 + x^171 + x^167 + x^166 + x^165 + x^164 + x^159 + x^157 + x^154 + x^153 + x^151 + x^150 + x^146 + x^145 + x^144 + x^142 + x^141 + x^140 + x^139 + x^137 + x^136 + x^134 + x^131 + x^130 + x^129 + x^125 + x^124 + x^123 + x^120 + x^118 + x^117 + x^111 + x^110 + x^108 + x^107 + x^106 + x^105 + x^98 + x^96 + x^95 + x^94 + x^92 + x^88 + x^83 + x^81 + x^78 + x^76 + x^72 + x^71 + x^67 + x^66 + x^65 + x^63 + x^60 + x^58 + x^57 + x^56 + x^52 + x^51 + x^49 + x^48 + x^46 + x^44 + x^40 + x^38 + x^34 + x^33 + x^32 + x^31 + x^30 + x^28 + x^20 + 1
+
+49-44-52 361 x^928 + x^898 + x^870 + x^864 + x^842 + x^837 + x^834 + x^812 + x^810 + x^808 + x^804 + x^788 + x^786 + x^783 + x^782 + x^780 + x^778 + x^774 + x^758 + x^756 + x^753 + x^752 + x^734 + x^732 + x^729 + x^727 + x^724 + x^723 + x^722 + x^717 + x^704 + x^702 + x^699 + x^696 + x^693 + x^692 + x^690 + x^680 + x^678 + x^672 + x^667 + x^665 + x^663 + x^662 + x^661 + x^660 + x^650 + x^646 + x^637 + x^636 + x^633 + x^631 + x^626 + x^621 + x^618 + x^616 + x^614 + x^612 + x^611 + x^610 + x^609 + x^605 + x^603 + x^602 + x^601 + x^599 + x^597 + x^596 + x^594 + x^589 + x^588 + x^586 + x^576 + x^575 + x^573 + x^572 + x^571 + x^569 + x^568 + x^565 + x^562 + x^561 + x^560 + x^558 + x^557 + x^555 + x^554 + x^551 + x^549 + x^548 + x^543 + x^542 + x^539 + x^536 + x^532 + x^529 + x^528 + x^527 + x^526 + x^525 + x^518 + x^517 + x^514 + x^513 + x^512 + x^511 + x^509 + x^508 + x^506 + x^505 + x^499 + x^496 + x^495 + x^493 + x^492 + x^491 + x^489 + x^486 + x^483 + x^482 + x^479 + x^477 + x^476 + x^474 + x^468 + x^467 + x^462 + x^461 + x^457 + x^456 + x^454 + x^453 + x^452 + x^451 + x^449 + x^444 + x^442 + x^441 + x^439 + x^438 + x^437 + x^436 + x^432 + x^431 + x^429 + x^428 + x^427 + x^425 + x^424 + x^423 + x^422 + x^420 + x^419 + x^418 + x^416 + x^414 + x^413 + x^409 + x^407 + x^406 + x^404 + x^403 + x^402 + x^401 + x^395 + x^394 + x^393 + x^392 + x^390 + x^389 + x^387 + x^386 + x^384 + x^380 + x^378 + x^377 + x^376 + x^372 + x^371 + x^370 + x^369 + x^365 + x^363 + x^362 + x^361 + x^358 + x^357 + x^356 + x^355 + x^352 + x^351 + x^350 + x^347 + x^346 + x^344 + x^343 + x^342 + x^340 + x^339 + x^338 + x^332 + x^331 + x^328 + x^326 + x^325 + x^323 + x^322 + x^321 + x^319 + x^317 + x^316 + x^314 + x^313 + x^309 + x^305 + x^303 + x^301 + x^300 + x^299 + x^298 + x^297 + x^294 + x^292 + x^290 + x^285 + x^284 + x^282 + x^280 + x^279 + x^278 + x^276 + x^272 + x^267 + x^266 + x^265 + x^264 + x^263 + x^262 + x^259 + x^256 + x^254 + x^253 + x^251 + x^250 + x^249 + x^248 + x^247 + x^245 + x^243 + x^241 + x^240 + x^238 + x^234 + x^231 + x^229 + x^228 + x^227 + x^224 + x^222 + x^221 + x^215 + x^214 + x^211 + x^210 + x^209 + x^207 + x^206 + x^205 + x^204 + x^197 + x^196 + x^194 + x^192 + x^191 + x^189 + x^188 + x^187 + x^186 + x^182 + x^180 + x^178 + x^175 + x^172 + x^168 + x^167 + x^166 + x^163 + x^162 + x^158 + x^154 + x^153 + x^150 + x^148 + x^146 + x^145 + x^144 + x^138 + x^136 + x^132 + x^131 + x^130 + x^129 + x^124 + x^122 + x^120 + x^116 + x^115 + x^113 + x^112 + x^109 + x^108 + x^107 + x^106 + x^103 + x^102 + x^101 + x^99 + x^98 + x^97 + x^96 + x^94 + x^92 + x^90 + x^86 + x^85 + x^84 + x^83 + x^82 + x^80 + x^79 + x^77 + x^76 + x^65 + x^60 + x^59 + x^57 + x^54 + x^52 + x^47 + x^45 + x^44 + x^42 + x^38 + x^37 + x^34 + x^33 + x^31 + x^29 + x^26 + x^25 + x^24 + x^22 + x^21 + x^19 + x^18 + x^17 + x^15 + x^14 + x^12 + x^10 + 1
+
+34-42-39 365 x^928 + x^898 + x^870 + x^860 + x^850 + x^840 + x^831 + x^830 + x^811 + x^808 + x^801 + x^800 + x^792 + x^790 + x^780 + x^778 + x^771 + x^770 + x^762 + x^753 + x^744 + x^742 + x^740 + x^734 + x^720 + x^715 + x^712 + x^710 + x^703 + x^702 + x^694 + x^693 + x^691 + x^688 + x^685 + x^682 + x^680 + x^676 + x^674 + x^672 + x^664 + x^663 + x^662 + x^660 + x^658 + x^657 + x^656 + x^653 + x^652 + x^650 + x^647 + x^646 + x^645 + x^643 + x^637 + x^634 + x^628 + x^627 + x^623 + x^622 + x^618 + x^617 + x^615 + x^614 + x^608 + x^607 + x^604 + x^603 + x^600 + x^597 + x^593 + x^592 + x^589 + x^588 + x^587 + x^586 + x^585 + x^584 + x^579 + x^578 + x^577 + x^574 + x^570 + x^567 + x^565 + x^563 + x^562 + x^560 + x^558 + x^555 + x^550 + x^549 + x^547 + x^544 + x^542 + x^541 + x^536 + x^533 + x^532 + x^529 + x^527 + x^526 + x^521 + x^520 + x^518 + x^517 + x^516 + x^514 + x^510 + x^509 + x^508 + x^506 + x^504 + x^503 + x^502 + x^501 + x^497 + x^496 + x^489 + x^488 + x^487 + x^486 + x^484 + x^481 + x^480 + x^476 + x^475 + x^473 + x^472 + x^471 + x^470 + x^467 + x^466 + x^463 + x^462 + x^459 + x^458 + x^457 + x^456 + x^453 + x^451 + x^450 + x^446 + x^445 + x^444 + x^443 + x^442 + x^439 + x^438 + x^437 + x^436 + x^433 + x^432 + x^430 + x^428 + x^427 + x^425 + x^421 + x^420 + x^413 + x^412 + x^411 + x^408 + x^406 + x^405 + x^404 + x^403 + x^401 + x^399 + x^398 + x^396 + x^391 + x^388 + x^385 + x^381 + x^378 + x^376 + x^375 + x^374 + x^372 + x^370 + x^368 + x^364 + x^363 + x^360 + x^359 + x^357 + x^354 + x^353 + x^350 + x^349 + x^348 + x^347 + x^346 + x^344 + x^343 + x^342 + x^340 + x^339 + x^337 + x^335 + x^334 + x^333 + x^331 + x^330 + x^329 + x^327 + x^326 + x^325 + x^324 + x^323 + x^321 + x^320 + x^317 + x^312 + x^310 + x^309 + x^303 + x^300 + x^298 + x^296 + x^295 + x^292 + x^291 + x^290 + x^288 + x^287 + x^286 + x^285 + x^284 + x^282 + x^278 + x^277 + x^275 + x^274 + x^273 + x^267 + x^266 + x^265 + x^264 + x^263 + x^262 + x^261 + x^260 + x^257 + x^254 + x^250 + x^249 + x^244 + x^243 + x^242 + x^239 + x^238 + x^237 + x^236 + x^231 + x^230 + x^229 + x^228 + x^226 + x^224 + x^223 + x^222 + x^221 + x^220 + x^217 + x^214 + x^213 + x^212 + x^211 + x^208 + x^207 + x^206 + x^205 + x^204 + x^202 + x^198 + x^197 + x^195 + x^194 + x^192 + x^189 + x^187 + x^186 + x^185 + x^181 + x^180 + x^179 + x^178 + x^175 + x^173 + x^170 + x^168 + x^167 + x^166 + x^165 + x^164 + x^157 + x^155 + x^154 + x^150 + x^149 + x^148 + x^144 + x^143 + x^140 + x^138 + x^137 + x^135 + x^134 + x^132 + x^126 + x^124 + x^123 + x^120 + x^119 + x^117 + x^115 + x^113 + x^105 + x^104 + x^102 + x^100 + x^97 + x^96 + x^94 + x^91 + x^88 + x^87 + x^85 + x^84 + x^83 + x^82 + x^80 + x^79 + x^77 + x^76 + x^69 + x^68 + x^64 + x^61 + x^60 + x^55 + x^53 + x^51 + x^50 + x^48 + x^45 + x^44 + x^43 + x^40 + x^39 + x^38 + x^37 + x^36 + x^34 + x^33 + x^30 + x^22 + x^20 + x^19 + x^18 + x^16 + x^14 + 1
+
+34-2-25 367 x^928 + x^898 + x^870 + x^868 + x^866 + x^850 + x^838 + x^832 + x^822 + x^820 + x^808 + x^804 + x^802 + x^797 + x^792 + x^790 + x^788 + x^786 + x^778 + x^770 + x^768 + x^767 + x^760 + x^754 + x^748 + x^747 + x^746 + x^744 + x^738 + x^736 + x^735 + x^728 + x^726 + x^720 + x^717 + x^712 + x^708 + x^696 + x^694 + x^692 + x^690 + x^688 + x^687 + x^685 + x^684 + x^678 + x^677 + x^675 + x^673 + x^669 + x^667 + x^662 + x^658 + x^657 + x^654 + x^652 + x^647 + x^643 + x^642 + x^640 + x^639 + x^638 + x^637 + x^634 + x^633 + x^624 + x^613 + x^612 + x^611 + x^610 + x^609 + x^607 + x^606 + x^603 + x^600 + x^598 + x^597 + x^593 + x^591 + x^590 + x^588 + x^587 + x^586 + x^584 + x^583 + x^582 + x^581 + x^577 + x^576 + x^574 + x^571 + x^570 + x^568 + x^567 + x^564 + x^563 + x^562 + x^560 + x^558 + x^557 + x^554 + x^553 + x^551 + x^549 + x^548 + x^547 + x^546 + x^545 + x^539 + x^538 + x^535 + x^533 + x^531 + x^530 + x^529 + x^527 + x^525 + x^524 + x^523 + x^522 + x^520 + x^517 + x^515 + x^514 + x^511 + x^510 + x^507 + x^506 + x^504 + x^503 + x^500 + x^499 + x^498 + x^496 + x^493 + x^491 + x^490 + x^489 + x^487 + x^485 + x^483 + x^482 + x^480 + x^478 + x^477 + x^474 + x^473 + x^471 + x^469 + x^468 + x^465 + x^464 + x^460 + x^459 + x^457 + x^455 + x^451 + x^450 + x^449 + x^447 + x^446 + x^442 + x^441 + x^438 + x^430 + x^428 + x^427 + x^426 + x^425 + x^421 + x^420 + x^417 + x^416 + x^415 + x^414 + x^411 + x^410 + x^409 + x^406 + x^405 + x^404 + x^402 + x^396 + x^394 + x^393 + x^390 + x^389 + x^388 + x^386 + x^384 + x^382 + x^381 + x^380 + x^379 + x^378 + x^377 + x^376 + x^374 + x^373 + x^372 + x^371 + x^369 + x^366 + x^365 + x^364 + x^363 + x^356 + x^354 + x^352 + x^351 + x^344 + x^342 + x^338 + x^336 + x^335 + x^334 + x^327 + x^323 + x^321 + x^319 + x^318 + x^317 + x^312 + x^308 + x^305 + x^303 + x^302 + x^301 + x^299 + x^298 + x^297 + x^289 + x^286 + x^285 + x^283 + x^277 + x^276 + x^275 + x^272 + x^271 + x^269 + x^268 + x^267 + x^266 + x^263 + x^258 + x^255 + x^254 + x^252 + x^251 + x^247 + x^246 + x^235 + x^233 + x^232 + x^229 + x^226 + x^225 + x^223 + x^220 + x^219 + x^216 + x^212 + x^210 + x^209 + x^208 + x^206 + x^205 + x^204 + x^202 + x^201 + x^200 + x^198 + x^196 + x^193 + x^190 + x^187 + x^185 + x^184 + x^182 + x^180 + x^179 + x^174 + x^173 + x^172 + x^171 + x^169 + x^167 + x^166 + x^165 + x^164 + x^159 + x^158 + x^156 + x^155 + x^154 + x^151 + x^150 + x^149 + x^148 + x^147 + x^146 + x^144 + x^143 + x^141 + x^137 + x^133 + x^132 + x^131 + x^130 + x^129 + x^126 + x^124 + x^123 + x^122 + x^118 + x^112 + x^111 + x^109 + x^108 + x^107 + x^105 + x^104 + x^103 + x^102 + x^99 + x^96 + x^93 + x^92 + x^91 + x^89 + x^86 + x^84 + x^83 + x^82 + x^81 + x^79 + x^77 + x^76 + x^75 + x^71 + x^70 + x^67 + x^65 + x^63 + x^53 + x^49 + x^44 + x^40 + x^38 + x^37 + x^36 + x^35 + x^34 + x^32 + x^31 + x^28 + x^26 + x^25 + x^24 + x^22 + x^18 + x^16 + x^10 + x^8 + x^4 + 1
+
+34-39-1 367 x^928 + x^898 + x^894 + x^874 + x^870 + x^864 + x^855 + x^844 + x^840 + x^835 + x^834 + x^825 + x^820 + x^815 + x^814 + x^808 + x^805 + x^804 + x^801 + x^800 + x^796 + x^790 + x^785 + x^784 + x^778 + x^776 + x^770 + x^766 + x^761 + x^760 + x^756 + x^754 + x^751 + x^750 + x^746 + x^741 + x^740 + x^735 + x^732 + x^731 + x^730 + x^727 + x^724 + x^722 + x^721 + x^720 + x^716 + x^715 + x^712 + x^706 + x^705 + x^700 + x^697 + x^694 + x^692 + x^688 + x^686 + x^685 + x^682 + x^677 + x^676 + x^672 + x^667 + x^664 + x^657 + x^655 + x^653 + x^651 + x^650 + x^648 + x^642 + x^638 + x^632 + x^631 + x^630 + x^628 + x^627 + x^625 + x^622 + x^620 + x^618 + x^617 + x^616 + x^612 + x^611 + x^602 + x^600 + x^598 + x^597 + x^591 + x^588 + x^586 + x^582 + x^581 + x^579 + x^578 + x^577 + x^574 + x^573 + x^572 + x^568 + x^566 + x^564 + x^560 + x^552 + x^541 + x^538 + x^537 + x^535 + x^534 + x^532 + x^531 + x^529 + x^528 + x^523 + x^522 + x^521 + x^519 + x^518 + x^516 + x^515 + x^510 + x^509 + x^508 + x^506 + x^504 + x^500 + x^499 + x^498 + x^497 + x^495 + x^492 + x^490 + x^489 + x^488 + x^484 + x^482 + x^477 + x^475 + x^474 + x^472 + x^471 + x^470 + x^469 + x^467 + x^466 + x^465 + x^464 + x^462 + x^461 + x^460 + x^457 + x^455 + x^454 + x^453 + x^448 + x^447 + x^446 + x^444 + x^443 + x^442 + x^441 + x^440 + x^437 + x^431 + x^430 + x^429 + x^426 + x^424 + x^423 + x^421 + x^419 + x^418 + x^417 + x^416 + x^412 + x^411 + x^409 + x^408 + x^407 + x^406 + x^405 + x^403 + x^402 + x^397 + x^395 + x^394 + x^389 + x^388 + x^384 + x^383 + x^382 + x^380 + x^379 + x^377 + x^376 + x^375 + x^374 + x^373 + x^372 + x^370 + x^369 + x^368 + x^367 + x^366 + x^361 + x^360 + x^359 + x^357 + x^355 + x^353 + x^350 + x^349 + x^344 + x^342 + x^341 + x^340 + x^338 + x^337 + x^336 + x^335 + x^334 + x^333 + x^332 + x^331 + x^329 + x^328 + x^326 + x^321 + x^320 + x^318 + x^317 + x^316 + x^313 + x^311 + x^310 + x^309 + x^306 + x^303 + x^302 + x^300 + x^299 + x^296 + x^295 + x^294 + x^293 + x^292 + x^291 + x^288 + x^287 + x^286 + x^284 + x^279 + x^276 + x^274 + x^270 + x^269 + x^268 + x^265 + x^264 + x^262 + x^259 + x^257 + x^256 + x^255 + x^251 + x^248 + x^247 + x^245 + x^244 + x^243 + x^240 + x^237 + x^234 + x^232 + x^230 + x^227 + x^224 + x^223 + x^219 + x^214 + x^212 + x^206 + x^204 + x^201 + x^198 + x^197 + x^194 + x^192 + x^190 + x^189 + x^186 + x^185 + x^182 + x^179 + x^178 + x^174 + x^172 + x^171 + x^168 + x^166 + x^163 + x^162 + x^161 + x^159 + x^158 + x^154 + x^153 + x^152 + x^151 + x^149 + x^148 + x^146 + x^143 + x^142 + x^140 + x^138 + x^137 + x^135 + x^134 + x^133 + x^132 + x^131 + x^128 + x^126 + x^125 + x^124 + x^123 + x^119 + x^118 + x^116 + x^115 + x^109 + x^108 + x^106 + x^105 + x^103 + x^100 + x^98 + x^91 + x^89 + x^86 + x^84 + x^83 + x^81 + x^79 + x^78 + x^70 + x^69 + x^67 + x^66 + x^65 + x^59 + x^58 + x^56 + x^48 + x^45 + x^43 + x^42 + x^38 + x^37 + x^34 + x^29 + x^26 + x^21 + x^10 + 1
+
+8-38-53 367 x^928 + x^898 + x^870 + x^843 + x^838 + x^833 + x^830 + x^820 + x^816 + x^811 + x^808 + x^800 + x^786 + x^781 + x^778 + x^773 + x^768 + x^760 + x^756 + x^752 + x^750 + x^743 + x^742 + x^738 + x^733 + x^732 + x^730 + x^728 + x^726 + x^723 + x^720 + x^718 + x^711 + x^710 + x^708 + x^700 + x^699 + x^698 + x^696 + x^695 + x^693 + x^691 + x^690 + x^688 + x^686 + x^685 + x^683 + x^681 + x^672 + x^670 + x^667 + x^666 + x^665 + x^664 + x^663 + x^662 + x^661 + x^658 + x^657 + x^655 + x^654 + x^650 + x^648 + x^646 + x^645 + x^644 + x^642 + x^640 + x^639 + x^638 + x^636 + x^634 + x^626 + x^622 + x^620 + x^617 + x^615 + x^614 + x^613 + x^612 + x^606 + x^605 + x^603 + x^600 + x^597 + x^596 + x^592 + x^591 + x^590 + x^589 + x^588 + x^585 + x^584 + x^581 + x^578 + x^577 + x^576 + x^575 + x^574 + x^572 + x^569 + x^568 + x^564 + x^562 + x^561 + x^556 + x^554 + x^551 + x^549 + x^544 + x^543 + x^542 + x^540 + x^539 + x^538 + x^533 + x^532 + x^530 + x^529 + x^527 + x^526 + x^524 + x^521 + x^520 + x^517 + x^515 + x^514 + x^510 + x^507 + x^504 + x^503 + x^502 + x^501 + x^500 + x^499 + x^498 + x^497 + x^495 + x^493 + x^489 + x^487 + x^486 + x^483 + x^482 + x^480 + x^477 + x^474 + x^471 + x^469 + x^468 + x^463 + x^461 + x^459 + x^456 + x^453 + x^450 + x^447 + x^443 + x^442 + x^441 + x^439 + x^438 + x^437 + x^436 + x^435 + x^431 + x^424 + x^422 + x^415 + x^411 + x^410 + x^409 + x^407 + x^406 + x^405 + x^404 + x^401 + x^400 + x^396 + x^395 + x^392 + x^391 + x^389 + x^388 + x^385 + x^382 + x^381 + x^380 + x^379 + x^377 + x^374 + x^369 + x^368 + x^367 + x^366 + x^365 + x^364 + x^359 + x^357 + x^353 + x^351 + x^349 + x^345 + x^344 + x^342 + x^341 + x^340 + x^339 + x^337 + x^335 + x^334 + x^333 + x^331 + x^330 + x^329 + x^327 + x^326 + x^324 + x^323 + x^322 + x^320 + x^319 + x^318 + x^314 + x^313 + x^312 + x^311 + x^309 + x^307 + x^304 + x^303 + x^300 + x^298 + x^294 + x^288 + x^285 + x^284 + x^281 + x^280 + x^279 + x^277 + x^276 + x^275 + x^273 + x^271 + x^270 + x^269 + x^268 + x^266 + x^261 + x^254 + x^253 + x^251 + x^250 + x^249 + x^248 + x^247 + x^245 + x^244 + x^242 + x^240 + x^238 + x^236 + x^233 + x^231 + x^230 + x^227 + x^226 + x^224 + x^223 + x^222 + x^221 + x^220 + x^219 + x^218 + x^216 + x^215 + x^213 + x^212 + x^209 + x^208 + x^207 + x^202 + x^198 + x^195 + x^189 + x^186 + x^183 + x^182 + x^180 + x^179 + x^177 + x^175 + x^172 + x^170 + x^168 + x^167 + x^159 + x^158 + x^154 + x^153 + x^150 + x^149 + x^144 + x^141 + x^140 + x^138 + x^136 + x^135 + x^134 + x^133 + x^132 + x^130 + x^129 + x^126 + x^125 + x^124 + x^123 + x^122 + x^121 + x^117 + x^116 + x^114 + x^113 + x^112 + x^111 + x^110 + x^108 + x^106 + x^105 + x^102 + x^98 + x^97 + x^96 + x^95 + x^92 + x^91 + x^90 + x^87 + x^79 + x^77 + x^74 + x^73 + x^72 + x^69 + x^64 + x^61 + x^60 + x^59 + x^58 + x^57 + x^56 + x^55 + x^53 + x^50 + x^49 + x^47 + x^46 + x^44 + x^43 + x^36 + x^35 + x^30 + x^29 + x^22 + x^16 + 1
+
+40-6-51 369 x^928 + x^898 + x^870 + x^859 + x^840 + x^830 + x^819 + x^790 + x^780 + x^779 + x^771 + x^770 + x^768 + x^761 + x^760 + x^757 + x^752 + x^750 + x^748 + x^742 + x^741 + x^740 + x^739 + x^738 + x^732 + x^728 + x^727 + x^721 + x^719 + x^718 + x^717 + x^712 + x^709 + x^708 + x^702 + x^699 + x^692 + x^690 + x^687 + x^684 + x^678 + x^677 + x^673 + x^672 + x^671 + x^668 + x^666 + x^659 + x^658 + x^657 + x^655 + x^654 + x^653 + x^652 + x^651 + x^648 + x^647 + x^645 + x^644 + x^643 + x^637 + x^636 + x^634 + x^632 + x^631 + x^624 + x^622 + x^621 + x^620 + x^616 + x^614 + x^613 + x^612 + x^611 + x^609 + x^608 + x^607 + x^598 + x^596 + x^594 + x^593 + x^592 + x^591 + x^588 + x^585 + x^583 + x^579 + x^578 + x^576 + x^575 + x^574 + x^573 + x^572 + x^571 + x^570 + x^567 + x^566 + x^563 + x^562 + x^560 + x^557 + x^555 + x^554 + x^549 + x^547 + x^546 + x^544 + x^542 + x^538 + x^537 + x^535 + x^534 + x^533 + x^531 + x^529 + x^527 + x^526 + x^522 + x^520 + x^518 + x^517 + x^515 + x^514 + x^513 + x^511 + x^510 + x^509 + x^508 + x^505 + x^504 + x^500 + x^497 + x^496 + x^494 + x^492 + x^481 + x^477 + x^475 + x^473 + x^471 + x^470 + x^468 + x^467 + x^466 + x^465 + x^464 + x^463 + x^462 + x^460 + x^457 + x^456 + x^453 + x^451 + x^450 + x^449 + x^447 + x^446 + x^444 + x^443 + x^441 + x^436 + x^435 + x^434 + x^429 + x^428 + x^427 + x^423 + x^422 + x^421 + x^419 + x^418 + x^416 + x^414 + x^413 + x^412 + x^410 + x^408 + x^406 + x^405 + x^402 + x^401 + x^400 + x^399 + x^398 + x^396 + x^395 + x^394 + x^393 + x^391 + x^390 + x^388 + x^385 + x^384 + x^382 + x^381 + x^379 + x^378 + x^377 + x^376 + x^375 + x^374 + x^373 + x^372 + x^371 + x^370 + x^367 + x^366 + x^365 + x^363 + x^360 + x^358 + x^355 + x^354 + x^353 + x^352 + x^350 + x^347 + x^344 + x^342 + x^340 + x^339 + x^338 + x^335 + x^334 + x^331 + x^330 + x^328 + x^324 + x^323 + x^322 + x^321 + x^318 + x^316 + x^315 + x^313 + x^307 + x^306 + x^304 + x^303 + x^301 + x^300 + x^299 + x^298 + x^297 + x^290 + x^287 + x^285 + x^283 + x^282 + x^281 + x^280 + x^279 + x^278 + x^276 + x^275 + x^274 + x^270 + x^264 + x^263 + x^262 + x^261 + x^259 + x^258 + x^254 + x^253 + x^252 + x^244 + x^242 + x^241 + x^240 + x^239 + x^237 + x^236 + x^235 + x^230 + x^228 + x^224 + x^220 + x^217 + x^214 + x^210 + x^209 + x^208 + x^206 + x^203 + x^202 + x^201 + x^200 + x^199 + x^196 + x^195 + x^194 + x^192 + x^189 + x^188 + x^186 + x^185 + x^184 + x^181 + x^176 + x^175 + x^173 + x^172 + x^171 + x^170 + x^165 + x^163 + x^161 + x^159 + x^156 + x^154 + x^153 + x^144 + x^143 + x^137 + x^135 + x^134 + x^132 + x^130 + x^129 + x^126 + x^125 + x^122 + x^120 + x^118 + x^114 + x^113 + x^110 + x^109 + x^108 + x^107 + x^98 + x^97 + x^95 + x^92 + x^88 + x^87 + x^86 + x^85 + x^84 + x^83 + x^80 + x^76 + x^74 + x^71 + x^70 + x^69 + x^64 + x^63 + x^62 + x^61 + x^57 + x^53 + x^52 + x^50 + x^46 + x^40 + x^38 + x^37 + x^34 + x^33 + x^32 + x^31 + x^28 + x^25 + x^22 + x^18 + x^6 + 1
+
+48-40-25 371 x^928 + x^898 + x^878 + x^870 + x^851 + x^844 + x^832 + x^828 + x^818 + x^809 + x^808 + x^802 + x^790 + x^782 + x^779 + x^772 + x^755 + x^751 + x^749 + x^744 + x^742 + x^740 + x^738 + x^732 + x^731 + x^728 + x^725 + x^719 + x^718 + x^714 + x^713 + x^712 + x^708 + x^705 + x^695 + x^691 + x^690 + x^688 + x^687 + x^686 + x^684 + x^683 + x^679 + x^676 + x^674 + x^671 + x^668 + x^665 + x^663 + x^662 + x^661 + x^656 + x^655 + x^652 + x^650 + x^649 + x^648 + x^647 + x^646 + x^641 + x^640 + x^638 + x^636 + x^635 + x^633 + x^630 + x^627 + x^626 + x^625 + x^624 + x^621 + x^620 + x^619 + x^618 + x^617 + x^614 + x^613 + x^608 + x^607 + x^606 + x^605 + x^604 + x^603 + x^602 + x^599 + x^597 + x^596 + x^591 + x^589 + x^586 + x^585 + x^584 + x^582 + x^578 + x^576 + x^572 + x^569 + x^566 + x^564 + x^558 + x^555 + x^553 + x^550 + x^549 + x^548 + x^545 + x^543 + x^541 + x^540 + x^538 + x^537 + x^533 + x^530 + x^527 + x^524 + x^523 + x^521 + x^520 + x^519 + x^517 + x^516 + x^515 + x^513 + x^510 + x^504 + x^503 + x^501 + x^500 + x^498 + x^497 + x^496 + x^494 + x^492 + x^491 + x^488 + x^485 + x^482 + x^478 + x^476 + x^474 + x^473 + x^471 + x^469 + x^468 + x^464 + x^461 + x^460 + x^459 + x^454 + x^450 + x^449 + x^448 + x^444 + x^439 + x^438 + x^437 + x^436 + x^435 + x^433 + x^431 + x^428 + x^426 + x^424 + x^420 + x^417 + x^416 + x^413 + x^411 + x^408 + x^407 + x^406 + x^403 + x^400 + x^399 + x^398 + x^397 + x^396 + x^392 + x^390 + x^389 + x^388 + x^387 + x^386 + x^385 + x^381 + x^378 + x^374 + x^370 + x^369 + x^368 + x^367 + x^365 + x^364 + x^359 + x^356 + x^354 + x^350 + x^348 + x^346 + x^344 + x^343 + x^342 + x^340 + x^338 + x^337 + x^334 + x^332 + x^330 + x^329 + x^327 + x^322 + x^317 + x^316 + x^314 + x^311 + x^308 + x^307 + x^301 + x^300 + x^299 + x^296 + x^295 + x^292 + x^291 + x^290 + x^286 + x^284 + x^282 + x^279 + x^278 + x^276 + x^273 + x^270 + x^269 + x^265 + x^263 + x^259 + x^258 + x^257 + x^256 + x^255 + x^253 + x^251 + x^249 + x^247 + x^245 + x^244 + x^243 + x^242 + x^241 + x^240 + x^238 + x^236 + x^231 + x^230 + x^229 + x^228 + x^226 + x^223 + x^221 + x^220 + x^219 + x^218 + x^217 + x^215 + x^214 + x^212 + x^211 + x^210 + x^208 + x^207 + x^206 + x^205 + x^202 + x^200 + x^198 + x^193 + x^192 + x^191 + x^187 + x^186 + x^184 + x^182 + x^179 + x^173 + x^171 + x^169 + x^168 + x^164 + x^163 + x^162 + x^161 + x^157 + x^156 + x^155 + x^154 + x^153 + x^151 + x^149 + x^147 + x^146 + x^145 + x^143 + x^140 + x^137 + x^136 + x^133 + x^127 + x^122 + x^121 + x^119 + x^115 + x^114 + x^112 + x^111 + x^110 + x^108 + x^104 + x^103 + x^101 + x^98 + x^94 + x^88 + x^87 + x^85 + x^83 + x^81 + x^80 + x^79 + x^78 + x^77 + x^75 + x^74 + x^73 + x^70 + x^69 + x^68 + x^67 + x^65 + x^63 + x^62 + x^60 + x^59 + x^58 + x^57 + x^56 + x^54 + x^53 + x^52 + x^50 + x^49 + x^47 + x^46 + x^45 + x^41 + x^39 + x^36 + x^34 + x^33 + x^32 + x^31 + x^30 + x^29 + x^28 + x^26 + x^25 + x^21 + x^16 + x^14 + x^4 + 1
+
+19-22-10 373 x^928 + x^898 + x^870 + x^866 + x^842 + x^836 + x^834 + x^821 + x^808 + x^807 + x^806 + x^804 + x^802 + x^794 + x^792 + x^782 + x^778 + x^777 + x^776 + x^770 + x^766 + x^761 + x^757 + x^753 + x^748 + x^743 + x^739 + x^738 + x^736 + x^735 + x^734 + x^732 + x^728 + x^725 + x^722 + x^721 + x^718 + x^716 + x^713 + x^711 + x^710 + x^709 + x^708 + x^705 + x^703 + x^702 + x^693 + x^686 + x^681 + x^680 + x^677 + x^664 + x^662 + x^659 + x^652 + x^651 + x^649 + x^646 + x^644 + x^643 + x^641 + x^638 + x^636 + x^629 + x^627 + x^625 + x^623 + x^622 + x^619 + x^617 + x^616 + x^615 + x^614 + x^612 + x^611 + x^609 + x^606 + x^605 + x^600 + x^597 + x^596 + x^595 + x^592 + x^591 + x^590 + x^586 + x^582 + x^580 + x^577 + x^576 + x^574 + x^572 + x^570 + x^569 + x^567 + x^565 + x^563 + x^562 + x^560 + x^557 + x^556 + x^555 + x^554 + x^552 + x^549 + x^548 + x^546 + x^545 + x^544 + x^542 + x^540 + x^538 + x^536 + x^534 + x^533 + x^532 + x^530 + x^528 + x^525 + x^520 + x^519 + x^518 + x^516 + x^514 + x^513 + x^511 + x^509 + x^504 + x^501 + x^497 + x^496 + x^495 + x^488 + x^487 + x^485 + x^482 + x^481 + x^480 + x^479 + x^478 + x^476 + x^475 + x^474 + x^472 + x^470 + x^468 + x^466 + x^465 + x^463 + x^458 + x^453 + x^451 + x^449 + x^448 + x^447 + x^446 + x^445 + x^444 + x^443 + x^439 + x^438 + x^437 + x^436 + x^433 + x^428 + x^424 + x^418 + x^417 + x^414 + x^412 + x^411 + x^408 + x^407 + x^406 + x^404 + x^403 + x^401 + x^400 + x^399 + x^396 + x^395 + x^393 + x^390 + x^389 + x^388 + x^387 + x^386 + x^385 + x^384 + x^382 + x^380 + x^379 + x^375 + x^371 + x^370 + x^369 + x^365 + x^363 + x^362 + x^357 + x^355 + x^354 + x^351 + x^348 + x^346 + x^345 + x^344 + x^342 + x^340 + x^338 + x^336 + x^334 + x^331 + x^328 + x^327 + x^326 + x^324 + x^323 + x^322 + x^320 + x^315 + x^308 + x^306 + x^298 + x^295 + x^292 + x^287 + x^286 + x^285 + x^284 + x^282 + x^281 + x^280 + x^279 + x^278 + x^276 + x^274 + x^273 + x^272 + x^270 + x^269 + x^268 + x^267 + x^265 + x^262 + x^258 + x^256 + x^253 + x^252 + x^251 + x^250 + x^246 + x^245 + x^244 + x^243 + x^242 + x^240 + x^239 + x^238 + x^237 + x^235 + x^232 + x^228 + x^226 + x^224 + x^217 + x^215 + x^213 + x^211 + x^210 + x^208 + x^206 + x^201 + x^199 + x^196 + x^195 + x^192 + x^190 + x^187 + x^186 + x^185 + x^184 + x^182 + x^180 + x^178 + x^175 + x^174 + x^173 + x^172 + x^165 + x^160 + x^159 + x^158 + x^157 + x^155 + x^154 + x^153 + x^148 + x^146 + x^145 + x^143 + x^142 + x^137 + x^135 + x^133 + x^132 + x^131 + x^128 + x^127 + x^124 + x^123 + x^122 + x^121 + x^117 + x^115 + x^114 + x^113 + x^112 + x^108 + x^107 + x^106 + x^105 + x^103 + x^102 + x^101 + x^100 + x^94 + x^93 + x^92 + x^89 + x^87 + x^86 + x^85 + x^83 + x^80 + x^79 + x^78 + x^77 + x^75 + x^74 + x^72 + x^70 + x^67 + x^66 + x^62 + x^61 + x^59 + x^58 + x^57 + x^55 + x^51 + x^50 + x^49 + x^42 + x^41 + x^39 + x^36 + x^34 + x^32 + x^30 + x^26 + x^24 + x^23 + x^22 + x^21 + x^18 + x^16 + x^14 + x^10 + x^9 + x^8 + x^2 + 1
+
+52-17-25 375 x^928 + x^898 + x^870 + x^861 + x^860 + x^859 + x^858 + x^849 + x^848 + x^847 + x^846 + x^842 + x^836 + x^835 + x^831 + x^830 + x^829 + x^828 + x^823 + x^822 + x^811 + x^810 + x^808 + x^807 + x^806 + x^804 + x^800 + x^799 + x^793 + x^792 + x^789 + x^788 + x^786 + x^780 + x^778 + x^777 + x^775 + x^774 + x^770 + x^769 + x^768 + x^764 + x^763 + x^762 + x^758 + x^757 + x^756 + x^755 + x^751 + x^750 + x^744 + x^740 + x^739 + x^738 + x^733 + x^731 + x^728 + x^721 + x^720 + x^716 + x^715 + x^714 + x^713 + x^710 + x^709 + x^702 + x^701 + x^697 + x^696 + x^695 + x^692 + x^688 + x^686 + x^684 + x^683 + x^680 + x^679 + x^678 + x^677 + x^674 + x^673 + x^672 + x^665 + x^662 + x^658 + x^654 + x^647 + x^643 + x^636 + x^635 + x^631 + x^628 + x^626 + x^625 + x^622 + x^621 + x^619 + x^618 + x^617 + x^614 + x^613 + x^612 + x^611 + x^609 + x^608 + x^598 + x^595 + x^591 + x^589 + x^588 + x^587 + x^586 + x^584 + x^582 + x^576 + x^574 + x^571 + x^569 + x^567 + x^564 + x^563 + x^560 + x^557 + x^550 + x^549 + x^548 + x^547 + x^546 + x^544 + x^539 + x^537 + x^536 + x^529 + x^527 + x^526 + x^523 + x^522 + x^521 + x^516 + x^513 + x^512 + x^509 + x^508 + x^505 + x^503 + x^502 + x^499 + x^493 + x^492 + x^491 + x^487 + x^486 + x^484 + x^482 + x^479 + x^478 + x^477 + x^475 + x^474 + x^471 + x^468 + x^467 + x^465 + x^463 + x^462 + x^461 + x^460 + x^455 + x^452 + x^445 + x^443 + x^442 + x^437 + x^433 + x^432 + x^429 + x^427 + x^426 + x^424 + x^423 + x^422 + x^421 + x^417 + x^411 + x^410 + x^408 + x^407 + x^403 + x^402 + x^400 + x^399 + x^393 + x^391 + x^390 + x^389 + x^386 + x^384 + x^381 + x^379 + x^375 + x^373 + x^372 + x^369 + x^367 + x^366 + x^364 + x^363 + x^362 + x^361 + x^360 + x^357 + x^356 + x^353 + x^352 + x^348 + x^345 + x^344 + x^342 + x^341 + x^340 + x^335 + x^332 + x^330 + x^329 + x^328 + x^327 + x^322 + x^321 + x^319 + x^318 + x^317 + x^315 + x^312 + x^311 + x^310 + x^308 + x^305 + x^302 + x^300 + x^299 + x^298 + x^297 + x^296 + x^292 + x^290 + x^289 + x^288 + x^286 + x^284 + x^283 + x^282 + x^281 + x^278 + x^277 + x^276 + x^274 + x^272 + x^269 + x^267 + x^263 + x^262 + x^260 + x^259 + x^256 + x^254 + x^253 + x^251 + x^250 + x^249 + x^248 + x^242 + x^241 + x^240 + x^235 + x^234 + x^231 + x^226 + x^225 + x^221 + x^219 + x^214 + x^212 + x^211 + x^209 + x^207 + x^206 + x^205 + x^202 + x^199 + x^198 + x^195 + x^190 + x^189 + x^187 + x^185 + x^182 + x^181 + x^180 + x^179 + x^177 + x^176 + x^175 + x^174 + x^171 + x^169 + x^165 + x^164 + x^163 + x^162 + x^161 + x^160 + x^155 + x^154 + x^153 + x^152 + x^146 + x^145 + x^142 + x^139 + x^137 + x^136 + x^128 + x^127 + x^124 + x^121 + x^120 + x^119 + x^117 + x^114 + x^113 + x^112 + x^110 + x^109 + x^108 + x^104 + x^102 + x^101 + x^99 + x^97 + x^87 + x^85 + x^84 + x^83 + x^82 + x^78 + x^76 + x^73 + x^72 + x^69 + x^64 + x^62 + x^59 + x^52 + x^51 + x^50 + x^49 + x^46 + x^45 + x^44 + x^42 + x^41 + x^40 + x^36 + x^35 + x^33 + x^28 + x^26 + x^25 + x^21 + x^19 + x^13 + x^12 + x^7 + x^6 + 1
+
+35-28-44 377 x^928 + x^898 + x^894 + x^870 + x^859 + x^829 + x^828 + x^825 + x^808 + x^804 + x^800 + x^799 + x^795 + x^794 + x^789 + x^778 + x^774 + x^769 + x^768 + x^759 + x^758 + x^755 + x^754 + x^748 + x^744 + x^739 + x^735 + x^734 + x^727 + x^726 + x^722 + x^718 + x^714 + x^713 + x^709 + x^708 + x^705 + x^704 + x^700 + x^694 + x^691 + x^690 + x^688 + x^687 + x^685 + x^682 + x^681 + x^675 + x^668 + x^665 + x^659 + x^657 + x^656 + x^655 + x^653 + x^652 + x^651 + x^649 + x^647 + x^644 + x^640 + x^638 + x^635 + x^634 + x^631 + x^630 + x^629 + x^628 + x^625 + x^624 + x^619 + x^617 + x^614 + x^613 + x^612 + x^611 + x^610 + x^608 + x^602 + x^599 + x^598 + x^593 + x^592 + x^591 + x^590 + x^586 + x^585 + x^583 + x^582 + x^581 + x^580 + x^579 + x^578 + x^576 + x^575 + x^573 + x^569 + x^566 + x^560 + x^559 + x^558 + x^557 + x^553 + x^552 + x^551 + x^549 + x^542 + x^536 + x^535 + x^533 + x^524 + x^522 + x^521 + x^520 + x^518 + x^517 + x^516 + x^515 + x^512 + x^509 + x^507 + x^506 + x^504 + x^502 + x^500 + x^499 + x^498 + x^497 + x^496 + x^491 + x^489 + x^485 + x^484 + x^483 + x^482 + x^481 + x^480 + x^477 + x^476 + x^474 + x^467 + x^466 + x^465 + x^462 + x^460 + x^459 + x^454 + x^450 + x^447 + x^446 + x^445 + x^443 + x^439 + x^434 + x^433 + x^432 + x^431 + x^430 + x^429 + x^428 + x^427 + x^426 + x^425 + x^424 + x^423 + x^421 + x^419 + x^417 + x^413 + x^412 + x^411 + x^409 + x^408 + x^407 + x^406 + x^405 + x^404 + x^403 + x^401 + x^400 + x^394 + x^389 + x^386 + x^383 + x^381 + x^380 + x^379 + x^378 + x^376 + x^375 + x^373 + x^372 + x^371 + x^369 + x^368 + x^367 + x^366 + x^365 + x^364 + x^362 + x^359 + x^356 + x^349 + x^347 + x^346 + x^345 + x^343 + x^342 + x^341 + x^340 + x^339 + x^338 + x^337 + x^336 + x^335 + x^332 + x^331 + x^330 + x^329 + x^325 + x^324 + x^320 + x^319 + x^318 + x^317 + x^316 + x^315 + x^311 + x^309 + x^307 + x^304 + x^303 + x^301 + x^300 + x^298 + x^297 + x^296 + x^295 + x^294 + x^292 + x^291 + x^289 + x^288 + x^285 + x^283 + x^282 + x^281 + x^274 + x^272 + x^271 + x^269 + x^262 + x^261 + x^260 + x^258 + x^257 + x^252 + x^251 + x^250 + x^249 + x^247 + x^246 + x^244 + x^241 + x^236 + x^234 + x^231 + x^230 + x^227 + x^226 + x^219 + x^218 + x^216 + x^215 + x^213 + x^206 + x^205 + x^204 + x^203 + x^202 + x^201 + x^200 + x^198 + x^196 + x^195 + x^194 + x^193 + x^192 + x^190 + x^186 + x^185 + x^184 + x^182 + x^176 + x^174 + x^167 + x^166 + x^164 + x^163 + x^162 + x^161 + x^159 + x^155 + x^154 + x^153 + x^151 + x^150 + x^146 + x^145 + x^143 + x^140 + x^138 + x^135 + x^131 + x^130 + x^129 + x^125 + x^124 + x^123 + x^118 + x^116 + x^113 + x^110 + x^107 + x^101 + x^100 + x^99 + x^95 + x^94 + x^93 + x^92 + x^91 + x^88 + x^86 + x^82 + x^81 + x^80 + x^79 + x^78 + x^76 + x^75 + x^73 + x^72 + x^71 + x^70 + x^69 + x^68 + x^67 + x^65 + x^63 + x^62 + x^60 + x^58 + x^57 + x^56 + x^55 + x^52 + x^50 + x^48 + x^46 + x^44 + x^42 + x^40 + x^39 + x^38 + x^33 + x^31 + x^30 + x^29 + x^28 + x^27 + x^24 + x^21 + x^16 + x^13 + x^8 + 1
+
+45-7-6 377 x^928 + x^898 + x^897 + x^870 + x^868 + x^854 + x^853 + x^850 + x^836 + x^835 + x^832 + x^821 + x^810 + x^809 + x^808 + x^807 + x^805 + x^803 + x^802 + x^801 + x^798 + x^794 + x^792 + x^791 + x^790 + x^780 + x^778 + x^775 + x^770 + x^767 + x^766 + x^765 + x^764 + x^760 + x^754 + x^750 + x^743 + x^740 + x^737 + x^735 + x^732 + x^726 + x^723 + x^722 + x^721 + x^720 + x^716 + x^714 + x^710 + x^707 + x^706 + x^703 + x^701 + x^700 + x^699 + x^695 + x^691 + x^689 + x^687 + x^686 + x^685 + x^683 + x^680 + x^676 + x^675 + x^672 + x^671 + x^670 + x^668 + x^667 + x^666 + x^665 + x^662 + x^658 + x^655 + x^653 + x^652 + x^648 + x^644 + x^643 + x^642 + x^637 + x^629 + x^628 + x^627 + x^626 + x^624 + x^621 + x^617 + x^616 + x^612 + x^610 + x^609 + x^608 + x^607 + x^603 + x^602 + x^600 + x^595 + x^594 + x^592 + x^591 + x^589 + x^586 + x^585 + x^582 + x^578 + x^576 + x^574 + x^573 + x^571 + x^570 + x^566 + x^563 + x^561 + x^560 + x^558 + x^557 + x^556 + x^555 + x^554 + x^553 + x^552 + x^551 + x^549 + x^548 + x^545 + x^538 + x^533 + x^530 + x^524 + x^520 + x^519 + x^512 + x^509 + x^508 + x^505 + x^503 + x^502 + x^497 + x^495 + x^493 + x^492 + x^486 + x^485 + x^484 + x^482 + x^480 + x^479 + x^477 + x^472 + x^470 + x^469 + x^466 + x^464 + x^462 + x^460 + x^459 + x^458 + x^456 + x^455 + x^454 + x^452 + x^451 + x^448 + x^446 + x^442 + x^441 + x^440 + x^437 + x^431 + x^430 + x^427 + x^426 + x^425 + x^424 + x^423 + x^420 + x^417 + x^415 + x^414 + x^413 + x^412 + x^410 + x^408 + x^406 + x^405 + x^404 + x^403 + x^401 + x^399 + x^395 + x^393 + x^392 + x^384 + x^381 + x^375 + x^370 + x^368 + x^367 + x^364 + x^363 + x^361 + x^360 + x^356 + x^355 + x^354 + x^353 + x^351 + x^349 + x^346 + x^343 + x^341 + x^340 + x^339 + x^335 + x^334 + x^333 + x^330 + x^328 + x^326 + x^325 + x^324 + x^323 + x^319 + x^318 + x^316 + x^315 + x^312 + x^306 + x^303 + x^302 + x^301 + x^299 + x^294 + x^292 + x^291 + x^290 + x^289 + x^283 + x^281 + x^276 + x^275 + x^274 + x^273 + x^271 + x^270 + x^269 + x^268 + x^267 + x^265 + x^264 + x^263 + x^262 + x^261 + x^260 + x^259 + x^258 + x^257 + x^255 + x^254 + x^253 + x^252 + x^250 + x^247 + x^246 + x^245 + x^243 + x^241 + x^240 + x^239 + x^235 + x^228 + x^224 + x^223 + x^220 + x^217 + x^216 + x^215 + x^209 + x^205 + x^204 + x^203 + x^202 + x^197 + x^196 + x^195 + x^192 + x^191 + x^189 + x^187 + x^183 + x^181 + x^180 + x^179 + x^178 + x^173 + x^172 + x^170 + x^165 + x^163 + x^161 + x^159 + x^156 + x^155 + x^153 + x^148 + x^146 + x^141 + x^138 + x^134 + x^133 + x^131 + x^130 + x^127 + x^126 + x^125 + x^123 + x^122 + x^119 + x^117 + x^116 + x^110 + x^109 + x^108 + x^107 + x^106 + x^95 + x^93 + x^92 + x^91 + x^88 + x^87 + x^86 + x^84 + x^82 + x^80 + x^79 + x^76 + x^75 + x^73 + x^72 + x^69 + x^68 + x^64 + x^63 + x^61 + x^59 + x^57 + x^55 + x^54 + x^53 + x^51 + x^49 + x^46 + x^43 + x^41 + x^40 + x^36 + x^35 + x^34 + x^33 + x^31 + x^27 + x^25 + x^23 + x^22 + x^21 + x^19 + x^15 + x^13 + x^12 + x^11 + x^10 + x^9 + x^8 + 1
+
+23-49-24 379 x^928 + x^898 + x^872 + x^870 + x^856 + x^843 + x^842 + x^827 + x^826 + x^824 + x^818 + x^813 + x^812 + x^811 + x^797 + x^796 + x^795 + x^792 + x^789 + x^788 + x^781 + x^780 + x^772 + x^767 + x^765 + x^759 + x^757 + x^752 + x^743 + x^742 + x^741 + x^740 + x^737 + x^735 + x^730 + x^729 + x^728 + x^727 + x^724 + x^722 + x^721 + x^720 + x^718 + x^714 + x^712 + x^710 + x^707 + x^706 + x^704 + x^703 + x^702 + x^700 + x^699 + x^698 + x^696 + x^694 + x^692 + x^691 + x^690 + x^689 + x^688 + x^686 + x^682 + x^681 + x^679 + x^677 + x^675 + x^674 + x^665 + x^663 + x^661 + x^660 + x^657 + x^656 + x^655 + x^651 + x^649 + x^647 + x^646 + x^644 + x^642 + x^640 + x^637 + x^635 + x^633 + x^625 + x^622 + x^620 + x^619 + x^617 + x^616 + x^615 + x^613 + x^612 + x^610 + x^609 + x^607 + x^606 + x^605 + x^601 + x^600 + x^597 + x^596 + x^595 + x^593 + x^592 + x^590 + x^588 + x^584 + x^583 + x^582 + x^579 + x^578 + x^574 + x^571 + x^570 + x^567 + x^566 + x^564 + x^561 + x^560 + x^559 + x^558 + x^554 + x^553 + x^547 + x^543 + x^539 + x^536 + x^535 + x^534 + x^533 + x^529 + x^527 + x^526 + x^525 + x^518 + x^516 + x^515 + x^510 + x^509 + x^508 + x^506 + x^505 + x^504 + x^503 + x^499 + x^498 + x^497 + x^495 + x^493 + x^491 + x^489 + x^488 + x^487 + x^486 + x^485 + x^484 + x^482 + x^479 + x^475 + x^473 + x^472 + x^469 + x^468 + x^464 + x^463 + x^462 + x^459 + x^457 + x^455 + x^453 + x^448 + x^446 + x^444 + x^443 + x^442 + x^438 + x^435 + x^431 + x^429 + x^427 + x^424 + x^423 + x^418 + x^416 + x^414 + x^406 + x^404 + x^403 + x^401 + x^397 + x^396 + x^390 + x^387 + x^384 + x^380 + x^377 + x^375 + x^373 + x^369 + x^366 + x^365 + x^364 + x^358 + x^356 + x^355 + x^354 + x^353 + x^352 + x^348 + x^346 + x^340 + x^338 + x^336 + x^334 + x^329 + x^326 + x^325 + x^322 + x^320 + x^318 + x^312 + x^307 + x^305 + x^302 + x^301 + x^299 + x^297 + x^296 + x^294 + x^293 + x^291 + x^288 + x^287 + x^286 + x^281 + x^278 + x^277 + x^276 + x^274 + x^273 + x^272 + x^271 + x^269 + x^268 + x^267 + x^266 + x^262 + x^261 + x^258 + x^256 + x^255 + x^253 + x^251 + x^250 + x^249 + x^248 + x^247 + x^243 + x^240 + x^237 + x^236 + x^235 + x^233 + x^231 + x^230 + x^223 + x^222 + x^220 + x^218 + x^216 + x^212 + x^211 + x^208 + x^207 + x^205 + x^203 + x^202 + x^201 + x^200 + x^199 + x^198 + x^197 + x^195 + x^193 + x^192 + x^191 + x^187 + x^186 + x^183 + x^181 + x^180 + x^179 + x^176 + x^174 + x^173 + x^169 + x^166 + x^161 + x^159 + x^158 + x^157 + x^156 + x^154 + x^152 + x^151 + x^149 + x^145 + x^144 + x^143 + x^142 + x^141 + x^139 + x^136 + x^135 + x^131 + x^128 + x^127 + x^126 + x^125 + x^123 + x^122 + x^120 + x^118 + x^117 + x^116 + x^114 + x^111 + x^110 + x^108 + x^107 + x^106 + x^103 + x^100 + x^99 + x^97 + x^96 + x^95 + x^93 + x^92 + x^91 + x^90 + x^87 + x^84 + x^81 + x^80 + x^79 + x^78 + x^77 + x^74 + x^73 + x^71 + x^67 + x^64 + x^61 + x^59 + x^58 + x^54 + x^49 + x^47 + x^44 + x^43 + x^41 + x^38 + x^37 + x^33 + x^30 + x^25 + x^17 + x^16 + x^15 + x^14 + x^12 + x^11 + x^8 + x^7 + x^4 + 1
+
+19-18-26 381 x^928 + x^898 + x^870 + x^844 + x^836 + x^832 + x^820 + x^814 + x^808 + x^802 + x^798 + x^794 + x^791 + x^790 + x^784 + x^778 + x^774 + x^770 + x^769 + x^766 + x^764 + x^761 + x^754 + x^748 + x^743 + x^734 + x^732 + x^731 + x^727 + x^726 + x^724 + x^723 + x^721 + x^718 + x^716 + x^715 + x^713 + x^711 + x^709 + x^706 + x^704 + x^703 + x^702 + x^701 + x^700 + x^699 + x^697 + x^696 + x^695 + x^693 + x^692 + x^691 + x^690 + x^685 + x^684 + x^676 + x^674 + x^667 + x^664 + x^663 + x^658 + x^657 + x^656 + x^654 + x^653 + x^651 + x^650 + x^646 + x^645 + x^644 + x^643 + x^639 + x^638 + x^637 + x^633 + x^631 + x^630 + x^627 + x^626 + x^625 + x^624 + x^620 + x^611 + x^610 + x^607 + x^606 + x^604 + x^603 + x^598 + x^597 + x^595 + x^593 + x^590 + x^589 + x^588 + x^586 + x^585 + x^584 + x^582 + x^580 + x^577 + x^575 + x^570 + x^569 + x^568 + x^563 + x^562 + x^561 + x^558 + x^557 + x^556 + x^555 + x^552 + x^551 + x^550 + x^548 + x^547 + x^546 + x^545 + x^542 + x^541 + x^540 + x^539 + x^538 + x^537 + x^535 + x^534 + x^533 + x^531 + x^530 + x^528 + x^523 + x^522 + x^521 + x^517 + x^515 + x^514 + x^512 + x^510 + x^509 + x^508 + x^506 + x^497 + x^494 + x^493 + x^490 + x^487 + x^486 + x^483 + x^481 + x^479 + x^476 + x^474 + x^472 + x^471 + x^467 + x^465 + x^464 + x^463 + x^462 + x^460 + x^456 + x^454 + x^452 + x^450 + x^449 + x^448 + x^447 + x^445 + x^444 + x^440 + x^439 + x^438 + x^437 + x^436 + x^432 + x^431 + x^430 + x^429 + x^428 + x^427 + x^425 + x^424 + x^422 + x^420 + x^419 + x^418 + x^416 + x^414 + x^413 + x^409 + x^407 + x^405 + x^404 + x^402 + x^397 + x^396 + x^392 + x^391 + x^389 + x^386 + x^385 + x^384 + x^381 + x^377 + x^376 + x^373 + x^371 + x^368 + x^366 + x^364 + x^362 + x^360 + x^359 + x^357 + x^355 + x^354 + x^353 + x^352 + x^351 + x^350 + x^349 + x^348 + x^346 + x^343 + x^341 + x^340 + x^338 + x^337 + x^336 + x^334 + x^331 + x^329 + x^328 + x^327 + x^325 + x^324 + x^323 + x^320 + x^316 + x^314 + x^313 + x^311 + x^309 + x^307 + x^306 + x^305 + x^304 + x^302 + x^301 + x^299 + x^297 + x^291 + x^289 + x^288 + x^285 + x^283 + x^282 + x^280 + x^279 + x^272 + x^271 + x^270 + x^269 + x^268 + x^264 + x^263 + x^260 + x^259 + x^257 + x^249 + x^245 + x^242 + x^241 + x^238 + x^234 + x^233 + x^232 + x^230 + x^229 + x^227 + x^226 + x^225 + x^223 + x^221 + x^214 + x^211 + x^210 + x^209 + x^206 + x^205 + x^204 + x^203 + x^201 + x^200 + x^199 + x^197 + x^195 + x^188 + x^186 + x^181 + x^180 + x^177 + x^174 + x^173 + x^171 + x^160 + x^159 + x^158 + x^157 + x^154 + x^148 + x^147 + x^144 + x^142 + x^141 + x^140 + x^139 + x^135 + x^134 + x^129 + x^124 + x^123 + x^120 + x^118 + x^117 + x^116 + x^113 + x^112 + x^110 + x^109 + x^108 + x^107 + x^106 + x^104 + x^103 + x^100 + x^97 + x^95 + x^94 + x^89 + x^86 + x^84 + x^83 + x^79 + x^76 + x^75 + x^73 + x^72 + x^70 + x^67 + x^66 + x^65 + x^63 + x^61 + x^60 + x^59 + x^58 + x^56 + x^53 + x^52 + x^51 + x^50 + x^45 + x^41 + x^40 + x^39 + x^37 + x^36 + x^35 + x^29 + x^26 + x^22 + x^19 + x^18 + x^17 + x^16 + x^13 + x^11 + x^6 + 1
+
+26-3-47 381 x^928 + x^898 + x^878 + x^870 + x^869 + x^860 + x^859 + x^858 + x^850 + x^849 + x^848 + x^840 + x^839 + x^838 + x^830 + x^820 + x^818 + x^810 + x^808 + x^807 + x^798 + x^788 + x^780 + x^778 + x^777 + x^769 + x^767 + x^758 + x^750 + x^740 + x^730 + x^729 + x^728 + x^727 + x^721 + x^720 + x^719 + x^717 + x^716 + x^711 + x^701 + x^700 + x^696 + x^690 + x^689 + x^687 + x^686 + x^681 + x^679 + x^678 + x^676 + x^670 + x^668 + x^667 + x^661 + x^660 + x^657 + x^656 + x^652 + x^650 + x^649 + x^648 + x^647 + x^646 + x^641 + x^638 + x^637 + x^636 + x^632 + x^629 + x^627 + x^625 + x^622 + x^620 + x^619 + x^617 + x^616 + x^610 + x^607 + x^606 + x^602 + x^601 + x^600 + x^599 + x^597 + x^596 + x^592 + x^591 + x^590 + x^588 + x^587 + x^586 + x^585 + x^581 + x^578 + x^576 + x^572 + x^571 + x^570 + x^567 + x^562 + x^560 + x^559 + x^558 + x^557 + x^555 + x^551 + x^550 + x^549 + x^548 + x^546 + x^542 + x^541 + x^536 + x^534 + x^531 + x^530 + x^528 + x^525 + x^523 + x^522 + x^520 + x^519 + x^518 + x^515 + x^514 + x^511 + x^510 + x^509 + x^508 + x^505 + x^504 + x^502 + x^501 + x^500 + x^499 + x^494 + x^493 + x^485 + x^484 + x^481 + x^480 + x^479 + x^477 + x^476 + x^475 + x^473 + x^466 + x^464 + x^462 + x^461 + x^460 + x^458 + x^457 + x^453 + x^447 + x^444 + x^442 + x^441 + x^440 + x^439 + x^438 + x^433 + x^432 + x^429 + x^428 + x^426 + x^425 + x^424 + x^422 + x^421 + x^420 + x^419 + x^418 + x^414 + x^412 + x^411 + x^407 + x^404 + x^401 + x^398 + x^396 + x^393 + x^392 + x^391 + x^389 + x^387 + x^385 + x^383 + x^382 + x^381 + x^380 + x^378 + x^377 + x^374 + x^372 + x^371 + x^368 + x^365 + x^363 + x^362 + x^359 + x^357 + x^356 + x^355 + x^354 + x^350 + x^347 + x^344 + x^343 + x^341 + x^338 + x^337 + x^335 + x^334 + x^333 + x^331 + x^330 + x^329 + x^328 + x^324 + x^322 + x^319 + x^317 + x^314 + x^310 + x^306 + x^300 + x^299 + x^295 + x^294 + x^291 + x^290 + x^289 + x^288 + x^287 + x^286 + x^285 + x^284 + x^282 + x^281 + x^279 + x^278 + x^275 + x^272 + x^271 + x^270 + x^269 + x^266 + x^264 + x^262 + x^260 + x^259 + x^258 + x^254 + x^250 + x^249 + x^247 + x^246 + x^244 + x^243 + x^241 + x^239 + x^237 + x^236 + x^233 + x^232 + x^231 + x^229 + x^227 + x^226 + x^221 + x^220 + x^218 + x^217 + x^216 + x^215 + x^214 + x^213 + x^212 + x^210 + x^209 + x^207 + x^206 + x^202 + x^201 + x^200 + x^199 + x^198 + x^197 + x^195 + x^193 + x^192 + x^189 + x^188 + x^180 + x^176 + x^174 + x^173 + x^172 + x^170 + x^167 + x^165 + x^164 + x^162 + x^160 + x^157 + x^155 + x^153 + x^152 + x^151 + x^149 + x^148 + x^147 + x^144 + x^142 + x^140 + x^139 + x^136 + x^134 + x^133 + x^128 + x^127 + x^124 + x^123 + x^122 + x^121 + x^119 + x^117 + x^115 + x^113 + x^112 + x^110 + x^107 + x^105 + x^101 + x^100 + x^99 + x^98 + x^94 + x^92 + x^91 + x^90 + x^89 + x^87 + x^85 + x^83 + x^81 + x^80 + x^78 + x^77 + x^74 + x^72 + x^71 + x^70 + x^69 + x^65 + x^64 + x^63 + x^62 + x^61 + x^57 + x^56 + x^55 + x^54 + x^53 + x^49 + x^48 + x^42 + x^41 + x^39 + x^36 + x^34 + x^32 + x^31 + x^24 + x^23 + x^21 + x^14 + x^10 + 1
+
+37-33-14 381 x^928 + x^898 + x^874 + x^870 + x^849 + x^845 + x^841 + x^837 + x^836 + x^832 + x^824 + x^820 + x^812 + x^811 + x^804 + x^802 + x^794 + x^789 + x^785 + x^783 + x^781 + x^777 + x^775 + x^771 + x^770 + x^764 + x^761 + x^757 + x^754 + x^751 + x^746 + x^742 + x^741 + x^740 + x^738 + x^736 + x^734 + x^733 + x^731 + x^727 + x^726 + x^725 + x^724 + x^723 + x^721 + x^720 + x^718 + x^717 + x^716 + x^715 + x^714 + x^713 + x^712 + x^711 + x^709 + x^705 + x^704 + x^703 + x^701 + x^695 + x^692 + x^691 + x^690 + x^688 + x^687 + x^686 + x^685 + x^684 + x^682 + x^680 + x^679 + x^676 + x^671 + x^670 + x^665 + x^663 + x^662 + x^661 + x^660 + x^659 + x^653 + x^652 + x^651 + x^650 + x^648 + x^644 + x^643 + x^642 + x^641 + x^637 + x^635 + x^634 + x^631 + x^630 + x^629 + x^627 + x^626 + x^623 + x^622 + x^621 + x^619 + x^617 + x^616 + x^614 + x^613 + x^611 + x^610 + x^603 + x^601 + x^600 + x^599 + x^597 + x^596 + x^594 + x^593 + x^592 + x^591 + x^589 + x^587 + x^585 + x^583 + x^582 + x^579 + x^575 + x^573 + x^571 + x^570 + x^567 + x^566 + x^560 + x^557 + x^556 + x^554 + x^553 + x^552 + x^551 + x^548 + x^546 + x^541 + x^540 + x^538 + x^535 + x^534 + x^531 + x^527 + x^526 + x^525 + x^524 + x^523 + x^517 + x^516 + x^511 + x^509 + x^507 + x^499 + x^496 + x^493 + x^491 + x^490 + x^485 + x^482 + x^481 + x^479 + x^477 + x^475 + x^474 + x^470 + x^469 + x^468 + x^465 + x^462 + x^461 + x^459 + x^458 + x^453 + x^451 + x^446 + x^444 + x^441 + x^436 + x^435 + x^434 + x^432 + x^429 + x^420 + x^419 + x^416 + x^414 + x^411 + x^410 + x^409 + x^407 + x^405 + x^404 + x^403 + x^402 + x^401 + x^397 + x^395 + x^393 + x^392 + x^390 + x^388 + x^384 + x^381 + x^379 + x^376 + x^374 + x^368 + x^367 + x^365 + x^362 + x^361 + x^360 + x^359 + x^357 + x^355 + x^351 + x^349 + x^346 + x^345 + x^344 + x^342 + x^341 + x^339 + x^337 + x^336 + x^335 + x^333 + x^331 + x^326 + x^320 + x^318 + x^316 + x^315 + x^314 + x^313 + x^312 + x^311 + x^310 + x^309 + x^306 + x^304 + x^303 + x^302 + x^301 + x^300 + x^298 + x^297 + x^296 + x^295 + x^294 + x^293 + x^292 + x^290 + x^289 + x^288 + x^284 + x^283 + x^282 + x^278 + x^277 + x^274 + x^273 + x^272 + x^270 + x^266 + x^265 + x^261 + x^258 + x^256 + x^255 + x^254 + x^248 + x^246 + x^245 + x^239 + x^237 + x^234 + x^230 + x^229 + x^225 + x^224 + x^222 + x^221 + x^217 + x^215 + x^214 + x^213 + x^212 + x^208 + x^206 + x^204 + x^203 + x^202 + x^201 + x^199 + x^198 + x^195 + x^194 + x^191 + x^189 + x^188 + x^186 + x^184 + x^182 + x^181 + x^179 + x^177 + x^176 + x^175 + x^171 + x^169 + x^168 + x^162 + x^161 + x^159 + x^157 + x^156 + x^151 + x^150 + x^148 + x^146 + x^145 + x^142 + x^140 + x^139 + x^138 + x^135 + x^134 + x^131 + x^129 + x^126 + x^124 + x^119 + x^118 + x^117 + x^116 + x^108 + x^106 + x^105 + x^103 + x^99 + x^97 + x^93 + x^92 + x^91 + x^90 + x^87 + x^86 + x^84 + x^83 + x^78 + x^76 + x^73 + x^66 + x^65 + x^64 + x^62 + x^61 + x^58 + x^53 + x^52 + x^51 + x^48 + x^47 + x^46 + x^45 + x^44 + x^42 + x^41 + x^38 + x^34 + x^29 + x^28 + x^26 + x^23 + x^16 + x^8 + x^6 + 1
+
+36-46-33 383 x^928 + x^898 + x^870 + x^857 + x^828 + x^827 + x^816 + x^815 + x^809 + x^808 + x^804 + x^797 + x^792 + x^786 + x^785 + x^780 + x^778 + x^775 + x^773 + x^768 + x^767 + x^762 + x^755 + x^751 + x^750 + x^737 + x^734 + x^732 + x^728 + x^727 + x^725 + x^722 + x^716 + x^715 + x^714 + x^710 + x^708 + x^707 + x^704 + x^703 + x^701 + x^698 + x^697 + x^695 + x^689 + x^688 + x^685 + x^681 + x^680 + x^679 + x^678 + x^677 + x^674 + x^665 + x^658 + x^656 + x^651 + x^650 + x^649 + x^648 + x^647 + x^640 + x^637 + x^635 + x^634 + x^633 + x^631 + x^628 + x^626 + x^624 + x^620 + x^619 + x^617 + x^616 + x^610 + x^607 + x^605 + x^603 + x^602 + x^601 + x^598 + x^591 + x^590 + x^587 + x^584 + x^582 + x^580 + x^577 + x^574 + x^573 + x^571 + x^567 + x^563 + x^562 + x^560 + x^559 + x^558 + x^557 + x^555 + x^553 + x^551 + x^550 + x^549 + x^548 + x^547 + x^544 + x^542 + x^540 + x^539 + x^538 + x^537 + x^535 + x^534 + x^533 + x^531 + x^528 + x^527 + x^525 + x^519 + x^517 + x^516 + x^515 + x^510 + x^509 + x^508 + x^507 + x^505 + x^500 + x^499 + x^496 + x^495 + x^494 + x^493 + x^489 + x^488 + x^487 + x^486 + x^485 + x^484 + x^482 + x^480 + x^479 + x^477 + x^475 + x^473 + x^470 + x^468 + x^467 + x^466 + x^465 + x^463 + x^461 + x^460 + x^455 + x^451 + x^450 + x^448 + x^444 + x^443 + x^442 + x^439 + x^438 + x^437 + x^435 + x^434 + x^433 + x^427 + x^426 + x^425 + x^423 + x^421 + x^420 + x^419 + x^418 + x^416 + x^413 + x^411 + x^410 + x^408 + x^407 + x^404 + x^402 + x^400 + x^399 + x^398 + x^397 + x^396 + x^395 + x^394 + x^393 + x^387 + x^386 + x^382 + x^379 + x^378 + x^377 + x^376 + x^375 + x^374 + x^372 + x^371 + x^370 + x^369 + x^366 + x^364 + x^363 + x^362 + x^361 + x^359 + x^358 + x^357 + x^356 + x^355 + x^354 + x^352 + x^347 + x^346 + x^345 + x^344 + x^343 + x^341 + x^340 + x^336 + x^335 + x^332 + x^330 + x^329 + x^328 + x^325 + x^324 + x^323 + x^322 + x^321 + x^320 + x^318 + x^316 + x^315 + x^312 + x^302 + x^301 + x^298 + x^295 + x^288 + x^287 + x^286 + x^285 + x^280 + x^279 + x^278 + x^275 + x^273 + x^272 + x^270 + x^267 + x^266 + x^264 + x^261 + x^259 + x^258 + x^255 + x^253 + x^252 + x^250 + x^249 + x^248 + x^247 + x^244 + x^243 + x^242 + x^241 + x^240 + x^237 + x^236 + x^235 + x^231 + x^230 + x^228 + x^225 + x^224 + x^222 + x^220 + x^218 + x^217 + x^216 + x^215 + x^212 + x^211 + x^205 + x^204 + x^203 + x^201 + x^196 + x^194 + x^193 + x^192 + x^191 + x^190 + x^187 + x^186 + x^184 + x^183 + x^182 + x^180 + x^179 + x^178 + x^174 + x^173 + x^172 + x^164 + x^163 + x^162 + x^161 + x^160 + x^159 + x^158 + x^156 + x^154 + x^153 + x^150 + x^149 + x^148 + x^146 + x^144 + x^143 + x^140 + x^134 + x^131 + x^127 + x^125 + x^124 + x^120 + x^119 + x^118 + x^116 + x^115 + x^113 + x^112 + x^109 + x^108 + x^107 + x^106 + x^103 + x^100 + x^99 + x^97 + x^96 + x^95 + x^94 + x^91 + x^87 + x^86 + x^83 + x^81 + x^80 + x^78 + x^77 + x^75 + x^74 + x^72 + x^71 + x^69 + x^68 + x^66 + x^64 + x^63 + x^59 + x^57 + x^55 + x^53 + x^48 + x^47 + x^44 + x^42 + x^41 + x^40 + x^37 + x^28 + x^27 + x^26 + x^20 + x^18 + x^16 + 1
+
+40-1-13 383 x^928 + x^898 + x^870 + x^864 + x^861 + x^858 + x^855 + x^852 + x^837 + x^834 + x^825 + x^808 + x^804 + x^801 + x^798 + x^792 + x^791 + x^788 + x^785 + x^778 + x^777 + x^774 + x^773 + x^758 + x^755 + x^752 + x^743 + x^740 + x^738 + x^737 + x^735 + x^734 + x^725 + x^721 + x^719 + x^718 + x^716 + x^715 + x^713 + x^710 + x^707 + x^705 + x^704 + x^703 + x^698 + x^695 + x^691 + x^689 + x^686 + x^682 + x^680 + x^678 + x^677 + x^676 + x^674 + x^673 + x^671 + x^668 + x^667 + x^664 + x^662 + x^661 + x^659 + x^658 + x^656 + x^652 + x^650 + x^648 + x^647 + x^645 + x^644 + x^643 + x^642 + x^641 + x^640 + x^636 + x^633 + x^630 + x^629 + x^628 + x^627 + x^626 + x^623 + x^621 + x^618 + x^615 + x^612 + x^608 + x^607 + x^605 + x^603 + x^602 + x^600 + x^598 + x^596 + x^594 + x^593 + x^588 + x^583 + x^582 + x^579 + x^574 + x^573 + x^569 + x^568 + x^567 + x^565 + x^564 + x^562 + x^558 + x^557 + x^556 + x^555 + x^552 + x^551 + x^548 + x^545 + x^544 + x^542 + x^540 + x^537 + x^535 + x^534 + x^533 + x^532 + x^531 + x^530 + x^526 + x^525 + x^524 + x^523 + x^521 + x^520 + x^519 + x^518 + x^517 + x^515 + x^513 + x^509 + x^508 + x^507 + x^502 + x^500 + x^499 + x^496 + x^495 + x^491 + x^489 + x^488 + x^485 + x^482 + x^480 + x^478 + x^476 + x^474 + x^471 + x^468 + x^466 + x^463 + x^462 + x^461 + x^460 + x^459 + x^457 + x^456 + x^453 + x^451 + x^450 + x^447 + x^443 + x^440 + x^439 + x^436 + x^435 + x^434 + x^433 + x^432 + x^426 + x^425 + x^424 + x^422 + x^421 + x^419 + x^417 + x^416 + x^410 + x^409 + x^408 + x^406 + x^405 + x^402 + x^401 + x^399 + x^398 + x^396 + x^389 + x^388 + x^387 + x^385 + x^383 + x^382 + x^381 + x^379 + x^378 + x^377 + x^376 + x^375 + x^373 + x^371 + x^368 + x^366 + x^364 + x^363 + x^360 + x^358 + x^356 + x^355 + x^353 + x^350 + x^349 + x^346 + x^345 + x^344 + x^340 + x^339 + x^338 + x^332 + x^331 + x^329 + x^326 + x^324 + x^323 + x^321 + x^316 + x^315 + x^313 + x^312 + x^310 + x^309 + x^307 + x^306 + x^305 + x^303 + x^302 + x^300 + x^299 + x^296 + x^294 + x^293 + x^292 + x^289 + x^288 + x^286 + x^285 + x^283 + x^282 + x^279 + x^277 + x^274 + x^273 + x^272 + x^270 + x^269 + x^268 + x^267 + x^265 + x^264 + x^261 + x^259 + x^256 + x^251 + x^249 + x^245 + x^241 + x^240 + x^239 + x^238 + x^236 + x^235 + x^234 + x^232 + x^230 + x^226 + x^222 + x^220 + x^217 + x^215 + x^211 + x^210 + x^208 + x^203 + x^200 + x^199 + x^197 + x^195 + x^194 + x^193 + x^190 + x^187 + x^186 + x^184 + x^183 + x^182 + x^178 + x^176 + x^174 + x^169 + x^168 + x^167 + x^164 + x^162 + x^161 + x^160 + x^159 + x^158 + x^154 + x^153 + x^147 + x^142 + x^138 + x^137 + x^129 + x^128 + x^127 + x^126 + x^124 + x^123 + x^121 + x^119 + x^116 + x^115 + x^112 + x^110 + x^109 + x^107 + x^106 + x^103 + x^101 + x^100 + x^99 + x^98 + x^95 + x^94 + x^93 + x^92 + x^91 + x^89 + x^85 + x^83 + x^80 + x^79 + x^77 + x^75 + x^73 + x^72 + x^71 + x^63 + x^61 + x^59 + x^58 + x^57 + x^55 + x^51 + x^48 + x^47 + x^46 + x^45 + x^39 + x^38 + x^37 + x^34 + x^33 + x^32 + x^29 + x^28 + x^25 + x^23 + x^20 + x^17 + x^11 + x^10 + x^7 + 1
+
+46-53-31 383 x^928 + x^898 + x^896 + x^875 + x^870 + x^864 + x^856 + x^854 + x^848 + x^845 + x^834 + x^833 + x^827 + x^817 + x^814 + x^812 + x^808 + x^807 + x^806 + x^804 + x^801 + x^796 + x^794 + x^791 + x^787 + x^786 + x^778 + x^777 + x^776 + x^774 + x^773 + x^772 + x^770 + x^767 + x^765 + x^764 + x^761 + x^757 + x^756 + x^754 + x^746 + x^745 + x^744 + x^741 + x^735 + x^734 + x^730 + x^727 + x^725 + x^723 + x^716 + x^715 + x^714 + x^713 + x^712 + x^705 + x^704 + x^703 + x^702 + x^697 + x^696 + x^692 + x^688 + x^685 + x^684 + x^683 + x^682 + x^681 + x^674 + x^673 + x^672 + x^671 + x^670 + x^667 + x^666 + x^664 + x^663 + x^661 + x^660 + x^658 + x^655 + x^654 + x^653 + x^652 + x^651 + x^650 + x^645 + x^639 + x^637 + x^634 + x^631 + x^630 + x^626 + x^625 + x^624 + x^621 + x^620 + x^618 + x^615 + x^610 + x^608 + x^607 + x^606 + x^605 + x^604 + x^602 + x^596 + x^594 + x^588 + x^586 + x^584 + x^582 + x^580 + x^578 + x^574 + x^573 + x^571 + x^570 + x^568 + x^567 + x^560 + x^553 + x^551 + x^548 + x^545 + x^543 + x^542 + x^538 + x^537 + x^536 + x^534 + x^533 + x^532 + x^530 + x^529 + x^528 + x^523 + x^521 + x^513 + x^512 + x^509 + x^508 + x^505 + x^502 + x^491 + x^490 + x^489 + x^487 + x^481 + x^479 + x^468 + x^466 + x^465 + x^464 + x^461 + x^460 + x^459 + x^457 + x^455 + x^454 + x^453 + x^451 + x^450 + x^444 + x^442 + x^440 + x^438 + x^431 + x^430 + x^429 + x^428 + x^427 + x^426 + x^425 + x^424 + x^423 + x^422 + x^421 + x^416 + x^415 + x^414 + x^412 + x^410 + x^409 + x^408 + x^402 + x^400 + x^399 + x^398 + x^396 + x^395 + x^393 + x^392 + x^391 + x^388 + x^385 + x^384 + x^381 + x^380 + x^379 + x^377 + x^376 + x^374 + x^373 + x^371 + x^368 + x^366 + x^365 + x^364 + x^362 + x^358 + x^357 + x^356 + x^351 + x^348 + x^345 + x^342 + x^339 + x^338 + x^336 + x^334 + x^331 + x^330 + x^328 + x^327 + x^323 + x^320 + x^319 + x^318 + x^312 + x^311 + x^307 + x^306 + x^305 + x^304 + x^303 + x^302 + x^301 + x^298 + x^295 + x^293 + x^292 + x^291 + x^287 + x^286 + x^285 + x^284 + x^283 + x^280 + x^279 + x^278 + x^276 + x^275 + x^271 + x^269 + x^266 + x^264 + x^263 + x^262 + x^260 + x^257 + x^255 + x^254 + x^253 + x^252 + x^251 + x^250 + x^248 + x^242 + x^241 + x^238 + x^234 + x^231 + x^225 + x^223 + x^222 + x^221 + x^220 + x^219 + x^218 + x^217 + x^214 + x^211 + x^209 + x^208 + x^207 + x^206 + x^204 + x^200 + x^196 + x^194 + x^191 + x^188 + x^186 + x^185 + x^182 + x^181 + x^178 + x^176 + x^175 + x^174 + x^169 + x^168 + x^166 + x^164 + x^160 + x^159 + x^158 + x^155 + x^154 + x^153 + x^151 + x^149 + x^147 + x^145 + x^143 + x^138 + x^135 + x^132 + x^131 + x^130 + x^128 + x^127 + x^124 + x^123 + x^121 + x^120 + x^119 + x^117 + x^116 + x^115 + x^112 + x^111 + x^110 + x^109 + x^106 + x^105 + x^104 + x^101 + x^99 + x^96 + x^87 + x^85 + x^84 + x^83 + x^81 + x^80 + x^79 + x^75 + x^73 + x^70 + x^69 + x^68 + x^67 + x^66 + x^63 + x^61 + x^60 + x^58 + x^56 + x^54 + x^53 + x^51 + x^49 + x^47 + x^45 + x^44 + x^43 + x^42 + x^41 + x^39 + x^36 + x^34 + x^31 + x^30 + x^29 + x^27 + x^24 + x^22 + x^14 + x^13 + x^12 + 1
+
+1-41-10 385 x^928 + x^898 + x^879 + x^870 + x^855 + x^850 + x^849 + x^831 + x^826 + x^825 + x^819 + x^816 + x^808 + x^807 + x^802 + x^801 + x^800 + x^796 + x^792 + x^789 + x^777 + x^776 + x^768 + x^766 + x^762 + x^758 + x^756 + x^754 + x^748 + x^746 + x^744 + x^742 + x^738 + x^736 + x^735 + x^733 + x^729 + x^728 + x^725 + x^720 + x^716 + x^710 + x^705 + x^704 + x^701 + x^700 + x^696 + x^688 + x^686 + x^682 + x^681 + x^680 + x^679 + x^678 + x^677 + x^676 + x^675 + x^674 + x^671 + x^670 + x^669 + x^666 + x^665 + x^661 + x^660 + x^658 + x^655 + x^653 + x^652 + x^649 + x^648 + x^645 + x^640 + x^637 + x^633 + x^629 + x^628 + x^624 + x^623 + x^621 + x^620 + x^619 + x^618 + x^617 + x^616 + x^610 + x^609 + x^607 + x^605 + x^604 + x^601 + x^600 + x^595 + x^591 + x^589 + x^586 + x^584 + x^581 + x^579 + x^575 + x^573 + x^569 + x^568 + x^561 + x^559 + x^556 + x^555 + x^546 + x^542 + x^540 + x^538 + x^537 + x^534 + x^533 + x^531 + x^530 + x^528 + x^526 + x^525 + x^523 + x^518 + x^517 + x^513 + x^511 + x^507 + x^497 + x^496 + x^494 + x^493 + x^491 + x^489 + x^488 + x^487 + x^485 + x^484 + x^483 + x^482 + x^479 + x^477 + x^476 + x^475 + x^474 + x^471 + x^470 + x^468 + x^466 + x^465 + x^464 + x^463 + x^462 + x^461 + x^459 + x^458 + x^454 + x^453 + x^452 + x^451 + x^449 + x^447 + x^446 + x^442 + x^441 + x^440 + x^434 + x^431 + x^428 + x^427 + x^426 + x^424 + x^421 + x^418 + x^417 + x^416 + x^414 + x^412 + x^411 + x^408 + x^405 + x^401 + x^400 + x^399 + x^398 + x^395 + x^394 + x^393 + x^392 + x^391 + x^388 + x^386 + x^385 + x^381 + x^380 + x^379 + x^378 + x^376 + x^375 + x^373 + x^372 + x^370 + x^367 + x^366 + x^365 + x^364 + x^361 + x^360 + x^359 + x^356 + x^354 + x^353 + x^349 + x^348 + x^346 + x^344 + x^340 + x^335 + x^332 + x^330 + x^325 + x^324 + x^321 + x^318 + x^316 + x^315 + x^314 + x^312 + x^310 + x^309 + x^307 + x^304 + x^301 + x^300 + x^299 + x^298 + x^297 + x^295 + x^291 + x^290 + x^289 + x^288 + x^287 + x^286 + x^285 + x^284 + x^281 + x^280 + x^276 + x^274 + x^269 + x^268 + x^267 + x^265 + x^264 + x^261 + x^260 + x^259 + x^257 + x^256 + x^255 + x^254 + x^251 + x^250 + x^245 + x^242 + x^239 + x^236 + x^233 + x^229 + x^227 + x^225 + x^223 + x^222 + x^219 + x^217 + x^214 + x^213 + x^210 + x^207 + x^205 + x^204 + x^203 + x^202 + x^201 + x^200 + x^199 + x^198 + x^197 + x^196 + x^195 + x^192 + x^190 + x^189 + x^181 + x^180 + x^178 + x^177 + x^175 + x^174 + x^173 + x^172 + x^169 + x^168 + x^165 + x^162 + x^159 + x^158 + x^154 + x^153 + x^152 + x^150 + x^148 + x^144 + x^143 + x^142 + x^141 + x^139 + x^138 + x^137 + x^133 + x^132 + x^128 + x^127 + x^124 + x^123 + x^122 + x^121 + x^118 + x^116 + x^106 + x^102 + x^101 + x^98 + x^96 + x^92 + x^91 + x^90 + x^89 + x^88 + x^86 + x^85 + x^84 + x^83 + x^81 + x^80 + x^78 + x^76 + x^73 + x^72 + x^71 + x^69 + x^67 + x^66 + x^65 + x^63 + x^58 + x^54 + x^53 + x^52 + x^51 + x^50 + x^47 + x^46 + x^45 + x^44 + x^43 + x^40 + x^39 + x^38 + x^37 + x^34 + x^33 + x^32 + x^30 + x^25 + x^23 + x^21 + x^20 + x^19 + x^17 + x^16 + x^15 + x^12 + x^9 + x^8 + x^4 + 1
+
+11-33-48 385 x^928 + x^898 + x^882 + x^870 + x^860 + x^853 + x^844 + x^835 + x^828 + x^827 + x^822 + x^819 + x^815 + x^811 + x^808 + x^806 + x^805 + x^794 + x^793 + x^786 + x^784 + x^781 + x^778 + x^773 + x^772 + x^769 + x^765 + x^762 + x^760 + x^759 + x^756 + x^755 + x^748 + x^746 + x^743 + x^739 + x^735 + x^734 + x^733 + x^731 + x^729 + x^727 + x^723 + x^718 + x^713 + x^709 + x^707 + x^706 + x^704 + x^702 + x^699 + x^696 + x^693 + x^692 + x^691 + x^686 + x^685 + x^683 + x^679 + x^677 + x^673 + x^670 + x^669 + x^666 + x^657 + x^656 + x^655 + x^649 + x^648 + x^646 + x^641 + x^639 + x^638 + x^635 + x^633 + x^632 + x^630 + x^628 + x^627 + x^625 + x^620 + x^616 + x^614 + x^613 + x^611 + x^610 + x^609 + x^607 + x^606 + x^600 + x^595 + x^593 + x^592 + x^589 + x^587 + x^584 + x^581 + x^580 + x^579 + x^577 + x^572 + x^570 + x^568 + x^567 + x^566 + x^564 + x^560 + x^559 + x^557 + x^555 + x^554 + x^552 + x^551 + x^546 + x^542 + x^538 + x^535 + x^534 + x^533 + x^531 + x^530 + x^528 + x^526 + x^524 + x^523 + x^520 + x^519 + x^511 + x^509 + x^506 + x^504 + x^503 + x^502 + x^501 + x^500 + x^499 + x^498 + x^495 + x^494 + x^491 + x^490 + x^489 + x^488 + x^487 + x^485 + x^484 + x^479 + x^475 + x^473 + x^466 + x^459 + x^457 + x^456 + x^455 + x^454 + x^451 + x^450 + x^449 + x^448 + x^447 + x^446 + x^444 + x^443 + x^442 + x^441 + x^440 + x^433 + x^432 + x^430 + x^428 + x^427 + x^425 + x^423 + x^419 + x^418 + x^417 + x^414 + x^409 + x^408 + x^406 + x^404 + x^402 + x^400 + x^398 + x^397 + x^396 + x^395 + x^393 + x^389 + x^388 + x^385 + x^379 + x^377 + x^375 + x^374 + x^369 + x^365 + x^364 + x^363 + x^362 + x^361 + x^359 + x^355 + x^354 + x^350 + x^348 + x^345 + x^344 + x^339 + x^336 + x^335 + x^334 + x^333 + x^332 + x^331 + x^330 + x^329 + x^328 + x^326 + x^319 + x^318 + x^316 + x^315 + x^314 + x^313 + x^312 + x^309 + x^308 + x^304 + x^303 + x^302 + x^299 + x^298 + x^297 + x^295 + x^294 + x^293 + x^292 + x^291 + x^290 + x^288 + x^285 + x^282 + x^281 + x^279 + x^277 + x^276 + x^274 + x^272 + x^271 + x^270 + x^269 + x^268 + x^267 + x^265 + x^264 + x^262 + x^261 + x^260 + x^257 + x^253 + x^251 + x^250 + x^247 + x^246 + x^243 + x^242 + x^241 + x^240 + x^237 + x^236 + x^233 + x^232 + x^230 + x^229 + x^226 + x^223 + x^222 + x^221 + x^220 + x^217 + x^215 + x^211 + x^210 + x^209 + x^207 + x^206 + x^205 + x^203 + x^201 + x^200 + x^198 + x^196 + x^195 + x^193 + x^189 + x^188 + x^186 + x^184 + x^180 + x^179 + x^177 + x^176 + x^170 + x^168 + x^163 + x^162 + x^160 + x^159 + x^158 + x^157 + x^156 + x^154 + x^151 + x^149 + x^148 + x^145 + x^144 + x^141 + x^140 + x^138 + x^137 + x^136 + x^135 + x^134 + x^133 + x^132 + x^131 + x^130 + x^129 + x^125 + x^124 + x^121 + x^117 + x^116 + x^110 + x^109 + x^108 + x^106 + x^104 + x^103 + x^102 + x^99 + x^98 + x^96 + x^95 + x^93 + x^92 + x^90 + x^89 + x^88 + x^85 + x^83 + x^81 + x^78 + x^76 + x^72 + x^71 + x^70 + x^68 + x^67 + x^66 + x^62 + x^59 + x^58 + x^56 + x^51 + x^48 + x^46 + x^45 + x^44 + x^43 + x^41 + x^40 + x^38 + x^37 + x^35 + x^34 + x^33 + x^32 + x^27 + x^22 + x^19 + x^13 + 1
+
+19-8-4 387 x^928 + x^898 + x^870 + x^844 + x^838 + x^834 + x^828 + x^818 + x^814 + x^806 + x^804 + x^803 + x^797 + x^782 + x^778 + x^776 + x^774 + x^773 + x^772 + x^768 + x^767 + x^764 + x^752 + x^751 + x^745 + x^744 + x^742 + x^740 + x^738 + x^736 + x^733 + x^730 + x^721 + x^718 + x^715 + x^714 + x^710 + x^707 + x^704 + x^702 + x^700 + x^699 + x^698 + x^697 + x^694 + x^692 + x^691 + x^688 + x^686 + x^685 + x^682 + x^676 + x^673 + x^671 + x^670 + x^669 + x^666 + x^662 + x^661 + x^658 + x^656 + x^655 + x^654 + x^652 + x^649 + x^648 + x^647 + x^645 + x^644 + x^642 + x^640 + x^638 + x^636 + x^632 + x^631 + x^630 + x^623 + x^622 + x^621 + x^616 + x^614 + x^612 + x^611 + x^606 + x^605 + x^602 + x^598 + x^597 + x^594 + x^593 + x^591 + x^590 + x^588 + x^587 + x^586 + x^584 + x^582 + x^581 + x^579 + x^577 + x^574 + x^572 + x^571 + x^568 + x^567 + x^566 + x^563 + x^562 + x^560 + x^559 + x^558 + x^556 + x^553 + x^551 + x^550 + x^549 + x^546 + x^545 + x^543 + x^542 + x^538 + x^536 + x^535 + x^534 + x^533 + x^531 + x^530 + x^529 + x^527 + x^525 + x^524 + x^522 + x^521 + x^520 + x^518 + x^517 + x^513 + x^512 + x^510 + x^509 + x^507 + x^506 + x^505 + x^504 + x^501 + x^500 + x^499 + x^493 + x^492 + x^491 + x^489 + x^488 + x^486 + x^485 + x^484 + x^480 + x^479 + x^478 + x^477 + x^474 + x^473 + x^472 + x^470 + x^468 + x^464 + x^462 + x^458 + x^456 + x^455 + x^454 + x^453 + x^452 + x^451 + x^450 + x^449 + x^447 + x^446 + x^445 + x^441 + x^439 + x^438 + x^437 + x^436 + x^434 + x^433 + x^432 + x^431 + x^429 + x^426 + x^425 + x^424 + x^423 + x^421 + x^419 + x^418 + x^416 + x^414 + x^412 + x^410 + x^407 + x^405 + x^404 + x^398 + x^397 + x^394 + x^393 + x^392 + x^391 + x^387 + x^386 + x^385 + x^382 + x^381 + x^379 + x^377 + x^375 + x^374 + x^369 + x^368 + x^365 + x^364 + x^363 + x^362 + x^361 + x^359 + x^358 + x^356 + x^355 + x^352 + x^351 + x^350 + x^345 + x^343 + x^341 + x^340 + x^338 + x^333 + x^331 + x^330 + x^329 + x^328 + x^327 + x^325 + x^324 + x^323 + x^322 + x^318 + x^315 + x^312 + x^310 + x^308 + x^305 + x^304 + x^303 + x^299 + x^296 + x^295 + x^294 + x^290 + x^289 + x^288 + x^285 + x^284 + x^281 + x^280 + x^275 + x^274 + x^273 + x^271 + x^268 + x^266 + x^264 + x^263 + x^262 + x^261 + x^260 + x^258 + x^256 + x^255 + x^254 + x^251 + x^245 + x^240 + x^237 + x^236 + x^231 + x^230 + x^229 + x^228 + x^223 + x^221 + x^219 + x^218 + x^215 + x^210 + x^208 + x^207 + x^206 + x^204 + x^202 + x^197 + x^196 + x^195 + x^194 + x^193 + x^192 + x^187 + x^186 + x^184 + x^183 + x^182 + x^180 + x^178 + x^177 + x^175 + x^174 + x^169 + x^168 + x^166 + x^165 + x^163 + x^160 + x^159 + x^156 + x^155 + x^152 + x^150 + x^145 + x^140 + x^138 + x^137 + x^136 + x^135 + x^134 + x^133 + x^131 + x^128 + x^127 + x^126 + x^122 + x^121 + x^118 + x^117 + x^114 + x^109 + x^105 + x^102 + x^101 + x^100 + x^99 + x^96 + x^94 + x^93 + x^91 + x^90 + x^89 + x^88 + x^87 + x^81 + x^79 + x^76 + x^74 + x^71 + x^70 + x^64 + x^63 + x^61 + x^59 + x^56 + x^55 + x^49 + x^47 + x^46 + x^44 + x^43 + x^40 + x^35 + x^34 + x^33 + x^31 + x^28 + x^26 + x^23 + x^21 + x^18 + x^13 + 1
+
+36-23-57 387 x^928 + x^898 + x^897 + x^890 + x^870 + x^860 + x^859 + x^854 + x^853 + x^846 + x^836 + x^835 + x^824 + x^816 + x^810 + x^809 + x^808 + x^804 + x^802 + x^792 + x^791 + x^785 + x^784 + x^780 + x^778 + x^777 + x^776 + x^775 + x^774 + x^773 + x^765 + x^755 + x^753 + x^748 + x^747 + x^744 + x^742 + x^733 + x^732 + x^728 + x^725 + x^724 + x^721 + x^716 + x^714 + x^713 + x^703 + x^701 + x^700 + x^699 + x^697 + x^693 + x^692 + x^691 + x^690 + x^689 + x^680 + x^679 + x^675 + x^673 + x^672 + x^666 + x^663 + x^662 + x^661 + x^658 + x^656 + x^655 + x^653 + x^652 + x^649 + x^647 + x^645 + x^642 + x^641 + x^639 + x^638 + x^637 + x^633 + x^630 + x^629 + x^625 + x^620 + x^619 + x^614 + x^613 + x^612 + x^611 + x^610 + x^606 + x^605 + x^604 + x^603 + x^601 + x^600 + x^599 + x^597 + x^593 + x^591 + x^589 + x^587 + x^586 + x^584 + x^583 + x^581 + x^579 + x^576 + x^572 + x^571 + x^566 + x^565 + x^563 + x^559 + x^554 + x^552 + x^549 + x^548 + x^545 + x^544 + x^543 + x^540 + x^535 + x^534 + x^533 + x^531 + x^529 + x^524 + x^522 + x^517 + x^516 + x^513 + x^512 + x^511 + x^509 + x^507 + x^506 + x^505 + x^503 + x^502 + x^496 + x^495 + x^494 + x^492 + x^491 + x^490 + x^489 + x^487 + x^478 + x^477 + x^475 + x^474 + x^472 + x^471 + x^470 + x^469 + x^466 + x^463 + x^461 + x^459 + x^458 + x^457 + x^456 + x^455 + x^454 + x^453 + x^452 + x^448 + x^447 + x^446 + x^444 + x^442 + x^440 + x^439 + x^438 + x^437 + x^434 + x^431 + x^428 + x^427 + x^426 + x^425 + x^424 + x^423 + x^414 + x^409 + x^408 + x^407 + x^403 + x^401 + x^400 + x^396 + x^395 + x^394 + x^390 + x^389 + x^388 + x^387 + x^386 + x^379 + x^378 + x^377 + x^375 + x^374 + x^370 + x^366 + x^360 + x^359 + x^358 + x^357 + x^356 + x^355 + x^353 + x^351 + x^350 + x^349 + x^348 + x^347 + x^345 + x^343 + x^342 + x^341 + x^340 + x^339 + x^338 + x^336 + x^335 + x^330 + x^329 + x^327 + x^325 + x^324 + x^323 + x^322 + x^319 + x^318 + x^315 + x^313 + x^309 + x^305 + x^304 + x^302 + x^300 + x^298 + x^296 + x^291 + x^289 + x^286 + x^285 + x^284 + x^283 + x^282 + x^281 + x^279 + x^275 + x^274 + x^272 + x^271 + x^265 + x^264 + x^263 + x^259 + x^258 + x^257 + x^253 + x^252 + x^249 + x^246 + x^245 + x^244 + x^242 + x^239 + x^233 + x^232 + x^231 + x^230 + x^229 + x^228 + x^221 + x^217 + x^216 + x^212 + x^211 + x^209 + x^208 + x^205 + x^202 + x^201 + x^200 + x^199 + x^198 + x^197 + x^196 + x^195 + x^193 + x^192 + x^191 + x^189 + x^187 + x^186 + x^183 + x^182 + x^181 + x^177 + x^174 + x^172 + x^170 + x^166 + x^164 + x^163 + x^162 + x^160 + x^156 + x^155 + x^152 + x^151 + x^147 + x^144 + x^143 + x^142 + x^141 + x^138 + x^137 + x^135 + x^133 + x^130 + x^129 + x^126 + x^125 + x^123 + x^121 + x^120 + x^117 + x^114 + x^112 + x^107 + x^106 + x^103 + x^102 + x^100 + x^98 + x^95 + x^94 + x^93 + x^91 + x^90 + x^89 + x^87 + x^85 + x^84 + x^82 + x^81 + x^80 + x^78 + x^76 + x^75 + x^71 + x^70 + x^69 + x^68 + x^66 + x^65 + x^61 + x^60 + x^59 + x^58 + x^56 + x^55 + x^51 + x^49 + x^48 + x^46 + x^44 + x^42 + x^36 + x^34 + x^33 + x^32 + x^29 + x^24 + x^23 + x^20 + x^14 + x^13 + x^12 + x^11 + x^10 + 1
+
+44-4-19 389 x^928 + x^898 + x^874 + x^870 + x^836 + x^832 + x^824 + x^812 + x^809 + x^802 + x^794 + x^793 + x^789 + x^785 + x^781 + x^766 + x^764 + x^763 + x^762 + x^759 + x^758 + x^751 + x^750 + x^746 + x^744 + x^742 + x^738 + x^734 + x^733 + x^732 + x^729 + x^721 + x^719 + x^716 + x^715 + x^714 + x^713 + x^710 + x^706 + x^705 + x^703 + x^702 + x^700 + x^699 + x^698 + x^696 + x^693 + x^691 + x^690 + x^689 + x^688 + x^684 + x^680 + x^678 + x^677 + x^674 + x^672 + x^669 + x^667 + x^665 + x^663 + x^662 + x^660 + x^659 + x^658 + x^656 + x^652 + x^651 + x^649 + x^646 + x^645 + x^642 + x^641 + x^640 + x^633 + x^632 + x^630 + x^627 + x^626 + x^622 + x^617 + x^612 + x^611 + x^610 + x^606 + x^605 + x^604 + x^603 + x^602 + x^601 + x^599 + x^597 + x^596 + x^594 + x^593 + x^592 + x^591 + x^582 + x^581 + x^580 + x^578 + x^577 + x^575 + x^574 + x^573 + x^568 + x^567 + x^564 + x^560 + x^559 + x^558 + x^556 + x^554 + x^550 + x^548 + x^547 + x^545 + x^544 + x^541 + x^540 + x^539 + x^538 + x^536 + x^535 + x^534 + x^532 + x^531 + x^529 + x^523 + x^521 + x^518 + x^517 + x^516 + x^514 + x^511 + x^510 + x^508 + x^507 + x^505 + x^504 + x^499 + x^498 + x^495 + x^494 + x^492 + x^491 + x^489 + x^488 + x^487 + x^486 + x^484 + x^483 + x^482 + x^481 + x^478 + x^477 + x^476 + x^475 + x^471 + x^470 + x^468 + x^465 + x^464 + x^460 + x^459 + x^455 + x^454 + x^453 + x^451 + x^445 + x^438 + x^434 + x^432 + x^431 + x^430 + x^429 + x^428 + x^427 + x^424 + x^423 + x^419 + x^418 + x^417 + x^416 + x^415 + x^413 + x^411 + x^409 + x^408 + x^406 + x^405 + x^404 + x^403 + x^402 + x^400 + x^397 + x^395 + x^390 + x^389 + x^387 + x^386 + x^385 + x^384 + x^382 + x^380 + x^379 + x^377 + x^376 + x^374 + x^373 + x^370 + x^369 + x^366 + x^365 + x^364 + x^362 + x^360 + x^359 + x^357 + x^356 + x^355 + x^354 + x^352 + x^349 + x^345 + x^342 + x^341 + x^340 + x^338 + x^334 + x^333 + x^326 + x^324 + x^322 + x^321 + x^319 + x^318 + x^317 + x^315 + x^312 + x^311 + x^309 + x^305 + x^304 + x^302 + x^298 + x^297 + x^296 + x^294 + x^293 + x^290 + x^289 + x^287 + x^286 + x^285 + x^279 + x^277 + x^275 + x^273 + x^268 + x^265 + x^264 + x^263 + x^260 + x^258 + x^254 + x^251 + x^249 + x^248 + x^247 + x^245 + x^244 + x^242 + x^241 + x^240 + x^239 + x^232 + x^229 + x^226 + x^225 + x^223 + x^222 + x^220 + x^219 + x^218 + x^215 + x^214 + x^213 + x^212 + x^210 + x^209 + x^206 + x^203 + x^202 + x^199 + x^197 + x^195 + x^194 + x^192 + x^191 + x^189 + x^188 + x^185 + x^184 + x^181 + x^177 + x^176 + x^175 + x^174 + x^172 + x^171 + x^170 + x^169 + x^167 + x^164 + x^162 + x^160 + x^159 + x^157 + x^156 + x^154 + x^153 + x^152 + x^150 + x^148 + x^145 + x^144 + x^139 + x^138 + x^137 + x^136 + x^133 + x^126 + x^124 + x^123 + x^122 + x^121 + x^120 + x^119 + x^113 + x^111 + x^108 + x^105 + x^104 + x^103 + x^102 + x^101 + x^98 + x^97 + x^96 + x^95 + x^92 + x^86 + x^85 + x^83 + x^81 + x^80 + x^77 + x^74 + x^73 + x^72 + x^71 + x^70 + x^68 + x^67 + x^66 + x^64 + x^62 + x^61 + x^60 + x^59 + x^57 + x^53 + x^51 + x^43 + x^41 + x^40 + x^39 + x^35 + x^30 + x^29 + x^27 + x^26 + x^24 + x^20 + x^18 + x^14 + x^6 + 1
+
+8-3-35 389 x^928 + x^898 + x^895 + x^870 + x^865 + x^835 + x^832 + x^824 + x^821 + x^812 + x^810 + x^808 + x^807 + x^805 + x^804 + x^794 + x^791 + x^788 + x^778 + x^777 + x^774 + x^772 + x^771 + x^763 + x^755 + x^752 + x^750 + x^747 + x^746 + x^742 + x^739 + x^733 + x^731 + x^728 + x^725 + x^722 + x^721 + x^720 + x^719 + x^716 + x^714 + x^713 + x^712 + x^711 + x^708 + x^705 + x^704 + x^701 + x^700 + x^698 + x^695 + x^694 + x^692 + x^689 + x^683 + x^680 + x^675 + x^674 + x^670 + x^668 + x^667 + x^664 + x^662 + x^661 + x^658 + x^656 + x^654 + x^651 + x^650 + x^645 + x^643 + x^640 + x^639 + x^637 + x^635 + x^634 + x^633 + x^631 + x^630 + x^628 + x^621 + x^620 + x^616 + x^615 + x^614 + x^613 + x^608 + x^605 + x^604 + x^602 + x^601 + x^598 + x^597 + x^591 + x^590 + x^588 + x^587 + x^581 + x^579 + x^578 + x^577 + x^576 + x^573 + x^572 + x^571 + x^570 + x^569 + x^568 + x^566 + x^564 + x^563 + x^562 + x^559 + x^557 + x^553 + x^550 + x^549 + x^547 + x^546 + x^540 + x^537 + x^536 + x^534 + x^530 + x^527 + x^526 + x^525 + x^524 + x^522 + x^521 + x^520 + x^519 + x^518 + x^510 + x^509 + x^505 + x^504 + x^498 + x^496 + x^493 + x^492 + x^490 + x^489 + x^488 + x^487 + x^484 + x^483 + x^482 + x^481 + x^480 + x^479 + x^477 + x^475 + x^474 + x^472 + x^470 + x^468 + x^465 + x^464 + x^463 + x^461 + x^458 + x^457 + x^455 + x^454 + x^453 + x^452 + x^451 + x^450 + x^448 + x^447 + x^445 + x^441 + x^440 + x^437 + x^435 + x^434 + x^433 + x^432 + x^431 + x^425 + x^421 + x^418 + x^415 + x^413 + x^412 + x^411 + x^410 + x^409 + x^408 + x^404 + x^403 + x^402 + x^399 + x^398 + x^394 + x^393 + x^391 + x^390 + x^389 + x^384 + x^383 + x^381 + x^380 + x^379 + x^378 + x^375 + x^374 + x^372 + x^370 + x^369 + x^367 + x^365 + x^364 + x^363 + x^362 + x^358 + x^357 + x^355 + x^354 + x^353 + x^351 + x^349 + x^347 + x^343 + x^342 + x^338 + x^337 + x^336 + x^334 + x^332 + x^329 + x^328 + x^327 + x^326 + x^323 + x^321 + x^320 + x^319 + x^317 + x^315 + x^311 + x^308 + x^305 + x^304 + x^303 + x^300 + x^298 + x^294 + x^293 + x^292 + x^290 + x^283 + x^281 + x^280 + x^279 + x^276 + x^274 + x^273 + x^269 + x^268 + x^267 + x^266 + x^264 + x^263 + x^259 + x^256 + x^248 + x^247 + x^246 + x^245 + x^244 + x^243 + x^242 + x^241 + x^240 + x^239 + x^235 + x^234 + x^231 + x^228 + x^227 + x^226 + x^225 + x^224 + x^220 + x^219 + x^218 + x^217 + x^216 + x^213 + x^211 + x^210 + x^206 + x^203 + x^200 + x^197 + x^196 + x^195 + x^193 + x^192 + x^191 + x^185 + x^184 + x^180 + x^178 + x^176 + x^175 + x^173 + x^170 + x^169 + x^167 + x^166 + x^165 + x^164 + x^162 + x^161 + x^160 + x^159 + x^154 + x^153 + x^152 + x^147 + x^141 + x^140 + x^138 + x^135 + x^133 + x^132 + x^131 + x^129 + x^127 + x^126 + x^125 + x^119 + x^115 + x^112 + x^111 + x^108 + x^106 + x^99 + x^97 + x^95 + x^94 + x^93 + x^92 + x^91 + x^89 + x^87 + x^84 + x^82 + x^81 + x^78 + x^76 + x^74 + x^69 + x^68 + x^67 + x^65 + x^63 + x^61 + x^58 + x^57 + x^56 + x^55 + x^54 + x^53 + x^51 + x^49 + x^48 + x^47 + x^46 + x^43 + x^40 + x^39 + x^35 + x^34 + x^32 + x^30 + x^28 + x^27 + x^25 + x^24 + x^21 + x^20 + x^15 + x^14 + x^10 + 1
+
+1-12-46 393 x^928 + x^898 + x^896 + x^870 + x^866 + x^836 + x^834 + x^828 + x^826 + x^808 + x^806 + x^804 + x^802 + x^796 + x^794 + x^778 + x^774 + x^767 + x^766 + x^758 + x^756 + x^744 + x^742 + x^740 + x^738 + x^736 + x^732 + x^731 + x^730 + x^727 + x^726 + x^718 + x^712 + x^710 + x^708 + x^707 + x^706 + x^704 + x^703 + x^701 + x^700 + x^699 + x^698 + x^697 + x^696 + x^695 + x^692 + x^686 + x^685 + x^680 + x^676 + x^672 + x^669 + x^668 + x^665 + x^664 + x^662 + x^661 + x^657 + x^656 + x^655 + x^653 + x^647 + x^646 + x^643 + x^640 + x^639 + x^638 + x^635 + x^628 + x^626 + x^623 + x^622 + x^621 + x^615 + x^612 + x^610 + x^609 + x^608 + x^607 + x^605 + x^604 + x^603 + x^602 + x^600 + x^599 + x^598 + x^597 + x^590 + x^589 + x^587 + x^586 + x^584 + x^583 + x^582 + x^581 + x^579 + x^578 + x^577 + x^576 + x^574 + x^573 + x^571 + x^567 + x^563 + x^561 + x^560 + x^559 + x^556 + x^554 + x^550 + x^548 + x^545 + x^544 + x^542 + x^535 + x^530 + x^529 + x^528 + x^526 + x^524 + x^522 + x^521 + x^519 + x^517 + x^516 + x^515 + x^512 + x^508 + x^507 + x^506 + x^505 + x^504 + x^499 + x^498 + x^497 + x^496 + x^495 + x^494 + x^489 + x^488 + x^487 + x^486 + x^484 + x^483 + x^481 + x^477 + x^476 + x^475 + x^474 + x^473 + x^471 + x^469 + x^466 + x^465 + x^464 + x^461 + x^460 + x^459 + x^457 + x^455 + x^452 + x^451 + x^449 + x^448 + x^447 + x^446 + x^445 + x^443 + x^442 + x^440 + x^439 + x^438 + x^433 + x^427 + x^425 + x^424 + x^422 + x^421 + x^419 + x^416 + x^415 + x^414 + x^413 + x^412 + x^408 + x^405 + x^404 + x^403 + x^402 + x^399 + x^398 + x^397 + x^396 + x^394 + x^393 + x^392 + x^391 + x^389 + x^388 + x^387 + x^386 + x^384 + x^381 + x^380 + x^376 + x^375 + x^374 + x^373 + x^366 + x^363 + x^362 + x^359 + x^358 + x^357 + x^356 + x^355 + x^353 + x^352 + x^351 + x^347 + x^344 + x^343 + x^342 + x^341 + x^339 + x^337 + x^336 + x^333 + x^331 + x^329 + x^328 + x^327 + x^326 + x^325 + x^321 + x^320 + x^317 + x^316 + x^315 + x^312 + x^311 + x^310 + x^307 + x^306 + x^303 + x^300 + x^298 + x^296 + x^295 + x^292 + x^291 + x^290 + x^287 + x^283 + x^279 + x^278 + x^277 + x^276 + x^273 + x^272 + x^271 + x^270 + x^269 + x^263 + x^262 + x^257 + x^256 + x^255 + x^254 + x^252 + x^249 + x^247 + x^245 + x^242 + x^241 + x^240 + x^235 + x^234 + x^233 + x^232 + x^231 + x^230 + x^229 + x^227 + x^225 + x^224 + x^223 + x^222 + x^219 + x^218 + x^217 + x^216 + x^215 + x^214 + x^213 + x^211 + x^206 + x^205 + x^203 + x^200 + x^199 + x^196 + x^194 + x^191 + x^186 + x^185 + x^183 + x^180 + x^179 + x^177 + x^176 + x^175 + x^174 + x^172 + x^171 + x^170 + x^169 + x^167 + x^160 + x^159 + x^158 + x^157 + x^156 + x^155 + x^154 + x^152 + x^146 + x^145 + x^144 + x^143 + x^142 + x^141 + x^139 + x^138 + x^137 + x^134 + x^133 + x^129 + x^126 + x^125 + x^124 + x^122 + x^121 + x^119 + x^118 + x^117 + x^113 + x^111 + x^110 + x^109 + x^108 + x^99 + x^98 + x^97 + x^95 + x^93 + x^92 + x^90 + x^85 + x^78 + x^76 + x^75 + x^70 + x^69 + x^65 + x^64 + x^63 + x^62 + x^59 + x^56 + x^54 + x^53 + x^51 + x^50 + x^49 + x^45 + x^44 + x^42 + x^41 + x^39 + x^36 + x^35 + x^34 + x^32 + x^31 + x^30 + x^23 + x^20 + x^16 + x^13 + x^12 + 1
+
+21-29-14 393 x^928 + x^898 + x^885 + x^870 + x^858 + x^856 + x^855 + x^831 + x^829 + x^828 + x^826 + x^815 + x^813 + x^812 + x^808 + x^804 + x^802 + x^801 + x^799 + x^798 + x^796 + x^788 + x^785 + x^778 + x^777 + x^775 + x^774 + x^772 + x^769 + x^768 + x^766 + x^765 + x^758 + x^752 + x^748 + x^747 + x^742 + x^741 + x^739 + x^738 + x^736 + x^735 + x^732 + x^728 + x^726 + x^725 + x^721 + x^718 + x^717 + x^714 + x^712 + x^709 + x^708 + x^706 + x^705 + x^702 + x^701 + x^699 + x^698 + x^694 + x^691 + x^687 + x^685 + x^684 + x^682 + x^681 + x^680 + x^679 + x^676 + x^675 + x^674 + x^671 + x^667 + x^664 + x^658 + x^657 + x^655 + x^653 + x^652 + x^650 + x^649 + x^648 + x^647 + x^646 + x^644 + x^641 + x^640 + x^637 + x^635 + x^632 + x^627 + x^625 + x^623 + x^622 + x^619 + x^618 + x^617 + x^613 + x^610 + x^608 + x^601 + x^595 + x^593 + x^592 + x^586 + x^585 + x^583 + x^582 + x^577 + x^572 + x^571 + x^570 + x^568 + x^565 + x^563 + x^561 + x^559 + x^557 + x^555 + x^553 + x^550 + x^548 + x^545 + x^544 + x^538 + x^537 + x^534 + x^532 + x^529 + x^526 + x^525 + x^521 + x^520 + x^518 + x^512 + x^511 + x^510 + x^508 + x^507 + x^503 + x^501 + x^500 + x^499 + x^498 + x^497 + x^496 + x^494 + x^489 + x^486 + x^485 + x^481 + x^480 + x^477 + x^476 + x^475 + x^466 + x^464 + x^462 + x^461 + x^460 + x^459 + x^458 + x^454 + x^452 + x^451 + x^449 + x^447 + x^446 + x^444 + x^441 + x^440 + x^439 + x^433 + x^431 + x^430 + x^429 + x^427 + x^425 + x^424 + x^422 + x^416 + x^414 + x^412 + x^408 + x^406 + x^403 + x^402 + x^401 + x^399 + x^398 + x^395 + x^393 + x^390 + x^389 + x^387 + x^386 + x^385 + x^384 + x^383 + x^381 + x^380 + x^378 + x^375 + x^374 + x^372 + x^371 + x^370 + x^368 + x^367 + x^362 + x^361 + x^358 + x^356 + x^354 + x^353 + x^351 + x^350 + x^347 + x^346 + x^343 + x^340 + x^339 + x^337 + x^335 + x^331 + x^330 + x^329 + x^328 + x^326 + x^325 + x^323 + x^322 + x^319 + x^318 + x^316 + x^315 + x^311 + x^310 + x^309 + x^308 + x^306 + x^304 + x^303 + x^298 + x^296 + x^295 + x^294 + x^292 + x^291 + x^290 + x^289 + x^287 + x^284 + x^281 + x^280 + x^276 + x^274 + x^272 + x^271 + x^270 + x^268 + x^267 + x^259 + x^258 + x^257 + x^256 + x^255 + x^254 + x^249 + x^248 + x^247 + x^246 + x^244 + x^243 + x^241 + x^240 + x^236 + x^234 + x^233 + x^232 + x^229 + x^224 + x^221 + x^220 + x^217 + x^216 + x^215 + x^213 + x^211 + x^210 + x^208 + x^207 + x^200 + x^199 + x^198 + x^197 + x^196 + x^195 + x^193 + x^192 + x^191 + x^190 + x^185 + x^184 + x^183 + x^181 + x^179 + x^176 + x^173 + x^170 + x^169 + x^168 + x^164 + x^162 + x^160 + x^157 + x^155 + x^154 + x^152 + x^151 + x^150 + x^149 + x^146 + x^144 + x^143 + x^142 + x^140 + x^136 + x^134 + x^132 + x^130 + x^129 + x^128 + x^126 + x^123 + x^120 + x^117 + x^112 + x^111 + x^108 + x^107 + x^105 + x^103 + x^100 + x^99 + x^96 + x^95 + x^91 + x^90 + x^89 + x^87 + x^86 + x^84 + x^83 + x^81 + x^79 + x^78 + x^76 + x^69 + x^68 + x^67 + x^66 + x^62 + x^61 + x^57 + x^56 + x^55 + x^53 + x^52 + x^51 + x^49 + x^48 + x^46 + x^43 + x^40 + x^38 + x^37 + x^36 + x^35 + x^34 + x^33 + x^31 + x^30 + x^29 + x^28 + x^27 + x^26 + x^24 + x^21 + x^20 + x^17 + x^13 + 1
+
+37-29-44 393 x^928 + x^898 + x^885 + x^870 + x^858 + x^856 + x^855 + x^831 + x^829 + x^828 + x^826 + x^815 + x^813 + x^812 + x^808 + x^804 + x^802 + x^801 + x^799 + x^798 + x^796 + x^788 + x^785 + x^778 + x^777 + x^775 + x^774 + x^772 + x^769 + x^768 + x^766 + x^765 + x^758 + x^752 + x^748 + x^747 + x^742 + x^741 + x^739 + x^738 + x^736 + x^735 + x^732 + x^728 + x^726 + x^725 + x^721 + x^718 + x^717 + x^714 + x^712 + x^709 + x^708 + x^706 + x^705 + x^702 + x^701 + x^699 + x^698 + x^694 + x^691 + x^687 + x^685 + x^684 + x^682 + x^681 + x^680 + x^679 + x^676 + x^675 + x^674 + x^671 + x^667 + x^664 + x^658 + x^657 + x^655 + x^653 + x^652 + x^650 + x^649 + x^648 + x^647 + x^646 + x^644 + x^641 + x^640 + x^637 + x^635 + x^632 + x^627 + x^625 + x^623 + x^622 + x^619 + x^618 + x^617 + x^613 + x^610 + x^608 + x^601 + x^595 + x^593 + x^592 + x^586 + x^585 + x^583 + x^582 + x^577 + x^572 + x^571 + x^570 + x^568 + x^565 + x^563 + x^561 + x^559 + x^557 + x^555 + x^553 + x^550 + x^548 + x^545 + x^544 + x^538 + x^537 + x^534 + x^532 + x^529 + x^526 + x^525 + x^521 + x^520 + x^518 + x^512 + x^511 + x^510 + x^508 + x^507 + x^503 + x^501 + x^500 + x^499 + x^498 + x^497 + x^496 + x^494 + x^489 + x^486 + x^485 + x^481 + x^480 + x^477 + x^476 + x^475 + x^466 + x^464 + x^462 + x^461 + x^460 + x^459 + x^458 + x^454 + x^452 + x^451 + x^449 + x^447 + x^446 + x^444 + x^441 + x^440 + x^439 + x^433 + x^431 + x^430 + x^429 + x^427 + x^425 + x^424 + x^422 + x^416 + x^414 + x^412 + x^408 + x^406 + x^403 + x^402 + x^401 + x^399 + x^398 + x^395 + x^393 + x^390 + x^389 + x^387 + x^386 + x^385 + x^384 + x^383 + x^381 + x^380 + x^378 + x^375 + x^374 + x^372 + x^371 + x^370 + x^368 + x^367 + x^362 + x^361 + x^358 + x^356 + x^354 + x^353 + x^351 + x^350 + x^347 + x^346 + x^343 + x^340 + x^339 + x^337 + x^335 + x^331 + x^330 + x^329 + x^328 + x^326 + x^325 + x^323 + x^322 + x^319 + x^318 + x^316 + x^315 + x^311 + x^310 + x^309 + x^308 + x^306 + x^304 + x^303 + x^298 + x^296 + x^295 + x^294 + x^292 + x^291 + x^290 + x^289 + x^287 + x^284 + x^281 + x^280 + x^276 + x^274 + x^272 + x^271 + x^270 + x^268 + x^267 + x^259 + x^258 + x^257 + x^256 + x^255 + x^254 + x^249 + x^248 + x^247 + x^246 + x^244 + x^243 + x^241 + x^240 + x^236 + x^234 + x^233 + x^232 + x^229 + x^224 + x^221 + x^220 + x^217 + x^216 + x^215 + x^213 + x^211 + x^210 + x^208 + x^207 + x^200 + x^199 + x^198 + x^197 + x^196 + x^195 + x^193 + x^192 + x^191 + x^190 + x^185 + x^184 + x^183 + x^181 + x^179 + x^176 + x^173 + x^170 + x^169 + x^168 + x^164 + x^162 + x^160 + x^157 + x^155 + x^154 + x^152 + x^151 + x^150 + x^149 + x^146 + x^144 + x^143 + x^142 + x^140 + x^136 + x^134 + x^132 + x^130 + x^129 + x^128 + x^126 + x^123 + x^120 + x^117 + x^112 + x^111 + x^108 + x^107 + x^105 + x^103 + x^100 + x^99 + x^96 + x^95 + x^91 + x^90 + x^89 + x^87 + x^86 + x^84 + x^83 + x^81 + x^79 + x^78 + x^76 + x^69 + x^68 + x^67 + x^66 + x^62 + x^61 + x^57 + x^56 + x^55 + x^53 + x^52 + x^51 + x^49 + x^48 + x^46 + x^43 + x^40 + x^38 + x^37 + x^36 + x^35 + x^34 + x^33 + x^31 + x^30 + x^29 + x^28 + x^27 + x^26 + x^24 + x^21 + x^20 + x^17 + x^13 + 1
+
+7-48-42 393 x^928 + x^898 + x^892 + x^870 + x^862 + x^843 + x^820 + x^813 + x^808 + x^800 + x^794 + x^784 + x^783 + x^780 + x^778 + x^774 + x^771 + x^770 + x^767 + x^760 + x^757 + x^753 + x^750 + x^748 + x^743 + x^741 + x^740 + x^737 + x^731 + x^727 + x^724 + x^723 + x^718 + x^713 + x^707 + x^705 + x^704 + x^701 + x^700 + x^697 + x^695 + x^693 + x^688 + x^684 + x^683 + x^682 + x^681 + x^678 + x^677 + x^674 + x^671 + x^669 + x^667 + x^664 + x^663 + x^660 + x^653 + x^652 + x^651 + x^650 + x^649 + x^645 + x^644 + x^641 + x^639 + x^638 + x^637 + x^634 + x^633 + x^630 + x^628 + x^625 + x^623 + x^621 + x^620 + x^619 + x^615 + x^612 + x^611 + x^608 + x^607 + x^605 + x^604 + x^603 + x^599 + x^595 + x^593 + x^585 + x^584 + x^581 + x^580 + x^578 + x^577 + x^575 + x^573 + x^572 + x^569 + x^568 + x^565 + x^564 + x^563 + x^561 + x^558 + x^557 + x^551 + x^550 + x^548 + x^547 + x^544 + x^538 + x^537 + x^534 + x^533 + x^532 + x^530 + x^529 + x^524 + x^522 + x^521 + x^519 + x^518 + x^516 + x^515 + x^514 + x^513 + x^512 + x^510 + x^508 + x^506 + x^505 + x^502 + x^501 + x^500 + x^499 + x^496 + x^493 + x^492 + x^491 + x^488 + x^487 + x^483 + x^482 + x^481 + x^479 + x^478 + x^476 + x^475 + x^474 + x^473 + x^472 + x^471 + x^470 + x^469 + x^467 + x^463 + x^460 + x^458 + x^453 + x^452 + x^451 + x^447 + x^446 + x^445 + x^439 + x^435 + x^434 + x^433 + x^432 + x^431 + x^430 + x^428 + x^427 + x^425 + x^421 + x^420 + x^419 + x^417 + x^415 + x^413 + x^412 + x^410 + x^407 + x^406 + x^405 + x^404 + x^402 + x^400 + x^397 + x^395 + x^394 + x^393 + x^392 + x^391 + x^390 + x^388 + x^385 + x^381 + x^378 + x^377 + x^376 + x^374 + x^373 + x^370 + x^369 + x^368 + x^366 + x^365 + x^364 + x^363 + x^361 + x^358 + x^356 + x^355 + x^354 + x^351 + x^350 + x^348 + x^347 + x^344 + x^341 + x^340 + x^337 + x^335 + x^334 + x^329 + x^326 + x^325 + x^324 + x^322 + x^321 + x^319 + x^318 + x^314 + x^312 + x^311 + x^310 + x^309 + x^308 + x^307 + x^303 + x^302 + x^301 + x^298 + x^293 + x^292 + x^291 + x^288 + x^281 + x^280 + x^279 + x^278 + x^275 + x^271 + x^270 + x^267 + x^265 + x^264 + x^263 + x^262 + x^261 + x^260 + x^259 + x^258 + x^257 + x^256 + x^253 + x^252 + x^251 + x^250 + x^249 + x^248 + x^247 + x^244 + x^243 + x^242 + x^240 + x^237 + x^236 + x^233 + x^227 + x^226 + x^224 + x^222 + x^221 + x^220 + x^219 + x^218 + x^217 + x^216 + x^213 + x^212 + x^210 + x^208 + x^207 + x^206 + x^205 + x^202 + x^201 + x^200 + x^197 + x^195 + x^194 + x^193 + x^192 + x^191 + x^190 + x^189 + x^186 + x^184 + x^183 + x^182 + x^181 + x^178 + x^177 + x^176 + x^170 + x^168 + x^167 + x^166 + x^162 + x^159 + x^157 + x^149 + x^148 + x^147 + x^143 + x^141 + x^139 + x^138 + x^136 + x^135 + x^131 + x^127 + x^121 + x^119 + x^117 + x^114 + x^110 + x^109 + x^107 + x^103 + x^99 + x^98 + x^96 + x^95 + x^94 + x^92 + x^90 + x^89 + x^88 + x^87 + x^86 + x^85 + x^84 + x^82 + x^80 + x^79 + x^78 + x^77 + x^76 + x^74 + x^71 + x^69 + x^68 + x^66 + x^64 + x^62 + x^61 + x^58 + x^57 + x^53 + x^50 + x^46 + x^44 + x^43 + x^42 + x^41 + x^40 + x^37 + x^35 + x^34 + x^32 + x^31 + x^29 + x^27 + x^26 + x^25 + x^22 + x^20 + x^16 + x^12 + x^10 + 1
+
+57-51-22 397 x^928 + x^898 + x^895 + x^870 + x^866 + x^865 + x^862 + x^860 + x^857 + x^835 + x^833 + x^832 + x^828 + x^822 + x^819 + x^810 + x^808 + x^805 + x^797 + x^796 + x^791 + x^790 + x^789 + x^786 + x^784 + x^782 + x^781 + x^778 + x^777 + x^773 + x^767 + x^766 + x^762 + x^757 + x^752 + x^743 + x^742 + x^737 + x^734 + x^717 + x^715 + x^713 + x^708 + x^707 + x^706 + x^705 + x^703 + x^702 + x^701 + x^698 + x^696 + x^690 + x^688 + x^685 + x^683 + x^682 + x^680 + x^677 + x^673 + x^671 + x^668 + x^667 + x^666 + x^663 + x^662 + x^661 + x^656 + x^654 + x^653 + x^649 + x^647 + x^646 + x^645 + x^643 + x^637 + x^635 + x^632 + x^630 + x^629 + x^627 + x^626 + x^625 + x^624 + x^622 + x^619 + x^613 + x^610 + x^608 + x^602 + x^597 + x^594 + x^593 + x^591 + x^590 + x^587 + x^586 + x^584 + x^583 + x^582 + x^580 + x^577 + x^575 + x^574 + x^573 + x^570 + x^569 + x^568 + x^562 + x^556 + x^553 + x^552 + x^551 + x^550 + x^547 + x^546 + x^545 + x^543 + x^541 + x^539 + x^538 + x^535 + x^534 + x^533 + x^528 + x^527 + x^526 + x^524 + x^522 + x^521 + x^515 + x^512 + x^509 + x^505 + x^503 + x^502 + x^501 + x^500 + x^499 + x^498 + x^497 + x^493 + x^491 + x^483 + x^480 + x^477 + x^474 + x^473 + x^472 + x^471 + x^470 + x^468 + x^467 + x^463 + x^459 + x^458 + x^457 + x^455 + x^453 + x^452 + x^451 + x^448 + x^447 + x^446 + x^445 + x^444 + x^443 + x^440 + x^439 + x^436 + x^435 + x^434 + x^432 + x^430 + x^429 + x^428 + x^427 + x^426 + x^423 + x^422 + x^421 + x^420 + x^417 + x^416 + x^415 + x^414 + x^413 + x^411 + x^410 + x^407 + x^406 + x^403 + x^401 + x^400 + x^391 + x^390 + x^387 + x^386 + x^385 + x^381 + x^380 + x^379 + x^377 + x^374 + x^373 + x^370 + x^369 + x^362 + x^359 + x^357 + x^356 + x^355 + x^354 + x^349 + x^346 + x^345 + x^344 + x^343 + x^340 + x^339 + x^338 + x^337 + x^336 + x^334 + x^331 + x^330 + x^328 + x^323 + x^322 + x^321 + x^319 + x^318 + x^317 + x^316 + x^314 + x^313 + x^312 + x^311 + x^310 + x^305 + x^303 + x^299 + x^295 + x^294 + x^293 + x^290 + x^289 + x^286 + x^285 + x^284 + x^281 + x^280 + x^278 + x^275 + x^272 + x^271 + x^269 + x^267 + x^266 + x^263 + x^262 + x^261 + x^260 + x^258 + x^257 + x^256 + x^255 + x^254 + x^253 + x^252 + x^251 + x^247 + x^246 + x^241 + x^240 + x^239 + x^238 + x^236 + x^233 + x^232 + x^230 + x^228 + x^224 + x^223 + x^220 + x^216 + x^215 + x^213 + x^212 + x^211 + x^208 + x^206 + x^205 + x^204 + x^201 + x^199 + x^197 + x^195 + x^194 + x^193 + x^191 + x^189 + x^188 + x^187 + x^186 + x^185 + x^184 + x^182 + x^179 + x^178 + x^176 + x^172 + x^171 + x^170 + x^169 + x^168 + x^167 + x^166 + x^163 + x^162 + x^161 + x^160 + x^157 + x^156 + x^155 + x^153 + x^152 + x^148 + x^145 + x^142 + x^140 + x^139 + x^137 + x^134 + x^133 + x^131 + x^123 + x^119 + x^118 + x^114 + x^112 + x^111 + x^110 + x^108 + x^107 + x^105 + x^104 + x^102 + x^99 + x^98 + x^95 + x^94 + x^93 + x^89 + x^88 + x^86 + x^84 + x^82 + x^80 + x^78 + x^76 + x^73 + x^71 + x^70 + x^68 + x^67 + x^66 + x^64 + x^62 + x^60 + x^59 + x^57 + x^53 + x^52 + x^49 + x^48 + x^47 + x^46 + x^40 + x^37 + x^36 + x^35 + x^34 + x^32 + x^31 + x^28 + x^26 + x^25 + x^24 + x^22 + x^20 + x^19 + x^18 + x^15 + x^10 + x^8 + x^5 + 1
+
+41-40-20 399 x^928 + x^898 + x^870 + x^846 + x^844 + x^821 + x^820 + x^816 + x^814 + x^808 + x^804 + x^801 + x^800 + x^798 + x^795 + x^778 + x^771 + x^770 + x^769 + x^768 + x^765 + x^760 + x^749 + x^748 + x^744 + x^743 + x^741 + x^738 + x^734 + x^729 + x^726 + x^719 + x^717 + x^716 + x^715 + x^714 + x^713 + x^712 + x^711 + x^710 + x^709 + x^706 + x^704 + x^703 + x^702 + x^701 + x^694 + x^693 + x^691 + x^690 + x^685 + x^684 + x^682 + x^681 + x^680 + x^678 + x^677 + x^676 + x^675 + x^674 + x^673 + x^671 + x^669 + x^667 + x^665 + x^661 + x^660 + x^659 + x^658 + x^656 + x^652 + x^651 + x^649 + x^648 + x^643 + x^642 + x^639 + x^637 + x^634 + x^631 + x^629 + x^628 + x^624 + x^620 + x^619 + x^618 + x^617 + x^616 + x^615 + x^614 + x^613 + x^611 + x^610 + x^605 + x^604 + x^603 + x^601 + x^599 + x^598 + x^595 + x^594 + x^593 + x^590 + x^589 + x^585 + x^584 + x^583 + x^579 + x^577 + x^575 + x^573 + x^572 + x^571 + x^570 + x^569 + x^566 + x^564 + x^562 + x^561 + x^560 + x^557 + x^555 + x^554 + x^553 + x^552 + x^551 + x^550 + x^549 + x^547 + x^545 + x^542 + x^540 + x^539 + x^538 + x^537 + x^536 + x^535 + x^533 + x^532 + x^530 + x^529 + x^524 + x^518 + x^516 + x^514 + x^513 + x^512 + x^510 + x^509 + x^504 + x^503 + x^501 + x^493 + x^490 + x^489 + x^487 + x^486 + x^485 + x^484 + x^481 + x^479 + x^478 + x^475 + x^473 + x^471 + x^470 + x^468 + x^467 + x^466 + x^462 + x^460 + x^455 + x^454 + x^451 + x^450 + x^449 + x^447 + x^446 + x^445 + x^444 + x^443 + x^442 + x^441 + x^440 + x^439 + x^438 + x^436 + x^430 + x^429 + x^424 + x^423 + x^420 + x^419 + x^418 + x^415 + x^414 + x^413 + x^410 + x^409 + x^408 + x^407 + x^406 + x^405 + x^403 + x^402 + x^400 + x^398 + x^397 + x^396 + x^395 + x^394 + x^392 + x^391 + x^389 + x^387 + x^386 + x^385 + x^383 + x^382 + x^381 + x^379 + x^375 + x^374 + x^369 + x^367 + x^366 + x^365 + x^363 + x^360 + x^359 + x^358 + x^357 + x^355 + x^354 + x^351 + x^339 + x^338 + x^337 + x^336 + x^335 + x^334 + x^332 + x^330 + x^329 + x^323 + x^320 + x^317 + x^315 + x^312 + x^311 + x^309 + x^305 + x^302 + x^301 + x^300 + x^299 + x^298 + x^297 + x^296 + x^295 + x^292 + x^291 + x^288 + x^286 + x^285 + x^284 + x^283 + x^282 + x^280 + x^279 + x^278 + x^273 + x^268 + x^267 + x^264 + x^263 + x^258 + x^257 + x^256 + x^255 + x^254 + x^253 + x^250 + x^249 + x^248 + x^244 + x^243 + x^242 + x^238 + x^237 + x^236 + x^234 + x^233 + x^231 + x^230 + x^222 + x^218 + x^215 + x^214 + x^211 + x^208 + x^206 + x^205 + x^201 + x^200 + x^198 + x^197 + x^195 + x^194 + x^193 + x^191 + x^189 + x^185 + x^182 + x^179 + x^176 + x^174 + x^173 + x^164 + x^163 + x^162 + x^159 + x^158 + x^156 + x^155 + x^152 + x^150 + x^148 + x^142 + x^140 + x^139 + x^138 + x^137 + x^135 + x^134 + x^133 + x^132 + x^131 + x^128 + x^124 + x^122 + x^121 + x^120 + x^119 + x^117 + x^116 + x^114 + x^111 + x^110 + x^108 + x^107 + x^105 + x^104 + x^103 + x^101 + x^95 + x^94 + x^93 + x^91 + x^89 + x^88 + x^87 + x^84 + x^83 + x^82 + x^81 + x^80 + x^79 + x^78 + x^77 + x^76 + x^74 + x^73 + x^72 + x^66 + x^65 + x^64 + x^59 + x^57 + x^56 + x^53 + x^49 + x^47 + x^44 + x^43 + x^39 + x^38 + x^37 + x^34 + x^33 + x^32 + x^31 + x^28 + x^23 + x^22 + x^19 + x^12 + x^8 + 1
+
+55-27-24 399 x^928 + x^898 + x^864 + x^847 + x^846 + x^834 + x^824 + x^818 + x^817 + x^816 + x^812 + x^810 + x^808 + x^806 + x^801 + x^800 + x^795 + x^794 + x^788 + x^783 + x^781 + x^777 + x^776 + x^775 + x^771 + x^765 + x^764 + x^753 + x^750 + x^749 + x^747 + x^746 + x^745 + x^743 + x^742 + x^741 + x^737 + x^734 + x^731 + x^728 + x^726 + x^725 + x^724 + x^721 + x^719 + x^717 + x^716 + x^714 + x^712 + x^706 + x^704 + x^703 + x^702 + x^701 + x^699 + x^698 + x^697 + x^695 + x^694 + x^691 + x^690 + x^688 + x^687 + x^684 + x^683 + x^681 + x^680 + x^673 + x^672 + x^670 + x^667 + x^666 + x^664 + x^663 + x^661 + x^659 + x^657 + x^655 + x^650 + x^649 + x^647 + x^640 + x^639 + x^637 + x^636 + x^634 + x^630 + x^626 + x^625 + x^623 + x^622 + x^620 + x^618 + x^617 + x^615 + x^612 + x^611 + x^609 + x^608 + x^607 + x^605 + x^604 + x^602 + x^600 + x^599 + x^596 + x^594 + x^592 + x^590 + x^587 + x^581 + x^578 + x^576 + x^575 + x^574 + x^570 + x^567 + x^566 + x^565 + x^564 + x^563 + x^561 + x^560 + x^555 + x^554 + x^553 + x^552 + x^551 + x^550 + x^549 + x^548 + x^543 + x^537 + x^536 + x^533 + x^532 + x^531 + x^529 + x^528 + x^527 + x^525 + x^524 + x^523 + x^522 + x^519 + x^518 + x^516 + x^515 + x^514 + x^513 + x^512 + x^511 + x^509 + x^507 + x^505 + x^500 + x^498 + x^497 + x^496 + x^494 + x^489 + x^486 + x^481 + x^480 + x^479 + x^476 + x^471 + x^469 + x^467 + x^466 + x^463 + x^459 + x^455 + x^451 + x^450 + x^449 + x^448 + x^447 + x^445 + x^444 + x^441 + x^440 + x^432 + x^430 + x^429 + x^428 + x^426 + x^424 + x^420 + x^418 + x^416 + x^415 + x^413 + x^411 + x^408 + x^406 + x^405 + x^404 + x^400 + x^398 + x^392 + x^390 + x^387 + x^386 + x^382 + x^379 + x^378 + x^377 + x^376 + x^374 + x^373 + x^371 + x^370 + x^368 + x^367 + x^365 + x^364 + x^363 + x^362 + x^360 + x^358 + x^351 + x^350 + x^344 + x^343 + x^341 + x^340 + x^339 + x^338 + x^337 + x^332 + x^331 + x^329 + x^327 + x^323 + x^321 + x^320 + x^318 + x^317 + x^314 + x^313 + x^312 + x^311 + x^309 + x^308 + x^306 + x^304 + x^301 + x^300 + x^299 + x^296 + x^295 + x^294 + x^291 + x^290 + x^287 + x^286 + x^285 + x^280 + x^275 + x^274 + x^271 + x^270 + x^268 + x^264 + x^263 + x^258 + x^257 + x^256 + x^254 + x^252 + x^249 + x^248 + x^246 + x^245 + x^242 + x^241 + x^239 + x^238 + x^236 + x^233 + x^231 + x^228 + x^226 + x^225 + x^222 + x^219 + x^218 + x^217 + x^216 + x^215 + x^213 + x^210 + x^209 + x^207 + x^205 + x^203 + x^202 + x^198 + x^197 + x^196 + x^193 + x^192 + x^189 + x^188 + x^187 + x^184 + x^183 + x^182 + x^181 + x^179 + x^178 + x^177 + x^175 + x^172 + x^171 + x^170 + x^169 + x^164 + x^162 + x^161 + x^160 + x^159 + x^155 + x^154 + x^152 + x^151 + x^148 + x^147 + x^143 + x^140 + x^139 + x^137 + x^134 + x^133 + x^132 + x^131 + x^126 + x^125 + x^120 + x^119 + x^118 + x^117 + x^113 + x^111 + x^110 + x^108 + x^104 + x^102 + x^101 + x^100 + x^97 + x^96 + x^90 + x^89 + x^85 + x^82 + x^81 + x^77 + x^76 + x^73 + x^69 + x^68 + x^67 + x^65 + x^64 + x^63 + x^62 + x^61 + x^55 + x^54 + x^53 + x^52 + x^49 + x^47 + x^46 + x^40 + x^39 + x^37 + x^36 + x^35 + x^34 + x^33 + x^32 + x^31 + x^29 + x^26 + x^25 + x^24 + x^23 + x^22 + x^19 + x^17 + x^16 + x^12 + x^9 + x^8 + x^5 + 1
+
+39-32-32 401 x^928 + x^898 + x^870 + x^867 + x^842 + x^837 + x^836 + x^832 + x^807 + x^806 + x^805 + x^802 + x^801 + x^780 + x^778 + x^775 + x^773 + x^771 + x^770 + x^768 + x^766 + x^758 + x^752 + x^749 + x^747 + x^740 + x^730 + x^724 + x^721 + x^719 + x^717 + x^716 + x^715 + x^714 + x^713 + x^711 + x^709 + x^708 + x^707 + x^704 + x^702 + x^700 + x^696 + x^693 + x^691 + x^689 + x^687 + x^686 + x^685 + x^683 + x^682 + x^680 + x^679 + x^677 + x^676 + x^674 + x^670 + x^669 + x^668 + x^665 + x^663 + x^661 + x^660 + x^659 + x^655 + x^653 + x^652 + x^651 + x^648 + x^647 + x^646 + x^645 + x^644 + x^642 + x^641 + x^640 + x^639 + x^638 + x^637 + x^635 + x^634 + x^633 + x^632 + x^631 + x^630 + x^625 + x^624 + x^620 + x^618 + x^615 + x^613 + x^611 + x^606 + x^605 + x^604 + x^602 + x^599 + x^597 + x^596 + x^593 + x^592 + x^591 + x^590 + x^589 + x^585 + x^584 + x^583 + x^580 + x^578 + x^577 + x^576 + x^575 + x^574 + x^572 + x^571 + x^570 + x^568 + x^567 + x^566 + x^563 + x^562 + x^560 + x^556 + x^554 + x^552 + x^549 + x^548 + x^547 + x^546 + x^544 + x^538 + x^536 + x^535 + x^534 + x^533 + x^530 + x^529 + x^528 + x^527 + x^526 + x^525 + x^524 + x^521 + x^519 + x^517 + x^516 + x^514 + x^513 + x^512 + x^510 + x^509 + x^507 + x^506 + x^504 + x^502 + x^500 + x^499 + x^498 + x^497 + x^493 + x^492 + x^490 + x^489 + x^485 + x^484 + x^481 + x^476 + x^475 + x^473 + x^467 + x^463 + x^462 + x^461 + x^459 + x^456 + x^453 + x^450 + x^449 + x^448 + x^445 + x^443 + x^442 + x^440 + x^438 + x^436 + x^433 + x^432 + x^431 + x^430 + x^429 + x^427 + x^421 + x^420 + x^419 + x^416 + x^415 + x^414 + x^413 + x^411 + x^410 + x^408 + x^407 + x^406 + x^405 + x^403 + x^400 + x^398 + x^397 + x^396 + x^394 + x^390 + x^389 + x^388 + x^385 + x^384 + x^383 + x^379 + x^376 + x^374 + x^373 + x^372 + x^370 + x^369 + x^368 + x^364 + x^362 + x^358 + x^355 + x^354 + x^353 + x^351 + x^348 + x^347 + x^344 + x^343 + x^339 + x^337 + x^336 + x^334 + x^333 + x^329 + x^328 + x^323 + x^321 + x^320 + x^319 + x^318 + x^317 + x^315 + x^314 + x^311 + x^309 + x^307 + x^306 + x^304 + x^302 + x^300 + x^297 + x^295 + x^294 + x^291 + x^289 + x^287 + x^285 + x^284 + x^283 + x^282 + x^281 + x^280 + x^278 + x^277 + x^276 + x^270 + x^269 + x^268 + x^267 + x^263 + x^261 + x^259 + x^257 + x^255 + x^253 + x^252 + x^250 + x^248 + x^247 + x^245 + x^244 + x^242 + x^241 + x^240 + x^238 + x^234 + x^233 + x^230 + x^227 + x^226 + x^224 + x^220 + x^219 + x^217 + x^216 + x^215 + x^209 + x^208 + x^207 + x^206 + x^205 + x^204 + x^203 + x^201 + x^199 + x^198 + x^197 + x^196 + x^193 + x^191 + x^187 + x^184 + x^183 + x^182 + x^173 + x^172 + x^169 + x^167 + x^166 + x^165 + x^162 + x^161 + x^160 + x^158 + x^157 + x^156 + x^155 + x^154 + x^152 + x^151 + x^149 + x^147 + x^141 + x^138 + x^137 + x^136 + x^135 + x^134 + x^131 + x^129 + x^126 + x^125 + x^122 + x^121 + x^117 + x^116 + x^113 + x^110 + x^109 + x^108 + x^104 + x^102 + x^101 + x^100 + x^98 + x^97 + x^95 + x^94 + x^87 + x^83 + x^82 + x^78 + x^77 + x^74 + x^73 + x^72 + x^70 + x^69 + x^66 + x^65 + x^62 + x^60 + x^55 + x^54 + x^52 + x^51 + x^49 + x^46 + x^45 + x^41 + x^40 + x^37 + x^33 + x^31 + x^29 + x^27 + x^26 + x^24 + x^20 + x^18 + x^17 + x^15 + x^6 + 1
+
+40-7-11 401 x^928 + x^898 + x^897 + x^882 + x^870 + x^866 + x^860 + x^854 + x^852 + x^851 + x^836 + x^832 + x^830 + x^829 + x^826 + x^824 + x^820 + x^814 + x^812 + x^811 + x^808 + x^806 + x^804 + x^800 + x^796 + x^793 + x^792 + x^790 + x^786 + x^780 + x^778 + x^777 + x^774 + x^770 + x^769 + x^767 + x^762 + x^761 + x^760 + x^756 + x^749 + x^748 + x^746 + x^742 + x^736 + x^733 + x^730 + x^728 + x^726 + x^725 + x^724 + x^723 + x^719 + x^718 + x^717 + x^716 + x^715 + x^712 + x^709 + x^708 + x^707 + x^705 + x^701 + x^700 + x^699 + x^698 + x^695 + x^689 + x^688 + x^687 + x^684 + x^683 + x^680 + x^678 + x^675 + x^672 + x^670 + x^669 + x^666 + x^664 + x^663 + x^656 + x^655 + x^654 + x^651 + x^647 + x^641 + x^639 + x^638 + x^636 + x^635 + x^633 + x^632 + x^631 + x^630 + x^629 + x^627 + x^626 + x^625 + x^623 + x^621 + x^620 + x^619 + x^617 + x^613 + x^611 + x^610 + x^609 + x^608 + x^607 + x^606 + x^604 + x^603 + x^600 + x^598 + x^596 + x^595 + x^592 + x^591 + x^590 + x^587 + x^586 + x^585 + x^584 + x^582 + x^581 + x^578 + x^577 + x^576 + x^575 + x^574 + x^569 + x^566 + x^565 + x^564 + x^560 + x^558 + x^557 + x^556 + x^554 + x^552 + x^550 + x^549 + x^548 + x^545 + x^539 + x^538 + x^536 + x^535 + x^534 + x^533 + x^532 + x^527 + x^524 + x^523 + x^522 + x^520 + x^518 + x^517 + x^514 + x^513 + x^512 + x^510 + x^507 + x^504 + x^501 + x^499 + x^497 + x^496 + x^494 + x^492 + x^491 + x^490 + x^489 + x^487 + x^485 + x^483 + x^479 + x^478 + x^477 + x^476 + x^475 + x^473 + x^472 + x^470 + x^469 + x^468 + x^465 + x^464 + x^462 + x^460 + x^457 + x^452 + x^449 + x^448 + x^447 + x^445 + x^443 + x^441 + x^440 + x^436 + x^434 + x^432 + x^430 + x^428 + x^426 + x^424 + x^420 + x^416 + x^415 + x^410 + x^408 + x^407 + x^406 + x^404 + x^397 + x^395 + x^394 + x^390 + x^389 + x^387 + x^384 + x^382 + x^380 + x^374 + x^370 + x^368 + x^366 + x^365 + x^364 + x^362 + x^360 + x^359 + x^358 + x^356 + x^352 + x^350 + x^349 + x^347 + x^346 + x^344 + x^342 + x^341 + x^337 + x^336 + x^332 + x^331 + x^327 + x^325 + x^323 + x^322 + x^320 + x^317 + x^316 + x^315 + x^314 + x^312 + x^309 + x^307 + x^306 + x^305 + x^304 + x^303 + x^301 + x^300 + x^298 + x^296 + x^294 + x^293 + x^290 + x^289 + x^287 + x^285 + x^282 + x^281 + x^279 + x^277 + x^273 + x^265 + x^264 + x^259 + x^258 + x^257 + x^255 + x^254 + x^253 + x^251 + x^250 + x^249 + x^248 + x^247 + x^246 + x^244 + x^237 + x^235 + x^233 + x^232 + x^231 + x^230 + x^229 + x^228 + x^227 + x^225 + x^221 + x^215 + x^214 + x^211 + x^208 + x^206 + x^204 + x^200 + x^199 + x^198 + x^196 + x^192 + x^188 + x^186 + x^185 + x^184 + x^183 + x^181 + x^179 + x^176 + x^175 + x^173 + x^171 + x^170 + x^168 + x^165 + x^164 + x^160 + x^158 + x^155 + x^154 + x^152 + x^151 + x^149 + x^147 + x^144 + x^141 + x^140 + x^139 + x^137 + x^136 + x^133 + x^131 + x^130 + x^128 + x^127 + x^126 + x^125 + x^123 + x^122 + x^121 + x^120 + x^119 + x^117 + x^116 + x^115 + x^112 + x^109 + x^106 + x^102 + x^101 + x^98 + x^92 + x^89 + x^87 + x^86 + x^81 + x^74 + x^72 + x^71 + x^69 + x^65 + x^61 + x^57 + x^55 + x^53 + x^51 + x^50 + x^47 + x^45 + x^44 + x^43 + x^42 + x^40 + x^39 + x^38 + x^37 + x^35 + x^31 + x^30 + x^29 + x^27 + x^24 + x^22 + x^21 + x^20 + x^19 + 1
+
+44-24-27 401 x^928 + x^898 + x^870 + x^858 + x^824 + x^821 + x^820 + x^798 + x^792 + x^791 + x^790 + x^789 + x^784 + x^776 + x^771 + x^770 + x^768 + x^764 + x^762 + x^761 + x^760 + x^759 + x^755 + x^754 + x^751 + x^742 + x^738 + x^735 + x^734 + x^731 + x^730 + x^729 + x^728 + x^725 + x^722 + x^721 + x^715 + x^711 + x^710 + x^706 + x^705 + x^701 + x^700 + x^698 + x^695 + x^692 + x^691 + x^689 + x^686 + x^685 + x^681 + x^676 + x^675 + x^674 + x^672 + x^671 + x^669 + x^668 + x^667 + x^666 + x^665 + x^658 + x^656 + x^654 + x^653 + x^651 + x^650 + x^648 + x^646 + x^644 + x^642 + x^635 + x^634 + x^633 + x^629 + x^626 + x^625 + x^624 + x^622 + x^621 + x^620 + x^618 + x^616 + x^614 + x^612 + x^608 + x^607 + x^606 + x^605 + x^604 + x^603 + x^602 + x^594 + x^593 + x^590 + x^589 + x^588 + x^586 + x^585 + x^584 + x^583 + x^582 + x^580 + x^577 + x^576 + x^575 + x^574 + x^569 + x^568 + x^566 + x^565 + x^564 + x^561 + x^559 + x^556 + x^554 + x^553 + x^552 + x^547 + x^543 + x^542 + x^541 + x^540 + x^539 + x^538 + x^536 + x^535 + x^534 + x^531 + x^530 + x^529 + x^527 + x^526 + x^524 + x^519 + x^514 + x^512 + x^511 + x^507 + x^504 + x^503 + x^502 + x^499 + x^498 + x^494 + x^493 + x^491 + x^489 + x^488 + x^486 + x^485 + x^483 + x^482 + x^480 + x^478 + x^476 + x^473 + x^468 + x^465 + x^463 + x^461 + x^460 + x^459 + x^458 + x^457 + x^455 + x^454 + x^453 + x^452 + x^451 + x^450 + x^449 + x^447 + x^446 + x^445 + x^443 + x^442 + x^439 + x^437 + x^436 + x^435 + x^433 + x^432 + x^429 + x^424 + x^423 + x^421 + x^418 + x^416 + x^412 + x^411 + x^406 + x^404 + x^403 + x^401 + x^400 + x^399 + x^398 + x^397 + x^394 + x^390 + x^388 + x^384 + x^383 + x^382 + x^381 + x^380 + x^378 + x^377 + x^376 + x^374 + x^373 + x^372 + x^368 + x^367 + x^366 + x^363 + x^361 + x^360 + x^359 + x^355 + x^353 + x^351 + x^350 + x^349 + x^348 + x^347 + x^345 + x^344 + x^342 + x^341 + x^340 + x^338 + x^337 + x^334 + x^329 + x^328 + x^326 + x^325 + x^319 + x^316 + x^314 + x^312 + x^311 + x^310 + x^308 + x^307 + x^305 + x^300 + x^296 + x^292 + x^291 + x^290 + x^287 + x^286 + x^284 + x^282 + x^280 + x^279 + x^277 + x^275 + x^274 + x^273 + x^272 + x^269 + x^268 + x^265 + x^264 + x^263 + x^262 + x^261 + x^258 + x^257 + x^256 + x^255 + x^254 + x^253 + x^252 + x^250 + x^249 + x^244 + x^242 + x^239 + x^238 + x^237 + x^235 + x^234 + x^232 + x^231 + x^228 + x^226 + x^225 + x^224 + x^221 + x^220 + x^219 + x^218 + x^216 + x^214 + x^213 + x^211 + x^210 + x^207 + x^205 + x^204 + x^203 + x^202 + x^200 + x^199 + x^198 + x^194 + x^186 + x^185 + x^184 + x^183 + x^182 + x^180 + x^179 + x^177 + x^174 + x^171 + x^169 + x^168 + x^165 + x^164 + x^163 + x^161 + x^159 + x^158 + x^157 + x^154 + x^152 + x^151 + x^148 + x^146 + x^145 + x^144 + x^142 + x^141 + x^139 + x^136 + x^135 + x^134 + x^132 + x^131 + x^130 + x^129 + x^128 + x^127 + x^124 + x^123 + x^120 + x^119 + x^117 + x^116 + x^114 + x^112 + x^106 + x^103 + x^101 + x^100 + x^98 + x^94 + x^93 + x^91 + x^86 + x^83 + x^82 + x^78 + x^76 + x^74 + x^73 + x^71 + x^69 + x^66 + x^65 + x^61 + x^60 + x^59 + x^58 + x^57 + x^56 + x^55 + x^54 + x^47 + x^45 + x^44 + x^43 + x^42 + x^40 + x^39 + x^38 + x^34 + x^31 + x^29 + x^28 + x^19 + x^16 + x^12 + x^6 + 1
+
+10-49-23 403 x^928 + x^900 + x^898 + x^893 + x^872 + x^870 + x^865 + x^858 + x^842 + x^840 + x^835 + x^833 + x^826 + x^823 + x^821 + x^816 + x^814 + x^809 + x^808 + x^807 + x^805 + x^802 + x^796 + x^793 + x^782 + x^780 + x^778 + x^775 + x^772 + x^770 + x^767 + x^766 + x^765 + x^760 + x^758 + x^756 + x^754 + x^753 + x^751 + x^747 + x^744 + x^740 + x^739 + x^738 + x^736 + x^735 + x^732 + x^728 + x^724 + x^723 + x^722 + x^720 + x^718 + x^717 + x^714 + x^712 + x^709 + x^708 + x^707 + x^706 + x^705 + x^702 + x^701 + x^700 + x^698 + x^697 + x^696 + x^694 + x^693 + x^691 + x^689 + x^688 + x^684 + x^682 + x^681 + x^680 + x^679 + x^677 + x^676 + x^674 + x^673 + x^672 + x^670 + x^668 + x^667 + x^666 + x^664 + x^661 + x^658 + x^657 + x^655 + x^652 + x^649 + x^646 + x^645 + x^643 + x^641 + x^640 + x^639 + x^638 + x^636 + x^635 + x^634 + x^632 + x^631 + x^628 + x^623 + x^622 + x^620 + x^619 + x^615 + x^612 + x^610 + x^607 + x^604 + x^602 + x^599 + x^598 + x^596 + x^593 + x^590 + x^588 + x^587 + x^585 + x^582 + x^581 + x^578 + x^576 + x^575 + x^573 + x^571 + x^570 + x^569 + x^568 + x^567 + x^565 + x^564 + x^563 + x^559 + x^557 + x^556 + x^552 + x^550 + x^549 + x^548 + x^546 + x^545 + x^543 + x^537 + x^536 + x^535 + x^534 + x^533 + x^532 + x^529 + x^526 + x^525 + x^523 + x^521 + x^520 + x^518 + x^515 + x^513 + x^512 + x^511 + x^508 + x^503 + x^502 + x^499 + x^498 + x^495 + x^494 + x^493 + x^492 + x^491 + x^480 + x^479 + x^475 + x^474 + x^472 + x^470 + x^469 + x^466 + x^465 + x^460 + x^453 + x^452 + x^451 + x^447 + x^444 + x^443 + x^438 + x^436 + x^431 + x^428 + x^426 + x^424 + x^423 + x^421 + x^420 + x^418 + x^417 + x^414 + x^413 + x^411 + x^410 + x^404 + x^401 + x^396 + x^395 + x^390 + x^389 + x^386 + x^384 + x^380 + x^378 + x^377 + x^376 + x^373 + x^372 + x^371 + x^369 + x^364 + x^361 + x^360 + x^359 + x^357 + x^356 + x^354 + x^353 + x^348 + x^347 + x^346 + x^342 + x^341 + x^339 + x^338 + x^333 + x^332 + x^331 + x^329 + x^328 + x^324 + x^322 + x^320 + x^315 + x^314 + x^312 + x^311 + x^310 + x^307 + x^306 + x^303 + x^295 + x^294 + x^292 + x^289 + x^288 + x^283 + x^281 + x^279 + x^274 + x^272 + x^271 + x^270 + x^268 + x^267 + x^266 + x^265 + x^264 + x^261 + x^258 + x^257 + x^256 + x^255 + x^252 + x^251 + x^248 + x^245 + x^243 + x^242 + x^238 + x^237 + x^236 + x^235 + x^233 + x^232 + x^231 + x^229 + x^228 + x^226 + x^225 + x^224 + x^222 + x^221 + x^220 + x^216 + x^215 + x^213 + x^212 + x^210 + x^209 + x^208 + x^202 + x^200 + x^199 + x^197 + x^194 + x^193 + x^192 + x^191 + x^190 + x^189 + x^187 + x^186 + x^184 + x^183 + x^181 + x^179 + x^178 + x^177 + x^176 + x^174 + x^173 + x^172 + x^171 + x^169 + x^166 + x^164 + x^163 + x^160 + x^158 + x^157 + x^155 + x^152 + x^151 + x^150 + x^148 + x^146 + x^145 + x^143 + x^142 + x^137 + x^133 + x^129 + x^126 + x^118 + x^116 + x^114 + x^113 + x^112 + x^110 + x^106 + x^102 + x^99 + x^98 + x^97 + x^96 + x^92 + x^91 + x^88 + x^86 + x^85 + x^83 + x^82 + x^81 + x^79 + x^78 + x^77 + x^76 + x^73 + x^71 + x^67 + x^66 + x^65 + x^64 + x^63 + x^61 + x^60 + x^58 + x^53 + x^52 + x^51 + x^48 + x^47 + x^44 + x^43 + x^42 + x^41 + x^39 + x^37 + x^36 + x^35 + x^34 + x^33 + x^31 + x^26 + x^21 + x^20 + x^16 + x^10 + x^5 + 1
+
+16-2-49 403 x^928 + x^898 + x^870 + x^858 + x^855 + x^846 + x^831 + x^828 + x^822 + x^818 + x^808 + x^800 + x^798 + x^795 + x^788 + x^786 + x^784 + x^783 + x^776 + x^775 + x^770 + x^768 + x^764 + x^759 + x^753 + x^751 + x^750 + x^746 + x^743 + x^740 + x^736 + x^735 + x^734 + x^724 + x^723 + x^719 + x^712 + x^708 + x^706 + x^703 + x^699 + x^698 + x^696 + x^695 + x^694 + x^693 + x^691 + x^690 + x^688 + x^686 + x^684 + x^683 + x^676 + x^675 + x^673 + x^672 + x^671 + x^670 + x^668 + x^664 + x^663 + x^662 + x^660 + x^655 + x^654 + x^652 + x^649 + x^644 + x^642 + x^636 + x^634 + x^633 + x^623 + x^622 + x^620 + x^619 + x^616 + x^614 + x^613 + x^611 + x^609 + x^608 + x^606 + x^604 + x^603 + x^602 + x^601 + x^600 + x^599 + x^598 + x^596 + x^595 + x^594 + x^592 + x^591 + x^588 + x^586 + x^585 + x^584 + x^583 + x^579 + x^578 + x^577 + x^576 + x^575 + x^574 + x^572 + x^569 + x^562 + x^560 + x^555 + x^553 + x^550 + x^549 + x^548 + x^547 + x^546 + x^545 + x^544 + x^543 + x^542 + x^538 + x^536 + x^533 + x^532 + x^531 + x^530 + x^529 + x^528 + x^527 + x^526 + x^523 + x^518 + x^516 + x^515 + x^511 + x^509 + x^507 + x^503 + x^501 + x^500 + x^498 + x^497 + x^496 + x^494 + x^491 + x^490 + x^487 + x^485 + x^484 + x^483 + x^482 + x^478 + x^477 + x^475 + x^474 + x^472 + x^470 + x^468 + x^467 + x^466 + x^465 + x^464 + x^462 + x^461 + x^460 + x^458 + x^457 + x^456 + x^455 + x^454 + x^453 + x^448 + x^446 + x^444 + x^443 + x^442 + x^441 + x^440 + x^437 + x^436 + x^435 + x^434 + x^433 + x^432 + x^431 + x^430 + x^429 + x^428 + x^427 + x^426 + x^425 + x^422 + x^421 + x^420 + x^419 + x^417 + x^414 + x^413 + x^411 + x^410 + x^406 + x^405 + x^400 + x^399 + x^397 + x^395 + x^394 + x^393 + x^392 + x^391 + x^389 + x^387 + x^382 + x^380 + x^379 + x^377 + x^375 + x^371 + x^370 + x^366 + x^365 + x^364 + x^363 + x^362 + x^358 + x^356 + x^354 + x^353 + x^351 + x^348 + x^346 + x^344 + x^343 + x^342 + x^340 + x^339 + x^337 + x^334 + x^333 + x^332 + x^331 + x^328 + x^327 + x^326 + x^325 + x^324 + x^323 + x^322 + x^321 + x^320 + x^318 + x^317 + x^316 + x^315 + x^314 + x^312 + x^310 + x^306 + x^304 + x^303 + x^301 + x^297 + x^295 + x^293 + x^290 + x^285 + x^283 + x^282 + x^273 + x^271 + x^268 + x^266 + x^262 + x^260 + x^259 + x^258 + x^253 + x^252 + x^251 + x^249 + x^248 + x^246 + x^245 + x^244 + x^243 + x^242 + x^241 + x^240 + x^239 + x^238 + x^237 + x^234 + x^233 + x^231 + x^229 + x^228 + x^227 + x^223 + x^222 + x^217 + x^216 + x^214 + x^213 + x^211 + x^209 + x^208 + x^203 + x^202 + x^201 + x^198 + x^197 + x^196 + x^194 + x^193 + x^189 + x^188 + x^187 + x^183 + x^182 + x^181 + x^177 + x^176 + x^174 + x^170 + x^166 + x^163 + x^162 + x^161 + x^160 + x^158 + x^157 + x^155 + x^153 + x^152 + x^151 + x^149 + x^148 + x^147 + x^146 + x^144 + x^142 + x^141 + x^140 + x^138 + x^132 + x^131 + x^129 + x^128 + x^126 + x^125 + x^123 + x^122 + x^120 + x^119 + x^117 + x^116 + x^115 + x^112 + x^109 + x^107 + x^105 + x^101 + x^97 + x^95 + x^94 + x^92 + x^91 + x^90 + x^87 + x^86 + x^85 + x^83 + x^82 + x^81 + x^79 + x^78 + x^77 + x^73 + x^72 + x^71 + x^68 + x^67 + x^65 + x^64 + x^63 + x^60 + x^58 + x^54 + x^50 + x^45 + x^44 + x^43 + x^42 + x^39 + x^37 + x^26 + x^24 + x^20 + x^16 + x^14 + x^10 + 1
+
+17-2-46 405 x^928 + x^898 + x^870 + x^860 + x^848 + x^831 + x^830 + x^818 + x^812 + x^808 + x^804 + x^801 + x^800 + x^792 + x^791 + x^790 + x^784 + x^780 + x^778 + x^775 + x^774 + x^770 + x^763 + x^762 + x^761 + x^760 + x^756 + x^754 + x^750 + x^748 + x^746 + x^745 + x^736 + x^733 + x^732 + x^731 + x^729 + x^728 + x^726 + x^720 + x^719 + x^712 + x^710 + x^706 + x^703 + x^702 + x^701 + x^700 + x^690 + x^686 + x^682 + x^679 + x^676 + x^675 + x^673 + x^672 + x^671 + x^669 + x^668 + x^666 + x^664 + x^663 + x^658 + x^652 + x^651 + x^648 + x^647 + x^646 + x^645 + x^644 + x^643 + x^642 + x^638 + x^633 + x^628 + x^626 + x^624 + x^623 + x^621 + x^617 + x^616 + x^614 + x^613 + x^611 + x^610 + x^609 + x^607 + x^606 + x^604 + x^599 + x^595 + x^594 + x^593 + x^592 + x^590 + x^589 + x^588 + x^584 + x^580 + x^579 + x^578 + x^577 + x^576 + x^574 + x^573 + x^569 + x^568 + x^567 + x^566 + x^564 + x^563 + x^561 + x^560 + x^559 + x^558 + x^557 + x^555 + x^549 + x^548 + x^547 + x^544 + x^543 + x^542 + x^540 + x^535 + x^534 + x^532 + x^531 + x^530 + x^528 + x^527 + x^526 + x^525 + x^520 + x^519 + x^516 + x^513 + x^510 + x^509 + x^500 + x^499 + x^498 + x^497 + x^496 + x^493 + x^492 + x^490 + x^489 + x^487 + x^484 + x^482 + x^480 + x^479 + x^476 + x^473 + x^471 + x^470 + x^468 + x^467 + x^465 + x^464 + x^463 + x^462 + x^461 + x^460 + x^457 + x^453 + x^452 + x^450 + x^448 + x^447 + x^443 + x^440 + x^439 + x^438 + x^437 + x^431 + x^430 + x^429 + x^428 + x^427 + x^426 + x^424 + x^423 + x^420 + x^418 + x^416 + x^415 + x^408 + x^407 + x^406 + x^405 + x^404 + x^403 + x^397 + x^395 + x^391 + x^389 + x^388 + x^386 + x^384 + x^382 + x^381 + x^380 + x^379 + x^378 + x^375 + x^374 + x^373 + x^372 + x^371 + x^369 + x^368 + x^365 + x^364 + x^363 + x^362 + x^360 + x^359 + x^358 + x^357 + x^353 + x^351 + x^350 + x^345 + x^341 + x^338 + x^336 + x^335 + x^334 + x^332 + x^331 + x^329 + x^328 + x^327 + x^323 + x^321 + x^320 + x^319 + x^317 + x^316 + x^314 + x^313 + x^312 + x^310 + x^308 + x^307 + x^304 + x^303 + x^300 + x^297 + x^295 + x^293 + x^291 + x^289 + x^288 + x^287 + x^285 + x^284 + x^282 + x^280 + x^279 + x^277 + x^273 + x^272 + x^269 + x^268 + x^267 + x^266 + x^265 + x^264 + x^262 + x^260 + x^259 + x^256 + x^255 + x^254 + x^253 + x^249 + x^247 + x^245 + x^243 + x^241 + x^240 + x^239 + x^238 + x^237 + x^236 + x^235 + x^234 + x^232 + x^228 + x^226 + x^225 + x^224 + x^223 + x^220 + x^219 + x^217 + x^209 + x^207 + x^206 + x^204 + x^203 + x^202 + x^201 + x^200 + x^199 + x^195 + x^194 + x^189 + x^187 + x^186 + x^185 + x^184 + x^182 + x^180 + x^178 + x^174 + x^173 + x^172 + x^170 + x^167 + x^166 + x^165 + x^164 + x^162 + x^161 + x^160 + x^159 + x^158 + x^157 + x^156 + x^155 + x^154 + x^153 + x^152 + x^151 + x^147 + x^143 + x^141 + x^138 + x^131 + x^130 + x^129 + x^127 + x^122 + x^121 + x^120 + x^118 + x^117 + x^114 + x^111 + x^109 + x^106 + x^105 + x^104 + x^103 + x^102 + x^101 + x^100 + x^99 + x^98 + x^97 + x^93 + x^92 + x^91 + x^90 + x^88 + x^87 + x^86 + x^82 + x^81 + x^80 + x^79 + x^78 + x^77 + x^75 + x^74 + x^73 + x^72 + x^71 + x^68 + x^59 + x^58 + x^51 + x^50 + x^43 + x^42 + x^40 + x^39 + x^34 + x^27 + x^25 + x^24 + x^23 + x^19 + x^18 + x^17 + x^15 + x^14 + x^13 + x^11 + x^10 + 1
+
+55-23-24 407 x^928 + x^898 + x^894 + x^870 + x^865 + x^849 + x^846 + x^842 + x^834 + x^833 + x^830 + x^826 + x^820 + x^819 + x^816 + x^813 + x^808 + x^804 + x^803 + x^794 + x^782 + x^778 + x^772 + x^769 + x^767 + x^765 + x^764 + x^762 + x^760 + x^759 + x^756 + x^751 + x^745 + x^743 + x^740 + x^739 + x^737 + x^733 + x^730 + x^729 + x^728 + x^726 + x^722 + x^720 + x^718 + x^717 + x^716 + x^713 + x^710 + x^709 + x^708 + x^707 + x^702 + x^699 + x^697 + x^694 + x^692 + x^691 + x^688 + x^687 + x^682 + x^680 + x^679 + x^678 + x^676 + x^675 + x^674 + x^670 + x^668 + x^666 + x^662 + x^661 + x^657 + x^652 + x^651 + x^649 + x^647 + x^646 + x^643 + x^640 + x^639 + x^637 + x^635 + x^634 + x^633 + x^630 + x^618 + x^616 + x^614 + x^613 + x^611 + x^610 + x^609 + x^608 + x^604 + x^603 + x^602 + x^597 + x^593 + x^591 + x^590 + x^585 + x^582 + x^579 + x^575 + x^574 + x^573 + x^572 + x^569 + x^567 + x^566 + x^564 + x^562 + x^561 + x^560 + x^557 + x^556 + x^555 + x^554 + x^551 + x^550 + x^547 + x^545 + x^542 + x^541 + x^539 + x^537 + x^534 + x^531 + x^530 + x^529 + x^528 + x^526 + x^525 + x^523 + x^522 + x^521 + x^520 + x^519 + x^518 + x^517 + x^515 + x^514 + x^513 + x^511 + x^510 + x^509 + x^508 + x^506 + x^505 + x^500 + x^498 + x^492 + x^485 + x^484 + x^480 + x^479 + x^478 + x^477 + x^476 + x^471 + x^470 + x^469 + x^467 + x^465 + x^464 + x^462 + x^458 + x^457 + x^454 + x^453 + x^452 + x^451 + x^450 + x^445 + x^444 + x^443 + x^441 + x^439 + x^437 + x^436 + x^435 + x^433 + x^431 + x^430 + x^429 + x^425 + x^424 + x^421 + x^419 + x^414 + x^411 + x^410 + x^409 + x^408 + x^407 + x^406 + x^405 + x^396 + x^395 + x^394 + x^390 + x^388 + x^385 + x^383 + x^381 + x^379 + x^378 + x^377 + x^376 + x^375 + x^373 + x^371 + x^369 + x^368 + x^367 + x^360 + x^358 + x^353 + x^351 + x^350 + x^348 + x^347 + x^346 + x^344 + x^343 + x^341 + x^338 + x^336 + x^335 + x^334 + x^331 + x^330 + x^329 + x^327 + x^326 + x^324 + x^322 + x^318 + x^314 + x^313 + x^311 + x^307 + x^305 + x^304 + x^302 + x^299 + x^295 + x^294 + x^293 + x^289 + x^284 + x^282 + x^281 + x^277 + x^272 + x^271 + x^270 + x^268 + x^265 + x^262 + x^259 + x^257 + x^254 + x^252 + x^251 + x^250 + x^249 + x^244 + x^243 + x^240 + x^239 + x^237 + x^235 + x^234 + x^233 + x^231 + x^230 + x^227 + x^224 + x^223 + x^220 + x^219 + x^218 + x^217 + x^215 + x^214 + x^213 + x^212 + x^211 + x^210 + x^209 + x^208 + x^207 + x^205 + x^203 + x^201 + x^200 + x^197 + x^193 + x^190 + x^187 + x^185 + x^184 + x^181 + x^180 + x^179 + x^178 + x^177 + x^176 + x^175 + x^173 + x^172 + x^169 + x^168 + x^166 + x^165 + x^162 + x^159 + x^157 + x^156 + x^155 + x^154 + x^153 + x^152 + x^150 + x^146 + x^145 + x^143 + x^142 + x^141 + x^139 + x^138 + x^137 + x^136 + x^135 + x^134 + x^132 + x^129 + x^123 + x^119 + x^115 + x^114 + x^112 + x^108 + x^107 + x^102 + x^100 + x^98 + x^97 + x^95 + x^93 + x^91 + x^90 + x^87 + x^86 + x^85 + x^83 + x^80 + x^79 + x^78 + x^77 + x^75 + x^74 + x^72 + x^69 + x^68 + x^65 + x^64 + x^61 + x^60 + x^59 + x^58 + x^57 + x^56 + x^55 + x^52 + x^51 + x^50 + x^45 + x^44 + x^43 + x^42 + x^41 + x^40 + x^39 + x^38 + x^37 + x^34 + x^33 + x^31 + x^30 + x^29 + x^26 + x^25 + x^23 + x^21 + x^20 + x^19 + x^18 + x^17 + x^13 + x^12 + x^10 + x^8 + x^7 + 1
+
+15-3-26 409 x^928 + x^898 + x^892 + x^870 + x^863 + x^862 + x^858 + x^856 + x^852 + x^833 + x^828 + x^827 + x^826 + x^824 + x^823 + x^820 + x^818 + x^816 + x^812 + x^808 + x^803 + x^801 + x^799 + x^798 + x^797 + x^795 + x^794 + x^792 + x^791 + x^790 + x^788 + x^787 + x^784 + x^783 + x^782 + x^773 + x^772 + x^771 + x^768 + x^767 + x^763 + x^760 + x^757 + x^753 + x^750 + x^746 + x^744 + x^737 + x^732 + x^731 + x^730 + x^729 + x^728 + x^726 + x^725 + x^724 + x^721 + x^717 + x^716 + x^713 + x^711 + x^710 + x^707 + x^706 + x^705 + x^703 + x^702 + x^699 + x^698 + x^697 + x^696 + x^694 + x^692 + x^691 + x^690 + x^689 + x^688 + x^681 + x^678 + x^673 + x^668 + x^666 + x^662 + x^658 + x^657 + x^656 + x^653 + x^651 + x^650 + x^648 + x^644 + x^643 + x^642 + x^641 + x^640 + x^638 + x^636 + x^635 + x^634 + x^633 + x^632 + x^630 + x^628 + x^626 + x^625 + x^623 + x^622 + x^620 + x^618 + x^617 + x^616 + x^614 + x^611 + x^609 + x^607 + x^605 + x^603 + x^596 + x^595 + x^593 + x^592 + x^590 + x^587 + x^586 + x^585 + x^584 + x^583 + x^582 + x^580 + x^577 + x^576 + x^571 + x^569 + x^568 + x^567 + x^565 + x^564 + x^562 + x^561 + x^560 + x^559 + x^558 + x^557 + x^556 + x^555 + x^554 + x^553 + x^552 + x^548 + x^547 + x^546 + x^545 + x^544 + x^542 + x^538 + x^537 + x^534 + x^533 + x^532 + x^529 + x^527 + x^526 + x^524 + x^523 + x^518 + x^517 + x^509 + x^505 + x^503 + x^501 + x^494 + x^493 + x^492 + x^488 + x^485 + x^484 + x^483 + x^480 + x^479 + x^477 + x^475 + x^474 + x^473 + x^472 + x^471 + x^469 + x^467 + x^466 + x^465 + x^464 + x^461 + x^458 + x^456 + x^453 + x^449 + x^446 + x^445 + x^444 + x^443 + x^442 + x^441 + x^440 + x^436 + x^435 + x^432 + x^431 + x^427 + x^426 + x^423 + x^418 + x^415 + x^413 + x^412 + x^411 + x^410 + x^407 + x^406 + x^403 + x^400 + x^398 + x^396 + x^385 + x^383 + x^382 + x^381 + x^375 + x^374 + x^373 + x^364 + x^363 + x^362 + x^360 + x^358 + x^357 + x^355 + x^353 + x^352 + x^350 + x^349 + x^345 + x^344 + x^343 + x^342 + x^340 + x^337 + x^331 + x^329 + x^328 + x^325 + x^324 + x^323 + x^322 + x^315 + x^314 + x^312 + x^311 + x^308 + x^304 + x^303 + x^299 + x^297 + x^295 + x^289 + x^284 + x^282 + x^281 + x^279 + x^278 + x^275 + x^274 + x^273 + x^272 + x^271 + x^270 + x^264 + x^263 + x^262 + x^260 + x^259 + x^258 + x^256 + x^253 + x^252 + x^251 + x^250 + x^248 + x^247 + x^246 + x^245 + x^243 + x^242 + x^240 + x^238 + x^237 + x^234 + x^233 + x^232 + x^231 + x^230 + x^228 + x^221 + x^220 + x^218 + x^213 + x^212 + x^211 + x^210 + x^204 + x^201 + x^200 + x^196 + x^195 + x^194 + x^191 + x^190 + x^189 + x^185 + x^183 + x^181 + x^180 + x^178 + x^176 + x^175 + x^170 + x^168 + x^167 + x^165 + x^164 + x^163 + x^160 + x^159 + x^158 + x^157 + x^156 + x^153 + x^151 + x^150 + x^149 + x^146 + x^145 + x^141 + x^139 + x^138 + x^137 + x^133 + x^132 + x^131 + x^130 + x^129 + x^128 + x^127 + x^125 + x^124 + x^122 + x^121 + x^120 + x^116 + x^115 + x^114 + x^112 + x^110 + x^106 + x^103 + x^101 + x^100 + x^97 + x^96 + x^94 + x^93 + x^92 + x^89 + x^88 + x^87 + x^86 + x^85 + x^84 + x^82 + x^80 + x^77 + x^73 + x^72 + x^71 + x^70 + x^68 + x^67 + x^65 + x^61 + x^60 + x^59 + x^56 + x^55 + x^48 + x^47 + x^42 + x^41 + x^36 + x^35 + x^33 + x^29 + x^27 + x^26 + x^25 + x^18 + x^14 + x^12 + x^10 + x^8 + x^4 + 1
+
+33-51-22 409 x^928 + x^898 + x^886 + x^870 + x^859 + x^858 + x^857 + x^844 + x^842 + x^832 + x^831 + x^830 + x^826 + x^815 + x^812 + x^808 + x^805 + x^804 + x^803 + x^799 + x^798 + x^789 + x^787 + x^786 + x^785 + x^782 + x^777 + x^776 + x^775 + x^771 + x^769 + x^766 + x^763 + x^758 + x^756 + x^752 + x^749 + x^745 + x^744 + x^743 + x^741 + x^739 + x^738 + x^735 + x^734 + x^731 + x^730 + x^721 + x^720 + x^715 + x^714 + x^711 + x^708 + x^705 + x^704 + x^703 + x^700 + x^698 + x^695 + x^693 + x^692 + x^690 + x^689 + x^684 + x^682 + x^681 + x^680 + x^677 + x^676 + x^673 + x^672 + x^671 + x^667 + x^666 + x^662 + x^661 + x^658 + x^656 + x^653 + x^652 + x^650 + x^649 + x^647 + x^646 + x^645 + x^644 + x^642 + x^641 + x^640 + x^638 + x^636 + x^634 + x^633 + x^632 + x^631 + x^629 + x^625 + x^624 + x^623 + x^621 + x^620 + x^619 + x^616 + x^615 + x^614 + x^612 + x^611 + x^609 + x^606 + x^605 + x^602 + x^601 + x^599 + x^596 + x^595 + x^592 + x^591 + x^588 + x^587 + x^586 + x^583 + x^582 + x^578 + x^577 + x^576 + x^574 + x^572 + x^570 + x^566 + x^562 + x^560 + x^555 + x^552 + x^550 + x^546 + x^545 + x^544 + x^543 + x^542 + x^539 + x^537 + x^535 + x^534 + x^533 + x^532 + x^531 + x^530 + x^528 + x^525 + x^524 + x^523 + x^519 + x^516 + x^513 + x^511 + x^509 + x^508 + x^507 + x^506 + x^504 + x^500 + x^499 + x^497 + x^495 + x^494 + x^491 + x^488 + x^487 + x^484 + x^480 + x^479 + x^476 + x^474 + x^472 + x^471 + x^470 + x^469 + x^468 + x^464 + x^463 + x^462 + x^460 + x^459 + x^458 + x^457 + x^456 + x^455 + x^454 + x^451 + x^449 + x^448 + x^447 + x^446 + x^445 + x^441 + x^440 + x^439 + x^437 + x^436 + x^435 + x^431 + x^430 + x^427 + x^423 + x^421 + x^419 + x^412 + x^410 + x^407 + x^406 + x^405 + x^404 + x^402 + x^400 + x^398 + x^396 + x^395 + x^394 + x^392 + x^389 + x^387 + x^386 + x^384 + x^382 + x^381 + x^379 + x^378 + x^377 + x^375 + x^372 + x^370 + x^369 + x^363 + x^361 + x^360 + x^351 + x^350 + x^347 + x^343 + x^342 + x^340 + x^336 + x^328 + x^327 + x^326 + x^325 + x^323 + x^322 + x^321 + x^319 + x^318 + x^315 + x^314 + x^313 + x^312 + x^311 + x^308 + x^307 + x^305 + x^301 + x^299 + x^298 + x^295 + x^293 + x^292 + x^290 + x^289 + x^288 + x^286 + x^284 + x^283 + x^282 + x^280 + x^279 + x^275 + x^273 + x^272 + x^269 + x^266 + x^265 + x^264 + x^255 + x^251 + x^249 + x^248 + x^246 + x^244 + x^243 + x^242 + x^238 + x^237 + x^235 + x^234 + x^232 + x^230 + x^229 + x^228 + x^226 + x^224 + x^222 + x^221 + x^218 + x^213 + x^210 + x^209 + x^208 + x^206 + x^203 + x^200 + x^195 + x^193 + x^189 + x^187 + x^186 + x^185 + x^182 + x^181 + x^179 + x^177 + x^174 + x^173 + x^170 + x^163 + x^160 + x^159 + x^155 + x^154 + x^153 + x^152 + x^151 + x^147 + x^146 + x^143 + x^141 + x^133 + x^130 + x^128 + x^125 + x^123 + x^118 + x^116 + x^115 + x^114 + x^110 + x^108 + x^106 + x^105 + x^104 + x^102 + x^100 + x^98 + x^97 + x^96 + x^95 + x^94 + x^93 + x^92 + x^91 + x^89 + x^85 + x^84 + x^83 + x^82 + x^81 + x^80 + x^78 + x^77 + x^74 + x^72 + x^71 + x^69 + x^67 + x^65 + x^64 + x^63 + x^61 + x^58 + x^56 + x^55 + x^53 + x^52 + x^51 + x^50 + x^48 + x^47 + x^46 + x^45 + x^44 + x^43 + x^40 + x^39 + x^37 + x^36 + x^35 + x^33 + x^32 + x^30 + x^29 + x^28 + x^27 + x^25 + x^23 + x^21 + x^16 + x^13 + x^11 + x^10 + x^8 + 1
+
+23-25-12 411 x^928 + x^898 + x^873 + x^870 + x^852 + x^847 + x^844 + x^842 + x^838 + x^836 + x^831 + x^828 + x^822 + x^821 + x^818 + x^817 + x^816 + x^814 + x^813 + x^812 + x^811 + x^801 + x^800 + x^798 + x^797 + x^796 + x^792 + x^791 + x^790 + x^787 + x^780 + x^776 + x^774 + x^770 + x^768 + x^766 + x^765 + x^762 + x^761 + x^759 + x^758 + x^757 + x^756 + x^755 + x^752 + x^749 + x^748 + x^747 + x^744 + x^741 + x^740 + x^739 + x^737 + x^735 + x^731 + x^730 + x^729 + x^728 + x^726 + x^725 + x^722 + x^720 + x^718 + x^714 + x^712 + x^711 + x^709 + x^708 + x^707 + x^706 + x^705 + x^704 + x^698 + x^694 + x^693 + x^691 + x^689 + x^686 + x^685 + x^682 + x^676 + x^674 + x^670 + x^669 + x^668 + x^667 + x^666 + x^665 + x^662 + x^661 + x^658 + x^655 + x^653 + x^652 + x^650 + x^647 + x^644 + x^643 + x^640 + x^638 + x^637 + x^635 + x^634 + x^632 + x^629 + x^627 + x^626 + x^625 + x^624 + x^619 + x^618 + x^614 + x^612 + x^611 + x^606 + x^604 + x^602 + x^601 + x^595 + x^592 + x^591 + x^590 + x^589 + x^586 + x^585 + x^581 + x^579 + x^578 + x^575 + x^574 + x^573 + x^568 + x^567 + x^565 + x^564 + x^562 + x^560 + x^559 + x^558 + x^555 + x^554 + x^553 + x^552 + x^549 + x^548 + x^546 + x^544 + x^543 + x^542 + x^541 + x^538 + x^533 + x^532 + x^529 + x^527 + x^526 + x^523 + x^522 + x^521 + x^517 + x^511 + x^508 + x^507 + x^506 + x^505 + x^504 + x^502 + x^497 + x^496 + x^494 + x^490 + x^489 + x^486 + x^485 + x^483 + x^482 + x^481 + x^477 + x^475 + x^473 + x^472 + x^471 + x^468 + x^464 + x^462 + x^461 + x^460 + x^459 + x^455 + x^454 + x^453 + x^449 + x^448 + x^447 + x^446 + x^438 + x^437 + x^435 + x^432 + x^429 + x^427 + x^426 + x^424 + x^423 + x^421 + x^419 + x^418 + x^416 + x^415 + x^413 + x^412 + x^410 + x^409 + x^407 + x^406 + x^405 + x^402 + x^401 + x^399 + x^397 + x^396 + x^394 + x^393 + x^390 + x^385 + x^384 + x^383 + x^380 + x^379 + x^378 + x^376 + x^375 + x^374 + x^372 + x^370 + x^368 + x^367 + x^366 + x^365 + x^363 + x^359 + x^357 + x^356 + x^355 + x^354 + x^353 + x^352 + x^351 + x^350 + x^348 + x^345 + x^341 + x^337 + x^335 + x^334 + x^333 + x^325 + x^319 + x^317 + x^316 + x^314 + x^305 + x^301 + x^298 + x^294 + x^293 + x^292 + x^289 + x^284 + x^281 + x^279 + x^272 + x^271 + x^269 + x^268 + x^267 + x^266 + x^264 + x^263 + x^262 + x^261 + x^256 + x^255 + x^254 + x^252 + x^251 + x^249 + x^248 + x^244 + x^242 + x^239 + x^235 + x^234 + x^233 + x^227 + x^226 + x^223 + x^221 + x^220 + x^216 + x^214 + x^211 + x^209 + x^207 + x^205 + x^204 + x^200 + x^198 + x^197 + x^196 + x^193 + x^188 + x^187 + x^185 + x^183 + x^182 + x^181 + x^179 + x^177 + x^175 + x^173 + x^172 + x^170 + x^169 + x^167 + x^163 + x^162 + x^158 + x^157 + x^156 + x^155 + x^154 + x^152 + x^151 + x^150 + x^149 + x^145 + x^144 + x^143 + x^142 + x^140 + x^139 + x^138 + x^136 + x^135 + x^133 + x^131 + x^130 + x^127 + x^126 + x^124 + x^122 + x^120 + x^118 + x^116 + x^114 + x^111 + x^110 + x^106 + x^105 + x^103 + x^102 + x^101 + x^100 + x^99 + x^98 + x^97 + x^95 + x^94 + x^93 + x^92 + x^91 + x^90 + x^86 + x^85 + x^82 + x^81 + x^78 + x^75 + x^70 + x^66 + x^64 + x^63 + x^61 + x^60 + x^55 + x^54 + x^53 + x^52 + x^50 + x^49 + x^46 + x^45 + x^44 + x^41 + x^38 + x^37 + x^36 + x^32 + x^30 + x^29 + x^27 + x^22 + x^18 + x^16 + x^13 + x^9 + x^8 + x^7 + x^5 + 1
+
+36-2-35 411 x^928 + x^898 + x^870 + x^860 + x^850 + x^842 + x^830 + x^824 + x^822 + x^812 + x^808 + x^806 + x^804 + x^794 + x^792 + x^790 + x^786 + x^782 + x^778 + x^776 + x^772 + x^768 + x^764 + x^754 + x^752 + x^747 + x^746 + x^745 + x^742 + x^738 + x^737 + x^736 + x^729 + x^728 + x^725 + x^724 + x^722 + x^721 + x^720 + x^718 + x^716 + x^715 + x^714 + x^712 + x^707 + x^706 + x^704 + x^703 + x^701 + x^699 + x^693 + x^691 + x^689 + x^688 + x^687 + x^684 + x^682 + x^680 + x^674 + x^672 + x^671 + x^669 + x^668 + x^663 + x^662 + x^661 + x^660 + x^659 + x^658 + x^654 + x^652 + x^651 + x^650 + x^649 + x^648 + x^644 + x^642 + x^640 + x^639 + x^638 + x^635 + x^633 + x^632 + x^624 + x^623 + x^620 + x^619 + x^618 + x^617 + x^611 + x^607 + x^606 + x^604 + x^602 + x^601 + x^600 + x^598 + x^596 + x^594 + x^593 + x^589 + x^585 + x^583 + x^580 + x^579 + x^577 + x^576 + x^575 + x^569 + x^568 + x^567 + x^565 + x^564 + x^563 + x^560 + x^558 + x^556 + x^555 + x^553 + x^552 + x^551 + x^549 + x^548 + x^545 + x^542 + x^541 + x^539 + x^536 + x^534 + x^533 + x^530 + x^528 + x^526 + x^524 + x^521 + x^519 + x^517 + x^515 + x^511 + x^510 + x^508 + x^506 + x^505 + x^504 + x^503 + x^502 + x^501 + x^500 + x^499 + x^498 + x^496 + x^494 + x^493 + x^492 + x^491 + x^490 + x^488 + x^487 + x^484 + x^480 + x^478 + x^474 + x^472 + x^471 + x^466 + x^465 + x^464 + x^463 + x^461 + x^459 + x^458 + x^457 + x^454 + x^453 + x^446 + x^445 + x^441 + x^440 + x^439 + x^438 + x^437 + x^436 + x^435 + x^433 + x^428 + x^427 + x^426 + x^425 + x^414 + x^407 + x^406 + x^405 + x^403 + x^402 + x^401 + x^399 + x^398 + x^397 + x^395 + x^393 + x^392 + x^391 + x^390 + x^387 + x^385 + x^384 + x^383 + x^382 + x^379 + x^378 + x^376 + x^374 + x^373 + x^371 + x^370 + x^369 + x^367 + x^365 + x^364 + x^363 + x^359 + x^357 + x^355 + x^354 + x^353 + x^350 + x^346 + x^345 + x^344 + x^343 + x^340 + x^338 + x^337 + x^336 + x^335 + x^330 + x^322 + x^321 + x^320 + x^317 + x^316 + x^311 + x^310 + x^309 + x^308 + x^307 + x^306 + x^305 + x^303 + x^299 + x^296 + x^295 + x^294 + x^293 + x^292 + x^289 + x^288 + x^284 + x^283 + x^282 + x^281 + x^280 + x^278 + x^277 + x^275 + x^269 + x^265 + x^263 + x^260 + x^258 + x^256 + x^255 + x^254 + x^253 + x^252 + x^250 + x^247 + x^246 + x^245 + x^242 + x^241 + x^240 + x^239 + x^234 + x^233 + x^232 + x^230 + x^226 + x^224 + x^222 + x^218 + x^217 + x^216 + x^215 + x^214 + x^213 + x^212 + x^211 + x^208 + x^204 + x^203 + x^202 + x^201 + x^200 + x^199 + x^198 + x^197 + x^194 + x^192 + x^191 + x^184 + x^181 + x^180 + x^178 + x^177 + x^176 + x^175 + x^174 + x^173 + x^171 + x^170 + x^168 + x^166 + x^161 + x^160 + x^157 + x^156 + x^153 + x^149 + x^148 + x^147 + x^145 + x^144 + x^143 + x^139 + x^137 + x^136 + x^134 + x^132 + x^131 + x^130 + x^129 + x^128 + x^127 + x^126 + x^125 + x^118 + x^117 + x^116 + x^115 + x^114 + x^113 + x^111 + x^107 + x^105 + x^104 + x^103 + x^101 + x^99 + x^98 + x^97 + x^96 + x^92 + x^91 + x^90 + x^89 + x^87 + x^86 + x^85 + x^84 + x^83 + x^82 + x^81 + x^79 + x^78 + x^76 + x^72 + x^70 + x^69 + x^68 + x^67 + x^65 + x^64 + x^62 + x^61 + x^58 + x^54 + x^53 + x^52 + x^50 + x^49 + x^48 + x^46 + x^44 + x^43 + x^40 + x^39 + x^38 + x^35 + x^32 + x^31 + x^30 + x^29 + x^28 + x^27 + x^25 + x^24 + x^18 + x^14 + x^10 + 1
+
+55-5-54 411 x^928 + x^898 + x^883 + x^870 + x^867 + x^854 + x^853 + x^840 + x^838 + x^837 + x^836 + x^834 + x^824 + x^822 + x^820 + x^812 + x^811 + x^810 + x^808 + x^807 + x^800 + x^797 + x^796 + x^795 + x^793 + x^792 + x^783 + x^779 + x^777 + x^776 + x^774 + x^770 + x^769 + x^768 + x^764 + x^762 + x^760 + x^754 + x^753 + x^752 + x^751 + x^749 + x^747 + x^746 + x^741 + x^740 + x^739 + x^738 + x^735 + x^734 + x^733 + x^732 + x^730 + x^728 + x^723 + x^721 + x^717 + x^715 + x^712 + x^711 + x^710 + x^709 + x^708 + x^707 + x^706 + x^704 + x^702 + x^701 + x^698 + x^697 + x^696 + x^694 + x^692 + x^690 + x^687 + x^683 + x^682 + x^681 + x^675 + x^674 + x^670 + x^669 + x^667 + x^666 + x^664 + x^663 + x^662 + x^657 + x^655 + x^654 + x^653 + x^652 + x^650 + x^646 + x^645 + x^644 + x^642 + x^637 + x^636 + x^635 + x^630 + x^629 + x^627 + x^626 + x^620 + x^615 + x^614 + x^612 + x^611 + x^610 + x^607 + x^606 + x^605 + x^604 + x^603 + x^601 + x^597 + x^594 + x^592 + x^591 + x^586 + x^584 + x^583 + x^582 + x^579 + x^577 + x^574 + x^573 + x^568 + x^565 + x^564 + x^563 + x^562 + x^557 + x^554 + x^553 + x^552 + x^550 + x^548 + x^546 + x^544 + x^543 + x^542 + x^540 + x^537 + x^536 + x^532 + x^531 + x^530 + x^524 + x^521 + x^520 + x^519 + x^517 + x^516 + x^515 + x^513 + x^512 + x^510 + x^509 + x^507 + x^505 + x^503 + x^502 + x^501 + x^500 + x^497 + x^496 + x^488 + x^486 + x^484 + x^481 + x^480 + x^478 + x^476 + x^475 + x^467 + x^465 + x^464 + x^463 + x^459 + x^458 + x^457 + x^455 + x^453 + x^452 + x^446 + x^445 + x^444 + x^441 + x^440 + x^439 + x^438 + x^434 + x^433 + x^432 + x^431 + x^427 + x^425 + x^421 + x^414 + x^412 + x^411 + x^409 + x^407 + x^406 + x^405 + x^403 + x^401 + x^400 + x^399 + x^398 + x^397 + x^396 + x^395 + x^394 + x^389 + x^385 + x^383 + x^380 + x^377 + x^376 + x^375 + x^374 + x^373 + x^372 + x^370 + x^367 + x^366 + x^365 + x^364 + x^363 + x^362 + x^360 + x^358 + x^356 + x^352 + x^351 + x^350 + x^349 + x^346 + x^342 + x^340 + x^338 + x^336 + x^335 + x^330 + x^329 + x^325 + x^324 + x^323 + x^321 + x^317 + x^314 + x^312 + x^307 + x^304 + x^303 + x^301 + x^298 + x^296 + x^295 + x^294 + x^293 + x^290 + x^289 + x^288 + x^287 + x^286 + x^285 + x^278 + x^277 + x^274 + x^273 + x^272 + x^270 + x^267 + x^265 + x^261 + x^260 + x^259 + x^258 + x^257 + x^256 + x^255 + x^254 + x^252 + x^249 + x^243 + x^241 + x^240 + x^239 + x^238 + x^235 + x^232 + x^231 + x^230 + x^227 + x^226 + x^224 + x^222 + x^221 + x^220 + x^219 + x^215 + x^214 + x^213 + x^211 + x^210 + x^209 + x^207 + x^206 + x^205 + x^200 + x^198 + x^195 + x^193 + x^192 + x^190 + x^186 + x^185 + x^181 + x^178 + x^176 + x^175 + x^172 + x^170 + x^169 + x^168 + x^166 + x^164 + x^158 + x^153 + x^152 + x^150 + x^149 + x^148 + x^147 + x^146 + x^143 + x^142 + x^140 + x^139 + x^136 + x^134 + x^133 + x^128 + x^125 + x^122 + x^121 + x^120 + x^116 + x^115 + x^114 + x^112 + x^111 + x^107 + x^106 + x^103 + x^101 + x^100 + x^99 + x^98 + x^96 + x^95 + x^94 + x^93 + x^92 + x^89 + x^88 + x^87 + x^86 + x^85 + x^84 + x^81 + x^79 + x^77 + x^76 + x^74 + x^72 + x^71 + x^70 + x^69 + x^65 + x^64 + x^62 + x^55 + x^53 + x^49 + x^48 + x^46 + x^44 + x^43 + x^39 + x^38 + x^37 + x^35 + x^33 + x^32 + x^31 + x^29 + x^27 + x^26 + x^24 + x^23 + x^22 + x^20 + x^18 + x^17 + x^8 + 1
+
+14-19-11 415 x^928 + x^898 + x^882 + x^870 + x^863 + x^862 + x^860 + x^854 + x^852 + x^844 + x^843 + x^833 + x^832 + x^825 + x^822 + x^819 + x^817 + x^816 + x^813 + x^811 + x^802 + x^798 + x^797 + x^795 + x^794 + x^790 + x^789 + x^787 + x^786 + x^781 + x^778 + x^776 + x^773 + x^772 + x^771 + x^768 + x^759 + x^754 + x^749 + x^746 + x^744 + x^743 + x^741 + x^740 + x^735 + x^734 + x^733 + x^730 + x^729 + x^725 + x^722 + x^717 + x^714 + x^711 + x^706 + x^705 + x^698 + x^697 + x^695 + x^691 + x^687 + x^686 + x^683 + x^681 + x^675 + x^674 + x^673 + x^672 + x^671 + x^670 + x^667 + x^665 + x^662 + x^661 + x^660 + x^658 + x^657 + x^656 + x^655 + x^654 + x^652 + x^649 + x^648 + x^645 + x^643 + x^642 + x^638 + x^636 + x^635 + x^634 + x^633 + x^632 + x^630 + x^629 + x^627 + x^626 + x^625 + x^624 + x^623 + x^622 + x^620 + x^617 + x^616 + x^615 + x^613 + x^612 + x^611 + x^608 + x^604 + x^603 + x^602 + x^599 + x^598 + x^597 + x^595 + x^594 + x^593 + x^592 + x^591 + x^590 + x^587 + x^586 + x^585 + x^584 + x^582 + x^580 + x^579 + x^578 + x^577 + x^570 + x^569 + x^568 + x^567 + x^566 + x^563 + x^562 + x^560 + x^558 + x^552 + x^550 + x^549 + x^546 + x^544 + x^543 + x^540 + x^537 + x^536 + x^535 + x^533 + x^532 + x^531 + x^530 + x^529 + x^527 + x^526 + x^522 + x^521 + x^519 + x^517 + x^514 + x^513 + x^512 + x^511 + x^510 + x^509 + x^507 + x^506 + x^504 + x^503 + x^502 + x^501 + x^500 + x^499 + x^498 + x^496 + x^494 + x^492 + x^491 + x^489 + x^488 + x^487 + x^485 + x^480 + x^479 + x^478 + x^475 + x^472 + x^463 + x^458 + x^455 + x^453 + x^452 + x^448 + x^443 + x^438 + x^436 + x^435 + x^432 + x^429 + x^428 + x^427 + x^421 + x^420 + x^419 + x^418 + x^417 + x^416 + x^414 + x^412 + x^411 + x^410 + x^406 + x^405 + x^404 + x^402 + x^401 + x^400 + x^399 + x^393 + x^388 + x^387 + x^386 + x^385 + x^384 + x^380 + x^379 + x^378 + x^376 + x^375 + x^373 + x^370 + x^368 + x^367 + x^365 + x^363 + x^362 + x^359 + x^358 + x^357 + x^356 + x^353 + x^350 + x^347 + x^343 + x^342 + x^341 + x^339 + x^338 + x^334 + x^333 + x^327 + x^325 + x^323 + x^321 + x^318 + x^317 + x^314 + x^310 + x^309 + x^308 + x^307 + x^306 + x^305 + x^304 + x^301 + x^300 + x^298 + x^295 + x^292 + x^288 + x^286 + x^285 + x^283 + x^282 + x^281 + x^278 + x^277 + x^275 + x^270 + x^269 + x^263 + x^260 + x^256 + x^254 + x^253 + x^250 + x^249 + x^248 + x^245 + x^244 + x^241 + x^239 + x^237 + x^233 + x^227 + x^225 + x^223 + x^222 + x^220 + x^219 + x^218 + x^216 + x^214 + x^212 + x^207 + x^203 + x^201 + x^200 + x^198 + x^197 + x^196 + x^195 + x^191 + x^189 + x^188 + x^184 + x^183 + x^181 + x^180 + x^179 + x^176 + x^174 + x^173 + x^170 + x^169 + x^168 + x^167 + x^165 + x^164 + x^163 + x^162 + x^161 + x^159 + x^158 + x^157 + x^155 + x^154 + x^152 + x^151 + x^150 + x^147 + x^144 + x^143 + x^142 + x^140 + x^139 + x^138 + x^134 + x^131 + x^130 + x^129 + x^124 + x^123 + x^122 + x^121 + x^120 + x^116 + x^115 + x^114 + x^111 + x^110 + x^108 + x^106 + x^104 + x^103 + x^99 + x^98 + x^95 + x^93 + x^91 + x^87 + x^84 + x^83 + x^80 + x^77 + x^76 + x^75 + x^74 + x^73 + x^70 + x^65 + x^64 + x^63 + x^62 + x^61 + x^57 + x^56 + x^55 + x^53 + x^51 + x^50 + x^49 + x^47 + x^46 + x^45 + x^43 + x^42 + x^41 + x^39 + x^37 + x^36 + x^33 + x^31 + x^29 + x^28 + x^24 + x^23 + x^22 + x^21 + x^18 + x^17 + x^16 + x^11 + x^10 + 1
+
+34-37-5 415 x^928 + x^898 + x^889 + x^874 + x^870 + x^861 + x^846 + x^844 + x^839 + x^835 + x^833 + x^831 + x^818 + x^816 + x^812 + x^809 + x^808 + x^805 + x^804 + x^794 + x^792 + x^790 + x^788 + x^787 + x^784 + x^783 + x^778 + x^776 + x^775 + x^773 + x^772 + x^770 + x^769 + x^768 + x^764 + x^760 + x^759 + x^757 + x^756 + x^755 + x^754 + x^749 + x^748 + x^744 + x^740 + x^737 + x^735 + x^730 + x^729 + x^728 + x^727 + x^726 + x^725 + x^721 + x^720 + x^719 + x^718 + x^716 + x^715 + x^713 + x^712 + x^710 + x^709 + x^706 + x^699 + x^695 + x^689 + x^686 + x^682 + x^681 + x^680 + x^677 + x^674 + x^673 + x^672 + x^671 + x^665 + x^664 + x^663 + x^662 + x^661 + x^660 + x^657 + x^656 + x^651 + x^649 + x^646 + x^640 + x^639 + x^635 + x^634 + x^633 + x^632 + x^629 + x^628 + x^624 + x^623 + x^621 + x^620 + x^616 + x^615 + x^614 + x^613 + x^611 + x^610 + x^609 + x^607 + x^606 + x^605 + x^604 + x^601 + x^599 + x^597 + x^596 + x^595 + x^593 + x^591 + x^590 + x^585 + x^584 + x^583 + x^582 + x^580 + x^577 + x^576 + x^573 + x^569 + x^567 + x^564 + x^560 + x^559 + x^558 + x^557 + x^556 + x^555 + x^552 + x^551 + x^550 + x^547 + x^545 + x^544 + x^542 + x^541 + x^540 + x^539 + x^538 + x^535 + x^534 + x^533 + x^526 + x^523 + x^520 + x^518 + x^517 + x^515 + x^514 + x^513 + x^511 + x^510 + x^509 + x^504 + x^503 + x^502 + x^501 + x^496 + x^495 + x^494 + x^493 + x^492 + x^489 + x^485 + x^484 + x^482 + x^481 + x^478 + x^475 + x^472 + x^469 + x^468 + x^467 + x^465 + x^464 + x^462 + x^460 + x^455 + x^453 + x^452 + x^451 + x^449 + x^448 + x^447 + x^446 + x^445 + x^443 + x^442 + x^441 + x^438 + x^435 + x^434 + x^432 + x^431 + x^430 + x^427 + x^424 + x^423 + x^422 + x^419 + x^412 + x^411 + x^409 + x^408 + x^406 + x^405 + x^404 + x^403 + x^401 + x^400 + x^399 + x^393 + x^390 + x^389 + x^387 + x^385 + x^384 + x^380 + x^378 + x^376 + x^374 + x^372 + x^371 + x^370 + x^369 + x^366 + x^365 + x^360 + x^359 + x^357 + x^350 + x^349 + x^347 + x^346 + x^345 + x^344 + x^342 + x^341 + x^340 + x^337 + x^335 + x^334 + x^332 + x^331 + x^330 + x^328 + x^327 + x^325 + x^323 + x^322 + x^321 + x^320 + x^316 + x^314 + x^310 + x^308 + x^306 + x^305 + x^304 + x^301 + x^300 + x^295 + x^291 + x^290 + x^289 + x^288 + x^287 + x^283 + x^281 + x^280 + x^279 + x^277 + x^274 + x^272 + x^271 + x^268 + x^266 + x^264 + x^263 + x^261 + x^259 + x^255 + x^254 + x^253 + x^250 + x^249 + x^246 + x^244 + x^242 + x^241 + x^237 + x^233 + x^230 + x^229 + x^227 + x^223 + x^222 + x^217 + x^216 + x^208 + x^207 + x^206 + x^205 + x^204 + x^203 + x^198 + x^196 + x^192 + x^191 + x^190 + x^189 + x^188 + x^187 + x^186 + x^185 + x^182 + x^181 + x^180 + x^178 + x^175 + x^171 + x^166 + x^165 + x^164 + x^163 + x^162 + x^161 + x^159 + x^157 + x^156 + x^149 + x^148 + x^146 + x^145 + x^143 + x^142 + x^141 + x^140 + x^139 + x^138 + x^136 + x^135 + x^131 + x^130 + x^129 + x^127 + x^125 + x^124 + x^117 + x^115 + x^113 + x^110 + x^108 + x^107 + x^106 + x^105 + x^103 + x^99 + x^98 + x^95 + x^93 + x^90 + x^87 + x^84 + x^83 + x^81 + x^80 + x^79 + x^78 + x^77 + x^72 + x^71 + x^68 + x^65 + x^64 + x^63 + x^62 + x^59 + x^58 + x^56 + x^55 + x^54 + x^53 + x^52 + x^51 + x^46 + x^45 + x^44 + x^43 + x^40 + x^39 + x^36 + x^35 + x^33 + x^32 + x^31 + x^30 + x^27 + x^25 + x^24 + x^22 + x^18 + x^17 + x^14 + x^13 + x^12 + x^10 + 1
+
+37-3-56 415 x^928 + x^898 + x^878 + x^870 + x^862 + x^860 + x^849 + x^840 + x^831 + x^822 + x^819 + x^818 + x^811 + x^802 + x^801 + x^796 + x^795 + x^794 + x^793 + x^790 + x^789 + x^784 + x^781 + x^780 + x^777 + x^775 + x^772 + x^766 + x^760 + x^758 + x^755 + x^753 + x^752 + x^747 + x^745 + x^744 + x^743 + x^740 + x^738 + x^737 + x^736 + x^732 + x^730 + x^729 + x^728 + x^726 + x^721 + x^716 + x^715 + x^713 + x^712 + x^711 + x^710 + x^709 + x^706 + x^705 + x^702 + x^700 + x^699 + x^698 + x^697 + x^696 + x^693 + x^692 + x^690 + x^687 + x^686 + x^684 + x^683 + x^682 + x^681 + x^680 + x^678 + x^675 + x^674 + x^673 + x^672 + x^670 + x^669 + x^667 + x^664 + x^662 + x^661 + x^660 + x^658 + x^657 + x^656 + x^654 + x^653 + x^652 + x^650 + x^649 + x^648 + x^645 + x^644 + x^641 + x^639 + x^635 + x^634 + x^631 + x^630 + x^629 + x^628 + x^622 + x^621 + x^620 + x^617 + x^616 + x^614 + x^610 + x^609 + x^608 + x^606 + x^604 + x^601 + x^600 + x^598 + x^597 + x^596 + x^593 + x^592 + x^590 + x^588 + x^587 + x^586 + x^585 + x^584 + x^583 + x^579 + x^578 + x^575 + x^574 + x^573 + x^569 + x^568 + x^566 + x^564 + x^563 + x^561 + x^559 + x^557 + x^556 + x^553 + x^552 + x^550 + x^548 + x^546 + x^543 + x^542 + x^541 + x^540 + x^538 + x^537 + x^536 + x^533 + x^532 + x^529 + x^528 + x^527 + x^525 + x^522 + x^520 + x^519 + x^518 + x^517 + x^515 + x^514 + x^513 + x^509 + x^507 + x^506 + x^504 + x^503 + x^502 + x^499 + x^495 + x^494 + x^493 + x^492 + x^490 + x^486 + x^482 + x^481 + x^480 + x^479 + x^477 + x^476 + x^475 + x^474 + x^473 + x^472 + x^470 + x^468 + x^467 + x^463 + x^457 + x^453 + x^451 + x^448 + x^446 + x^445 + x^440 + x^438 + x^437 + x^434 + x^433 + x^432 + x^431 + x^430 + x^425 + x^424 + x^423 + x^417 + x^414 + x^409 + x^407 + x^406 + x^405 + x^402 + x^400 + x^399 + x^398 + x^397 + x^396 + x^395 + x^394 + x^391 + x^389 + x^387 + x^386 + x^384 + x^383 + x^379 + x^377 + x^372 + x^371 + x^369 + x^368 + x^366 + x^365 + x^364 + x^361 + x^359 + x^357 + x^354 + x^351 + x^348 + x^347 + x^340 + x^339 + x^337 + x^336 + x^334 + x^329 + x^327 + x^326 + x^325 + x^322 + x^320 + x^318 + x^315 + x^314 + x^313 + x^312 + x^310 + x^309 + x^308 + x^306 + x^305 + x^301 + x^300 + x^298 + x^294 + x^293 + x^292 + x^291 + x^288 + x^285 + x^284 + x^282 + x^279 + x^275 + x^272 + x^271 + x^270 + x^269 + x^268 + x^266 + x^259 + x^257 + x^254 + x^253 + x^251 + x^250 + x^248 + x^246 + x^244 + x^243 + x^242 + x^238 + x^237 + x^234 + x^233 + x^232 + x^231 + x^230 + x^227 + x^223 + x^222 + x^221 + x^219 + x^216 + x^215 + x^212 + x^207 + x^205 + x^203 + x^200 + x^199 + x^198 + x^196 + x^195 + x^193 + x^191 + x^187 + x^185 + x^183 + x^181 + x^179 + x^178 + x^177 + x^174 + x^171 + x^170 + x^168 + x^166 + x^165 + x^163 + x^160 + x^156 + x^155 + x^154 + x^151 + x^150 + x^149 + x^146 + x^145 + x^142 + x^141 + x^136 + x^135 + x^134 + x^132 + x^128 + x^127 + x^125 + x^121 + x^118 + x^117 + x^116 + x^113 + x^112 + x^111 + x^108 + x^106 + x^105 + x^104 + x^102 + x^101 + x^100 + x^99 + x^96 + x^95 + x^94 + x^89 + x^85 + x^83 + x^81 + x^80 + x^79 + x^69 + x^65 + x^63 + x^62 + x^61 + x^59 + x^58 + x^57 + x^56 + x^52 + x^49 + x^46 + x^45 + x^43 + x^42 + x^41 + x^40 + x^39 + x^38 + x^37 + x^36 + x^33 + x^32 + x^28 + x^24 + x^23 + x^20 + x^18 + x^17 + x^14 + x^11 + x^10 + x^9 + x^8 + 1
+
+55-11-54 417 x^928 + x^898 + x^896 + x^870 + x^867 + x^866 + x^864 + x^853 + x^846 + x^837 + x^836 + x^835 + x^828 + x^826 + x^824 + x^823 + x^817 + x^814 + x^812 + x^810 + x^808 + x^807 + x^806 + x^805 + x^804 + x^803 + x^802 + x^800 + x^796 + x^791 + x^789 + x^786 + x^784 + x^781 + x^780 + x^777 + x^772 + x^771 + x^770 + x^767 + x^762 + x^761 + x^757 + x^753 + x^747 + x^742 + x^740 + x^739 + x^737 + x^736 + x^735 + x^734 + x^733 + x^731 + x^730 + x^725 + x^723 + x^722 + x^717 + x^715 + x^708 + x^707 + x^705 + x^704 + x^703 + x^699 + x^698 + x^695 + x^690 + x^689 + x^686 + x^685 + x^684 + x^682 + x^681 + x^680 + x^678 + x^677 + x^675 + x^669 + x^667 + x^666 + x^665 + x^664 + x^663 + x^662 + x^661 + x^660 + x^658 + x^657 + x^656 + x^655 + x^654 + x^651 + x^650 + x^646 + x^645 + x^643 + x^641 + x^640 + x^639 + x^637 + x^634 + x^633 + x^632 + x^631 + x^627 + x^624 + x^622 + x^620 + x^617 + x^616 + x^615 + x^614 + x^613 + x^608 + x^601 + x^600 + x^599 + x^595 + x^592 + x^591 + x^590 + x^586 + x^580 + x^579 + x^578 + x^577 + x^576 + x^575 + x^571 + x^570 + x^569 + x^567 + x^566 + x^565 + x^564 + x^563 + x^562 + x^561 + x^560 + x^558 + x^557 + x^555 + x^554 + x^553 + x^552 + x^551 + x^550 + x^549 + x^545 + x^543 + x^542 + x^539 + x^537 + x^532 + x^530 + x^526 + x^525 + x^520 + x^519 + x^517 + x^515 + x^513 + x^511 + x^510 + x^508 + x^504 + x^502 + x^501 + x^498 + x^493 + x^492 + x^490 + x^489 + x^488 + x^487 + x^485 + x^484 + x^483 + x^481 + x^480 + x^479 + x^477 + x^475 + x^473 + x^472 + x^469 + x^468 + x^467 + x^466 + x^463 + x^462 + x^461 + x^459 + x^455 + x^453 + x^451 + x^450 + x^449 + x^445 + x^444 + x^443 + x^442 + x^441 + x^440 + x^437 + x^435 + x^434 + x^431 + x^430 + x^429 + x^427 + x^426 + x^422 + x^421 + x^420 + x^413 + x^410 + x^409 + x^408 + x^407 + x^405 + x^403 + x^402 + x^401 + x^397 + x^396 + x^393 + x^389 + x^386 + x^384 + x^380 + x^379 + x^376 + x^373 + x^372 + x^370 + x^369 + x^367 + x^365 + x^364 + x^363 + x^358 + x^356 + x^355 + x^354 + x^353 + x^349 + x^345 + x^342 + x^334 + x^332 + x^331 + x^329 + x^325 + x^324 + x^322 + x^316 + x^315 + x^314 + x^312 + x^310 + x^307 + x^306 + x^298 + x^297 + x^296 + x^294 + x^293 + x^292 + x^288 + x^285 + x^284 + x^283 + x^282 + x^279 + x^273 + x^271 + x^267 + x^262 + x^257 + x^255 + x^253 + x^252 + x^251 + x^250 + x^248 + x^247 + x^245 + x^244 + x^243 + x^240 + x^238 + x^237 + x^236 + x^234 + x^232 + x^229 + x^224 + x^223 + x^222 + x^221 + x^218 + x^216 + x^215 + x^213 + x^211 + x^210 + x^209 + x^207 + x^205 + x^203 + x^202 + x^201 + x^198 + x^195 + x^194 + x^193 + x^192 + x^190 + x^189 + x^187 + x^186 + x^185 + x^184 + x^183 + x^182 + x^181 + x^179 + x^177 + x^176 + x^175 + x^174 + x^172 + x^170 + x^167 + x^160 + x^157 + x^156 + x^153 + x^151 + x^150 + x^149 + x^143 + x^140 + x^137 + x^136 + x^134 + x^133 + x^129 + x^128 + x^124 + x^123 + x^120 + x^118 + x^117 + x^116 + x^115 + x^114 + x^112 + x^111 + x^110 + x^108 + x^105 + x^104 + x^102 + x^101 + x^100 + x^98 + x^97 + x^93 + x^92 + x^91 + x^90 + x^88 + x^87 + x^85 + x^81 + x^79 + x^77 + x^76 + x^74 + x^73 + x^72 + x^70 + x^65 + x^63 + x^62 + x^61 + x^59 + x^55 + x^53 + x^51 + x^50 + x^47 + x^46 + x^45 + x^44 + x^43 + x^40 + x^38 + x^34 + x^32 + x^30 + x^29 + x^28 + x^27 + x^24 + x^22 + x^21 + x^18 + x^17 + x^14 + x^11 + x^4 + 1
+
+30-3-41 419 x^928 + x^906 + x^898 + x^884 + x^879 + x^876 + x^870 + x^862 + x^854 + x^852 + x^849 + x^844 + x^835 + x^832 + x^829 + x^825 + x^822 + x^819 + x^818 + x^813 + x^812 + x^807 + x^805 + x^803 + x^802 + x^798 + x^795 + x^794 + x^792 + x^790 + x^789 + x^788 + x^786 + x^785 + x^778 + x^777 + x^769 + x^768 + x^762 + x^760 + x^753 + x^751 + x^748 + x^747 + x^746 + x^742 + x^738 + x^735 + x^734 + x^733 + x^731 + x^729 + x^726 + x^725 + x^723 + x^719 + x^718 + x^716 + x^713 + x^706 + x^703 + x^702 + x^701 + x^700 + x^699 + x^696 + x^693 + x^690 + x^687 + x^686 + x^685 + x^684 + x^682 + x^679 + x^677 + x^673 + x^672 + x^671 + x^670 + x^664 + x^659 + x^656 + x^653 + x^651 + x^650 + x^647 + x^643 + x^642 + x^639 + x^637 + x^635 + x^633 + x^630 + x^627 + x^625 + x^624 + x^621 + x^616 + x^615 + x^614 + x^613 + x^612 + x^607 + x^604 + x^603 + x^600 + x^597 + x^596 + x^595 + x^593 + x^592 + x^591 + x^588 + x^586 + x^583 + x^581 + x^580 + x^578 + x^575 + x^574 + x^571 + x^569 + x^568 + x^567 + x^566 + x^565 + x^564 + x^562 + x^560 + x^559 + x^558 + x^557 + x^555 + x^554 + x^553 + x^552 + x^550 + x^546 + x^545 + x^543 + x^542 + x^537 + x^535 + x^534 + x^532 + x^530 + x^527 + x^525 + x^523 + x^521 + x^520 + x^512 + x^506 + x^505 + x^504 + x^503 + x^501 + x^500 + x^499 + x^498 + x^497 + x^495 + x^494 + x^493 + x^489 + x^487 + x^485 + x^484 + x^479 + x^478 + x^477 + x^475 + x^474 + x^471 + x^470 + x^469 + x^468 + x^467 + x^466 + x^464 + x^462 + x^459 + x^458 + x^457 + x^456 + x^451 + x^449 + x^448 + x^447 + x^446 + x^443 + x^441 + x^440 + x^439 + x^437 + x^435 + x^434 + x^433 + x^432 + x^431 + x^430 + x^427 + x^425 + x^424 + x^423 + x^420 + x^419 + x^418 + x^417 + x^416 + x^414 + x^412 + x^410 + x^409 + x^405 + x^404 + x^402 + x^401 + x^400 + x^396 + x^394 + x^393 + x^391 + x^390 + x^389 + x^388 + x^387 + x^386 + x^385 + x^380 + x^379 + x^369 + x^368 + x^363 + x^362 + x^361 + x^360 + x^359 + x^355 + x^354 + x^351 + x^347 + x^346 + x^345 + x^342 + x^337 + x^336 + x^332 + x^328 + x^324 + x^322 + x^321 + x^319 + x^318 + x^317 + x^315 + x^312 + x^310 + x^309 + x^307 + x^303 + x^302 + x^300 + x^298 + x^295 + x^289 + x^288 + x^287 + x^286 + x^285 + x^284 + x^283 + x^282 + x^281 + x^276 + x^275 + x^273 + x^272 + x^271 + x^268 + x^265 + x^263 + x^262 + x^260 + x^259 + x^255 + x^254 + x^253 + x^252 + x^249 + x^245 + x^244 + x^243 + x^242 + x^241 + x^240 + x^239 + x^236 + x^235 + x^233 + x^232 + x^231 + x^230 + x^224 + x^223 + x^222 + x^221 + x^218 + x^215 + x^214 + x^213 + x^209 + x^206 + x^204 + x^199 + x^197 + x^196 + x^194 + x^190 + x^186 + x^185 + x^183 + x^182 + x^181 + x^180 + x^179 + x^178 + x^177 + x^176 + x^175 + x^174 + x^173 + x^168 + x^167 + x^166 + x^165 + x^164 + x^163 + x^162 + x^161 + x^159 + x^158 + x^156 + x^155 + x^153 + x^151 + x^148 + x^144 + x^143 + x^142 + x^141 + x^139 + x^136 + x^135 + x^131 + x^129 + x^128 + x^127 + x^126 + x^125 + x^124 + x^123 + x^121 + x^119 + x^118 + x^116 + x^113 + x^111 + x^109 + x^107 + x^106 + x^103 + x^102 + x^100 + x^99 + x^98 + x^96 + x^93 + x^92 + x^90 + x^86 + x^85 + x^83 + x^82 + x^80 + x^76 + x^73 + x^72 + x^71 + x^70 + x^67 + x^66 + x^64 + x^61 + x^60 + x^59 + x^56 + x^53 + x^50 + x^49 + x^45 + x^44 + x^42 + x^39 + x^36 + x^35 + x^30 + x^28 + x^25 + x^22 + x^19 + x^18 + x^17 + x^15 + x^14 + x^11 + x^10 + x^5 + 1
+
+11-45-50 423 x^928 + x^898 + x^891 + x^870 + x^862 + x^861 + x^858 + x^857 + x^854 + x^851 + x^828 + x^825 + x^824 + x^822 + x^818 + x^814 + x^811 + x^808 + x^802 + x^800 + x^798 + x^797 + x^787 + x^786 + x^785 + x^783 + x^782 + x^781 + x^776 + x^772 + x^771 + x^770 + x^768 + x^765 + x^760 + x^758 + x^756 + x^754 + x^750 + x^749 + x^746 + x^742 + x^738 + x^737 + x^736 + x^735 + x^734 + x^732 + x^729 + x^723 + x^719 + x^718 + x^716 + x^715 + x^714 + x^713 + x^708 + x^707 + x^705 + x^704 + x^703 + x^702 + x^701 + x^700 + x^698 + x^697 + x^696 + x^694 + x^692 + x^688 + x^684 + x^683 + x^681 + x^680 + x^678 + x^666 + x^664 + x^663 + x^662 + x^660 + x^659 + x^658 + x^656 + x^654 + x^653 + x^652 + x^651 + x^650 + x^649 + x^647 + x^645 + x^642 + x^641 + x^639 + x^638 + x^637 + x^636 + x^634 + x^632 + x^631 + x^626 + x^625 + x^623 + x^620 + x^617 + x^616 + x^614 + x^612 + x^610 + x^609 + x^607 + x^605 + x^603 + x^601 + x^600 + x^598 + x^597 + x^596 + x^595 + x^594 + x^591 + x^589 + x^588 + x^586 + x^585 + x^584 + x^581 + x^579 + x^578 + x^577 + x^576 + x^575 + x^573 + x^572 + x^570 + x^569 + x^568 + x^566 + x^561 + x^559 + x^558 + x^557 + x^554 + x^552 + x^551 + x^550 + x^549 + x^548 + x^546 + x^544 + x^543 + x^541 + x^540 + x^538 + x^533 + x^531 + x^529 + x^528 + x^523 + x^519 + x^515 + x^512 + x^511 + x^510 + x^508 + x^507 + x^506 + x^501 + x^498 + x^497 + x^496 + x^495 + x^494 + x^492 + x^490 + x^489 + x^488 + x^487 + x^486 + x^485 + x^483 + x^477 + x^476 + x^474 + x^472 + x^470 + x^469 + x^467 + x^465 + x^462 + x^460 + x^458 + x^452 + x^451 + x^449 + x^447 + x^446 + x^445 + x^442 + x^441 + x^440 + x^437 + x^436 + x^434 + x^433 + x^431 + x^428 + x^427 + x^426 + x^425 + x^423 + x^422 + x^420 + x^419 + x^418 + x^417 + x^415 + x^414 + x^413 + x^412 + x^411 + x^409 + x^407 + x^404 + x^403 + x^402 + x^399 + x^398 + x^396 + x^395 + x^392 + x^391 + x^389 + x^388 + x^387 + x^386 + x^385 + x^384 + x^381 + x^379 + x^378 + x^377 + x^375 + x^373 + x^369 + x^367 + x^365 + x^364 + x^362 + x^359 + x^358 + x^357 + x^355 + x^351 + x^348 + x^347 + x^346 + x^345 + x^344 + x^343 + x^335 + x^334 + x^332 + x^328 + x^325 + x^324 + x^321 + x^319 + x^318 + x^316 + x^314 + x^312 + x^311 + x^310 + x^304 + x^300 + x^297 + x^296 + x^294 + x^293 + x^292 + x^291 + x^289 + x^288 + x^285 + x^283 + x^277 + x^276 + x^274 + x^271 + x^270 + x^269 + x^268 + x^265 + x^264 + x^260 + x^259 + x^258 + x^257 + x^256 + x^252 + x^251 + x^249 + x^248 + x^247 + x^246 + x^244 + x^242 + x^238 + x^236 + x^233 + x^232 + x^231 + x^230 + x^229 + x^228 + x^227 + x^222 + x^220 + x^218 + x^214 + x^212 + x^209 + x^208 + x^207 + x^204 + x^203 + x^202 + x^200 + x^193 + x^190 + x^189 + x^188 + x^186 + x^185 + x^183 + x^178 + x^176 + x^174 + x^171 + x^169 + x^168 + x^166 + x^165 + x^163 + x^162 + x^161 + x^158 + x^156 + x^155 + x^154 + x^153 + x^150 + x^147 + x^146 + x^145 + x^141 + x^136 + x^134 + x^132 + x^128 + x^127 + x^126 + x^123 + x^120 + x^119 + x^114 + x^112 + x^111 + x^105 + x^104 + x^101 + x^100 + x^98 + x^97 + x^96 + x^95 + x^94 + x^92 + x^91 + x^88 + x^87 + x^85 + x^84 + x^83 + x^80 + x^78 + x^77 + x^76 + x^74 + x^73 + x^72 + x^68 + x^64 + x^62 + x^61 + x^60 + x^56 + x^55 + x^54 + x^53 + x^50 + x^46 + x^42 + x^41 + x^40 + x^39 + x^36 + x^32 + x^31 + x^30 + x^28 + x^25 + x^24 + x^16 + x^15 + x^14 + x^13 + x^10 + x^9 + x^6 + x^3 + 1
+
+50-19-47 423 x^928 + x^906 + x^898 + x^897 + x^884 + x^876 + x^870 + x^862 + x^854 + x^840 + x^836 + x^835 + x^832 + x^831 + x^830 + x^821 + x^814 + x^813 + x^812 + x^810 + x^808 + x^805 + x^803 + x^796 + x^794 + x^792 + x^791 + x^786 + x^785 + x^783 + x^777 + x^774 + x^773 + x^767 + x^766 + x^764 + x^762 + x^761 + x^760 + x^759 + x^758 + x^754 + x^750 + x^748 + x^747 + x^746 + x^743 + x^742 + x^739 + x^734 + x^732 + x^728 + x^727 + x^724 + x^722 + x^720 + x^718 + x^716 + x^714 + x^713 + x^712 + x^711 + x^709 + x^708 + x^705 + x^704 + x^702 + x^699 + x^698 + x^695 + x^694 + x^693 + x^692 + x^691 + x^688 + x^686 + x^683 + x^682 + x^681 + x^679 + x^676 + x^674 + x^672 + x^671 + x^668 + x^664 + x^663 + x^661 + x^659 + x^657 + x^656 + x^654 + x^652 + x^646 + x^645 + x^641 + x^638 + x^635 + x^634 + x^632 + x^629 + x^628 + x^619 + x^618 + x^617 + x^615 + x^613 + x^612 + x^610 + x^609 + x^607 + x^606 + x^605 + x^604 + x^603 + x^602 + x^598 + x^597 + x^596 + x^595 + x^593 + x^591 + x^590 + x^589 + x^584 + x^583 + x^582 + x^581 + x^580 + x^579 + x^576 + x^575 + x^573 + x^569 + x^568 + x^567 + x^565 + x^564 + x^562 + x^556 + x^554 + x^552 + x^551 + x^550 + x^548 + x^547 + x^546 + x^545 + x^542 + x^541 + x^540 + x^539 + x^537 + x^535 + x^534 + x^532 + x^528 + x^526 + x^525 + x^524 + x^522 + x^521 + x^519 + x^515 + x^513 + x^510 + x^508 + x^507 + x^506 + x^505 + x^504 + x^502 + x^501 + x^500 + x^499 + x^496 + x^495 + x^494 + x^492 + x^490 + x^489 + x^486 + x^485 + x^484 + x^483 + x^481 + x^479 + x^478 + x^476 + x^474 + x^471 + x^469 + x^467 + x^465 + x^463 + x^458 + x^456 + x^455 + x^454 + x^451 + x^449 + x^448 + x^443 + x^442 + x^440 + x^439 + x^437 + x^436 + x^433 + x^432 + x^431 + x^430 + x^428 + x^427 + x^426 + x^425 + x^424 + x^421 + x^420 + x^416 + x^415 + x^413 + x^412 + x^411 + x^410 + x^409 + x^408 + x^406 + x^405 + x^403 + x^400 + x^399 + x^398 + x^396 + x^395 + x^393 + x^391 + x^388 + x^387 + x^386 + x^381 + x^380 + x^377 + x^376 + x^375 + x^374 + x^373 + x^371 + x^370 + x^369 + x^368 + x^361 + x^359 + x^358 + x^357 + x^355 + x^352 + x^350 + x^348 + x^347 + x^346 + x^343 + x^342 + x^339 + x^337 + x^335 + x^334 + x^332 + x^329 + x^325 + x^324 + x^323 + x^322 + x^318 + x^317 + x^315 + x^314 + x^311 + x^310 + x^306 + x^304 + x^300 + x^299 + x^297 + x^295 + x^294 + x^289 + x^286 + x^283 + x^279 + x^278 + x^276 + x^275 + x^273 + x^269 + x^268 + x^266 + x^264 + x^260 + x^258 + x^257 + x^254 + x^252 + x^250 + x^248 + x^247 + x^246 + x^245 + x^241 + x^239 + x^237 + x^236 + x^235 + x^234 + x^232 + x^228 + x^227 + x^226 + x^225 + x^218 + x^215 + x^214 + x^212 + x^211 + x^210 + x^208 + x^206 + x^205 + x^204 + x^203 + x^201 + x^198 + x^196 + x^193 + x^192 + x^190 + x^189 + x^188 + x^184 + x^181 + x^180 + x^178 + x^177 + x^176 + x^175 + x^174 + x^173 + x^171 + x^169 + x^168 + x^166 + x^165 + x^164 + x^162 + x^160 + x^159 + x^158 + x^153 + x^150 + x^148 + x^147 + x^146 + x^143 + x^142 + x^139 + x^136 + x^135 + x^134 + x^133 + x^132 + x^126 + x^124 + x^121 + x^118 + x^116 + x^112 + x^109 + x^108 + x^107 + x^104 + x^101 + x^98 + x^97 + x^95 + x^93 + x^88 + x^86 + x^85 + x^84 + x^83 + x^78 + x^77 + x^73 + x^70 + x^69 + x^68 + x^66 + x^64 + x^63 + x^62 + x^58 + x^57 + x^53 + x^52 + x^50 + x^48 + x^45 + x^43 + x^42 + x^41 + x^40 + x^39 + x^38 + x^33 + x^26 + x^22 + x^21 + x^20 + x^18 + x^17 + x^10 + x^8 + 1
+
+52-27-13 427 x^928 + x^898 + x^870 + x^866 + x^858 + x^855 + x^854 + x^847 + x^844 + x^836 + x^833 + x^832 + x^829 + x^828 + x^825 + x^822 + x^818 + x^817 + x^814 + x^811 + x^808 + x^807 + x^800 + x^799 + x^798 + x^796 + x^795 + x^792 + x^789 + x^781 + x^777 + x^774 + x^770 + x^769 + x^768 + x^767 + x^765 + x^762 + x^759 + x^756 + x^755 + x^754 + x^752 + x^751 + x^748 + x^746 + x^745 + x^744 + x^740 + x^739 + x^738 + x^736 + x^735 + x^734 + x^732 + x^730 + x^729 + x^728 + x^724 + x^721 + x^719 + x^718 + x^717 + x^716 + x^713 + x^712 + x^710 + x^709 + x^706 + x^705 + x^704 + x^702 + x^701 + x^699 + x^698 + x^697 + x^695 + x^693 + x^690 + x^689 + x^687 + x^686 + x^685 + x^683 + x^682 + x^681 + x^680 + x^677 + x^676 + x^675 + x^674 + x^671 + x^669 + x^668 + x^667 + x^666 + x^665 + x^663 + x^660 + x^659 + x^655 + x^654 + x^653 + x^652 + x^650 + x^648 + x^647 + x^643 + x^642 + x^640 + x^639 + x^638 + x^635 + x^634 + x^633 + x^632 + x^630 + x^629 + x^628 + x^626 + x^624 + x^620 + x^618 + x^617 + x^616 + x^615 + x^612 + x^610 + x^607 + x^606 + x^604 + x^603 + x^602 + x^598 + x^597 + x^593 + x^589 + x^588 + x^587 + x^585 + x^583 + x^581 + x^580 + x^579 + x^578 + x^570 + x^569 + x^566 + x^565 + x^564 + x^563 + x^561 + x^559 + x^558 + x^557 + x^556 + x^555 + x^551 + x^550 + x^548 + x^547 + x^545 + x^544 + x^540 + x^539 + x^538 + x^537 + x^536 + x^535 + x^534 + x^532 + x^529 + x^528 + x^527 + x^526 + x^525 + x^524 + x^523 + x^522 + x^519 + x^517 + x^516 + x^515 + x^513 + x^512 + x^511 + x^507 + x^504 + x^502 + x^495 + x^493 + x^492 + x^491 + x^490 + x^489 + x^484 + x^483 + x^481 + x^480 + x^478 + x^466 + x^464 + x^463 + x^460 + x^459 + x^457 + x^455 + x^454 + x^451 + x^450 + x^448 + x^447 + x^435 + x^434 + x^433 + x^432 + x^431 + x^428 + x^424 + x^423 + x^422 + x^421 + x^420 + x^419 + x^414 + x^413 + x^412 + x^411 + x^410 + x^409 + x^407 + x^404 + x^401 + x^396 + x^395 + x^394 + x^391 + x^390 + x^389 + x^388 + x^385 + x^382 + x^379 + x^377 + x^372 + x^370 + x^367 + x^365 + x^362 + x^361 + x^357 + x^355 + x^354 + x^351 + x^349 + x^348 + x^345 + x^343 + x^342 + x^340 + x^338 + x^334 + x^330 + x^328 + x^324 + x^323 + x^320 + x^319 + x^318 + x^317 + x^315 + x^313 + x^310 + x^309 + x^307 + x^303 + x^302 + x^301 + x^300 + x^299 + x^298 + x^297 + x^296 + x^295 + x^292 + x^289 + x^288 + x^287 + x^285 + x^283 + x^280 + x^274 + x^273 + x^271 + x^267 + x^265 + x^264 + x^261 + x^259 + x^258 + x^256 + x^254 + x^253 + x^248 + x^247 + x^244 + x^239 + x^238 + x^237 + x^233 + x^232 + x^230 + x^229 + x^228 + x^227 + x^224 + x^221 + x^217 + x^216 + x^215 + x^214 + x^209 + x^207 + x^206 + x^205 + x^203 + x^201 + x^200 + x^199 + x^196 + x^195 + x^194 + x^192 + x^191 + x^190 + x^189 + x^187 + x^186 + x^182 + x^180 + x^177 + x^176 + x^174 + x^173 + x^170 + x^169 + x^168 + x^167 + x^164 + x^160 + x^154 + x^153 + x^152 + x^148 + x^144 + x^143 + x^142 + x^141 + x^140 + x^139 + x^135 + x^134 + x^133 + x^132 + x^129 + x^125 + x^124 + x^122 + x^121 + x^120 + x^118 + x^117 + x^116 + x^115 + x^112 + x^111 + x^110 + x^109 + x^108 + x^107 + x^106 + x^104 + x^103 + x^101 + x^96 + x^95 + x^93 + x^90 + x^87 + x^86 + x^82 + x^79 + x^77 + x^75 + x^70 + x^68 + x^67 + x^66 + x^62 + x^60 + x^57 + x^54 + x^53 + x^52 + x^51 + x^49 + x^46 + x^45 + x^43 + x^42 + x^41 + x^40 + x^39 + x^38 + x^36 + x^33 + x^31 + x^30 + x^29 + x^27 + x^26 + x^24 + x^22 + x^18 + x^7 + x^6 + 1
+
+54-9-25 433 x^928 + x^898 + x^875 + x^870 + x^860 + x^850 + x^847 + x^840 + x^835 + x^832 + x^822 + x^819 + x^815 + x^812 + x^808 + x^807 + x^805 + x^804 + x^800 + x^797 + x^794 + x^792 + x^791 + x^790 + x^787 + x^785 + x^782 + x^778 + x^777 + x^776 + x^771 + x^770 + x^767 + x^766 + x^764 + x^763 + x^760 + x^759 + x^757 + x^755 + x^754 + x^753 + x^752 + x^748 + x^743 + x^742 + x^739 + x^738 + x^737 + x^735 + x^734 + x^733 + x^731 + x^730 + x^729 + x^725 + x^724 + x^723 + x^720 + x^719 + x^717 + x^716 + x^714 + x^713 + x^711 + x^710 + x^709 + x^706 + x^705 + x^700 + x^699 + x^697 + x^696 + x^695 + x^693 + x^692 + x^691 + x^688 + x^687 + x^686 + x^685 + x^683 + x^682 + x^680 + x^676 + x^671 + x^670 + x^664 + x^663 + x^662 + x^661 + x^660 + x^658 + x^657 + x^656 + x^654 + x^653 + x^649 + x^648 + x^646 + x^645 + x^642 + x^637 + x^635 + x^633 + x^632 + x^630 + x^627 + x^624 + x^623 + x^621 + x^620 + x^619 + x^617 + x^615 + x^614 + x^613 + x^610 + x^609 + x^608 + x^607 + x^604 + x^602 + x^601 + x^600 + x^599 + x^593 + x^592 + x^591 + x^589 + x^585 + x^584 + x^580 + x^576 + x^575 + x^574 + x^570 + x^569 + x^566 + x^565 + x^564 + x^563 + x^562 + x^561 + x^559 + x^558 + x^554 + x^552 + x^551 + x^547 + x^546 + x^545 + x^543 + x^541 + x^540 + x^535 + x^532 + x^531 + x^530 + x^529 + x^525 + x^524 + x^523 + x^521 + x^520 + x^519 + x^518 + x^517 + x^516 + x^515 + x^513 + x^512 + x^510 + x^509 + x^504 + x^503 + x^502 + x^501 + x^500 + x^497 + x^496 + x^494 + x^493 + x^488 + x^487 + x^486 + x^484 + x^482 + x^481 + x^480 + x^479 + x^475 + x^472 + x^465 + x^464 + x^462 + x^461 + x^460 + x^457 + x^456 + x^455 + x^454 + x^452 + x^451 + x^450 + x^449 + x^448 + x^446 + x^445 + x^444 + x^443 + x^441 + x^438 + x^437 + x^436 + x^434 + x^432 + x^430 + x^427 + x^425 + x^424 + x^421 + x^420 + x^419 + x^418 + x^417 + x^414 + x^413 + x^410 + x^409 + x^407 + x^404 + x^403 + x^402 + x^401 + x^400 + x^399 + x^398 + x^396 + x^393 + x^392 + x^391 + x^390 + x^389 + x^385 + x^382 + x^381 + x^380 + x^379 + x^378 + x^375 + x^373 + x^372 + x^367 + x^366 + x^362 + x^358 + x^356 + x^355 + x^354 + x^353 + x^349 + x^348 + x^347 + x^342 + x^340 + x^339 + x^336 + x^334 + x^331 + x^329 + x^328 + x^327 + x^326 + x^325 + x^323 + x^319 + x^317 + x^316 + x^314 + x^313 + x^312 + x^310 + x^309 + x^308 + x^307 + x^302 + x^299 + x^298 + x^297 + x^296 + x^293 + x^291 + x^289 + x^288 + x^286 + x^285 + x^284 + x^282 + x^279 + x^274 + x^272 + x^271 + x^268 + x^266 + x^263 + x^261 + x^258 + x^255 + x^252 + x^251 + x^249 + x^248 + x^247 + x^246 + x^243 + x^242 + x^240 + x^237 + x^236 + x^234 + x^233 + x^232 + x^231 + x^228 + x^226 + x^223 + x^222 + x^221 + x^220 + x^219 + x^217 + x^216 + x^215 + x^213 + x^212 + x^210 + x^205 + x^203 + x^202 + x^199 + x^197 + x^195 + x^194 + x^193 + x^191 + x^189 + x^188 + x^187 + x^184 + x^182 + x^178 + x^173 + x^172 + x^170 + x^169 + x^167 + x^165 + x^162 + x^159 + x^158 + x^157 + x^156 + x^154 + x^149 + x^148 + x^145 + x^144 + x^141 + x^140 + x^135 + x^134 + x^133 + x^131 + x^130 + x^129 + x^127 + x^126 + x^123 + x^120 + x^119 + x^118 + x^117 + x^115 + x^110 + x^108 + x^106 + x^105 + x^104 + x^99 + x^97 + x^95 + x^89 + x^86 + x^84 + x^82 + x^78 + x^75 + x^71 + x^70 + x^69 + x^68 + x^65 + x^63 + x^62 + x^61 + x^59 + x^58 + x^51 + x^50 + x^49 + x^48 + x^47 + x^44 + x^43 + x^42 + x^39 + x^38 + x^37 + x^35 + x^30 + x^27 + x^25 + x^21 + x^19 + x^17 + x^16 + x^13 + x^12 + x^10 + x^8 + x^6 + 1
+
+56-43-35 433 x^928 + x^898 + x^896 + x^871 + x^870 + x^864 + x^848 + x^847 + x^846 + x^841 + x^840 + x^834 + x^833 + x^832 + x^829 + x^821 + x^814 + x^811 + x^808 + x^806 + x^803 + x^798 + x^797 + x^796 + x^792 + x^788 + x^786 + x^784 + x^783 + x^781 + x^779 + x^777 + x^776 + x^774 + x^773 + x^770 + x^769 + x^766 + x^762 + x^760 + x^756 + x^754 + x^752 + x^751 + x^749 + x^746 + x^745 + x^740 + x^737 + x^736 + x^734 + x^730 + x^727 + x^723 + x^721 + x^720 + x^718 + x^716 + x^714 + x^712 + x^709 + x^707 + x^706 + x^705 + x^704 + x^703 + x^702 + x^701 + x^700 + x^699 + x^697 + x^696 + x^695 + x^690 + x^689 + x^687 + x^685 + x^684 + x^682 + x^678 + x^675 + x^672 + x^670 + x^669 + x^668 + x^666 + x^665 + x^663 + x^662 + x^661 + x^659 + x^657 + x^655 + x^651 + x^650 + x^648 + x^646 + x^641 + x^639 + x^634 + x^632 + x^631 + x^630 + x^629 + x^626 + x^625 + x^623 + x^620 + x^619 + x^614 + x^612 + x^610 + x^609 + x^608 + x^607 + x^606 + x^604 + x^603 + x^602 + x^601 + x^600 + x^597 + x^596 + x^595 + x^594 + x^593 + x^591 + x^588 + x^585 + x^584 + x^583 + x^582 + x^581 + x^580 + x^578 + x^576 + x^574 + x^573 + x^572 + x^571 + x^570 + x^569 + x^563 + x^561 + x^560 + x^558 + x^556 + x^553 + x^552 + x^551 + x^550 + x^549 + x^546 + x^545 + x^544 + x^543 + x^542 + x^539 + x^538 + x^537 + x^536 + x^534 + x^532 + x^531 + x^529 + x^523 + x^519 + x^518 + x^517 + x^515 + x^514 + x^513 + x^512 + x^510 + x^509 + x^508 + x^503 + x^502 + x^501 + x^500 + x^499 + x^498 + x^496 + x^495 + x^494 + x^491 + x^490 + x^489 + x^487 + x^486 + x^484 + x^482 + x^481 + x^473 + x^471 + x^468 + x^466 + x^465 + x^464 + x^461 + x^460 + x^457 + x^456 + x^455 + x^453 + x^450 + x^448 + x^444 + x^442 + x^436 + x^435 + x^434 + x^433 + x^432 + x^431 + x^430 + x^429 + x^422 + x^421 + x^420 + x^419 + x^418 + x^417 + x^416 + x^414 + x^413 + x^412 + x^411 + x^409 + x^408 + x^407 + x^406 + x^404 + x^403 + x^402 + x^401 + x^398 + x^395 + x^392 + x^391 + x^389 + x^387 + x^385 + x^380 + x^377 + x^374 + x^372 + x^371 + x^369 + x^366 + x^363 + x^362 + x^361 + x^359 + x^358 + x^356 + x^355 + x^354 + x^353 + x^352 + x^350 + x^349 + x^348 + x^347 + x^345 + x^344 + x^343 + x^336 + x^334 + x^331 + x^330 + x^327 + x^325 + x^324 + x^322 + x^317 + x^310 + x^308 + x^307 + x^304 + x^301 + x^300 + x^299 + x^298 + x^297 + x^293 + x^290 + x^286 + x^284 + x^283 + x^282 + x^281 + x^279 + x^277 + x^275 + x^274 + x^270 + x^269 + x^267 + x^264 + x^262 + x^259 + x^254 + x^253 + x^248 + x^247 + x^245 + x^243 + x^242 + x^241 + x^237 + x^236 + x^232 + x^231 + x^230 + x^229 + x^228 + x^226 + x^225 + x^224 + x^223 + x^221 + x^218 + x^215 + x^214 + x^213 + x^212 + x^210 + x^208 + x^204 + x^202 + x^201 + x^199 + x^196 + x^195 + x^193 + x^192 + x^191 + x^190 + x^186 + x^184 + x^179 + x^178 + x^177 + x^176 + x^175 + x^174 + x^173 + x^171 + x^169 + x^167 + x^166 + x^165 + x^160 + x^158 + x^155 + x^154 + x^153 + x^152 + x^151 + x^150 + x^149 + x^148 + x^147 + x^145 + x^143 + x^140 + x^139 + x^138 + x^134 + x^132 + x^130 + x^129 + x^128 + x^127 + x^120 + x^118 + x^117 + x^115 + x^113 + x^112 + x^109 + x^108 + x^107 + x^106 + x^105 + x^101 + x^100 + x^96 + x^95 + x^94 + x^93 + x^91 + x^89 + x^88 + x^87 + x^85 + x^84 + x^83 + x^82 + x^81 + x^79 + x^77 + x^75 + x^74 + x^73 + x^72 + x^70 + x^68 + x^67 + x^65 + x^64 + x^63 + x^60 + x^58 + x^57 + x^56 + x^54 + x^53 + x^52 + x^50 + x^45 + x^44 + x^43 + x^41 + x^35 + x^30 + x^23 + x^20 + x^18 + x^15 + x^6 + 1
+
+44-9-45 441 x^928 + x^898 + x^890 + x^885 + x^880 + x^872 + x^870 + x^867 + x^860 + x^850 + x^847 + x^842 + x^837 + x^834 + x^830 + x^825 + x^824 + x^817 + x^816 + x^811 + x^808 + x^806 + x^802 + x^800 + x^798 + x^797 + x^794 + x^792 + x^790 + x^787 + x^786 + x^782 + x^778 + x^777 + x^776 + x^774 + x^773 + x^772 + x^771 + x^769 + x^768 + x^767 + x^765 + x^760 + x^759 + x^758 + x^757 + x^754 + x^750 + x^749 + x^747 + x^746 + x^745 + x^743 + x^741 + x^738 + x^737 + x^736 + x^734 + x^732 + x^725 + x^724 + x^722 + x^721 + x^720 + x^717 + x^716 + x^714 + x^713 + x^710 + x^708 + x^707 + x^705 + x^704 + x^702 + x^701 + x^699 + x^698 + x^696 + x^694 + x^692 + x^691 + x^690 + x^686 + x^683 + x^681 + x^679 + x^676 + x^674 + x^673 + x^672 + x^671 + x^668 + x^667 + x^665 + x^664 + x^663 + x^662 + x^661 + x^659 + x^658 + x^657 + x^655 + x^654 + x^652 + x^651 + x^648 + x^644 + x^643 + x^641 + x^640 + x^635 + x^634 + x^633 + x^632 + x^631 + x^630 + x^629 + x^628 + x^624 + x^621 + x^619 + x^618 + x^617 + x^616 + x^614 + x^611 + x^610 + x^608 + x^607 + x^599 + x^598 + x^596 + x^594 + x^590 + x^589 + x^588 + x^587 + x^586 + x^584 + x^581 + x^579 + x^578 + x^577 + x^575 + x^573 + x^572 + x^570 + x^569 + x^568 + x^567 + x^565 + x^564 + x^563 + x^562 + x^561 + x^559 + x^558 + x^554 + x^553 + x^552 + x^551 + x^549 + x^546 + x^544 + x^541 + x^537 + x^536 + x^535 + x^532 + x^531 + x^529 + x^526 + x^517 + x^516 + x^514 + x^511 + x^509 + x^507 + x^502 + x^501 + x^498 + x^497 + x^495 + x^494 + x^493 + x^491 + x^487 + x^486 + x^485 + x^484 + x^483 + x^482 + x^481 + x^480 + x^477 + x^474 + x^473 + x^470 + x^469 + x^467 + x^466 + x^465 + x^463 + x^462 + x^461 + x^460 + x^459 + x^457 + x^455 + x^454 + x^453 + x^451 + x^449 + x^448 + x^446 + x^443 + x^442 + x^440 + x^437 + x^436 + x^435 + x^434 + x^433 + x^431 + x^430 + x^427 + x^423 + x^419 + x^418 + x^414 + x^412 + x^411 + x^410 + x^409 + x^407 + x^406 + x^405 + x^402 + x^397 + x^395 + x^394 + x^389 + x^388 + x^384 + x^381 + x^380 + x^379 + x^378 + x^376 + x^373 + x^372 + x^371 + x^370 + x^368 + x^367 + x^366 + x^365 + x^364 + x^362 + x^361 + x^355 + x^354 + x^352 + x^350 + x^347 + x^345 + x^344 + x^343 + x^342 + x^339 + x^337 + x^335 + x^333 + x^332 + x^329 + x^327 + x^323 + x^322 + x^321 + x^320 + x^319 + x^316 + x^312 + x^310 + x^309 + x^308 + x^307 + x^305 + x^303 + x^302 + x^301 + x^298 + x^294 + x^293 + x^283 + x^282 + x^276 + x^275 + x^274 + x^271 + x^267 + x^264 + x^262 + x^261 + x^259 + x^258 + x^257 + x^256 + x^253 + x^252 + x^251 + x^250 + x^246 + x^245 + x^244 + x^243 + x^242 + x^241 + x^240 + x^238 + x^237 + x^236 + x^235 + x^233 + x^232 + x^229 + x^228 + x^225 + x^224 + x^223 + x^220 + x^216 + x^211 + x^210 + x^207 + x^205 + x^204 + x^202 + x^201 + x^200 + x^197 + x^196 + x^195 + x^194 + x^190 + x^189 + x^185 + x^183 + x^182 + x^181 + x^180 + x^179 + x^177 + x^176 + x^174 + x^173 + x^172 + x^171 + x^168 + x^167 + x^164 + x^163 + x^157 + x^156 + x^152 + x^151 + x^150 + x^148 + x^147 + x^146 + x^143 + x^142 + x^141 + x^140 + x^139 + x^138 + x^137 + x^135 + x^134 + x^133 + x^132 + x^129 + x^128 + x^127 + x^125 + x^122 + x^120 + x^119 + x^113 + x^112 + x^110 + x^109 + x^108 + x^107 + x^106 + x^105 + x^104 + x^101 + x^98 + x^97 + x^96 + x^93 + x^92 + x^91 + x^87 + x^83 + x^80 + x^78 + x^77 + x^74 + x^72 + x^66 + x^64 + x^63 + x^60 + x^59 + x^56 + x^51 + x^50 + x^49 + x^46 + x^43 + x^42 + x^41 + x^39 + x^38 + x^32 + x^31 + x^29 + x^28 + x^26 + x^24 + x^23 + x^21 + x^20 + x^19 + x^18 + x^15 + x^10 + 1
diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl
index c9ef9da990..06d8fe9255 100644
--- a/lib/stdlib/test/re_SUITE.erl
+++ b/lib/stdlib/test/re_SUITE.erl
@@ -28,7 +28,8 @@
pcre_compile_workspace_overflow/1,re_infinite_loop/1,
re_backwards_accented/1,opt_dupnames/1,opt_all_names/1,inspect/1,
opt_no_start_optimize/1,opt_never_utf/1,opt_ucp/1,
- match_limit/1,sub_binaries/1,copt/1]).
+ match_limit/1,sub_binaries/1,copt/1,global_unicode_validation/1,
+ yield_on_subject_validation/1]).
-include_lib("common_test/include/ct.hrl").
-include_lib("kernel/include/file.hrl").
@@ -45,7 +46,8 @@ all() ->
pcre_compile_workspace_overflow, re_infinite_loop,
re_backwards_accented, opt_dupnames, opt_all_names,
inspect, opt_no_start_optimize,opt_never_utf,opt_ucp,
- match_limit, sub_binaries, re_version].
+ match_limit, sub_binaries, re_version, global_unicode_validation,
+ yield_on_subject_validation].
groups() ->
[].
@@ -200,7 +202,58 @@ re_version(_Config) ->
{match,[Version]} = re:run(Version,"^[0-9]\\.[0-9]{2} 20[0-9]{2}-[0-9]{2}-[0-9]{2}",[{capture,all,binary}]),
ok.
+global_unicode_validation(Config) when is_list(Config) ->
+ %% Test that unicode validation of the subject is not done
+ %% for every match found...
+ Bin = binary:copy(<<"abc\n">>,100000),
+ {TimeAscii, _} = take_time(fun () ->
+ re:run(Bin, <<"b">>, [global])
+ end),
+ {TimeUnicode, _} = take_time(fun () ->
+ re:run(Bin, <<"b">>, [unicode,global])
+ end),
+ if TimeAscii == 0; TimeUnicode == 0 ->
+ {comment, "Not good enough resolution to compare results"};
+ true ->
+ %% The time the operations takes should be in the
+ %% same order of magnitude. If validation of the
+ %% whole subject occurs for every match, the unicode
+ %% variant will take way longer time...
+ true = TimeUnicode div TimeAscii < 10
+ end.
+
+take_time(Fun) ->
+ Start = erlang:monotonic_time(nanosecond),
+ Res = Fun(),
+ End = erlang:monotonic_time(nanosecond),
+ {End-Start, Res}.
+
+yield_on_subject_validation(Config) when is_list(Config) ->
+ Go = make_ref(),
+ Bin = binary:copy(<<"abc\n">>,100000),
+ {P, M} = spawn_opt(fun () ->
+ receive Go -> ok end,
+ {match,[{1,1}]} = re:run(Bin, <<"b">>, [unicode])
+ end,
+ [link, monitor]),
+ 1 = erlang:trace(P, true, [running]),
+ P ! Go,
+ N = count_re_run_trap_out(P, M),
+ true = N >= 5,
+ ok.
+count_re_run_trap_out(P, M) when is_reference(M) ->
+ receive {'DOWN',M,process,P,normal} -> ok end,
+ TD = erlang:trace_delivered(P),
+ receive {trace_delivered, P, TD} -> ok end,
+ count_re_run_trap_out(P, 0);
+count_re_run_trap_out(P, N) when is_integer(N) ->
+ receive
+ {trace,P,out,{erlang,re_run_trap,3}} ->
+ count_re_run_trap_out(P, N+1)
+ after 0 ->
+ N
+ end.
%% Test compile options given directly to run.
combined_options(Config) when is_list(Config) ->
diff --git a/lib/stdlib/test/re_SUITE_data/testoutput1 b/lib/stdlib/test/re_SUITE_data/testoutput1
index eff8ecc948..e6147e60b9 100644
--- a/lib/stdlib/test/re_SUITE_data/testoutput1
+++ b/lib/stdlib/test/re_SUITE_data/testoutput1
@@ -9446,4 +9446,28 @@ No match
>XXX<
0: X
+/ (?<word> \w+ )* \. /xi
+ pokus.
+ 0: pokus.
+ 1: pokus
+
+/(?(DEFINE) (?<word> \w+ ) ) (?&word)* \./xi
+ pokus.
+ 0: pokus.
+
+/(?(DEFINE) (?<word> \w+ ) ) ( (?&word)* ) \./xi
+ pokus.
+ 0: pokus.
+ 1: <unset>
+ 2: pokus
+
+/(?&word)* (?(DEFINE) (?<word> \w+ ) ) \./xi
+ pokus.
+ 0: pokus.
+
+/(?&word)* \. (?<word> \w+ )/xi
+ pokus.hokus
+ 0: pokus.hokus
+ 1: hokus
+
/-- End of testinput1 --/
diff --git a/lib/stdlib/test/re_SUITE_data/testoutput2 b/lib/stdlib/test/re_SUITE_data/testoutput2
index 61ed8d9d4e..4ccda27201 100644
--- a/lib/stdlib/test/re_SUITE_data/testoutput2
+++ b/lib/stdlib/test/re_SUITE_data/testoutput2
@@ -14721,4 +14721,8 @@ No need char
0: ab
1: a
+/(?(?=^))b/
+ abc
+ 0: b
+
/-- End of testinput2 --/
diff --git a/lib/stdlib/test/re_SUITE_data/testoutput4 b/lib/stdlib/test/re_SUITE_data/testoutput4
index d43c12392d..69e812cd35 100644
--- a/lib/stdlib/test/re_SUITE_data/testoutput4
+++ b/lib/stdlib/test/re_SUITE_data/testoutput4
@@ -1277,4 +1277,8 @@ No match
\\C(\\W?ſ)'?{{
No match
+/[^\x{100}-\x{ffff}]*[\x80-\xff]/8
+ \x{99}\x{99}\x{99}
+ 0: \x{99}\x{99}\x{99}
+
/-- End of testinput4 --/
diff --git a/lib/stdlib/test/re_testoutput1_replacement_test.erl b/lib/stdlib/test/re_testoutput1_replacement_test.erl
index f14df547ef..bb43047757 100644
--- a/lib/stdlib/test/re_testoutput1_replacement_test.erl
+++ b/lib/stdlib/test/re_testoutput1_replacement_test.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2008-2017. All Rights Reserved.
+%% Copyright Ericsson AB 2008-2019. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -20014,4 +20014,31 @@ run56() ->
<<" MumdPEeFred:099">> = iolist_to_binary(re:replace(" Fred:099","(?=.*[A-Z])(?=.*[a-z])(?=.*[0-9])(?=.*[,;:])(?=.{8,16})(?!.*[\\s])","\\1&M&umdPE&e",[global])),
<<" ugxGKrBXEcHyG">> = iolist_to_binary(re:replace(" X","(?=.*X)X$","ugxGKrB&EcHyG",[])),
<<" ugxGKrBXEcHyG">> = iolist_to_binary(re:replace(" X","(?=.*X)X$","ugxGKrB&EcHyG",[global])),
+ <<">MHFvXX<">> = iolist_to_binary(re:replace(">XXX<","X+(?#comment)?","MHFv",[])),
+ <<">MHFvMHFvMHFv<">> = iolist_to_binary(re:replace(">XXX<","X+(?#comment)?","MHFv",[global])),
+ <<"lTpokusldxfHXOpokuswsrRorpokus.">> = iolist_to_binary(re:replace("pokus."," (?<word> \\w+ )* \\. ","lT\\1ldxfHXO\\1wsrRor&",[extended,
+ caseless])),
+ <<"lTpokusldxfHXOpokuswsrRorpokus.">> = iolist_to_binary(re:replace("pokus."," (?<word> \\w+ )* \\. ","lT\\1ldxfHXO\\1wsrRor&",[extended,
+ caseless,
+ global])),
+ <<"Oeapokus.xo">> = iolist_to_binary(re:replace("pokus.","(?(DEFINE) (?<word> \\w+ ) ) (?&word)* \\.","Oea&xo",[extended,
+ caseless])),
+ <<"Oeapokus.xo">> = iolist_to_binary(re:replace("pokus.","(?(DEFINE) (?<word> \\w+ ) ) (?&word)* \\.","Oea&xo",[extended,
+ caseless,
+ global])),
+ <<"Wpokus.pity">> = iolist_to_binary(re:replace("pokus.","(?(DEFINE) (?<word> \\w+ ) ) ( (?&word)* ) \\.","W&pity",[extended,
+ caseless])),
+ <<"Wpokus.pity">> = iolist_to_binary(re:replace("pokus.","(?(DEFINE) (?<word> \\w+ ) ) ( (?&word)* ) \\.","W&pity",[extended,
+ caseless,
+ global])),
+ <<"iujmNtBvmcyi">> = iolist_to_binary(re:replace("pokus.","(?&word)* (?(DEFINE) (?<word> \\w+ ) ) \\.","iuj\\1m\\1NtBvmcyi\\1",[extended,
+ caseless])),
+ <<"iujmNtBvmcyi">> = iolist_to_binary(re:replace("pokus.","(?&word)* (?(DEFINE) (?<word> \\w+ ) ) \\.","iuj\\1m\\1NtBvmcyi\\1",[extended,
+ caseless,
+ global])),
+ <<"Ipokus.hokusbQpokus.hokusB">> = iolist_to_binary(re:replace("pokus.hokus","(?&word)* \\. (?<word> \\w+ )","I&bQ&B",[extended,
+ caseless])),
+ <<"Ipokus.hokusbQpokus.hokusB">> = iolist_to_binary(re:replace("pokus.hokus","(?&word)* \\. (?<word> \\w+ )","I&bQ&B",[extended,
+ caseless,
+ global])),
ok.
diff --git a/lib/stdlib/test/re_testoutput1_split_test.erl b/lib/stdlib/test/re_testoutput1_split_test.erl
index 8218cd9bd2..fcffa89e3f 100644
--- a/lib/stdlib/test/re_testoutput1_split_test.erl
+++ b/lib/stdlib/test/re_testoutput1_split_test.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2008-2017. All Rights Reserved.
+%% Copyright Ericsson AB 2008-2019. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -84,1360 +84,1360 @@ run() ->
run56(),
ok.
run0() ->
- <<"">> = iolist_to_binary(join(re:split("the quick brown fox","the quick brown fox",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("the quick brown fox","the quick brown fox",[trim]))),
<<":">> = iolist_to_binary(join(re:split("the quick brown fox","the quick brown fox",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("the quick brown fox","the quick brown fox",[]))),
- <<"The quick brown FOX">> = iolist_to_binary(join(re:split("The quick brown FOX","the quick brown fox",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("the quick brown fox","the quick brown fox",[]))),
+ <<"The quick brown FOX">> = iolist_to_binary(join(re:split("The quick brown FOX","the quick brown fox",[trim]))),
<<"The quick brown FOX">> = iolist_to_binary(join(re:split("The quick brown FOX","the quick brown fox",[{parts,
- 2}]))),
- <<"The quick brown FOX">> = iolist_to_binary(join(re:split("The quick brown FOX","the quick brown fox",[]))),
- <<"What do you know about :?">> = iolist_to_binary(join(re:split("What do you know about the quick brown fox?","the quick brown fox",[trim]))),
+ 2}]))),
+ <<"The quick brown FOX">> = iolist_to_binary(join(re:split("The quick brown FOX","the quick brown fox",[]))),
+ <<"What do you know about :?">> = iolist_to_binary(join(re:split("What do you know about the quick brown fox?","the quick brown fox",[trim]))),
<<"What do you know about :?">> = iolist_to_binary(join(re:split("What do you know about the quick brown fox?","the quick brown fox",[{parts,
- 2}]))),
- <<"What do you know about :?">> = iolist_to_binary(join(re:split("What do you know about the quick brown fox?","the quick brown fox",[]))),
- <<"What do you know about THE QUICK BROWN FOX?">> = iolist_to_binary(join(re:split("What do you know about THE QUICK BROWN FOX?","the quick brown fox",[trim]))),
+ 2}]))),
+ <<"What do you know about :?">> = iolist_to_binary(join(re:split("What do you know about the quick brown fox?","the quick brown fox",[]))),
+ <<"What do you know about THE QUICK BROWN FOX?">> = iolist_to_binary(join(re:split("What do you know about THE QUICK BROWN FOX?","the quick brown fox",[trim]))),
<<"What do you know about THE QUICK BROWN FOX?">> = iolist_to_binary(join(re:split("What do you know about THE QUICK BROWN FOX?","the quick brown fox",[{parts,
- 2}]))),
- <<"What do you know about THE QUICK BROWN FOX?">> = iolist_to_binary(join(re:split("What do you know about THE QUICK BROWN FOX?","the quick brown fox",[]))),
+ 2}]))),
+ <<"What do you know about THE QUICK BROWN FOX?">> = iolist_to_binary(join(re:split("What do you know about THE QUICK BROWN FOX?","the quick brown fox",[]))),
<<"">> = iolist_to_binary(join(re:split("the quick brown fox","The quick brown fox",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("the quick brown fox","The quick brown fox",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("the quick brown fox","The quick brown fox",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("the quick brown fox","The quick brown fox",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("The quick brown FOX","The quick brown fox",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("The quick brown FOX","The quick brown fox",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("The quick brown FOX","The quick brown fox",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("The quick brown FOX","The quick brown fox",[caseless]))),
<<"What do you know about :?">> = iolist_to_binary(join(re:split("What do you know about the quick brown fox?","The quick brown fox",[caseless,
- trim]))),
+ trim]))),
<<"What do you know about :?">> = iolist_to_binary(join(re:split("What do you know about the quick brown fox?","The quick brown fox",[caseless,
{parts,
- 2}]))),
- <<"What do you know about :?">> = iolist_to_binary(join(re:split("What do you know about the quick brown fox?","The quick brown fox",[caseless]))),
+ 2}]))),
+ <<"What do you know about :?">> = iolist_to_binary(join(re:split("What do you know about the quick brown fox?","The quick brown fox",[caseless]))),
<<"What do you know about :?">> = iolist_to_binary(join(re:split("What do you know about THE QUICK BROWN FOX?","The quick brown fox",[caseless,
- trim]))),
+ trim]))),
<<"What do you know about :?">> = iolist_to_binary(join(re:split("What do you know about THE QUICK BROWN FOX?","The quick brown fox",[caseless,
{parts,
- 2}]))),
- <<"What do you know about :?">> = iolist_to_binary(join(re:split("What do you know about THE QUICK BROWN FOX?","The quick brown fox",[caseless]))),
+ 2}]))),
+ <<"What do you know about :?">> = iolist_to_binary(join(re:split("What do you know about THE QUICK BROWN FOX?","The quick brown fox",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("abcd
- 9;$\\?caxyz","abcd\\t\\n\\r\\f\\a\\e\\071\\x3b\\$\\\\\\?caxyz",[trim]))),
+ 9;$\\?caxyz","abcd\\t\\n\\r\\f\\a\\e\\071\\x3b\\$\\\\\\?caxyz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcd
9;$\\?caxyz","abcd\\t\\n\\r\\f\\a\\e\\071\\x3b\\$\\\\\\?caxyz",[{parts,
- 2}]))),
+ 2}]))),
<<":">> = iolist_to_binary(join(re:split("abcd
- 9;$\\?caxyz","abcd\\t\\n\\r\\f\\a\\e\\071\\x3b\\$\\\\\\?caxyz",[]))),
- <<"">> = iolist_to_binary(join(re:split("abxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 9;$\\?caxyz","abcd\\t\\n\\r\\f\\a\\e\\071\\x3b\\$\\\\\\?caxyz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("abxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("abxyzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaabcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abxyzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abxyzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abxyzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aabxyzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abxyzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aabxyzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aabxyzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aabxyzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aabxyzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaabxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaabxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaabxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaabxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcxyzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaabxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcxyzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcxyzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcxyzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aabcxyzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcxyzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aabcxyzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aabcxyzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aabcxyzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabcxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aabcxyzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabcxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabcxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabcxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabcxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypABzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypABzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypABzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypABzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypABBzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypABzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypABBzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypABBzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypABBzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<">>>">> = iolist_to_binary(join(re:split(">>>aaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypABBzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<">>>">> = iolist_to_binary(join(re:split(">>>aaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<">>>:">> = iolist_to_binary(join(re:split(">>>aaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<">>>:">> = iolist_to_binary(join(re:split(">>>aaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<">">> = iolist_to_binary(join(re:split(">aaaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<">>>:">> = iolist_to_binary(join(re:split(">>>aaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<">">> = iolist_to_binary(join(re:split(">aaaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<">:">> = iolist_to_binary(join(re:split(">aaaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<">:">> = iolist_to_binary(join(re:split(">aaaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<">>>>">> = iolist_to_binary(join(re:split(">>>>abcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<">:">> = iolist_to_binary(join(re:split(">aaaabxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<">>>>">> = iolist_to_binary(join(re:split(">>>>abcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<">>>>:">> = iolist_to_binary(join(re:split(">>>>abcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<">>>>:">> = iolist_to_binary(join(re:split(">>>>abcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<">>>>:">> = iolist_to_binary(join(re:split(">>>>abcxyzpqrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"abxyzpqrrabbxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"abxyzpqrrabbxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<"abxyzpqrrabbxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<"abxyzpqrrabbxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"abxyzpqrrrrabbxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<"abxyzpqrrabbxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"abxyzpqrrrrabbxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<"abxyzpqrrrrabbxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<"abxyzpqrrrrabbxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"abxyzpqrrrabxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrrabxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<"abxyzpqrrrrabbxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrrrabbxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"abxyzpqrrrabxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrrabxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<"abxyzpqrrrabxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrrabxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<"abxyzpqrrrabxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrrabxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"aaaabcxyzzzzpqrrrabbbxyyyyyypqAzz">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<"abxyzpqrrrabxyyyypqAzz">> = iolist_to_binary(join(re:split("abxyzpqrrrabxyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"aaaabcxyzzzzpqrrrabbbxyyyyyypqAzz">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<"aaaabcxyzzzzpqrrrabbbxyyyyyypqAzz">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<"aaaabcxyzzzzpqrrrabbbxyyyyyypqAzz">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"aaaabcxyzzzzpqrrrabbbxyyypqAzz">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<"aaaabcxyzzzzpqrrrabbbxyyyyyypqAzz">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyyyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"aaaabcxyzzzzpqrrrabbbxyyypqAzz">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<"aaaabcxyzzzzpqrrrabbbxyyypqAzz">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<"aaaabcxyzzzzpqrrrabbbxyyypqAzz">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<"aaabcxyzpqrrrabbxyyyypqqqqqqqAzz">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
+ 2}]))),
+ <<"aaaabcxyzzzzpqrrrabbbxyyypqAzz">> = iolist_to_binary(join(re:split("aaaabcxyzzzzpqrrrabbbxyyypqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<"aaabcxyzpqrrrabbxyyyypqqqqqqqAzz">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[trim]))),
<<"aaabcxyzpqrrrabbxyyyypqqqqqqqAzz">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[{parts,
- 2}]))),
- <<"aaabcxyzpqrrrabbxyyyypqqqqqqqAzz">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abczz","^(abc){1,2}zz",[trim]))),
+ 2}]))),
+ <<"aaabcxyzpqrrrabbxyyyypqqqqqqqAzz">> = iolist_to_binary(join(re:split("aaabcxyzpqrrrabbxyyyypqqqqqqqAzz","a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abczz","^(abc){1,2}zz",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abczz","^(abc){1,2}zz",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abczz","^(abc){1,2}zz",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abcabczz","^(abc){1,2}zz",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abczz","^(abc){1,2}zz",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abcabczz","^(abc){1,2}zz",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abcabczz","^(abc){1,2}zz",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abcabczz","^(abc){1,2}zz",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(abc){1,2}zz",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abcabczz","^(abc){1,2}zz",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(abc){1,2}zz",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(abc){1,2}zz",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(abc){1,2}zz",[]))),
- <<"zz">> = iolist_to_binary(join(re:split("zz","^(abc){1,2}zz",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(abc){1,2}zz",[]))),
+ <<"zz">> = iolist_to_binary(join(re:split("zz","^(abc){1,2}zz",[trim]))),
<<"zz">> = iolist_to_binary(join(re:split("zz","^(abc){1,2}zz",[{parts,
- 2}]))),
- <<"zz">> = iolist_to_binary(join(re:split("zz","^(abc){1,2}zz",[]))),
- <<"abcabcabczz">> = iolist_to_binary(join(re:split("abcabcabczz","^(abc){1,2}zz",[trim]))),
+ 2}]))),
+ <<"zz">> = iolist_to_binary(join(re:split("zz","^(abc){1,2}zz",[]))),
+ <<"abcabcabczz">> = iolist_to_binary(join(re:split("abcabcabczz","^(abc){1,2}zz",[trim]))),
<<"abcabcabczz">> = iolist_to_binary(join(re:split("abcabcabczz","^(abc){1,2}zz",[{parts,
- 2}]))),
- <<"abcabcabczz">> = iolist_to_binary(join(re:split("abcabcabczz","^(abc){1,2}zz",[]))),
- <<">>abczz">> = iolist_to_binary(join(re:split(">>abczz","^(abc){1,2}zz",[trim]))),
+ 2}]))),
+ <<"abcabcabczz">> = iolist_to_binary(join(re:split("abcabcabczz","^(abc){1,2}zz",[]))),
+ <<">>abczz">> = iolist_to_binary(join(re:split(">>abczz","^(abc){1,2}zz",[trim]))),
<<">>abczz">> = iolist_to_binary(join(re:split(">>abczz","^(abc){1,2}zz",[{parts,
- 2}]))),
- <<">>abczz">> = iolist_to_binary(join(re:split(">>abczz","^(abc){1,2}zz",[]))),
- <<":b">> = iolist_to_binary(join(re:split("bc","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<">>abczz">> = iolist_to_binary(join(re:split(">>abczz","^(abc){1,2}zz",[]))),
+ <<":b">> = iolist_to_binary(join(re:split("bc","^(b+?|a){1,2}?c",[trim]))),
<<":b:">> = iolist_to_binary(join(re:split("bc","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<":b:">> = iolist_to_binary(join(re:split("bc","^(b+?|a){1,2}?c",[]))),
- <<":b">> = iolist_to_binary(join(re:split("bbc","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":b:">> = iolist_to_binary(join(re:split("bc","^(b+?|a){1,2}?c",[]))),
+ <<":b">> = iolist_to_binary(join(re:split("bbc","^(b+?|a){1,2}?c",[trim]))),
<<":b:">> = iolist_to_binary(join(re:split("bbc","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<":b:">> = iolist_to_binary(join(re:split("bbc","^(b+?|a){1,2}?c",[]))),
- <<":bb">> = iolist_to_binary(join(re:split("bbbc","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":b:">> = iolist_to_binary(join(re:split("bbc","^(b+?|a){1,2}?c",[]))),
+ <<":bb">> = iolist_to_binary(join(re:split("bbbc","^(b+?|a){1,2}?c",[trim]))),
<<":bb:">> = iolist_to_binary(join(re:split("bbbc","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<":bb:">> = iolist_to_binary(join(re:split("bbbc","^(b+?|a){1,2}?c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bac","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":bb:">> = iolist_to_binary(join(re:split("bbbc","^(b+?|a){1,2}?c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bac","^(b+?|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bac","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bac","^(b+?|a){1,2}?c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bbac","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bac","^(b+?|a){1,2}?c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bbac","^(b+?|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bbac","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bbac","^(b+?|a){1,2}?c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aac","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bbac","^(b+?|a){1,2}?c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aac","^(b+?|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aac","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aac","^(b+?|a){1,2}?c",[]))),
- <<":bbbbbbbbbbb">> = iolist_to_binary(join(re:split("abbbbbbbbbbbc","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aac","^(b+?|a){1,2}?c",[]))),
+ <<":bbbbbbbbbbb">> = iolist_to_binary(join(re:split("abbbbbbbbbbbc","^(b+?|a){1,2}?c",[trim]))),
<<":bbbbbbbbbbb:">> = iolist_to_binary(join(re:split("abbbbbbbbbbbc","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<":bbbbbbbbbbb:">> = iolist_to_binary(join(re:split("abbbbbbbbbbbc","^(b+?|a){1,2}?c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bbbbbbbbbbbac","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":bbbbbbbbbbb:">> = iolist_to_binary(join(re:split("abbbbbbbbbbbc","^(b+?|a){1,2}?c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bbbbbbbbbbbac","^(b+?|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bbbbbbbbbbbac","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bbbbbbbbbbbac","^(b+?|a){1,2}?c",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bbbbbbbbbbbac","^(b+?|a){1,2}?c",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b+?|a){1,2}?c",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b+?|a){1,2}?c",[]))),
- <<"aaac">> = iolist_to_binary(join(re:split("aaac","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b+?|a){1,2}?c",[]))),
+ <<"aaac">> = iolist_to_binary(join(re:split("aaac","^(b+?|a){1,2}?c",[trim]))),
<<"aaac">> = iolist_to_binary(join(re:split("aaac","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<"aaac">> = iolist_to_binary(join(re:split("aaac","^(b+?|a){1,2}?c",[]))),
- <<"abbbbbbbbbbbac">> = iolist_to_binary(join(re:split("abbbbbbbbbbbac","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<"aaac">> = iolist_to_binary(join(re:split("aaac","^(b+?|a){1,2}?c",[]))),
+ <<"abbbbbbbbbbbac">> = iolist_to_binary(join(re:split("abbbbbbbbbbbac","^(b+?|a){1,2}?c",[trim]))),
<<"abbbbbbbbbbbac">> = iolist_to_binary(join(re:split("abbbbbbbbbbbac","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<"abbbbbbbbbbbac">> = iolist_to_binary(join(re:split("abbbbbbbbbbbac","^(b+?|a){1,2}?c",[]))),
- <<":b">> = iolist_to_binary(join(re:split("bc","^(b+|a){1,2}c",[trim]))),
+ 2}]))),
+ <<"abbbbbbbbbbbac">> = iolist_to_binary(join(re:split("abbbbbbbbbbbac","^(b+?|a){1,2}?c",[]))),
+ <<":b">> = iolist_to_binary(join(re:split("bc","^(b+|a){1,2}c",[trim]))),
<<":b:">> = iolist_to_binary(join(re:split("bc","^(b+|a){1,2}c",[{parts,
- 2}]))),
- <<":b:">> = iolist_to_binary(join(re:split("bc","^(b+|a){1,2}c",[]))),
- <<":bb">> = iolist_to_binary(join(re:split("bbc","^(b+|a){1,2}c",[trim]))),
+ 2}]))),
+ <<":b:">> = iolist_to_binary(join(re:split("bc","^(b+|a){1,2}c",[]))),
+ <<":bb">> = iolist_to_binary(join(re:split("bbc","^(b+|a){1,2}c",[trim]))),
<<":bb:">> = iolist_to_binary(join(re:split("bbc","^(b+|a){1,2}c",[{parts,
- 2}]))),
- <<":bb:">> = iolist_to_binary(join(re:split("bbc","^(b+|a){1,2}c",[]))),
- <<":bbb">> = iolist_to_binary(join(re:split("bbbc","^(b+|a){1,2}c",[trim]))),
+ 2}]))),
+ <<":bb:">> = iolist_to_binary(join(re:split("bbc","^(b+|a){1,2}c",[]))),
+ <<":bbb">> = iolist_to_binary(join(re:split("bbbc","^(b+|a){1,2}c",[trim]))),
<<":bbb:">> = iolist_to_binary(join(re:split("bbbc","^(b+|a){1,2}c",[{parts,
- 2}]))),
- <<":bbb:">> = iolist_to_binary(join(re:split("bbbc","^(b+|a){1,2}c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bac","^(b+|a){1,2}c",[trim]))),
+ 2}]))),
+ <<":bbb:">> = iolist_to_binary(join(re:split("bbbc","^(b+|a){1,2}c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bac","^(b+|a){1,2}c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bac","^(b+|a){1,2}c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bac","^(b+|a){1,2}c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bbac","^(b+|a){1,2}c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bac","^(b+|a){1,2}c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bbac","^(b+|a){1,2}c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bbac","^(b+|a){1,2}c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bbac","^(b+|a){1,2}c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aac","^(b+|a){1,2}c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bbac","^(b+|a){1,2}c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aac","^(b+|a){1,2}c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aac","^(b+|a){1,2}c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aac","^(b+|a){1,2}c",[]))),
- <<":bbbbbbbbbbb">> = iolist_to_binary(join(re:split("abbbbbbbbbbbc","^(b+|a){1,2}c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aac","^(b+|a){1,2}c",[]))),
+ <<":bbbbbbbbbbb">> = iolist_to_binary(join(re:split("abbbbbbbbbbbc","^(b+|a){1,2}c",[trim]))),
<<":bbbbbbbbbbb:">> = iolist_to_binary(join(re:split("abbbbbbbbbbbc","^(b+|a){1,2}c",[{parts,
- 2}]))),
- <<":bbbbbbbbbbb:">> = iolist_to_binary(join(re:split("abbbbbbbbbbbc","^(b+|a){1,2}c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bbbbbbbbbbbac","^(b+|a){1,2}c",[trim]))),
+ 2}]))),
+ <<":bbbbbbbbbbb:">> = iolist_to_binary(join(re:split("abbbbbbbbbbbc","^(b+|a){1,2}c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bbbbbbbbbbbac","^(b+|a){1,2}c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bbbbbbbbbbbac","^(b+|a){1,2}c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bbbbbbbbbbbac","^(b+|a){1,2}c",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b+|a){1,2}c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bbbbbbbbbbbac","^(b+|a){1,2}c",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b+|a){1,2}c",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b+|a){1,2}c",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b+|a){1,2}c",[]))),
- <<"aaac">> = iolist_to_binary(join(re:split("aaac","^(b+|a){1,2}c",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b+|a){1,2}c",[]))),
+ <<"aaac">> = iolist_to_binary(join(re:split("aaac","^(b+|a){1,2}c",[trim]))),
<<"aaac">> = iolist_to_binary(join(re:split("aaac","^(b+|a){1,2}c",[{parts,
- 2}]))),
- <<"aaac">> = iolist_to_binary(join(re:split("aaac","^(b+|a){1,2}c",[]))),
- <<"abbbbbbbbbbbac">> = iolist_to_binary(join(re:split("abbbbbbbbbbbac","^(b+|a){1,2}c",[trim]))),
+ 2}]))),
+ <<"aaac">> = iolist_to_binary(join(re:split("aaac","^(b+|a){1,2}c",[]))),
+ <<"abbbbbbbbbbbac">> = iolist_to_binary(join(re:split("abbbbbbbbbbbac","^(b+|a){1,2}c",[trim]))),
<<"abbbbbbbbbbbac">> = iolist_to_binary(join(re:split("abbbbbbbbbbbac","^(b+|a){1,2}c",[{parts,
- 2}]))),
- <<"abbbbbbbbbbbac">> = iolist_to_binary(join(re:split("abbbbbbbbbbbac","^(b+|a){1,2}c",[]))),
- <<":b">> = iolist_to_binary(join(re:split("bbc","^(b+|a){1,2}?bc",[trim]))),
+ 2}]))),
+ <<"abbbbbbbbbbbac">> = iolist_to_binary(join(re:split("abbbbbbbbbbbac","^(b+|a){1,2}c",[]))),
+ <<":b">> = iolist_to_binary(join(re:split("bbc","^(b+|a){1,2}?bc",[trim]))),
<<":b:">> = iolist_to_binary(join(re:split("bbc","^(b+|a){1,2}?bc",[{parts,
- 2}]))),
- <<":b:">> = iolist_to_binary(join(re:split("bbc","^(b+|a){1,2}?bc",[]))),
- <<":ba">> = iolist_to_binary(join(re:split("babc","^(b*|ba){1,2}?bc",[trim]))),
+ 2}]))),
+ <<":b:">> = iolist_to_binary(join(re:split("bbc","^(b+|a){1,2}?bc",[]))),
+ <<":ba">> = iolist_to_binary(join(re:split("babc","^(b*|ba){1,2}?bc",[trim]))),
<<":ba:">> = iolist_to_binary(join(re:split("babc","^(b*|ba){1,2}?bc",[{parts,
- 2}]))),
- <<":ba:">> = iolist_to_binary(join(re:split("babc","^(b*|ba){1,2}?bc",[]))),
- <<":ba">> = iolist_to_binary(join(re:split("bbabc","^(b*|ba){1,2}?bc",[trim]))),
+ 2}]))),
+ <<":ba:">> = iolist_to_binary(join(re:split("babc","^(b*|ba){1,2}?bc",[]))),
+ <<":ba">> = iolist_to_binary(join(re:split("bbabc","^(b*|ba){1,2}?bc",[trim]))),
<<":ba:">> = iolist_to_binary(join(re:split("bbabc","^(b*|ba){1,2}?bc",[{parts,
- 2}]))),
- <<":ba:">> = iolist_to_binary(join(re:split("bbabc","^(b*|ba){1,2}?bc",[]))),
- <<":ba">> = iolist_to_binary(join(re:split("bababc","^(b*|ba){1,2}?bc",[trim]))),
+ 2}]))),
+ <<":ba:">> = iolist_to_binary(join(re:split("bbabc","^(b*|ba){1,2}?bc",[]))),
+ <<":ba">> = iolist_to_binary(join(re:split("bababc","^(b*|ba){1,2}?bc",[trim]))),
<<":ba:">> = iolist_to_binary(join(re:split("bababc","^(b*|ba){1,2}?bc",[{parts,
- 2}]))),
- <<":ba:">> = iolist_to_binary(join(re:split("bababc","^(b*|ba){1,2}?bc",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b*|ba){1,2}?bc",[trim]))),
+ 2}]))),
+ <<":ba:">> = iolist_to_binary(join(re:split("bababc","^(b*|ba){1,2}?bc",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b*|ba){1,2}?bc",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b*|ba){1,2}?bc",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b*|ba){1,2}?bc",[]))),
- <<"bababbc">> = iolist_to_binary(join(re:split("bababbc","^(b*|ba){1,2}?bc",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(b*|ba){1,2}?bc",[]))),
+ <<"bababbc">> = iolist_to_binary(join(re:split("bababbc","^(b*|ba){1,2}?bc",[trim]))),
<<"bababbc">> = iolist_to_binary(join(re:split("bababbc","^(b*|ba){1,2}?bc",[{parts,
- 2}]))),
- <<"bababbc">> = iolist_to_binary(join(re:split("bababbc","^(b*|ba){1,2}?bc",[]))),
- <<"babababc">> = iolist_to_binary(join(re:split("babababc","^(b*|ba){1,2}?bc",[trim]))),
+ 2}]))),
+ <<"bababbc">> = iolist_to_binary(join(re:split("bababbc","^(b*|ba){1,2}?bc",[]))),
+ <<"babababc">> = iolist_to_binary(join(re:split("babababc","^(b*|ba){1,2}?bc",[trim]))),
<<"babababc">> = iolist_to_binary(join(re:split("babababc","^(b*|ba){1,2}?bc",[{parts,
- 2}]))),
- <<"babababc">> = iolist_to_binary(join(re:split("babababc","^(b*|ba){1,2}?bc",[]))),
- <<":ba">> = iolist_to_binary(join(re:split("babc","^(ba|b*){1,2}?bc",[trim]))),
+ 2}]))),
+ <<"babababc">> = iolist_to_binary(join(re:split("babababc","^(b*|ba){1,2}?bc",[]))),
+ <<":ba">> = iolist_to_binary(join(re:split("babc","^(ba|b*){1,2}?bc",[trim]))),
<<":ba:">> = iolist_to_binary(join(re:split("babc","^(ba|b*){1,2}?bc",[{parts,
- 2}]))),
- <<":ba:">> = iolist_to_binary(join(re:split("babc","^(ba|b*){1,2}?bc",[]))),
- <<":ba">> = iolist_to_binary(join(re:split("bbabc","^(ba|b*){1,2}?bc",[trim]))),
+ 2}]))),
+ <<":ba:">> = iolist_to_binary(join(re:split("babc","^(ba|b*){1,2}?bc",[]))),
+ <<":ba">> = iolist_to_binary(join(re:split("bbabc","^(ba|b*){1,2}?bc",[trim]))),
<<":ba:">> = iolist_to_binary(join(re:split("bbabc","^(ba|b*){1,2}?bc",[{parts,
- 2}]))),
- <<":ba:">> = iolist_to_binary(join(re:split("bbabc","^(ba|b*){1,2}?bc",[]))),
- <<":ba">> = iolist_to_binary(join(re:split("bababc","^(ba|b*){1,2}?bc",[trim]))),
+ 2}]))),
+ <<":ba:">> = iolist_to_binary(join(re:split("bbabc","^(ba|b*){1,2}?bc",[]))),
+ <<":ba">> = iolist_to_binary(join(re:split("bababc","^(ba|b*){1,2}?bc",[trim]))),
<<":ba:">> = iolist_to_binary(join(re:split("bababc","^(ba|b*){1,2}?bc",[{parts,
- 2}]))),
- <<":ba:">> = iolist_to_binary(join(re:split("bababc","^(ba|b*){1,2}?bc",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(ba|b*){1,2}?bc",[trim]))),
+ 2}]))),
+ <<":ba:">> = iolist_to_binary(join(re:split("bababc","^(ba|b*){1,2}?bc",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(ba|b*){1,2}?bc",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(ba|b*){1,2}?bc",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(ba|b*){1,2}?bc",[]))),
- <<"bababbc">> = iolist_to_binary(join(re:split("bababbc","^(ba|b*){1,2}?bc",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(ba|b*){1,2}?bc",[]))),
+ <<"bababbc">> = iolist_to_binary(join(re:split("bababbc","^(ba|b*){1,2}?bc",[trim]))),
<<"bababbc">> = iolist_to_binary(join(re:split("bababbc","^(ba|b*){1,2}?bc",[{parts,
- 2}]))),
- <<"bababbc">> = iolist_to_binary(join(re:split("bababbc","^(ba|b*){1,2}?bc",[]))),
- <<"babababc">> = iolist_to_binary(join(re:split("babababc","^(ba|b*){1,2}?bc",[trim]))),
+ 2}]))),
+ <<"bababbc">> = iolist_to_binary(join(re:split("bababbc","^(ba|b*){1,2}?bc",[]))),
+ <<"babababc">> = iolist_to_binary(join(re:split("babababc","^(ba|b*){1,2}?bc",[trim]))),
<<"babababc">> = iolist_to_binary(join(re:split("babababc","^(ba|b*){1,2}?bc",[{parts,
- 2}]))),
- <<"babababc">> = iolist_to_binary(join(re:split("babababc","^(ba|b*){1,2}?bc",[]))),
- <<"">> = iolist_to_binary(join(re:split(";z","^\\ca\\cA\\c[;\\c:",[trim]))),
+ 2}]))),
+ <<"babababc">> = iolist_to_binary(join(re:split("babababc","^(ba|b*){1,2}?bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split(";z","^\\ca\\cA\\c[;\\c:",[trim]))),
<<":">> = iolist_to_binary(join(re:split(";z","^\\ca\\cA\\c[;\\c:",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split(";z","^\\ca\\cA\\c[;\\c:",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("athing","^[ab\\]cde]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split(";z","^\\ca\\cA\\c[;\\c:",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("athing","^[ab\\]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("athing","^[ab\\]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("athing","^[ab\\]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("bthing","^[ab\\]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("athing","^[ab\\]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("bthing","^[ab\\]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("bthing","^[ab\\]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("bthing","^[ab\\]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("]thing","^[ab\\]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("bthing","^[ab\\]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("]thing","^[ab\\]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("]thing","^[ab\\]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("]thing","^[ab\\]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("cthing","^[ab\\]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("]thing","^[ab\\]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("cthing","^[ab\\]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("cthing","^[ab\\]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("cthing","^[ab\\]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("dthing","^[ab\\]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("cthing","^[ab\\]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("dthing","^[ab\\]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("dthing","^[ab\\]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("dthing","^[ab\\]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("ething","^[ab\\]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("dthing","^[ab\\]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("ething","^[ab\\]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("ething","^[ab\\]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("ething","^[ab\\]cde]",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[ab\\]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("ething","^[ab\\]cde]",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[ab\\]cde]",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[ab\\]cde]",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[ab\\]cde]",[]))),
- <<"fthing">> = iolist_to_binary(join(re:split("fthing","^[ab\\]cde]",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[ab\\]cde]",[]))),
+ <<"fthing">> = iolist_to_binary(join(re:split("fthing","^[ab\\]cde]",[trim]))),
<<"fthing">> = iolist_to_binary(join(re:split("fthing","^[ab\\]cde]",[{parts,
- 2}]))),
- <<"fthing">> = iolist_to_binary(join(re:split("fthing","^[ab\\]cde]",[]))),
- <<"[thing">> = iolist_to_binary(join(re:split("[thing","^[ab\\]cde]",[trim]))),
+ 2}]))),
+ <<"fthing">> = iolist_to_binary(join(re:split("fthing","^[ab\\]cde]",[]))),
+ <<"[thing">> = iolist_to_binary(join(re:split("[thing","^[ab\\]cde]",[trim]))),
<<"[thing">> = iolist_to_binary(join(re:split("[thing","^[ab\\]cde]",[{parts,
- 2}]))),
- <<"[thing">> = iolist_to_binary(join(re:split("[thing","^[ab\\]cde]",[]))),
- <<"\\thing">> = iolist_to_binary(join(re:split("\\thing","^[ab\\]cde]",[trim]))),
+ 2}]))),
+ <<"[thing">> = iolist_to_binary(join(re:split("[thing","^[ab\\]cde]",[]))),
+ <<"\\thing">> = iolist_to_binary(join(re:split("\\thing","^[ab\\]cde]",[trim]))),
<<"\\thing">> = iolist_to_binary(join(re:split("\\thing","^[ab\\]cde]",[{parts,
- 2}]))),
- <<"\\thing">> = iolist_to_binary(join(re:split("\\thing","^[ab\\]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("]thing","^[]cde]",[trim]))),
+ 2}]))),
+ <<"\\thing">> = iolist_to_binary(join(re:split("\\thing","^[ab\\]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("]thing","^[]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("]thing","^[]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("]thing","^[]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("cthing","^[]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("]thing","^[]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("cthing","^[]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("cthing","^[]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("cthing","^[]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("dthing","^[]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("cthing","^[]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("dthing","^[]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("dthing","^[]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("dthing","^[]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("ething","^[]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("dthing","^[]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("ething","^[]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("ething","^[]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("ething","^[]cde]",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("ething","^[]cde]",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[]cde]",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[]cde]",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[]cde]",[]))),
- <<"athing">> = iolist_to_binary(join(re:split("athing","^[]cde]",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[]cde]",[]))),
+ <<"athing">> = iolist_to_binary(join(re:split("athing","^[]cde]",[trim]))),
<<"athing">> = iolist_to_binary(join(re:split("athing","^[]cde]",[{parts,
- 2}]))),
- <<"athing">> = iolist_to_binary(join(re:split("athing","^[]cde]",[]))),
- <<"fthing">> = iolist_to_binary(join(re:split("fthing","^[]cde]",[trim]))),
+ 2}]))),
+ <<"athing">> = iolist_to_binary(join(re:split("athing","^[]cde]",[]))),
+ <<"fthing">> = iolist_to_binary(join(re:split("fthing","^[]cde]",[trim]))),
<<"fthing">> = iolist_to_binary(join(re:split("fthing","^[]cde]",[{parts,
- 2}]))),
- <<"fthing">> = iolist_to_binary(join(re:split("fthing","^[]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("fthing","^[^ab\\]cde]",[trim]))),
+ 2}]))),
+ <<"fthing">> = iolist_to_binary(join(re:split("fthing","^[]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("fthing","^[^ab\\]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("fthing","^[^ab\\]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("fthing","^[^ab\\]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("[thing","^[^ab\\]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("fthing","^[^ab\\]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("[thing","^[^ab\\]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("[thing","^[^ab\\]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("[thing","^[^ab\\]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("\\thing","^[^ab\\]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("[thing","^[^ab\\]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("\\thing","^[^ab\\]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("\\thing","^[^ab\\]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("\\thing","^[^ab\\]cde]",[]))),
- <<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[^ab\\]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("\\thing","^[^ab\\]cde]",[]))),
+ <<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[^ab\\]cde]",[trim]))),
<<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[^ab\\]cde]",[{parts,
- 2}]))),
- <<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[^ab\\]cde]",[]))),
- <<"athing">> = iolist_to_binary(join(re:split("athing","^[^ab\\]cde]",[trim]))),
+ 2}]))),
+ <<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[^ab\\]cde]",[]))),
+ <<"athing">> = iolist_to_binary(join(re:split("athing","^[^ab\\]cde]",[trim]))),
<<"athing">> = iolist_to_binary(join(re:split("athing","^[^ab\\]cde]",[{parts,
- 2}]))),
- <<"athing">> = iolist_to_binary(join(re:split("athing","^[^ab\\]cde]",[]))),
- <<"bthing">> = iolist_to_binary(join(re:split("bthing","^[^ab\\]cde]",[trim]))),
+ 2}]))),
+ <<"athing">> = iolist_to_binary(join(re:split("athing","^[^ab\\]cde]",[]))),
+ <<"bthing">> = iolist_to_binary(join(re:split("bthing","^[^ab\\]cde]",[trim]))),
<<"bthing">> = iolist_to_binary(join(re:split("bthing","^[^ab\\]cde]",[{parts,
- 2}]))),
- <<"bthing">> = iolist_to_binary(join(re:split("bthing","^[^ab\\]cde]",[]))),
- <<"]thing">> = iolist_to_binary(join(re:split("]thing","^[^ab\\]cde]",[trim]))),
+ 2}]))),
+ <<"bthing">> = iolist_to_binary(join(re:split("bthing","^[^ab\\]cde]",[]))),
+ <<"]thing">> = iolist_to_binary(join(re:split("]thing","^[^ab\\]cde]",[trim]))),
<<"]thing">> = iolist_to_binary(join(re:split("]thing","^[^ab\\]cde]",[{parts,
- 2}]))),
- <<"]thing">> = iolist_to_binary(join(re:split("]thing","^[^ab\\]cde]",[]))),
- <<"cthing">> = iolist_to_binary(join(re:split("cthing","^[^ab\\]cde]",[trim]))),
+ 2}]))),
+ <<"]thing">> = iolist_to_binary(join(re:split("]thing","^[^ab\\]cde]",[]))),
+ <<"cthing">> = iolist_to_binary(join(re:split("cthing","^[^ab\\]cde]",[trim]))),
<<"cthing">> = iolist_to_binary(join(re:split("cthing","^[^ab\\]cde]",[{parts,
- 2}]))),
- <<"cthing">> = iolist_to_binary(join(re:split("cthing","^[^ab\\]cde]",[]))),
- <<"dthing">> = iolist_to_binary(join(re:split("dthing","^[^ab\\]cde]",[trim]))),
+ 2}]))),
+ <<"cthing">> = iolist_to_binary(join(re:split("cthing","^[^ab\\]cde]",[]))),
+ <<"dthing">> = iolist_to_binary(join(re:split("dthing","^[^ab\\]cde]",[trim]))),
<<"dthing">> = iolist_to_binary(join(re:split("dthing","^[^ab\\]cde]",[{parts,
- 2}]))),
- <<"dthing">> = iolist_to_binary(join(re:split("dthing","^[^ab\\]cde]",[]))),
- <<"ething">> = iolist_to_binary(join(re:split("ething","^[^ab\\]cde]",[trim]))),
+ 2}]))),
+ <<"dthing">> = iolist_to_binary(join(re:split("dthing","^[^ab\\]cde]",[]))),
+ <<"ething">> = iolist_to_binary(join(re:split("ething","^[^ab\\]cde]",[trim]))),
<<"ething">> = iolist_to_binary(join(re:split("ething","^[^ab\\]cde]",[{parts,
- 2}]))),
- <<"ething">> = iolist_to_binary(join(re:split("ething","^[^ab\\]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("athing","^[^]cde]",[trim]))),
+ 2}]))),
+ <<"ething">> = iolist_to_binary(join(re:split("ething","^[^ab\\]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("athing","^[^]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("athing","^[^]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("athing","^[^]cde]",[]))),
- <<":thing">> = iolist_to_binary(join(re:split("fthing","^[^]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("athing","^[^]cde]",[]))),
+ <<":thing">> = iolist_to_binary(join(re:split("fthing","^[^]cde]",[trim]))),
<<":thing">> = iolist_to_binary(join(re:split("fthing","^[^]cde]",[{parts,
- 2}]))),
- <<":thing">> = iolist_to_binary(join(re:split("fthing","^[^]cde]",[]))),
- <<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[^]cde]",[trim]))),
+ 2}]))),
+ <<":thing">> = iolist_to_binary(join(re:split("fthing","^[^]cde]",[]))),
+ <<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[^]cde]",[trim]))),
<<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[^]cde]",[{parts,
- 2}]))),
- <<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[^]cde]",[]))),
- <<"]thing">> = iolist_to_binary(join(re:split("]thing","^[^]cde]",[trim]))),
+ 2}]))),
+ <<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[^]cde]",[]))),
+ <<"]thing">> = iolist_to_binary(join(re:split("]thing","^[^]cde]",[trim]))),
<<"]thing">> = iolist_to_binary(join(re:split("]thing","^[^]cde]",[{parts,
- 2}]))),
- <<"]thing">> = iolist_to_binary(join(re:split("]thing","^[^]cde]",[]))),
- <<"cthing">> = iolist_to_binary(join(re:split("cthing","^[^]cde]",[trim]))),
+ 2}]))),
+ <<"]thing">> = iolist_to_binary(join(re:split("]thing","^[^]cde]",[]))),
+ <<"cthing">> = iolist_to_binary(join(re:split("cthing","^[^]cde]",[trim]))),
<<"cthing">> = iolist_to_binary(join(re:split("cthing","^[^]cde]",[{parts,
- 2}]))),
- <<"cthing">> = iolist_to_binary(join(re:split("cthing","^[^]cde]",[]))),
- <<"dthing">> = iolist_to_binary(join(re:split("dthing","^[^]cde]",[trim]))),
+ 2}]))),
+ <<"cthing">> = iolist_to_binary(join(re:split("cthing","^[^]cde]",[]))),
+ <<"dthing">> = iolist_to_binary(join(re:split("dthing","^[^]cde]",[trim]))),
<<"dthing">> = iolist_to_binary(join(re:split("dthing","^[^]cde]",[{parts,
- 2}]))),
- <<"dthing">> = iolist_to_binary(join(re:split("dthing","^[^]cde]",[]))),
- <<"ething">> = iolist_to_binary(join(re:split("ething","^[^]cde]",[trim]))),
+ 2}]))),
+ <<"dthing">> = iolist_to_binary(join(re:split("dthing","^[^]cde]",[]))),
+ <<"ething">> = iolist_to_binary(join(re:split("ething","^[^]cde]",[trim]))),
<<"ething">> = iolist_to_binary(join(re:split("ething","^[^]cde]",[{parts,
- 2}]))),
- <<"ething">> = iolist_to_binary(join(re:split("ething","^[^]cde]",[]))),
- <<"">> = iolist_to_binary(join(re:split("0","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<"ething">> = iolist_to_binary(join(re:split("ething","^[^]cde]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("0","^[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("0","^[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("0","^[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("1","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("0","^[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("1","^[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("1","^[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("1","^[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("2","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("1","^[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("2","^[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("2","^[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("2","^[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("3","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("2","^[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("3","^[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("3","^[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("3","^[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("4","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("3","^[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("4","^[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("4","^[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("4","^[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("5","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("4","^[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("5","^[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("5","^[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("5","^[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("6","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("5","^[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("6","^[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("6","^[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("6","^[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("7","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("6","^[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("7","^[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("7","^[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("7","^[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("8","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("7","^[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("8","^[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("8","^[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("8","^[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("9","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("8","^[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("9","^[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("9","^[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("9","^[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("10","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("9","^[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("10","^[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("10","^[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("10","^[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("100","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("10","^[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("100","^[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("100","^[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("100","^[0-9]+$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("100","^[0-9]+$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[0-9]+$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[0-9]+$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[0-9]+$",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^[0-9]+$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[0-9]+$",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^[0-9]+$",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","^[0-9]+$",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("enter","^.*nter",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("enter","^.*nter",[trim]))),
<<":">> = iolist_to_binary(join(re:split("enter","^.*nter",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("enter","^.*nter",[]))),
- <<"">> = iolist_to_binary(join(re:split("inter","^.*nter",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("enter","^.*nter",[]))),
+ <<"">> = iolist_to_binary(join(re:split("inter","^.*nter",[trim]))),
<<":">> = iolist_to_binary(join(re:split("inter","^.*nter",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("inter","^.*nter",[]))),
- <<"">> = iolist_to_binary(join(re:split("uponter","^.*nter",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("inter","^.*nter",[]))),
+ <<"">> = iolist_to_binary(join(re:split("uponter","^.*nter",[trim]))),
<<":">> = iolist_to_binary(join(re:split("uponter","^.*nter",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("uponter","^.*nter",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("uponter","^.*nter",[]))),
ok.
run1() ->
- <<"">> = iolist_to_binary(join(re:split("xxx0","^xxx[0-9]+$",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("xxx0","^xxx[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("xxx0","^xxx[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("xxx0","^xxx[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("xxx1234","^xxx[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("xxx0","^xxx[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("xxx1234","^xxx[0-9]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("xxx1234","^xxx[0-9]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("xxx1234","^xxx[0-9]+$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^xxx[0-9]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("xxx1234","^xxx[0-9]+$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^xxx[0-9]+$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^xxx[0-9]+$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^xxx[0-9]+$",[]))),
- <<"xxx">> = iolist_to_binary(join(re:split("xxx","^xxx[0-9]+$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^xxx[0-9]+$",[]))),
+ <<"xxx">> = iolist_to_binary(join(re:split("xxx","^xxx[0-9]+$",[trim]))),
<<"xxx">> = iolist_to_binary(join(re:split("xxx","^xxx[0-9]+$",[{parts,
- 2}]))),
- <<"xxx">> = iolist_to_binary(join(re:split("xxx","^xxx[0-9]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("x123","^.+[0-9][0-9][0-9]$",[trim]))),
+ 2}]))),
+ <<"xxx">> = iolist_to_binary(join(re:split("xxx","^xxx[0-9]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("x123","^.+[0-9][0-9][0-9]$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("x123","^.+[0-9][0-9][0-9]$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("x123","^.+[0-9][0-9][0-9]$",[]))),
- <<"">> = iolist_to_binary(join(re:split("xx123","^.+[0-9][0-9][0-9]$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("x123","^.+[0-9][0-9][0-9]$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("xx123","^.+[0-9][0-9][0-9]$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("xx123","^.+[0-9][0-9][0-9]$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("xx123","^.+[0-9][0-9][0-9]$",[]))),
- <<"">> = iolist_to_binary(join(re:split("123456","^.+[0-9][0-9][0-9]$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("xx123","^.+[0-9][0-9][0-9]$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("123456","^.+[0-9][0-9][0-9]$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("123456","^.+[0-9][0-9][0-9]$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("123456","^.+[0-9][0-9][0-9]$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.+[0-9][0-9][0-9]$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("123456","^.+[0-9][0-9][0-9]$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.+[0-9][0-9][0-9]$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.+[0-9][0-9][0-9]$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.+[0-9][0-9][0-9]$",[]))),
- <<"123">> = iolist_to_binary(join(re:split("123","^.+[0-9][0-9][0-9]$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.+[0-9][0-9][0-9]$",[]))),
+ <<"123">> = iolist_to_binary(join(re:split("123","^.+[0-9][0-9][0-9]$",[trim]))),
<<"123">> = iolist_to_binary(join(re:split("123","^.+[0-9][0-9][0-9]$",[{parts,
- 2}]))),
- <<"123">> = iolist_to_binary(join(re:split("123","^.+[0-9][0-9][0-9]$",[]))),
- <<"">> = iolist_to_binary(join(re:split("x1234","^.+[0-9][0-9][0-9]$",[trim]))),
+ 2}]))),
+ <<"123">> = iolist_to_binary(join(re:split("123","^.+[0-9][0-9][0-9]$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("x1234","^.+[0-9][0-9][0-9]$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("x1234","^.+[0-9][0-9][0-9]$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("x1234","^.+[0-9][0-9][0-9]$",[]))),
- <<"">> = iolist_to_binary(join(re:split("x123","^.+?[0-9][0-9][0-9]$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("x1234","^.+[0-9][0-9][0-9]$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("x123","^.+?[0-9][0-9][0-9]$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("x123","^.+?[0-9][0-9][0-9]$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("x123","^.+?[0-9][0-9][0-9]$",[]))),
- <<"">> = iolist_to_binary(join(re:split("xx123","^.+?[0-9][0-9][0-9]$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("x123","^.+?[0-9][0-9][0-9]$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("xx123","^.+?[0-9][0-9][0-9]$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("xx123","^.+?[0-9][0-9][0-9]$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("xx123","^.+?[0-9][0-9][0-9]$",[]))),
- <<"">> = iolist_to_binary(join(re:split("123456","^.+?[0-9][0-9][0-9]$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("xx123","^.+?[0-9][0-9][0-9]$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("123456","^.+?[0-9][0-9][0-9]$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("123456","^.+?[0-9][0-9][0-9]$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("123456","^.+?[0-9][0-9][0-9]$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.+?[0-9][0-9][0-9]$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("123456","^.+?[0-9][0-9][0-9]$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.+?[0-9][0-9][0-9]$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.+?[0-9][0-9][0-9]$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.+?[0-9][0-9][0-9]$",[]))),
- <<"123">> = iolist_to_binary(join(re:split("123","^.+?[0-9][0-9][0-9]$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.+?[0-9][0-9][0-9]$",[]))),
+ <<"123">> = iolist_to_binary(join(re:split("123","^.+?[0-9][0-9][0-9]$",[trim]))),
<<"123">> = iolist_to_binary(join(re:split("123","^.+?[0-9][0-9][0-9]$",[{parts,
- 2}]))),
- <<"123">> = iolist_to_binary(join(re:split("123","^.+?[0-9][0-9][0-9]$",[]))),
- <<"">> = iolist_to_binary(join(re:split("x1234","^.+?[0-9][0-9][0-9]$",[trim]))),
+ 2}]))),
+ <<"123">> = iolist_to_binary(join(re:split("123","^.+?[0-9][0-9][0-9]$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("x1234","^.+?[0-9][0-9][0-9]$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("x1234","^.+?[0-9][0-9][0-9]$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("x1234","^.+?[0-9][0-9][0-9]$",[]))),
- <<":abc:pqr">> = iolist_to_binary(join(re:split("abc!pqr=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("x1234","^.+?[0-9][0-9][0-9]$",[]))),
+ <<":abc:pqr">> = iolist_to_binary(join(re:split("abc!pqr=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[trim]))),
<<":abc:pqr:">> = iolist_to_binary(join(re:split("abc!pqr=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[{parts,
- 2}]))),
- <<":abc:pqr:">> = iolist_to_binary(join(re:split("abc!pqr=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[trim]))),
+ 2}]))),
+ <<":abc:pqr:">> = iolist_to_binary(join(re:split("abc!pqr=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[]))),
- <<"!pqr=apquxz.ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("!pqr=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[]))),
+ <<"!pqr=apquxz.ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("!pqr=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[trim]))),
<<"!pqr=apquxz.ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("!pqr=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[{parts,
- 2}]))),
- <<"!pqr=apquxz.ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("!pqr=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[]))),
- <<"abc!=apquxz.ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("abc!=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[trim]))),
+ 2}]))),
+ <<"!pqr=apquxz.ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("!pqr=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[]))),
+ <<"abc!=apquxz.ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("abc!=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[trim]))),
<<"abc!=apquxz.ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("abc!=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[{parts,
- 2}]))),
- <<"abc!=apquxz.ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("abc!=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[]))),
- <<"abc!pqr=apquxz:ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("abc!pqr=apquxz:ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[trim]))),
+ 2}]))),
+ <<"abc!=apquxz.ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("abc!=apquxz.ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[]))),
+ <<"abc!pqr=apquxz:ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("abc!pqr=apquxz:ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[trim]))),
<<"abc!pqr=apquxz:ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("abc!pqr=apquxz:ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[{parts,
- 2}]))),
- <<"abc!pqr=apquxz:ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("abc!pqr=apquxz:ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[]))),
- <<"abc!pqr=apquxz.ixr.zzz.ac.ukk">> = iolist_to_binary(join(re:split("abc!pqr=apquxz.ixr.zzz.ac.ukk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[trim]))),
+ 2}]))),
+ <<"abc!pqr=apquxz:ixr.zzz.ac.uk">> = iolist_to_binary(join(re:split("abc!pqr=apquxz:ixr.zzz.ac.uk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[]))),
+ <<"abc!pqr=apquxz.ixr.zzz.ac.ukk">> = iolist_to_binary(join(re:split("abc!pqr=apquxz.ixr.zzz.ac.ukk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[trim]))),
<<"abc!pqr=apquxz.ixr.zzz.ac.ukk">> = iolist_to_binary(join(re:split("abc!pqr=apquxz.ixr.zzz.ac.ukk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[{parts,
- 2}]))),
- <<"abc!pqr=apquxz.ixr.zzz.ac.ukk">> = iolist_to_binary(join(re:split("abc!pqr=apquxz.ixr.zzz.ac.ukk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[]))),
- <<"Well, we need a colon: somewhere">> = iolist_to_binary(join(re:split("Well, we need a colon: somewhere",":",[trim]))),
+ 2}]))),
+ <<"abc!pqr=apquxz.ixr.zzz.ac.ukk">> = iolist_to_binary(join(re:split("abc!pqr=apquxz.ixr.zzz.ac.ukk","^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$",[]))),
+ <<"Well, we need a colon: somewhere">> = iolist_to_binary(join(re:split("Well, we need a colon: somewhere",":",[trim]))),
<<"Well, we need a colon: somewhere">> = iolist_to_binary(join(re:split("Well, we need a colon: somewhere",":",[{parts,
- 2}]))),
- <<"Well, we need a colon: somewhere">> = iolist_to_binary(join(re:split("Well, we need a colon: somewhere",":",[]))),
- <<"*** Fail if we don't">> = iolist_to_binary(join(re:split("*** Fail if we don't",":",[trim]))),
+ 2}]))),
+ <<"Well, we need a colon: somewhere">> = iolist_to_binary(join(re:split("Well, we need a colon: somewhere",":",[]))),
+ <<"*** Fail if we don't">> = iolist_to_binary(join(re:split("*** Fail if we don't",":",[trim]))),
<<"*** Fail if we don't">> = iolist_to_binary(join(re:split("*** Fail if we don't",":",[{parts,
- 2}]))),
- <<"*** Fail if we don't">> = iolist_to_binary(join(re:split("*** Fail if we don't",":",[]))),
+ 2}]))),
+ <<"*** Fail if we don't">> = iolist_to_binary(join(re:split("*** Fail if we don't",":",[]))),
<<":0abc">> = iolist_to_binary(join(re:split("0abc","([\\da-f:]+)$",[caseless,
- trim]))),
+ trim]))),
<<":0abc:">> = iolist_to_binary(join(re:split("0abc","([\\da-f:]+)$",[caseless,
{parts,
- 2}]))),
- <<":0abc:">> = iolist_to_binary(join(re:split("0abc","([\\da-f:]+)$",[caseless]))),
+ 2}]))),
+ <<":0abc:">> = iolist_to_binary(join(re:split("0abc","([\\da-f:]+)$",[caseless]))),
<<":abc">> = iolist_to_binary(join(re:split("abc","([\\da-f:]+)$",[caseless,
- trim]))),
+ trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abc","([\\da-f:]+)$",[caseless,
{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abc","([\\da-f:]+)$",[caseless]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abc","([\\da-f:]+)$",[caseless]))),
<<":fed">> = iolist_to_binary(join(re:split("fed","([\\da-f:]+)$",[caseless,
- trim]))),
+ trim]))),
<<":fed:">> = iolist_to_binary(join(re:split("fed","([\\da-f:]+)$",[caseless,
{parts,
- 2}]))),
- <<":fed:">> = iolist_to_binary(join(re:split("fed","([\\da-f:]+)$",[caseless]))),
+ 2}]))),
+ <<":fed:">> = iolist_to_binary(join(re:split("fed","([\\da-f:]+)$",[caseless]))),
<<":E">> = iolist_to_binary(join(re:split("E","([\\da-f:]+)$",[caseless,
- trim]))),
+ trim]))),
<<":E:">> = iolist_to_binary(join(re:split("E","([\\da-f:]+)$",[caseless,
{parts,
- 2}]))),
- <<":E:">> = iolist_to_binary(join(re:split("E","([\\da-f:]+)$",[caseless]))),
+ 2}]))),
+ <<":E:">> = iolist_to_binary(join(re:split("E","([\\da-f:]+)$",[caseless]))),
<<":::">> = iolist_to_binary(join(re:split("::","([\\da-f:]+)$",[caseless,
- trim]))),
+ trim]))),
<<"::::">> = iolist_to_binary(join(re:split("::","([\\da-f:]+)$",[caseless,
{parts,
- 2}]))),
- <<"::::">> = iolist_to_binary(join(re:split("::","([\\da-f:]+)$",[caseless]))),
+ 2}]))),
+ <<"::::">> = iolist_to_binary(join(re:split("::","([\\da-f:]+)$",[caseless]))),
<<":5f03:12C0::932e">> = iolist_to_binary(join(re:split("5f03:12C0::932e","([\\da-f:]+)$",[caseless,
- trim]))),
+ trim]))),
<<":5f03:12C0::932e:">> = iolist_to_binary(join(re:split("5f03:12C0::932e","([\\da-f:]+)$",[caseless,
{parts,
- 2}]))),
- <<":5f03:12C0::932e:">> = iolist_to_binary(join(re:split("5f03:12C0::932e","([\\da-f:]+)$",[caseless]))),
+ 2}]))),
+ <<":5f03:12C0::932e:">> = iolist_to_binary(join(re:split("5f03:12C0::932e","([\\da-f:]+)$",[caseless]))),
<<"fed :def">> = iolist_to_binary(join(re:split("fed def","([\\da-f:]+)$",[caseless,
- trim]))),
+ trim]))),
<<"fed :def:">> = iolist_to_binary(join(re:split("fed def","([\\da-f:]+)$",[caseless,
{parts,
- 2}]))),
- <<"fed :def:">> = iolist_to_binary(join(re:split("fed def","([\\da-f:]+)$",[caseless]))),
+ 2}]))),
+ <<"fed :def:">> = iolist_to_binary(join(re:split("fed def","([\\da-f:]+)$",[caseless]))),
<<"Any old stu:ff">> = iolist_to_binary(join(re:split("Any old stuff","([\\da-f:]+)$",[caseless,
- trim]))),
+ trim]))),
<<"Any old stu:ff:">> = iolist_to_binary(join(re:split("Any old stuff","([\\da-f:]+)$",[caseless,
{parts,
- 2}]))),
- <<"Any old stu:ff:">> = iolist_to_binary(join(re:split("Any old stuff","([\\da-f:]+)$",[caseless]))),
+ 2}]))),
+ <<"Any old stu:ff:">> = iolist_to_binary(join(re:split("Any old stuff","([\\da-f:]+)$",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","([\\da-f:]+)$",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","([\\da-f:]+)$",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","([\\da-f:]+)$",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","([\\da-f:]+)$",[caseless]))),
<<"0zzz">> = iolist_to_binary(join(re:split("0zzz","([\\da-f:]+)$",[caseless,
- trim]))),
+ trim]))),
<<"0zzz">> = iolist_to_binary(join(re:split("0zzz","([\\da-f:]+)$",[caseless,
{parts,
- 2}]))),
- <<"0zzz">> = iolist_to_binary(join(re:split("0zzz","([\\da-f:]+)$",[caseless]))),
+ 2}]))),
+ <<"0zzz">> = iolist_to_binary(join(re:split("0zzz","([\\da-f:]+)$",[caseless]))),
<<"gzzz">> = iolist_to_binary(join(re:split("gzzz","([\\da-f:]+)$",[caseless,
- trim]))),
+ trim]))),
<<"gzzz">> = iolist_to_binary(join(re:split("gzzz","([\\da-f:]+)$",[caseless,
{parts,
- 2}]))),
- <<"gzzz">> = iolist_to_binary(join(re:split("gzzz","([\\da-f:]+)$",[caseless]))),
+ 2}]))),
+ <<"gzzz">> = iolist_to_binary(join(re:split("gzzz","([\\da-f:]+)$",[caseless]))),
<<"fed ">> = iolist_to_binary(join(re:split("fed ","([\\da-f:]+)$",[caseless,
- trim]))),
+ trim]))),
<<"fed ">> = iolist_to_binary(join(re:split("fed ","([\\da-f:]+)$",[caseless,
{parts,
- 2}]))),
- <<"fed ">> = iolist_to_binary(join(re:split("fed ","([\\da-f:]+)$",[caseless]))),
+ 2}]))),
+ <<"fed ">> = iolist_to_binary(join(re:split("fed ","([\\da-f:]+)$",[caseless]))),
<<"Any old rubbish">> = iolist_to_binary(join(re:split("Any old rubbish","([\\da-f:]+)$",[caseless,
- trim]))),
+ trim]))),
<<"Any old rubbish">> = iolist_to_binary(join(re:split("Any old rubbish","([\\da-f:]+)$",[caseless,
{parts,
- 2}]))),
- <<"Any old rubbish">> = iolist_to_binary(join(re:split("Any old rubbish","([\\da-f:]+)$",[caseless]))),
- <<":1:2:3">> = iolist_to_binary(join(re:split(".1.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[trim]))),
+ 2}]))),
+ <<"Any old rubbish">> = iolist_to_binary(join(re:split("Any old rubbish","([\\da-f:]+)$",[caseless]))),
+ <<":1:2:3">> = iolist_to_binary(join(re:split(".1.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[trim]))),
<<":1:2:3:">> = iolist_to_binary(join(re:split(".1.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[{parts,
- 2}]))),
- <<":1:2:3:">> = iolist_to_binary(join(re:split(".1.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[]))),
- <<":12:123:0">> = iolist_to_binary(join(re:split("A.12.123.0","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[trim]))),
+ 2}]))),
+ <<":1:2:3:">> = iolist_to_binary(join(re:split(".1.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[]))),
+ <<":12:123:0">> = iolist_to_binary(join(re:split("A.12.123.0","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[trim]))),
<<":12:123:0:">> = iolist_to_binary(join(re:split("A.12.123.0","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[{parts,
- 2}]))),
- <<":12:123:0:">> = iolist_to_binary(join(re:split("A.12.123.0","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[trim]))),
+ 2}]))),
+ <<":12:123:0:">> = iolist_to_binary(join(re:split("A.12.123.0","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[]))),
- <<".1.2.3333">> = iolist_to_binary(join(re:split(".1.2.3333","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[]))),
+ <<".1.2.3333">> = iolist_to_binary(join(re:split(".1.2.3333","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[trim]))),
<<".1.2.3333">> = iolist_to_binary(join(re:split(".1.2.3333","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[{parts,
- 2}]))),
- <<".1.2.3333">> = iolist_to_binary(join(re:split(".1.2.3333","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[]))),
- <<"1.2.3">> = iolist_to_binary(join(re:split("1.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[trim]))),
+ 2}]))),
+ <<".1.2.3333">> = iolist_to_binary(join(re:split(".1.2.3333","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[]))),
+ <<"1.2.3">> = iolist_to_binary(join(re:split("1.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[trim]))),
<<"1.2.3">> = iolist_to_binary(join(re:split("1.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[{parts,
- 2}]))),
- <<"1.2.3">> = iolist_to_binary(join(re:split("1.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[]))),
- <<"1234.2.3">> = iolist_to_binary(join(re:split("1234.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[trim]))),
+ 2}]))),
+ <<"1.2.3">> = iolist_to_binary(join(re:split("1.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[]))),
+ <<"1234.2.3">> = iolist_to_binary(join(re:split("1234.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[trim]))),
<<"1234.2.3">> = iolist_to_binary(join(re:split("1234.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[{parts,
- 2}]))),
- <<"1234.2.3">> = iolist_to_binary(join(re:split("1234.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[]))),
- <<":1:non-sp1:non-sp2">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[trim]))),
+ 2}]))),
+ <<"1234.2.3">> = iolist_to_binary(join(re:split("1234.2.3","^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$",[]))),
+ <<":1:non-sp1:non-sp2">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[trim]))),
<<":1:non-sp1:non-sp2:">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[{parts,
- 2}]))),
- <<":1:non-sp1:non-sp2:">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[]))),
- <<":1:non-sp1:non-sp2">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2 (","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[trim]))),
+ 2}]))),
+ <<":1:non-sp1:non-sp2:">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[]))),
+ <<":1:non-sp1:non-sp2">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2 (","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[trim]))),
<<":1:non-sp1:non-sp2:">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2 (","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[{parts,
- 2}]))),
- <<":1:non-sp1:non-sp2:">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2 (","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[trim]))),
+ 2}]))),
+ <<":1:non-sp1:non-sp2:">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2 (","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[]))),
- <<"1IN SOA non-sp1 non-sp2(">> = iolist_to_binary(join(re:split("1IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[]))),
+ <<"1IN SOA non-sp1 non-sp2(">> = iolist_to_binary(join(re:split("1IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[trim]))),
<<"1IN SOA non-sp1 non-sp2(">> = iolist_to_binary(join(re:split("1IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[{parts,
- 2}]))),
- <<"1IN SOA non-sp1 non-sp2(">> = iolist_to_binary(join(re:split("1IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[]))),
- <<"">> = iolist_to_binary(join(re:split("a.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
+ 2}]))),
+ <<"1IN SOA non-sp1 non-sp2(">> = iolist_to_binary(join(re:split("1IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
- <<"">> = iolist_to_binary(join(re:split("Z.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("Z.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("Z.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("Z.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
- <<"">> = iolist_to_binary(join(re:split("2.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("Z.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("2.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("2.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("2.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
- <<":.pq-r">> = iolist_to_binary(join(re:split("ab-c.pq-r.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("2.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
+ <<":.pq-r">> = iolist_to_binary(join(re:split("ab-c.pq-r.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
<<":.pq-r:">> = iolist_to_binary(join(re:split("ab-c.pq-r.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[{parts,
- 2}]))),
- <<":.pq-r:">> = iolist_to_binary(join(re:split("ab-c.pq-r.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
- <<":.uk">> = iolist_to_binary(join(re:split("sxk.zzz.ac.uk.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
+ 2}]))),
+ <<":.pq-r:">> = iolist_to_binary(join(re:split("ab-c.pq-r.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
+ <<":.uk">> = iolist_to_binary(join(re:split("sxk.zzz.ac.uk.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
<<":.uk:">> = iolist_to_binary(join(re:split("sxk.zzz.ac.uk.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[{parts,
- 2}]))),
- <<":.uk:">> = iolist_to_binary(join(re:split("sxk.zzz.ac.uk.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
- <<":.y-">> = iolist_to_binary(join(re:split("x-.y-.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
+ 2}]))),
+ <<":.uk:">> = iolist_to_binary(join(re:split("sxk.zzz.ac.uk.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
+ <<":.y-">> = iolist_to_binary(join(re:split("x-.y-.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
<<":.y-:">> = iolist_to_binary(join(re:split("x-.y-.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[{parts,
- 2}]))),
- <<":.y-:">> = iolist_to_binary(join(re:split("x-.y-.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
+ 2}]))),
+ <<":.y-:">> = iolist_to_binary(join(re:split("x-.y-.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
- <<"-abc.peq.">> = iolist_to_binary(join(re:split("-abc.peq.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
+ <<"-abc.peq.">> = iolist_to_binary(join(re:split("-abc.peq.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[trim]))),
<<"-abc.peq.">> = iolist_to_binary(join(re:split("-abc.peq.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[{parts,
- 2}]))),
- <<"-abc.peq.">> = iolist_to_binary(join(re:split("-abc.peq.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
- <<"">> = iolist_to_binary(join(re:split("*.a","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
+ 2}]))),
+ <<"-abc.peq.">> = iolist_to_binary(join(re:split("-abc.peq.","^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("*.a","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
<<"::::">> = iolist_to_binary(join(re:split("*.a","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[{parts,
- 2}]))),
- <<"::::">> = iolist_to_binary(join(re:split("*.a","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
- <<":0-a">> = iolist_to_binary(join(re:split("*.b0-a","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
+ 2}]))),
+ <<"::::">> = iolist_to_binary(join(re:split("*.a","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
+ <<":0-a">> = iolist_to_binary(join(re:split("*.b0-a","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
<<":0-a:::">> = iolist_to_binary(join(re:split("*.b0-a","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[{parts,
- 2}]))),
- <<":0-a:::">> = iolist_to_binary(join(re:split("*.b0-a","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
- <<":3-b:.c">> = iolist_to_binary(join(re:split("*.c3-b.c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
+ 2}]))),
+ <<":0-a:::">> = iolist_to_binary(join(re:split("*.b0-a","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
+ <<":3-b:.c">> = iolist_to_binary(join(re:split("*.c3-b.c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
<<":3-b:.c::">> = iolist_to_binary(join(re:split("*.c3-b.c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[{parts,
- 2}]))),
- <<":3-b:.c::">> = iolist_to_binary(join(re:split("*.c3-b.c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
- <<":-a:.b-c:-c">> = iolist_to_binary(join(re:split("*.c-a.b-c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
+ 2}]))),
+ <<":3-b:.c::">> = iolist_to_binary(join(re:split("*.c3-b.c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
+ <<":-a:.b-c:-c">> = iolist_to_binary(join(re:split("*.c-a.b-c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
<<":-a:.b-c:-c:">> = iolist_to_binary(join(re:split("*.c-a.b-c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[{parts,
- 2}]))),
- <<":-a:.b-c:-c:">> = iolist_to_binary(join(re:split("*.c-a.b-c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
+ 2}]))),
+ <<":-a:.b-c:-c:">> = iolist_to_binary(join(re:split("*.c-a.b-c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
- <<"*.0">> = iolist_to_binary(join(re:split("*.0","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
+ <<"*.0">> = iolist_to_binary(join(re:split("*.0","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
<<"*.0">> = iolist_to_binary(join(re:split("*.0","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[{parts,
- 2}]))),
- <<"*.0">> = iolist_to_binary(join(re:split("*.0","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
- <<"*.a-">> = iolist_to_binary(join(re:split("*.a-","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
+ 2}]))),
+ <<"*.0">> = iolist_to_binary(join(re:split("*.0","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
+ <<"*.a-">> = iolist_to_binary(join(re:split("*.a-","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
<<"*.a-">> = iolist_to_binary(join(re:split("*.a-","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[{parts,
- 2}]))),
- <<"*.a-">> = iolist_to_binary(join(re:split("*.a-","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
- <<"*.a-b.c-">> = iolist_to_binary(join(re:split("*.a-b.c-","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
+ 2}]))),
+ <<"*.a-">> = iolist_to_binary(join(re:split("*.a-","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
+ <<"*.a-b.c-">> = iolist_to_binary(join(re:split("*.a-b.c-","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
<<"*.a-b.c-">> = iolist_to_binary(join(re:split("*.a-b.c-","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[{parts,
- 2}]))),
- <<"*.a-b.c-">> = iolist_to_binary(join(re:split("*.a-b.c-","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
- <<"*.c-a.0-c">> = iolist_to_binary(join(re:split("*.c-a.0-c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
+ 2}]))),
+ <<"*.a-b.c-">> = iolist_to_binary(join(re:split("*.a-b.c-","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
+ <<"*.c-a.0-c">> = iolist_to_binary(join(re:split("*.c-a.0-c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[trim]))),
<<"*.c-a.0-c">> = iolist_to_binary(join(re:split("*.c-a.0-c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[{parts,
- 2}]))),
- <<"*.c-a.0-c">> = iolist_to_binary(join(re:split("*.c-a.0-c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
- <<":de:abd:e">> = iolist_to_binary(join(re:split("abde","^(?=ab(de))(abd)(e)",[trim]))),
+ 2}]))),
+ <<"*.c-a.0-c">> = iolist_to_binary(join(re:split("*.c-a.0-c","^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$",[]))),
+ <<":de:abd:e">> = iolist_to_binary(join(re:split("abde","^(?=ab(de))(abd)(e)",[trim]))),
<<":de:abd:e:">> = iolist_to_binary(join(re:split("abde","^(?=ab(de))(abd)(e)",[{parts,
- 2}]))),
- <<":de:abd:e:">> = iolist_to_binary(join(re:split("abde","^(?=ab(de))(abd)(e)",[]))),
- <<"::abd:f">> = iolist_to_binary(join(re:split("abdf","^(?!(ab)de|x)(abd)(f)",[trim]))),
+ 2}]))),
+ <<":de:abd:e:">> = iolist_to_binary(join(re:split("abde","^(?=ab(de))(abd)(e)",[]))),
+ <<"::abd:f">> = iolist_to_binary(join(re:split("abdf","^(?!(ab)de|x)(abd)(f)",[trim]))),
<<"::abd:f:">> = iolist_to_binary(join(re:split("abdf","^(?!(ab)de|x)(abd)(f)",[{parts,
- 2}]))),
- <<"::abd:f:">> = iolist_to_binary(join(re:split("abdf","^(?!(ab)de|x)(abd)(f)",[]))),
- <<":abcd:cd:ab:cd">> = iolist_to_binary(join(re:split("abcd","^(?=(ab(cd)))(ab)",[trim]))),
+ 2}]))),
+ <<"::abd:f:">> = iolist_to_binary(join(re:split("abdf","^(?!(ab)de|x)(abd)(f)",[]))),
+ <<":abcd:cd:ab:cd">> = iolist_to_binary(join(re:split("abcd","^(?=(ab(cd)))(ab)",[trim]))),
<<":abcd:cd:ab:cd">> = iolist_to_binary(join(re:split("abcd","^(?=(ab(cd)))(ab)",[{parts,
- 2}]))),
- <<":abcd:cd:ab:cd">> = iolist_to_binary(join(re:split("abcd","^(?=(ab(cd)))(ab)",[]))),
+ 2}]))),
+ <<":abcd:cd:ab:cd">> = iolist_to_binary(join(re:split("abcd","^(?=(ab(cd)))(ab)",[]))),
<<":.d">> = iolist_to_binary(join(re:split("a.b.c.d","^[\\da-f](\\.[\\da-f])*$",[caseless,
- trim]))),
+ trim]))),
<<":.d:">> = iolist_to_binary(join(re:split("a.b.c.d","^[\\da-f](\\.[\\da-f])*$",[caseless,
{parts,
- 2}]))),
- <<":.d:">> = iolist_to_binary(join(re:split("a.b.c.d","^[\\da-f](\\.[\\da-f])*$",[caseless]))),
+ 2}]))),
+ <<":.d:">> = iolist_to_binary(join(re:split("a.b.c.d","^[\\da-f](\\.[\\da-f])*$",[caseless]))),
<<":.D">> = iolist_to_binary(join(re:split("A.B.C.D","^[\\da-f](\\.[\\da-f])*$",[caseless,
- trim]))),
+ trim]))),
<<":.D:">> = iolist_to_binary(join(re:split("A.B.C.D","^[\\da-f](\\.[\\da-f])*$",[caseless,
{parts,
- 2}]))),
- <<":.D:">> = iolist_to_binary(join(re:split("A.B.C.D","^[\\da-f](\\.[\\da-f])*$",[caseless]))),
+ 2}]))),
+ <<":.D:">> = iolist_to_binary(join(re:split("A.B.C.D","^[\\da-f](\\.[\\da-f])*$",[caseless]))),
<<":.C">> = iolist_to_binary(join(re:split("a.b.c.1.2.3.C","^[\\da-f](\\.[\\da-f])*$",[caseless,
- trim]))),
+ trim]))),
<<":.C:">> = iolist_to_binary(join(re:split("a.b.c.1.2.3.C","^[\\da-f](\\.[\\da-f])*$",[caseless,
{parts,
- 2}]))),
- <<":.C:">> = iolist_to_binary(join(re:split("a.b.c.1.2.3.C","^[\\da-f](\\.[\\da-f])*$",[caseless]))),
- <<"">> = iolist_to_binary(join(re:split("\"1234\"","^\\\".*\\\"\\s*(;.*)?$",[trim]))),
+ 2}]))),
+ <<":.C:">> = iolist_to_binary(join(re:split("a.b.c.1.2.3.C","^[\\da-f](\\.[\\da-f])*$",[caseless]))),
+ <<"">> = iolist_to_binary(join(re:split("\"1234\"","^\\\".*\\\"\\s*(;.*)?$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("\"1234\"","^\\\".*\\\"\\s*(;.*)?$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("\"1234\"","^\\\".*\\\"\\s*(;.*)?$",[]))),
- <<":;">> = iolist_to_binary(join(re:split("\"abcd\" ;","^\\\".*\\\"\\s*(;.*)?$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("\"1234\"","^\\\".*\\\"\\s*(;.*)?$",[]))),
+ <<":;">> = iolist_to_binary(join(re:split("\"abcd\" ;","^\\\".*\\\"\\s*(;.*)?$",[trim]))),
<<":;:">> = iolist_to_binary(join(re:split("\"abcd\" ;","^\\\".*\\\"\\s*(;.*)?$",[{parts,
- 2}]))),
- <<":;:">> = iolist_to_binary(join(re:split("\"abcd\" ;","^\\\".*\\\"\\s*(;.*)?$",[]))),
- <<":; rhubarb">> = iolist_to_binary(join(re:split("\"\" ; rhubarb","^\\\".*\\\"\\s*(;.*)?$",[trim]))),
+ 2}]))),
+ <<":;:">> = iolist_to_binary(join(re:split("\"abcd\" ;","^\\\".*\\\"\\s*(;.*)?$",[]))),
+ <<":; rhubarb">> = iolist_to_binary(join(re:split("\"\" ; rhubarb","^\\\".*\\\"\\s*(;.*)?$",[trim]))),
<<":; rhubarb:">> = iolist_to_binary(join(re:split("\"\" ; rhubarb","^\\\".*\\\"\\s*(;.*)?$",[{parts,
- 2}]))),
- <<":; rhubarb:">> = iolist_to_binary(join(re:split("\"\" ; rhubarb","^\\\".*\\\"\\s*(;.*)?$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\\".*\\\"\\s*(;.*)?$",[trim]))),
+ 2}]))),
+ <<":; rhubarb:">> = iolist_to_binary(join(re:split("\"\" ; rhubarb","^\\\".*\\\"\\s*(;.*)?$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\\".*\\\"\\s*(;.*)?$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\\".*\\\"\\s*(;.*)?$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\\".*\\\"\\s*(;.*)?$",[]))),
- <<"\"1234\" : things">> = iolist_to_binary(join(re:split("\"1234\" : things","^\\\".*\\\"\\s*(;.*)?$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\\".*\\\"\\s*(;.*)?$",[]))),
+ <<"\"1234\" : things">> = iolist_to_binary(join(re:split("\"1234\" : things","^\\\".*\\\"\\s*(;.*)?$",[trim]))),
<<"\"1234\" : things">> = iolist_to_binary(join(re:split("\"1234\" : things","^\\\".*\\\"\\s*(;.*)?$",[{parts,
- 2}]))),
- <<"\"1234\" : things">> = iolist_to_binary(join(re:split("\"1234\" : things","^\\\".*\\\"\\s*(;.*)?$",[]))),
- <<"">> = iolist_to_binary(join(re:split("","^$",[trim]))),
+ 2}]))),
+ <<"\"1234\" : things">> = iolist_to_binary(join(re:split("\"1234\" : things","^\\\".*\\\"\\s*(;.*)?$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("","^$",[trim]))),
<<"">> = iolist_to_binary(join(re:split("","^$",[{parts,
- 2}]))),
- <<"">> = iolist_to_binary(join(re:split("","^$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^$",[trim]))),
+ 2}]))),
+ <<"">> = iolist_to_binary(join(re:split("","^$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^$",[]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^$",[]))),
<<"">> = iolist_to_binary(join(re:split("ab c"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ab c"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab c"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab c"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended]))),
<<"abc">> = iolist_to_binary(join(re:split("abc"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended,
- trim]))),
+ trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended,
{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended]))),
<<"ab cde">> = iolist_to_binary(join(re:split("ab cde"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended,
- trim]))),
+ trim]))),
<<"ab cde">> = iolist_to_binary(join(re:split("ab cde"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended,
{parts,
- 2}]))),
- <<"ab cde">> = iolist_to_binary(join(re:split("ab cde"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended]))),
- <<"">> = iolist_to_binary(join(re:split("ab c","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[trim]))),
+ 2}]))),
+ <<"ab cde">> = iolist_to_binary(join(re:split("ab cde"," ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[extended]))),
+ <<"">> = iolist_to_binary(join(re:split("ab c","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ab c","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab c","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab c","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[]))),
- <<"ab cde">> = iolist_to_binary(join(re:split("ab cde","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[]))),
+ <<"ab cde">> = iolist_to_binary(join(re:split("ab cde","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[trim]))),
<<"ab cde">> = iolist_to_binary(join(re:split("ab cde","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[{parts,
- 2}]))),
- <<"ab cde">> = iolist_to_binary(join(re:split("ab cde","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[]))),
+ 2}]))),
+ <<"ab cde">> = iolist_to_binary(join(re:split("ab cde","(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)",[]))),
<<"">> = iolist_to_binary(join(re:split("a bcd","^ a\\ b[c ]d $",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("a bcd","^ a\\ b[c ]d $",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a bcd","^ a\\ b[c ]d $",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a bcd","^ a\\ b[c ]d $",[extended]))),
<<"">> = iolist_to_binary(join(re:split("a b d","^ a\\ b[c ]d $",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("a b d","^ a\\ b[c ]d $",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a b d","^ a\\ b[c ]d $",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a b d","^ a\\ b[c ]d $",[extended]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^ a\\ b[c ]d $",[extended,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^ a\\ b[c ]d $",[extended,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^ a\\ b[c ]d $",[extended]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^ a\\ b[c ]d $",[extended]))),
<<"abcd">> = iolist_to_binary(join(re:split("abcd","^ a\\ b[c ]d $",[extended,
- trim]))),
+ trim]))),
<<"abcd">> = iolist_to_binary(join(re:split("abcd","^ a\\ b[c ]d $",[extended,
{parts,
- 2}]))),
- <<"abcd">> = iolist_to_binary(join(re:split("abcd","^ a\\ b[c ]d $",[extended]))),
+ 2}]))),
+ <<"abcd">> = iolist_to_binary(join(re:split("abcd","^ a\\ b[c ]d $",[extended]))),
<<"ab d">> = iolist_to_binary(join(re:split("ab d","^ a\\ b[c ]d $",[extended,
- trim]))),
+ trim]))),
<<"ab d">> = iolist_to_binary(join(re:split("ab d","^ a\\ b[c ]d $",[extended,
{parts,
- 2}]))),
- <<"ab d">> = iolist_to_binary(join(re:split("ab d","^ a\\ b[c ]d $",[extended]))),
- <<":abc:bc:c:def:ef:f:hij:ij:j:klm:lm:m">> = iolist_to_binary(join(re:split("abcdefhijklm","^(a(b(c)))(d(e(f)))(h(i(j)))(k(l(m)))$",[trim]))),
+ 2}]))),
+ <<"ab d">> = iolist_to_binary(join(re:split("ab d","^ a\\ b[c ]d $",[extended]))),
+ <<":abc:bc:c:def:ef:f:hij:ij:j:klm:lm:m">> = iolist_to_binary(join(re:split("abcdefhijklm","^(a(b(c)))(d(e(f)))(h(i(j)))(k(l(m)))$",[trim]))),
<<":abc:bc:c:def:ef:f:hij:ij:j:klm:lm:m:">> = iolist_to_binary(join(re:split("abcdefhijklm","^(a(b(c)))(d(e(f)))(h(i(j)))(k(l(m)))$",[{parts,
- 2}]))),
- <<":abc:bc:c:def:ef:f:hij:ij:j:klm:lm:m:">> = iolist_to_binary(join(re:split("abcdefhijklm","^(a(b(c)))(d(e(f)))(h(i(j)))(k(l(m)))$",[]))),
+ 2}]))),
+ <<":abc:bc:c:def:ef:f:hij:ij:j:klm:lm:m:">> = iolist_to_binary(join(re:split("abcdefhijklm","^(a(b(c)))(d(e(f)))(h(i(j)))(k(l(m)))$",[]))),
ok.
run2() ->
- <<":bc:c:ef:f:ij:j:lm:m">> = iolist_to_binary(join(re:split("abcdefhijklm","^(?:a(b(c)))(?:d(e(f)))(?:h(i(j)))(?:k(l(m)))$",[trim]))),
+ <<":bc:c:ef:f:ij:j:lm:m">> = iolist_to_binary(join(re:split("abcdefhijklm","^(?:a(b(c)))(?:d(e(f)))(?:h(i(j)))(?:k(l(m)))$",[trim]))),
<<":bc:c:ef:f:ij:j:lm:m:">> = iolist_to_binary(join(re:split("abcdefhijklm","^(?:a(b(c)))(?:d(e(f)))(?:h(i(j)))(?:k(l(m)))$",[{parts,
- 2}]))),
- <<":bc:c:ef:f:ij:j:lm:m:">> = iolist_to_binary(join(re:split("abcdefhijklm","^(?:a(b(c)))(?:d(e(f)))(?:h(i(j)))(?:k(l(m)))$",[]))),
+ 2}]))),
+ <<":bc:c:ef:f:ij:j:lm:m:">> = iolist_to_binary(join(re:split("abcdefhijklm","^(?:a(b(c)))(?:d(e(f)))(?:h(i(j)))(?:k(l(m)))$",[]))),
<<"">> = iolist_to_binary(join(re:split("a+ Z0+
-","^[\\w][\\W][\\s][\\S][\\d][\\D][\\b][\\n][\\c]][\\022]",[trim]))),
+","^[\\w][\\W][\\s][\\S][\\d][\\D][\\b][\\n][\\c]][\\022]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a+ Z0+
","^[\\w][\\W][\\s][\\S][\\d][\\D][\\b][\\n][\\c]][\\022]",[{parts,
- 2}]))),
+ 2}]))),
<<":">> = iolist_to_binary(join(re:split("a+ Z0+
-","^[\\w][\\W][\\s][\\S][\\d][\\D][\\b][\\n][\\c]][\\022]",[]))),
- <<"">> = iolist_to_binary(join(re:split(".^$(*+)|{?,?}","^[.^$|()*+?{,}]+",[trim]))),
+","^[\\w][\\W][\\s][\\S][\\d][\\D][\\b][\\n][\\c]][\\022]",[]))),
+ <<"">> = iolist_to_binary(join(re:split(".^$(*+)|{?,?}","^[.^$|()*+?{,}]+",[trim]))),
<<":">> = iolist_to_binary(join(re:split(".^$(*+)|{?,?}","^[.^$|()*+?{,}]+",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split(".^$(*+)|{?,?}","^[.^$|()*+?{,}]+",[]))),
- <<"">> = iolist_to_binary(join(re:split("z","^a*\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split(".^$(*+)|{?,?}","^[.^$|()*+?{,}]+",[]))),
+ <<"">> = iolist_to_binary(join(re:split("z","^a*\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("z","^a*\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("z","^a*\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("az","^a*\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("z","^a*\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("az","^a*\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("az","^a*\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("az","^a*\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaz","^a*\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("az","^a*\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaz","^a*\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaz","^a*\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaz","^a*\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","^a*\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaz","^a*\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","^a*\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","^a*\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","^a*\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aa","^a*\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","^a*\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aa","^a*\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aa","^a*\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aa","^a*\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaa","^a*\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aa","^a*\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaa","^a*\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaa","^a*\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaa","^a*\\w",[]))),
- <<":+">> = iolist_to_binary(join(re:split("a+","^a*\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaa","^a*\\w",[]))),
+ <<":+">> = iolist_to_binary(join(re:split("a+","^a*\\w",[trim]))),
<<":+">> = iolist_to_binary(join(re:split("a+","^a*\\w",[{parts,
- 2}]))),
- <<":+">> = iolist_to_binary(join(re:split("a+","^a*\\w",[]))),
- <<":+">> = iolist_to_binary(join(re:split("aa+","^a*\\w",[trim]))),
+ 2}]))),
+ <<":+">> = iolist_to_binary(join(re:split("a+","^a*\\w",[]))),
+ <<":+">> = iolist_to_binary(join(re:split("aa+","^a*\\w",[trim]))),
<<":+">> = iolist_to_binary(join(re:split("aa+","^a*\\w",[{parts,
- 2}]))),
- <<":+">> = iolist_to_binary(join(re:split("aa+","^a*\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("z","^a*?\\w",[trim]))),
+ 2}]))),
+ <<":+">> = iolist_to_binary(join(re:split("aa+","^a*\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("z","^a*?\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("z","^a*?\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("z","^a*?\\w",[]))),
- <<":z">> = iolist_to_binary(join(re:split("az","^a*?\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("z","^a*?\\w",[]))),
+ <<":z">> = iolist_to_binary(join(re:split("az","^a*?\\w",[trim]))),
<<":z">> = iolist_to_binary(join(re:split("az","^a*?\\w",[{parts,
- 2}]))),
- <<":z">> = iolist_to_binary(join(re:split("az","^a*?\\w",[]))),
- <<":aaz">> = iolist_to_binary(join(re:split("aaaz","^a*?\\w",[trim]))),
+ 2}]))),
+ <<":z">> = iolist_to_binary(join(re:split("az","^a*?\\w",[]))),
+ <<":aaz">> = iolist_to_binary(join(re:split("aaaz","^a*?\\w",[trim]))),
<<":aaz">> = iolist_to_binary(join(re:split("aaaz","^a*?\\w",[{parts,
- 2}]))),
- <<":aaz">> = iolist_to_binary(join(re:split("aaaz","^a*?\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","^a*?\\w",[trim]))),
+ 2}]))),
+ <<":aaz">> = iolist_to_binary(join(re:split("aaaz","^a*?\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","^a*?\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","^a*?\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","^a*?\\w",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aa","^a*?\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","^a*?\\w",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aa","^a*?\\w",[trim]))),
<<":a">> = iolist_to_binary(join(re:split("aa","^a*?\\w",[{parts,
- 2}]))),
- <<":a">> = iolist_to_binary(join(re:split("aa","^a*?\\w",[]))),
- <<":aaa">> = iolist_to_binary(join(re:split("aaaa","^a*?\\w",[trim]))),
+ 2}]))),
+ <<":a">> = iolist_to_binary(join(re:split("aa","^a*?\\w",[]))),
+ <<":aaa">> = iolist_to_binary(join(re:split("aaaa","^a*?\\w",[trim]))),
<<":aaa">> = iolist_to_binary(join(re:split("aaaa","^a*?\\w",[{parts,
- 2}]))),
- <<":aaa">> = iolist_to_binary(join(re:split("aaaa","^a*?\\w",[]))),
- <<":+">> = iolist_to_binary(join(re:split("a+","^a*?\\w",[trim]))),
+ 2}]))),
+ <<":aaa">> = iolist_to_binary(join(re:split("aaaa","^a*?\\w",[]))),
+ <<":+">> = iolist_to_binary(join(re:split("a+","^a*?\\w",[trim]))),
<<":+">> = iolist_to_binary(join(re:split("a+","^a*?\\w",[{parts,
- 2}]))),
- <<":+">> = iolist_to_binary(join(re:split("a+","^a*?\\w",[]))),
- <<":a+">> = iolist_to_binary(join(re:split("aa+","^a*?\\w",[trim]))),
+ 2}]))),
+ <<":+">> = iolist_to_binary(join(re:split("a+","^a*?\\w",[]))),
+ <<":a+">> = iolist_to_binary(join(re:split("aa+","^a*?\\w",[trim]))),
<<":a+">> = iolist_to_binary(join(re:split("aa+","^a*?\\w",[{parts,
- 2}]))),
- <<":a+">> = iolist_to_binary(join(re:split("aa+","^a*?\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("az","^a+\\w",[trim]))),
+ 2}]))),
+ <<":a+">> = iolist_to_binary(join(re:split("aa+","^a*?\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("az","^a+\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("az","^a+\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("az","^a+\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaz","^a+\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("az","^a+\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaz","^a+\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaz","^a+\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaz","^a+\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aa","^a+\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaz","^a+\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aa","^a+\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aa","^a+\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aa","^a+\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaa","^a+\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aa","^a+\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaa","^a+\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaa","^a+\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaa","^a+\\w",[]))),
- <<":+">> = iolist_to_binary(join(re:split("aa+","^a+\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaa","^a+\\w",[]))),
+ <<":+">> = iolist_to_binary(join(re:split("aa+","^a+\\w",[trim]))),
<<":+">> = iolist_to_binary(join(re:split("aa+","^a+\\w",[{parts,
- 2}]))),
- <<":+">> = iolist_to_binary(join(re:split("aa+","^a+\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("az","^a+?\\w",[trim]))),
+ 2}]))),
+ <<":+">> = iolist_to_binary(join(re:split("aa+","^a+\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("az","^a+?\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("az","^a+?\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("az","^a+?\\w",[]))),
- <<":az">> = iolist_to_binary(join(re:split("aaaz","^a+?\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("az","^a+?\\w",[]))),
+ <<":az">> = iolist_to_binary(join(re:split("aaaz","^a+?\\w",[trim]))),
<<":az">> = iolist_to_binary(join(re:split("aaaz","^a+?\\w",[{parts,
- 2}]))),
- <<":az">> = iolist_to_binary(join(re:split("aaaz","^a+?\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aa","^a+?\\w",[trim]))),
+ 2}]))),
+ <<":az">> = iolist_to_binary(join(re:split("aaaz","^a+?\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aa","^a+?\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aa","^a+?\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aa","^a+?\\w",[]))),
- <<":aa">> = iolist_to_binary(join(re:split("aaaa","^a+?\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aa","^a+?\\w",[]))),
+ <<":aa">> = iolist_to_binary(join(re:split("aaaa","^a+?\\w",[trim]))),
<<":aa">> = iolist_to_binary(join(re:split("aaaa","^a+?\\w",[{parts,
- 2}]))),
- <<":aa">> = iolist_to_binary(join(re:split("aaaa","^a+?\\w",[]))),
- <<":+">> = iolist_to_binary(join(re:split("aa+","^a+?\\w",[trim]))),
+ 2}]))),
+ <<":aa">> = iolist_to_binary(join(re:split("aaaa","^a+?\\w",[]))),
+ <<":+">> = iolist_to_binary(join(re:split("aa+","^a+?\\w",[trim]))),
<<":+">> = iolist_to_binary(join(re:split("aa+","^a+?\\w",[{parts,
- 2}]))),
- <<":+">> = iolist_to_binary(join(re:split("aa+","^a+?\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("1234567890","^\\d{8}\\w{2,}",[trim]))),
+ 2}]))),
+ <<":+">> = iolist_to_binary(join(re:split("aa+","^a+?\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("1234567890","^\\d{8}\\w{2,}",[trim]))),
<<":">> = iolist_to_binary(join(re:split("1234567890","^\\d{8}\\w{2,}",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("1234567890","^\\d{8}\\w{2,}",[]))),
- <<"">> = iolist_to_binary(join(re:split("12345678ab","^\\d{8}\\w{2,}",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("1234567890","^\\d{8}\\w{2,}",[]))),
+ <<"">> = iolist_to_binary(join(re:split("12345678ab","^\\d{8}\\w{2,}",[trim]))),
<<":">> = iolist_to_binary(join(re:split("12345678ab","^\\d{8}\\w{2,}",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("12345678ab","^\\d{8}\\w{2,}",[]))),
- <<"">> = iolist_to_binary(join(re:split("12345678__","^\\d{8}\\w{2,}",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("12345678ab","^\\d{8}\\w{2,}",[]))),
+ <<"">> = iolist_to_binary(join(re:split("12345678__","^\\d{8}\\w{2,}",[trim]))),
<<":">> = iolist_to_binary(join(re:split("12345678__","^\\d{8}\\w{2,}",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("12345678__","^\\d{8}\\w{2,}",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\d{8}\\w{2,}",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("12345678__","^\\d{8}\\w{2,}",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\d{8}\\w{2,}",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\d{8}\\w{2,}",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\d{8}\\w{2,}",[]))),
- <<"1234567">> = iolist_to_binary(join(re:split("1234567","^\\d{8}\\w{2,}",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\d{8}\\w{2,}",[]))),
+ <<"1234567">> = iolist_to_binary(join(re:split("1234567","^\\d{8}\\w{2,}",[trim]))),
<<"1234567">> = iolist_to_binary(join(re:split("1234567","^\\d{8}\\w{2,}",[{parts,
- 2}]))),
- <<"1234567">> = iolist_to_binary(join(re:split("1234567","^\\d{8}\\w{2,}",[]))),
- <<"">> = iolist_to_binary(join(re:split("uoie","^[aeiou\\d]{4,5}$",[trim]))),
+ 2}]))),
+ <<"1234567">> = iolist_to_binary(join(re:split("1234567","^\\d{8}\\w{2,}",[]))),
+ <<"">> = iolist_to_binary(join(re:split("uoie","^[aeiou\\d]{4,5}$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("uoie","^[aeiou\\d]{4,5}$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("uoie","^[aeiou\\d]{4,5}$",[]))),
- <<"">> = iolist_to_binary(join(re:split("1234","^[aeiou\\d]{4,5}$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("uoie","^[aeiou\\d]{4,5}$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("1234","^[aeiou\\d]{4,5}$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("1234","^[aeiou\\d]{4,5}$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("1234","^[aeiou\\d]{4,5}$",[]))),
- <<"">> = iolist_to_binary(join(re:split("12345","^[aeiou\\d]{4,5}$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("1234","^[aeiou\\d]{4,5}$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("12345","^[aeiou\\d]{4,5}$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("12345","^[aeiou\\d]{4,5}$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("12345","^[aeiou\\d]{4,5}$",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaaa","^[aeiou\\d]{4,5}$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("12345","^[aeiou\\d]{4,5}$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaa","^[aeiou\\d]{4,5}$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaaa","^[aeiou\\d]{4,5}$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaaa","^[aeiou\\d]{4,5}$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[aeiou\\d]{4,5}$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaaa","^[aeiou\\d]{4,5}$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[aeiou\\d]{4,5}$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[aeiou\\d]{4,5}$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[aeiou\\d]{4,5}$",[]))),
- <<"123456">> = iolist_to_binary(join(re:split("123456","^[aeiou\\d]{4,5}$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[aeiou\\d]{4,5}$",[]))),
+ <<"123456">> = iolist_to_binary(join(re:split("123456","^[aeiou\\d]{4,5}$",[trim]))),
<<"123456">> = iolist_to_binary(join(re:split("123456","^[aeiou\\d]{4,5}$",[{parts,
- 2}]))),
- <<"123456">> = iolist_to_binary(join(re:split("123456","^[aeiou\\d]{4,5}$",[]))),
- <<"">> = iolist_to_binary(join(re:split("uoie","^[aeiou\\d]{4,5}?",[trim]))),
+ 2}]))),
+ <<"123456">> = iolist_to_binary(join(re:split("123456","^[aeiou\\d]{4,5}$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("uoie","^[aeiou\\d]{4,5}?",[trim]))),
<<":">> = iolist_to_binary(join(re:split("uoie","^[aeiou\\d]{4,5}?",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("uoie","^[aeiou\\d]{4,5}?",[]))),
- <<"">> = iolist_to_binary(join(re:split("1234","^[aeiou\\d]{4,5}?",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("uoie","^[aeiou\\d]{4,5}?",[]))),
+ <<"">> = iolist_to_binary(join(re:split("1234","^[aeiou\\d]{4,5}?",[trim]))),
<<":">> = iolist_to_binary(join(re:split("1234","^[aeiou\\d]{4,5}?",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("1234","^[aeiou\\d]{4,5}?",[]))),
- <<":5">> = iolist_to_binary(join(re:split("12345","^[aeiou\\d]{4,5}?",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("1234","^[aeiou\\d]{4,5}?",[]))),
+ <<":5">> = iolist_to_binary(join(re:split("12345","^[aeiou\\d]{4,5}?",[trim]))),
<<":5">> = iolist_to_binary(join(re:split("12345","^[aeiou\\d]{4,5}?",[{parts,
- 2}]))),
- <<":5">> = iolist_to_binary(join(re:split("12345","^[aeiou\\d]{4,5}?",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaaaa","^[aeiou\\d]{4,5}?",[trim]))),
+ 2}]))),
+ <<":5">> = iolist_to_binary(join(re:split("12345","^[aeiou\\d]{4,5}?",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaaa","^[aeiou\\d]{4,5}?",[trim]))),
<<":a">> = iolist_to_binary(join(re:split("aaaaa","^[aeiou\\d]{4,5}?",[{parts,
- 2}]))),
- <<":a">> = iolist_to_binary(join(re:split("aaaaa","^[aeiou\\d]{4,5}?",[]))),
- <<":56">> = iolist_to_binary(join(re:split("123456","^[aeiou\\d]{4,5}?",[trim]))),
+ 2}]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaaa","^[aeiou\\d]{4,5}?",[]))),
+ <<":56">> = iolist_to_binary(join(re:split("123456","^[aeiou\\d]{4,5}?",[trim]))),
<<":56">> = iolist_to_binary(join(re:split("123456","^[aeiou\\d]{4,5}?",[{parts,
- 2}]))),
- <<":56">> = iolist_to_binary(join(re:split("123456","^[aeiou\\d]{4,5}?",[]))),
- <<":abc:abc">> = iolist_to_binary(join(re:split("abc=abcabc","\\A(abc|def)=(\\1){2,3}\\Z",[trim]))),
+ 2}]))),
+ <<":56">> = iolist_to_binary(join(re:split("123456","^[aeiou\\d]{4,5}?",[]))),
+ <<":abc:abc">> = iolist_to_binary(join(re:split("abc=abcabc","\\A(abc|def)=(\\1){2,3}\\Z",[trim]))),
<<":abc:abc:">> = iolist_to_binary(join(re:split("abc=abcabc","\\A(abc|def)=(\\1){2,3}\\Z",[{parts,
- 2}]))),
- <<":abc:abc:">> = iolist_to_binary(join(re:split("abc=abcabc","\\A(abc|def)=(\\1){2,3}\\Z",[]))),
- <<":def:def">> = iolist_to_binary(join(re:split("def=defdefdef","\\A(abc|def)=(\\1){2,3}\\Z",[trim]))),
+ 2}]))),
+ <<":abc:abc:">> = iolist_to_binary(join(re:split("abc=abcabc","\\A(abc|def)=(\\1){2,3}\\Z",[]))),
+ <<":def:def">> = iolist_to_binary(join(re:split("def=defdefdef","\\A(abc|def)=(\\1){2,3}\\Z",[trim]))),
<<":def:def:">> = iolist_to_binary(join(re:split("def=defdefdef","\\A(abc|def)=(\\1){2,3}\\Z",[{parts,
- 2}]))),
- <<":def:def:">> = iolist_to_binary(join(re:split("def=defdefdef","\\A(abc|def)=(\\1){2,3}\\Z",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\A(abc|def)=(\\1){2,3}\\Z",[trim]))),
+ 2}]))),
+ <<":def:def:">> = iolist_to_binary(join(re:split("def=defdefdef","\\A(abc|def)=(\\1){2,3}\\Z",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\A(abc|def)=(\\1){2,3}\\Z",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\A(abc|def)=(\\1){2,3}\\Z",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\A(abc|def)=(\\1){2,3}\\Z",[]))),
- <<"abc=defdef">> = iolist_to_binary(join(re:split("abc=defdef","\\A(abc|def)=(\\1){2,3}\\Z",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\A(abc|def)=(\\1){2,3}\\Z",[]))),
+ <<"abc=defdef">> = iolist_to_binary(join(re:split("abc=defdef","\\A(abc|def)=(\\1){2,3}\\Z",[trim]))),
<<"abc=defdef">> = iolist_to_binary(join(re:split("abc=defdef","\\A(abc|def)=(\\1){2,3}\\Z",[{parts,
- 2}]))),
- <<"abc=defdef">> = iolist_to_binary(join(re:split("abc=defdef","\\A(abc|def)=(\\1){2,3}\\Z",[]))),
- <<":a:b:c:d:e:f:g:h:i:j:k:cd">> = iolist_to_binary(join(re:split("abcdefghijkcda2","^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$",[trim]))),
+ 2}]))),
+ <<"abc=defdef">> = iolist_to_binary(join(re:split("abc=defdef","\\A(abc|def)=(\\1){2,3}\\Z",[]))),
+ <<":a:b:c:d:e:f:g:h:i:j:k:cd">> = iolist_to_binary(join(re:split("abcdefghijkcda2","^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$",[trim]))),
<<":a:b:c:d:e:f:g:h:i:j:k:cd:">> = iolist_to_binary(join(re:split("abcdefghijkcda2","^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$",[{parts,
- 2}]))),
- <<":a:b:c:d:e:f:g:h:i:j:k:cd:">> = iolist_to_binary(join(re:split("abcdefghijkcda2","^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$",[]))),
- <<":a:b:c:d:e:f:g:h:i:j:k:cd">> = iolist_to_binary(join(re:split("abcdefghijkkkkcda2","^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$",[trim]))),
+ 2}]))),
+ <<":a:b:c:d:e:f:g:h:i:j:k:cd:">> = iolist_to_binary(join(re:split("abcdefghijkcda2","^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$",[]))),
+ <<":a:b:c:d:e:f:g:h:i:j:k:cd">> = iolist_to_binary(join(re:split("abcdefghijkkkkcda2","^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$",[trim]))),
<<":a:b:c:d:e:f:g:h:i:j:k:cd:">> = iolist_to_binary(join(re:split("abcdefghijkkkkcda2","^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$",[{parts,
- 2}]))),
- <<":a:b:c:d:e:f:g:h:i:j:k:cd:">> = iolist_to_binary(join(re:split("abcdefghijkkkkcda2","^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$",[]))),
- <<":cataract:aract:ract::3">> = iolist_to_binary(join(re:split("cataract cataract23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[trim]))),
+ 2}]))),
+ <<":a:b:c:d:e:f:g:h:i:j:k:cd:">> = iolist_to_binary(join(re:split("abcdefghijkkkkcda2","^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$",[]))),
+ <<":cataract:aract:ract::3">> = iolist_to_binary(join(re:split("cataract cataract23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[trim]))),
<<":cataract:aract:ract::3:">> = iolist_to_binary(join(re:split("cataract cataract23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[{parts,
- 2}]))),
- <<":cataract:aract:ract::3:">> = iolist_to_binary(join(re:split("cataract cataract23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[]))),
- <<":catatonic:atonic:tonic::3">> = iolist_to_binary(join(re:split("catatonic catatonic23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[trim]))),
+ 2}]))),
+ <<":cataract:aract:ract::3:">> = iolist_to_binary(join(re:split("cataract cataract23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[]))),
+ <<":catatonic:atonic:tonic::3">> = iolist_to_binary(join(re:split("catatonic catatonic23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[trim]))),
<<":catatonic:atonic:tonic::3:">> = iolist_to_binary(join(re:split("catatonic catatonic23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[{parts,
- 2}]))),
- <<":catatonic:atonic:tonic::3:">> = iolist_to_binary(join(re:split("catatonic catatonic23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[]))),
- <<":caterpillar:erpillar:::3">> = iolist_to_binary(join(re:split("caterpillar caterpillar23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[trim]))),
+ 2}]))),
+ <<":catatonic:atonic:tonic::3:">> = iolist_to_binary(join(re:split("catatonic catatonic23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[]))),
+ <<":caterpillar:erpillar:::3">> = iolist_to_binary(join(re:split("caterpillar caterpillar23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[trim]))),
<<":caterpillar:erpillar:::3:">> = iolist_to_binary(join(re:split("caterpillar caterpillar23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[{parts,
- 2}]))),
- <<":caterpillar:erpillar:::3:">> = iolist_to_binary(join(re:split("caterpillar caterpillar23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[]))),
- <<":abcd::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 01 12:33:02 1997","^From +([^ ]+) +[a-zA-Z][a-zA-Z][a-zA-Z] +[a-zA-Z][a-zA-Z][a-zA-Z] +[0-9]?[0-9] +[0-9][0-9]:[0-9][0-9]",[trim]))),
+ 2}]))),
+ <<":caterpillar:erpillar:::3:">> = iolist_to_binary(join(re:split("caterpillar caterpillar23","(cat(a(ract|tonic)|erpillar)) \\1()2(3)",[]))),
+ <<":abcd::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 01 12:33:02 1997","^From +([^ ]+) +[a-zA-Z][a-zA-Z][a-zA-Z] +[a-zA-Z][a-zA-Z][a-zA-Z] +[0-9]?[0-9] +[0-9][0-9]:[0-9][0-9]",[trim]))),
<<":abcd::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 01 12:33:02 1997","^From +([^ ]+) +[a-zA-Z][a-zA-Z][a-zA-Z] +[a-zA-Z][a-zA-Z][a-zA-Z] +[0-9]?[0-9] +[0-9][0-9]:[0-9][0-9]",[{parts,
- 2}]))),
- <<":abcd::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 01 12:33:02 1997","^From +([^ ]+) +[a-zA-Z][a-zA-Z][a-zA-Z] +[a-zA-Z][a-zA-Z][a-zA-Z] +[0-9]?[0-9] +[0-9][0-9]:[0-9][0-9]",[]))),
- <<":Sep ::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 01 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[trim]))),
+ 2}]))),
+ <<":abcd::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 01 12:33:02 1997","^From +([^ ]+) +[a-zA-Z][a-zA-Z][a-zA-Z] +[a-zA-Z][a-zA-Z][a-zA-Z] +[0-9]?[0-9] +[0-9][0-9]:[0-9][0-9]",[]))),
+ <<":Sep ::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 01 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[trim]))),
<<":Sep ::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 01 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[{parts,
- 2}]))),
- <<":Sep ::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 01 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[]))),
- <<":Sep ::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 1 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[trim]))),
+ 2}]))),
+ <<":Sep ::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 01 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[]))),
+ <<":Sep ::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 1 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[trim]))),
<<":Sep ::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 1 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[{parts,
- 2}]))),
- <<":Sep ::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 1 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[trim]))),
+ 2}]))),
+ <<":Sep ::02 1997">> = iolist_to_binary(join(re:split("From abcd Mon Sep 1 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[]))),
- <<"From abcd Sep 01 12:33:02 1997">> = iolist_to_binary(join(re:split("From abcd Sep 01 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[]))),
+ <<"From abcd Sep 01 12:33:02 1997">> = iolist_to_binary(join(re:split("From abcd Sep 01 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[trim]))),
<<"From abcd Sep 01 12:33:02 1997">> = iolist_to_binary(join(re:split("From abcd Sep 01 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[{parts,
- 2}]))),
- <<"From abcd Sep 01 12:33:02 1997">> = iolist_to_binary(join(re:split("From abcd Sep 01 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[]))),
+ 2}]))),
+ <<"From abcd Sep 01 12:33:02 1997">> = iolist_to_binary(join(re:split("From abcd Sep 01 12:33:02 1997","^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d",[]))),
<<"">> = iolist_to_binary(join(re:split("12
-34","^12.34",[dotall,trim]))),
+34","^12.34",[dotall,trim]))),
<<":">> = iolist_to_binary(join(re:split("12
-34","^12.34",[dotall,{parts,2}]))),
+34","^12.34",[dotall,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("12
-34","^12.34",[dotall]))),
+34","^12.34",[dotall]))),
<<"">> = iolist_to_binary(join(re:split("12 34","^12.34",[dotall,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("12 34","^12.34",[dotall,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("12 34","^12.34",[dotall]))),
- <<"the quick : fox">> = iolist_to_binary(join(re:split("the quick brown fox","\\w+(?=\\t)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("12 34","^12.34",[dotall]))),
+ <<"the quick : fox">> = iolist_to_binary(join(re:split("the quick brown fox","\\w+(?=\\t)",[trim]))),
<<"the quick : fox">> = iolist_to_binary(join(re:split("the quick brown fox","\\w+(?=\\t)",[{parts,
- 2}]))),
- <<"the quick : fox">> = iolist_to_binary(join(re:split("the quick brown fox","\\w+(?=\\t)",[]))),
- <<"foobar is :lish see?">> = iolist_to_binary(join(re:split("foobar is foolish see?","foo(?!bar)(.*)",[trim]))),
+ 2}]))),
+ <<"the quick : fox">> = iolist_to_binary(join(re:split("the quick brown fox","\\w+(?=\\t)",[]))),
+ <<"foobar is :lish see?">> = iolist_to_binary(join(re:split("foobar is foolish see?","foo(?!bar)(.*)",[trim]))),
<<"foobar is :lish see?:">> = iolist_to_binary(join(re:split("foobar is foolish see?","foo(?!bar)(.*)",[{parts,
- 2}]))),
- <<"foobar is :lish see?:">> = iolist_to_binary(join(re:split("foobar is foolish see?","foo(?!bar)(.*)",[]))),
- <<"foobar c: etc">> = iolist_to_binary(join(re:split("foobar crowbar etc","(?:(?!foo)...|^.{0,2})bar(.*)",[trim]))),
+ 2}]))),
+ <<"foobar is :lish see?:">> = iolist_to_binary(join(re:split("foobar is foolish see?","foo(?!bar)(.*)",[]))),
+ <<"foobar c: etc">> = iolist_to_binary(join(re:split("foobar crowbar etc","(?:(?!foo)...|^.{0,2})bar(.*)",[trim]))),
<<"foobar c: etc:">> = iolist_to_binary(join(re:split("foobar crowbar etc","(?:(?!foo)...|^.{0,2})bar(.*)",[{parts,
- 2}]))),
- <<"foobar c: etc:">> = iolist_to_binary(join(re:split("foobar crowbar etc","(?:(?!foo)...|^.{0,2})bar(.*)",[]))),
- <<":rel">> = iolist_to_binary(join(re:split("barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[trim]))),
+ 2}]))),
+ <<"foobar c: etc:">> = iolist_to_binary(join(re:split("foobar crowbar etc","(?:(?!foo)...|^.{0,2})bar(.*)",[]))),
+ <<":rel">> = iolist_to_binary(join(re:split("barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[trim]))),
<<":rel:">> = iolist_to_binary(join(re:split("barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[{parts,
- 2}]))),
- <<":rel:">> = iolist_to_binary(join(re:split("barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[]))),
- <<":rel">> = iolist_to_binary(join(re:split("2barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[trim]))),
+ 2}]))),
+ <<":rel:">> = iolist_to_binary(join(re:split("barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[]))),
+ <<":rel">> = iolist_to_binary(join(re:split("2barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[trim]))),
<<":rel:">> = iolist_to_binary(join(re:split("2barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[{parts,
- 2}]))),
- <<":rel:">> = iolist_to_binary(join(re:split("2barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[]))),
- <<":rel">> = iolist_to_binary(join(re:split("A barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[trim]))),
+ 2}]))),
+ <<":rel:">> = iolist_to_binary(join(re:split("2barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[]))),
+ <<":rel">> = iolist_to_binary(join(re:split("A barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[trim]))),
<<":rel:">> = iolist_to_binary(join(re:split("A barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[{parts,
- 2}]))),
- <<":rel:">> = iolist_to_binary(join(re:split("A barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[]))),
- <<":abc:456">> = iolist_to_binary(join(re:split("abc456","^(\\D*)(?=\\d)(?!123)",[trim]))),
+ 2}]))),
+ <<":rel:">> = iolist_to_binary(join(re:split("A barrel","(?:(?!foo)...|^.{0,2})bar(.*)",[]))),
+ <<":abc:456">> = iolist_to_binary(join(re:split("abc456","^(\\D*)(?=\\d)(?!123)",[trim]))),
<<":abc:456">> = iolist_to_binary(join(re:split("abc456","^(\\D*)(?=\\d)(?!123)",[{parts,
- 2}]))),
- <<":abc:456">> = iolist_to_binary(join(re:split("abc456","^(\\D*)(?=\\d)(?!123)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\D*)(?=\\d)(?!123)",[trim]))),
+ 2}]))),
+ <<":abc:456">> = iolist_to_binary(join(re:split("abc456","^(\\D*)(?=\\d)(?!123)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\D*)(?=\\d)(?!123)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\D*)(?=\\d)(?!123)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\D*)(?=\\d)(?!123)",[]))),
- <<"abc123">> = iolist_to_binary(join(re:split("abc123","^(\\D*)(?=\\d)(?!123)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\D*)(?=\\d)(?!123)",[]))),
+ <<"abc123">> = iolist_to_binary(join(re:split("abc123","^(\\D*)(?=\\d)(?!123)",[trim]))),
<<"abc123">> = iolist_to_binary(join(re:split("abc123","^(\\D*)(?=\\d)(?!123)",[{parts,
- 2}]))),
- <<"abc123">> = iolist_to_binary(join(re:split("abc123","^(\\D*)(?=\\d)(?!123)",[]))),
+ 2}]))),
+ <<"abc123">> = iolist_to_binary(join(re:split("abc123","^(\\D*)(?=\\d)(?!123)",[]))),
ok.
run3() ->
<<"">> = iolist_to_binary(join(re:split("1234","^1234(?# test newlines
- inside)",[trim]))),
+ inside)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("1234","^1234(?# test newlines
- inside)",[{parts,2}]))),
+ inside)",[{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("1234","^1234(?# test newlines
- inside)",[]))),
+ inside)",[]))),
<<"">> = iolist_to_binary(join(re:split("1234","^1234 #comment in extended re
- ",[extended,trim]))),
+ ",[extended,trim]))),
<<":">> = iolist_to_binary(join(re:split("1234","^1234 #comment in extended re
- ",[extended,{parts,2}]))),
+ ",[extended,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("1234","^1234 #comment in extended re
- ",[extended]))),
+ ",[extended]))),
<<"">> = iolist_to_binary(join(re:split("abcd","#rhubarb
- abcd",[extended,trim]))),
+ abcd",[extended,trim]))),
<<":">> = iolist_to_binary(join(re:split("abcd","#rhubarb
- abcd",[extended,{parts,2}]))),
+ abcd",[extended,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("abcd","#rhubarb
- abcd",[extended]))),
+ abcd",[extended]))),
<<"">> = iolist_to_binary(join(re:split("abcd","^abcd#rhubarb",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("abcd","^abcd#rhubarb",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcd","^abcd#rhubarb",[extended]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aaab","^(a)\\1{2,3}(.)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcd","^abcd#rhubarb",[extended]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aaab","^(a)\\1{2,3}(.)",[trim]))),
<<":a:b:">> = iolist_to_binary(join(re:split("aaab","^(a)\\1{2,3}(.)",[{parts,
- 2}]))),
- <<":a:b:">> = iolist_to_binary(join(re:split("aaab","^(a)\\1{2,3}(.)",[]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aaaab","^(a)\\1{2,3}(.)",[trim]))),
+ 2}]))),
+ <<":a:b:">> = iolist_to_binary(join(re:split("aaab","^(a)\\1{2,3}(.)",[]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aaaab","^(a)\\1{2,3}(.)",[trim]))),
<<":a:b:">> = iolist_to_binary(join(re:split("aaaab","^(a)\\1{2,3}(.)",[{parts,
- 2}]))),
- <<":a:b:">> = iolist_to_binary(join(re:split("aaaab","^(a)\\1{2,3}(.)",[]))),
- <<":a:a:b">> = iolist_to_binary(join(re:split("aaaaab","^(a)\\1{2,3}(.)",[trim]))),
+ 2}]))),
+ <<":a:b:">> = iolist_to_binary(join(re:split("aaaab","^(a)\\1{2,3}(.)",[]))),
+ <<":a:a:b">> = iolist_to_binary(join(re:split("aaaaab","^(a)\\1{2,3}(.)",[trim]))),
<<":a:a:b">> = iolist_to_binary(join(re:split("aaaaab","^(a)\\1{2,3}(.)",[{parts,
- 2}]))),
- <<":a:a:b">> = iolist_to_binary(join(re:split("aaaaab","^(a)\\1{2,3}(.)",[]))),
- <<":a:a:ab">> = iolist_to_binary(join(re:split("aaaaaab","^(a)\\1{2,3}(.)",[trim]))),
+ 2}]))),
+ <<":a:a:b">> = iolist_to_binary(join(re:split("aaaaab","^(a)\\1{2,3}(.)",[]))),
+ <<":a:a:ab">> = iolist_to_binary(join(re:split("aaaaaab","^(a)\\1{2,3}(.)",[trim]))),
<<":a:a:ab">> = iolist_to_binary(join(re:split("aaaaaab","^(a)\\1{2,3}(.)",[{parts,
- 2}]))),
- <<":a:a:ab">> = iolist_to_binary(join(re:split("aaaaaab","^(a)\\1{2,3}(.)",[]))),
- <<"the ">> = iolist_to_binary(join(re:split("the abc","(?!^)abc",[trim]))),
+ 2}]))),
+ <<":a:a:ab">> = iolist_to_binary(join(re:split("aaaaaab","^(a)\\1{2,3}(.)",[]))),
+ <<"the ">> = iolist_to_binary(join(re:split("the abc","(?!^)abc",[trim]))),
<<"the :">> = iolist_to_binary(join(re:split("the abc","(?!^)abc",[{parts,
- 2}]))),
- <<"the :">> = iolist_to_binary(join(re:split("the abc","(?!^)abc",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?!^)abc",[trim]))),
+ 2}]))),
+ <<"the :">> = iolist_to_binary(join(re:split("the abc","(?!^)abc",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?!^)abc",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?!^)abc",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?!^)abc",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(?!^)abc",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?!^)abc",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(?!^)abc",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","(?!^)abc",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(?!^)abc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","(?=^)abc",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(?!^)abc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","(?=^)abc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","(?=^)abc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","(?=^)abc",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?=^)abc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","(?=^)abc",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?=^)abc",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?=^)abc",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?=^)abc",[]))),
- <<"the abc">> = iolist_to_binary(join(re:split("the abc","(?=^)abc",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?=^)abc",[]))),
+ <<"the abc">> = iolist_to_binary(join(re:split("the abc","(?=^)abc",[trim]))),
<<"the abc">> = iolist_to_binary(join(re:split("the abc","(?=^)abc",[{parts,
- 2}]))),
- <<"the abc">> = iolist_to_binary(join(re:split("the abc","(?=^)abc",[]))),
- <<":b:bbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}(ab*|b)",[trim]))),
+ 2}]))),
+ <<"the abc">> = iolist_to_binary(join(re:split("the abc","(?=^)abc",[]))),
+ <<":b:bbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}(ab*|b)",[trim]))),
<<":b:bbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}(ab*|b)",[{parts,
- 2}]))),
- <<":b:bbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}(ab*|b)",[]))),
- <<":abbbbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}?(ab*|b)",[trim]))),
+ 2}]))),
+ <<":b:bbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}(ab*|b)",[]))),
+ <<":abbbbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}?(ab*|b)",[trim]))),
<<":abbbbb:">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}?(ab*|b)",[{parts,
- 2}]))),
- <<":abbbbb:">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}?(ab*|b)",[]))),
- <<":a:bbbbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}?(ab*?|b)",[trim]))),
+ 2}]))),
+ <<":abbbbb:">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}?(ab*|b)",[]))),
+ <<":a:bbbbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}?(ab*?|b)",[trim]))),
<<":a:bbbbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}?(ab*?|b)",[{parts,
- 2}]))),
- <<":a:bbbbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}?(ab*?|b)",[]))),
- <<":b:bbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}(ab*?|b)",[trim]))),
+ 2}]))),
+ <<":a:bbbbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}?(ab*?|b)",[]))),
+ <<":b:bbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}(ab*?|b)",[trim]))),
<<":b:bbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}(ab*?|b)",[{parts,
- 2}]))),
- <<":b:bbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}(ab*?|b)",[]))),
+ 2}]))),
+ <<":b:bbb">> = iolist_to_binary(join(re:split("aabbbbb","^[ab]{1,3}(ab*?|b)",[]))),
<<"Alan Other <user.ain>">> = iolist_to_binary(join(re:split("Alan Other <user.ain>"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -1630,7 +1630,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended,trim]))),
+\\) )* # optional trailing comment",[extended,trim]))),
<<"Alan Other <user.ain>">> = iolist_to_binary(join(re:split("Alan Other <user.ain>"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -1824,7 +1824,7 @@ run3() ->
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional trailing comment",[extended,
- {parts,2}]))),
+ {parts,2}]))),
<<"Alan Other <user.ain>">> = iolist_to_binary(join(re:split("Alan Other <user.ain>"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -2017,7 +2017,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended]))),
+\\) )* # optional trailing comment",[extended]))),
<<"<user.ain>">> = iolist_to_binary(join(re:split("<user.ain>"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -2210,7 +2210,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended,trim]))),
+\\) )* # optional trailing comment",[extended,trim]))),
<<"<user.ain>">> = iolist_to_binary(join(re:split("<user.ain>"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -2404,7 +2404,7 @@ run3() ->
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional trailing comment",[extended,
- {parts,2}]))),
+ {parts,2}]))),
<<"<user.ain>">> = iolist_to_binary(join(re:split("<user.ain>"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -2597,7 +2597,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended]))),
+\\) )* # optional trailing comment",[extended]))),
<<"user.ain">> = iolist_to_binary(join(re:split("user.ain"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -2790,7 +2790,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended,trim]))),
+\\) )* # optional trailing comment",[extended,trim]))),
<<"user.ain">> = iolist_to_binary(join(re:split("user.ain"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -2984,7 +2984,7 @@ run3() ->
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional trailing comment",[extended,
- {parts,2}]))),
+ {parts,2}]))),
<<"user.ain">> = iolist_to_binary(join(re:split("user.ain"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -3177,7 +3177,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended]))),
+\\) )* # optional trailing comment",[extended]))),
<<"\"A. Other\" <user.1234.ain> (a comment)">> = iolist_to_binary(join(re:split("\"A. Other\" <user.1234.ain> (a comment)"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -3370,7 +3370,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended,trim]))),
+\\) )* # optional trailing comment",[extended,trim]))),
<<"\"A. Other\" <user.1234.ain> (a comment)">> = iolist_to_binary(join(re:split("\"A. Other\" <user.1234.ain> (a comment)"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -3564,7 +3564,7 @@ run3() ->
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional trailing comment",[extended,
- {parts,2}]))),
+ {parts,2}]))),
<<"\"A. Other\" <user.1234.ain> (a comment)">> = iolist_to_binary(join(re:split("\"A. Other\" <user.1234.ain> (a comment)"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -3757,7 +3757,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended]))),
+\\) )* # optional trailing comment",[extended]))),
<<"A. Other <user.1234.ain> (a comment)">> = iolist_to_binary(join(re:split("A. Other <user.1234.ain> (a comment)"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -3950,7 +3950,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended,trim]))),
+\\) )* # optional trailing comment",[extended,trim]))),
<<"A. Other <user.1234.ain> (a comment)">> = iolist_to_binary(join(re:split("A. Other <user.1234.ain> (a comment)"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -4144,7 +4144,7 @@ run3() ->
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional trailing comment",[extended,
- {parts,2}]))),
+ {parts,2}]))),
<<"A. Other <user.1234.ain> (a comment)">> = iolist_to_binary(join(re:split("A. Other <user.1234.ain> (a comment)"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -4337,7 +4337,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended]))),
+\\) )* # optional trailing comment",[extended]))),
<<"\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"-re.lay">> = iolist_to_binary(join(re:split("\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"-re.lay"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -4530,7 +4530,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended,trim]))),
+\\) )* # optional trailing comment",[extended,trim]))),
<<"\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"-re.lay">> = iolist_to_binary(join(re:split("\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"-re.lay"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -4724,7 +4724,7 @@ run3() ->
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional trailing comment",[extended,
- {parts,2}]))),
+ {parts,2}]))),
<<"\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"-re.lay">> = iolist_to_binary(join(re:split("\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"-re.lay"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -4917,7 +4917,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended]))),
+\\) )* # optional trailing comment",[extended]))),
<<"A missing angle <user.where">> = iolist_to_binary(join(re:split("A missing angle <user.where"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -5110,7 +5110,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended,trim]))),
+\\) )* # optional trailing comment",[extended,trim]))),
<<"A missing angle <user.where">> = iolist_to_binary(join(re:split("A missing angle <user.where"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -5304,7 +5304,7 @@ run3() ->
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional trailing comment",[extended,
- {parts,2}]))),
+ {parts,2}]))),
<<"A missing angle <user.where">> = iolist_to_binary(join(re:split("A missing angle <user.where"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -5497,7 +5497,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended]))),
+\\) )* # optional trailing comment",[extended]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -5690,7 +5690,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended,trim]))),
+\\) )* # optional trailing comment",[extended,trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -5884,7 +5884,7 @@ run3() ->
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional trailing comment",[extended,
- {parts,2}]))),
+ {parts,2}]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -6077,7 +6077,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended]))),
+\\) )* # optional trailing comment",[extended]))),
<<"The quick brown fox">> = iolist_to_binary(join(re:split("The quick brown fox"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -6270,7 +6270,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended,trim]))),
+\\) )* # optional trailing comment",[extended,trim]))),
<<"The quick brown fox">> = iolist_to_binary(join(re:split("The quick brown fox"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -6464,7 +6464,7 @@ run3() ->
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional trailing comment",[extended,
- {parts,2}]))),
+ {parts,2}]))),
<<"The quick brown fox">> = iolist_to_binary(join(re:split("The quick brown fox"," (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
\\) )* # optional leading comment
@@ -6657,7 +6657,7 @@ run3() ->
# name and address
) (?: [\\040\\t] | \\(
(?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )*
-\\) )* # optional trailing comment",[extended]))),
+\\) )* # optional trailing comment",[extended]))),
<<"Alan Other <user.ain>">> = iolist_to_binary(join(re:split("Alan Other <user.ain>","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -7238,7 +7238,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,trim]))),
+)",[extended,trim]))),
<<"Alan Other <user.ain>">> = iolist_to_binary(join(re:split("Alan Other <user.ain>","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -7819,7 +7819,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,{parts,2}]))),
+)",[extended,{parts,2}]))),
<<"Alan Other <user.ain>">> = iolist_to_binary(join(re:split("Alan Other <user.ain>","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -8400,7 +8400,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended]))),
+)",[extended]))),
<<"<user.ain>">> = iolist_to_binary(join(re:split("<user.ain>","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -8981,7 +8981,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,trim]))),
+)",[extended,trim]))),
<<"<user.ain>">> = iolist_to_binary(join(re:split("<user.ain>","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -9562,7 +9562,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,{parts,2}]))),
+)",[extended,{parts,2}]))),
<<"<user.ain>">> = iolist_to_binary(join(re:split("<user.ain>","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -10143,7 +10143,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended]))),
+)",[extended]))),
<<"user.ain">> = iolist_to_binary(join(re:split("user.ain","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -10724,7 +10724,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,trim]))),
+)",[extended,trim]))),
<<"user.ain">> = iolist_to_binary(join(re:split("user.ain","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -11305,7 +11305,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,{parts,2}]))),
+)",[extended,{parts,2}]))),
<<"user.ain">> = iolist_to_binary(join(re:split("user.ain","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -11886,7 +11886,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended]))),
+)",[extended]))),
<<"\"A. Other\" <user.1234.ain> (a comment)">> = iolist_to_binary(join(re:split("\"A. Other\" <user.1234.ain> (a comment)","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -12467,7 +12467,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,trim]))),
+)",[extended,trim]))),
<<"\"A. Other\" <user.1234.ain> (a comment)">> = iolist_to_binary(join(re:split("\"A. Other\" <user.1234.ain> (a comment)","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -13048,7 +13048,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,{parts,2}]))),
+)",[extended,{parts,2}]))),
<<"\"A. Other\" <user.1234.ain> (a comment)">> = iolist_to_binary(join(re:split("\"A. Other\" <user.1234.ain> (a comment)","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -13629,7 +13629,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended]))),
+)",[extended]))),
<<"A. Other <user.1234.ain> (a comment)">> = iolist_to_binary(join(re:split("A. Other <user.1234.ain> (a comment)","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -14210,7 +14210,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,trim]))),
+)",[extended,trim]))),
<<"A. Other <user.1234.ain> (a comment)">> = iolist_to_binary(join(re:split("A. Other <user.1234.ain> (a comment)","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -14791,7 +14791,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,{parts,2}]))),
+)",[extended,{parts,2}]))),
<<"A. Other <user.1234.ain> (a comment)">> = iolist_to_binary(join(re:split("A. Other <user.1234.ain> (a comment)","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -15372,7 +15372,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended]))),
+)",[extended]))),
<<"\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"-re.lay">> = iolist_to_binary(join(re:split("\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"-re.lay","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -15953,7 +15953,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,trim]))),
+)",[extended,trim]))),
<<"\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"-re.lay">> = iolist_to_binary(join(re:split("\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"-re.lay","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -16534,7 +16534,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,{parts,2}]))),
+)",[extended,{parts,2}]))),
<<"\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"-re.lay">> = iolist_to_binary(join(re:split("\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"-re.lay","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -17115,7 +17115,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended]))),
+)",[extended]))),
<<"A missing angle <user.where">> = iolist_to_binary(join(re:split("A missing angle <user.where","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -17696,7 +17696,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,trim]))),
+)",[extended,trim]))),
<<"A missing angle <user.where">> = iolist_to_binary(join(re:split("A missing angle <user.where","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -18277,7 +18277,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,{parts,2}]))),
+)",[extended,{parts,2}]))),
<<"A missing angle <user.where">> = iolist_to_binary(join(re:split("A missing angle <user.where","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -18858,7 +18858,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended]))),
+)",[extended]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -19439,7 +19439,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,trim]))),
+)",[extended,trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -20020,7 +20020,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,{parts,2}]))),
+)",[extended,{parts,2}]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -20601,7 +20601,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended]))),
+)",[extended]))),
<<"The quick brown fox">> = iolist_to_binary(join(re:split("The quick brown fox","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -21182,7 +21182,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,trim]))),
+)",[extended,trim]))),
<<"The quick brown fox">> = iolist_to_binary(join(re:split("The quick brown fox","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -21763,7 +21763,7 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended,{parts,2}]))),
+)",[extended,{parts,2}]))),
<<"The quick brown fox">> = iolist_to_binary(join(re:split("The quick brown fox","[\\040\\t]* # Nab whitespace.
(?:
\\( # (
@@ -22344,5763 +22344,5763 @@ run3() ->
# address spec
> # >
# name and address
-)",[extended]))),
- <<"abcdefpqrxyz0AB">> = iolist_to_binary(join(re:split("abcdefpqrxyz0AB","abc\\0def\\00pqr\\000xyz\\0000AB",[trim]))),
+)",[extended]))),
+ <<"abcdefpqrxyz0AB">> = iolist_to_binary(join(re:split("abcdefpqrxyz0AB","abc\\0def\\00pqr\\000xyz\\0000AB",[trim]))),
<<"abcdefpqrxyz0AB">> = iolist_to_binary(join(re:split("abcdefpqrxyz0AB","abc\\0def\\00pqr\\000xyz\\0000AB",[{parts,
- 2}]))),
- <<"abcdefpqrxyz0AB">> = iolist_to_binary(join(re:split("abcdefpqrxyz0AB","abc\\0def\\00pqr\\000xyz\\0000AB",[]))),
- <<"abc456 abcdefpqrxyz0ABCDE">> = iolist_to_binary(join(re:split("abc456 abcdefpqrxyz0ABCDE","abc\\0def\\00pqr\\000xyz\\0000AB",[trim]))),
+ 2}]))),
+ <<"abcdefpqrxyz0AB">> = iolist_to_binary(join(re:split("abcdefpqrxyz0AB","abc\\0def\\00pqr\\000xyz\\0000AB",[]))),
+ <<"abc456 abcdefpqrxyz0ABCDE">> = iolist_to_binary(join(re:split("abc456 abcdefpqrxyz0ABCDE","abc\\0def\\00pqr\\000xyz\\0000AB",[trim]))),
<<"abc456 abcdefpqrxyz0ABCDE">> = iolist_to_binary(join(re:split("abc456 abcdefpqrxyz0ABCDE","abc\\0def\\00pqr\\000xyz\\0000AB",[{parts,
- 2}]))),
- <<"abc456 abcdefpqrxyz0ABCDE">> = iolist_to_binary(join(re:split("abc456 abcdefpqrxyz0ABCDE","abc\\0def\\00pqr\\000xyz\\0000AB",[]))),
- <<"abc efpqr0xyz00AB">> = iolist_to_binary(join(re:split("abc efpqr0xyz00AB","abc\\x0def\\x00pqr\\x000xyz\\x0000AB",[trim]))),
+ 2}]))),
+ <<"abc456 abcdefpqrxyz0ABCDE">> = iolist_to_binary(join(re:split("abc456 abcdefpqrxyz0ABCDE","abc\\0def\\00pqr\\000xyz\\0000AB",[]))),
+ <<"abc efpqr0xyz00AB">> = iolist_to_binary(join(re:split("abc efpqr0xyz00AB","abc\\x0def\\x00pqr\\x000xyz\\x0000AB",[trim]))),
<<"abc efpqr0xyz00AB">> = iolist_to_binary(join(re:split("abc efpqr0xyz00AB","abc\\x0def\\x00pqr\\x000xyz\\x0000AB",[{parts,
- 2}]))),
- <<"abc efpqr0xyz00AB">> = iolist_to_binary(join(re:split("abc efpqr0xyz00AB","abc\\x0def\\x00pqr\\x000xyz\\x0000AB",[]))),
- <<"abc456 abc efpqr0xyz00ABCDE">> = iolist_to_binary(join(re:split("abc456 abc efpqr0xyz00ABCDE","abc\\x0def\\x00pqr\\x000xyz\\x0000AB",[trim]))),
+ 2}]))),
+ <<"abc efpqr0xyz00AB">> = iolist_to_binary(join(re:split("abc efpqr0xyz00AB","abc\\x0def\\x00pqr\\x000xyz\\x0000AB",[]))),
+ <<"abc456 abc efpqr0xyz00ABCDE">> = iolist_to_binary(join(re:split("abc456 abc efpqr0xyz00ABCDE","abc\\x0def\\x00pqr\\x000xyz\\x0000AB",[trim]))),
<<"abc456 abc efpqr0xyz00ABCDE">> = iolist_to_binary(join(re:split("abc456 abc efpqr0xyz00ABCDE","abc\\x0def\\x00pqr\\x000xyz\\x0000AB",[{parts,
- 2}]))),
- <<"abc456 abc efpqr0xyz00ABCDE">> = iolist_to_binary(join(re:split("abc456 abc efpqr0xyz00ABCDE","abc\\x0def\\x00pqr\\x000xyz\\x0000AB",[]))),
- <<"A">> = iolist_to_binary(join(re:split("A","^[\\000-\\037]",[trim]))),
+ 2}]))),
+ <<"abc456 abc efpqr0xyz00ABCDE">> = iolist_to_binary(join(re:split("abc456 abc efpqr0xyz00ABCDE","abc\\x0def\\x00pqr\\x000xyz\\x0000AB",[]))),
+ <<"A">> = iolist_to_binary(join(re:split("A","^[\\000-\\037]",[trim]))),
<<"A">> = iolist_to_binary(join(re:split("A","^[\\000-\\037]",[{parts,
- 2}]))),
- <<"A">> = iolist_to_binary(join(re:split("A","^[\\000-\\037]",[]))),
- <<":B">> = iolist_to_binary(join(re:split("B","^[\\000-\\037]",[trim]))),
+ 2}]))),
+ <<"A">> = iolist_to_binary(join(re:split("A","^[\\000-\\037]",[]))),
+ <<":B">> = iolist_to_binary(join(re:split("B","^[\\000-\\037]",[trim]))),
<<":B">> = iolist_to_binary(join(re:split("B","^[\\000-\\037]",[{parts,
- 2}]))),
- <<":B">> = iolist_to_binary(join(re:split("B","^[\\000-\\037]",[]))),
- <<":C">> = iolist_to_binary(join(re:split("C","^[\\000-\\037]",[trim]))),
+ 2}]))),
+ <<":B">> = iolist_to_binary(join(re:split("B","^[\\000-\\037]",[]))),
+ <<":C">> = iolist_to_binary(join(re:split("C","^[\\000-\\037]",[trim]))),
<<":C">> = iolist_to_binary(join(re:split("C","^[\\000-\\037]",[{parts,
- 2}]))),
- <<":C">> = iolist_to_binary(join(re:split("C","^[\\000-\\037]",[]))),
- <<"">> = iolist_to_binary(join(re:split("","\\0*",[trim]))),
+ 2}]))),
+ <<":C">> = iolist_to_binary(join(re:split("C","^[\\000-\\037]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("","\\0*",[trim]))),
<<"">> = iolist_to_binary(join(re:split("","\\0*",[{parts,
- 2}]))),
- <<"">> = iolist_to_binary(join(re:split("","\\0*",[]))),
- <<"The AZ">> = iolist_to_binary(join(re:split("The AZ","A\\x0{2,3}Z",[trim]))),
+ 2}]))),
+ <<"">> = iolist_to_binary(join(re:split("","\\0*",[]))),
+ <<"The AZ">> = iolist_to_binary(join(re:split("The AZ","A\\x0{2,3}Z",[trim]))),
<<"The AZ">> = iolist_to_binary(join(re:split("The AZ","A\\x0{2,3}Z",[{parts,
- 2}]))),
- <<"The AZ">> = iolist_to_binary(join(re:split("The AZ","A\\x0{2,3}Z",[]))),
- <<"An AZ">> = iolist_to_binary(join(re:split("An AZ","A\\x0{2,3}Z",[trim]))),
+ 2}]))),
+ <<"The AZ">> = iolist_to_binary(join(re:split("The AZ","A\\x0{2,3}Z",[]))),
+ <<"An AZ">> = iolist_to_binary(join(re:split("An AZ","A\\x0{2,3}Z",[trim]))),
<<"An AZ">> = iolist_to_binary(join(re:split("An AZ","A\\x0{2,3}Z",[{parts,
- 2}]))),
- <<"An AZ">> = iolist_to_binary(join(re:split("An AZ","A\\x0{2,3}Z",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","A\\x0{2,3}Z",[trim]))),
+ 2}]))),
+ <<"An AZ">> = iolist_to_binary(join(re:split("An AZ","A\\x0{2,3}Z",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","A\\x0{2,3}Z",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","A\\x0{2,3}Z",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","A\\x0{2,3}Z",[]))),
- <<"AZ">> = iolist_to_binary(join(re:split("AZ","A\\x0{2,3}Z",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","A\\x0{2,3}Z",[]))),
+ <<"AZ">> = iolist_to_binary(join(re:split("AZ","A\\x0{2,3}Z",[trim]))),
<<"AZ">> = iolist_to_binary(join(re:split("AZ","A\\x0{2,3}Z",[{parts,
- 2}]))),
- <<"AZ">> = iolist_to_binary(join(re:split("AZ","A\\x0{2,3}Z",[]))),
- <<"AZ">> = iolist_to_binary(join(re:split("AZ","A\\x0{2,3}Z",[trim]))),
+ 2}]))),
+ <<"AZ">> = iolist_to_binary(join(re:split("AZ","A\\x0{2,3}Z",[]))),
+ <<"AZ">> = iolist_to_binary(join(re:split("AZ","A\\x0{2,3}Z",[trim]))),
<<"AZ">> = iolist_to_binary(join(re:split("AZ","A\\x0{2,3}Z",[{parts,
- 2}]))),
- <<"AZ">> = iolist_to_binary(join(re:split("AZ","A\\x0{2,3}Z",[]))),
- <<":cow:bell">> = iolist_to_binary(join(re:split("cowcowbell","^(cow|)\\1(bell)",[trim]))),
+ 2}]))),
+ <<"AZ">> = iolist_to_binary(join(re:split("AZ","A\\x0{2,3}Z",[]))),
+ <<":cow:bell">> = iolist_to_binary(join(re:split("cowcowbell","^(cow|)\\1(bell)",[trim]))),
<<":cow:bell:">> = iolist_to_binary(join(re:split("cowcowbell","^(cow|)\\1(bell)",[{parts,
- 2}]))),
- <<":cow:bell:">> = iolist_to_binary(join(re:split("cowcowbell","^(cow|)\\1(bell)",[]))),
- <<"::bell">> = iolist_to_binary(join(re:split("bell","^(cow|)\\1(bell)",[trim]))),
+ 2}]))),
+ <<":cow:bell:">> = iolist_to_binary(join(re:split("cowcowbell","^(cow|)\\1(bell)",[]))),
+ <<"::bell">> = iolist_to_binary(join(re:split("bell","^(cow|)\\1(bell)",[trim]))),
<<"::bell:">> = iolist_to_binary(join(re:split("bell","^(cow|)\\1(bell)",[{parts,
- 2}]))),
- <<"::bell:">> = iolist_to_binary(join(re:split("bell","^(cow|)\\1(bell)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(cow|)\\1(bell)",[trim]))),
+ 2}]))),
+ <<"::bell:">> = iolist_to_binary(join(re:split("bell","^(cow|)\\1(bell)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(cow|)\\1(bell)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(cow|)\\1(bell)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(cow|)\\1(bell)",[]))),
- <<"cowbell">> = iolist_to_binary(join(re:split("cowbell","^(cow|)\\1(bell)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(cow|)\\1(bell)",[]))),
+ <<"cowbell">> = iolist_to_binary(join(re:split("cowbell","^(cow|)\\1(bell)",[trim]))),
<<"cowbell">> = iolist_to_binary(join(re:split("cowbell","^(cow|)\\1(bell)",[{parts,
- 2}]))),
- <<"cowbell">> = iolist_to_binary(join(re:split("cowbell","^(cow|)\\1(bell)",[]))),
- <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[trim]))),
+ 2}]))),
+ <<"cowbell">> = iolist_to_binary(join(re:split("cowbell","^(cow|)\\1(bell)",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[trim]))),
<<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[{parts,
- 2}]))),
- <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[]))),
- <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[trim]))),
+ 2}]))),
+ <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[trim]))),
<<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[{parts,
- 2}]))),
- <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[]))),
+ 2}]))),
+ <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[]))),
<<":abc">> = iolist_to_binary(join(re:split("
-abc","^\\s",[trim]))),
+abc","^\\s",[trim]))),
<<":abc">> = iolist_to_binary(join(re:split("
-abc","^\\s",[{parts,2}]))),
+abc","^\\s",[{parts,2}]))),
<<":abc">> = iolist_to_binary(join(re:split("
-abc","^\\s",[]))),
- <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[trim]))),
+abc","^\\s",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[trim]))),
<<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[{parts,
- 2}]))),
- <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[]))),
- <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[trim]))),
+ 2}]))),
+ <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[trim]))),
<<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[{parts,
- 2}]))),
- <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\s",[trim]))),
+ 2}]))),
+ <<":abc">> = iolist_to_binary(join(re:split(" abc","^\\s",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\s",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\s",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\s",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^\\s",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\s",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^\\s",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","^\\s",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^\\s",[]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^\\s",[]))),
ok.
run4() ->
<<"">> = iolist_to_binary(join(re:split("abc","^a b
- c",[extended,trim]))),
+ c",[extended,trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","^a b
- c",[extended,{parts,2}]))),
+ c",[extended,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("abc","^a b
- c",[extended]))),
- <<":a">> = iolist_to_binary(join(re:split("ab","^(a|)\\1*b",[trim]))),
+ c",[extended]))),
+ <<":a">> = iolist_to_binary(join(re:split("ab","^(a|)\\1*b",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("ab","^(a|)\\1*b",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("ab","^(a|)\\1*b",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1*b",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("ab","^(a|)\\1*b",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1*b",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1*b",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1*b",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","^(a|)\\1*b",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1*b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","^(a|)\\1*b",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1*b",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1*b",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1*b",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1*b",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1*b",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1*b",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1*b",[]))),
- <<"acb">> = iolist_to_binary(join(re:split("acb","^(a|)\\1*b",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1*b",[]))),
+ <<"acb">> = iolist_to_binary(join(re:split("acb","^(a|)\\1*b",[trim]))),
<<"acb">> = iolist_to_binary(join(re:split("acb","^(a|)\\1*b",[{parts,
- 2}]))),
- <<"acb">> = iolist_to_binary(join(re:split("acb","^(a|)\\1*b",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aab","^(a|)\\1+b",[trim]))),
+ 2}]))),
+ <<"acb">> = iolist_to_binary(join(re:split("acb","^(a|)\\1*b",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aab","^(a|)\\1+b",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aab","^(a|)\\1+b",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aab","^(a|)\\1+b",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1+b",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aab","^(a|)\\1+b",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1+b",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1+b",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1+b",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","^(a|)\\1+b",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1+b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","^(a|)\\1+b",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1+b",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1+b",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1+b",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1+b",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1+b",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1+b",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1+b",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1+b",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1+b",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1+b",[trim]))),
<<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1+b",[{parts,
- 2}]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1+b",[]))),
- <<":a">> = iolist_to_binary(join(re:split("ab","^(a|)\\1?b",[trim]))),
+ 2}]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1+b",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("ab","^(a|)\\1?b",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("ab","^(a|)\\1?b",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("ab","^(a|)\\1?b",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aab","^(a|)\\1?b",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("ab","^(a|)\\1?b",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aab","^(a|)\\1?b",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aab","^(a|)\\1?b",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aab","^(a|)\\1?b",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","^(a|)\\1?b",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aab","^(a|)\\1?b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","^(a|)\\1?b",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1?b",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1?b",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1?b",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1?b",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1?b",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1?b",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1?b",[]))),
- <<"acb">> = iolist_to_binary(join(re:split("acb","^(a|)\\1?b",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1?b",[]))),
+ <<"acb">> = iolist_to_binary(join(re:split("acb","^(a|)\\1?b",[trim]))),
<<"acb">> = iolist_to_binary(join(re:split("acb","^(a|)\\1?b",[{parts,
- 2}]))),
- <<"acb">> = iolist_to_binary(join(re:split("acb","^(a|)\\1?b",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaab","^(a|)\\1{2}b",[trim]))),
+ 2}]))),
+ <<"acb">> = iolist_to_binary(join(re:split("acb","^(a|)\\1?b",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaab","^(a|)\\1{2}b",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaab","^(a|)\\1{2}b",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaab","^(a|)\\1{2}b",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","^(a|)\\1{2}b",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaab","^(a|)\\1{2}b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","^(a|)\\1{2}b",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1{2}b",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1{2}b",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1{2}b",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1{2}b",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1{2}b",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1{2}b",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1{2}b",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1{2}b",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1{2}b",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1{2}b",[trim]))),
<<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1{2}b",[{parts,
- 2}]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1{2}b",[]))),
- <<"aab">> = iolist_to_binary(join(re:split("aab","^(a|)\\1{2}b",[trim]))),
+ 2}]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1{2}b",[]))),
+ <<"aab">> = iolist_to_binary(join(re:split("aab","^(a|)\\1{2}b",[trim]))),
<<"aab">> = iolist_to_binary(join(re:split("aab","^(a|)\\1{2}b",[{parts,
- 2}]))),
- <<"aab">> = iolist_to_binary(join(re:split("aab","^(a|)\\1{2}b",[]))),
- <<"aaaab">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1{2}b",[trim]))),
+ 2}]))),
+ <<"aab">> = iolist_to_binary(join(re:split("aab","^(a|)\\1{2}b",[]))),
+ <<"aaaab">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1{2}b",[trim]))),
<<"aaaab">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1{2}b",[{parts,
- 2}]))),
- <<"aaaab">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1{2}b",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaab","^(a|)\\1{2,3}b",[trim]))),
+ 2}]))),
+ <<"aaaab">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1{2}b",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaab","^(a|)\\1{2,3}b",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaab","^(a|)\\1{2,3}b",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaab","^(a|)\\1{2,3}b",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1{2,3}b",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaab","^(a|)\\1{2,3}b",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1{2,3}b",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1{2,3}b",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1{2,3}b",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","^(a|)\\1{2,3}b",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaaab","^(a|)\\1{2,3}b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","^(a|)\\1{2,3}b",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1{2,3}b",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1{2,3}b",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1{2,3}b",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("b","^(a|)\\1{2,3}b",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1{2,3}b",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1{2,3}b",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1{2,3}b",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1{2,3}b",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a|)\\1{2,3}b",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1{2,3}b",[trim]))),
<<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1{2,3}b",[{parts,
- 2}]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1{2,3}b",[]))),
- <<"aab">> = iolist_to_binary(join(re:split("aab","^(a|)\\1{2,3}b",[trim]))),
+ 2}]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","^(a|)\\1{2,3}b",[]))),
+ <<"aab">> = iolist_to_binary(join(re:split("aab","^(a|)\\1{2,3}b",[trim]))),
<<"aab">> = iolist_to_binary(join(re:split("aab","^(a|)\\1{2,3}b",[{parts,
- 2}]))),
- <<"aab">> = iolist_to_binary(join(re:split("aab","^(a|)\\1{2,3}b",[]))),
- <<"aaaaab">> = iolist_to_binary(join(re:split("aaaaab","^(a|)\\1{2,3}b",[trim]))),
+ 2}]))),
+ <<"aab">> = iolist_to_binary(join(re:split("aab","^(a|)\\1{2,3}b",[]))),
+ <<"aaaaab">> = iolist_to_binary(join(re:split("aaaaab","^(a|)\\1{2,3}b",[trim]))),
<<"aaaaab">> = iolist_to_binary(join(re:split("aaaaab","^(a|)\\1{2,3}b",[{parts,
- 2}]))),
- <<"aaaaab">> = iolist_to_binary(join(re:split("aaaaab","^(a|)\\1{2,3}b",[]))),
- <<"">> = iolist_to_binary(join(re:split("abbbbc","ab{1,3}bc",[trim]))),
+ 2}]))),
+ <<"aaaaab">> = iolist_to_binary(join(re:split("aaaaab","^(a|)\\1{2,3}b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abbbbc","ab{1,3}bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abbbbc","ab{1,3}bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abbbbc","ab{1,3}bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abbbc","ab{1,3}bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abbbbc","ab{1,3}bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abbbc","ab{1,3}bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abbbc","ab{1,3}bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abbbc","ab{1,3}bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abbc","ab{1,3}bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abbbc","ab{1,3}bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abbc","ab{1,3}bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abbc","ab{1,3}bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abbc","ab{1,3}bc",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{1,3}bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abbc","ab{1,3}bc",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{1,3}bc",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{1,3}bc",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{1,3}bc",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","ab{1,3}bc",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{1,3}bc",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","ab{1,3}bc",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","ab{1,3}bc",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","ab{1,3}bc",[]))),
- <<"abbbbbc">> = iolist_to_binary(join(re:split("abbbbbc","ab{1,3}bc",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","ab{1,3}bc",[]))),
+ <<"abbbbbc">> = iolist_to_binary(join(re:split("abbbbbc","ab{1,3}bc",[trim]))),
<<"abbbbbc">> = iolist_to_binary(join(re:split("abbbbbc","ab{1,3}bc",[{parts,
- 2}]))),
- <<"abbbbbc">> = iolist_to_binary(join(re:split("abbbbbc","ab{1,3}bc",[]))),
- <<":track1:title:Blah blah blah">> = iolist_to_binary(join(re:split("track1.title:TBlah blah blah","([^.]*)\\.([^:]*):[T ]+(.*)",[trim]))),
+ 2}]))),
+ <<"abbbbbc">> = iolist_to_binary(join(re:split("abbbbbc","ab{1,3}bc",[]))),
+ <<":track1:title:Blah blah blah">> = iolist_to_binary(join(re:split("track1.title:TBlah blah blah","([^.]*)\\.([^:]*):[T ]+(.*)",[trim]))),
<<":track1:title:Blah blah blah:">> = iolist_to_binary(join(re:split("track1.title:TBlah blah blah","([^.]*)\\.([^:]*):[T ]+(.*)",[{parts,
- 2}]))),
- <<":track1:title:Blah blah blah:">> = iolist_to_binary(join(re:split("track1.title:TBlah blah blah","([^.]*)\\.([^:]*):[T ]+(.*)",[]))),
+ 2}]))),
+ <<":track1:title:Blah blah blah:">> = iolist_to_binary(join(re:split("track1.title:TBlah blah blah","([^.]*)\\.([^:]*):[T ]+(.*)",[]))),
<<":track1:title:Blah blah blah">> = iolist_to_binary(join(re:split("track1.title:TBlah blah blah","([^.]*)\\.([^:]*):[T ]+(.*)",[caseless,
- trim]))),
+ trim]))),
<<":track1:title:Blah blah blah:">> = iolist_to_binary(join(re:split("track1.title:TBlah blah blah","([^.]*)\\.([^:]*):[T ]+(.*)",[caseless,
{parts,
- 2}]))),
- <<":track1:title:Blah blah blah:">> = iolist_to_binary(join(re:split("track1.title:TBlah blah blah","([^.]*)\\.([^:]*):[T ]+(.*)",[caseless]))),
+ 2}]))),
+ <<":track1:title:Blah blah blah:">> = iolist_to_binary(join(re:split("track1.title:TBlah blah blah","([^.]*)\\.([^:]*):[T ]+(.*)",[caseless]))),
<<":track1:title:Blah blah blah">> = iolist_to_binary(join(re:split("track1.title:TBlah blah blah","([^.]*)\\.([^:]*):[t ]+(.*)",[caseless,
- trim]))),
+ trim]))),
<<":track1:title:Blah blah blah:">> = iolist_to_binary(join(re:split("track1.title:TBlah blah blah","([^.]*)\\.([^:]*):[t ]+(.*)",[caseless,
{parts,
- 2}]))),
- <<":track1:title:Blah blah blah:">> = iolist_to_binary(join(re:split("track1.title:TBlah blah blah","([^.]*)\\.([^:]*):[t ]+(.*)",[caseless]))),
- <<"">> = iolist_to_binary(join(re:split("WXY_^abc","^[W-c]+$",[trim]))),
+ 2}]))),
+ <<":track1:title:Blah blah blah:">> = iolist_to_binary(join(re:split("track1.title:TBlah blah blah","([^.]*)\\.([^:]*):[t ]+(.*)",[caseless]))),
+ <<"">> = iolist_to_binary(join(re:split("WXY_^abc","^[W-c]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("WXY_^abc","^[W-c]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("WXY_^abc","^[W-c]+$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-c]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("WXY_^abc","^[W-c]+$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-c]+$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-c]+$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-c]+$",[]))),
- <<"wxy">> = iolist_to_binary(join(re:split("wxy","^[W-c]+$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-c]+$",[]))),
+ <<"wxy">> = iolist_to_binary(join(re:split("wxy","^[W-c]+$",[trim]))),
<<"wxy">> = iolist_to_binary(join(re:split("wxy","^[W-c]+$",[{parts,
- 2}]))),
- <<"wxy">> = iolist_to_binary(join(re:split("wxy","^[W-c]+$",[]))),
+ 2}]))),
+ <<"wxy">> = iolist_to_binary(join(re:split("wxy","^[W-c]+$",[]))),
<<"">> = iolist_to_binary(join(re:split("WXY_^abc","^[W-c]+$",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("WXY_^abc","^[W-c]+$",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("WXY_^abc","^[W-c]+$",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("WXY_^abc","^[W-c]+$",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("wxy_^ABC","^[W-c]+$",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("wxy_^ABC","^[W-c]+$",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("wxy_^ABC","^[W-c]+$",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("wxy_^ABC","^[W-c]+$",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("WXY_^abc","^[\\x3f-\\x5F]+$",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("WXY_^abc","^[\\x3f-\\x5F]+$",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("WXY_^abc","^[\\x3f-\\x5F]+$",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("WXY_^abc","^[\\x3f-\\x5F]+$",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("wxy_^ABC","^[\\x3f-\\x5F]+$",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("wxy_^ABC","^[\\x3f-\\x5F]+$",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("wxy_^ABC","^[\\x3f-\\x5F]+$",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("wxy_^ABC","^[\\x3f-\\x5F]+$",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("abc","^abc$",[multiline,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","^abc$",[multiline,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","^abc$",[multiline]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","^abc$",[multiline]))),
<<"qqq
">> = iolist_to_binary(join(re:split("qqq
-abc","^abc$",[multiline,trim]))),
+abc","^abc$",[multiline,trim]))),
<<"qqq
:">> = iolist_to_binary(join(re:split("qqq
-abc","^abc$",[multiline,{parts,2}]))),
+abc","^abc$",[multiline,{parts,2}]))),
<<"qqq
:">> = iolist_to_binary(join(re:split("qqq
-abc","^abc$",[multiline]))),
+abc","^abc$",[multiline]))),
<<":
zzz">> = iolist_to_binary(join(re:split("abc
-zzz","^abc$",[multiline,trim]))),
+zzz","^abc$",[multiline,trim]))),
<<":
zzz">> = iolist_to_binary(join(re:split("abc
-zzz","^abc$",[multiline,{parts,2}]))),
+zzz","^abc$",[multiline,{parts,2}]))),
<<":
zzz">> = iolist_to_binary(join(re:split("abc
-zzz","^abc$",[multiline]))),
+zzz","^abc$",[multiline]))),
<<"qqq
:
zzz">> = iolist_to_binary(join(re:split("qqq
abc
-zzz","^abc$",[multiline,trim]))),
+zzz","^abc$",[multiline,trim]))),
<<"qqq
:
zzz">> = iolist_to_binary(join(re:split("qqq
abc
-zzz","^abc$",[multiline,{parts,2}]))),
+zzz","^abc$",[multiline,{parts,2}]))),
<<"qqq
:
zzz">> = iolist_to_binary(join(re:split("qqq
abc
-zzz","^abc$",[multiline]))),
- <<"">> = iolist_to_binary(join(re:split("abc","^abc$",[trim]))),
+zzz","^abc$",[multiline]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","^abc$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","^abc$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","^abc$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","^abc$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[]))),
<<"qqq
abc">> = iolist_to_binary(join(re:split("qqq
-abc","^abc$",[trim]))),
+abc","^abc$",[trim]))),
<<"qqq
abc">> = iolist_to_binary(join(re:split("qqq
-abc","^abc$",[{parts,2}]))),
+abc","^abc$",[{parts,2}]))),
<<"qqq
abc">> = iolist_to_binary(join(re:split("qqq
-abc","^abc$",[]))),
+abc","^abc$",[]))),
<<"abc
zzz">> = iolist_to_binary(join(re:split("abc
-zzz","^abc$",[trim]))),
+zzz","^abc$",[trim]))),
<<"abc
zzz">> = iolist_to_binary(join(re:split("abc
-zzz","^abc$",[{parts,2}]))),
+zzz","^abc$",[{parts,2}]))),
<<"abc
zzz">> = iolist_to_binary(join(re:split("abc
-zzz","^abc$",[]))),
+zzz","^abc$",[]))),
<<"qqq
abc
zzz">> = iolist_to_binary(join(re:split("qqq
abc
-zzz","^abc$",[trim]))),
+zzz","^abc$",[trim]))),
<<"qqq
abc
zzz">> = iolist_to_binary(join(re:split("qqq
abc
-zzz","^abc$",[{parts,2}]))),
+zzz","^abc$",[{parts,2}]))),
<<"qqq
abc
zzz">> = iolist_to_binary(join(re:split("qqq
abc
-zzz","^abc$",[]))),
+zzz","^abc$",[]))),
<<"">> = iolist_to_binary(join(re:split("abc","\\Aabc\\Z",[multiline,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","\\Aabc\\Z",[multiline,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","\\Aabc\\Z",[multiline]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","\\Aabc\\Z",[multiline]))),
<<"">> = iolist_to_binary(join(re:split("abc","\\Aabc\\Z",[multiline,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","\\Aabc\\Z",[multiline,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","\\Aabc\\Z",[multiline]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","\\Aabc\\Z",[multiline]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\Aabc\\Z",[multiline,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\Aabc\\Z",[multiline,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\Aabc\\Z",[multiline]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\Aabc\\Z",[multiline]))),
<<"qqq
abc">> = iolist_to_binary(join(re:split("qqq
-abc","\\Aabc\\Z",[multiline,trim]))),
+abc","\\Aabc\\Z",[multiline,trim]))),
<<"qqq
abc">> = iolist_to_binary(join(re:split("qqq
-abc","\\Aabc\\Z",[multiline,{parts,2}]))),
+abc","\\Aabc\\Z",[multiline,{parts,2}]))),
<<"qqq
abc">> = iolist_to_binary(join(re:split("qqq
-abc","\\Aabc\\Z",[multiline]))),
+abc","\\Aabc\\Z",[multiline]))),
<<"abc
zzz">> = iolist_to_binary(join(re:split("abc
-zzz","\\Aabc\\Z",[multiline,trim]))),
+zzz","\\Aabc\\Z",[multiline,trim]))),
<<"abc
zzz">> = iolist_to_binary(join(re:split("abc
-zzz","\\Aabc\\Z",[multiline,{parts,2}]))),
+zzz","\\Aabc\\Z",[multiline,{parts,2}]))),
<<"abc
zzz">> = iolist_to_binary(join(re:split("abc
-zzz","\\Aabc\\Z",[multiline]))),
+zzz","\\Aabc\\Z",[multiline]))),
<<"qqq
abc
zzz">> = iolist_to_binary(join(re:split("qqq
abc
-zzz","\\Aabc\\Z",[multiline,trim]))),
+zzz","\\Aabc\\Z",[multiline,trim]))),
<<"qqq
abc
zzz">> = iolist_to_binary(join(re:split("qqq
abc
-zzz","\\Aabc\\Z",[multiline,{parts,2}]))),
+zzz","\\Aabc\\Z",[multiline,{parts,2}]))),
<<"qqq
abc
zzz">> = iolist_to_binary(join(re:split("qqq
abc
-zzz","\\Aabc\\Z",[multiline]))),
+zzz","\\Aabc\\Z",[multiline]))),
<<":f">> = iolist_to_binary(join(re:split("abc
-def","\\A(.)*\\Z",[dotall,trim]))),
+def","\\A(.)*\\Z",[dotall,trim]))),
<<":f:">> = iolist_to_binary(join(re:split("abc
-def","\\A(.)*\\Z",[dotall,{parts,2}]))),
+def","\\A(.)*\\Z",[dotall,{parts,2}]))),
<<":f:">> = iolist_to_binary(join(re:split("abc
-def","\\A(.)*\\Z",[dotall]))),
+def","\\A(.)*\\Z",[dotall]))),
<<":s">> = iolist_to_binary(join(re:split("*** Failers","\\A(.)*\\Z",[multiline,
- trim]))),
+ trim]))),
<<":s:">> = iolist_to_binary(join(re:split("*** Failers","\\A(.)*\\Z",[multiline,
{parts,
- 2}]))),
- <<":s:">> = iolist_to_binary(join(re:split("*** Failers","\\A(.)*\\Z",[multiline]))),
+ 2}]))),
+ <<":s:">> = iolist_to_binary(join(re:split("*** Failers","\\A(.)*\\Z",[multiline]))),
<<"abc
def">> = iolist_to_binary(join(re:split("abc
-def","\\A(.)*\\Z",[multiline,trim]))),
+def","\\A(.)*\\Z",[multiline,trim]))),
<<"abc
def">> = iolist_to_binary(join(re:split("abc
-def","\\A(.)*\\Z",[multiline,{parts,2}]))),
+def","\\A(.)*\\Z",[multiline,{parts,2}]))),
<<"abc
def">> = iolist_to_binary(join(re:split("abc
-def","\\A(.)*\\Z",[multiline]))),
- <<"::c">> = iolist_to_binary(join(re:split("b::c","(?:b)|(?::+)",[trim]))),
+def","\\A(.)*\\Z",[multiline]))),
+ <<"::c">> = iolist_to_binary(join(re:split("b::c","(?:b)|(?::+)",[trim]))),
<<":::c">> = iolist_to_binary(join(re:split("b::c","(?:b)|(?::+)",[{parts,
- 2}]))),
- <<"::c">> = iolist_to_binary(join(re:split("b::c","(?:b)|(?::+)",[]))),
- <<"c">> = iolist_to_binary(join(re:split("c::b","(?:b)|(?::+)",[trim]))),
+ 2}]))),
+ <<"::c">> = iolist_to_binary(join(re:split("b::c","(?:b)|(?::+)",[]))),
+ <<"c">> = iolist_to_binary(join(re:split("c::b","(?:b)|(?::+)",[trim]))),
<<"c:b">> = iolist_to_binary(join(re:split("c::b","(?:b)|(?::+)",[{parts,
- 2}]))),
- <<"c::">> = iolist_to_binary(join(re:split("c::b","(?:b)|(?::+)",[]))),
- <<"">> = iolist_to_binary(join(re:split("az-","[-az]+",[trim]))),
+ 2}]))),
+ <<"c::">> = iolist_to_binary(join(re:split("c::b","(?:b)|(?::+)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("az-","[-az]+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("az-","[-az]+",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("az-","[-az]+",[]))),
- <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[-az]+",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("az-","[-az]+",[]))),
+ <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[-az]+",[trim]))),
<<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[-az]+",[{parts,
- 2}]))),
- <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[-az]+",[]))),
- <<"b">> = iolist_to_binary(join(re:split("b","[-az]+",[trim]))),
+ 2}]))),
+ <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[-az]+",[]))),
+ <<"b">> = iolist_to_binary(join(re:split("b","[-az]+",[trim]))),
<<"b">> = iolist_to_binary(join(re:split("b","[-az]+",[{parts,
- 2}]))),
- <<"b">> = iolist_to_binary(join(re:split("b","[-az]+",[]))),
+ 2}]))),
+ <<"b">> = iolist_to_binary(join(re:split("b","[-az]+",[]))),
ok.
run5() ->
- <<"">> = iolist_to_binary(join(re:split("za-","[az-]+",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("za-","[az-]+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("za-","[az-]+",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("za-","[az-]+",[]))),
- <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[az-]+",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("za-","[az-]+",[]))),
+ <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[az-]+",[trim]))),
<<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[az-]+",[{parts,
- 2}]))),
- <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[az-]+",[]))),
- <<"b">> = iolist_to_binary(join(re:split("b","[az-]+",[trim]))),
+ 2}]))),
+ <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[az-]+",[]))),
+ <<"b">> = iolist_to_binary(join(re:split("b","[az-]+",[trim]))),
<<"b">> = iolist_to_binary(join(re:split("b","[az-]+",[{parts,
- 2}]))),
- <<"b">> = iolist_to_binary(join(re:split("b","[az-]+",[]))),
- <<"">> = iolist_to_binary(join(re:split("a-z","[a\\-z]+",[trim]))),
+ 2}]))),
+ <<"b">> = iolist_to_binary(join(re:split("b","[az-]+",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a-z","[a\\-z]+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a-z","[a\\-z]+",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a-z","[a\\-z]+",[]))),
- <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[a\\-z]+",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a-z","[a\\-z]+",[]))),
+ <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[a\\-z]+",[trim]))),
<<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[a\\-z]+",[{parts,
- 2}]))),
- <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[a\\-z]+",[]))),
- <<"b">> = iolist_to_binary(join(re:split("b","[a\\-z]+",[trim]))),
+ 2}]))),
+ <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[a\\-z]+",[]))),
+ <<"b">> = iolist_to_binary(join(re:split("b","[a\\-z]+",[trim]))),
<<"b">> = iolist_to_binary(join(re:split("b","[a\\-z]+",[{parts,
- 2}]))),
- <<"b">> = iolist_to_binary(join(re:split("b","[a\\-z]+",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcdxyz","[a-z]+",[trim]))),
+ 2}]))),
+ <<"b">> = iolist_to_binary(join(re:split("b","[a\\-z]+",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcdxyz","[a-z]+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcdxyz","[a-z]+",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcdxyz","[a-z]+",[]))),
- <<"">> = iolist_to_binary(join(re:split("12-34","[\\d-]+",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcdxyz","[a-z]+",[]))),
+ <<"">> = iolist_to_binary(join(re:split("12-34","[\\d-]+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("12-34","[\\d-]+",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("12-34","[\\d-]+",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\d-]+",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("12-34","[\\d-]+",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\d-]+",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\d-]+",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\d-]+",[]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","[\\d-]+",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\d-]+",[]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","[\\d-]+",[trim]))),
<<"aaa">> = iolist_to_binary(join(re:split("aaa","[\\d-]+",[{parts,
- 2}]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","[\\d-]+",[]))),
- <<"">> = iolist_to_binary(join(re:split("12-34z","[\\d-z]+",[trim]))),
+ 2}]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","[\\d-]+",[]))),
+ <<"">> = iolist_to_binary(join(re:split("12-34z","[\\d-z]+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("12-34z","[\\d-z]+",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("12-34z","[\\d-z]+",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\d-z]+",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("12-34z","[\\d-z]+",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\d-z]+",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\d-z]+",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\d-z]+",[]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","[\\d-z]+",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\d-z]+",[]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","[\\d-z]+",[trim]))),
<<"aaa">> = iolist_to_binary(join(re:split("aaa","[\\d-z]+",[{parts,
- 2}]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","[\\d-z]+",[]))),
- <<": ">> = iolist_to_binary(join(re:split("\\ ","\\x5c",[trim]))),
+ 2}]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","[\\d-z]+",[]))),
+ <<": ">> = iolist_to_binary(join(re:split("\\ ","\\x5c",[trim]))),
<<": ">> = iolist_to_binary(join(re:split("\\ ","\\x5c",[{parts,
- 2}]))),
- <<": ">> = iolist_to_binary(join(re:split("\\ ","\\x5c",[]))),
- <<"the:oo">> = iolist_to_binary(join(re:split("the Zoo","\\x20Z",[trim]))),
+ 2}]))),
+ <<": ">> = iolist_to_binary(join(re:split("\\ ","\\x5c",[]))),
+ <<"the:oo">> = iolist_to_binary(join(re:split("the Zoo","\\x20Z",[trim]))),
<<"the:oo">> = iolist_to_binary(join(re:split("the Zoo","\\x20Z",[{parts,
- 2}]))),
- <<"the:oo">> = iolist_to_binary(join(re:split("the Zoo","\\x20Z",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\x20Z",[trim]))),
+ 2}]))),
+ <<"the:oo">> = iolist_to_binary(join(re:split("the Zoo","\\x20Z",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\x20Z",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\x20Z",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\x20Z",[]))),
- <<"Zulu">> = iolist_to_binary(join(re:split("Zulu","\\x20Z",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\x20Z",[]))),
+ <<"Zulu">> = iolist_to_binary(join(re:split("Zulu","\\x20Z",[trim]))),
<<"Zulu">> = iolist_to_binary(join(re:split("Zulu","\\x20Z",[{parts,
- 2}]))),
- <<"Zulu">> = iolist_to_binary(join(re:split("Zulu","\\x20Z",[]))),
+ 2}]))),
+ <<"Zulu">> = iolist_to_binary(join(re:split("Zulu","\\x20Z",[]))),
<<":abc">> = iolist_to_binary(join(re:split("abcabc","(abc)\\1",[caseless,
- trim]))),
+ trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abcabc","(abc)\\1",[caseless,
{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abcabc","(abc)\\1",[caseless]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abcabc","(abc)\\1",[caseless]))),
<<":ABC">> = iolist_to_binary(join(re:split("ABCabc","(abc)\\1",[caseless,
- trim]))),
+ trim]))),
<<":ABC:">> = iolist_to_binary(join(re:split("ABCabc","(abc)\\1",[caseless,
{parts,
- 2}]))),
- <<":ABC:">> = iolist_to_binary(join(re:split("ABCabc","(abc)\\1",[caseless]))),
+ 2}]))),
+ <<":ABC:">> = iolist_to_binary(join(re:split("ABCabc","(abc)\\1",[caseless]))),
<<":abc">> = iolist_to_binary(join(re:split("abcABC","(abc)\\1",[caseless,
- trim]))),
+ trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abcABC","(abc)\\1",[caseless,
{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abcABC","(abc)\\1",[caseless]))),
- <<"">> = iolist_to_binary(join(re:split("ab{3cd","ab{3cd",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abcABC","(abc)\\1",[caseless]))),
+ <<"">> = iolist_to_binary(join(re:split("ab{3cd","ab{3cd",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ab{3cd","ab{3cd",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab{3cd","ab{3cd",[]))),
- <<"">> = iolist_to_binary(join(re:split("ab{3,cd","ab{3,cd",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab{3cd","ab{3cd",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ab{3,cd","ab{3,cd",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ab{3,cd","ab{3,cd",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab{3,cd","ab{3,cd",[]))),
- <<"">> = iolist_to_binary(join(re:split("ab{3,4a}cd","ab{3,4a}cd",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab{3,cd","ab{3,cd",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ab{3,4a}cd","ab{3,4a}cd",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ab{3,4a}cd","ab{3,4a}cd",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab{3,4a}cd","ab{3,4a}cd",[]))),
- <<"">> = iolist_to_binary(join(re:split("{4,5a}bc","{4,5a}bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab{3,4a}cd","ab{3,4a}cd",[]))),
+ <<"">> = iolist_to_binary(join(re:split("{4,5a}bc","{4,5a}bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("{4,5a}bc","{4,5a}bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("{4,5a}bc","{4,5a}bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","abc$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("{4,5a}bc","{4,5a}bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","abc$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","abc$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","abc$",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","abc$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","abc$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","abc$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","abc$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","abc$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","abc$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc$",[]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc$",[]))),
<<"abc
def">> = iolist_to_binary(join(re:split("abc
-def","abc$",[trim]))),
+def","abc$",[trim]))),
<<"abc
def">> = iolist_to_binary(join(re:split("abc
-def","abc$",[{parts,2}]))),
+def","abc$",[{parts,2}]))),
<<"abc
def">> = iolist_to_binary(join(re:split("abc
-def","abc$",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abcS","(abc)\\123",[trim]))),
+def","abc$",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abcS","(abc)\\123",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abcS","(abc)\\123",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abcS","(abc)\\123",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abc“","(abc)\\223",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abcS","(abc)\\123",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abc“","(abc)\\223",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abc“","(abc)\\223",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abc“","(abc)\\223",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abcÓ","(abc)\\323",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abc“","(abc)\\223",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abcÓ","(abc)\\323",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abcÓ","(abc)\\323",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abcÓ","(abc)\\323",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abc@","(abc)\\100",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abcÓ","(abc)\\323",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abc@","(abc)\\100",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abc@","(abc)\\100",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abc@","(abc)\\100",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abc@","(abc)\\100",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abc@","(abc)\\100",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abc@","(abc)\\100",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abc@","(abc)\\100",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abc@","(abc)\\100",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abc@","(abc)\\100",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[]))),
- <<":A:B:C:D:E:F:G:H:I">> = iolist_to_binary(join(re:split("ABCDEFGHIHI","^(A)(B)(C)(D)(E)(F)(G)(H)(I)\\8\\9$",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1000",[]))),
+ <<":A:B:C:D:E:F:G:H:I">> = iolist_to_binary(join(re:split("ABCDEFGHIHI","^(A)(B)(C)(D)(E)(F)(G)(H)(I)\\8\\9$",[trim]))),
<<":A:B:C:D:E:F:G:H:I:">> = iolist_to_binary(join(re:split("ABCDEFGHIHI","^(A)(B)(C)(D)(E)(F)(G)(H)(I)\\8\\9$",[{parts,
- 2}]))),
- <<":A:B:C:D:E:F:G:H:I:">> = iolist_to_binary(join(re:split("ABCDEFGHIHI","^(A)(B)(C)(D)(E)(F)(G)(H)(I)\\8\\9$",[]))),
+ 2}]))),
+ <<":A:B:C:D:E:F:G:H:I:">> = iolist_to_binary(join(re:split("ABCDEFGHIHI","^(A)(B)(C)(D)(E)(F)(G)(H)(I)\\8\\9$",[]))),
ok.
run6() ->
- <<"">> = iolist_to_binary(join(re:split("A8B9C","^[A\\8B\\9C]+$",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("A8B9C","^[A\\8B\\9C]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("A8B9C","^[A\\8B\\9C]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("A8B9C","^[A\\8B\\9C]+$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[A\\8B\\9C]+$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("A8B9C","^[A\\8B\\9C]+$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[A\\8B\\9C]+$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[A\\8B\\9C]+$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[A\\8B\\9C]+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("A8B9C","^[A\\8B\\9C]+$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[A\\8B\\9C]+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("A8B9C","^[A\\8B\\9C]+$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("A8B9C","^[A\\8B\\9C]+$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("A8B9C","^[A\\8B\\9C]+$",[]))),
- <<":a:b:c:d:e:f:g:h:i:j:k:l">> = iolist_to_binary(join(re:split("abcdefghijkllS","(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)(l)\\12\\123",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("A8B9C","^[A\\8B\\9C]+$",[]))),
+ <<":a:b:c:d:e:f:g:h:i:j:k:l">> = iolist_to_binary(join(re:split("abcdefghijkllS","(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)(l)\\12\\123",[trim]))),
<<":a:b:c:d:e:f:g:h:i:j:k:l:">> = iolist_to_binary(join(re:split("abcdefghijkllS","(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)(l)\\12\\123",[{parts,
- 2}]))),
- <<":a:b:c:d:e:f:g:h:i:j:k:l:">> = iolist_to_binary(join(re:split("abcdefghijkllS","(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)(l)\\12\\123",[]))),
+ 2}]))),
+ <<":a:b:c:d:e:f:g:h:i:j:k:l:">> = iolist_to_binary(join(re:split("abcdefghijkllS","(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)(l)\\12\\123",[]))),
<<":a:b:c:d:e:f:g:h:i:j:k">> = iolist_to_binary(join(re:split("abcdefghijk
-S","(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\12\\123",[trim]))),
+S","(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\12\\123",[trim]))),
<<":a:b:c:d:e:f:g:h:i:j:k:">> = iolist_to_binary(join(re:split("abcdefghijk
-S","(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\12\\123",[{parts,2}]))),
+S","(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\12\\123",[{parts,2}]))),
<<":a:b:c:d:e:f:g:h:i:j:k:">> = iolist_to_binary(join(re:split("abcdefghijk
-S","(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\12\\123",[]))),
- <<"">> = iolist_to_binary(join(re:split("abidef","ab\\idef",[trim]))),
+S","(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\12\\123",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abidef","ab\\idef",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abidef","ab\\idef",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abidef","ab\\idef",[]))),
- <<"">> = iolist_to_binary(join(re:split("bc","a{0}bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abidef","ab\\idef",[]))),
+ <<"">> = iolist_to_binary(join(re:split("bc","a{0}bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("bc","a{0}bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("bc","a{0}bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("xyz","(a|(bc)){0,0}?xyz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("bc","a{0}bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("xyz","(a|(bc)){0,0}?xyz",[trim]))),
<<":::">> = iolist_to_binary(join(re:split("xyz","(a|(bc)){0,0}?xyz",[{parts,
- 2}]))),
- <<":::">> = iolist_to_binary(join(re:split("xyz","(a|(bc)){0,0}?xyz",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcde","abc[\\10]de",[trim]))),
+ 2}]))),
+ <<":::">> = iolist_to_binary(join(re:split("xyz","(a|(bc)){0,0}?xyz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcde","abc[\\10]de",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcde","abc[\\10]de",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcde","abc[\\10]de",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcde","abc[\\1]de",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcde","abc[\\10]de",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcde","abc[\\1]de",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcde","abc[\\1]de",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcde","abc[\\1]de",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abcde","(abc)[\\1]de",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcde","abc[\\1]de",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abcde","(abc)[\\1]de",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abcde","(abc)[\\1]de",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abcde","(abc)[\\1]de",[]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abcde","(abc)[\\1]de",[]))),
<<"">> = iolist_to_binary(join(re:split("a
-b","(?s)a.b",[trim]))),
+b","(?s)a.b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a
-b","(?s)a.b",[{parts,2}]))),
+b","(?s)a.b",[{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("a
-b","(?s)a.b",[]))),
- <<":b:a:NOT:cccc:d">> = iolist_to_binary(join(re:split("baNOTccccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
+b","(?s)a.b",[]))),
+ <<":b:a:NOT:cccc:d">> = iolist_to_binary(join(re:split("baNOTccccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
<<":b:a:NOT:cccc:d">> = iolist_to_binary(join(re:split("baNOTccccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[{parts,
- 2}]))),
- <<":b:a:NOT:cccc:d">> = iolist_to_binary(join(re:split("baNOTccccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
- <<":b:a:NOT:ccc:d">> = iolist_to_binary(join(re:split("baNOTcccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
+ 2}]))),
+ <<":b:a:NOT:cccc:d">> = iolist_to_binary(join(re:split("baNOTccccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
+ <<":b:a:NOT:ccc:d">> = iolist_to_binary(join(re:split("baNOTcccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
<<":b:a:NOT:ccc:d">> = iolist_to_binary(join(re:split("baNOTcccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[{parts,
- 2}]))),
- <<":b:a:NOT:ccc:d">> = iolist_to_binary(join(re:split("baNOTcccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
- <<":b:a:NO:Tcc:d">> = iolist_to_binary(join(re:split("baNOTccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
+ 2}]))),
+ <<":b:a:NOT:ccc:d">> = iolist_to_binary(join(re:split("baNOTcccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
+ <<":b:a:NO:Tcc:d">> = iolist_to_binary(join(re:split("baNOTccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
<<":b:a:NO:Tcc:d">> = iolist_to_binary(join(re:split("baNOTccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[{parts,
- 2}]))),
- <<":b:a:NO:Tcc:d">> = iolist_to_binary(join(re:split("baNOTccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
- <<":b:a::ccc:d">> = iolist_to_binary(join(re:split("bacccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
+ 2}]))),
+ <<":b:a:NO:Tcc:d">> = iolist_to_binary(join(re:split("baNOTccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
+ <<":b:a::ccc:d">> = iolist_to_binary(join(re:split("bacccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
<<":b:a::ccc:d">> = iolist_to_binary(join(re:split("bacccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[{parts,
- 2}]))),
- <<":b:a::ccc:d">> = iolist_to_binary(join(re:split("bacccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
- <<":*:*:* Fail:ers">> = iolist_to_binary(join(re:split("*** Failers","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
+ 2}]))),
+ <<":b:a::ccc:d">> = iolist_to_binary(join(re:split("bacccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
+ <<":*:*:* Fail:ers">> = iolist_to_binary(join(re:split("*** Failers","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
<<":*:*:* Fail:ers:">> = iolist_to_binary(join(re:split("*** Failers","^([^a])([^\\b])([^c]*)([^d]{3,4})",[{parts,
- 2}]))),
- <<":*:*:* Fail:ers:">> = iolist_to_binary(join(re:split("*** Failers","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
- <<"anything">> = iolist_to_binary(join(re:split("anything","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
+ 2}]))),
+ <<":*:*:* Fail:ers:">> = iolist_to_binary(join(re:split("*** Failers","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
+ <<"anything">> = iolist_to_binary(join(re:split("anything","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
<<"anything">> = iolist_to_binary(join(re:split("anything","^([^a])([^\\b])([^c]*)([^d]{3,4})",[{parts,
- 2}]))),
- <<"anything">> = iolist_to_binary(join(re:split("anything","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
- <<"bc">> = iolist_to_binary(join(re:split("bc","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
+ 2}]))),
+ <<"anything">> = iolist_to_binary(join(re:split("anything","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
+ <<"bc">> = iolist_to_binary(join(re:split("bc","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
<<"bc">> = iolist_to_binary(join(re:split("bc","^([^a])([^\\b])([^c]*)([^d]{3,4})",[{parts,
- 2}]))),
- <<"bc">> = iolist_to_binary(join(re:split("bc","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
- <<"baccd">> = iolist_to_binary(join(re:split("baccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
+ 2}]))),
+ <<"bc">> = iolist_to_binary(join(re:split("bc","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
+ <<"baccd">> = iolist_to_binary(join(re:split("baccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[trim]))),
<<"baccd">> = iolist_to_binary(join(re:split("baccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[{parts,
- 2}]))),
- <<"baccd">> = iolist_to_binary(join(re:split("baccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
- <<"">> = iolist_to_binary(join(re:split("Abc","[^a]",[trim]))),
+ 2}]))),
+ <<"baccd">> = iolist_to_binary(join(re:split("baccd","^([^a])([^\\b])([^c]*)([^d]{3,4})",[]))),
+ <<"">> = iolist_to_binary(join(re:split("Abc","[^a]",[trim]))),
<<":bc">> = iolist_to_binary(join(re:split("Abc","[^a]",[{parts,
- 2}]))),
- <<":::">> = iolist_to_binary(join(re:split("Abc","[^a]",[]))),
+ 2}]))),
+ <<":::">> = iolist_to_binary(join(re:split("Abc","[^a]",[]))),
<<"A">> = iolist_to_binary(join(re:split("Abc","[^a]",[caseless,
- trim]))),
+ trim]))),
<<"A:c">> = iolist_to_binary(join(re:split("Abc","[^a]",[caseless,
{parts,
- 2}]))),
- <<"A::">> = iolist_to_binary(join(re:split("Abc","[^a]",[caseless]))),
- <<":a">> = iolist_to_binary(join(re:split("AAAaAbc","[^a]+",[trim]))),
+ 2}]))),
+ <<"A::">> = iolist_to_binary(join(re:split("Abc","[^a]",[caseless]))),
+ <<":a">> = iolist_to_binary(join(re:split("AAAaAbc","[^a]+",[trim]))),
<<":aAbc">> = iolist_to_binary(join(re:split("AAAaAbc","[^a]+",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("AAAaAbc","[^a]+",[]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("AAAaAbc","[^a]+",[]))),
<<"AAAaA">> = iolist_to_binary(join(re:split("AAAaAbc","[^a]+",[caseless,
- trim]))),
+ trim]))),
<<"AAAaA:">> = iolist_to_binary(join(re:split("AAAaAbc","[^a]+",[caseless,
{parts,
- 2}]))),
- <<"AAAaA:">> = iolist_to_binary(join(re:split("AAAaAbc","[^a]+",[caseless]))),
+ 2}]))),
+ <<"AAAaA:">> = iolist_to_binary(join(re:split("AAAaAbc","[^a]+",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("bbb
-ccc","[^a]+",[trim]))),
+ccc","[^a]+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("bbb
-ccc","[^a]+",[{parts,2}]))),
+ccc","[^a]+",[{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("bbb
-ccc","[^a]+",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("abc","[^k]$",[trim]))),
+ccc","[^a]+",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("abc","[^k]$",[trim]))),
<<"ab:">> = iolist_to_binary(join(re:split("abc","[^k]$",[{parts,
- 2}]))),
- <<"ab:">> = iolist_to_binary(join(re:split("abc","[^k]$",[]))),
- <<"*** Failer">> = iolist_to_binary(join(re:split("*** Failers","[^k]$",[trim]))),
+ 2}]))),
+ <<"ab:">> = iolist_to_binary(join(re:split("abc","[^k]$",[]))),
+ <<"*** Failer">> = iolist_to_binary(join(re:split("*** Failers","[^k]$",[trim]))),
<<"*** Failer:">> = iolist_to_binary(join(re:split("*** Failers","[^k]$",[{parts,
- 2}]))),
- <<"*** Failer:">> = iolist_to_binary(join(re:split("*** Failers","[^k]$",[]))),
- <<"abk">> = iolist_to_binary(join(re:split("abk","[^k]$",[trim]))),
+ 2}]))),
+ <<"*** Failer:">> = iolist_to_binary(join(re:split("*** Failers","[^k]$",[]))),
+ <<"abk">> = iolist_to_binary(join(re:split("abk","[^k]$",[trim]))),
<<"abk">> = iolist_to_binary(join(re:split("abk","[^k]$",[{parts,
- 2}]))),
- <<"abk">> = iolist_to_binary(join(re:split("abk","[^k]$",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","[^k]{2,3}$",[trim]))),
+ 2}]))),
+ <<"abk">> = iolist_to_binary(join(re:split("abk","[^k]$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","[^k]{2,3}$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","[^k]{2,3}$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","[^k]{2,3}$",[]))),
- <<"k">> = iolist_to_binary(join(re:split("kbc","[^k]{2,3}$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","[^k]{2,3}$",[]))),
+ <<"k">> = iolist_to_binary(join(re:split("kbc","[^k]{2,3}$",[trim]))),
<<"k:">> = iolist_to_binary(join(re:split("kbc","[^k]{2,3}$",[{parts,
- 2}]))),
- <<"k:">> = iolist_to_binary(join(re:split("kbc","[^k]{2,3}$",[]))),
- <<"k">> = iolist_to_binary(join(re:split("kabc","[^k]{2,3}$",[trim]))),
+ 2}]))),
+ <<"k:">> = iolist_to_binary(join(re:split("kbc","[^k]{2,3}$",[]))),
+ <<"k">> = iolist_to_binary(join(re:split("kabc","[^k]{2,3}$",[trim]))),
<<"k:">> = iolist_to_binary(join(re:split("kabc","[^k]{2,3}$",[{parts,
- 2}]))),
- <<"k:">> = iolist_to_binary(join(re:split("kabc","[^k]{2,3}$",[]))),
- <<"*** Fail">> = iolist_to_binary(join(re:split("*** Failers","[^k]{2,3}$",[trim]))),
+ 2}]))),
+ <<"k:">> = iolist_to_binary(join(re:split("kabc","[^k]{2,3}$",[]))),
+ <<"*** Fail">> = iolist_to_binary(join(re:split("*** Failers","[^k]{2,3}$",[trim]))),
<<"*** Fail:">> = iolist_to_binary(join(re:split("*** Failers","[^k]{2,3}$",[{parts,
- 2}]))),
- <<"*** Fail:">> = iolist_to_binary(join(re:split("*** Failers","[^k]{2,3}$",[]))),
- <<"abk">> = iolist_to_binary(join(re:split("abk","[^k]{2,3}$",[trim]))),
+ 2}]))),
+ <<"*** Fail:">> = iolist_to_binary(join(re:split("*** Failers","[^k]{2,3}$",[]))),
+ <<"abk">> = iolist_to_binary(join(re:split("abk","[^k]{2,3}$",[trim]))),
<<"abk">> = iolist_to_binary(join(re:split("abk","[^k]{2,3}$",[{parts,
- 2}]))),
- <<"abk">> = iolist_to_binary(join(re:split("abk","[^k]{2,3}$",[]))),
- <<"akb">> = iolist_to_binary(join(re:split("akb","[^k]{2,3}$",[trim]))),
+ 2}]))),
+ <<"abk">> = iolist_to_binary(join(re:split("abk","[^k]{2,3}$",[]))),
+ <<"akb">> = iolist_to_binary(join(re:split("akb","[^k]{2,3}$",[trim]))),
<<"akb">> = iolist_to_binary(join(re:split("akb","[^k]{2,3}$",[{parts,
- 2}]))),
- <<"akb">> = iolist_to_binary(join(re:split("akb","[^k]{2,3}$",[]))),
- <<"akk">> = iolist_to_binary(join(re:split("akk","[^k]{2,3}$",[trim]))),
+ 2}]))),
+ <<"akb">> = iolist_to_binary(join(re:split("akb","[^k]{2,3}$",[]))),
+ <<"akk">> = iolist_to_binary(join(re:split("akk","[^k]{2,3}$",[trim]))),
<<"akk">> = iolist_to_binary(join(re:split("akk","[^k]{2,3}$",[{parts,
- 2}]))),
- <<"akk">> = iolist_to_binary(join(re:split("akk","[^k]{2,3}$",[]))),
- <<"12345678.b.c.d">> = iolist_to_binary(join(re:split("12345678.b.c.d","^\\d{8,}\\@.+[^k]$",[trim]))),
+ 2}]))),
+ <<"akk">> = iolist_to_binary(join(re:split("akk","[^k]{2,3}$",[]))),
+ <<"12345678.b.c.d">> = iolist_to_binary(join(re:split("12345678.b.c.d","^\\d{8,}\\@.+[^k]$",[trim]))),
<<"12345678.b.c.d">> = iolist_to_binary(join(re:split("12345678.b.c.d","^\\d{8,}\\@.+[^k]$",[{parts,
- 2}]))),
- <<"12345678.b.c.d">> = iolist_to_binary(join(re:split("12345678.b.c.d","^\\d{8,}\\@.+[^k]$",[]))),
- <<"123456789.y.z">> = iolist_to_binary(join(re:split("123456789.y.z","^\\d{8,}\\@.+[^k]$",[trim]))),
+ 2}]))),
+ <<"12345678.b.c.d">> = iolist_to_binary(join(re:split("12345678.b.c.d","^\\d{8,}\\@.+[^k]$",[]))),
+ <<"123456789.y.z">> = iolist_to_binary(join(re:split("123456789.y.z","^\\d{8,}\\@.+[^k]$",[trim]))),
<<"123456789.y.z">> = iolist_to_binary(join(re:split("123456789.y.z","^\\d{8,}\\@.+[^k]$",[{parts,
- 2}]))),
- <<"123456789.y.z">> = iolist_to_binary(join(re:split("123456789.y.z","^\\d{8,}\\@.+[^k]$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\d{8,}\\@.+[^k]$",[trim]))),
+ 2}]))),
+ <<"123456789.y.z">> = iolist_to_binary(join(re:split("123456789.y.z","^\\d{8,}\\@.+[^k]$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\d{8,}\\@.+[^k]$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\d{8,}\\@.+[^k]$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\d{8,}\\@.+[^k]$",[]))),
- <<"12345678.y.uk">> = iolist_to_binary(join(re:split("12345678.y.uk","^\\d{8,}\\@.+[^k]$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\d{8,}\\@.+[^k]$",[]))),
+ <<"12345678.y.uk">> = iolist_to_binary(join(re:split("12345678.y.uk","^\\d{8,}\\@.+[^k]$",[trim]))),
<<"12345678.y.uk">> = iolist_to_binary(join(re:split("12345678.y.uk","^\\d{8,}\\@.+[^k]$",[{parts,
- 2}]))),
- <<"12345678.y.uk">> = iolist_to_binary(join(re:split("12345678.y.uk","^\\d{8,}\\@.+[^k]$",[]))),
- <<"1234567.b.c.d">> = iolist_to_binary(join(re:split("1234567.b.c.d","^\\d{8,}\\@.+[^k]$",[trim]))),
+ 2}]))),
+ <<"12345678.y.uk">> = iolist_to_binary(join(re:split("12345678.y.uk","^\\d{8,}\\@.+[^k]$",[]))),
+ <<"1234567.b.c.d">> = iolist_to_binary(join(re:split("1234567.b.c.d","^\\d{8,}\\@.+[^k]$",[trim]))),
<<"1234567.b.c.d">> = iolist_to_binary(join(re:split("1234567.b.c.d","^\\d{8,}\\@.+[^k]$",[{parts,
- 2}]))),
- <<"1234567.b.c.d">> = iolist_to_binary(join(re:split("1234567.b.c.d","^\\d{8,}\\@.+[^k]$",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaaaaaaaa","(a)\\1{8,}",[trim]))),
+ 2}]))),
+ <<"1234567.b.c.d">> = iolist_to_binary(join(re:split("1234567.b.c.d","^\\d{8,}\\@.+[^k]$",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaaaaaaa","(a)\\1{8,}",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaaaaaaaa","(a)\\1{8,}",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaaaaaaaa","(a)\\1{8,}",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaaaaaaaaa","(a)\\1{8,}",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaaaaaaaa","(a)\\1{8,}",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaaaaaaaa","(a)\\1{8,}",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","(a)\\1{8,}",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","(a)\\1{8,}",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a)\\1{8,}",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","(a)\\1{8,}",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a)\\1{8,}",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a)\\1{8,}",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a)\\1{8,}",[]))),
- <<"aaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaa","(a)\\1{8,}",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a)\\1{8,}",[]))),
+ <<"aaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaa","(a)\\1{8,}",[trim]))),
<<"aaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaa","(a)\\1{8,}",[{parts,
- 2}]))),
- <<"aaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaa","(a)\\1{8,}",[]))),
+ 2}]))),
+ <<"aaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaa","(a)\\1{8,}",[]))),
ok.
run7() ->
- <<"aaaa">> = iolist_to_binary(join(re:split("aaaabcd","[^a]",[trim]))),
+ <<"aaaa">> = iolist_to_binary(join(re:split("aaaabcd","[^a]",[trim]))),
<<"aaaa:cd">> = iolist_to_binary(join(re:split("aaaabcd","[^a]",[{parts,
- 2}]))),
- <<"aaaa:::">> = iolist_to_binary(join(re:split("aaaabcd","[^a]",[]))),
- <<"aa:a">> = iolist_to_binary(join(re:split("aaAabcd","[^a]",[trim]))),
+ 2}]))),
+ <<"aaaa:::">> = iolist_to_binary(join(re:split("aaaabcd","[^a]",[]))),
+ <<"aa:a">> = iolist_to_binary(join(re:split("aaAabcd","[^a]",[trim]))),
<<"aa:abcd">> = iolist_to_binary(join(re:split("aaAabcd","[^a]",[{parts,
- 2}]))),
- <<"aa:a:::">> = iolist_to_binary(join(re:split("aaAabcd","[^a]",[]))),
+ 2}]))),
+ <<"aa:a:::">> = iolist_to_binary(join(re:split("aaAabcd","[^a]",[]))),
<<"aaaa">> = iolist_to_binary(join(re:split("aaaabcd","[^a]",[caseless,
- trim]))),
+ trim]))),
<<"aaaa:cd">> = iolist_to_binary(join(re:split("aaaabcd","[^a]",[caseless,
{parts,
- 2}]))),
- <<"aaaa:::">> = iolist_to_binary(join(re:split("aaaabcd","[^a]",[caseless]))),
+ 2}]))),
+ <<"aaaa:::">> = iolist_to_binary(join(re:split("aaaabcd","[^a]",[caseless]))),
<<"aaAa">> = iolist_to_binary(join(re:split("aaAabcd","[^a]",[caseless,
- trim]))),
+ trim]))),
<<"aaAa:cd">> = iolist_to_binary(join(re:split("aaAabcd","[^a]",[caseless,
{parts,
- 2}]))),
- <<"aaAa:::">> = iolist_to_binary(join(re:split("aaAabcd","[^a]",[caseless]))),
- <<"aaaa">> = iolist_to_binary(join(re:split("aaaabcd","[^az]",[trim]))),
+ 2}]))),
+ <<"aaAa:::">> = iolist_to_binary(join(re:split("aaAabcd","[^a]",[caseless]))),
+ <<"aaaa">> = iolist_to_binary(join(re:split("aaaabcd","[^az]",[trim]))),
<<"aaaa:cd">> = iolist_to_binary(join(re:split("aaaabcd","[^az]",[{parts,
- 2}]))),
- <<"aaaa:::">> = iolist_to_binary(join(re:split("aaaabcd","[^az]",[]))),
- <<"aa:a">> = iolist_to_binary(join(re:split("aaAabcd","[^az]",[trim]))),
+ 2}]))),
+ <<"aaaa:::">> = iolist_to_binary(join(re:split("aaaabcd","[^az]",[]))),
+ <<"aa:a">> = iolist_to_binary(join(re:split("aaAabcd","[^az]",[trim]))),
<<"aa:abcd">> = iolist_to_binary(join(re:split("aaAabcd","[^az]",[{parts,
- 2}]))),
- <<"aa:a:::">> = iolist_to_binary(join(re:split("aaAabcd","[^az]",[]))),
+ 2}]))),
+ <<"aa:a:::">> = iolist_to_binary(join(re:split("aaAabcd","[^az]",[]))),
<<"aaaa">> = iolist_to_binary(join(re:split("aaaabcd","[^az]",[caseless,
- trim]))),
+ trim]))),
<<"aaaa:cd">> = iolist_to_binary(join(re:split("aaaabcd","[^az]",[caseless,
{parts,
- 2}]))),
- <<"aaaa:::">> = iolist_to_binary(join(re:split("aaaabcd","[^az]",[caseless]))),
+ 2}]))),
+ <<"aaaa:::">> = iolist_to_binary(join(re:split("aaaabcd","[^az]",[caseless]))),
<<"aaAa">> = iolist_to_binary(join(re:split("aaAabcd","[^az]",[caseless,
- trim]))),
+ trim]))),
<<"aaAa:cd">> = iolist_to_binary(join(re:split("aaAabcd","[^az]",[caseless,
{parts,
- 2}]))),
- <<"aaAa:::">> = iolist_to_binary(join(re:split("aaAabcd","[^az]",[caseless]))),
- <<"xxxxxxxxxxx:xxxxxxxxx">> = iolist_to_binary(join(re:split("xxxxxxxxxxxPSTAIREISLLxxxxxxxxx","P[^*]TAIRE[^*]{1,6}?LL",[trim]))),
+ 2}]))),
+ <<"aaAa:::">> = iolist_to_binary(join(re:split("aaAabcd","[^az]",[caseless]))),
+ <<"xxxxxxxxxxx:xxxxxxxxx">> = iolist_to_binary(join(re:split("xxxxxxxxxxxPSTAIREISLLxxxxxxxxx","P[^*]TAIRE[^*]{1,6}?LL",[trim]))),
<<"xxxxxxxxxxx:xxxxxxxxx">> = iolist_to_binary(join(re:split("xxxxxxxxxxxPSTAIREISLLxxxxxxxxx","P[^*]TAIRE[^*]{1,6}?LL",[{parts,
- 2}]))),
- <<"xxxxxxxxxxx:xxxxxxxxx">> = iolist_to_binary(join(re:split("xxxxxxxxxxxPSTAIREISLLxxxxxxxxx","P[^*]TAIRE[^*]{1,6}?LL",[]))),
- <<"xxxxxxxxxxx:xxxxxxxxx">> = iolist_to_binary(join(re:split("xxxxxxxxxxxPSTAIREISLLxxxxxxxxx","P[^*]TAIRE[^*]{1,}?LL",[trim]))),
+ 2}]))),
+ <<"xxxxxxxxxxx:xxxxxxxxx">> = iolist_to_binary(join(re:split("xxxxxxxxxxxPSTAIREISLLxxxxxxxxx","P[^*]TAIRE[^*]{1,6}?LL",[]))),
+ <<"xxxxxxxxxxx:xxxxxxxxx">> = iolist_to_binary(join(re:split("xxxxxxxxxxxPSTAIREISLLxxxxxxxxx","P[^*]TAIRE[^*]{1,}?LL",[trim]))),
<<"xxxxxxxxxxx:xxxxxxxxx">> = iolist_to_binary(join(re:split("xxxxxxxxxxxPSTAIREISLLxxxxxxxxx","P[^*]TAIRE[^*]{1,}?LL",[{parts,
- 2}]))),
- <<"xxxxxxxxxxx:xxxxxxxxx">> = iolist_to_binary(join(re:split("xxxxxxxxxxxPSTAIREISLLxxxxxxxxx","P[^*]TAIRE[^*]{1,}?LL",[]))),
- <<"1:.23">> = iolist_to_binary(join(re:split("1.230003938","(\\.\\d\\d[1-9]?)\\d+",[trim]))),
+ 2}]))),
+ <<"xxxxxxxxxxx:xxxxxxxxx">> = iolist_to_binary(join(re:split("xxxxxxxxxxxPSTAIREISLLxxxxxxxxx","P[^*]TAIRE[^*]{1,}?LL",[]))),
+ <<"1:.23">> = iolist_to_binary(join(re:split("1.230003938","(\\.\\d\\d[1-9]?)\\d+",[trim]))),
<<"1:.23:">> = iolist_to_binary(join(re:split("1.230003938","(\\.\\d\\d[1-9]?)\\d+",[{parts,
- 2}]))),
- <<"1:.23:">> = iolist_to_binary(join(re:split("1.230003938","(\\.\\d\\d[1-9]?)\\d+",[]))),
- <<"1:.875">> = iolist_to_binary(join(re:split("1.875000282","(\\.\\d\\d[1-9]?)\\d+",[trim]))),
+ 2}]))),
+ <<"1:.23:">> = iolist_to_binary(join(re:split("1.230003938","(\\.\\d\\d[1-9]?)\\d+",[]))),
+ <<"1:.875">> = iolist_to_binary(join(re:split("1.875000282","(\\.\\d\\d[1-9]?)\\d+",[trim]))),
<<"1:.875:">> = iolist_to_binary(join(re:split("1.875000282","(\\.\\d\\d[1-9]?)\\d+",[{parts,
- 2}]))),
- <<"1:.875:">> = iolist_to_binary(join(re:split("1.875000282","(\\.\\d\\d[1-9]?)\\d+",[]))),
- <<"1:.23">> = iolist_to_binary(join(re:split("1.235","(\\.\\d\\d[1-9]?)\\d+",[trim]))),
+ 2}]))),
+ <<"1:.875:">> = iolist_to_binary(join(re:split("1.875000282","(\\.\\d\\d[1-9]?)\\d+",[]))),
+ <<"1:.23">> = iolist_to_binary(join(re:split("1.235","(\\.\\d\\d[1-9]?)\\d+",[trim]))),
<<"1:.23:">> = iolist_to_binary(join(re:split("1.235","(\\.\\d\\d[1-9]?)\\d+",[{parts,
- 2}]))),
- <<"1:.23:">> = iolist_to_binary(join(re:split("1.235","(\\.\\d\\d[1-9]?)\\d+",[]))),
- <<"1:.23::0003938">> = iolist_to_binary(join(re:split("1.230003938","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[trim]))),
+ 2}]))),
+ <<"1:.23:">> = iolist_to_binary(join(re:split("1.235","(\\.\\d\\d[1-9]?)\\d+",[]))),
+ <<"1:.23::0003938">> = iolist_to_binary(join(re:split("1.230003938","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[trim]))),
<<"1:.23::0003938">> = iolist_to_binary(join(re:split("1.230003938","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[{parts,
- 2}]))),
- <<"1:.23::0003938">> = iolist_to_binary(join(re:split("1.230003938","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[]))),
- <<"1:.875:5:000282">> = iolist_to_binary(join(re:split("1.875000282","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[trim]))),
+ 2}]))),
+ <<"1:.23::0003938">> = iolist_to_binary(join(re:split("1.230003938","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[]))),
+ <<"1:.875:5:000282">> = iolist_to_binary(join(re:split("1.875000282","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[trim]))),
<<"1:.875:5:000282">> = iolist_to_binary(join(re:split("1.875000282","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[{parts,
- 2}]))),
- <<"1:.875:5:000282">> = iolist_to_binary(join(re:split("1.875000282","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[trim]))),
+ 2}]))),
+ <<"1:.875:5:000282">> = iolist_to_binary(join(re:split("1.875000282","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[]))),
- <<"1.235">> = iolist_to_binary(join(re:split("1.235","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[]))),
+ <<"1.235">> = iolist_to_binary(join(re:split("1.235","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[trim]))),
<<"1.235">> = iolist_to_binary(join(re:split("1.235","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[{parts,
- 2}]))),
- <<"1.235">> = iolist_to_binary(join(re:split("1.235","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[]))),
- <<"">> = iolist_to_binary(join(re:split("ab","a(?)b",[trim]))),
+ 2}]))),
+ <<"1.235">> = iolist_to_binary(join(re:split("1.235","(\\.\\d\\d((?=0)|\\d(?=\\d)))",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ab","a(?)b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ab","a(?)b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab","a(?)b",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab","a(?)b",[]))),
<<"Food is on the :foo:table">> = iolist_to_binary(join(re:split("Food is on the foo table","\\b(foo)\\s+(\\w+)",[caseless,
- trim]))),
+ trim]))),
<<"Food is on the :foo:table:">> = iolist_to_binary(join(re:split("Food is on the foo table","\\b(foo)\\s+(\\w+)",[caseless,
{parts,
- 2}]))),
- <<"Food is on the :foo:table:">> = iolist_to_binary(join(re:split("Food is on the foo table","\\b(foo)\\s+(\\w+)",[caseless]))),
- <<"The :d is under the bar in the :n.">> = iolist_to_binary(join(re:split("The food is under the bar in the barn.","foo(.*)bar",[trim]))),
+ 2}]))),
+ <<"Food is on the :foo:table:">> = iolist_to_binary(join(re:split("Food is on the foo table","\\b(foo)\\s+(\\w+)",[caseless]))),
+ <<"The :d is under the bar in the :n.">> = iolist_to_binary(join(re:split("The food is under the bar in the barn.","foo(.*)bar",[trim]))),
<<"The :d is under the bar in the :n.">> = iolist_to_binary(join(re:split("The food is under the bar in the barn.","foo(.*)bar",[{parts,
- 2}]))),
- <<"The :d is under the bar in the :n.">> = iolist_to_binary(join(re:split("The food is under the bar in the barn.","foo(.*)bar",[]))),
- <<"The :d is under the : in the barn.">> = iolist_to_binary(join(re:split("The food is under the bar in the barn.","foo(.*?)bar",[trim]))),
+ 2}]))),
+ <<"The :d is under the bar in the :n.">> = iolist_to_binary(join(re:split("The food is under the bar in the barn.","foo(.*)bar",[]))),
+ <<"The :d is under the : in the barn.">> = iolist_to_binary(join(re:split("The food is under the bar in the barn.","foo(.*?)bar",[trim]))),
<<"The :d is under the : in the barn.">> = iolist_to_binary(join(re:split("The food is under the bar in the barn.","foo(.*?)bar",[{parts,
- 2}]))),
- <<"The :d is under the : in the barn.">> = iolist_to_binary(join(re:split("The food is under the bar in the barn.","foo(.*?)bar",[]))),
- <<":I have 2 numbers: 53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d*)",[trim]))),
+ 2}]))),
+ <<"The :d is under the : in the barn.">> = iolist_to_binary(join(re:split("The food is under the bar in the barn.","foo(.*?)bar",[]))),
+ <<":I have 2 numbers: 53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d*)",[trim]))),
<<":I have 2 numbers: 53147::">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d*)",[{parts,
- 2}]))),
- <<":I have 2 numbers: 53147::">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d*)",[]))),
- <<":I have 2 numbers: 5314:7">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d+)",[trim]))),
+ 2}]))),
+ <<":I have 2 numbers: 53147::">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d*)",[]))),
+ <<":I have 2 numbers: 5314:7">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d+)",[trim]))),
<<":I have 2 numbers: 5314:7:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d+)",[{parts,
- 2}]))),
- <<":I have 2 numbers: 5314:7:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d+)",[]))),
- <<":I::: :::h:::a:::v:::e::: :2:: :::n:::u:::m:::b:::e:::r:::s::::::: :53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d*)",[trim]))),
+ 2}]))),
+ <<":I have 2 numbers: 5314:7:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d+)",[]))),
+ <<":I::: :::h:::a:::v:::e::: :2:: :::n:::u:::m:::b:::e:::r:::s::::::: :53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d*)",[trim]))),
<<":I:: have 2 numbers: 53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d*)",[{parts,
- 2}]))),
- <<":I::: :::h:::a:::v:::e::: :2:: :::n:::u:::m:::b:::e:::r:::s::::::: :53147:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d*)",[]))),
- <<":I have :2:: numbers: :53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d+)",[trim]))),
+ 2}]))),
+ <<":I::: :::h:::a:::v:::e::: :2:: :::n:::u:::m:::b:::e:::r:::s::::::: :53147:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d*)",[]))),
+ <<":I have :2:: numbers: :53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d+)",[trim]))),
<<":I have :2: numbers: 53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d+)",[{parts,
- 2}]))),
- <<":I have :2:: numbers: :53147:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d+)",[]))),
- <<":I have 2 numbers: 5314:7">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d+)$",[trim]))),
+ 2}]))),
+ <<":I have :2:: numbers: :53147:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d+)",[]))),
+ <<":I have 2 numbers: 5314:7">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d+)$",[trim]))),
<<":I have 2 numbers: 5314:7:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d+)$",[{parts,
- 2}]))),
- <<":I have 2 numbers: 5314:7:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d+)$",[]))),
- <<":I have 2 numbers: :53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d+)$",[trim]))),
+ 2}]))),
+ <<":I have 2 numbers: 5314:7:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)(\\d+)$",[]))),
+ <<":I have 2 numbers: :53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d+)$",[trim]))),
<<":I have 2 numbers: :53147:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d+)$",[{parts,
- 2}]))),
- <<":I have 2 numbers: :53147:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d+)$",[]))),
- <<":I have 2 numbers: :53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)\\b(\\d+)$",[trim]))),
+ 2}]))),
+ <<":I have 2 numbers: :53147:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*?)(\\d+)$",[]))),
+ <<":I have 2 numbers: :53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)\\b(\\d+)$",[trim]))),
<<":I have 2 numbers: :53147:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)\\b(\\d+)$",[{parts,
- 2}]))),
- <<":I have 2 numbers: :53147:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)\\b(\\d+)$",[]))),
+ 2}]))),
+ <<":I have 2 numbers: :53147:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*)\\b(\\d+)$",[]))),
ok.
run8() ->
- <<":I have 2 numbers: :53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*\\D)(\\d+)$",[trim]))),
+ <<":I have 2 numbers: :53147">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*\\D)(\\d+)$",[trim]))),
<<":I have 2 numbers: :53147:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*\\D)(\\d+)$",[{parts,
- 2}]))),
- <<":I have 2 numbers: :53147:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*\\D)(\\d+)$",[]))),
- <<":C123">> = iolist_to_binary(join(re:split("ABC123","^\\D*(?!123)",[trim]))),
+ 2}]))),
+ <<":I have 2 numbers: :53147:">> = iolist_to_binary(join(re:split("I have 2 numbers: 53147","(.*\\D)(\\d+)$",[]))),
+ <<":C123">> = iolist_to_binary(join(re:split("ABC123","^\\D*(?!123)",[trim]))),
<<":C123">> = iolist_to_binary(join(re:split("ABC123","^\\D*(?!123)",[{parts,
- 2}]))),
- <<":C123">> = iolist_to_binary(join(re:split("ABC123","^\\D*(?!123)",[]))),
- <<":ABC:445">> = iolist_to_binary(join(re:split("ABC445","^(\\D*)(?=\\d)(?!123)",[trim]))),
+ 2}]))),
+ <<":C123">> = iolist_to_binary(join(re:split("ABC123","^\\D*(?!123)",[]))),
+ <<":ABC:445">> = iolist_to_binary(join(re:split("ABC445","^(\\D*)(?=\\d)(?!123)",[trim]))),
<<":ABC:445">> = iolist_to_binary(join(re:split("ABC445","^(\\D*)(?=\\d)(?!123)",[{parts,
- 2}]))),
- <<":ABC:445">> = iolist_to_binary(join(re:split("ABC445","^(\\D*)(?=\\d)(?!123)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\D*)(?=\\d)(?!123)",[trim]))),
+ 2}]))),
+ <<":ABC:445">> = iolist_to_binary(join(re:split("ABC445","^(\\D*)(?=\\d)(?!123)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\D*)(?=\\d)(?!123)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\D*)(?=\\d)(?!123)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\D*)(?=\\d)(?!123)",[]))),
- <<"ABC123">> = iolist_to_binary(join(re:split("ABC123","^(\\D*)(?=\\d)(?!123)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\D*)(?=\\d)(?!123)",[]))),
+ <<"ABC123">> = iolist_to_binary(join(re:split("ABC123","^(\\D*)(?=\\d)(?!123)",[trim]))),
<<"ABC123">> = iolist_to_binary(join(re:split("ABC123","^(\\D*)(?=\\d)(?!123)",[{parts,
- 2}]))),
- <<"ABC123">> = iolist_to_binary(join(re:split("ABC123","^(\\D*)(?=\\d)(?!123)",[]))),
- <<":789">> = iolist_to_binary(join(re:split("W46]789","^[W-]46]",[trim]))),
+ 2}]))),
+ <<"ABC123">> = iolist_to_binary(join(re:split("ABC123","^(\\D*)(?=\\d)(?!123)",[]))),
+ <<":789">> = iolist_to_binary(join(re:split("W46]789","^[W-]46]",[trim]))),
<<":789">> = iolist_to_binary(join(re:split("W46]789","^[W-]46]",[{parts,
- 2}]))),
- <<":789">> = iolist_to_binary(join(re:split("W46]789","^[W-]46]",[]))),
- <<":789">> = iolist_to_binary(join(re:split("-46]789","^[W-]46]",[trim]))),
+ 2}]))),
+ <<":789">> = iolist_to_binary(join(re:split("W46]789","^[W-]46]",[]))),
+ <<":789">> = iolist_to_binary(join(re:split("-46]789","^[W-]46]",[trim]))),
<<":789">> = iolist_to_binary(join(re:split("-46]789","^[W-]46]",[{parts,
- 2}]))),
- <<":789">> = iolist_to_binary(join(re:split("-46]789","^[W-]46]",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-]46]",[trim]))),
+ 2}]))),
+ <<":789">> = iolist_to_binary(join(re:split("-46]789","^[W-]46]",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-]46]",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-]46]",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-]46]",[]))),
- <<"Wall">> = iolist_to_binary(join(re:split("Wall","^[W-]46]",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-]46]",[]))),
+ <<"Wall">> = iolist_to_binary(join(re:split("Wall","^[W-]46]",[trim]))),
<<"Wall">> = iolist_to_binary(join(re:split("Wall","^[W-]46]",[{parts,
- 2}]))),
- <<"Wall">> = iolist_to_binary(join(re:split("Wall","^[W-]46]",[]))),
- <<"Zebra">> = iolist_to_binary(join(re:split("Zebra","^[W-]46]",[trim]))),
+ 2}]))),
+ <<"Wall">> = iolist_to_binary(join(re:split("Wall","^[W-]46]",[]))),
+ <<"Zebra">> = iolist_to_binary(join(re:split("Zebra","^[W-]46]",[trim]))),
<<"Zebra">> = iolist_to_binary(join(re:split("Zebra","^[W-]46]",[{parts,
- 2}]))),
- <<"Zebra">> = iolist_to_binary(join(re:split("Zebra","^[W-]46]",[]))),
- <<"42">> = iolist_to_binary(join(re:split("42","^[W-]46]",[trim]))),
+ 2}]))),
+ <<"Zebra">> = iolist_to_binary(join(re:split("Zebra","^[W-]46]",[]))),
+ <<"42">> = iolist_to_binary(join(re:split("42","^[W-]46]",[trim]))),
<<"42">> = iolist_to_binary(join(re:split("42","^[W-]46]",[{parts,
- 2}]))),
- <<"42">> = iolist_to_binary(join(re:split("42","^[W-]46]",[]))),
- <<"[abcd]">> = iolist_to_binary(join(re:split("[abcd]","^[W-]46]",[trim]))),
+ 2}]))),
+ <<"42">> = iolist_to_binary(join(re:split("42","^[W-]46]",[]))),
+ <<"[abcd]">> = iolist_to_binary(join(re:split("[abcd]","^[W-]46]",[trim]))),
<<"[abcd]">> = iolist_to_binary(join(re:split("[abcd]","^[W-]46]",[{parts,
- 2}]))),
- <<"[abcd]">> = iolist_to_binary(join(re:split("[abcd]","^[W-]46]",[]))),
- <<"]abcd[">> = iolist_to_binary(join(re:split("]abcd[","^[W-]46]",[trim]))),
+ 2}]))),
+ <<"[abcd]">> = iolist_to_binary(join(re:split("[abcd]","^[W-]46]",[]))),
+ <<"]abcd[">> = iolist_to_binary(join(re:split("]abcd[","^[W-]46]",[trim]))),
<<"]abcd[">> = iolist_to_binary(join(re:split("]abcd[","^[W-]46]",[{parts,
- 2}]))),
- <<"]abcd[">> = iolist_to_binary(join(re:split("]abcd[","^[W-]46]",[]))),
- <<":46]789">> = iolist_to_binary(join(re:split("W46]789","^[W-\\]46]",[trim]))),
+ 2}]))),
+ <<"]abcd[">> = iolist_to_binary(join(re:split("]abcd[","^[W-]46]",[]))),
+ <<":46]789">> = iolist_to_binary(join(re:split("W46]789","^[W-\\]46]",[trim]))),
<<":46]789">> = iolist_to_binary(join(re:split("W46]789","^[W-\\]46]",[{parts,
- 2}]))),
- <<":46]789">> = iolist_to_binary(join(re:split("W46]789","^[W-\\]46]",[]))),
- <<":all">> = iolist_to_binary(join(re:split("Wall","^[W-\\]46]",[trim]))),
+ 2}]))),
+ <<":46]789">> = iolist_to_binary(join(re:split("W46]789","^[W-\\]46]",[]))),
+ <<":all">> = iolist_to_binary(join(re:split("Wall","^[W-\\]46]",[trim]))),
<<":all">> = iolist_to_binary(join(re:split("Wall","^[W-\\]46]",[{parts,
- 2}]))),
- <<":all">> = iolist_to_binary(join(re:split("Wall","^[W-\\]46]",[]))),
- <<":ebra">> = iolist_to_binary(join(re:split("Zebra","^[W-\\]46]",[trim]))),
+ 2}]))),
+ <<":all">> = iolist_to_binary(join(re:split("Wall","^[W-\\]46]",[]))),
+ <<":ebra">> = iolist_to_binary(join(re:split("Zebra","^[W-\\]46]",[trim]))),
<<":ebra">> = iolist_to_binary(join(re:split("Zebra","^[W-\\]46]",[{parts,
- 2}]))),
- <<":ebra">> = iolist_to_binary(join(re:split("Zebra","^[W-\\]46]",[]))),
- <<":ylophone">> = iolist_to_binary(join(re:split("Xylophone","^[W-\\]46]",[trim]))),
+ 2}]))),
+ <<":ebra">> = iolist_to_binary(join(re:split("Zebra","^[W-\\]46]",[]))),
+ <<":ylophone">> = iolist_to_binary(join(re:split("Xylophone","^[W-\\]46]",[trim]))),
<<":ylophone">> = iolist_to_binary(join(re:split("Xylophone","^[W-\\]46]",[{parts,
- 2}]))),
- <<":ylophone">> = iolist_to_binary(join(re:split("Xylophone","^[W-\\]46]",[]))),
- <<":2">> = iolist_to_binary(join(re:split("42","^[W-\\]46]",[trim]))),
+ 2}]))),
+ <<":ylophone">> = iolist_to_binary(join(re:split("Xylophone","^[W-\\]46]",[]))),
+ <<":2">> = iolist_to_binary(join(re:split("42","^[W-\\]46]",[trim]))),
<<":2">> = iolist_to_binary(join(re:split("42","^[W-\\]46]",[{parts,
- 2}]))),
- <<":2">> = iolist_to_binary(join(re:split("42","^[W-\\]46]",[]))),
- <<":abcd]">> = iolist_to_binary(join(re:split("[abcd]","^[W-\\]46]",[trim]))),
+ 2}]))),
+ <<":2">> = iolist_to_binary(join(re:split("42","^[W-\\]46]",[]))),
+ <<":abcd]">> = iolist_to_binary(join(re:split("[abcd]","^[W-\\]46]",[trim]))),
<<":abcd]">> = iolist_to_binary(join(re:split("[abcd]","^[W-\\]46]",[{parts,
- 2}]))),
- <<":abcd]">> = iolist_to_binary(join(re:split("[abcd]","^[W-\\]46]",[]))),
- <<":abcd[">> = iolist_to_binary(join(re:split("]abcd[","^[W-\\]46]",[trim]))),
+ 2}]))),
+ <<":abcd]">> = iolist_to_binary(join(re:split("[abcd]","^[W-\\]46]",[]))),
+ <<":abcd[">> = iolist_to_binary(join(re:split("]abcd[","^[W-\\]46]",[trim]))),
<<":abcd[">> = iolist_to_binary(join(re:split("]abcd[","^[W-\\]46]",[{parts,
- 2}]))),
- <<":abcd[">> = iolist_to_binary(join(re:split("]abcd[","^[W-\\]46]",[]))),
- <<":backslash">> = iolist_to_binary(join(re:split("\\backslash","^[W-\\]46]",[trim]))),
+ 2}]))),
+ <<":abcd[">> = iolist_to_binary(join(re:split("]abcd[","^[W-\\]46]",[]))),
+ <<":backslash">> = iolist_to_binary(join(re:split("\\backslash","^[W-\\]46]",[trim]))),
<<":backslash">> = iolist_to_binary(join(re:split("\\backslash","^[W-\\]46]",[{parts,
- 2}]))),
- <<":backslash">> = iolist_to_binary(join(re:split("\\backslash","^[W-\\]46]",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-\\]46]",[trim]))),
+ 2}]))),
+ <<":backslash">> = iolist_to_binary(join(re:split("\\backslash","^[W-\\]46]",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-\\]46]",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-\\]46]",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-\\]46]",[]))),
- <<"-46]789">> = iolist_to_binary(join(re:split("-46]789","^[W-\\]46]",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[W-\\]46]",[]))),
+ <<"-46]789">> = iolist_to_binary(join(re:split("-46]789","^[W-\\]46]",[trim]))),
<<"-46]789">> = iolist_to_binary(join(re:split("-46]789","^[W-\\]46]",[{parts,
- 2}]))),
- <<"-46]789">> = iolist_to_binary(join(re:split("-46]789","^[W-\\]46]",[]))),
- <<"well">> = iolist_to_binary(join(re:split("well","^[W-\\]46]",[trim]))),
+ 2}]))),
+ <<"-46]789">> = iolist_to_binary(join(re:split("-46]789","^[W-\\]46]",[]))),
+ <<"well">> = iolist_to_binary(join(re:split("well","^[W-\\]46]",[trim]))),
<<"well">> = iolist_to_binary(join(re:split("well","^[W-\\]46]",[{parts,
- 2}]))),
- <<"well">> = iolist_to_binary(join(re:split("well","^[W-\\]46]",[]))),
- <<"">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark otherword","word (?:[a-zA-Z0-9]+ ){0,10}otherword",[trim]))),
+ 2}]))),
+ <<"well">> = iolist_to_binary(join(re:split("well","^[W-\\]46]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark otherword","word (?:[a-zA-Z0-9]+ ){0,10}otherword",[trim]))),
<<":">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark otherword","word (?:[a-zA-Z0-9]+ ){0,10}otherword",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark otherword","word (?:[a-zA-Z0-9]+ ){0,10}otherword",[]))),
- <<"word cat dog elephant mussel cow horse canary baboon snake shark">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark","word (?:[a-zA-Z0-9]+ ){0,10}otherword",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark otherword","word (?:[a-zA-Z0-9]+ ){0,10}otherword",[]))),
+ <<"word cat dog elephant mussel cow horse canary baboon snake shark">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark","word (?:[a-zA-Z0-9]+ ){0,10}otherword",[trim]))),
<<"word cat dog elephant mussel cow horse canary baboon snake shark">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark","word (?:[a-zA-Z0-9]+ ){0,10}otherword",[{parts,
- 2}]))),
- <<"word cat dog elephant mussel cow horse canary baboon snake shark">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark","word (?:[a-zA-Z0-9]+ ){0,10}otherword",[]))),
- <<"word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope","word (?:[a-zA-Z0-9]+ ){0,300}otherword",[trim]))),
+ 2}]))),
+ <<"word cat dog elephant mussel cow horse canary baboon snake shark">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark","word (?:[a-zA-Z0-9]+ ){0,10}otherword",[]))),
+ <<"word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope","word (?:[a-zA-Z0-9]+ ){0,300}otherword",[trim]))),
<<"word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope","word (?:[a-zA-Z0-9]+ ){0,300}otherword",[{parts,
- 2}]))),
- <<"word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope","word (?:[a-zA-Z0-9]+ ){0,300}otherword",[]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,0}",[trim]))),
+ 2}]))),
+ <<"word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope","word (?:[a-zA-Z0-9]+ ){0,300}otherword",[]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,0}",[trim]))),
<<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,0}",[{parts,
- 2}]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,0}",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^(a){0,0}",[trim]))),
+ 2}]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,0}",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^(a){0,0}",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","^(a){0,0}",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^(a){0,0}",[]))),
- <<"aab">> = iolist_to_binary(join(re:split("aab","^(a){0,0}",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^(a){0,0}",[]))),
+ <<"aab">> = iolist_to_binary(join(re:split("aab","^(a){0,0}",[trim]))),
<<"aab">> = iolist_to_binary(join(re:split("aab","^(a){0,0}",[{parts,
- 2}]))),
- <<"aab">> = iolist_to_binary(join(re:split("aab","^(a){0,0}",[]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,1}",[trim]))),
+ 2}]))),
+ <<"aab">> = iolist_to_binary(join(re:split("aab","^(a){0,0}",[]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,1}",[trim]))),
<<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,1}",[{parts,
- 2}]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,1}",[]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,1}",[trim]))),
+ 2}]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,1}",[]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,1}",[trim]))),
<<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,1}",[{parts,
- 2}]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,1}",[]))),
- <<":a:ab">> = iolist_to_binary(join(re:split("aab","^(a){0,1}",[trim]))),
+ 2}]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,1}",[]))),
+ <<":a:ab">> = iolist_to_binary(join(re:split("aab","^(a){0,1}",[trim]))),
<<":a:ab">> = iolist_to_binary(join(re:split("aab","^(a){0,1}",[{parts,
- 2}]))),
- <<":a:ab">> = iolist_to_binary(join(re:split("aab","^(a){0,1}",[]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,2}",[trim]))),
+ 2}]))),
+ <<":a:ab">> = iolist_to_binary(join(re:split("aab","^(a){0,1}",[]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,2}",[trim]))),
<<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,2}",[{parts,
- 2}]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,2}",[]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,2}",[trim]))),
+ 2}]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,2}",[]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,2}",[trim]))),
<<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,2}",[{parts,
- 2}]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,2}",[]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,2}",[trim]))),
+ 2}]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,2}",[]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,2}",[trim]))),
<<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,2}",[{parts,
- 2}]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,2}",[]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,3}",[trim]))),
+ 2}]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,2}",[]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,3}",[trim]))),
<<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,3}",[{parts,
- 2}]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,3}",[]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,3}",[trim]))),
+ 2}]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,3}",[]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,3}",[trim]))),
<<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,3}",[{parts,
- 2}]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,3}",[]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,3}",[trim]))),
+ 2}]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,3}",[]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,3}",[trim]))),
<<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,3}",[{parts,
- 2}]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,3}",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaa","^(a){0,3}",[trim]))),
+ 2}]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,3}",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaa","^(a){0,3}",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaa","^(a){0,3}",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaa","^(a){0,3}",[]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,}",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaa","^(a){0,3}",[]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,}",[trim]))),
<<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,}",[{parts,
- 2}]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,}",[]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,}",[trim]))),
+ 2}]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){0,}",[]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,}",[trim]))),
<<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,}",[{parts,
- 2}]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,}",[]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,}",[trim]))),
+ 2}]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){0,}",[]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,}",[trim]))),
<<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,}",[{parts,
- 2}]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,}",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaa","^(a){0,}",[trim]))),
+ 2}]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){0,}",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaa","^(a){0,}",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaa","^(a){0,}",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaa","^(a){0,}",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a){0,}",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaa","^(a){0,}",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a){0,}",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a){0,}",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a){0,}",[]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,1}",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a){0,}",[]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,1}",[trim]))),
<<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,1}",[{parts,
- 2}]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,1}",[]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,1}",[trim]))),
+ 2}]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,1}",[]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,1}",[trim]))),
<<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,1}",[{parts,
- 2}]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,1}",[]))),
- <<":a:ab">> = iolist_to_binary(join(re:split("aab","^(a){1,1}",[trim]))),
+ 2}]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,1}",[]))),
+ <<":a:ab">> = iolist_to_binary(join(re:split("aab","^(a){1,1}",[trim]))),
<<":a:ab">> = iolist_to_binary(join(re:split("aab","^(a){1,1}",[{parts,
- 2}]))),
- <<":a:ab">> = iolist_to_binary(join(re:split("aab","^(a){1,1}",[]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,2}",[trim]))),
+ 2}]))),
+ <<":a:ab">> = iolist_to_binary(join(re:split("aab","^(a){1,1}",[]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,2}",[trim]))),
<<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,2}",[{parts,
- 2}]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,2}",[]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,2}",[trim]))),
+ 2}]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,2}",[]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,2}",[trim]))),
<<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,2}",[{parts,
- 2}]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,2}",[]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,2}",[trim]))),
+ 2}]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,2}",[]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,2}",[trim]))),
<<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,2}",[{parts,
- 2}]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,2}",[]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,3}",[trim]))),
+ 2}]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,2}",[]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,3}",[trim]))),
<<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,3}",[{parts,
- 2}]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,3}",[]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,3}",[trim]))),
+ 2}]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,3}",[]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,3}",[trim]))),
<<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,3}",[{parts,
- 2}]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,3}",[]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,3}",[trim]))),
+ 2}]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,3}",[]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,3}",[trim]))),
<<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,3}",[{parts,
- 2}]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,3}",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaa","^(a){1,3}",[trim]))),
+ 2}]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,3}",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaa","^(a){1,3}",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaa","^(a){1,3}",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaa","^(a){1,3}",[]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,}",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaa","^(a){1,3}",[]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,}",[trim]))),
<<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,}",[{parts,
- 2}]))),
- <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,}",[]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,}",[trim]))),
+ 2}]))),
+ <<"bcd">> = iolist_to_binary(join(re:split("bcd","^(a){1,}",[]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,}",[trim]))),
<<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,}",[{parts,
- 2}]))),
- <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,}",[]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,}",[trim]))),
+ 2}]))),
+ <<":a:bc">> = iolist_to_binary(join(re:split("abc","^(a){1,}",[]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,}",[trim]))),
<<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,}",[{parts,
- 2}]))),
- <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,}",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaa","^(a){1,}",[trim]))),
+ 2}]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("aab","^(a){1,}",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaa","^(a){1,}",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaa","^(a){1,}",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaa","^(a){1,}",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a){1,}",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaa","^(a){1,}",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a){1,}",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a){1,}",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a){1,}",[]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a){1,}",[]))),
<<"borfle
:
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*\\.gif",[trim]))),
+no",".*\\.gif",[trim]))),
<<"borfle
:
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*\\.gif",[{parts,2}]))),
+no",".*\\.gif",[{parts,2}]))),
<<"borfle
:
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*\\.gif",[]))),
+no",".*\\.gif",[]))),
<<"borfle
:
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".{0,}\\.gif",[trim]))),
+no",".{0,}\\.gif",[trim]))),
<<"borfle
:
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".{0,}\\.gif",[{parts,2}]))),
+no",".{0,}\\.gif",[{parts,2}]))),
<<"borfle
:
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".{0,}\\.gif",[]))),
+no",".{0,}\\.gif",[]))),
<<"borfle
:
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*\\.gif",[multiline,trim]))),
+no",".*\\.gif",[multiline,trim]))),
<<"borfle
:
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*\\.gif",[multiline,{parts,2}]))),
+no",".*\\.gif",[multiline,{parts,2}]))),
<<"borfle
:
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*\\.gif",[multiline]))),
+no",".*\\.gif",[multiline]))),
ok.
run9() ->
<<":
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*\\.gif",[dotall,trim]))),
+no",".*\\.gif",[dotall,trim]))),
<<":
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*\\.gif",[dotall,{parts,2}]))),
+no",".*\\.gif",[dotall,{parts,2}]))),
<<":
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*\\.gif",[dotall]))),
+no",".*\\.gif",[dotall]))),
<<":
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*\\.gif",[multiline,dotall,trim]))),
+no",".*\\.gif",[multiline,dotall,trim]))),
<<":
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*\\.gif",[multiline,dotall,{parts,2}]))),
+no",".*\\.gif",[multiline,dotall,{parts,2}]))),
<<":
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*\\.gif",[multiline,dotall]))),
+no",".*\\.gif",[multiline,dotall]))),
<<"borfle
bib.gif
">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[trim]))),
+no",".*$",[trim]))),
<<"borfle
bib.gif
:">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[{parts,2}]))),
+no",".*$",[{parts,2}]))),
<<"borfle
bib.gif
:">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[]))),
+no",".*$",[]))),
<<":
:
">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[multiline,trim]))),
+no",".*$",[multiline,trim]))),
<<":
bib.gif
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[multiline,{parts,2}]))),
+no",".*$",[multiline,{parts,2}]))),
<<":
:
:">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[multiline]))),
+no",".*$",[multiline]))),
<<"">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[dotall,trim]))),
+no",".*$",[dotall,trim]))),
<<":">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[dotall,{parts,2}]))),
+no",".*$",[dotall,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[dotall]))),
+no",".*$",[dotall]))),
<<"">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[multiline,dotall,trim]))),
+no",".*$",[multiline,dotall,trim]))),
<<":">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[multiline,dotall,{parts,2}]))),
+no",".*$",[multiline,dotall,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[multiline,dotall]))),
+no",".*$",[multiline,dotall]))),
<<"borfle
bib.gif
">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[trim]))),
+no",".*$",[trim]))),
<<"borfle
bib.gif
:">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[{parts,2}]))),
+no",".*$",[{parts,2}]))),
<<"borfle
bib.gif
:">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[]))),
+no",".*$",[]))),
<<":
:
">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[multiline,trim]))),
+no",".*$",[multiline,trim]))),
<<":
bib.gif
no">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[multiline,{parts,2}]))),
+no",".*$",[multiline,{parts,2}]))),
<<":
:
:">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[multiline]))),
+no",".*$",[multiline]))),
<<"">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[dotall,trim]))),
+no",".*$",[dotall,trim]))),
<<":">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[dotall,{parts,2}]))),
+no",".*$",[dotall,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[dotall]))),
+no",".*$",[dotall]))),
<<"">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[multiline,dotall,trim]))),
+no",".*$",[multiline,dotall,trim]))),
<<":">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[multiline,dotall,{parts,2}]))),
+no",".*$",[multiline,dotall,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("borfle
bib.gif
-no",".*$",[multiline,dotall]))),
+no",".*$",[multiline,dotall]))),
<<"abcde
:1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(.*X|^B)",[trim]))),
+1234Xyz","(.*X|^B)",[trim]))),
<<"abcde
:1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(.*X|^B)",[{parts,2}]))),
+1234Xyz","(.*X|^B)",[{parts,2}]))),
<<"abcde
:1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(.*X|^B)",[]))),
- <<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[trim]))),
+1234Xyz","(.*X|^B)",[]))),
+ <<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[trim]))),
<<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[{parts,
- 2}]))),
- <<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(.*X|^B)",[trim]))),
+ 2}]))),
+ <<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(.*X|^B)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(.*X|^B)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(.*X|^B)",[]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(.*X|^B)",[]))),
<<"abcde
Bar">> = iolist_to_binary(join(re:split("abcde
-Bar","(.*X|^B)",[trim]))),
+Bar","(.*X|^B)",[trim]))),
<<"abcde
Bar">> = iolist_to_binary(join(re:split("abcde
-Bar","(.*X|^B)",[{parts,2}]))),
+Bar","(.*X|^B)",[{parts,2}]))),
<<"abcde
Bar">> = iolist_to_binary(join(re:split("abcde
-Bar","(.*X|^B)",[]))),
+Bar","(.*X|^B)",[]))),
<<"abcde
:1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(.*X|^B)",[multiline,trim]))),
+1234Xyz","(.*X|^B)",[multiline,trim]))),
<<"abcde
:1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(.*X|^B)",[multiline,{parts,2}]))),
+1234Xyz","(.*X|^B)",[multiline,{parts,2}]))),
<<"abcde
:1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(.*X|^B)",[multiline]))),
+1234Xyz","(.*X|^B)",[multiline]))),
<<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[multiline,
- trim]))),
+ trim]))),
<<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[multiline,
{parts,
- 2}]))),
- <<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[multiline]))),
+ 2}]))),
+ <<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[multiline]))),
<<"abcde
:B:ar">> = iolist_to_binary(join(re:split("abcde
-Bar","(.*X|^B)",[multiline,trim]))),
+Bar","(.*X|^B)",[multiline,trim]))),
<<"abcde
:B:ar">> = iolist_to_binary(join(re:split("abcde
-Bar","(.*X|^B)",[multiline,{parts,2}]))),
+Bar","(.*X|^B)",[multiline,{parts,2}]))),
<<"abcde
:B:ar">> = iolist_to_binary(join(re:split("abcde
-Bar","(.*X|^B)",[multiline]))),
+Bar","(.*X|^B)",[multiline]))),
<<":abcde
1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(.*X|^B)",[dotall,trim]))),
+1234Xyz","(.*X|^B)",[dotall,trim]))),
<<":abcde
1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(.*X|^B)",[dotall,{parts,2}]))),
+1234Xyz","(.*X|^B)",[dotall,{parts,2}]))),
<<":abcde
1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(.*X|^B)",[dotall]))),
+1234Xyz","(.*X|^B)",[dotall]))),
<<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[dotall,
- trim]))),
+ trim]))),
<<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[dotall,
{parts,
- 2}]))),
- <<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[dotall]))),
+ 2}]))),
+ <<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[dotall]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(.*X|^B)",[dotall,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(.*X|^B)",[dotall,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(.*X|^B)",[dotall]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(.*X|^B)",[dotall]))),
<<"abcde
Bar">> = iolist_to_binary(join(re:split("abcde
-Bar","(.*X|^B)",[dotall,trim]))),
+Bar","(.*X|^B)",[dotall,trim]))),
<<"abcde
Bar">> = iolist_to_binary(join(re:split("abcde
-Bar","(.*X|^B)",[dotall,{parts,2}]))),
+Bar","(.*X|^B)",[dotall,{parts,2}]))),
<<"abcde
Bar">> = iolist_to_binary(join(re:split("abcde
-Bar","(.*X|^B)",[dotall]))),
+Bar","(.*X|^B)",[dotall]))),
<<":abcde
1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(.*X|^B)",[multiline,dotall,trim]))),
+1234Xyz","(.*X|^B)",[multiline,dotall,trim]))),
<<":abcde
1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(.*X|^B)",[multiline,dotall,{parts,2}]))),
+1234Xyz","(.*X|^B)",[multiline,dotall,{parts,2}]))),
<<":abcde
1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(.*X|^B)",[multiline,dotall]))),
+1234Xyz","(.*X|^B)",[multiline,dotall]))),
<<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[multiline,
dotall,
- trim]))),
+ trim]))),
<<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[multiline,
dotall,
{parts,
- 2}]))),
+ 2}]))),
<<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(.*X|^B)",[multiline,
- dotall]))),
+ dotall]))),
<<"abcde
:B:ar">> = iolist_to_binary(join(re:split("abcde
-Bar","(.*X|^B)",[multiline,dotall,trim]))),
+Bar","(.*X|^B)",[multiline,dotall,trim]))),
<<"abcde
:B:ar">> = iolist_to_binary(join(re:split("abcde
-Bar","(.*X|^B)",[multiline,dotall,{parts,2}]))),
+Bar","(.*X|^B)",[multiline,dotall,{parts,2}]))),
<<"abcde
:B:ar">> = iolist_to_binary(join(re:split("abcde
-Bar","(.*X|^B)",[multiline,dotall]))),
+Bar","(.*X|^B)",[multiline,dotall]))),
<<":abcde
1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(?s)(.*X|^B)",[trim]))),
+1234Xyz","(?s)(.*X|^B)",[trim]))),
<<":abcde
1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(?s)(.*X|^B)",[{parts,2}]))),
+1234Xyz","(?s)(.*X|^B)",[{parts,2}]))),
<<":abcde
1234X:yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(?s)(.*X|^B)",[]))),
- <<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(?s)(.*X|^B)",[trim]))),
+1234Xyz","(?s)(.*X|^B)",[]))),
+ <<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(?s)(.*X|^B)",[trim]))),
<<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(?s)(.*X|^B)",[{parts,
- 2}]))),
- <<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(?s)(.*X|^B)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s)(.*X|^B)",[trim]))),
+ 2}]))),
+ <<":B:arFoo">> = iolist_to_binary(join(re:split("BarFoo","(?s)(.*X|^B)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s)(.*X|^B)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s)(.*X|^B)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s)(.*X|^B)",[]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s)(.*X|^B)",[]))),
<<"abcde
Bar">> = iolist_to_binary(join(re:split("abcde
-Bar","(?s)(.*X|^B)",[trim]))),
+Bar","(?s)(.*X|^B)",[trim]))),
<<"abcde
Bar">> = iolist_to_binary(join(re:split("abcde
-Bar","(?s)(.*X|^B)",[{parts,2}]))),
+Bar","(?s)(.*X|^B)",[{parts,2}]))),
<<"abcde
Bar">> = iolist_to_binary(join(re:split("abcde
-Bar","(?s)(.*X|^B)",[]))),
+Bar","(?s)(.*X|^B)",[]))),
<<":yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(?s:.*X|^B)",[trim]))),
+1234Xyz","(?s:.*X|^B)",[trim]))),
<<":yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(?s:.*X|^B)",[{parts,2}]))),
+1234Xyz","(?s:.*X|^B)",[{parts,2}]))),
<<":yz">> = iolist_to_binary(join(re:split("abcde
-1234Xyz","(?s:.*X|^B)",[]))),
- <<":arFoo">> = iolist_to_binary(join(re:split("BarFoo","(?s:.*X|^B)",[trim]))),
+1234Xyz","(?s:.*X|^B)",[]))),
+ <<":arFoo">> = iolist_to_binary(join(re:split("BarFoo","(?s:.*X|^B)",[trim]))),
<<":arFoo">> = iolist_to_binary(join(re:split("BarFoo","(?s:.*X|^B)",[{parts,
- 2}]))),
- <<":arFoo">> = iolist_to_binary(join(re:split("BarFoo","(?s:.*X|^B)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s:.*X|^B)",[trim]))),
+ 2}]))),
+ <<":arFoo">> = iolist_to_binary(join(re:split("BarFoo","(?s:.*X|^B)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s:.*X|^B)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s:.*X|^B)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s:.*X|^B)",[]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s:.*X|^B)",[]))),
<<"abcde
Bar">> = iolist_to_binary(join(re:split("abcde
-Bar","(?s:.*X|^B)",[trim]))),
+Bar","(?s:.*X|^B)",[trim]))),
<<"abcde
Bar">> = iolist_to_binary(join(re:split("abcde
-Bar","(?s:.*X|^B)",[{parts,2}]))),
+Bar","(?s:.*X|^B)",[{parts,2}]))),
<<"abcde
Bar">> = iolist_to_binary(join(re:split("abcde
-Bar","(?s:.*X|^B)",[]))),
- <<"**** Failers">> = iolist_to_binary(join(re:split("**** Failers","^.*B",[trim]))),
+Bar","(?s:.*X|^B)",[]))),
+ <<"**** Failers">> = iolist_to_binary(join(re:split("**** Failers","^.*B",[trim]))),
<<"**** Failers">> = iolist_to_binary(join(re:split("**** Failers","^.*B",[{parts,
- 2}]))),
- <<"**** Failers">> = iolist_to_binary(join(re:split("**** Failers","^.*B",[]))),
+ 2}]))),
+ <<"**** Failers">> = iolist_to_binary(join(re:split("**** Failers","^.*B",[]))),
<<"abc
B">> = iolist_to_binary(join(re:split("abc
-B","^.*B",[trim]))),
+B","^.*B",[trim]))),
<<"abc
B">> = iolist_to_binary(join(re:split("abc
-B","^.*B",[{parts,2}]))),
+B","^.*B",[{parts,2}]))),
<<"abc
B">> = iolist_to_binary(join(re:split("abc
-B","^.*B",[]))),
+B","^.*B",[]))),
<<"">> = iolist_to_binary(join(re:split("abc
-B","(?s)^.*B",[trim]))),
+B","(?s)^.*B",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc
-B","(?s)^.*B",[{parts,2}]))),
+B","(?s)^.*B",[{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("abc
-B","(?s)^.*B",[]))),
+B","(?s)^.*B",[]))),
<<"abc
">> = iolist_to_binary(join(re:split("abc
-B","(?m)^.*B",[trim]))),
+B","(?m)^.*B",[trim]))),
<<"abc
:">> = iolist_to_binary(join(re:split("abc
-B","(?m)^.*B",[{parts,2}]))),
+B","(?m)^.*B",[{parts,2}]))),
<<"abc
:">> = iolist_to_binary(join(re:split("abc
-B","(?m)^.*B",[]))),
+B","(?m)^.*B",[]))),
<<"">> = iolist_to_binary(join(re:split("abc
-B","(?ms)^.*B",[trim]))),
+B","(?ms)^.*B",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc
-B","(?ms)^.*B",[{parts,2}]))),
+B","(?ms)^.*B",[{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("abc
-B","(?ms)^.*B",[]))),
+B","(?ms)^.*B",[]))),
ok.
run10() ->
<<"abc
">> = iolist_to_binary(join(re:split("abc
-B","(?ms)^B",[trim]))),
+B","(?ms)^B",[trim]))),
<<"abc
:">> = iolist_to_binary(join(re:split("abc
-B","(?ms)^B",[{parts,2}]))),
+B","(?ms)^B",[{parts,2}]))),
<<"abc
:">> = iolist_to_binary(join(re:split("abc
-B","(?ms)^B",[]))),
- <<"">> = iolist_to_binary(join(re:split("B","(?s)B$",[trim]))),
+B","(?ms)^B",[]))),
+ <<"">> = iolist_to_binary(join(re:split("B","(?s)B$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("B","(?s)B$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("B","(?s)B$",[]))),
- <<"">> = iolist_to_binary(join(re:split("123456654321","^[0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("B","(?s)B$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("123456654321","^[0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("123456654321","^[0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("123456654321","^[0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9]",[]))),
- <<"">> = iolist_to_binary(join(re:split("123456654321","^\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("123456654321","^[0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("123456654321","^\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d",[trim]))),
<<":">> = iolist_to_binary(join(re:split("123456654321","^\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("123456654321","^\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d",[]))),
- <<"">> = iolist_to_binary(join(re:split("123456654321","^[\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("123456654321","^\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d",[]))),
+ <<"">> = iolist_to_binary(join(re:split("123456654321","^[\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("123456654321","^[\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("123456654321","^[\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d]",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcabcabcabc","^[abc]{12}",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("123456654321","^[\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcabcabcabc","^[abc]{12}",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcabcabcabc","^[abc]{12}",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcabcabcabc","^[abc]{12}",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcabcabcabc","^[a-c]{12}",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcabcabcabc","^[abc]{12}",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcabcabcabc","^[a-c]{12}",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcabcabcabc","^[a-c]{12}",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcabcabcabc","^[a-c]{12}",[]))),
- <<":c">> = iolist_to_binary(join(re:split("abcabcabcabc","^(a|b|c){12}",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcabcabcabc","^[a-c]{12}",[]))),
+ <<":c">> = iolist_to_binary(join(re:split("abcabcabcabc","^(a|b|c){12}",[trim]))),
<<":c:">> = iolist_to_binary(join(re:split("abcabcabcabc","^(a|b|c){12}",[{parts,
- 2}]))),
- <<":c:">> = iolist_to_binary(join(re:split("abcabcabcabc","^(a|b|c){12}",[]))),
- <<"">> = iolist_to_binary(join(re:split("n","^[abcdefghijklmnopqrstuvwxy0123456789]",[trim]))),
+ 2}]))),
+ <<":c:">> = iolist_to_binary(join(re:split("abcabcabcabc","^(a|b|c){12}",[]))),
+ <<"">> = iolist_to_binary(join(re:split("n","^[abcdefghijklmnopqrstuvwxy0123456789]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("n","^[abcdefghijklmnopqrstuvwxy0123456789]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("n","^[abcdefghijklmnopqrstuvwxy0123456789]",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[abcdefghijklmnopqrstuvwxy0123456789]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("n","^[abcdefghijklmnopqrstuvwxy0123456789]",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[abcdefghijklmnopqrstuvwxy0123456789]",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[abcdefghijklmnopqrstuvwxy0123456789]",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[abcdefghijklmnopqrstuvwxy0123456789]",[]))),
- <<"z">> = iolist_to_binary(join(re:split("z","^[abcdefghijklmnopqrstuvwxy0123456789]",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[abcdefghijklmnopqrstuvwxy0123456789]",[]))),
+ <<"z">> = iolist_to_binary(join(re:split("z","^[abcdefghijklmnopqrstuvwxy0123456789]",[trim]))),
<<"z">> = iolist_to_binary(join(re:split("z","^[abcdefghijklmnopqrstuvwxy0123456789]",[{parts,
- 2}]))),
- <<"z">> = iolist_to_binary(join(re:split("z","^[abcdefghijklmnopqrstuvwxy0123456789]",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcd","abcde{0,0}",[trim]))),
+ 2}]))),
+ <<"z">> = iolist_to_binary(join(re:split("z","^[abcdefghijklmnopqrstuvwxy0123456789]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcd","abcde{0,0}",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcd","abcde{0,0}",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcd","abcde{0,0}",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abcde{0,0}",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcd","abcde{0,0}",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abcde{0,0}",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abcde{0,0}",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abcde{0,0}",[]))),
- <<"abce">> = iolist_to_binary(join(re:split("abce","abcde{0,0}",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abcde{0,0}",[]))),
+ <<"abce">> = iolist_to_binary(join(re:split("abce","abcde{0,0}",[trim]))),
<<"abce">> = iolist_to_binary(join(re:split("abce","abcde{0,0}",[{parts,
- 2}]))),
- <<"abce">> = iolist_to_binary(join(re:split("abce","abcde{0,0}",[]))),
- <<"">> = iolist_to_binary(join(re:split("abe","ab[cd]{0,0}e",[trim]))),
+ 2}]))),
+ <<"abce">> = iolist_to_binary(join(re:split("abce","abcde{0,0}",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abe","ab[cd]{0,0}e",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abe","ab[cd]{0,0}e",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abe","ab[cd]{0,0}e",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab[cd]{0,0}e",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abe","ab[cd]{0,0}e",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab[cd]{0,0}e",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab[cd]{0,0}e",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab[cd]{0,0}e",[]))),
- <<"abcde">> = iolist_to_binary(join(re:split("abcde","ab[cd]{0,0}e",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab[cd]{0,0}e",[]))),
+ <<"abcde">> = iolist_to_binary(join(re:split("abcde","ab[cd]{0,0}e",[trim]))),
<<"abcde">> = iolist_to_binary(join(re:split("abcde","ab[cd]{0,0}e",[{parts,
- 2}]))),
- <<"abcde">> = iolist_to_binary(join(re:split("abcde","ab[cd]{0,0}e",[]))),
- <<"">> = iolist_to_binary(join(re:split("abd","ab(c){0,0}d",[trim]))),
+ 2}]))),
+ <<"abcde">> = iolist_to_binary(join(re:split("abcde","ab[cd]{0,0}e",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abd","ab(c){0,0}d",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("abd","ab(c){0,0}d",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("abd","ab(c){0,0}d",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab(c){0,0}d",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("abd","ab(c){0,0}d",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab(c){0,0}d",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab(c){0,0}d",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab(c){0,0}d",[]))),
- <<"abcd">> = iolist_to_binary(join(re:split("abcd","ab(c){0,0}d",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab(c){0,0}d",[]))),
+ <<"abcd">> = iolist_to_binary(join(re:split("abcd","ab(c){0,0}d",[trim]))),
<<"abcd">> = iolist_to_binary(join(re:split("abcd","ab(c){0,0}d",[{parts,
- 2}]))),
- <<"abcd">> = iolist_to_binary(join(re:split("abcd","ab(c){0,0}d",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","a(b*)",[trim]))),
+ 2}]))),
+ <<"abcd">> = iolist_to_binary(join(re:split("abcd","ab(c){0,0}d",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","a(b*)",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a","a(b*)",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a","a(b*)",[]))),
- <<":b">> = iolist_to_binary(join(re:split("ab","a(b*)",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a","a(b*)",[]))),
+ <<":b">> = iolist_to_binary(join(re:split("ab","a(b*)",[trim]))),
<<":b:">> = iolist_to_binary(join(re:split("ab","a(b*)",[{parts,
- 2}]))),
- <<":b:">> = iolist_to_binary(join(re:split("ab","a(b*)",[]))),
- <<":bbbb">> = iolist_to_binary(join(re:split("abbbb","a(b*)",[trim]))),
+ 2}]))),
+ <<":b:">> = iolist_to_binary(join(re:split("ab","a(b*)",[]))),
+ <<":bbbb">> = iolist_to_binary(join(re:split("abbbb","a(b*)",[trim]))),
<<":bbbb:">> = iolist_to_binary(join(re:split("abbbb","a(b*)",[{parts,
- 2}]))),
- <<":bbbb:">> = iolist_to_binary(join(re:split("abbbb","a(b*)",[]))),
- <<"*** F::ilers">> = iolist_to_binary(join(re:split("*** Failers","a(b*)",[trim]))),
+ 2}]))),
+ <<":bbbb:">> = iolist_to_binary(join(re:split("abbbb","a(b*)",[]))),
+ <<"*** F::ilers">> = iolist_to_binary(join(re:split("*** Failers","a(b*)",[trim]))),
<<"*** F::ilers">> = iolist_to_binary(join(re:split("*** Failers","a(b*)",[{parts,
- 2}]))),
- <<"*** F::ilers">> = iolist_to_binary(join(re:split("*** Failers","a(b*)",[]))),
- <<"bbbbb">> = iolist_to_binary(join(re:split("bbbbb","a(b*)",[trim]))),
+ 2}]))),
+ <<"*** F::ilers">> = iolist_to_binary(join(re:split("*** Failers","a(b*)",[]))),
+ <<"bbbbb">> = iolist_to_binary(join(re:split("bbbbb","a(b*)",[trim]))),
<<"bbbbb">> = iolist_to_binary(join(re:split("bbbbb","a(b*)",[{parts,
- 2}]))),
- <<"bbbbb">> = iolist_to_binary(join(re:split("bbbbb","a(b*)",[]))),
- <<"">> = iolist_to_binary(join(re:split("abe","ab\\d{0}e",[trim]))),
+ 2}]))),
+ <<"bbbbb">> = iolist_to_binary(join(re:split("bbbbb","a(b*)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abe","ab\\d{0}e",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abe","ab\\d{0}e",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abe","ab\\d{0}e",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab\\d{0}e",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abe","ab\\d{0}e",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab\\d{0}e",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab\\d{0}e",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab\\d{0}e",[]))),
- <<"ab1e">> = iolist_to_binary(join(re:split("ab1e","ab\\d{0}e",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab\\d{0}e",[]))),
+ <<"ab1e">> = iolist_to_binary(join(re:split("ab1e","ab\\d{0}e",[trim]))),
<<"ab1e">> = iolist_to_binary(join(re:split("ab1e","ab\\d{0}e",[{parts,
- 2}]))),
- <<"ab1e">> = iolist_to_binary(join(re:split("ab1e","ab\\d{0}e",[]))),
- <<"the :quick: brown fox">> = iolist_to_binary(join(re:split("the \"quick\" brown fox","\"([^\\\\\"]+|\\\\.)*\"",[trim]))),
+ 2}]))),
+ <<"ab1e">> = iolist_to_binary(join(re:split("ab1e","ab\\d{0}e",[]))),
+ <<"the :quick: brown fox">> = iolist_to_binary(join(re:split("the \"quick\" brown fox","\"([^\\\\\"]+|\\\\.)*\"",[trim]))),
<<"the :quick: brown fox">> = iolist_to_binary(join(re:split("the \"quick\" brown fox","\"([^\\\\\"]+|\\\\.)*\"",[{parts,
- 2}]))),
- <<"the :quick: brown fox">> = iolist_to_binary(join(re:split("the \"quick\" brown fox","\"([^\\\\\"]+|\\\\.)*\"",[]))),
- <<": brown fox">> = iolist_to_binary(join(re:split("\"the \\\"quick\\\" brown fox\"","\"([^\\\\\"]+|\\\\.)*\"",[trim]))),
+ 2}]))),
+ <<"the :quick: brown fox">> = iolist_to_binary(join(re:split("the \"quick\" brown fox","\"([^\\\\\"]+|\\\\.)*\"",[]))),
+ <<": brown fox">> = iolist_to_binary(join(re:split("\"the \\\"quick\\\" brown fox\"","\"([^\\\\\"]+|\\\\.)*\"",[trim]))),
<<": brown fox:">> = iolist_to_binary(join(re:split("\"the \\\"quick\\\" brown fox\"","\"([^\\\\\"]+|\\\\.)*\"",[{parts,
- 2}]))),
- <<": brown fox:">> = iolist_to_binary(join(re:split("\"the \\\"quick\\\" brown fox\"","\"([^\\\\\"]+|\\\\.)*\"",[]))),
- <<"a:b:c">> = iolist_to_binary(join(re:split("abc","",[trim]))),
+ 2}]))),
+ <<": brown fox:">> = iolist_to_binary(join(re:split("\"the \\\"quick\\\" brown fox\"","\"([^\\\\\"]+|\\\\.)*\"",[]))),
+ <<"a:b:c">> = iolist_to_binary(join(re:split("abc","",[trim]))),
<<"a:bc">> = iolist_to_binary(join(re:split("abc","",[{parts,
- 2}]))),
- <<"a:b:c:">> = iolist_to_binary(join(re:split("abc","",[]))),
- <<"">> = iolist_to_binary(join(re:split("acb","a[^a]b",[trim]))),
+ 2}]))),
+ <<"a:b:c:">> = iolist_to_binary(join(re:split("abc","",[]))),
+ <<"">> = iolist_to_binary(join(re:split("acb","a[^a]b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("acb","a[^a]b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("acb","a[^a]b",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("acb","a[^a]b",[]))),
<<"">> = iolist_to_binary(join(re:split("a
-b","a[^a]b",[trim]))),
+b","a[^a]b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a
-b","a[^a]b",[{parts,2}]))),
+b","a[^a]b",[{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("a
-b","a[^a]b",[]))),
- <<"">> = iolist_to_binary(join(re:split("acb","a.b",[trim]))),
+b","a[^a]b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("acb","a.b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("acb","a.b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("acb","a.b",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a.b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("acb","a.b",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a.b",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a.b",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a.b",[]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a.b",[]))),
<<"a
b">> = iolist_to_binary(join(re:split("a
-b","a.b",[trim]))),
+b","a.b",[trim]))),
<<"a
b">> = iolist_to_binary(join(re:split("a
-b","a.b",[{parts,2}]))),
+b","a.b",[{parts,2}]))),
<<"a
b">> = iolist_to_binary(join(re:split("a
-b","a.b",[]))),
+b","a.b",[]))),
<<"">> = iolist_to_binary(join(re:split("acb","a[^a]b",[dotall,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("acb","a[^a]b",[dotall,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("acb","a[^a]b",[dotall]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("acb","a[^a]b",[dotall]))),
<<"">> = iolist_to_binary(join(re:split("a
-b","a[^a]b",[dotall,trim]))),
+b","a[^a]b",[dotall,trim]))),
<<":">> = iolist_to_binary(join(re:split("a
-b","a[^a]b",[dotall,{parts,2}]))),
+b","a[^a]b",[dotall,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("a
-b","a[^a]b",[dotall]))),
+b","a[^a]b",[dotall]))),
ok.
run11() ->
<<"">> = iolist_to_binary(join(re:split("acb","a.b",[dotall,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("acb","a.b",[dotall,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("acb","a.b",[dotall]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("acb","a.b",[dotall]))),
<<"">> = iolist_to_binary(join(re:split("a
-b","a.b",[dotall,trim]))),
+b","a.b",[dotall,trim]))),
<<":">> = iolist_to_binary(join(re:split("a
-b","a.b",[dotall,{parts,2}]))),
+b","a.b",[dotall,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("a
-b","a.b",[dotall]))),
- <<":a">> = iolist_to_binary(join(re:split("bac","^(b+?|a){1,2}?c",[trim]))),
+b","a.b",[dotall]))),
+ <<":a">> = iolist_to_binary(join(re:split("bac","^(b+?|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bac","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bac","^(b+?|a){1,2}?c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bbac","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bac","^(b+?|a){1,2}?c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bbac","^(b+?|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bbac","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bbac","^(b+?|a){1,2}?c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bbbac","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bbac","^(b+?|a){1,2}?c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bbbac","^(b+?|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bbbac","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bbbac","^(b+?|a){1,2}?c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bbbbac","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bbbac","^(b+?|a){1,2}?c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bbbbac","^(b+?|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bbbbac","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bbbbac","^(b+?|a){1,2}?c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bbbbbac","^(b+?|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bbbbac","^(b+?|a){1,2}?c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bbbbbac","^(b+?|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bbbbbac","^(b+?|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bbbbbac","^(b+?|a){1,2}?c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bac","^(b+|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bbbbbac","^(b+?|a){1,2}?c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bac","^(b+|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bac","^(b+|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bac","^(b+|a){1,2}?c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bbac","^(b+|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bac","^(b+|a){1,2}?c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bbac","^(b+|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bbac","^(b+|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bbac","^(b+|a){1,2}?c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bbbac","^(b+|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bbac","^(b+|a){1,2}?c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bbbac","^(b+|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bbbac","^(b+|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bbbac","^(b+|a){1,2}?c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bbbbac","^(b+|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bbbac","^(b+|a){1,2}?c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bbbbac","^(b+|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bbbbac","^(b+|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bbbbac","^(b+|a){1,2}?c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("bbbbbac","^(b+|a){1,2}?c",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bbbbac","^(b+|a){1,2}?c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("bbbbbac","^(b+|a){1,2}?c",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("bbbbbac","^(b+|a){1,2}?c",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("bbbbbac","^(b+|a){1,2}?c",[]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("bbbbbac","^(b+|a){1,2}?c",[]))),
<<"x
b">> = iolist_to_binary(join(re:split("x
-b","(?!\\A)x",[multiline,trim]))),
+b","(?!\\A)x",[multiline,trim]))),
<<"x
b">> = iolist_to_binary(join(re:split("x
-b","(?!\\A)x",[multiline,{parts,2}]))),
+b","(?!\\A)x",[multiline,{parts,2}]))),
<<"x
b">> = iolist_to_binary(join(re:split("x
-b","(?!\\A)x",[multiline]))),
+b","(?!\\A)x",[multiline]))),
<<"a">> = iolist_to_binary(join(re:split("ax","(?!\\A)x",[multiline,
- trim]))),
+ trim]))),
<<"a:">> = iolist_to_binary(join(re:split("ax","(?!\\A)x",[multiline,
{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("ax","(?!\\A)x",[multiline]))),
- <<"{ab}">> = iolist_to_binary(join(re:split("{ab}","\\x0{ab}",[trim]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("ax","(?!\\A)x",[multiline]))),
+ <<"{ab}">> = iolist_to_binary(join(re:split("{ab}","\\x0{ab}",[trim]))),
<<"{ab}">> = iolist_to_binary(join(re:split("{ab}","\\x0{ab}",[{parts,
- 2}]))),
- <<"{ab}">> = iolist_to_binary(join(re:split("{ab}","\\x0{ab}",[]))),
- <<"">> = iolist_to_binary(join(re:split("CD","(A|B)*?CD",[trim]))),
+ 2}]))),
+ <<"{ab}">> = iolist_to_binary(join(re:split("{ab}","\\x0{ab}",[]))),
+ <<"">> = iolist_to_binary(join(re:split("CD","(A|B)*?CD",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("CD","(A|B)*?CD",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("CD","(A|B)*?CD",[]))),
- <<"">> = iolist_to_binary(join(re:split("CD","(A|B)*CD",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("CD","(A|B)*?CD",[]))),
+ <<"">> = iolist_to_binary(join(re:split("CD","(A|B)*CD",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("CD","(A|B)*CD",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("CD","(A|B)*CD",[]))),
- <<":AB:AB">> = iolist_to_binary(join(re:split("ABABAB","(AB)*?\\1",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("CD","(A|B)*CD",[]))),
+ <<":AB:AB">> = iolist_to_binary(join(re:split("ABABAB","(AB)*?\\1",[trim]))),
<<":AB:AB">> = iolist_to_binary(join(re:split("ABABAB","(AB)*?\\1",[{parts,
- 2}]))),
- <<":AB:AB">> = iolist_to_binary(join(re:split("ABABAB","(AB)*?\\1",[]))),
- <<":AB">> = iolist_to_binary(join(re:split("ABABAB","(AB)*\\1",[trim]))),
+ 2}]))),
+ <<":AB:AB">> = iolist_to_binary(join(re:split("ABABAB","(AB)*?\\1",[]))),
+ <<":AB">> = iolist_to_binary(join(re:split("ABABAB","(AB)*\\1",[trim]))),
<<":AB:">> = iolist_to_binary(join(re:split("ABABAB","(AB)*\\1",[{parts,
- 2}]))),
- <<":AB:">> = iolist_to_binary(join(re:split("ABABAB","(AB)*\\1",[]))),
- <<"">> = iolist_to_binary(join(re:split("foo","(?<!bar)foo",[trim]))),
+ 2}]))),
+ <<":AB:">> = iolist_to_binary(join(re:split("ABABAB","(AB)*\\1",[]))),
+ <<"">> = iolist_to_binary(join(re:split("foo","(?<!bar)foo",[trim]))),
<<":">> = iolist_to_binary(join(re:split("foo","(?<!bar)foo",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("foo","(?<!bar)foo",[]))),
- <<"cat:d">> = iolist_to_binary(join(re:split("catfood","(?<!bar)foo",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("foo","(?<!bar)foo",[]))),
+ <<"cat:d">> = iolist_to_binary(join(re:split("catfood","(?<!bar)foo",[trim]))),
<<"cat:d">> = iolist_to_binary(join(re:split("catfood","(?<!bar)foo",[{parts,
- 2}]))),
- <<"cat:d">> = iolist_to_binary(join(re:split("catfood","(?<!bar)foo",[]))),
- <<"ar:tle">> = iolist_to_binary(join(re:split("arfootle","(?<!bar)foo",[trim]))),
+ 2}]))),
+ <<"cat:d">> = iolist_to_binary(join(re:split("catfood","(?<!bar)foo",[]))),
+ <<"ar:tle">> = iolist_to_binary(join(re:split("arfootle","(?<!bar)foo",[trim]))),
<<"ar:tle">> = iolist_to_binary(join(re:split("arfootle","(?<!bar)foo",[{parts,
- 2}]))),
- <<"ar:tle">> = iolist_to_binary(join(re:split("arfootle","(?<!bar)foo",[]))),
- <<"r:sh">> = iolist_to_binary(join(re:split("rfoosh","(?<!bar)foo",[trim]))),
+ 2}]))),
+ <<"ar:tle">> = iolist_to_binary(join(re:split("arfootle","(?<!bar)foo",[]))),
+ <<"r:sh">> = iolist_to_binary(join(re:split("rfoosh","(?<!bar)foo",[trim]))),
<<"r:sh">> = iolist_to_binary(join(re:split("rfoosh","(?<!bar)foo",[{parts,
- 2}]))),
- <<"r:sh">> = iolist_to_binary(join(re:split("rfoosh","(?<!bar)foo",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<!bar)foo",[trim]))),
+ 2}]))),
+ <<"r:sh">> = iolist_to_binary(join(re:split("rfoosh","(?<!bar)foo",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<!bar)foo",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<!bar)foo",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<!bar)foo",[]))),
- <<"barfoo">> = iolist_to_binary(join(re:split("barfoo","(?<!bar)foo",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<!bar)foo",[]))),
+ <<"barfoo">> = iolist_to_binary(join(re:split("barfoo","(?<!bar)foo",[trim]))),
<<"barfoo">> = iolist_to_binary(join(re:split("barfoo","(?<!bar)foo",[{parts,
- 2}]))),
- <<"barfoo">> = iolist_to_binary(join(re:split("barfoo","(?<!bar)foo",[]))),
- <<"towbarfoo">> = iolist_to_binary(join(re:split("towbarfoo","(?<!bar)foo",[trim]))),
+ 2}]))),
+ <<"barfoo">> = iolist_to_binary(join(re:split("barfoo","(?<!bar)foo",[]))),
+ <<"towbarfoo">> = iolist_to_binary(join(re:split("towbarfoo","(?<!bar)foo",[trim]))),
<<"towbarfoo">> = iolist_to_binary(join(re:split("towbarfoo","(?<!bar)foo",[{parts,
- 2}]))),
- <<"towbarfoo">> = iolist_to_binary(join(re:split("towbarfoo","(?<!bar)foo",[]))),
- <<":d">> = iolist_to_binary(join(re:split("catfood","\\w{3}(?<!bar)foo",[trim]))),
+ 2}]))),
+ <<"towbarfoo">> = iolist_to_binary(join(re:split("towbarfoo","(?<!bar)foo",[]))),
+ <<":d">> = iolist_to_binary(join(re:split("catfood","\\w{3}(?<!bar)foo",[trim]))),
<<":d">> = iolist_to_binary(join(re:split("catfood","\\w{3}(?<!bar)foo",[{parts,
- 2}]))),
- <<":d">> = iolist_to_binary(join(re:split("catfood","\\w{3}(?<!bar)foo",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\w{3}(?<!bar)foo",[trim]))),
+ 2}]))),
+ <<":d">> = iolist_to_binary(join(re:split("catfood","\\w{3}(?<!bar)foo",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\w{3}(?<!bar)foo",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\w{3}(?<!bar)foo",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\w{3}(?<!bar)foo",[]))),
- <<"foo">> = iolist_to_binary(join(re:split("foo","\\w{3}(?<!bar)foo",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\w{3}(?<!bar)foo",[]))),
+ <<"foo">> = iolist_to_binary(join(re:split("foo","\\w{3}(?<!bar)foo",[trim]))),
<<"foo">> = iolist_to_binary(join(re:split("foo","\\w{3}(?<!bar)foo",[{parts,
- 2}]))),
- <<"foo">> = iolist_to_binary(join(re:split("foo","\\w{3}(?<!bar)foo",[]))),
- <<"barfoo">> = iolist_to_binary(join(re:split("barfoo","\\w{3}(?<!bar)foo",[trim]))),
+ 2}]))),
+ <<"foo">> = iolist_to_binary(join(re:split("foo","\\w{3}(?<!bar)foo",[]))),
+ <<"barfoo">> = iolist_to_binary(join(re:split("barfoo","\\w{3}(?<!bar)foo",[trim]))),
<<"barfoo">> = iolist_to_binary(join(re:split("barfoo","\\w{3}(?<!bar)foo",[{parts,
- 2}]))),
- <<"barfoo">> = iolist_to_binary(join(re:split("barfoo","\\w{3}(?<!bar)foo",[]))),
- <<"towbarfoo">> = iolist_to_binary(join(re:split("towbarfoo","\\w{3}(?<!bar)foo",[trim]))),
+ 2}]))),
+ <<"barfoo">> = iolist_to_binary(join(re:split("barfoo","\\w{3}(?<!bar)foo",[]))),
+ <<"towbarfoo">> = iolist_to_binary(join(re:split("towbarfoo","\\w{3}(?<!bar)foo",[trim]))),
<<"towbarfoo">> = iolist_to_binary(join(re:split("towbarfoo","\\w{3}(?<!bar)foo",[{parts,
- 2}]))),
- <<"towbarfoo">> = iolist_to_binary(join(re:split("towbarfoo","\\w{3}(?<!bar)foo",[]))),
- <<"fooa:foo">> = iolist_to_binary(join(re:split("fooabar","(?<=(foo)a)bar",[trim]))),
+ 2}]))),
+ <<"towbarfoo">> = iolist_to_binary(join(re:split("towbarfoo","\\w{3}(?<!bar)foo",[]))),
+ <<"fooa:foo">> = iolist_to_binary(join(re:split("fooabar","(?<=(foo)a)bar",[trim]))),
<<"fooa:foo:">> = iolist_to_binary(join(re:split("fooabar","(?<=(foo)a)bar",[{parts,
- 2}]))),
- <<"fooa:foo:">> = iolist_to_binary(join(re:split("fooabar","(?<=(foo)a)bar",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(foo)a)bar",[trim]))),
+ 2}]))),
+ <<"fooa:foo:">> = iolist_to_binary(join(re:split("fooabar","(?<=(foo)a)bar",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(foo)a)bar",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(foo)a)bar",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(foo)a)bar",[]))),
- <<"bar">> = iolist_to_binary(join(re:split("bar","(?<=(foo)a)bar",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(foo)a)bar",[]))),
+ <<"bar">> = iolist_to_binary(join(re:split("bar","(?<=(foo)a)bar",[trim]))),
<<"bar">> = iolist_to_binary(join(re:split("bar","(?<=(foo)a)bar",[{parts,
- 2}]))),
- <<"bar">> = iolist_to_binary(join(re:split("bar","(?<=(foo)a)bar",[]))),
- <<"foobbar">> = iolist_to_binary(join(re:split("foobbar","(?<=(foo)a)bar",[trim]))),
+ 2}]))),
+ <<"bar">> = iolist_to_binary(join(re:split("bar","(?<=(foo)a)bar",[]))),
+ <<"foobbar">> = iolist_to_binary(join(re:split("foobbar","(?<=(foo)a)bar",[trim]))),
<<"foobbar">> = iolist_to_binary(join(re:split("foobbar","(?<=(foo)a)bar",[{parts,
- 2}]))),
- <<"foobbar">> = iolist_to_binary(join(re:split("foobbar","(?<=(foo)a)bar",[]))),
+ 2}]))),
+ <<"foobbar">> = iolist_to_binary(join(re:split("foobbar","(?<=(foo)a)bar",[]))),
<<"">> = iolist_to_binary(join(re:split("abc","\\Aabc\\z",[multiline,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","\\Aabc\\z",[multiline,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","\\Aabc\\z",[multiline]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","\\Aabc\\z",[multiline]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\Aabc\\z",[multiline,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\Aabc\\z",[multiline,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\Aabc\\z",[multiline]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\Aabc\\z",[multiline]))),
<<"">> = iolist_to_binary(join(re:split("abc","\\Aabc\\z",[multiline,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","\\Aabc\\z",[multiline,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","\\Aabc\\z",[multiline]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","\\Aabc\\z",[multiline]))),
<<"qqq
abc">> = iolist_to_binary(join(re:split("qqq
-abc","\\Aabc\\z",[multiline,trim]))),
+abc","\\Aabc\\z",[multiline,trim]))),
<<"qqq
abc">> = iolist_to_binary(join(re:split("qqq
-abc","\\Aabc\\z",[multiline,{parts,2}]))),
+abc","\\Aabc\\z",[multiline,{parts,2}]))),
<<"qqq
abc">> = iolist_to_binary(join(re:split("qqq
-abc","\\Aabc\\z",[multiline]))),
+abc","\\Aabc\\z",[multiline]))),
<<"abc
zzz">> = iolist_to_binary(join(re:split("abc
-zzz","\\Aabc\\z",[multiline,trim]))),
+zzz","\\Aabc\\z",[multiline,trim]))),
<<"abc
zzz">> = iolist_to_binary(join(re:split("abc
-zzz","\\Aabc\\z",[multiline,{parts,2}]))),
+zzz","\\Aabc\\z",[multiline,{parts,2}]))),
<<"abc
zzz">> = iolist_to_binary(join(re:split("abc
-zzz","\\Aabc\\z",[multiline]))),
+zzz","\\Aabc\\z",[multiline]))),
<<"qqq
abc
zzz">> = iolist_to_binary(join(re:split("qqq
abc
-zzz","\\Aabc\\z",[multiline,trim]))),
+zzz","\\Aabc\\z",[multiline,trim]))),
<<"qqq
abc
zzz">> = iolist_to_binary(join(re:split("qqq
abc
-zzz","\\Aabc\\z",[multiline,{parts,2}]))),
+zzz","\\Aabc\\z",[multiline,{parts,2}]))),
<<"qqq
abc
zzz">> = iolist_to_binary(join(re:split("qqq
abc
-zzz","\\Aabc\\z",[multiline]))),
- <<"1:.23">> = iolist_to_binary(join(re:split("1.230003938","(?>(\\.\\d\\d[1-9]?))\\d+",[trim]))),
+zzz","\\Aabc\\z",[multiline]))),
+ <<"1:.23">> = iolist_to_binary(join(re:split("1.230003938","(?>(\\.\\d\\d[1-9]?))\\d+",[trim]))),
<<"1:.23:">> = iolist_to_binary(join(re:split("1.230003938","(?>(\\.\\d\\d[1-9]?))\\d+",[{parts,
- 2}]))),
- <<"1:.23:">> = iolist_to_binary(join(re:split("1.230003938","(?>(\\.\\d\\d[1-9]?))\\d+",[]))),
- <<"1:.875">> = iolist_to_binary(join(re:split("1.875000282","(?>(\\.\\d\\d[1-9]?))\\d+",[trim]))),
+ 2}]))),
+ <<"1:.23:">> = iolist_to_binary(join(re:split("1.230003938","(?>(\\.\\d\\d[1-9]?))\\d+",[]))),
+ <<"1:.875">> = iolist_to_binary(join(re:split("1.875000282","(?>(\\.\\d\\d[1-9]?))\\d+",[trim]))),
<<"1:.875:">> = iolist_to_binary(join(re:split("1.875000282","(?>(\\.\\d\\d[1-9]?))\\d+",[{parts,
- 2}]))),
- <<"1:.875:">> = iolist_to_binary(join(re:split("1.875000282","(?>(\\.\\d\\d[1-9]?))\\d+",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>(\\.\\d\\d[1-9]?))\\d+",[trim]))),
+ 2}]))),
+ <<"1:.875:">> = iolist_to_binary(join(re:split("1.875000282","(?>(\\.\\d\\d[1-9]?))\\d+",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>(\\.\\d\\d[1-9]?))\\d+",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>(\\.\\d\\d[1-9]?))\\d+",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>(\\.\\d\\d[1-9]?))\\d+",[]))),
- <<"1.235">> = iolist_to_binary(join(re:split("1.235","(?>(\\.\\d\\d[1-9]?))\\d+",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>(\\.\\d\\d[1-9]?))\\d+",[]))),
+ <<"1.235">> = iolist_to_binary(join(re:split("1.235","(?>(\\.\\d\\d[1-9]?))\\d+",[trim]))),
<<"1.235">> = iolist_to_binary(join(re:split("1.235","(?>(\\.\\d\\d[1-9]?))\\d+",[{parts,
- 2}]))),
- <<"1.235">> = iolist_to_binary(join(re:split("1.235","(?>(\\.\\d\\d[1-9]?))\\d+",[]))),
- <<":party">> = iolist_to_binary(join(re:split("now is the time for all good men to come to the aid of the party","^((?>\\w+)|(?>\\s+))*$",[trim]))),
+ 2}]))),
+ <<"1.235">> = iolist_to_binary(join(re:split("1.235","(?>(\\.\\d\\d[1-9]?))\\d+",[]))),
+ <<":party">> = iolist_to_binary(join(re:split("now is the time for all good men to come to the aid of the party","^((?>\\w+)|(?>\\s+))*$",[trim]))),
<<":party:">> = iolist_to_binary(join(re:split("now is the time for all good men to come to the aid of the party","^((?>\\w+)|(?>\\s+))*$",[{parts,
- 2}]))),
- <<":party:">> = iolist_to_binary(join(re:split("now is the time for all good men to come to the aid of the party","^((?>\\w+)|(?>\\s+))*$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^((?>\\w+)|(?>\\s+))*$",[trim]))),
+ 2}]))),
+ <<":party:">> = iolist_to_binary(join(re:split("now is the time for all good men to come to the aid of the party","^((?>\\w+)|(?>\\s+))*$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^((?>\\w+)|(?>\\s+))*$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^((?>\\w+)|(?>\\s+))*$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^((?>\\w+)|(?>\\s+))*$",[]))),
- <<"this is not a line with only words and spaces!">> = iolist_to_binary(join(re:split("this is not a line with only words and spaces!","^((?>\\w+)|(?>\\s+))*$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^((?>\\w+)|(?>\\s+))*$",[]))),
+ <<"this is not a line with only words and spaces!">> = iolist_to_binary(join(re:split("this is not a line with only words and spaces!","^((?>\\w+)|(?>\\s+))*$",[trim]))),
<<"this is not a line with only words and spaces!">> = iolist_to_binary(join(re:split("this is not a line with only words and spaces!","^((?>\\w+)|(?>\\s+))*$",[{parts,
- 2}]))),
- <<"this is not a line with only words and spaces!">> = iolist_to_binary(join(re:split("this is not a line with only words and spaces!","^((?>\\w+)|(?>\\s+))*$",[]))),
- <<":12345:a">> = iolist_to_binary(join(re:split("12345a","(\\d+)(\\w)",[trim]))),
+ 2}]))),
+ <<"this is not a line with only words and spaces!">> = iolist_to_binary(join(re:split("this is not a line with only words and spaces!","^((?>\\w+)|(?>\\s+))*$",[]))),
+ <<":12345:a">> = iolist_to_binary(join(re:split("12345a","(\\d+)(\\w)",[trim]))),
<<":12345:a:">> = iolist_to_binary(join(re:split("12345a","(\\d+)(\\w)",[{parts,
- 2}]))),
- <<":12345:a:">> = iolist_to_binary(join(re:split("12345a","(\\d+)(\\w)",[]))),
- <<":1234:5:+">> = iolist_to_binary(join(re:split("12345+","(\\d+)(\\w)",[trim]))),
+ 2}]))),
+ <<":12345:a:">> = iolist_to_binary(join(re:split("12345a","(\\d+)(\\w)",[]))),
+ <<":1234:5:+">> = iolist_to_binary(join(re:split("12345+","(\\d+)(\\w)",[trim]))),
<<":1234:5:+">> = iolist_to_binary(join(re:split("12345+","(\\d+)(\\w)",[{parts,
- 2}]))),
- <<":1234:5:+">> = iolist_to_binary(join(re:split("12345+","(\\d+)(\\w)",[]))),
- <<":12345:a">> = iolist_to_binary(join(re:split("12345a","((?>\\d+))(\\w)",[trim]))),
+ 2}]))),
+ <<":1234:5:+">> = iolist_to_binary(join(re:split("12345+","(\\d+)(\\w)",[]))),
+ <<":12345:a">> = iolist_to_binary(join(re:split("12345a","((?>\\d+))(\\w)",[trim]))),
<<":12345:a:">> = iolist_to_binary(join(re:split("12345a","((?>\\d+))(\\w)",[{parts,
- 2}]))),
- <<":12345:a:">> = iolist_to_binary(join(re:split("12345a","((?>\\d+))(\\w)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?>\\d+))(\\w)",[trim]))),
+ 2}]))),
+ <<":12345:a:">> = iolist_to_binary(join(re:split("12345a","((?>\\d+))(\\w)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?>\\d+))(\\w)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?>\\d+))(\\w)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?>\\d+))(\\w)",[]))),
- <<"12345+">> = iolist_to_binary(join(re:split("12345+","((?>\\d+))(\\w)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?>\\d+))(\\w)",[]))),
+ <<"12345+">> = iolist_to_binary(join(re:split("12345+","((?>\\d+))(\\w)",[trim]))),
<<"12345+">> = iolist_to_binary(join(re:split("12345+","((?>\\d+))(\\w)",[{parts,
- 2}]))),
- <<"12345+">> = iolist_to_binary(join(re:split("12345+","((?>\\d+))(\\w)",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaab","(?>a+)b",[trim]))),
+ 2}]))),
+ <<"12345+">> = iolist_to_binary(join(re:split("12345+","((?>\\d+))(\\w)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaab","(?>a+)b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaab","(?>a+)b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaab","(?>a+)b",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaab","(?>a+)b",[]))),
ok.
run12() ->
- <<":aaab">> = iolist_to_binary(join(re:split("aaab","((?>a+)b)",[trim]))),
+ <<":aaab">> = iolist_to_binary(join(re:split("aaab","((?>a+)b)",[trim]))),
<<":aaab:">> = iolist_to_binary(join(re:split("aaab","((?>a+)b)",[{parts,
- 2}]))),
- <<":aaab:">> = iolist_to_binary(join(re:split("aaab","((?>a+)b)",[]))),
- <<":aaa">> = iolist_to_binary(join(re:split("aaab","(?>(a+))b",[trim]))),
+ 2}]))),
+ <<":aaab:">> = iolist_to_binary(join(re:split("aaab","((?>a+)b)",[]))),
+ <<":aaa">> = iolist_to_binary(join(re:split("aaab","(?>(a+))b",[trim]))),
<<":aaa:">> = iolist_to_binary(join(re:split("aaab","(?>(a+))b",[{parts,
- 2}]))),
- <<":aaa:">> = iolist_to_binary(join(re:split("aaab","(?>(a+))b",[]))),
- <<"aaa:ccc">> = iolist_to_binary(join(re:split("aaabbbccc","(?>b)+",[trim]))),
+ 2}]))),
+ <<":aaa:">> = iolist_to_binary(join(re:split("aaab","(?>(a+))b",[]))),
+ <<"aaa:ccc">> = iolist_to_binary(join(re:split("aaabbbccc","(?>b)+",[trim]))),
<<"aaa:ccc">> = iolist_to_binary(join(re:split("aaabbbccc","(?>b)+",[{parts,
- 2}]))),
- <<"aaa:ccc">> = iolist_to_binary(join(re:split("aaabbbccc","(?>b)+",[]))),
- <<"::::d">> = iolist_to_binary(join(re:split("aaabbbbccccd","(?>a+|b+|c+)*c",[trim]))),
+ 2}]))),
+ <<"aaa:ccc">> = iolist_to_binary(join(re:split("aaabbbccc","(?>b)+",[]))),
+ <<"::::d">> = iolist_to_binary(join(re:split("aaabbbbccccd","(?>a+|b+|c+)*c",[trim]))),
<<":cccd">> = iolist_to_binary(join(re:split("aaabbbbccccd","(?>a+|b+|c+)*c",[{parts,
- 2}]))),
- <<"::::d">> = iolist_to_binary(join(re:split("aaabbbbccccd","(?>a+|b+|c+)*c",[]))),
- <<"((:x">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","((?>[^()]+)|\\([^()]*\\))+",[trim]))),
+ 2}]))),
+ <<"::::d">> = iolist_to_binary(join(re:split("aaabbbbccccd","(?>a+|b+|c+)*c",[]))),
+ <<"((:x">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","((?>[^()]+)|\\([^()]*\\))+",[trim]))),
<<"((:x:">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","((?>[^()]+)|\\([^()]*\\))+",[{parts,
- 2}]))),
- <<"((:x:">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","((?>[^()]+)|\\([^()]*\\))+",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("(abc)","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[trim]))),
+ 2}]))),
+ <<"((:x:">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","((?>[^()]+)|\\([^()]*\\))+",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("(abc)","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("(abc)","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("(abc)","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[]))),
- <<":xyz">> = iolist_to_binary(join(re:split("(abc(def)xyz)","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("(abc)","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[]))),
+ <<":xyz">> = iolist_to_binary(join(re:split("(abc(def)xyz)","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[trim]))),
<<":xyz:">> = iolist_to_binary(join(re:split("(abc(def)xyz)","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[{parts,
- 2}]))),
- <<":xyz:">> = iolist_to_binary(join(re:split("(abc(def)xyz)","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[trim]))),
+ 2}]))),
+ <<":xyz:">> = iolist_to_binary(join(re:split("(abc(def)xyz)","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[]))),
- <<"((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[]))),
+ <<"((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[trim]))),
<<"((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[{parts,
- 2}]))),
- <<"((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[]))),
+ 2}]))),
+ <<"((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","\\(((?>[^()]+)|\\([^()]+\\))+\\)",[]))),
<<"">> = iolist_to_binary(join(re:split("ab","a(?-i)b",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ab","a(?-i)b",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab","a(?-i)b",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab","a(?-i)b",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("Ab","a(?-i)b",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("Ab","a(?-i)b",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("Ab","a(?-i)b",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("Ab","a(?-i)b",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?-i)b",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?-i)b",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?-i)b",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?-i)b",[caseless]))),
<<"aB">> = iolist_to_binary(join(re:split("aB","a(?-i)b",[caseless,
- trim]))),
+ trim]))),
<<"aB">> = iolist_to_binary(join(re:split("aB","a(?-i)b",[caseless,
{parts,
- 2}]))),
- <<"aB">> = iolist_to_binary(join(re:split("aB","a(?-i)b",[caseless]))),
+ 2}]))),
+ <<"aB">> = iolist_to_binary(join(re:split("aB","a(?-i)b",[caseless]))),
<<"AB">> = iolist_to_binary(join(re:split("AB","a(?-i)b",[caseless,
- trim]))),
+ trim]))),
<<"AB">> = iolist_to_binary(join(re:split("AB","a(?-i)b",[caseless,
{parts,
- 2}]))),
- <<"AB">> = iolist_to_binary(join(re:split("AB","a(?-i)b",[caseless]))),
- <<":a bc">> = iolist_to_binary(join(re:split("a bcd e","(a (?x)b c)d e",[trim]))),
+ 2}]))),
+ <<"AB">> = iolist_to_binary(join(re:split("AB","a(?-i)b",[caseless]))),
+ <<":a bc">> = iolist_to_binary(join(re:split("a bcd e","(a (?x)b c)d e",[trim]))),
<<":a bc:">> = iolist_to_binary(join(re:split("a bcd e","(a (?x)b c)d e",[{parts,
- 2}]))),
- <<":a bc:">> = iolist_to_binary(join(re:split("a bcd e","(a (?x)b c)d e",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a (?x)b c)d e",[trim]))),
+ 2}]))),
+ <<":a bc:">> = iolist_to_binary(join(re:split("a bcd e","(a (?x)b c)d e",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a (?x)b c)d e",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a (?x)b c)d e",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a (?x)b c)d e",[]))),
- <<"a b cd e">> = iolist_to_binary(join(re:split("a b cd e","(a (?x)b c)d e",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a (?x)b c)d e",[]))),
+ <<"a b cd e">> = iolist_to_binary(join(re:split("a b cd e","(a (?x)b c)d e",[trim]))),
<<"a b cd e">> = iolist_to_binary(join(re:split("a b cd e","(a (?x)b c)d e",[{parts,
- 2}]))),
- <<"a b cd e">> = iolist_to_binary(join(re:split("a b cd e","(a (?x)b c)d e",[]))),
- <<"abcd e">> = iolist_to_binary(join(re:split("abcd e","(a (?x)b c)d e",[trim]))),
+ 2}]))),
+ <<"a b cd e">> = iolist_to_binary(join(re:split("a b cd e","(a (?x)b c)d e",[]))),
+ <<"abcd e">> = iolist_to_binary(join(re:split("abcd e","(a (?x)b c)d e",[trim]))),
<<"abcd e">> = iolist_to_binary(join(re:split("abcd e","(a (?x)b c)d e",[{parts,
- 2}]))),
- <<"abcd e">> = iolist_to_binary(join(re:split("abcd e","(a (?x)b c)d e",[]))),
- <<"a bcde">> = iolist_to_binary(join(re:split("a bcde","(a (?x)b c)d e",[trim]))),
+ 2}]))),
+ <<"abcd e">> = iolist_to_binary(join(re:split("abcd e","(a (?x)b c)d e",[]))),
+ <<"a bcde">> = iolist_to_binary(join(re:split("a bcde","(a (?x)b c)d e",[trim]))),
<<"a bcde">> = iolist_to_binary(join(re:split("a bcde","(a (?x)b c)d e",[{parts,
- 2}]))),
- <<"a bcde">> = iolist_to_binary(join(re:split("a bcde","(a (?x)b c)d e",[]))),
- <<":a bcde f">> = iolist_to_binary(join(re:split("a bcde f","(a b(?x)c d (?-x)e f)",[trim]))),
+ 2}]))),
+ <<"a bcde">> = iolist_to_binary(join(re:split("a bcde","(a (?x)b c)d e",[]))),
+ <<":a bcde f">> = iolist_to_binary(join(re:split("a bcde f","(a b(?x)c d (?-x)e f)",[trim]))),
<<":a bcde f:">> = iolist_to_binary(join(re:split("a bcde f","(a b(?x)c d (?-x)e f)",[{parts,
- 2}]))),
- <<":a bcde f:">> = iolist_to_binary(join(re:split("a bcde f","(a b(?x)c d (?-x)e f)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a b(?x)c d (?-x)e f)",[trim]))),
+ 2}]))),
+ <<":a bcde f:">> = iolist_to_binary(join(re:split("a bcde f","(a b(?x)c d (?-x)e f)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a b(?x)c d (?-x)e f)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a b(?x)c d (?-x)e f)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a b(?x)c d (?-x)e f)",[]))),
- <<"abcdef">> = iolist_to_binary(join(re:split("abcdef","(a b(?x)c d (?-x)e f)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a b(?x)c d (?-x)e f)",[]))),
+ <<"abcdef">> = iolist_to_binary(join(re:split("abcdef","(a b(?x)c d (?-x)e f)",[trim]))),
<<"abcdef">> = iolist_to_binary(join(re:split("abcdef","(a b(?x)c d (?-x)e f)",[{parts,
- 2}]))),
- <<"abcdef">> = iolist_to_binary(join(re:split("abcdef","(a b(?x)c d (?-x)e f)",[]))),
- <<":ab">> = iolist_to_binary(join(re:split("abc","(a(?i)b)c",[trim]))),
+ 2}]))),
+ <<"abcdef">> = iolist_to_binary(join(re:split("abcdef","(a b(?x)c d (?-x)e f)",[]))),
+ <<":ab">> = iolist_to_binary(join(re:split("abc","(a(?i)b)c",[trim]))),
<<":ab:">> = iolist_to_binary(join(re:split("abc","(a(?i)b)c",[{parts,
- 2}]))),
- <<":ab:">> = iolist_to_binary(join(re:split("abc","(a(?i)b)c",[]))),
- <<":aB">> = iolist_to_binary(join(re:split("aBc","(a(?i)b)c",[trim]))),
+ 2}]))),
+ <<":ab:">> = iolist_to_binary(join(re:split("abc","(a(?i)b)c",[]))),
+ <<":aB">> = iolist_to_binary(join(re:split("aBc","(a(?i)b)c",[trim]))),
<<":aB:">> = iolist_to_binary(join(re:split("aBc","(a(?i)b)c",[{parts,
- 2}]))),
- <<":aB:">> = iolist_to_binary(join(re:split("aBc","(a(?i)b)c",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a(?i)b)c",[trim]))),
+ 2}]))),
+ <<":aB:">> = iolist_to_binary(join(re:split("aBc","(a(?i)b)c",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a(?i)b)c",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a(?i)b)c",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a(?i)b)c",[]))),
- <<"abC">> = iolist_to_binary(join(re:split("abC","(a(?i)b)c",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a(?i)b)c",[]))),
+ <<"abC">> = iolist_to_binary(join(re:split("abC","(a(?i)b)c",[trim]))),
<<"abC">> = iolist_to_binary(join(re:split("abC","(a(?i)b)c",[{parts,
- 2}]))),
- <<"abC">> = iolist_to_binary(join(re:split("abC","(a(?i)b)c",[]))),
- <<"aBC">> = iolist_to_binary(join(re:split("aBC","(a(?i)b)c",[trim]))),
+ 2}]))),
+ <<"abC">> = iolist_to_binary(join(re:split("abC","(a(?i)b)c",[]))),
+ <<"aBC">> = iolist_to_binary(join(re:split("aBC","(a(?i)b)c",[trim]))),
<<"aBC">> = iolist_to_binary(join(re:split("aBC","(a(?i)b)c",[{parts,
- 2}]))),
- <<"aBC">> = iolist_to_binary(join(re:split("aBC","(a(?i)b)c",[]))),
- <<"Abc">> = iolist_to_binary(join(re:split("Abc","(a(?i)b)c",[trim]))),
+ 2}]))),
+ <<"aBC">> = iolist_to_binary(join(re:split("aBC","(a(?i)b)c",[]))),
+ <<"Abc">> = iolist_to_binary(join(re:split("Abc","(a(?i)b)c",[trim]))),
<<"Abc">> = iolist_to_binary(join(re:split("Abc","(a(?i)b)c",[{parts,
- 2}]))),
- <<"Abc">> = iolist_to_binary(join(re:split("Abc","(a(?i)b)c",[]))),
- <<"ABc">> = iolist_to_binary(join(re:split("ABc","(a(?i)b)c",[trim]))),
+ 2}]))),
+ <<"Abc">> = iolist_to_binary(join(re:split("Abc","(a(?i)b)c",[]))),
+ <<"ABc">> = iolist_to_binary(join(re:split("ABc","(a(?i)b)c",[trim]))),
<<"ABc">> = iolist_to_binary(join(re:split("ABc","(a(?i)b)c",[{parts,
- 2}]))),
- <<"ABc">> = iolist_to_binary(join(re:split("ABc","(a(?i)b)c",[]))),
- <<"ABC">> = iolist_to_binary(join(re:split("ABC","(a(?i)b)c",[trim]))),
+ 2}]))),
+ <<"ABc">> = iolist_to_binary(join(re:split("ABc","(a(?i)b)c",[]))),
+ <<"ABC">> = iolist_to_binary(join(re:split("ABC","(a(?i)b)c",[trim]))),
<<"ABC">> = iolist_to_binary(join(re:split("ABC","(a(?i)b)c",[{parts,
- 2}]))),
- <<"ABC">> = iolist_to_binary(join(re:split("ABC","(a(?i)b)c",[]))),
- <<"AbC">> = iolist_to_binary(join(re:split("AbC","(a(?i)b)c",[trim]))),
+ 2}]))),
+ <<"ABC">> = iolist_to_binary(join(re:split("ABC","(a(?i)b)c",[]))),
+ <<"AbC">> = iolist_to_binary(join(re:split("AbC","(a(?i)b)c",[trim]))),
<<"AbC">> = iolist_to_binary(join(re:split("AbC","(a(?i)b)c",[{parts,
- 2}]))),
- <<"AbC">> = iolist_to_binary(join(re:split("AbC","(a(?i)b)c",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","a(?i:b)c",[trim]))),
+ 2}]))),
+ <<"AbC">> = iolist_to_binary(join(re:split("AbC","(a(?i)b)c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","a(?i:b)c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","a(?i:b)c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","a(?i:b)c",[]))),
- <<"">> = iolist_to_binary(join(re:split("aBc","a(?i:b)c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","a(?i:b)c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aBc","a(?i:b)c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aBc","a(?i:b)c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aBc","a(?i:b)c",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?i:b)c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aBc","a(?i:b)c",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?i:b)c",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?i:b)c",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?i:b)c",[]))),
- <<"ABC">> = iolist_to_binary(join(re:split("ABC","a(?i:b)c",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?i:b)c",[]))),
+ <<"ABC">> = iolist_to_binary(join(re:split("ABC","a(?i:b)c",[trim]))),
<<"ABC">> = iolist_to_binary(join(re:split("ABC","a(?i:b)c",[{parts,
- 2}]))),
- <<"ABC">> = iolist_to_binary(join(re:split("ABC","a(?i:b)c",[]))),
- <<"abC">> = iolist_to_binary(join(re:split("abC","a(?i:b)c",[trim]))),
+ 2}]))),
+ <<"ABC">> = iolist_to_binary(join(re:split("ABC","a(?i:b)c",[]))),
+ <<"abC">> = iolist_to_binary(join(re:split("abC","a(?i:b)c",[trim]))),
<<"abC">> = iolist_to_binary(join(re:split("abC","a(?i:b)c",[{parts,
- 2}]))),
- <<"abC">> = iolist_to_binary(join(re:split("abC","a(?i:b)c",[]))),
- <<"aBC">> = iolist_to_binary(join(re:split("aBC","a(?i:b)c",[trim]))),
+ 2}]))),
+ <<"abC">> = iolist_to_binary(join(re:split("abC","a(?i:b)c",[]))),
+ <<"aBC">> = iolist_to_binary(join(re:split("aBC","a(?i:b)c",[trim]))),
<<"aBC">> = iolist_to_binary(join(re:split("aBC","a(?i:b)c",[{parts,
- 2}]))),
- <<"aBC">> = iolist_to_binary(join(re:split("aBC","a(?i:b)c",[]))),
- <<"">> = iolist_to_binary(join(re:split("aBc","a(?i:b)*c",[trim]))),
+ 2}]))),
+ <<"aBC">> = iolist_to_binary(join(re:split("aBC","a(?i:b)c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aBc","a(?i:b)*c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aBc","a(?i:b)*c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aBc","a(?i:b)*c",[]))),
- <<"">> = iolist_to_binary(join(re:split("aBBc","a(?i:b)*c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aBc","a(?i:b)*c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aBBc","a(?i:b)*c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aBBc","a(?i:b)*c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aBBc","a(?i:b)*c",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?i:b)*c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aBBc","a(?i:b)*c",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?i:b)*c",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?i:b)*c",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?i:b)*c",[]))),
- <<"aBC">> = iolist_to_binary(join(re:split("aBC","a(?i:b)*c",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?i:b)*c",[]))),
+ <<"aBC">> = iolist_to_binary(join(re:split("aBC","a(?i:b)*c",[trim]))),
<<"aBC">> = iolist_to_binary(join(re:split("aBC","a(?i:b)*c",[{parts,
- 2}]))),
- <<"aBC">> = iolist_to_binary(join(re:split("aBC","a(?i:b)*c",[]))),
- <<"aBBC">> = iolist_to_binary(join(re:split("aBBC","a(?i:b)*c",[trim]))),
+ 2}]))),
+ <<"aBC">> = iolist_to_binary(join(re:split("aBC","a(?i:b)*c",[]))),
+ <<"aBBC">> = iolist_to_binary(join(re:split("aBBC","a(?i:b)*c",[trim]))),
<<"aBBC">> = iolist_to_binary(join(re:split("aBBC","a(?i:b)*c",[{parts,
- 2}]))),
- <<"aBBC">> = iolist_to_binary(join(re:split("aBBC","a(?i:b)*c",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcd","a(?=b(?i)c)\\w\\wd",[trim]))),
+ 2}]))),
+ <<"aBBC">> = iolist_to_binary(join(re:split("aBBC","a(?i:b)*c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcd","a(?=b(?i)c)\\w\\wd",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcd","a(?=b(?i)c)\\w\\wd",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcd","a(?=b(?i)c)\\w\\wd",[]))),
- <<"">> = iolist_to_binary(join(re:split("abCd","a(?=b(?i)c)\\w\\wd",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcd","a(?=b(?i)c)\\w\\wd",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abCd","a(?=b(?i)c)\\w\\wd",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abCd","a(?=b(?i)c)\\w\\wd",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abCd","a(?=b(?i)c)\\w\\wd",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?=b(?i)c)\\w\\wd",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abCd","a(?=b(?i)c)\\w\\wd",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?=b(?i)c)\\w\\wd",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?=b(?i)c)\\w\\wd",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?=b(?i)c)\\w\\wd",[]))),
- <<"aBCd">> = iolist_to_binary(join(re:split("aBCd","a(?=b(?i)c)\\w\\wd",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?=b(?i)c)\\w\\wd",[]))),
+ <<"aBCd">> = iolist_to_binary(join(re:split("aBCd","a(?=b(?i)c)\\w\\wd",[trim]))),
<<"aBCd">> = iolist_to_binary(join(re:split("aBCd","a(?=b(?i)c)\\w\\wd",[{parts,
- 2}]))),
- <<"aBCd">> = iolist_to_binary(join(re:split("aBCd","a(?=b(?i)c)\\w\\wd",[]))),
- <<"abcD">> = iolist_to_binary(join(re:split("abcD","a(?=b(?i)c)\\w\\wd",[trim]))),
+ 2}]))),
+ <<"aBCd">> = iolist_to_binary(join(re:split("aBCd","a(?=b(?i)c)\\w\\wd",[]))),
+ <<"abcD">> = iolist_to_binary(join(re:split("abcD","a(?=b(?i)c)\\w\\wd",[trim]))),
<<"abcD">> = iolist_to_binary(join(re:split("abcD","a(?=b(?i)c)\\w\\wd",[{parts,
- 2}]))),
- <<"abcD">> = iolist_to_binary(join(re:split("abcD","a(?=b(?i)c)\\w\\wd",[]))),
+ 2}]))),
+ <<"abcD">> = iolist_to_binary(join(re:split("abcD","a(?=b(?i)c)\\w\\wd",[]))),
<<"">> = iolist_to_binary(join(re:split("more than million","(?s-i:more.*than).*million",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("more than million","(?s-i:more.*than).*million",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("more than million","(?s-i:more.*than).*million",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("more than million","(?s-i:more.*than).*million",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("more than MILLION","(?s-i:more.*than).*million",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("more than MILLION","(?s-i:more.*than).*million",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("more than MILLION","(?s-i:more.*than).*million",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("more than MILLION","(?s-i:more.*than).*million",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("more
- than Million","(?s-i:more.*than).*million",[caseless,trim]))),
+ than Million","(?s-i:more.*than).*million",[caseless,trim]))),
<<":">> = iolist_to_binary(join(re:split("more
- than Million","(?s-i:more.*than).*million",[caseless,{parts,2}]))),
+ than Million","(?s-i:more.*than).*million",[caseless,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("more
- than Million","(?s-i:more.*than).*million",[caseless]))),
+ than Million","(?s-i:more.*than).*million",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s-i:more.*than).*million",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s-i:more.*than).*million",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s-i:more.*than).*million",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?s-i:more.*than).*million",[caseless]))),
<<"MORE THAN MILLION">> = iolist_to_binary(join(re:split("MORE THAN MILLION","(?s-i:more.*than).*million",[caseless,
- trim]))),
+ trim]))),
<<"MORE THAN MILLION">> = iolist_to_binary(join(re:split("MORE THAN MILLION","(?s-i:more.*than).*million",[caseless,
{parts,
- 2}]))),
- <<"MORE THAN MILLION">> = iolist_to_binary(join(re:split("MORE THAN MILLION","(?s-i:more.*than).*million",[caseless]))),
+ 2}]))),
+ <<"MORE THAN MILLION">> = iolist_to_binary(join(re:split("MORE THAN MILLION","(?s-i:more.*than).*million",[caseless]))),
<<"more
than
million">> = iolist_to_binary(join(re:split("more
than
- million","(?s-i:more.*than).*million",[caseless,trim]))),
+ million","(?s-i:more.*than).*million",[caseless,trim]))),
<<"more
than
million">> = iolist_to_binary(join(re:split("more
than
- million","(?s-i:more.*than).*million",[caseless,{parts,2}]))),
+ million","(?s-i:more.*than).*million",[caseless,{parts,2}]))),
<<"more
than
million">> = iolist_to_binary(join(re:split("more
than
- million","(?s-i:more.*than).*million",[caseless]))),
+ million","(?s-i:more.*than).*million",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("more than million","(?:(?s-i)more.*than).*million",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("more than million","(?:(?s-i)more.*than).*million",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("more than million","(?:(?s-i)more.*than).*million",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("more than million","(?:(?s-i)more.*than).*million",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("more than MILLION","(?:(?s-i)more.*than).*million",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("more than MILLION","(?:(?s-i)more.*than).*million",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("more than MILLION","(?:(?s-i)more.*than).*million",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("more than MILLION","(?:(?s-i)more.*than).*million",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("more
- than Million","(?:(?s-i)more.*than).*million",[caseless,trim]))),
+ than Million","(?:(?s-i)more.*than).*million",[caseless,trim]))),
<<":">> = iolist_to_binary(join(re:split("more
- than Million","(?:(?s-i)more.*than).*million",[caseless,{parts,2}]))),
+ than Million","(?:(?s-i)more.*than).*million",[caseless,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("more
- than Million","(?:(?s-i)more.*than).*million",[caseless]))),
+ than Million","(?:(?s-i)more.*than).*million",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?s-i)more.*than).*million",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?s-i)more.*than).*million",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?s-i)more.*than).*million",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?s-i)more.*than).*million",[caseless]))),
<<"MORE THAN MILLION">> = iolist_to_binary(join(re:split("MORE THAN MILLION","(?:(?s-i)more.*than).*million",[caseless,
- trim]))),
+ trim]))),
<<"MORE THAN MILLION">> = iolist_to_binary(join(re:split("MORE THAN MILLION","(?:(?s-i)more.*than).*million",[caseless,
{parts,
- 2}]))),
- <<"MORE THAN MILLION">> = iolist_to_binary(join(re:split("MORE THAN MILLION","(?:(?s-i)more.*than).*million",[caseless]))),
+ 2}]))),
+ <<"MORE THAN MILLION">> = iolist_to_binary(join(re:split("MORE THAN MILLION","(?:(?s-i)more.*than).*million",[caseless]))),
<<"more
than
million">> = iolist_to_binary(join(re:split("more
than
- million","(?:(?s-i)more.*than).*million",[caseless,trim]))),
+ million","(?:(?s-i)more.*than).*million",[caseless,trim]))),
<<"more
than
million">> = iolist_to_binary(join(re:split("more
than
- million","(?:(?s-i)more.*than).*million",[caseless,{parts,2}]))),
+ million","(?:(?s-i)more.*than).*million",[caseless,{parts,2}]))),
<<"more
than
million">> = iolist_to_binary(join(re:split("more
than
- million","(?:(?s-i)more.*than).*million",[caseless]))),
- <<"">> = iolist_to_binary(join(re:split("abc","(?>a(?i)b+)+c",[trim]))),
+ million","(?:(?s-i)more.*than).*million",[caseless]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","(?>a(?i)b+)+c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","(?>a(?i)b+)+c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","(?>a(?i)b+)+c",[]))),
- <<"">> = iolist_to_binary(join(re:split("aBbc","(?>a(?i)b+)+c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","(?>a(?i)b+)+c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aBbc","(?>a(?i)b+)+c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aBbc","(?>a(?i)b+)+c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aBbc","(?>a(?i)b+)+c",[]))),
- <<"">> = iolist_to_binary(join(re:split("aBBc","(?>a(?i)b+)+c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aBbc","(?>a(?i)b+)+c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aBBc","(?>a(?i)b+)+c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aBBc","(?>a(?i)b+)+c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aBBc","(?>a(?i)b+)+c",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>a(?i)b+)+c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aBBc","(?>a(?i)b+)+c",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>a(?i)b+)+c",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>a(?i)b+)+c",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>a(?i)b+)+c",[]))),
- <<"Abc">> = iolist_to_binary(join(re:split("Abc","(?>a(?i)b+)+c",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>a(?i)b+)+c",[]))),
+ <<"Abc">> = iolist_to_binary(join(re:split("Abc","(?>a(?i)b+)+c",[trim]))),
<<"Abc">> = iolist_to_binary(join(re:split("Abc","(?>a(?i)b+)+c",[{parts,
- 2}]))),
- <<"Abc">> = iolist_to_binary(join(re:split("Abc","(?>a(?i)b+)+c",[]))),
- <<"abAb">> = iolist_to_binary(join(re:split("abAb","(?>a(?i)b+)+c",[trim]))),
+ 2}]))),
+ <<"Abc">> = iolist_to_binary(join(re:split("Abc","(?>a(?i)b+)+c",[]))),
+ <<"abAb">> = iolist_to_binary(join(re:split("abAb","(?>a(?i)b+)+c",[trim]))),
<<"abAb">> = iolist_to_binary(join(re:split("abAb","(?>a(?i)b+)+c",[{parts,
- 2}]))),
- <<"abAb">> = iolist_to_binary(join(re:split("abAb","(?>a(?i)b+)+c",[]))),
- <<"abbC">> = iolist_to_binary(join(re:split("abbC","(?>a(?i)b+)+c",[trim]))),
+ 2}]))),
+ <<"abAb">> = iolist_to_binary(join(re:split("abAb","(?>a(?i)b+)+c",[]))),
+ <<"abbC">> = iolist_to_binary(join(re:split("abbC","(?>a(?i)b+)+c",[trim]))),
<<"abbC">> = iolist_to_binary(join(re:split("abbC","(?>a(?i)b+)+c",[{parts,
- 2}]))),
- <<"abbC">> = iolist_to_binary(join(re:split("abbC","(?>a(?i)b+)+c",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","(?=a(?i)b)\\w\\wc",[trim]))),
+ 2}]))),
+ <<"abbC">> = iolist_to_binary(join(re:split("abbC","(?>a(?i)b+)+c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","(?=a(?i)b)\\w\\wc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","(?=a(?i)b)\\w\\wc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","(?=a(?i)b)\\w\\wc",[]))),
- <<"">> = iolist_to_binary(join(re:split("aBc","(?=a(?i)b)\\w\\wc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","(?=a(?i)b)\\w\\wc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aBc","(?=a(?i)b)\\w\\wc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aBc","(?=a(?i)b)\\w\\wc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aBc","(?=a(?i)b)\\w\\wc",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?=a(?i)b)\\w\\wc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aBc","(?=a(?i)b)\\w\\wc",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?=a(?i)b)\\w\\wc",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?=a(?i)b)\\w\\wc",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?=a(?i)b)\\w\\wc",[]))),
- <<"Ab">> = iolist_to_binary(join(re:split("Ab","(?=a(?i)b)\\w\\wc",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?=a(?i)b)\\w\\wc",[]))),
+ <<"Ab">> = iolist_to_binary(join(re:split("Ab","(?=a(?i)b)\\w\\wc",[trim]))),
<<"Ab">> = iolist_to_binary(join(re:split("Ab","(?=a(?i)b)\\w\\wc",[{parts,
- 2}]))),
- <<"Ab">> = iolist_to_binary(join(re:split("Ab","(?=a(?i)b)\\w\\wc",[]))),
- <<"abC">> = iolist_to_binary(join(re:split("abC","(?=a(?i)b)\\w\\wc",[trim]))),
+ 2}]))),
+ <<"Ab">> = iolist_to_binary(join(re:split("Ab","(?=a(?i)b)\\w\\wc",[]))),
+ <<"abC">> = iolist_to_binary(join(re:split("abC","(?=a(?i)b)\\w\\wc",[trim]))),
<<"abC">> = iolist_to_binary(join(re:split("abC","(?=a(?i)b)\\w\\wc",[{parts,
- 2}]))),
- <<"abC">> = iolist_to_binary(join(re:split("abC","(?=a(?i)b)\\w\\wc",[]))),
- <<"aBC">> = iolist_to_binary(join(re:split("aBC","(?=a(?i)b)\\w\\wc",[trim]))),
+ 2}]))),
+ <<"abC">> = iolist_to_binary(join(re:split("abC","(?=a(?i)b)\\w\\wc",[]))),
+ <<"aBC">> = iolist_to_binary(join(re:split("aBC","(?=a(?i)b)\\w\\wc",[trim]))),
<<"aBC">> = iolist_to_binary(join(re:split("aBC","(?=a(?i)b)\\w\\wc",[{parts,
- 2}]))),
- <<"aBC">> = iolist_to_binary(join(re:split("aBC","(?=a(?i)b)\\w\\wc",[]))),
- <<"ab:xx">> = iolist_to_binary(join(re:split("abxxc","(?<=a(?i)b)(\\w\\w)c",[trim]))),
+ 2}]))),
+ <<"aBC">> = iolist_to_binary(join(re:split("aBC","(?=a(?i)b)\\w\\wc",[]))),
+ <<"ab:xx">> = iolist_to_binary(join(re:split("abxxc","(?<=a(?i)b)(\\w\\w)c",[trim]))),
<<"ab:xx:">> = iolist_to_binary(join(re:split("abxxc","(?<=a(?i)b)(\\w\\w)c",[{parts,
- 2}]))),
- <<"ab:xx:">> = iolist_to_binary(join(re:split("abxxc","(?<=a(?i)b)(\\w\\w)c",[]))),
- <<"aB:xx">> = iolist_to_binary(join(re:split("aBxxc","(?<=a(?i)b)(\\w\\w)c",[trim]))),
+ 2}]))),
+ <<"ab:xx:">> = iolist_to_binary(join(re:split("abxxc","(?<=a(?i)b)(\\w\\w)c",[]))),
+ <<"aB:xx">> = iolist_to_binary(join(re:split("aBxxc","(?<=a(?i)b)(\\w\\w)c",[trim]))),
<<"aB:xx:">> = iolist_to_binary(join(re:split("aBxxc","(?<=a(?i)b)(\\w\\w)c",[{parts,
- 2}]))),
- <<"aB:xx:">> = iolist_to_binary(join(re:split("aBxxc","(?<=a(?i)b)(\\w\\w)c",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=a(?i)b)(\\w\\w)c",[trim]))),
+ 2}]))),
+ <<"aB:xx:">> = iolist_to_binary(join(re:split("aBxxc","(?<=a(?i)b)(\\w\\w)c",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=a(?i)b)(\\w\\w)c",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=a(?i)b)(\\w\\w)c",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=a(?i)b)(\\w\\w)c",[]))),
- <<"Abxxc">> = iolist_to_binary(join(re:split("Abxxc","(?<=a(?i)b)(\\w\\w)c",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=a(?i)b)(\\w\\w)c",[]))),
+ <<"Abxxc">> = iolist_to_binary(join(re:split("Abxxc","(?<=a(?i)b)(\\w\\w)c",[trim]))),
<<"Abxxc">> = iolist_to_binary(join(re:split("Abxxc","(?<=a(?i)b)(\\w\\w)c",[{parts,
- 2}]))),
- <<"Abxxc">> = iolist_to_binary(join(re:split("Abxxc","(?<=a(?i)b)(\\w\\w)c",[]))),
- <<"ABxxc">> = iolist_to_binary(join(re:split("ABxxc","(?<=a(?i)b)(\\w\\w)c",[trim]))),
+ 2}]))),
+ <<"Abxxc">> = iolist_to_binary(join(re:split("Abxxc","(?<=a(?i)b)(\\w\\w)c",[]))),
+ <<"ABxxc">> = iolist_to_binary(join(re:split("ABxxc","(?<=a(?i)b)(\\w\\w)c",[trim]))),
<<"ABxxc">> = iolist_to_binary(join(re:split("ABxxc","(?<=a(?i)b)(\\w\\w)c",[{parts,
- 2}]))),
- <<"ABxxc">> = iolist_to_binary(join(re:split("ABxxc","(?<=a(?i)b)(\\w\\w)c",[]))),
- <<"abxxC">> = iolist_to_binary(join(re:split("abxxC","(?<=a(?i)b)(\\w\\w)c",[trim]))),
+ 2}]))),
+ <<"ABxxc">> = iolist_to_binary(join(re:split("ABxxc","(?<=a(?i)b)(\\w\\w)c",[]))),
+ <<"abxxC">> = iolist_to_binary(join(re:split("abxxC","(?<=a(?i)b)(\\w\\w)c",[trim]))),
<<"abxxC">> = iolist_to_binary(join(re:split("abxxC","(?<=a(?i)b)(\\w\\w)c",[{parts,
- 2}]))),
- <<"abxxC">> = iolist_to_binary(join(re:split("abxxC","(?<=a(?i)b)(\\w\\w)c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aA","(?:(a)|b)(?(1)A|B)",[trim]))),
+ 2}]))),
+ <<"abxxC">> = iolist_to_binary(join(re:split("abxxC","(?<=a(?i)b)(\\w\\w)c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aA","(?:(a)|b)(?(1)A|B)",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aA","(?:(a)|b)(?(1)A|B)",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aA","(?:(a)|b)(?(1)A|B)",[]))),
- <<"">> = iolist_to_binary(join(re:split("bB","(?:(a)|b)(?(1)A|B)",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aA","(?:(a)|b)(?(1)A|B)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("bB","(?:(a)|b)(?(1)A|B)",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("bB","(?:(a)|b)(?(1)A|B)",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("bB","(?:(a)|b)(?(1)A|B)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(a)|b)(?(1)A|B)",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("bB","(?:(a)|b)(?(1)A|B)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(a)|b)(?(1)A|B)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(a)|b)(?(1)A|B)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(a)|b)(?(1)A|B)",[]))),
- <<"aB">> = iolist_to_binary(join(re:split("aB","(?:(a)|b)(?(1)A|B)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(a)|b)(?(1)A|B)",[]))),
+ <<"aB">> = iolist_to_binary(join(re:split("aB","(?:(a)|b)(?(1)A|B)",[trim]))),
<<"aB">> = iolist_to_binary(join(re:split("aB","(?:(a)|b)(?(1)A|B)",[{parts,
- 2}]))),
- <<"aB">> = iolist_to_binary(join(re:split("aB","(?:(a)|b)(?(1)A|B)",[]))),
- <<"bA">> = iolist_to_binary(join(re:split("bA","(?:(a)|b)(?(1)A|B)",[trim]))),
+ 2}]))),
+ <<"aB">> = iolist_to_binary(join(re:split("aB","(?:(a)|b)(?(1)A|B)",[]))),
+ <<"bA">> = iolist_to_binary(join(re:split("bA","(?:(a)|b)(?(1)A|B)",[trim]))),
<<"bA">> = iolist_to_binary(join(re:split("bA","(?:(a)|b)(?(1)A|B)",[{parts,
- 2}]))),
- <<"bA">> = iolist_to_binary(join(re:split("bA","(?:(a)|b)(?(1)A|B)",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aa","^(a)?(?(1)a|b)+$",[trim]))),
+ 2}]))),
+ <<"bA">> = iolist_to_binary(join(re:split("bA","(?:(a)|b)(?(1)A|B)",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aa","^(a)?(?(1)a|b)+$",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aa","^(a)?(?(1)a|b)+$",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aa","^(a)?(?(1)a|b)+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","^(a)?(?(1)a|b)+$",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aa","^(a)?(?(1)a|b)+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","^(a)?(?(1)a|b)+$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("b","^(a)?(?(1)a|b)+$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("b","^(a)?(?(1)a|b)+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("bb","^(a)?(?(1)a|b)+$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("b","^(a)?(?(1)a|b)+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("bb","^(a)?(?(1)a|b)+$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("bb","^(a)?(?(1)a|b)+$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("bb","^(a)?(?(1)a|b)+$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a)?(?(1)a|b)+$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("bb","^(a)?(?(1)a|b)+$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a)?(?(1)a|b)+$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a)?(?(1)a|b)+$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a)?(?(1)a|b)+$",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","^(a)?(?(1)a|b)+$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a)?(?(1)a|b)+$",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","^(a)?(?(1)a|b)+$",[trim]))),
<<"ab">> = iolist_to_binary(join(re:split("ab","^(a)?(?(1)a|b)+$",[{parts,
- 2}]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","^(a)?(?(1)a|b)+$",[]))),
+ 2}]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","^(a)?(?(1)a|b)+$",[]))),
ok.
run13() ->
- <<"">> = iolist_to_binary(join(re:split("abc:","^(?(?=abc)\\w{3}:|\\d\\d)$",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("abc:","^(?(?=abc)\\w{3}:|\\d\\d)$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc:","^(?(?=abc)\\w{3}:|\\d\\d)$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc:","^(?(?=abc)\\w{3}:|\\d\\d)$",[]))),
- <<"">> = iolist_to_binary(join(re:split("12","^(?(?=abc)\\w{3}:|\\d\\d)$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc:","^(?(?=abc)\\w{3}:|\\d\\d)$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("12","^(?(?=abc)\\w{3}:|\\d\\d)$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("12","^(?(?=abc)\\w{3}:|\\d\\d)$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("12","^(?(?=abc)\\w{3}:|\\d\\d)$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(?=abc)\\w{3}:|\\d\\d)$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("12","^(?(?=abc)\\w{3}:|\\d\\d)$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(?=abc)\\w{3}:|\\d\\d)$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(?=abc)\\w{3}:|\\d\\d)$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(?=abc)\\w{3}:|\\d\\d)$",[]))),
- <<"123">> = iolist_to_binary(join(re:split("123","^(?(?=abc)\\w{3}:|\\d\\d)$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(?=abc)\\w{3}:|\\d\\d)$",[]))),
+ <<"123">> = iolist_to_binary(join(re:split("123","^(?(?=abc)\\w{3}:|\\d\\d)$",[trim]))),
<<"123">> = iolist_to_binary(join(re:split("123","^(?(?=abc)\\w{3}:|\\d\\d)$",[{parts,
- 2}]))),
- <<"123">> = iolist_to_binary(join(re:split("123","^(?(?=abc)\\w{3}:|\\d\\d)$",[]))),
- <<"xyz">> = iolist_to_binary(join(re:split("xyz","^(?(?=abc)\\w{3}:|\\d\\d)$",[trim]))),
+ 2}]))),
+ <<"123">> = iolist_to_binary(join(re:split("123","^(?(?=abc)\\w{3}:|\\d\\d)$",[]))),
+ <<"xyz">> = iolist_to_binary(join(re:split("xyz","^(?(?=abc)\\w{3}:|\\d\\d)$",[trim]))),
<<"xyz">> = iolist_to_binary(join(re:split("xyz","^(?(?=abc)\\w{3}:|\\d\\d)$",[{parts,
- 2}]))),
- <<"xyz">> = iolist_to_binary(join(re:split("xyz","^(?(?=abc)\\w{3}:|\\d\\d)$",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc:","^(?(?!abc)\\d\\d|\\w{3}:)$",[trim]))),
+ 2}]))),
+ <<"xyz">> = iolist_to_binary(join(re:split("xyz","^(?(?=abc)\\w{3}:|\\d\\d)$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc:","^(?(?!abc)\\d\\d|\\w{3}:)$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc:","^(?(?!abc)\\d\\d|\\w{3}:)$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc:","^(?(?!abc)\\d\\d|\\w{3}:)$",[]))),
- <<"">> = iolist_to_binary(join(re:split("12","^(?(?!abc)\\d\\d|\\w{3}:)$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc:","^(?(?!abc)\\d\\d|\\w{3}:)$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("12","^(?(?!abc)\\d\\d|\\w{3}:)$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("12","^(?(?!abc)\\d\\d|\\w{3}:)$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("12","^(?(?!abc)\\d\\d|\\w{3}:)$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(?!abc)\\d\\d|\\w{3}:)$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("12","^(?(?!abc)\\d\\d|\\w{3}:)$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(?!abc)\\d\\d|\\w{3}:)$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(?!abc)\\d\\d|\\w{3}:)$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(?!abc)\\d\\d|\\w{3}:)$",[]))),
- <<"123">> = iolist_to_binary(join(re:split("123","^(?(?!abc)\\d\\d|\\w{3}:)$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(?!abc)\\d\\d|\\w{3}:)$",[]))),
+ <<"123">> = iolist_to_binary(join(re:split("123","^(?(?!abc)\\d\\d|\\w{3}:)$",[trim]))),
<<"123">> = iolist_to_binary(join(re:split("123","^(?(?!abc)\\d\\d|\\w{3}:)$",[{parts,
- 2}]))),
- <<"123">> = iolist_to_binary(join(re:split("123","^(?(?!abc)\\d\\d|\\w{3}:)$",[]))),
- <<"xyz">> = iolist_to_binary(join(re:split("xyz","^(?(?!abc)\\d\\d|\\w{3}:)$",[trim]))),
+ 2}]))),
+ <<"123">> = iolist_to_binary(join(re:split("123","^(?(?!abc)\\d\\d|\\w{3}:)$",[]))),
+ <<"xyz">> = iolist_to_binary(join(re:split("xyz","^(?(?!abc)\\d\\d|\\w{3}:)$",[trim]))),
<<"xyz">> = iolist_to_binary(join(re:split("xyz","^(?(?!abc)\\d\\d|\\w{3}:)$",[{parts,
- 2}]))),
- <<"xyz">> = iolist_to_binary(join(re:split("xyz","^(?(?!abc)\\d\\d|\\w{3}:)$",[]))),
- <<"foo">> = iolist_to_binary(join(re:split("foobar","(?(?<=foo)bar|cat)",[trim]))),
+ 2}]))),
+ <<"xyz">> = iolist_to_binary(join(re:split("xyz","^(?(?!abc)\\d\\d|\\w{3}:)$",[]))),
+ <<"foo">> = iolist_to_binary(join(re:split("foobar","(?(?<=foo)bar|cat)",[trim]))),
<<"foo:">> = iolist_to_binary(join(re:split("foobar","(?(?<=foo)bar|cat)",[{parts,
- 2}]))),
- <<"foo:">> = iolist_to_binary(join(re:split("foobar","(?(?<=foo)bar|cat)",[]))),
- <<"">> = iolist_to_binary(join(re:split("cat","(?(?<=foo)bar|cat)",[trim]))),
+ 2}]))),
+ <<"foo:">> = iolist_to_binary(join(re:split("foobar","(?(?<=foo)bar|cat)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("cat","(?(?<=foo)bar|cat)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("cat","(?(?<=foo)bar|cat)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("cat","(?(?<=foo)bar|cat)",[]))),
- <<"f">> = iolist_to_binary(join(re:split("fcat","(?(?<=foo)bar|cat)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("cat","(?(?<=foo)bar|cat)",[]))),
+ <<"f">> = iolist_to_binary(join(re:split("fcat","(?(?<=foo)bar|cat)",[trim]))),
<<"f:">> = iolist_to_binary(join(re:split("fcat","(?(?<=foo)bar|cat)",[{parts,
- 2}]))),
- <<"f:">> = iolist_to_binary(join(re:split("fcat","(?(?<=foo)bar|cat)",[]))),
- <<"fo">> = iolist_to_binary(join(re:split("focat","(?(?<=foo)bar|cat)",[trim]))),
+ 2}]))),
+ <<"f:">> = iolist_to_binary(join(re:split("fcat","(?(?<=foo)bar|cat)",[]))),
+ <<"fo">> = iolist_to_binary(join(re:split("focat","(?(?<=foo)bar|cat)",[trim]))),
<<"fo:">> = iolist_to_binary(join(re:split("focat","(?(?<=foo)bar|cat)",[{parts,
- 2}]))),
- <<"fo:">> = iolist_to_binary(join(re:split("focat","(?(?<=foo)bar|cat)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?<=foo)bar|cat)",[trim]))),
+ 2}]))),
+ <<"fo:">> = iolist_to_binary(join(re:split("focat","(?(?<=foo)bar|cat)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?<=foo)bar|cat)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?<=foo)bar|cat)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?<=foo)bar|cat)",[]))),
- <<"foocat">> = iolist_to_binary(join(re:split("foocat","(?(?<=foo)bar|cat)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?<=foo)bar|cat)",[]))),
+ <<"foocat">> = iolist_to_binary(join(re:split("foocat","(?(?<=foo)bar|cat)",[trim]))),
<<"foocat">> = iolist_to_binary(join(re:split("foocat","(?(?<=foo)bar|cat)",[{parts,
- 2}]))),
- <<"foocat">> = iolist_to_binary(join(re:split("foocat","(?(?<=foo)bar|cat)",[]))),
- <<"foo">> = iolist_to_binary(join(re:split("foobar","(?(?<!foo)cat|bar)",[trim]))),
+ 2}]))),
+ <<"foocat">> = iolist_to_binary(join(re:split("foocat","(?(?<=foo)bar|cat)",[]))),
+ <<"foo">> = iolist_to_binary(join(re:split("foobar","(?(?<!foo)cat|bar)",[trim]))),
<<"foo:">> = iolist_to_binary(join(re:split("foobar","(?(?<!foo)cat|bar)",[{parts,
- 2}]))),
- <<"foo:">> = iolist_to_binary(join(re:split("foobar","(?(?<!foo)cat|bar)",[]))),
- <<"">> = iolist_to_binary(join(re:split("cat","(?(?<!foo)cat|bar)",[trim]))),
+ 2}]))),
+ <<"foo:">> = iolist_to_binary(join(re:split("foobar","(?(?<!foo)cat|bar)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("cat","(?(?<!foo)cat|bar)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("cat","(?(?<!foo)cat|bar)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("cat","(?(?<!foo)cat|bar)",[]))),
- <<"f">> = iolist_to_binary(join(re:split("fcat","(?(?<!foo)cat|bar)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("cat","(?(?<!foo)cat|bar)",[]))),
+ <<"f">> = iolist_to_binary(join(re:split("fcat","(?(?<!foo)cat|bar)",[trim]))),
<<"f:">> = iolist_to_binary(join(re:split("fcat","(?(?<!foo)cat|bar)",[{parts,
- 2}]))),
- <<"f:">> = iolist_to_binary(join(re:split("fcat","(?(?<!foo)cat|bar)",[]))),
- <<"fo">> = iolist_to_binary(join(re:split("focat","(?(?<!foo)cat|bar)",[trim]))),
+ 2}]))),
+ <<"f:">> = iolist_to_binary(join(re:split("fcat","(?(?<!foo)cat|bar)",[]))),
+ <<"fo">> = iolist_to_binary(join(re:split("focat","(?(?<!foo)cat|bar)",[trim]))),
<<"fo:">> = iolist_to_binary(join(re:split("focat","(?(?<!foo)cat|bar)",[{parts,
- 2}]))),
- <<"fo:">> = iolist_to_binary(join(re:split("focat","(?(?<!foo)cat|bar)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?<!foo)cat|bar)",[trim]))),
+ 2}]))),
+ <<"fo:">> = iolist_to_binary(join(re:split("focat","(?(?<!foo)cat|bar)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?<!foo)cat|bar)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?<!foo)cat|bar)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?<!foo)cat|bar)",[]))),
- <<"foocat">> = iolist_to_binary(join(re:split("foocat","(?(?<!foo)cat|bar)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?<!foo)cat|bar)",[]))),
+ <<"foocat">> = iolist_to_binary(join(re:split("foocat","(?(?<!foo)cat|bar)",[trim]))),
<<"foocat">> = iolist_to_binary(join(re:split("foocat","(?(?<!foo)cat|bar)",[{parts,
- 2}]))),
- <<"foocat">> = iolist_to_binary(join(re:split("foocat","(?(?<!foo)cat|bar)",[]))),
+ 2}]))),
+ <<"foocat">> = iolist_to_binary(join(re:split("foocat","(?(?<!foo)cat|bar)",[]))),
<<"">> = iolist_to_binary(join(re:split("abcd","( \\( )? [^()]+ (?(1) \\) |) ",[extended,
- trim]))),
+ trim]))),
<<"::">> = iolist_to_binary(join(re:split("abcd","( \\( )? [^()]+ (?(1) \\) |) ",[extended,
{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("abcd","( \\( )? [^()]+ (?(1) \\) |) ",[extended]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("abcd","( \\( )? [^()]+ (?(1) \\) |) ",[extended]))),
<<":(">> = iolist_to_binary(join(re:split("(abcd)","( \\( )? [^()]+ (?(1) \\) |) ",[extended,
- trim]))),
+ trim]))),
<<":(:">> = iolist_to_binary(join(re:split("(abcd)","( \\( )? [^()]+ (?(1) \\) |) ",[extended,
{parts,
- 2}]))),
- <<":(:">> = iolist_to_binary(join(re:split("(abcd)","( \\( )? [^()]+ (?(1) \\) |) ",[extended]))),
+ 2}]))),
+ <<":(:">> = iolist_to_binary(join(re:split("(abcd)","( \\( )? [^()]+ (?(1) \\) |) ",[extended]))),
<<":::(">> = iolist_to_binary(join(re:split("the quick (abcd) fox","( \\( )? [^()]+ (?(1) \\) |) ",[extended,
- trim]))),
+ trim]))),
<<"::(abcd) fox">> = iolist_to_binary(join(re:split("the quick (abcd) fox","( \\( )? [^()]+ (?(1) \\) |) ",[extended,
{parts,
- 2}]))),
- <<":::(:::">> = iolist_to_binary(join(re:split("the quick (abcd) fox","( \\( )? [^()]+ (?(1) \\) |) ",[extended]))),
+ 2}]))),
+ <<":::(:::">> = iolist_to_binary(join(re:split("the quick (abcd) fox","( \\( )? [^()]+ (?(1) \\) |) ",[extended]))),
<<"(">> = iolist_to_binary(join(re:split("(abcd","( \\( )? [^()]+ (?(1) \\) |) ",[extended,
- trim]))),
+ trim]))),
<<"(::">> = iolist_to_binary(join(re:split("(abcd","( \\( )? [^()]+ (?(1) \\) |) ",[extended,
{parts,
- 2}]))),
- <<"(::">> = iolist_to_binary(join(re:split("(abcd","( \\( )? [^()]+ (?(1) \\) |) ",[extended]))),
+ 2}]))),
+ <<"(::">> = iolist_to_binary(join(re:split("(abcd","( \\( )? [^()]+ (?(1) \\) |) ",[extended]))),
<<"">> = iolist_to_binary(join(re:split("abcd","( \\( )? [^()]+ (?(1) \\) ) ",[extended,
- trim]))),
+ trim]))),
<<"::">> = iolist_to_binary(join(re:split("abcd","( \\( )? [^()]+ (?(1) \\) ) ",[extended,
{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("abcd","( \\( )? [^()]+ (?(1) \\) ) ",[extended]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("abcd","( \\( )? [^()]+ (?(1) \\) ) ",[extended]))),
<<":(">> = iolist_to_binary(join(re:split("(abcd)","( \\( )? [^()]+ (?(1) \\) ) ",[extended,
- trim]))),
+ trim]))),
<<":(:">> = iolist_to_binary(join(re:split("(abcd)","( \\( )? [^()]+ (?(1) \\) ) ",[extended,
{parts,
- 2}]))),
- <<":(:">> = iolist_to_binary(join(re:split("(abcd)","( \\( )? [^()]+ (?(1) \\) ) ",[extended]))),
+ 2}]))),
+ <<":(:">> = iolist_to_binary(join(re:split("(abcd)","( \\( )? [^()]+ (?(1) \\) ) ",[extended]))),
<<":::(">> = iolist_to_binary(join(re:split("the quick (abcd) fox","( \\( )? [^()]+ (?(1) \\) ) ",[extended,
- trim]))),
+ trim]))),
<<"::(abcd) fox">> = iolist_to_binary(join(re:split("the quick (abcd) fox","( \\( )? [^()]+ (?(1) \\) ) ",[extended,
{parts,
- 2}]))),
- <<":::(:::">> = iolist_to_binary(join(re:split("the quick (abcd) fox","( \\( )? [^()]+ (?(1) \\) ) ",[extended]))),
+ 2}]))),
+ <<":::(:::">> = iolist_to_binary(join(re:split("the quick (abcd) fox","( \\( )? [^()]+ (?(1) \\) ) ",[extended]))),
<<"(">> = iolist_to_binary(join(re:split("(abcd","( \\( )? [^()]+ (?(1) \\) ) ",[extended,
- trim]))),
+ trim]))),
<<"(::">> = iolist_to_binary(join(re:split("(abcd","( \\( )? [^()]+ (?(1) \\) ) ",[extended,
{parts,
- 2}]))),
- <<"(::">> = iolist_to_binary(join(re:split("(abcd","( \\( )? [^()]+ (?(1) \\) ) ",[extended]))),
- <<":1:2">> = iolist_to_binary(join(re:split("12","^(?(2)a|(1)(2))+$",[trim]))),
+ 2}]))),
+ <<"(::">> = iolist_to_binary(join(re:split("(abcd","( \\( )? [^()]+ (?(1) \\) ) ",[extended]))),
+ <<":1:2">> = iolist_to_binary(join(re:split("12","^(?(2)a|(1)(2))+$",[trim]))),
<<":1:2:">> = iolist_to_binary(join(re:split("12","^(?(2)a|(1)(2))+$",[{parts,
- 2}]))),
- <<":1:2:">> = iolist_to_binary(join(re:split("12","^(?(2)a|(1)(2))+$",[]))),
- <<":1:2">> = iolist_to_binary(join(re:split("12a","^(?(2)a|(1)(2))+$",[trim]))),
+ 2}]))),
+ <<":1:2:">> = iolist_to_binary(join(re:split("12","^(?(2)a|(1)(2))+$",[]))),
+ <<":1:2">> = iolist_to_binary(join(re:split("12a","^(?(2)a|(1)(2))+$",[trim]))),
<<":1:2:">> = iolist_to_binary(join(re:split("12a","^(?(2)a|(1)(2))+$",[{parts,
- 2}]))),
- <<":1:2:">> = iolist_to_binary(join(re:split("12a","^(?(2)a|(1)(2))+$",[]))),
- <<":1:2">> = iolist_to_binary(join(re:split("12aa","^(?(2)a|(1)(2))+$",[trim]))),
+ 2}]))),
+ <<":1:2:">> = iolist_to_binary(join(re:split("12a","^(?(2)a|(1)(2))+$",[]))),
+ <<":1:2">> = iolist_to_binary(join(re:split("12aa","^(?(2)a|(1)(2))+$",[trim]))),
<<":1:2:">> = iolist_to_binary(join(re:split("12aa","^(?(2)a|(1)(2))+$",[{parts,
- 2}]))),
- <<":1:2:">> = iolist_to_binary(join(re:split("12aa","^(?(2)a|(1)(2))+$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(2)a|(1)(2))+$",[trim]))),
+ 2}]))),
+ <<":1:2:">> = iolist_to_binary(join(re:split("12aa","^(?(2)a|(1)(2))+$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(2)a|(1)(2))+$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(2)a|(1)(2))+$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(2)a|(1)(2))+$",[]))),
- <<"1234">> = iolist_to_binary(join(re:split("1234","^(?(2)a|(1)(2))+$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?(2)a|(1)(2))+$",[]))),
+ <<"1234">> = iolist_to_binary(join(re:split("1234","^(?(2)a|(1)(2))+$",[trim]))),
<<"1234">> = iolist_to_binary(join(re:split("1234","^(?(2)a|(1)(2))+$",[{parts,
- 2}]))),
- <<"1234">> = iolist_to_binary(join(re:split("1234","^(?(2)a|(1)(2))+$",[]))),
- <<":blah">> = iolist_to_binary(join(re:split("blah blah","((?i)blah)\\s+\\1",[trim]))),
+ 2}]))),
+ <<"1234">> = iolist_to_binary(join(re:split("1234","^(?(2)a|(1)(2))+$",[]))),
+ <<":blah">> = iolist_to_binary(join(re:split("blah blah","((?i)blah)\\s+\\1",[trim]))),
<<":blah:">> = iolist_to_binary(join(re:split("blah blah","((?i)blah)\\s+\\1",[{parts,
- 2}]))),
- <<":blah:">> = iolist_to_binary(join(re:split("blah blah","((?i)blah)\\s+\\1",[]))),
- <<":BLAH">> = iolist_to_binary(join(re:split("BLAH BLAH","((?i)blah)\\s+\\1",[trim]))),
+ 2}]))),
+ <<":blah:">> = iolist_to_binary(join(re:split("blah blah","((?i)blah)\\s+\\1",[]))),
+ <<":BLAH">> = iolist_to_binary(join(re:split("BLAH BLAH","((?i)blah)\\s+\\1",[trim]))),
<<":BLAH:">> = iolist_to_binary(join(re:split("BLAH BLAH","((?i)blah)\\s+\\1",[{parts,
- 2}]))),
- <<":BLAH:">> = iolist_to_binary(join(re:split("BLAH BLAH","((?i)blah)\\s+\\1",[]))),
- <<":Blah">> = iolist_to_binary(join(re:split("Blah Blah","((?i)blah)\\s+\\1",[trim]))),
+ 2}]))),
+ <<":BLAH:">> = iolist_to_binary(join(re:split("BLAH BLAH","((?i)blah)\\s+\\1",[]))),
+ <<":Blah">> = iolist_to_binary(join(re:split("Blah Blah","((?i)blah)\\s+\\1",[trim]))),
<<":Blah:">> = iolist_to_binary(join(re:split("Blah Blah","((?i)blah)\\s+\\1",[{parts,
- 2}]))),
- <<":Blah:">> = iolist_to_binary(join(re:split("Blah Blah","((?i)blah)\\s+\\1",[]))),
- <<":blaH">> = iolist_to_binary(join(re:split("blaH blaH","((?i)blah)\\s+\\1",[trim]))),
+ 2}]))),
+ <<":Blah:">> = iolist_to_binary(join(re:split("Blah Blah","((?i)blah)\\s+\\1",[]))),
+ <<":blaH">> = iolist_to_binary(join(re:split("blaH blaH","((?i)blah)\\s+\\1",[trim]))),
<<":blaH:">> = iolist_to_binary(join(re:split("blaH blaH","((?i)blah)\\s+\\1",[{parts,
- 2}]))),
- <<":blaH:">> = iolist_to_binary(join(re:split("blaH blaH","((?i)blah)\\s+\\1",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?i)blah)\\s+\\1",[trim]))),
+ 2}]))),
+ <<":blaH:">> = iolist_to_binary(join(re:split("blaH blaH","((?i)blah)\\s+\\1",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?i)blah)\\s+\\1",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?i)blah)\\s+\\1",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?i)blah)\\s+\\1",[]))),
- <<"blah BLAH">> = iolist_to_binary(join(re:split("blah BLAH","((?i)blah)\\s+\\1",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?i)blah)\\s+\\1",[]))),
+ <<"blah BLAH">> = iolist_to_binary(join(re:split("blah BLAH","((?i)blah)\\s+\\1",[trim]))),
<<"blah BLAH">> = iolist_to_binary(join(re:split("blah BLAH","((?i)blah)\\s+\\1",[{parts,
- 2}]))),
- <<"blah BLAH">> = iolist_to_binary(join(re:split("blah BLAH","((?i)blah)\\s+\\1",[]))),
- <<"Blah blah">> = iolist_to_binary(join(re:split("Blah blah","((?i)blah)\\s+\\1",[trim]))),
+ 2}]))),
+ <<"blah BLAH">> = iolist_to_binary(join(re:split("blah BLAH","((?i)blah)\\s+\\1",[]))),
+ <<"Blah blah">> = iolist_to_binary(join(re:split("Blah blah","((?i)blah)\\s+\\1",[trim]))),
<<"Blah blah">> = iolist_to_binary(join(re:split("Blah blah","((?i)blah)\\s+\\1",[{parts,
- 2}]))),
- <<"Blah blah">> = iolist_to_binary(join(re:split("Blah blah","((?i)blah)\\s+\\1",[]))),
- <<"blaH blah">> = iolist_to_binary(join(re:split("blaH blah","((?i)blah)\\s+\\1",[trim]))),
+ 2}]))),
+ <<"Blah blah">> = iolist_to_binary(join(re:split("Blah blah","((?i)blah)\\s+\\1",[]))),
+ <<"blaH blah">> = iolist_to_binary(join(re:split("blaH blah","((?i)blah)\\s+\\1",[trim]))),
<<"blaH blah">> = iolist_to_binary(join(re:split("blaH blah","((?i)blah)\\s+\\1",[{parts,
- 2}]))),
- <<"blaH blah">> = iolist_to_binary(join(re:split("blaH blah","((?i)blah)\\s+\\1",[]))),
- <<":blah">> = iolist_to_binary(join(re:split("blah blah","((?i)blah)\\s+(?i:\\1)",[trim]))),
+ 2}]))),
+ <<"blaH blah">> = iolist_to_binary(join(re:split("blaH blah","((?i)blah)\\s+\\1",[]))),
+ <<":blah">> = iolist_to_binary(join(re:split("blah blah","((?i)blah)\\s+(?i:\\1)",[trim]))),
<<":blah:">> = iolist_to_binary(join(re:split("blah blah","((?i)blah)\\s+(?i:\\1)",[{parts,
- 2}]))),
- <<":blah:">> = iolist_to_binary(join(re:split("blah blah","((?i)blah)\\s+(?i:\\1)",[]))),
- <<":BLAH">> = iolist_to_binary(join(re:split("BLAH BLAH","((?i)blah)\\s+(?i:\\1)",[trim]))),
+ 2}]))),
+ <<":blah:">> = iolist_to_binary(join(re:split("blah blah","((?i)blah)\\s+(?i:\\1)",[]))),
+ <<":BLAH">> = iolist_to_binary(join(re:split("BLAH BLAH","((?i)blah)\\s+(?i:\\1)",[trim]))),
<<":BLAH:">> = iolist_to_binary(join(re:split("BLAH BLAH","((?i)blah)\\s+(?i:\\1)",[{parts,
- 2}]))),
- <<":BLAH:">> = iolist_to_binary(join(re:split("BLAH BLAH","((?i)blah)\\s+(?i:\\1)",[]))),
- <<":Blah">> = iolist_to_binary(join(re:split("Blah Blah","((?i)blah)\\s+(?i:\\1)",[trim]))),
+ 2}]))),
+ <<":BLAH:">> = iolist_to_binary(join(re:split("BLAH BLAH","((?i)blah)\\s+(?i:\\1)",[]))),
+ <<":Blah">> = iolist_to_binary(join(re:split("Blah Blah","((?i)blah)\\s+(?i:\\1)",[trim]))),
<<":Blah:">> = iolist_to_binary(join(re:split("Blah Blah","((?i)blah)\\s+(?i:\\1)",[{parts,
- 2}]))),
- <<":Blah:">> = iolist_to_binary(join(re:split("Blah Blah","((?i)blah)\\s+(?i:\\1)",[]))),
- <<":blaH">> = iolist_to_binary(join(re:split("blaH blaH","((?i)blah)\\s+(?i:\\1)",[trim]))),
+ 2}]))),
+ <<":Blah:">> = iolist_to_binary(join(re:split("Blah Blah","((?i)blah)\\s+(?i:\\1)",[]))),
+ <<":blaH">> = iolist_to_binary(join(re:split("blaH blaH","((?i)blah)\\s+(?i:\\1)",[trim]))),
<<":blaH:">> = iolist_to_binary(join(re:split("blaH blaH","((?i)blah)\\s+(?i:\\1)",[{parts,
- 2}]))),
- <<":blaH:">> = iolist_to_binary(join(re:split("blaH blaH","((?i)blah)\\s+(?i:\\1)",[]))),
- <<":blah">> = iolist_to_binary(join(re:split("blah BLAH","((?i)blah)\\s+(?i:\\1)",[trim]))),
+ 2}]))),
+ <<":blaH:">> = iolist_to_binary(join(re:split("blaH blaH","((?i)blah)\\s+(?i:\\1)",[]))),
+ <<":blah">> = iolist_to_binary(join(re:split("blah BLAH","((?i)blah)\\s+(?i:\\1)",[trim]))),
<<":blah:">> = iolist_to_binary(join(re:split("blah BLAH","((?i)blah)\\s+(?i:\\1)",[{parts,
- 2}]))),
- <<":blah:">> = iolist_to_binary(join(re:split("blah BLAH","((?i)blah)\\s+(?i:\\1)",[]))),
- <<":Blah">> = iolist_to_binary(join(re:split("Blah blah","((?i)blah)\\s+(?i:\\1)",[trim]))),
+ 2}]))),
+ <<":blah:">> = iolist_to_binary(join(re:split("blah BLAH","((?i)blah)\\s+(?i:\\1)",[]))),
+ <<":Blah">> = iolist_to_binary(join(re:split("Blah blah","((?i)blah)\\s+(?i:\\1)",[trim]))),
<<":Blah:">> = iolist_to_binary(join(re:split("Blah blah","((?i)blah)\\s+(?i:\\1)",[{parts,
- 2}]))),
- <<":Blah:">> = iolist_to_binary(join(re:split("Blah blah","((?i)blah)\\s+(?i:\\1)",[]))),
- <<":blaH">> = iolist_to_binary(join(re:split("blaH blah","((?i)blah)\\s+(?i:\\1)",[trim]))),
+ 2}]))),
+ <<":Blah:">> = iolist_to_binary(join(re:split("Blah blah","((?i)blah)\\s+(?i:\\1)",[]))),
+ <<":blaH">> = iolist_to_binary(join(re:split("blaH blah","((?i)blah)\\s+(?i:\\1)",[trim]))),
<<":blaH:">> = iolist_to_binary(join(re:split("blaH blah","((?i)blah)\\s+(?i:\\1)",[{parts,
- 2}]))),
- <<":blaH:">> = iolist_to_binary(join(re:split("blaH blah","((?i)blah)\\s+(?i:\\1)",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","(?>a*)*",[trim]))),
+ 2}]))),
+ <<":blaH:">> = iolist_to_binary(join(re:split("blaH blah","((?i)blah)\\s+(?i:\\1)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","(?>a*)*",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","(?>a*)*",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","(?>a*)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("aa","(?>a*)*",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","(?>a*)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aa","(?>a*)*",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aa","(?>a*)*",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aa","(?>a*)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaa","(?>a*)*",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aa","(?>a*)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaa","(?>a*)*",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaa","(?>a*)*",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaa","(?>a*)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","(abc|)+",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaa","(?>a*)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","(abc|)+",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("abc","(abc|)+",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("abc","(abc|)+",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcabc","(abc|)+",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("abc","(abc|)+",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcabc","(abc|)+",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("abcabc","(abc|)+",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("abcabc","(abc|)+",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcabcabc","(abc|)+",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("abcabc","(abc|)+",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcabcabc","(abc|)+",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("abcabcabc","(abc|)+",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("abcabcabc","(abc|)+",[]))),
- <<"x::y::z">> = iolist_to_binary(join(re:split("xyz","(abc|)+",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("abcabcabc","(abc|)+",[]))),
+ <<"x::y::z">> = iolist_to_binary(join(re:split("xyz","(abc|)+",[trim]))),
<<"x::yz">> = iolist_to_binary(join(re:split("xyz","(abc|)+",[{parts,
- 2}]))),
- <<"x::y::z::">> = iolist_to_binary(join(re:split("xyz","(abc|)+",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","([a]*)*",[trim]))),
+ 2}]))),
+ <<"x::y::z::">> = iolist_to_binary(join(re:split("xyz","(abc|)+",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","([a]*)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a","([a]*)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a","([a]*)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaaa","([a]*)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a","([a]*)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaa","([a]*)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("aaaaa","([a]*)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("aaaaa","([a]*)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","([ab]*)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("aaaaa","([a]*)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","([ab]*)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a","([ab]*)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a","([ab]*)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","([ab]*)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a","([ab]*)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","([ab]*)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("b","([ab]*)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("b","([ab]*)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("ababab","([ab]*)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("b","([ab]*)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ababab","([ab]*)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("ababab","([ab]*)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("ababab","([ab]*)*",[]))),
- <<"::c::d::e">> = iolist_to_binary(join(re:split("aaaabcde","([ab]*)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("ababab","([ab]*)*",[]))),
+ <<"::c::d::e">> = iolist_to_binary(join(re:split("aaaabcde","([ab]*)*",[trim]))),
<<"::cde">> = iolist_to_binary(join(re:split("aaaabcde","([ab]*)*",[{parts,
- 2}]))),
- <<"::c::d::e::">> = iolist_to_binary(join(re:split("aaaabcde","([ab]*)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("bbbb","([ab]*)*",[trim]))),
+ 2}]))),
+ <<"::c::d::e::">> = iolist_to_binary(join(re:split("aaaabcde","([ab]*)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("bbbb","([ab]*)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("bbbb","([ab]*)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("bbbb","([ab]*)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","([^a]*)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("bbbb","([ab]*)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","([^a]*)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("b","([^a]*)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("b","([^a]*)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("bbbb","([^a]*)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("b","([^a]*)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("bbbb","([^a]*)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("bbbb","([^a]*)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("bbbb","([^a]*)*",[]))),
- <<"a::a::a">> = iolist_to_binary(join(re:split("aaa","([^a]*)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("bbbb","([^a]*)*",[]))),
+ <<"a::a::a">> = iolist_to_binary(join(re:split("aaa","([^a]*)*",[trim]))),
<<"a::aa">> = iolist_to_binary(join(re:split("aaa","([^a]*)*",[{parts,
- 2}]))),
- <<"a::a::a::">> = iolist_to_binary(join(re:split("aaa","([^a]*)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("cccc","([^ab]*)*",[trim]))),
+ 2}]))),
+ <<"a::a::a::">> = iolist_to_binary(join(re:split("aaa","([^a]*)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("cccc","([^ab]*)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("cccc","([^ab]*)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("cccc","([^ab]*)*",[]))),
- <<"a::b::a::b">> = iolist_to_binary(join(re:split("abab","([^ab]*)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("cccc","([^ab]*)*",[]))),
+ <<"a::b::a::b">> = iolist_to_binary(join(re:split("abab","([^ab]*)*",[trim]))),
<<"a::bab">> = iolist_to_binary(join(re:split("abab","([^ab]*)*",[{parts,
- 2}]))),
- <<"a::b::a::b::">> = iolist_to_binary(join(re:split("abab","([^ab]*)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","([a]*?)*",[trim]))),
+ 2}]))),
+ <<"a::b::a::b::">> = iolist_to_binary(join(re:split("abab","([^ab]*)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","([a]*?)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a","([a]*?)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a","([a]*?)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaa","([a]*?)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a","([a]*?)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaa","([a]*?)*",[trim]))),
<<"::aaa">> = iolist_to_binary(join(re:split("aaaa","([a]*?)*",[{parts,
- 2}]))),
- <<"::::::::">> = iolist_to_binary(join(re:split("aaaa","([a]*?)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","([ab]*?)*",[trim]))),
+ 2}]))),
+ <<"::::::::">> = iolist_to_binary(join(re:split("aaaa","([a]*?)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","([ab]*?)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a","([ab]*?)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a","([ab]*?)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","([ab]*?)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a","([ab]*?)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","([ab]*?)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("b","([ab]*?)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("b","([ab]*?)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("abab","([ab]*?)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("b","([ab]*?)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abab","([ab]*?)*",[trim]))),
<<"::bab">> = iolist_to_binary(join(re:split("abab","([ab]*?)*",[{parts,
- 2}]))),
- <<"::::::::">> = iolist_to_binary(join(re:split("abab","([ab]*?)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("baba","([ab]*?)*",[trim]))),
+ 2}]))),
+ <<"::::::::">> = iolist_to_binary(join(re:split("abab","([ab]*?)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("baba","([ab]*?)*",[trim]))),
<<"::aba">> = iolist_to_binary(join(re:split("baba","([ab]*?)*",[{parts,
- 2}]))),
- <<"::::::::">> = iolist_to_binary(join(re:split("baba","([ab]*?)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","([^a]*?)*",[trim]))),
+ 2}]))),
+ <<"::::::::">> = iolist_to_binary(join(re:split("baba","([ab]*?)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","([^a]*?)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("b","([^a]*?)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("b","([^a]*?)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("bbbb","([^a]*?)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("b","([^a]*?)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("bbbb","([^a]*?)*",[trim]))),
<<"::bbb">> = iolist_to_binary(join(re:split("bbbb","([^a]*?)*",[{parts,
- 2}]))),
- <<"::::::::">> = iolist_to_binary(join(re:split("bbbb","([^a]*?)*",[]))),
- <<"a::a::a">> = iolist_to_binary(join(re:split("aaa","([^a]*?)*",[trim]))),
+ 2}]))),
+ <<"::::::::">> = iolist_to_binary(join(re:split("bbbb","([^a]*?)*",[]))),
+ <<"a::a::a">> = iolist_to_binary(join(re:split("aaa","([^a]*?)*",[trim]))),
<<"a::aa">> = iolist_to_binary(join(re:split("aaa","([^a]*?)*",[{parts,
- 2}]))),
- <<"a::a::a::">> = iolist_to_binary(join(re:split("aaa","([^a]*?)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("c","([^ab]*?)*",[trim]))),
+ 2}]))),
+ <<"a::a::a::">> = iolist_to_binary(join(re:split("aaa","([^a]*?)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("c","([^ab]*?)*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("c","([^ab]*?)*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("c","([^ab]*?)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("cccc","([^ab]*?)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("c","([^ab]*?)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("cccc","([^ab]*?)*",[trim]))),
<<"::ccc">> = iolist_to_binary(join(re:split("cccc","([^ab]*?)*",[{parts,
- 2}]))),
- <<"::::::::">> = iolist_to_binary(join(re:split("cccc","([^ab]*?)*",[]))),
- <<"b::a::b::a">> = iolist_to_binary(join(re:split("baba","([^ab]*?)*",[trim]))),
+ 2}]))),
+ <<"::::::::">> = iolist_to_binary(join(re:split("cccc","([^ab]*?)*",[]))),
+ <<"b::a::b::a">> = iolist_to_binary(join(re:split("baba","([^ab]*?)*",[trim]))),
<<"b::aba">> = iolist_to_binary(join(re:split("baba","([^ab]*?)*",[{parts,
- 2}]))),
- <<"b::a::b::a::">> = iolist_to_binary(join(re:split("baba","([^ab]*?)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","(?>a*)*",[trim]))),
+ 2}]))),
+ <<"b::a::b::a::">> = iolist_to_binary(join(re:split("baba","([^ab]*?)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","(?>a*)*",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","(?>a*)*",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","(?>a*)*",[]))),
- <<":b:c:d:e">> = iolist_to_binary(join(re:split("aaabcde","(?>a*)*",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","(?>a*)*",[]))),
+ <<":b:c:d:e">> = iolist_to_binary(join(re:split("aaabcde","(?>a*)*",[trim]))),
<<":bcde">> = iolist_to_binary(join(re:split("aaabcde","(?>a*)*",[{parts,
- 2}]))),
- <<":b:c:d:e:">> = iolist_to_binary(join(re:split("aaabcde","(?>a*)*",[]))),
+ 2}]))),
+ <<":b:c:d:e:">> = iolist_to_binary(join(re:split("aaabcde","(?>a*)*",[]))),
ok.
run14() ->
- <<"">> = iolist_to_binary(join(re:split("aaaaa","((?>a*))*",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaa","((?>a*))*",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("aaaaa","((?>a*))*",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("aaaaa","((?>a*))*",[]))),
- <<"::b::b">> = iolist_to_binary(join(re:split("aabbaa","((?>a*))*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("aaaaa","((?>a*))*",[]))),
+ <<"::b::b">> = iolist_to_binary(join(re:split("aabbaa","((?>a*))*",[trim]))),
<<"::bbaa">> = iolist_to_binary(join(re:split("aabbaa","((?>a*))*",[{parts,
- 2}]))),
- <<"::b::b::">> = iolist_to_binary(join(re:split("aabbaa","((?>a*))*",[]))),
- <<"a::a::a::a::a">> = iolist_to_binary(join(re:split("aaaaa","((?>a*?))*",[trim]))),
+ 2}]))),
+ <<"::b::b::">> = iolist_to_binary(join(re:split("aabbaa","((?>a*))*",[]))),
+ <<"a::a::a::a::a">> = iolist_to_binary(join(re:split("aaaaa","((?>a*?))*",[trim]))),
<<"a::aaaa">> = iolist_to_binary(join(re:split("aaaaa","((?>a*?))*",[{parts,
- 2}]))),
- <<"a::a::a::a::a::">> = iolist_to_binary(join(re:split("aaaaa","((?>a*?))*",[]))),
- <<"a::a::b::b::a::a">> = iolist_to_binary(join(re:split("aabbaa","((?>a*?))*",[trim]))),
+ 2}]))),
+ <<"a::a::a::a::a::">> = iolist_to_binary(join(re:split("aaaaa","((?>a*?))*",[]))),
+ <<"a::a::b::b::a::a">> = iolist_to_binary(join(re:split("aabbaa","((?>a*?))*",[trim]))),
<<"a::abbaa">> = iolist_to_binary(join(re:split("aabbaa","((?>a*?))*",[{parts,
- 2}]))),
- <<"a::a::b::b::a::a::">> = iolist_to_binary(join(re:split("aabbaa","((?>a*?))*",[]))),
+ 2}]))),
+ <<"a::a::b::b::a::a::">> = iolist_to_binary(join(re:split("aabbaa","((?>a*?))*",[]))),
<<"">> = iolist_to_binary(join(re:split("12-sep-98","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("12-sep-98","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("12-sep-98","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("12-sep-98","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended]))),
<<"">> = iolist_to_binary(join(re:split("12-09-98","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("12-09-98","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("12-09-98","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("12-09-98","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended]))),
<<"sep-12-98">> = iolist_to_binary(join(re:split("sep-12-98","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended,
- trim]))),
+ trim]))),
<<"sep-12-98">> = iolist_to_binary(join(re:split("sep-12-98","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended,
{parts,
- 2}]))),
- <<"sep-12-98">> = iolist_to_binary(join(re:split("sep-12-98","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended]))),
- <<"foo:foo">> = iolist_to_binary(join(re:split("foobarfoo","(?<=(foo))bar\\1",[trim]))),
+ 2}]))),
+ <<"sep-12-98">> = iolist_to_binary(join(re:split("sep-12-98","(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) ",[extended]))),
+ <<"foo:foo">> = iolist_to_binary(join(re:split("foobarfoo","(?<=(foo))bar\\1",[trim]))),
<<"foo:foo:">> = iolist_to_binary(join(re:split("foobarfoo","(?<=(foo))bar\\1",[{parts,
- 2}]))),
- <<"foo:foo:">> = iolist_to_binary(join(re:split("foobarfoo","(?<=(foo))bar\\1",[]))),
- <<"foo:foo:tling">> = iolist_to_binary(join(re:split("foobarfootling","(?<=(foo))bar\\1",[trim]))),
+ 2}]))),
+ <<"foo:foo:">> = iolist_to_binary(join(re:split("foobarfoo","(?<=(foo))bar\\1",[]))),
+ <<"foo:foo:tling">> = iolist_to_binary(join(re:split("foobarfootling","(?<=(foo))bar\\1",[trim]))),
<<"foo:foo:tling">> = iolist_to_binary(join(re:split("foobarfootling","(?<=(foo))bar\\1",[{parts,
- 2}]))),
- <<"foo:foo:tling">> = iolist_to_binary(join(re:split("foobarfootling","(?<=(foo))bar\\1",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(foo))bar\\1",[trim]))),
+ 2}]))),
+ <<"foo:foo:tling">> = iolist_to_binary(join(re:split("foobarfootling","(?<=(foo))bar\\1",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(foo))bar\\1",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(foo))bar\\1",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(foo))bar\\1",[]))),
- <<"foobar">> = iolist_to_binary(join(re:split("foobar","(?<=(foo))bar\\1",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(foo))bar\\1",[]))),
+ <<"foobar">> = iolist_to_binary(join(re:split("foobar","(?<=(foo))bar\\1",[trim]))),
<<"foobar">> = iolist_to_binary(join(re:split("foobar","(?<=(foo))bar\\1",[{parts,
- 2}]))),
- <<"foobar">> = iolist_to_binary(join(re:split("foobar","(?<=(foo))bar\\1",[]))),
- <<"barfoo">> = iolist_to_binary(join(re:split("barfoo","(?<=(foo))bar\\1",[trim]))),
+ 2}]))),
+ <<"foobar">> = iolist_to_binary(join(re:split("foobar","(?<=(foo))bar\\1",[]))),
+ <<"barfoo">> = iolist_to_binary(join(re:split("barfoo","(?<=(foo))bar\\1",[trim]))),
<<"barfoo">> = iolist_to_binary(join(re:split("barfoo","(?<=(foo))bar\\1",[{parts,
- 2}]))),
- <<"barfoo">> = iolist_to_binary(join(re:split("barfoo","(?<=(foo))bar\\1",[]))),
- <<"">> = iolist_to_binary(join(re:split("saturday","(?i:saturday|sunday)",[trim]))),
+ 2}]))),
+ <<"barfoo">> = iolist_to_binary(join(re:split("barfoo","(?<=(foo))bar\\1",[]))),
+ <<"">> = iolist_to_binary(join(re:split("saturday","(?i:saturday|sunday)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("saturday","(?i:saturday|sunday)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("saturday","(?i:saturday|sunday)",[]))),
- <<"">> = iolist_to_binary(join(re:split("sunday","(?i:saturday|sunday)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("saturday","(?i:saturday|sunday)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("sunday","(?i:saturday|sunday)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("sunday","(?i:saturday|sunday)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("sunday","(?i:saturday|sunday)",[]))),
- <<"">> = iolist_to_binary(join(re:split("Saturday","(?i:saturday|sunday)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("sunday","(?i:saturday|sunday)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("Saturday","(?i:saturday|sunday)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("Saturday","(?i:saturday|sunday)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("Saturday","(?i:saturday|sunday)",[]))),
- <<"">> = iolist_to_binary(join(re:split("Sunday","(?i:saturday|sunday)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("Saturday","(?i:saturday|sunday)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("Sunday","(?i:saturday|sunday)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("Sunday","(?i:saturday|sunday)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("Sunday","(?i:saturday|sunday)",[]))),
- <<"">> = iolist_to_binary(join(re:split("SATURDAY","(?i:saturday|sunday)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("Sunday","(?i:saturday|sunday)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("SATURDAY","(?i:saturday|sunday)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("SATURDAY","(?i:saturday|sunday)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("SATURDAY","(?i:saturday|sunday)",[]))),
- <<"">> = iolist_to_binary(join(re:split("SUNDAY","(?i:saturday|sunday)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("SATURDAY","(?i:saturday|sunday)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("SUNDAY","(?i:saturday|sunday)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("SUNDAY","(?i:saturday|sunday)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("SUNDAY","(?i:saturday|sunday)",[]))),
- <<"">> = iolist_to_binary(join(re:split("SunDay","(?i:saturday|sunday)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("SUNDAY","(?i:saturday|sunday)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("SunDay","(?i:saturday|sunday)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("SunDay","(?i:saturday|sunday)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("SunDay","(?i:saturday|sunday)",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abcx","(a(?i)bc|BB)x",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("SunDay","(?i:saturday|sunday)",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abcx","(a(?i)bc|BB)x",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abcx","(a(?i)bc|BB)x",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abcx","(a(?i)bc|BB)x",[]))),
- <<":aBC">> = iolist_to_binary(join(re:split("aBCx","(a(?i)bc|BB)x",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abcx","(a(?i)bc|BB)x",[]))),
+ <<":aBC">> = iolist_to_binary(join(re:split("aBCx","(a(?i)bc|BB)x",[trim]))),
<<":aBC:">> = iolist_to_binary(join(re:split("aBCx","(a(?i)bc|BB)x",[{parts,
- 2}]))),
- <<":aBC:">> = iolist_to_binary(join(re:split("aBCx","(a(?i)bc|BB)x",[]))),
- <<":bb">> = iolist_to_binary(join(re:split("bbx","(a(?i)bc|BB)x",[trim]))),
+ 2}]))),
+ <<":aBC:">> = iolist_to_binary(join(re:split("aBCx","(a(?i)bc|BB)x",[]))),
+ <<":bb">> = iolist_to_binary(join(re:split("bbx","(a(?i)bc|BB)x",[trim]))),
<<":bb:">> = iolist_to_binary(join(re:split("bbx","(a(?i)bc|BB)x",[{parts,
- 2}]))),
- <<":bb:">> = iolist_to_binary(join(re:split("bbx","(a(?i)bc|BB)x",[]))),
- <<":BB">> = iolist_to_binary(join(re:split("BBx","(a(?i)bc|BB)x",[trim]))),
+ 2}]))),
+ <<":bb:">> = iolist_to_binary(join(re:split("bbx","(a(?i)bc|BB)x",[]))),
+ <<":BB">> = iolist_to_binary(join(re:split("BBx","(a(?i)bc|BB)x",[trim]))),
<<":BB:">> = iolist_to_binary(join(re:split("BBx","(a(?i)bc|BB)x",[{parts,
- 2}]))),
- <<":BB:">> = iolist_to_binary(join(re:split("BBx","(a(?i)bc|BB)x",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a(?i)bc|BB)x",[trim]))),
+ 2}]))),
+ <<":BB:">> = iolist_to_binary(join(re:split("BBx","(a(?i)bc|BB)x",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a(?i)bc|BB)x",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a(?i)bc|BB)x",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a(?i)bc|BB)x",[]))),
- <<"abcX">> = iolist_to_binary(join(re:split("abcX","(a(?i)bc|BB)x",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(a(?i)bc|BB)x",[]))),
+ <<"abcX">> = iolist_to_binary(join(re:split("abcX","(a(?i)bc|BB)x",[trim]))),
<<"abcX">> = iolist_to_binary(join(re:split("abcX","(a(?i)bc|BB)x",[{parts,
- 2}]))),
- <<"abcX">> = iolist_to_binary(join(re:split("abcX","(a(?i)bc|BB)x",[]))),
- <<"aBCX">> = iolist_to_binary(join(re:split("aBCX","(a(?i)bc|BB)x",[trim]))),
+ 2}]))),
+ <<"abcX">> = iolist_to_binary(join(re:split("abcX","(a(?i)bc|BB)x",[]))),
+ <<"aBCX">> = iolist_to_binary(join(re:split("aBCX","(a(?i)bc|BB)x",[trim]))),
<<"aBCX">> = iolist_to_binary(join(re:split("aBCX","(a(?i)bc|BB)x",[{parts,
- 2}]))),
- <<"aBCX">> = iolist_to_binary(join(re:split("aBCX","(a(?i)bc|BB)x",[]))),
- <<"bbX">> = iolist_to_binary(join(re:split("bbX","(a(?i)bc|BB)x",[trim]))),
+ 2}]))),
+ <<"aBCX">> = iolist_to_binary(join(re:split("aBCX","(a(?i)bc|BB)x",[]))),
+ <<"bbX">> = iolist_to_binary(join(re:split("bbX","(a(?i)bc|BB)x",[trim]))),
<<"bbX">> = iolist_to_binary(join(re:split("bbX","(a(?i)bc|BB)x",[{parts,
- 2}]))),
- <<"bbX">> = iolist_to_binary(join(re:split("bbX","(a(?i)bc|BB)x",[]))),
- <<"BBX">> = iolist_to_binary(join(re:split("BBX","(a(?i)bc|BB)x",[trim]))),
+ 2}]))),
+ <<"bbX">> = iolist_to_binary(join(re:split("bbX","(a(?i)bc|BB)x",[]))),
+ <<"BBX">> = iolist_to_binary(join(re:split("BBX","(a(?i)bc|BB)x",[trim]))),
<<"BBX">> = iolist_to_binary(join(re:split("BBX","(a(?i)bc|BB)x",[{parts,
- 2}]))),
- <<"BBX">> = iolist_to_binary(join(re:split("BBX","(a(?i)bc|BB)x",[]))),
- <<":ac">> = iolist_to_binary(join(re:split("ac","^([ab](?i)[cd]|[ef])",[trim]))),
+ 2}]))),
+ <<"BBX">> = iolist_to_binary(join(re:split("BBX","(a(?i)bc|BB)x",[]))),
+ <<":ac">> = iolist_to_binary(join(re:split("ac","^([ab](?i)[cd]|[ef])",[trim]))),
<<":ac:">> = iolist_to_binary(join(re:split("ac","^([ab](?i)[cd]|[ef])",[{parts,
- 2}]))),
- <<":ac:">> = iolist_to_binary(join(re:split("ac","^([ab](?i)[cd]|[ef])",[]))),
- <<":aC">> = iolist_to_binary(join(re:split("aC","^([ab](?i)[cd]|[ef])",[trim]))),
+ 2}]))),
+ <<":ac:">> = iolist_to_binary(join(re:split("ac","^([ab](?i)[cd]|[ef])",[]))),
+ <<":aC">> = iolist_to_binary(join(re:split("aC","^([ab](?i)[cd]|[ef])",[trim]))),
<<":aC:">> = iolist_to_binary(join(re:split("aC","^([ab](?i)[cd]|[ef])",[{parts,
- 2}]))),
- <<":aC:">> = iolist_to_binary(join(re:split("aC","^([ab](?i)[cd]|[ef])",[]))),
- <<":bD">> = iolist_to_binary(join(re:split("bD","^([ab](?i)[cd]|[ef])",[trim]))),
+ 2}]))),
+ <<":aC:">> = iolist_to_binary(join(re:split("aC","^([ab](?i)[cd]|[ef])",[]))),
+ <<":bD">> = iolist_to_binary(join(re:split("bD","^([ab](?i)[cd]|[ef])",[trim]))),
<<":bD:">> = iolist_to_binary(join(re:split("bD","^([ab](?i)[cd]|[ef])",[{parts,
- 2}]))),
- <<":bD:">> = iolist_to_binary(join(re:split("bD","^([ab](?i)[cd]|[ef])",[]))),
- <<":e:lephant">> = iolist_to_binary(join(re:split("elephant","^([ab](?i)[cd]|[ef])",[trim]))),
+ 2}]))),
+ <<":bD:">> = iolist_to_binary(join(re:split("bD","^([ab](?i)[cd]|[ef])",[]))),
+ <<":e:lephant">> = iolist_to_binary(join(re:split("elephant","^([ab](?i)[cd]|[ef])",[trim]))),
<<":e:lephant">> = iolist_to_binary(join(re:split("elephant","^([ab](?i)[cd]|[ef])",[{parts,
- 2}]))),
- <<":e:lephant">> = iolist_to_binary(join(re:split("elephant","^([ab](?i)[cd]|[ef])",[]))),
- <<":E:urope">> = iolist_to_binary(join(re:split("Europe","^([ab](?i)[cd]|[ef])",[trim]))),
+ 2}]))),
+ <<":e:lephant">> = iolist_to_binary(join(re:split("elephant","^([ab](?i)[cd]|[ef])",[]))),
+ <<":E:urope">> = iolist_to_binary(join(re:split("Europe","^([ab](?i)[cd]|[ef])",[trim]))),
<<":E:urope">> = iolist_to_binary(join(re:split("Europe","^([ab](?i)[cd]|[ef])",[{parts,
- 2}]))),
- <<":E:urope">> = iolist_to_binary(join(re:split("Europe","^([ab](?i)[cd]|[ef])",[]))),
- <<":f:rog">> = iolist_to_binary(join(re:split("frog","^([ab](?i)[cd]|[ef])",[trim]))),
+ 2}]))),
+ <<":E:urope">> = iolist_to_binary(join(re:split("Europe","^([ab](?i)[cd]|[ef])",[]))),
+ <<":f:rog">> = iolist_to_binary(join(re:split("frog","^([ab](?i)[cd]|[ef])",[trim]))),
<<":f:rog">> = iolist_to_binary(join(re:split("frog","^([ab](?i)[cd]|[ef])",[{parts,
- 2}]))),
- <<":f:rog">> = iolist_to_binary(join(re:split("frog","^([ab](?i)[cd]|[ef])",[]))),
- <<":F:rance">> = iolist_to_binary(join(re:split("France","^([ab](?i)[cd]|[ef])",[trim]))),
+ 2}]))),
+ <<":f:rog">> = iolist_to_binary(join(re:split("frog","^([ab](?i)[cd]|[ef])",[]))),
+ <<":F:rance">> = iolist_to_binary(join(re:split("France","^([ab](?i)[cd]|[ef])",[trim]))),
<<":F:rance">> = iolist_to_binary(join(re:split("France","^([ab](?i)[cd]|[ef])",[{parts,
- 2}]))),
- <<":F:rance">> = iolist_to_binary(join(re:split("France","^([ab](?i)[cd]|[ef])",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^([ab](?i)[cd]|[ef])",[trim]))),
+ 2}]))),
+ <<":F:rance">> = iolist_to_binary(join(re:split("France","^([ab](?i)[cd]|[ef])",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^([ab](?i)[cd]|[ef])",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^([ab](?i)[cd]|[ef])",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^([ab](?i)[cd]|[ef])",[]))),
- <<"Africa">> = iolist_to_binary(join(re:split("Africa","^([ab](?i)[cd]|[ef])",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^([ab](?i)[cd]|[ef])",[]))),
+ <<"Africa">> = iolist_to_binary(join(re:split("Africa","^([ab](?i)[cd]|[ef])",[trim]))),
<<"Africa">> = iolist_to_binary(join(re:split("Africa","^([ab](?i)[cd]|[ef])",[{parts,
- 2}]))),
- <<"Africa">> = iolist_to_binary(join(re:split("Africa","^([ab](?i)[cd]|[ef])",[]))),
- <<":ab">> = iolist_to_binary(join(re:split("ab","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
+ 2}]))),
+ <<"Africa">> = iolist_to_binary(join(re:split("Africa","^([ab](?i)[cd]|[ef])",[]))),
+ <<":ab">> = iolist_to_binary(join(re:split("ab","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
<<":ab:">> = iolist_to_binary(join(re:split("ab","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[{parts,
- 2}]))),
- <<":ab:">> = iolist_to_binary(join(re:split("ab","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
- <<":aBd">> = iolist_to_binary(join(re:split("aBd","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
+ 2}]))),
+ <<":ab:">> = iolist_to_binary(join(re:split("ab","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
+ <<":aBd">> = iolist_to_binary(join(re:split("aBd","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
<<":aBd:">> = iolist_to_binary(join(re:split("aBd","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[{parts,
- 2}]))),
- <<":aBd:">> = iolist_to_binary(join(re:split("aBd","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
- <<":xy">> = iolist_to_binary(join(re:split("xy","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
+ 2}]))),
+ <<":aBd:">> = iolist_to_binary(join(re:split("aBd","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
+ <<":xy">> = iolist_to_binary(join(re:split("xy","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
<<":xy:">> = iolist_to_binary(join(re:split("xy","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[{parts,
- 2}]))),
- <<":xy:">> = iolist_to_binary(join(re:split("xy","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
- <<":xY">> = iolist_to_binary(join(re:split("xY","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
+ 2}]))),
+ <<":xy:">> = iolist_to_binary(join(re:split("xy","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
+ <<":xY">> = iolist_to_binary(join(re:split("xY","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
<<":xY:">> = iolist_to_binary(join(re:split("xY","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[{parts,
- 2}]))),
- <<":xY:">> = iolist_to_binary(join(re:split("xY","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
- <<":z:ebra">> = iolist_to_binary(join(re:split("zebra","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
+ 2}]))),
+ <<":xY:">> = iolist_to_binary(join(re:split("xY","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
+ <<":z:ebra">> = iolist_to_binary(join(re:split("zebra","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
<<":z:ebra">> = iolist_to_binary(join(re:split("zebra","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[{parts,
- 2}]))),
- <<":z:ebra">> = iolist_to_binary(join(re:split("zebra","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
- <<":Z:ambesi">> = iolist_to_binary(join(re:split("Zambesi","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
+ 2}]))),
+ <<":z:ebra">> = iolist_to_binary(join(re:split("zebra","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
+ <<":Z:ambesi">> = iolist_to_binary(join(re:split("Zambesi","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
<<":Z:ambesi">> = iolist_to_binary(join(re:split("Zambesi","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[{parts,
- 2}]))),
- <<":Z:ambesi">> = iolist_to_binary(join(re:split("Zambesi","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
+ 2}]))),
+ <<":Z:ambesi">> = iolist_to_binary(join(re:split("Zambesi","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
- <<"aCD">> = iolist_to_binary(join(re:split("aCD","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
+ <<"aCD">> = iolist_to_binary(join(re:split("aCD","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
<<"aCD">> = iolist_to_binary(join(re:split("aCD","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[{parts,
- 2}]))),
- <<"aCD">> = iolist_to_binary(join(re:split("aCD","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
- <<"XY">> = iolist_to_binary(join(re:split("XY","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
+ 2}]))),
+ <<"aCD">> = iolist_to_binary(join(re:split("aCD","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
+ <<"XY">> = iolist_to_binary(join(re:split("XY","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[trim]))),
<<"XY">> = iolist_to_binary(join(re:split("XY","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[{parts,
- 2}]))),
- <<"XY">> = iolist_to_binary(join(re:split("XY","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
+ 2}]))),
+ <<"XY">> = iolist_to_binary(join(re:split("XY","^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)",[]))),
<<"foo
">> = iolist_to_binary(join(re:split("foo
-bar","(?<=foo\\n)^bar",[multiline,trim]))),
+bar","(?<=foo\\n)^bar",[multiline,trim]))),
<<"foo
:">> = iolist_to_binary(join(re:split("foo
-bar","(?<=foo\\n)^bar",[multiline,{parts,2}]))),
+bar","(?<=foo\\n)^bar",[multiline,{parts,2}]))),
<<"foo
:">> = iolist_to_binary(join(re:split("foo
-bar","(?<=foo\\n)^bar",[multiline]))),
+bar","(?<=foo\\n)^bar",[multiline]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=foo\\n)^bar",[multiline,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=foo\\n)^bar",[multiline,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=foo\\n)^bar",[multiline]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=foo\\n)^bar",[multiline]))),
<<"bar">> = iolist_to_binary(join(re:split("bar","(?<=foo\\n)^bar",[multiline,
- trim]))),
+ trim]))),
<<"bar">> = iolist_to_binary(join(re:split("bar","(?<=foo\\n)^bar",[multiline,
{parts,
- 2}]))),
- <<"bar">> = iolist_to_binary(join(re:split("bar","(?<=foo\\n)^bar",[multiline]))),
+ 2}]))),
+ <<"bar">> = iolist_to_binary(join(re:split("bar","(?<=foo\\n)^bar",[multiline]))),
<<"baz
bar">> = iolist_to_binary(join(re:split("baz
-bar","(?<=foo\\n)^bar",[multiline,trim]))),
+bar","(?<=foo\\n)^bar",[multiline,trim]))),
<<"baz
bar">> = iolist_to_binary(join(re:split("baz
-bar","(?<=foo\\n)^bar",[multiline,{parts,2}]))),
+bar","(?<=foo\\n)^bar",[multiline,{parts,2}]))),
<<"baz
bar">> = iolist_to_binary(join(re:split("baz
-bar","(?<=foo\\n)^bar",[multiline]))),
- <<"bar">> = iolist_to_binary(join(re:split("barbaz","(?<=(?<!foo)bar)baz",[trim]))),
+bar","(?<=foo\\n)^bar",[multiline]))),
+ <<"bar">> = iolist_to_binary(join(re:split("barbaz","(?<=(?<!foo)bar)baz",[trim]))),
<<"bar:">> = iolist_to_binary(join(re:split("barbaz","(?<=(?<!foo)bar)baz",[{parts,
- 2}]))),
- <<"bar:">> = iolist_to_binary(join(re:split("barbaz","(?<=(?<!foo)bar)baz",[]))),
- <<"barbar">> = iolist_to_binary(join(re:split("barbarbaz","(?<=(?<!foo)bar)baz",[trim]))),
+ 2}]))),
+ <<"bar:">> = iolist_to_binary(join(re:split("barbaz","(?<=(?<!foo)bar)baz",[]))),
+ <<"barbar">> = iolist_to_binary(join(re:split("barbarbaz","(?<=(?<!foo)bar)baz",[trim]))),
<<"barbar:">> = iolist_to_binary(join(re:split("barbarbaz","(?<=(?<!foo)bar)baz",[{parts,
- 2}]))),
- <<"barbar:">> = iolist_to_binary(join(re:split("barbarbaz","(?<=(?<!foo)bar)baz",[]))),
- <<"koobar">> = iolist_to_binary(join(re:split("koobarbaz","(?<=(?<!foo)bar)baz",[trim]))),
+ 2}]))),
+ <<"barbar:">> = iolist_to_binary(join(re:split("barbarbaz","(?<=(?<!foo)bar)baz",[]))),
+ <<"koobar">> = iolist_to_binary(join(re:split("koobarbaz","(?<=(?<!foo)bar)baz",[trim]))),
<<"koobar:">> = iolist_to_binary(join(re:split("koobarbaz","(?<=(?<!foo)bar)baz",[{parts,
- 2}]))),
- <<"koobar:">> = iolist_to_binary(join(re:split("koobarbaz","(?<=(?<!foo)bar)baz",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(?<!foo)bar)baz",[trim]))),
+ 2}]))),
+ <<"koobar:">> = iolist_to_binary(join(re:split("koobarbaz","(?<=(?<!foo)bar)baz",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(?<!foo)bar)baz",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(?<!foo)bar)baz",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(?<!foo)bar)baz",[]))),
- <<"baz">> = iolist_to_binary(join(re:split("baz","(?<=(?<!foo)bar)baz",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(?<!foo)bar)baz",[]))),
+ <<"baz">> = iolist_to_binary(join(re:split("baz","(?<=(?<!foo)bar)baz",[trim]))),
<<"baz">> = iolist_to_binary(join(re:split("baz","(?<=(?<!foo)bar)baz",[{parts,
- 2}]))),
- <<"baz">> = iolist_to_binary(join(re:split("baz","(?<=(?<!foo)bar)baz",[]))),
- <<"foobarbaz">> = iolist_to_binary(join(re:split("foobarbaz","(?<=(?<!foo)bar)baz",[trim]))),
+ 2}]))),
+ <<"baz">> = iolist_to_binary(join(re:split("baz","(?<=(?<!foo)bar)baz",[]))),
+ <<"foobarbaz">> = iolist_to_binary(join(re:split("foobarbaz","(?<=(?<!foo)bar)baz",[trim]))),
<<"foobarbaz">> = iolist_to_binary(join(re:split("foobarbaz","(?<=(?<!foo)bar)baz",[{parts,
- 2}]))),
- <<"foobarbaz">> = iolist_to_binary(join(re:split("foobarbaz","(?<=(?<!foo)bar)baz",[]))),
- <<"a">> = iolist_to_binary(join(re:split("a","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"foobarbaz">> = iolist_to_binary(join(re:split("foobarbaz","(?<=(?<!foo)bar)baz",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","^(a\\1?){4}$",[trim]))),
<<"a">> = iolist_to_binary(join(re:split("a","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"a">> = iolist_to_binary(join(re:split("a","^(a\\1?){4}$",[]))),
- <<"aa">> = iolist_to_binary(join(re:split("aa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","^(a\\1?){4}$",[]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aa","^(a\\1?){4}$",[trim]))),
<<"aa">> = iolist_to_binary(join(re:split("aa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"aa">> = iolist_to_binary(join(re:split("aa","^(a\\1?){4}$",[]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aa","^(a\\1?){4}$",[]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a\\1?){4}$",[trim]))),
<<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a\\1?){4}$",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a\\1?){4}$",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaaa","^(a\\1?){4}$",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaaaa","^(a\\1?){4}$",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaaaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaaaa","^(a\\1?){4}$",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaaaaa","^(a\\1?){4}$",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaaaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaaaaaa","^(a\\1?){4}$",[]))),
- <<"aaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaaaaaa","^(a\\1?){4}$",[]))),
+ <<"aaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a\\1?){4}$",[trim]))),
<<"aaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"aaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a\\1?){4}$",[]))),
- <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a\\1?){4}$",[]))),
+ <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?){4}$",[trim]))),
<<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?){4}$",[]))),
- <<":aaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?){4}$",[]))),
+ <<":aaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?){4}$",[trim]))),
<<":aaaa:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<":aaaa:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?){4}$",[]))),
- <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<":aaaa:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?){4}$",[]))),
+ <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
<<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?){4}$",[]))),
- <<"aaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?){4}$",[]))),
+ <<"aaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
<<"aaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaa","^(a\\1?){4}$",[]))),
- <<"aaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaa","^(a\\1?){4}$",[]))),
+ <<"aaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
<<"aaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaa","^(a\\1?){4}$",[]))),
- <<"aaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaa","^(a\\1?){4}$",[]))),
+ <<"aaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
<<"aaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaa","^(a\\1?){4}$",[]))),
- <<"aaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaa","^(a\\1?){4}$",[]))),
+ <<"aaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
<<"aaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaa","^(a\\1?){4}$",[]))),
- <<"aaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaa","^(a\\1?){4}$",[]))),
+ <<"aaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
<<"aaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaa","^(a\\1?){4}$",[]))),
- <<"a">> = iolist_to_binary(join(re:split("a","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaa","^(a\\1?){4}$",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<"a">> = iolist_to_binary(join(re:split("a","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<"a">> = iolist_to_binary(join(re:split("a","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<"aa">> = iolist_to_binary(join(re:split("aa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<"aa">> = iolist_to_binary(join(re:split("aa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<"aa">> = iolist_to_binary(join(re:split("aa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<":a:a:a:a">> = iolist_to_binary(join(re:split("aaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<":a:a:a:a">> = iolist_to_binary(join(re:split("aaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<":a:a:a:a:">> = iolist_to_binary(join(re:split("aaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<":a:a:a:a:">> = iolist_to_binary(join(re:split("aaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<":a:aa:a:a">> = iolist_to_binary(join(re:split("aaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<":a:a:a:a:">> = iolist_to_binary(join(re:split("aaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<":a:aa:a:a">> = iolist_to_binary(join(re:split("aaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<":a:aa:a:a:">> = iolist_to_binary(join(re:split("aaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<":a:aa:a:a:">> = iolist_to_binary(join(re:split("aaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<":a:aa:a:aa">> = iolist_to_binary(join(re:split("aaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<":a:aa:a:a:">> = iolist_to_binary(join(re:split("aaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<":a:aa:a:aa">> = iolist_to_binary(join(re:split("aaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<":a:aa:a:aa:">> = iolist_to_binary(join(re:split("aaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<":a:aa:a:aa:">> = iolist_to_binary(join(re:split("aaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<":a:aa:aaa:a">> = iolist_to_binary(join(re:split("aaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<":a:aa:a:aa:">> = iolist_to_binary(join(re:split("aaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<":a:aa:aaa:a">> = iolist_to_binary(join(re:split("aaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<":a:aa:aaa:a:">> = iolist_to_binary(join(re:split("aaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<":a:aa:aaa:a:">> = iolist_to_binary(join(re:split("aaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<"aaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<":a:aa:aaa:a:">> = iolist_to_binary(join(re:split("aaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<"aaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<"aaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<"aaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<":a:aa:aaa:aaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<":a:aa:aaa:aaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<":a:aa:aaa:aaaa:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<":a:aa:aaa:aaaa:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<":a:aa:aaa:aaaa:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<"aaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<"aaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<"aaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<"aaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<"aaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<"aaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<"aaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<"aaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<"aaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<"aaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<"aaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<"aaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<"aaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<"aaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[trim]))),
<<"aaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","abc",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaa","^(a\\1?)(a\\1?)(a\\2?)(a\\3?)$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","abc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","abc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","abc",[]))),
- <<"x:y">> = iolist_to_binary(join(re:split("xabcy","abc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","abc",[]))),
+ <<"x:y">> = iolist_to_binary(join(re:split("xabcy","abc",[trim]))),
<<"x:y">> = iolist_to_binary(join(re:split("xabcy","abc",[{parts,
- 2}]))),
- <<"x:y">> = iolist_to_binary(join(re:split("xabcy","abc",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("ababc","abc",[trim]))),
+ 2}]))),
+ <<"x:y">> = iolist_to_binary(join(re:split("xabcy","abc",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ababc","abc",[trim]))),
<<"ab:">> = iolist_to_binary(join(re:split("ababc","abc",[{parts,
- 2}]))),
- <<"ab:">> = iolist_to_binary(join(re:split("ababc","abc",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[trim]))),
+ 2}]))),
+ <<"ab:">> = iolist_to_binary(join(re:split("ababc","abc",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[]))),
- <<"xbc">> = iolist_to_binary(join(re:split("xbc","abc",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[]))),
+ <<"xbc">> = iolist_to_binary(join(re:split("xbc","abc",[trim]))),
<<"xbc">> = iolist_to_binary(join(re:split("xbc","abc",[{parts,
- 2}]))),
- <<"xbc">> = iolist_to_binary(join(re:split("xbc","abc",[]))),
- <<"axc">> = iolist_to_binary(join(re:split("axc","abc",[trim]))),
+ 2}]))),
+ <<"xbc">> = iolist_to_binary(join(re:split("xbc","abc",[]))),
+ <<"axc">> = iolist_to_binary(join(re:split("axc","abc",[trim]))),
<<"axc">> = iolist_to_binary(join(re:split("axc","abc",[{parts,
- 2}]))),
- <<"axc">> = iolist_to_binary(join(re:split("axc","abc",[]))),
- <<"abx">> = iolist_to_binary(join(re:split("abx","abc",[trim]))),
+ 2}]))),
+ <<"axc">> = iolist_to_binary(join(re:split("axc","abc",[]))),
+ <<"abx">> = iolist_to_binary(join(re:split("abx","abc",[trim]))),
<<"abx">> = iolist_to_binary(join(re:split("abx","abc",[{parts,
- 2}]))),
- <<"abx">> = iolist_to_binary(join(re:split("abx","abc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","ab*c",[trim]))),
+ 2}]))),
+ <<"abx">> = iolist_to_binary(join(re:split("abx","abc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","ab*c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","ab*c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","ab*c",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","ab*bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","ab*c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","ab*bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","ab*bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","ab*bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abbc","ab*bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","ab*bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abbc","ab*bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abbc","ab*bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abbc","ab*bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abbbbc","ab*bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abbc","ab*bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abbbbc","ab*bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abbbbc","ab*bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abbbbc","ab*bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abbbbc",".{1}",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abbbbc","ab*bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abbbbc",".{1}",[trim]))),
<<":bbbbc">> = iolist_to_binary(join(re:split("abbbbc",".{1}",[{parts,
- 2}]))),
- <<"::::::">> = iolist_to_binary(join(re:split("abbbbc",".{1}",[]))),
- <<":bc">> = iolist_to_binary(join(re:split("abbbbc",".{3,4}",[trim]))),
+ 2}]))),
+ <<"::::::">> = iolist_to_binary(join(re:split("abbbbc",".{1}",[]))),
+ <<":bc">> = iolist_to_binary(join(re:split("abbbbc",".{3,4}",[trim]))),
<<":bc">> = iolist_to_binary(join(re:split("abbbbc",".{3,4}",[{parts,
- 2}]))),
- <<":bc">> = iolist_to_binary(join(re:split("abbbbc",".{3,4}",[]))),
- <<"">> = iolist_to_binary(join(re:split("abbbbc","ab{0,}bc",[trim]))),
+ 2}]))),
+ <<":bc">> = iolist_to_binary(join(re:split("abbbbc",".{3,4}",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abbbbc","ab{0,}bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abbbbc","ab{0,}bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abbbbc","ab{0,}bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abbc","ab+bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abbbbc","ab{0,}bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abbc","ab+bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abbc","ab+bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abbc","ab+bc",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab+bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abbc","ab+bc",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab+bc",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab+bc",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab+bc",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","ab+bc",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab+bc",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","ab+bc",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","ab+bc",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","ab+bc",[]))),
- <<"abq">> = iolist_to_binary(join(re:split("abq","ab+bc",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","ab+bc",[]))),
+ <<"abq">> = iolist_to_binary(join(re:split("abq","ab+bc",[trim]))),
<<"abq">> = iolist_to_binary(join(re:split("abq","ab+bc",[{parts,
- 2}]))),
- <<"abq">> = iolist_to_binary(join(re:split("abq","ab+bc",[]))),
+ 2}]))),
+ <<"abq">> = iolist_to_binary(join(re:split("abq","ab+bc",[]))),
ok.
run15() ->
- <<"">> = iolist_to_binary(join(re:split("abbbbc","ab+bc",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("abbbbc","ab+bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abbbbc","ab+bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abbbbc","ab+bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abbbbc","ab{1,}bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abbbbc","ab+bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abbbbc","ab{1,}bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abbbbc","ab{1,}bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abbbbc","ab{1,}bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abbbbc","ab{1,3}bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abbbbc","ab{1,}bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abbbbc","ab{1,3}bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abbbbc","ab{1,3}bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abbbbc","ab{1,3}bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abbbbc","ab{3,4}bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abbbbc","ab{1,3}bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abbbbc","ab{3,4}bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abbbbc","ab{3,4}bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abbbbc","ab{3,4}bc",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{4,5}bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abbbbc","ab{3,4}bc",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{4,5}bc",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{4,5}bc",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{4,5}bc",[]))),
- <<"abq">> = iolist_to_binary(join(re:split("abq","ab{4,5}bc",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{4,5}bc",[]))),
+ <<"abq">> = iolist_to_binary(join(re:split("abq","ab{4,5}bc",[trim]))),
<<"abq">> = iolist_to_binary(join(re:split("abq","ab{4,5}bc",[{parts,
- 2}]))),
- <<"abq">> = iolist_to_binary(join(re:split("abq","ab{4,5}bc",[]))),
- <<"abbbbc">> = iolist_to_binary(join(re:split("abbbbc","ab{4,5}bc",[trim]))),
+ 2}]))),
+ <<"abq">> = iolist_to_binary(join(re:split("abq","ab{4,5}bc",[]))),
+ <<"abbbbc">> = iolist_to_binary(join(re:split("abbbbc","ab{4,5}bc",[trim]))),
<<"abbbbc">> = iolist_to_binary(join(re:split("abbbbc","ab{4,5}bc",[{parts,
- 2}]))),
- <<"abbbbc">> = iolist_to_binary(join(re:split("abbbbc","ab{4,5}bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abbc","ab?bc",[trim]))),
+ 2}]))),
+ <<"abbbbc">> = iolist_to_binary(join(re:split("abbbbc","ab{4,5}bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abbc","ab?bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abbc","ab?bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abbc","ab?bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","ab?bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abbc","ab?bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","ab?bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","ab?bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","ab?bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","ab{0,1}bc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","ab?bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","ab{0,1}bc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","ab{0,1}bc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","ab{0,1}bc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","ab?c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","ab{0,1}bc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","ab?c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","ab?c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","ab?c",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","ab{0,1}c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","ab?c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","ab{0,1}c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","ab{0,1}c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","ab{0,1}c",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","^abc$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","ab{0,1}c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","^abc$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","^abc$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","^abc$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","^abc$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[]))),
- <<"abbbbc">> = iolist_to_binary(join(re:split("abbbbc","^abc$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[]))),
+ <<"abbbbc">> = iolist_to_binary(join(re:split("abbbbc","^abc$",[trim]))),
<<"abbbbc">> = iolist_to_binary(join(re:split("abbbbc","^abc$",[{parts,
- 2}]))),
- <<"abbbbc">> = iolist_to_binary(join(re:split("abbbbc","^abc$",[]))),
- <<"abcc">> = iolist_to_binary(join(re:split("abcc","^abc$",[trim]))),
+ 2}]))),
+ <<"abbbbc">> = iolist_to_binary(join(re:split("abbbbc","^abc$",[]))),
+ <<"abcc">> = iolist_to_binary(join(re:split("abcc","^abc$",[trim]))),
<<"abcc">> = iolist_to_binary(join(re:split("abcc","^abc$",[{parts,
- 2}]))),
- <<"abcc">> = iolist_to_binary(join(re:split("abcc","^abc$",[]))),
- <<":c">> = iolist_to_binary(join(re:split("abcc","^abc",[trim]))),
+ 2}]))),
+ <<"abcc">> = iolist_to_binary(join(re:split("abcc","^abc$",[]))),
+ <<":c">> = iolist_to_binary(join(re:split("abcc","^abc",[trim]))),
<<":c">> = iolist_to_binary(join(re:split("abcc","^abc",[{parts,
- 2}]))),
- <<":c">> = iolist_to_binary(join(re:split("abcc","^abc",[]))),
- <<"a">> = iolist_to_binary(join(re:split("aabc","abc$",[trim]))),
+ 2}]))),
+ <<":c">> = iolist_to_binary(join(re:split("abcc","^abc",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("aabc","abc$",[trim]))),
<<"a:">> = iolist_to_binary(join(re:split("aabc","abc$",[{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("aabc","abc$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc$",[trim]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("aabc","abc$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc$",[]))),
- <<"a">> = iolist_to_binary(join(re:split("aabc","abc$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc$",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("aabc","abc$",[trim]))),
<<"a:">> = iolist_to_binary(join(re:split("aabc","abc$",[{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("aabc","abc$",[]))),
- <<"aabcd">> = iolist_to_binary(join(re:split("aabcd","abc$",[trim]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("aabc","abc$",[]))),
+ <<"aabcd">> = iolist_to_binary(join(re:split("aabcd","abc$",[trim]))),
<<"aabcd">> = iolist_to_binary(join(re:split("aabcd","abc$",[{parts,
- 2}]))),
- <<"aabcd">> = iolist_to_binary(join(re:split("aabcd","abc$",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^",[trim]))),
+ 2}]))),
+ <<"aabcd">> = iolist_to_binary(join(re:split("aabcd","abc$",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","^",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","$",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","$",[trim]))),
<<"abc:">> = iolist_to_binary(join(re:split("abc","$",[{parts,
- 2}]))),
- <<"abc:">> = iolist_to_binary(join(re:split("abc","$",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","a.c",[trim]))),
+ 2}]))),
+ <<"abc:">> = iolist_to_binary(join(re:split("abc","$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","a.c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","a.c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","a.c",[]))),
- <<"">> = iolist_to_binary(join(re:split("axc","a.c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","a.c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("axc","a.c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("axc","a.c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("axc","a.c",[]))),
- <<"">> = iolist_to_binary(join(re:split("axyzc","a.*c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("axc","a.c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("axyzc","a.*c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("axyzc","a.*c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("axyzc","a.*c",[]))),
- <<"">> = iolist_to_binary(join(re:split("abd","a[bc]d",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("axyzc","a.*c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abd","a[bc]d",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abd","a[bc]d",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abd","a[bc]d",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[bc]d",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abd","a[bc]d",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[bc]d",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[bc]d",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[bc]d",[]))),
- <<"axyzd">> = iolist_to_binary(join(re:split("axyzd","a[bc]d",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[bc]d",[]))),
+ <<"axyzd">> = iolist_to_binary(join(re:split("axyzd","a[bc]d",[trim]))),
<<"axyzd">> = iolist_to_binary(join(re:split("axyzd","a[bc]d",[{parts,
- 2}]))),
- <<"axyzd">> = iolist_to_binary(join(re:split("axyzd","a[bc]d",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","a[bc]d",[trim]))),
+ 2}]))),
+ <<"axyzd">> = iolist_to_binary(join(re:split("axyzd","a[bc]d",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","a[bc]d",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","a[bc]d",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","a[bc]d",[]))),
- <<"">> = iolist_to_binary(join(re:split("ace","a[b-d]e",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","a[bc]d",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ace","a[b-d]e",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ace","a[b-d]e",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ace","a[b-d]e",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ace","a[b-d]e",[]))),
ok.
run16() ->
- <<"a">> = iolist_to_binary(join(re:split("aac","a[b-d]",[trim]))),
+ <<"a">> = iolist_to_binary(join(re:split("aac","a[b-d]",[trim]))),
<<"a:">> = iolist_to_binary(join(re:split("aac","a[b-d]",[{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("aac","a[b-d]",[]))),
- <<"">> = iolist_to_binary(join(re:split("a-","a[-b]",[trim]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("aac","a[b-d]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a-","a[-b]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a-","a[-b]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a-","a[-b]",[]))),
- <<"">> = iolist_to_binary(join(re:split("a-","a[b-]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a-","a[-b]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a-","a[b-]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a-","a[b-]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a-","a[b-]",[]))),
- <<"">> = iolist_to_binary(join(re:split("a]","a]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a-","a[b-]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a]","a]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a]","a]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a]","a]",[]))),
- <<"">> = iolist_to_binary(join(re:split("a]b","a[]]b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a]","a]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a]b","a[]]b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a]b","a[]]b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a]b","a[]]b",[]))),
- <<"">> = iolist_to_binary(join(re:split("aed","a[^bc]d",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a]b","a[]]b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aed","a[^bc]d",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aed","a[^bc]d",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aed","a[^bc]d",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^bc]d",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aed","a[^bc]d",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^bc]d",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^bc]d",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^bc]d",[]))),
- <<"abd">> = iolist_to_binary(join(re:split("abd","a[^bc]d",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^bc]d",[]))),
+ <<"abd">> = iolist_to_binary(join(re:split("abd","a[^bc]d",[trim]))),
<<"abd">> = iolist_to_binary(join(re:split("abd","a[^bc]d",[{parts,
- 2}]))),
- <<"abd">> = iolist_to_binary(join(re:split("abd","a[^bc]d",[]))),
- <<"abd">> = iolist_to_binary(join(re:split("abd","a[^bc]d",[trim]))),
+ 2}]))),
+ <<"abd">> = iolist_to_binary(join(re:split("abd","a[^bc]d",[]))),
+ <<"abd">> = iolist_to_binary(join(re:split("abd","a[^bc]d",[trim]))),
<<"abd">> = iolist_to_binary(join(re:split("abd","a[^bc]d",[{parts,
- 2}]))),
- <<"abd">> = iolist_to_binary(join(re:split("abd","a[^bc]d",[]))),
- <<"">> = iolist_to_binary(join(re:split("adc","a[^-b]c",[trim]))),
+ 2}]))),
+ <<"abd">> = iolist_to_binary(join(re:split("abd","a[^bc]d",[]))),
+ <<"">> = iolist_to_binary(join(re:split("adc","a[^-b]c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("adc","a[^-b]c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("adc","a[^-b]c",[]))),
- <<"">> = iolist_to_binary(join(re:split("adc","a[^]b]c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("adc","a[^-b]c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("adc","a[^]b]c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("adc","a[^]b]c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("adc","a[^]b]c",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^]b]c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("adc","a[^]b]c",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^]b]c",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^]b]c",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^]b]c",[]))),
- <<"">> = iolist_to_binary(join(re:split("a-c","a[^]b]c",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^]b]c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a-c","a[^]b]c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a-c","a[^]b]c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a-c","a[^]b]c",[]))),
- <<"a]c">> = iolist_to_binary(join(re:split("a]c","a[^]b]c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a-c","a[^]b]c",[]))),
+ <<"a]c">> = iolist_to_binary(join(re:split("a]c","a[^]b]c",[trim]))),
<<"a]c">> = iolist_to_binary(join(re:split("a]c","a[^]b]c",[{parts,
- 2}]))),
- <<"a]c">> = iolist_to_binary(join(re:split("a]c","a[^]b]c",[]))),
- <<":-">> = iolist_to_binary(join(re:split("a-","\\ba\\b",[trim]))),
+ 2}]))),
+ <<"a]c">> = iolist_to_binary(join(re:split("a]c","a[^]b]c",[]))),
+ <<":-">> = iolist_to_binary(join(re:split("a-","\\ba\\b",[trim]))),
<<":-">> = iolist_to_binary(join(re:split("a-","\\ba\\b",[{parts,
- 2}]))),
- <<":-">> = iolist_to_binary(join(re:split("a-","\\ba\\b",[]))),
- <<"-">> = iolist_to_binary(join(re:split("-a","\\ba\\b",[trim]))),
+ 2}]))),
+ <<":-">> = iolist_to_binary(join(re:split("a-","\\ba\\b",[]))),
+ <<"-">> = iolist_to_binary(join(re:split("-a","\\ba\\b",[trim]))),
<<"-:">> = iolist_to_binary(join(re:split("-a","\\ba\\b",[{parts,
- 2}]))),
- <<"-:">> = iolist_to_binary(join(re:split("-a","\\ba\\b",[]))),
- <<"-:-">> = iolist_to_binary(join(re:split("-a-","\\ba\\b",[trim]))),
+ 2}]))),
+ <<"-:">> = iolist_to_binary(join(re:split("-a","\\ba\\b",[]))),
+ <<"-:-">> = iolist_to_binary(join(re:split("-a-","\\ba\\b",[trim]))),
<<"-:-">> = iolist_to_binary(join(re:split("-a-","\\ba\\b",[{parts,
- 2}]))),
- <<"-:-">> = iolist_to_binary(join(re:split("-a-","\\ba\\b",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\by\\b",[trim]))),
+ 2}]))),
+ <<"-:-">> = iolist_to_binary(join(re:split("-a-","\\ba\\b",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\by\\b",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\by\\b",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\by\\b",[]))),
- <<"xy">> = iolist_to_binary(join(re:split("xy","\\by\\b",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\by\\b",[]))),
+ <<"xy">> = iolist_to_binary(join(re:split("xy","\\by\\b",[trim]))),
<<"xy">> = iolist_to_binary(join(re:split("xy","\\by\\b",[{parts,
- 2}]))),
- <<"xy">> = iolist_to_binary(join(re:split("xy","\\by\\b",[]))),
- <<"yz">> = iolist_to_binary(join(re:split("yz","\\by\\b",[trim]))),
+ 2}]))),
+ <<"xy">> = iolist_to_binary(join(re:split("xy","\\by\\b",[]))),
+ <<"yz">> = iolist_to_binary(join(re:split("yz","\\by\\b",[trim]))),
<<"yz">> = iolist_to_binary(join(re:split("yz","\\by\\b",[{parts,
- 2}]))),
- <<"yz">> = iolist_to_binary(join(re:split("yz","\\by\\b",[]))),
- <<"xyz">> = iolist_to_binary(join(re:split("xyz","\\by\\b",[trim]))),
+ 2}]))),
+ <<"yz">> = iolist_to_binary(join(re:split("yz","\\by\\b",[]))),
+ <<"xyz">> = iolist_to_binary(join(re:split("xyz","\\by\\b",[trim]))),
<<"xyz">> = iolist_to_binary(join(re:split("xyz","\\by\\b",[{parts,
- 2}]))),
- <<"xyz">> = iolist_to_binary(join(re:split("xyz","\\by\\b",[]))),
- <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","\\Ba\\B",[trim]))),
+ 2}]))),
+ <<"xyz">> = iolist_to_binary(join(re:split("xyz","\\by\\b",[]))),
+ <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","\\Ba\\B",[trim]))),
<<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","\\Ba\\B",[{parts,
- 2}]))),
- <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","\\Ba\\B",[]))),
- <<"a-">> = iolist_to_binary(join(re:split("a-","\\Ba\\B",[trim]))),
+ 2}]))),
+ <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","\\Ba\\B",[]))),
+ <<"a-">> = iolist_to_binary(join(re:split("a-","\\Ba\\B",[trim]))),
<<"a-">> = iolist_to_binary(join(re:split("a-","\\Ba\\B",[{parts,
- 2}]))),
- <<"a-">> = iolist_to_binary(join(re:split("a-","\\Ba\\B",[]))),
- <<"-a">> = iolist_to_binary(join(re:split("-a","\\Ba\\B",[trim]))),
+ 2}]))),
+ <<"a-">> = iolist_to_binary(join(re:split("a-","\\Ba\\B",[]))),
+ <<"-a">> = iolist_to_binary(join(re:split("-a","\\Ba\\B",[trim]))),
<<"-a">> = iolist_to_binary(join(re:split("-a","\\Ba\\B",[{parts,
- 2}]))),
- <<"-a">> = iolist_to_binary(join(re:split("-a","\\Ba\\B",[]))),
- <<"-a-">> = iolist_to_binary(join(re:split("-a-","\\Ba\\B",[trim]))),
+ 2}]))),
+ <<"-a">> = iolist_to_binary(join(re:split("-a","\\Ba\\B",[]))),
+ <<"-a-">> = iolist_to_binary(join(re:split("-a-","\\Ba\\B",[trim]))),
<<"-a-">> = iolist_to_binary(join(re:split("-a-","\\Ba\\B",[{parts,
- 2}]))),
- <<"-a-">> = iolist_to_binary(join(re:split("-a-","\\Ba\\B",[]))),
- <<"x">> = iolist_to_binary(join(re:split("xy","\\By\\b",[trim]))),
+ 2}]))),
+ <<"-a-">> = iolist_to_binary(join(re:split("-a-","\\Ba\\B",[]))),
+ <<"x">> = iolist_to_binary(join(re:split("xy","\\By\\b",[trim]))),
<<"x:">> = iolist_to_binary(join(re:split("xy","\\By\\b",[{parts,
- 2}]))),
- <<"x:">> = iolist_to_binary(join(re:split("xy","\\By\\b",[]))),
- <<":z">> = iolist_to_binary(join(re:split("yz","\\by\\B",[trim]))),
+ 2}]))),
+ <<"x:">> = iolist_to_binary(join(re:split("xy","\\By\\b",[]))),
+ <<":z">> = iolist_to_binary(join(re:split("yz","\\by\\B",[trim]))),
<<":z">> = iolist_to_binary(join(re:split("yz","\\by\\B",[{parts,
- 2}]))),
- <<":z">> = iolist_to_binary(join(re:split("yz","\\by\\B",[]))),
- <<"x:z">> = iolist_to_binary(join(re:split("xyz","\\By\\B",[trim]))),
+ 2}]))),
+ <<":z">> = iolist_to_binary(join(re:split("yz","\\by\\B",[]))),
+ <<"x:z">> = iolist_to_binary(join(re:split("xyz","\\By\\B",[trim]))),
<<"x:z">> = iolist_to_binary(join(re:split("xyz","\\By\\B",[{parts,
- 2}]))),
- <<"x:z">> = iolist_to_binary(join(re:split("xyz","\\By\\B",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","\\w",[trim]))),
+ 2}]))),
+ <<"x:z">> = iolist_to_binary(join(re:split("xyz","\\By\\B",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("-","\\W",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("-","\\W",[trim]))),
<<":">> = iolist_to_binary(join(re:split("-","\\W",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("-","\\W",[]))),
- <<"::::Failers">> = iolist_to_binary(join(re:split("*** Failers","\\W",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("-","\\W",[]))),
+ <<"::::Failers">> = iolist_to_binary(join(re:split("*** Failers","\\W",[trim]))),
<<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\W",[{parts,
- 2}]))),
- <<"::::Failers">> = iolist_to_binary(join(re:split("*** Failers","\\W",[]))),
- <<"">> = iolist_to_binary(join(re:split("-","\\W",[trim]))),
+ 2}]))),
+ <<"::::Failers">> = iolist_to_binary(join(re:split("*** Failers","\\W",[]))),
+ <<"">> = iolist_to_binary(join(re:split("-","\\W",[trim]))),
<<":">> = iolist_to_binary(join(re:split("-","\\W",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("-","\\W",[]))),
- <<"a">> = iolist_to_binary(join(re:split("a","\\W",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("-","\\W",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","\\W",[trim]))),
<<"a">> = iolist_to_binary(join(re:split("a","\\W",[{parts,
- 2}]))),
- <<"a">> = iolist_to_binary(join(re:split("a","\\W",[]))),
- <<"">> = iolist_to_binary(join(re:split("a b","a\\sb",[trim]))),
+ 2}]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","\\W",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a b","a\\sb",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a b","a\\sb",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a b","a\\sb",[]))),
- <<"">> = iolist_to_binary(join(re:split("a-b","a\\Sb",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a b","a\\sb",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a-b","a\\Sb",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a-b","a\\Sb",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a-b","a\\Sb",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a\\Sb",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a-b","a\\Sb",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a\\Sb",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a\\Sb",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a\\Sb",[]))),
- <<"">> = iolist_to_binary(join(re:split("a-b","a\\Sb",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a\\Sb",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a-b","a\\Sb",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a-b","a\\Sb",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a-b","a\\Sb",[]))),
- <<"a b">> = iolist_to_binary(join(re:split("a b","a\\Sb",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a-b","a\\Sb",[]))),
+ <<"a b">> = iolist_to_binary(join(re:split("a b","a\\Sb",[trim]))),
<<"a b">> = iolist_to_binary(join(re:split("a b","a\\Sb",[{parts,
- 2}]))),
- <<"a b">> = iolist_to_binary(join(re:split("a b","a\\Sb",[]))),
- <<"">> = iolist_to_binary(join(re:split("1","\\d",[trim]))),
+ 2}]))),
+ <<"a b">> = iolist_to_binary(join(re:split("a b","a\\Sb",[]))),
+ <<"">> = iolist_to_binary(join(re:split("1","\\d",[trim]))),
<<":">> = iolist_to_binary(join(re:split("1","\\d",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("1","\\d",[]))),
- <<"">> = iolist_to_binary(join(re:split("-","\\D",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("1","\\d",[]))),
+ <<"">> = iolist_to_binary(join(re:split("-","\\D",[trim]))),
<<":">> = iolist_to_binary(join(re:split("-","\\D",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("-","\\D",[]))),
- <<"">> = iolist_to_binary(join(re:split("*** Failers","\\D",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("-","\\D",[]))),
+ <<"">> = iolist_to_binary(join(re:split("*** Failers","\\D",[trim]))),
<<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\D",[{parts,
- 2}]))),
- <<":::::::::::">> = iolist_to_binary(join(re:split("*** Failers","\\D",[]))),
- <<"">> = iolist_to_binary(join(re:split("-","\\D",[trim]))),
+ 2}]))),
+ <<":::::::::::">> = iolist_to_binary(join(re:split("*** Failers","\\D",[]))),
+ <<"">> = iolist_to_binary(join(re:split("-","\\D",[trim]))),
<<":">> = iolist_to_binary(join(re:split("-","\\D",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("-","\\D",[]))),
- <<"1">> = iolist_to_binary(join(re:split("1","\\D",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("-","\\D",[]))),
+ <<"1">> = iolist_to_binary(join(re:split("1","\\D",[trim]))),
<<"1">> = iolist_to_binary(join(re:split("1","\\D",[{parts,
- 2}]))),
- <<"1">> = iolist_to_binary(join(re:split("1","\\D",[]))),
+ 2}]))),
+ <<"1">> = iolist_to_binary(join(re:split("1","\\D",[]))),
ok.
run17() ->
- <<"">> = iolist_to_binary(join(re:split("a","[\\w]",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("a","[\\w]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","[\\w]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","[\\w]",[]))),
- <<"">> = iolist_to_binary(join(re:split("-","[\\W]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","[\\w]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("-","[\\W]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("-","[\\W]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("-","[\\W]",[]))),
- <<"::::Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\W]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("-","[\\W]",[]))),
+ <<"::::Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\W]",[trim]))),
<<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\W]",[{parts,
- 2}]))),
- <<"::::Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\W]",[]))),
- <<"">> = iolist_to_binary(join(re:split("-","[\\W]",[trim]))),
+ 2}]))),
+ <<"::::Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\W]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("-","[\\W]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("-","[\\W]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("-","[\\W]",[]))),
- <<"a">> = iolist_to_binary(join(re:split("a","[\\W]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("-","[\\W]",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","[\\W]",[trim]))),
<<"a">> = iolist_to_binary(join(re:split("a","[\\W]",[{parts,
- 2}]))),
- <<"a">> = iolist_to_binary(join(re:split("a","[\\W]",[]))),
- <<"">> = iolist_to_binary(join(re:split("a b","a[\\s]b",[trim]))),
+ 2}]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","[\\W]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a b","a[\\s]b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a b","a[\\s]b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a b","a[\\s]b",[]))),
- <<"">> = iolist_to_binary(join(re:split("a-b","a[\\S]b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a b","a[\\s]b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a-b","a[\\S]b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a-b","a[\\S]b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a-b","a[\\S]b",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[\\S]b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a-b","a[\\S]b",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[\\S]b",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[\\S]b",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[\\S]b",[]))),
- <<"">> = iolist_to_binary(join(re:split("a-b","a[\\S]b",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[\\S]b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a-b","a[\\S]b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a-b","a[\\S]b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a-b","a[\\S]b",[]))),
- <<"a b">> = iolist_to_binary(join(re:split("a b","a[\\S]b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a-b","a[\\S]b",[]))),
+ <<"a b">> = iolist_to_binary(join(re:split("a b","a[\\S]b",[trim]))),
<<"a b">> = iolist_to_binary(join(re:split("a b","a[\\S]b",[{parts,
- 2}]))),
- <<"a b">> = iolist_to_binary(join(re:split("a b","a[\\S]b",[]))),
- <<"">> = iolist_to_binary(join(re:split("1","[\\d]",[trim]))),
+ 2}]))),
+ <<"a b">> = iolist_to_binary(join(re:split("a b","a[\\S]b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("1","[\\d]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("1","[\\d]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("1","[\\d]",[]))),
- <<"">> = iolist_to_binary(join(re:split("-","[\\D]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("1","[\\d]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("-","[\\D]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("-","[\\D]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("-","[\\D]",[]))),
- <<"">> = iolist_to_binary(join(re:split("*** Failers","[\\D]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("-","[\\D]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("*** Failers","[\\D]",[trim]))),
<<":** Failers">> = iolist_to_binary(join(re:split("*** Failers","[\\D]",[{parts,
- 2}]))),
- <<":::::::::::">> = iolist_to_binary(join(re:split("*** Failers","[\\D]",[]))),
- <<"">> = iolist_to_binary(join(re:split("-","[\\D]",[trim]))),
+ 2}]))),
+ <<":::::::::::">> = iolist_to_binary(join(re:split("*** Failers","[\\D]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("-","[\\D]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("-","[\\D]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("-","[\\D]",[]))),
- <<"1">> = iolist_to_binary(join(re:split("1","[\\D]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("-","[\\D]",[]))),
+ <<"1">> = iolist_to_binary(join(re:split("1","[\\D]",[trim]))),
<<"1">> = iolist_to_binary(join(re:split("1","[\\D]",[{parts,
- 2}]))),
- <<"1">> = iolist_to_binary(join(re:split("1","[\\D]",[]))),
- <<":c">> = iolist_to_binary(join(re:split("abc","ab|cd",[trim]))),
+ 2}]))),
+ <<"1">> = iolist_to_binary(join(re:split("1","[\\D]",[]))),
+ <<":c">> = iolist_to_binary(join(re:split("abc","ab|cd",[trim]))),
<<":c">> = iolist_to_binary(join(re:split("abc","ab|cd",[{parts,
- 2}]))),
- <<":c">> = iolist_to_binary(join(re:split("abc","ab|cd",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcd","ab|cd",[trim]))),
+ 2}]))),
+ <<":c">> = iolist_to_binary(join(re:split("abc","ab|cd",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcd","ab|cd",[trim]))),
<<":cd">> = iolist_to_binary(join(re:split("abcd","ab|cd",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("abcd","ab|cd",[]))),
- <<"d">> = iolist_to_binary(join(re:split("def","()ef",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("abcd","ab|cd",[]))),
+ <<"d">> = iolist_to_binary(join(re:split("def","()ef",[trim]))),
<<"d::">> = iolist_to_binary(join(re:split("def","()ef",[{parts,
- 2}]))),
- <<"d::">> = iolist_to_binary(join(re:split("def","()ef",[]))),
- <<"">> = iolist_to_binary(join(re:split("a(b","a\\(b",[trim]))),
+ 2}]))),
+ <<"d::">> = iolist_to_binary(join(re:split("def","()ef",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a(b","a\\(b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a(b","a\\(b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a(b","a\\(b",[]))),
- <<"">> = iolist_to_binary(join(re:split("ab","a\\(*b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a(b","a\\(b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ab","a\\(*b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ab","a\\(*b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab","a\\(*b",[]))),
- <<"">> = iolist_to_binary(join(re:split("a((b","a\\(*b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab","a\\(*b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a((b","a\\(*b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a((b","a\\(*b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a((b","a\\(*b",[]))),
- <<"a">> = iolist_to_binary(join(re:split("a","a\\\\b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a((b","a\\(*b",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","a\\\\b",[trim]))),
<<"a">> = iolist_to_binary(join(re:split("a","a\\\\b",[{parts,
- 2}]))),
- <<"a">> = iolist_to_binary(join(re:split("a","a\\\\b",[]))),
- <<":a:a:bc">> = iolist_to_binary(join(re:split("abc","((a))",[trim]))),
+ 2}]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","a\\\\b",[]))),
+ <<":a:a:bc">> = iolist_to_binary(join(re:split("abc","((a))",[trim]))),
<<":a:a:bc">> = iolist_to_binary(join(re:split("abc","((a))",[{parts,
- 2}]))),
- <<":a:a:bc">> = iolist_to_binary(join(re:split("abc","((a))",[]))),
- <<":a:c">> = iolist_to_binary(join(re:split("abc","(a)b(c)",[trim]))),
+ 2}]))),
+ <<":a:a:bc">> = iolist_to_binary(join(re:split("abc","((a))",[]))),
+ <<":a:c">> = iolist_to_binary(join(re:split("abc","(a)b(c)",[trim]))),
<<":a:c:">> = iolist_to_binary(join(re:split("abc","(a)b(c)",[{parts,
- 2}]))),
- <<":a:c:">> = iolist_to_binary(join(re:split("abc","(a)b(c)",[]))),
- <<"aabb">> = iolist_to_binary(join(re:split("aabbabc","a+b+c",[trim]))),
+ 2}]))),
+ <<":a:c:">> = iolist_to_binary(join(re:split("abc","(a)b(c)",[]))),
+ <<"aabb">> = iolist_to_binary(join(re:split("aabbabc","a+b+c",[trim]))),
<<"aabb:">> = iolist_to_binary(join(re:split("aabbabc","a+b+c",[{parts,
- 2}]))),
- <<"aabb:">> = iolist_to_binary(join(re:split("aabbabc","a+b+c",[]))),
- <<"aabb">> = iolist_to_binary(join(re:split("aabbabc","a{1,}b{1,}c",[trim]))),
+ 2}]))),
+ <<"aabb:">> = iolist_to_binary(join(re:split("aabbabc","a+b+c",[]))),
+ <<"aabb">> = iolist_to_binary(join(re:split("aabbabc","a{1,}b{1,}c",[trim]))),
<<"aabb:">> = iolist_to_binary(join(re:split("aabbabc","a{1,}b{1,}c",[{parts,
- 2}]))),
- <<"aabb:">> = iolist_to_binary(join(re:split("aabbabc","a{1,}b{1,}c",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcabc","a.+?c",[trim]))),
+ 2}]))),
+ <<"aabb:">> = iolist_to_binary(join(re:split("aabbabc","a{1,}b{1,}c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcabc","a.+?c",[trim]))),
<<":abc">> = iolist_to_binary(join(re:split("abcabc","a.+?c",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("abcabc","a.+?c",[]))),
- <<":b">> = iolist_to_binary(join(re:split("ab","(a+|b)*",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("abcabc","a.+?c",[]))),
+ <<":b">> = iolist_to_binary(join(re:split("ab","(a+|b)*",[trim]))),
<<":b:">> = iolist_to_binary(join(re:split("ab","(a+|b)*",[{parts,
- 2}]))),
- <<":b:">> = iolist_to_binary(join(re:split("ab","(a+|b)*",[]))),
- <<":b">> = iolist_to_binary(join(re:split("ab","(a+|b){0,}",[trim]))),
+ 2}]))),
+ <<":b:">> = iolist_to_binary(join(re:split("ab","(a+|b)*",[]))),
+ <<":b">> = iolist_to_binary(join(re:split("ab","(a+|b){0,}",[trim]))),
<<":b:">> = iolist_to_binary(join(re:split("ab","(a+|b){0,}",[{parts,
- 2}]))),
- <<":b:">> = iolist_to_binary(join(re:split("ab","(a+|b){0,}",[]))),
- <<":b">> = iolist_to_binary(join(re:split("ab","(a+|b)+",[trim]))),
+ 2}]))),
+ <<":b:">> = iolist_to_binary(join(re:split("ab","(a+|b){0,}",[]))),
+ <<":b">> = iolist_to_binary(join(re:split("ab","(a+|b)+",[trim]))),
<<":b:">> = iolist_to_binary(join(re:split("ab","(a+|b)+",[{parts,
- 2}]))),
- <<":b:">> = iolist_to_binary(join(re:split("ab","(a+|b)+",[]))),
+ 2}]))),
+ <<":b:">> = iolist_to_binary(join(re:split("ab","(a+|b)+",[]))),
ok.
run18() ->
- <<":b">> = iolist_to_binary(join(re:split("ab","(a+|b){1,}",[trim]))),
+ <<":b">> = iolist_to_binary(join(re:split("ab","(a+|b){1,}",[trim]))),
<<":b:">> = iolist_to_binary(join(re:split("ab","(a+|b){1,}",[{parts,
- 2}]))),
- <<":b:">> = iolist_to_binary(join(re:split("ab","(a+|b){1,}",[]))),
- <<":a::b">> = iolist_to_binary(join(re:split("ab","(a+|b)?",[trim]))),
+ 2}]))),
+ <<":b:">> = iolist_to_binary(join(re:split("ab","(a+|b){1,}",[]))),
+ <<":a::b">> = iolist_to_binary(join(re:split("ab","(a+|b)?",[trim]))),
<<":a:b">> = iolist_to_binary(join(re:split("ab","(a+|b)?",[{parts,
- 2}]))),
- <<":a::b:">> = iolist_to_binary(join(re:split("ab","(a+|b)?",[]))),
- <<":a::b">> = iolist_to_binary(join(re:split("ab","(a+|b){0,1}",[trim]))),
+ 2}]))),
+ <<":a::b:">> = iolist_to_binary(join(re:split("ab","(a+|b)?",[]))),
+ <<":a::b">> = iolist_to_binary(join(re:split("ab","(a+|b){0,1}",[trim]))),
<<":a:b">> = iolist_to_binary(join(re:split("ab","(a+|b){0,1}",[{parts,
- 2}]))),
- <<":a::b:">> = iolist_to_binary(join(re:split("ab","(a+|b){0,1}",[]))),
- <<"">> = iolist_to_binary(join(re:split("cde","[^ab]*",[trim]))),
+ 2}]))),
+ <<":a::b:">> = iolist_to_binary(join(re:split("ab","(a+|b){0,1}",[]))),
+ <<"">> = iolist_to_binary(join(re:split("cde","[^ab]*",[trim]))),
<<":">> = iolist_to_binary(join(re:split("cde","[^ab]*",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("cde","[^ab]*",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("cde","[^ab]*",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[]))),
- <<"b">> = iolist_to_binary(join(re:split("b","abc",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[]))),
+ <<"b">> = iolist_to_binary(join(re:split("b","abc",[trim]))),
<<"b">> = iolist_to_binary(join(re:split("b","abc",[{parts,
- 2}]))),
- <<"b">> = iolist_to_binary(join(re:split("b","abc",[]))),
- <<":c">> = iolist_to_binary(join(re:split("abbbcd","([abc])*d",[trim]))),
+ 2}]))),
+ <<"b">> = iolist_to_binary(join(re:split("b","abc",[]))),
+ <<":c">> = iolist_to_binary(join(re:split("abbbcd","([abc])*d",[trim]))),
<<":c:">> = iolist_to_binary(join(re:split("abbbcd","([abc])*d",[{parts,
- 2}]))),
- <<":c:">> = iolist_to_binary(join(re:split("abbbcd","([abc])*d",[]))),
- <<":a">> = iolist_to_binary(join(re:split("abcd","([abc])*bcd",[trim]))),
+ 2}]))),
+ <<":c:">> = iolist_to_binary(join(re:split("abbbcd","([abc])*d",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("abcd","([abc])*bcd",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("abcd","([abc])*bcd",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("abcd","([abc])*bcd",[]))),
- <<"">> = iolist_to_binary(join(re:split("e","a|b|c|d|e",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("abcd","([abc])*bcd",[]))),
+ <<"">> = iolist_to_binary(join(re:split("e","a|b|c|d|e",[trim]))),
<<":">> = iolist_to_binary(join(re:split("e","a|b|c|d|e",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("e","a|b|c|d|e",[]))),
- <<":e">> = iolist_to_binary(join(re:split("ef","(a|b|c|d|e)f",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("e","a|b|c|d|e",[]))),
+ <<":e">> = iolist_to_binary(join(re:split("ef","(a|b|c|d|e)f",[trim]))),
<<":e:">> = iolist_to_binary(join(re:split("ef","(a|b|c|d|e)f",[{parts,
- 2}]))),
- <<":e:">> = iolist_to_binary(join(re:split("ef","(a|b|c|d|e)f",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcdefg","abcd*efg",[trim]))),
+ 2}]))),
+ <<":e:">> = iolist_to_binary(join(re:split("ef","(a|b|c|d|e)f",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcdefg","abcd*efg",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcdefg","abcd*efg",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcdefg","abcd*efg",[]))),
- <<"x:y:z">> = iolist_to_binary(join(re:split("xabyabbbz","ab*",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcdefg","abcd*efg",[]))),
+ <<"x:y:z">> = iolist_to_binary(join(re:split("xabyabbbz","ab*",[trim]))),
<<"x:yabbbz">> = iolist_to_binary(join(re:split("xabyabbbz","ab*",[{parts,
- 2}]))),
- <<"x:y:z">> = iolist_to_binary(join(re:split("xabyabbbz","ab*",[]))),
- <<"x:y:z">> = iolist_to_binary(join(re:split("xayabbbz","ab*",[trim]))),
+ 2}]))),
+ <<"x:y:z">> = iolist_to_binary(join(re:split("xabyabbbz","ab*",[]))),
+ <<"x:y:z">> = iolist_to_binary(join(re:split("xayabbbz","ab*",[trim]))),
<<"x:yabbbz">> = iolist_to_binary(join(re:split("xayabbbz","ab*",[{parts,
- 2}]))),
- <<"x:y:z">> = iolist_to_binary(join(re:split("xayabbbz","ab*",[]))),
- <<"ab:cd">> = iolist_to_binary(join(re:split("abcde","(ab|cd)e",[trim]))),
+ 2}]))),
+ <<"x:y:z">> = iolist_to_binary(join(re:split("xayabbbz","ab*",[]))),
+ <<"ab:cd">> = iolist_to_binary(join(re:split("abcde","(ab|cd)e",[trim]))),
<<"ab:cd:">> = iolist_to_binary(join(re:split("abcde","(ab|cd)e",[{parts,
- 2}]))),
- <<"ab:cd:">> = iolist_to_binary(join(re:split("abcde","(ab|cd)e",[]))),
- <<"">> = iolist_to_binary(join(re:split("hij","[abhgefdc]ij",[trim]))),
+ 2}]))),
+ <<"ab:cd:">> = iolist_to_binary(join(re:split("abcde","(ab|cd)e",[]))),
+ <<"">> = iolist_to_binary(join(re:split("hij","[abhgefdc]ij",[trim]))),
<<":">> = iolist_to_binary(join(re:split("hij","[abhgefdc]ij",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("hij","[abhgefdc]ij",[]))),
- <<"abcd">> = iolist_to_binary(join(re:split("abcdef","(abc|)ef",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("hij","[abhgefdc]ij",[]))),
+ <<"abcd">> = iolist_to_binary(join(re:split("abcdef","(abc|)ef",[trim]))),
<<"abcd::">> = iolist_to_binary(join(re:split("abcdef","(abc|)ef",[{parts,
- 2}]))),
- <<"abcd::">> = iolist_to_binary(join(re:split("abcdef","(abc|)ef",[]))),
- <<"a:b">> = iolist_to_binary(join(re:split("abcd","(a|b)c*d",[trim]))),
+ 2}]))),
+ <<"abcd::">> = iolist_to_binary(join(re:split("abcdef","(abc|)ef",[]))),
+ <<"a:b">> = iolist_to_binary(join(re:split("abcd","(a|b)c*d",[trim]))),
<<"a:b:">> = iolist_to_binary(join(re:split("abcd","(a|b)c*d",[{parts,
- 2}]))),
- <<"a:b:">> = iolist_to_binary(join(re:split("abcd","(a|b)c*d",[]))),
- <<":a">> = iolist_to_binary(join(re:split("abc","(ab|ab*)bc",[trim]))),
+ 2}]))),
+ <<"a:b:">> = iolist_to_binary(join(re:split("abcd","(a|b)c*d",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("abc","(ab|ab*)bc",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("abc","(ab|ab*)bc",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("abc","(ab|ab*)bc",[]))),
- <<":bc">> = iolist_to_binary(join(re:split("abc","a([bc]*)c*",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("abc","(ab|ab*)bc",[]))),
+ <<":bc">> = iolist_to_binary(join(re:split("abc","a([bc]*)c*",[trim]))),
<<":bc:">> = iolist_to_binary(join(re:split("abc","a([bc]*)c*",[{parts,
- 2}]))),
- <<":bc:">> = iolist_to_binary(join(re:split("abc","a([bc]*)c*",[]))),
- <<":bc:d">> = iolist_to_binary(join(re:split("abcd","a([bc]*)(c*d)",[trim]))),
+ 2}]))),
+ <<":bc:">> = iolist_to_binary(join(re:split("abc","a([bc]*)c*",[]))),
+ <<":bc:d">> = iolist_to_binary(join(re:split("abcd","a([bc]*)(c*d)",[trim]))),
<<":bc:d:">> = iolist_to_binary(join(re:split("abcd","a([bc]*)(c*d)",[{parts,
- 2}]))),
- <<":bc:d:">> = iolist_to_binary(join(re:split("abcd","a([bc]*)(c*d)",[]))),
+ 2}]))),
+ <<":bc:d:">> = iolist_to_binary(join(re:split("abcd","a([bc]*)(c*d)",[]))),
ok.
run19() ->
- <<":bc:d">> = iolist_to_binary(join(re:split("abcd","a([bc]+)(c*d)",[trim]))),
+ <<":bc:d">> = iolist_to_binary(join(re:split("abcd","a([bc]+)(c*d)",[trim]))),
<<":bc:d:">> = iolist_to_binary(join(re:split("abcd","a([bc]+)(c*d)",[{parts,
- 2}]))),
- <<":bc:d:">> = iolist_to_binary(join(re:split("abcd","a([bc]+)(c*d)",[]))),
- <<":b:cd">> = iolist_to_binary(join(re:split("abcd","a([bc]*)(c+d)",[trim]))),
+ 2}]))),
+ <<":bc:d:">> = iolist_to_binary(join(re:split("abcd","a([bc]+)(c*d)",[]))),
+ <<":b:cd">> = iolist_to_binary(join(re:split("abcd","a([bc]*)(c+d)",[trim]))),
<<":b:cd:">> = iolist_to_binary(join(re:split("abcd","a([bc]*)(c+d)",[{parts,
- 2}]))),
- <<":b:cd:">> = iolist_to_binary(join(re:split("abcd","a([bc]*)(c+d)",[]))),
- <<"">> = iolist_to_binary(join(re:split("adcdcde","a[bcd]*dcdcde",[trim]))),
+ 2}]))),
+ <<":b:cd:">> = iolist_to_binary(join(re:split("abcd","a([bc]*)(c+d)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("adcdcde","a[bcd]*dcdcde",[trim]))),
<<":">> = iolist_to_binary(join(re:split("adcdcde","a[bcd]*dcdcde",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("adcdcde","a[bcd]*dcdcde",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[bcd]+dcdcde",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("adcdcde","a[bcd]*dcdcde",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[bcd]+dcdcde",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[bcd]+dcdcde",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[bcd]+dcdcde",[]))),
- <<"abcde">> = iolist_to_binary(join(re:split("abcde","a[bcd]+dcdcde",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[bcd]+dcdcde",[]))),
+ <<"abcde">> = iolist_to_binary(join(re:split("abcde","a[bcd]+dcdcde",[trim]))),
<<"abcde">> = iolist_to_binary(join(re:split("abcde","a[bcd]+dcdcde",[{parts,
- 2}]))),
- <<"abcde">> = iolist_to_binary(join(re:split("abcde","a[bcd]+dcdcde",[]))),
- <<"adcdcde">> = iolist_to_binary(join(re:split("adcdcde","a[bcd]+dcdcde",[trim]))),
+ 2}]))),
+ <<"abcde">> = iolist_to_binary(join(re:split("abcde","a[bcd]+dcdcde",[]))),
+ <<"adcdcde">> = iolist_to_binary(join(re:split("adcdcde","a[bcd]+dcdcde",[trim]))),
<<"adcdcde">> = iolist_to_binary(join(re:split("adcdcde","a[bcd]+dcdcde",[{parts,
- 2}]))),
- <<"adcdcde">> = iolist_to_binary(join(re:split("adcdcde","a[bcd]+dcdcde",[]))),
- <<":ab">> = iolist_to_binary(join(re:split("abc","(ab|a)b*c",[trim]))),
+ 2}]))),
+ <<"adcdcde">> = iolist_to_binary(join(re:split("adcdcde","a[bcd]+dcdcde",[]))),
+ <<":ab">> = iolist_to_binary(join(re:split("abc","(ab|a)b*c",[trim]))),
<<":ab:">> = iolist_to_binary(join(re:split("abc","(ab|a)b*c",[{parts,
- 2}]))),
- <<":ab:">> = iolist_to_binary(join(re:split("abc","(ab|a)b*c",[]))),
- <<":abc:a:b:d">> = iolist_to_binary(join(re:split("abcd","((a)(b)c)(d)",[trim]))),
+ 2}]))),
+ <<":ab:">> = iolist_to_binary(join(re:split("abc","(ab|a)b*c",[]))),
+ <<":abc:a:b:d">> = iolist_to_binary(join(re:split("abcd","((a)(b)c)(d)",[trim]))),
<<":abc:a:b:d:">> = iolist_to_binary(join(re:split("abcd","((a)(b)c)(d)",[{parts,
- 2}]))),
- <<":abc:a:b:d:">> = iolist_to_binary(join(re:split("abcd","((a)(b)c)(d)",[]))),
- <<"">> = iolist_to_binary(join(re:split("alpha","[a-zA-Z_][a-zA-Z0-9_]*",[trim]))),
+ 2}]))),
+ <<":abc:a:b:d:">> = iolist_to_binary(join(re:split("abcd","((a)(b)c)(d)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("alpha","[a-zA-Z_][a-zA-Z0-9_]*",[trim]))),
<<":">> = iolist_to_binary(join(re:split("alpha","[a-zA-Z_][a-zA-Z0-9_]*",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("alpha","[a-zA-Z_][a-zA-Z0-9_]*",[]))),
- <<"a">> = iolist_to_binary(join(re:split("abh","^a(bc+|b[eh])g|.h$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("alpha","[a-zA-Z_][a-zA-Z0-9_]*",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("abh","^a(bc+|b[eh])g|.h$",[trim]))),
<<"a::">> = iolist_to_binary(join(re:split("abh","^a(bc+|b[eh])g|.h$",[{parts,
- 2}]))),
- <<"a::">> = iolist_to_binary(join(re:split("abh","^a(bc+|b[eh])g|.h$",[]))),
- <<":effgz">> = iolist_to_binary(join(re:split("effgz","(bc+d$|ef*g.|h?i(j|k))",[trim]))),
+ 2}]))),
+ <<"a::">> = iolist_to_binary(join(re:split("abh","^a(bc+|b[eh])g|.h$",[]))),
+ <<":effgz">> = iolist_to_binary(join(re:split("effgz","(bc+d$|ef*g.|h?i(j|k))",[trim]))),
<<":effgz::">> = iolist_to_binary(join(re:split("effgz","(bc+d$|ef*g.|h?i(j|k))",[{parts,
- 2}]))),
- <<":effgz::">> = iolist_to_binary(join(re:split("effgz","(bc+d$|ef*g.|h?i(j|k))",[]))),
- <<":ij:j">> = iolist_to_binary(join(re:split("ij","(bc+d$|ef*g.|h?i(j|k))",[trim]))),
+ 2}]))),
+ <<":effgz::">> = iolist_to_binary(join(re:split("effgz","(bc+d$|ef*g.|h?i(j|k))",[]))),
+ <<":ij:j">> = iolist_to_binary(join(re:split("ij","(bc+d$|ef*g.|h?i(j|k))",[trim]))),
<<":ij:j:">> = iolist_to_binary(join(re:split("ij","(bc+d$|ef*g.|h?i(j|k))",[{parts,
- 2}]))),
- <<":ij:j:">> = iolist_to_binary(join(re:split("ij","(bc+d$|ef*g.|h?i(j|k))",[]))),
- <<"r:effgz">> = iolist_to_binary(join(re:split("reffgz","(bc+d$|ef*g.|h?i(j|k))",[trim]))),
+ 2}]))),
+ <<":ij:j:">> = iolist_to_binary(join(re:split("ij","(bc+d$|ef*g.|h?i(j|k))",[]))),
+ <<"r:effgz">> = iolist_to_binary(join(re:split("reffgz","(bc+d$|ef*g.|h?i(j|k))",[trim]))),
<<"r:effgz::">> = iolist_to_binary(join(re:split("reffgz","(bc+d$|ef*g.|h?i(j|k))",[{parts,
- 2}]))),
- <<"r:effgz::">> = iolist_to_binary(join(re:split("reffgz","(bc+d$|ef*g.|h?i(j|k))",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(bc+d$|ef*g.|h?i(j|k))",[trim]))),
+ 2}]))),
+ <<"r:effgz::">> = iolist_to_binary(join(re:split("reffgz","(bc+d$|ef*g.|h?i(j|k))",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(bc+d$|ef*g.|h?i(j|k))",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(bc+d$|ef*g.|h?i(j|k))",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(bc+d$|ef*g.|h?i(j|k))",[]))),
- <<"effg">> = iolist_to_binary(join(re:split("effg","(bc+d$|ef*g.|h?i(j|k))",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(bc+d$|ef*g.|h?i(j|k))",[]))),
+ <<"effg">> = iolist_to_binary(join(re:split("effg","(bc+d$|ef*g.|h?i(j|k))",[trim]))),
<<"effg">> = iolist_to_binary(join(re:split("effg","(bc+d$|ef*g.|h?i(j|k))",[{parts,
- 2}]))),
- <<"effg">> = iolist_to_binary(join(re:split("effg","(bc+d$|ef*g.|h?i(j|k))",[]))),
- <<"bcdd">> = iolist_to_binary(join(re:split("bcdd","(bc+d$|ef*g.|h?i(j|k))",[trim]))),
+ 2}]))),
+ <<"effg">> = iolist_to_binary(join(re:split("effg","(bc+d$|ef*g.|h?i(j|k))",[]))),
+ <<"bcdd">> = iolist_to_binary(join(re:split("bcdd","(bc+d$|ef*g.|h?i(j|k))",[trim]))),
<<"bcdd">> = iolist_to_binary(join(re:split("bcdd","(bc+d$|ef*g.|h?i(j|k))",[{parts,
- 2}]))),
- <<"bcdd">> = iolist_to_binary(join(re:split("bcdd","(bc+d$|ef*g.|h?i(j|k))",[]))),
- <<":a:a:a:a:a:a:a:a:a:a">> = iolist_to_binary(join(re:split("a","((((((((((a))))))))))",[trim]))),
+ 2}]))),
+ <<"bcdd">> = iolist_to_binary(join(re:split("bcdd","(bc+d$|ef*g.|h?i(j|k))",[]))),
+ <<":a:a:a:a:a:a:a:a:a:a">> = iolist_to_binary(join(re:split("a","((((((((((a))))))))))",[trim]))),
<<":a:a:a:a:a:a:a:a:a:a:">> = iolist_to_binary(join(re:split("a","((((((((((a))))))))))",[{parts,
- 2}]))),
- <<":a:a:a:a:a:a:a:a:a:a:">> = iolist_to_binary(join(re:split("a","((((((((((a))))))))))",[]))),
- <<":a:a:a:a:a:a:a:a:a:a">> = iolist_to_binary(join(re:split("aa","((((((((((a))))))))))\\10",[trim]))),
+ 2}]))),
+ <<":a:a:a:a:a:a:a:a:a:a:">> = iolist_to_binary(join(re:split("a","((((((((((a))))))))))",[]))),
+ <<":a:a:a:a:a:a:a:a:a:a">> = iolist_to_binary(join(re:split("aa","((((((((((a))))))))))\\10",[trim]))),
<<":a:a:a:a:a:a:a:a:a:a:">> = iolist_to_binary(join(re:split("aa","((((((((((a))))))))))\\10",[{parts,
- 2}]))),
- <<":a:a:a:a:a:a:a:a:a:a:">> = iolist_to_binary(join(re:split("aa","((((((((((a))))))))))\\10",[]))),
- <<":a:a:a:a:a:a:a:a:a">> = iolist_to_binary(join(re:split("a","(((((((((a)))))))))",[trim]))),
+ 2}]))),
+ <<":a:a:a:a:a:a:a:a:a:a:">> = iolist_to_binary(join(re:split("aa","((((((((((a))))))))))\\10",[]))),
+ <<":a:a:a:a:a:a:a:a:a">> = iolist_to_binary(join(re:split("a","(((((((((a)))))))))",[trim]))),
<<":a:a:a:a:a:a:a:a:a:">> = iolist_to_binary(join(re:split("a","(((((((((a)))))))))",[{parts,
- 2}]))),
- <<":a:a:a:a:a:a:a:a:a:">> = iolist_to_binary(join(re:split("a","(((((((((a)))))))))",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","multiple words of text",[trim]))),
+ 2}]))),
+ <<":a:a:a:a:a:a:a:a:a:">> = iolist_to_binary(join(re:split("a","(((((((((a)))))))))",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","multiple words of text",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","multiple words of text",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","multiple words of text",[]))),
- <<"aa">> = iolist_to_binary(join(re:split("aa","multiple words of text",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","multiple words of text",[]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aa","multiple words of text",[trim]))),
<<"aa">> = iolist_to_binary(join(re:split("aa","multiple words of text",[{parts,
- 2}]))),
- <<"aa">> = iolist_to_binary(join(re:split("aa","multiple words of text",[]))),
- <<"uh-uh">> = iolist_to_binary(join(re:split("uh-uh","multiple words of text",[trim]))),
+ 2}]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aa","multiple words of text",[]))),
+ <<"uh-uh">> = iolist_to_binary(join(re:split("uh-uh","multiple words of text",[trim]))),
<<"uh-uh">> = iolist_to_binary(join(re:split("uh-uh","multiple words of text",[{parts,
- 2}]))),
- <<"uh-uh">> = iolist_to_binary(join(re:split("uh-uh","multiple words of text",[]))),
- <<":, yeah">> = iolist_to_binary(join(re:split("multiple words, yeah","multiple words",[trim]))),
+ 2}]))),
+ <<"uh-uh">> = iolist_to_binary(join(re:split("uh-uh","multiple words of text",[]))),
+ <<":, yeah">> = iolist_to_binary(join(re:split("multiple words, yeah","multiple words",[trim]))),
<<":, yeah">> = iolist_to_binary(join(re:split("multiple words, yeah","multiple words",[{parts,
- 2}]))),
- <<":, yeah">> = iolist_to_binary(join(re:split("multiple words, yeah","multiple words",[]))),
- <<":ab:de">> = iolist_to_binary(join(re:split("abcde","(.*)c(.*)",[trim]))),
+ 2}]))),
+ <<":, yeah">> = iolist_to_binary(join(re:split("multiple words, yeah","multiple words",[]))),
+ <<":ab:de">> = iolist_to_binary(join(re:split("abcde","(.*)c(.*)",[trim]))),
<<":ab:de:">> = iolist_to_binary(join(re:split("abcde","(.*)c(.*)",[{parts,
- 2}]))),
- <<":ab:de:">> = iolist_to_binary(join(re:split("abcde","(.*)c(.*)",[]))),
- <<":a:b">> = iolist_to_binary(join(re:split("(a, b)","\\((.*), (.*)\\)",[trim]))),
+ 2}]))),
+ <<":ab:de:">> = iolist_to_binary(join(re:split("abcde","(.*)c(.*)",[]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("(a, b)","\\((.*), (.*)\\)",[trim]))),
<<":a:b:">> = iolist_to_binary(join(re:split("(a, b)","\\((.*), (.*)\\)",[{parts,
- 2}]))),
- <<":a:b:">> = iolist_to_binary(join(re:split("(a, b)","\\((.*), (.*)\\)",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcd","abcd",[trim]))),
+ 2}]))),
+ <<":a:b:">> = iolist_to_binary(join(re:split("(a, b)","\\((.*), (.*)\\)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcd","abcd",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcd","abcd",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcd","abcd",[]))),
- <<":bc">> = iolist_to_binary(join(re:split("abcd","a(bc)d",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcd","abcd",[]))),
+ <<":bc">> = iolist_to_binary(join(re:split("abcd","a(bc)d",[trim]))),
<<":bc:">> = iolist_to_binary(join(re:split("abcd","a(bc)d",[{parts,
- 2}]))),
- <<":bc:">> = iolist_to_binary(join(re:split("abcd","a(bc)d",[]))),
- <<"">> = iolist_to_binary(join(re:split("ac","a[-]?c",[trim]))),
+ 2}]))),
+ <<":bc:">> = iolist_to_binary(join(re:split("abcd","a(bc)d",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ac","a[-]?c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ac","a[-]?c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ac","a[-]?c",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ac","a[-]?c",[]))),
ok.
run20() ->
- <<":abc">> = iolist_to_binary(join(re:split("abcabc","(abc)\\1",[trim]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abcabc","(abc)\\1",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abcabc","(abc)\\1",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abcabc","(abc)\\1",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abcabc","([a-c]*)\\1",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abcabc","(abc)\\1",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abcabc","([a-c]*)\\1",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abcabc","([a-c]*)\\1",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abcabc","([a-c]*)\\1",[]))),
- <<":a">> = iolist_to_binary(join(re:split("a","(a)|\\1",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abcabc","([a-c]*)\\1",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("a","(a)|\\1",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("a","(a)|\\1",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("a","(a)|\\1",[]))),
- <<"*** F:a:ilers">> = iolist_to_binary(join(re:split("*** Failers","(a)|\\1",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("a","(a)|\\1",[]))),
+ <<"*** F:a:ilers">> = iolist_to_binary(join(re:split("*** Failers","(a)|\\1",[trim]))),
<<"*** F:a:ilers">> = iolist_to_binary(join(re:split("*** Failers","(a)|\\1",[{parts,
- 2}]))),
- <<"*** F:a:ilers">> = iolist_to_binary(join(re:split("*** Failers","(a)|\\1",[]))),
- <<":a:b">> = iolist_to_binary(join(re:split("ab","(a)|\\1",[trim]))),
+ 2}]))),
+ <<"*** F:a:ilers">> = iolist_to_binary(join(re:split("*** Failers","(a)|\\1",[]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("ab","(a)|\\1",[trim]))),
<<":a:b">> = iolist_to_binary(join(re:split("ab","(a)|\\1",[{parts,
- 2}]))),
- <<":a:b">> = iolist_to_binary(join(re:split("ab","(a)|\\1",[]))),
- <<"x">> = iolist_to_binary(join(re:split("x","(a)|\\1",[trim]))),
+ 2}]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("ab","(a)|\\1",[]))),
+ <<"x">> = iolist_to_binary(join(re:split("x","(a)|\\1",[trim]))),
<<"x">> = iolist_to_binary(join(re:split("x","(a)|\\1",[{parts,
- 2}]))),
- <<"x">> = iolist_to_binary(join(re:split("x","(a)|\\1",[]))),
- <<":bb:b:b:cbc:c">> = iolist_to_binary(join(re:split("ababbbcbc","(([a-c])b*?\\2)*",[trim]))),
+ 2}]))),
+ <<"x">> = iolist_to_binary(join(re:split("x","(a)|\\1",[]))),
+ <<":bb:b:b:cbc:c">> = iolist_to_binary(join(re:split("ababbbcbc","(([a-c])b*?\\2)*",[trim]))),
<<":bb:b:bcbc">> = iolist_to_binary(join(re:split("ababbbcbc","(([a-c])b*?\\2)*",[{parts,
- 2}]))),
- <<":bb:b:b:cbc:c:">> = iolist_to_binary(join(re:split("ababbbcbc","(([a-c])b*?\\2)*",[]))),
- <<":cbc:c">> = iolist_to_binary(join(re:split("ababbbcbc","(([a-c])b*?\\2){3}",[trim]))),
+ 2}]))),
+ <<":bb:b:b:cbc:c:">> = iolist_to_binary(join(re:split("ababbbcbc","(([a-c])b*?\\2)*",[]))),
+ <<":cbc:c">> = iolist_to_binary(join(re:split("ababbbcbc","(([a-c])b*?\\2){3}",[trim]))),
<<":cbc:c:">> = iolist_to_binary(join(re:split("ababbbcbc","(([a-c])b*?\\2){3}",[{parts,
- 2}]))),
- <<":cbc:c:">> = iolist_to_binary(join(re:split("ababbbcbc","(([a-c])b*?\\2){3}",[]))),
- <<"aaaxabaxbaax:bbax:b:a">> = iolist_to_binary(join(re:split("aaaxabaxbaaxbbax","((\\3|b)\\2(a)x)+",[trim]))),
+ 2}]))),
+ <<":cbc:c:">> = iolist_to_binary(join(re:split("ababbbcbc","(([a-c])b*?\\2){3}",[]))),
+ <<"aaaxabaxbaax:bbax:b:a">> = iolist_to_binary(join(re:split("aaaxabaxbaaxbbax","((\\3|b)\\2(a)x)+",[trim]))),
<<"aaaxabaxbaax:bbax:b:a:">> = iolist_to_binary(join(re:split("aaaxabaxbaaxbbax","((\\3|b)\\2(a)x)+",[{parts,
- 2}]))),
- <<"aaaxabaxbaax:bbax:b:a:">> = iolist_to_binary(join(re:split("aaaxabaxbaaxbbax","((\\3|b)\\2(a)x)+",[]))),
- <<"bbaababbabaaaaa:bba:b:a">> = iolist_to_binary(join(re:split("bbaababbabaaaaabbaaaabba","((\\3|b)\\2(a)){2,}",[trim]))),
+ 2}]))),
+ <<"aaaxabaxbaax:bbax:b:a:">> = iolist_to_binary(join(re:split("aaaxabaxbaaxbbax","((\\3|b)\\2(a)x)+",[]))),
+ <<"bbaababbabaaaaa:bba:b:a">> = iolist_to_binary(join(re:split("bbaababbabaaaaabbaaaabba","((\\3|b)\\2(a)){2,}",[trim]))),
<<"bbaababbabaaaaa:bba:b:a:">> = iolist_to_binary(join(re:split("bbaababbabaaaaabbaaaabba","((\\3|b)\\2(a)){2,}",[{parts,
- 2}]))),
- <<"bbaababbabaaaaa:bba:b:a:">> = iolist_to_binary(join(re:split("bbaababbabaaaaabbaaaabba","((\\3|b)\\2(a)){2,}",[]))),
+ 2}]))),
+ <<"bbaababbabaaaaa:bba:b:a:">> = iolist_to_binary(join(re:split("bbaababbabaaaaabbaaaabba","((\\3|b)\\2(a)){2,}",[]))),
<<"">> = iolist_to_binary(join(re:split("ABC","abc",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABC","abc",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABC","abc",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABC","abc",[caseless]))),
<<"X:Y">> = iolist_to_binary(join(re:split("XABCY","abc",[caseless,
- trim]))),
+ trim]))),
<<"X:Y">> = iolist_to_binary(join(re:split("XABCY","abc",[caseless,
{parts,
- 2}]))),
- <<"X:Y">> = iolist_to_binary(join(re:split("XABCY","abc",[caseless]))),
+ 2}]))),
+ <<"X:Y">> = iolist_to_binary(join(re:split("XABCY","abc",[caseless]))),
<<"AB">> = iolist_to_binary(join(re:split("ABABC","abc",[caseless,
- trim]))),
+ trim]))),
<<"AB:">> = iolist_to_binary(join(re:split("ABABC","abc",[caseless,
{parts,
- 2}]))),
- <<"AB:">> = iolist_to_binary(join(re:split("ABABC","abc",[caseless]))),
+ 2}]))),
+ <<"AB:">> = iolist_to_binary(join(re:split("ABABC","abc",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","abc",[caseless]))),
<<"aaxabxbaxbbx">> = iolist_to_binary(join(re:split("aaxabxbaxbbx","abc",[caseless,
- trim]))),
+ trim]))),
<<"aaxabxbaxbbx">> = iolist_to_binary(join(re:split("aaxabxbaxbbx","abc",[caseless,
{parts,
- 2}]))),
- <<"aaxabxbaxbbx">> = iolist_to_binary(join(re:split("aaxabxbaxbbx","abc",[caseless]))),
+ 2}]))),
+ <<"aaxabxbaxbbx">> = iolist_to_binary(join(re:split("aaxabxbaxbbx","abc",[caseless]))),
<<"XBC">> = iolist_to_binary(join(re:split("XBC","abc",[caseless,
- trim]))),
+ trim]))),
<<"XBC">> = iolist_to_binary(join(re:split("XBC","abc",[caseless,
{parts,
- 2}]))),
- <<"XBC">> = iolist_to_binary(join(re:split("XBC","abc",[caseless]))),
+ 2}]))),
+ <<"XBC">> = iolist_to_binary(join(re:split("XBC","abc",[caseless]))),
<<"AXC">> = iolist_to_binary(join(re:split("AXC","abc",[caseless,
- trim]))),
+ trim]))),
<<"AXC">> = iolist_to_binary(join(re:split("AXC","abc",[caseless,
{parts,
- 2}]))),
- <<"AXC">> = iolist_to_binary(join(re:split("AXC","abc",[caseless]))),
+ 2}]))),
+ <<"AXC">> = iolist_to_binary(join(re:split("AXC","abc",[caseless]))),
<<"ABX">> = iolist_to_binary(join(re:split("ABX","abc",[caseless,
- trim]))),
+ trim]))),
<<"ABX">> = iolist_to_binary(join(re:split("ABX","abc",[caseless,
{parts,
- 2}]))),
- <<"ABX">> = iolist_to_binary(join(re:split("ABX","abc",[caseless]))),
+ 2}]))),
+ <<"ABX">> = iolist_to_binary(join(re:split("ABX","abc",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABC","ab*c",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABC","ab*c",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABC","ab*c",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABC","ab*c",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABC","ab*bc",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABC","ab*bc",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABC","ab*bc",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABC","ab*bc",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABBC","ab*bc",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABBC","ab*bc",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABBC","ab*bc",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABBC","ab*bc",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABBBBC","ab*?bc",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABBBBC","ab*?bc",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABBBBC","ab*?bc",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABBBBC","ab*?bc",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABBBBC","ab{0,}?bc",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABBBBC","ab{0,}?bc",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABBBBC","ab{0,}?bc",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABBBBC","ab{0,}?bc",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABBC","ab+?bc",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABBC","ab+?bc",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABBC","ab+?bc",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABBC","ab+?bc",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab+bc",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab+bc",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab+bc",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab+bc",[caseless]))),
<<"ABC">> = iolist_to_binary(join(re:split("ABC","ab+bc",[caseless,
- trim]))),
+ trim]))),
<<"ABC">> = iolist_to_binary(join(re:split("ABC","ab+bc",[caseless,
{parts,
- 2}]))),
- <<"ABC">> = iolist_to_binary(join(re:split("ABC","ab+bc",[caseless]))),
+ 2}]))),
+ <<"ABC">> = iolist_to_binary(join(re:split("ABC","ab+bc",[caseless]))),
<<"ABQ">> = iolist_to_binary(join(re:split("ABQ","ab+bc",[caseless,
- trim]))),
+ trim]))),
<<"ABQ">> = iolist_to_binary(join(re:split("ABQ","ab+bc",[caseless,
{parts,
- 2}]))),
- <<"ABQ">> = iolist_to_binary(join(re:split("ABQ","ab+bc",[caseless]))),
+ 2}]))),
+ <<"ABQ">> = iolist_to_binary(join(re:split("ABQ","ab+bc",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABBBBC","ab+bc",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABBBBC","ab+bc",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABBBBC","ab+bc",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABBBBC","ab+bc",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABBBBC","ab{1,}?bc",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABBBBC","ab{1,}?bc",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABBBBC","ab{1,}?bc",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABBBBC","ab{1,}?bc",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABBBBC","ab{1,3}?bc",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABBBBC","ab{1,3}?bc",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABBBBC","ab{1,3}?bc",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABBBBC","ab{1,3}?bc",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABBBBC","ab{3,4}?bc",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABBBBC","ab{3,4}?bc",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABBBBC","ab{3,4}?bc",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABBBBC","ab{3,4}?bc",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{4,5}?bc",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{4,5}?bc",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{4,5}?bc",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","ab{4,5}?bc",[caseless]))),
<<"ABQ">> = iolist_to_binary(join(re:split("ABQ","ab{4,5}?bc",[caseless,
- trim]))),
+ trim]))),
<<"ABQ">> = iolist_to_binary(join(re:split("ABQ","ab{4,5}?bc",[caseless,
{parts,
- 2}]))),
- <<"ABQ">> = iolist_to_binary(join(re:split("ABQ","ab{4,5}?bc",[caseless]))),
+ 2}]))),
+ <<"ABQ">> = iolist_to_binary(join(re:split("ABQ","ab{4,5}?bc",[caseless]))),
<<"ABBBBC">> = iolist_to_binary(join(re:split("ABBBBC","ab{4,5}?bc",[caseless,
- trim]))),
+ trim]))),
<<"ABBBBC">> = iolist_to_binary(join(re:split("ABBBBC","ab{4,5}?bc",[caseless,
{parts,
- 2}]))),
- <<"ABBBBC">> = iolist_to_binary(join(re:split("ABBBBC","ab{4,5}?bc",[caseless]))),
+ 2}]))),
+ <<"ABBBBC">> = iolist_to_binary(join(re:split("ABBBBC","ab{4,5}?bc",[caseless]))),
ok.
run21() ->
<<"">> = iolist_to_binary(join(re:split("ABBC","ab??bc",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABBC","ab??bc",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABBC","ab??bc",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABBC","ab??bc",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABC","ab??bc",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABC","ab??bc",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABC","ab??bc",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABC","ab??bc",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABC","ab{0,1}?bc",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABC","ab{0,1}?bc",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABC","ab{0,1}?bc",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABC","ab{0,1}?bc",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABC","ab??c",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABC","ab??c",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABC","ab??c",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABC","ab??c",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABC","ab{0,1}?c",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABC","ab{0,1}?c",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABC","ab{0,1}?c",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABC","ab{0,1}?c",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABC","^abc$",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABC","^abc$",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABC","^abc$",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABC","^abc$",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^abc$",[caseless]))),
<<"ABBBBC">> = iolist_to_binary(join(re:split("ABBBBC","^abc$",[caseless,
- trim]))),
+ trim]))),
<<"ABBBBC">> = iolist_to_binary(join(re:split("ABBBBC","^abc$",[caseless,
{parts,
- 2}]))),
- <<"ABBBBC">> = iolist_to_binary(join(re:split("ABBBBC","^abc$",[caseless]))),
+ 2}]))),
+ <<"ABBBBC">> = iolist_to_binary(join(re:split("ABBBBC","^abc$",[caseless]))),
<<"ABCC">> = iolist_to_binary(join(re:split("ABCC","^abc$",[caseless,
- trim]))),
+ trim]))),
<<"ABCC">> = iolist_to_binary(join(re:split("ABCC","^abc$",[caseless,
{parts,
- 2}]))),
- <<"ABCC">> = iolist_to_binary(join(re:split("ABCC","^abc$",[caseless]))),
+ 2}]))),
+ <<"ABCC">> = iolist_to_binary(join(re:split("ABCC","^abc$",[caseless]))),
<<":C">> = iolist_to_binary(join(re:split("ABCC","^abc",[caseless,
- trim]))),
+ trim]))),
<<":C">> = iolist_to_binary(join(re:split("ABCC","^abc",[caseless,
{parts,
- 2}]))),
- <<":C">> = iolist_to_binary(join(re:split("ABCC","^abc",[caseless]))),
+ 2}]))),
+ <<":C">> = iolist_to_binary(join(re:split("ABCC","^abc",[caseless]))),
<<"A">> = iolist_to_binary(join(re:split("AABC","abc$",[caseless,
- trim]))),
+ trim]))),
<<"A:">> = iolist_to_binary(join(re:split("AABC","abc$",[caseless,
{parts,
- 2}]))),
- <<"A:">> = iolist_to_binary(join(re:split("AABC","abc$",[caseless]))),
+ 2}]))),
+ <<"A:">> = iolist_to_binary(join(re:split("AABC","abc$",[caseless]))),
<<"ABC">> = iolist_to_binary(join(re:split("ABC","^",[caseless,
- trim]))),
+ trim]))),
<<"ABC">> = iolist_to_binary(join(re:split("ABC","^",[caseless,
{parts,
- 2}]))),
- <<"ABC">> = iolist_to_binary(join(re:split("ABC","^",[caseless]))),
+ 2}]))),
+ <<"ABC">> = iolist_to_binary(join(re:split("ABC","^",[caseless]))),
<<"ABC">> = iolist_to_binary(join(re:split("ABC","$",[caseless,
- trim]))),
+ trim]))),
<<"ABC:">> = iolist_to_binary(join(re:split("ABC","$",[caseless,
{parts,
- 2}]))),
- <<"ABC:">> = iolist_to_binary(join(re:split("ABC","$",[caseless]))),
+ 2}]))),
+ <<"ABC:">> = iolist_to_binary(join(re:split("ABC","$",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABC","a.c",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABC","a.c",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABC","a.c",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABC","a.c",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("AXC","a.c",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("AXC","a.c",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("AXC","a.c",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("AXC","a.c",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("AXYZC","a.*?c",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("AXYZC","a.*?c",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("AXYZC","a.*?c",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("AXYZC","a.*?c",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a.*c",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a.*c",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a.*c",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a.*c",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("AABC","a.*c",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("AABC","a.*c",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("AABC","a.*c",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("AABC","a.*c",[caseless]))),
<<"AXYZD">> = iolist_to_binary(join(re:split("AXYZD","a.*c",[caseless,
- trim]))),
+ trim]))),
<<"AXYZD">> = iolist_to_binary(join(re:split("AXYZD","a.*c",[caseless,
{parts,
- 2}]))),
- <<"AXYZD">> = iolist_to_binary(join(re:split("AXYZD","a.*c",[caseless]))),
+ 2}]))),
+ <<"AXYZD">> = iolist_to_binary(join(re:split("AXYZD","a.*c",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABD","a[bc]d",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABD","a[bc]d",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABD","a[bc]d",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABD","a[bc]d",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ACE","a[b-d]e",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ACE","a[b-d]e",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ACE","a[b-d]e",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ACE","a[b-d]e",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[b-d]e",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[b-d]e",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[b-d]e",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[b-d]e",[caseless]))),
<<"ABC">> = iolist_to_binary(join(re:split("ABC","a[b-d]e",[caseless,
- trim]))),
+ trim]))),
<<"ABC">> = iolist_to_binary(join(re:split("ABC","a[b-d]e",[caseless,
{parts,
- 2}]))),
- <<"ABC">> = iolist_to_binary(join(re:split("ABC","a[b-d]e",[caseless]))),
+ 2}]))),
+ <<"ABC">> = iolist_to_binary(join(re:split("ABC","a[b-d]e",[caseless]))),
<<"ABD">> = iolist_to_binary(join(re:split("ABD","a[b-d]e",[caseless,
- trim]))),
+ trim]))),
<<"ABD">> = iolist_to_binary(join(re:split("ABD","a[b-d]e",[caseless,
{parts,
- 2}]))),
- <<"ABD">> = iolist_to_binary(join(re:split("ABD","a[b-d]e",[caseless]))),
+ 2}]))),
+ <<"ABD">> = iolist_to_binary(join(re:split("ABD","a[b-d]e",[caseless]))),
<<"A">> = iolist_to_binary(join(re:split("AAC","a[b-d]",[caseless,
- trim]))),
+ trim]))),
<<"A:">> = iolist_to_binary(join(re:split("AAC","a[b-d]",[caseless,
{parts,
- 2}]))),
- <<"A:">> = iolist_to_binary(join(re:split("AAC","a[b-d]",[caseless]))),
+ 2}]))),
+ <<"A:">> = iolist_to_binary(join(re:split("AAC","a[b-d]",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("A-","a[-b]",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("A-","a[-b]",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("A-","a[-b]",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("A-","a[-b]",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("A-","a[b-]",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("A-","a[b-]",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("A-","a[b-]",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("A-","a[b-]",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("A]","a]",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("A]","a]",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("A]","a]",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("A]","a]",[caseless]))),
ok.
run22() ->
<<"">> = iolist_to_binary(join(re:split("A]B","a[]]b",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("A]B","a[]]b",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("A]B","a[]]b",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("A]B","a[]]b",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("AED","a[^bc]d",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("AED","a[^bc]d",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("AED","a[^bc]d",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("AED","a[^bc]d",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ADC","a[^-b]c",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ADC","a[^-b]c",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ADC","a[^-b]c",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ADC","a[^-b]c",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^-b]c",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^-b]c",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^-b]c",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a[^-b]c",[caseless]))),
<<"ABD">> = iolist_to_binary(join(re:split("ABD","a[^-b]c",[caseless,
- trim]))),
+ trim]))),
<<"ABD">> = iolist_to_binary(join(re:split("ABD","a[^-b]c",[caseless,
{parts,
- 2}]))),
- <<"ABD">> = iolist_to_binary(join(re:split("ABD","a[^-b]c",[caseless]))),
+ 2}]))),
+ <<"ABD">> = iolist_to_binary(join(re:split("ABD","a[^-b]c",[caseless]))),
<<"A-C">> = iolist_to_binary(join(re:split("A-C","a[^-b]c",[caseless,
- trim]))),
+ trim]))),
<<"A-C">> = iolist_to_binary(join(re:split("A-C","a[^-b]c",[caseless,
{parts,
- 2}]))),
- <<"A-C">> = iolist_to_binary(join(re:split("A-C","a[^-b]c",[caseless]))),
+ 2}]))),
+ <<"A-C">> = iolist_to_binary(join(re:split("A-C","a[^-b]c",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ADC","a[^]b]c",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ADC","a[^]b]c",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ADC","a[^]b]c",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ADC","a[^]b]c",[caseless]))),
<<":C">> = iolist_to_binary(join(re:split("ABC","ab|cd",[caseless,
- trim]))),
+ trim]))),
<<":C">> = iolist_to_binary(join(re:split("ABC","ab|cd",[caseless,
{parts,
- 2}]))),
- <<":C">> = iolist_to_binary(join(re:split("ABC","ab|cd",[caseless]))),
+ 2}]))),
+ <<":C">> = iolist_to_binary(join(re:split("ABC","ab|cd",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABCD","ab|cd",[caseless,
- trim]))),
+ trim]))),
<<":CD">> = iolist_to_binary(join(re:split("ABCD","ab|cd",[caseless,
{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("ABCD","ab|cd",[caseless]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("ABCD","ab|cd",[caseless]))),
<<"D">> = iolist_to_binary(join(re:split("DEF","()ef",[caseless,
- trim]))),
+ trim]))),
<<"D::">> = iolist_to_binary(join(re:split("DEF","()ef",[caseless,
{parts,
- 2}]))),
- <<"D::">> = iolist_to_binary(join(re:split("DEF","()ef",[caseless]))),
+ 2}]))),
+ <<"D::">> = iolist_to_binary(join(re:split("DEF","()ef",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","$b",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","$b",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","$b",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","$b",[caseless]))),
<<"A]C">> = iolist_to_binary(join(re:split("A]C","$b",[caseless,
- trim]))),
+ trim]))),
<<"A]C">> = iolist_to_binary(join(re:split("A]C","$b",[caseless,
{parts,
- 2}]))),
- <<"A]C">> = iolist_to_binary(join(re:split("A]C","$b",[caseless]))),
+ 2}]))),
+ <<"A]C">> = iolist_to_binary(join(re:split("A]C","$b",[caseless]))),
<<"B">> = iolist_to_binary(join(re:split("B","$b",[caseless,
- trim]))),
+ trim]))),
<<"B">> = iolist_to_binary(join(re:split("B","$b",[caseless,
{parts,
- 2}]))),
- <<"B">> = iolist_to_binary(join(re:split("B","$b",[caseless]))),
+ 2}]))),
+ <<"B">> = iolist_to_binary(join(re:split("B","$b",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("A(B","a\\(b",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("A(B","a\\(b",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("A(B","a\\(b",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("A(B","a\\(b",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("AB","a\\(*b",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("AB","a\\(*b",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("AB","a\\(*b",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("AB","a\\(*b",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("A((B","a\\(*b",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("A((B","a\\(*b",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("A((B","a\\(*b",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("A((B","a\\(*b",[caseless]))),
<<"A">> = iolist_to_binary(join(re:split("A","a\\\\b",[caseless,
notbol,
- trim]))),
+ trim]))),
<<"A">> = iolist_to_binary(join(re:split("A","a\\\\b",[caseless,
notbol,
{parts,
- 2}]))),
+ 2}]))),
<<"A">> = iolist_to_binary(join(re:split("A","a\\\\b",[caseless,
- notbol]))),
+ notbol]))),
<<":A:A:BC">> = iolist_to_binary(join(re:split("ABC","((a))",[caseless,
- trim]))),
+ trim]))),
<<":A:A:BC">> = iolist_to_binary(join(re:split("ABC","((a))",[caseless,
{parts,
- 2}]))),
- <<":A:A:BC">> = iolist_to_binary(join(re:split("ABC","((a))",[caseless]))),
+ 2}]))),
+ <<":A:A:BC">> = iolist_to_binary(join(re:split("ABC","((a))",[caseless]))),
<<":A:C">> = iolist_to_binary(join(re:split("ABC","(a)b(c)",[caseless,
- trim]))),
+ trim]))),
<<":A:C:">> = iolist_to_binary(join(re:split("ABC","(a)b(c)",[caseless,
{parts,
- 2}]))),
- <<":A:C:">> = iolist_to_binary(join(re:split("ABC","(a)b(c)",[caseless]))),
+ 2}]))),
+ <<":A:C:">> = iolist_to_binary(join(re:split("ABC","(a)b(c)",[caseless]))),
<<"AABB">> = iolist_to_binary(join(re:split("AABBABC","a+b+c",[caseless,
- trim]))),
+ trim]))),
<<"AABB:">> = iolist_to_binary(join(re:split("AABBABC","a+b+c",[caseless,
{parts,
- 2}]))),
- <<"AABB:">> = iolist_to_binary(join(re:split("AABBABC","a+b+c",[caseless]))),
+ 2}]))),
+ <<"AABB:">> = iolist_to_binary(join(re:split("AABBABC","a+b+c",[caseless]))),
<<"AABB">> = iolist_to_binary(join(re:split("AABBABC","a{1,}b{1,}c",[caseless,
- trim]))),
+ trim]))),
<<"AABB:">> = iolist_to_binary(join(re:split("AABBABC","a{1,}b{1,}c",[caseless,
{parts,
- 2}]))),
- <<"AABB:">> = iolist_to_binary(join(re:split("AABBABC","a{1,}b{1,}c",[caseless]))),
+ 2}]))),
+ <<"AABB:">> = iolist_to_binary(join(re:split("AABBABC","a{1,}b{1,}c",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABCABC","a.+?c",[caseless,
- trim]))),
+ trim]))),
<<":ABC">> = iolist_to_binary(join(re:split("ABCABC","a.+?c",[caseless,
{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("ABCABC","a.+?c",[caseless]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("ABCABC","a.+?c",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABCABC","a.*?c",[caseless,
- trim]))),
+ trim]))),
<<":ABC">> = iolist_to_binary(join(re:split("ABCABC","a.*?c",[caseless,
{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("ABCABC","a.*?c",[caseless]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("ABCABC","a.*?c",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABCABC","a.{0,5}?c",[caseless,
- trim]))),
+ trim]))),
<<":ABC">> = iolist_to_binary(join(re:split("ABCABC","a.{0,5}?c",[caseless,
{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("ABCABC","a.{0,5}?c",[caseless]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("ABCABC","a.{0,5}?c",[caseless]))),
<<":B">> = iolist_to_binary(join(re:split("AB","(a+|b)*",[caseless,
- trim]))),
+ trim]))),
<<":B:">> = iolist_to_binary(join(re:split("AB","(a+|b)*",[caseless,
{parts,
- 2}]))),
- <<":B:">> = iolist_to_binary(join(re:split("AB","(a+|b)*",[caseless]))),
+ 2}]))),
+ <<":B:">> = iolist_to_binary(join(re:split("AB","(a+|b)*",[caseless]))),
<<":B">> = iolist_to_binary(join(re:split("AB","(a+|b){0,}",[caseless,
- trim]))),
+ trim]))),
<<":B:">> = iolist_to_binary(join(re:split("AB","(a+|b){0,}",[caseless,
{parts,
- 2}]))),
- <<":B:">> = iolist_to_binary(join(re:split("AB","(a+|b){0,}",[caseless]))),
+ 2}]))),
+ <<":B:">> = iolist_to_binary(join(re:split("AB","(a+|b){0,}",[caseless]))),
<<":B">> = iolist_to_binary(join(re:split("AB","(a+|b)+",[caseless,
- trim]))),
+ trim]))),
<<":B:">> = iolist_to_binary(join(re:split("AB","(a+|b)+",[caseless,
{parts,
- 2}]))),
- <<":B:">> = iolist_to_binary(join(re:split("AB","(a+|b)+",[caseless]))),
+ 2}]))),
+ <<":B:">> = iolist_to_binary(join(re:split("AB","(a+|b)+",[caseless]))),
ok.
run23() ->
<<":B">> = iolist_to_binary(join(re:split("AB","(a+|b){1,}",[caseless,
- trim]))),
+ trim]))),
<<":B:">> = iolist_to_binary(join(re:split("AB","(a+|b){1,}",[caseless,
{parts,
- 2}]))),
- <<":B:">> = iolist_to_binary(join(re:split("AB","(a+|b){1,}",[caseless]))),
+ 2}]))),
+ <<":B:">> = iolist_to_binary(join(re:split("AB","(a+|b){1,}",[caseless]))),
<<":A::B">> = iolist_to_binary(join(re:split("AB","(a+|b)?",[caseless,
- trim]))),
+ trim]))),
<<":A:B">> = iolist_to_binary(join(re:split("AB","(a+|b)?",[caseless,
{parts,
- 2}]))),
- <<":A::B:">> = iolist_to_binary(join(re:split("AB","(a+|b)?",[caseless]))),
+ 2}]))),
+ <<":A::B:">> = iolist_to_binary(join(re:split("AB","(a+|b)?",[caseless]))),
<<":A::B">> = iolist_to_binary(join(re:split("AB","(a+|b){0,1}",[caseless,
- trim]))),
+ trim]))),
<<":A:B">> = iolist_to_binary(join(re:split("AB","(a+|b){0,1}",[caseless,
{parts,
- 2}]))),
- <<":A::B:">> = iolist_to_binary(join(re:split("AB","(a+|b){0,1}",[caseless]))),
+ 2}]))),
+ <<":A::B:">> = iolist_to_binary(join(re:split("AB","(a+|b){0,1}",[caseless]))),
<<":A::B">> = iolist_to_binary(join(re:split("AB","(a+|b){0,1}?",[caseless,
- trim]))),
+ trim]))),
<<":A:B">> = iolist_to_binary(join(re:split("AB","(a+|b){0,1}?",[caseless,
{parts,
- 2}]))),
- <<":A::B:">> = iolist_to_binary(join(re:split("AB","(a+|b){0,1}?",[caseless]))),
+ 2}]))),
+ <<":A::B:">> = iolist_to_binary(join(re:split("AB","(a+|b){0,1}?",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("CDE","[^ab]*",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("CDE","[^ab]*",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("CDE","[^ab]*",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("CDE","[^ab]*",[caseless]))),
<<":C">> = iolist_to_binary(join(re:split("ABBBCD","([abc])*d",[caseless,
- trim]))),
+ trim]))),
<<":C:">> = iolist_to_binary(join(re:split("ABBBCD","([abc])*d",[caseless,
{parts,
- 2}]))),
- <<":C:">> = iolist_to_binary(join(re:split("ABBBCD","([abc])*d",[caseless]))),
+ 2}]))),
+ <<":C:">> = iolist_to_binary(join(re:split("ABBBCD","([abc])*d",[caseless]))),
<<":A">> = iolist_to_binary(join(re:split("ABCD","([abc])*bcd",[caseless,
- trim]))),
+ trim]))),
<<":A:">> = iolist_to_binary(join(re:split("ABCD","([abc])*bcd",[caseless,
{parts,
- 2}]))),
- <<":A:">> = iolist_to_binary(join(re:split("ABCD","([abc])*bcd",[caseless]))),
+ 2}]))),
+ <<":A:">> = iolist_to_binary(join(re:split("ABCD","([abc])*bcd",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("E","a|b|c|d|e",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("E","a|b|c|d|e",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("E","a|b|c|d|e",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("E","a|b|c|d|e",[caseless]))),
<<":E">> = iolist_to_binary(join(re:split("EF","(a|b|c|d|e)f",[caseless,
- trim]))),
+ trim]))),
<<":E:">> = iolist_to_binary(join(re:split("EF","(a|b|c|d|e)f",[caseless,
{parts,
- 2}]))),
- <<":E:">> = iolist_to_binary(join(re:split("EF","(a|b|c|d|e)f",[caseless]))),
+ 2}]))),
+ <<":E:">> = iolist_to_binary(join(re:split("EF","(a|b|c|d|e)f",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ABCDEFG","abcd*efg",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABCDEFG","abcd*efg",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABCDEFG","abcd*efg",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABCDEFG","abcd*efg",[caseless]))),
<<"X:Y:Z">> = iolist_to_binary(join(re:split("XABYABBBZ","ab*",[caseless,
- trim]))),
+ trim]))),
<<"X:YABBBZ">> = iolist_to_binary(join(re:split("XABYABBBZ","ab*",[caseless,
{parts,
- 2}]))),
- <<"X:Y:Z">> = iolist_to_binary(join(re:split("XABYABBBZ","ab*",[caseless]))),
+ 2}]))),
+ <<"X:Y:Z">> = iolist_to_binary(join(re:split("XABYABBBZ","ab*",[caseless]))),
<<"X:Y:Z">> = iolist_to_binary(join(re:split("XAYABBBZ","ab*",[caseless,
- trim]))),
+ trim]))),
<<"X:YABBBZ">> = iolist_to_binary(join(re:split("XAYABBBZ","ab*",[caseless,
{parts,
- 2}]))),
- <<"X:Y:Z">> = iolist_to_binary(join(re:split("XAYABBBZ","ab*",[caseless]))),
+ 2}]))),
+ <<"X:Y:Z">> = iolist_to_binary(join(re:split("XAYABBBZ","ab*",[caseless]))),
<<"AB:CD">> = iolist_to_binary(join(re:split("ABCDE","(ab|cd)e",[caseless,
- trim]))),
+ trim]))),
<<"AB:CD:">> = iolist_to_binary(join(re:split("ABCDE","(ab|cd)e",[caseless,
{parts,
- 2}]))),
- <<"AB:CD:">> = iolist_to_binary(join(re:split("ABCDE","(ab|cd)e",[caseless]))),
+ 2}]))),
+ <<"AB:CD:">> = iolist_to_binary(join(re:split("ABCDE","(ab|cd)e",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("HIJ","[abhgefdc]ij",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("HIJ","[abhgefdc]ij",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("HIJ","[abhgefdc]ij",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("HIJ","[abhgefdc]ij",[caseless]))),
<<"ABCDE">> = iolist_to_binary(join(re:split("ABCDE","^(ab|cd)e",[caseless,
- trim]))),
+ trim]))),
<<"ABCDE">> = iolist_to_binary(join(re:split("ABCDE","^(ab|cd)e",[caseless,
{parts,
- 2}]))),
- <<"ABCDE">> = iolist_to_binary(join(re:split("ABCDE","^(ab|cd)e",[caseless]))),
+ 2}]))),
+ <<"ABCDE">> = iolist_to_binary(join(re:split("ABCDE","^(ab|cd)e",[caseless]))),
<<"ABCD">> = iolist_to_binary(join(re:split("ABCDEF","(abc|)ef",[caseless,
- trim]))),
+ trim]))),
<<"ABCD::">> = iolist_to_binary(join(re:split("ABCDEF","(abc|)ef",[caseless,
{parts,
- 2}]))),
- <<"ABCD::">> = iolist_to_binary(join(re:split("ABCDEF","(abc|)ef",[caseless]))),
+ 2}]))),
+ <<"ABCD::">> = iolist_to_binary(join(re:split("ABCDEF","(abc|)ef",[caseless]))),
<<"A:B">> = iolist_to_binary(join(re:split("ABCD","(a|b)c*d",[caseless,
- trim]))),
+ trim]))),
<<"A:B:">> = iolist_to_binary(join(re:split("ABCD","(a|b)c*d",[caseless,
{parts,
- 2}]))),
- <<"A:B:">> = iolist_to_binary(join(re:split("ABCD","(a|b)c*d",[caseless]))),
+ 2}]))),
+ <<"A:B:">> = iolist_to_binary(join(re:split("ABCD","(a|b)c*d",[caseless]))),
<<":A">> = iolist_to_binary(join(re:split("ABC","(ab|ab*)bc",[caseless,
- trim]))),
+ trim]))),
<<":A:">> = iolist_to_binary(join(re:split("ABC","(ab|ab*)bc",[caseless,
{parts,
- 2}]))),
- <<":A:">> = iolist_to_binary(join(re:split("ABC","(ab|ab*)bc",[caseless]))),
+ 2}]))),
+ <<":A:">> = iolist_to_binary(join(re:split("ABC","(ab|ab*)bc",[caseless]))),
<<":BC">> = iolist_to_binary(join(re:split("ABC","a([bc]*)c*",[caseless,
- trim]))),
+ trim]))),
<<":BC:">> = iolist_to_binary(join(re:split("ABC","a([bc]*)c*",[caseless,
{parts,
- 2}]))),
- <<":BC:">> = iolist_to_binary(join(re:split("ABC","a([bc]*)c*",[caseless]))),
+ 2}]))),
+ <<":BC:">> = iolist_to_binary(join(re:split("ABC","a([bc]*)c*",[caseless]))),
ok.
run24() ->
<<":BC:D">> = iolist_to_binary(join(re:split("ABCD","a([bc]*)(c*d)",[caseless,
- trim]))),
+ trim]))),
<<":BC:D:">> = iolist_to_binary(join(re:split("ABCD","a([bc]*)(c*d)",[caseless,
{parts,
- 2}]))),
- <<":BC:D:">> = iolist_to_binary(join(re:split("ABCD","a([bc]*)(c*d)",[caseless]))),
+ 2}]))),
+ <<":BC:D:">> = iolist_to_binary(join(re:split("ABCD","a([bc]*)(c*d)",[caseless]))),
<<":BC:D">> = iolist_to_binary(join(re:split("ABCD","a([bc]+)(c*d)",[caseless,
- trim]))),
+ trim]))),
<<":BC:D:">> = iolist_to_binary(join(re:split("ABCD","a([bc]+)(c*d)",[caseless,
{parts,
- 2}]))),
- <<":BC:D:">> = iolist_to_binary(join(re:split("ABCD","a([bc]+)(c*d)",[caseless]))),
+ 2}]))),
+ <<":BC:D:">> = iolist_to_binary(join(re:split("ABCD","a([bc]+)(c*d)",[caseless]))),
<<":B:CD">> = iolist_to_binary(join(re:split("ABCD","a([bc]*)(c+d)",[caseless,
- trim]))),
+ trim]))),
<<":B:CD:">> = iolist_to_binary(join(re:split("ABCD","a([bc]*)(c+d)",[caseless,
{parts,
- 2}]))),
- <<":B:CD:">> = iolist_to_binary(join(re:split("ABCD","a([bc]*)(c+d)",[caseless]))),
+ 2}]))),
+ <<":B:CD:">> = iolist_to_binary(join(re:split("ABCD","a([bc]*)(c+d)",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ADCDCDE","a[bcd]*dcdcde",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ADCDCDE","a[bcd]*dcdcde",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ADCDCDE","a[bcd]*dcdcde",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ADCDCDE","a[bcd]*dcdcde",[caseless]))),
<<":AB">> = iolist_to_binary(join(re:split("ABC","(ab|a)b*c",[caseless,
- trim]))),
+ trim]))),
<<":AB:">> = iolist_to_binary(join(re:split("ABC","(ab|a)b*c",[caseless,
{parts,
- 2}]))),
- <<":AB:">> = iolist_to_binary(join(re:split("ABC","(ab|a)b*c",[caseless]))),
+ 2}]))),
+ <<":AB:">> = iolist_to_binary(join(re:split("ABC","(ab|a)b*c",[caseless]))),
<<":ABC:A:B:D">> = iolist_to_binary(join(re:split("ABCD","((a)(b)c)(d)",[caseless,
- trim]))),
+ trim]))),
<<":ABC:A:B:D:">> = iolist_to_binary(join(re:split("ABCD","((a)(b)c)(d)",[caseless,
{parts,
- 2}]))),
- <<":ABC:A:B:D:">> = iolist_to_binary(join(re:split("ABCD","((a)(b)c)(d)",[caseless]))),
+ 2}]))),
+ <<":ABC:A:B:D:">> = iolist_to_binary(join(re:split("ABCD","((a)(b)c)(d)",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ALPHA","[a-zA-Z_][a-zA-Z0-9_]*",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ALPHA","[a-zA-Z_][a-zA-Z0-9_]*",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ALPHA","[a-zA-Z_][a-zA-Z0-9_]*",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ALPHA","[a-zA-Z_][a-zA-Z0-9_]*",[caseless]))),
<<"A">> = iolist_to_binary(join(re:split("ABH","^a(bc+|b[eh])g|.h$",[caseless,
- trim]))),
+ trim]))),
<<"A::">> = iolist_to_binary(join(re:split("ABH","^a(bc+|b[eh])g|.h$",[caseless,
{parts,
- 2}]))),
- <<"A::">> = iolist_to_binary(join(re:split("ABH","^a(bc+|b[eh])g|.h$",[caseless]))),
+ 2}]))),
+ <<"A::">> = iolist_to_binary(join(re:split("ABH","^a(bc+|b[eh])g|.h$",[caseless]))),
<<":EFFGZ">> = iolist_to_binary(join(re:split("EFFGZ","(bc+d$|ef*g.|h?i(j|k))",[caseless,
- trim]))),
+ trim]))),
<<":EFFGZ::">> = iolist_to_binary(join(re:split("EFFGZ","(bc+d$|ef*g.|h?i(j|k))",[caseless,
{parts,
- 2}]))),
- <<":EFFGZ::">> = iolist_to_binary(join(re:split("EFFGZ","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
+ 2}]))),
+ <<":EFFGZ::">> = iolist_to_binary(join(re:split("EFFGZ","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
<<":IJ:J">> = iolist_to_binary(join(re:split("IJ","(bc+d$|ef*g.|h?i(j|k))",[caseless,
- trim]))),
+ trim]))),
<<":IJ:J:">> = iolist_to_binary(join(re:split("IJ","(bc+d$|ef*g.|h?i(j|k))",[caseless,
{parts,
- 2}]))),
- <<":IJ:J:">> = iolist_to_binary(join(re:split("IJ","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
+ 2}]))),
+ <<":IJ:J:">> = iolist_to_binary(join(re:split("IJ","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
<<"R:EFFGZ">> = iolist_to_binary(join(re:split("REFFGZ","(bc+d$|ef*g.|h?i(j|k))",[caseless,
- trim]))),
+ trim]))),
<<"R:EFFGZ::">> = iolist_to_binary(join(re:split("REFFGZ","(bc+d$|ef*g.|h?i(j|k))",[caseless,
{parts,
- 2}]))),
- <<"R:EFFGZ::">> = iolist_to_binary(join(re:split("REFFGZ","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
+ 2}]))),
+ <<"R:EFFGZ::">> = iolist_to_binary(join(re:split("REFFGZ","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(bc+d$|ef*g.|h?i(j|k))",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(bc+d$|ef*g.|h?i(j|k))",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
<<"ADCDCDE">> = iolist_to_binary(join(re:split("ADCDCDE","(bc+d$|ef*g.|h?i(j|k))",[caseless,
- trim]))),
+ trim]))),
<<"ADCDCDE">> = iolist_to_binary(join(re:split("ADCDCDE","(bc+d$|ef*g.|h?i(j|k))",[caseless,
{parts,
- 2}]))),
- <<"ADCDCDE">> = iolist_to_binary(join(re:split("ADCDCDE","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
+ 2}]))),
+ <<"ADCDCDE">> = iolist_to_binary(join(re:split("ADCDCDE","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
<<"EFFG">> = iolist_to_binary(join(re:split("EFFG","(bc+d$|ef*g.|h?i(j|k))",[caseless,
- trim]))),
+ trim]))),
<<"EFFG">> = iolist_to_binary(join(re:split("EFFG","(bc+d$|ef*g.|h?i(j|k))",[caseless,
{parts,
- 2}]))),
- <<"EFFG">> = iolist_to_binary(join(re:split("EFFG","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
+ 2}]))),
+ <<"EFFG">> = iolist_to_binary(join(re:split("EFFG","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
<<"BCDD">> = iolist_to_binary(join(re:split("BCDD","(bc+d$|ef*g.|h?i(j|k))",[caseless,
- trim]))),
+ trim]))),
<<"BCDD">> = iolist_to_binary(join(re:split("BCDD","(bc+d$|ef*g.|h?i(j|k))",[caseless,
{parts,
- 2}]))),
- <<"BCDD">> = iolist_to_binary(join(re:split("BCDD","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
+ 2}]))),
+ <<"BCDD">> = iolist_to_binary(join(re:split("BCDD","(bc+d$|ef*g.|h?i(j|k))",[caseless]))),
<<":A:A:A:A:A:A:A:A:A:A">> = iolist_to_binary(join(re:split("A","((((((((((a))))))))))",[caseless,
- trim]))),
+ trim]))),
<<":A:A:A:A:A:A:A:A:A:A:">> = iolist_to_binary(join(re:split("A","((((((((((a))))))))))",[caseless,
{parts,
- 2}]))),
- <<":A:A:A:A:A:A:A:A:A:A:">> = iolist_to_binary(join(re:split("A","((((((((((a))))))))))",[caseless]))),
+ 2}]))),
+ <<":A:A:A:A:A:A:A:A:A:A:">> = iolist_to_binary(join(re:split("A","((((((((((a))))))))))",[caseless]))),
<<":A:A:A:A:A:A:A:A:A:A">> = iolist_to_binary(join(re:split("AA","((((((((((a))))))))))\\10",[caseless,
- trim]))),
+ trim]))),
<<":A:A:A:A:A:A:A:A:A:A:">> = iolist_to_binary(join(re:split("AA","((((((((((a))))))))))\\10",[caseless,
{parts,
- 2}]))),
- <<":A:A:A:A:A:A:A:A:A:A:">> = iolist_to_binary(join(re:split("AA","((((((((((a))))))))))\\10",[caseless]))),
+ 2}]))),
+ <<":A:A:A:A:A:A:A:A:A:A:">> = iolist_to_binary(join(re:split("AA","((((((((((a))))))))))\\10",[caseless]))),
<<":A:A:A:A:A:A:A:A:A">> = iolist_to_binary(join(re:split("A","(((((((((a)))))))))",[caseless,
- trim]))),
+ trim]))),
<<":A:A:A:A:A:A:A:A:A:">> = iolist_to_binary(join(re:split("A","(((((((((a)))))))))",[caseless,
{parts,
- 2}]))),
- <<":A:A:A:A:A:A:A:A:A:">> = iolist_to_binary(join(re:split("A","(((((((((a)))))))))",[caseless]))),
+ 2}]))),
+ <<":A:A:A:A:A:A:A:A:A:">> = iolist_to_binary(join(re:split("A","(((((((((a)))))))))",[caseless]))),
<<":A">> = iolist_to_binary(join(re:split("A","(?:(?:(?:(?:(?:(?:(?:(?:(?:(a))))))))))",[caseless,
- trim]))),
+ trim]))),
<<":A:">> = iolist_to_binary(join(re:split("A","(?:(?:(?:(?:(?:(?:(?:(?:(?:(a))))))))))",[caseless,
{parts,
- 2}]))),
- <<":A:">> = iolist_to_binary(join(re:split("A","(?:(?:(?:(?:(?:(?:(?:(?:(?:(a))))))))))",[caseless]))),
+ 2}]))),
+ <<":A:">> = iolist_to_binary(join(re:split("A","(?:(?:(?:(?:(?:(?:(?:(?:(?:(a))))))))))",[caseless]))),
<<":C">> = iolist_to_binary(join(re:split("C","(?:(?:(?:(?:(?:(?:(?:(?:(?:(a|b|c))))))))))",[caseless,
- trim]))),
+ trim]))),
<<":C:">> = iolist_to_binary(join(re:split("C","(?:(?:(?:(?:(?:(?:(?:(?:(?:(a|b|c))))))))))",[caseless,
{parts,
- 2}]))),
- <<":C:">> = iolist_to_binary(join(re:split("C","(?:(?:(?:(?:(?:(?:(?:(?:(?:(a|b|c))))))))))",[caseless]))),
+ 2}]))),
+ <<":C:">> = iolist_to_binary(join(re:split("C","(?:(?:(?:(?:(?:(?:(?:(?:(?:(a|b|c))))))))))",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","multiple words of text",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","multiple words of text",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","multiple words of text",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","multiple words of text",[caseless]))),
<<"AA">> = iolist_to_binary(join(re:split("AA","multiple words of text",[caseless,
- trim]))),
+ trim]))),
<<"AA">> = iolist_to_binary(join(re:split("AA","multiple words of text",[caseless,
{parts,
- 2}]))),
- <<"AA">> = iolist_to_binary(join(re:split("AA","multiple words of text",[caseless]))),
+ 2}]))),
+ <<"AA">> = iolist_to_binary(join(re:split("AA","multiple words of text",[caseless]))),
<<"UH-UH">> = iolist_to_binary(join(re:split("UH-UH","multiple words of text",[caseless,
- trim]))),
+ trim]))),
<<"UH-UH">> = iolist_to_binary(join(re:split("UH-UH","multiple words of text",[caseless,
{parts,
- 2}]))),
- <<"UH-UH">> = iolist_to_binary(join(re:split("UH-UH","multiple words of text",[caseless]))),
+ 2}]))),
+ <<"UH-UH">> = iolist_to_binary(join(re:split("UH-UH","multiple words of text",[caseless]))),
<<":, YEAH">> = iolist_to_binary(join(re:split("MULTIPLE WORDS, YEAH","multiple words",[caseless,
- trim]))),
+ trim]))),
<<":, YEAH">> = iolist_to_binary(join(re:split("MULTIPLE WORDS, YEAH","multiple words",[caseless,
{parts,
- 2}]))),
- <<":, YEAH">> = iolist_to_binary(join(re:split("MULTIPLE WORDS, YEAH","multiple words",[caseless]))),
+ 2}]))),
+ <<":, YEAH">> = iolist_to_binary(join(re:split("MULTIPLE WORDS, YEAH","multiple words",[caseless]))),
<<":AB:DE">> = iolist_to_binary(join(re:split("ABCDE","(.*)c(.*)",[caseless,
- trim]))),
+ trim]))),
<<":AB:DE:">> = iolist_to_binary(join(re:split("ABCDE","(.*)c(.*)",[caseless,
{parts,
- 2}]))),
- <<":AB:DE:">> = iolist_to_binary(join(re:split("ABCDE","(.*)c(.*)",[caseless]))),
+ 2}]))),
+ <<":AB:DE:">> = iolist_to_binary(join(re:split("ABCDE","(.*)c(.*)",[caseless]))),
<<":A:B">> = iolist_to_binary(join(re:split("(A, B)","\\((.*), (.*)\\)",[caseless,
- trim]))),
+ trim]))),
<<":A:B:">> = iolist_to_binary(join(re:split("(A, B)","\\((.*), (.*)\\)",[caseless,
{parts,
- 2}]))),
- <<":A:B:">> = iolist_to_binary(join(re:split("(A, B)","\\((.*), (.*)\\)",[caseless]))),
+ 2}]))),
+ <<":A:B:">> = iolist_to_binary(join(re:split("(A, B)","\\((.*), (.*)\\)",[caseless]))),
ok.
run25() ->
<<"">> = iolist_to_binary(join(re:split("ABCD","abcd",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ABCD","abcd",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ABCD","abcd",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ABCD","abcd",[caseless]))),
<<":BC">> = iolist_to_binary(join(re:split("ABCD","a(bc)d",[caseless,
- trim]))),
+ trim]))),
<<":BC:">> = iolist_to_binary(join(re:split("ABCD","a(bc)d",[caseless,
{parts,
- 2}]))),
- <<":BC:">> = iolist_to_binary(join(re:split("ABCD","a(bc)d",[caseless]))),
+ 2}]))),
+ <<":BC:">> = iolist_to_binary(join(re:split("ABCD","a(bc)d",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("AC","a[-]?c",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("AC","a[-]?c",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("AC","a[-]?c",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("AC","a[-]?c",[caseless]))),
<<":ABC">> = iolist_to_binary(join(re:split("ABCABC","(abc)\\1",[caseless,
- trim]))),
+ trim]))),
<<":ABC:">> = iolist_to_binary(join(re:split("ABCABC","(abc)\\1",[caseless,
{parts,
- 2}]))),
- <<":ABC:">> = iolist_to_binary(join(re:split("ABCABC","(abc)\\1",[caseless]))),
+ 2}]))),
+ <<":ABC:">> = iolist_to_binary(join(re:split("ABCABC","(abc)\\1",[caseless]))),
<<":ABC">> = iolist_to_binary(join(re:split("ABCABC","([a-c]*)\\1",[caseless,
- trim]))),
+ trim]))),
<<":ABC:">> = iolist_to_binary(join(re:split("ABCABC","([a-c]*)\\1",[caseless,
{parts,
- 2}]))),
- <<":ABC:">> = iolist_to_binary(join(re:split("ABCABC","([a-c]*)\\1",[caseless]))),
- <<"ab">> = iolist_to_binary(join(re:split("abad","a(?!b).",[trim]))),
+ 2}]))),
+ <<":ABC:">> = iolist_to_binary(join(re:split("ABCABC","([a-c]*)\\1",[caseless]))),
+ <<"ab">> = iolist_to_binary(join(re:split("abad","a(?!b).",[trim]))),
<<"ab:">> = iolist_to_binary(join(re:split("abad","a(?!b).",[{parts,
- 2}]))),
- <<"ab:">> = iolist_to_binary(join(re:split("abad","a(?!b).",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("abad","a(?=d).",[trim]))),
+ 2}]))),
+ <<"ab:">> = iolist_to_binary(join(re:split("abad","a(?!b).",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("abad","a(?=d).",[trim]))),
<<"ab:">> = iolist_to_binary(join(re:split("abad","a(?=d).",[{parts,
- 2}]))),
- <<"ab:">> = iolist_to_binary(join(re:split("abad","a(?=d).",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("abad","a(?=c|d).",[trim]))),
+ 2}]))),
+ <<"ab:">> = iolist_to_binary(join(re:split("abad","a(?=d).",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("abad","a(?=c|d).",[trim]))),
<<"ab:">> = iolist_to_binary(join(re:split("abad","a(?=c|d).",[{parts,
- 2}]))),
- <<"ab:">> = iolist_to_binary(join(re:split("abad","a(?=c|d).",[]))),
- <<":e">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)(.)",[trim]))),
+ 2}]))),
+ <<"ab:">> = iolist_to_binary(join(re:split("abad","a(?=c|d).",[]))),
+ <<":e">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)(.)",[trim]))),
<<":e:">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)(.)",[{parts,
- 2}]))),
- <<":e:">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)(.)",[]))),
- <<":e">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)*(.)",[trim]))),
+ 2}]))),
+ <<":e:">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)(.)",[]))),
+ <<":e">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)*(.)",[trim]))),
<<":e:">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)*(.)",[{parts,
- 2}]))),
- <<":e:">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)*(.)",[]))),
- <<":e">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)+?(.)",[trim]))),
+ 2}]))),
+ <<":e:">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)*(.)",[]))),
+ <<":e">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)+?(.)",[trim]))),
<<":e:">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)+?(.)",[{parts,
- 2}]))),
- <<":e:">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)+?(.)",[]))),
- <<":d:bcdbe">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d)+?(.)",[trim]))),
+ 2}]))),
+ <<":e:">> = iolist_to_binary(join(re:split("ace","a(?:b|c|d)+?(.)",[]))),
+ <<":d:bcdbe">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d)+?(.)",[trim]))),
<<":d:bcdbe">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d)+?(.)",[{parts,
- 2}]))),
- <<":d:bcdbe">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d)+?(.)",[]))),
- <<":e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d)+(.)",[trim]))),
+ 2}]))),
+ <<":d:bcdbe">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d)+?(.)",[]))),
+ <<":e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d)+(.)",[trim]))),
<<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d)+(.)",[{parts,
- 2}]))),
- <<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d)+(.)",[]))),
- <<":b:cdbe">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){2}(.)",[trim]))),
+ 2}]))),
+ <<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d)+(.)",[]))),
+ <<":b:cdbe">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){2}(.)",[trim]))),
<<":b:cdbe">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){2}(.)",[{parts,
- 2}]))),
- <<":b:cdbe">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){2}(.)",[]))),
- <<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){4,5}(.)",[trim]))),
+ 2}]))),
+ <<":b:cdbe">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){2}(.)",[]))),
+ <<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){4,5}(.)",[trim]))),
<<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){4,5}(.)",[{parts,
- 2}]))),
- <<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){4,5}(.)",[]))),
- <<":d:be">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){4,5}?(.)",[trim]))),
+ 2}]))),
+ <<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){4,5}(.)",[]))),
+ <<":d:be">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){4,5}?(.)",[trim]))),
<<":d:be">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){4,5}?(.)",[{parts,
- 2}]))),
- <<":d:be">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){4,5}?(.)",[]))),
- <<":bar:foo:bar">> = iolist_to_binary(join(re:split("foobar","((foo)|(bar))*",[trim]))),
+ 2}]))),
+ <<":d:be">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){4,5}?(.)",[]))),
+ <<":bar:foo:bar">> = iolist_to_binary(join(re:split("foobar","((foo)|(bar))*",[trim]))),
<<":bar:foo:bar:">> = iolist_to_binary(join(re:split("foobar","((foo)|(bar))*",[{parts,
- 2}]))),
- <<":bar:foo:bar:">> = iolist_to_binary(join(re:split("foobar","((foo)|(bar))*",[]))),
- <<":e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){6,7}(.)",[trim]))),
+ 2}]))),
+ <<":bar:foo:bar:">> = iolist_to_binary(join(re:split("foobar","((foo)|(bar))*",[]))),
+ <<":e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){6,7}(.)",[trim]))),
<<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){6,7}(.)",[{parts,
- 2}]))),
- <<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){6,7}(.)",[]))),
- <<":e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){6,7}?(.)",[trim]))),
+ 2}]))),
+ <<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){6,7}(.)",[]))),
+ <<":e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){6,7}?(.)",[trim]))),
<<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){6,7}?(.)",[{parts,
- 2}]))),
- <<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){6,7}?(.)",[]))),
- <<":e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,6}(.)",[trim]))),
+ 2}]))),
+ <<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){6,7}?(.)",[]))),
+ <<":e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,6}(.)",[trim]))),
<<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,6}(.)",[{parts,
- 2}]))),
- <<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,6}(.)",[]))),
- <<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,6}?(.)",[trim]))),
+ 2}]))),
+ <<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,6}(.)",[]))),
+ <<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,6}?(.)",[trim]))),
<<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,6}?(.)",[{parts,
- 2}]))),
- <<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,6}?(.)",[]))),
+ 2}]))),
+ <<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,6}?(.)",[]))),
ok.
run26() ->
- <<":e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,7}(.)",[trim]))),
+ <<":e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,7}(.)",[trim]))),
<<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,7}(.)",[{parts,
- 2}]))),
- <<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,7}(.)",[]))),
- <<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,7}?(.)",[trim]))),
+ 2}]))),
+ <<":e:">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,7}(.)",[]))),
+ <<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,7}?(.)",[trim]))),
<<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,7}?(.)",[{parts,
- 2}]))),
- <<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,7}?(.)",[]))),
- <<":c:e">> = iolist_to_binary(join(re:split("ace","a(?:b|(c|e){1,2}?|d)+?(.)",[trim]))),
+ 2}]))),
+ <<":b:e">> = iolist_to_binary(join(re:split("acdbcdbe","a(?:b|c|d){5,7}?(.)",[]))),
+ <<":c:e">> = iolist_to_binary(join(re:split("ace","a(?:b|(c|e){1,2}?|d)+?(.)",[trim]))),
<<":c:e:">> = iolist_to_binary(join(re:split("ace","a(?:b|(c|e){1,2}?|d)+?(.)",[{parts,
- 2}]))),
- <<":c:e:">> = iolist_to_binary(join(re:split("ace","a(?:b|(c|e){1,2}?|d)+?(.)",[]))),
- <<":A">> = iolist_to_binary(join(re:split("AB","^(.+)?B",[trim]))),
+ 2}]))),
+ <<":c:e:">> = iolist_to_binary(join(re:split("ace","a(?:b|(c|e){1,2}?|d)+?(.)",[]))),
+ <<":A">> = iolist_to_binary(join(re:split("AB","^(.+)?B",[trim]))),
<<":A:">> = iolist_to_binary(join(re:split("AB","^(.+)?B",[{parts,
- 2}]))),
- <<":A:">> = iolist_to_binary(join(re:split("AB","^(.+)?B",[]))),
- <<":.">> = iolist_to_binary(join(re:split(".","^([^a-z])|(\\^)$",[trim]))),
+ 2}]))),
+ <<":A:">> = iolist_to_binary(join(re:split("AB","^(.+)?B",[]))),
+ <<":.">> = iolist_to_binary(join(re:split(".","^([^a-z])|(\\^)$",[trim]))),
<<":.::">> = iolist_to_binary(join(re:split(".","^([^a-z])|(\\^)$",[{parts,
- 2}]))),
- <<":.::">> = iolist_to_binary(join(re:split(".","^([^a-z])|(\\^)$",[]))),
- <<":OUT">> = iolist_to_binary(join(re:split("<&OUT","^[<>]&",[trim]))),
+ 2}]))),
+ <<":.::">> = iolist_to_binary(join(re:split(".","^([^a-z])|(\\^)$",[]))),
+ <<":OUT">> = iolist_to_binary(join(re:split("<&OUT","^[<>]&",[trim]))),
<<":OUT">> = iolist_to_binary(join(re:split("<&OUT","^[<>]&",[{parts,
- 2}]))),
- <<":OUT">> = iolist_to_binary(join(re:split("<&OUT","^[<>]&",[]))),
- <<":aaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<":OUT">> = iolist_to_binary(join(re:split("<&OUT","^[<>]&",[]))),
+ <<":aaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?){4}$",[trim]))),
<<":aaaa:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<":aaaa:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?){4}$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<":aaaa:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a\\1?){4}$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a\\1?){4}$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a\\1?){4}$",[]))),
- <<"AB">> = iolist_to_binary(join(re:split("AB","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a\\1?){4}$",[]))),
+ <<"AB">> = iolist_to_binary(join(re:split("AB","^(a\\1?){4}$",[trim]))),
<<"AB">> = iolist_to_binary(join(re:split("AB","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"AB">> = iolist_to_binary(join(re:split("AB","^(a\\1?){4}$",[]))),
- <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"AB">> = iolist_to_binary(join(re:split("AB","^(a\\1?){4}$",[]))),
+ <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?){4}$",[trim]))),
<<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?){4}$",[]))),
- <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a\\1?){4}$",[]))),
+ <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?){4}$",[trim]))),
<<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?){4}$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?){4}$",[]))),
- <<":aaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a(?(1)\\1)){4}$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a\\1?){4}$",[]))),
+ <<":aaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a(?(1)\\1)){4}$",[trim]))),
<<":aaaa:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a(?(1)\\1)){4}$",[{parts,
- 2}]))),
- <<":aaaa:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a(?(1)\\1)){4}$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a(?(1)\\1)){4}$",[trim]))),
+ 2}]))),
+ <<":aaaa:">> = iolist_to_binary(join(re:split("aaaaaaaaaa","^(a(?(1)\\1)){4}$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a(?(1)\\1)){4}$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a(?(1)\\1)){4}$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a(?(1)\\1)){4}$",[]))),
- <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a(?(1)\\1)){4}$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a(?(1)\\1)){4}$",[]))),
+ <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a(?(1)\\1)){4}$",[trim]))),
<<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a(?(1)\\1)){4}$",[{parts,
- 2}]))),
- <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a(?(1)\\1)){4}$",[]))),
- <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a(?(1)\\1)){4}$",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a(?(1)\\1)){4}$",[]))),
+ <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a(?(1)\\1)){4}$",[trim]))),
<<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a(?(1)\\1)){4}$",[{parts,
- 2}]))),
- <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a(?(1)\\1)){4}$",[]))),
- <<":f:o:o:b:a:r">> = iolist_to_binary(join(re:split("foobar","(?:(f)(o)(o)|(b)(a)(r))*",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaa","^(a(?(1)\\1)){4}$",[]))),
+ <<":f:o:o:b:a:r">> = iolist_to_binary(join(re:split("foobar","(?:(f)(o)(o)|(b)(a)(r))*",[trim]))),
<<":f:o:o:b:a:r:">> = iolist_to_binary(join(re:split("foobar","(?:(f)(o)(o)|(b)(a)(r))*",[{parts,
- 2}]))),
- <<":f:o:o:b:a:r:">> = iolist_to_binary(join(re:split("foobar","(?:(f)(o)(o)|(b)(a)(r))*",[]))),
- <<"a">> = iolist_to_binary(join(re:split("ab","(?<=a)b",[trim]))),
+ 2}]))),
+ <<":f:o:o:b:a:r:">> = iolist_to_binary(join(re:split("foobar","(?:(f)(o)(o)|(b)(a)(r))*",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("ab","(?<=a)b",[trim]))),
<<"a:">> = iolist_to_binary(join(re:split("ab","(?<=a)b",[{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("ab","(?<=a)b",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=a)b",[trim]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("ab","(?<=a)b",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=a)b",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=a)b",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=a)b",[]))),
- <<"cb">> = iolist_to_binary(join(re:split("cb","(?<=a)b",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=a)b",[]))),
+ <<"cb">> = iolist_to_binary(join(re:split("cb","(?<=a)b",[trim]))),
<<"cb">> = iolist_to_binary(join(re:split("cb","(?<=a)b",[{parts,
- 2}]))),
- <<"cb">> = iolist_to_binary(join(re:split("cb","(?<=a)b",[]))),
- <<"b">> = iolist_to_binary(join(re:split("b","(?<=a)b",[trim]))),
+ 2}]))),
+ <<"cb">> = iolist_to_binary(join(re:split("cb","(?<=a)b",[]))),
+ <<"b">> = iolist_to_binary(join(re:split("b","(?<=a)b",[trim]))),
<<"b">> = iolist_to_binary(join(re:split("b","(?<=a)b",[{parts,
- 2}]))),
- <<"b">> = iolist_to_binary(join(re:split("b","(?<=a)b",[]))),
- <<"a">> = iolist_to_binary(join(re:split("ab","(?<!c)b",[trim]))),
+ 2}]))),
+ <<"b">> = iolist_to_binary(join(re:split("b","(?<=a)b",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("ab","(?<!c)b",[trim]))),
<<"a:">> = iolist_to_binary(join(re:split("ab","(?<!c)b",[{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("ab","(?<!c)b",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","(?<!c)b",[trim]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("ab","(?<!c)b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","(?<!c)b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("b","(?<!c)b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("b","(?<!c)b",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","(?<!c)b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("b","(?<!c)b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","(?<!c)b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("b","(?<!c)b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("b","(?<!c)b",[]))),
- <<"">> = iolist_to_binary(join(re:split("aba","(?:..)*a",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("b","(?<!c)b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aba","(?:..)*a",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aba","(?:..)*a",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aba","(?:..)*a",[]))),
- <<":b">> = iolist_to_binary(join(re:split("aba","(?:..)*?a",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aba","(?:..)*a",[]))),
+ <<":b">> = iolist_to_binary(join(re:split("aba","(?:..)*?a",[trim]))),
<<":ba">> = iolist_to_binary(join(re:split("aba","(?:..)*?a",[{parts,
- 2}]))),
- <<":b:">> = iolist_to_binary(join(re:split("aba","(?:..)*?a",[]))),
- <<":b:c">> = iolist_to_binary(join(re:split("abc","^(?:b|a(?=(.)))*\\1",[trim]))),
+ 2}]))),
+ <<":b:">> = iolist_to_binary(join(re:split("aba","(?:..)*?a",[]))),
+ <<":b:c">> = iolist_to_binary(join(re:split("abc","^(?:b|a(?=(.)))*\\1",[trim]))),
<<":b:c">> = iolist_to_binary(join(re:split("abc","^(?:b|a(?=(.)))*\\1",[{parts,
- 2}]))),
- <<":b:c">> = iolist_to_binary(join(re:split("abc","^(?:b|a(?=(.)))*\\1",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^(){3,5}",[trim]))),
+ 2}]))),
+ <<":b:c">> = iolist_to_binary(join(re:split("abc","^(?:b|a(?=(.)))*\\1",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^(){3,5}",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","^(){3,5}",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^(){3,5}",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aax","^(a+)*ax",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^(){3,5}",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aax","^(a+)*ax",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aax","^(a+)*ax",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aax","^(a+)*ax",[]))),
- <<":a:a">> = iolist_to_binary(join(re:split("aax","^((a|b)+)*ax",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aax","^(a+)*ax",[]))),
+ <<":a:a">> = iolist_to_binary(join(re:split("aax","^((a|b)+)*ax",[trim]))),
<<":a:a:">> = iolist_to_binary(join(re:split("aax","^((a|b)+)*ax",[{parts,
- 2}]))),
- <<":a:a:">> = iolist_to_binary(join(re:split("aax","^((a|b)+)*ax",[]))),
- <<":a:a">> = iolist_to_binary(join(re:split("aax","^((a|bc)+)*ax",[trim]))),
+ 2}]))),
+ <<":a:a:">> = iolist_to_binary(join(re:split("aax","^((a|b)+)*ax",[]))),
+ <<":a:a">> = iolist_to_binary(join(re:split("aax","^((a|bc)+)*ax",[trim]))),
<<":a:a:">> = iolist_to_binary(join(re:split("aax","^((a|bc)+)*ax",[{parts,
- 2}]))),
- <<":a:a:">> = iolist_to_binary(join(re:split("aax","^((a|bc)+)*ax",[]))),
- <<"c">> = iolist_to_binary(join(re:split("cab","(a|x)*ab",[trim]))),
+ 2}]))),
+ <<":a:a:">> = iolist_to_binary(join(re:split("aax","^((a|bc)+)*ax",[]))),
+ <<"c">> = iolist_to_binary(join(re:split("cab","(a|x)*ab",[trim]))),
<<"c::">> = iolist_to_binary(join(re:split("cab","(a|x)*ab",[{parts,
- 2}]))),
- <<"c::">> = iolist_to_binary(join(re:split("cab","(a|x)*ab",[]))),
- <<"c">> = iolist_to_binary(join(re:split("cab","(a)*ab",[trim]))),
+ 2}]))),
+ <<"c::">> = iolist_to_binary(join(re:split("cab","(a|x)*ab",[]))),
+ <<"c">> = iolist_to_binary(join(re:split("cab","(a)*ab",[trim]))),
<<"c::">> = iolist_to_binary(join(re:split("cab","(a)*ab",[{parts,
- 2}]))),
- <<"c::">> = iolist_to_binary(join(re:split("cab","(a)*ab",[]))),
+ 2}]))),
+ <<"c::">> = iolist_to_binary(join(re:split("cab","(a)*ab",[]))),
ok.
run27() ->
- <<"">> = iolist_to_binary(join(re:split("ab","(?:(?i)a)b",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("ab","(?:(?i)a)b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ab","(?:(?i)a)b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab","(?:(?i)a)b",[]))),
- <<":a">> = iolist_to_binary(join(re:split("ab","((?i)a)b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab","(?:(?i)a)b",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("ab","((?i)a)b",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("ab","((?i)a)b",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("ab","((?i)a)b",[]))),
- <<"">> = iolist_to_binary(join(re:split("Ab","(?:(?i)a)b",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("ab","((?i)a)b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("Ab","(?:(?i)a)b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("Ab","(?:(?i)a)b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("Ab","(?:(?i)a)b",[]))),
- <<":A">> = iolist_to_binary(join(re:split("Ab","((?i)a)b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("Ab","(?:(?i)a)b",[]))),
+ <<":A">> = iolist_to_binary(join(re:split("Ab","((?i)a)b",[trim]))),
<<":A:">> = iolist_to_binary(join(re:split("Ab","((?i)a)b",[{parts,
- 2}]))),
- <<":A:">> = iolist_to_binary(join(re:split("Ab","((?i)a)b",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?i)a)b",[trim]))),
+ 2}]))),
+ <<":A:">> = iolist_to_binary(join(re:split("Ab","((?i)a)b",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?i)a)b",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?i)a)b",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?i)a)b",[]))),
- <<"cb">> = iolist_to_binary(join(re:split("cb","(?:(?i)a)b",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?i)a)b",[]))),
+ <<"cb">> = iolist_to_binary(join(re:split("cb","(?:(?i)a)b",[trim]))),
<<"cb">> = iolist_to_binary(join(re:split("cb","(?:(?i)a)b",[{parts,
- 2}]))),
- <<"cb">> = iolist_to_binary(join(re:split("cb","(?:(?i)a)b",[]))),
- <<"aB">> = iolist_to_binary(join(re:split("aB","(?:(?i)a)b",[trim]))),
+ 2}]))),
+ <<"cb">> = iolist_to_binary(join(re:split("cb","(?:(?i)a)b",[]))),
+ <<"aB">> = iolist_to_binary(join(re:split("aB","(?:(?i)a)b",[trim]))),
<<"aB">> = iolist_to_binary(join(re:split("aB","(?:(?i)a)b",[{parts,
- 2}]))),
- <<"aB">> = iolist_to_binary(join(re:split("aB","(?:(?i)a)b",[]))),
- <<"">> = iolist_to_binary(join(re:split("ab","(?i:a)b",[trim]))),
+ 2}]))),
+ <<"aB">> = iolist_to_binary(join(re:split("aB","(?:(?i)a)b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ab","(?i:a)b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ab","(?i:a)b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab","(?i:a)b",[]))),
- <<":a">> = iolist_to_binary(join(re:split("ab","((?i:a))b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab","(?i:a)b",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("ab","((?i:a))b",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("ab","((?i:a))b",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("ab","((?i:a))b",[]))),
- <<"">> = iolist_to_binary(join(re:split("Ab","(?i:a)b",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("ab","((?i:a))b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("Ab","(?i:a)b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("Ab","(?i:a)b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("Ab","(?i:a)b",[]))),
- <<":A">> = iolist_to_binary(join(re:split("Ab","((?i:a))b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("Ab","(?i:a)b",[]))),
+ <<":A">> = iolist_to_binary(join(re:split("Ab","((?i:a))b",[trim]))),
<<":A:">> = iolist_to_binary(join(re:split("Ab","((?i:a))b",[{parts,
- 2}]))),
- <<":A:">> = iolist_to_binary(join(re:split("Ab","((?i:a))b",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?i:a)b",[trim]))),
+ 2}]))),
+ <<":A:">> = iolist_to_binary(join(re:split("Ab","((?i:a))b",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?i:a)b",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?i:a)b",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?i:a)b",[]))),
- <<"aB">> = iolist_to_binary(join(re:split("aB","(?i:a)b",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?i:a)b",[]))),
+ <<"aB">> = iolist_to_binary(join(re:split("aB","(?i:a)b",[trim]))),
<<"aB">> = iolist_to_binary(join(re:split("aB","(?i:a)b",[{parts,
- 2}]))),
- <<"aB">> = iolist_to_binary(join(re:split("aB","(?i:a)b",[]))),
- <<"aB">> = iolist_to_binary(join(re:split("aB","(?i:a)b",[trim]))),
+ 2}]))),
+ <<"aB">> = iolist_to_binary(join(re:split("aB","(?i:a)b",[]))),
+ <<"aB">> = iolist_to_binary(join(re:split("aB","(?i:a)b",[trim]))),
<<"aB">> = iolist_to_binary(join(re:split("aB","(?i:a)b",[{parts,
- 2}]))),
- <<"aB">> = iolist_to_binary(join(re:split("aB","(?i:a)b",[]))),
+ 2}]))),
+ <<"aB">> = iolist_to_binary(join(re:split("aB","(?i:a)b",[]))),
<<"">> = iolist_to_binary(join(re:split("ab","(?:(?-i)a)b",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ab","(?:(?-i)a)b",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab","(?:(?-i)a)b",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab","(?:(?-i)a)b",[caseless]))),
<<":a">> = iolist_to_binary(join(re:split("ab","((?-i)a)b",[caseless,
- trim]))),
+ trim]))),
<<":a:">> = iolist_to_binary(join(re:split("ab","((?-i)a)b",[caseless,
{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("ab","((?-i)a)b",[caseless]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("ab","((?-i)a)b",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("aB","(?:(?-i)a)b",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aB","(?:(?-i)a)b",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aB","(?:(?-i)a)b",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aB","(?:(?-i)a)b",[caseless]))),
<<":a">> = iolist_to_binary(join(re:split("aB","((?-i)a)b",[caseless,
- trim]))),
+ trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aB","((?-i)a)b",[caseless,
{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aB","((?-i)a)b",[caseless]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aB","((?-i)a)b",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?-i)a)b",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?-i)a)b",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?-i)a)b",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?-i)a)b",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("aB","(?:(?-i)a)b",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aB","(?:(?-i)a)b",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aB","(?:(?-i)a)b",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aB","(?:(?-i)a)b",[caseless]))),
<<"Ab">> = iolist_to_binary(join(re:split("Ab","(?:(?-i)a)b",[caseless,
- trim]))),
+ trim]))),
<<"Ab">> = iolist_to_binary(join(re:split("Ab","(?:(?-i)a)b",[caseless,
{parts,
- 2}]))),
- <<"Ab">> = iolist_to_binary(join(re:split("Ab","(?:(?-i)a)b",[caseless]))),
+ 2}]))),
+ <<"Ab">> = iolist_to_binary(join(re:split("Ab","(?:(?-i)a)b",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("aB","(?:(?-i)a)b",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aB","(?:(?-i)a)b",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aB","(?:(?-i)a)b",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aB","(?:(?-i)a)b",[caseless]))),
<<":a">> = iolist_to_binary(join(re:split("aB","((?-i)a)b",[caseless,
- trim]))),
+ trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aB","((?-i)a)b",[caseless,
{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aB","((?-i)a)b",[caseless]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aB","((?-i)a)b",[caseless]))),
ok.
run28() ->
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?-i)a)b",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?-i)a)b",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?-i)a)b",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?:(?-i)a)b",[caseless]))),
<<"Ab">> = iolist_to_binary(join(re:split("Ab","(?:(?-i)a)b",[caseless,
- trim]))),
+ trim]))),
<<"Ab">> = iolist_to_binary(join(re:split("Ab","(?:(?-i)a)b",[caseless,
{parts,
- 2}]))),
- <<"Ab">> = iolist_to_binary(join(re:split("Ab","(?:(?-i)a)b",[caseless]))),
+ 2}]))),
+ <<"Ab">> = iolist_to_binary(join(re:split("Ab","(?:(?-i)a)b",[caseless]))),
<<"AB">> = iolist_to_binary(join(re:split("AB","(?:(?-i)a)b",[caseless,
- trim]))),
+ trim]))),
<<"AB">> = iolist_to_binary(join(re:split("AB","(?:(?-i)a)b",[caseless,
{parts,
- 2}]))),
- <<"AB">> = iolist_to_binary(join(re:split("AB","(?:(?-i)a)b",[caseless]))),
+ 2}]))),
+ <<"AB">> = iolist_to_binary(join(re:split("AB","(?:(?-i)a)b",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("ab","(?-i:a)b",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ab","(?-i:a)b",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab","(?-i:a)b",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab","(?-i:a)b",[caseless]))),
<<":a">> = iolist_to_binary(join(re:split("ab","((?-i:a))b",[caseless,
- trim]))),
+ trim]))),
<<":a:">> = iolist_to_binary(join(re:split("ab","((?-i:a))b",[caseless,
{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("ab","((?-i:a))b",[caseless]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("ab","((?-i:a))b",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("aB","(?-i:a)b",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aB","(?-i:a)b",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aB","(?-i:a)b",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aB","(?-i:a)b",[caseless]))),
<<":a">> = iolist_to_binary(join(re:split("aB","((?-i:a))b",[caseless,
- trim]))),
+ trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aB","((?-i:a))b",[caseless,
{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aB","((?-i:a))b",[caseless]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aB","((?-i:a))b",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?-i:a)b",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?-i:a)b",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?-i:a)b",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?-i:a)b",[caseless]))),
<<"AB">> = iolist_to_binary(join(re:split("AB","(?-i:a)b",[caseless,
- trim]))),
+ trim]))),
<<"AB">> = iolist_to_binary(join(re:split("AB","(?-i:a)b",[caseless,
{parts,
- 2}]))),
- <<"AB">> = iolist_to_binary(join(re:split("AB","(?-i:a)b",[caseless]))),
+ 2}]))),
+ <<"AB">> = iolist_to_binary(join(re:split("AB","(?-i:a)b",[caseless]))),
<<"Ab">> = iolist_to_binary(join(re:split("Ab","(?-i:a)b",[caseless,
- trim]))),
+ trim]))),
<<"Ab">> = iolist_to_binary(join(re:split("Ab","(?-i:a)b",[caseless,
{parts,
- 2}]))),
- <<"Ab">> = iolist_to_binary(join(re:split("Ab","(?-i:a)b",[caseless]))),
+ 2}]))),
+ <<"Ab">> = iolist_to_binary(join(re:split("Ab","(?-i:a)b",[caseless]))),
<<"">> = iolist_to_binary(join(re:split("aB","(?-i:a)b",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aB","(?-i:a)b",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aB","(?-i:a)b",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aB","(?-i:a)b",[caseless]))),
<<":a">> = iolist_to_binary(join(re:split("aB","((?-i:a))b",[caseless,
- trim]))),
+ trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aB","((?-i:a))b",[caseless,
{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aB","((?-i:a))b",[caseless]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aB","((?-i:a))b",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?-i:a)b",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?-i:a)b",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?-i:a)b",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?-i:a)b",[caseless]))),
<<"Ab">> = iolist_to_binary(join(re:split("Ab","(?-i:a)b",[caseless,
- trim]))),
+ trim]))),
<<"Ab">> = iolist_to_binary(join(re:split("Ab","(?-i:a)b",[caseless,
{parts,
- 2}]))),
- <<"Ab">> = iolist_to_binary(join(re:split("Ab","(?-i:a)b",[caseless]))),
+ 2}]))),
+ <<"Ab">> = iolist_to_binary(join(re:split("Ab","(?-i:a)b",[caseless]))),
<<"AB">> = iolist_to_binary(join(re:split("AB","(?-i:a)b",[caseless,
- trim]))),
+ trim]))),
<<"AB">> = iolist_to_binary(join(re:split("AB","(?-i:a)b",[caseless,
{parts,
- 2}]))),
- <<"AB">> = iolist_to_binary(join(re:split("AB","(?-i:a)b",[caseless]))),
+ 2}]))),
+ <<"AB">> = iolist_to_binary(join(re:split("AB","(?-i:a)b",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?-i:a.))b",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?-i:a.))b",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?-i:a.))b",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?-i:a.))b",[caseless]))),
<<"AB">> = iolist_to_binary(join(re:split("AB","((?-i:a.))b",[caseless,
- trim]))),
+ trim]))),
<<"AB">> = iolist_to_binary(join(re:split("AB","((?-i:a.))b",[caseless,
{parts,
- 2}]))),
- <<"AB">> = iolist_to_binary(join(re:split("AB","((?-i:a.))b",[caseless]))),
+ 2}]))),
+ <<"AB">> = iolist_to_binary(join(re:split("AB","((?-i:a.))b",[caseless]))),
<<"a
B">> = iolist_to_binary(join(re:split("a
-B","((?-i:a.))b",[caseless,trim]))),
+B","((?-i:a.))b",[caseless,trim]))),
<<"a
B">> = iolist_to_binary(join(re:split("a
-B","((?-i:a.))b",[caseless,{parts,2}]))),
+B","((?-i:a.))b",[caseless,{parts,2}]))),
<<"a
B">> = iolist_to_binary(join(re:split("a
-B","((?-i:a.))b",[caseless]))),
+B","((?-i:a.))b",[caseless]))),
<<":a
">> = iolist_to_binary(join(re:split("a
-B","((?s-i:a.))b",[caseless,trim]))),
+B","((?s-i:a.))b",[caseless,trim]))),
<<":a
:">> = iolist_to_binary(join(re:split("a
-B","((?s-i:a.))b",[caseless,{parts,2}]))),
+B","((?s-i:a.))b",[caseless,{parts,2}]))),
<<":a
:">> = iolist_to_binary(join(re:split("a
-B","((?s-i:a.))b",[caseless]))),
- <<"">> = iolist_to_binary(join(re:split("cabbbb","(?:c|d)(?:)(?:a(?:)(?:b)(?:b(?:))(?:b(?:)(?:b)))",[trim]))),
+B","((?s-i:a.))b",[caseless]))),
+ <<"">> = iolist_to_binary(join(re:split("cabbbb","(?:c|d)(?:)(?:a(?:)(?:b)(?:b(?:))(?:b(?:)(?:b)))",[trim]))),
<<":">> = iolist_to_binary(join(re:split("cabbbb","(?:c|d)(?:)(?:a(?:)(?:b)(?:b(?:))(?:b(?:)(?:b)))",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("cabbbb","(?:c|d)(?:)(?:a(?:)(?:b)(?:b(?:))(?:b(?:)(?:b)))",[]))),
- <<"">> = iolist_to_binary(join(re:split("caaaaaaaabbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb","(?:c|d)(?:)(?:aaaaaaaa(?:)(?:bbbbbbbb)(?:bbbbbbbb(?:))(?:bbbbbbbb(?:)(?:bbbbbbbb)))",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("cabbbb","(?:c|d)(?:)(?:a(?:)(?:b)(?:b(?:))(?:b(?:)(?:b)))",[]))),
+ <<"">> = iolist_to_binary(join(re:split("caaaaaaaabbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb","(?:c|d)(?:)(?:aaaaaaaa(?:)(?:bbbbbbbb)(?:bbbbbbbb(?:))(?:bbbbbbbb(?:)(?:bbbbbbbb)))",[trim]))),
<<":">> = iolist_to_binary(join(re:split("caaaaaaaabbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb","(?:c|d)(?:)(?:aaaaaaaa(?:)(?:bbbbbbbb)(?:bbbbbbbb(?:))(?:bbbbbbbb(?:)(?:bbbbbbbb)))",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("caaaaaaaabbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb","(?:c|d)(?:)(?:aaaaaaaa(?:)(?:bbbbbbbb)(?:bbbbbbbb(?:))(?:bbbbbbbb(?:)(?:bbbbbbbb)))",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("caaaaaaaabbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb","(?:c|d)(?:)(?:aaaaaaaa(?:)(?:bbbbbbbb)(?:bbbbbbbb(?:))(?:bbbbbbbb(?:)(?:bbbbbbbb)))",[]))),
<<":Ab">> = iolist_to_binary(join(re:split("Ab4ab","(ab)\\d\\1",[caseless,
- trim]))),
+ trim]))),
<<":Ab:">> = iolist_to_binary(join(re:split("Ab4ab","(ab)\\d\\1",[caseless,
{parts,
- 2}]))),
- <<":Ab:">> = iolist_to_binary(join(re:split("Ab4ab","(ab)\\d\\1",[caseless]))),
+ 2}]))),
+ <<":Ab:">> = iolist_to_binary(join(re:split("Ab4ab","(ab)\\d\\1",[caseless]))),
<<":ab">> = iolist_to_binary(join(re:split("ab4Ab","(ab)\\d\\1",[caseless,
- trim]))),
+ trim]))),
<<":ab:">> = iolist_to_binary(join(re:split("ab4Ab","(ab)\\d\\1",[caseless,
{parts,
- 2}]))),
- <<":ab:">> = iolist_to_binary(join(re:split("ab4Ab","(ab)\\d\\1",[caseless]))),
- <<"">> = iolist_to_binary(join(re:split("foobar1234baz","foo\\w*\\d{4}baz",[trim]))),
+ 2}]))),
+ <<":ab:">> = iolist_to_binary(join(re:split("ab4Ab","(ab)\\d\\1",[caseless]))),
+ <<"">> = iolist_to_binary(join(re:split("foobar1234baz","foo\\w*\\d{4}baz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("foobar1234baz","foo\\w*\\d{4}baz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("foobar1234baz","foo\\w*\\d{4}baz",[]))),
- <<":~~">> = iolist_to_binary(join(re:split("x~~","x(~~)*(?:(?:F)?)?",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("foobar1234baz","foo\\w*\\d{4}baz",[]))),
+ <<":~~">> = iolist_to_binary(join(re:split("x~~","x(~~)*(?:(?:F)?)?",[trim]))),
<<":~~:">> = iolist_to_binary(join(re:split("x~~","x(~~)*(?:(?:F)?)?",[{parts,
- 2}]))),
- <<":~~:">> = iolist_to_binary(join(re:split("x~~","x(~~)*(?:(?:F)?)?",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaac","^a(?#xxx){3}c",[trim]))),
+ 2}]))),
+ <<":~~:">> = iolist_to_binary(join(re:split("x~~","x(~~)*(?:(?:F)?)?",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaac","^a(?#xxx){3}c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaac","^a(?#xxx){3}c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaac","^a(?#xxx){3}c",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaac","^a(?#xxx){3}c",[]))),
ok.
run29() ->
<<"">> = iolist_to_binary(join(re:split("aaac","^a (?#xxx) (?#yyy) {3}c",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aaac","^a (?#xxx) (?#yyy) {3}c",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaac","^a (?#xxx) (?#yyy) {3}c",[extended]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<![cd])b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaac","^a (?#xxx) (?#yyy) {3}c",[extended]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<![cd])b",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<![cd])b",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<![cd])b",[]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<![cd])b",[]))),
<<"B
B">> = iolist_to_binary(join(re:split("B
-B","(?<![cd])b",[trim]))),
+B","(?<![cd])b",[trim]))),
<<"B
B">> = iolist_to_binary(join(re:split("B
-B","(?<![cd])b",[{parts,2}]))),
+B","(?<![cd])b",[{parts,2}]))),
<<"B
B">> = iolist_to_binary(join(re:split("B
-B","(?<![cd])b",[]))),
- <<"dbcb">> = iolist_to_binary(join(re:split("dbcb","(?<![cd])b",[trim]))),
+B","(?<![cd])b",[]))),
+ <<"dbcb">> = iolist_to_binary(join(re:split("dbcb","(?<![cd])b",[trim]))),
<<"dbcb">> = iolist_to_binary(join(re:split("dbcb","(?<![cd])b",[{parts,
- 2}]))),
- <<"dbcb">> = iolist_to_binary(join(re:split("dbcb","(?<![cd])b",[]))),
- <<"db::cb">> = iolist_to_binary(join(re:split("dbaacb","(?<![cd])[ab]",[trim]))),
+ 2}]))),
+ <<"dbcb">> = iolist_to_binary(join(re:split("dbcb","(?<![cd])b",[]))),
+ <<"db::cb">> = iolist_to_binary(join(re:split("dbaacb","(?<![cd])[ab]",[trim]))),
<<"db:acb">> = iolist_to_binary(join(re:split("dbaacb","(?<![cd])[ab]",[{parts,
- 2}]))),
- <<"db::cb">> = iolist_to_binary(join(re:split("dbaacb","(?<![cd])[ab]",[]))),
- <<"db::::cb">> = iolist_to_binary(join(re:split("dbaacb","(?<!(c|d))[ab]",[trim]))),
+ 2}]))),
+ <<"db::cb">> = iolist_to_binary(join(re:split("dbaacb","(?<![cd])[ab]",[]))),
+ <<"db::::cb">> = iolist_to_binary(join(re:split("dbaacb","(?<!(c|d))[ab]",[trim]))),
<<"db::acb">> = iolist_to_binary(join(re:split("dbaacb","(?<!(c|d))[ab]",[{parts,
- 2}]))),
- <<"db::::cb">> = iolist_to_binary(join(re:split("dbaacb","(?<!(c|d))[ab]",[]))),
- <<"cdacc">> = iolist_to_binary(join(re:split("cdaccb","(?<!cd)[ab]",[trim]))),
+ 2}]))),
+ <<"db::::cb">> = iolist_to_binary(join(re:split("dbaacb","(?<!(c|d))[ab]",[]))),
+ <<"cdacc">> = iolist_to_binary(join(re:split("cdaccb","(?<!cd)[ab]",[trim]))),
<<"cdacc:">> = iolist_to_binary(join(re:split("cdaccb","(?<!cd)[ab]",[{parts,
- 2}]))),
- <<"cdacc:">> = iolist_to_binary(join(re:split("cdaccb","(?<!cd)[ab]",[]))),
- <<"">> = iolist_to_binary(join(re:split("","^(?:a?b?)*$",[trim]))),
+ 2}]))),
+ <<"cdacc:">> = iolist_to_binary(join(re:split("cdaccb","(?<!cd)[ab]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("","^(?:a?b?)*$",[trim]))),
<<"">> = iolist_to_binary(join(re:split("","^(?:a?b?)*$",[{parts,
- 2}]))),
- <<"">> = iolist_to_binary(join(re:split("","^(?:a?b?)*$",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","^(?:a?b?)*$",[trim]))),
+ 2}]))),
+ <<"">> = iolist_to_binary(join(re:split("","^(?:a?b?)*$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","^(?:a?b?)*$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","^(?:a?b?)*$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","^(?:a?b?)*$",[]))),
- <<"">> = iolist_to_binary(join(re:split("ab","^(?:a?b?)*$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","^(?:a?b?)*$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ab","^(?:a?b?)*$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ab","^(?:a?b?)*$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab","^(?:a?b?)*$",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaa","^(?:a?b?)*$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab","^(?:a?b?)*$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaa","^(?:a?b?)*$",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaa","^(?:a?b?)*$",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaa","^(?:a?b?)*$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?:a?b?)*$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaa","^(?:a?b?)*$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?:a?b?)*$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?:a?b?)*$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?:a?b?)*$",[]))),
- <<"dbcb">> = iolist_to_binary(join(re:split("dbcb","^(?:a?b?)*$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?:a?b?)*$",[]))),
+ <<"dbcb">> = iolist_to_binary(join(re:split("dbcb","^(?:a?b?)*$",[trim]))),
<<"dbcb">> = iolist_to_binary(join(re:split("dbcb","^(?:a?b?)*$",[{parts,
- 2}]))),
- <<"dbcb">> = iolist_to_binary(join(re:split("dbcb","^(?:a?b?)*$",[]))),
- <<"a--">> = iolist_to_binary(join(re:split("a--","^(?:a?b?)*$",[trim]))),
+ 2}]))),
+ <<"dbcb">> = iolist_to_binary(join(re:split("dbcb","^(?:a?b?)*$",[]))),
+ <<"a--">> = iolist_to_binary(join(re:split("a--","^(?:a?b?)*$",[trim]))),
<<"a--">> = iolist_to_binary(join(re:split("a--","^(?:a?b?)*$",[{parts,
- 2}]))),
- <<"a--">> = iolist_to_binary(join(re:split("a--","^(?:a?b?)*$",[]))),
- <<"aa--">> = iolist_to_binary(join(re:split("aa--","^(?:a?b?)*$",[trim]))),
+ 2}]))),
+ <<"a--">> = iolist_to_binary(join(re:split("a--","^(?:a?b?)*$",[]))),
+ <<"aa--">> = iolist_to_binary(join(re:split("aa--","^(?:a?b?)*$",[trim]))),
<<"aa--">> = iolist_to_binary(join(re:split("aa--","^(?:a?b?)*$",[{parts,
- 2}]))),
- <<"aa--">> = iolist_to_binary(join(re:split("aa--","^(?:a?b?)*$",[]))),
+ 2}]))),
+ <<"aa--">> = iolist_to_binary(join(re:split("aa--","^(?:a?b?)*$",[]))),
<<":a
:
:b:
c">> = iolist_to_binary(join(re:split("a
b
-c","((?s)^a(.))((?m)^b$)",[trim]))),
+c","((?s)^a(.))((?m)^b$)",[trim]))),
<<":a
:
:b:
c">> = iolist_to_binary(join(re:split("a
b
-c","((?s)^a(.))((?m)^b$)",[{parts,2}]))),
+c","((?s)^a(.))((?m)^b$)",[{parts,2}]))),
<<":a
:
:b:
c">> = iolist_to_binary(join(re:split("a
b
-c","((?s)^a(.))((?m)^b$)",[]))),
+c","((?s)^a(.))((?m)^b$)",[]))),
<<"a
:b:
c">> = iolist_to_binary(join(re:split("a
b
-c","((?m)^b$)",[trim]))),
+c","((?m)^b$)",[trim]))),
<<"a
:b:
c">> = iolist_to_binary(join(re:split("a
b
-c","((?m)^b$)",[{parts,2}]))),
+c","((?m)^b$)",[{parts,2}]))),
<<"a
:b:
c">> = iolist_to_binary(join(re:split("a
b
-c","((?m)^b$)",[]))),
+c","((?m)^b$)",[]))),
<<"a
">> = iolist_to_binary(join(re:split("a
-b","(?m)^b",[trim]))),
+b","(?m)^b",[trim]))),
<<"a
:">> = iolist_to_binary(join(re:split("a
-b","(?m)^b",[{parts,2}]))),
+b","(?m)^b",[{parts,2}]))),
<<"a
:">> = iolist_to_binary(join(re:split("a
-b","(?m)^b",[]))),
+b","(?m)^b",[]))),
<<"a
:b">> = iolist_to_binary(join(re:split("a
-b","(?m)^(b)",[trim]))),
+b","(?m)^(b)",[trim]))),
<<"a
:b:">> = iolist_to_binary(join(re:split("a
-b","(?m)^(b)",[{parts,2}]))),
+b","(?m)^(b)",[{parts,2}]))),
<<"a
:b:">> = iolist_to_binary(join(re:split("a
-b","(?m)^(b)",[]))),
+b","(?m)^(b)",[]))),
<<"a
:b">> = iolist_to_binary(join(re:split("a
-b","((?m)^b)",[trim]))),
+b","((?m)^b)",[trim]))),
<<"a
:b:">> = iolist_to_binary(join(re:split("a
-b","((?m)^b)",[{parts,2}]))),
+b","((?m)^b)",[{parts,2}]))),
<<"a
:b:">> = iolist_to_binary(join(re:split("a
-b","((?m)^b)",[]))),
+b","((?m)^b)",[]))),
<<"a:b">> = iolist_to_binary(join(re:split("a
-b","\\n((?m)^b)",[trim]))),
+b","\\n((?m)^b)",[trim]))),
<<"a:b:">> = iolist_to_binary(join(re:split("a
-b","\\n((?m)^b)",[{parts,2}]))),
+b","\\n((?m)^b)",[{parts,2}]))),
<<"a:b:">> = iolist_to_binary(join(re:split("a
-b","\\n((?m)^b)",[]))),
+b","\\n((?m)^b)",[]))),
<<"a
b:
">> = iolist_to_binary(join(re:split("a
b
-c","((?s).)c(?!.)",[trim]))),
+c","((?s).)c(?!.)",[trim]))),
<<"a
b:
:">> = iolist_to_binary(join(re:split("a
b
-c","((?s).)c(?!.)",[{parts,2}]))),
+c","((?s).)c(?!.)",[{parts,2}]))),
<<"a
b:
:">> = iolist_to_binary(join(re:split("a
b
-c","((?s).)c(?!.)",[]))),
+c","((?s).)c(?!.)",[]))),
<<"a
b:
">> = iolist_to_binary(join(re:split("a
b
-c","((?s).)c(?!.)",[trim]))),
+c","((?s).)c(?!.)",[trim]))),
<<"a
b:
:">> = iolist_to_binary(join(re:split("a
b
-c","((?s).)c(?!.)",[{parts,2}]))),
+c","((?s).)c(?!.)",[{parts,2}]))),
<<"a
b:
:">> = iolist_to_binary(join(re:split("a
b
-c","((?s).)c(?!.)",[]))),
+c","((?s).)c(?!.)",[]))),
<<"a
:b
">> = iolist_to_binary(join(re:split("a
b
-c","((?s)b.)c(?!.)",[trim]))),
+c","((?s)b.)c(?!.)",[trim]))),
<<"a
:b
:">> = iolist_to_binary(join(re:split("a
b
-c","((?s)b.)c(?!.)",[{parts,2}]))),
+c","((?s)b.)c(?!.)",[{parts,2}]))),
<<"a
:b
:">> = iolist_to_binary(join(re:split("a
b
-c","((?s)b.)c(?!.)",[]))),
+c","((?s)b.)c(?!.)",[]))),
<<"a
:b
">> = iolist_to_binary(join(re:split("a
b
-c","((?s)b.)c(?!.)",[trim]))),
+c","((?s)b.)c(?!.)",[trim]))),
<<"a
:b
:">> = iolist_to_binary(join(re:split("a
b
-c","((?s)b.)c(?!.)",[{parts,2}]))),
+c","((?s)b.)c(?!.)",[{parts,2}]))),
<<"a
:b
:">> = iolist_to_binary(join(re:split("a
b
-c","((?s)b.)c(?!.)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","()^b",[trim]))),
+c","((?s)b.)c(?!.)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","()^b",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","()^b",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","()^b",[]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","()^b",[]))),
<<"a
b
c">> = iolist_to_binary(join(re:split("a
b
-c","()^b",[trim]))),
+c","()^b",[trim]))),
<<"a
b
c">> = iolist_to_binary(join(re:split("a
b
-c","()^b",[{parts,2}]))),
+c","()^b",[{parts,2}]))),
<<"a
b
c">> = iolist_to_binary(join(re:split("a
b
-c","()^b",[]))),
+c","()^b",[]))),
<<"a
b
c">> = iolist_to_binary(join(re:split("a
b
-c","()^b",[trim]))),
+c","()^b",[trim]))),
<<"a
b
c">> = iolist_to_binary(join(re:split("a
b
-c","()^b",[{parts,2}]))),
+c","()^b",[{parts,2}]))),
<<"a
b
c">> = iolist_to_binary(join(re:split("a
b
-c","()^b",[]))),
+c","()^b",[]))),
<<"a
:b:
c">> = iolist_to_binary(join(re:split("a
b
-c","((?m)^b)",[trim]))),
+c","((?m)^b)",[trim]))),
<<"a
:b:
c">> = iolist_to_binary(join(re:split("a
b
-c","((?m)^b)",[{parts,2}]))),
+c","((?m)^b)",[{parts,2}]))),
<<"a
:b:
c">> = iolist_to_binary(join(re:split("a
b
-c","((?m)^b)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(x)?(?(1)a|b)",[trim]))),
+c","((?m)^b)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(x)?(?(1)a|b)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(x)?(?(1)a|b)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(x)?(?(1)a|b)",[]))),
- <<"a">> = iolist_to_binary(join(re:split("a","(x)?(?(1)a|b)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(x)?(?(1)a|b)",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","(x)?(?(1)a|b)",[trim]))),
<<"a">> = iolist_to_binary(join(re:split("a","(x)?(?(1)a|b)",[{parts,
- 2}]))),
- <<"a">> = iolist_to_binary(join(re:split("a","(x)?(?(1)a|b)",[]))),
- <<"a">> = iolist_to_binary(join(re:split("a","(x)?(?(1)a|b)",[trim]))),
+ 2}]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","(x)?(?(1)a|b)",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","(x)?(?(1)a|b)",[trim]))),
<<"a">> = iolist_to_binary(join(re:split("a","(x)?(?(1)a|b)",[{parts,
- 2}]))),
- <<"a">> = iolist_to_binary(join(re:split("a","(x)?(?(1)a|b)",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","(x)?(?(1)b|a)",[trim]))),
+ 2}]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","(x)?(?(1)a|b)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","(x)?(?(1)b|a)",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a","(x)?(?(1)b|a)",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a","(x)?(?(1)b|a)",[]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a","(x)?(?(1)b|a)",[]))),
ok.
run30() ->
- <<"">> = iolist_to_binary(join(re:split("a","()?(?(1)b|a)",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("a","()?(?(1)b|a)",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a","()?(?(1)b|a)",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a","()?(?(1)b|a)",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","()?(?(1)a|b)",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a","()?(?(1)b|a)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","()?(?(1)a|b)",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a","()?(?(1)a|b)",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a","()?(?(1)a|b)",[]))),
- <<":(:)">> = iolist_to_binary(join(re:split("(blah)","^(\\()?blah(?(1)(\\)))$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a","()?(?(1)a|b)",[]))),
+ <<":(:)">> = iolist_to_binary(join(re:split("(blah)","^(\\()?blah(?(1)(\\)))$",[trim]))),
<<":(:):">> = iolist_to_binary(join(re:split("(blah)","^(\\()?blah(?(1)(\\)))$",[{parts,
- 2}]))),
- <<":(:):">> = iolist_to_binary(join(re:split("(blah)","^(\\()?blah(?(1)(\\)))$",[]))),
- <<"">> = iolist_to_binary(join(re:split("blah","^(\\()?blah(?(1)(\\)))$",[trim]))),
+ 2}]))),
+ <<":(:):">> = iolist_to_binary(join(re:split("(blah)","^(\\()?blah(?(1)(\\)))$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("blah","^(\\()?blah(?(1)(\\)))$",[trim]))),
<<":::">> = iolist_to_binary(join(re:split("blah","^(\\()?blah(?(1)(\\)))$",[{parts,
- 2}]))),
- <<":::">> = iolist_to_binary(join(re:split("blah","^(\\()?blah(?(1)(\\)))$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\()?blah(?(1)(\\)))$",[trim]))),
+ 2}]))),
+ <<":::">> = iolist_to_binary(join(re:split("blah","^(\\()?blah(?(1)(\\)))$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\()?blah(?(1)(\\)))$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\()?blah(?(1)(\\)))$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\()?blah(?(1)(\\)))$",[]))),
- <<"a">> = iolist_to_binary(join(re:split("a","^(\\()?blah(?(1)(\\)))$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\()?blah(?(1)(\\)))$",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","^(\\()?blah(?(1)(\\)))$",[trim]))),
<<"a">> = iolist_to_binary(join(re:split("a","^(\\()?blah(?(1)(\\)))$",[{parts,
- 2}]))),
- <<"a">> = iolist_to_binary(join(re:split("a","^(\\()?blah(?(1)(\\)))$",[]))),
- <<"blah)">> = iolist_to_binary(join(re:split("blah)","^(\\()?blah(?(1)(\\)))$",[trim]))),
+ 2}]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","^(\\()?blah(?(1)(\\)))$",[]))),
+ <<"blah)">> = iolist_to_binary(join(re:split("blah)","^(\\()?blah(?(1)(\\)))$",[trim]))),
<<"blah)">> = iolist_to_binary(join(re:split("blah)","^(\\()?blah(?(1)(\\)))$",[{parts,
- 2}]))),
- <<"blah)">> = iolist_to_binary(join(re:split("blah)","^(\\()?blah(?(1)(\\)))$",[]))),
- <<"(blah">> = iolist_to_binary(join(re:split("(blah","^(\\()?blah(?(1)(\\)))$",[trim]))),
+ 2}]))),
+ <<"blah)">> = iolist_to_binary(join(re:split("blah)","^(\\()?blah(?(1)(\\)))$",[]))),
+ <<"(blah">> = iolist_to_binary(join(re:split("(blah","^(\\()?blah(?(1)(\\)))$",[trim]))),
<<"(blah">> = iolist_to_binary(join(re:split("(blah","^(\\()?blah(?(1)(\\)))$",[{parts,
- 2}]))),
- <<"(blah">> = iolist_to_binary(join(re:split("(blah","^(\\()?blah(?(1)(\\)))$",[]))),
- <<":(:)">> = iolist_to_binary(join(re:split("(blah)","^(\\(+)?blah(?(1)(\\)))$",[trim]))),
+ 2}]))),
+ <<"(blah">> = iolist_to_binary(join(re:split("(blah","^(\\()?blah(?(1)(\\)))$",[]))),
+ <<":(:)">> = iolist_to_binary(join(re:split("(blah)","^(\\(+)?blah(?(1)(\\)))$",[trim]))),
<<":(:):">> = iolist_to_binary(join(re:split("(blah)","^(\\(+)?blah(?(1)(\\)))$",[{parts,
- 2}]))),
- <<":(:):">> = iolist_to_binary(join(re:split("(blah)","^(\\(+)?blah(?(1)(\\)))$",[]))),
- <<"">> = iolist_to_binary(join(re:split("blah","^(\\(+)?blah(?(1)(\\)))$",[trim]))),
+ 2}]))),
+ <<":(:):">> = iolist_to_binary(join(re:split("(blah)","^(\\(+)?blah(?(1)(\\)))$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("blah","^(\\(+)?blah(?(1)(\\)))$",[trim]))),
<<":::">> = iolist_to_binary(join(re:split("blah","^(\\(+)?blah(?(1)(\\)))$",[{parts,
- 2}]))),
- <<":::">> = iolist_to_binary(join(re:split("blah","^(\\(+)?blah(?(1)(\\)))$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\(+)?blah(?(1)(\\)))$",[trim]))),
+ 2}]))),
+ <<":::">> = iolist_to_binary(join(re:split("blah","^(\\(+)?blah(?(1)(\\)))$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\(+)?blah(?(1)(\\)))$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\(+)?blah(?(1)(\\)))$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\(+)?blah(?(1)(\\)))$",[]))),
- <<"blah)">> = iolist_to_binary(join(re:split("blah)","^(\\(+)?blah(?(1)(\\)))$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\(+)?blah(?(1)(\\)))$",[]))),
+ <<"blah)">> = iolist_to_binary(join(re:split("blah)","^(\\(+)?blah(?(1)(\\)))$",[trim]))),
<<"blah)">> = iolist_to_binary(join(re:split("blah)","^(\\(+)?blah(?(1)(\\)))$",[{parts,
- 2}]))),
- <<"blah)">> = iolist_to_binary(join(re:split("blah)","^(\\(+)?blah(?(1)(\\)))$",[]))),
- <<"(blah">> = iolist_to_binary(join(re:split("(blah","^(\\(+)?blah(?(1)(\\)))$",[trim]))),
+ 2}]))),
+ <<"blah)">> = iolist_to_binary(join(re:split("blah)","^(\\(+)?blah(?(1)(\\)))$",[]))),
+ <<"(blah">> = iolist_to_binary(join(re:split("(blah","^(\\(+)?blah(?(1)(\\)))$",[trim]))),
<<"(blah">> = iolist_to_binary(join(re:split("(blah","^(\\(+)?blah(?(1)(\\)))$",[{parts,
- 2}]))),
- <<"(blah">> = iolist_to_binary(join(re:split("(blah","^(\\(+)?blah(?(1)(\\)))$",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","(?(?!a)b|a)",[trim]))),
+ 2}]))),
+ <<"(blah">> = iolist_to_binary(join(re:split("(blah","^(\\(+)?blah(?(1)(\\)))$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","(?(?!a)b|a)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","(?(?!a)b|a)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","(?(?!a)b|a)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?=a)b|a)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","(?(?!a)b|a)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?=a)b|a)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?=a)b|a)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?=a)b|a)",[]))),
- <<"a">> = iolist_to_binary(join(re:split("a","(?(?=a)b|a)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?(?=a)b|a)",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","(?(?=a)b|a)",[trim]))),
<<"a">> = iolist_to_binary(join(re:split("a","(?(?=a)b|a)",[{parts,
- 2}]))),
- <<"a">> = iolist_to_binary(join(re:split("a","(?(?=a)b|a)",[]))),
- <<"a">> = iolist_to_binary(join(re:split("a","(?(?=a)b|a)",[trim]))),
+ 2}]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","(?(?=a)b|a)",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","(?(?=a)b|a)",[trim]))),
<<"a">> = iolist_to_binary(join(re:split("a","(?(?=a)b|a)",[{parts,
- 2}]))),
- <<"a">> = iolist_to_binary(join(re:split("a","(?(?=a)b|a)",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","(?(?=a)a|b)",[trim]))),
+ 2}]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","(?(?=a)b|a)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","(?(?=a)a|b)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","(?(?=a)a|b)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","(?(?=a)a|b)",[]))),
- <<"a:a:aab">> = iolist_to_binary(join(re:split("aaab","(?=(a+?))(\\1ab)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","(?(?=a)a|b)",[]))),
+ <<"a:a:aab">> = iolist_to_binary(join(re:split("aaab","(?=(a+?))(\\1ab)",[trim]))),
<<"a:a:aab:">> = iolist_to_binary(join(re:split("aaab","(?=(a+?))(\\1ab)",[{parts,
- 2}]))),
- <<"a:a:aab:">> = iolist_to_binary(join(re:split("aaab","(?=(a+?))(\\1ab)",[]))),
- <<":one:">> = iolist_to_binary(join(re:split("one:","(\\w+:)+",[trim]))),
+ 2}]))),
+ <<"a:a:aab:">> = iolist_to_binary(join(re:split("aaab","(?=(a+?))(\\1ab)",[]))),
+ <<":one:">> = iolist_to_binary(join(re:split("one:","(\\w+:)+",[trim]))),
<<":one::">> = iolist_to_binary(join(re:split("one:","(\\w+:)+",[{parts,
- 2}]))),
- <<":one::">> = iolist_to_binary(join(re:split("one:","(\\w+:)+",[]))),
- <<"a:a">> = iolist_to_binary(join(re:split("a","$(?<=^(a))",[trim]))),
+ 2}]))),
+ <<":one::">> = iolist_to_binary(join(re:split("one:","(\\w+:)+",[]))),
+ <<"a:a">> = iolist_to_binary(join(re:split("a","$(?<=^(a))",[trim]))),
<<"a:a:">> = iolist_to_binary(join(re:split("a","$(?<=^(a))",[{parts,
- 2}]))),
- <<"a:a:">> = iolist_to_binary(join(re:split("a","$(?<=^(a))",[]))),
- <<"a:a:aab">> = iolist_to_binary(join(re:split("aaab","(?=(a+?))(\\1ab)",[trim]))),
+ 2}]))),
+ <<"a:a:">> = iolist_to_binary(join(re:split("a","$(?<=^(a))",[]))),
+ <<"a:a:aab">> = iolist_to_binary(join(re:split("aaab","(?=(a+?))(\\1ab)",[trim]))),
<<"a:a:aab:">> = iolist_to_binary(join(re:split("aaab","(?=(a+?))(\\1ab)",[{parts,
- 2}]))),
- <<"a:a:aab:">> = iolist_to_binary(join(re:split("aaab","(?=(a+?))(\\1ab)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?=(a+?))\\1ab",[trim]))),
+ 2}]))),
+ <<"a:a:aab:">> = iolist_to_binary(join(re:split("aaab","(?=(a+?))(\\1ab)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?=(a+?))\\1ab",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?=(a+?))\\1ab",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?=(a+?))\\1ab",[]))),
- <<"aaab">> = iolist_to_binary(join(re:split("aaab","^(?=(a+?))\\1ab",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?=(a+?))\\1ab",[]))),
+ <<"aaab">> = iolist_to_binary(join(re:split("aaab","^(?=(a+?))\\1ab",[trim]))),
<<"aaab">> = iolist_to_binary(join(re:split("aaab","^(?=(a+?))\\1ab",[{parts,
- 2}]))),
- <<"aaab">> = iolist_to_binary(join(re:split("aaab","^(?=(a+?))\\1ab",[]))),
- <<"aaab">> = iolist_to_binary(join(re:split("aaab","^(?=(a+?))\\1ab",[trim]))),
+ 2}]))),
+ <<"aaab">> = iolist_to_binary(join(re:split("aaab","^(?=(a+?))\\1ab",[]))),
+ <<"aaab">> = iolist_to_binary(join(re:split("aaab","^(?=(a+?))\\1ab",[trim]))),
<<"aaab">> = iolist_to_binary(join(re:split("aaab","^(?=(a+?))\\1ab",[{parts,
- 2}]))),
- <<"aaab">> = iolist_to_binary(join(re:split("aaab","^(?=(a+?))\\1ab",[]))),
- <<"::abcd">> = iolist_to_binary(join(re:split("abcd","([\\w:]+::)?(\\w+)$",[trim]))),
+ 2}]))),
+ <<"aaab">> = iolist_to_binary(join(re:split("aaab","^(?=(a+?))\\1ab",[]))),
+ <<"::abcd">> = iolist_to_binary(join(re:split("abcd","([\\w:]+::)?(\\w+)$",[trim]))),
<<"::abcd:">> = iolist_to_binary(join(re:split("abcd","([\\w:]+::)?(\\w+)$",[{parts,
- 2}]))),
- <<"::abcd:">> = iolist_to_binary(join(re:split("abcd","([\\w:]+::)?(\\w+)$",[]))),
- <<":xy:z::::abcd">> = iolist_to_binary(join(re:split("xy:z:::abcd","([\\w:]+::)?(\\w+)$",[trim]))),
+ 2}]))),
+ <<"::abcd:">> = iolist_to_binary(join(re:split("abcd","([\\w:]+::)?(\\w+)$",[]))),
+ <<":xy:z::::abcd">> = iolist_to_binary(join(re:split("xy:z:::abcd","([\\w:]+::)?(\\w+)$",[trim]))),
<<":xy:z::::abcd:">> = iolist_to_binary(join(re:split("xy:z:::abcd","([\\w:]+::)?(\\w+)$",[{parts,
- 2}]))),
- <<":xy:z::::abcd:">> = iolist_to_binary(join(re:split("xy:z:::abcd","([\\w:]+::)?(\\w+)$",[]))),
- <<":c:d">> = iolist_to_binary(join(re:split("aexycd","^[^bcd]*(c+)",[trim]))),
+ 2}]))),
+ <<":xy:z::::abcd:">> = iolist_to_binary(join(re:split("xy:z:::abcd","([\\w:]+::)?(\\w+)$",[]))),
+ <<":c:d">> = iolist_to_binary(join(re:split("aexycd","^[^bcd]*(c+)",[trim]))),
<<":c:d">> = iolist_to_binary(join(re:split("aexycd","^[^bcd]*(c+)",[{parts,
- 2}]))),
- <<":c:d">> = iolist_to_binary(join(re:split("aexycd","^[^bcd]*(c+)",[]))),
- <<"c:aa">> = iolist_to_binary(join(re:split("caab","(a*)b+",[trim]))),
+ 2}]))),
+ <<":c:d">> = iolist_to_binary(join(re:split("aexycd","^[^bcd]*(c+)",[]))),
+ <<"c:aa">> = iolist_to_binary(join(re:split("caab","(a*)b+",[trim]))),
<<"c:aa:">> = iolist_to_binary(join(re:split("caab","(a*)b+",[{parts,
- 2}]))),
- <<"c:aa:">> = iolist_to_binary(join(re:split("caab","(a*)b+",[]))),
- <<"::abcd">> = iolist_to_binary(join(re:split("abcd","([\\w:]+::)?(\\w+)$",[trim]))),
+ 2}]))),
+ <<"c:aa:">> = iolist_to_binary(join(re:split("caab","(a*)b+",[]))),
+ <<"::abcd">> = iolist_to_binary(join(re:split("abcd","([\\w:]+::)?(\\w+)$",[trim]))),
<<"::abcd:">> = iolist_to_binary(join(re:split("abcd","([\\w:]+::)?(\\w+)$",[{parts,
- 2}]))),
- <<"::abcd:">> = iolist_to_binary(join(re:split("abcd","([\\w:]+::)?(\\w+)$",[]))),
- <<":xy:z::::abcd">> = iolist_to_binary(join(re:split("xy:z:::abcd","([\\w:]+::)?(\\w+)$",[trim]))),
+ 2}]))),
+ <<"::abcd:">> = iolist_to_binary(join(re:split("abcd","([\\w:]+::)?(\\w+)$",[]))),
+ <<":xy:z::::abcd">> = iolist_to_binary(join(re:split("xy:z:::abcd","([\\w:]+::)?(\\w+)$",[trim]))),
<<":xy:z::::abcd:">> = iolist_to_binary(join(re:split("xy:z:::abcd","([\\w:]+::)?(\\w+)$",[{parts,
- 2}]))),
- <<":xy:z::::abcd:">> = iolist_to_binary(join(re:split("xy:z:::abcd","([\\w:]+::)?(\\w+)$",[]))),
- <<"*** ::Failers">> = iolist_to_binary(join(re:split("*** Failers","([\\w:]+::)?(\\w+)$",[trim]))),
+ 2}]))),
+ <<":xy:z::::abcd:">> = iolist_to_binary(join(re:split("xy:z:::abcd","([\\w:]+::)?(\\w+)$",[]))),
+ <<"*** ::Failers">> = iolist_to_binary(join(re:split("*** Failers","([\\w:]+::)?(\\w+)$",[trim]))),
<<"*** ::Failers:">> = iolist_to_binary(join(re:split("*** Failers","([\\w:]+::)?(\\w+)$",[{parts,
- 2}]))),
- <<"*** ::Failers:">> = iolist_to_binary(join(re:split("*** Failers","([\\w:]+::)?(\\w+)$",[]))),
- <<"abcd:">> = iolist_to_binary(join(re:split("abcd:","([\\w:]+::)?(\\w+)$",[trim]))),
+ 2}]))),
+ <<"*** ::Failers:">> = iolist_to_binary(join(re:split("*** Failers","([\\w:]+::)?(\\w+)$",[]))),
+ <<"abcd:">> = iolist_to_binary(join(re:split("abcd:","([\\w:]+::)?(\\w+)$",[trim]))),
<<"abcd:">> = iolist_to_binary(join(re:split("abcd:","([\\w:]+::)?(\\w+)$",[{parts,
- 2}]))),
- <<"abcd:">> = iolist_to_binary(join(re:split("abcd:","([\\w:]+::)?(\\w+)$",[]))),
- <<"abcd:">> = iolist_to_binary(join(re:split("abcd:","([\\w:]+::)?(\\w+)$",[trim]))),
+ 2}]))),
+ <<"abcd:">> = iolist_to_binary(join(re:split("abcd:","([\\w:]+::)?(\\w+)$",[]))),
+ <<"abcd:">> = iolist_to_binary(join(re:split("abcd:","([\\w:]+::)?(\\w+)$",[trim]))),
<<"abcd:">> = iolist_to_binary(join(re:split("abcd:","([\\w:]+::)?(\\w+)$",[{parts,
- 2}]))),
- <<"abcd:">> = iolist_to_binary(join(re:split("abcd:","([\\w:]+::)?(\\w+)$",[]))),
- <<":c:d">> = iolist_to_binary(join(re:split("aexycd","^[^bcd]*(c+)",[trim]))),
+ 2}]))),
+ <<"abcd:">> = iolist_to_binary(join(re:split("abcd:","([\\w:]+::)?(\\w+)$",[]))),
+ <<":c:d">> = iolist_to_binary(join(re:split("aexycd","^[^bcd]*(c+)",[trim]))),
<<":c:d">> = iolist_to_binary(join(re:split("aexycd","^[^bcd]*(c+)",[{parts,
- 2}]))),
- <<":c:d">> = iolist_to_binary(join(re:split("aexycd","^[^bcd]*(c+)",[]))),
+ 2}]))),
+ <<":c:d">> = iolist_to_binary(join(re:split("aexycd","^[^bcd]*(c+)",[]))),
ok.
run31() ->
- <<"">> = iolist_to_binary(join(re:split("aaab","(?>a+)b",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("aaab","(?>a+)b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaab","(?>a+)b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaab","(?>a+)b",[]))),
- <<"a::[:b]::">> = iolist_to_binary(join(re:split("a:[b]:","([[:]+)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaab","(?>a+)b",[]))),
+ <<"a::[:b]::">> = iolist_to_binary(join(re:split("a:[b]:","([[:]+)",[trim]))),
<<"a::[:b]:">> = iolist_to_binary(join(re:split("a:[b]:","([[:]+)",[{parts,
- 2}]))),
- <<"a::[:b]:::">> = iolist_to_binary(join(re:split("a:[b]:","([[:]+)",[]))),
- <<"a:=[:b]:=">> = iolist_to_binary(join(re:split("a=[b]=","([[=]+)",[trim]))),
+ 2}]))),
+ <<"a::[:b]:::">> = iolist_to_binary(join(re:split("a:[b]:","([[:]+)",[]))),
+ <<"a:=[:b]:=">> = iolist_to_binary(join(re:split("a=[b]=","([[=]+)",[trim]))),
<<"a:=[:b]=">> = iolist_to_binary(join(re:split("a=[b]=","([[=]+)",[{parts,
- 2}]))),
- <<"a:=[:b]:=:">> = iolist_to_binary(join(re:split("a=[b]=","([[=]+)",[]))),
- <<"a:.[:b]:.">> = iolist_to_binary(join(re:split("a.[b].","([[.]+)",[trim]))),
+ 2}]))),
+ <<"a:=[:b]:=:">> = iolist_to_binary(join(re:split("a=[b]=","([[=]+)",[]))),
+ <<"a:.[:b]:.">> = iolist_to_binary(join(re:split("a.[b].","([[.]+)",[trim]))),
<<"a:.[:b].">> = iolist_to_binary(join(re:split("a.[b].","([[.]+)",[{parts,
- 2}]))),
- <<"a:.[:b]:.:">> = iolist_to_binary(join(re:split("a.[b].","([[.]+)",[]))),
- <<":aaab">> = iolist_to_binary(join(re:split("aaab","((?>a+)b)",[trim]))),
+ 2}]))),
+ <<"a:.[:b]:.:">> = iolist_to_binary(join(re:split("a.[b].","([[.]+)",[]))),
+ <<":aaab">> = iolist_to_binary(join(re:split("aaab","((?>a+)b)",[trim]))),
<<":aaab:">> = iolist_to_binary(join(re:split("aaab","((?>a+)b)",[{parts,
- 2}]))),
- <<":aaab:">> = iolist_to_binary(join(re:split("aaab","((?>a+)b)",[]))),
- <<":aaa">> = iolist_to_binary(join(re:split("aaab","(?>(a+))b",[trim]))),
+ 2}]))),
+ <<":aaab:">> = iolist_to_binary(join(re:split("aaab","((?>a+)b)",[]))),
+ <<":aaa">> = iolist_to_binary(join(re:split("aaab","(?>(a+))b",[trim]))),
<<":aaa:">> = iolist_to_binary(join(re:split("aaab","(?>(a+))b",[{parts,
- 2}]))),
- <<":aaa:">> = iolist_to_binary(join(re:split("aaab","(?>(a+))b",[]))),
- <<"((:x">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","((?>[^()]+)|\\([^()]*\\))+",[trim]))),
+ 2}]))),
+ <<":aaa:">> = iolist_to_binary(join(re:split("aaab","(?>(a+))b",[]))),
+ <<"((:x">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","((?>[^()]+)|\\([^()]*\\))+",[trim]))),
<<"((:x:">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","((?>[^()]+)|\\([^()]*\\))+",[{parts,
- 2}]))),
- <<"((:x:">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","((?>[^()]+)|\\([^()]*\\))+",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a\\Z",[trim]))),
+ 2}]))),
+ <<"((:x:">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","((?>[^()]+)|\\([^()]*\\))+",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a\\Z",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a\\Z",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a\\Z",[]))),
- <<"aaab">> = iolist_to_binary(join(re:split("aaab","a\\Z",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a\\Z",[]))),
+ <<"aaab">> = iolist_to_binary(join(re:split("aaab","a\\Z",[trim]))),
<<"aaab">> = iolist_to_binary(join(re:split("aaab","a\\Z",[{parts,
- 2}]))),
- <<"aaab">> = iolist_to_binary(join(re:split("aaab","a\\Z",[]))),
+ 2}]))),
+ <<"aaab">> = iolist_to_binary(join(re:split("aaab","a\\Z",[]))),
<<"a
b">> = iolist_to_binary(join(re:split("a
-b","a\\Z",[trim]))),
+b","a\\Z",[trim]))),
<<"a
b">> = iolist_to_binary(join(re:split("a
-b","a\\Z",[{parts,2}]))),
+b","a\\Z",[{parts,2}]))),
<<"a
b">> = iolist_to_binary(join(re:split("a
-b","a\\Z",[]))),
+b","a\\Z",[]))),
<<"a
">> = iolist_to_binary(join(re:split("a
-b","b\\Z",[trim]))),
+b","b\\Z",[trim]))),
<<"a
:">> = iolist_to_binary(join(re:split("a
-b","b\\Z",[{parts,2}]))),
+b","b\\Z",[{parts,2}]))),
<<"a
:">> = iolist_to_binary(join(re:split("a
-b","b\\Z",[]))),
+b","b\\Z",[]))),
<<"a
">> = iolist_to_binary(join(re:split("a
-b","b\\Z",[trim]))),
+b","b\\Z",[trim]))),
<<"a
:">> = iolist_to_binary(join(re:split("a
-b","b\\Z",[{parts,2}]))),
+b","b\\Z",[{parts,2}]))),
<<"a
:">> = iolist_to_binary(join(re:split("a
-b","b\\Z",[]))),
+b","b\\Z",[]))),
<<"a
">> = iolist_to_binary(join(re:split("a
-b","b\\z",[trim]))),
+b","b\\z",[trim]))),
<<"a
:">> = iolist_to_binary(join(re:split("a
-b","b\\z",[{parts,2}]))),
+b","b\\z",[{parts,2}]))),
<<"a
:">> = iolist_to_binary(join(re:split("a
-b","b\\z",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","b\\z",[trim]))),
+b","b\\z",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","b\\z",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","b\\z",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","b\\z",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","b\\z",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("abc","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("abc","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("a-b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("abc","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a-b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a-b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a-b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("0-9","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a-b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("0-9","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("0-9","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("0-9","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("a.b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("0-9","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a.b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a.b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a.b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("5.6.7","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a.b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("5.6.7","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("5.6.7","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("5.6.7","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("the.quick.brown.fox","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("5.6.7","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("the.quick.brown.fox","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("the.quick.brown.fox","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("the.quick.brown.fox","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("a100.b200.300c","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("the.quick.brown.fox","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a100.b200.300c","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a100.b200.300c","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a100.b200.300c","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("12-ab.1245","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a100.b200.300c","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("12-ab.1245","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("12-ab.1245","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("12-ab.1245","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("12-ab.1245","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"">> = iolist_to_binary(join(re:split("","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"">> = iolist_to_binary(join(re:split("","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"">> = iolist_to_binary(join(re:split("","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<".a">> = iolist_to_binary(join(re:split(".a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"">> = iolist_to_binary(join(re:split("","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<".a">> = iolist_to_binary(join(re:split(".a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<".a">> = iolist_to_binary(join(re:split(".a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<".a">> = iolist_to_binary(join(re:split(".a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"-a">> = iolist_to_binary(join(re:split("-a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<".a">> = iolist_to_binary(join(re:split(".a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"-a">> = iolist_to_binary(join(re:split("-a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"-a">> = iolist_to_binary(join(re:split("-a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"-a">> = iolist_to_binary(join(re:split("-a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"a-">> = iolist_to_binary(join(re:split("a-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"-a">> = iolist_to_binary(join(re:split("-a","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"a-">> = iolist_to_binary(join(re:split("a-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"a-">> = iolist_to_binary(join(re:split("a-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"a-">> = iolist_to_binary(join(re:split("a-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"a.">> = iolist_to_binary(join(re:split("a.","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"a-">> = iolist_to_binary(join(re:split("a-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"a.">> = iolist_to_binary(join(re:split("a.","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"a.">> = iolist_to_binary(join(re:split("a.","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"a.">> = iolist_to_binary(join(re:split("a.","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"a_b">> = iolist_to_binary(join(re:split("a_b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"a.">> = iolist_to_binary(join(re:split("a.","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"a_b">> = iolist_to_binary(join(re:split("a_b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"a_b">> = iolist_to_binary(join(re:split("a_b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"a_b">> = iolist_to_binary(join(re:split("a_b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"a.-">> = iolist_to_binary(join(re:split("a.-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"a_b">> = iolist_to_binary(join(re:split("a_b","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"a.-">> = iolist_to_binary(join(re:split("a.-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"a.-">> = iolist_to_binary(join(re:split("a.-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"a.-">> = iolist_to_binary(join(re:split("a.-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"a..">> = iolist_to_binary(join(re:split("a..","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"a.-">> = iolist_to_binary(join(re:split("a.-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"a..">> = iolist_to_binary(join(re:split("a..","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"a..">> = iolist_to_binary(join(re:split("a..","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"a..">> = iolist_to_binary(join(re:split("a..","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"ab..bc">> = iolist_to_binary(join(re:split("ab..bc","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"a..">> = iolist_to_binary(join(re:split("a..","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"ab..bc">> = iolist_to_binary(join(re:split("ab..bc","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"ab..bc">> = iolist_to_binary(join(re:split("ab..bc","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"ab..bc">> = iolist_to_binary(join(re:split("ab..bc","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"the.quick.brown.fox-">> = iolist_to_binary(join(re:split("the.quick.brown.fox-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"ab..bc">> = iolist_to_binary(join(re:split("ab..bc","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"the.quick.brown.fox-">> = iolist_to_binary(join(re:split("the.quick.brown.fox-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"the.quick.brown.fox-">> = iolist_to_binary(join(re:split("the.quick.brown.fox-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"the.quick.brown.fox-">> = iolist_to_binary(join(re:split("the.quick.brown.fox-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"the.quick.brown.fox.">> = iolist_to_binary(join(re:split("the.quick.brown.fox.","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"the.quick.brown.fox-">> = iolist_to_binary(join(re:split("the.quick.brown.fox-","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"the.quick.brown.fox.">> = iolist_to_binary(join(re:split("the.quick.brown.fox.","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"the.quick.brown.fox.">> = iolist_to_binary(join(re:split("the.quick.brown.fox.","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"the.quick.brown.fox.">> = iolist_to_binary(join(re:split("the.quick.brown.fox.","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"the.quick.brown.fox_">> = iolist_to_binary(join(re:split("the.quick.brown.fox_","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"the.quick.brown.fox.">> = iolist_to_binary(join(re:split("the.quick.brown.fox.","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"the.quick.brown.fox_">> = iolist_to_binary(join(re:split("the.quick.brown.fox_","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"the.quick.brown.fox_">> = iolist_to_binary(join(re:split("the.quick.brown.fox_","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"the.quick.brown.fox_">> = iolist_to_binary(join(re:split("the.quick.brown.fox_","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<"the.quick.brown.fox+">> = iolist_to_binary(join(re:split("the.quick.brown.fox+","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
+ 2}]))),
+ <<"the.quick.brown.fox_">> = iolist_to_binary(join(re:split("the.quick.brown.fox_","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<"the.quick.brown.fox+">> = iolist_to_binary(join(re:split("the.quick.brown.fox+","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[trim]))),
<<"the.quick.brown.fox+">> = iolist_to_binary(join(re:split("the.quick.brown.fox+","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[{parts,
- 2}]))),
- <<"the.quick.brown.fox+">> = iolist_to_binary(join(re:split("the.quick.brown.fox+","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
- <<":abcd">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*)(?<=(abcd|wxyz))",[trim]))),
+ 2}]))),
+ <<"the.quick.brown.fox+">> = iolist_to_binary(join(re:split("the.quick.brown.fox+","^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$",[]))),
+ <<":abcd">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*)(?<=(abcd|wxyz))",[trim]))),
<<":abcd:">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*)(?<=(abcd|wxyz))",[{parts,
- 2}]))),
- <<":abcd:">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*)(?<=(abcd|wxyz))",[]))),
- <<":wxyz">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*)(?<=(abcd|wxyz))",[trim]))),
+ 2}]))),
+ <<":abcd:">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*)(?<=(abcd|wxyz))",[]))),
+ <<":wxyz">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*)(?<=(abcd|wxyz))",[trim]))),
<<":wxyz:">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*)(?<=(abcd|wxyz))",[{parts,
- 2}]))),
- <<":wxyz:">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*)(?<=(abcd|wxyz))",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>.*)(?<=(abcd|wxyz))",[trim]))),
+ 2}]))),
+ <<":wxyz:">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*)(?<=(abcd|wxyz))",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>.*)(?<=(abcd|wxyz))",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>.*)(?<=(abcd|wxyz))",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>.*)(?<=(abcd|wxyz))",[]))),
- <<"a rather long string that doesn't end with one of them">> = iolist_to_binary(join(re:split("a rather long string that doesn't end with one of them","(?>.*)(?<=(abcd|wxyz))",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?>.*)(?<=(abcd|wxyz))",[]))),
+ <<"a rather long string that doesn't end with one of them">> = iolist_to_binary(join(re:split("a rather long string that doesn't end with one of them","(?>.*)(?<=(abcd|wxyz))",[trim]))),
<<"a rather long string that doesn't end with one of them">> = iolist_to_binary(join(re:split("a rather long string that doesn't end with one of them","(?>.*)(?<=(abcd|wxyz))",[{parts,
- 2}]))),
- <<"a rather long string that doesn't end with one of them">> = iolist_to_binary(join(re:split("a rather long string that doesn't end with one of them","(?>.*)(?<=(abcd|wxyz))",[]))),
- <<"">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark otherword","word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword",[trim]))),
+ 2}]))),
+ <<"a rather long string that doesn't end with one of them">> = iolist_to_binary(join(re:split("a rather long string that doesn't end with one of them","(?>.*)(?<=(abcd|wxyz))",[]))),
+ <<"">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark otherword","word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword",[trim]))),
<<":">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark otherword","word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark otherword","word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword",[]))),
- <<"word cat dog elephant mussel cow horse canary baboon snake shark">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark","word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark otherword","word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword",[]))),
+ <<"word cat dog elephant mussel cow horse canary baboon snake shark">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark","word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword",[trim]))),
<<"word cat dog elephant mussel cow horse canary baboon snake shark">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark","word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword",[{parts,
- 2}]))),
- <<"word cat dog elephant mussel cow horse canary baboon snake shark">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark","word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword",[]))),
- <<"word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope","word (?>[a-zA-Z0-9]+ ){0,30}otherword",[trim]))),
+ 2}]))),
+ <<"word cat dog elephant mussel cow horse canary baboon snake shark">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark","word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword",[]))),
+ <<"word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope","word (?>[a-zA-Z0-9]+ ){0,30}otherword",[trim]))),
<<"word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope","word (?>[a-zA-Z0-9]+ ){0,30}otherword",[{parts,
- 2}]))),
- <<"word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope","word (?>[a-zA-Z0-9]+ ){0,30}otherword",[]))),
- <<"999">> = iolist_to_binary(join(re:split("999foo","(?<=\\d{3}(?!999))foo",[trim]))),
+ 2}]))),
+ <<"word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope">> = iolist_to_binary(join(re:split("word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope","word (?>[a-zA-Z0-9]+ ){0,30}otherword",[]))),
+ <<"999">> = iolist_to_binary(join(re:split("999foo","(?<=\\d{3}(?!999))foo",[trim]))),
<<"999:">> = iolist_to_binary(join(re:split("999foo","(?<=\\d{3}(?!999))foo",[{parts,
- 2}]))),
- <<"999:">> = iolist_to_binary(join(re:split("999foo","(?<=\\d{3}(?!999))foo",[]))),
- <<"123999">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}(?!999))foo",[trim]))),
+ 2}]))),
+ <<"999:">> = iolist_to_binary(join(re:split("999foo","(?<=\\d{3}(?!999))foo",[]))),
+ <<"123999">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}(?!999))foo",[trim]))),
<<"123999:">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}(?!999))foo",[{parts,
- 2}]))),
- <<"123999:">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}(?!999))foo",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}(?!999))foo",[trim]))),
+ 2}]))),
+ <<"123999:">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}(?!999))foo",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}(?!999))foo",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}(?!999))foo",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}(?!999))foo",[]))),
- <<"123abcfoo">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}(?!999))foo",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}(?!999))foo",[]))),
+ <<"123abcfoo">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}(?!999))foo",[trim]))),
<<"123abcfoo">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}(?!999))foo",[{parts,
- 2}]))),
- <<"123abcfoo">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}(?!999))foo",[]))),
- <<"999">> = iolist_to_binary(join(re:split("999foo","(?<=(?!...999)\\d{3})foo",[trim]))),
+ 2}]))),
+ <<"123abcfoo">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}(?!999))foo",[]))),
+ <<"999">> = iolist_to_binary(join(re:split("999foo","(?<=(?!...999)\\d{3})foo",[trim]))),
<<"999:">> = iolist_to_binary(join(re:split("999foo","(?<=(?!...999)\\d{3})foo",[{parts,
- 2}]))),
- <<"999:">> = iolist_to_binary(join(re:split("999foo","(?<=(?!...999)\\d{3})foo",[]))),
- <<"123999">> = iolist_to_binary(join(re:split("123999foo","(?<=(?!...999)\\d{3})foo",[trim]))),
+ 2}]))),
+ <<"999:">> = iolist_to_binary(join(re:split("999foo","(?<=(?!...999)\\d{3})foo",[]))),
+ <<"123999">> = iolist_to_binary(join(re:split("123999foo","(?<=(?!...999)\\d{3})foo",[trim]))),
<<"123999:">> = iolist_to_binary(join(re:split("123999foo","(?<=(?!...999)\\d{3})foo",[{parts,
- 2}]))),
- <<"123999:">> = iolist_to_binary(join(re:split("123999foo","(?<=(?!...999)\\d{3})foo",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(?!...999)\\d{3})foo",[trim]))),
+ 2}]))),
+ <<"123999:">> = iolist_to_binary(join(re:split("123999foo","(?<=(?!...999)\\d{3})foo",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(?!...999)\\d{3})foo",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(?!...999)\\d{3})foo",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(?!...999)\\d{3})foo",[]))),
- <<"123abcfoo">> = iolist_to_binary(join(re:split("123abcfoo","(?<=(?!...999)\\d{3})foo",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=(?!...999)\\d{3})foo",[]))),
+ <<"123abcfoo">> = iolist_to_binary(join(re:split("123abcfoo","(?<=(?!...999)\\d{3})foo",[trim]))),
<<"123abcfoo">> = iolist_to_binary(join(re:split("123abcfoo","(?<=(?!...999)\\d{3})foo",[{parts,
- 2}]))),
- <<"123abcfoo">> = iolist_to_binary(join(re:split("123abcfoo","(?<=(?!...999)\\d{3})foo",[]))),
- <<"123abc">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}(?!999)...)foo",[trim]))),
+ 2}]))),
+ <<"123abcfoo">> = iolist_to_binary(join(re:split("123abcfoo","(?<=(?!...999)\\d{3})foo",[]))),
+ <<"123abc">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}(?!999)...)foo",[trim]))),
<<"123abc:">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}(?!999)...)foo",[{parts,
- 2}]))),
- <<"123abc:">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}(?!999)...)foo",[]))),
- <<"123456">> = iolist_to_binary(join(re:split("123456foo","(?<=\\d{3}(?!999)...)foo",[trim]))),
+ 2}]))),
+ <<"123abc:">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}(?!999)...)foo",[]))),
+ <<"123456">> = iolist_to_binary(join(re:split("123456foo","(?<=\\d{3}(?!999)...)foo",[trim]))),
<<"123456:">> = iolist_to_binary(join(re:split("123456foo","(?<=\\d{3}(?!999)...)foo",[{parts,
- 2}]))),
- <<"123456:">> = iolist_to_binary(join(re:split("123456foo","(?<=\\d{3}(?!999)...)foo",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}(?!999)...)foo",[trim]))),
+ 2}]))),
+ <<"123456:">> = iolist_to_binary(join(re:split("123456foo","(?<=\\d{3}(?!999)...)foo",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}(?!999)...)foo",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}(?!999)...)foo",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}(?!999)...)foo",[]))),
- <<"123999foo">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}(?!999)...)foo",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}(?!999)...)foo",[]))),
+ <<"123999foo">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}(?!999)...)foo",[trim]))),
<<"123999foo">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}(?!999)...)foo",[{parts,
- 2}]))),
- <<"123999foo">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}(?!999)...)foo",[]))),
+ 2}]))),
+ <<"123999foo">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}(?!999)...)foo",[]))),
ok.
run32() ->
- <<"123abc">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}...)(?<!999)foo",[trim]))),
+ <<"123abc">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}...)(?<!999)foo",[trim]))),
<<"123abc:">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}...)(?<!999)foo",[{parts,
- 2}]))),
- <<"123abc:">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}...)(?<!999)foo",[]))),
- <<"123456">> = iolist_to_binary(join(re:split("123456foo","(?<=\\d{3}...)(?<!999)foo",[trim]))),
+ 2}]))),
+ <<"123abc:">> = iolist_to_binary(join(re:split("123abcfoo","(?<=\\d{3}...)(?<!999)foo",[]))),
+ <<"123456">> = iolist_to_binary(join(re:split("123456foo","(?<=\\d{3}...)(?<!999)foo",[trim]))),
<<"123456:">> = iolist_to_binary(join(re:split("123456foo","(?<=\\d{3}...)(?<!999)foo",[{parts,
- 2}]))),
- <<"123456:">> = iolist_to_binary(join(re:split("123456foo","(?<=\\d{3}...)(?<!999)foo",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}...)(?<!999)foo",[trim]))),
+ 2}]))),
+ <<"123456:">> = iolist_to_binary(join(re:split("123456foo","(?<=\\d{3}...)(?<!999)foo",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}...)(?<!999)foo",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}...)(?<!999)foo",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}...)(?<!999)foo",[]))),
- <<"123999foo">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}...)(?<!999)foo",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?<=\\d{3}...)(?<!999)foo",[]))),
+ <<"123999foo">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}...)(?<!999)foo",[trim]))),
<<"123999foo">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}...)(?<!999)foo",[{parts,
- 2}]))),
- <<"123999foo">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}...)(?<!999)foo",[]))),
+ 2}]))),
+ <<"123999foo">> = iolist_to_binary(join(re:split("123999foo","(?<=\\d{3}...)(?<!999)foo",[]))),
<<":::abcd: xyz">> = iolist_to_binary(join(re:split("<a href=abcd xyz","<a[\\s]+href[\\s]*=[\\s]* # find <a href=
([\\\"\\'])? # find single or double quote
(?(1) (.*?)\\1 | ([^\\s]+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
extended,
- trim]))),
+ trim]))),
<<":::abcd: xyz">> = iolist_to_binary(join(re:split("<a href=abcd xyz","<a[\\s]+href[\\s]*=[\\s]* # find <a href=
([\\\"\\'])? # find single or double quote
(?(1) (.*?)\\1 | ([^\\s]+)) # if quote found, match up to next matching
@@ -28108,20 +28108,20 @@ run32() ->
dotall,
extended,
{parts,
- 2}]))),
+ 2}]))),
<<":::abcd: xyz">> = iolist_to_binary(join(re:split("<a href=abcd xyz","<a[\\s]+href[\\s]*=[\\s]* # find <a href=
([\\\"\\'])? # find single or double quote
(?(1) (.*?)\\1 | ([^\\s]+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
- extended]))),
+ extended]))),
<<":\":abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href=\"abcd xyz pqr\" cats","<a[\\s]+href[\\s]*=[\\s]* # find <a href=
([\\\"\\'])? # find single or double quote
(?(1) (.*?)\\1 | ([^\\s]+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
extended,
- trim]))),
+ trim]))),
<<":\":abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href=\"abcd xyz pqr\" cats","<a[\\s]+href[\\s]*=[\\s]* # find <a href=
([\\\"\\'])? # find single or double quote
(?(1) (.*?)\\1 | ([^\\s]+)) # if quote found, match up to next matching
@@ -28129,20 +28129,20 @@ run32() ->
dotall,
extended,
{parts,
- 2}]))),
+ 2}]))),
<<":\":abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href=\"abcd xyz pqr\" cats","<a[\\s]+href[\\s]*=[\\s]* # find <a href=
([\\\"\\'])? # find single or double quote
(?(1) (.*?)\\1 | ([^\\s]+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
- extended]))),
+ extended]))),
<<":':abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href='abcd xyz pqr' cats","<a[\\s]+href[\\s]*=[\\s]* # find <a href=
([\\\"\\'])? # find single or double quote
(?(1) (.*?)\\1 | ([^\\s]+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
extended,
- trim]))),
+ trim]))),
<<":':abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href='abcd xyz pqr' cats","<a[\\s]+href[\\s]*=[\\s]* # find <a href=
([\\\"\\'])? # find single or double quote
(?(1) (.*?)\\1 | ([^\\s]+)) # if quote found, match up to next matching
@@ -28150,20 +28150,20 @@ run32() ->
dotall,
extended,
{parts,
- 2}]))),
+ 2}]))),
<<":':abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href='abcd xyz pqr' cats","<a[\\s]+href[\\s]*=[\\s]* # find <a href=
([\\\"\\'])? # find single or double quote
(?(1) (.*?)\\1 | ([^\\s]+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
- extended]))),
+ extended]))),
<<":::abcd: xyz">> = iolist_to_binary(join(re:split("<a href=abcd xyz","<a\\s+href\\s*=\\s* # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
extended,
- trim]))),
+ trim]))),
<<":::abcd: xyz">> = iolist_to_binary(join(re:split("<a href=abcd xyz","<a\\s+href\\s*=\\s* # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
@@ -28171,20 +28171,20 @@ run32() ->
dotall,
extended,
{parts,
- 2}]))),
+ 2}]))),
<<":::abcd: xyz">> = iolist_to_binary(join(re:split("<a href=abcd xyz","<a\\s+href\\s*=\\s* # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
- extended]))),
+ extended]))),
<<":\":abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href=\"abcd xyz pqr\" cats","<a\\s+href\\s*=\\s* # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
extended,
- trim]))),
+ trim]))),
<<":\":abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href=\"abcd xyz pqr\" cats","<a\\s+href\\s*=\\s* # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
@@ -28192,20 +28192,20 @@ run32() ->
dotall,
extended,
{parts,
- 2}]))),
+ 2}]))),
<<":\":abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href=\"abcd xyz pqr\" cats","<a\\s+href\\s*=\\s* # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
- extended]))),
+ extended]))),
<<":':abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href = 'abcd xyz pqr' cats","<a\\s+href\\s*=\\s* # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
extended,
- trim]))),
+ trim]))),
<<":':abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href = 'abcd xyz pqr' cats","<a\\s+href\\s*=\\s* # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
@@ -28213,20 +28213,20 @@ run32() ->
dotall,
extended,
{parts,
- 2}]))),
+ 2}]))),
<<":':abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href = 'abcd xyz pqr' cats","<a\\s+href\\s*=\\s* # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
- extended]))),
+ extended]))),
<<":::abcd: xyz">> = iolist_to_binary(join(re:split("<a href=abcd xyz","<a\\s+href(?>\\s*)=(?>\\s*) # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
extended,
- trim]))),
+ trim]))),
<<":::abcd: xyz">> = iolist_to_binary(join(re:split("<a href=abcd xyz","<a\\s+href(?>\\s*)=(?>\\s*) # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
@@ -28234,20 +28234,20 @@ run32() ->
dotall,
extended,
{parts,
- 2}]))),
+ 2}]))),
<<":::abcd: xyz">> = iolist_to_binary(join(re:split("<a href=abcd xyz","<a\\s+href(?>\\s*)=(?>\\s*) # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
- extended]))),
+ extended]))),
<<":\":abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href=\"abcd xyz pqr\" cats","<a\\s+href(?>\\s*)=(?>\\s*) # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
extended,
- trim]))),
+ trim]))),
<<":\":abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href=\"abcd xyz pqr\" cats","<a\\s+href(?>\\s*)=(?>\\s*) # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
@@ -28255,20 +28255,20 @@ run32() ->
dotall,
extended,
{parts,
- 2}]))),
+ 2}]))),
<<":\":abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href=\"abcd xyz pqr\" cats","<a\\s+href(?>\\s*)=(?>\\s*) # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
- extended]))),
+ extended]))),
<<":':abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href = 'abcd xyz pqr' cats","<a\\s+href(?>\\s*)=(?>\\s*) # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
extended,
- trim]))),
+ trim]))),
<<":':abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href = 'abcd xyz pqr' cats","<a\\s+href(?>\\s*)=(?>\\s*) # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
@@ -28276,303 +28276,303 @@ run32() ->
dotall,
extended,
{parts,
- 2}]))),
+ 2}]))),
<<":':abcd xyz pqr:: cats">> = iolist_to_binary(join(re:split("<a href = 'abcd xyz pqr' cats","<a\\s+href(?>\\s*)=(?>\\s*) # find <a href=
([\"'])? # find single or double quote
(?(1) (.*?)\\1 | (\\S+)) # if quote found, match up to next matching
# quote, otherwise match up to next space",[caseless,
dotall,
- extended]))),
- <<":A:Z:B:::C:::D:::E:::F:::G">> = iolist_to_binary(join(re:split("ZABCDEFG","((Z)+|A)*",[trim]))),
+ extended]))),
+ <<":A:Z:B:::C:::D:::E:::F:::G">> = iolist_to_binary(join(re:split("ZABCDEFG","((Z)+|A)*",[trim]))),
<<":A:Z:BCDEFG">> = iolist_to_binary(join(re:split("ZABCDEFG","((Z)+|A)*",[{parts,
- 2}]))),
- <<":A:Z:B:::C:::D:::E:::F:::G:::">> = iolist_to_binary(join(re:split("ZABCDEFG","((Z)+|A)*",[]))),
- <<":A::B:::C:::D:::E:::F:::G">> = iolist_to_binary(join(re:split("ZABCDEFG","(Z()|A)*",[trim]))),
+ 2}]))),
+ <<":A:Z:B:::C:::D:::E:::F:::G:::">> = iolist_to_binary(join(re:split("ZABCDEFG","((Z)+|A)*",[]))),
+ <<":A::B:::C:::D:::E:::F:::G">> = iolist_to_binary(join(re:split("ZABCDEFG","(Z()|A)*",[trim]))),
<<":A::BCDEFG">> = iolist_to_binary(join(re:split("ZABCDEFG","(Z()|A)*",[{parts,
- 2}]))),
- <<":A::B:::C:::D:::E:::F:::G:::">> = iolist_to_binary(join(re:split("ZABCDEFG","(Z()|A)*",[]))),
- <<":A:::B::::C::::D::::E::::F::::G">> = iolist_to_binary(join(re:split("ZABCDEFG","(Z(())|A)*",[trim]))),
+ 2}]))),
+ <<":A::B:::C:::D:::E:::F:::G:::">> = iolist_to_binary(join(re:split("ZABCDEFG","(Z()|A)*",[]))),
+ <<":A:::B::::C::::D::::E::::F::::G">> = iolist_to_binary(join(re:split("ZABCDEFG","(Z(())|A)*",[trim]))),
<<":A:::BCDEFG">> = iolist_to_binary(join(re:split("ZABCDEFG","(Z(())|A)*",[{parts,
- 2}]))),
- <<":A:::B::::C::::D::::E::::F::::G::::">> = iolist_to_binary(join(re:split("ZABCDEFG","(Z(())|A)*",[]))),
- <<":A:B::C::D::E::F::G">> = iolist_to_binary(join(re:split("ZABCDEFG","((?>Z)+|A)*",[trim]))),
+ 2}]))),
+ <<":A:::B::::C::::D::::E::::F::::G::::">> = iolist_to_binary(join(re:split("ZABCDEFG","(Z(())|A)*",[]))),
+ <<":A:B::C::D::E::F::G">> = iolist_to_binary(join(re:split("ZABCDEFG","((?>Z)+|A)*",[trim]))),
<<":A:BCDEFG">> = iolist_to_binary(join(re:split("ZABCDEFG","((?>Z)+|A)*",[{parts,
- 2}]))),
- <<":A:B::C::D::E::F::G::">> = iolist_to_binary(join(re:split("ZABCDEFG","((?>Z)+|A)*",[]))),
- <<"Z::::B::C::D::E::F::G">> = iolist_to_binary(join(re:split("ZABCDEFG","((?>)+|A)*",[trim]))),
+ 2}]))),
+ <<":A:B::C::D::E::F::G::">> = iolist_to_binary(join(re:split("ZABCDEFG","((?>Z)+|A)*",[]))),
+ <<"Z::::B::C::D::E::F::G">> = iolist_to_binary(join(re:split("ZABCDEFG","((?>)+|A)*",[trim]))),
<<"Z::ABCDEFG">> = iolist_to_binary(join(re:split("ZABCDEFG","((?>)+|A)*",[{parts,
- 2}]))),
- <<"Z::::B::C::D::E::F::G::">> = iolist_to_binary(join(re:split("ZABCDEFG","((?>)+|A)*",[]))),
- <<":b:b:b">> = iolist_to_binary(join(re:split("abbab","a*",[trim]))),
+ 2}]))),
+ <<"Z::::B::C::D::E::F::G::">> = iolist_to_binary(join(re:split("ZABCDEFG","((?>)+|A)*",[]))),
+ <<":b:b:b">> = iolist_to_binary(join(re:split("abbab","a*",[trim]))),
<<":bbab">> = iolist_to_binary(join(re:split("abbab","a*",[{parts,
- 2}]))),
- <<":b:b:b:">> = iolist_to_binary(join(re:split("abbab","a*",[]))),
- <<":bcde">> = iolist_to_binary(join(re:split("abcde","^[\\d-a]",[trim]))),
+ 2}]))),
+ <<":b:b:b:">> = iolist_to_binary(join(re:split("abbab","a*",[]))),
+ <<":bcde">> = iolist_to_binary(join(re:split("abcde","^[\\d-a]",[trim]))),
<<":bcde">> = iolist_to_binary(join(re:split("abcde","^[\\d-a]",[{parts,
- 2}]))),
- <<":bcde">> = iolist_to_binary(join(re:split("abcde","^[\\d-a]",[]))),
- <<":things">> = iolist_to_binary(join(re:split("-things","^[\\d-a]",[trim]))),
+ 2}]))),
+ <<":bcde">> = iolist_to_binary(join(re:split("abcde","^[\\d-a]",[]))),
+ <<":things">> = iolist_to_binary(join(re:split("-things","^[\\d-a]",[trim]))),
<<":things">> = iolist_to_binary(join(re:split("-things","^[\\d-a]",[{parts,
- 2}]))),
- <<":things">> = iolist_to_binary(join(re:split("-things","^[\\d-a]",[]))),
- <<":digit">> = iolist_to_binary(join(re:split("0digit","^[\\d-a]",[trim]))),
+ 2}]))),
+ <<":things">> = iolist_to_binary(join(re:split("-things","^[\\d-a]",[]))),
+ <<":digit">> = iolist_to_binary(join(re:split("0digit","^[\\d-a]",[trim]))),
<<":digit">> = iolist_to_binary(join(re:split("0digit","^[\\d-a]",[{parts,
- 2}]))),
- <<":digit">> = iolist_to_binary(join(re:split("0digit","^[\\d-a]",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[\\d-a]",[trim]))),
+ 2}]))),
+ <<":digit">> = iolist_to_binary(join(re:split("0digit","^[\\d-a]",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[\\d-a]",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[\\d-a]",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[\\d-a]",[]))),
- <<"bcdef">> = iolist_to_binary(join(re:split("bcdef","^[\\d-a]",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^[\\d-a]",[]))),
+ <<"bcdef">> = iolist_to_binary(join(re:split("bcdef","^[\\d-a]",[trim]))),
<<"bcdef">> = iolist_to_binary(join(re:split("bcdef","^[\\d-a]",[{parts,
- 2}]))),
- <<"bcdef">> = iolist_to_binary(join(re:split("bcdef","^[\\d-a]",[]))),
+ 2}]))),
+ <<"bcdef">> = iolist_to_binary(join(re:split("bcdef","^[\\d-a]",[]))),
<<">:<">> = iolist_to_binary(join(re:split(">
- <","[[:space:]]+",[trim]))),
+ <","[[:space:]]+",[trim]))),
<<">:<">> = iolist_to_binary(join(re:split(">
- <","[[:space:]]+",[{parts,2}]))),
+ <","[[:space:]]+",[{parts,2}]))),
<<">:<">> = iolist_to_binary(join(re:split(">
- <","[[:space:]]+",[]))),
+ <","[[:space:]]+",[]))),
<<">:
<">> = iolist_to_binary(join(re:split(">
- <","[[:blank:]]+",[trim]))),
+ <","[[:blank:]]+",[trim]))),
<<">:
<">> = iolist_to_binary(join(re:split(">
- <","[[:blank:]]+",[{parts,2}]))),
+ <","[[:blank:]]+",[{parts,2}]))),
<<">:
<">> = iolist_to_binary(join(re:split(">
- <","[[:blank:]]+",[]))),
+ <","[[:blank:]]+",[]))),
<<">:<">> = iolist_to_binary(join(re:split(">
- <","[\\s]+",[trim]))),
+ <","[\\s]+",[trim]))),
<<">:<">> = iolist_to_binary(join(re:split(">
- <","[\\s]+",[{parts,2}]))),
+ <","[\\s]+",[{parts,2}]))),
<<">:<">> = iolist_to_binary(join(re:split(">
- <","[\\s]+",[]))),
+ <","[\\s]+",[]))),
<<">:<">> = iolist_to_binary(join(re:split(">
- <","\\s+",[trim]))),
+ <","\\s+",[trim]))),
<<">:<">> = iolist_to_binary(join(re:split(">
- <","\\s+",[{parts,2}]))),
+ <","\\s+",[{parts,2}]))),
<<">:<">> = iolist_to_binary(join(re:split(">
- <","\\s+",[]))),
+ <","\\s+",[]))),
<<"">> = iolist_to_binary(join(re:split("ab","a b",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("ab","a b",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab","a b",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab","a b",[extended]))),
<<"a
:b">> = iolist_to_binary(join(re:split("a
-xb","(?!\\A)x",[multiline,trim]))),
+xb","(?!\\A)x",[multiline,trim]))),
<<"a
:b">> = iolist_to_binary(join(re:split("a
-xb","(?!\\A)x",[multiline,{parts,2}]))),
+xb","(?!\\A)x",[multiline,{parts,2}]))),
<<"a
:b">> = iolist_to_binary(join(re:split("a
-xb","(?!\\A)x",[multiline]))),
+xb","(?!\\A)x",[multiline]))),
<<"a
xb">> = iolist_to_binary(join(re:split("a
-xb","(?!^)x",[multiline,trim]))),
+xb","(?!^)x",[multiline,trim]))),
<<"a
xb">> = iolist_to_binary(join(re:split("a
-xb","(?!^)x",[multiline,{parts,2}]))),
+xb","(?!^)x",[multiline,{parts,2}]))),
<<"a
xb">> = iolist_to_binary(join(re:split("a
-xb","(?!^)x",[multiline]))),
- <<"">> = iolist_to_binary(join(re:split("abcabcabc","abc\\Qabc\\Eabc",[trim]))),
+xb","(?!^)x",[multiline]))),
+ <<"">> = iolist_to_binary(join(re:split("abcabcabc","abc\\Qabc\\Eabc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcabcabc","abc\\Qabc\\Eabc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcabcabc","abc\\Qabc\\Eabc",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc(*+|abc","abc\\Q(*+|\\Eabc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcabcabc","abc\\Qabc\\Eabc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc(*+|abc","abc\\Q(*+|\\Eabc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc(*+|abc","abc\\Q(*+|\\Eabc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc(*+|abc","abc\\Q(*+|\\Eabc",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc(*+|abc","abc\\Q(*+|\\Eabc",[]))),
ok.
run33() ->
<<"">> = iolist_to_binary(join(re:split("abc abcabc"," abc\\Q abc\\Eabc",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("abc abcabc"," abc\\Q abc\\Eabc",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc abcabc"," abc\\Q abc\\Eabc",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc abcabc"," abc\\Q abc\\Eabc",[extended]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers"," abc\\Q abc\\Eabc",[extended,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers"," abc\\Q abc\\Eabc",[extended,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers"," abc\\Q abc\\Eabc",[extended]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers"," abc\\Q abc\\Eabc",[extended]))),
<<"abcabcabc">> = iolist_to_binary(join(re:split("abcabcabc"," abc\\Q abc\\Eabc",[extended,
- trim]))),
+ trim]))),
<<"abcabcabc">> = iolist_to_binary(join(re:split("abcabcabc"," abc\\Q abc\\Eabc",[extended,
{parts,
- 2}]))),
- <<"abcabcabc">> = iolist_to_binary(join(re:split("abcabcabc"," abc\\Q abc\\Eabc",[extended]))),
+ 2}]))),
+ <<"abcabcabc">> = iolist_to_binary(join(re:split("abcabcabc"," abc\\Q abc\\Eabc",[extended]))),
<<"">> = iolist_to_binary(join(re:split("abc#not comment
literal","abc#comment
\\Q#not comment
- literal\\E",[extended,trim]))),
+ literal\\E",[extended,trim]))),
<<":">> = iolist_to_binary(join(re:split("abc#not comment
literal","abc#comment
\\Q#not comment
- literal\\E",[extended,{parts,2}]))),
+ literal\\E",[extended,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("abc#not comment
literal","abc#comment
\\Q#not comment
- literal\\E",[extended]))),
+ literal\\E",[extended]))),
<<"">> = iolist_to_binary(join(re:split("abc#not comment
literal","abc#comment
\\Q#not comment
- literal",[extended,trim]))),
+ literal",[extended,trim]))),
<<":">> = iolist_to_binary(join(re:split("abc#not comment
literal","abc#comment
\\Q#not comment
- literal",[extended,{parts,2}]))),
+ literal",[extended,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("abc#not comment
literal","abc#comment
\\Q#not comment
- literal",[extended]))),
+ literal",[extended]))),
<<"">> = iolist_to_binary(join(re:split("abc#not comment
literal","abc#comment
\\Q#not comment
literal\\E #more comment
- ",[extended,trim]))),
+ ",[extended,trim]))),
<<":">> = iolist_to_binary(join(re:split("abc#not comment
literal","abc#comment
\\Q#not comment
literal\\E #more comment
- ",[extended,{parts,2}]))),
+ ",[extended,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("abc#not comment
literal","abc#comment
\\Q#not comment
literal\\E #more comment
- ",[extended]))),
+ ",[extended]))),
<<"">> = iolist_to_binary(join(re:split("abc#not comment
literal","abc#comment
\\Q#not comment
- literal\\E #more comment",[extended,trim]))),
+ literal\\E #more comment",[extended,trim]))),
<<":">> = iolist_to_binary(join(re:split("abc#not comment
literal","abc#comment
\\Q#not comment
- literal\\E #more comment",[extended,{parts,2}]))),
+ literal\\E #more comment",[extended,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("abc#not comment
literal","abc#comment
\\Q#not comment
- literal\\E #more comment",[extended]))),
- <<"">> = iolist_to_binary(join(re:split("abc\\$xyz","\\Qabc\\$xyz\\E",[trim]))),
+ literal\\E #more comment",[extended]))),
+ <<"">> = iolist_to_binary(join(re:split("abc\\$xyz","\\Qabc\\$xyz\\E",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc\\$xyz","\\Qabc\\$xyz\\E",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc\\$xyz","\\Qabc\\$xyz\\E",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc$xyz","\\Qabc\\E\\$\\Qxyz\\E",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc\\$xyz","\\Qabc\\$xyz\\E",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc$xyz","\\Qabc\\E\\$\\Qxyz\\E",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc$xyz","\\Qabc\\E\\$\\Qxyz\\E",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc$xyz","\\Qabc\\E\\$\\Qxyz\\E",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","\\Aabc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc$xyz","\\Qabc\\E\\$\\Qxyz\\E",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","\\Aabc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","\\Aabc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","\\Aabc",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\Aabc",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","\\Aabc",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\Aabc",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\Aabc",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\Aabc",[]))),
- <<"xyzabc">> = iolist_to_binary(join(re:split("xyzabc","\\Aabc",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\Aabc",[]))),
+ <<"xyzabc">> = iolist_to_binary(join(re:split("xyzabc","\\Aabc",[trim]))),
<<"xyzabc">> = iolist_to_binary(join(re:split("xyzabc","\\Aabc",[{parts,
- 2}]))),
- <<"xyzabc">> = iolist_to_binary(join(re:split("xyzabc","\\Aabc",[]))),
- <<":abc2xyzabc3">> = iolist_to_binary(join(re:split("abc1abc2xyzabc3","\\Aabc.",[trim]))),
+ 2}]))),
+ <<"xyzabc">> = iolist_to_binary(join(re:split("xyzabc","\\Aabc",[]))),
+ <<":abc2xyzabc3">> = iolist_to_binary(join(re:split("abc1abc2xyzabc3","\\Aabc.",[trim]))),
<<":abc2xyzabc3">> = iolist_to_binary(join(re:split("abc1abc2xyzabc3","\\Aabc.",[{parts,
- 2}]))),
- <<":abc2xyzabc3">> = iolist_to_binary(join(re:split("abc1abc2xyzabc3","\\Aabc.",[]))),
- <<"::xyz">> = iolist_to_binary(join(re:split("abc1abc2xyzabc3","abc.",[trim]))),
+ 2}]))),
+ <<":abc2xyzabc3">> = iolist_to_binary(join(re:split("abc1abc2xyzabc3","\\Aabc.",[]))),
+ <<"::xyz">> = iolist_to_binary(join(re:split("abc1abc2xyzabc3","abc.",[trim]))),
<<":abc2xyzabc3">> = iolist_to_binary(join(re:split("abc1abc2xyzabc3","abc.",[{parts,
- 2}]))),
- <<"::xyz:">> = iolist_to_binary(join(re:split("abc1abc2xyzabc3","abc.",[]))),
- <<"X:Y">> = iolist_to_binary(join(re:split("XabcdY","a(?x: b c )d",[trim]))),
+ 2}]))),
+ <<"::xyz:">> = iolist_to_binary(join(re:split("abc1abc2xyzabc3","abc.",[]))),
+ <<"X:Y">> = iolist_to_binary(join(re:split("XabcdY","a(?x: b c )d",[trim]))),
<<"X:Y">> = iolist_to_binary(join(re:split("XabcdY","a(?x: b c )d",[{parts,
- 2}]))),
- <<"X:Y">> = iolist_to_binary(join(re:split("XabcdY","a(?x: b c )d",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?x: b c )d",[trim]))),
+ 2}]))),
+ <<"X:Y">> = iolist_to_binary(join(re:split("XabcdY","a(?x: b c )d",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?x: b c )d",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?x: b c )d",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?x: b c )d",[]))),
- <<"Xa b c d Y">> = iolist_to_binary(join(re:split("Xa b c d Y","a(?x: b c )d",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","a(?x: b c )d",[]))),
+ <<"Xa b c d Y">> = iolist_to_binary(join(re:split("Xa b c d Y","a(?x: b c )d",[trim]))),
<<"Xa b c d Y">> = iolist_to_binary(join(re:split("Xa b c d Y","a(?x: b c )d",[{parts,
- 2}]))),
- <<"Xa b c d Y">> = iolist_to_binary(join(re:split("Xa b c d Y","a(?x: b c )d",[]))),
- <<"X:abc:Y">> = iolist_to_binary(join(re:split("XabcY","((?x)x y z | a b c)",[trim]))),
+ 2}]))),
+ <<"Xa b c d Y">> = iolist_to_binary(join(re:split("Xa b c d Y","a(?x: b c )d",[]))),
+ <<"X:abc:Y">> = iolist_to_binary(join(re:split("XabcY","((?x)x y z | a b c)",[trim]))),
<<"X:abc:Y">> = iolist_to_binary(join(re:split("XabcY","((?x)x y z | a b c)",[{parts,
- 2}]))),
- <<"X:abc:Y">> = iolist_to_binary(join(re:split("XabcY","((?x)x y z | a b c)",[]))),
- <<"A:xyz:B">> = iolist_to_binary(join(re:split("AxyzB","((?x)x y z | a b c)",[trim]))),
+ 2}]))),
+ <<"X:abc:Y">> = iolist_to_binary(join(re:split("XabcY","((?x)x y z | a b c)",[]))),
+ <<"A:xyz:B">> = iolist_to_binary(join(re:split("AxyzB","((?x)x y z | a b c)",[trim]))),
<<"A:xyz:B">> = iolist_to_binary(join(re:split("AxyzB","((?x)x y z | a b c)",[{parts,
- 2}]))),
- <<"A:xyz:B">> = iolist_to_binary(join(re:split("AxyzB","((?x)x y z | a b c)",[]))),
- <<"X:Y">> = iolist_to_binary(join(re:split("XabCY","(?i)AB(?-i)C",[trim]))),
+ 2}]))),
+ <<"A:xyz:B">> = iolist_to_binary(join(re:split("AxyzB","((?x)x y z | a b c)",[]))),
+ <<"X:Y">> = iolist_to_binary(join(re:split("XabCY","(?i)AB(?-i)C",[trim]))),
<<"X:Y">> = iolist_to_binary(join(re:split("XabCY","(?i)AB(?-i)C",[{parts,
- 2}]))),
- <<"X:Y">> = iolist_to_binary(join(re:split("XabCY","(?i)AB(?-i)C",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?i)AB(?-i)C",[trim]))),
+ 2}]))),
+ <<"X:Y">> = iolist_to_binary(join(re:split("XabCY","(?i)AB(?-i)C",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?i)AB(?-i)C",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?i)AB(?-i)C",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?i)AB(?-i)C",[]))),
- <<"XabcY">> = iolist_to_binary(join(re:split("XabcY","(?i)AB(?-i)C",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(?i)AB(?-i)C",[]))),
+ <<"XabcY">> = iolist_to_binary(join(re:split("XabcY","(?i)AB(?-i)C",[trim]))),
<<"XabcY">> = iolist_to_binary(join(re:split("XabcY","(?i)AB(?-i)C",[{parts,
- 2}]))),
- <<"XabcY">> = iolist_to_binary(join(re:split("XabcY","(?i)AB(?-i)C",[]))),
- <<":abC">> = iolist_to_binary(join(re:split("abCE","((?i)AB(?-i)C|D)E",[trim]))),
+ 2}]))),
+ <<"XabcY">> = iolist_to_binary(join(re:split("XabcY","(?i)AB(?-i)C",[]))),
+ <<":abC">> = iolist_to_binary(join(re:split("abCE","((?i)AB(?-i)C|D)E",[trim]))),
<<":abC:">> = iolist_to_binary(join(re:split("abCE","((?i)AB(?-i)C|D)E",[{parts,
- 2}]))),
- <<":abC:">> = iolist_to_binary(join(re:split("abCE","((?i)AB(?-i)C|D)E",[]))),
- <<":D">> = iolist_to_binary(join(re:split("DE","((?i)AB(?-i)C|D)E",[trim]))),
+ 2}]))),
+ <<":abC:">> = iolist_to_binary(join(re:split("abCE","((?i)AB(?-i)C|D)E",[]))),
+ <<":D">> = iolist_to_binary(join(re:split("DE","((?i)AB(?-i)C|D)E",[trim]))),
<<":D:">> = iolist_to_binary(join(re:split("DE","((?i)AB(?-i)C|D)E",[{parts,
- 2}]))),
- <<":D:">> = iolist_to_binary(join(re:split("DE","((?i)AB(?-i)C|D)E",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?i)AB(?-i)C|D)E",[trim]))),
+ 2}]))),
+ <<":D:">> = iolist_to_binary(join(re:split("DE","((?i)AB(?-i)C|D)E",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?i)AB(?-i)C|D)E",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?i)AB(?-i)C|D)E",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?i)AB(?-i)C|D)E",[]))),
- <<"abcE">> = iolist_to_binary(join(re:split("abcE","((?i)AB(?-i)C|D)E",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((?i)AB(?-i)C|D)E",[]))),
+ <<"abcE">> = iolist_to_binary(join(re:split("abcE","((?i)AB(?-i)C|D)E",[trim]))),
<<"abcE">> = iolist_to_binary(join(re:split("abcE","((?i)AB(?-i)C|D)E",[{parts,
- 2}]))),
- <<"abcE">> = iolist_to_binary(join(re:split("abcE","((?i)AB(?-i)C|D)E",[]))),
- <<"abCe">> = iolist_to_binary(join(re:split("abCe","((?i)AB(?-i)C|D)E",[trim]))),
+ 2}]))),
+ <<"abcE">> = iolist_to_binary(join(re:split("abcE","((?i)AB(?-i)C|D)E",[]))),
+ <<"abCe">> = iolist_to_binary(join(re:split("abCe","((?i)AB(?-i)C|D)E",[trim]))),
<<"abCe">> = iolist_to_binary(join(re:split("abCe","((?i)AB(?-i)C|D)E",[{parts,
- 2}]))),
- <<"abCe">> = iolist_to_binary(join(re:split("abCe","((?i)AB(?-i)C|D)E",[]))),
- <<"dE">> = iolist_to_binary(join(re:split("dE","((?i)AB(?-i)C|D)E",[trim]))),
+ 2}]))),
+ <<"abCe">> = iolist_to_binary(join(re:split("abCe","((?i)AB(?-i)C|D)E",[]))),
+ <<"dE">> = iolist_to_binary(join(re:split("dE","((?i)AB(?-i)C|D)E",[trim]))),
<<"dE">> = iolist_to_binary(join(re:split("dE","((?i)AB(?-i)C|D)E",[{parts,
- 2}]))),
- <<"dE">> = iolist_to_binary(join(re:split("dE","((?i)AB(?-i)C|D)E",[]))),
- <<"De">> = iolist_to_binary(join(re:split("De","((?i)AB(?-i)C|D)E",[trim]))),
+ 2}]))),
+ <<"dE">> = iolist_to_binary(join(re:split("dE","((?i)AB(?-i)C|D)E",[]))),
+ <<"De">> = iolist_to_binary(join(re:split("De","((?i)AB(?-i)C|D)E",[trim]))),
<<"De">> = iolist_to_binary(join(re:split("De","((?i)AB(?-i)C|D)E",[{parts,
- 2}]))),
- <<"De">> = iolist_to_binary(join(re:split("De","((?i)AB(?-i)C|D)E",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abc123abc","(.*)\\d+\\1",[trim]))),
+ 2}]))),
+ <<"De">> = iolist_to_binary(join(re:split("De","((?i)AB(?-i)C|D)E",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abc123abc","(.*)\\d+\\1",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abc123abc","(.*)\\d+\\1",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abc123abc","(.*)\\d+\\1",[]))),
- <<"a:bc">> = iolist_to_binary(join(re:split("abc123bc","(.*)\\d+\\1",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abc123abc","(.*)\\d+\\1",[]))),
+ <<"a:bc">> = iolist_to_binary(join(re:split("abc123bc","(.*)\\d+\\1",[trim]))),
<<"a:bc:">> = iolist_to_binary(join(re:split("abc123bc","(.*)\\d+\\1",[{parts,
- 2}]))),
- <<"a:bc:">> = iolist_to_binary(join(re:split("abc123bc","(.*)\\d+\\1",[]))),
+ 2}]))),
+ <<"a:bc:">> = iolist_to_binary(join(re:split("abc123bc","(.*)\\d+\\1",[]))),
<<":abc">> = iolist_to_binary(join(re:split("abc123abc","(.*)\\d+\\1",[dotall,
- trim]))),
+ trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abc123abc","(.*)\\d+\\1",[dotall,
{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abc123abc","(.*)\\d+\\1",[dotall]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abc123abc","(.*)\\d+\\1",[dotall]))),
<<"a:bc">> = iolist_to_binary(join(re:split("abc123bc","(.*)\\d+\\1",[dotall,
- trim]))),
+ trim]))),
<<"a:bc:">> = iolist_to_binary(join(re:split("abc123bc","(.*)\\d+\\1",[dotall,
{parts,
- 2}]))),
- <<"a:bc:">> = iolist_to_binary(join(re:split("abc123bc","(.*)\\d+\\1",[dotall]))),
- <<":abc:abc">> = iolist_to_binary(join(re:split("abc123abc","((.*))\\d+\\1",[trim]))),
+ 2}]))),
+ <<"a:bc:">> = iolist_to_binary(join(re:split("abc123bc","(.*)\\d+\\1",[dotall]))),
+ <<":abc:abc">> = iolist_to_binary(join(re:split("abc123abc","((.*))\\d+\\1",[trim]))),
<<":abc:abc:">> = iolist_to_binary(join(re:split("abc123abc","((.*))\\d+\\1",[{parts,
- 2}]))),
- <<":abc:abc:">> = iolist_to_binary(join(re:split("abc123abc","((.*))\\d+\\1",[]))),
- <<"a:bc:bc">> = iolist_to_binary(join(re:split("abc123bc","((.*))\\d+\\1",[trim]))),
+ 2}]))),
+ <<":abc:abc:">> = iolist_to_binary(join(re:split("abc123abc","((.*))\\d+\\1",[]))),
+ <<"a:bc:bc">> = iolist_to_binary(join(re:split("abc123bc","((.*))\\d+\\1",[trim]))),
<<"a:bc:bc:">> = iolist_to_binary(join(re:split("abc123bc","((.*))\\d+\\1",[{parts,
- 2}]))),
- <<"a:bc:bc:">> = iolist_to_binary(join(re:split("abc123bc","((.*))\\d+\\1",[]))),
+ 2}]))),
+ <<"a:bc:bc:">> = iolist_to_binary(join(re:split("abc123bc","((.*))\\d+\\1",[]))),
<<"">> = iolist_to_binary(join(re:split("a123::a123","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28581,7 +28581,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"::">> = iolist_to_binary(join(re:split("a123::a123","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28590,7 +28590,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"::">> = iolist_to_binary(join(re:split("a123::a123","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28599,7 +28599,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<"">> = iolist_to_binary(join(re:split("a123:b342::abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28608,7 +28608,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"::">> = iolist_to_binary(join(re:split("a123:b342::abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28617,7 +28617,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"::">> = iolist_to_binary(join(re:split("a123:b342::abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28626,7 +28626,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<"">> = iolist_to_binary(join(re:split("a123:b342::324e:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28635,7 +28635,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"::">> = iolist_to_binary(join(re:split("a123:b342::324e:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28644,7 +28644,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"::">> = iolist_to_binary(join(re:split("a123:b342::324e:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28653,7 +28653,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<"">> = iolist_to_binary(join(re:split("a123:ddde:b342::324e:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28662,7 +28662,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"::">> = iolist_to_binary(join(re:split("a123:ddde:b342::324e:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28671,7 +28671,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"::">> = iolist_to_binary(join(re:split("a123:ddde:b342::324e:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28680,7 +28680,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<"">> = iolist_to_binary(join(re:split("a123:ddde:b342::324e:dcba:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28689,7 +28689,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"::">> = iolist_to_binary(join(re:split("a123:ddde:b342::324e:dcba:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28698,7 +28698,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"::">> = iolist_to_binary(join(re:split("a123:ddde:b342::324e:dcba:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28707,7 +28707,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<"">> = iolist_to_binary(join(re:split("a123:ddde:9999:b342::324e:dcba:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28716,7 +28716,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"::">> = iolist_to_binary(join(re:split("a123:ddde:9999:b342::324e:dcba:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28725,7 +28725,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"::">> = iolist_to_binary(join(re:split("a123:ddde:9999:b342::324e:dcba:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28734,7 +28734,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28743,7 +28743,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28752,7 +28752,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28761,7 +28761,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<"1:2:3:4:5:6:7:8">> = iolist_to_binary(join(re:split("1:2:3:4:5:6:7:8","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28770,7 +28770,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"1:2:3:4:5:6:7:8">> = iolist_to_binary(join(re:split("1:2:3:4:5:6:7:8","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28779,7 +28779,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"1:2:3:4:5:6:7:8">> = iolist_to_binary(join(re:split("1:2:3:4:5:6:7:8","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28788,7 +28788,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<"a123:bce:ddde:9999:b342::324e:dcba:abcd">> = iolist_to_binary(join(re:split("a123:bce:ddde:9999:b342::324e:dcba:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28797,7 +28797,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"a123:bce:ddde:9999:b342::324e:dcba:abcd">> = iolist_to_binary(join(re:split("a123:bce:ddde:9999:b342::324e:dcba:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28806,7 +28806,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"a123:bce:ddde:9999:b342::324e:dcba:abcd">> = iolist_to_binary(join(re:split("a123:bce:ddde:9999:b342::324e:dcba:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28815,7 +28815,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<"a123::9999:b342::324e:dcba:abcd">> = iolist_to_binary(join(re:split("a123::9999:b342::324e:dcba:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28824,7 +28824,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"a123::9999:b342::324e:dcba:abcd">> = iolist_to_binary(join(re:split("a123::9999:b342::324e:dcba:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28833,7 +28833,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"a123::9999:b342::324e:dcba:abcd">> = iolist_to_binary(join(re:split("a123::9999:b342::324e:dcba:abcd","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28842,7 +28842,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<"abcde:2:3:4:5:6:7:8">> = iolist_to_binary(join(re:split("abcde:2:3:4:5:6:7:8","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28851,7 +28851,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"abcde:2:3:4:5:6:7:8">> = iolist_to_binary(join(re:split("abcde:2:3:4:5:6:7:8","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28860,7 +28860,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"abcde:2:3:4:5:6:7:8">> = iolist_to_binary(join(re:split("abcde:2:3:4:5:6:7:8","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28869,7 +28869,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<"::1">> = iolist_to_binary(join(re:split("::1","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28878,7 +28878,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"::1">> = iolist_to_binary(join(re:split("::1","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28887,7 +28887,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"::1">> = iolist_to_binary(join(re:split("::1","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28896,7 +28896,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<"abcd:fee0:123::">> = iolist_to_binary(join(re:split("abcd:fee0:123::","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28905,7 +28905,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"abcd:fee0:123::">> = iolist_to_binary(join(re:split("abcd:fee0:123::","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28914,7 +28914,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"abcd:fee0:123::">> = iolist_to_binary(join(re:split("abcd:fee0:123::","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28923,7 +28923,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<":1">> = iolist_to_binary(join(re:split(":1","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28932,7 +28932,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<":1">> = iolist_to_binary(join(re:split(":1","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28941,7 +28941,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<":1">> = iolist_to_binary(join(re:split(":1","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28950,7 +28950,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
+ ",[extended,caseless]))),
<<"1:">> = iolist_to_binary(join(re:split("1:","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28959,7 +28959,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,trim]))),
+ ",[extended,caseless,trim]))),
<<"1:">> = iolist_to_binary(join(re:split("1:","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28968,7 +28968,7 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless,{parts,2}]))),
+ ",[extended,caseless,{parts,2}]))),
<<"1:">> = iolist_to_binary(join(re:split("1:","^(?!:) # colon disallowed at start
(?: # start of item
(?: [0-9a-f]{1,4} | # 1-4 hex digits or
@@ -28977,3098 +28977,3147 @@ run33() ->
){1,7} # end item; 1-7 of them required
[0-9a-f]{1,4} $ # final hex number at end of string
(?(1)|.) # check that there was an empty component
- ",[extended,caseless]))),
- <<"">> = iolist_to_binary(join(re:split("z","[z\\Qa-d]\\E]",[trim]))),
+ ",[extended,caseless]))),
+ <<"">> = iolist_to_binary(join(re:split("z","[z\\Qa-d]\\E]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("z","[z\\Qa-d]\\E]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("z","[z\\Qa-d]\\E]",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","[z\\Qa-d]\\E]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("z","[z\\Qa-d]\\E]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","[z\\Qa-d]\\E]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","[z\\Qa-d]\\E]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","[z\\Qa-d]\\E]",[]))),
- <<"">> = iolist_to_binary(join(re:split("-","[z\\Qa-d]\\E]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","[z\\Qa-d]\\E]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("-","[z\\Qa-d]\\E]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("-","[z\\Qa-d]\\E]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("-","[z\\Qa-d]\\E]",[]))),
- <<"">> = iolist_to_binary(join(re:split("d","[z\\Qa-d]\\E]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("-","[z\\Qa-d]\\E]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("d","[z\\Qa-d]\\E]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("d","[z\\Qa-d]\\E]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("d","[z\\Qa-d]\\E]",[]))),
- <<"">> = iolist_to_binary(join(re:split("]","[z\\Qa-d]\\E]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("d","[z\\Qa-d]\\E]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("]","[z\\Qa-d]\\E]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("]","[z\\Qa-d]\\E]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("]","[z\\Qa-d]\\E]",[]))),
- <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[z\\Qa-d]\\E]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("]","[z\\Qa-d]\\E]",[]))),
+ <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[z\\Qa-d]\\E]",[trim]))),
<<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[z\\Qa-d]\\E]",[{parts,
- 2}]))),
- <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[z\\Qa-d]\\E]",[]))),
- <<"b">> = iolist_to_binary(join(re:split("b","[z\\Qa-d]\\E]",[trim]))),
+ 2}]))),
+ <<"*** F:ilers">> = iolist_to_binary(join(re:split("*** Failers","[z\\Qa-d]\\E]",[]))),
+ <<"b">> = iolist_to_binary(join(re:split("b","[z\\Qa-d]\\E]",[trim]))),
<<"b">> = iolist_to_binary(join(re:split("b","[z\\Qa-d]\\E]",[{parts,
- 2}]))),
- <<"b">> = iolist_to_binary(join(re:split("b","[z\\Qa-d]\\E]",[]))),
+ 2}]))),
+ <<"b">> = iolist_to_binary(join(re:split("b","[z\\Qa-d]\\E]",[]))),
ok.
run34() ->
- <<"">> = iolist_to_binary(join(re:split("z","[\\z\\C]",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("z","[\\z\\C]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("z","[\\z\\C]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("z","[\\z\\C]",[]))),
- <<"">> = iolist_to_binary(join(re:split("C","[\\z\\C]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("z","[\\z\\C]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("C","[\\z\\C]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("C","[\\z\\C]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("C","[\\z\\C]",[]))),
- <<"">> = iolist_to_binary(join(re:split("M","\\M",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("C","[\\z\\C]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("M","\\M",[trim]))),
<<":">> = iolist_to_binary(join(re:split("M","\\M",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("M","\\M",[]))),
- <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a+)*b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("M","\\M",[]))),
+ <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a+)*b",[trim]))),
<<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a+)*b",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a+)*b",[]))),
- <<"„XAZ">> = iolist_to_binary(join(re:split("„XAZXB","(?<=Z)X.",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a+)*b",[]))),
+ <<"„XAZ">> = iolist_to_binary(join(re:split("„XAZXB","(?<=Z)X.",[trim]))),
<<"„XAZ:">> = iolist_to_binary(join(re:split("„XAZXB","(?<=Z)X.",[{parts,
- 2}]))),
- <<"„XAZ:">> = iolist_to_binary(join(re:split("„XAZXB","(?<=Z)X.",[]))),
- <<"">> = iolist_to_binary(join(re:split("ab cd defg","ab cd (?x) de fg",[trim]))),
+ 2}]))),
+ <<"„XAZ:">> = iolist_to_binary(join(re:split("„XAZXB","(?<=Z)X.",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ab cd defg","ab cd (?x) de fg",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ab cd defg","ab cd (?x) de fg",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab cd defg","ab cd (?x) de fg",[]))),
- <<"">> = iolist_to_binary(join(re:split("ab cddefg","ab cd(?x) de fg",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab cd defg","ab cd (?x) de fg",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ab cddefg","ab cd(?x) de fg",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ab cddefg","ab cd(?x) de fg",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab cddefg","ab cd(?x) de fg",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","ab cd(?x) de fg",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab cddefg","ab cd(?x) de fg",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","ab cd(?x) de fg",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","ab cd(?x) de fg",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","ab cd(?x) de fg",[]))),
- <<"abcddefg">> = iolist_to_binary(join(re:split("abcddefg","ab cd(?x) de fg",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","ab cd(?x) de fg",[]))),
+ <<"abcddefg">> = iolist_to_binary(join(re:split("abcddefg","ab cd(?x) de fg",[trim]))),
<<"abcddefg">> = iolist_to_binary(join(re:split("abcddefg","ab cd(?x) de fg",[{parts,
- 2}]))),
- <<"abcddefg">> = iolist_to_binary(join(re:split("abcddefg","ab cd(?x) de fg",[]))),
- <<"foo:bar:X">> = iolist_to_binary(join(re:split("foobarX","(?<![^f]oo)(bar)",[trim]))),
+ 2}]))),
+ <<"abcddefg">> = iolist_to_binary(join(re:split("abcddefg","ab cd(?x) de fg",[]))),
+ <<"foo:bar:X">> = iolist_to_binary(join(re:split("foobarX","(?<![^f]oo)(bar)",[trim]))),
<<"foo:bar:X">> = iolist_to_binary(join(re:split("foobarX","(?<![^f]oo)(bar)",[{parts,
- 2}]))),
- <<"foo:bar:X">> = iolist_to_binary(join(re:split("foobarX","(?<![^f]oo)(bar)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<![^f]oo)(bar)",[trim]))),
+ 2}]))),
+ <<"foo:bar:X">> = iolist_to_binary(join(re:split("foobarX","(?<![^f]oo)(bar)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<![^f]oo)(bar)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<![^f]oo)(bar)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<![^f]oo)(bar)",[]))),
- <<"boobarX">> = iolist_to_binary(join(re:split("boobarX","(?<![^f]oo)(bar)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<![^f]oo)(bar)",[]))),
+ <<"boobarX">> = iolist_to_binary(join(re:split("boobarX","(?<![^f]oo)(bar)",[trim]))),
<<"boobarX">> = iolist_to_binary(join(re:split("boobarX","(?<![^f]oo)(bar)",[{parts,
- 2}]))),
- <<"boobarX">> = iolist_to_binary(join(re:split("boobarX","(?<![^f]oo)(bar)",[]))),
- <<"off">> = iolist_to_binary(join(re:split("offX","(?<![^f])X",[trim]))),
+ 2}]))),
+ <<"boobarX">> = iolist_to_binary(join(re:split("boobarX","(?<![^f]oo)(bar)",[]))),
+ <<"off">> = iolist_to_binary(join(re:split("offX","(?<![^f])X",[trim]))),
<<"off:">> = iolist_to_binary(join(re:split("offX","(?<![^f])X",[{parts,
- 2}]))),
- <<"off:">> = iolist_to_binary(join(re:split("offX","(?<![^f])X",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<![^f])X",[trim]))),
+ 2}]))),
+ <<"off:">> = iolist_to_binary(join(re:split("offX","(?<![^f])X",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<![^f])X",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<![^f])X",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<![^f])X",[]))),
- <<"onyX">> = iolist_to_binary(join(re:split("onyX","(?<![^f])X",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<![^f])X",[]))),
+ <<"onyX">> = iolist_to_binary(join(re:split("onyX","(?<![^f])X",[trim]))),
<<"onyX">> = iolist_to_binary(join(re:split("onyX","(?<![^f])X",[{parts,
- 2}]))),
- <<"onyX">> = iolist_to_binary(join(re:split("onyX","(?<![^f])X",[]))),
- <<"ony">> = iolist_to_binary(join(re:split("onyX","(?<=[^f])X",[trim]))),
+ 2}]))),
+ <<"onyX">> = iolist_to_binary(join(re:split("onyX","(?<![^f])X",[]))),
+ <<"ony">> = iolist_to_binary(join(re:split("onyX","(?<=[^f])X",[trim]))),
<<"ony:">> = iolist_to_binary(join(re:split("onyX","(?<=[^f])X",[{parts,
- 2}]))),
- <<"ony:">> = iolist_to_binary(join(re:split("onyX","(?<=[^f])X",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^f])X",[trim]))),
+ 2}]))),
+ <<"ony:">> = iolist_to_binary(join(re:split("onyX","(?<=[^f])X",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^f])X",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^f])X",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^f])X",[]))),
- <<"offX">> = iolist_to_binary(join(re:split("offX","(?<=[^f])X",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^f])X",[]))),
+ <<"offX">> = iolist_to_binary(join(re:split("offX","(?<=[^f])X",[trim]))),
<<"offX">> = iolist_to_binary(join(re:split("offX","(?<=[^f])X",[{parts,
- 2}]))),
- <<"offX">> = iolist_to_binary(join(re:split("offX","(?<=[^f])X",[]))),
+ 2}]))),
+ <<"offX">> = iolist_to_binary(join(re:split("offX","(?<=[^f])X",[]))),
<<"a
:b
:c">> = iolist_to_binary(join(re:split("a
b
-c","^",[multiline,trim]))),
+c","^",[multiline,trim]))),
<<"a
:b
c">> = iolist_to_binary(join(re:split("a
b
-c","^",[multiline,{parts,2}]))),
+c","^",[multiline,{parts,2}]))),
<<"a
:b
:c">> = iolist_to_binary(join(re:split("a
b
-c","^",[multiline]))),
+c","^",[multiline]))),
<<"">> = iolist_to_binary(join(re:split("","^",[multiline,
- trim]))),
+ trim]))),
<<"">> = iolist_to_binary(join(re:split("","^",[multiline,
{parts,
- 2}]))),
- <<"">> = iolist_to_binary(join(re:split("","^",[multiline]))),
+ 2}]))),
+ <<"">> = iolist_to_binary(join(re:split("","^",[multiline]))),
<<"A
C
:C">> = iolist_to_binary(join(re:split("A
C
-C","(?<=C\\n)^",[multiline,trim]))),
+C","(?<=C\\n)^",[multiline,trim]))),
<<"A
C
:C">> = iolist_to_binary(join(re:split("A
C
-C","(?<=C\\n)^",[multiline,{parts,2}]))),
+C","(?<=C\\n)^",[multiline,{parts,2}]))),
<<"A
C
:C">> = iolist_to_binary(join(re:split("A
C
-C","(?<=C\\n)^",[multiline]))),
- <<":X">> = iolist_to_binary(join(re:split("bXaX","(?:(?(1)a|b)(X))+",[trim]))),
+C","(?<=C\\n)^",[multiline]))),
+ <<":X">> = iolist_to_binary(join(re:split("bXaX","(?:(?(1)a|b)(X))+",[trim]))),
<<":X:">> = iolist_to_binary(join(re:split("bXaX","(?:(?(1)a|b)(X))+",[{parts,
- 2}]))),
- <<":X:">> = iolist_to_binary(join(re:split("bXaX","(?:(?(1)a|b)(X))+",[]))),
- <<":Y">> = iolist_to_binary(join(re:split("bXXaYYaY","(?:(?(1)\\1a|b)(X|Y))+",[trim]))),
+ 2}]))),
+ <<":X:">> = iolist_to_binary(join(re:split("bXaX","(?:(?(1)a|b)(X))+",[]))),
+ <<":Y">> = iolist_to_binary(join(re:split("bXXaYYaY","(?:(?(1)\\1a|b)(X|Y))+",[trim]))),
<<":Y:">> = iolist_to_binary(join(re:split("bXXaYYaY","(?:(?(1)\\1a|b)(X|Y))+",[{parts,
- 2}]))),
- <<":Y:">> = iolist_to_binary(join(re:split("bXXaYYaY","(?:(?(1)\\1a|b)(X|Y))+",[]))),
- <<":X:YaXXaX">> = iolist_to_binary(join(re:split("bXYaXXaX","(?:(?(1)\\1a|b)(X|Y))+",[trim]))),
+ 2}]))),
+ <<":Y:">> = iolist_to_binary(join(re:split("bXXaYYaY","(?:(?(1)\\1a|b)(X|Y))+",[]))),
+ <<":X:YaXXaX">> = iolist_to_binary(join(re:split("bXYaXXaX","(?:(?(1)\\1a|b)(X|Y))+",[trim]))),
<<":X:YaXXaX">> = iolist_to_binary(join(re:split("bXYaXXaX","(?:(?(1)\\1a|b)(X|Y))+",[{parts,
- 2}]))),
- <<":X:YaXXaX">> = iolist_to_binary(join(re:split("bXYaXXaX","(?:(?(1)\\1a|b)(X|Y))+",[]))),
- <<"::::::::::X:XaYYaY">> = iolist_to_binary(join(re:split("bXXaYYaY","()()()()()()()()()(?:(?(10)\\10a|b)(X|Y))+",[trim]))),
+ 2}]))),
+ <<":X:YaXXaX">> = iolist_to_binary(join(re:split("bXYaXXaX","(?:(?(1)\\1a|b)(X|Y))+",[]))),
+ <<"::::::::::X:XaYYaY">> = iolist_to_binary(join(re:split("bXXaYYaY","()()()()()()()()()(?:(?(10)\\10a|b)(X|Y))+",[trim]))),
<<"::::::::::X:XaYYaY">> = iolist_to_binary(join(re:split("bXXaYYaY","()()()()()()()()()(?:(?(10)\\10a|b)(X|Y))+",[{parts,
- 2}]))),
- <<"::::::::::X:XaYYaY">> = iolist_to_binary(join(re:split("bXXaYYaY","()()()()()()()()()(?:(?(10)\\10a|b)(X|Y))+",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc]","[[,abc,]+]",[trim]))),
+ 2}]))),
+ <<"::::::::::X:XaYYaY">> = iolist_to_binary(join(re:split("bXXaYYaY","()()()()()()()()()(?:(?(10)\\10a|b)(X|Y))+",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc]","[[,abc,]+]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc]","[[,abc,]+]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc]","[[,abc,]+]",[]))),
- <<"">> = iolist_to_binary(join(re:split("a,b]","[[,abc,]+]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc]","[[,abc,]+]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a,b]","[[,abc,]+]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a,b]","[[,abc,]+]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a,b]","[[,abc,]+]",[]))),
- <<"">> = iolist_to_binary(join(re:split("[a,b,c]","[[,abc,]+]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a,b]","[[,abc,]+]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("[a,b,c]","[[,abc,]+]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("[a,b,c]","[[,abc,]+]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("[a,b,c]","[[,abc,]+]",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("[a,b,c]","[[,abc,]+]",[]))),
<<"A:B">> = iolist_to_binary(join(re:split("A B","(?-x: )",[extended,
- trim]))),
+ trim]))),
<<"A:B">> = iolist_to_binary(join(re:split("A B","(?-x: )",[extended,
{parts,
- 2}]))),
- <<"A:B">> = iolist_to_binary(join(re:split("A B","(?-x: )",[extended]))),
- <<"A:B">> = iolist_to_binary(join(re:split("A # B","(?x)(?-x: \\s*#\\s*)",[trim]))),
+ 2}]))),
+ <<"A:B">> = iolist_to_binary(join(re:split("A B","(?-x: )",[extended]))),
+ <<"A:B">> = iolist_to_binary(join(re:split("A # B","(?x)(?-x: \\s*#\\s*)",[trim]))),
<<"A:B">> = iolist_to_binary(join(re:split("A # B","(?x)(?-x: \\s*#\\s*)",[{parts,
- 2}]))),
- <<"A:B">> = iolist_to_binary(join(re:split("A # B","(?x)(?-x: \\s*#\\s*)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?x)(?-x: \\s*#\\s*)",[trim]))),
+ 2}]))),
+ <<"A:B">> = iolist_to_binary(join(re:split("A # B","(?x)(?-x: \\s*#\\s*)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?x)(?-x: \\s*#\\s*)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?x)(?-x: \\s*#\\s*)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?x)(?-x: \\s*#\\s*)",[]))),
- <<"#">> = iolist_to_binary(join(re:split("#","(?x)(?-x: \\s*#\\s*)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?x)(?-x: \\s*#\\s*)",[]))),
+ <<"#">> = iolist_to_binary(join(re:split("#","(?x)(?-x: \\s*#\\s*)",[trim]))),
<<"#">> = iolist_to_binary(join(re:split("#","(?x)(?-x: \\s*#\\s*)",[{parts,
- 2}]))),
- <<"#">> = iolist_to_binary(join(re:split("#","(?x)(?-x: \\s*#\\s*)",[]))),
- <<"A">> = iolist_to_binary(join(re:split("A #include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[trim]))),
+ 2}]))),
+ <<"#">> = iolist_to_binary(join(re:split("#","(?x)(?-x: \\s*#\\s*)",[]))),
+ <<"A">> = iolist_to_binary(join(re:split("A #include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[trim]))),
<<"A:">> = iolist_to_binary(join(re:split("A #include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[{parts,
- 2}]))),
- <<"A:">> = iolist_to_binary(join(re:split("A #include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[trim]))),
+ 2}]))),
+ <<"A:">> = iolist_to_binary(join(re:split("A #include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[]))),
- <<"A#include">> = iolist_to_binary(join(re:split("A#include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[]))),
+ <<"A#include">> = iolist_to_binary(join(re:split("A#include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[trim]))),
<<"A#include">> = iolist_to_binary(join(re:split("A#include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[{parts,
- 2}]))),
- <<"A#include">> = iolist_to_binary(join(re:split("A#include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[]))),
- <<"A #Include">> = iolist_to_binary(join(re:split("A #Include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[trim]))),
+ 2}]))),
+ <<"A#include">> = iolist_to_binary(join(re:split("A#include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[]))),
+ <<"A #Include">> = iolist_to_binary(join(re:split("A #Include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[trim]))),
<<"A #Include">> = iolist_to_binary(join(re:split("A #Include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[{parts,
- 2}]))),
- <<"A #Include">> = iolist_to_binary(join(re:split("A #Include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[]))),
+ 2}]))),
+ <<"A #Include">> = iolist_to_binary(join(re:split("A #Include","(?x-is)(?:(?-ixs) \\s*#\\s*) include",[]))),
ok.
run35() ->
- <<"">> = iolist_to_binary(join(re:split("aaabbbb","a*b*\\w",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabbbb","a*b*\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabbbb","a*b*\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabbbb","a*b*\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaa","a*b*\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabbbb","a*b*\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaa","a*b*\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaa","a*b*\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaa","a*b*\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","a*b*\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaa","a*b*\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","a*b*\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","a*b*\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","a*b*\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabbbb","a*b?\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","a*b*\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabbbb","a*b?\\w",[trim]))),
<<":bb">> = iolist_to_binary(join(re:split("aaabbbb","a*b?\\w",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("aaabbbb","a*b?\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaa","a*b?\\w",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("aaabbbb","a*b?\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaa","a*b?\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaa","a*b?\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaa","a*b?\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","a*b?\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaa","a*b?\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","a*b?\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","a*b?\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","a*b?\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabbbb","a*b{0,4}\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","a*b?\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabbbb","a*b{0,4}\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabbbb","a*b{0,4}\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabbbb","a*b{0,4}\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaa","a*b{0,4}\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabbbb","a*b{0,4}\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaa","a*b{0,4}\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaa","a*b{0,4}\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaa","a*b{0,4}\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","a*b{0,4}\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaa","a*b{0,4}\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","a*b{0,4}\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","a*b{0,4}\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","a*b{0,4}\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaabbbb","a*b{0,}\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","a*b{0,4}\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaabbbb","a*b{0,}\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaabbbb","a*b{0,}\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaabbbb","a*b{0,}\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaa","a*b{0,}\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaabbbb","a*b{0,}\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaa","a*b{0,}\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaa","a*b{0,}\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaa","a*b{0,}\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","a*b{0,}\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaa","a*b{0,}\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","a*b{0,}\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","a*b{0,}\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","a*b{0,}\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("0a","a*\\d*\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","a*b{0,}\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("0a","a*\\d*\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("0a","a*\\d*\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("0a","a*\\d*\\w",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","a*\\d*\\w",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("0a","a*\\d*\\w",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","a*\\d*\\w",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","a*\\d*\\w",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","a*\\d*\\w",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","a*\\d*\\w",[]))),
<<"">> = iolist_to_binary(join(re:split("a","a*b *\\w",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("a","a*b *\\w",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","a*b *\\w",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","a*b *\\w",[extended]))),
<<"">> = iolist_to_binary(join(re:split("a","a*b#comment
- *\\w",[extended,trim]))),
+ *\\w",[extended,trim]))),
<<":">> = iolist_to_binary(join(re:split("a","a*b#comment
- *\\w",[extended,{parts,2}]))),
+ *\\w",[extended,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("a","a*b#comment
- *\\w",[extended]))),
+ *\\w",[extended]))),
<<"">> = iolist_to_binary(join(re:split("a","a* b *\\w",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("a","a* b *\\w",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","a* b *\\w",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","a* b *\\w",[extended]))),
<<"::
pqr">> = iolist_to_binary(join(re:split("abc=xyz\\
-pqr","^\\w+=.*(\\\\\\n.*)*",[trim]))),
+pqr","^\\w+=.*(\\\\\\n.*)*",[trim]))),
<<"::
pqr">> = iolist_to_binary(join(re:split("abc=xyz\\
-pqr","^\\w+=.*(\\\\\\n.*)*",[{parts,2}]))),
+pqr","^\\w+=.*(\\\\\\n.*)*",[{parts,2}]))),
<<"::
pqr">> = iolist_to_binary(join(re:split("abc=xyz\\
-pqr","^\\w+=.*(\\\\\\n.*)*",[]))),
- <<":abcd">> = iolist_to_binary(join(re:split("abcd:","(?=(\\w+))\\1:",[trim]))),
+pqr","^\\w+=.*(\\\\\\n.*)*",[]))),
+ <<":abcd">> = iolist_to_binary(join(re:split("abcd:","(?=(\\w+))\\1:",[trim]))),
<<":abcd:">> = iolist_to_binary(join(re:split("abcd:","(?=(\\w+))\\1:",[{parts,
- 2}]))),
- <<":abcd:">> = iolist_to_binary(join(re:split("abcd:","(?=(\\w+))\\1:",[]))),
- <<":abcd">> = iolist_to_binary(join(re:split("abcd:","^(?=(\\w+))\\1:",[trim]))),
+ 2}]))),
+ <<":abcd:">> = iolist_to_binary(join(re:split("abcd:","(?=(\\w+))\\1:",[]))),
+ <<":abcd">> = iolist_to_binary(join(re:split("abcd:","^(?=(\\w+))\\1:",[trim]))),
<<":abcd:">> = iolist_to_binary(join(re:split("abcd:","^(?=(\\w+))\\1:",[{parts,
- 2}]))),
- <<":abcd:">> = iolist_to_binary(join(re:split("abcd:","^(?=(\\w+))\\1:",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","^\\Eabc",[trim]))),
+ 2}]))),
+ <<":abcd:">> = iolist_to_binary(join(re:split("abcd:","^(?=(\\w+))\\1:",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","^\\Eabc",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","^\\Eabc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","^\\Eabc",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","^[\\Eabc]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","^\\Eabc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","^[\\Eabc]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","^[\\Eabc]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","^[\\Eabc]",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\Eabc]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","^[\\Eabc]",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\Eabc]",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\Eabc]",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\Eabc]",[]))),
- <<"E">> = iolist_to_binary(join(re:split("E","^[\\Eabc]",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\Eabc]",[]))),
+ <<"E">> = iolist_to_binary(join(re:split("E","^[\\Eabc]",[trim]))),
<<"E">> = iolist_to_binary(join(re:split("E","^[\\Eabc]",[{parts,
- 2}]))),
- <<"E">> = iolist_to_binary(join(re:split("E","^[\\Eabc]",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","^[a-\\Ec]",[trim]))),
+ 2}]))),
+ <<"E">> = iolist_to_binary(join(re:split("E","^[\\Eabc]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","^[a-\\Ec]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("b","^[a-\\Ec]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("b","^[a-\\Ec]",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[a-\\Ec]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("b","^[a-\\Ec]",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[a-\\Ec]",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[a-\\Ec]",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[a-\\Ec]",[]))),
- <<"-">> = iolist_to_binary(join(re:split("-","^[a-\\Ec]",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[a-\\Ec]",[]))),
+ <<"-">> = iolist_to_binary(join(re:split("-","^[a-\\Ec]",[trim]))),
<<"-">> = iolist_to_binary(join(re:split("-","^[a-\\Ec]",[{parts,
- 2}]))),
- <<"-">> = iolist_to_binary(join(re:split("-","^[a-\\Ec]",[]))),
- <<"E">> = iolist_to_binary(join(re:split("E","^[a-\\Ec]",[trim]))),
+ 2}]))),
+ <<"-">> = iolist_to_binary(join(re:split("-","^[a-\\Ec]",[]))),
+ <<"E">> = iolist_to_binary(join(re:split("E","^[a-\\Ec]",[trim]))),
<<"E">> = iolist_to_binary(join(re:split("E","^[a-\\Ec]",[{parts,
- 2}]))),
- <<"E">> = iolist_to_binary(join(re:split("E","^[a-\\Ec]",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","^[a\\E\\E-\\Ec]",[trim]))),
+ 2}]))),
+ <<"E">> = iolist_to_binary(join(re:split("E","^[a-\\Ec]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","^[a\\E\\E-\\Ec]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("b","^[a\\E\\E-\\Ec]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("b","^[a\\E\\E-\\Ec]",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[a\\E\\E-\\Ec]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("b","^[a\\E\\E-\\Ec]",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[a\\E\\E-\\Ec]",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[a\\E\\E-\\Ec]",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[a\\E\\E-\\Ec]",[]))),
- <<"-">> = iolist_to_binary(join(re:split("-","^[a\\E\\E-\\Ec]",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[a\\E\\E-\\Ec]",[]))),
+ <<"-">> = iolist_to_binary(join(re:split("-","^[a\\E\\E-\\Ec]",[trim]))),
<<"-">> = iolist_to_binary(join(re:split("-","^[a\\E\\E-\\Ec]",[{parts,
- 2}]))),
- <<"-">> = iolist_to_binary(join(re:split("-","^[a\\E\\E-\\Ec]",[]))),
- <<"E">> = iolist_to_binary(join(re:split("E","^[a\\E\\E-\\Ec]",[trim]))),
+ 2}]))),
+ <<"-">> = iolist_to_binary(join(re:split("-","^[a\\E\\E-\\Ec]",[]))),
+ <<"E">> = iolist_to_binary(join(re:split("E","^[a\\E\\E-\\Ec]",[trim]))),
<<"E">> = iolist_to_binary(join(re:split("E","^[a\\E\\E-\\Ec]",[{parts,
- 2}]))),
- <<"E">> = iolist_to_binary(join(re:split("E","^[a\\E\\E-\\Ec]",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","^[\\E\\Qa\\E-\\Qz\\E]+",[trim]))),
+ 2}]))),
+ <<"E">> = iolist_to_binary(join(re:split("E","^[a\\E\\E-\\Ec]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","^[\\E\\Qa\\E-\\Qz\\E]+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("b","^[\\E\\Qa\\E-\\Qz\\E]+",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("b","^[\\E\\Qa\\E-\\Qz\\E]+",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\E\\Qa\\E-\\Qz\\E]+",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("b","^[\\E\\Qa\\E-\\Qz\\E]+",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\E\\Qa\\E-\\Qz\\E]+",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\E\\Qa\\E-\\Qz\\E]+",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\E\\Qa\\E-\\Qz\\E]+",[]))),
- <<"-">> = iolist_to_binary(join(re:split("-","^[\\E\\Qa\\E-\\Qz\\E]+",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\E\\Qa\\E-\\Qz\\E]+",[]))),
+ <<"-">> = iolist_to_binary(join(re:split("-","^[\\E\\Qa\\E-\\Qz\\E]+",[trim]))),
<<"-">> = iolist_to_binary(join(re:split("-","^[\\E\\Qa\\E-\\Qz\\E]+",[{parts,
- 2}]))),
- <<"-">> = iolist_to_binary(join(re:split("-","^[\\E\\Qa\\E-\\Qz\\E]+",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","^[a\\Q]bc\\E]",[trim]))),
+ 2}]))),
+ <<"-">> = iolist_to_binary(join(re:split("-","^[\\E\\Qa\\E-\\Qz\\E]+",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","^[a\\Q]bc\\E]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","^[a\\Q]bc\\E]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","^[a\\Q]bc\\E]",[]))),
- <<"">> = iolist_to_binary(join(re:split("]","^[a\\Q]bc\\E]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","^[a\\Q]bc\\E]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("]","^[a\\Q]bc\\E]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("]","^[a\\Q]bc\\E]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("]","^[a\\Q]bc\\E]",[]))),
- <<"">> = iolist_to_binary(join(re:split("c","^[a\\Q]bc\\E]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("]","^[a\\Q]bc\\E]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("c","^[a\\Q]bc\\E]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("c","^[a\\Q]bc\\E]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("c","^[a\\Q]bc\\E]",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","^[a-\\Q\\E]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("c","^[a\\Q]bc\\E]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","^[a-\\Q\\E]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","^[a-\\Q\\E]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","^[a-\\Q\\E]",[]))),
- <<"">> = iolist_to_binary(join(re:split("-","^[a-\\Q\\E]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","^[a-\\Q\\E]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("-","^[a-\\Q\\E]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("-","^[a-\\Q\\E]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("-","^[a-\\Q\\E]",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaaa","^(a()*)*",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("-","^[a-\\Q\\E]",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaa","^(a()*)*",[trim]))),
<<":a::">> = iolist_to_binary(join(re:split("aaaa","^(a()*)*",[{parts,
- 2}]))),
- <<":a::">> = iolist_to_binary(join(re:split("aaaa","^(a()*)*",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaa","^(?:a(?:(?:))*)*",[trim]))),
+ 2}]))),
+ <<":a::">> = iolist_to_binary(join(re:split("aaaa","^(a()*)*",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaa","^(?:a(?:(?:))*)*",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaa","^(?:a(?:(?:))*)*",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaa","^(?:a(?:(?:))*)*",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaa","^(?:a(?:(?:))*)*",[]))),
ok.
run36() ->
- <<":a">> = iolist_to_binary(join(re:split("aaaa","^(a()+)+",[trim]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaa","^(a()+)+",[trim]))),
<<":a::">> = iolist_to_binary(join(re:split("aaaa","^(a()+)+",[{parts,
- 2}]))),
- <<":a::">> = iolist_to_binary(join(re:split("aaaa","^(a()+)+",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaa","^(?:a(?:(?:))+)+",[trim]))),
+ 2}]))),
+ <<":a::">> = iolist_to_binary(join(re:split("aaaa","^(a()+)+",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaa","^(?:a(?:(?:))+)+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaa","^(?:a(?:(?:))+)+",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaa","^(?:a(?:(?:))+)+",[]))),
- <<":a">> = iolist_to_binary(join(re:split("abbD","(a){0,3}(?(1)b|(c|))*D",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaa","^(?:a(?:(?:))+)+",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("abbD","(a){0,3}(?(1)b|(c|))*D",[trim]))),
<<":a::">> = iolist_to_binary(join(re:split("abbD","(a){0,3}(?(1)b|(c|))*D",[{parts,
- 2}]))),
- <<":a::">> = iolist_to_binary(join(re:split("abbD","(a){0,3}(?(1)b|(c|))*D",[]))),
- <<"">> = iolist_to_binary(join(re:split("ccccD","(a){0,3}(?(1)b|(c|))*D",[trim]))),
+ 2}]))),
+ <<":a::">> = iolist_to_binary(join(re:split("abbD","(a){0,3}(?(1)b|(c|))*D",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ccccD","(a){0,3}(?(1)b|(c|))*D",[trim]))),
<<":::">> = iolist_to_binary(join(re:split("ccccD","(a){0,3}(?(1)b|(c|))*D",[{parts,
- 2}]))),
- <<":::">> = iolist_to_binary(join(re:split("ccccD","(a){0,3}(?(1)b|(c|))*D",[]))),
- <<"">> = iolist_to_binary(join(re:split("D","(a){0,3}(?(1)b|(c|))*D",[trim]))),
+ 2}]))),
+ <<":::">> = iolist_to_binary(join(re:split("ccccD","(a){0,3}(?(1)b|(c|))*D",[]))),
+ <<"">> = iolist_to_binary(join(re:split("D","(a){0,3}(?(1)b|(c|))*D",[trim]))),
<<":::">> = iolist_to_binary(join(re:split("D","(a){0,3}(?(1)b|(c|))*D",[{parts,
- 2}]))),
- <<":::">> = iolist_to_binary(join(re:split("D","(a){0,3}(?(1)b|(c|))*D",[]))),
- <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a|)*\\d",[trim]))),
+ 2}]))),
+ <<":::">> = iolist_to_binary(join(re:split("D","(a){0,3}(?(1)b|(c|))*D",[]))),
+ <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a|)*\\d",[trim]))),
<<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a|)*\\d",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a|)*\\d",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(a|)*\\d",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(a|)*\\d",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(a|)*\\d",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(a|)*\\d",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(a|)*\\d",[]))),
- <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(?>a|)*\\d",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(a|)*\\d",[]))),
+ <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(?>a|)*\\d",[trim]))),
<<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(?>a|)*\\d",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(?>a|)*\\d",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(?>a|)*\\d",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(?>a|)*\\d",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(?>a|)*\\d",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(?>a|)*\\d",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(?>a|)*\\d",[]))),
- <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(?:a|)*\\d",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(?>a|)*\\d",[]))),
+ <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(?:a|)*\\d",[trim]))),
<<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(?:a|)*\\d",[{parts,
- 2}]))),
- <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(?:a|)*\\d",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(?:a|)*\\d",[trim]))),
+ 2}]))),
+ <<"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","(?:a|)*\\d",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(?:a|)*\\d",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(?:a|)*\\d",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(?:a|)*\\d",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","\\Z",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa4","(?:a|)*\\d",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","\\Z",[trim]))),
<<"abc:">> = iolist_to_binary(join(re:split("abc","\\Z",[{parts,
- 2}]))),
- <<"abc:">> = iolist_to_binary(join(re:split("abc","\\Z",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","^(?s)(?>.*)(?<!\\n)",[trim]))),
+ 2}]))),
+ <<"abc:">> = iolist_to_binary(join(re:split("abc","\\Z",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","^(?s)(?>.*)(?<!\\n)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","^(?s)(?>.*)(?<!\\n)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","^(?s)(?>.*)(?<!\\n)",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","^(?s)(?>.*)(?<!\\n)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","^(?s)(?>.*)(?<!\\n)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","^(?s)(?>.*)(?<!\\n)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","^(?s)(?>.*)(?<!\\n)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","^(?s)(?>.*)(?<!\\n)",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^(?![^\\n]*\\n\\z)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","^(?s)(?>.*)(?<!\\n)",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^(?![^\\n]*\\n\\z)",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","^(?![^\\n]*\\n\\z)",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^(?![^\\n]*\\n\\z)",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^(?![^\\n]*\\n\\z)",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^(?![^\\n]*\\n\\z)",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^(?![^\\n]*\\n\\z)",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","^(?![^\\n]*\\n\\z)",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","^(?![^\\n]*\\n\\z)",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","\\z(?<!\\n)",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","^(?![^\\n]*\\n\\z)",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","\\z(?<!\\n)",[trim]))),
<<"abc:">> = iolist_to_binary(join(re:split("abc","\\z(?<!\\n)",[{parts,
- 2}]))),
- <<"abc:">> = iolist_to_binary(join(re:split("abc","\\z(?<!\\n)",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","\\z(?<!\\n)",[trim]))),
+ 2}]))),
+ <<"abc:">> = iolist_to_binary(join(re:split("abc","\\z(?<!\\n)",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","\\z(?<!\\n)",[trim]))),
<<"abc:">> = iolist_to_binary(join(re:split("abc","\\z(?<!\\n)",[{parts,
- 2}]))),
- <<"abc:">> = iolist_to_binary(join(re:split("abc","\\z(?<!\\n)",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcd","(.*(.)?)*",[trim]))),
+ 2}]))),
+ <<"abc:">> = iolist_to_binary(join(re:split("abc","\\z(?<!\\n)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcd","(.*(.)?)*",[trim]))),
<<":::">> = iolist_to_binary(join(re:split("abcd","(.*(.)?)*",[{parts,
- 2}]))),
- <<":::">> = iolist_to_binary(join(re:split("abcd","(.*(.)?)*",[]))),
+ 2}]))),
+ <<":::">> = iolist_to_binary(join(re:split("abcd","(.*(.)?)*",[]))),
<<"a:::b:::c:::d">> = iolist_to_binary(join(re:split("abcd","( (A | (?(1)0|) )* )",[extended,
- trim]))),
+ trim]))),
<<"a:::bcd">> = iolist_to_binary(join(re:split("abcd","( (A | (?(1)0|) )* )",[extended,
{parts,
- 2}]))),
- <<"a:::b:::c:::d:::">> = iolist_to_binary(join(re:split("abcd","( (A | (?(1)0|) )* )",[extended]))),
+ 2}]))),
+ <<"a:::b:::c:::d:::">> = iolist_to_binary(join(re:split("abcd","( (A | (?(1)0|) )* )",[extended]))),
<<"a:::b:::c:::d">> = iolist_to_binary(join(re:split("abcd","( ( (?(1)0|) )* )",[extended,
- trim]))),
+ trim]))),
<<"a:::bcd">> = iolist_to_binary(join(re:split("abcd","( ( (?(1)0|) )* )",[extended,
{parts,
- 2}]))),
- <<"a:::b:::c:::d:::">> = iolist_to_binary(join(re:split("abcd","( ( (?(1)0|) )* )",[extended]))),
+ 2}]))),
+ <<"a:::b:::c:::d:::">> = iolist_to_binary(join(re:split("abcd","( ( (?(1)0|) )* )",[extended]))),
<<"a::b::c::d">> = iolist_to_binary(join(re:split("abcd","( (?(1)0|)* )",[extended,
- trim]))),
+ trim]))),
<<"a::bcd">> = iolist_to_binary(join(re:split("abcd","( (?(1)0|)* )",[extended,
{parts,
- 2}]))),
- <<"a::b::c::d::">> = iolist_to_binary(join(re:split("abcd","( (?(1)0|)* )",[extended]))),
- <<"">> = iolist_to_binary(join(re:split("a]","[[:abcd:xyz]]",[trim]))),
+ 2}]))),
+ <<"a::b::c::d::">> = iolist_to_binary(join(re:split("abcd","( (?(1)0|)* )",[extended]))),
+ <<"">> = iolist_to_binary(join(re:split("a]","[[:abcd:xyz]]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a]","[[:abcd:xyz]]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a]","[[:abcd:xyz]]",[]))),
- <<"">> = iolist_to_binary(join(re:split(":]","[[:abcd:xyz]]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a]","[[:abcd:xyz]]",[]))),
+ <<"">> = iolist_to_binary(join(re:split(":]","[[:abcd:xyz]]",[trim]))),
<<":">> = iolist_to_binary(join(re:split(":]","[[:abcd:xyz]]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split(":]","[[:abcd:xyz]]",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","[abc[:x\\]pqr]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split(":]","[[:abcd:xyz]]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","[abc[:x\\]pqr]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("a","[abc[:x\\]pqr]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("a","[abc[:x\\]pqr]",[]))),
- <<"">> = iolist_to_binary(join(re:split("[","[abc[:x\\]pqr]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("a","[abc[:x\\]pqr]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("[","[abc[:x\\]pqr]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("[","[abc[:x\\]pqr]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("[","[abc[:x\\]pqr]",[]))),
- <<"">> = iolist_to_binary(join(re:split(":","[abc[:x\\]pqr]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("[","[abc[:x\\]pqr]",[]))),
+ <<"">> = iolist_to_binary(join(re:split(":","[abc[:x\\]pqr]",[trim]))),
<<":">> = iolist_to_binary(join(re:split(":","[abc[:x\\]pqr]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split(":","[abc[:x\\]pqr]",[]))),
- <<"">> = iolist_to_binary(join(re:split("]","[abc[:x\\]pqr]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split(":","[abc[:x\\]pqr]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("]","[abc[:x\\]pqr]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("]","[abc[:x\\]pqr]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("]","[abc[:x\\]pqr]",[]))),
- <<"">> = iolist_to_binary(join(re:split("p","[abc[:x\\]pqr]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("]","[abc[:x\\]pqr]",[]))),
+ <<"">> = iolist_to_binary(join(re:split("p","[abc[:x\\]pqr]",[trim]))),
<<":">> = iolist_to_binary(join(re:split("p","[abc[:x\\]pqr]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("p","[abc[:x\\]pqr]",[]))),
- <<"fooabcfoo">> = iolist_to_binary(join(re:split("fooabcfoo",".*[op][xyz]",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("p","[abc[:x\\]pqr]",[]))),
+ <<"fooabcfoo">> = iolist_to_binary(join(re:split("fooabcfoo",".*[op][xyz]",[trim]))),
<<"fooabcfoo">> = iolist_to_binary(join(re:split("fooabcfoo",".*[op][xyz]",[{parts,
- 2}]))),
- <<"fooabcfoo">> = iolist_to_binary(join(re:split("fooabcfoo",".*[op][xyz]",[]))),
- <<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)",[trim]))),
+ 2}]))),
+ <<"fooabcfoo">> = iolist_to_binary(join(re:split("fooabcfoo",".*[op][xyz]",[]))),
+ <<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)",[trim]))),
<<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)",[{parts,
- 2}]))),
- <<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)",[]))),
- <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)",[trim]))),
+ 2}]))),
+ <<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)",[]))),
+ <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)",[trim]))),
<<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)",[{parts,
- 2}]))),
- <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)",[]))),
- <<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=^.*b)b|^)",[trim]))),
+ 2}]))),
+ <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)",[]))),
+ <<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=^.*b)b|^)",[trim]))),
<<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=^.*b)b|^)",[{parts,
- 2}]))),
- <<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=^.*b)b|^)",[]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(?(?=^.*b)b|^)",[trim]))),
+ 2}]))),
+ <<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=^.*b)b|^)",[]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(?(?=^.*b)b|^)",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","(?(?=^.*b)b|^)",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(?(?=^.*b)b|^)",[]))),
- <<"a:d:c">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)*",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(?(?=^.*b)b|^)",[]))),
+ <<"a:d:c">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)*",[trim]))),
<<"a:dc">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)*",[{parts,
- 2}]))),
- <<"a:d:c:">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)*",[]))),
- <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)*",[trim]))),
+ 2}]))),
+ <<"a:d:c:">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)*",[]))),
+ <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)*",[trim]))),
<<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)*",[{parts,
- 2}]))),
- <<"a:c:">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)*",[]))),
+ 2}]))),
+ <<"a:c:">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)*",[]))),
ok.
run37() ->
- <<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)+",[trim]))),
+ <<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)+",[trim]))),
<<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)+",[{parts,
- 2}]))),
- <<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)+",[]))),
- <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)+",[trim]))),
+ 2}]))),
+ <<"adc">> = iolist_to_binary(join(re:split("adc","(?(?=.*b)b|^)+",[]))),
+ <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)+",[trim]))),
<<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)+",[{parts,
- 2}]))),
- <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)+",[]))),
- <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=b).*b|^d)",[trim]))),
+ 2}]))),
+ <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b)b|^)+",[]))),
+ <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=b).*b|^d)",[trim]))),
<<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=b).*b|^d)",[{parts,
- 2}]))),
- <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=b).*b|^d)",[]))),
- <<":c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b).*b|^d)",[trim]))),
+ 2}]))),
+ <<"a:c">> = iolist_to_binary(join(re:split("abc","(?(?=b).*b|^d)",[]))),
+ <<":c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b).*b|^d)",[trim]))),
<<":c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b).*b|^d)",[{parts,
- 2}]))),
- <<":c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b).*b|^d)",[]))),
- <<"">> = iolist_to_binary(join(re:split("%ab%","^%((?(?=[a])[^%])|b)*%$",[trim]))),
+ 2}]))),
+ <<":c">> = iolist_to_binary(join(re:split("abc","(?(?=.*b).*b|^d)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("%ab%","^%((?(?=[a])[^%])|b)*%$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("%ab%","^%((?(?=[a])[^%])|b)*%$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("%ab%","^%((?(?=[a])[^%])|b)*%$",[]))),
- <<"X:X">> = iolist_to_binary(join(re:split("XabX","(?i)a(?-i)b|c",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("%ab%","^%((?(?=[a])[^%])|b)*%$",[]))),
+ <<"X:X">> = iolist_to_binary(join(re:split("XabX","(?i)a(?-i)b|c",[trim]))),
<<"X:X">> = iolist_to_binary(join(re:split("XabX","(?i)a(?-i)b|c",[{parts,
- 2}]))),
- <<"X:X">> = iolist_to_binary(join(re:split("XabX","(?i)a(?-i)b|c",[]))),
- <<"X:X">> = iolist_to_binary(join(re:split("XAbX","(?i)a(?-i)b|c",[trim]))),
+ 2}]))),
+ <<"X:X">> = iolist_to_binary(join(re:split("XabX","(?i)a(?-i)b|c",[]))),
+ <<"X:X">> = iolist_to_binary(join(re:split("XAbX","(?i)a(?-i)b|c",[trim]))),
<<"X:X">> = iolist_to_binary(join(re:split("XAbX","(?i)a(?-i)b|c",[{parts,
- 2}]))),
- <<"X:X">> = iolist_to_binary(join(re:split("XAbX","(?i)a(?-i)b|c",[]))),
- <<"C:C">> = iolist_to_binary(join(re:split("CcC","(?i)a(?-i)b|c",[trim]))),
+ 2}]))),
+ <<"X:X">> = iolist_to_binary(join(re:split("XAbX","(?i)a(?-i)b|c",[]))),
+ <<"C:C">> = iolist_to_binary(join(re:split("CcC","(?i)a(?-i)b|c",[trim]))),
<<"C:C">> = iolist_to_binary(join(re:split("CcC","(?i)a(?-i)b|c",[{parts,
- 2}]))),
- <<"C:C">> = iolist_to_binary(join(re:split("CcC","(?i)a(?-i)b|c",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?i)a(?-i)b|c",[trim]))),
+ 2}]))),
+ <<"C:C">> = iolist_to_binary(join(re:split("CcC","(?i)a(?-i)b|c",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?i)a(?-i)b|c",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?i)a(?-i)b|c",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?i)a(?-i)b|c",[]))),
- <<"XABX">> = iolist_to_binary(join(re:split("XABX","(?i)a(?-i)b|c",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?i)a(?-i)b|c",[]))),
+ <<"XABX">> = iolist_to_binary(join(re:split("XABX","(?i)a(?-i)b|c",[trim]))),
<<"XABX">> = iolist_to_binary(join(re:split("XABX","(?i)a(?-i)b|c",[{parts,
- 2}]))),
- <<"XABX">> = iolist_to_binary(join(re:split("XABX","(?i)a(?-i)b|c",[]))),
+ 2}]))),
+ <<"XABX">> = iolist_to_binary(join(re:split("XABX","(?i)a(?-i)b|c",[]))),
<<"">> = iolist_to_binary(join(re:split("
- ","[\\x00-\\xff\\s]+",[trim]))),
+ ","[\\x00-\\xff\\s]+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("
- ","[\\x00-\\xff\\s]+",[{parts,2}]))),
+ ","[\\x00-\\xff\\s]+",[{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("
- ","[\\x00-\\xff\\s]+",[]))),
+ ","[\\x00-\\xff\\s]+",[]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1",[caseless,
- trim]))),
+ trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1",[caseless,
{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1",[caseless]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1",[trim]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1",[caseless]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1",[trim]))),
<<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1",[{parts,
- 2}]))),
- <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1",[]))),
+ 2}]))),
+ <<"abc">> = iolist_to_binary(join(re:split("abc","(abc)\\1",[]))),
<<":a">> = iolist_to_binary(join(re:split("12abc","[^a]*",[caseless,
- trim]))),
+ trim]))),
<<":abc">> = iolist_to_binary(join(re:split("12abc","[^a]*",[caseless,
{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("12abc","[^a]*",[caseless]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("12abc","[^a]*",[caseless]))),
<<":A">> = iolist_to_binary(join(re:split("12ABC","[^a]*",[caseless,
- trim]))),
+ trim]))),
<<":ABC">> = iolist_to_binary(join(re:split("12ABC","[^a]*",[caseless,
{parts,
- 2}]))),
- <<":A:">> = iolist_to_binary(join(re:split("12ABC","[^a]*",[caseless]))),
+ 2}]))),
+ <<":A:">> = iolist_to_binary(join(re:split("12ABC","[^a]*",[caseless]))),
<<":a">> = iolist_to_binary(join(re:split("12abc","[^a]*+",[caseless,
- trim]))),
+ trim]))),
<<":abc">> = iolist_to_binary(join(re:split("12abc","[^a]*+",[caseless,
{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("12abc","[^a]*+",[caseless]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("12abc","[^a]*+",[caseless]))),
<<":A">> = iolist_to_binary(join(re:split("12ABC","[^a]*+",[caseless,
- trim]))),
+ trim]))),
<<":ABC">> = iolist_to_binary(join(re:split("12ABC","[^a]*+",[caseless,
{parts,
- 2}]))),
- <<":A:">> = iolist_to_binary(join(re:split("12ABC","[^a]*+",[caseless]))),
+ 2}]))),
+ <<":A:">> = iolist_to_binary(join(re:split("12ABC","[^a]*+",[caseless]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","[^a]*?X",[caseless,
- trim]))),
+ trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","[^a]*?X",[caseless,
{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","[^a]*?X",[caseless]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","[^a]*?X",[caseless]))),
<<"12abc">> = iolist_to_binary(join(re:split("12abc","[^a]*?X",[caseless,
- trim]))),
+ trim]))),
<<"12abc">> = iolist_to_binary(join(re:split("12abc","[^a]*?X",[caseless,
{parts,
- 2}]))),
- <<"12abc">> = iolist_to_binary(join(re:split("12abc","[^a]*?X",[caseless]))),
+ 2}]))),
+ <<"12abc">> = iolist_to_binary(join(re:split("12abc","[^a]*?X",[caseless]))),
<<"12ABC">> = iolist_to_binary(join(re:split("12ABC","[^a]*?X",[caseless,
- trim]))),
+ trim]))),
<<"12ABC">> = iolist_to_binary(join(re:split("12ABC","[^a]*?X",[caseless,
{parts,
- 2}]))),
- <<"12ABC">> = iolist_to_binary(join(re:split("12ABC","[^a]*?X",[caseless]))),
+ 2}]))),
+ <<"12ABC">> = iolist_to_binary(join(re:split("12ABC","[^a]*?X",[caseless]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","[^a]+?X",[caseless,
- trim]))),
+ trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","[^a]+?X",[caseless,
{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","[^a]+?X",[caseless]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","[^a]+?X",[caseless]))),
<<"12abc">> = iolist_to_binary(join(re:split("12abc","[^a]+?X",[caseless,
- trim]))),
+ trim]))),
<<"12abc">> = iolist_to_binary(join(re:split("12abc","[^a]+?X",[caseless,
{parts,
- 2}]))),
- <<"12abc">> = iolist_to_binary(join(re:split("12abc","[^a]+?X",[caseless]))),
+ 2}]))),
+ <<"12abc">> = iolist_to_binary(join(re:split("12abc","[^a]+?X",[caseless]))),
<<"12ABC">> = iolist_to_binary(join(re:split("12ABC","[^a]+?X",[caseless,
- trim]))),
+ trim]))),
<<"12ABC">> = iolist_to_binary(join(re:split("12ABC","[^a]+?X",[caseless,
{parts,
- 2}]))),
- <<"12ABC">> = iolist_to_binary(join(re:split("12ABC","[^a]+?X",[caseless]))),
+ 2}]))),
+ <<"12ABC">> = iolist_to_binary(join(re:split("12ABC","[^a]+?X",[caseless]))),
<<"12a:b">> = iolist_to_binary(join(re:split("12aXbcX","[^a]?X",[caseless,
- trim]))),
+ trim]))),
<<"12a:bcX">> = iolist_to_binary(join(re:split("12aXbcX","[^a]?X",[caseless,
{parts,
- 2}]))),
- <<"12a:b:">> = iolist_to_binary(join(re:split("12aXbcX","[^a]?X",[caseless]))),
+ 2}]))),
+ <<"12a:b:">> = iolist_to_binary(join(re:split("12aXbcX","[^a]?X",[caseless]))),
<<"12A:B">> = iolist_to_binary(join(re:split("12AXBCX","[^a]?X",[caseless,
- trim]))),
+ trim]))),
<<"12A:BCX">> = iolist_to_binary(join(re:split("12AXBCX","[^a]?X",[caseless,
{parts,
- 2}]))),
- <<"12A:B:">> = iolist_to_binary(join(re:split("12AXBCX","[^a]?X",[caseless]))),
+ 2}]))),
+ <<"12A:B:">> = iolist_to_binary(join(re:split("12AXBCX","[^a]?X",[caseless]))),
<<"B">> = iolist_to_binary(join(re:split("BCX","[^a]?X",[caseless,
- trim]))),
+ trim]))),
<<"B:">> = iolist_to_binary(join(re:split("BCX","[^a]?X",[caseless,
{parts,
- 2}]))),
- <<"B:">> = iolist_to_binary(join(re:split("BCX","[^a]?X",[caseless]))),
+ 2}]))),
+ <<"B:">> = iolist_to_binary(join(re:split("BCX","[^a]?X",[caseless]))),
<<"12a:b">> = iolist_to_binary(join(re:split("12aXbcX","[^a]??X",[caseless,
- trim]))),
+ trim]))),
<<"12a:bcX">> = iolist_to_binary(join(re:split("12aXbcX","[^a]??X",[caseless,
{parts,
- 2}]))),
- <<"12a:b:">> = iolist_to_binary(join(re:split("12aXbcX","[^a]??X",[caseless]))),
+ 2}]))),
+ <<"12a:b:">> = iolist_to_binary(join(re:split("12aXbcX","[^a]??X",[caseless]))),
<<"12A:B">> = iolist_to_binary(join(re:split("12AXBCX","[^a]??X",[caseless,
- trim]))),
+ trim]))),
<<"12A:BCX">> = iolist_to_binary(join(re:split("12AXBCX","[^a]??X",[caseless,
{parts,
- 2}]))),
- <<"12A:B:">> = iolist_to_binary(join(re:split("12AXBCX","[^a]??X",[caseless]))),
+ 2}]))),
+ <<"12A:B:">> = iolist_to_binary(join(re:split("12AXBCX","[^a]??X",[caseless]))),
<<"B">> = iolist_to_binary(join(re:split("BCX","[^a]??X",[caseless,
- trim]))),
+ trim]))),
<<"B:">> = iolist_to_binary(join(re:split("BCX","[^a]??X",[caseless,
{parts,
- 2}]))),
- <<"B:">> = iolist_to_binary(join(re:split("BCX","[^a]??X",[caseless]))),
+ 2}]))),
+ <<"B:">> = iolist_to_binary(join(re:split("BCX","[^a]??X",[caseless]))),
<<"12aXb">> = iolist_to_binary(join(re:split("12aXbcX","[^a]?+X",[caseless,
- trim]))),
+ trim]))),
<<"12aXb:">> = iolist_to_binary(join(re:split("12aXbcX","[^a]?+X",[caseless,
{parts,
- 2}]))),
- <<"12aXb:">> = iolist_to_binary(join(re:split("12aXbcX","[^a]?+X",[caseless]))),
+ 2}]))),
+ <<"12aXb:">> = iolist_to_binary(join(re:split("12aXbcX","[^a]?+X",[caseless]))),
<<"12AXB">> = iolist_to_binary(join(re:split("12AXBCX","[^a]?+X",[caseless,
- trim]))),
+ trim]))),
<<"12AXB:">> = iolist_to_binary(join(re:split("12AXBCX","[^a]?+X",[caseless,
{parts,
- 2}]))),
- <<"12AXB:">> = iolist_to_binary(join(re:split("12AXBCX","[^a]?+X",[caseless]))),
+ 2}]))),
+ <<"12AXB:">> = iolist_to_binary(join(re:split("12AXBCX","[^a]?+X",[caseless]))),
<<"B">> = iolist_to_binary(join(re:split("BCX","[^a]?+X",[caseless,
- trim]))),
+ trim]))),
<<"B:">> = iolist_to_binary(join(re:split("BCX","[^a]?+X",[caseless,
{parts,
- 2}]))),
- <<"B:">> = iolist_to_binary(join(re:split("BCX","[^a]?+X",[caseless]))),
+ 2}]))),
+ <<"B:">> = iolist_to_binary(join(re:split("BCX","[^a]?+X",[caseless]))),
<<"a">> = iolist_to_binary(join(re:split("abcdef","[^a]{2,3}",[caseless,
- trim]))),
+ trim]))),
<<"a:ef">> = iolist_to_binary(join(re:split("abcdef","[^a]{2,3}",[caseless,
{parts,
- 2}]))),
- <<"a::">> = iolist_to_binary(join(re:split("abcdef","[^a]{2,3}",[caseless]))),
+ 2}]))),
+ <<"a::">> = iolist_to_binary(join(re:split("abcdef","[^a]{2,3}",[caseless]))),
<<"A">> = iolist_to_binary(join(re:split("ABCDEF","[^a]{2,3}",[caseless,
- trim]))),
+ trim]))),
<<"A:EF">> = iolist_to_binary(join(re:split("ABCDEF","[^a]{2,3}",[caseless,
{parts,
- 2}]))),
- <<"A::">> = iolist_to_binary(join(re:split("ABCDEF","[^a]{2,3}",[caseless]))),
+ 2}]))),
+ <<"A::">> = iolist_to_binary(join(re:split("ABCDEF","[^a]{2,3}",[caseless]))),
<<"a::f">> = iolist_to_binary(join(re:split("abcdef","[^a]{2,3}?",[caseless,
- trim]))),
+ trim]))),
<<"a:def">> = iolist_to_binary(join(re:split("abcdef","[^a]{2,3}?",[caseless,
{parts,
- 2}]))),
- <<"a::f">> = iolist_to_binary(join(re:split("abcdef","[^a]{2,3}?",[caseless]))),
+ 2}]))),
+ <<"a::f">> = iolist_to_binary(join(re:split("abcdef","[^a]{2,3}?",[caseless]))),
<<"A::F">> = iolist_to_binary(join(re:split("ABCDEF","[^a]{2,3}?",[caseless,
- trim]))),
+ trim]))),
<<"A:DEF">> = iolist_to_binary(join(re:split("ABCDEF","[^a]{2,3}?",[caseless,
{parts,
- 2}]))),
- <<"A::F">> = iolist_to_binary(join(re:split("ABCDEF","[^a]{2,3}?",[caseless]))),
+ 2}]))),
+ <<"A::F">> = iolist_to_binary(join(re:split("ABCDEF","[^a]{2,3}?",[caseless]))),
<<"a">> = iolist_to_binary(join(re:split("abcdef","[^a]{2,3}+",[caseless,
- trim]))),
+ trim]))),
<<"a:ef">> = iolist_to_binary(join(re:split("abcdef","[^a]{2,3}+",[caseless,
{parts,
- 2}]))),
- <<"a::">> = iolist_to_binary(join(re:split("abcdef","[^a]{2,3}+",[caseless]))),
+ 2}]))),
+ <<"a::">> = iolist_to_binary(join(re:split("abcdef","[^a]{2,3}+",[caseless]))),
<<"A">> = iolist_to_binary(join(re:split("ABCDEF","[^a]{2,3}+",[caseless,
- trim]))),
+ trim]))),
<<"A:EF">> = iolist_to_binary(join(re:split("ABCDEF","[^a]{2,3}+",[caseless,
{parts,
- 2}]))),
- <<"A::">> = iolist_to_binary(join(re:split("ABCDEF","[^a]{2,3}+",[caseless]))),
- <<"">> = iolist_to_binary(join(re:split("Z","((a|)+)+Z",[trim]))),
+ 2}]))),
+ <<"A::">> = iolist_to_binary(join(re:split("ABCDEF","[^a]{2,3}+",[caseless]))),
+ <<"">> = iolist_to_binary(join(re:split("Z","((a|)+)+Z",[trim]))),
<<":::">> = iolist_to_binary(join(re:split("Z","((a|)+)+Z",[{parts,
- 2}]))),
- <<":::">> = iolist_to_binary(join(re:split("Z","((a|)+)+Z",[]))),
+ 2}]))),
+ <<":::">> = iolist_to_binary(join(re:split("Z","((a|)+)+Z",[]))),
ok.
run38() ->
- <<"::a">> = iolist_to_binary(join(re:split("ac","(a)b|(a)c",[trim]))),
+ <<"::a">> = iolist_to_binary(join(re:split("ac","(a)b|(a)c",[trim]))),
<<"::a:">> = iolist_to_binary(join(re:split("ac","(a)b|(a)c",[{parts,
- 2}]))),
- <<"::a:">> = iolist_to_binary(join(re:split("ac","(a)b|(a)c",[]))),
- <<"::a">> = iolist_to_binary(join(re:split("ac","(?>(a))b|(a)c",[trim]))),
+ 2}]))),
+ <<"::a:">> = iolist_to_binary(join(re:split("ac","(a)b|(a)c",[]))),
+ <<"::a">> = iolist_to_binary(join(re:split("ac","(?>(a))b|(a)c",[trim]))),
<<"::a:">> = iolist_to_binary(join(re:split("ac","(?>(a))b|(a)c",[{parts,
- 2}]))),
- <<"::a:">> = iolist_to_binary(join(re:split("ac","(?>(a))b|(a)c",[]))),
- <<"::a">> = iolist_to_binary(join(re:split("ac","(?=(a))ab|(a)c",[trim]))),
+ 2}]))),
+ <<"::a:">> = iolist_to_binary(join(re:split("ac","(?>(a))b|(a)c",[]))),
+ <<"::a">> = iolist_to_binary(join(re:split("ac","(?=(a))ab|(a)c",[trim]))),
<<"::a:">> = iolist_to_binary(join(re:split("ac","(?=(a))ab|(a)c",[{parts,
- 2}]))),
- <<"::a:">> = iolist_to_binary(join(re:split("ac","(?=(a))ab|(a)c",[]))),
- <<":ac::a">> = iolist_to_binary(join(re:split("ac","((?>(a))b|(a)c)",[trim]))),
+ 2}]))),
+ <<"::a:">> = iolist_to_binary(join(re:split("ac","(?=(a))ab|(a)c",[]))),
+ <<":ac::a">> = iolist_to_binary(join(re:split("ac","((?>(a))b|(a)c)",[trim]))),
<<":ac::a:">> = iolist_to_binary(join(re:split("ac","((?>(a))b|(a)c)",[{parts,
- 2}]))),
- <<":ac::a:">> = iolist_to_binary(join(re:split("ac","((?>(a))b|(a)c)",[]))),
- <<":ac::a">> = iolist_to_binary(join(re:split("ac","((?>(a))b|(a)c)++",[trim]))),
+ 2}]))),
+ <<":ac::a:">> = iolist_to_binary(join(re:split("ac","((?>(a))b|(a)c)",[]))),
+ <<":ac::a">> = iolist_to_binary(join(re:split("ac","((?>(a))b|(a)c)++",[trim]))),
<<":ac::a:">> = iolist_to_binary(join(re:split("ac","((?>(a))b|(a)c)++",[{parts,
- 2}]))),
- <<":ac::a:">> = iolist_to_binary(join(re:split("ac","((?>(a))b|(a)c)++",[]))),
- <<"::a">> = iolist_to_binary(join(re:split("ac","(?:(?>(a))b|(a)c)++",[trim]))),
+ 2}]))),
+ <<":ac::a:">> = iolist_to_binary(join(re:split("ac","((?>(a))b|(a)c)++",[]))),
+ <<"::a">> = iolist_to_binary(join(re:split("ac","(?:(?>(a))b|(a)c)++",[trim]))),
<<"::a:">> = iolist_to_binary(join(re:split("ac","(?:(?>(a))b|(a)c)++",[{parts,
- 2}]))),
- <<"::a:">> = iolist_to_binary(join(re:split("ac","(?:(?>(a))b|(a)c)++",[]))),
- <<"::a:ac">> = iolist_to_binary(join(re:split("ac","(?=(?>(a))b|(a)c)(..)",[trim]))),
+ 2}]))),
+ <<"::a:">> = iolist_to_binary(join(re:split("ac","(?:(?>(a))b|(a)c)++",[]))),
+ <<"::a:ac">> = iolist_to_binary(join(re:split("ac","(?=(?>(a))b|(a)c)(..)",[trim]))),
<<"::a:ac:">> = iolist_to_binary(join(re:split("ac","(?=(?>(a))b|(a)c)(..)",[{parts,
- 2}]))),
- <<"::a:ac:">> = iolist_to_binary(join(re:split("ac","(?=(?>(a))b|(a)c)(..)",[]))),
- <<"::a">> = iolist_to_binary(join(re:split("ac","(?>(?>(a))b|(a)c)",[trim]))),
+ 2}]))),
+ <<"::a:ac:">> = iolist_to_binary(join(re:split("ac","(?=(?>(a))b|(a)c)(..)",[]))),
+ <<"::a">> = iolist_to_binary(join(re:split("ac","(?>(?>(a))b|(a)c)",[trim]))),
<<"::a:">> = iolist_to_binary(join(re:split("ac","(?>(?>(a))b|(a)c)",[{parts,
- 2}]))),
- <<"::a:">> = iolist_to_binary(join(re:split("ac","(?>(?>(a))b|(a)c)",[]))),
- <<":aaaabaaabaabab:aaa:aabab">> = iolist_to_binary(join(re:split("aaaabaaabaabab","((?>(a+)b)+(aabab))",[trim]))),
+ 2}]))),
+ <<"::a:">> = iolist_to_binary(join(re:split("ac","(?>(?>(a))b|(a)c)",[]))),
+ <<":aaaabaaabaabab:aaa:aabab">> = iolist_to_binary(join(re:split("aaaabaaabaabab","((?>(a+)b)+(aabab))",[trim]))),
<<":aaaabaaabaabab:aaa:aabab:">> = iolist_to_binary(join(re:split("aaaabaaabaabab","((?>(a+)b)+(aabab))",[{parts,
- 2}]))),
- <<":aaaabaaabaabab:aaa:aabab:">> = iolist_to_binary(join(re:split("aaaabaaabaabab","((?>(a+)b)+(aabab))",[]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","(?>a+|ab)+?c",[trim]))),
+ 2}]))),
+ <<":aaaabaaabaabab:aaa:aabab:">> = iolist_to_binary(join(re:split("aaaabaaabaabab","((?>(a+)b)+(aabab))",[]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","(?>a+|ab)+?c",[trim]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","(?>a+|ab)+?c",[{parts,
- 2}]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","(?>a+|ab)+?c",[]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","(?>a+|ab)+c",[trim]))),
+ 2}]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","(?>a+|ab)+?c",[]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","(?>a+|ab)+c",[trim]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","(?>a+|ab)+c",[{parts,
- 2}]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","(?>a+|ab)+c",[]))),
- <<"">> = iolist_to_binary(join(re:split("aabc","(?:a+|ab)+c",[trim]))),
+ 2}]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","(?>a+|ab)+c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aabc","(?:a+|ab)+c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aabc","(?:a+|ab)+c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aabc","(?:a+|ab)+c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("a","(?(?=(a))a)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aabc","(?:a+|ab)+c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("a","(?(?=(a))a)",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("a","(?(?=(a))a)",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("a","(?(?=(a))a)",[]))),
- <<":a:b">> = iolist_to_binary(join(re:split("ab","(?(?=(a))a)(b)",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("a","(?(?=(a))a)",[]))),
+ <<":a:b">> = iolist_to_binary(join(re:split("ab","(?(?=(a))a)(b)",[trim]))),
<<":a:b:">> = iolist_to_binary(join(re:split("ab","(?(?=(a))a)(b)",[{parts,
- 2}]))),
- <<":a:b:">> = iolist_to_binary(join(re:split("ab","(?(?=(a))a)(b)",[]))),
- <<"aaaabc">> = iolist_to_binary(join(re:split("aaaabc","^(?:a|ab)++c",[trim]))),
+ 2}]))),
+ <<":a:b:">> = iolist_to_binary(join(re:split("ab","(?(?=(a))a)(b)",[]))),
+ <<"aaaabc">> = iolist_to_binary(join(re:split("aaaabc","^(?:a|ab)++c",[trim]))),
<<"aaaabc">> = iolist_to_binary(join(re:split("aaaabc","^(?:a|ab)++c",[{parts,
- 2}]))),
- <<"aaaabc">> = iolist_to_binary(join(re:split("aaaabc","^(?:a|ab)++c",[]))),
- <<"aaaabc">> = iolist_to_binary(join(re:split("aaaabc","^(?>a|ab)++c",[trim]))),
+ 2}]))),
+ <<"aaaabc">> = iolist_to_binary(join(re:split("aaaabc","^(?:a|ab)++c",[]))),
+ <<"aaaabc">> = iolist_to_binary(join(re:split("aaaabc","^(?>a|ab)++c",[trim]))),
<<"aaaabc">> = iolist_to_binary(join(re:split("aaaabc","^(?>a|ab)++c",[{parts,
- 2}]))),
- <<"aaaabc">> = iolist_to_binary(join(re:split("aaaabc","^(?>a|ab)++c",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaabc","^(?:a|ab)+c",[trim]))),
+ 2}]))),
+ <<"aaaabc">> = iolist_to_binary(join(re:split("aaaabc","^(?>a|ab)++c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaabc","^(?:a|ab)+c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaabc","^(?:a|ab)+c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaabc","^(?:a|ab)+c",[]))),
- <<"">> = iolist_to_binary(join(re:split("xyz","(?=abc){0}xyz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaabc","^(?:a|ab)+c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("xyz","(?=abc){0}xyz",[trim]))),
<<":">> = iolist_to_binary(join(re:split("xyz","(?=abc){0}xyz",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("xyz","(?=abc){0}xyz",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?=abc){1}xyz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("xyz","(?=abc){0}xyz",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?=abc){1}xyz",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?=abc){1}xyz",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?=abc){1}xyz",[]))),
- <<"xyz">> = iolist_to_binary(join(re:split("xyz","(?=abc){1}xyz",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?=abc){1}xyz",[]))),
+ <<"xyz">> = iolist_to_binary(join(re:split("xyz","(?=abc){1}xyz",[trim]))),
<<"xyz">> = iolist_to_binary(join(re:split("xyz","(?=abc){1}xyz",[{parts,
- 2}]))),
- <<"xyz">> = iolist_to_binary(join(re:split("xyz","(?=abc){1}xyz",[]))),
- <<":a">> = iolist_to_binary(join(re:split("ab","(?=(a))?.",[trim]))),
+ 2}]))),
+ <<"xyz">> = iolist_to_binary(join(re:split("xyz","(?=abc){1}xyz",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("ab","(?=(a))?.",[trim]))),
<<":a:b">> = iolist_to_binary(join(re:split("ab","(?=(a))?.",[{parts,
- 2}]))),
- <<":a:::">> = iolist_to_binary(join(re:split("ab","(?=(a))?.",[]))),
- <<"">> = iolist_to_binary(join(re:split("bc","(?=(a))?.",[trim]))),
+ 2}]))),
+ <<":a:::">> = iolist_to_binary(join(re:split("ab","(?=(a))?.",[]))),
+ <<"">> = iolist_to_binary(join(re:split("bc","(?=(a))?.",[trim]))),
<<"::c">> = iolist_to_binary(join(re:split("bc","(?=(a))?.",[{parts,
- 2}]))),
- <<"::::">> = iolist_to_binary(join(re:split("bc","(?=(a))?.",[]))),
+ 2}]))),
+ <<"::::">> = iolist_to_binary(join(re:split("bc","(?=(a))?.",[]))),
ok.
run39() ->
- <<"">> = iolist_to_binary(join(re:split("ab","(?=(a))??.",[trim]))),
+ <<"">> = iolist_to_binary(join(re:split("ab","(?=(a))??.",[trim]))),
<<"::b">> = iolist_to_binary(join(re:split("ab","(?=(a))??.",[{parts,
- 2}]))),
- <<"::::">> = iolist_to_binary(join(re:split("ab","(?=(a))??.",[]))),
- <<"">> = iolist_to_binary(join(re:split("bc","(?=(a))??.",[trim]))),
+ 2}]))),
+ <<"::::">> = iolist_to_binary(join(re:split("ab","(?=(a))??.",[]))),
+ <<"">> = iolist_to_binary(join(re:split("bc","(?=(a))??.",[trim]))),
<<"::c">> = iolist_to_binary(join(re:split("bc","(?=(a))??.",[{parts,
- 2}]))),
- <<"::::">> = iolist_to_binary(join(re:split("bc","(?=(a))??.",[]))),
- <<":b">> = iolist_to_binary(join(re:split("abd","^(?=(?1))?[az]([abc])d",[trim]))),
+ 2}]))),
+ <<"::::">> = iolist_to_binary(join(re:split("bc","(?=(a))??.",[]))),
+ <<":b">> = iolist_to_binary(join(re:split("abd","^(?=(?1))?[az]([abc])d",[trim]))),
<<":b:">> = iolist_to_binary(join(re:split("abd","^(?=(?1))?[az]([abc])d",[{parts,
- 2}]))),
- <<":b:">> = iolist_to_binary(join(re:split("abd","^(?=(?1))?[az]([abc])d",[]))),
- <<":c:xx">> = iolist_to_binary(join(re:split("zcdxx","^(?=(?1))?[az]([abc])d",[trim]))),
+ 2}]))),
+ <<":b:">> = iolist_to_binary(join(re:split("abd","^(?=(?1))?[az]([abc])d",[]))),
+ <<":c:xx">> = iolist_to_binary(join(re:split("zcdxx","^(?=(?1))?[az]([abc])d",[trim]))),
<<":c:xx">> = iolist_to_binary(join(re:split("zcdxx","^(?=(?1))?[az]([abc])d",[{parts,
- 2}]))),
- <<":c:xx">> = iolist_to_binary(join(re:split("zcdxx","^(?=(?1))?[az]([abc])d",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaaa","^(?!a){0}\\w+",[trim]))),
+ 2}]))),
+ <<":c:xx">> = iolist_to_binary(join(re:split("zcdxx","^(?=(?1))?[az]([abc])d",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaa","^(?!a){0}\\w+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaaa","^(?!a){0}\\w+",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaaa","^(?!a){0}\\w+",[]))),
- <<"abc:abc">> = iolist_to_binary(join(re:split("abcxyz","(?<=(abc))?xyz",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaaa","^(?!a){0}\\w+",[]))),
+ <<"abc:abc">> = iolist_to_binary(join(re:split("abcxyz","(?<=(abc))?xyz",[trim]))),
<<"abc:abc:">> = iolist_to_binary(join(re:split("abcxyz","(?<=(abc))?xyz",[{parts,
- 2}]))),
- <<"abc:abc:">> = iolist_to_binary(join(re:split("abcxyz","(?<=(abc))?xyz",[]))),
- <<"pqr">> = iolist_to_binary(join(re:split("pqrxyz","(?<=(abc))?xyz",[trim]))),
+ 2}]))),
+ <<"abc:abc:">> = iolist_to_binary(join(re:split("abcxyz","(?<=(abc))?xyz",[]))),
+ <<"pqr">> = iolist_to_binary(join(re:split("pqrxyz","(?<=(abc))?xyz",[trim]))),
<<"pqr::">> = iolist_to_binary(join(re:split("pqrxyz","(?<=(abc))?xyz",[{parts,
- 2}]))),
- <<"pqr::">> = iolist_to_binary(join(re:split("pqrxyz","(?<=(abc))?xyz",[]))),
- <<"">> = iolist_to_binary(join(re:split("ggg<<<aaa>>>","^[\\g<a>]+",[trim]))),
+ 2}]))),
+ <<"pqr::">> = iolist_to_binary(join(re:split("pqrxyz","(?<=(abc))?xyz",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ggg<<<aaa>>>","^[\\g<a>]+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ggg<<<aaa>>>","^[\\g<a>]+",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ggg<<<aaa>>>","^[\\g<a>]+",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\g<a>]+",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ggg<<<aaa>>>","^[\\g<a>]+",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\g<a>]+",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\g<a>]+",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\g<a>]+",[]))),
- <<"\\ga">> = iolist_to_binary(join(re:split("\\ga","^[\\g<a>]+",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^[\\g<a>]+",[]))),
+ <<"\\ga">> = iolist_to_binary(join(re:split("\\ga","^[\\g<a>]+",[trim]))),
<<"\\ga">> = iolist_to_binary(join(re:split("\\ga","^[\\g<a>]+",[{parts,
- 2}]))),
- <<"\\ga">> = iolist_to_binary(join(re:split("\\ga","^[\\g<a>]+",[]))),
- <<":xyz">> = iolist_to_binary(join(re:split("gggagagaxyz","^[\\ga]+",[trim]))),
+ 2}]))),
+ <<"\\ga">> = iolist_to_binary(join(re:split("\\ga","^[\\g<a>]+",[]))),
+ <<":xyz">> = iolist_to_binary(join(re:split("gggagagaxyz","^[\\ga]+",[trim]))),
<<":xyz">> = iolist_to_binary(join(re:split("gggagagaxyz","^[\\ga]+",[{parts,
- 2}]))),
- <<":xyz">> = iolist_to_binary(join(re:split("gggagagaxyz","^[\\ga]+",[]))),
- <<":Z">> = iolist_to_binary(join(re:split("aaaa444:::Z","^[:a[:digit:]]+",[trim]))),
+ 2}]))),
+ <<":xyz">> = iolist_to_binary(join(re:split("gggagagaxyz","^[\\ga]+",[]))),
+ <<":Z">> = iolist_to_binary(join(re:split("aaaa444:::Z","^[:a[:digit:]]+",[trim]))),
<<":Z">> = iolist_to_binary(join(re:split("aaaa444:::Z","^[:a[:digit:]]+",[{parts,
- 2}]))),
- <<":Z">> = iolist_to_binary(join(re:split("aaaa444:::Z","^[:a[:digit:]]+",[]))),
- <<":Z">> = iolist_to_binary(join(re:split("aaaa444:::bbbZ","^[:a[:digit:]:b]+",[trim]))),
+ 2}]))),
+ <<":Z">> = iolist_to_binary(join(re:split("aaaa444:::Z","^[:a[:digit:]]+",[]))),
+ <<":Z">> = iolist_to_binary(join(re:split("aaaa444:::bbbZ","^[:a[:digit:]:b]+",[trim]))),
<<":Z">> = iolist_to_binary(join(re:split("aaaa444:::bbbZ","^[:a[:digit:]:b]+",[{parts,
- 2}]))),
- <<":Z">> = iolist_to_binary(join(re:split("aaaa444:::bbbZ","^[:a[:digit:]:b]+",[]))),
- <<"">> = iolist_to_binary(join(re:split(":xxx:","[:a]xxx[b:]",[trim]))),
+ 2}]))),
+ <<":Z">> = iolist_to_binary(join(re:split("aaaa444:::bbbZ","^[:a[:digit:]:b]+",[]))),
+ <<"">> = iolist_to_binary(join(re:split(":xxx:","[:a]xxx[b:]",[trim]))),
<<":">> = iolist_to_binary(join(re:split(":xxx:","[:a]xxx[b:]",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split(":xxx:","[:a]xxx[b:]",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split(":xxx:","[:a]xxx[b:]",[]))),
<<"xaa:c">> = iolist_to_binary(join(re:split("xaabc","(?<=a{2})b",[caseless,
- trim]))),
+ trim]))),
<<"xaa:c">> = iolist_to_binary(join(re:split("xaabc","(?<=a{2})b",[caseless,
{parts,
- 2}]))),
- <<"xaa:c">> = iolist_to_binary(join(re:split("xaabc","(?<=a{2})b",[caseless]))),
+ 2}]))),
+ <<"xaa:c">> = iolist_to_binary(join(re:split("xaabc","(?<=a{2})b",[caseless]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=a{2})b",[caseless,
- trim]))),
+ trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=a{2})b",[caseless,
{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=a{2})b",[caseless]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=a{2})b",[caseless]))),
<<"xabc">> = iolist_to_binary(join(re:split("xabc","(?<=a{2})b",[caseless,
- trim]))),
+ trim]))),
<<"xabc">> = iolist_to_binary(join(re:split("xabc","(?<=a{2})b",[caseless,
{parts,
- 2}]))),
- <<"xabc">> = iolist_to_binary(join(re:split("xabc","(?<=a{2})b",[caseless]))),
+ 2}]))),
+ <<"xabc">> = iolist_to_binary(join(re:split("xabc","(?<=a{2})b",[caseless]))),
<<"xa:c">> = iolist_to_binary(join(re:split("xabc","(?<!a{2})b",[caseless,
- trim]))),
+ trim]))),
<<"xa:c">> = iolist_to_binary(join(re:split("xabc","(?<!a{2})b",[caseless,
{parts,
- 2}]))),
- <<"xa:c">> = iolist_to_binary(join(re:split("xabc","(?<!a{2})b",[caseless]))),
+ 2}]))),
+ <<"xa:c">> = iolist_to_binary(join(re:split("xabc","(?<!a{2})b",[caseless]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<!a{2})b",[caseless,
- trim]))),
+ trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<!a{2})b",[caseless,
{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<!a{2})b",[caseless]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<!a{2})b",[caseless]))),
<<"xaabc">> = iolist_to_binary(join(re:split("xaabc","(?<!a{2})b",[caseless,
- trim]))),
+ trim]))),
<<"xaabc">> = iolist_to_binary(join(re:split("xaabc","(?<!a{2})b",[caseless,
{parts,
- 2}]))),
- <<"xaabc">> = iolist_to_binary(join(re:split("xaabc","(?<!a{2})b",[caseless]))),
- <<"xa ">> = iolist_to_binary(join(re:split("xa c","(?<=a\\h)c",[trim]))),
+ 2}]))),
+ <<"xaabc">> = iolist_to_binary(join(re:split("xaabc","(?<!a{2})b",[caseless]))),
+ <<"xa ">> = iolist_to_binary(join(re:split("xa c","(?<=a\\h)c",[trim]))),
<<"xa :">> = iolist_to_binary(join(re:split("xa c","(?<=a\\h)c",[{parts,
- 2}]))),
- <<"xa :">> = iolist_to_binary(join(re:split("xa c","(?<=a\\h)c",[]))),
- <<"axx:c">> = iolist_to_binary(join(re:split("axxbc","(?<=[^a]{2})b",[trim]))),
+ 2}]))),
+ <<"xa :">> = iolist_to_binary(join(re:split("xa c","(?<=a\\h)c",[]))),
+ <<"axx:c">> = iolist_to_binary(join(re:split("axxbc","(?<=[^a]{2})b",[trim]))),
<<"axx:c">> = iolist_to_binary(join(re:split("axxbc","(?<=[^a]{2})b",[{parts,
- 2}]))),
- <<"axx:c">> = iolist_to_binary(join(re:split("axxbc","(?<=[^a]{2})b",[]))),
- <<"aAA:c">> = iolist_to_binary(join(re:split("aAAbc","(?<=[^a]{2})b",[trim]))),
+ 2}]))),
+ <<"axx:c">> = iolist_to_binary(join(re:split("axxbc","(?<=[^a]{2})b",[]))),
+ <<"aAA:c">> = iolist_to_binary(join(re:split("aAAbc","(?<=[^a]{2})b",[trim]))),
<<"aAA:c">> = iolist_to_binary(join(re:split("aAAbc","(?<=[^a]{2})b",[{parts,
- 2}]))),
- <<"aAA:c">> = iolist_to_binary(join(re:split("aAAbc","(?<=[^a]{2})b",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^a]{2})b",[trim]))),
+ 2}]))),
+ <<"aAA:c">> = iolist_to_binary(join(re:split("aAAbc","(?<=[^a]{2})b",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^a]{2})b",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^a]{2})b",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^a]{2})b",[]))),
- <<"xaabc">> = iolist_to_binary(join(re:split("xaabc","(?<=[^a]{2})b",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^a]{2})b",[]))),
+ <<"xaabc">> = iolist_to_binary(join(re:split("xaabc","(?<=[^a]{2})b",[trim]))),
<<"xaabc">> = iolist_to_binary(join(re:split("xaabc","(?<=[^a]{2})b",[{parts,
- 2}]))),
- <<"xaabc">> = iolist_to_binary(join(re:split("xaabc","(?<=[^a]{2})b",[]))),
+ 2}]))),
+ <<"xaabc">> = iolist_to_binary(join(re:split("xaabc","(?<=[^a]{2})b",[]))),
<<"axx:c">> = iolist_to_binary(join(re:split("axxbc","(?<=[^a]{2})b",[caseless,
- trim]))),
+ trim]))),
<<"axx:c">> = iolist_to_binary(join(re:split("axxbc","(?<=[^a]{2})b",[caseless,
{parts,
- 2}]))),
- <<"axx:c">> = iolist_to_binary(join(re:split("axxbc","(?<=[^a]{2})b",[caseless]))),
+ 2}]))),
+ <<"axx:c">> = iolist_to_binary(join(re:split("axxbc","(?<=[^a]{2})b",[caseless]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^a]{2})b",[caseless,
- trim]))),
+ trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^a]{2})b",[caseless,
{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^a]{2})b",[caseless]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=[^a]{2})b",[caseless]))),
<<"aAAbc">> = iolist_to_binary(join(re:split("aAAbc","(?<=[^a]{2})b",[caseless,
- trim]))),
+ trim]))),
<<"aAAbc">> = iolist_to_binary(join(re:split("aAAbc","(?<=[^a]{2})b",[caseless,
{parts,
- 2}]))),
- <<"aAAbc">> = iolist_to_binary(join(re:split("aAAbc","(?<=[^a]{2})b",[caseless]))),
+ 2}]))),
+ <<"aAAbc">> = iolist_to_binary(join(re:split("aAAbc","(?<=[^a]{2})b",[caseless]))),
<<"xaabc">> = iolist_to_binary(join(re:split("xaabc","(?<=[^a]{2})b",[caseless,
- trim]))),
+ trim]))),
<<"xaabc">> = iolist_to_binary(join(re:split("xaabc","(?<=[^a]{2})b",[caseless,
{parts,
- 2}]))),
- <<"xaabc">> = iolist_to_binary(join(re:split("xaabc","(?<=[^a]{2})b",[caseless]))),
- <<"ab">> = iolist_to_binary(join(re:split("abc","(?<=a\\H)c",[trim]))),
+ 2}]))),
+ <<"xaabc">> = iolist_to_binary(join(re:split("xaabc","(?<=[^a]{2})b",[caseless]))),
+ <<"ab">> = iolist_to_binary(join(re:split("abc","(?<=a\\H)c",[trim]))),
<<"ab:">> = iolist_to_binary(join(re:split("abc","(?<=a\\H)c",[{parts,
- 2}]))),
- <<"ab:">> = iolist_to_binary(join(re:split("abc","(?<=a\\H)c",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("abc","(?<=a\\V)c",[trim]))),
+ 2}]))),
+ <<"ab:">> = iolist_to_binary(join(re:split("abc","(?<=a\\H)c",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("abc","(?<=a\\V)c",[trim]))),
<<"ab:">> = iolist_to_binary(join(re:split("abc","(?<=a\\V)c",[{parts,
- 2}]))),
- <<"ab:">> = iolist_to_binary(join(re:split("abc","(?<=a\\V)c",[]))),
+ 2}]))),
+ <<"ab:">> = iolist_to_binary(join(re:split("abc","(?<=a\\V)c",[]))),
<<"a
">> = iolist_to_binary(join(re:split("a
-c","(?<=a\\v)c",[trim]))),
+c","(?<=a\\v)c",[trim]))),
<<"a
:">> = iolist_to_binary(join(re:split("a
-c","(?<=a\\v)c",[{parts,2}]))),
+c","(?<=a\\v)c",[{parts,2}]))),
<<"a
:">> = iolist_to_binary(join(re:split("a
-c","(?<=a\\v)c",[]))),
- <<"X:X">> = iolist_to_binary(join(re:split("XcccddYX","(?(?=c)c|d)++Y",[trim]))),
+c","(?<=a\\v)c",[]))),
+ <<"X:X">> = iolist_to_binary(join(re:split("XcccddYX","(?(?=c)c|d)++Y",[trim]))),
<<"X:X">> = iolist_to_binary(join(re:split("XcccddYX","(?(?=c)c|d)++Y",[{parts,
- 2}]))),
- <<"X:X">> = iolist_to_binary(join(re:split("XcccddYX","(?(?=c)c|d)++Y",[]))),
- <<"X:X">> = iolist_to_binary(join(re:split("XcccddYX","(?(?=c)c|d)*+Y",[trim]))),
+ 2}]))),
+ <<"X:X">> = iolist_to_binary(join(re:split("XcccddYX","(?(?=c)c|d)++Y",[]))),
+ <<"X:X">> = iolist_to_binary(join(re:split("XcccddYX","(?(?=c)c|d)*+Y",[trim]))),
<<"X:X">> = iolist_to_binary(join(re:split("XcccddYX","(?(?=c)c|d)*+Y",[{parts,
- 2}]))),
- <<"X:X">> = iolist_to_binary(join(re:split("XcccddYX","(?(?=c)c|d)*+Y",[]))),
- <<":aaa">> = iolist_to_binary(join(re:split("aaaaaaa","^(a{2,3}){2,}+a",[trim]))),
+ 2}]))),
+ <<"X:X">> = iolist_to_binary(join(re:split("XcccddYX","(?(?=c)c|d)*+Y",[]))),
+ <<":aaa">> = iolist_to_binary(join(re:split("aaaaaaa","^(a{2,3}){2,}+a",[trim]))),
<<":aaa:">> = iolist_to_binary(join(re:split("aaaaaaa","^(a{2,3}){2,}+a",[{parts,
- 2}]))),
- <<":aaa:">> = iolist_to_binary(join(re:split("aaaaaaa","^(a{2,3}){2,}+a",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3}){2,}+a",[trim]))),
+ 2}]))),
+ <<":aaa:">> = iolist_to_binary(join(re:split("aaaaaaa","^(a{2,3}){2,}+a",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3}){2,}+a",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3}){2,}+a",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3}){2,}+a",[]))),
- <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3}){2,}+a",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3}){2,}+a",[]))),
+ <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3}){2,}+a",[trim]))),
<<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3}){2,}+a",[{parts,
- 2}]))),
- <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3}){2,}+a",[]))),
- <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a{2,3}){2,}+a",[trim]))),
+ 2}]))),
+ <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3}){2,}+a",[]))),
+ <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a{2,3}){2,}+a",[trim]))),
<<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a{2,3}){2,}+a",[{parts,
- 2}]))),
- <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a{2,3}){2,}+a",[]))),
+ 2}]))),
+ <<"aaaaaaaaa">> = iolist_to_binary(join(re:split("aaaaaaaaa","^(a{2,3}){2,}+a",[]))),
ok.
run40() ->
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3})++a",[trim]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3})++a",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3})++a",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3})++a",[]))),
- <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3})++a",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3})++a",[]))),
+ <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3})++a",[trim]))),
<<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3})++a",[{parts,
- 2}]))),
- <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3})++a",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3})*+a",[trim]))),
+ 2}]))),
+ <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3})++a",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3})*+a",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3})*+a",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3})*+a",[]))),
- <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3})*+a",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a{2,3})*+a",[]))),
+ <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3})*+a",[trim]))),
<<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3})*+a",[{parts,
- 2}]))),
- <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3})*+a",[]))),
- <<"">> = iolist_to_binary(join(re:split("abXde","ab\\Cde",[trim]))),
+ 2}]))),
+ <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(a{2,3})*+a",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abXde","ab\\Cde",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abXde","ab\\Cde",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abXde","ab\\Cde",[]))),
- <<"abZde">> = iolist_to_binary(join(re:split("abZdeX","(?<=ab\\Cde)X",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abXde","ab\\Cde",[]))),
+ <<"abZde">> = iolist_to_binary(join(re:split("abZdeX","(?<=ab\\Cde)X",[trim]))),
<<"abZde:">> = iolist_to_binary(join(re:split("abZdeX","(?<=ab\\Cde)X",[{parts,
- 2}]))),
- <<"abZde:">> = iolist_to_binary(join(re:split("abZdeX","(?<=ab\\Cde)X",[]))),
- <<"">> = iolist_to_binary(join(re:split("aCb","a[\\CD]b",[trim]))),
+ 2}]))),
+ <<"abZde:">> = iolist_to_binary(join(re:split("abZdeX","(?<=ab\\Cde)X",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aCb","a[\\CD]b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aCb","a[\\CD]b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aCb","a[\\CD]b",[]))),
- <<"">> = iolist_to_binary(join(re:split("aDb","a[\\CD]b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aCb","a[\\CD]b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aDb","a[\\CD]b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aDb","a[\\CD]b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aDb","a[\\CD]b",[]))),
- <<"">> = iolist_to_binary(join(re:split("aJb","a[\\C-X]b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aDb","a[\\CD]b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aJb","a[\\C-X]b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aJb","a[\\C-X]b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aJb","a[\\C-X]b",[]))),
- <<"X X">> = iolist_to_binary(join(re:split("X X","\\H\\h\\V\\v",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aJb","a[\\C-X]b",[]))),
+ <<"X X">> = iolist_to_binary(join(re:split("X X","\\H\\h\\V\\v",[trim]))),
<<"X X">> = iolist_to_binary(join(re:split("X X","\\H\\h\\V\\v",[{parts,
- 2}]))),
- <<"X X">> = iolist_to_binary(join(re:split("X X","\\H\\h\\V\\v",[]))),
- <<"">> = iolist_to_binary(join(re:split("X X ","\\H\\h\\V\\v",[trim]))),
+ 2}]))),
+ <<"X X">> = iolist_to_binary(join(re:split("X X","\\H\\h\\V\\v",[]))),
+ <<"">> = iolist_to_binary(join(re:split("X X ","\\H\\h\\V\\v",[trim]))),
<<":">> = iolist_to_binary(join(re:split("X X ","\\H\\h\\V\\v",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("X X ","\\H\\h\\V\\v",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\H\\h\\V\\v",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("X X ","\\H\\h\\V\\v",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\H\\h\\V\\v",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\H\\h\\V\\v",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\H\\h\\V\\v",[]))),
- <<"  X">> = iolist_to_binary(join(re:split("  X","\\H\\h\\V\\v",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\H\\h\\V\\v",[]))),
+ <<"  X">> = iolist_to_binary(join(re:split("  X","\\H\\h\\V\\v",[trim]))),
<<"  X">> = iolist_to_binary(join(re:split("  X","\\H\\h\\V\\v",[{parts,
- 2}]))),
- <<"  X">> = iolist_to_binary(join(re:split("  X","\\H\\h\\V\\v",[]))),
+ 2}]))),
+ <<"  X">> = iolist_to_binary(join(re:split("  X","\\H\\h\\V\\v",[]))),
<<"">> = iolist_to_binary(join(re:split("  X
- ","\\H*\\h+\\V?\\v{3,4}",[trim]))),
+ ","\\H*\\h+\\V?\\v{3,4}",[trim]))),
<<":">> = iolist_to_binary(join(re:split("  X
- ","\\H*\\h+\\V?\\v{3,4}",[{parts,2}]))),
+ ","\\H*\\h+\\V?\\v{3,4}",[{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("  X
- ","\\H*\\h+\\V?\\v{3,4}",[]))),
+ ","\\H*\\h+\\V?\\v{3,4}",[]))),
<<"">> = iolist_to_binary(join(re:split("  
- ","\\H*\\h+\\V?\\v{3,4}",[trim]))),
+ ","\\H*\\h+\\V?\\v{3,4}",[trim]))),
<<":">> = iolist_to_binary(join(re:split("  
- ","\\H*\\h+\\V?\\v{3,4}",[{parts,2}]))),
+ ","\\H*\\h+\\V?\\v{3,4}",[{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("  
- ","\\H*\\h+\\V?\\v{3,4}",[]))),
+ ","\\H*\\h+\\V?\\v{3,4}",[]))),
<<"">> = iolist_to_binary(join(re:split("  
- ","\\H*\\h+\\V?\\v{3,4}",[trim]))),
+ ","\\H*\\h+\\V?\\v{3,4}",[trim]))),
<<":">> = iolist_to_binary(join(re:split("  
- ","\\H*\\h+\\V?\\v{3,4}",[{parts,2}]))),
+ ","\\H*\\h+\\V?\\v{3,4}",[{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("  
- ","\\H*\\h+\\V?\\v{3,4}",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\H*\\h+\\V?\\v{3,4}",[trim]))),
+ ","\\H*\\h+\\V?\\v{3,4}",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\H*\\h+\\V?\\v{3,4}",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\H*\\h+\\V?\\v{3,4}",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\H*\\h+\\V?\\v{3,4}",[]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\H*\\h+\\V?\\v{3,4}",[]))),
<<"  
">> = iolist_to_binary(join(re:split("  
- ","\\H*\\h+\\V?\\v{3,4}",[trim]))),
+ ","\\H*\\h+\\V?\\v{3,4}",[trim]))),
<<"  
">> = iolist_to_binary(join(re:split("  
- ","\\H*\\h+\\V?\\v{3,4}",[{parts,2}]))),
+ ","\\H*\\h+\\V?\\v{3,4}",[{parts,2}]))),
<<"  
">> = iolist_to_binary(join(re:split("  
- ","\\H*\\h+\\V?\\v{3,4}",[]))),
- <<"XY :E">> = iolist_to_binary(join(re:split("XY ABCDE","\\H{3,4}",[trim]))),
+ ","\\H*\\h+\\V?\\v{3,4}",[]))),
+ <<"XY :E">> = iolist_to_binary(join(re:split("XY ABCDE","\\H{3,4}",[trim]))),
<<"XY :E">> = iolist_to_binary(join(re:split("XY ABCDE","\\H{3,4}",[{parts,
- 2}]))),
- <<"XY :E">> = iolist_to_binary(join(re:split("XY ABCDE","\\H{3,4}",[]))),
- <<"XY : ST">> = iolist_to_binary(join(re:split("XY PQR ST","\\H{3,4}",[trim]))),
+ 2}]))),
+ <<"XY :E">> = iolist_to_binary(join(re:split("XY ABCDE","\\H{3,4}",[]))),
+ <<"XY : ST">> = iolist_to_binary(join(re:split("XY PQR ST","\\H{3,4}",[trim]))),
<<"XY : ST">> = iolist_to_binary(join(re:split("XY PQR ST","\\H{3,4}",[{parts,
- 2}]))),
- <<"XY : ST">> = iolist_to_binary(join(re:split("XY PQR ST","\\H{3,4}",[]))),
- <<"XY A:QRS">> = iolist_to_binary(join(re:split("XY AB PQRS",".\\h{3,4}.",[trim]))),
+ 2}]))),
+ <<"XY : ST">> = iolist_to_binary(join(re:split("XY PQR ST","\\H{3,4}",[]))),
+ <<"XY A:QRS">> = iolist_to_binary(join(re:split("XY AB PQRS",".\\h{3,4}.",[trim]))),
<<"XY A:QRS">> = iolist_to_binary(join(re:split("XY AB PQRS",".\\h{3,4}.",[{parts,
- 2}]))),
- <<"XY A:QRS">> = iolist_to_binary(join(re:split("XY AB PQRS",".\\h{3,4}.",[]))),
- <<">">> = iolist_to_binary(join(re:split(">XNNNYZ","\\h*X\\h?\\H+Y\\H?Z",[trim]))),
+ 2}]))),
+ <<"XY A:QRS">> = iolist_to_binary(join(re:split("XY AB PQRS",".\\h{3,4}.",[]))),
+ <<">">> = iolist_to_binary(join(re:split(">XNNNYZ","\\h*X\\h?\\H+Y\\H?Z",[trim]))),
<<">:">> = iolist_to_binary(join(re:split(">XNNNYZ","\\h*X\\h?\\H+Y\\H?Z",[{parts,
- 2}]))),
- <<">:">> = iolist_to_binary(join(re:split(">XNNNYZ","\\h*X\\h?\\H+Y\\H?Z",[]))),
- <<">">> = iolist_to_binary(join(re:split("> X NYQZ","\\h*X\\h?\\H+Y\\H?Z",[trim]))),
+ 2}]))),
+ <<">:">> = iolist_to_binary(join(re:split(">XNNNYZ","\\h*X\\h?\\H+Y\\H?Z",[]))),
+ <<">">> = iolist_to_binary(join(re:split("> X NYQZ","\\h*X\\h?\\H+Y\\H?Z",[trim]))),
<<">:">> = iolist_to_binary(join(re:split("> X NYQZ","\\h*X\\h?\\H+Y\\H?Z",[{parts,
- 2}]))),
- <<">:">> = iolist_to_binary(join(re:split("> X NYQZ","\\h*X\\h?\\H+Y\\H?Z",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\h*X\\h?\\H+Y\\H?Z",[trim]))),
+ 2}]))),
+ <<">:">> = iolist_to_binary(join(re:split("> X NYQZ","\\h*X\\h?\\H+Y\\H?Z",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\h*X\\h?\\H+Y\\H?Z",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\h*X\\h?\\H+Y\\H?Z",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\h*X\\h?\\H+Y\\H?Z",[]))),
- <<">XYZ">> = iolist_to_binary(join(re:split(">XYZ","\\h*X\\h?\\H+Y\\H?Z",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\h*X\\h?\\H+Y\\H?Z",[]))),
+ <<">XYZ">> = iolist_to_binary(join(re:split(">XYZ","\\h*X\\h?\\H+Y\\H?Z",[trim]))),
<<">XYZ">> = iolist_to_binary(join(re:split(">XYZ","\\h*X\\h?\\H+Y\\H?Z",[{parts,
- 2}]))),
- <<">XYZ">> = iolist_to_binary(join(re:split(">XYZ","\\h*X\\h?\\H+Y\\H?Z",[]))),
- <<"> X NY Z">> = iolist_to_binary(join(re:split("> X NY Z","\\h*X\\h?\\H+Y\\H?Z",[trim]))),
+ 2}]))),
+ <<">XYZ">> = iolist_to_binary(join(re:split(">XYZ","\\h*X\\h?\\H+Y\\H?Z",[]))),
+ <<"> X NY Z">> = iolist_to_binary(join(re:split("> X NY Z","\\h*X\\h?\\H+Y\\H?Z",[trim]))),
<<"> X NY Z">> = iolist_to_binary(join(re:split("> X NY Z","\\h*X\\h?\\H+Y\\H?Z",[{parts,
- 2}]))),
- <<"> X NY Z">> = iolist_to_binary(join(re:split("> X NY Z","\\h*X\\h?\\H+Y\\H?Z",[]))),
+ 2}]))),
+ <<"> X NY Z">> = iolist_to_binary(join(re:split("> X NY Z","\\h*X\\h?\\H+Y\\H?Z",[]))),
<<">">> = iolist_to_binary(join(re:split(">XY
Z
-A NN ","\\v*X\\v?Y\\v+Z\\V*\\x0a\\V+\\x0b\\V{2,3}\\x0c",[trim]))),
+A NN ","\\v*X\\v?Y\\v+Z\\V*\\x0a\\V+\\x0b\\V{2,3}\\x0c",[trim]))),
<<">:">> = iolist_to_binary(join(re:split(">XY
Z
A NN ","\\v*X\\v?Y\\v+Z\\V*\\x0a\\V+\\x0b\\V{2,3}\\x0c",[{parts,
- 2}]))),
+ 2}]))),
<<">:">> = iolist_to_binary(join(re:split(">XY
Z
-A NN ","\\v*X\\v?Y\\v+Z\\V*\\x0a\\V+\\x0b\\V{2,3}\\x0c",[]))),
+A NN ","\\v*X\\v?Y\\v+Z\\V*\\x0a\\V+\\x0b\\V{2,3}\\x0c",[]))),
<<">">> = iolist_to_binary(join(re:split(">
X
Y
ZZZ
-AAA NNN ","\\v*X\\v?Y\\v+Z\\V*\\x0a\\V+\\x0b\\V{2,3}\\x0c",[trim]))),
+AAA NNN ","\\v*X\\v?Y\\v+Z\\V*\\x0a\\V+\\x0b\\V{2,3}\\x0c",[trim]))),
<<">:">> = iolist_to_binary(join(re:split(">
X
Y
ZZZ
AAA NNN ","\\v*X\\v?Y\\v+Z\\V*\\x0a\\V+\\x0b\\V{2,3}\\x0c",[{parts,
- 2}]))),
+ 2}]))),
<<">:">> = iolist_to_binary(join(re:split(">
X
Y
ZZZ
-AAA NNN ","\\v*X\\v?Y\\v+Z\\V*\\x0a\\V+\\x0b\\V{2,3}\\x0c",[]))),
- <<"foo:foo">> = iolist_to_binary(join(re:split("foobar","(foo)\\Kbar",[trim]))),
+AAA NNN ","\\v*X\\v?Y\\v+Z\\V*\\x0a\\V+\\x0b\\V{2,3}\\x0c",[]))),
+ <<"foo:foo">> = iolist_to_binary(join(re:split("foobar","(foo)\\Kbar",[trim]))),
<<"foo:foo:">> = iolist_to_binary(join(re:split("foobar","(foo)\\Kbar",[{parts,
- 2}]))),
- <<"foo:foo:">> = iolist_to_binary(join(re:split("foobar","(foo)\\Kbar",[]))),
- <<"foo:foo:bar">> = iolist_to_binary(join(re:split("foobar","(foo)(\\Kbar|baz)",[trim]))),
+ 2}]))),
+ <<"foo:foo:">> = iolist_to_binary(join(re:split("foobar","(foo)\\Kbar",[]))),
+ <<"foo:foo:bar">> = iolist_to_binary(join(re:split("foobar","(foo)(\\Kbar|baz)",[trim]))),
<<"foo:foo:bar:">> = iolist_to_binary(join(re:split("foobar","(foo)(\\Kbar|baz)",[{parts,
- 2}]))),
- <<"foo:foo:bar:">> = iolist_to_binary(join(re:split("foobar","(foo)(\\Kbar|baz)",[]))),
- <<":foo:baz">> = iolist_to_binary(join(re:split("foobaz","(foo)(\\Kbar|baz)",[trim]))),
+ 2}]))),
+ <<"foo:foo:bar:">> = iolist_to_binary(join(re:split("foobar","(foo)(\\Kbar|baz)",[]))),
+ <<":foo:baz">> = iolist_to_binary(join(re:split("foobaz","(foo)(\\Kbar|baz)",[trim]))),
<<":foo:baz:">> = iolist_to_binary(join(re:split("foobaz","(foo)(\\Kbar|baz)",[{parts,
- 2}]))),
- <<":foo:baz:">> = iolist_to_binary(join(re:split("foobaz","(foo)(\\Kbar|baz)",[]))),
- <<"foo:foobar">> = iolist_to_binary(join(re:split("foobarbaz","(foo\\Kbar)baz",[trim]))),
+ 2}]))),
+ <<":foo:baz:">> = iolist_to_binary(join(re:split("foobaz","(foo)(\\Kbar|baz)",[]))),
+ <<"foo:foobar">> = iolist_to_binary(join(re:split("foobarbaz","(foo\\Kbar)baz",[trim]))),
<<"foo:foobar:">> = iolist_to_binary(join(re:split("foobarbaz","(foo\\Kbar)baz",[{parts,
- 2}]))),
- <<"foo:foobar:">> = iolist_to_binary(join(re:split("foobarbaz","(foo\\Kbar)baz",[]))),
- <<":tom">> = iolist_to_binary(join(re:split("tom-tom","(?<A>tom|bon)-\\g{A}",[trim]))),
+ 2}]))),
+ <<"foo:foobar:">> = iolist_to_binary(join(re:split("foobarbaz","(foo\\Kbar)baz",[]))),
+ <<":tom">> = iolist_to_binary(join(re:split("tom-tom","(?<A>tom|bon)-\\g{A}",[trim]))),
<<":tom:">> = iolist_to_binary(join(re:split("tom-tom","(?<A>tom|bon)-\\g{A}",[{parts,
- 2}]))),
- <<":tom:">> = iolist_to_binary(join(re:split("tom-tom","(?<A>tom|bon)-\\g{A}",[]))),
- <<":bon">> = iolist_to_binary(join(re:split("bon-bon","(?<A>tom|bon)-\\g{A}",[trim]))),
+ 2}]))),
+ <<":tom:">> = iolist_to_binary(join(re:split("tom-tom","(?<A>tom|bon)-\\g{A}",[]))),
+ <<":bon">> = iolist_to_binary(join(re:split("bon-bon","(?<A>tom|bon)-\\g{A}",[trim]))),
<<":bon:">> = iolist_to_binary(join(re:split("bon-bon","(?<A>tom|bon)-\\g{A}",[{parts,
- 2}]))),
- <<":bon:">> = iolist_to_binary(join(re:split("bon-bon","(?<A>tom|bon)-\\g{A}",[]))),
- <<"bacxxx">> = iolist_to_binary(join(re:split("bacxxx","(^(a|b\\g{-1}))",[trim]))),
+ 2}]))),
+ <<":bon:">> = iolist_to_binary(join(re:split("bon-bon","(?<A>tom|bon)-\\g{A}",[]))),
+ <<"bacxxx">> = iolist_to_binary(join(re:split("bacxxx","(^(a|b\\g{-1}))",[trim]))),
<<"bacxxx">> = iolist_to_binary(join(re:split("bacxxx","(^(a|b\\g{-1}))",[{parts,
- 2}]))),
- <<"bacxxx">> = iolist_to_binary(join(re:split("bacxxx","(^(a|b\\g{-1}))",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abcabc","(?|(abc)|(xyz))\\1",[trim]))),
+ 2}]))),
+ <<"bacxxx">> = iolist_to_binary(join(re:split("bacxxx","(^(a|b\\g{-1}))",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abcabc","(?|(abc)|(xyz))\\1",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abcabc","(?|(abc)|(xyz))\\1",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abcabc","(?|(abc)|(xyz))\\1",[]))),
- <<":xyz">> = iolist_to_binary(join(re:split("xyzxyz","(?|(abc)|(xyz))\\1",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abcabc","(?|(abc)|(xyz))\\1",[]))),
+ <<":xyz">> = iolist_to_binary(join(re:split("xyzxyz","(?|(abc)|(xyz))\\1",[trim]))),
<<":xyz:">> = iolist_to_binary(join(re:split("xyzxyz","(?|(abc)|(xyz))\\1",[{parts,
- 2}]))),
- <<":xyz:">> = iolist_to_binary(join(re:split("xyzxyz","(?|(abc)|(xyz))\\1",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?|(abc)|(xyz))\\1",[trim]))),
+ 2}]))),
+ <<":xyz:">> = iolist_to_binary(join(re:split("xyzxyz","(?|(abc)|(xyz))\\1",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?|(abc)|(xyz))\\1",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?|(abc)|(xyz))\\1",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?|(abc)|(xyz))\\1",[]))),
- <<"abcxyz">> = iolist_to_binary(join(re:split("abcxyz","(?|(abc)|(xyz))\\1",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?|(abc)|(xyz))\\1",[]))),
+ <<"abcxyz">> = iolist_to_binary(join(re:split("abcxyz","(?|(abc)|(xyz))\\1",[trim]))),
<<"abcxyz">> = iolist_to_binary(join(re:split("abcxyz","(?|(abc)|(xyz))\\1",[{parts,
- 2}]))),
- <<"abcxyz">> = iolist_to_binary(join(re:split("abcxyz","(?|(abc)|(xyz))\\1",[]))),
- <<"xyzabc">> = iolist_to_binary(join(re:split("xyzabc","(?|(abc)|(xyz))\\1",[trim]))),
+ 2}]))),
+ <<"abcxyz">> = iolist_to_binary(join(re:split("abcxyz","(?|(abc)|(xyz))\\1",[]))),
+ <<"xyzabc">> = iolist_to_binary(join(re:split("xyzabc","(?|(abc)|(xyz))\\1",[trim]))),
<<"xyzabc">> = iolist_to_binary(join(re:split("xyzabc","(?|(abc)|(xyz))\\1",[{parts,
- 2}]))),
- <<"xyzabc">> = iolist_to_binary(join(re:split("xyzabc","(?|(abc)|(xyz))\\1",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abcabc","(?|(abc)|(xyz))(?1)",[trim]))),
+ 2}]))),
+ <<"xyzabc">> = iolist_to_binary(join(re:split("xyzabc","(?|(abc)|(xyz))\\1",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abcabc","(?|(abc)|(xyz))(?1)",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abcabc","(?|(abc)|(xyz))(?1)",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abcabc","(?|(abc)|(xyz))(?1)",[]))),
- <<":xyz">> = iolist_to_binary(join(re:split("xyzabc","(?|(abc)|(xyz))(?1)",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abcabc","(?|(abc)|(xyz))(?1)",[]))),
+ <<":xyz">> = iolist_to_binary(join(re:split("xyzabc","(?|(abc)|(xyz))(?1)",[trim]))),
<<":xyz:">> = iolist_to_binary(join(re:split("xyzabc","(?|(abc)|(xyz))(?1)",[{parts,
- 2}]))),
- <<":xyz:">> = iolist_to_binary(join(re:split("xyzabc","(?|(abc)|(xyz))(?1)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?|(abc)|(xyz))(?1)",[trim]))),
+ 2}]))),
+ <<":xyz:">> = iolist_to_binary(join(re:split("xyzabc","(?|(abc)|(xyz))(?1)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?|(abc)|(xyz))(?1)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?|(abc)|(xyz))(?1)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?|(abc)|(xyz))(?1)",[]))),
- <<"xyzxyz">> = iolist_to_binary(join(re:split("xyzxyz","(?|(abc)|(xyz))(?1)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?|(abc)|(xyz))(?1)",[]))),
+ <<"xyzxyz">> = iolist_to_binary(join(re:split("xyzxyz","(?|(abc)|(xyz))(?1)",[trim]))),
<<"xyzxyz">> = iolist_to_binary(join(re:split("xyzxyz","(?|(abc)|(xyz))(?1)",[{parts,
- 2}]))),
- <<"xyzxyz">> = iolist_to_binary(join(re:split("xyzxyz","(?|(abc)|(xyz))(?1)",[]))),
+ 2}]))),
+ <<"xyzxyz">> = iolist_to_binary(join(re:split("xyzxyz","(?|(abc)|(xyz))(?1)",[]))),
ok.
run41() ->
- <<":a:b:c:d:Y">> = iolist_to_binary(join(re:split("XYabcdY","^X(?5)(a)(?|(b)|(q))(c)(d)(Y)",[trim]))),
+ <<":a:b:c:d:Y">> = iolist_to_binary(join(re:split("XYabcdY","^X(?5)(a)(?|(b)|(q))(c)(d)(Y)",[trim]))),
<<":a:b:c:d:Y:">> = iolist_to_binary(join(re:split("XYabcdY","^X(?5)(a)(?|(b)|(q))(c)(d)(Y)",[{parts,
- 2}]))),
- <<":a:b:c:d:Y:">> = iolist_to_binary(join(re:split("XYabcdY","^X(?5)(a)(?|(b)|(q))(c)(d)(Y)",[]))),
- <<":a:b:::c:d:Y">> = iolist_to_binary(join(re:split("XYabcdY","^X(?7)(a)(?|(b|(r)(s))|(q))(c)(d)(Y)",[trim]))),
+ 2}]))),
+ <<":a:b:c:d:Y:">> = iolist_to_binary(join(re:split("XYabcdY","^X(?5)(a)(?|(b)|(q))(c)(d)(Y)",[]))),
+ <<":a:b:::c:d:Y">> = iolist_to_binary(join(re:split("XYabcdY","^X(?7)(a)(?|(b|(r)(s))|(q))(c)(d)(Y)",[trim]))),
<<":a:b:::c:d:Y:">> = iolist_to_binary(join(re:split("XYabcdY","^X(?7)(a)(?|(b|(r)(s))|(q))(c)(d)(Y)",[{parts,
- 2}]))),
- <<":a:b:::c:d:Y:">> = iolist_to_binary(join(re:split("XYabcdY","^X(?7)(a)(?|(b|(r)(s))|(q))(c)(d)(Y)",[]))),
- <<":a:b:::c:d:Y">> = iolist_to_binary(join(re:split("XYabcdY","^X(?7)(a)(?|(b|(?|(r)|(t))(s))|(q))(c)(d)(Y)",[trim]))),
+ 2}]))),
+ <<":a:b:::c:d:Y:">> = iolist_to_binary(join(re:split("XYabcdY","^X(?7)(a)(?|(b|(r)(s))|(q))(c)(d)(Y)",[]))),
+ <<":a:b:::c:d:Y">> = iolist_to_binary(join(re:split("XYabcdY","^X(?7)(a)(?|(b|(?|(r)|(t))(s))|(q))(c)(d)(Y)",[trim]))),
<<":a:b:::c:d:Y:">> = iolist_to_binary(join(re:split("XYabcdY","^X(?7)(a)(?|(b|(?|(r)|(t))(s))|(q))(c)(d)(Y)",[{parts,
- 2}]))),
- <<":a:b:::c:d:Y:">> = iolist_to_binary(join(re:split("XYabcdY","^X(?7)(a)(?|(b|(?|(r)|(t))(s))|(q))(c)(d)(Y)",[]))),
- <<":a:xyz">> = iolist_to_binary(join(re:split("a:aaxyz","(?'abc'\\w+):\\k<abc>{2}",[trim]))),
+ 2}]))),
+ <<":a:b:::c:d:Y:">> = iolist_to_binary(join(re:split("XYabcdY","^X(?7)(a)(?|(b|(?|(r)|(t))(s))|(q))(c)(d)(Y)",[]))),
+ <<":a:xyz">> = iolist_to_binary(join(re:split("a:aaxyz","(?'abc'\\w+):\\k<abc>{2}",[trim]))),
<<":a:xyz">> = iolist_to_binary(join(re:split("a:aaxyz","(?'abc'\\w+):\\k<abc>{2}",[{parts,
- 2}]))),
- <<":a:xyz">> = iolist_to_binary(join(re:split("a:aaxyz","(?'abc'\\w+):\\k<abc>{2}",[]))),
- <<":ab:xyz">> = iolist_to_binary(join(re:split("ab:ababxyz","(?'abc'\\w+):\\k<abc>{2}",[trim]))),
+ 2}]))),
+ <<":a:xyz">> = iolist_to_binary(join(re:split("a:aaxyz","(?'abc'\\w+):\\k<abc>{2}",[]))),
+ <<":ab:xyz">> = iolist_to_binary(join(re:split("ab:ababxyz","(?'abc'\\w+):\\k<abc>{2}",[trim]))),
<<":ab:xyz">> = iolist_to_binary(join(re:split("ab:ababxyz","(?'abc'\\w+):\\k<abc>{2}",[{parts,
- 2}]))),
- <<":ab:xyz">> = iolist_to_binary(join(re:split("ab:ababxyz","(?'abc'\\w+):\\k<abc>{2}",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?'abc'\\w+):\\k<abc>{2}",[trim]))),
+ 2}]))),
+ <<":ab:xyz">> = iolist_to_binary(join(re:split("ab:ababxyz","(?'abc'\\w+):\\k<abc>{2}",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?'abc'\\w+):\\k<abc>{2}",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?'abc'\\w+):\\k<abc>{2}",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?'abc'\\w+):\\k<abc>{2}",[]))),
- <<"a:axyz">> = iolist_to_binary(join(re:split("a:axyz","(?'abc'\\w+):\\k<abc>{2}",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?'abc'\\w+):\\k<abc>{2}",[]))),
+ <<"a:axyz">> = iolist_to_binary(join(re:split("a:axyz","(?'abc'\\w+):\\k<abc>{2}",[trim]))),
<<"a:axyz">> = iolist_to_binary(join(re:split("a:axyz","(?'abc'\\w+):\\k<abc>{2}",[{parts,
- 2}]))),
- <<"a:axyz">> = iolist_to_binary(join(re:split("a:axyz","(?'abc'\\w+):\\k<abc>{2}",[]))),
- <<"ab:abxyz">> = iolist_to_binary(join(re:split("ab:abxyz","(?'abc'\\w+):\\k<abc>{2}",[trim]))),
+ 2}]))),
+ <<"a:axyz">> = iolist_to_binary(join(re:split("a:axyz","(?'abc'\\w+):\\k<abc>{2}",[]))),
+ <<"ab:abxyz">> = iolist_to_binary(join(re:split("ab:abxyz","(?'abc'\\w+):\\k<abc>{2}",[trim]))),
<<"ab:abxyz">> = iolist_to_binary(join(re:split("ab:abxyz","(?'abc'\\w+):\\k<abc>{2}",[{parts,
- 2}]))),
- <<"ab:abxyz">> = iolist_to_binary(join(re:split("ab:abxyz","(?'abc'\\w+):\\k<abc>{2}",[]))),
- <<":a:xyz">> = iolist_to_binary(join(re:split("a:aaxyz","(?'abc'\\w+):\\g{abc}{2}",[trim]))),
+ 2}]))),
+ <<"ab:abxyz">> = iolist_to_binary(join(re:split("ab:abxyz","(?'abc'\\w+):\\k<abc>{2}",[]))),
+ <<":a:xyz">> = iolist_to_binary(join(re:split("a:aaxyz","(?'abc'\\w+):\\g{abc}{2}",[trim]))),
<<":a:xyz">> = iolist_to_binary(join(re:split("a:aaxyz","(?'abc'\\w+):\\g{abc}{2}",[{parts,
- 2}]))),
- <<":a:xyz">> = iolist_to_binary(join(re:split("a:aaxyz","(?'abc'\\w+):\\g{abc}{2}",[]))),
- <<":ab:xyz">> = iolist_to_binary(join(re:split("ab:ababxyz","(?'abc'\\w+):\\g{abc}{2}",[trim]))),
+ 2}]))),
+ <<":a:xyz">> = iolist_to_binary(join(re:split("a:aaxyz","(?'abc'\\w+):\\g{abc}{2}",[]))),
+ <<":ab:xyz">> = iolist_to_binary(join(re:split("ab:ababxyz","(?'abc'\\w+):\\g{abc}{2}",[trim]))),
<<":ab:xyz">> = iolist_to_binary(join(re:split("ab:ababxyz","(?'abc'\\w+):\\g{abc}{2}",[{parts,
- 2}]))),
- <<":ab:xyz">> = iolist_to_binary(join(re:split("ab:ababxyz","(?'abc'\\w+):\\g{abc}{2}",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?'abc'\\w+):\\g{abc}{2}",[trim]))),
+ 2}]))),
+ <<":ab:xyz">> = iolist_to_binary(join(re:split("ab:ababxyz","(?'abc'\\w+):\\g{abc}{2}",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?'abc'\\w+):\\g{abc}{2}",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?'abc'\\w+):\\g{abc}{2}",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?'abc'\\w+):\\g{abc}{2}",[]))),
- <<"a:axyz">> = iolist_to_binary(join(re:split("a:axyz","(?'abc'\\w+):\\g{abc}{2}",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?'abc'\\w+):\\g{abc}{2}",[]))),
+ <<"a:axyz">> = iolist_to_binary(join(re:split("a:axyz","(?'abc'\\w+):\\g{abc}{2}",[trim]))),
<<"a:axyz">> = iolist_to_binary(join(re:split("a:axyz","(?'abc'\\w+):\\g{abc}{2}",[{parts,
- 2}]))),
- <<"a:axyz">> = iolist_to_binary(join(re:split("a:axyz","(?'abc'\\w+):\\g{abc}{2}",[]))),
- <<"ab:abxyz">> = iolist_to_binary(join(re:split("ab:abxyz","(?'abc'\\w+):\\g{abc}{2}",[trim]))),
+ 2}]))),
+ <<"a:axyz">> = iolist_to_binary(join(re:split("a:axyz","(?'abc'\\w+):\\g{abc}{2}",[]))),
+ <<"ab:abxyz">> = iolist_to_binary(join(re:split("ab:abxyz","(?'abc'\\w+):\\g{abc}{2}",[trim]))),
<<"ab:abxyz">> = iolist_to_binary(join(re:split("ab:abxyz","(?'abc'\\w+):\\g{abc}{2}",[{parts,
- 2}]))),
- <<"ab:abxyz">> = iolist_to_binary(join(re:split("ab:abxyz","(?'abc'\\w+):\\g{abc}{2}",[]))),
+ 2}]))),
+ <<"ab:abxyz">> = iolist_to_binary(join(re:split("ab:abxyz","(?'abc'\\w+):\\g{abc}{2}",[]))),
<<":a">> = iolist_to_binary(join(re:split("abd","^(?<ab>a)? (?(<ab>)b|c) (?('ab')d|e)",[extended,
- trim]))),
+ trim]))),
<<":a:">> = iolist_to_binary(join(re:split("abd","^(?<ab>a)? (?(<ab>)b|c) (?('ab')d|e)",[extended,
{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("abd","^(?<ab>a)? (?(<ab>)b|c) (?('ab')d|e)",[extended]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("abd","^(?<ab>a)? (?(<ab>)b|c) (?('ab')d|e)",[extended]))),
<<"">> = iolist_to_binary(join(re:split("ce","^(?<ab>a)? (?(<ab>)b|c) (?('ab')d|e)",[extended,
- trim]))),
+ trim]))),
<<"::">> = iolist_to_binary(join(re:split("ce","^(?<ab>a)? (?(<ab>)b|c) (?('ab')d|e)",[extended,
{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("ce","^(?<ab>a)? (?(<ab>)b|c) (?('ab')d|e)",[extended]))),
- <<":aX">> = iolist_to_binary(join(re:split("aXaXZ","^(a.)\\g-1Z",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("ce","^(?<ab>a)? (?(<ab>)b|c) (?('ab')d|e)",[extended]))),
+ <<":aX">> = iolist_to_binary(join(re:split("aXaXZ","^(a.)\\g-1Z",[trim]))),
<<":aX:">> = iolist_to_binary(join(re:split("aXaXZ","^(a.)\\g-1Z",[{parts,
- 2}]))),
- <<":aX:">> = iolist_to_binary(join(re:split("aXaXZ","^(a.)\\g-1Z",[]))),
- <<":aX">> = iolist_to_binary(join(re:split("aXaXZ","^(a.)\\g{-1}Z",[trim]))),
+ 2}]))),
+ <<":aX:">> = iolist_to_binary(join(re:split("aXaXZ","^(a.)\\g-1Z",[]))),
+ <<":aX">> = iolist_to_binary(join(re:split("aXaXZ","^(a.)\\g{-1}Z",[trim]))),
<<":aX:">> = iolist_to_binary(join(re:split("aXaXZ","^(a.)\\g{-1}Z",[{parts,
- 2}]))),
- <<":aX:">> = iolist_to_binary(join(re:split("aXaXZ","^(a.)\\g{-1}Z",[]))),
+ 2}]))),
+ <<":aX:">> = iolist_to_binary(join(re:split("aXaXZ","^(a.)\\g{-1}Z",[]))),
<<":::cd">> = iolist_to_binary(join(re:split("abcd","^(?(DEFINE) (?<A> a) (?<B> b) ) (?&A) (?&B) ",[extended,
- trim]))),
+ trim]))),
<<":::cd">> = iolist_to_binary(join(re:split("abcd","^(?(DEFINE) (?<A> a) (?<B> b) ) (?&A) (?&B) ",[extended,
{parts,
- 2}]))),
- <<":::cd">> = iolist_to_binary(join(re:split("abcd","^(?(DEFINE) (?<A> a) (?<B> b) ) (?&A) (?&B) ",[extended]))),
+ 2}]))),
+ <<":::cd">> = iolist_to_binary(join(re:split("abcd","^(?(DEFINE) (?<A> a) (?<B> b) ) (?&A) (?&B) ",[extended]))),
<<":metcalfe:33">> = iolist_to_binary(join(re:split("metcalfe 33","(?<NAME>(?&NAME_PAT))\\s+(?<ADDR>(?&ADDRESS_PAT))
(?(DEFINE)
(?<NAME_PAT>[a-z]+)
(?<ADDRESS_PAT>\\d+)
- )",[extended,trim]))),
+ )",[extended,trim]))),
<<":metcalfe:33:::">> = iolist_to_binary(join(re:split("metcalfe 33","(?<NAME>(?&NAME_PAT))\\s+(?<ADDR>(?&ADDRESS_PAT))
(?(DEFINE)
(?<NAME_PAT>[a-z]+)
(?<ADDRESS_PAT>\\d+)
- )",[extended,{parts,2}]))),
+ )",[extended,{parts,2}]))),
<<":metcalfe:33:::">> = iolist_to_binary(join(re:split("metcalfe 33","(?<NAME>(?&NAME_PAT))\\s+(?<ADDR>(?&ADDRESS_PAT))
(?(DEFINE)
(?<NAME_PAT>[a-z]+)
(?<ADDRESS_PAT>\\d+)
- )",[extended]))),
- <<"::.4">> = iolist_to_binary(join(re:split("1.2.3.4","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[trim]))),
+ )",[extended]))),
+ <<"::.4">> = iolist_to_binary(join(re:split("1.2.3.4","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[trim]))),
<<"::.4:">> = iolist_to_binary(join(re:split("1.2.3.4","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[{parts,
- 2}]))),
- <<"::.4:">> = iolist_to_binary(join(re:split("1.2.3.4","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[]))),
- <<"::.206">> = iolist_to_binary(join(re:split("131.111.10.206","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[trim]))),
+ 2}]))),
+ <<"::.4:">> = iolist_to_binary(join(re:split("1.2.3.4","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[]))),
+ <<"::.206">> = iolist_to_binary(join(re:split("131.111.10.206","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[trim]))),
<<"::.206:">> = iolist_to_binary(join(re:split("131.111.10.206","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[{parts,
- 2}]))),
- <<"::.206:">> = iolist_to_binary(join(re:split("131.111.10.206","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[]))),
- <<"::.0">> = iolist_to_binary(join(re:split("10.0.0.0","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[trim]))),
+ 2}]))),
+ <<"::.206:">> = iolist_to_binary(join(re:split("131.111.10.206","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[]))),
+ <<"::.0">> = iolist_to_binary(join(re:split("10.0.0.0","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[trim]))),
<<"::.0:">> = iolist_to_binary(join(re:split("10.0.0.0","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[{parts,
- 2}]))),
- <<"::.0:">> = iolist_to_binary(join(re:split("10.0.0.0","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[trim]))),
+ 2}]))),
+ <<"::.0:">> = iolist_to_binary(join(re:split("10.0.0.0","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[]))),
- <<"10.6">> = iolist_to_binary(join(re:split("10.6","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[]))),
+ <<"10.6">> = iolist_to_binary(join(re:split("10.6","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[trim]))),
<<"10.6">> = iolist_to_binary(join(re:split("10.6","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[{parts,
- 2}]))),
- <<"10.6">> = iolist_to_binary(join(re:split("10.6","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[]))),
- <<"455.3.4.5">> = iolist_to_binary(join(re:split("455.3.4.5","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[trim]))),
+ 2}]))),
+ <<"10.6">> = iolist_to_binary(join(re:split("10.6","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[]))),
+ <<"455.3.4.5">> = iolist_to_binary(join(re:split("455.3.4.5","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[trim]))),
<<"455.3.4.5">> = iolist_to_binary(join(re:split("455.3.4.5","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[{parts,
- 2}]))),
- <<"455.3.4.5">> = iolist_to_binary(join(re:split("455.3.4.5","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[]))),
- <<":.4">> = iolist_to_binary(join(re:split("1.2.3.4","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[trim]))),
+ 2}]))),
+ <<"455.3.4.5">> = iolist_to_binary(join(re:split("455.3.4.5","(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))\\b(?&byte)(\\.(?&byte)){3}",[]))),
+ <<":.4">> = iolist_to_binary(join(re:split("1.2.3.4","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[trim]))),
<<":.4::">> = iolist_to_binary(join(re:split("1.2.3.4","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[{parts,
- 2}]))),
- <<":.4::">> = iolist_to_binary(join(re:split("1.2.3.4","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[]))),
- <<":.206">> = iolist_to_binary(join(re:split("131.111.10.206","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[trim]))),
+ 2}]))),
+ <<":.4::">> = iolist_to_binary(join(re:split("1.2.3.4","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[]))),
+ <<":.206">> = iolist_to_binary(join(re:split("131.111.10.206","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[trim]))),
<<":.206::">> = iolist_to_binary(join(re:split("131.111.10.206","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[{parts,
- 2}]))),
- <<":.206::">> = iolist_to_binary(join(re:split("131.111.10.206","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[]))),
- <<":.0">> = iolist_to_binary(join(re:split("10.0.0.0","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[trim]))),
+ 2}]))),
+ <<":.206::">> = iolist_to_binary(join(re:split("131.111.10.206","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[]))),
+ <<":.0">> = iolist_to_binary(join(re:split("10.0.0.0","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[trim]))),
<<":.0::">> = iolist_to_binary(join(re:split("10.0.0.0","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[{parts,
- 2}]))),
- <<":.0::">> = iolist_to_binary(join(re:split("10.0.0.0","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[trim]))),
+ 2}]))),
+ <<":.0::">> = iolist_to_binary(join(re:split("10.0.0.0","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[]))),
- <<"10.6">> = iolist_to_binary(join(re:split("10.6","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[]))),
+ <<"10.6">> = iolist_to_binary(join(re:split("10.6","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[trim]))),
<<"10.6">> = iolist_to_binary(join(re:split("10.6","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[{parts,
- 2}]))),
- <<"10.6">> = iolist_to_binary(join(re:split("10.6","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[]))),
- <<"455.3.4.5">> = iolist_to_binary(join(re:split("455.3.4.5","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[trim]))),
+ 2}]))),
+ <<"10.6">> = iolist_to_binary(join(re:split("10.6","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[]))),
+ <<"455.3.4.5">> = iolist_to_binary(join(re:split("455.3.4.5","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[trim]))),
<<"455.3.4.5">> = iolist_to_binary(join(re:split("455.3.4.5","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[{parts,
- 2}]))),
- <<"455.3.4.5">> = iolist_to_binary(join(re:split("455.3.4.5","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[]))),
- <<":party">> = iolist_to_binary(join(re:split("now is the time for all good men to come to the aid of the party","^(\\w++|\\s++)*$",[trim]))),
+ 2}]))),
+ <<"455.3.4.5">> = iolist_to_binary(join(re:split("455.3.4.5","\\b(?&byte)(\\.(?&byte)){3}(?(DEFINE)(?<byte>2[0-4]\\d|25[0-5]|1\\d\\d|[1-9]?\\d))",[]))),
+ <<":party">> = iolist_to_binary(join(re:split("now is the time for all good men to come to the aid of the party","^(\\w++|\\s++)*$",[trim]))),
<<":party:">> = iolist_to_binary(join(re:split("now is the time for all good men to come to the aid of the party","^(\\w++|\\s++)*$",[{parts,
- 2}]))),
- <<":party:">> = iolist_to_binary(join(re:split("now is the time for all good men to come to the aid of the party","^(\\w++|\\s++)*$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\w++|\\s++)*$",[trim]))),
+ 2}]))),
+ <<":party:">> = iolist_to_binary(join(re:split("now is the time for all good men to come to the aid of the party","^(\\w++|\\s++)*$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\w++|\\s++)*$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\w++|\\s++)*$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\w++|\\s++)*$",[]))),
- <<"this is not a line with only words and spaces!">> = iolist_to_binary(join(re:split("this is not a line with only words and spaces!","^(\\w++|\\s++)*$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\w++|\\s++)*$",[]))),
+ <<"this is not a line with only words and spaces!">> = iolist_to_binary(join(re:split("this is not a line with only words and spaces!","^(\\w++|\\s++)*$",[trim]))),
<<"this is not a line with only words and spaces!">> = iolist_to_binary(join(re:split("this is not a line with only words and spaces!","^(\\w++|\\s++)*$",[{parts,
- 2}]))),
- <<"this is not a line with only words and spaces!">> = iolist_to_binary(join(re:split("this is not a line with only words and spaces!","^(\\w++|\\s++)*$",[]))),
- <<":12345:a">> = iolist_to_binary(join(re:split("12345a","(\\d++)(\\w)",[trim]))),
+ 2}]))),
+ <<"this is not a line with only words and spaces!">> = iolist_to_binary(join(re:split("this is not a line with only words and spaces!","^(\\w++|\\s++)*$",[]))),
+ <<":12345:a">> = iolist_to_binary(join(re:split("12345a","(\\d++)(\\w)",[trim]))),
<<":12345:a:">> = iolist_to_binary(join(re:split("12345a","(\\d++)(\\w)",[{parts,
- 2}]))),
- <<":12345:a:">> = iolist_to_binary(join(re:split("12345a","(\\d++)(\\w)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(\\d++)(\\w)",[trim]))),
+ 2}]))),
+ <<":12345:a:">> = iolist_to_binary(join(re:split("12345a","(\\d++)(\\w)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(\\d++)(\\w)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(\\d++)(\\w)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(\\d++)(\\w)",[]))),
- <<"12345+">> = iolist_to_binary(join(re:split("12345+","(\\d++)(\\w)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","(\\d++)(\\w)",[]))),
+ <<"12345+">> = iolist_to_binary(join(re:split("12345+","(\\d++)(\\w)",[trim]))),
<<"12345+">> = iolist_to_binary(join(re:split("12345+","(\\d++)(\\w)",[{parts,
- 2}]))),
- <<"12345+">> = iolist_to_binary(join(re:split("12345+","(\\d++)(\\w)",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaab","a++b",[trim]))),
+ 2}]))),
+ <<"12345+">> = iolist_to_binary(join(re:split("12345+","(\\d++)(\\w)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaab","a++b",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaab","a++b",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaab","a++b",[]))),
- <<":aaab">> = iolist_to_binary(join(re:split("aaab","(a++b)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaab","a++b",[]))),
+ <<":aaab">> = iolist_to_binary(join(re:split("aaab","(a++b)",[trim]))),
<<":aaab:">> = iolist_to_binary(join(re:split("aaab","(a++b)",[{parts,
- 2}]))),
- <<":aaab:">> = iolist_to_binary(join(re:split("aaab","(a++b)",[]))),
- <<":aaa">> = iolist_to_binary(join(re:split("aaab","(a++)b",[trim]))),
+ 2}]))),
+ <<":aaab:">> = iolist_to_binary(join(re:split("aaab","(a++b)",[]))),
+ <<":aaa">> = iolist_to_binary(join(re:split("aaab","(a++)b",[trim]))),
<<":aaa:">> = iolist_to_binary(join(re:split("aaab","(a++)b",[{parts,
- 2}]))),
- <<":aaa:">> = iolist_to_binary(join(re:split("aaab","(a++)b",[]))),
- <<"((:x">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","([^()]++|\\([^()]*\\))+",[trim]))),
+ 2}]))),
+ <<":aaa:">> = iolist_to_binary(join(re:split("aaab","(a++)b",[]))),
+ <<"((:x">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","([^()]++|\\([^()]*\\))+",[trim]))),
<<"((:x:">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","([^()]++|\\([^()]*\\))+",[{parts,
- 2}]))),
- <<"((:x:">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","([^()]++|\\([^()]*\\))+",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("(abc)","\\(([^()]++|\\([^()]+\\))+\\)",[trim]))),
+ 2}]))),
+ <<"((:x:">> = iolist_to_binary(join(re:split("((abc(ade)ufh()()x","([^()]++|\\([^()]*\\))+",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("(abc)","\\(([^()]++|\\([^()]+\\))+\\)",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("(abc)","\\(([^()]++|\\([^()]+\\))+\\)",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("(abc)","\\(([^()]++|\\([^()]+\\))+\\)",[]))),
- <<":xyz">> = iolist_to_binary(join(re:split("(abc(def)xyz)","\\(([^()]++|\\([^()]+\\))+\\)",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("(abc)","\\(([^()]++|\\([^()]+\\))+\\)",[]))),
+ <<":xyz">> = iolist_to_binary(join(re:split("(abc(def)xyz)","\\(([^()]++|\\([^()]+\\))+\\)",[trim]))),
<<":xyz:">> = iolist_to_binary(join(re:split("(abc(def)xyz)","\\(([^()]++|\\([^()]+\\))+\\)",[{parts,
- 2}]))),
- <<":xyz:">> = iolist_to_binary(join(re:split("(abc(def)xyz)","\\(([^()]++|\\([^()]+\\))+\\)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\(([^()]++|\\([^()]+\\))+\\)",[trim]))),
+ 2}]))),
+ <<":xyz:">> = iolist_to_binary(join(re:split("(abc(def)xyz)","\\(([^()]++|\\([^()]+\\))+\\)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\(([^()]++|\\([^()]+\\))+\\)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\(([^()]++|\\([^()]+\\))+\\)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\(([^()]++|\\([^()]+\\))+\\)",[]))),
- <<"((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","\\(([^()]++|\\([^()]+\\))+\\)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","\\(([^()]++|\\([^()]+\\))+\\)",[]))),
+ <<"((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","\\(([^()]++|\\([^()]+\\))+\\)",[trim]))),
<<"((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","\\(([^()]++|\\([^()]+\\))+\\)",[{parts,
- 2}]))),
- <<"((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","\\(([^()]++|\\([^()]+\\))+\\)",[]))),
- <<":c">> = iolist_to_binary(join(re:split("abc","^([^()]|\\((?1)*\\))*$",[trim]))),
+ 2}]))),
+ <<"((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa">> = iolist_to_binary(join(re:split("((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa","\\(([^()]++|\\([^()]+\\))+\\)",[]))),
+ <<":c">> = iolist_to_binary(join(re:split("abc","^([^()]|\\((?1)*\\))*$",[trim]))),
<<":c:">> = iolist_to_binary(join(re:split("abc","^([^()]|\\((?1)*\\))*$",[{parts,
- 2}]))),
- <<":c:">> = iolist_to_binary(join(re:split("abc","^([^()]|\\((?1)*\\))*$",[]))),
- <<":c">> = iolist_to_binary(join(re:split("a(b)c","^([^()]|\\((?1)*\\))*$",[trim]))),
+ 2}]))),
+ <<":c:">> = iolist_to_binary(join(re:split("abc","^([^()]|\\((?1)*\\))*$",[]))),
+ <<":c">> = iolist_to_binary(join(re:split("a(b)c","^([^()]|\\((?1)*\\))*$",[trim]))),
<<":c:">> = iolist_to_binary(join(re:split("a(b)c","^([^()]|\\((?1)*\\))*$",[{parts,
- 2}]))),
- <<":c:">> = iolist_to_binary(join(re:split("a(b)c","^([^()]|\\((?1)*\\))*$",[]))),
- <<":d">> = iolist_to_binary(join(re:split("a(b(c))d","^([^()]|\\((?1)*\\))*$",[trim]))),
+ 2}]))),
+ <<":c:">> = iolist_to_binary(join(re:split("a(b)c","^([^()]|\\((?1)*\\))*$",[]))),
+ <<":d">> = iolist_to_binary(join(re:split("a(b(c))d","^([^()]|\\((?1)*\\))*$",[trim]))),
<<":d:">> = iolist_to_binary(join(re:split("a(b(c))d","^([^()]|\\((?1)*\\))*$",[{parts,
- 2}]))),
- <<":d:">> = iolist_to_binary(join(re:split("a(b(c))d","^([^()]|\\((?1)*\\))*$",[]))),
- <<"*** Failers)">> = iolist_to_binary(join(re:split("*** Failers)","^([^()]|\\((?1)*\\))*$",[trim]))),
+ 2}]))),
+ <<":d:">> = iolist_to_binary(join(re:split("a(b(c))d","^([^()]|\\((?1)*\\))*$",[]))),
+ <<"*** Failers)">> = iolist_to_binary(join(re:split("*** Failers)","^([^()]|\\((?1)*\\))*$",[trim]))),
<<"*** Failers)">> = iolist_to_binary(join(re:split("*** Failers)","^([^()]|\\((?1)*\\))*$",[{parts,
- 2}]))),
- <<"*** Failers)">> = iolist_to_binary(join(re:split("*** Failers)","^([^()]|\\((?1)*\\))*$",[]))),
- <<"a(b(c)d">> = iolist_to_binary(join(re:split("a(b(c)d","^([^()]|\\((?1)*\\))*$",[trim]))),
+ 2}]))),
+ <<"*** Failers)">> = iolist_to_binary(join(re:split("*** Failers)","^([^()]|\\((?1)*\\))*$",[]))),
+ <<"a(b(c)d">> = iolist_to_binary(join(re:split("a(b(c)d","^([^()]|\\((?1)*\\))*$",[trim]))),
<<"a(b(c)d">> = iolist_to_binary(join(re:split("a(b(c)d","^([^()]|\\((?1)*\\))*$",[{parts,
- 2}]))),
- <<"a(b(c)d">> = iolist_to_binary(join(re:split("a(b(c)d","^([^()]|\\((?1)*\\))*$",[]))),
+ 2}]))),
+ <<"a(b(c)d">> = iolist_to_binary(join(re:split("a(b(c)d","^([^()]|\\((?1)*\\))*$",[]))),
ok.
run42() ->
- <<":3">> = iolist_to_binary(join(re:split(">abc>123<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[trim]))),
+ <<":3">> = iolist_to_binary(join(re:split(">abc>123<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[trim]))),
<<":3:">> = iolist_to_binary(join(re:split(">abc>123<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[{parts,
- 2}]))),
- <<":3:">> = iolist_to_binary(join(re:split(">abc>123<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[]))),
- <<":3">> = iolist_to_binary(join(re:split(">abc>1(2)3<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[trim]))),
+ 2}]))),
+ <<":3:">> = iolist_to_binary(join(re:split(">abc>123<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[]))),
+ <<":3">> = iolist_to_binary(join(re:split(">abc>1(2)3<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[trim]))),
<<":3:">> = iolist_to_binary(join(re:split(">abc>1(2)3<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[{parts,
- 2}]))),
- <<":3:">> = iolist_to_binary(join(re:split(">abc>1(2)3<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[]))),
- <<":(1(2)3)">> = iolist_to_binary(join(re:split(">abc>(1(2)3)<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[trim]))),
+ 2}]))),
+ <<":3:">> = iolist_to_binary(join(re:split(">abc>1(2)3<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[]))),
+ <<":(1(2)3)">> = iolist_to_binary(join(re:split(">abc>(1(2)3)<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[trim]))),
<<":(1(2)3):">> = iolist_to_binary(join(re:split(">abc>(1(2)3)<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[{parts,
- 2}]))),
- <<":(1(2)3):">> = iolist_to_binary(join(re:split(">abc>(1(2)3)<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[]))),
+ 2}]))),
+ <<":(1(2)3):">> = iolist_to_binary(join(re:split(">abc>(1(2)3)<xyz<","^>abc>([^()]|\\((?1)*\\))*<xyz<$",[]))),
<<":1221:1">> = iolist_to_binary(join(re:split("1221","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless,
- trim]))),
+ trim]))),
<<":1221:1:::">> = iolist_to_binary(join(re:split("1221","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless,
{parts,
- 2}]))),
- <<":1221:1:::">> = iolist_to_binary(join(re:split("1221","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless]))),
+ 2}]))),
+ <<":1221:1:::">> = iolist_to_binary(join(re:split("1221","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless]))),
<<":::Satanoscillatemymetallicsonatas:S">> = iolist_to_binary(join(re:split("Satanoscillatemymetallicsonatas","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless,
- trim]))),
+ trim]))),
<<":::Satanoscillatemymetallicsonatas:S:">> = iolist_to_binary(join(re:split("Satanoscillatemymetallicsonatas","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless,
{parts,
- 2}]))),
- <<":::Satanoscillatemymetallicsonatas:S:">> = iolist_to_binary(join(re:split("Satanoscillatemymetallicsonatas","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless]))),
+ 2}]))),
+ <<":::Satanoscillatemymetallicsonatas:S:">> = iolist_to_binary(join(re:split("Satanoscillatemymetallicsonatas","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless]))),
<<":::AmanaplanacanalPanama:A">> = iolist_to_binary(join(re:split("AmanaplanacanalPanama","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless,
- trim]))),
+ trim]))),
<<":::AmanaplanacanalPanama:A:">> = iolist_to_binary(join(re:split("AmanaplanacanalPanama","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless,
{parts,
- 2}]))),
- <<":::AmanaplanacanalPanama:A:">> = iolist_to_binary(join(re:split("AmanaplanacanalPanama","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless]))),
+ 2}]))),
+ <<":::AmanaplanacanalPanama:A:">> = iolist_to_binary(join(re:split("AmanaplanacanalPanama","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless]))),
<<":::AblewasIereIsawElba:A">> = iolist_to_binary(join(re:split("AblewasIereIsawElba","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless,
- trim]))),
+ trim]))),
<<":::AblewasIereIsawElba:A:">> = iolist_to_binary(join(re:split("AblewasIereIsawElba","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless,
{parts,
- 2}]))),
- <<":::AblewasIereIsawElba:A:">> = iolist_to_binary(join(re:split("AblewasIereIsawElba","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless]))),
+ 2}]))),
+ <<":::AblewasIereIsawElba:A:">> = iolist_to_binary(join(re:split("AblewasIereIsawElba","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless]))),
<<"Thequickbrownfox">> = iolist_to_binary(join(re:split("Thequickbrownfox","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless,
- trim]))),
+ trim]))),
<<"Thequickbrownfox">> = iolist_to_binary(join(re:split("Thequickbrownfox","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless,
{parts,
- 2}]))),
- <<"Thequickbrownfox">> = iolist_to_binary(join(re:split("Thequickbrownfox","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless]))),
- <<":12">> = iolist_to_binary(join(re:split("12","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[trim]))),
+ 2}]))),
+ <<"Thequickbrownfox">> = iolist_to_binary(join(re:split("Thequickbrownfox","^(?:((.)(?1)\\2|)|((.)(?3)\\4|.))$",[caseless]))),
+ <<":12">> = iolist_to_binary(join(re:split("12","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[trim]))),
<<":12::">> = iolist_to_binary(join(re:split("12","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[{parts,
- 2}]))),
- <<":12::">> = iolist_to_binary(join(re:split("12","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[]))),
- <<":(((2+2)*-3)-7):-">> = iolist_to_binary(join(re:split("(((2+2)*-3)-7)","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[trim]))),
+ 2}]))),
+ <<":12::">> = iolist_to_binary(join(re:split("12","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[]))),
+ <<":(((2+2)*-3)-7):-">> = iolist_to_binary(join(re:split("(((2+2)*-3)-7)","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[trim]))),
<<":(((2+2)*-3)-7):-:">> = iolist_to_binary(join(re:split("(((2+2)*-3)-7)","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[{parts,
- 2}]))),
- <<":(((2+2)*-3)-7):-:">> = iolist_to_binary(join(re:split("(((2+2)*-3)-7)","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[]))),
- <<":-12">> = iolist_to_binary(join(re:split("-12","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[trim]))),
+ 2}]))),
+ <<":(((2+2)*-3)-7):-:">> = iolist_to_binary(join(re:split("(((2+2)*-3)-7)","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[]))),
+ <<":-12">> = iolist_to_binary(join(re:split("-12","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[trim]))),
<<":-12::">> = iolist_to_binary(join(re:split("-12","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[{parts,
- 2}]))),
- <<":-12::">> = iolist_to_binary(join(re:split("-12","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[trim]))),
+ 2}]))),
+ <<":-12::">> = iolist_to_binary(join(re:split("-12","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[]))),
- <<"((2+2)*-3)-7)">> = iolist_to_binary(join(re:split("((2+2)*-3)-7)","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[]))),
+ <<"((2+2)*-3)-7)">> = iolist_to_binary(join(re:split("((2+2)*-3)-7)","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[trim]))),
<<"((2+2)*-3)-7)">> = iolist_to_binary(join(re:split("((2+2)*-3)-7)","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[{parts,
- 2}]))),
- <<"((2+2)*-3)-7)">> = iolist_to_binary(join(re:split("((2+2)*-3)-7)","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[]))),
- <<":xyz:y">> = iolist_to_binary(join(re:split("xyz","^(x(y|(?1){2})z)",[trim]))),
+ 2}]))),
+ <<"((2+2)*-3)-7)">> = iolist_to_binary(join(re:split("((2+2)*-3)-7)","^(\\d+|\\((?1)([+*-])(?1)\\)|-(?1))$",[]))),
+ <<":xyz:y">> = iolist_to_binary(join(re:split("xyz","^(x(y|(?1){2})z)",[trim]))),
<<":xyz:y:">> = iolist_to_binary(join(re:split("xyz","^(x(y|(?1){2})z)",[{parts,
- 2}]))),
- <<":xyz:y:">> = iolist_to_binary(join(re:split("xyz","^(x(y|(?1){2})z)",[]))),
- <<":xxyzxyzz:xyzxyz">> = iolist_to_binary(join(re:split("xxyzxyzz","^(x(y|(?1){2})z)",[trim]))),
+ 2}]))),
+ <<":xyz:y:">> = iolist_to_binary(join(re:split("xyz","^(x(y|(?1){2})z)",[]))),
+ <<":xxyzxyzz:xyzxyz">> = iolist_to_binary(join(re:split("xxyzxyzz","^(x(y|(?1){2})z)",[trim]))),
<<":xxyzxyzz:xyzxyz:">> = iolist_to_binary(join(re:split("xxyzxyzz","^(x(y|(?1){2})z)",[{parts,
- 2}]))),
- <<":xxyzxyzz:xyzxyz:">> = iolist_to_binary(join(re:split("xxyzxyzz","^(x(y|(?1){2})z)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(x(y|(?1){2})z)",[trim]))),
+ 2}]))),
+ <<":xxyzxyzz:xyzxyz:">> = iolist_to_binary(join(re:split("xxyzxyzz","^(x(y|(?1){2})z)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(x(y|(?1){2})z)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(x(y|(?1){2})z)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(x(y|(?1){2})z)",[]))),
- <<"xxyzz">> = iolist_to_binary(join(re:split("xxyzz","^(x(y|(?1){2})z)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(x(y|(?1){2})z)",[]))),
+ <<"xxyzz">> = iolist_to_binary(join(re:split("xxyzz","^(x(y|(?1){2})z)",[trim]))),
<<"xxyzz">> = iolist_to_binary(join(re:split("xxyzz","^(x(y|(?1){2})z)",[{parts,
- 2}]))),
- <<"xxyzz">> = iolist_to_binary(join(re:split("xxyzz","^(x(y|(?1){2})z)",[]))),
- <<"xxyzxyzxyzz">> = iolist_to_binary(join(re:split("xxyzxyzxyzz","^(x(y|(?1){2})z)",[trim]))),
+ 2}]))),
+ <<"xxyzz">> = iolist_to_binary(join(re:split("xxyzz","^(x(y|(?1){2})z)",[]))),
+ <<"xxyzxyzxyzz">> = iolist_to_binary(join(re:split("xxyzxyzxyzz","^(x(y|(?1){2})z)",[trim]))),
<<"xxyzxyzxyzz">> = iolist_to_binary(join(re:split("xxyzxyzxyzz","^(x(y|(?1){2})z)",[{parts,
- 2}]))),
- <<"xxyzxyzxyzz">> = iolist_to_binary(join(re:split("xxyzxyzxyzz","^(x(y|(?1){2})z)",[]))),
+ 2}]))),
+ <<"xxyzxyzxyzz">> = iolist_to_binary(join(re:split("xxyzxyzxyzz","^(x(y|(?1){2})z)",[]))),
<<":<>:<>">> = iolist_to_binary(join(re:split("<>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
- trim]))),
+ trim]))),
<<":<>:<>:">> = iolist_to_binary(join(re:split("<>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
{parts,
- 2}]))),
- <<":<>:<>:">> = iolist_to_binary(join(re:split("<>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
+ 2}]))),
+ <<":<>:<>:">> = iolist_to_binary(join(re:split("<>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
<<":<abcd>:<abcd>">> = iolist_to_binary(join(re:split("<abcd>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
- trim]))),
+ trim]))),
<<":<abcd>:<abcd>:">> = iolist_to_binary(join(re:split("<abcd>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
{parts,
- 2}]))),
- <<":<abcd>:<abcd>:">> = iolist_to_binary(join(re:split("<abcd>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
+ 2}]))),
+ <<":<abcd>:<abcd>:">> = iolist_to_binary(join(re:split("<abcd>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
<<":<abc <123> hij>:<abc <123> hij>">> = iolist_to_binary(join(re:split("<abc <123> hij>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
- trim]))),
+ trim]))),
<<":<abc <123> hij>:<abc <123> hij>:">> = iolist_to_binary(join(re:split("<abc <123> hij>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
{parts,
- 2}]))),
- <<":<abc <123> hij>:<abc <123> hij>:">> = iolist_to_binary(join(re:split("<abc <123> hij>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
+ 2}]))),
+ <<":<abc <123> hij>:<abc <123> hij>:">> = iolist_to_binary(join(re:split("<abc <123> hij>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
<<"<abc :<def>:<def>: hij>">> = iolist_to_binary(join(re:split("<abc <def> hij>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
- trim]))),
+ trim]))),
<<"<abc :<def>:<def>: hij>">> = iolist_to_binary(join(re:split("<abc <def> hij>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
{parts,
- 2}]))),
- <<"<abc :<def>:<def>: hij>">> = iolist_to_binary(join(re:split("<abc <def> hij>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
+ 2}]))),
+ <<"<abc :<def>:<def>: hij>">> = iolist_to_binary(join(re:split("<abc <def> hij>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
<<":<abc<>def>:<abc<>def>">> = iolist_to_binary(join(re:split("<abc<>def>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
- trim]))),
+ trim]))),
<<":<abc<>def>:<abc<>def>:">> = iolist_to_binary(join(re:split("<abc<>def>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
{parts,
- 2}]))),
- <<":<abc<>def>:<abc<>def>:">> = iolist_to_binary(join(re:split("<abc<>def>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
+ 2}]))),
+ <<":<abc<>def>:<abc<>def>:">> = iolist_to_binary(join(re:split("<abc<>def>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
<<"<abc:<>:<>">> = iolist_to_binary(join(re:split("<abc<>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
- trim]))),
+ trim]))),
<<"<abc:<>:<>:">> = iolist_to_binary(join(re:split("<abc<>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
{parts,
- 2}]))),
- <<"<abc:<>:<>:">> = iolist_to_binary(join(re:split("<abc<>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
+ 2}]))),
+ <<"<abc:<>:<>:">> = iolist_to_binary(join(re:split("<abc<>","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
<<"<abc">> = iolist_to_binary(join(re:split("<abc","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
- trim]))),
+ trim]))),
<<"<abc">> = iolist_to_binary(join(re:split("<abc","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended,
{parts,
- 2}]))),
- <<"<abc">> = iolist_to_binary(join(re:split("<abc","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
- <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^a+(*FAIL)",[trim]))),
+ 2}]))),
+ <<"<abc">> = iolist_to_binary(join(re:split("<abc","((< (?: (?(R) \\d++ | [^<>]*+) | (?2)) * >))",[extended]))),
+ <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^a+(*FAIL)",[trim]))),
<<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^a+(*FAIL)",[{parts,
- 2}]))),
- <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^a+(*FAIL)",[]))),
- <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?c+(*FAIL)",[trim]))),
+ 2}]))),
+ <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^a+(*FAIL)",[]))),
+ <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?c+(*FAIL)",[trim]))),
<<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?c+(*FAIL)",[{parts,
- 2}]))),
- <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?c+(*FAIL)",[]))),
- <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*PRUNE)c+(*FAIL)",[trim]))),
+ 2}]))),
+ <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?c+(*FAIL)",[]))),
+ <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*PRUNE)c+(*FAIL)",[trim]))),
<<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*PRUNE)c+(*FAIL)",[{parts,
- 2}]))),
- <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*PRUNE)c+(*FAIL)",[]))),
- <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*COMMIT)c+(*FAIL)",[trim]))),
+ 2}]))),
+ <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*PRUNE)c+(*FAIL)",[]))),
+ <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*COMMIT)c+(*FAIL)",[trim]))),
<<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*COMMIT)c+(*FAIL)",[{parts,
- 2}]))),
- <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*COMMIT)c+(*FAIL)",[]))),
- <<"aaabcccaaabccc">> = iolist_to_binary(join(re:split("aaabcccaaabccc","a+b?(*SKIP)c+(*FAIL)",[trim]))),
+ 2}]))),
+ <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*COMMIT)c+(*FAIL)",[]))),
+ <<"aaabcccaaabccc">> = iolist_to_binary(join(re:split("aaabcccaaabccc","a+b?(*SKIP)c+(*FAIL)",[trim]))),
<<"aaabcccaaabccc">> = iolist_to_binary(join(re:split("aaabcccaaabccc","a+b?(*SKIP)c+(*FAIL)",[{parts,
- 2}]))),
- <<"aaabcccaaabccc">> = iolist_to_binary(join(re:split("aaabcccaaabccc","a+b?(*SKIP)c+(*FAIL)",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaxxxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<"aaabcccaaabccc">> = iolist_to_binary(join(re:split("aaabcccaaabccc","a+b?(*SKIP)c+(*FAIL)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaxxxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaxxxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaxxxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<":++++++">> = iolist_to_binary(join(re:split("aaa++++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaxxxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<":++++++">> = iolist_to_binary(join(re:split("aaa++++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":++++++">> = iolist_to_binary(join(re:split("aaa++++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":++++++">> = iolist_to_binary(join(re:split("aaa++++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<"">> = iolist_to_binary(join(re:split("bbbxxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<":++++++">> = iolist_to_binary(join(re:split("aaa++++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<"">> = iolist_to_binary(join(re:split("bbbxxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":">> = iolist_to_binary(join(re:split("bbbxxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("bbbxxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<":+++++">> = iolist_to_binary(join(re:split("bbb+++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("bbbxxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<":+++++">> = iolist_to_binary(join(re:split("bbb+++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":+++++">> = iolist_to_binary(join(re:split("bbb+++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":+++++">> = iolist_to_binary(join(re:split("bbb+++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<"">> = iolist_to_binary(join(re:split("cccxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<":+++++">> = iolist_to_binary(join(re:split("bbb+++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<"">> = iolist_to_binary(join(re:split("cccxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":">> = iolist_to_binary(join(re:split("cccxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("cccxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<":++++">> = iolist_to_binary(join(re:split("ccc++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("cccxxxx","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<":++++">> = iolist_to_binary(join(re:split("ccc++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":++++">> = iolist_to_binary(join(re:split("ccc++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":++++">> = iolist_to_binary(join(re:split("ccc++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<":ddddd">> = iolist_to_binary(join(re:split("dddddddd","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<":++++">> = iolist_to_binary(join(re:split("ccc++++","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<":ddddd">> = iolist_to_binary(join(re:split("dddddddd","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":ddddd">> = iolist_to_binary(join(re:split("dddddddd","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":ddddd">> = iolist_to_binary(join(re:split("dddddddd","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<":aaaxxxxxx">> = iolist_to_binary(join(re:split("aaaxxxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<":ddddd">> = iolist_to_binary(join(re:split("dddddddd","^(?:aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<":aaaxxxxxx">> = iolist_to_binary(join(re:split("aaaxxxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":aaaxxxxxx:">> = iolist_to_binary(join(re:split("aaaxxxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":aaaxxxxxx:">> = iolist_to_binary(join(re:split("aaaxxxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<":aaa:++++++">> = iolist_to_binary(join(re:split("aaa++++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<":aaaxxxxxx:">> = iolist_to_binary(join(re:split("aaaxxxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<":aaa:++++++">> = iolist_to_binary(join(re:split("aaa++++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":aaa:++++++">> = iolist_to_binary(join(re:split("aaa++++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":aaa:++++++">> = iolist_to_binary(join(re:split("aaa++++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<":bbbxxxxx">> = iolist_to_binary(join(re:split("bbbxxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<":aaa:++++++">> = iolist_to_binary(join(re:split("aaa++++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<":bbbxxxxx">> = iolist_to_binary(join(re:split("bbbxxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":bbbxxxxx:">> = iolist_to_binary(join(re:split("bbbxxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":bbbxxxxx:">> = iolist_to_binary(join(re:split("bbbxxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<":bbb:+++++">> = iolist_to_binary(join(re:split("bbb+++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<":bbbxxxxx:">> = iolist_to_binary(join(re:split("bbbxxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<":bbb:+++++">> = iolist_to_binary(join(re:split("bbb+++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":bbb:+++++">> = iolist_to_binary(join(re:split("bbb+++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":bbb:+++++">> = iolist_to_binary(join(re:split("bbb+++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<":cccxxxx">> = iolist_to_binary(join(re:split("cccxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<":bbb:+++++">> = iolist_to_binary(join(re:split("bbb+++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<":cccxxxx">> = iolist_to_binary(join(re:split("cccxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":cccxxxx:">> = iolist_to_binary(join(re:split("cccxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":cccxxxx:">> = iolist_to_binary(join(re:split("cccxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<":ccc:++++">> = iolist_to_binary(join(re:split("ccc++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<":cccxxxx:">> = iolist_to_binary(join(re:split("cccxxxx","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<":ccc:++++">> = iolist_to_binary(join(re:split("ccc++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":ccc:++++">> = iolist_to_binary(join(re:split("ccc++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":ccc:++++">> = iolist_to_binary(join(re:split("ccc++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<":ddd:ddddd">> = iolist_to_binary(join(re:split("dddddddd","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
+ 2}]))),
+ <<":ccc:++++">> = iolist_to_binary(join(re:split("ccc++++","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<":ddd:ddddd">> = iolist_to_binary(join(re:split("dddddddd","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[trim]))),
<<":ddd:ddddd">> = iolist_to_binary(join(re:split("dddddddd","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[{parts,
- 2}]))),
- <<":ddd:ddddd">> = iolist_to_binary(join(re:split("dddddddd","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
- <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*THEN)c+(*FAIL)",[trim]))),
+ 2}]))),
+ <<":ddd:ddddd">> = iolist_to_binary(join(re:split("dddddddd","^(aaa(*THEN)\\w{6}|bbb(*THEN)\\w{5}|ccc(*THEN)\\w{4}|\\w{3})",[]))),
+ <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*THEN)c+(*FAIL)",[trim]))),
<<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*THEN)c+(*FAIL)",[{parts,
- 2}]))),
- <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*THEN)c+(*FAIL)",[]))),
+ 2}]))),
+ <<"aaabccc">> = iolist_to_binary(join(re:split("aaabccc","a+b?(*THEN)c+(*FAIL)",[]))),
<<":AB:B">> = iolist_to_binary(join(re:split("AB","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
- trim]))),
+ trim]))),
<<":AB:B::">> = iolist_to_binary(join(re:split("AB","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
{parts,
- 2}]))),
- <<":AB:B::">> = iolist_to_binary(join(re:split("AB","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
+ 2}]))),
+ <<":AB:B::">> = iolist_to_binary(join(re:split("AB","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
<<":AB:B::X">> = iolist_to_binary(join(re:split("ABX","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
- trim]))),
+ trim]))),
<<":AB:B::X">> = iolist_to_binary(join(re:split("ABX","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
{parts,
- 2}]))),
- <<":AB:B::X">> = iolist_to_binary(join(re:split("ABX","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
+ 2}]))),
+ <<":AB:B::X">> = iolist_to_binary(join(re:split("ABX","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
<<":AAD:A:E">> = iolist_to_binary(join(re:split("AADE","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
- trim]))),
+ trim]))),
<<":AAD:A:E:">> = iolist_to_binary(join(re:split("AADE","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
{parts,
- 2}]))),
- <<":AAD:A:E:">> = iolist_to_binary(join(re:split("AADE","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
+ 2}]))),
+ <<":AAD:A:E:">> = iolist_to_binary(join(re:split("AADE","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
<<":ACD:C:E">> = iolist_to_binary(join(re:split("ACDE","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
- trim]))),
+ trim]))),
<<":ACD:C:E:">> = iolist_to_binary(join(re:split("ACDE","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
{parts,
- 2}]))),
- <<":ACD:C:E:">> = iolist_to_binary(join(re:split("ACDE","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
+ 2}]))),
+ <<":ACD:C:E:">> = iolist_to_binary(join(re:split("ACDE","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
- trim]))),
+ trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
<<"AD">> = iolist_to_binary(join(re:split("AD","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
- trim]))),
+ trim]))),
<<"AD">> = iolist_to_binary(join(re:split("AD","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
{parts,
- 2}]))),
- <<"AD">> = iolist_to_binary(join(re:split("AD","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
+ 2}]))),
+ <<"AD">> = iolist_to_binary(join(re:split("AD","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
<<":1221:1">> = iolist_to_binary(join(re:split("1221","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless,
- trim]))),
+ trim]))),
<<":1221:1:::">> = iolist_to_binary(join(re:split("1221","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless,
{parts,
- 2}]))),
- <<":1221:1:::">> = iolist_to_binary(join(re:split("1221","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless]))),
+ 2}]))),
+ <<":1221:1:::">> = iolist_to_binary(join(re:split("1221","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless]))),
<<":::Satan, oscillate my metallic sonatas:S">> = iolist_to_binary(join(re:split("Satan, oscillate my metallic sonatas!","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless,
- trim]))),
+ trim]))),
<<":::Satan, oscillate my metallic sonatas:S:">> = iolist_to_binary(join(re:split("Satan, oscillate my metallic sonatas!","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless,
{parts,
- 2}]))),
- <<":::Satan, oscillate my metallic sonatas:S:">> = iolist_to_binary(join(re:split("Satan, oscillate my metallic sonatas!","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless]))),
+ 2}]))),
+ <<":::Satan, oscillate my metallic sonatas:S:">> = iolist_to_binary(join(re:split("Satan, oscillate my metallic sonatas!","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless]))),
<<":::A man, a plan, a canal: Panama:A">> = iolist_to_binary(join(re:split("A man, a plan, a canal: Panama!","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless,
- trim]))),
+ trim]))),
<<":::A man, a plan, a canal: Panama:A:">> = iolist_to_binary(join(re:split("A man, a plan, a canal: Panama!","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless,
{parts,
- 2}]))),
- <<":::A man, a plan, a canal: Panama:A:">> = iolist_to_binary(join(re:split("A man, a plan, a canal: Panama!","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless]))),
+ 2}]))),
+ <<":::A man, a plan, a canal: Panama:A:">> = iolist_to_binary(join(re:split("A man, a plan, a canal: Panama!","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless]))),
<<":::Able was I ere I saw Elba:A">> = iolist_to_binary(join(re:split("Able was I ere I saw Elba.","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless,
- trim]))),
+ trim]))),
<<":::Able was I ere I saw Elba:A:">> = iolist_to_binary(join(re:split("Able was I ere I saw Elba.","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless,
{parts,
- 2}]))),
- <<":::Able was I ere I saw Elba:A:">> = iolist_to_binary(join(re:split("Able was I ere I saw Elba.","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless]))),
+ 2}]))),
+ <<":::Able was I ere I saw Elba:A:">> = iolist_to_binary(join(re:split("Able was I ere I saw Elba.","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless,
- trim]))),
+ trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless,
{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless]))),
<<"The quick brown fox">> = iolist_to_binary(join(re:split("The quick brown fox","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless,
- trim]))),
+ trim]))),
<<"The quick brown fox">> = iolist_to_binary(join(re:split("The quick brown fox","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless,
{parts,
- 2}]))),
- <<"The quick brown fox">> = iolist_to_binary(join(re:split("The quick brown fox","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless]))),
- <<":a">> = iolist_to_binary(join(re:split("a","^((.)(?1)\\2|.)$",[trim]))),
+ 2}]))),
+ <<"The quick brown fox">> = iolist_to_binary(join(re:split("The quick brown fox","^\\W*+(?:((.)\\W*+(?1)\\W*+\\2|)|((.)\\W*+(?3)\\W*+\\4|\\W*+.\\W*+))\\W*+$",[caseless]))),
+ <<":a">> = iolist_to_binary(join(re:split("a","^((.)(?1)\\2|.)$",[trim]))),
<<":a::">> = iolist_to_binary(join(re:split("a","^((.)(?1)\\2|.)$",[{parts,
- 2}]))),
- <<":a::">> = iolist_to_binary(join(re:split("a","^((.)(?1)\\2|.)$",[]))),
- <<":aba:a">> = iolist_to_binary(join(re:split("aba","^((.)(?1)\\2|.)$",[trim]))),
+ 2}]))),
+ <<":a::">> = iolist_to_binary(join(re:split("a","^((.)(?1)\\2|.)$",[]))),
+ <<":aba:a">> = iolist_to_binary(join(re:split("aba","^((.)(?1)\\2|.)$",[trim]))),
<<":aba:a:">> = iolist_to_binary(join(re:split("aba","^((.)(?1)\\2|.)$",[{parts,
- 2}]))),
- <<":aba:a:">> = iolist_to_binary(join(re:split("aba","^((.)(?1)\\2|.)$",[]))),
- <<":aabaa:a">> = iolist_to_binary(join(re:split("aabaa","^((.)(?1)\\2|.)$",[trim]))),
+ 2}]))),
+ <<":aba:a:">> = iolist_to_binary(join(re:split("aba","^((.)(?1)\\2|.)$",[]))),
+ <<":aabaa:a">> = iolist_to_binary(join(re:split("aabaa","^((.)(?1)\\2|.)$",[trim]))),
<<":aabaa:a:">> = iolist_to_binary(join(re:split("aabaa","^((.)(?1)\\2|.)$",[{parts,
- 2}]))),
- <<":aabaa:a:">> = iolist_to_binary(join(re:split("aabaa","^((.)(?1)\\2|.)$",[]))),
- <<":abcdcba:a">> = iolist_to_binary(join(re:split("abcdcba","^((.)(?1)\\2|.)$",[trim]))),
+ 2}]))),
+ <<":aabaa:a:">> = iolist_to_binary(join(re:split("aabaa","^((.)(?1)\\2|.)$",[]))),
+ <<":abcdcba:a">> = iolist_to_binary(join(re:split("abcdcba","^((.)(?1)\\2|.)$",[trim]))),
<<":abcdcba:a:">> = iolist_to_binary(join(re:split("abcdcba","^((.)(?1)\\2|.)$",[{parts,
- 2}]))),
- <<":abcdcba:a:">> = iolist_to_binary(join(re:split("abcdcba","^((.)(?1)\\2|.)$",[]))),
- <<":pqaabaaqp:p">> = iolist_to_binary(join(re:split("pqaabaaqp","^((.)(?1)\\2|.)$",[trim]))),
+ 2}]))),
+ <<":abcdcba:a:">> = iolist_to_binary(join(re:split("abcdcba","^((.)(?1)\\2|.)$",[]))),
+ <<":pqaabaaqp:p">> = iolist_to_binary(join(re:split("pqaabaaqp","^((.)(?1)\\2|.)$",[trim]))),
<<":pqaabaaqp:p:">> = iolist_to_binary(join(re:split("pqaabaaqp","^((.)(?1)\\2|.)$",[{parts,
- 2}]))),
- <<":pqaabaaqp:p:">> = iolist_to_binary(join(re:split("pqaabaaqp","^((.)(?1)\\2|.)$",[]))),
- <<":ablewasiereisawelba:a">> = iolist_to_binary(join(re:split("ablewasiereisawelba","^((.)(?1)\\2|.)$",[trim]))),
+ 2}]))),
+ <<":pqaabaaqp:p:">> = iolist_to_binary(join(re:split("pqaabaaqp","^((.)(?1)\\2|.)$",[]))),
+ <<":ablewasiereisawelba:a">> = iolist_to_binary(join(re:split("ablewasiereisawelba","^((.)(?1)\\2|.)$",[trim]))),
<<":ablewasiereisawelba:a:">> = iolist_to_binary(join(re:split("ablewasiereisawelba","^((.)(?1)\\2|.)$",[{parts,
- 2}]))),
- <<":ablewasiereisawelba:a:">> = iolist_to_binary(join(re:split("ablewasiereisawelba","^((.)(?1)\\2|.)$",[]))),
- <<"rhubarb">> = iolist_to_binary(join(re:split("rhubarb","^((.)(?1)\\2|.)$",[trim]))),
+ 2}]))),
+ <<":ablewasiereisawelba:a:">> = iolist_to_binary(join(re:split("ablewasiereisawelba","^((.)(?1)\\2|.)$",[]))),
+ <<"rhubarb">> = iolist_to_binary(join(re:split("rhubarb","^((.)(?1)\\2|.)$",[trim]))),
<<"rhubarb">> = iolist_to_binary(join(re:split("rhubarb","^((.)(?1)\\2|.)$",[{parts,
- 2}]))),
- <<"rhubarb">> = iolist_to_binary(join(re:split("rhubarb","^((.)(?1)\\2|.)$",[]))),
- <<"the quick brown fox">> = iolist_to_binary(join(re:split("the quick brown fox","^((.)(?1)\\2|.)$",[trim]))),
+ 2}]))),
+ <<"rhubarb">> = iolist_to_binary(join(re:split("rhubarb","^((.)(?1)\\2|.)$",[]))),
+ <<"the quick brown fox">> = iolist_to_binary(join(re:split("the quick brown fox","^((.)(?1)\\2|.)$",[trim]))),
<<"the quick brown fox">> = iolist_to_binary(join(re:split("the quick brown fox","^((.)(?1)\\2|.)$",[{parts,
- 2}]))),
- <<"the quick brown fox">> = iolist_to_binary(join(re:split("the quick brown fox","^((.)(?1)\\2|.)$",[]))),
- <<"b:a:z">> = iolist_to_binary(join(re:split("baz","(a)(?<=b(?1))",[trim]))),
+ 2}]))),
+ <<"the quick brown fox">> = iolist_to_binary(join(re:split("the quick brown fox","^((.)(?1)\\2|.)$",[]))),
+ <<"b:a:z">> = iolist_to_binary(join(re:split("baz","(a)(?<=b(?1))",[trim]))),
<<"b:a:z">> = iolist_to_binary(join(re:split("baz","(a)(?<=b(?1))",[{parts,
- 2}]))),
- <<"b:a:z">> = iolist_to_binary(join(re:split("baz","(a)(?<=b(?1))",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)(?<=b(?1))",[trim]))),
+ 2}]))),
+ <<"b:a:z">> = iolist_to_binary(join(re:split("baz","(a)(?<=b(?1))",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)(?<=b(?1))",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)(?<=b(?1))",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)(?<=b(?1))",[]))),
- <<"caz">> = iolist_to_binary(join(re:split("caz","(a)(?<=b(?1))",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)(?<=b(?1))",[]))),
+ <<"caz">> = iolist_to_binary(join(re:split("caz","(a)(?<=b(?1))",[trim]))),
<<"caz">> = iolist_to_binary(join(re:split("caz","(a)(?<=b(?1))",[{parts,
- 2}]))),
- <<"caz">> = iolist_to_binary(join(re:split("caz","(a)(?<=b(?1))",[]))),
- <<"zba:a:z">> = iolist_to_binary(join(re:split("zbaaz","(?<=b(?1))(a)",[trim]))),
+ 2}]))),
+ <<"caz">> = iolist_to_binary(join(re:split("caz","(a)(?<=b(?1))",[]))),
+ <<"zba:a:z">> = iolist_to_binary(join(re:split("zbaaz","(?<=b(?1))(a)",[trim]))),
<<"zba:a:z">> = iolist_to_binary(join(re:split("zbaaz","(?<=b(?1))(a)",[{parts,
- 2}]))),
- <<"zba:a:z">> = iolist_to_binary(join(re:split("zbaaz","(?<=b(?1))(a)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=b(?1))(a)",[trim]))),
+ 2}]))),
+ <<"zba:a:z">> = iolist_to_binary(join(re:split("zbaaz","(?<=b(?1))(a)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=b(?1))(a)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=b(?1))(a)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=b(?1))(a)",[]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","(?<=b(?1))(a)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=b(?1))(a)",[]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","(?<=b(?1))(a)",[trim]))),
<<"aaa">> = iolist_to_binary(join(re:split("aaa","(?<=b(?1))(a)",[{parts,
- 2}]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","(?<=b(?1))(a)",[]))),
- <<"b:a:z">> = iolist_to_binary(join(re:split("baz","(?<X>a)(?<=b(?&X))",[trim]))),
+ 2}]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","(?<=b(?1))(a)",[]))),
+ <<"b:a:z">> = iolist_to_binary(join(re:split("baz","(?<X>a)(?<=b(?&X))",[trim]))),
<<"b:a:z">> = iolist_to_binary(join(re:split("baz","(?<X>a)(?<=b(?&X))",[{parts,
- 2}]))),
- <<"b:a:z">> = iolist_to_binary(join(re:split("baz","(?<X>a)(?<=b(?&X))",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("abcabc","^(?|(abc)|(def))\\1",[trim]))),
+ 2}]))),
+ <<"b:a:z">> = iolist_to_binary(join(re:split("baz","(?<X>a)(?<=b(?&X))",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abcabc","^(?|(abc)|(def))\\1",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abcabc","^(?|(abc)|(def))\\1",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abcabc","^(?|(abc)|(def))\\1",[]))),
- <<":def">> = iolist_to_binary(join(re:split("defdef","^(?|(abc)|(def))\\1",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abcabc","^(?|(abc)|(def))\\1",[]))),
+ <<":def">> = iolist_to_binary(join(re:split("defdef","^(?|(abc)|(def))\\1",[trim]))),
<<":def:">> = iolist_to_binary(join(re:split("defdef","^(?|(abc)|(def))\\1",[{parts,
- 2}]))),
- <<":def:">> = iolist_to_binary(join(re:split("defdef","^(?|(abc)|(def))\\1",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?|(abc)|(def))\\1",[trim]))),
+ 2}]))),
+ <<":def:">> = iolist_to_binary(join(re:split("defdef","^(?|(abc)|(def))\\1",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?|(abc)|(def))\\1",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?|(abc)|(def))\\1",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?|(abc)|(def))\\1",[]))),
- <<"abcdef">> = iolist_to_binary(join(re:split("abcdef","^(?|(abc)|(def))\\1",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?|(abc)|(def))\\1",[]))),
+ <<"abcdef">> = iolist_to_binary(join(re:split("abcdef","^(?|(abc)|(def))\\1",[trim]))),
<<"abcdef">> = iolist_to_binary(join(re:split("abcdef","^(?|(abc)|(def))\\1",[{parts,
- 2}]))),
- <<"abcdef">> = iolist_to_binary(join(re:split("abcdef","^(?|(abc)|(def))\\1",[]))),
- <<"defabc">> = iolist_to_binary(join(re:split("defabc","^(?|(abc)|(def))\\1",[trim]))),
+ 2}]))),
+ <<"abcdef">> = iolist_to_binary(join(re:split("abcdef","^(?|(abc)|(def))\\1",[]))),
+ <<"defabc">> = iolist_to_binary(join(re:split("defabc","^(?|(abc)|(def))\\1",[trim]))),
<<"defabc">> = iolist_to_binary(join(re:split("defabc","^(?|(abc)|(def))\\1",[{parts,
- 2}]))),
- <<"defabc">> = iolist_to_binary(join(re:split("defabc","^(?|(abc)|(def))\\1",[]))),
+ 2}]))),
+ <<"defabc">> = iolist_to_binary(join(re:split("defabc","^(?|(abc)|(def))\\1",[]))),
ok.
run43() ->
- <<":abc">> = iolist_to_binary(join(re:split("abcabc","^(?|(abc)|(def))(?1)",[trim]))),
+ <<":abc">> = iolist_to_binary(join(re:split("abcabc","^(?|(abc)|(def))(?1)",[trim]))),
<<":abc:">> = iolist_to_binary(join(re:split("abcabc","^(?|(abc)|(def))(?1)",[{parts,
- 2}]))),
- <<":abc:">> = iolist_to_binary(join(re:split("abcabc","^(?|(abc)|(def))(?1)",[]))),
- <<":def">> = iolist_to_binary(join(re:split("defabc","^(?|(abc)|(def))(?1)",[trim]))),
+ 2}]))),
+ <<":abc:">> = iolist_to_binary(join(re:split("abcabc","^(?|(abc)|(def))(?1)",[]))),
+ <<":def">> = iolist_to_binary(join(re:split("defabc","^(?|(abc)|(def))(?1)",[trim]))),
<<":def:">> = iolist_to_binary(join(re:split("defabc","^(?|(abc)|(def))(?1)",[{parts,
- 2}]))),
- <<":def:">> = iolist_to_binary(join(re:split("defabc","^(?|(abc)|(def))(?1)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?|(abc)|(def))(?1)",[trim]))),
+ 2}]))),
+ <<":def:">> = iolist_to_binary(join(re:split("defabc","^(?|(abc)|(def))(?1)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?|(abc)|(def))(?1)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?|(abc)|(def))(?1)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?|(abc)|(def))(?1)",[]))),
- <<"defdef">> = iolist_to_binary(join(re:split("defdef","^(?|(abc)|(def))(?1)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?|(abc)|(def))(?1)",[]))),
+ <<"defdef">> = iolist_to_binary(join(re:split("defdef","^(?|(abc)|(def))(?1)",[trim]))),
<<"defdef">> = iolist_to_binary(join(re:split("defdef","^(?|(abc)|(def))(?1)",[{parts,
- 2}]))),
- <<"defdef">> = iolist_to_binary(join(re:split("defdef","^(?|(abc)|(def))(?1)",[]))),
- <<"abcdef">> = iolist_to_binary(join(re:split("abcdef","^(?|(abc)|(def))(?1)",[trim]))),
+ 2}]))),
+ <<"defdef">> = iolist_to_binary(join(re:split("defdef","^(?|(abc)|(def))(?1)",[]))),
+ <<"abcdef">> = iolist_to_binary(join(re:split("abcdef","^(?|(abc)|(def))(?1)",[trim]))),
<<"abcdef">> = iolist_to_binary(join(re:split("abcdef","^(?|(abc)|(def))(?1)",[{parts,
- 2}]))),
- <<"abcdef">> = iolist_to_binary(join(re:split("abcdef","^(?|(abc)|(def))(?1)",[]))),
- <<"A:C:D">> = iolist_to_binary(join(re:split("ABCD","(?:(?1)|B)(A(*F)|C)",[trim]))),
+ 2}]))),
+ <<"abcdef">> = iolist_to_binary(join(re:split("abcdef","^(?|(abc)|(def))(?1)",[]))),
+ <<"A:C:D">> = iolist_to_binary(join(re:split("ABCD","(?:(?1)|B)(A(*F)|C)",[trim]))),
<<"A:C:D">> = iolist_to_binary(join(re:split("ABCD","(?:(?1)|B)(A(*F)|C)",[{parts,
- 2}]))),
- <<"A:C:D">> = iolist_to_binary(join(re:split("ABCD","(?:(?1)|B)(A(*F)|C)",[]))),
- <<":C:D">> = iolist_to_binary(join(re:split("CCD","(?:(?1)|B)(A(*F)|C)",[trim]))),
+ 2}]))),
+ <<"A:C:D">> = iolist_to_binary(join(re:split("ABCD","(?:(?1)|B)(A(*F)|C)",[]))),
+ <<":C:D">> = iolist_to_binary(join(re:split("CCD","(?:(?1)|B)(A(*F)|C)",[trim]))),
<<":C:D">> = iolist_to_binary(join(re:split("CCD","(?:(?1)|B)(A(*F)|C)",[{parts,
- 2}]))),
- <<":C:D">> = iolist_to_binary(join(re:split("CCD","(?:(?1)|B)(A(*F)|C)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?:(?1)|B)(A(*F)|C)",[trim]))),
+ 2}]))),
+ <<":C:D">> = iolist_to_binary(join(re:split("CCD","(?:(?1)|B)(A(*F)|C)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?:(?1)|B)(A(*F)|C)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?:(?1)|B)(A(*F)|C)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?:(?1)|B)(A(*F)|C)",[]))),
- <<"CAD">> = iolist_to_binary(join(re:split("CAD","(?:(?1)|B)(A(*F)|C)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?:(?1)|B)(A(*F)|C)",[]))),
+ <<"CAD">> = iolist_to_binary(join(re:split("CAD","(?:(?1)|B)(A(*F)|C)",[trim]))),
<<"CAD">> = iolist_to_binary(join(re:split("CAD","(?:(?1)|B)(A(*F)|C)",[{parts,
- 2}]))),
- <<"CAD">> = iolist_to_binary(join(re:split("CAD","(?:(?1)|B)(A(*F)|C)",[]))),
- <<":C:D">> = iolist_to_binary(join(re:split("CCD","^(?:(?1)|B)(A(*F)|C)",[trim]))),
+ 2}]))),
+ <<"CAD">> = iolist_to_binary(join(re:split("CAD","(?:(?1)|B)(A(*F)|C)",[]))),
+ <<":C:D">> = iolist_to_binary(join(re:split("CCD","^(?:(?1)|B)(A(*F)|C)",[trim]))),
<<":C:D">> = iolist_to_binary(join(re:split("CCD","^(?:(?1)|B)(A(*F)|C)",[{parts,
- 2}]))),
- <<":C:D">> = iolist_to_binary(join(re:split("CCD","^(?:(?1)|B)(A(*F)|C)",[]))),
- <<":C:D">> = iolist_to_binary(join(re:split("BCD","^(?:(?1)|B)(A(*F)|C)",[trim]))),
+ 2}]))),
+ <<":C:D">> = iolist_to_binary(join(re:split("CCD","^(?:(?1)|B)(A(*F)|C)",[]))),
+ <<":C:D">> = iolist_to_binary(join(re:split("BCD","^(?:(?1)|B)(A(*F)|C)",[trim]))),
<<":C:D">> = iolist_to_binary(join(re:split("BCD","^(?:(?1)|B)(A(*F)|C)",[{parts,
- 2}]))),
- <<":C:D">> = iolist_to_binary(join(re:split("BCD","^(?:(?1)|B)(A(*F)|C)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:(?1)|B)(A(*F)|C)",[trim]))),
+ 2}]))),
+ <<":C:D">> = iolist_to_binary(join(re:split("BCD","^(?:(?1)|B)(A(*F)|C)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:(?1)|B)(A(*F)|C)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:(?1)|B)(A(*F)|C)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:(?1)|B)(A(*F)|C)",[]))),
- <<"ABCD">> = iolist_to_binary(join(re:split("ABCD","^(?:(?1)|B)(A(*F)|C)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:(?1)|B)(A(*F)|C)",[]))),
+ <<"ABCD">> = iolist_to_binary(join(re:split("ABCD","^(?:(?1)|B)(A(*F)|C)",[trim]))),
<<"ABCD">> = iolist_to_binary(join(re:split("ABCD","^(?:(?1)|B)(A(*F)|C)",[{parts,
- 2}]))),
- <<"ABCD">> = iolist_to_binary(join(re:split("ABCD","^(?:(?1)|B)(A(*F)|C)",[]))),
- <<"CAD">> = iolist_to_binary(join(re:split("CAD","^(?:(?1)|B)(A(*F)|C)",[trim]))),
+ 2}]))),
+ <<"ABCD">> = iolist_to_binary(join(re:split("ABCD","^(?:(?1)|B)(A(*F)|C)",[]))),
+ <<"CAD">> = iolist_to_binary(join(re:split("CAD","^(?:(?1)|B)(A(*F)|C)",[trim]))),
<<"CAD">> = iolist_to_binary(join(re:split("CAD","^(?:(?1)|B)(A(*F)|C)",[{parts,
- 2}]))),
- <<"CAD">> = iolist_to_binary(join(re:split("CAD","^(?:(?1)|B)(A(*F)|C)",[]))),
- <<"BAD">> = iolist_to_binary(join(re:split("BAD","^(?:(?1)|B)(A(*F)|C)",[trim]))),
+ 2}]))),
+ <<"CAD">> = iolist_to_binary(join(re:split("CAD","^(?:(?1)|B)(A(*F)|C)",[]))),
+ <<"BAD">> = iolist_to_binary(join(re:split("BAD","^(?:(?1)|B)(A(*F)|C)",[trim]))),
<<"BAD">> = iolist_to_binary(join(re:split("BAD","^(?:(?1)|B)(A(*F)|C)",[{parts,
- 2}]))),
- <<"BAD">> = iolist_to_binary(join(re:split("BAD","^(?:(?1)|B)(A(*F)|C)",[]))),
- <<":A:D">> = iolist_to_binary(join(re:split("AAD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
+ 2}]))),
+ <<"BAD">> = iolist_to_binary(join(re:split("BAD","^(?:(?1)|B)(A(*F)|C)",[]))),
+ <<":A:D">> = iolist_to_binary(join(re:split("AAD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
<<":A:D">> = iolist_to_binary(join(re:split("AAD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[{parts,
- 2}]))),
- <<":A:D">> = iolist_to_binary(join(re:split("AAD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
- <<":C">> = iolist_to_binary(join(re:split("ACD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
+ 2}]))),
+ <<":A:D">> = iolist_to_binary(join(re:split("AAD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
+ <<":C">> = iolist_to_binary(join(re:split("ACD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
<<":C:">> = iolist_to_binary(join(re:split("ACD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[{parts,
- 2}]))),
- <<":C:">> = iolist_to_binary(join(re:split("ACD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
- <<":A:D">> = iolist_to_binary(join(re:split("BAD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
+ 2}]))),
+ <<":C:">> = iolist_to_binary(join(re:split("ACD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
+ <<":A:D">> = iolist_to_binary(join(re:split("BAD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
<<":A:D">> = iolist_to_binary(join(re:split("BAD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[{parts,
- 2}]))),
- <<":A:D">> = iolist_to_binary(join(re:split("BAD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
- <<":C">> = iolist_to_binary(join(re:split("BCD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
+ 2}]))),
+ <<":A:D">> = iolist_to_binary(join(re:split("BAD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
+ <<":C">> = iolist_to_binary(join(re:split("BCD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
<<":C:">> = iolist_to_binary(join(re:split("BCD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[{parts,
- 2}]))),
- <<":C:">> = iolist_to_binary(join(re:split("BCD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
- <<":A:X">> = iolist_to_binary(join(re:split("BAX","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
+ 2}]))),
+ <<":C:">> = iolist_to_binary(join(re:split("BCD","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
+ <<":A:X">> = iolist_to_binary(join(re:split("BAX","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
<<":A:X">> = iolist_to_binary(join(re:split("BAX","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[{parts,
- 2}]))),
- <<":A:X">> = iolist_to_binary(join(re:split("BAX","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
+ 2}]))),
+ <<":A:X">> = iolist_to_binary(join(re:split("BAX","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
- <<"ACX">> = iolist_to_binary(join(re:split("ACX","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
+ <<"ACX">> = iolist_to_binary(join(re:split("ACX","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
<<"ACX">> = iolist_to_binary(join(re:split("ACX","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[{parts,
- 2}]))),
- <<"ACX">> = iolist_to_binary(join(re:split("ACX","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
- <<"ABC">> = iolist_to_binary(join(re:split("ABC","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
+ 2}]))),
+ <<"ACX">> = iolist_to_binary(join(re:split("ACX","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
+ <<"ABC">> = iolist_to_binary(join(re:split("ABC","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[trim]))),
<<"ABC">> = iolist_to_binary(join(re:split("ABC","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[{parts,
- 2}]))),
- <<"ABC">> = iolist_to_binary(join(re:split("ABC","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
- <<"">> = iolist_to_binary(join(re:split("BAC","(?(DEFINE)(A))B(?1)C",[trim]))),
+ 2}]))),
+ <<"ABC">> = iolist_to_binary(join(re:split("ABC","(?:(?1)|B)(A(*ACCEPT)XX|C)D",[]))),
+ <<"">> = iolist_to_binary(join(re:split("BAC","(?(DEFINE)(A))B(?1)C",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("BAC","(?(DEFINE)(A))B(?1)C",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("BAC","(?(DEFINE)(A))B(?1)C",[]))),
- <<"">> = iolist_to_binary(join(re:split("BAAC","(?(DEFINE)((A)\\2))B(?1)C",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("BAC","(?(DEFINE)(A))B(?1)C",[]))),
+ <<"">> = iolist_to_binary(join(re:split("BAAC","(?(DEFINE)((A)\\2))B(?1)C",[trim]))),
<<":::">> = iolist_to_binary(join(re:split("BAAC","(?(DEFINE)((A)\\2))B(?1)C",[{parts,
- 2}]))),
- <<":::">> = iolist_to_binary(join(re:split("BAAC","(?(DEFINE)((A)\\2))B(?1)C",[]))),
+ 2}]))),
+ <<":::">> = iolist_to_binary(join(re:split("BAAC","(?(DEFINE)((A)\\2))B(?1)C",[]))),
<<":(ab(cd)ef):ef">> = iolist_to_binary(join(re:split("(ab(cd)ef)","(?<pn> \\( ( [^()]++ | (?&pn) )* \\) )",[extended,
- trim]))),
+ trim]))),
<<":(ab(cd)ef):ef:">> = iolist_to_binary(join(re:split("(ab(cd)ef)","(?<pn> \\( ( [^()]++ | (?&pn) )* \\) )",[extended,
{parts,
- 2}]))),
- <<":(ab(cd)ef):ef:">> = iolist_to_binary(join(re:split("(ab(cd)ef)","(?<pn> \\( ( [^()]++ | (?&pn) )* \\) )",[extended]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?=a(*SKIP)b|ac)",[trim]))),
+ 2}]))),
+ <<":(ab(cd)ef):ef:">> = iolist_to_binary(join(re:split("(ab(cd)ef)","(?<pn> \\( ( [^()]++ | (?&pn) )* \\) )",[extended]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?=a(*SKIP)b|ac)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?=a(*SKIP)b|ac)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?=a(*SKIP)b|ac)",[]))),
- <<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*SKIP)b|ac)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?=a(*SKIP)b|ac)",[]))),
+ <<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*SKIP)b|ac)",[trim]))),
<<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*SKIP)b|ac)",[{parts,
- 2}]))),
- <<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*SKIP)b|ac)",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","^(?=a(*PRUNE)b)",[trim]))),
+ 2}]))),
+ <<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*SKIP)b|ac)",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","^(?=a(*PRUNE)b)",[trim]))),
<<"ab">> = iolist_to_binary(join(re:split("ab","^(?=a(*PRUNE)b)",[{parts,
- 2}]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","^(?=a(*PRUNE)b)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?=a(*PRUNE)b)",[trim]))),
+ 2}]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","^(?=a(*PRUNE)b)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?=a(*PRUNE)b)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?=a(*PRUNE)b)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?=a(*PRUNE)b)",[]))),
- <<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*PRUNE)b)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?=a(*PRUNE)b)",[]))),
+ <<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*PRUNE)b)",[trim]))),
<<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*PRUNE)b)",[{parts,
- 2}]))),
- <<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*PRUNE)b)",[]))),
- <<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*ACCEPT)b)",[trim]))),
+ 2}]))),
+ <<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*PRUNE)b)",[]))),
+ <<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*ACCEPT)b)",[trim]))),
<<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*ACCEPT)b)",[{parts,
- 2}]))),
- <<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*ACCEPT)b)",[]))),
- <<"a">> = iolist_to_binary(join(re:split("ab","(?>a\\Kb)",[trim]))),
+ 2}]))),
+ <<"ac">> = iolist_to_binary(join(re:split("ac","^(?=a(*ACCEPT)b)",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("ab","(?>a\\Kb)",[trim]))),
<<"a:">> = iolist_to_binary(join(re:split("ab","(?>a\\Kb)",[{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("ab","(?>a\\Kb)",[]))),
- <<"a:ab">> = iolist_to_binary(join(re:split("ab","((?>a\\Kb))",[trim]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("ab","(?>a\\Kb)",[]))),
+ <<"a:ab">> = iolist_to_binary(join(re:split("ab","((?>a\\Kb))",[trim]))),
<<"a:ab:">> = iolist_to_binary(join(re:split("ab","((?>a\\Kb))",[{parts,
- 2}]))),
- <<"a:ab:">> = iolist_to_binary(join(re:split("ab","((?>a\\Kb))",[]))),
- <<"a:ab">> = iolist_to_binary(join(re:split("ab","(a\\Kb)",[trim]))),
+ 2}]))),
+ <<"a:ab:">> = iolist_to_binary(join(re:split("ab","((?>a\\Kb))",[]))),
+ <<"a:ab">> = iolist_to_binary(join(re:split("ab","(a\\Kb)",[trim]))),
<<"a:ab:">> = iolist_to_binary(join(re:split("ab","(a\\Kb)",[{parts,
- 2}]))),
- <<"a:ab:">> = iolist_to_binary(join(re:split("ab","(a\\Kb)",[]))),
- <<"">> = iolist_to_binary(join(re:split("ac","^a\\Kcz|ac",[trim]))),
+ 2}]))),
+ <<"a:ab:">> = iolist_to_binary(join(re:split("ab","(a\\Kb)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ac","^a\\Kcz|ac",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ac","^a\\Kcz|ac",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ac","^a\\Kcz|ac",[]))),
- <<"">> = iolist_to_binary(join(re:split("ab","(?>a\\Kbz|ab)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ac","^a\\Kcz|ac",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ab","(?>a\\Kbz|ab)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ab","(?>a\\Kbz|ab)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ab","(?>a\\Kbz|ab)",[]))),
- <<"a">> = iolist_to_binary(join(re:split("ab","^(?&t)(?(DEFINE)(?<t>a\\Kb))$",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ab","(?>a\\Kbz|ab)",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("ab","^(?&t)(?(DEFINE)(?<t>a\\Kb))$",[trim]))),
<<"a::">> = iolist_to_binary(join(re:split("ab","^(?&t)(?(DEFINE)(?<t>a\\Kb))$",[{parts,
- 2}]))),
- <<"a::">> = iolist_to_binary(join(re:split("ab","^(?&t)(?(DEFINE)(?<t>a\\Kb))$",[]))),
- <<":c">> = iolist_to_binary(join(re:split("a(b)c","^([^()]|\\((?1)*\\))*$",[trim]))),
+ 2}]))),
+ <<"a::">> = iolist_to_binary(join(re:split("ab","^(?&t)(?(DEFINE)(?<t>a\\Kb))$",[]))),
+ <<":c">> = iolist_to_binary(join(re:split("a(b)c","^([^()]|\\((?1)*\\))*$",[trim]))),
<<":c:">> = iolist_to_binary(join(re:split("a(b)c","^([^()]|\\((?1)*\\))*$",[{parts,
- 2}]))),
- <<":c:">> = iolist_to_binary(join(re:split("a(b)c","^([^()]|\\((?1)*\\))*$",[]))),
- <<":e">> = iolist_to_binary(join(re:split("a(b(c)d)e","^([^()]|\\((?1)*\\))*$",[trim]))),
+ 2}]))),
+ <<":c:">> = iolist_to_binary(join(re:split("a(b)c","^([^()]|\\((?1)*\\))*$",[]))),
+ <<":e">> = iolist_to_binary(join(re:split("a(b(c)d)e","^([^()]|\\((?1)*\\))*$",[trim]))),
<<":e:">> = iolist_to_binary(join(re:split("a(b(c)d)e","^([^()]|\\((?1)*\\))*$",[{parts,
- 2}]))),
- <<":e:">> = iolist_to_binary(join(re:split("a(b(c)d)e","^([^()]|\\((?1)*\\))*$",[]))),
- <<":0">> = iolist_to_binary(join(re:split("0","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[trim]))),
+ 2}]))),
+ <<":e:">> = iolist_to_binary(join(re:split("a(b(c)d)e","^([^()]|\\((?1)*\\))*$",[]))),
+ <<":0">> = iolist_to_binary(join(re:split("0","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[trim]))),
<<":0::">> = iolist_to_binary(join(re:split("0","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[{parts,
- 2}]))),
- <<":0::">> = iolist_to_binary(join(re:split("0","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[]))),
- <<":00:0">> = iolist_to_binary(join(re:split("00","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[trim]))),
+ 2}]))),
+ <<":0::">> = iolist_to_binary(join(re:split("0","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[]))),
+ <<":00:0">> = iolist_to_binary(join(re:split("00","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[trim]))),
<<":00:0:">> = iolist_to_binary(join(re:split("00","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[{parts,
- 2}]))),
- <<":00:0:">> = iolist_to_binary(join(re:split("00","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[]))),
- <<":0000:0">> = iolist_to_binary(join(re:split("0000","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[trim]))),
+ 2}]))),
+ <<":00:0:">> = iolist_to_binary(join(re:split("00","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[]))),
+ <<":0000:0">> = iolist_to_binary(join(re:split("0000","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[trim]))),
<<":0000:0:">> = iolist_to_binary(join(re:split("0000","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[{parts,
- 2}]))),
- <<":0000:0:">> = iolist_to_binary(join(re:split("0000","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[]))),
- <<":0:0">> = iolist_to_binary(join(re:split("0","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[trim]))),
+ 2}]))),
+ <<":0000:0:">> = iolist_to_binary(join(re:split("0000","(?P<L1>(?P<L2>0)(?P>L1)|(?P>L2))",[]))),
+ <<":0:0">> = iolist_to_binary(join(re:split("0","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[trim]))),
<<":0:0:">> = iolist_to_binary(join(re:split("0","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[{parts,
- 2}]))),
- <<":0:0:">> = iolist_to_binary(join(re:split("0","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[]))),
- <<":0:0::0:0">> = iolist_to_binary(join(re:split("00","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[trim]))),
+ 2}]))),
+ <<":0:0:">> = iolist_to_binary(join(re:split("0","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[]))),
+ <<":0:0::0:0">> = iolist_to_binary(join(re:split("00","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[trim]))),
<<":0:0:0">> = iolist_to_binary(join(re:split("00","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[{parts,
- 2}]))),
- <<":0:0::0:0:">> = iolist_to_binary(join(re:split("00","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[]))),
- <<":0:0::0:0::0:0::0:0">> = iolist_to_binary(join(re:split("0000","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[trim]))),
+ 2}]))),
+ <<":0:0::0:0:">> = iolist_to_binary(join(re:split("00","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[]))),
+ <<":0:0::0:0::0:0::0:0">> = iolist_to_binary(join(re:split("0000","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[trim]))),
<<":0:0:000">> = iolist_to_binary(join(re:split("0000","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[{parts,
- 2}]))),
- <<":0:0::0:0::0:0::0:0:">> = iolist_to_binary(join(re:split("0000","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[]))),
+ 2}]))),
+ <<":0:0::0:0::0:0::0:0:">> = iolist_to_binary(join(re:split("0000","(?P<L1>(?P<L2>0)|(?P>L2)(?P>L1))",[]))),
ok.
run44() ->
- <<"ACABX">> = iolist_to_binary(join(re:split("ACABX","A(*COMMIT)(B|D)",[trim]))),
+ <<"ACABX">> = iolist_to_binary(join(re:split("ACABX","A(*COMMIT)(B|D)",[trim]))),
<<"ACABX">> = iolist_to_binary(join(re:split("ACABX","A(*COMMIT)(B|D)",[{parts,
- 2}]))),
- <<"ACABX">> = iolist_to_binary(join(re:split("ACABX","A(*COMMIT)(B|D)",[]))),
- <<":A:B:C:DEFG">> = iolist_to_binary(join(re:split("ABCDEFG","(*COMMIT)(A|P)(B|P)(C|P)",[trim]))),
+ 2}]))),
+ <<"ACABX">> = iolist_to_binary(join(re:split("ACABX","A(*COMMIT)(B|D)",[]))),
+ <<":A:B:C:DEFG">> = iolist_to_binary(join(re:split("ABCDEFG","(*COMMIT)(A|P)(B|P)(C|P)",[trim]))),
<<":A:B:C:DEFG">> = iolist_to_binary(join(re:split("ABCDEFG","(*COMMIT)(A|P)(B|P)(C|P)",[{parts,
- 2}]))),
- <<":A:B:C:DEFG">> = iolist_to_binary(join(re:split("ABCDEFG","(*COMMIT)(A|P)(B|P)(C|P)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(*COMMIT)(A|P)(B|P)(C|P)",[trim]))),
+ 2}]))),
+ <<":A:B:C:DEFG">> = iolist_to_binary(join(re:split("ABCDEFG","(*COMMIT)(A|P)(B|P)(C|P)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(*COMMIT)(A|P)(B|P)(C|P)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(*COMMIT)(A|P)(B|P)(C|P)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(*COMMIT)(A|P)(B|P)(C|P)",[]))),
- <<"DEFGABC">> = iolist_to_binary(join(re:split("DEFGABC","(*COMMIT)(A|P)(B|P)(C|P)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(*COMMIT)(A|P)(B|P)(C|P)",[]))),
+ <<"DEFGABC">> = iolist_to_binary(join(re:split("DEFGABC","(*COMMIT)(A|P)(B|P)(C|P)",[trim]))),
<<"DEFGABC">> = iolist_to_binary(join(re:split("DEFGABC","(*COMMIT)(A|P)(B|P)(C|P)",[{parts,
- 2}]))),
- <<"DEFGABC">> = iolist_to_binary(join(re:split("DEFGABC","(*COMMIT)(A|P)(B|P)(C|P)",[]))),
- <<":a">> = iolist_to_binary(join(re:split("abbb","(\\w+)(?>b(*COMMIT))\\w{2}",[trim]))),
+ 2}]))),
+ <<"DEFGABC">> = iolist_to_binary(join(re:split("DEFGABC","(*COMMIT)(A|P)(B|P)(C|P)",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("abbb","(\\w+)(?>b(*COMMIT))\\w{2}",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("abbb","(\\w+)(?>b(*COMMIT))\\w{2}",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("abbb","(\\w+)(?>b(*COMMIT))\\w{2}",[]))),
- <<"abbb">> = iolist_to_binary(join(re:split("abbb","(\\w+)b(*COMMIT)\\w{2}",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("abbb","(\\w+)(?>b(*COMMIT))\\w{2}",[]))),
+ <<"abbb">> = iolist_to_binary(join(re:split("abbb","(\\w+)b(*COMMIT)\\w{2}",[trim]))),
<<"abbb">> = iolist_to_binary(join(re:split("abbb","(\\w+)b(*COMMIT)\\w{2}",[{parts,
- 2}]))),
- <<"abbb">> = iolist_to_binary(join(re:split("abbb","(\\w+)b(*COMMIT)\\w{2}",[]))),
- <<"b::c">> = iolist_to_binary(join(re:split("bac","(?&t)(?#()(?(DEFINE)(?<t>a))",[trim]))),
+ 2}]))),
+ <<"abbb">> = iolist_to_binary(join(re:split("abbb","(\\w+)b(*COMMIT)\\w{2}",[]))),
+ <<"b::c">> = iolist_to_binary(join(re:split("bac","(?&t)(?#()(?(DEFINE)(?<t>a))",[trim]))),
<<"b::c">> = iolist_to_binary(join(re:split("bac","(?&t)(?#()(?(DEFINE)(?<t>a))",[{parts,
- 2}]))),
- <<"b::c">> = iolist_to_binary(join(re:split("bac","(?&t)(?#()(?(DEFINE)(?<t>a))",[]))),
- <<"yes">> = iolist_to_binary(join(re:split("yes","(?>(*COMMIT)(?>yes|no)(*THEN)(*F))?",[trim]))),
+ 2}]))),
+ <<"b::c">> = iolist_to_binary(join(re:split("bac","(?&t)(?#()(?(DEFINE)(?<t>a))",[]))),
+ <<"yes">> = iolist_to_binary(join(re:split("yes","(?>(*COMMIT)(?>yes|no)(*THEN)(*F))?",[trim]))),
<<"yes">> = iolist_to_binary(join(re:split("yes","(?>(*COMMIT)(?>yes|no)(*THEN)(*F))?",[{parts,
- 2}]))),
- <<"yes">> = iolist_to_binary(join(re:split("yes","(?>(*COMMIT)(?>yes|no)(*THEN)(*F))?",[]))),
- <<"yes">> = iolist_to_binary(join(re:split("yes","(?>(*COMMIT)(yes|no)(*THEN)(*F))?",[trim]))),
+ 2}]))),
+ <<"yes">> = iolist_to_binary(join(re:split("yes","(?>(*COMMIT)(?>yes|no)(*THEN)(*F))?",[]))),
+ <<"yes">> = iolist_to_binary(join(re:split("yes","(?>(*COMMIT)(yes|no)(*THEN)(*F))?",[trim]))),
<<"yes">> = iolist_to_binary(join(re:split("yes","(?>(*COMMIT)(yes|no)(*THEN)(*F))?",[{parts,
- 2}]))),
- <<"yes">> = iolist_to_binary(join(re:split("yes","(?>(*COMMIT)(yes|no)(*THEN)(*F))?",[]))),
- <<"">> = iolist_to_binary(join(re:split("bc","b?(*SKIP)c",[trim]))),
+ 2}]))),
+ <<"yes">> = iolist_to_binary(join(re:split("yes","(?>(*COMMIT)(yes|no)(*THEN)(*F))?",[]))),
+ <<"">> = iolist_to_binary(join(re:split("bc","b?(*SKIP)c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("bc","b?(*SKIP)c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("bc","b?(*SKIP)c",[]))),
- <<"a">> = iolist_to_binary(join(re:split("abc","b?(*SKIP)c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("bc","b?(*SKIP)c",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("abc","b?(*SKIP)c",[trim]))),
<<"a:">> = iolist_to_binary(join(re:split("abc","b?(*SKIP)c",[{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("abc","b?(*SKIP)c",[]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("abc","b?(*SKIP)c",[]))),
ok.
run45() ->
- <<"a">> = iolist_to_binary(join(re:split("a","(*SKIP)bc",[trim]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","(*SKIP)bc",[trim]))),
<<"a">> = iolist_to_binary(join(re:split("a","(*SKIP)bc",[{parts,
- 2}]))),
- <<"a">> = iolist_to_binary(join(re:split("a","(*SKIP)bc",[]))),
- <<"a">> = iolist_to_binary(join(re:split("a","(*SKIP)b",[trim]))),
+ 2}]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","(*SKIP)bc",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","(*SKIP)b",[trim]))),
<<"a">> = iolist_to_binary(join(re:split("a","(*SKIP)b",[{parts,
- 2}]))),
- <<"a">> = iolist_to_binary(join(re:split("a","(*SKIP)b",[]))),
- <<"x::x::x">> = iolist_to_binary(join(re:split("xxx","(?P<abn>(?P=abn)xxx|)+",[trim]))),
+ 2}]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","(*SKIP)b",[]))),
+ <<"x::x::x">> = iolist_to_binary(join(re:split("xxx","(?P<abn>(?P=abn)xxx|)+",[trim]))),
<<"x::xx">> = iolist_to_binary(join(re:split("xxx","(?P<abn>(?P=abn)xxx|)+",[{parts,
- 2}]))),
- <<"x::x::x::">> = iolist_to_binary(join(re:split("xxx","(?P<abn>(?P=abn)xxx|)+",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aa","(?i:([^b]))(?1)",[trim]))),
+ 2}]))),
+ <<"x::x::x::">> = iolist_to_binary(join(re:split("xxx","(?P<abn>(?P=abn)xxx|)+",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aa","(?i:([^b]))(?1)",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aa","(?i:([^b]))(?1)",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aa","(?i:([^b]))(?1)",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aA","(?i:([^b]))(?1)",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aa","(?i:([^b]))(?1)",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aA","(?i:([^b]))(?1)",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aA","(?i:([^b]))(?1)",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aA","(?i:([^b]))(?1)",[]))),
- <<":*:: ::a::l::r">> = iolist_to_binary(join(re:split("** Failers","(?i:([^b]))(?1)",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aA","(?i:([^b]))(?1)",[]))),
+ <<":*:: ::a::l::r">> = iolist_to_binary(join(re:split("** Failers","(?i:([^b]))(?1)",[trim]))),
<<":*: Failers">> = iolist_to_binary(join(re:split("** Failers","(?i:([^b]))(?1)",[{parts,
- 2}]))),
- <<":*:: ::a::l::r:">> = iolist_to_binary(join(re:split("** Failers","(?i:([^b]))(?1)",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","(?i:([^b]))(?1)",[trim]))),
+ 2}]))),
+ <<":*:: ::a::l::r:">> = iolist_to_binary(join(re:split("** Failers","(?i:([^b]))(?1)",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","(?i:([^b]))(?1)",[trim]))),
<<"ab">> = iolist_to_binary(join(re:split("ab","(?i:([^b]))(?1)",[{parts,
- 2}]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","(?i:([^b]))(?1)",[]))),
- <<"aB">> = iolist_to_binary(join(re:split("aB","(?i:([^b]))(?1)",[trim]))),
+ 2}]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","(?i:([^b]))(?1)",[]))),
+ <<"aB">> = iolist_to_binary(join(re:split("aB","(?i:([^b]))(?1)",[trim]))),
<<"aB">> = iolist_to_binary(join(re:split("aB","(?i:([^b]))(?1)",[{parts,
- 2}]))),
- <<"aB">> = iolist_to_binary(join(re:split("aB","(?i:([^b]))(?1)",[]))),
- <<"Ba">> = iolist_to_binary(join(re:split("Ba","(?i:([^b]))(?1)",[trim]))),
+ 2}]))),
+ <<"aB">> = iolist_to_binary(join(re:split("aB","(?i:([^b]))(?1)",[]))),
+ <<"Ba">> = iolist_to_binary(join(re:split("Ba","(?i:([^b]))(?1)",[trim]))),
<<"Ba">> = iolist_to_binary(join(re:split("Ba","(?i:([^b]))(?1)",[{parts,
- 2}]))),
- <<"Ba">> = iolist_to_binary(join(re:split("Ba","(?i:([^b]))(?1)",[]))),
- <<"ba">> = iolist_to_binary(join(re:split("ba","(?i:([^b]))(?1)",[trim]))),
+ 2}]))),
+ <<"Ba">> = iolist_to_binary(join(re:split("Ba","(?i:([^b]))(?1)",[]))),
+ <<"ba">> = iolist_to_binary(join(re:split("ba","(?i:([^b]))(?1)",[trim]))),
<<"ba">> = iolist_to_binary(join(re:split("ba","(?i:([^b]))(?1)",[{parts,
- 2}]))),
- <<"ba">> = iolist_to_binary(join(re:split("ba","(?i:([^b]))(?1)",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaaaaX","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[trim]))),
+ 2}]))),
+ <<"ba">> = iolist_to_binary(join(re:split("ba","(?i:([^b]))(?1)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaaaX","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("aaaaaaX","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("aaaaaaX","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("aaaaaaX","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[]))),
- <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[]))),
+ <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[trim]))),
<<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[{parts,
- 2}]))),
- <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaaaaX","^(?&t)*(?(DEFINE)(?<t>a))\\w$",[trim]))),
+ 2}]))),
+ <<"aaaaaa">> = iolist_to_binary(join(re:split("aaaaaa","^(?&t)*+(?(DEFINE)(?<t>a))\\w$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaaaX","^(?&t)*(?(DEFINE)(?<t>a))\\w$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("aaaaaaX","^(?&t)*(?(DEFINE)(?<t>a))\\w$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("aaaaaaX","^(?&t)*(?(DEFINE)(?<t>a))\\w$",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaaaa","^(?&t)*(?(DEFINE)(?<t>a))\\w$",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("aaaaaaX","^(?&t)*(?(DEFINE)(?<t>a))\\w$",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaaa","^(?&t)*(?(DEFINE)(?<t>a))\\w$",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("aaaaaa","^(?&t)*(?(DEFINE)(?<t>a))\\w$",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("aaaaaa","^(?&t)*(?(DEFINE)(?<t>a))\\w$",[]))),
- <<":a:X">> = iolist_to_binary(join(re:split("aaaaX","^(a)*+(\\w)",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("aaaaaa","^(?&t)*(?(DEFINE)(?<t>a))\\w$",[]))),
+ <<":a:X">> = iolist_to_binary(join(re:split("aaaaX","^(a)*+(\\w)",[trim]))),
<<":a:X:">> = iolist_to_binary(join(re:split("aaaaX","^(a)*+(\\w)",[{parts,
- 2}]))),
- <<":a:X:">> = iolist_to_binary(join(re:split("aaaaX","^(a)*+(\\w)",[]))),
- <<"::Y:Z">> = iolist_to_binary(join(re:split("YZ","^(a)*+(\\w)",[trim]))),
+ 2}]))),
+ <<":a:X:">> = iolist_to_binary(join(re:split("aaaaX","^(a)*+(\\w)",[]))),
+ <<"::Y:Z">> = iolist_to_binary(join(re:split("YZ","^(a)*+(\\w)",[trim]))),
<<"::Y:Z">> = iolist_to_binary(join(re:split("YZ","^(a)*+(\\w)",[{parts,
- 2}]))),
- <<"::Y:Z">> = iolist_to_binary(join(re:split("YZ","^(a)*+(\\w)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a)*+(\\w)",[trim]))),
+ 2}]))),
+ <<"::Y:Z">> = iolist_to_binary(join(re:split("YZ","^(a)*+(\\w)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a)*+(\\w)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a)*+(\\w)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a)*+(\\w)",[]))),
- <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(a)*+(\\w)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a)*+(\\w)",[]))),
+ <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(a)*+(\\w)",[trim]))),
<<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(a)*+(\\w)",[{parts,
- 2}]))),
- <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(a)*+(\\w)",[]))),
- <<":X">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)*+(\\w)",[trim]))),
+ 2}]))),
+ <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(a)*+(\\w)",[]))),
+ <<":X">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)*+(\\w)",[trim]))),
<<":X:">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)*+(\\w)",[{parts,
- 2}]))),
- <<":X:">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)*+(\\w)",[]))),
- <<":Y:Z">> = iolist_to_binary(join(re:split("YZ","^(?:a)*+(\\w)",[trim]))),
+ 2}]))),
+ <<":X:">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)*+(\\w)",[]))),
+ <<":Y:Z">> = iolist_to_binary(join(re:split("YZ","^(?:a)*+(\\w)",[trim]))),
<<":Y:Z">> = iolist_to_binary(join(re:split("YZ","^(?:a)*+(\\w)",[{parts,
- 2}]))),
- <<":Y:Z">> = iolist_to_binary(join(re:split("YZ","^(?:a)*+(\\w)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a)*+(\\w)",[trim]))),
+ 2}]))),
+ <<":Y:Z">> = iolist_to_binary(join(re:split("YZ","^(?:a)*+(\\w)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a)*+(\\w)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a)*+(\\w)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a)*+(\\w)",[]))),
- <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(?:a)*+(\\w)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a)*+(\\w)",[]))),
+ <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(?:a)*+(\\w)",[trim]))),
<<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(?:a)*+(\\w)",[{parts,
- 2}]))),
- <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(?:a)*+(\\w)",[]))),
- <<":a:X">> = iolist_to_binary(join(re:split("aaaaX","^(a)++(\\w)",[trim]))),
+ 2}]))),
+ <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(?:a)*+(\\w)",[]))),
+ <<":a:X">> = iolist_to_binary(join(re:split("aaaaX","^(a)++(\\w)",[trim]))),
<<":a:X:">> = iolist_to_binary(join(re:split("aaaaX","^(a)++(\\w)",[{parts,
- 2}]))),
- <<":a:X:">> = iolist_to_binary(join(re:split("aaaaX","^(a)++(\\w)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a)++(\\w)",[trim]))),
+ 2}]))),
+ <<":a:X:">> = iolist_to_binary(join(re:split("aaaaX","^(a)++(\\w)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a)++(\\w)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a)++(\\w)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a)++(\\w)",[]))),
- <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(a)++(\\w)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a)++(\\w)",[]))),
+ <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(a)++(\\w)",[trim]))),
<<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(a)++(\\w)",[{parts,
- 2}]))),
- <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(a)++(\\w)",[]))),
- <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(a)++(\\w)",[trim]))),
+ 2}]))),
+ <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(a)++(\\w)",[]))),
+ <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(a)++(\\w)",[trim]))),
<<"YZ">> = iolist_to_binary(join(re:split("YZ","^(a)++(\\w)",[{parts,
- 2}]))),
- <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(a)++(\\w)",[]))),
- <<":X">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)++(\\w)",[trim]))),
+ 2}]))),
+ <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(a)++(\\w)",[]))),
+ <<":X">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)++(\\w)",[trim]))),
<<":X:">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)++(\\w)",[{parts,
- 2}]))),
- <<":X:">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)++(\\w)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a)++(\\w)",[trim]))),
+ 2}]))),
+ <<":X:">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)++(\\w)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a)++(\\w)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a)++(\\w)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a)++(\\w)",[]))),
- <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(?:a)++(\\w)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a)++(\\w)",[]))),
+ <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(?:a)++(\\w)",[trim]))),
<<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(?:a)++(\\w)",[{parts,
- 2}]))),
- <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(?:a)++(\\w)",[]))),
- <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(?:a)++(\\w)",[trim]))),
+ 2}]))),
+ <<"aaaa">> = iolist_to_binary(join(re:split("aaaa","^(?:a)++(\\w)",[]))),
+ <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(?:a)++(\\w)",[trim]))),
<<"YZ">> = iolist_to_binary(join(re:split("YZ","^(?:a)++(\\w)",[{parts,
- 2}]))),
- <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(?:a)++(\\w)",[]))),
- <<":a:a:aaX">> = iolist_to_binary(join(re:split("aaaaX","^(a)?+(\\w)",[trim]))),
+ 2}]))),
+ <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(?:a)++(\\w)",[]))),
+ <<":a:a:aaX">> = iolist_to_binary(join(re:split("aaaaX","^(a)?+(\\w)",[trim]))),
<<":a:a:aaX">> = iolist_to_binary(join(re:split("aaaaX","^(a)?+(\\w)",[{parts,
- 2}]))),
- <<":a:a:aaX">> = iolist_to_binary(join(re:split("aaaaX","^(a)?+(\\w)",[]))),
- <<"::Y:Z">> = iolist_to_binary(join(re:split("YZ","^(a)?+(\\w)",[trim]))),
+ 2}]))),
+ <<":a:a:aaX">> = iolist_to_binary(join(re:split("aaaaX","^(a)?+(\\w)",[]))),
+ <<"::Y:Z">> = iolist_to_binary(join(re:split("YZ","^(a)?+(\\w)",[trim]))),
<<"::Y:Z">> = iolist_to_binary(join(re:split("YZ","^(a)?+(\\w)",[{parts,
- 2}]))),
- <<"::Y:Z">> = iolist_to_binary(join(re:split("YZ","^(a)?+(\\w)",[]))),
- <<":a:aaX">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)?+(\\w)",[trim]))),
+ 2}]))),
+ <<"::Y:Z">> = iolist_to_binary(join(re:split("YZ","^(a)?+(\\w)",[]))),
+ <<":a:aaX">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)?+(\\w)",[trim]))),
<<":a:aaX">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)?+(\\w)",[{parts,
- 2}]))),
- <<":a:aaX">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)?+(\\w)",[]))),
- <<":Y:Z">> = iolist_to_binary(join(re:split("YZ","^(?:a)?+(\\w)",[trim]))),
+ 2}]))),
+ <<":a:aaX">> = iolist_to_binary(join(re:split("aaaaX","^(?:a)?+(\\w)",[]))),
+ <<":Y:Z">> = iolist_to_binary(join(re:split("YZ","^(?:a)?+(\\w)",[trim]))),
<<":Y:Z">> = iolist_to_binary(join(re:split("YZ","^(?:a)?+(\\w)",[{parts,
- 2}]))),
- <<":Y:Z">> = iolist_to_binary(join(re:split("YZ","^(?:a)?+(\\w)",[]))),
- <<":a:X">> = iolist_to_binary(join(re:split("aaaaX","^(a){2,}+(\\w)",[trim]))),
+ 2}]))),
+ <<":Y:Z">> = iolist_to_binary(join(re:split("YZ","^(?:a)?+(\\w)",[]))),
+ <<":a:X">> = iolist_to_binary(join(re:split("aaaaX","^(a){2,}+(\\w)",[trim]))),
<<":a:X:">> = iolist_to_binary(join(re:split("aaaaX","^(a){2,}+(\\w)",[{parts,
- 2}]))),
- <<":a:X:">> = iolist_to_binary(join(re:split("aaaaX","^(a){2,}+(\\w)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a){2,}+(\\w)",[trim]))),
+ 2}]))),
+ <<":a:X:">> = iolist_to_binary(join(re:split("aaaaX","^(a){2,}+(\\w)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a){2,}+(\\w)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a){2,}+(\\w)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a){2,}+(\\w)",[]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a){2,}+(\\w)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(a){2,}+(\\w)",[]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a){2,}+(\\w)",[trim]))),
<<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a){2,}+(\\w)",[{parts,
- 2}]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a){2,}+(\\w)",[]))),
- <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(a){2,}+(\\w)",[trim]))),
+ 2}]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(a){2,}+(\\w)",[]))),
+ <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(a){2,}+(\\w)",[trim]))),
<<"YZ">> = iolist_to_binary(join(re:split("YZ","^(a){2,}+(\\w)",[{parts,
- 2}]))),
- <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(a){2,}+(\\w)",[]))),
- <<":X">> = iolist_to_binary(join(re:split("aaaaX","^(?:a){2,}+(\\w)",[trim]))),
+ 2}]))),
+ <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(a){2,}+(\\w)",[]))),
+ <<":X">> = iolist_to_binary(join(re:split("aaaaX","^(?:a){2,}+(\\w)",[trim]))),
<<":X:">> = iolist_to_binary(join(re:split("aaaaX","^(?:a){2,}+(\\w)",[{parts,
- 2}]))),
- <<":X:">> = iolist_to_binary(join(re:split("aaaaX","^(?:a){2,}+(\\w)",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a){2,}+(\\w)",[trim]))),
+ 2}]))),
+ <<":X:">> = iolist_to_binary(join(re:split("aaaaX","^(?:a){2,}+(\\w)",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a){2,}+(\\w)",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a){2,}+(\\w)",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a){2,}+(\\w)",[]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(?:a){2,}+(\\w)",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","^(?:a){2,}+(\\w)",[]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(?:a){2,}+(\\w)",[trim]))),
<<"aaa">> = iolist_to_binary(join(re:split("aaa","^(?:a){2,}+(\\w)",[{parts,
- 2}]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(?:a){2,}+(\\w)",[]))),
- <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(?:a){2,}+(\\w)",[trim]))),
+ 2}]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^(?:a){2,}+(\\w)",[]))),
+ <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(?:a){2,}+(\\w)",[trim]))),
<<"YZ">> = iolist_to_binary(join(re:split("YZ","^(?:a){2,}+(\\w)",[{parts,
- 2}]))),
- <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(?:a){2,}+(\\w)",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","(a|)*(?1)b",[trim]))),
+ 2}]))),
+ <<"YZ">> = iolist_to_binary(join(re:split("YZ","^(?:a){2,}+(\\w)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","(a|)*(?1)b",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("b","(a|)*(?1)b",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("b","(a|)*(?1)b",[]))),
- <<"">> = iolist_to_binary(join(re:split("ab","(a|)*(?1)b",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("b","(a|)*(?1)b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ab","(a|)*(?1)b",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("ab","(a|)*(?1)b",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("ab","(a|)*(?1)b",[]))),
- <<"">> = iolist_to_binary(join(re:split("aab","(a|)*(?1)b",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("ab","(a|)*(?1)b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aab","(a|)*(?1)b",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("aab","(a|)*(?1)b",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("aab","(a|)*(?1)b",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)++(?1)b",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("aab","(a|)*(?1)b",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)++(?1)b",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)++(?1)b",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)++(?1)b",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","(a)++(?1)b",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)++(?1)b",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","(a)++(?1)b",[trim]))),
<<"ab">> = iolist_to_binary(join(re:split("ab","(a)++(?1)b",[{parts,
- 2}]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","(a)++(?1)b",[]))),
- <<"aab">> = iolist_to_binary(join(re:split("aab","(a)++(?1)b",[trim]))),
+ 2}]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","(a)++(?1)b",[]))),
+ <<"aab">> = iolist_to_binary(join(re:split("aab","(a)++(?1)b",[trim]))),
<<"aab">> = iolist_to_binary(join(re:split("aab","(a)++(?1)b",[{parts,
- 2}]))),
- <<"aab">> = iolist_to_binary(join(re:split("aab","(a)++(?1)b",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)*+(?1)b",[trim]))),
+ 2}]))),
+ <<"aab">> = iolist_to_binary(join(re:split("aab","(a)++(?1)b",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)*+(?1)b",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)*+(?1)b",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)*+(?1)b",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","(a)*+(?1)b",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(a)*+(?1)b",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","(a)*+(?1)b",[trim]))),
<<"ab">> = iolist_to_binary(join(re:split("ab","(a)*+(?1)b",[{parts,
- 2}]))),
- <<"ab">> = iolist_to_binary(join(re:split("ab","(a)*+(?1)b",[]))),
- <<"aab">> = iolist_to_binary(join(re:split("aab","(a)*+(?1)b",[trim]))),
+ 2}]))),
+ <<"ab">> = iolist_to_binary(join(re:split("ab","(a)*+(?1)b",[]))),
+ <<"aab">> = iolist_to_binary(join(re:split("aab","(a)*+(?1)b",[trim]))),
<<"aab">> = iolist_to_binary(join(re:split("aab","(a)*+(?1)b",[{parts,
- 2}]))),
- <<"aab">> = iolist_to_binary(join(re:split("aab","(a)*+(?1)b",[]))),
- <<"">> = iolist_to_binary(join(re:split("b","(?1)(?:(b)){0}",[trim]))),
+ 2}]))),
+ <<"aab">> = iolist_to_binary(join(re:split("aab","(a)*+(?1)b",[]))),
+ <<"">> = iolist_to_binary(join(re:split("b","(?1)(?:(b)){0}",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("b","(?1)(?:(b)){0}",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("b","(?1)(?:(b)){0}",[]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("b","(?1)(?:(b)){0}",[]))),
<<":foo(bar(baz)+baz(bop)):(bar(baz)+baz(bop)):bar(baz)+baz(bop)">> = iolist_to_binary(join(re:split("foo(bar(baz)+baz(bop))","(foo ( \\( ((?:(?> [^()]+ )|(?2))*) \\) ) )",[extended,
- trim]))),
+ trim]))),
<<":foo(bar(baz)+baz(bop)):(bar(baz)+baz(bop)):bar(baz)+baz(bop):">> = iolist_to_binary(join(re:split("foo(bar(baz)+baz(bop))","(foo ( \\( ((?:(?> [^()]+ )|(?2))*) \\) ) )",[extended,
{parts,
- 2}]))),
- <<":foo(bar(baz)+baz(bop)):(bar(baz)+baz(bop)):bar(baz)+baz(bop):">> = iolist_to_binary(join(re:split("foo(bar(baz)+baz(bop))","(foo ( \\( ((?:(?> [^()]+ )|(?2))*) \\) ) )",[extended]))),
+ 2}]))),
+ <<":foo(bar(baz)+baz(bop)):(bar(baz)+baz(bop)):bar(baz)+baz(bop):">> = iolist_to_binary(join(re:split("foo(bar(baz)+baz(bop))","(foo ( \\( ((?:(?> [^()]+ )|(?2))*) \\) ) )",[extended]))),
<<":AB:B">> = iolist_to_binary(join(re:split("AB","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
- trim]))),
+ trim]))),
<<":AB:B::">> = iolist_to_binary(join(re:split("AB","(A (A|B(*ACCEPT)|C) D)(E)",[extended,
{parts,
- 2}]))),
- <<":AB:B::">> = iolist_to_binary(join(re:split("AB","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
+ 2}]))),
+ <<":AB:B::">> = iolist_to_binary(join(re:split("AB","(A (A|B(*ACCEPT)|C) D)(E)",[extended]))),
ok.
run46() ->
- <<":a">> = iolist_to_binary(join(re:split("ba","\\A.*?(a|bc)",[trim]))),
+ <<":a">> = iolist_to_binary(join(re:split("ba","\\A.*?(a|bc)",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("ba","\\A.*?(a|bc)",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("ba","\\A.*?(a|bc)",[]))),
- <<"">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc)++",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("ba","\\A.*?(a|bc)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc)++",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc)++",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc)++",[]))),
- <<":a">> = iolist_to_binary(join(re:split("ba","\\A.*?(a|bc)++",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc)++",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("ba","\\A.*?(a|bc)++",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("ba","\\A.*?(a|bc)++",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("ba","\\A.*?(a|bc)++",[]))),
- <<"">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc|d)",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("ba","\\A.*?(a|bc)++",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc|d)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc|d)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc|d)",[]))),
- <<":b:eetle">> = iolist_to_binary(join(re:split("beetle","(?:(b))++",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc|d)",[]))),
+ <<":b:eetle">> = iolist_to_binary(join(re:split("beetle","(?:(b))++",[trim]))),
<<":b:eetle">> = iolist_to_binary(join(re:split("beetle","(?:(b))++",[{parts,
- 2}]))),
- <<":b:eetle">> = iolist_to_binary(join(re:split("beetle","(?:(b))++",[]))),
- <<":a">> = iolist_to_binary(join(re:split("a","(?(?=(a(*ACCEPT)z))a)",[trim]))),
+ 2}]))),
+ <<":b:eetle">> = iolist_to_binary(join(re:split("beetle","(?:(b))++",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("a","(?(?=(a(*ACCEPT)z))a)",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("a","(?(?=(a(*ACCEPT)z))a)",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("a","(?(?=(a(*ACCEPT)z))a)",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaaab","^(a)(?1)+ab",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("a","(?(?=(a(*ACCEPT)z))a)",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaaab","^(a)(?1)+ab",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaaab","^(a)(?1)+ab",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaaab","^(a)(?1)+ab",[]))),
- <<"aaaab">> = iolist_to_binary(join(re:split("aaaab","^(a)(?1)++ab",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaaab","^(a)(?1)+ab",[]))),
+ <<"aaaab">> = iolist_to_binary(join(re:split("aaaab","^(a)(?1)++ab",[trim]))),
<<"aaaab">> = iolist_to_binary(join(re:split("aaaab","^(a)(?1)++ab",[{parts,
- 2}]))),
- <<"aaaab">> = iolist_to_binary(join(re:split("aaaab","^(a)(?1)++ab",[]))),
- <<"::ckgammon">> = iolist_to_binary(join(re:split("backgammon","(?(DEFINE)(a))?b(?1)",[trim]))),
+ 2}]))),
+ <<"aaaab">> = iolist_to_binary(join(re:split("aaaab","^(a)(?1)++ab",[]))),
+ <<"::ckgammon">> = iolist_to_binary(join(re:split("backgammon","(?(DEFINE)(a))?b(?1)",[trim]))),
<<"::ckgammon">> = iolist_to_binary(join(re:split("backgammon","(?(DEFINE)(a))?b(?1)",[{parts,
- 2}]))),
- <<"::ckgammon">> = iolist_to_binary(join(re:split("backgammon","(?(DEFINE)(a))?b(?1)",[]))),
+ 2}]))),
+ <<"::ckgammon">> = iolist_to_binary(join(re:split("backgammon","(?(DEFINE)(a))?b(?1)",[]))),
<<":
def">> = iolist_to_binary(join(re:split("abc
-def","^\\N+",[trim]))),
+def","^\\N+",[trim]))),
<<":
def">> = iolist_to_binary(join(re:split("abc
-def","^\\N+",[{parts,2}]))),
+def","^\\N+",[{parts,2}]))),
<<":
def">> = iolist_to_binary(join(re:split("abc
-def","^\\N+",[]))),
+def","^\\N+",[]))),
<<":
def">> = iolist_to_binary(join(re:split("abc
-def","^\\N{1,}",[trim]))),
+def","^\\N{1,}",[trim]))),
<<":
def">> = iolist_to_binary(join(re:split("abc
-def","^\\N{1,}",[{parts,2}]))),
+def","^\\N{1,}",[{parts,2}]))),
<<":
def">> = iolist_to_binary(join(re:split("abc
-def","^\\N{1,}",[]))),
- <<":cde">> = iolist_to_binary(join(re:split("aaaabcde","(?(R)a+|(?R)b)",[trim]))),
+def","^\\N{1,}",[]))),
+ <<":cde">> = iolist_to_binary(join(re:split("aaaabcde","(?(R)a+|(?R)b)",[trim]))),
<<":cde">> = iolist_to_binary(join(re:split("aaaabcde","(?(R)a+|(?R)b)",[{parts,
- 2}]))),
- <<":cde">> = iolist_to_binary(join(re:split("aaaabcde","(?(R)a+|(?R)b)",[]))),
- <<":aaaa:cde">> = iolist_to_binary(join(re:split("aaaabcde","(?(R)a+|((?R))b)",[trim]))),
+ 2}]))),
+ <<":cde">> = iolist_to_binary(join(re:split("aaaabcde","(?(R)a+|(?R)b)",[]))),
+ <<":aaaa:cde">> = iolist_to_binary(join(re:split("aaaabcde","(?(R)a+|((?R))b)",[trim]))),
<<":aaaa:cde">> = iolist_to_binary(join(re:split("aaaabcde","(?(R)a+|((?R))b)",[{parts,
- 2}]))),
- <<":aaaa:cde">> = iolist_to_binary(join(re:split("aaaabcde","(?(R)a+|((?R))b)",[]))),
- <<":aaaab:cde">> = iolist_to_binary(join(re:split("aaaabcde","((?(R)a+|(?1)b))",[trim]))),
+ 2}]))),
+ <<":aaaa:cde">> = iolist_to_binary(join(re:split("aaaabcde","(?(R)a+|((?R))b)",[]))),
+ <<":aaaab:cde">> = iolist_to_binary(join(re:split("aaaabcde","((?(R)a+|(?1)b))",[trim]))),
<<":aaaab:cde">> = iolist_to_binary(join(re:split("aaaabcde","((?(R)a+|(?1)b))",[{parts,
- 2}]))),
- <<":aaaab:cde">> = iolist_to_binary(join(re:split("aaaabcde","((?(R)a+|(?1)b))",[]))),
- <<":aaaab:cde">> = iolist_to_binary(join(re:split("aaaabcde","((?(R1)a+|(?1)b))",[trim]))),
+ 2}]))),
+ <<":aaaab:cde">> = iolist_to_binary(join(re:split("aaaabcde","((?(R)a+|(?1)b))",[]))),
+ <<":aaaab:cde">> = iolist_to_binary(join(re:split("aaaabcde","((?(R1)a+|(?1)b))",[trim]))),
<<":aaaab:cde">> = iolist_to_binary(join(re:split("aaaabcde","((?(R1)a+|(?1)b))",[{parts,
- 2}]))),
- <<":aaaab:cde">> = iolist_to_binary(join(re:split("aaaabcde","((?(R1)a+|(?1)b))",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaa","((?(R)a|(?1)))*",[trim]))),
+ 2}]))),
+ <<":aaaab:cde">> = iolist_to_binary(join(re:split("aaaabcde","((?(R1)a+|(?1)b))",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaa","((?(R)a|(?1)))*",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaa","((?(R)a|(?1)))*",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaa","((?(R)a|(?1)))*",[]))),
- <<":a">> = iolist_to_binary(join(re:split("aaa","((?(R)a|(?1)))+",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaa","((?(R)a|(?1)))*",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("aaa","((?(R)a|(?1)))+",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("aaa","((?(R)a|(?1)))+",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("aaa","((?(R)a|(?1)))+",[]))),
- <<"">> = iolist_to_binary(join(re:split("a","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("aaa","((?(R)a|(?1)))+",[]))),
+ <<"">> = iolist_to_binary(join(re:split("a","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("a","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("a","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[]))),
- <<"b">> = iolist_to_binary(join(re:split("ba","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("a","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[]))),
+ <<"b">> = iolist_to_binary(join(re:split("ba","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[trim]))),
<<"b::">> = iolist_to_binary(join(re:split("ba","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[{parts,
- 2}]))),
- <<"b::">> = iolist_to_binary(join(re:split("ba","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[]))),
- <<"bb">> = iolist_to_binary(join(re:split("bba","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[trim]))),
+ 2}]))),
+ <<"b::">> = iolist_to_binary(join(re:split("ba","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[]))),
+ <<"bb">> = iolist_to_binary(join(re:split("bba","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[trim]))),
<<"bb::">> = iolist_to_binary(join(re:split("bba","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[{parts,
- 2}]))),
- <<"bb::">> = iolist_to_binary(join(re:split("bba","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[]))),
+ 2}]))),
+ <<"bb::">> = iolist_to_binary(join(re:split("bba","(?>(?&t)c|(?&t))(?(DEFINE)(?<t>a|b(*PRUNE)c))",[]))),
ok.
run47() ->
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b) c",[extended,
- trim]))),
+ trim]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b) c",[extended,
{parts,
- 2}]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b) c",[extended]))),
+ 2}]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b) c",[extended]))),
<<":ab">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b|(*F)) c",[extended,
- trim]))),
+ trim]))),
<<":ab:">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b|(*F)) c",[extended,
{parts,
- 2}]))),
- <<":ab:">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b|(*F)) c",[extended]))),
+ 2}]))),
+ <<":ab:">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b|(*F)) c",[extended]))),
<<":ab:ab">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b) | (*F) ) c",[extended,
- trim]))),
+ trim]))),
<<":ab:ab:">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b) | (*F) ) c",[extended,
{parts,
- 2}]))),
- <<":ab:ab:">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b) | (*F) ) c",[extended]))),
+ 2}]))),
+ <<":ab:ab:">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b) | (*F) ) c",[extended]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b) ) c",[extended,
- trim]))),
+ trim]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b) ) c",[extended,
{parts,
- 2}]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b) ) c",[extended]))),
+ 2}]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b) ) c",[extended]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b) c",[extended,
- trim]))),
+ trim]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b) c",[extended,
{parts,
- 2}]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b) c",[extended]))),
+ 2}]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b) c",[extended]))),
<<"">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b|(*F)) c",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b|(*F)) c",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b|(*F)) c",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b|(*F)) c",[extended]))),
<<"">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b) | (*F) ) c",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b) | (*F) ) c",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b) | (*F) ) c",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b) | (*F) ) c",[extended]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b) ) c",[extended,
- trim]))),
+ trim]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b) ) c",[extended,
{parts,
- 2}]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b) ) c",[extended]))),
+ 2}]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b) ) c",[extended]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?>a(*THEN)b) c",[extended,
- trim]))),
+ trim]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?>a(*THEN)b) c",[extended,
{parts,
- 2}]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?>a(*THEN)b) c",[extended]))),
+ 2}]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?>a(*THEN)b) c",[extended]))),
<<"">> = iolist_to_binary(join(re:split("aabc","^.*? (?>a(*THEN)b|(*F)) c",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?>a(*THEN)b|(*F)) c",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?>a(*THEN)b|(*F)) c",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?>a(*THEN)b|(*F)) c",[extended]))),
<<"">> = iolist_to_binary(join(re:split("aabc","^.*? (?> (?>a(*THEN)b) | (*F) ) c",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?> (?>a(*THEN)b) | (*F) ) c",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?> (?>a(*THEN)b) | (*F) ) c",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?> (?>a(*THEN)b) | (*F) ) c",[extended]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?> (?>a(*THEN)b) ) c",[extended,
- trim]))),
+ trim]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?> (?>a(*THEN)b) ) c",[extended,
{parts,
- 2}]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?> (?>a(*THEN)b) ) c",[extended]))),
+ 2}]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?> (?>a(*THEN)b) ) c",[extended]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b)++ c",[extended,
- trim]))),
+ trim]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b)++ c",[extended,
{parts,
- 2}]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b)++ c",[extended]))),
+ 2}]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b)++ c",[extended]))),
<<":ab">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b|(*F))++ c",[extended,
- trim]))),
+ trim]))),
<<":ab:">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b|(*F))++ c",[extended,
{parts,
- 2}]))),
- <<":ab:">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b|(*F))++ c",[extended]))),
+ 2}]))),
+ <<":ab:">> = iolist_to_binary(join(re:split("aabc","^.*? (a(*THEN)b|(*F))++ c",[extended]))),
<<":ab:ab">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b)++ | (*F) )++ c",[extended,
- trim]))),
+ trim]))),
<<":ab:ab:">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b)++ | (*F) )++ c",[extended,
{parts,
- 2}]))),
- <<":ab:ab:">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b)++ | (*F) )++ c",[extended]))),
+ 2}]))),
+ <<":ab:ab:">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b)++ | (*F) )++ c",[extended]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b)++ )++ c",[extended,
- trim]))),
+ trim]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b)++ )++ c",[extended,
{parts,
- 2}]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b)++ )++ c",[extended]))),
+ 2}]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? ( (a(*THEN)b)++ )++ c",[extended]))),
ok.
run48() ->
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b)++ c",[extended,
- trim]))),
+ trim]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b)++ c",[extended,
{parts,
- 2}]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b)++ c",[extended]))),
+ 2}]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b)++ c",[extended]))),
<<"">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b|(*F))++ c",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b|(*F))++ c",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b|(*F))++ c",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?:a(*THEN)b|(*F))++ c",[extended]))),
<<"">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b)++ | (*F) )++ c",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b)++ | (*F) )++ c",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b)++ | (*F) )++ c",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b)++ | (*F) )++ c",[extended]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b)++ )++ c",[extended,
- trim]))),
+ trim]))),
<<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b)++ )++ c",[extended,
{parts,
- 2}]))),
- <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b)++ )++ c",[extended]))),
- <<"">> = iolist_to_binary(join(re:split("ac","^(?(?=a(*THEN)b)ab|ac)",[trim]))),
+ 2}]))),
+ <<"aabc">> = iolist_to_binary(join(re:split("aabc","^.*? (?: (?:a(*THEN)b)++ )++ c",[extended]))),
+ <<"">> = iolist_to_binary(join(re:split("ac","^(?(?=a(*THEN)b)ab|ac)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ac","^(?(?=a(*THEN)b)ab|ac)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ac","^(?(?=a(*THEN)b)ab|ac)",[]))),
- <<"ba">> = iolist_to_binary(join(re:split("ba","^.*?(?(?=a)a|b(*THEN)c)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ac","^(?(?=a(*THEN)b)ab|ac)",[]))),
+ <<"ba">> = iolist_to_binary(join(re:split("ba","^.*?(?(?=a)a|b(*THEN)c)",[trim]))),
<<"ba">> = iolist_to_binary(join(re:split("ba","^.*?(?(?=a)a|b(*THEN)c)",[{parts,
- 2}]))),
- <<"ba">> = iolist_to_binary(join(re:split("ba","^.*?(?(?=a)a|b(*THEN)c)",[]))),
- <<"">> = iolist_to_binary(join(re:split("ba","^.*?(?:(?(?=a)a|b(*THEN)c)|d)",[trim]))),
+ 2}]))),
+ <<"ba">> = iolist_to_binary(join(re:split("ba","^.*?(?(?=a)a|b(*THEN)c)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ba","^.*?(?:(?(?=a)a|b(*THEN)c)|d)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ba","^.*?(?:(?(?=a)a|b(*THEN)c)|d)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ba","^.*?(?:(?(?=a)a|b(*THEN)c)|d)",[]))),
- <<"ac">> = iolist_to_binary(join(re:split("ac","^.*?(?(?=a)a(*THEN)b|c)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ba","^.*?(?:(?(?=a)a|b(*THEN)c)|d)",[]))),
+ <<"ac">> = iolist_to_binary(join(re:split("ac","^.*?(?(?=a)a(*THEN)b|c)",[trim]))),
<<"ac">> = iolist_to_binary(join(re:split("ac","^.*?(?(?=a)a(*THEN)b|c)",[{parts,
- 2}]))),
- <<"ac">> = iolist_to_binary(join(re:split("ac","^.*?(?(?=a)a(*THEN)b|c)",[]))),
- <<":abc">> = iolist_to_binary(join(re:split("aabc","^.*(?=a(*THEN)b)",[trim]))),
+ 2}]))),
+ <<"ac">> = iolist_to_binary(join(re:split("ac","^.*?(?(?=a)a(*THEN)b|c)",[]))),
+ <<":abc">> = iolist_to_binary(join(re:split("aabc","^.*(?=a(*THEN)b)",[trim]))),
<<":abc">> = iolist_to_binary(join(re:split("aabc","^.*(?=a(*THEN)b)",[{parts,
- 2}]))),
- <<":abc">> = iolist_to_binary(join(re:split("aabc","^.*(?=a(*THEN)b)",[]))),
- <<"xa:d">> = iolist_to_binary(join(re:split("xacd","(?<=a(*ACCEPT)b)c",[trim]))),
+ 2}]))),
+ <<":abc">> = iolist_to_binary(join(re:split("aabc","^.*(?=a(*THEN)b)",[]))),
+ <<"xa:d">> = iolist_to_binary(join(re:split("xacd","(?<=a(*ACCEPT)b)c",[trim]))),
<<"xa:d">> = iolist_to_binary(join(re:split("xacd","(?<=a(*ACCEPT)b)c",[{parts,
- 2}]))),
- <<"xa:d">> = iolist_to_binary(join(re:split("xacd","(?<=a(*ACCEPT)b)c",[]))),
- <<"xa:a:d">> = iolist_to_binary(join(re:split("xacd","(?<=(a(*ACCEPT)b))c",[trim]))),
+ 2}]))),
+ <<"xa:d">> = iolist_to_binary(join(re:split("xacd","(?<=a(*ACCEPT)b)c",[]))),
+ <<"xa:a:d">> = iolist_to_binary(join(re:split("xacd","(?<=(a(*ACCEPT)b))c",[trim]))),
<<"xa:a:d">> = iolist_to_binary(join(re:split("xacd","(?<=(a(*ACCEPT)b))c",[{parts,
- 2}]))),
- <<"xa:a:d">> = iolist_to_binary(join(re:split("xacd","(?<=(a(*ACCEPT)b))c",[]))),
- <<"xab:ab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=(a(*COMMIT)b))c",[trim]))),
+ 2}]))),
+ <<"xa:a:d">> = iolist_to_binary(join(re:split("xacd","(?<=(a(*ACCEPT)b))c",[]))),
+ <<"xab:ab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=(a(*COMMIT)b))c",[trim]))),
<<"xab:ab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=(a(*COMMIT)b))c",[{parts,
- 2}]))),
- <<"xab:ab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=(a(*COMMIT)b))c",[]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=(a(*COMMIT)b))c",[trim]))),
+ 2}]))),
+ <<"xab:ab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=(a(*COMMIT)b))c",[]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=(a(*COMMIT)b))c",[trim]))),
<<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=(a(*COMMIT)b))c",[{parts,
- 2}]))),
- <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=(a(*COMMIT)b))c",[]))),
- <<"xacd">> = iolist_to_binary(join(re:split("xacd","(?<=(a(*COMMIT)b))c",[trim]))),
+ 2}]))),
+ <<"** Failers">> = iolist_to_binary(join(re:split("** Failers","(?<=(a(*COMMIT)b))c",[]))),
+ <<"xacd">> = iolist_to_binary(join(re:split("xacd","(?<=(a(*COMMIT)b))c",[trim]))),
<<"xacd">> = iolist_to_binary(join(re:split("xacd","(?<=(a(*COMMIT)b))c",[{parts,
- 2}]))),
- <<"xacd">> = iolist_to_binary(join(re:split("xacd","(?<=(a(*COMMIT)b))c",[]))),
- <<"x:d">> = iolist_to_binary(join(re:split("xcd","(?<!a(*FAIL)b)c",[trim]))),
+ 2}]))),
+ <<"xacd">> = iolist_to_binary(join(re:split("xacd","(?<=(a(*COMMIT)b))c",[]))),
+ <<"x:d">> = iolist_to_binary(join(re:split("xcd","(?<!a(*FAIL)b)c",[trim]))),
<<"x:d">> = iolist_to_binary(join(re:split("xcd","(?<!a(*FAIL)b)c",[{parts,
- 2}]))),
- <<"x:d">> = iolist_to_binary(join(re:split("xcd","(?<!a(*FAIL)b)c",[]))),
- <<"a:d">> = iolist_to_binary(join(re:split("acd","(?<!a(*FAIL)b)c",[trim]))),
+ 2}]))),
+ <<"x:d">> = iolist_to_binary(join(re:split("xcd","(?<!a(*FAIL)b)c",[]))),
+ <<"a:d">> = iolist_to_binary(join(re:split("acd","(?<!a(*FAIL)b)c",[trim]))),
<<"a:d">> = iolist_to_binary(join(re:split("acd","(?<!a(*FAIL)b)c",[{parts,
- 2}]))),
- <<"a:d">> = iolist_to_binary(join(re:split("acd","(?<!a(*FAIL)b)c",[]))),
- <<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*PRUNE)b)c",[trim]))),
+ 2}]))),
+ <<"a:d">> = iolist_to_binary(join(re:split("acd","(?<!a(*FAIL)b)c",[]))),
+ <<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*PRUNE)b)c",[trim]))),
<<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*PRUNE)b)c",[{parts,
- 2}]))),
- <<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*PRUNE)b)c",[]))),
- <<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*SKIP)b)c",[trim]))),
+ 2}]))),
+ <<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*PRUNE)b)c",[]))),
+ <<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*SKIP)b)c",[trim]))),
<<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*SKIP)b)c",[{parts,
- 2}]))),
- <<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*SKIP)b)c",[]))),
- <<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*THEN)b)c",[trim]))),
+ 2}]))),
+ <<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*SKIP)b)c",[]))),
+ <<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*THEN)b)c",[trim]))),
<<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*THEN)b)c",[{parts,
- 2}]))),
- <<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*THEN)b)c",[]))),
+ 2}]))),
+ <<"xab:d">> = iolist_to_binary(join(re:split("xabcd","(?<=a(*THEN)b)c",[]))),
ok.
run49() ->
- <<":a:d">> = iolist_to_binary(join(re:split("abcd","(a)(?2){2}(.)",[trim]))),
+ <<":a:d">> = iolist_to_binary(join(re:split("abcd","(a)(?2){2}(.)",[trim]))),
<<":a:d:">> = iolist_to_binary(join(re:split("abcd","(a)(?2){2}(.)",[{parts,
- 2}]))),
- <<":a:d:">> = iolist_to_binary(join(re:split("abcd","(a)(?2){2}(.)",[]))),
- <<"hello world ">> = iolist_to_binary(join(re:split("hello world test","(another)?(\\1?)test",[trim]))),
+ 2}]))),
+ <<":a:d:">> = iolist_to_binary(join(re:split("abcd","(a)(?2){2}(.)",[]))),
+ <<"hello world ">> = iolist_to_binary(join(re:split("hello world test","(another)?(\\1?)test",[trim]))),
<<"hello world :::">> = iolist_to_binary(join(re:split("hello world test","(another)?(\\1?)test",[{parts,
- 2}]))),
- <<"hello world :::">> = iolist_to_binary(join(re:split("hello world test","(another)?(\\1?)test",[]))),
- <<"hello world test">> = iolist_to_binary(join(re:split("hello world test","(another)?(\\1+)test",[trim]))),
+ 2}]))),
+ <<"hello world :::">> = iolist_to_binary(join(re:split("hello world test","(another)?(\\1?)test",[]))),
+ <<"hello world test">> = iolist_to_binary(join(re:split("hello world test","(another)?(\\1+)test",[trim]))),
<<"hello world test">> = iolist_to_binary(join(re:split("hello world test","(another)?(\\1+)test",[{parts,
- 2}]))),
- <<"hello world test">> = iolist_to_binary(join(re:split("hello world test","(another)?(\\1+)test",[]))),
- <<"">> = iolist_to_binary(join(re:split("aac","(a(*COMMIT)b){0}a(?1)|aac",[trim]))),
+ 2}]))),
+ <<"hello world test">> = iolist_to_binary(join(re:split("hello world test","(another)?(\\1+)test",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aac","(a(*COMMIT)b){0}a(?1)|aac",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("aac","(a(*COMMIT)b){0}a(?1)|aac",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("aac","(a(*COMMIT)b){0}a(?1)|aac",[]))),
- <<"">> = iolist_to_binary(join(re:split("aac","((?:a?)*)*c",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("aac","(a(*COMMIT)b){0}a(?1)|aac",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aac","((?:a?)*)*c",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("aac","((?:a?)*)*c",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("aac","((?:a?)*)*c",[]))),
- <<"">> = iolist_to_binary(join(re:split("aac","((?>a?)*)*c",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("aac","((?:a?)*)*c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aac","((?>a?)*)*c",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("aac","((?>a?)*)*c",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("aac","((?>a?)*)*c",[]))),
- <<"a">> = iolist_to_binary(join(re:split("aba","(?>.*?a)(?<=ba)",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("aac","((?>a?)*)*c",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("aba","(?>.*?a)(?<=ba)",[trim]))),
<<"a:">> = iolist_to_binary(join(re:split("aba","(?>.*?a)(?<=ba)",[{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("aba","(?>.*?a)(?<=ba)",[]))),
- <<"">> = iolist_to_binary(join(re:split("aba","(?:.*?a)(?<=ba)",[trim]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("aba","(?>.*?a)(?<=ba)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aba","(?:.*?a)(?<=ba)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aba","(?:.*?a)(?<=ba)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aba","(?:.*?a)(?<=ba)",[]))),
- <<"a">> = iolist_to_binary(join(re:split("aab",".*?a(*PRUNE)b",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aba","(?:.*?a)(?<=ba)",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("aab",".*?a(*PRUNE)b",[trim]))),
<<"a:">> = iolist_to_binary(join(re:split("aab",".*?a(*PRUNE)b",[{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("aab",".*?a(*PRUNE)b",[]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("aab",".*?a(*PRUNE)b",[]))),
<<"a">> = iolist_to_binary(join(re:split("aab",".*?a(*PRUNE)b",[dotall,
- trim]))),
+ trim]))),
<<"a:">> = iolist_to_binary(join(re:split("aab",".*?a(*PRUNE)b",[dotall,
{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("aab",".*?a(*PRUNE)b",[dotall]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("aab",".*?a(*PRUNE)b",[dotall]))),
<<"aab">> = iolist_to_binary(join(re:split("aab","^a(*PRUNE)b",[dotall,
- trim]))),
+ trim]))),
<<"aab">> = iolist_to_binary(join(re:split("aab","^a(*PRUNE)b",[dotall,
{parts,
- 2}]))),
- <<"aab">> = iolist_to_binary(join(re:split("aab","^a(*PRUNE)b",[dotall]))),
- <<"a">> = iolist_to_binary(join(re:split("aab",".*?a(*SKIP)b",[trim]))),
+ 2}]))),
+ <<"aab">> = iolist_to_binary(join(re:split("aab","^a(*PRUNE)b",[dotall]))),
+ <<"a">> = iolist_to_binary(join(re:split("aab",".*?a(*SKIP)b",[trim]))),
<<"a:">> = iolist_to_binary(join(re:split("aab",".*?a(*SKIP)b",[{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("aab",".*?a(*SKIP)b",[]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("aab",".*?a(*SKIP)b",[]))),
<<"a">> = iolist_to_binary(join(re:split("aab","(?>.*?a)b",[dotall,
- trim]))),
+ trim]))),
<<"a:">> = iolist_to_binary(join(re:split("aab","(?>.*?a)b",[dotall,
{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("aab","(?>.*?a)b",[dotall]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("aab","(?>.*?a)b",[dotall]))),
ok.
run50() ->
- <<"a">> = iolist_to_binary(join(re:split("aab","(?>.*?a)b",[trim]))),
+ <<"a">> = iolist_to_binary(join(re:split("aab","(?>.*?a)b",[trim]))),
<<"a:">> = iolist_to_binary(join(re:split("aab","(?>.*?a)b",[{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("aab","(?>.*?a)b",[]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("aab","(?>.*?a)b",[]))),
<<"aab">> = iolist_to_binary(join(re:split("aab","(?>^a)b",[dotall,
- trim]))),
+ trim]))),
<<"aab">> = iolist_to_binary(join(re:split("aab","(?>^a)b",[dotall,
{parts,
- 2}]))),
- <<"aab">> = iolist_to_binary(join(re:split("aab","(?>^a)b",[dotall]))),
- <<"alphabetabcd:abcd">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*?)(?<=(abcd)|(wxyz))",[trim]))),
+ 2}]))),
+ <<"aab">> = iolist_to_binary(join(re:split("aab","(?>^a)b",[dotall]))),
+ <<"alphabetabcd:abcd">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*?)(?<=(abcd)|(wxyz))",[trim]))),
<<"alphabetabcd:abcd::">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*?)(?<=(abcd)|(wxyz))",[{parts,
- 2}]))),
- <<"alphabetabcd:abcd::">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*?)(?<=(abcd)|(wxyz))",[]))),
- <<"endingwxyz::wxyz">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*?)(?<=(abcd)|(wxyz))",[trim]))),
+ 2}]))),
+ <<"alphabetabcd:abcd::">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*?)(?<=(abcd)|(wxyz))",[]))),
+ <<"endingwxyz::wxyz">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*?)(?<=(abcd)|(wxyz))",[trim]))),
<<"endingwxyz::wxyz:">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*?)(?<=(abcd)|(wxyz))",[{parts,
- 2}]))),
- <<"endingwxyz::wxyz:">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*?)(?<=(abcd)|(wxyz))",[]))),
- <<":abcd">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*)(?<=(abcd)|(wxyz))",[trim]))),
+ 2}]))),
+ <<"endingwxyz::wxyz:">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*?)(?<=(abcd)|(wxyz))",[]))),
+ <<":abcd">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*)(?<=(abcd)|(wxyz))",[trim]))),
<<":abcd::">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*)(?<=(abcd)|(wxyz))",[{parts,
- 2}]))),
- <<":abcd::">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*)(?<=(abcd)|(wxyz))",[]))),
- <<"::wxyz">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*)(?<=(abcd)|(wxyz))",[trim]))),
+ 2}]))),
+ <<":abcd::">> = iolist_to_binary(join(re:split("alphabetabcd","(?>.*)(?<=(abcd)|(wxyz))",[]))),
+ <<"::wxyz">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*)(?<=(abcd)|(wxyz))",[trim]))),
<<"::wxyz:">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*)(?<=(abcd)|(wxyz))",[{parts,
- 2}]))),
- <<"::wxyz:">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*)(?<=(abcd)|(wxyz))",[]))),
- <<"abcdfooxyz">> = iolist_to_binary(join(re:split("abcdfooxyz","(?>.*)foo",[trim]))),
+ 2}]))),
+ <<"::wxyz:">> = iolist_to_binary(join(re:split("endingwxyz","(?>.*)(?<=(abcd)|(wxyz))",[]))),
+ <<"abcdfooxyz">> = iolist_to_binary(join(re:split("abcdfooxyz","(?>.*)foo",[trim]))),
<<"abcdfooxyz">> = iolist_to_binary(join(re:split("abcdfooxyz","(?>.*)foo",[{parts,
- 2}]))),
- <<"abcdfooxyz">> = iolist_to_binary(join(re:split("abcdfooxyz","(?>.*)foo",[]))),
- <<"abcd:xyz">> = iolist_to_binary(join(re:split("abcdfooxyz","(?>.*?)foo",[trim]))),
+ 2}]))),
+ <<"abcdfooxyz">> = iolist_to_binary(join(re:split("abcdfooxyz","(?>.*)foo",[]))),
+ <<"abcd:xyz">> = iolist_to_binary(join(re:split("abcdfooxyz","(?>.*?)foo",[trim]))),
<<"abcd:xyz">> = iolist_to_binary(join(re:split("abcdfooxyz","(?>.*?)foo",[{parts,
- 2}]))),
- <<"abcd:xyz">> = iolist_to_binary(join(re:split("abcdfooxyz","(?>.*?)foo",[]))),
- <<"">> = iolist_to_binary(join(re:split("ac","(?:(a(*PRUNE)b)){0}(?:(?1)|ac)",[trim]))),
+ 2}]))),
+ <<"abcd:xyz">> = iolist_to_binary(join(re:split("abcdfooxyz","(?>.*?)foo",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ac","(?:(a(*PRUNE)b)){0}(?:(?1)|ac)",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("ac","(?:(a(*PRUNE)b)){0}(?:(?1)|ac)",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("ac","(?:(a(*PRUNE)b)){0}(?:(?1)|ac)",[]))),
- <<"">> = iolist_to_binary(join(re:split("ac","(?:(a(*SKIP)b)){0}(?:(?1)|ac)",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("ac","(?:(a(*PRUNE)b)){0}(?:(?1)|ac)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ac","(?:(a(*SKIP)b)){0}(?:(?1)|ac)",[trim]))),
<<"::">> = iolist_to_binary(join(re:split("ac","(?:(a(*SKIP)b)){0}(?:(?1)|ac)",[{parts,
- 2}]))),
- <<"::">> = iolist_to_binary(join(re:split("ac","(?:(a(*SKIP)b)){0}(?:(?1)|ac)",[]))),
- <<"aa">> = iolist_to_binary(join(re:split("aa","(?<=(*SKIP)ac)a",[trim]))),
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("ac","(?:(a(*SKIP)b)){0}(?:(?1)|ac)",[]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aa","(?<=(*SKIP)ac)a",[trim]))),
<<"aa">> = iolist_to_binary(join(re:split("aa","(?<=(*SKIP)ac)a",[{parts,
- 2}]))),
- <<"aa">> = iolist_to_binary(join(re:split("aa","(?<=(*SKIP)ac)a",[]))),
- <<"aa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)b|a+c",[trim]))),
+ 2}]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aa","(?<=(*SKIP)ac)a",[]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)b|a+c",[trim]))),
<<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)b|a+c",[{parts,
- 2}]))),
- <<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)b|a+c",[]))),
- <<"aa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)(*PRUNE)b|a+c",[trim]))),
+ 2}]))),
+ <<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)b|a+c",[]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)(*PRUNE)b|a+c",[trim]))),
<<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)(*PRUNE)b|a+c",[{parts,
- 2}]))),
- <<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)(*PRUNE)b|a+c",[]))),
- <<"aa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP:N)(*PRUNE)b|a+c",[trim]))),
+ 2}]))),
+ <<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)(*PRUNE)b|a+c",[]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP:N)(*PRUNE)b|a+c",[trim]))),
<<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP:N)(*PRUNE)b|a+c",[{parts,
- 2}]))),
- <<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP:N)(*PRUNE)b|a+c",[]))),
- <<"aa">> = iolist_to_binary(join(re:split("aaaaaac","aaaa(*:N)a(*SKIP:N)(*PRUNE)b|a+c",[trim]))),
+ 2}]))),
+ <<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP:N)(*PRUNE)b|a+c",[]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aaaaaac","aaaa(*:N)a(*SKIP:N)(*PRUNE)b|a+c",[trim]))),
<<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaa(*:N)a(*SKIP:N)(*PRUNE)b|a+c",[{parts,
- 2}]))),
- <<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaa(*:N)a(*SKIP:N)(*PRUNE)b|a+c",[]))),
- <<"aa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)(*PRUNE)b|a+c",[trim]))),
+ 2}]))),
+ <<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaa(*:N)a(*SKIP:N)(*PRUNE)b|a+c",[]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)(*PRUNE)b|a+c",[trim]))),
<<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)(*PRUNE)b|a+c",[{parts,
- 2}]))),
- <<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)(*PRUNE)b|a+c",[]))),
+ 2}]))),
+ <<"aa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)(*PRUNE)b|a+c",[]))),
ok.
run51() ->
- <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)b|a+c",[trim]))),
+ <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)b|a+c",[trim]))),
<<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)b|a+c",[{parts,
- 2}]))),
- <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)b|a+c",[]))),
- <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)(*SKIP)b|a+c",[trim]))),
+ 2}]))),
+ <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)b|a+c",[]))),
+ <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)(*SKIP)b|a+c",[trim]))),
<<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)(*SKIP)b|a+c",[{parts,
- 2}]))),
- <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)(*SKIP)b|a+c",[]))),
- <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)(*SKIP)b|a+c",[trim]))),
+ 2}]))),
+ <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)(*SKIP)b|a+c",[]))),
+ <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)(*SKIP)b|a+c",[trim]))),
<<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)(*SKIP)b|a+c",[{parts,
- 2}]))),
- <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)(*SKIP)b|a+c",[]))),
- <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)(*SKIP)b|a+c",[trim]))),
+ 2}]))),
+ <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)(*SKIP)b|a+c",[]))),
+ <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)(*SKIP)b|a+c",[trim]))),
<<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)(*SKIP)b|a+c",[{parts,
- 2}]))),
- <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)(*SKIP)b|a+c",[]))),
- <<"aaaaaac">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)b|a+c",[trim]))),
+ 2}]))),
+ <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)(*SKIP)b|a+c",[]))),
+ <<"aaaaaac">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)b|a+c",[trim]))),
<<"aaaaaac">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)b|a+c",[{parts,
- 2}]))),
- <<"aaaaaac">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)b|a+c",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)b|a+c",[trim]))),
+ 2}]))),
+ <<"aaaaaac">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)b|a+c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)b|a+c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)b|a+c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)b|a+c",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)(*THEN)b|a+c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*THEN)b|a+c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)(*THEN)b|a+c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)(*THEN)b|a+c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)(*THEN)b|a+c",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)(*THEN)b|a+c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*SKIP)(*THEN)b|a+c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)(*THEN)b|a+c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)(*THEN)b|a+c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)(*THEN)b|a+c",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)(*THEN)b|a+c",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*PRUNE)(*THEN)b|a+c",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)(*THEN)b|a+c",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)(*THEN)b|a+c",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)(*THEN)b|a+c",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaaaac","aaaaa(*COMMIT)(*THEN)b|a+c",[]))),
ok.
run52() ->
- <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:m)(*PRUNE:m)(*SKIP:m)m|a+",[trim]))),
+ <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:m)(*PRUNE:m)(*SKIP:m)m|a+",[trim]))),
<<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:m)(*PRUNE:m)(*SKIP:m)m|a+",[{parts,
- 2}]))),
- <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:m)(*PRUNE:m)(*SKIP:m)m|a+",[]))),
- <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:m)(*MARK:m)(*PRUNE)(*SKIP:m)m|a+",[trim]))),
+ 2}]))),
+ <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:m)(*PRUNE:m)(*SKIP:m)m|a+",[]))),
+ <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:m)(*MARK:m)(*PRUNE)(*SKIP:m)m|a+",[trim]))),
<<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:m)(*MARK:m)(*PRUNE)(*SKIP:m)m|a+",[{parts,
- 2}]))),
- <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:m)(*MARK:m)(*PRUNE)(*SKIP:m)m|a+",[]))),
- <<"aa">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:n)(*PRUNE:m)(*SKIP:m)m|a+",[trim]))),
+ 2}]))),
+ <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:m)(*MARK:m)(*PRUNE)(*SKIP:m)m|a+",[]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:n)(*PRUNE:m)(*SKIP:m)m|a+",[trim]))),
<<"aa:">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:n)(*PRUNE:m)(*SKIP:m)m|a+",[{parts,
- 2}]))),
- <<"aa:">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:n)(*PRUNE:m)(*SKIP:m)m|a+",[]))),
- <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:n)(*MARK:m)(*PRUNE)(*SKIP:m)m|a+",[trim]))),
+ 2}]))),
+ <<"aa:">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:n)(*PRUNE:m)(*SKIP:m)m|a+",[]))),
+ <<"aaaaa">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:n)(*MARK:m)(*PRUNE)(*SKIP:m)m|a+",[trim]))),
<<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:n)(*MARK:m)(*PRUNE)(*SKIP:m)m|a+",[{parts,
- 2}]))),
- <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:n)(*MARK:m)(*PRUNE)(*SKIP:m)m|a+",[]))),
- <<"aa">> = iolist_to_binary(join(re:split("aaaac","a(*MARK:A)aa(*PRUNE:A)a(*SKIP:A)b|a+c",[trim]))),
+ 2}]))),
+ <<"aaaaa:">> = iolist_to_binary(join(re:split("aaaaaa","aaaaa(*:n)(*MARK:m)(*PRUNE)(*SKIP:m)m|a+",[]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aaaac","a(*MARK:A)aa(*PRUNE:A)a(*SKIP:A)b|a+c",[trim]))),
<<"aa:">> = iolist_to_binary(join(re:split("aaaac","a(*MARK:A)aa(*PRUNE:A)a(*SKIP:A)b|a+c",[{parts,
- 2}]))),
- <<"aa:">> = iolist_to_binary(join(re:split("aaaac","a(*MARK:A)aa(*PRUNE:A)a(*SKIP:A)b|a+c",[]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaaac","a(*MARK:A)aa(*MARK:A)a(*SKIP:A)b|a+c",[trim]))),
+ 2}]))),
+ <<"aa:">> = iolist_to_binary(join(re:split("aaaac","a(*MARK:A)aa(*PRUNE:A)a(*SKIP:A)b|a+c",[]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaaac","a(*MARK:A)aa(*MARK:A)a(*SKIP:A)b|a+c",[trim]))),
<<"aaa:">> = iolist_to_binary(join(re:split("aaaac","a(*MARK:A)aa(*MARK:A)a(*SKIP:A)b|a+c",[{parts,
- 2}]))),
- <<"aaa:">> = iolist_to_binary(join(re:split("aaaac","a(*MARK:A)aa(*MARK:A)a(*SKIP:A)b|a+c",[]))),
- <<"aa">> = iolist_to_binary(join(re:split("aaaac","aaa(*PRUNE:A)a(*SKIP:A)b|a+c",[trim]))),
+ 2}]))),
+ <<"aaa:">> = iolist_to_binary(join(re:split("aaaac","a(*MARK:A)aa(*MARK:A)a(*SKIP:A)b|a+c",[]))),
+ <<"aa">> = iolist_to_binary(join(re:split("aaaac","aaa(*PRUNE:A)a(*SKIP:A)b|a+c",[trim]))),
<<"aa:">> = iolist_to_binary(join(re:split("aaaac","aaa(*PRUNE:A)a(*SKIP:A)b|a+c",[{parts,
- 2}]))),
- <<"aa:">> = iolist_to_binary(join(re:split("aaaac","aaa(*PRUNE:A)a(*SKIP:A)b|a+c",[]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaaac","aaa(*MARK:A)a(*SKIP:A)b|a+c",[trim]))),
+ 2}]))),
+ <<"aa:">> = iolist_to_binary(join(re:split("aaaac","aaa(*PRUNE:A)a(*SKIP:A)b|a+c",[]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaaac","aaa(*MARK:A)a(*SKIP:A)b|a+c",[trim]))),
<<"aaa:">> = iolist_to_binary(join(re:split("aaaac","aaa(*MARK:A)a(*SKIP:A)b|a+c",[{parts,
- 2}]))),
- <<"aaa:">> = iolist_to_binary(join(re:split("aaaac","aaa(*MARK:A)a(*SKIP:A)b|a+c",[]))),
- <<":a">> = iolist_to_binary(join(re:split("ba",".?(a|b(*THEN)c)",[trim]))),
+ 2}]))),
+ <<"aaa:">> = iolist_to_binary(join(re:split("aaaac","aaa(*MARK:A)a(*SKIP:A)b|a+c",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("ba",".?(a|b(*THEN)c)",[trim]))),
<<":a:">> = iolist_to_binary(join(re:split("ba",".?(a|b(*THEN)c)",[{parts,
- 2}]))),
- <<":a:">> = iolist_to_binary(join(re:split("ba",".?(a|b(*THEN)c)",[]))),
- <<":ab">> = iolist_to_binary(join(re:split("abc","(a(*COMMIT)b)c|abd",[trim]))),
+ 2}]))),
+ <<":a:">> = iolist_to_binary(join(re:split("ba",".?(a|b(*THEN)c)",[]))),
+ <<":ab">> = iolist_to_binary(join(re:split("abc","(a(*COMMIT)b)c|abd",[trim]))),
<<":ab:">> = iolist_to_binary(join(re:split("abc","(a(*COMMIT)b)c|abd",[{parts,
- 2}]))),
- <<":ab:">> = iolist_to_binary(join(re:split("abc","(a(*COMMIT)b)c|abd",[]))),
- <<"abd">> = iolist_to_binary(join(re:split("abd","(a(*COMMIT)b)c|abd",[trim]))),
+ 2}]))),
+ <<":ab:">> = iolist_to_binary(join(re:split("abc","(a(*COMMIT)b)c|abd",[]))),
+ <<"abd">> = iolist_to_binary(join(re:split("abd","(a(*COMMIT)b)c|abd",[trim]))),
<<"abd">> = iolist_to_binary(join(re:split("abd","(a(*COMMIT)b)c|abd",[{parts,
- 2}]))),
- <<"abd">> = iolist_to_binary(join(re:split("abd","(a(*COMMIT)b)c|abd",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","(?=a(*COMMIT)b)abc|abd",[trim]))),
+ 2}]))),
+ <<"abd">> = iolist_to_binary(join(re:split("abd","(a(*COMMIT)b)c|abd",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","(?=a(*COMMIT)b)abc|abd",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","(?=a(*COMMIT)b)abc|abd",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","(?=a(*COMMIT)b)abc|abd",[]))),
- <<"">> = iolist_to_binary(join(re:split("abd","(?=a(*COMMIT)b)abc|abd",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","(?=a(*COMMIT)b)abc|abd",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abd","(?=a(*COMMIT)b)abc|abd",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abd","(?=a(*COMMIT)b)abc|abd",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abd","(?=a(*COMMIT)b)abc|abd",[]))),
- <<"">> = iolist_to_binary(join(re:split("abc","(?>a(*COMMIT)b)c|abd",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abd","(?=a(*COMMIT)b)abc|abd",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abc","(?>a(*COMMIT)b)c|abd",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abc","(?>a(*COMMIT)b)c|abd",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abc","(?>a(*COMMIT)b)c|abd",[]))),
- <<"">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)b)c|abd",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abc","(?>a(*COMMIT)b)c|abd",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)b)c|abd",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)b)c|abd",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)b)c|abd",[]))),
- <<"abd">> = iolist_to_binary(join(re:split("abd","a(?=b(*COMMIT)c)[^d]|abd",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)b)c|abd",[]))),
+ <<"abd">> = iolist_to_binary(join(re:split("abd","a(?=b(*COMMIT)c)[^d]|abd",[trim]))),
<<"abd">> = iolist_to_binary(join(re:split("abd","a(?=b(*COMMIT)c)[^d]|abd",[{parts,
- 2}]))),
- <<"abd">> = iolist_to_binary(join(re:split("abd","a(?=b(*COMMIT)c)[^d]|abd",[]))),
- <<":c">> = iolist_to_binary(join(re:split("abc","a(?=b(*COMMIT)c)[^d]|abd",[trim]))),
+ 2}]))),
+ <<"abd">> = iolist_to_binary(join(re:split("abd","a(?=b(*COMMIT)c)[^d]|abd",[]))),
+ <<":c">> = iolist_to_binary(join(re:split("abc","a(?=b(*COMMIT)c)[^d]|abd",[trim]))),
<<":c">> = iolist_to_binary(join(re:split("abc","a(?=b(*COMMIT)c)[^d]|abd",[{parts,
- 2}]))),
- <<":c">> = iolist_to_binary(join(re:split("abc","a(?=b(*COMMIT)c)[^d]|abd",[]))),
- <<"">> = iolist_to_binary(join(re:split("abd","a(?=bc).|abd",[trim]))),
+ 2}]))),
+ <<":c">> = iolist_to_binary(join(re:split("abc","a(?=b(*COMMIT)c)[^d]|abd",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abd","a(?=bc).|abd",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abd","a(?=bc).|abd",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abd","a(?=bc).|abd",[]))),
- <<":c">> = iolist_to_binary(join(re:split("abc","a(?=bc).|abd",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abd","a(?=bc).|abd",[]))),
+ <<":c">> = iolist_to_binary(join(re:split("abc","a(?=bc).|abd",[trim]))),
<<":c">> = iolist_to_binary(join(re:split("abc","a(?=bc).|abd",[{parts,
- 2}]))),
- <<":c">> = iolist_to_binary(join(re:split("abc","a(?=bc).|abd",[]))),
- <<"abceabd">> = iolist_to_binary(join(re:split("abceabd","a(?>b(*COMMIT)c)d|abd",[trim]))),
+ 2}]))),
+ <<":c">> = iolist_to_binary(join(re:split("abc","a(?=bc).|abd",[]))),
+ <<"abceabd">> = iolist_to_binary(join(re:split("abceabd","a(?>b(*COMMIT)c)d|abd",[trim]))),
<<"abceabd">> = iolist_to_binary(join(re:split("abceabd","a(?>b(*COMMIT)c)d|abd",[{parts,
- 2}]))),
- <<"abceabd">> = iolist_to_binary(join(re:split("abceabd","a(?>b(*COMMIT)c)d|abd",[]))),
- <<"abce">> = iolist_to_binary(join(re:split("abceabd","a(?>bc)d|abd",[trim]))),
+ 2}]))),
+ <<"abceabd">> = iolist_to_binary(join(re:split("abceabd","a(?>b(*COMMIT)c)d|abd",[]))),
+ <<"abce">> = iolist_to_binary(join(re:split("abceabd","a(?>bc)d|abd",[trim]))),
<<"abce:">> = iolist_to_binary(join(re:split("abceabd","a(?>bc)d|abd",[{parts,
- 2}]))),
- <<"abce:">> = iolist_to_binary(join(re:split("abceabd","a(?>bc)d|abd",[]))),
- <<"">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)b)c|abd",[trim]))),
+ 2}]))),
+ <<"abce:">> = iolist_to_binary(join(re:split("abceabd","a(?>bc)d|abd",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)b)c|abd",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)b)c|abd",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)b)c|abd",[]))),
- <<"abd">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)c)d|abd",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)b)c|abd",[]))),
+ <<"abd">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)c)d|abd",[trim]))),
<<"abd">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)c)d|abd",[{parts,
- 2}]))),
- <<"abd">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)c)d|abd",[]))),
- <<"::c">> = iolist_to_binary(join(re:split("ac","((?=a(*COMMIT)b)ab|ac){0}(?:(?1)|a(c))",[trim]))),
+ 2}]))),
+ <<"abd">> = iolist_to_binary(join(re:split("abd","(?>a(*COMMIT)c)d|abd",[]))),
+ <<"::c">> = iolist_to_binary(join(re:split("ac","((?=a(*COMMIT)b)ab|ac){0}(?:(?1)|a(c))",[trim]))),
<<"::c:">> = iolist_to_binary(join(re:split("ac","((?=a(*COMMIT)b)ab|ac){0}(?:(?1)|a(c))",[{parts,
- 2}]))),
- <<"::c:">> = iolist_to_binary(join(re:split("ac","((?=a(*COMMIT)b)ab|ac){0}(?:(?1)|a(c))",[]))),
+ 2}]))),
+ <<"::c:">> = iolist_to_binary(join(re:split("ac","((?=a(*COMMIT)b)ab|ac){0}(?:(?1)|a(c))",[]))),
ok.
run53() ->
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a)?(?(1)a|b)+$",[trim]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a)?(?(1)a|b)+$",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a)?(?(1)a|b)+$",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a)?(?(1)a|b)+$",[]))),
- <<"a">> = iolist_to_binary(join(re:split("a","^(a)?(?(1)a|b)+$",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^(a)?(?(1)a|b)+$",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","^(a)?(?(1)a|b)+$",[trim]))),
<<"a">> = iolist_to_binary(join(re:split("a","^(a)?(?(1)a|b)+$",[{parts,
- 2}]))),
- <<"a">> = iolist_to_binary(join(re:split("a","^(a)?(?(1)a|b)+$",[]))),
- <<"a">> = iolist_to_binary(join(re:split("ab","(?=a\\Kb)ab",[trim]))),
+ 2}]))),
+ <<"a">> = iolist_to_binary(join(re:split("a","^(a)?(?(1)a|b)+$",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("ab","(?=a\\Kb)ab",[trim]))),
<<"a:">> = iolist_to_binary(join(re:split("ab","(?=a\\Kb)ab",[{parts,
- 2}]))),
- <<"a:">> = iolist_to_binary(join(re:split("ab","(?=a\\Kb)ab",[]))),
- <<"">> = iolist_to_binary(join(re:split("ac","(?!a\\Kb)ac",[trim]))),
+ 2}]))),
+ <<"a:">> = iolist_to_binary(join(re:split("ab","(?=a\\Kb)ab",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ac","(?!a\\Kb)ac",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ac","(?!a\\Kb)ac",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ac","(?!a\\Kb)ac",[]))),
- <<"ab">> = iolist_to_binary(join(re:split("abcd","^abc(?<=b\\Kc)d",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ac","(?!a\\Kb)ac",[]))),
+ <<"ab">> = iolist_to_binary(join(re:split("abcd","^abc(?<=b\\Kc)d",[trim]))),
<<"ab:">> = iolist_to_binary(join(re:split("abcd","^abc(?<=b\\Kc)d",[{parts,
- 2}]))),
- <<"ab:">> = iolist_to_binary(join(re:split("abcd","^abc(?<=b\\Kc)d",[]))),
- <<"">> = iolist_to_binary(join(re:split("abcd","^abc(?<!b\\Kq)d",[trim]))),
+ 2}]))),
+ <<"ab:">> = iolist_to_binary(join(re:split("abcd","^abc(?<=b\\Kc)d",[]))),
+ <<"">> = iolist_to_binary(join(re:split("abcd","^abc(?<!b\\Kq)d",[trim]))),
<<":">> = iolist_to_binary(join(re:split("abcd","^abc(?<!b\\Kq)d",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("abcd","^abc(?<!b\\Kq)d",[]))),
- <<":abcd">> = iolist_to_binary(join(re:split("abcd","^((abc|abcx)(*THEN)y|abcd)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("abcd","^abc(?<!b\\Kq)d",[]))),
+ <<":abcd">> = iolist_to_binary(join(re:split("abcd","^((abc|abcx)(*THEN)y|abcd)",[trim]))),
<<":abcd::">> = iolist_to_binary(join(re:split("abcd","^((abc|abcx)(*THEN)y|abcd)",[{parts,
- 2}]))),
- <<":abcd::">> = iolist_to_binary(join(re:split("abcd","^((abc|abcx)(*THEN)y|abcd)",[]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^((abc|abcx)(*THEN)y|abcd)",[trim]))),
+ 2}]))),
+ <<":abcd::">> = iolist_to_binary(join(re:split("abcd","^((abc|abcx)(*THEN)y|abcd)",[]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^((abc|abcx)(*THEN)y|abcd)",[trim]))),
<<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^((abc|abcx)(*THEN)y|abcd)",[{parts,
- 2}]))),
- <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^((abc|abcx)(*THEN)y|abcd)",[]))),
- <<"abcxy">> = iolist_to_binary(join(re:split("abcxy","^((abc|abcx)(*THEN)y|abcd)",[trim]))),
+ 2}]))),
+ <<"*** Failers">> = iolist_to_binary(join(re:split("*** Failers","^((abc|abcx)(*THEN)y|abcd)",[]))),
+ <<"abcxy">> = iolist_to_binary(join(re:split("abcxy","^((abc|abcx)(*THEN)y|abcd)",[trim]))),
<<"abcxy">> = iolist_to_binary(join(re:split("abcxy","^((abc|abcx)(*THEN)y|abcd)",[{parts,
- 2}]))),
- <<"abcxy">> = iolist_to_binary(join(re:split("abcxy","^((abc|abcx)(*THEN)y|abcd)",[]))),
- <<"yes">> = iolist_to_binary(join(re:split("yes","^((yes|no)(*THEN)(*F))?",[trim]))),
+ 2}]))),
+ <<"abcxy">> = iolist_to_binary(join(re:split("abcxy","^((abc|abcx)(*THEN)y|abcd)",[]))),
+ <<"yes">> = iolist_to_binary(join(re:split("yes","^((yes|no)(*THEN)(*F))?",[trim]))),
<<"yes">> = iolist_to_binary(join(re:split("yes","^((yes|no)(*THEN)(*F))?",[{parts,
- 2}]))),
- <<"yes">> = iolist_to_binary(join(re:split("yes","^((yes|no)(*THEN)(*F))?",[]))),
- <<"ac">> = iolist_to_binary(join(re:split("ac","(?=a(*COMMIT)b|ac)ac|ac",[trim]))),
+ 2}]))),
+ <<"yes">> = iolist_to_binary(join(re:split("yes","^((yes|no)(*THEN)(*F))?",[]))),
+ <<"ac">> = iolist_to_binary(join(re:split("ac","(?=a(*COMMIT)b|ac)ac|ac",[trim]))),
<<"ac">> = iolist_to_binary(join(re:split("ac","(?=a(*COMMIT)b|ac)ac|ac",[{parts,
- 2}]))),
- <<"ac">> = iolist_to_binary(join(re:split("ac","(?=a(*COMMIT)b|ac)ac|ac",[]))),
+ 2}]))),
+ <<"ac">> = iolist_to_binary(join(re:split("ac","(?=a(*COMMIT)b|ac)ac|ac",[]))),
<<"ac">> = iolist_to_binary(join(re:split("ac","(?=a(*COMMIT)b|(ac)) ac | (a)c",[extended,
- trim]))),
+ trim]))),
<<"ac">> = iolist_to_binary(join(re:split("ac","(?=a(*COMMIT)b|(ac)) ac | (a)c",[extended,
{parts,
- 2}]))),
- <<"ac">> = iolist_to_binary(join(re:split("ac","(?=a(*COMMIT)b|(ac)) ac | (a)c",[extended]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*THEN)a)bn|bnn)",[trim]))),
+ 2}]))),
+ <<"ac">> = iolist_to_binary(join(re:split("ac","(?=a(*COMMIT)b|(ac)) ac | (a)c",[extended]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*THEN)a)bn|bnn)",[trim]))),
<<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*THEN)a)bn|bnn)",[{parts,
- 2}]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*THEN)a)bn|bnn)",[]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*SKIP)a)bn|bnn",[trim]))),
+ 2}]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*THEN)a)bn|bnn)",[]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*SKIP)a)bn|bnn",[trim]))),
<<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*SKIP)a)bn|bnn",[{parts,
- 2}]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*SKIP)a)bn|bnn",[]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*SKIP)a)bn|bnn)",[trim]))),
+ 2}]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*SKIP)a)bn|bnn",[]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*SKIP)a)bn|bnn)",[trim]))),
<<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*SKIP)a)bn|bnn)",[{parts,
- 2}]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*SKIP)a)bn|bnn)",[]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*PRUNE)a)bn|bnn",[trim]))),
+ 2}]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*SKIP)a)bn|bnn)",[]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*PRUNE)a)bn|bnn",[trim]))),
<<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*PRUNE)a)bn|bnn",[{parts,
- 2}]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*PRUNE)a)bn|bnn",[]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*PRUNE)a)bn|bnn)",[trim]))),
+ 2}]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*PRUNE)a)bn|bnn",[]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*PRUNE)a)bn|bnn)",[trim]))),
<<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*PRUNE)a)bn|bnn)",[{parts,
- 2}]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*PRUNE)a)bn|bnn)",[]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*COMMIT)a)bn|bnn",[trim]))),
+ 2}]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*PRUNE)a)bn|bnn)",[]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*COMMIT)a)bn|bnn",[trim]))),
<<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*COMMIT)a)bn|bnn",[{parts,
- 2}]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*COMMIT)a)bn|bnn",[]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*COMMIT)a)bn|bnn)",[trim]))),
+ 2}]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?!b(*COMMIT)a)bn|bnn",[]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*COMMIT)a)bn|bnn)",[trim]))),
<<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*COMMIT)a)bn|bnn)",[{parts,
- 2}]))),
- <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*COMMIT)a)bn|bnn)",[]))),
- <<"bnn">> = iolist_to_binary(join(re:split("bnn","(?=b(*SKIP)a)bn|bnn",[trim]))),
+ 2}]))),
+ <<":n">> = iolist_to_binary(join(re:split("bnn","(?(?!b(*COMMIT)a)bn|bnn)",[]))),
+ <<"bnn">> = iolist_to_binary(join(re:split("bnn","(?=b(*SKIP)a)bn|bnn",[trim]))),
<<"bnn">> = iolist_to_binary(join(re:split("bnn","(?=b(*SKIP)a)bn|bnn",[{parts,
- 2}]))),
- <<"bnn">> = iolist_to_binary(join(re:split("bnn","(?=b(*SKIP)a)bn|bnn",[]))),
- <<"">> = iolist_to_binary(join(re:split("bnn","(?=b(*THEN)a)bn|bnn",[trim]))),
+ 2}]))),
+ <<"bnn">> = iolist_to_binary(join(re:split("bnn","(?=b(*SKIP)a)bn|bnn",[]))),
+ <<"">> = iolist_to_binary(join(re:split("bnn","(?=b(*THEN)a)bn|bnn",[trim]))),
<<":">> = iolist_to_binary(join(re:split("bnn","(?=b(*THEN)a)bn|bnn",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("bnn","(?=b(*THEN)a)bn|bnn",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("bnn","(?=b(*THEN)a)bn|bnn",[]))),
ok.
run54() ->
- <<":d">> = iolist_to_binary(join(re:split("acd","(?!a(*SKIP)b)..",[trim]))),
+ <<":d">> = iolist_to_binary(join(re:split("acd","(?!a(*SKIP)b)..",[trim]))),
<<":d">> = iolist_to_binary(join(re:split("acd","(?!a(*SKIP)b)..",[{parts,
- 2}]))),
- <<":d">> = iolist_to_binary(join(re:split("acd","(?!a(*SKIP)b)..",[]))),
- <<"ac">> = iolist_to_binary(join(re:split("ac","^(?(?!a(*SKIP)b))",[trim]))),
+ 2}]))),
+ <<":d">> = iolist_to_binary(join(re:split("acd","(?!a(*SKIP)b)..",[]))),
+ <<"ac">> = iolist_to_binary(join(re:split("ac","^(?(?!a(*SKIP)b))",[trim]))),
<<"ac">> = iolist_to_binary(join(re:split("ac","^(?(?!a(*SKIP)b))",[{parts,
- 2}]))),
- <<"ac">> = iolist_to_binary(join(re:split("ac","^(?(?!a(*SKIP)b))",[]))),
- <<":d">> = iolist_to_binary(join(re:split("acd","^(?!a(*PRUNE)b)..",[trim]))),
+ 2}]))),
+ <<"ac">> = iolist_to_binary(join(re:split("ac","^(?(?!a(*SKIP)b))",[]))),
+ <<":d">> = iolist_to_binary(join(re:split("acd","^(?!a(*PRUNE)b)..",[trim]))),
<<":d">> = iolist_to_binary(join(re:split("acd","^(?!a(*PRUNE)b)..",[{parts,
- 2}]))),
- <<":d">> = iolist_to_binary(join(re:split("acd","^(?!a(*PRUNE)b)..",[]))),
- <<":d">> = iolist_to_binary(join(re:split("acd","(?!a(*PRUNE)b)..",[trim]))),
+ 2}]))),
+ <<":d">> = iolist_to_binary(join(re:split("acd","^(?!a(*PRUNE)b)..",[]))),
+ <<":d">> = iolist_to_binary(join(re:split("acd","(?!a(*PRUNE)b)..",[trim]))),
<<":d">> = iolist_to_binary(join(re:split("acd","(?!a(*PRUNE)b)..",[{parts,
- 2}]))),
- <<":d">> = iolist_to_binary(join(re:split("acd","(?!a(*PRUNE)b)..",[]))),
- <<"">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc)",[trim]))),
+ 2}]))),
+ <<":d">> = iolist_to_binary(join(re:split("acd","(?!a(*PRUNE)b)..",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc)",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc)",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc)",[]))),
- <<":CD">> = iolist_to_binary(join(re:split("CD","^(A(*THEN)B|C(*THEN)D)",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ba","\\A.*?(?:a|bc)",[]))),
+ <<":CD">> = iolist_to_binary(join(re:split("CD","^(A(*THEN)B|C(*THEN)D)",[trim]))),
<<":CD:">> = iolist_to_binary(join(re:split("CD","^(A(*THEN)B|C(*THEN)D)",[{parts,
- 2}]))),
- <<":CD:">> = iolist_to_binary(join(re:split("CD","^(A(*THEN)B|C(*THEN)D)",[]))),
- <<"">> = iolist_to_binary(join(re:split("1234","^\\d*\\w{4}",[trim]))),
+ 2}]))),
+ <<":CD:">> = iolist_to_binary(join(re:split("CD","^(A(*THEN)B|C(*THEN)D)",[]))),
+ <<"">> = iolist_to_binary(join(re:split("1234","^\\d*\\w{4}",[trim]))),
<<":">> = iolist_to_binary(join(re:split("1234","^\\d*\\w{4}",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("1234","^\\d*\\w{4}",[]))),
- <<"123">> = iolist_to_binary(join(re:split("123","^\\d*\\w{4}",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("1234","^\\d*\\w{4}",[]))),
+ <<"123">> = iolist_to_binary(join(re:split("123","^\\d*\\w{4}",[trim]))),
<<"123">> = iolist_to_binary(join(re:split("123","^\\d*\\w{4}",[{parts,
- 2}]))),
- <<"123">> = iolist_to_binary(join(re:split("123","^\\d*\\w{4}",[]))),
- <<"">> = iolist_to_binary(join(re:split("aaaa","^[^b]*\\w{4}",[trim]))),
+ 2}]))),
+ <<"123">> = iolist_to_binary(join(re:split("123","^\\d*\\w{4}",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaa","^[^b]*\\w{4}",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaa","^[^b]*\\w{4}",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaa","^[^b]*\\w{4}",[]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^[^b]*\\w{4}",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaa","^[^b]*\\w{4}",[]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^[^b]*\\w{4}",[trim]))),
<<"aaa">> = iolist_to_binary(join(re:split("aaa","^[^b]*\\w{4}",[{parts,
- 2}]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^[^b]*\\w{4}",[]))),
+ 2}]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^[^b]*\\w{4}",[]))),
<<"">> = iolist_to_binary(join(re:split("aaaa","^[^b]*\\w{4}",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaa","^[^b]*\\w{4}",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaa","^[^b]*\\w{4}",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaa","^[^b]*\\w{4}",[caseless]))),
<<"aaa">> = iolist_to_binary(join(re:split("aaa","^[^b]*\\w{4}",[caseless,
- trim]))),
+ trim]))),
<<"aaa">> = iolist_to_binary(join(re:split("aaa","^[^b]*\\w{4}",[caseless,
{parts,
- 2}]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^[^b]*\\w{4}",[caseless]))),
- <<"">> = iolist_to_binary(join(re:split("aaaa","^a*\\w{4}",[trim]))),
+ 2}]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^[^b]*\\w{4}",[caseless]))),
+ <<"">> = iolist_to_binary(join(re:split("aaaa","^a*\\w{4}",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaa","^a*\\w{4}",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaa","^a*\\w{4}",[]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^a*\\w{4}",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaa","^a*\\w{4}",[]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^a*\\w{4}",[trim]))),
<<"aaa">> = iolist_to_binary(join(re:split("aaa","^a*\\w{4}",[{parts,
- 2}]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^a*\\w{4}",[]))),
+ 2}]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^a*\\w{4}",[]))),
<<"">> = iolist_to_binary(join(re:split("aaaa","^a*\\w{4}",[caseless,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaa","^a*\\w{4}",[caseless,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaa","^a*\\w{4}",[caseless]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaa","^a*\\w{4}",[caseless]))),
<<"aaa">> = iolist_to_binary(join(re:split("aaa","^a*\\w{4}",[caseless,
- trim]))),
+ trim]))),
<<"aaa">> = iolist_to_binary(join(re:split("aaa","^a*\\w{4}",[caseless,
{parts,
- 2}]))),
- <<"aaa">> = iolist_to_binary(join(re:split("aaa","^a*\\w{4}",[caseless]))),
- <<":1:non-sp1:non-sp2">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[trim]))),
+ 2}]))),
+ <<"aaa">> = iolist_to_binary(join(re:split("aaa","^a*\\w{4}",[caseless]))),
+ <<":1:non-sp1:non-sp2">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[trim]))),
<<":1:non-sp1:non-sp2:">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[{parts,
- 2}]))),
- <<":1:non-sp1:non-sp2:">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[]))),
- <<"AZ">> = iolist_to_binary(join(re:split("AZ","^A\\xZ",[trim]))),
+ 2}]))),
+ <<":1:non-sp1:non-sp2:">> = iolist_to_binary(join(re:split("1 IN SOA non-sp1 non-sp2(","^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$",[]))),
+ <<"AZ">> = iolist_to_binary(join(re:split("AZ","^A\\xZ",[trim]))),
<<"AZ">> = iolist_to_binary(join(re:split("AZ","^A\\xZ",[{parts,
- 2}]))),
- <<"AZ">> = iolist_to_binary(join(re:split("AZ","^A\\xZ",[]))),
- <<"">> = iolist_to_binary(join(re:split("ASB","^A\\o{123}B",[trim]))),
+ 2}]))),
+ <<"AZ">> = iolist_to_binary(join(re:split("AZ","^A\\xZ",[]))),
+ <<"">> = iolist_to_binary(join(re:split("ASB","^A\\o{123}B",[trim]))),
<<":">> = iolist_to_binary(join(re:split("ASB","^A\\o{123}B",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("ASB","^A\\o{123}B",[]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("ASB","^A\\o{123}B",[]))),
<<"">> = iolist_to_binary(join(re:split("aaaab"," ^ a + + b $ ",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaab"," ^ a + + b $ ",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaab"," ^ a + + b $ ",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaab"," ^ a + + b $ ",[extended]))),
<<"">> = iolist_to_binary(join(re:split("aaaab"," ^ a + #comment
- + b $ ",[extended,trim]))),
+ + b $ ",[extended,trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaab"," ^ a + #comment
- + b $ ",[extended,{parts,2}]))),
+ + b $ ",[extended,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("aaaab"," ^ a + #comment
- + b $ ",[extended]))),
+ + b $ ",[extended]))),
<<"">> = iolist_to_binary(join(re:split("aaaab"," ^ a + #comment
#comment
- + b $ ",[extended,trim]))),
+ + b $ ",[extended,trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaab"," ^ a + #comment
#comment
- + b $ ",[extended,{parts,2}]))),
+ + b $ ",[extended,{parts,2}]))),
<<":">> = iolist_to_binary(join(re:split("aaaab"," ^ a + #comment
#comment
- + b $ ",[extended]))),
+ + b $ ",[extended]))),
ok.
run55() ->
<<"">> = iolist_to_binary(join(re:split("aaaab"," ^ (?> a + ) b $ ",[extended,
- trim]))),
+ trim]))),
<<":">> = iolist_to_binary(join(re:split("aaaab"," ^ (?> a + ) b $ ",[extended,
{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aaaab"," ^ (?> a + ) b $ ",[extended]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aaaab"," ^ (?> a + ) b $ ",[extended]))),
<<":aaaa">> = iolist_to_binary(join(re:split("aaaab"," ^ ( a + ) + + \\w $ ",[extended,
- trim]))),
+ trim]))),
<<":aaaa:">> = iolist_to_binary(join(re:split("aaaab"," ^ ( a + ) + + \\w $ ",[extended,
{parts,
- 2}]))),
- <<":aaaa:">> = iolist_to_binary(join(re:split("aaaab"," ^ ( a + ) + + \\w $ ",[extended]))),
- <<"acb">> = iolist_to_binary(join(re:split("acb","(?:x|(?:(xx|yy)+|x|x|x|x|x)|a|a|a)bc",[trim]))),
+ 2}]))),
+ <<":aaaa:">> = iolist_to_binary(join(re:split("aaaab"," ^ ( a + ) + + \\w $ ",[extended]))),
+ <<"acb">> = iolist_to_binary(join(re:split("acb","(?:x|(?:(xx|yy)+|x|x|x|x|x)|a|a|a)bc",[trim]))),
<<"acb">> = iolist_to_binary(join(re:split("acb","(?:x|(?:(xx|yy)+|x|x|x|x|x)|a|a|a)bc",[{parts,
- 2}]))),
- <<"acb">> = iolist_to_binary(join(re:split("acb","(?:x|(?:(xx|yy)+|x|x|x|x|x)|a|a|a)bc",[]))),
- <<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]*+|\\\"\\\")*+\\\")++",[trim]))),
+ 2}]))),
+ <<"acb">> = iolist_to_binary(join(re:split("acb","(?:x|(?:(xx|yy)+|x|x|x|x|x)|a|a|a)bc",[]))),
+ <<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]*+|\\\"\\\")*+\\\")++",[trim]))),
<<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]*+|\\\"\\\")*+\\\")++",[{parts,
- 2}]))),
- <<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]*+|\\\"\\\")*+\\\")++",[]))),
- <<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]++|\\\"\\\")*+\\\")++",[trim]))),
+ 2}]))),
+ <<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]*+|\\\"\\\")*+\\\")++",[]))),
+ <<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]++|\\\"\\\")*+\\\")++",[trim]))),
<<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]++|\\\"\\\")*+\\\")++",[{parts,
- 2}]))),
- <<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]++|\\\"\\\")*+\\\")++",[]))),
- <<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]++|\\\"\\\")++\\\")++",[trim]))),
+ 2}]))),
+ <<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]++|\\\"\\\")*+\\\")++",[]))),
+ <<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]++|\\\"\\\")++\\\")++",[trim]))),
<<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]++|\\\"\\\")++\\\")++",[{parts,
- 2}]))),
- <<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]++|\\\"\\\")++\\\")++",[]))),
- <<": AFTER ::\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A([^\\\"1]++|[\\\"2]([^\\\"3]*+|[\\\"4][\\\"5])*+[\\\"6])++",[trim]))),
+ 2}]))),
+ <<":\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A(?:[^\\\"]++|\\\"(?:[^\\\"]++|\\\"\\\")++\\\")++",[]))),
+ <<": AFTER ::\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A([^\\\"1]++|[\\\"2]([^\\\"3]*+|[\\\"4][\\\"5])*+[\\\"6])++",[trim]))),
<<": AFTER ::\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A([^\\\"1]++|[\\\"2]([^\\\"3]*+|[\\\"4][\\\"5])*+[\\\"6])++",[{parts,
- 2}]))),
- <<": AFTER ::\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A([^\\\"1]++|[\\\"2]([^\\\"3]*+|[\\\"4][\\\"5])*+[\\\"6])++",[]))),
- <<":t test">> = iolist_to_binary(join(re:split("test test","^\\w+(?>\\s*)(?<=\\w)",[trim]))),
+ 2}]))),
+ <<": AFTER ::\"NOT MATCHED">> = iolist_to_binary(join(re:split("NON QUOTED \"QUOT\"\"ED\" AFTER \"NOT MATCHED","\\A([^\\\"1]++|[\\\"2]([^\\\"3]*+|[\\\"4][\\\"5])*+[\\\"6])++",[]))),
+ <<":t test">> = iolist_to_binary(join(re:split("test test","^\\w+(?>\\s*)(?<=\\w)",[trim]))),
<<":t test">> = iolist_to_binary(join(re:split("test test","^\\w+(?>\\s*)(?<=\\w)",[{parts,
- 2}]))),
- <<":t test">> = iolist_to_binary(join(re:split("test test","^\\w+(?>\\s*)(?<=\\w)",[]))),
- <<":a">> = iolist_to_binary(join(re:split("acl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[trim]))),
+ 2}]))),
+ <<":t test">> = iolist_to_binary(join(re:split("test test","^\\w+(?>\\s*)(?<=\\w)",[]))),
+ <<":a">> = iolist_to_binary(join(re:split("acl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[trim]))),
<<":a::">> = iolist_to_binary(join(re:split("acl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[{parts,
- 2}]))),
- <<":a::">> = iolist_to_binary(join(re:split("acl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[]))),
- <<"::b">> = iolist_to_binary(join(re:split("bdl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[trim]))),
+ 2}]))),
+ <<":a::">> = iolist_to_binary(join(re:split("acl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[]))),
+ <<"::b">> = iolist_to_binary(join(re:split("bdl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[trim]))),
<<"::b:">> = iolist_to_binary(join(re:split("bdl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[{parts,
- 2}]))),
- <<"::b:">> = iolist_to_binary(join(re:split("bdl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[]))),
- <<"a">> = iolist_to_binary(join(re:split("adl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[trim]))),
+ 2}]))),
+ <<"::b:">> = iolist_to_binary(join(re:split("bdl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[]))),
+ <<"a">> = iolist_to_binary(join(re:split("adl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[trim]))),
<<"a:::">> = iolist_to_binary(join(re:split("adl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[{parts,
- 2}]))),
- <<"a:::">> = iolist_to_binary(join(re:split("adl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[]))),
- <<"bc">> = iolist_to_binary(join(re:split("bcl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[trim]))),
+ 2}]))),
+ <<"a:::">> = iolist_to_binary(join(re:split("adl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[]))),
+ <<"bc">> = iolist_to_binary(join(re:split("bcl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[trim]))),
<<"bc:::">> = iolist_to_binary(join(re:split("bcl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[{parts,
- 2}]))),
- <<"bc:::">> = iolist_to_binary(join(re:split("bcl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[]))),
- <<"">> = iolist_to_binary(join(re:split(" abc","\\sabc",[trim]))),
+ 2}]))),
+ <<"bc:::">> = iolist_to_binary(join(re:split("bcl","(?P<Name>a)?(?P<Name2>b)?(?(<Name>)c|d)*l",[]))),
+ <<"">> = iolist_to_binary(join(re:split(" abc","\\sabc",[trim]))),
<<":">> = iolist_to_binary(join(re:split(" abc","\\sabc",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split(" abc","\\sabc",[]))),
- <<"">> = iolist_to_binary(join(re:split("aa]]","[\\Qa]\\E]+",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split(" abc","\\sabc",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aa]]","[\\Qa]\\E]+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aa]]","[\\Qa]\\E]+",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aa]]","[\\Qa]\\E]+",[]))),
- <<"">> = iolist_to_binary(join(re:split("aa]]","[\\Q]a\\E]+",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aa]]","[\\Qa]\\E]+",[]))),
+ <<"">> = iolist_to_binary(join(re:split("aa]]","[\\Q]a\\E]+",[trim]))),
<<":">> = iolist_to_binary(join(re:split("aa]]","[\\Q]a\\E]+",[{parts,
- 2}]))),
- <<":">> = iolist_to_binary(join(re:split("aa]]","[\\Q]a\\E]+",[]))),
- <<"1::::::2::::::3::::::4:abcd:abcd">> = iolist_to_binary(join(re:split("1234abcd","(?:((abcd))|(((?:(?:(?:(?:abc|(?:abcdef))))b)abcdefghi)abc)|((*ACCEPT)))",[trim]))),
+ 2}]))),
+ <<":">> = iolist_to_binary(join(re:split("aa]]","[\\Q]a\\E]+",[]))),
+ <<"1::::::2::::::3::::::4:abcd:abcd">> = iolist_to_binary(join(re:split("1234abcd","(?:((abcd))|(((?:(?:(?:(?:abc|(?:abcdef))))b)abcdefghi)abc)|((*ACCEPT)))",[trim]))),
<<"1::::::234abcd">> = iolist_to_binary(join(re:split("1234abcd","(?:((abcd))|(((?:(?:(?:(?:abc|(?:abcdef))))b)abcdefghi)abc)|((*ACCEPT)))",[{parts,
- 2}]))),
- <<"1::::::2::::::3::::::4:abcd:abcd::::">> = iolist_to_binary(join(re:split("1234abcd","(?:((abcd))|(((?:(?:(?:(?:abc|(?:abcdef))))b)abcdefghi)abc)|((*ACCEPT)))",[]))),
+ 2}]))),
+ <<"1::::::2::::::3::::::4:abcd:abcd::::">> = iolist_to_binary(join(re:split("1234abcd","(?:((abcd))|(((?:(?:(?:(?:abc|(?:abcdef))))b)abcdefghi)abc)|((*ACCEPT)))",[]))),
ok.
run56() ->
- <<"b:a:c">> = iolist_to_binary(join(re:split("baaaaaaaaac","(?1)(?#?'){8}(a)",[trim]))),
+ <<"b:a:c">> = iolist_to_binary(join(re:split("baaaaaaaaac","(?1)(?#?'){8}(a)",[trim]))),
<<"b:a:c">> = iolist_to_binary(join(re:split("baaaaaaaaac","(?1)(?#?'){8}(a)",[{parts,
- 2}]))),
- <<"b:a:c">> = iolist_to_binary(join(re:split("baaaaaaaaac","(?1)(?#?'){8}(a)",[]))),
- <<"a::b::c::d">> = iolist_to_binary(join(re:split("abcd","(?|(\\k'Pm')|(?'Pm'))",[trim]))),
+ 2}]))),
+ <<"b:a:c">> = iolist_to_binary(join(re:split("baaaaaaaaac","(?1)(?#?'){8}(a)",[]))),
+ <<"a::b::c::d">> = iolist_to_binary(join(re:split("abcd","(?|(\\k'Pm')|(?'Pm'))",[trim]))),
<<"a::bcd">> = iolist_to_binary(join(re:split("abcd","(?|(\\k'Pm')|(?'Pm'))",[{parts,
- 2}]))),
- <<"a::b::c::d::">> = iolist_to_binary(join(re:split("abcd","(?|(\\k'Pm')|(?'Pm'))",[]))),
- <<" :Fred:099">> = iolist_to_binary(join(re:split(" Fred:099","(?=.*[A-Z])(?=.*[a-z])(?=.*[0-9])(?=.*[,;:])(?=.{8,16})(?!.*[\\s])",[trim]))),
+ 2}]))),
+ <<"a::b::c::d::">> = iolist_to_binary(join(re:split("abcd","(?|(\\k'Pm')|(?'Pm'))",[]))),
+ <<" :Fred:099">> = iolist_to_binary(join(re:split(" Fred:099","(?=.*[A-Z])(?=.*[a-z])(?=.*[0-9])(?=.*[,;:])(?=.{8,16})(?!.*[\\s])",[trim]))),
<<" :Fred:099">> = iolist_to_binary(join(re:split(" Fred:099","(?=.*[A-Z])(?=.*[a-z])(?=.*[0-9])(?=.*[,;:])(?=.{8,16})(?!.*[\\s])",[{parts,
- 2}]))),
- <<" :Fred:099">> = iolist_to_binary(join(re:split(" Fred:099","(?=.*[A-Z])(?=.*[a-z])(?=.*[0-9])(?=.*[,;:])(?=.{8,16})(?!.*[\\s])",[]))),
- <<" ">> = iolist_to_binary(join(re:split(" X","(?=.*X)X$",[trim]))),
+ 2}]))),
+ <<" :Fred:099">> = iolist_to_binary(join(re:split(" Fred:099","(?=.*[A-Z])(?=.*[a-z])(?=.*[0-9])(?=.*[,;:])(?=.{8,16})(?!.*[\\s])",[]))),
+ <<" ">> = iolist_to_binary(join(re:split(" X","(?=.*X)X$",[trim]))),
<<" :">> = iolist_to_binary(join(re:split(" X","(?=.*X)X$",[{parts,
- 2}]))),
- <<" :">> = iolist_to_binary(join(re:split(" X","(?=.*X)X$",[]))),
+ 2}]))),
+ <<" :">> = iolist_to_binary(join(re:split(" X","(?=.*X)X$",[]))),
+ <<">:::<">> = iolist_to_binary(join(re:split(">XXX<","X+(?#comment)?",[trim]))),
+ <<">:XX<">> = iolist_to_binary(join(re:split(">XXX<","X+(?#comment)?",[{parts,
+ 2}]))),
+ <<">:::<">> = iolist_to_binary(join(re:split(">XXX<","X+(?#comment)?",[]))),
+ <<":pokus">> = iolist_to_binary(join(re:split("pokus."," (?<word> \\w+ )* \\. ",[extended,
+ caseless,
+ trim]))),
+ <<":pokus:">> = iolist_to_binary(join(re:split("pokus."," (?<word> \\w+ )* \\. ",[extended,
+ caseless,
+ {parts,
+ 2}]))),
+ <<":pokus:">> = iolist_to_binary(join(re:split("pokus."," (?<word> \\w+ )* \\. ",[extended,
+ caseless]))),
+ <<"">> = iolist_to_binary(join(re:split("pokus.","(?(DEFINE) (?<word> \\w+ ) ) (?&word)* \\.",[extended,
+ caseless,
+ trim]))),
+ <<"::">> = iolist_to_binary(join(re:split("pokus.","(?(DEFINE) (?<word> \\w+ ) ) (?&word)* \\.",[extended,
+ caseless,
+ {parts,
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("pokus.","(?(DEFINE) (?<word> \\w+ ) ) (?&word)* \\.",[extended,
+ caseless]))),
+ <<"::pokus">> = iolist_to_binary(join(re:split("pokus.","(?(DEFINE) (?<word> \\w+ ) ) ( (?&word)* ) \\.",[extended,
+ caseless,
+ trim]))),
+ <<"::pokus:">> = iolist_to_binary(join(re:split("pokus.","(?(DEFINE) (?<word> \\w+ ) ) ( (?&word)* ) \\.",[extended,
+ caseless,
+ {parts,
+ 2}]))),
+ <<"::pokus:">> = iolist_to_binary(join(re:split("pokus.","(?(DEFINE) (?<word> \\w+ ) ) ( (?&word)* ) \\.",[extended,
+ caseless]))),
+ <<"">> = iolist_to_binary(join(re:split("pokus.","(?&word)* (?(DEFINE) (?<word> \\w+ ) ) \\.",[extended,
+ caseless,
+ trim]))),
+ <<"::">> = iolist_to_binary(join(re:split("pokus.","(?&word)* (?(DEFINE) (?<word> \\w+ ) ) \\.",[extended,
+ caseless,
+ {parts,
+ 2}]))),
+ <<"::">> = iolist_to_binary(join(re:split("pokus.","(?&word)* (?(DEFINE) (?<word> \\w+ ) ) \\.",[extended,
+ caseless]))),
+ <<":hokus">> = iolist_to_binary(join(re:split("pokus.hokus","(?&word)* \\. (?<word> \\w+ )",[extended,
+ caseless,
+ trim]))),
+ <<":hokus:">> = iolist_to_binary(join(re:split("pokus.hokus","(?&word)* \\. (?<word> \\w+ )",[extended,
+ caseless,
+ {parts,
+ 2}]))),
+ <<":hokus:">> = iolist_to_binary(join(re:split("pokus.hokus","(?&word)* \\. (?<word> \\w+ )",[extended,
+ caseless]))),
ok.
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index 22136d687c..cdb6031b07 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2004-2018. All Rights Reserved.
+%% Copyright Ericsson AB 2004-2019. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -2591,7 +2591,7 @@ otp_7184(Config) when is_list(Config) ->
otp_7232(Config) when is_list(Config) ->
Info = <<"qlc:info(qlc:sort(qlc:q([X || X <- [55296,56296]]), "
"{order, fun(A,B)-> A>B end})).">>,
- "qlc:sort([55296,56296],\n"
+ "qlc:sort([55296, 56296],\n"
" [{order,\n"
" fun(A, B) ->\n"
" A > B\n"
@@ -2752,7 +2752,7 @@ otp_10302(Config) when is_list(Config) ->
h().">>,
"ok.\n\"\x{400}\"\nA = \"\x{400}\".\nok.\n"
- "1: io:setopts([{encoding,utf8}])\n-> ok.\n"
+ "1: io:setopts([{encoding, utf8}])\n-> ok.\n"
"2: A = [1024] = \"\x{400}\"\n-> \"\x{400}\"\n"
"3: b()\n-> ok.\nok.\n" = t({Node,Test4}),
diff --git a/lib/stdlib/test/stdlib.spec b/lib/stdlib/test/stdlib.spec
index 9c625091a8..bf64eae2c7 100644
--- a/lib/stdlib/test/stdlib.spec
+++ b/lib/stdlib/test/stdlib.spec
@@ -1,4 +1,7 @@
{suites,"../stdlib_test",all}.
{skip_groups,"../stdlib_test",stdlib_bench_SUITE,
- [base64,gen_server,gen_statem,unicode],
+ [binary,base64,gen_server,gen_statem,unicode],
+ "Benchmark only"}.
+{skip_groups,"../stdlib_test",ets_SUITE,
+ [benchmark],
"Benchmark only"}.
diff --git a/lib/stdlib/test/stdlib_bench.spec b/lib/stdlib/test/stdlib_bench.spec
index 7a0da811a0..6d665f22b6 100644
--- a/lib/stdlib/test/stdlib_bench.spec
+++ b/lib/stdlib/test/stdlib_bench.spec
@@ -8,3 +8,4 @@
{skip_groups,"../stdlib_test",stdlib_bench_SUITE,
[gen_server_comparison,gen_statem_comparison],
"Not a benchmark"}.
+{groups,"../stdlib_test",ets_SUITE,[benchmark]}.
diff --git a/lib/stdlib/test/stdlib_bench_SUITE.erl b/lib/stdlib/test/stdlib_bench_SUITE.erl
index 2364e8376f..3456442088 100644
--- a/lib/stdlib/test/stdlib_bench_SUITE.erl
+++ b/lib/stdlib/test/stdlib_bench_SUITE.erl
@@ -29,7 +29,7 @@ suite() -> [{ct_hooks,[{ts_install_cth,[{nodenames,2}]}]}].
all() ->
- [{group,unicode},{group,base64},
+ [{group,unicode},{group,base64},{group,binary},
{group,gen_server},{group,gen_statem},
{group,gen_server_comparison},{group,gen_statem_comparison}].
@@ -38,6 +38,13 @@ groups() ->
[norm_nfc_list, norm_nfc_deep_l, norm_nfc_binary,
string_lexemes_list, string_lexemes_binary
]},
+ %% Only run 1 binary match repeat as it is very slow pre OTP-22.
+ %% The results seem to be stable enough anyway
+ {binary, [{repeat, 1}],
+ [match_single_pattern_no_match,
+ matches_single_pattern_no_match,
+ matches_single_pattern_eventual_match,
+ matches_single_pattern_frequent_match]},
{base64,[{repeat,5}],
[decode_binary, decode_binary_to_string,
decode_list, decode_list_to_string,
@@ -60,9 +67,9 @@ cases(gen_server) ->
[simple, simple_timer, simple_mon, simple_timer_mon,
generic, generic_timer];
cases(gen_statem) ->
- [generic, generic_fsm, generic_fsm_transit,
- generic_statem, generic_statem_transit,
- generic_statem_complex].
+ [generic, generic_log, generic_log100, generic_fsm, generic_fsm_transit,
+ generic_statem, generic_statem_log, generic_statem_log100,
+ generic_statem_transit, generic_statem_complex].
init_per_group(gen_server, Config) ->
compile_servers(Config),
@@ -157,41 +164,59 @@ norm_data(Config) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+match_single_pattern_no_match(_Config) ->
+ Binary = binary:copy(<<"ugbcfuysabfuqyfikgfsdalpaskfhgjsdgfjwsalp">>, 1000000),
+ comment(test(100, binary, match, [Binary, <<"o">>])).
+
+matches_single_pattern_no_match(_Config) ->
+ Binary = binary:copy(<<"ugbcfuysabfuqyfikgfsdalpaskfhgjsdgfjwsalp">>, 1000000),
+ comment(test(100, binary, matches, [Binary, <<"o">>])).
+
+matches_single_pattern_eventual_match(_Config) ->
+ Binary = binary:copy(<<"ugbcfuysabfuqyfikgfsdalpaskfhgjsdgfjwsal\n">>, 1000000),
+ comment(test(100, binary, matches, [Binary, <<"\n">>])).
+
+matches_single_pattern_frequent_match(_Config) ->
+ Binary = binary:copy(<<"abc\n">>, 1000000),
+ comment(test(100, binary, matches, [Binary, <<"abc">>])).
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
decode_binary(_Config) ->
- comment(test(decode, encoded_binary())).
+ comment(test(base64, decode, [encoded_binary()])).
decode_binary_to_string(_Config) ->
- comment(test(decode_to_string, encoded_binary())).
+ comment(test(base64, decode_to_string, [encoded_binary()])).
decode_list(_Config) ->
- comment(test(decode, encoded_list())).
+ comment(test(base64, decode, [encoded_list()])).
decode_list_to_string(_Config) ->
- comment(test(decode_to_string, encoded_list())).
+ comment(test(base64, decode_to_string, [encoded_list()])).
encode_binary(_Config) ->
- comment(test(encode, binary())).
+ comment(test(base64, encode, [binary()])).
encode_binary_to_string(_Config) ->
- comment(test(encode_to_string, binary())).
+ comment(test(base64, encode_to_string, [binary()])).
encode_list(_Config) ->
- comment(test(encode, list())).
+ comment(test(base64, encode, [list()])).
encode_list_to_string(_Config) ->
- comment(test(encode_to_string, list())).
+ comment(test(base64, encode_to_string, [list()])).
mime_binary_decode(_Config) ->
- comment(test(mime_decode, encoded_binary())).
+ comment(test(base64, mime_decode, [encoded_binary()])).
mime_binary_decode_to_string(_Config) ->
- comment(test(mime_decode_to_string, encoded_binary())).
+ comment(test(base64, mime_decode_to_string, [encoded_binary()])).
mime_list_decode(_Config) ->
- comment(test(mime_decode, encoded_list())).
+ comment(test(base64, mime_decode, [encoded_list()])).
mime_list_decode_to_string(_Config) ->
- comment(test(mime_decode_to_string, encoded_list())).
+ comment(test(base64, mime_decode_to_string, [encoded_list()])).
-define(SIZE, 10000).
-define(N, 1000).
@@ -209,15 +234,17 @@ binary() ->
list() ->
random_byte_list(?SIZE).
-test(Func, Data) ->
- F = fun() -> loop(?N, Func, Data) end,
+test(Mod, Fun, Args) ->
+ test(?N, Mod, Fun, Args).
+test(Iter, Mod, Fun, Args) ->
+ F = fun() -> loop(Iter, Mod, Fun, Args) end,
{Time, ok} = timer:tc(fun() -> lspawn(F) end),
- report_base64(Time).
+ report_mfa(Iter, Time, Mod).
-loop(0, _F, _D) -> garbage_collect(), ok;
-loop(N, F, D) ->
- _ = base64:F(D),
- loop(N - 1, F, D).
+loop(0, _M, _F, _A) -> garbage_collect(), ok;
+loop(N, M, F, A) ->
+ _ = apply(M, F, A),
+ loop(N - 1, M, F, A).
lspawn(Fun) ->
{Pid, Ref} = spawn_monitor(fun() -> exit(Fun()) end),
@@ -225,10 +252,10 @@ lspawn(Fun) ->
{'DOWN', Ref, process, Pid, Rep} -> Rep
end.
-report_base64(Time) ->
- Tps = round((?N*1000000)/Time),
+report_mfa(Iter, Time, Mod) ->
+ Tps = round((Iter*1000000)/Time),
ct_event:notify(#event{name = benchmark_data,
- data = [{suite, "stdlib_base64"},
+ data = [{suite, "stdlib_" ++ atom_to_list(Mod)},
{value, Tps}]}),
Tps.
@@ -267,12 +294,24 @@ simple_timer_mon(Config) when is_list(Config) ->
generic(Config) when is_list(Config) ->
comment(do_tests(generic, single_small, Config)).
+generic_log(Config) when is_list(Config) ->
+ comment(do_tests(generic_log, single_small, Config)).
+
+generic_log100(Config) when is_list(Config) ->
+ comment(do_tests(generic_log100, single_small, Config)).
+
generic_timer(Config) when is_list(Config) ->
comment(do_tests(generic_timer, single_small, Config)).
generic_statem(Config) when is_list(Config) ->
comment(do_tests(generic_statem, single_small, Config)).
+generic_statem_log(Config) when is_list(Config) ->
+ comment(do_tests(generic_statem_log, single_small, Config)).
+
+generic_statem_log100(Config) when is_list(Config) ->
+ comment(do_tests(generic_statem_log100, single_small, Config)).
+
generic_statem_transit(Config) when is_list(Config) ->
comment(do_tests(generic_statem_transit, single_small, Config)).
@@ -344,9 +383,9 @@ norm(T, Ref) ->
do_tests(Test, ParamSet, Config) ->
BenchmarkSuite = ?config(benchmark_suite, Config),
- {Client, ServerMod} = bench(Test),
+ {Client, ServerMod, ServerArg} = bench(Test),
{Parallelism, Message} = bench_params(ParamSet),
- Fun = create_clients(Message, ServerMod, Client, Parallelism),
+ Fun = create_clients(Message, ServerMod, ServerArg, Client, Parallelism),
{TotalLoops, AllPidTime} = run_test(Fun),
try ?CALLS_PER_LOOP * round((1000 * TotalLoops) / AllPidTime) of
PerSecond ->
@@ -461,27 +500,35 @@ generic_fsm_transit_client(N, M, P) ->
generic_fsm_transit_client(N+1, M, P).
bench(simple) ->
- {fun simple_client/3, simple_server};
+ {fun simple_client/3, simple_server, term};
bench(simple_timer) ->
- {fun simple_client_timer/3, simple_server_timer};
+ {fun simple_client_timer/3, simple_server_timer, term};
bench(simple_mon) ->
- {fun simple_client_mon/3, simple_server_mon};
+ {fun simple_client_mon/3, simple_server_mon, term};
bench(simple_timer_mon) ->
- {fun simple_client_timer_mon/3, simple_server_timer_mon};
+ {fun simple_client_timer_mon/3, simple_server_timer_mon, term};
bench(generic) ->
- {fun generic_client/3, generic_server};
+ {fun generic_client/3, generic_server, [term]};
+bench(generic_log) ->
+ {fun generic_client/3, generic_server, [term,{debug,[log]}]};
+bench(generic_log100) ->
+ {fun generic_client/3, generic_server, [term,{debug,[{log,100}]}]};
bench(generic_timer) ->
- {fun generic_timer_client/3, generic_server_timer};
+ {fun generic_timer_client/3, generic_server_timer, term};
bench(generic_statem) ->
- {fun generic_statem_client/3, generic_statem};
+ {fun generic_statem_client/3, generic_statem, [term]};
+bench(generic_statem_log) ->
+ {fun generic_statem_client/3, generic_statem, [term,{debug,[log]}]};
+bench(generic_statem_log100) ->
+ {fun generic_statem_client/3, generic_statem, [term,{debug,[{log,100}]}]};
bench(generic_statem_transit) ->
- {fun generic_statem_transit_client/3, generic_statem};
+ {fun generic_statem_transit_client/3, generic_statem, [term]};
bench(generic_statem_complex) ->
- {fun generic_statem_complex_client/3, generic_statem_complex};
+ {fun generic_statem_complex_client/3, generic_statem_complex, term};
bench(generic_fsm) ->
- {fun generic_fsm_client/3, generic_fsm};
+ {fun generic_fsm_client/3, generic_fsm, term};
bench(generic_fsm_transit) ->
- {fun generic_fsm_transit_client/3, generic_fsm}.
+ {fun generic_fsm_transit_client/3, generic_fsm, term}.
%% -> {Parallelism, MessageTerm}
bench_params(single_small) -> {1, small()};
@@ -509,10 +556,9 @@ parallelism() ->
_ -> 1
end.
-create_clients(M, ServerMod, Client, Parallel) ->
+create_clients(M, ServerMod, ServerArg, Client, Parallel) ->
fun() ->
- State = term,
- ServerPid = ServerMod:start(State),
+ ServerPid = ServerMod:start(ServerArg),
PidRefs = [spawn_monitor(fun() -> Client(0, M, ServerPid) end) ||
_ <- lists:seq(1, Parallel)],
timer:sleep(?MAX_TIME),
diff --git a/lib/stdlib/test/stdlib_bench_SUITE_data/generic_fsm.erl b/lib/stdlib/test/stdlib_bench_SUITE_data/generic_fsm.erl
index 50f7df7a2a..1abd9b1f2f 100644
--- a/lib/stdlib/test/stdlib_bench_SUITE_data/generic_fsm.erl
+++ b/lib/stdlib/test/stdlib_bench_SUITE_data/generic_fsm.erl
@@ -24,7 +24,7 @@
-export([init/1, terminate/3]).
-export([state1/3, state2/3]).
--behaivour(gen_fsm).
+-behaviour(gen_fsm).
%% API
diff --git a/lib/stdlib/test/stdlib_bench_SUITE_data/generic_server.erl b/lib/stdlib/test/stdlib_bench_SUITE_data/generic_server.erl
index abd61dcdef..3707d00dee 100644
--- a/lib/stdlib/test/stdlib_bench_SUITE_data/generic_server.erl
+++ b/lib/stdlib/test/stdlib_bench_SUITE_data/generic_server.erl
@@ -8,8 +8,8 @@
-define(GEN_SERVER, gen_server).
-start(State) ->
- {ok, Pid} = ?GEN_SERVER:start(?MODULE, State, []),
+start([State|Opts]) ->
+ {ok, Pid} = ?GEN_SERVER:start(?MODULE, State, Opts),
Pid.
init(State) ->
diff --git a/lib/stdlib/test/stdlib_bench_SUITE_data/generic_statem.erl b/lib/stdlib/test/stdlib_bench_SUITE_data/generic_statem.erl
index 2e0491f060..b106619568 100644
--- a/lib/stdlib/test/stdlib_bench_SUITE_data/generic_statem.erl
+++ b/lib/stdlib/test/stdlib_bench_SUITE_data/generic_statem.erl
@@ -28,8 +28,8 @@
%% API
-start(Data) ->
- {ok, Pid} = gen_statem:start(?MODULE, Data, []),
+start([Data|Opts]) ->
+ {ok, Pid} = gen_statem:start(?MODULE, Data, Opts),
Pid.
stop(P) ->
@@ -52,7 +52,9 @@ init(Data) ->
state1({call, From}, {reply, M}, Data) ->
{keep_state, Data, {reply, From, M}};
state1({call, From}, {transit, M}, Data) ->
- {next_state, state2, Data, {reply, From, M}}.
+ {next_state, state2, Data,
+ [{reply, From, M},{state_timeout,5000,5000}]}.
state2({call, From}, {transit, M}, Data) ->
- {next_state, state1, Data, {reply, From, M}}.
+ {next_state, state1, Data,
+ [{reply, From, M},{state_timeout,5000,5000}]}.
diff --git a/lib/stdlib/test/string_SUITE.erl b/lib/stdlib/test/string_SUITE.erl
index 251e09121c..c9aadd7f10 100644
--- a/lib/stdlib/test/string_SUITE.erl
+++ b/lib/stdlib/test/string_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2004-2018. All Rights Reserved.
+%% Copyright Ericsson AB 2004-2019. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -103,6 +103,15 @@ debug() ->
test(?LINE,?FUNCTION_NAME,B,C,D, false),
test(?LINE,?FUNCTION_NAME,hd(C),[B|tl(C)],D, false)).
+-define(TRY(Exp),
+ fun() ->
+ try Exp
+ catch _E:Reason:_ST ->
+ %% io:format("~p:~w: ~p: ~.0p ~p~n",
+ %% [?FUNCTION_NAME, ?LINE,_E,Reason, hd(_ST)]),
+ {'EXIT', Reason}
+ end
+ end()).
is_empty(_) ->
?TEST("", [], true),
@@ -126,6 +135,10 @@ length(_) ->
?TEST(["abc"|<<"abc">>], [], 6),
?TEST(["abc",["def"]], [], 6),
?TEST([<<97/utf8, 778/utf8, 98/utf8>>, [776,111,776]], [], 3), %% åäö in nfd
+
+ InvalidUTF8 = <<192,192>>,
+ {'EXIT', {badarg, _}} = ?TRY(string:length(InvalidUTF8)),
+ {'EXIT', {badarg, _}} = ?TRY(string:length(<<$a, InvalidUTF8/binary, $z>>)),
ok.
equal(_) ->
@@ -226,6 +239,8 @@ to_graphemes(_) ->
true = erlang:length(GCs) =:= erlang:length(string:to_graphemes(NFD)),
true = erlang:length(GCs) =:=
erlang:length(string:to_graphemes(unicode:characters_to_nfc_list(String))),
+
+ {'EXIT', {badarg, _}} = ?TRY(string:to_graphemes(<<$a,192,192,$z>>)),
ok.
reverse(_) ->
@@ -238,6 +253,11 @@ reverse(_) ->
?TEST(Str2, [], lists:reverse(Str2)),
?TEST(Str3, [], lists:reverse(Str3)),
true = string:reverse(Str3) =:= lists:reverse(string:to_graphemes(Str3)),
+
+ InvalidUTF8 = <<192,192>>,
+ {'EXIT', {badarg, _}} = ?TRY(string:reverse(InvalidUTF8)),
+ {'EXIT', {badarg, _}} = ?TRY(string:reverse(<<$a, InvalidUTF8/binary, $z>>)),
+
ok.
slice(_) ->
@@ -258,6 +278,14 @@ slice(_) ->
?TEST([<<"aå"/utf8>>,"äöbcd"], [3,3], "öbc"),
?TEST([<<"aåä"/utf8>>,"öbcd"], [3,10], "öbcd"),
+ InvalidUTF8 = <<192,192>>,
+ [$b, $c|InvalidUTF8] = string:slice(["abc", InvalidUTF8], 1),
+ InvalidUTF8 = string:slice(["abc", InvalidUTF8], 3),
+ {'EXIT', {badarg, _}} = ?TRY(string:slice(["abc", InvalidUTF8], 1, 5)),
+ BadUtf8 = <<$a, InvalidUTF8/binary, "teststring">>,
+ {'EXIT', {badarg, _}} = ?TRY(string:slice(BadUtf8, 2)),
+ {'EXIT', {badarg, _}} = ?TRY(string:slice(BadUtf8, 1, 5)),
+ {'EXIT', {badarg, _}} = ?TRY(string:slice(BadUtf8, 0, 5)),
ok.
pad(_) ->
@@ -270,6 +298,10 @@ pad(_) ->
?TEST(Str, [10, trailing, $.], "Hallå....."),
?TEST(Str++["f"], [10, trailing, $.], "Hallåf...."),
?TEST(Str++[" flåwer"], [10, trailing, $.], "Hallå flåwer"),
+
+ InvalidUTF8 = <<192,192>>,
+ {'EXIT', {badarg, _}} = ?TRY(string:pad(InvalidUTF8, 10, both, $.)),
+ {'EXIT', {badarg, _}} = ?TRY(string:pad(<<$a, InvalidUTF8/binary, $z>>, 10, both, $.)),
ok.
trim(_) ->
@@ -300,6 +332,11 @@ trim(_) ->
?TEST([[<<"!v">>|<<204,128,$v,204,129>>]],[trailing, [[$v,769]]], [$!,$v,768]),
?TEST([[[<<"v">>|<<204,129,118,204,128,118>>],769,118,769]], [trailing, [[118,769]]], [$v,769,$v,768]),
?TEST([<<"vv">>|<<204,128,118,204,128>>], [trailing, [[118,768]]], "v"),
+
+ InvalidUTF8 = <<192,192>>,
+ {'EXIT', {badarg, _}} = ?TRY(string:trim(InvalidUTF8, both, "az")),
+ %% Not checked (using binary search)
+ %% {'EXIT', {badarg, _}} = ?TRY(string:trim(<<$a, $b, InvalidUTF8/binary, $z>>, both, "az")),
ok.
chomp(_) ->
@@ -400,6 +437,13 @@ take(_) ->
?TEST([<<"e">>,778,"åäöe", <<778/utf8>>, $e, 779], [[[$e,778]], true, trailing],
{[$e,778]++"åäöe"++[778], [$e,779]}),
+ InvalidUTF8 = <<192,192>>,
+ {'EXIT', {badarg, _}} = ?TRY(string:take(InvalidUTF8, [$.], false, leading)),
+ %% Not checked (using binary search)
+ %% {'EXIT', {badarg, _}} = ?TRY(string:take(InvalidUTF8, [$.], true, leading)),
+ %% {'EXIT', {badarg, _}} = ?TRY(string:take(InvalidUTF8, [$.], false, trailing)),
+ {'EXIT', {badarg, _}} = ?TRY(string:take(InvalidUTF8, [$.], true, trailing)),
+
ok.
@@ -416,6 +460,11 @@ uppercase(_) ->
?TEST("ljLJ", [], "LJLJ"),
?TEST("LJlj", [], "LJLJ"),
?TEST("ß sharp s", [], "SS SHARP S"),
+
+ InvalidUTF8 = <<192,192>>,
+ {'EXIT', {badarg, _}} = ?TRY(string:uppercase(InvalidUTF8)),
+ {'EXIT', {badarg, _}} = ?TRY(string:uppercase(<<$a, InvalidUTF8/binary, $z>>)),
+
ok.
lowercase(_) ->
@@ -429,6 +478,10 @@ lowercase(_) ->
?TEST(["Mic",<<"HAŁ"/utf8>>], [], "michał"),
?TEST("ß SHARP S", [], "ß sharp s"),
?TEST("İ I WITH DOT ABOVE", [], "i̇ i with dot above"),
+
+ InvalidUTF8 = <<192,192>>,
+ {'EXIT', {badarg, _}} = ?TRY(string:lowercase(InvalidUTF8)),
+ {'EXIT', {badarg, _}} = ?TRY(string:lowercase(<<$a, InvalidUTF8/binary, $z>>)),
ok.
titlecase(_) ->
@@ -442,6 +495,10 @@ titlecase(_) ->
?TEST("ljLJ", [], "LjLJ"),
?TEST("LJlj", [], "Ljlj"),
?TEST("ß sharp s", [], "Ss sharp s"),
+
+ InvalidUTF8 = <<192,192>>,
+ {'EXIT', {badarg, _}} = ?TRY(string:titlecase(InvalidUTF8)),
+ <<$A, _/binary>> = ?TRY(string:titlecase(<<$a, InvalidUTF8/binary, $z>>)),
ok.
casefold(_) ->
@@ -456,6 +513,10 @@ casefold(_) ->
?TEST("ß SHARP S", [], "ss sharp s"),
?TEST("ẞ SHARP S", [], "ss sharp s"),
?TEST("İ I WITH DOT ABOVE", [], "i̇ i with dot above"),
+
+ InvalidUTF8 = <<192,192>>,
+ {'EXIT', {badarg, _}} = ?TRY(string:casefold(InvalidUTF8)),
+ {'EXIT', {badarg, _}} = ?TRY(string:casefold(<<$a, InvalidUTF8/binary, $z>>)),
ok.
@@ -740,7 +801,7 @@ meas(Config) ->
_ -> % No scaling, run at most 1.5 min
Tester = spawn(Exec),
receive {test_done, Tester} -> ok
- after 90000 ->
+ after 118000 ->
io:format("Timelimit reached stopping~n",[]),
exit(Tester, die)
end,
@@ -754,19 +815,22 @@ do_measure(DataDir) ->
io:format("~p~n",[byte_size(Bin)]),
Do = fun(Name, Func, Mode) ->
{N, Mean, Stddev, _} = time_func(Func, Mode, Bin, 20),
- io:format("~15w ~6w ~6.2fms ±~5.2fms #~.2w gc included~n",
+ io:format("~15w ~15w ~8.2fms ±~6.2fms #~.2w gc included~n",
[Name, Mode, Mean/1000, Stddev/1000, N])
end,
Do2 = fun(Name, Func, Mode) ->
{N, Mean, Stddev, _} = time_func(Func, binary, <<>>, 20),
- io:format("~15w ~6w ~6.2fms ±~5.2fms #~.2w gc included~n",
+ io:format("~15w ~15w ~8.2fms ±~6.2fms #~.2w gc included~n",
[Name, Mode, Mean/1000, Stddev/1000, N])
end,
+ %% lefty_list means a list balanced to the left, like
+ %% [[[30],31],32]. Only some functions check such lists.
+ Modes = [list, lefty_list, binary, {many_lists,1}, {many_lists, 4}],
io:format("----------------------~n"),
Do(old_tokens, fun(Str) -> string:tokens(Str, [$\n,$\r]) end, list),
Tokens = {lexemes, fun(Str) -> string:lexemes(Str, [$\n,$\r]) end},
- [Do(Name,Fun,Mode) || {Name,Fun} <- [Tokens], Mode <- [list, binary]],
+ [Do(Name,Fun,Mode) || {Name,Fun} <- [Tokens], Mode <- Modes],
S0 = "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxy.....",
S0B = <<"xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxy.....">>,
@@ -824,17 +888,17 @@ do_measure(DataDir) ->
io:format("--~n",[]),
NthTokens = {nth_lexemes, fun(Str) -> string:nth_lexeme(Str, 18000, [$\n,$\r]) end},
- [Do(Name,Fun,Mode) || {Name,Fun} <- [NthTokens], Mode <- [list, binary]],
+ [Do(Name,Fun,Mode) || {Name,Fun} <- [NthTokens], Mode <- Modes],
Do2(take_t, repeat(fun() -> string:take(S0, [$.,$y], false, trailing) end), list),
Do2(take_t, repeat(fun() -> string:take(S0B, [$.,$y], false, trailing) end), binary),
Do2(take_tc, repeat(fun() -> string:take(S0, [$x], true, trailing) end), list),
Do2(take_tc, repeat(fun() -> string:take(S0B, [$x], true, trailing) end), binary),
Length = {length, fun(Str) -> string:length(Str) end},
- [Do(Name,Fun,Mode) || {Name,Fun} <- [Length], Mode <- [list, binary]],
+ [Do(Name,Fun,Mode) || {Name,Fun} <- [Length], Mode <- Modes],
Reverse = {reverse, fun(Str) -> string:reverse(Str) end},
- [Do(Name,Fun,Mode) || {Name,Fun} <- [Reverse], Mode <- [list, binary]],
+ [Do(Name,Fun,Mode) || {Name,Fun} <- [Reverse], Mode <- Modes],
ok.
@@ -1064,7 +1128,33 @@ time_func(N,Sum,SumSq, _, _, Res, _) ->
{N, Mean, Stdev, Res}.
mode(binary, Bin) -> Bin;
-mode(list, Bin) -> unicode:characters_to_list(Bin).
+mode(list, Bin) -> unicode:characters_to_list(Bin);
+mode(lefty_list, Bin) ->
+ L = unicode:characters_to_list(Bin),
+ to_left(L);
+mode({many_lists, N}, Bin) ->
+ group(unicode:characters_to_list(Bin), N).
+
+group([], _N) ->
+ [];
+group(L, N) ->
+ try lists:split(N, L) of
+ {L1, L2} ->
+ [L1 | group(L2, N)]
+ catch
+ _:_ ->
+ [L]
+ end.
+
+to_left([]) ->
+ [];
+to_left([H|L]) ->
+ to_left([H], L).
+
+to_left(V, []) ->
+ V;
+to_left(V, [H|L]) ->
+ to_left([V,H], L).
%%
%% Old string lists Test cases starts here.
diff --git a/lib/stdlib/test/unicode_util_SUITE.erl b/lib/stdlib/test/unicode_util_SUITE.erl
index 044b4e5834..6f55f204f4 100644
--- a/lib/stdlib/test/unicode_util_SUITE.erl
+++ b/lib/stdlib/test/unicode_util_SUITE.erl
@@ -428,7 +428,15 @@ mode(deep_l, Bin) -> [unicode:characters_to_list(Bin)].
fetch(Str, F) ->
case F(Str) of
[] -> [];
- [CP|R] -> [CP|fetch(R,F)]
+ [CP|R] ->
+ %% If input is a binary R should be binary
+ if is_binary(Str) == false -> ok;
+ is_binary(R); R =:= [] -> ok;
+ true ->
+ io:format("Char: ~tc Tail:~tP~n", [CP,R,10]),
+ exit({bug, F})
+ end,
+ [CP|fetch(R,F)]
end.
%% *Test.txt file helpers
diff --git a/lib/stdlib/test/unicode_util_SUITE_data/GraphemeBreakTest.txt b/lib/stdlib/test/unicode_util_SUITE_data/GraphemeBreakTest.txt
index d7d8f90de0..6847953c23 100644
--- a/lib/stdlib/test/unicode_util_SUITE_data/GraphemeBreakTest.txt
+++ b/lib/stdlib/test/unicode_util_SUITE_data/GraphemeBreakTest.txt
@@ -1,6 +1,6 @@
-# GraphemeBreakTest-10.0.0.txt
-# Date: 2017-04-14, 05:40:29 GMT
-# © 2017 Unicode®, Inc.
+# GraphemeBreakTest-11.0.0.txt
+# Date: 2018-03-18, 13:30:33 GMT
+# © 2018 Unicode®, Inc.
# Unicode and the Unicode Logo are registered trademarks of Unicode, Inc. in the U.S. and other countries.
# For terms of use, see http://www.unicode.org/terms_of_use.html
#
@@ -23,828 +23,678 @@
# These samples may be extended or changed in the future.
#
÷ 0020 ÷ 0020 ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 0020 × 0308 ÷ 0020 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 0020 × 0308 ÷ 0020 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ 0020 ÷ 000D ÷ # ÷ [0.2] SPACE (Other) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 0020 × 0308 ÷ 000D ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 0020 × 0308 ÷ 000D ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
÷ 0020 ÷ 000A ÷ # ÷ [0.2] SPACE (Other) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 0020 × 0308 ÷ 000A ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 0020 × 0308 ÷ 000A ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
÷ 0020 ÷ 0001 ÷ # ÷ [0.2] SPACE (Other) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 0020 × 0308 ÷ 0001 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 0020 × 0300 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 0020 × 0308 × 0300 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
+÷ 0020 × 0308 ÷ 0001 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 0020 × 034F ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 0020 × 0308 × 034F ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 0020 ÷ 1F1E6 ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 0020 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
÷ 0020 ÷ 0600 ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 0020 × 0308 ÷ 0600 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 0020 × 0308 ÷ 0600 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
÷ 0020 × 0903 ÷ # ÷ [0.2] SPACE (Other) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 0020 × 0308 × 0903 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 0020 × 0308 × 0903 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
÷ 0020 ÷ 1100 ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 0020 × 0308 ÷ 1100 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 0020 × 0308 ÷ 1100 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ 0020 ÷ 1160 ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 0020 × 0308 ÷ 1160 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 0020 × 0308 ÷ 1160 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
÷ 0020 ÷ 11A8 ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 0020 × 0308 ÷ 11A8 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 0020 × 0308 ÷ 11A8 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
÷ 0020 ÷ AC00 ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 0020 × 0308 ÷ AC00 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 0020 × 0308 ÷ AC00 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
÷ 0020 ÷ AC01 ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 0020 × 0308 ÷ AC01 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 0020 ÷ 1F1E6 ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 0020 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 0020 ÷ 261D ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 0020 × 0308 ÷ 261D ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 0020 ÷ 1F3FB ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 0020 × 0308 ÷ 1F3FB ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 0020 × 200D ÷ # ÷ [0.2] SPACE (Other) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 0020 × 0308 × 200D ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 0020 ÷ 2640 ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 0020 × 0308 ÷ 2640 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 0020 ÷ 1F466 ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 0020 × 0308 ÷ 1F466 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ 0020 × 0308 ÷ AC01 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 0020 ÷ 231A ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 0020 × 0308 ÷ 231A ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 0020 × 0300 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0020 × 0308 × 0300 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0020 × 200D ÷ # ÷ [0.2] SPACE (Other) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 0020 × 0308 × 200D ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
÷ 0020 ÷ 0378 ÷ # ÷ [0.2] SPACE (Other) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 0020 × 0308 ÷ 0378 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 0020 × 0308 ÷ 0378 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
÷ 0020 ÷ D800 ÷ # ÷ [0.2] SPACE (Other) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 0020 × 0308 ÷ D800 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 0020 × 0308 ÷ D800 ÷ # ÷ [0.2] SPACE (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
÷ 000D ÷ 0020 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] SPACE (Other) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 0020 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ 0020 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ 000D ÷ 000D ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 000D ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ 000D ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
÷ 000D × 000A ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) × [3.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 000A ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ 000A ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
÷ 000D ÷ 0001 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 0001 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 000D ÷ 0300 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 000D ÷ 0308 × 0300 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ 0001 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 000D ÷ 034F ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 000D ÷ 0308 × 034F ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 000D ÷ 1F1E6 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ 1F1E6 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
÷ 000D ÷ 0600 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 0600 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ 0600 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
÷ 000D ÷ 0903 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 000D ÷ 0308 × 0903 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 000D ÷ 0308 × 0903 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
÷ 000D ÷ 1100 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 1100 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ 1100 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ 000D ÷ 1160 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 1160 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ 1160 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
÷ 000D ÷ 11A8 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 11A8 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ 11A8 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
÷ 000D ÷ AC00 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ AC00 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ AC00 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
÷ 000D ÷ AC01 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ AC01 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 000D ÷ 1F1E6 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 1F1E6 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 000D ÷ 261D ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 261D ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 000D ÷ 1F3FB ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 1F3FB ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 000D ÷ 200D ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 000D ÷ 0308 × 200D ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 000D ÷ 2640 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 2640 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 000D ÷ 1F466 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] BOY (EBG) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 1F466 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ AC01 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 000D ÷ 231A ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] WATCH (ExtPict) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ 231A ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 000D ÷ 0300 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 000D ÷ 0308 × 0300 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 000D ÷ 200D ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 000D ÷ 0308 × 200D ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
÷ 000D ÷ 0378 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ 0378 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ 0378 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
÷ 000D ÷ D800 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 000D ÷ 0308 ÷ D800 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 000D ÷ 0308 ÷ D800 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
÷ 000A ÷ 0020 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] SPACE (Other) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 0020 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ 0020 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ 000A ÷ 000D ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 000D ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ 000D ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
÷ 000A ÷ 000A ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 000A ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ 000A ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
÷ 000A ÷ 0001 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 0001 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 000A ÷ 0300 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 000A ÷ 0308 × 0300 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ 0001 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 000A ÷ 034F ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 000A ÷ 0308 × 034F ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 000A ÷ 1F1E6 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ 1F1E6 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
÷ 000A ÷ 0600 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 0600 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ 0600 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
÷ 000A ÷ 0903 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 000A ÷ 0308 × 0903 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 000A ÷ 0308 × 0903 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
÷ 000A ÷ 1100 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 1100 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ 1100 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ 000A ÷ 1160 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 1160 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ 1160 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
÷ 000A ÷ 11A8 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 11A8 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ 11A8 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
÷ 000A ÷ AC00 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ AC00 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ AC00 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
÷ 000A ÷ AC01 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ AC01 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 000A ÷ 1F1E6 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 1F1E6 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 000A ÷ 261D ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 261D ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 000A ÷ 1F3FB ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 1F3FB ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 000A ÷ 200D ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 000A ÷ 0308 × 200D ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 000A ÷ 2640 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 2640 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 000A ÷ 1F466 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] BOY (EBG) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 1F466 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ AC01 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 000A ÷ 231A ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] WATCH (ExtPict) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ 231A ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 000A ÷ 0300 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 000A ÷ 0308 × 0300 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 000A ÷ 200D ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 000A ÷ 0308 × 200D ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
÷ 000A ÷ 0378 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ 0378 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ 0378 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
÷ 000A ÷ D800 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 000A ÷ 0308 ÷ D800 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 000A ÷ 0308 ÷ D800 ÷ # ÷ [0.2] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
÷ 0001 ÷ 0020 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] SPACE (Other) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 0020 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ 0020 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ 0001 ÷ 000D ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 000D ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ 000D ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
÷ 0001 ÷ 000A ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 000A ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ 000A ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
÷ 0001 ÷ 0001 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 0001 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 0001 ÷ 0300 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 0001 ÷ 0308 × 0300 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ 0001 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 0001 ÷ 034F ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 0001 ÷ 0308 × 034F ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 0001 ÷ 1F1E6 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ 1F1E6 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
÷ 0001 ÷ 0600 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 0600 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ 0600 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
÷ 0001 ÷ 0903 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 0001 ÷ 0308 × 0903 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 0001 ÷ 0308 × 0903 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
÷ 0001 ÷ 1100 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 1100 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ 1100 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ 0001 ÷ 1160 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 1160 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ 1160 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
÷ 0001 ÷ 11A8 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 11A8 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ 11A8 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
÷ 0001 ÷ AC00 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ AC00 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ AC00 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
÷ 0001 ÷ AC01 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ AC01 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 0001 ÷ 1F1E6 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 1F1E6 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 0001 ÷ 261D ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 261D ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 0001 ÷ 1F3FB ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 1F3FB ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 0001 ÷ 200D ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 0001 ÷ 0308 × 200D ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 0001 ÷ 2640 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 2640 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 0001 ÷ 1F466 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] BOY (EBG) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 1F466 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ AC01 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 0001 ÷ 231A ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] WATCH (ExtPict) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ 231A ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 0001 ÷ 0300 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0001 ÷ 0308 × 0300 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0001 ÷ 200D ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 0001 ÷ 0308 × 200D ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
÷ 0001 ÷ 0378 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ 0378 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ 0378 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
÷ 0001 ÷ D800 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 0001 ÷ 0308 ÷ D800 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 0300 ÷ 0020 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 0300 × 0308 ÷ 0020 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 0300 ÷ 000D ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 0300 × 0308 ÷ 000D ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 0300 ÷ 000A ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 0300 × 0308 ÷ 000A ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 0300 ÷ 0001 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 0300 × 0308 ÷ 0001 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 0300 × 0300 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 0300 × 0308 × 0300 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 0300 ÷ 0600 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 0300 × 0308 ÷ 0600 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 0300 × 0903 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 0300 × 0308 × 0903 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 0300 ÷ 1100 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 0300 × 0308 ÷ 1100 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 0300 ÷ 1160 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 0300 × 0308 ÷ 1160 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 0300 ÷ 11A8 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 0300 × 0308 ÷ 11A8 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 0300 ÷ AC00 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 0300 × 0308 ÷ AC00 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 0300 ÷ AC01 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 0300 × 0308 ÷ AC01 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 0300 ÷ 1F1E6 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 0300 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 0300 ÷ 261D ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 0300 × 0308 ÷ 261D ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 0300 ÷ 1F3FB ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 0300 × 0308 ÷ 1F3FB ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 0300 × 200D ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 0300 × 0308 × 200D ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 0300 ÷ 2640 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 0300 × 0308 ÷ 2640 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 0300 ÷ 1F466 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 0300 × 0308 ÷ 1F466 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 0300 ÷ 0378 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 0300 × 0308 ÷ 0378 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 0300 ÷ D800 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 0300 × 0308 ÷ D800 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 0001 ÷ 0308 ÷ D800 ÷ # ÷ [0.2] <START OF HEADING> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 034F ÷ 0020 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 034F × 0308 ÷ 0020 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 034F ÷ 000D ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 034F × 0308 ÷ 000D ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 034F ÷ 000A ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 034F × 0308 ÷ 000A ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 034F ÷ 0001 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 034F × 0308 ÷ 0001 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 034F × 034F ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 034F × 0308 × 034F ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 034F ÷ 1F1E6 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 034F × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 034F ÷ 0600 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 034F × 0308 ÷ 0600 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 034F × 0903 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 034F × 0308 × 0903 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 034F ÷ 1100 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 034F × 0308 ÷ 1100 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 034F ÷ 1160 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 034F × 0308 ÷ 1160 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 034F ÷ 11A8 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 034F × 0308 ÷ 11A8 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 034F ÷ AC00 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 034F × 0308 ÷ AC00 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 034F ÷ AC01 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 034F × 0308 ÷ AC01 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 034F ÷ 231A ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 034F × 0308 ÷ 231A ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 034F × 0300 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 034F × 0308 × 0300 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 034F × 200D ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 034F × 0308 × 200D ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 034F ÷ 0378 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 034F × 0308 ÷ 0378 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 034F ÷ D800 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 034F × 0308 ÷ D800 ÷ # ÷ [0.2] COMBINING GRAPHEME JOINER (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 1F1E6 ÷ 0020 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ 0020 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 1F1E6 ÷ 000D ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ 000D ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 1F1E6 ÷ 000A ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ 000A ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 1F1E6 ÷ 0001 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ 0001 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 1F1E6 × 034F ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 1F1E6 × 0308 × 034F ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 1F1E6 × 1F1E6 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [12.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 1F1E6 ÷ 0600 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ 0600 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 1F1E6 × 0903 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 1F1E6 × 0308 × 0903 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 1F1E6 ÷ 1100 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ 1100 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 1F1E6 ÷ 1160 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ 1160 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 1F1E6 ÷ 11A8 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ 11A8 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 1F1E6 ÷ AC00 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ AC00 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 1F1E6 ÷ AC01 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ AC01 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 1F1E6 ÷ 231A ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ 231A ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 1F1E6 × 0300 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 1F1E6 × 0308 × 0300 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 1F1E6 × 200D ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 1F1E6 × 0308 × 200D ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 1F1E6 ÷ 0378 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ 0378 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 1F1E6 ÷ D800 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 1F1E6 × 0308 ÷ D800 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
÷ 0600 × 0020 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] SPACE (Other) ÷ [0.3]
-÷ 0600 × 0308 ÷ 0020 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 0600 × 0308 ÷ 0020 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ 0600 ÷ 000D ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 0600 × 0308 ÷ 000D ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 0600 × 0308 ÷ 000D ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
÷ 0600 ÷ 000A ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 0600 × 0308 ÷ 000A ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 0600 × 0308 ÷ 000A ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
÷ 0600 ÷ 0001 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 0600 × 0308 ÷ 0001 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 0600 × 0300 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 0600 × 0308 × 0300 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
+÷ 0600 × 0308 ÷ 0001 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 0600 × 034F ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 0600 × 0308 × 034F ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 0600 × 1F1E6 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 0600 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
÷ 0600 × 0600 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 0600 × 0308 ÷ 0600 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 0600 × 0308 ÷ 0600 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
÷ 0600 × 0903 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 0600 × 0308 × 0903 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 0600 × 0308 × 0903 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
÷ 0600 × 1100 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 0600 × 0308 ÷ 1100 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 0600 × 0308 ÷ 1100 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ 0600 × 1160 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 0600 × 0308 ÷ 1160 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 0600 × 0308 ÷ 1160 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
÷ 0600 × 11A8 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 0600 × 0308 ÷ 11A8 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 0600 × 0308 ÷ 11A8 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
÷ 0600 × AC00 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 0600 × 0308 ÷ AC00 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 0600 × 0308 ÷ AC00 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
÷ 0600 × AC01 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 0600 × 0308 ÷ AC01 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 0600 × 1F1E6 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 0600 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 0600 × 261D ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 0600 × 0308 ÷ 261D ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 0600 × 1F3FB ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 0600 × 0308 ÷ 1F3FB ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 0600 × 200D ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 0600 × 0308 × 200D ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 0600 × 2640 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 0600 × 0308 ÷ 2640 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 0600 × 1F466 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] BOY (EBG) ÷ [0.3]
-÷ 0600 × 0308 ÷ 1F466 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ 0600 × 0308 ÷ AC01 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 0600 × 231A ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] WATCH (ExtPict) ÷ [0.3]
+÷ 0600 × 0308 ÷ 231A ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 0600 × 0300 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0600 × 0308 × 0300 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0600 × 200D ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 0600 × 0308 × 200D ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
÷ 0600 × 0378 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.2] <reserved-0378> (Other) ÷ [0.3]
-÷ 0600 × 0308 ÷ 0378 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 0600 × 0308 ÷ 0378 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
÷ 0600 ÷ D800 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 0600 × 0308 ÷ D800 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 0600 × 0308 ÷ D800 ÷ # ÷ [0.2] ARABIC NUMBER SIGN (Prepend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
÷ 0903 ÷ 0020 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 0903 × 0308 ÷ 0020 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 0903 × 0308 ÷ 0020 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ 0903 ÷ 000D ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 0903 × 0308 ÷ 000D ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 0903 × 0308 ÷ 000D ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
÷ 0903 ÷ 000A ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 0903 × 0308 ÷ 000A ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 0903 × 0308 ÷ 000A ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
÷ 0903 ÷ 0001 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 0903 × 0308 ÷ 0001 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 0903 × 0300 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 0903 × 0308 × 0300 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
+÷ 0903 × 0308 ÷ 0001 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 0903 × 034F ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 0903 × 0308 × 034F ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 0903 ÷ 1F1E6 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 0903 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
÷ 0903 ÷ 0600 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 0903 × 0308 ÷ 0600 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 0903 × 0308 ÷ 0600 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
÷ 0903 × 0903 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 0903 × 0308 × 0903 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 0903 × 0308 × 0903 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
÷ 0903 ÷ 1100 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 0903 × 0308 ÷ 1100 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 0903 × 0308 ÷ 1100 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ 0903 ÷ 1160 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 0903 × 0308 ÷ 1160 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 0903 × 0308 ÷ 1160 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
÷ 0903 ÷ 11A8 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 0903 × 0308 ÷ 11A8 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 0903 × 0308 ÷ 11A8 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
÷ 0903 ÷ AC00 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 0903 × 0308 ÷ AC00 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 0903 × 0308 ÷ AC00 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
÷ 0903 ÷ AC01 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 0903 × 0308 ÷ AC01 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 0903 ÷ 1F1E6 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 0903 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 0903 ÷ 261D ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 0903 × 0308 ÷ 261D ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 0903 ÷ 1F3FB ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 0903 × 0308 ÷ 1F3FB ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 0903 × 200D ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 0903 × 0308 × 200D ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 0903 ÷ 2640 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 0903 × 0308 ÷ 2640 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 0903 ÷ 1F466 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 0903 × 0308 ÷ 1F466 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ 0903 × 0308 ÷ AC01 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 0903 ÷ 231A ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 0903 × 0308 ÷ 231A ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 0903 × 0300 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0903 × 0308 × 0300 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0903 × 200D ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 0903 × 0308 × 200D ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
÷ 0903 ÷ 0378 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 0903 × 0308 ÷ 0378 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 0903 × 0308 ÷ 0378 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
÷ 0903 ÷ D800 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 0903 × 0308 ÷ D800 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 0903 × 0308 ÷ D800 ÷ # ÷ [0.2] DEVANAGARI SIGN VISARGA (SpacingMark) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
÷ 1100 ÷ 0020 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 1100 × 0308 ÷ 0020 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 1100 × 0308 ÷ 0020 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ 1100 ÷ 000D ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 1100 × 0308 ÷ 000D ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 1100 × 0308 ÷ 000D ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
÷ 1100 ÷ 000A ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 1100 × 0308 ÷ 000A ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 1100 × 0308 ÷ 000A ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
÷ 1100 ÷ 0001 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 1100 × 0308 ÷ 0001 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 1100 × 0300 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 1100 × 0308 × 0300 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
+÷ 1100 × 0308 ÷ 0001 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 1100 × 034F ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 1100 × 0308 × 034F ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 1100 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 1100 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
÷ 1100 ÷ 0600 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 1100 × 0308 ÷ 0600 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 1100 × 0308 ÷ 0600 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
÷ 1100 × 0903 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 1100 × 0308 × 0903 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 1100 × 0308 × 0903 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
÷ 1100 × 1100 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [6.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 1100 × 0308 ÷ 1100 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 1100 × 0308 ÷ 1100 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ 1100 × 1160 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [6.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 1100 × 0308 ÷ 1160 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 1100 × 0308 ÷ 1160 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
÷ 1100 ÷ 11A8 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 1100 × 0308 ÷ 11A8 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 1100 × 0308 ÷ 11A8 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
÷ 1100 × AC00 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [6.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 1100 × 0308 ÷ AC00 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 1100 × 0308 ÷ AC00 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
÷ 1100 × AC01 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [6.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 1100 × 0308 ÷ AC01 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 1100 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 1100 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 1100 ÷ 261D ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 1100 × 0308 ÷ 261D ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 1100 ÷ 1F3FB ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 1100 × 0308 ÷ 1F3FB ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 1100 × 200D ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 1100 × 0308 × 200D ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 1100 ÷ 2640 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 1100 × 0308 ÷ 2640 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 1100 ÷ 1F466 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 1100 × 0308 ÷ 1F466 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ 1100 × 0308 ÷ AC01 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 1100 ÷ 231A ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 1100 × 0308 ÷ 231A ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 1100 × 0300 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 1100 × 0308 × 0300 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 1100 × 200D ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 1100 × 0308 × 200D ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
÷ 1100 ÷ 0378 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 1100 × 0308 ÷ 0378 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 1100 × 0308 ÷ 0378 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
÷ 1100 ÷ D800 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 1100 × 0308 ÷ D800 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 1100 × 0308 ÷ D800 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
÷ 1160 ÷ 0020 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 1160 × 0308 ÷ 0020 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 1160 × 0308 ÷ 0020 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ 1160 ÷ 000D ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 1160 × 0308 ÷ 000D ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 1160 × 0308 ÷ 000D ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
÷ 1160 ÷ 000A ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 1160 × 0308 ÷ 000A ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 1160 × 0308 ÷ 000A ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
÷ 1160 ÷ 0001 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 1160 × 0308 ÷ 0001 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 1160 × 0300 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 1160 × 0308 × 0300 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
+÷ 1160 × 0308 ÷ 0001 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 1160 × 034F ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 1160 × 0308 × 034F ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 1160 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 1160 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
÷ 1160 ÷ 0600 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 1160 × 0308 ÷ 0600 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 1160 × 0308 ÷ 0600 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
÷ 1160 × 0903 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 1160 × 0308 × 0903 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 1160 × 0308 × 0903 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
÷ 1160 ÷ 1100 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 1160 × 0308 ÷ 1100 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 1160 × 0308 ÷ 1100 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ 1160 × 1160 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [7.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 1160 × 0308 ÷ 1160 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 1160 × 0308 ÷ 1160 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
÷ 1160 × 11A8 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [7.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 1160 × 0308 ÷ 11A8 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 1160 × 0308 ÷ 11A8 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
÷ 1160 ÷ AC00 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 1160 × 0308 ÷ AC00 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 1160 × 0308 ÷ AC00 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
÷ 1160 ÷ AC01 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 1160 × 0308 ÷ AC01 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 1160 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 1160 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 1160 ÷ 261D ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 1160 × 0308 ÷ 261D ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 1160 ÷ 1F3FB ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 1160 × 0308 ÷ 1F3FB ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 1160 × 200D ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 1160 × 0308 × 200D ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 1160 ÷ 2640 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 1160 × 0308 ÷ 2640 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 1160 ÷ 1F466 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 1160 × 0308 ÷ 1F466 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ 1160 × 0308 ÷ AC01 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 1160 ÷ 231A ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 1160 × 0308 ÷ 231A ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 1160 × 0300 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 1160 × 0308 × 0300 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 1160 × 200D ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 1160 × 0308 × 200D ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
÷ 1160 ÷ 0378 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 1160 × 0308 ÷ 0378 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 1160 × 0308 ÷ 0378 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
÷ 1160 ÷ D800 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 1160 × 0308 ÷ D800 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 1160 × 0308 ÷ D800 ÷ # ÷ [0.2] HANGUL JUNGSEONG FILLER (V) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
÷ 11A8 ÷ 0020 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 0020 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 11A8 × 0308 ÷ 0020 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ 11A8 ÷ 000D ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 000D ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 11A8 × 0308 ÷ 000D ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
÷ 11A8 ÷ 000A ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 000A ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 11A8 × 0308 ÷ 000A ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
÷ 11A8 ÷ 0001 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 0001 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 11A8 × 0300 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 11A8 × 0308 × 0300 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
+÷ 11A8 × 0308 ÷ 0001 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 11A8 × 034F ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 11A8 × 0308 × 034F ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 11A8 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 11A8 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
÷ 11A8 ÷ 0600 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 0600 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 11A8 × 0308 ÷ 0600 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
÷ 11A8 × 0903 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 11A8 × 0308 × 0903 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 11A8 × 0308 × 0903 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
÷ 11A8 ÷ 1100 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 1100 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 11A8 × 0308 ÷ 1100 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ 11A8 ÷ 1160 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 1160 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 11A8 × 0308 ÷ 1160 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
÷ 11A8 × 11A8 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [8.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 11A8 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 11A8 × 0308 ÷ 11A8 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
÷ 11A8 ÷ AC00 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 11A8 × 0308 ÷ AC00 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 11A8 × 0308 ÷ AC00 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
÷ 11A8 ÷ AC01 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 11A8 × 0308 ÷ AC01 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 11A8 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 11A8 ÷ 261D ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 261D ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 11A8 ÷ 1F3FB ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 1F3FB ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 11A8 × 200D ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 11A8 × 0308 × 200D ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 11A8 ÷ 2640 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 2640 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 11A8 ÷ 1F466 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 1F466 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ 11A8 × 0308 ÷ AC01 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 11A8 ÷ 231A ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 11A8 × 0308 ÷ 231A ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 11A8 × 0300 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 11A8 × 0308 × 0300 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 11A8 × 200D ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 11A8 × 0308 × 200D ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
÷ 11A8 ÷ 0378 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 11A8 × 0308 ÷ 0378 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 11A8 × 0308 ÷ 0378 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
÷ 11A8 ÷ D800 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 11A8 × 0308 ÷ D800 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 11A8 × 0308 ÷ D800 ÷ # ÷ [0.2] HANGUL JONGSEONG KIYEOK (T) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
÷ AC00 ÷ 0020 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ AC00 × 0308 ÷ 0020 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ AC00 × 0308 ÷ 0020 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ AC00 ÷ 000D ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ AC00 × 0308 ÷ 000D ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ AC00 × 0308 ÷ 000D ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
÷ AC00 ÷ 000A ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ AC00 × 0308 ÷ 000A ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ AC00 × 0308 ÷ 000A ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
÷ AC00 ÷ 0001 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ AC00 × 0308 ÷ 0001 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ AC00 × 0300 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ AC00 × 0308 × 0300 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
+÷ AC00 × 0308 ÷ 0001 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ AC00 × 034F ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ AC00 × 0308 × 034F ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ AC00 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ AC00 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
÷ AC00 ÷ 0600 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ AC00 × 0308 ÷ 0600 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ AC00 × 0308 ÷ 0600 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
÷ AC00 × 0903 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ AC00 × 0308 × 0903 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ AC00 × 0308 × 0903 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
÷ AC00 ÷ 1100 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ AC00 × 0308 ÷ 1100 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ AC00 × 0308 ÷ 1100 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ AC00 × 1160 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [7.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ AC00 × 0308 ÷ 1160 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ AC00 × 0308 ÷ 1160 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
÷ AC00 × 11A8 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [7.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ AC00 × 0308 ÷ 11A8 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ AC00 × 0308 ÷ 11A8 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
÷ AC00 ÷ AC00 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ AC00 × 0308 ÷ AC00 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ AC00 × 0308 ÷ AC00 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
÷ AC00 ÷ AC01 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ AC00 × 0308 ÷ AC01 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ AC00 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ AC00 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ AC00 ÷ 261D ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ AC00 × 0308 ÷ 261D ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ AC00 ÷ 1F3FB ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ AC00 × 0308 ÷ 1F3FB ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ AC00 × 200D ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ AC00 × 0308 × 200D ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ AC00 ÷ 2640 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ AC00 × 0308 ÷ 2640 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ AC00 ÷ 1F466 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ AC00 × 0308 ÷ 1F466 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ AC00 × 0308 ÷ AC01 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ AC00 ÷ 231A ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ AC00 × 0308 ÷ 231A ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ AC00 × 0300 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ AC00 × 0308 × 0300 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ AC00 × 200D ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ AC00 × 0308 × 200D ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
÷ AC00 ÷ 0378 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ AC00 × 0308 ÷ 0378 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ AC00 × 0308 ÷ 0378 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
÷ AC00 ÷ D800 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ AC00 × 0308 ÷ D800 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ AC00 × 0308 ÷ D800 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
÷ AC01 ÷ 0020 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ AC01 × 0308 ÷ 0020 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ AC01 × 0308 ÷ 0020 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ AC01 ÷ 000D ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ AC01 × 0308 ÷ 000D ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ AC01 × 0308 ÷ 000D ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
÷ AC01 ÷ 000A ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ AC01 × 0308 ÷ 000A ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ AC01 × 0308 ÷ 000A ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
÷ AC01 ÷ 0001 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ AC01 × 0308 ÷ 0001 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ AC01 × 0300 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ AC01 × 0308 × 0300 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
+÷ AC01 × 0308 ÷ 0001 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ AC01 × 034F ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ AC01 × 0308 × 034F ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ AC01 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ AC01 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
÷ AC01 ÷ 0600 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ AC01 × 0308 ÷ 0600 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ AC01 × 0308 ÷ 0600 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
÷ AC01 × 0903 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ AC01 × 0308 × 0903 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ AC01 × 0308 × 0903 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
÷ AC01 ÷ 1100 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ AC01 × 0308 ÷ 1100 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ AC01 × 0308 ÷ 1100 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ AC01 ÷ 1160 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ AC01 × 0308 ÷ 1160 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ AC01 × 0308 ÷ 1160 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
÷ AC01 × 11A8 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [8.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ AC01 × 0308 ÷ 11A8 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ AC01 × 0308 ÷ 11A8 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
÷ AC01 ÷ AC00 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ AC01 × 0308 ÷ AC00 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ AC01 × 0308 ÷ AC00 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
÷ AC01 ÷ AC01 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ AC01 × 0308 ÷ AC01 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ AC01 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ AC01 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ AC01 ÷ 261D ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ AC01 × 0308 ÷ 261D ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ AC01 ÷ 1F3FB ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ AC01 × 0308 ÷ 1F3FB ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ AC01 × 200D ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ AC01 × 0308 × 200D ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ AC01 ÷ 2640 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ AC01 × 0308 ÷ 2640 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ AC01 ÷ 1F466 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ AC01 × 0308 ÷ 1F466 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ AC01 × 0308 ÷ AC01 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ AC01 ÷ 231A ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ AC01 × 0308 ÷ 231A ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ AC01 × 0300 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ AC01 × 0308 × 0300 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ AC01 × 200D ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ AC01 × 0308 × 200D ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
÷ AC01 ÷ 0378 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ AC01 × 0308 ÷ 0378 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ AC01 × 0308 ÷ 0378 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
÷ AC01 ÷ D800 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ AC01 × 0308 ÷ D800 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 1F1E6 ÷ 0020 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 0020 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 1F1E6 ÷ 000D ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 000D ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 1F1E6 ÷ 000A ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 000A ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 1F1E6 ÷ 0001 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 0001 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 1F1E6 × 0300 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 1F1E6 × 0308 × 0300 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 1F1E6 ÷ 0600 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 0600 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 1F1E6 × 0903 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 1F1E6 × 0308 × 0903 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 1F1E6 ÷ 1100 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 1100 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 1F1E6 ÷ 1160 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 1160 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 1F1E6 ÷ 11A8 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 11A8 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 1F1E6 ÷ AC00 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ AC00 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 1F1E6 ÷ AC01 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ AC01 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 1F1E6 × 1F1E6 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [12.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 1F1E6 ÷ 261D ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 261D ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 1F1E6 ÷ 1F3FB ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 1F3FB ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 1F1E6 × 200D ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 1F1E6 × 0308 × 200D ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 1F1E6 ÷ 2640 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 2640 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 1F1E6 ÷ 1F466 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 1F466 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 1F1E6 ÷ 0378 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ 0378 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 1F1E6 ÷ D800 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 1F1E6 × 0308 ÷ D800 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 261D ÷ 0020 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 261D × 0308 ÷ 0020 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 261D ÷ 000D ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 261D × 0308 ÷ 000D ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 261D ÷ 000A ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 261D × 0308 ÷ 000A ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 261D ÷ 0001 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 261D × 0308 ÷ 0001 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 261D × 0300 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 261D × 0308 × 0300 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 261D ÷ 0600 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 261D × 0308 ÷ 0600 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 261D × 0903 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 261D × 0308 × 0903 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 261D ÷ 1100 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 261D × 0308 ÷ 1100 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 261D ÷ 1160 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 261D × 0308 ÷ 1160 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 261D ÷ 11A8 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 261D × 0308 ÷ 11A8 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 261D ÷ AC00 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 261D × 0308 ÷ AC00 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 261D ÷ AC01 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 261D × 0308 ÷ AC01 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 261D ÷ 1F1E6 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 261D × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 261D ÷ 261D ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 261D × 0308 ÷ 261D ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 261D × 1F3FB ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [10.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 261D × 0308 × 1F3FB ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) × [10.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 261D × 200D ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 261D × 0308 × 200D ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 261D ÷ 2640 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 261D × 0308 ÷ 2640 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 261D ÷ 1F466 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 261D × 0308 ÷ 1F466 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 261D ÷ 0378 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 261D × 0308 ÷ 0378 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 261D ÷ D800 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 261D × 0308 ÷ D800 ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 1F3FB ÷ 0020 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 0020 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 1F3FB ÷ 000D ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 000D ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 1F3FB ÷ 000A ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 000A ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 1F3FB ÷ 0001 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 0001 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 1F3FB × 0300 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 1F3FB × 0308 × 0300 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 1F3FB ÷ 0600 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 0600 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 1F3FB × 0903 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 1F3FB × 0308 × 0903 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 1F3FB ÷ 1100 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 1100 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 1F3FB ÷ 1160 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 1160 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 1F3FB ÷ 11A8 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 11A8 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 1F3FB ÷ AC00 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ AC00 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 1F3FB ÷ AC01 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ AC01 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 1F3FB ÷ 1F1E6 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 1F3FB ÷ 261D ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 261D ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 1F3FB ÷ 1F3FB ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 1F3FB ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 1F3FB × 200D ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 1F3FB × 0308 × 200D ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 1F3FB ÷ 2640 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 2640 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 1F3FB ÷ 1F466 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 1F466 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 1F3FB ÷ 0378 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ 0378 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 1F3FB ÷ D800 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 1F3FB × 0308 ÷ D800 ÷ # ÷ [0.2] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 200D ÷ 0020 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 200D × 0308 ÷ 0020 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 200D ÷ 000D ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 200D × 0308 ÷ 000D ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 200D ÷ 000A ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 200D × 0308 ÷ 000A ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 200D ÷ 0001 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 200D × 0308 ÷ 0001 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 200D × 0300 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 200D × 0308 × 0300 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 200D ÷ 0600 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 200D × 0308 ÷ 0600 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 200D × 0903 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 200D × 0308 × 0903 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 200D ÷ 1100 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 200D × 0308 ÷ 1100 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 200D ÷ 1160 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 200D × 0308 ÷ 1160 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 200D ÷ 11A8 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 200D × 0308 ÷ 11A8 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 200D ÷ AC00 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 200D × 0308 ÷ AC00 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 200D ÷ AC01 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 200D × 0308 ÷ AC01 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 200D ÷ 1F1E6 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 200D × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 200D ÷ 261D ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 200D × 0308 ÷ 261D ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 200D ÷ 1F3FB ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 200D × 0308 ÷ 1F3FB ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 200D × 200D ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 200D × 0308 × 200D ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 200D × 2640 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [11.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 200D × 0308 ÷ 2640 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 200D × 1F466 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [11.0] BOY (EBG) ÷ [0.3]
-÷ 200D × 0308 ÷ 1F466 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 200D ÷ 0378 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 200D × 0308 ÷ 0378 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 200D ÷ D800 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 200D × 0308 ÷ D800 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 2640 ÷ 0020 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 2640 × 0308 ÷ 0020 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 2640 ÷ 000D ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 2640 × 0308 ÷ 000D ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 2640 ÷ 000A ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 2640 × 0308 ÷ 000A ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 2640 ÷ 0001 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 2640 × 0308 ÷ 0001 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 2640 × 0300 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 2640 × 0308 × 0300 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 2640 ÷ 0600 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 2640 × 0308 ÷ 0600 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 2640 × 0903 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 2640 × 0308 × 0903 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 2640 ÷ 1100 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 2640 × 0308 ÷ 1100 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 2640 ÷ 1160 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 2640 × 0308 ÷ 1160 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 2640 ÷ 11A8 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 2640 × 0308 ÷ 11A8 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 2640 ÷ AC00 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 2640 × 0308 ÷ AC00 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 2640 ÷ AC01 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 2640 × 0308 ÷ AC01 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 2640 ÷ 1F1E6 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 2640 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 2640 ÷ 261D ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 2640 × 0308 ÷ 261D ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 2640 ÷ 1F3FB ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 2640 × 0308 ÷ 1F3FB ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 2640 × 200D ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 2640 × 0308 × 200D ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 2640 ÷ 2640 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 2640 × 0308 ÷ 2640 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 2640 ÷ 1F466 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 2640 × 0308 ÷ 1F466 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 2640 ÷ 0378 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 2640 × 0308 ÷ 0378 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 2640 ÷ D800 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 2640 × 0308 ÷ D800 ÷ # ÷ [0.2] FEMALE SIGN (Glue_After_Zwj) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 1F466 ÷ 0020 ÷ # ÷ [0.2] BOY (EBG) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 1F466 × 0308 ÷ 0020 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 1F466 ÷ 000D ÷ # ÷ [0.2] BOY (EBG) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 1F466 × 0308 ÷ 000D ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 1F466 ÷ 000A ÷ # ÷ [0.2] BOY (EBG) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 1F466 × 0308 ÷ 000A ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 1F466 ÷ 0001 ÷ # ÷ [0.2] BOY (EBG) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 1F466 × 0308 ÷ 0001 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 1F466 × 0300 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 1F466 × 0308 × 0300 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 1F466 ÷ 0600 ÷ # ÷ [0.2] BOY (EBG) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 1F466 × 0308 ÷ 0600 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 1F466 × 0903 ÷ # ÷ [0.2] BOY (EBG) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 1F466 × 0308 × 0903 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 1F466 ÷ 1100 ÷ # ÷ [0.2] BOY (EBG) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 1F466 × 0308 ÷ 1100 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 1F466 ÷ 1160 ÷ # ÷ [0.2] BOY (EBG) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 1F466 × 0308 ÷ 1160 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 1F466 ÷ 11A8 ÷ # ÷ [0.2] BOY (EBG) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 1F466 × 0308 ÷ 11A8 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 1F466 ÷ AC00 ÷ # ÷ [0.2] BOY (EBG) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 1F466 × 0308 ÷ AC00 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 1F466 ÷ AC01 ÷ # ÷ [0.2] BOY (EBG) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 1F466 × 0308 ÷ AC01 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 1F466 ÷ 1F1E6 ÷ # ÷ [0.2] BOY (EBG) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 1F466 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 1F466 ÷ 261D ÷ # ÷ [0.2] BOY (EBG) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 1F466 × 0308 ÷ 261D ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 1F466 × 1F3FB ÷ # ÷ [0.2] BOY (EBG) × [10.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 1F466 × 0308 × 1F3FB ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) × [10.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 1F466 × 200D ÷ # ÷ [0.2] BOY (EBG) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 1F466 × 0308 × 200D ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 1F466 ÷ 2640 ÷ # ÷ [0.2] BOY (EBG) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 1F466 × 0308 ÷ 2640 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 1F466 ÷ 1F466 ÷ # ÷ [0.2] BOY (EBG) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 1F466 × 0308 ÷ 1F466 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 1F466 ÷ 0378 ÷ # ÷ [0.2] BOY (EBG) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 1F466 × 0308 ÷ 0378 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 1F466 ÷ D800 ÷ # ÷ [0.2] BOY (EBG) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 1F466 × 0308 ÷ D800 ÷ # ÷ [0.2] BOY (EBG) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ AC01 × 0308 ÷ D800 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 231A ÷ 0020 ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 231A × 0308 ÷ 0020 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 231A ÷ 000D ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 231A × 0308 ÷ 000D ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 231A ÷ 000A ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 231A × 0308 ÷ 000A ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 231A ÷ 0001 ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 231A × 0308 ÷ 0001 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 231A × 034F ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 231A × 0308 × 034F ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 231A ÷ 1F1E6 ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 231A × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 231A ÷ 0600 ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 231A × 0308 ÷ 0600 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 231A × 0903 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 231A × 0308 × 0903 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 231A ÷ 1100 ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 231A × 0308 ÷ 1100 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 231A ÷ 1160 ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 231A × 0308 ÷ 1160 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 231A ÷ 11A8 ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 231A × 0308 ÷ 11A8 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 231A ÷ AC00 ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 231A × 0308 ÷ AC00 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 231A ÷ AC01 ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 231A × 0308 ÷ AC01 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 231A ÷ 231A ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 231A × 0308 ÷ 231A ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 231A × 0300 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 231A × 0308 × 0300 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 231A × 200D ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 231A × 0308 × 200D ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 231A ÷ 0378 ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 231A × 0308 ÷ 0378 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 231A ÷ D800 ÷ # ÷ [0.2] WATCH (ExtPict) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 231A × 0308 ÷ D800 ÷ # ÷ [0.2] WATCH (ExtPict) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 0300 ÷ 0020 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 0300 × 0308 ÷ 0020 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 0300 ÷ 000D ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 0300 × 0308 ÷ 000D ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 0300 ÷ 000A ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 0300 × 0308 ÷ 000A ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 0300 ÷ 0001 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 0300 × 0308 ÷ 0001 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 0300 × 034F ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 0300 × 0308 × 034F ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 0300 ÷ 1F1E6 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 0300 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 0300 ÷ 0600 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 0300 × 0308 ÷ 0600 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 0300 × 0903 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 0300 × 0308 × 0903 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 0300 ÷ 1100 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 0300 × 0308 ÷ 1100 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 0300 ÷ 1160 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 0300 × 0308 ÷ 1160 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 0300 ÷ 11A8 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 0300 × 0308 ÷ 11A8 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 0300 ÷ AC00 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 0300 × 0308 ÷ AC00 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 0300 ÷ AC01 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 0300 × 0308 ÷ AC01 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 0300 ÷ 231A ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 0300 × 0308 ÷ 231A ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 0300 × 0300 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0300 × 0308 × 0300 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0300 × 200D ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 0300 × 0308 × 200D ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 0300 ÷ 0378 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 0300 × 0308 ÷ 0378 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 0300 ÷ D800 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 0300 × 0308 ÷ D800 ÷ # ÷ [0.2] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 200D ÷ 0020 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 200D × 0308 ÷ 0020 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 200D ÷ 000D ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 200D × 0308 ÷ 000D ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 200D ÷ 000A ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 200D × 0308 ÷ 000A ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 200D ÷ 0001 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 200D × 0308 ÷ 0001 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 200D × 034F ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 200D × 0308 × 034F ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 200D ÷ 1F1E6 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 200D × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 200D ÷ 0600 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 200D × 0308 ÷ 0600 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 200D × 0903 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 200D × 0308 × 0903 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 200D ÷ 1100 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 200D × 0308 ÷ 1100 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 200D ÷ 1160 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 200D × 0308 ÷ 1160 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 200D ÷ 11A8 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 200D × 0308 ÷ 11A8 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 200D ÷ AC00 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 200D × 0308 ÷ AC00 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 200D ÷ AC01 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 200D × 0308 ÷ AC01 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 200D ÷ 231A ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 200D × 0308 ÷ 231A ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 200D × 0300 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 200D × 0308 × 0300 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 200D × 200D ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 200D × 0308 × 200D ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 200D ÷ 0378 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 200D × 0308 ÷ 0378 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 200D ÷ D800 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 200D × 0308 ÷ D800 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
÷ 0378 ÷ 0020 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] SPACE (Other) ÷ [0.3]
-÷ 0378 × 0308 ÷ 0020 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ 0378 × 0308 ÷ 0020 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ 0378 ÷ 000D ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ 0378 × 0308 ÷ 000D ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ 0378 × 0308 ÷ 000D ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
÷ 0378 ÷ 000A ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ 0378 × 0308 ÷ 000A ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ 0378 × 0308 ÷ 000A ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
÷ 0378 ÷ 0001 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 0378 × 0308 ÷ 0001 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ 0378 × 0300 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ 0378 × 0308 × 0300 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
+÷ 0378 × 0308 ÷ 0001 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ 0378 × 034F ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 0378 × 0308 × 034F ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ 0378 ÷ 1F1E6 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ 0378 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
÷ 0378 ÷ 0600 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ 0378 × 0308 ÷ 0600 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ 0378 × 0308 ÷ 0600 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
÷ 0378 × 0903 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ 0378 × 0308 × 0903 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ 0378 × 0308 × 0903 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
÷ 0378 ÷ 1100 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ 0378 × 0308 ÷ 1100 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ 0378 × 0308 ÷ 1100 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ 0378 ÷ 1160 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ 0378 × 0308 ÷ 1160 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ 0378 × 0308 ÷ 1160 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
÷ 0378 ÷ 11A8 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ 0378 × 0308 ÷ 11A8 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ 0378 × 0308 ÷ 11A8 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
÷ 0378 ÷ AC00 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ 0378 × 0308 ÷ AC00 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ 0378 × 0308 ÷ AC00 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
÷ 0378 ÷ AC01 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 0378 × 0308 ÷ AC01 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ 0378 ÷ 1F1E6 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 0378 × 0308 ÷ 1F1E6 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ 0378 ÷ 261D ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 0378 × 0308 ÷ 261D ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 0378 ÷ 1F3FB ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 0378 × 0308 ÷ 1F3FB ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 0378 × 200D ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 0378 × 0308 × 200D ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 0378 ÷ 2640 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 0378 × 0308 ÷ 2640 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 0378 ÷ 1F466 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] BOY (EBG) ÷ [0.3]
-÷ 0378 × 0308 ÷ 1F466 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ 0378 × 0308 ÷ AC01 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ 0378 ÷ 231A ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 0378 × 0308 ÷ 231A ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ 0378 × 0300 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0378 × 0308 × 0300 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0378 × 200D ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 0378 × 0308 × 200D ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
÷ 0378 ÷ 0378 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
-÷ 0378 × 0308 ÷ 0378 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ 0378 × 0308 ÷ 0378 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
÷ 0378 ÷ D800 ÷ # ÷ [0.2] <reserved-0378> (Other) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 0378 × 0308 ÷ D800 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 0378 × 0308 ÷ D800 ÷ # ÷ [0.2] <reserved-0378> (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
÷ D800 ÷ 0020 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] SPACE (Other) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 0020 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ 0020 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ D800 ÷ 000D ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 000D ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ 000D ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
÷ D800 ÷ 000A ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 000A ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ 000A ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [0.3]
÷ D800 ÷ 0001 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 0001 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
-÷ D800 ÷ 0300 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
-÷ D800 ÷ 0308 × 0300 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) × [9.0] COMBINING GRAVE ACCENT (Extend) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ 0001 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <START OF HEADING> (Control) ÷ [0.3]
+÷ D800 ÷ 034F ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ D800 ÷ 0308 × 034F ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAPHEME JOINER (Extend) ÷ [0.3]
+÷ D800 ÷ 1F1E6 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ 1F1E6 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
÷ D800 ÷ 0600 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 0600 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ 0600 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) ÷ [0.3]
÷ D800 ÷ 0903 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
-÷ D800 ÷ 0308 × 0903 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
+÷ D800 ÷ 0308 × 0903 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [0.3]
÷ D800 ÷ 1100 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 1100 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ 1100 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ D800 ÷ 1160 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 1160 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ 1160 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JUNGSEONG FILLER (V) ÷ [0.3]
÷ D800 ÷ 11A8 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 11A8 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ 11A8 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL JONGSEONG KIYEOK (T) ÷ [0.3]
÷ D800 ÷ AC00 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ AC00 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ AC00 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GA (LV) ÷ [0.3]
÷ D800 ÷ AC01 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ AC01 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
-÷ D800 ÷ 1F1E6 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 1F1E6 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-÷ D800 ÷ 261D ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 261D ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ D800 ÷ 1F3FB ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 1F3FB ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ D800 ÷ 200D ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ D800 ÷ 0308 × 200D ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ D800 ÷ 2640 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 2640 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ D800 ÷ 1F466 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] BOY (EBG) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 1F466 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ AC01 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] HANGUL SYLLABLE GAG (LVT) ÷ [0.3]
+÷ D800 ÷ 231A ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] WATCH (ExtPict) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ 231A ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] WATCH (ExtPict) ÷ [0.3]
+÷ D800 ÷ 0300 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ D800 ÷ 0308 × 0300 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] COMBINING GRAVE ACCENT (Extend_ExtCccZwj) ÷ [0.3]
+÷ D800 ÷ 200D ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ D800 ÷ 0308 × 200D ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
÷ D800 ÷ 0378 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] <reserved-0378> (Other) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ 0378 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ 0378 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] <reserved-0378> (Other) ÷ [0.3]
÷ D800 ÷ D800 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ D800 ÷ 0308 ÷ D800 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
-÷ 000D × 000A ÷ 0061 ÷ 000A ÷ 0308 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) × [3.0] <LINE FEED (LF)> (LF) ÷ [4.0] LATIN SMALL LETTER A (Other) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend) ÷ [0.3]
-÷ 0061 × 0308 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [0.3]
-÷ 0020 × 200D ÷ 0646 ÷ # ÷ [0.2] SPACE (Other) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] ARABIC LETTER NOON (Other) ÷ [0.3]
-÷ 0646 × 200D ÷ 0020 ÷ # ÷ [0.2] ARABIC LETTER NOON (Other) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] SPACE (Other) ÷ [0.3]
+÷ D800 ÷ 0308 ÷ D800 ÷ # ÷ [0.2] <surrogate-D800> (Control) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [5.0] <surrogate-D800> (Control) ÷ [0.3]
+÷ 000D × 000A ÷ 0061 ÷ 000A ÷ 0308 ÷ # ÷ [0.2] <CARRIAGE RETURN (CR)> (CR) × [3.0] <LINE FEED (LF)> (LF) ÷ [4.0] LATIN SMALL LETTER A (Other) ÷ [5.0] <LINE FEED (LF)> (LF) ÷ [4.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0061 × 0308 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [0.3]
+÷ 0020 × 200D ÷ 0646 ÷ # ÷ [0.2] SPACE (Other) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] ARABIC LETTER NOON (Other) ÷ [0.3]
+÷ 0646 × 200D ÷ 0020 ÷ # ÷ [0.2] ARABIC LETTER NOON (Other) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] SPACE (Other) ÷ [0.3]
÷ 1100 × 1100 ÷ # ÷ [0.2] HANGUL CHOSEONG KIYEOK (L) × [6.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ AC00 × 11A8 ÷ 1100 ÷ # ÷ [0.2] HANGUL SYLLABLE GA (LV) × [7.0] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ AC01 × 11A8 ÷ 1100 ÷ # ÷ [0.2] HANGUL SYLLABLE GAG (LVT) × [8.0] HANGUL JONGSEONG KIYEOK (T) ÷ [999.0] HANGUL CHOSEONG KIYEOK (L) ÷ [0.3]
÷ 1F1E6 × 1F1E7 ÷ 1F1E8 ÷ 0062 ÷ # ÷ [0.2] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [12.0] REGIONAL INDICATOR SYMBOL LETTER B (RI) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER C (RI) ÷ [999.0] LATIN SMALL LETTER B (Other) ÷ [0.3]
÷ 0061 ÷ 1F1E6 × 1F1E7 ÷ 1F1E8 ÷ 0062 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [13.0] REGIONAL INDICATOR SYMBOL LETTER B (RI) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER C (RI) ÷ [999.0] LATIN SMALL LETTER B (Other) ÷ [0.3]
-÷ 0061 ÷ 1F1E6 × 1F1E7 × 200D ÷ 1F1E8 ÷ 0062 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [13.0] REGIONAL INDICATOR SYMBOL LETTER B (RI) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER C (RI) ÷ [999.0] LATIN SMALL LETTER B (Other) ÷ [0.3]
-÷ 0061 ÷ 1F1E6 × 200D ÷ 1F1E7 × 1F1E8 ÷ 0062 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER B (RI) × [13.0] REGIONAL INDICATOR SYMBOL LETTER C (RI) ÷ [999.0] LATIN SMALL LETTER B (Other) ÷ [0.3]
+÷ 0061 ÷ 1F1E6 × 1F1E7 × 200D ÷ 1F1E8 ÷ 0062 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [13.0] REGIONAL INDICATOR SYMBOL LETTER B (RI) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER C (RI) ÷ [999.0] LATIN SMALL LETTER B (Other) ÷ [0.3]
+÷ 0061 ÷ 1F1E6 × 200D ÷ 1F1E7 × 1F1E8 ÷ 0062 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER B (RI) × [13.0] REGIONAL INDICATOR SYMBOL LETTER C (RI) ÷ [999.0] LATIN SMALL LETTER B (Other) ÷ [0.3]
÷ 0061 ÷ 1F1E6 × 1F1E7 ÷ 1F1E8 × 1F1E9 ÷ 0062 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) × [13.0] REGIONAL INDICATOR SYMBOL LETTER B (RI) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER C (RI) × [13.0] REGIONAL INDICATOR SYMBOL LETTER D (RI) ÷ [999.0] LATIN SMALL LETTER B (Other) ÷ [0.3]
-÷ 0061 × 200D ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) × [9.0] ZERO WIDTH JOINER (ZWJ) ÷ [0.3]
-÷ 0061 × 0308 ÷ 0062 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) × [9.0] COMBINING DIAERESIS (Extend) ÷ [999.0] LATIN SMALL LETTER B (Other) ÷ [0.3]
+÷ 0061 × 200D ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [0.3]
+÷ 0061 × 0308 ÷ 0062 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) ÷ [999.0] LATIN SMALL LETTER B (Other) ÷ [0.3]
÷ 0061 × 0903 ÷ 0062 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) × [9.1] DEVANAGARI SIGN VISARGA (SpacingMark) ÷ [999.0] LATIN SMALL LETTER B (Other) ÷ [0.3]
÷ 0061 ÷ 0600 × 0062 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) ÷ [999.0] ARABIC NUMBER SIGN (Prepend) × [9.2] LATIN SMALL LETTER B (Other) ÷ [0.3]
-÷ 261D × 1F3FB ÷ 261D ÷ # ÷ [0.2] WHITE UP POINTING INDEX (E_Base) × [10.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [999.0] WHITE UP POINTING INDEX (E_Base) ÷ [0.3]
-÷ 1F466 × 1F3FB ÷ # ÷ [0.2] BOY (EBG) × [10.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 200D × 1F466 × 1F3FB ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [11.0] BOY (EBG) × [10.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (E_Modifier) ÷ [0.3]
-÷ 200D × 2640 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [11.0] FEMALE SIGN (Glue_After_Zwj) ÷ [0.3]
-÷ 200D × 1F466 ÷ # ÷ [0.2] ZERO WIDTH JOINER (ZWJ) × [11.0] BOY (EBG) ÷ [0.3]
-÷ 1F466 ÷ 1F466 ÷ # ÷ [0.2] BOY (EBG) ÷ [999.0] BOY (EBG) ÷ [0.3]
+÷ 1F476 × 1F3FF ÷ 1F476 ÷ # ÷ [0.2] BABY (ExtPict) × [9.0] EMOJI MODIFIER FITZPATRICK TYPE-6 (Extend) ÷ [999.0] BABY (ExtPict) ÷ [0.3]
+÷ 0061 × 1F3FF ÷ 1F476 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) × [9.0] EMOJI MODIFIER FITZPATRICK TYPE-6 (Extend) ÷ [999.0] BABY (ExtPict) ÷ [0.3]
+÷ 0061 × 1F3FF ÷ 1F476 × 200D × 1F6D1 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) × [9.0] EMOJI MODIFIER FITZPATRICK TYPE-6 (Extend) ÷ [999.0] BABY (ExtPict) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [11.0] OCTAGONAL SIGN (ExtPict) ÷ [0.3]
+÷ 1F476 × 1F3FF × 0308 × 200D × 1F476 × 1F3FF ÷ # ÷ [0.2] BABY (ExtPict) × [9.0] EMOJI MODIFIER FITZPATRICK TYPE-6 (Extend) × [9.0] COMBINING DIAERESIS (Extend_ExtCccZwj) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [11.0] BABY (ExtPict) × [9.0] EMOJI MODIFIER FITZPATRICK TYPE-6 (Extend) ÷ [0.3]
+÷ 1F6D1 × 200D × 1F6D1 ÷ # ÷ [0.2] OCTAGONAL SIGN (ExtPict) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [11.0] OCTAGONAL SIGN (ExtPict) ÷ [0.3]
+÷ 0061 × 200D ÷ 1F6D1 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] OCTAGONAL SIGN (ExtPict) ÷ [0.3]
+÷ 2701 × 200D × 2701 ÷ # ÷ [0.2] UPPER BLADE SCISSORS (Other) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) × [11.0] UPPER BLADE SCISSORS (Other) ÷ [0.3]
+÷ 0061 × 200D ÷ 2701 ÷ # ÷ [0.2] LATIN SMALL LETTER A (Other) × [9.0] ZERO WIDTH JOINER (ZWJ_ExtCccZwj) ÷ [999.0] UPPER BLADE SCISSORS (Other) ÷ [0.3]
#
-# Lines: 822
+# Lines: 672
#
# EOF
diff --git a/lib/stdlib/test/unicode_util_SUITE_data/LineBreakTest.txt b/lib/stdlib/test/unicode_util_SUITE_data/LineBreakTest.txt
index 6715446aba..0e9e678a85 100644
--- a/lib/stdlib/test/unicode_util_SUITE_data/LineBreakTest.txt
+++ b/lib/stdlib/test/unicode_util_SUITE_data/LineBreakTest.txt
@@ -1,6 +1,6 @@
-# LineBreakTest-10.0.0.txt
-# Date: 2017-04-14, 05:40:30 GMT
-# © 2017 Unicode®, Inc.
+# LineBreakTest-11.0.0.txt
+# Date: 2018-05-20, 09:03:09 GMT
+# © 2018 Unicode®, Inc.
# Unicode and the Unicode Logo are registered trademarks of Unicode, Inc. in the U.S. and other countries.
# For terms of use, see http://www.unicode.org/terms_of_use.html
#
@@ -6242,174 +6242,174 @@
× 0001 × 0020 ÷ 3041 ÷ # × [0.3] <START OF HEADING> (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
× 0001 × 0308 × 3041 ÷ # × [0.3] <START OF HEADING> (CM1_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [21.03] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
× 0001 × 0308 × 0020 ÷ 3041 ÷ # × [0.3] <START OF HEADING> (CM1_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
-× 200D × 0023 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [28.0] NUMBER SIGN (AL) ÷ [0.3]
+× 200D × 0023 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] NUMBER SIGN (AL) ÷ [0.3]
× 200D × 0020 ÷ 0023 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] NUMBER SIGN (AL) ÷ [0.3]
-× 200D × 0308 × 0023 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [28.0] NUMBER SIGN (AL) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 0023 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] NUMBER SIGN (AL) ÷ [0.3]
-× 200D ÷ 2014 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [999.0] EM DASH (B2) ÷ [0.3]
+× 200D × 0308 × 0023 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [28.0] NUMBER SIGN (AL) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 0023 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] NUMBER SIGN (AL) ÷ [0.3]
+× 200D × 2014 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] EM DASH (B2) ÷ [0.3]
× 200D × 0020 ÷ 2014 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] EM DASH (B2) ÷ [0.3]
-× 200D × 0308 ÷ 2014 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] EM DASH (B2) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 2014 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] EM DASH (B2) ÷ [0.3]
-× 200D × 0009 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [21.01] <CHARACTER TABULATION> (BA) ÷ [0.3]
+× 200D × 0308 ÷ 2014 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] EM DASH (B2) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 2014 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] EM DASH (B2) ÷ [0.3]
+× 200D × 0009 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] <CHARACTER TABULATION> (BA) ÷ [0.3]
× 200D × 0020 ÷ 0009 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] <CHARACTER TABULATION> (BA) ÷ [0.3]
-× 200D × 0308 × 0009 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [21.01] <CHARACTER TABULATION> (BA) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 0009 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] <CHARACTER TABULATION> (BA) ÷ [0.3]
-× 200D ÷ 00B4 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [999.0] ACUTE ACCENT (BB) ÷ [0.3]
+× 200D × 0308 × 0009 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [21.01] <CHARACTER TABULATION> (BA) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 0009 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] <CHARACTER TABULATION> (BA) ÷ [0.3]
+× 200D × 00B4 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] ACUTE ACCENT (BB) ÷ [0.3]
× 200D × 0020 ÷ 00B4 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] ACUTE ACCENT (BB) ÷ [0.3]
-× 200D × 0308 ÷ 00B4 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] ACUTE ACCENT (BB) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 00B4 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] ACUTE ACCENT (BB) ÷ [0.3]
+× 200D × 0308 ÷ 00B4 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] ACUTE ACCENT (BB) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 00B4 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] ACUTE ACCENT (BB) ÷ [0.3]
× 200D × 000B ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [6.0] <LINE TABULATION> (BK) ÷ [0.3]
× 200D × 0020 × 000B ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) × [6.0] <LINE TABULATION> (BK) ÷ [0.3]
-× 200D × 0308 × 000B ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [6.0] <LINE TABULATION> (BK) ÷ [0.3]
-× 200D × 0308 × 0020 × 000B ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [6.0] <LINE TABULATION> (BK) ÷ [0.3]
-× 200D ÷ FFFC ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [20.01] OBJECT REPLACEMENT CHARACTER (CB) ÷ [0.3]
+× 200D × 0308 × 000B ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [6.0] <LINE TABULATION> (BK) ÷ [0.3]
+× 200D × 0308 × 0020 × 000B ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [6.0] <LINE TABULATION> (BK) ÷ [0.3]
+× 200D × FFFC ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] OBJECT REPLACEMENT CHARACTER (CB) ÷ [0.3]
× 200D × 0020 ÷ FFFC ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] OBJECT REPLACEMENT CHARACTER (CB) ÷ [0.3]
-× 200D × 0308 ÷ FFFC ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) ÷ [20.01] OBJECT REPLACEMENT CHARACTER (CB) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ FFFC ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] OBJECT REPLACEMENT CHARACTER (CB) ÷ [0.3]
-× 200D × 007D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [13.04] RIGHT CURLY BRACKET (CL) ÷ [0.3]
+× 200D × 0308 ÷ FFFC ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) ÷ [20.01] OBJECT REPLACEMENT CHARACTER (CB) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ FFFC ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] OBJECT REPLACEMENT CHARACTER (CB) ÷ [0.3]
+× 200D × 007D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] RIGHT CURLY BRACKET (CL) ÷ [0.3]
× 200D × 0020 × 007D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) × [13.02] RIGHT CURLY BRACKET (CL) ÷ [0.3]
-× 200D × 0308 × 007D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [13.04] RIGHT CURLY BRACKET (CL) ÷ [0.3]
-× 200D × 0308 × 0020 × 007D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [13.02] RIGHT CURLY BRACKET (CL) ÷ [0.3]
-× 200D × 0029 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [13.04] RIGHT PARENTHESIS (CP) ÷ [0.3]
+× 200D × 0308 × 007D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [13.04] RIGHT CURLY BRACKET (CL) ÷ [0.3]
+× 200D × 0308 × 0020 × 007D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [13.02] RIGHT CURLY BRACKET (CL) ÷ [0.3]
+× 200D × 0029 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] RIGHT PARENTHESIS (CP) ÷ [0.3]
× 200D × 0020 × 0029 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) × [13.02] RIGHT PARENTHESIS (CP) ÷ [0.3]
-× 200D × 0308 × 0029 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [13.04] RIGHT PARENTHESIS (CP) ÷ [0.3]
-× 200D × 0308 × 0020 × 0029 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [13.02] RIGHT PARENTHESIS (CP) ÷ [0.3]
+× 200D × 0308 × 0029 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [13.04] RIGHT PARENTHESIS (CP) ÷ [0.3]
+× 200D × 0308 × 0020 × 0029 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [13.02] RIGHT PARENTHESIS (CP) ÷ [0.3]
× 200D × 000D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [6.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
× 200D × 0020 × 000D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) × [6.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-× 200D × 0308 × 000D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [6.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-× 200D × 0308 × 0020 × 000D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [6.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
-× 200D × 0021 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [13.01] EXCLAMATION MARK (EX) ÷ [0.3]
+× 200D × 0308 × 000D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [6.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+× 200D × 0308 × 0020 × 000D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [6.0] <CARRIAGE RETURN (CR)> (CR) ÷ [0.3]
+× 200D × 0021 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] EXCLAMATION MARK (EX) ÷ [0.3]
× 200D × 0020 × 0021 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) × [13.01] EXCLAMATION MARK (EX) ÷ [0.3]
-× 200D × 0308 × 0021 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [13.01] EXCLAMATION MARK (EX) ÷ [0.3]
-× 200D × 0308 × 0020 × 0021 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [13.01] EXCLAMATION MARK (EX) ÷ [0.3]
-× 200D × 00A0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [12.3] NO-BREAK SPACE (GL) ÷ [0.3]
+× 200D × 0308 × 0021 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [13.01] EXCLAMATION MARK (EX) ÷ [0.3]
+× 200D × 0308 × 0020 × 0021 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [13.01] EXCLAMATION MARK (EX) ÷ [0.3]
+× 200D × 00A0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] NO-BREAK SPACE (GL) ÷ [0.3]
× 200D × 0020 ÷ 00A0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] NO-BREAK SPACE (GL) ÷ [0.3]
-× 200D × 0308 × 00A0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [12.3] NO-BREAK SPACE (GL) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 00A0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] NO-BREAK SPACE (GL) ÷ [0.3]
-× 200D ÷ AC00 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [999.0] HANGUL SYLLABLE GA (H2) ÷ [0.3]
+× 200D × 0308 × 00A0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [12.3] NO-BREAK SPACE (GL) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 00A0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] NO-BREAK SPACE (GL) ÷ [0.3]
+× 200D × AC00 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] HANGUL SYLLABLE GA (H2) ÷ [0.3]
× 200D × 0020 ÷ AC00 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL SYLLABLE GA (H2) ÷ [0.3]
-× 200D × 0308 ÷ AC00 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] HANGUL SYLLABLE GA (H2) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ AC00 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL SYLLABLE GA (H2) ÷ [0.3]
-× 200D ÷ AC01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [999.0] HANGUL SYLLABLE GAG (H3) ÷ [0.3]
+× 200D × 0308 ÷ AC00 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] HANGUL SYLLABLE GA (H2) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ AC00 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL SYLLABLE GA (H2) ÷ [0.3]
+× 200D × AC01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] HANGUL SYLLABLE GAG (H3) ÷ [0.3]
× 200D × 0020 ÷ AC01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL SYLLABLE GAG (H3) ÷ [0.3]
-× 200D × 0308 ÷ AC01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] HANGUL SYLLABLE GAG (H3) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ AC01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL SYLLABLE GAG (H3) ÷ [0.3]
-× 200D × 05D0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [28.0] HEBREW LETTER ALEF (HL) ÷ [0.3]
+× 200D × 0308 ÷ AC01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] HANGUL SYLLABLE GAG (H3) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ AC01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL SYLLABLE GAG (H3) ÷ [0.3]
+× 200D × 05D0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] HEBREW LETTER ALEF (HL) ÷ [0.3]
× 200D × 0020 ÷ 05D0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] HEBREW LETTER ALEF (HL) ÷ [0.3]
-× 200D × 0308 × 05D0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [28.0] HEBREW LETTER ALEF (HL) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 05D0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HEBREW LETTER ALEF (HL) ÷ [0.3]
-× 200D × 002D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [21.02] HYPHEN-MINUS (HY) ÷ [0.3]
+× 200D × 0308 × 05D0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [28.0] HEBREW LETTER ALEF (HL) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 05D0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HEBREW LETTER ALEF (HL) ÷ [0.3]
+× 200D × 002D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] HYPHEN-MINUS (HY) ÷ [0.3]
× 200D × 0020 ÷ 002D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] HYPHEN-MINUS (HY) ÷ [0.3]
-× 200D × 0308 × 002D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [21.02] HYPHEN-MINUS (HY) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 002D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HYPHEN-MINUS (HY) ÷ [0.3]
+× 200D × 0308 × 002D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [21.02] HYPHEN-MINUS (HY) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 002D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HYPHEN-MINUS (HY) ÷ [0.3]
× 200D × 231A ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] WATCH (ID) ÷ [0.3]
× 200D × 0020 ÷ 231A ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] WATCH (ID) ÷ [0.3]
-× 200D × 0308 ÷ 231A ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] WATCH (ID) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 231A ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] WATCH (ID) ÷ [0.3]
-× 200D × 2024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [22.01] ONE DOT LEADER (IN) ÷ [0.3]
+× 200D × 0308 ÷ 231A ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] WATCH (ID) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 231A ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] WATCH (ID) ÷ [0.3]
+× 200D × 2024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] ONE DOT LEADER (IN) ÷ [0.3]
× 200D × 0020 ÷ 2024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] ONE DOT LEADER (IN) ÷ [0.3]
-× 200D × 0308 × 2024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [22.01] ONE DOT LEADER (IN) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 2024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] ONE DOT LEADER (IN) ÷ [0.3]
-× 200D × 002C ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [13.04] COMMA (IS) ÷ [0.3]
+× 200D × 0308 × 2024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [22.01] ONE DOT LEADER (IN) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 2024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] ONE DOT LEADER (IN) ÷ [0.3]
+× 200D × 002C ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMMA (IS) ÷ [0.3]
× 200D × 0020 × 002C ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) × [13.02] COMMA (IS) ÷ [0.3]
-× 200D × 0308 × 002C ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [13.04] COMMA (IS) ÷ [0.3]
-× 200D × 0308 × 0020 × 002C ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [13.02] COMMA (IS) ÷ [0.3]
-× 200D ÷ 1100 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [999.0] HANGUL CHOSEONG KIYEOK (JL) ÷ [0.3]
+× 200D × 0308 × 002C ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [13.04] COMMA (IS) ÷ [0.3]
+× 200D × 0308 × 0020 × 002C ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [13.02] COMMA (IS) ÷ [0.3]
+× 200D × 1100 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] HANGUL CHOSEONG KIYEOK (JL) ÷ [0.3]
× 200D × 0020 ÷ 1100 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL CHOSEONG KIYEOK (JL) ÷ [0.3]
-× 200D × 0308 ÷ 1100 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] HANGUL CHOSEONG KIYEOK (JL) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 1100 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL CHOSEONG KIYEOK (JL) ÷ [0.3]
-× 200D ÷ 11A8 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [999.0] HANGUL JONGSEONG KIYEOK (JT) ÷ [0.3]
+× 200D × 0308 ÷ 1100 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] HANGUL CHOSEONG KIYEOK (JL) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 1100 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL CHOSEONG KIYEOK (JL) ÷ [0.3]
+× 200D × 11A8 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] HANGUL JONGSEONG KIYEOK (JT) ÷ [0.3]
× 200D × 0020 ÷ 11A8 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL JONGSEONG KIYEOK (JT) ÷ [0.3]
-× 200D × 0308 ÷ 11A8 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] HANGUL JONGSEONG KIYEOK (JT) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 11A8 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL JONGSEONG KIYEOK (JT) ÷ [0.3]
-× 200D ÷ 1160 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [999.0] HANGUL JUNGSEONG FILLER (JV) ÷ [0.3]
+× 200D × 0308 ÷ 11A8 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] HANGUL JONGSEONG KIYEOK (JT) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 11A8 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL JONGSEONG KIYEOK (JT) ÷ [0.3]
+× 200D × 1160 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] HANGUL JUNGSEONG FILLER (JV) ÷ [0.3]
× 200D × 0020 ÷ 1160 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL JUNGSEONG FILLER (JV) ÷ [0.3]
-× 200D × 0308 ÷ 1160 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] HANGUL JUNGSEONG FILLER (JV) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 1160 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL JUNGSEONG FILLER (JV) ÷ [0.3]
+× 200D × 0308 ÷ 1160 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] HANGUL JUNGSEONG FILLER (JV) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 1160 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HANGUL JUNGSEONG FILLER (JV) ÷ [0.3]
× 200D × 000A ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [6.0] <LINE FEED (LF)> (LF) ÷ [0.3]
× 200D × 0020 × 000A ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) × [6.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-× 200D × 0308 × 000A ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [6.0] <LINE FEED (LF)> (LF) ÷ [0.3]
-× 200D × 0308 × 0020 × 000A ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [6.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+× 200D × 0308 × 000A ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [6.0] <LINE FEED (LF)> (LF) ÷ [0.3]
+× 200D × 0308 × 0020 × 000A ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [6.0] <LINE FEED (LF)> (LF) ÷ [0.3]
× 200D × 0085 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [6.0] <NEXT LINE (NEL)> (NL) ÷ [0.3]
× 200D × 0020 × 0085 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) × [6.0] <NEXT LINE (NEL)> (NL) ÷ [0.3]
-× 200D × 0308 × 0085 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [6.0] <NEXT LINE (NEL)> (NL) ÷ [0.3]
-× 200D × 0308 × 0020 × 0085 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [6.0] <NEXT LINE (NEL)> (NL) ÷ [0.3]
-× 200D × 17D6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [21.03] KHMER SIGN CAMNUC PII KUUH (NS) ÷ [0.3]
+× 200D × 0308 × 0085 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [6.0] <NEXT LINE (NEL)> (NL) ÷ [0.3]
+× 200D × 0308 × 0020 × 0085 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [6.0] <NEXT LINE (NEL)> (NL) ÷ [0.3]
+× 200D × 17D6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] KHMER SIGN CAMNUC PII KUUH (NS) ÷ [0.3]
× 200D × 0020 ÷ 17D6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] KHMER SIGN CAMNUC PII KUUH (NS) ÷ [0.3]
-× 200D × 0308 × 17D6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [21.03] KHMER SIGN CAMNUC PII KUUH (NS) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 17D6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] KHMER SIGN CAMNUC PII KUUH (NS) ÷ [0.3]
-× 200D × 0030 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [23.02] DIGIT ZERO (NU) ÷ [0.3]
+× 200D × 0308 × 17D6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [21.03] KHMER SIGN CAMNUC PII KUUH (NS) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 17D6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] KHMER SIGN CAMNUC PII KUUH (NS) ÷ [0.3]
+× 200D × 0030 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] DIGIT ZERO (NU) ÷ [0.3]
× 200D × 0020 ÷ 0030 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] DIGIT ZERO (NU) ÷ [0.3]
-× 200D × 0308 × 0030 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [23.02] DIGIT ZERO (NU) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 0030 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] DIGIT ZERO (NU) ÷ [0.3]
-× 200D × 0028 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [30.01] LEFT PARENTHESIS (OP) ÷ [0.3]
+× 200D × 0308 × 0030 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [23.02] DIGIT ZERO (NU) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 0030 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] DIGIT ZERO (NU) ÷ [0.3]
+× 200D × 0028 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] LEFT PARENTHESIS (OP) ÷ [0.3]
× 200D × 0020 ÷ 0028 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] LEFT PARENTHESIS (OP) ÷ [0.3]
-× 200D × 0308 × 0028 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [30.01] LEFT PARENTHESIS (OP) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 0028 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] LEFT PARENTHESIS (OP) ÷ [0.3]
-× 200D × 0025 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [24.03] PERCENT SIGN (PO) ÷ [0.3]
+× 200D × 0308 × 0028 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [30.01] LEFT PARENTHESIS (OP) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 0028 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] LEFT PARENTHESIS (OP) ÷ [0.3]
+× 200D × 0025 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] PERCENT SIGN (PO) ÷ [0.3]
× 200D × 0020 ÷ 0025 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] PERCENT SIGN (PO) ÷ [0.3]
-× 200D × 0308 × 0025 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [24.03] PERCENT SIGN (PO) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 0025 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] PERCENT SIGN (PO) ÷ [0.3]
-× 200D × 0024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [24.03] DOLLAR SIGN (PR) ÷ [0.3]
+× 200D × 0308 × 0025 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [24.03] PERCENT SIGN (PO) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 0025 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] PERCENT SIGN (PO) ÷ [0.3]
+× 200D × 0024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] DOLLAR SIGN (PR) ÷ [0.3]
× 200D × 0020 ÷ 0024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] DOLLAR SIGN (PR) ÷ [0.3]
-× 200D × 0308 × 0024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [24.03] DOLLAR SIGN (PR) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 0024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] DOLLAR SIGN (PR) ÷ [0.3]
-× 200D × 0022 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [19.01] QUOTATION MARK (QU) ÷ [0.3]
+× 200D × 0308 × 0024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [24.03] DOLLAR SIGN (PR) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 0024 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] DOLLAR SIGN (PR) ÷ [0.3]
+× 200D × 0022 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] QUOTATION MARK (QU) ÷ [0.3]
× 200D × 0020 ÷ 0022 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] QUOTATION MARK (QU) ÷ [0.3]
-× 200D × 0308 × 0022 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [19.01] QUOTATION MARK (QU) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 0022 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] QUOTATION MARK (QU) ÷ [0.3]
+× 200D × 0308 × 0022 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [19.01] QUOTATION MARK (QU) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 0022 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] QUOTATION MARK (QU) ÷ [0.3]
× 200D × 0020 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [0.3]
× 200D × 0020 × 0020 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) × [7.01] SPACE (SP) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [0.3]
-× 200D × 0308 × 0020 × 0020 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [7.01] SPACE (SP) ÷ [0.3]
-× 200D × 002F ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [13.04] SOLIDUS (SY) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [0.3]
+× 200D × 0308 × 0020 × 0020 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [7.01] SPACE (SP) ÷ [0.3]
+× 200D × 002F ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] SOLIDUS (SY) ÷ [0.3]
× 200D × 0020 × 002F ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) × [13.02] SOLIDUS (SY) ÷ [0.3]
-× 200D × 0308 × 002F ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [13.04] SOLIDUS (SY) ÷ [0.3]
-× 200D × 0308 × 0020 × 002F ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [13.02] SOLIDUS (SY) ÷ [0.3]
-× 200D × 2060 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [11.01] WORD JOINER (WJ) ÷ [0.3]
+× 200D × 0308 × 002F ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [13.04] SOLIDUS (SY) ÷ [0.3]
+× 200D × 0308 × 0020 × 002F ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [13.02] SOLIDUS (SY) ÷ [0.3]
+× 200D × 2060 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] WORD JOINER (WJ) ÷ [0.3]
× 200D × 0020 × 2060 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) × [11.01] WORD JOINER (WJ) ÷ [0.3]
-× 200D × 0308 × 2060 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [11.01] WORD JOINER (WJ) ÷ [0.3]
-× 200D × 0308 × 0020 × 2060 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [11.01] WORD JOINER (WJ) ÷ [0.3]
+× 200D × 0308 × 2060 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [11.01] WORD JOINER (WJ) ÷ [0.3]
+× 200D × 0308 × 0020 × 2060 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [11.01] WORD JOINER (WJ) ÷ [0.3]
× 200D × 200B ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.02] ZERO WIDTH SPACE (ZW) ÷ [0.3]
× 200D × 0020 × 200B ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) × [7.02] ZERO WIDTH SPACE (ZW) ÷ [0.3]
-× 200D × 0308 × 200B ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.02] ZERO WIDTH SPACE (ZW) ÷ [0.3]
-× 200D × 0308 × 0020 × 200B ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [7.02] ZERO WIDTH SPACE (ZW) ÷ [0.3]
-× 200D ÷ 1F1E6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+× 200D × 0308 × 200B ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.02] ZERO WIDTH SPACE (ZW) ÷ [0.3]
+× 200D × 0308 × 0020 × 200B ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) × [7.02] ZERO WIDTH SPACE (ZW) ÷ [0.3]
+× 200D × 1F1E6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
× 200D × 0020 ÷ 1F1E6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-× 200D × 0308 ÷ 1F1E6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 1F1E6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+× 200D × 0308 ÷ 1F1E6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 1F1E6 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] REGIONAL INDICATOR SYMBOL LETTER A (RI) ÷ [0.3]
× 200D × 261D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] WHITE UP POINTING INDEX (EB) ÷ [0.3]
× 200D × 0020 ÷ 261D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] WHITE UP POINTING INDEX (EB) ÷ [0.3]
-× 200D × 0308 ÷ 261D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] WHITE UP POINTING INDEX (EB) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 261D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] WHITE UP POINTING INDEX (EB) ÷ [0.3]
+× 200D × 0308 ÷ 261D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] WHITE UP POINTING INDEX (EB) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 261D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] WHITE UP POINTING INDEX (EB) ÷ [0.3]
× 200D × 1F3FB ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (EM) ÷ [0.3]
× 200D × 0020 ÷ 1F3FB ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (EM) ÷ [0.3]
-× 200D × 0308 ÷ 1F3FB ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (EM) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 1F3FB ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (EM) ÷ [0.3]
-× 200D × 0001 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] <START OF HEADING> (CM1_CM) ÷ [0.3]
+× 200D × 0308 ÷ 1F3FB ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) ÷ [999.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (EM) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 1F3FB ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] EMOJI MODIFIER FITZPATRICK TYPE-1-2 (EM) ÷ [0.3]
+× 200D × 0001 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] <START OF HEADING> (CM1_CM) ÷ [0.3]
× 200D × 0020 ÷ 0001 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] <START OF HEADING> (CM1_CM) ÷ [0.3]
-× 200D × 0308 × 0001 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [9.0] <START OF HEADING> (CM1_CM) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 0001 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] <START OF HEADING> (CM1_CM) ÷ [0.3]
-× 200D × 200D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [0.3]
+× 200D × 0308 × 0001 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [9.0] <START OF HEADING> (CM1_CM) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 0001 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] <START OF HEADING> (CM1_CM) ÷ [0.3]
+× 200D × 200D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [0.3]
× 200D × 0020 ÷ 200D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [0.3]
-× 200D × 0308 × 200D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [9.0] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 200D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [0.3]
-× 200D × 00A7 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [28.0] SECTION SIGN (AI_AL) ÷ [0.3]
+× 200D × 0308 × 200D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [9.0] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 200D ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) ÷ [0.3]
+× 200D × 00A7 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] SECTION SIGN (AI_AL) ÷ [0.3]
× 200D × 0020 ÷ 00A7 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] SECTION SIGN (AI_AL) ÷ [0.3]
-× 200D × 0308 × 00A7 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [28.0] SECTION SIGN (AI_AL) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 00A7 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] SECTION SIGN (AI_AL) ÷ [0.3]
-× 200D × 50005 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [28.0] <reserved-50005> (XX_AL) ÷ [0.3]
+× 200D × 0308 × 00A7 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [28.0] SECTION SIGN (AI_AL) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 00A7 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] SECTION SIGN (AI_AL) ÷ [0.3]
+× 200D × 50005 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] <reserved-50005> (XX_AL) ÷ [0.3]
× 200D × 0020 ÷ 50005 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] <reserved-50005> (XX_AL) ÷ [0.3]
-× 200D × 0308 × 50005 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [28.0] <reserved-50005> (XX_AL) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 50005 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] <reserved-50005> (XX_AL) ÷ [0.3]
-× 200D × 0E01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [28.0] THAI CHARACTER KO KAI (SA_AL) ÷ [0.3]
+× 200D × 0308 × 50005 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [28.0] <reserved-50005> (XX_AL) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 50005 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] <reserved-50005> (XX_AL) ÷ [0.3]
+× 200D × 0E01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] THAI CHARACTER KO KAI (SA_AL) ÷ [0.3]
× 200D × 0020 ÷ 0E01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] THAI CHARACTER KO KAI (SA_AL) ÷ [0.3]
-× 200D × 0308 × 0E01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [28.0] THAI CHARACTER KO KAI (SA_AL) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 0E01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] THAI CHARACTER KO KAI (SA_AL) ÷ [0.3]
-× 200D × 3041 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [21.03] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
+× 200D × 0308 × 0E01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [28.0] THAI CHARACTER KO KAI (SA_AL) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 0E01 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] THAI CHARACTER KO KAI (SA_AL) ÷ [0.3]
+× 200D × 3041 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
× 200D × 0020 ÷ 3041 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [18.0] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
-× 200D × 0308 × 3041 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [21.03] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
-× 200D × 0308 × 0020 ÷ 3041 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
+× 200D × 0308 × 3041 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [21.03] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
+× 200D × 0308 × 0020 ÷ 3041 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
× 00A7 × 0023 ÷ # × [0.3] SECTION SIGN (AI_AL) × [28.0] NUMBER SIGN (AL) ÷ [0.3]
× 00A7 × 0020 ÷ 0023 ÷ # × [0.3] SECTION SIGN (AI_AL) × [7.01] SPACE (SP) ÷ [18.0] NUMBER SIGN (AL) ÷ [0.3]
× 00A7 × 0308 × 0023 ÷ # × [0.3] SECTION SIGN (AI_AL) × [9.0] COMBINING DIAERESIS (CM1_CM) × [28.0] NUMBER SIGN (AL) ÷ [0.3]
@@ -7084,7 +7084,7 @@
× 3041 × 0308 × 0020 ÷ 3041 ÷ # × [0.3] HIRAGANA LETTER SMALL A (CJ_NS) × [9.0] COMBINING DIAERESIS (CM1_CM) × [7.01] SPACE (SP) ÷ [18.0] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
× 000D × 000A ÷ 0061 × 000A ÷ 0308 ÷ # × [0.3] <CARRIAGE RETURN (CR)> (CR) × [5.01] <LINE FEED (LF)> (LF) ÷ [5.03] LATIN SMALL LETTER A (AL) × [6.0] <LINE FEED (LF)> (LF) ÷ [5.03] COMBINING DIAERESIS (CM1_CM) ÷ [0.3]
× 0061 × 0308 ÷ # × [0.3] LATIN SMALL LETTER A (AL) × [9.0] COMBINING DIAERESIS (CM1_CM) ÷ [0.3]
-× 0020 ÷ 200D × 0646 ÷ # × [0.3] SPACE (SP) ÷ [18.0] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [28.0] ARABIC LETTER NOON (AL) ÷ [0.3]
+× 0020 ÷ 200D × 0646 ÷ # × [0.3] SPACE (SP) ÷ [18.0] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] ARABIC LETTER NOON (AL) ÷ [0.3]
× 0646 × 200D × 0020 ÷ # × [0.3] ARABIC LETTER NOON (AL) × [9.0] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [7.01] SPACE (SP) ÷ [0.3]
× 000B ÷ 3041 ÷ # × [0.3] <LINE TABULATION> (BK) ÷ [4.0] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
× 000D ÷ 3041 ÷ # × [0.3] <CARRIAGE RETURN (CR)> (CR) ÷ [5.02] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
@@ -7093,8 +7093,8 @@
× 3041 × 2060 ÷ # × [0.3] HIRAGANA LETTER SMALL A (CJ_NS) × [11.01] WORD JOINER (WJ) ÷ [0.3]
× 2060 × 3041 ÷ # × [0.3] WORD JOINER (WJ) × [11.02] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
× 3041 × 0308 × 00A0 ÷ # × [0.3] HIRAGANA LETTER SMALL A (CJ_NS) × [9.0] COMBINING DIAERESIS (CM1_CM) × [12.2] NO-BREAK SPACE (GL) ÷ [0.3]
-× 200D × 00A0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [12.3] NO-BREAK SPACE (GL) ÷ [0.3]
-× 200D × 002F ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [13.04] SOLIDUS (SY) ÷ [0.3]
+× 200D × 00A0 ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] NO-BREAK SPACE (GL) ÷ [0.3]
+× 200D × 002F ÷ # × [0.3] ZERO WIDTH JOINER (ZWJ_O_ZWJ_CM) × [8.1] SOLIDUS (SY) ÷ [0.3]
× 2014 × 2014 ÷ # × [0.3] EM DASH (B2) × [17.0] EM DASH (B2) ÷ [0.3]
× 3041 ÷ FFFC ÷ # × [0.3] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [20.01] OBJECT REPLACEMENT CHARACTER (CB) ÷ [0.3]
× FFFC ÷ 3041 ÷ # × [0.3] OBJECT REPLACEMENT CHARACTER (CB) ÷ [20.02] HIRAGANA LETTER SMALL A (CJ_NS) ÷ [0.3]
diff --git a/lib/stdlib/test/unicode_util_SUITE_data/NormalizationTest.txt b/lib/stdlib/test/unicode_util_SUITE_data/NormalizationTest.txt
index 71f2371c5e..72a31bcdf1 100644
--- a/lib/stdlib/test/unicode_util_SUITE_data/NormalizationTest.txt
+++ b/lib/stdlib/test/unicode_util_SUITE_data/NormalizationTest.txt
@@ -1,6 +1,6 @@
-# NormalizationTest-10.0.0.txt
-# Date: 2017-03-08, 08:41:55 GMT
-# © 2017 Unicode®, Inc.
+# NormalizationTest-11.0.0.txt
+# Date: 2018-02-19, 18:33:08 GMT
+# © 2018 Unicode®, Inc.
# Unicode and the Unicode Logo are registered trademarks of Unicode, Inc. in the U.S. and other countries.
# For terms of use, see http://www.unicode.org/terms_of_use.html
#
@@ -17479,6 +17479,8 @@ FFEE;FFEE;FFEE;25CB;25CB; # (○; ○; ○; ○; ○; ) HALFWIDTH WHITE CIRCLE
0061 07F2 059A 0316 302A 0062;0061 302A 07F2 0316 059A 0062;0061 302A 07F2 0316 059A 0062;0061 302A 07F2 0316 059A 0062;0061 302A 07F2 0316 059A 0062; # (a◌߲◌֚◌̖◌〪b; a◌〪◌߲◌̖◌֚b; a◌〪◌߲◌̖◌֚b; a◌〪◌߲◌̖◌֚b; a◌〪◌߲◌̖◌֚b; ) LATIN SMALL LETTER A, NKO COMBINING NASALIZATION MARK, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, LATIN SMALL LETTER B
0061 0315 0300 05AE 07F3 0062;00E0 05AE 07F3 0315 0062;0061 05AE 0300 07F3 0315 0062;00E0 05AE 07F3 0315 0062;0061 05AE 0300 07F3 0315 0062; # (a◌̕◌̀◌֮◌߳b; à◌֮◌߳◌̕b; a◌֮◌̀◌߳◌̕b; à◌֮◌߳◌̕b; a◌֮◌̀◌߳◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, NKO COMBINING DOUBLE DOT ABOVE, LATIN SMALL LETTER B
0061 07F3 0315 0300 05AE 0062;0061 05AE 07F3 0300 0315 0062;0061 05AE 07F3 0300 0315 0062;0061 05AE 07F3 0300 0315 0062;0061 05AE 07F3 0300 0315 0062; # (a◌߳◌̕◌̀◌֮b; a◌֮◌߳◌̀◌̕b; a◌֮◌߳◌̀◌̕b; a◌֮◌߳◌̀◌̕b; a◌֮◌߳◌̀◌̕b; ) LATIN SMALL LETTER A, NKO COMBINING DOUBLE DOT ABOVE, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
+0061 059A 0316 302A 07FD 0062;0061 302A 0316 07FD 059A 0062;0061 302A 0316 07FD 059A 0062;0061 302A 0316 07FD 059A 0062;0061 302A 0316 07FD 059A 0062; # (a◌֚◌̖◌〪◌߽b; a◌〪◌̖◌߽◌֚b; a◌〪◌̖◌߽◌֚b; a◌〪◌̖◌߽◌֚b; a◌〪◌̖◌߽◌֚b; ) LATIN SMALL LETTER A, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, NKO DANTAYALAN, LATIN SMALL LETTER B
+0061 07FD 059A 0316 302A 0062;0061 302A 07FD 0316 059A 0062;0061 302A 07FD 0316 059A 0062;0061 302A 07FD 0316 059A 0062;0061 302A 07FD 0316 059A 0062; # (a◌߽◌֚◌̖◌〪b; a◌〪◌߽◌̖◌֚b; a◌〪◌߽◌̖◌֚b; a◌〪◌߽◌̖◌֚b; a◌〪◌߽◌̖◌֚b; ) LATIN SMALL LETTER A, NKO DANTAYALAN, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, LATIN SMALL LETTER B
0061 0315 0300 05AE 0816 0062;00E0 05AE 0816 0315 0062;0061 05AE 0300 0816 0315 0062;00E0 05AE 0816 0315 0062;0061 05AE 0300 0816 0315 0062; # (a◌̕◌̀◌֮◌ࠖb; à◌֮◌ࠖ◌̕b; a◌֮◌̀◌ࠖ◌̕b; à◌֮◌ࠖ◌̕b; a◌֮◌̀◌ࠖ◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, SAMARITAN MARK IN, LATIN SMALL LETTER B
0061 0816 0315 0300 05AE 0062;0061 05AE 0816 0300 0315 0062;0061 05AE 0816 0300 0315 0062;0061 05AE 0816 0300 0315 0062;0061 05AE 0816 0300 0315 0062; # (a◌ࠖ◌̕◌̀◌֮b; a◌֮◌ࠖ◌̀◌̕b; a◌֮◌ࠖ◌̀◌̕b; a◌֮◌ࠖ◌̀◌̕b; a◌֮◌ࠖ◌̀◌̕b; ) LATIN SMALL LETTER A, SAMARITAN MARK IN, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
0061 0315 0300 05AE 0817 0062;00E0 05AE 0817 0315 0062;0061 05AE 0300 0817 0315 0062;00E0 05AE 0817 0315 0062;0061 05AE 0300 0817 0315 0062; # (a◌̕◌̀◌֮◌ࠗb; à◌֮◌ࠗ◌̕b; a◌֮◌̀◌ࠗ◌̕b; à◌֮◌ࠗ◌̕b; a◌֮◌̀◌ࠗ◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, SAMARITAN MARK IN-ALAF, LATIN SMALL LETTER B
@@ -17527,6 +17529,8 @@ FFEE;FFEE;FFEE;25CB;25CB; # (○; ○; ○; ○; ○; ) HALFWIDTH WHITE CIRCLE
0061 085A 059A 0316 302A 0062;0061 302A 085A 0316 059A 0062;0061 302A 085A 0316 059A 0062;0061 302A 085A 0316 059A 0062;0061 302A 085A 0316 059A 0062; # (a◌࡚◌֚◌̖◌〪b; a◌〪◌࡚◌̖◌֚b; a◌〪◌࡚◌̖◌֚b; a◌〪◌࡚◌̖◌֚b; a◌〪◌࡚◌̖◌֚b; ) LATIN SMALL LETTER A, MANDAIC VOCALIZATION MARK, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, LATIN SMALL LETTER B
0061 059A 0316 302A 085B 0062;0061 302A 0316 085B 059A 0062;0061 302A 0316 085B 059A 0062;0061 302A 0316 085B 059A 0062;0061 302A 0316 085B 059A 0062; # (a◌֚◌̖◌〪◌࡛b; a◌〪◌̖◌࡛◌֚b; a◌〪◌̖◌࡛◌֚b; a◌〪◌̖◌࡛◌֚b; a◌〪◌̖◌࡛◌֚b; ) LATIN SMALL LETTER A, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, MANDAIC GEMINATION MARK, LATIN SMALL LETTER B
0061 085B 059A 0316 302A 0062;0061 302A 085B 0316 059A 0062;0061 302A 085B 0316 059A 0062;0061 302A 085B 0316 059A 0062;0061 302A 085B 0316 059A 0062; # (a◌࡛◌֚◌̖◌〪b; a◌〪◌࡛◌̖◌֚b; a◌〪◌࡛◌̖◌֚b; a◌〪◌࡛◌̖◌֚b; a◌〪◌࡛◌̖◌֚b; ) LATIN SMALL LETTER A, MANDAIC GEMINATION MARK, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, LATIN SMALL LETTER B
+0061 059A 0316 302A 08D3 0062;0061 302A 0316 08D3 059A 0062;0061 302A 0316 08D3 059A 0062;0061 302A 0316 08D3 059A 0062;0061 302A 0316 08D3 059A 0062; # (a◌֚◌̖◌〪◌࣓b; a◌〪◌̖◌࣓◌֚b; a◌〪◌̖◌࣓◌֚b; a◌〪◌̖◌࣓◌֚b; a◌〪◌̖◌࣓◌֚b; ) LATIN SMALL LETTER A, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, ARABIC SMALL LOW WAW, LATIN SMALL LETTER B
+0061 08D3 059A 0316 302A 0062;0061 302A 08D3 0316 059A 0062;0061 302A 08D3 0316 059A 0062;0061 302A 08D3 0316 059A 0062;0061 302A 08D3 0316 059A 0062; # (a◌࣓◌֚◌̖◌〪b; a◌〪◌࣓◌̖◌֚b; a◌〪◌࣓◌̖◌֚b; a◌〪◌࣓◌̖◌֚b; a◌〪◌࣓◌̖◌֚b; ) LATIN SMALL LETTER A, ARABIC SMALL LOW WAW, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, LATIN SMALL LETTER B
0061 0315 0300 05AE 08D4 0062;00E0 05AE 08D4 0315 0062;0061 05AE 0300 08D4 0315 0062;00E0 05AE 08D4 0315 0062;0061 05AE 0300 08D4 0315 0062; # (a◌̕◌̀◌֮◌ࣔb; à◌֮◌ࣔ◌̕b; a◌֮◌̀◌ࣔ◌̕b; à◌֮◌ࣔ◌̕b; a◌֮◌̀◌ࣔ◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, ARABIC SMALL HIGH WORD AR-RUB, LATIN SMALL LETTER B
0061 08D4 0315 0300 05AE 0062;0061 05AE 08D4 0300 0315 0062;0061 05AE 08D4 0300 0315 0062;0061 05AE 08D4 0300 0315 0062;0061 05AE 08D4 0300 0315 0062; # (a◌ࣔ◌̕◌̀◌֮b; a◌֮◌ࣔ◌̀◌̕b; a◌֮◌ࣔ◌̀◌̕b; a◌֮◌ࣔ◌̀◌̕b; a◌֮◌ࣔ◌̀◌̕b; ) LATIN SMALL LETTER A, ARABIC SMALL HIGH WORD AR-RUB, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
0061 0315 0300 05AE 08D5 0062;00E0 05AE 08D5 0315 0062;0061 05AE 0300 08D5 0315 0062;00E0 05AE 08D5 0315 0062;0061 05AE 0300 08D5 0315 0062; # (a◌̕◌̀◌֮◌ࣕb; à◌֮◌ࣕ◌̕b; a◌֮◌̀◌ࣕ◌̕b; à◌֮◌ࣕ◌̕b; a◌֮◌̀◌ࣕ◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, ARABIC SMALL HIGH SAD, LATIN SMALL LETTER B
@@ -17629,6 +17633,8 @@ FFEE;FFEE;FFEE;25CB;25CB; # (○; ○; ○; ○; ○; ) HALFWIDTH WHITE CIRCLE
0061 09BC 3099 093C 0334 0062;0061 0334 09BC 093C 3099 0062;0061 0334 09BC 093C 3099 0062;0061 0334 09BC 093C 3099 0062;0061 0334 09BC 093C 3099 0062; # (a◌়◌゙◌़◌̴b; a◌̴◌়◌़◌゙b; a◌̴◌়◌़◌゙b; a◌̴◌়◌़◌゙b; a◌̴◌়◌़◌゙b; ) LATIN SMALL LETTER A, BENGALI SIGN NUKTA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, LATIN SMALL LETTER B
0061 05B0 094D 3099 09CD 0062;0061 3099 094D 09CD 05B0 0062;0061 3099 094D 09CD 05B0 0062;0061 3099 094D 09CD 05B0 0062;0061 3099 094D 09CD 05B0 0062; # (a◌ְ◌्◌゙◌্b; a◌゙◌्◌্◌ְb; a◌゙◌्◌্◌ְb; a◌゙◌्◌্◌ְb; a◌゙◌्◌্◌ְb; ) LATIN SMALL LETTER A, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, BENGALI SIGN VIRAMA, LATIN SMALL LETTER B
0061 09CD 05B0 094D 3099 0062;0061 3099 09CD 094D 05B0 0062;0061 3099 09CD 094D 05B0 0062;0061 3099 09CD 094D 05B0 0062;0061 3099 09CD 094D 05B0 0062; # (a◌্◌ְ◌्◌゙b; a◌゙◌্◌्◌ְb; a◌゙◌্◌्◌ְb; a◌゙◌্◌्◌ְb; a◌゙◌্◌्◌ְb; ) LATIN SMALL LETTER A, BENGALI SIGN VIRAMA, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, LATIN SMALL LETTER B
+0061 0315 0300 05AE 09FE 0062;00E0 05AE 09FE 0315 0062;0061 05AE 0300 09FE 0315 0062;00E0 05AE 09FE 0315 0062;0061 05AE 0300 09FE 0315 0062; # (a◌̕◌̀◌֮◌৾b; à◌֮◌৾◌̕b; a◌֮◌̀◌৾◌̕b; à◌֮◌৾◌̕b; a◌֮◌̀◌৾◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, BENGALI SANDHI MARK, LATIN SMALL LETTER B
+0061 09FE 0315 0300 05AE 0062;0061 05AE 09FE 0300 0315 0062;0061 05AE 09FE 0300 0315 0062;0061 05AE 09FE 0300 0315 0062;0061 05AE 09FE 0300 0315 0062; # (a◌৾◌̕◌̀◌֮b; a◌֮◌৾◌̀◌̕b; a◌֮◌৾◌̀◌̕b; a◌֮◌৾◌̀◌̕b; a◌֮◌৾◌̀◌̕b; ) LATIN SMALL LETTER A, BENGALI SANDHI MARK, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
0061 3099 093C 0334 0A3C 0062;0061 0334 093C 0A3C 3099 0062;0061 0334 093C 0A3C 3099 0062;0061 0334 093C 0A3C 3099 0062;0061 0334 093C 0A3C 3099 0062; # (a◌゙◌़◌̴◌਼b; a◌̴◌़◌਼◌゙b; a◌̴◌़◌਼◌゙b; a◌̴◌़◌਼◌゙b; a◌̴◌़◌਼◌゙b; ) LATIN SMALL LETTER A, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, GURMUKHI SIGN NUKTA, LATIN SMALL LETTER B
0061 0A3C 3099 093C 0334 0062;0061 0334 0A3C 093C 3099 0062;0061 0334 0A3C 093C 3099 0062;0061 0334 0A3C 093C 3099 0062;0061 0334 0A3C 093C 3099 0062; # (a◌਼◌゙◌़◌̴b; a◌̴◌਼◌़◌゙b; a◌̴◌਼◌़◌゙b; a◌̴◌਼◌़◌゙b; a◌̴◌਼◌़◌゙b; ) LATIN SMALL LETTER A, GURMUKHI SIGN NUKTA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, LATIN SMALL LETTER B
0061 05B0 094D 3099 0A4D 0062;0061 3099 094D 0A4D 05B0 0062;0061 3099 094D 0A4D 05B0 0062;0061 3099 094D 0A4D 05B0 0062;0061 3099 094D 0A4D 05B0 0062; # (a◌ְ◌्◌゙◌੍b; a◌゙◌्◌੍◌ְb; a◌゙◌्◌੍◌ְb; a◌゙◌्◌੍◌ְb; a◌゙◌्◌੍◌ְb; ) LATIN SMALL LETTER A, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, GURMUKHI SIGN VIRAMA, LATIN SMALL LETTER B
@@ -18329,6 +18335,36 @@ FFEE;FFEE;FFEE;25CB;25CB; # (○; ○; ○; ○; ○; ) HALFWIDTH WHITE CIRCLE
0061 10AE5 0315 0300 05AE 0062;0061 05AE 10AE5 0300 0315 0062;0061 05AE 10AE5 0300 0315 0062;0061 05AE 10AE5 0300 0315 0062;0061 05AE 10AE5 0300 0315 0062; # (a◌𐫥◌̕◌̀◌֮b; a◌֮◌𐫥◌̀◌̕b; a◌֮◌𐫥◌̀◌̕b; a◌֮◌𐫥◌̀◌̕b; a◌֮◌𐫥◌̀◌̕b; ) LATIN SMALL LETTER A, MANICHAEAN ABBREVIATION MARK ABOVE, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
0061 059A 0316 302A 10AE6 0062;0061 302A 0316 10AE6 059A 0062;0061 302A 0316 10AE6 059A 0062;0061 302A 0316 10AE6 059A 0062;0061 302A 0316 10AE6 059A 0062; # (a◌֚◌̖◌〪◌𐫦b; a◌〪◌̖◌𐫦◌֚b; a◌〪◌̖◌𐫦◌֚b; a◌〪◌̖◌𐫦◌֚b; a◌〪◌̖◌𐫦◌֚b; ) LATIN SMALL LETTER A, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, MANICHAEAN ABBREVIATION MARK BELOW, LATIN SMALL LETTER B
0061 10AE6 059A 0316 302A 0062;0061 302A 10AE6 0316 059A 0062;0061 302A 10AE6 0316 059A 0062;0061 302A 10AE6 0316 059A 0062;0061 302A 10AE6 0316 059A 0062; # (a◌𐫦◌֚◌̖◌〪b; a◌〪◌𐫦◌̖◌֚b; a◌〪◌𐫦◌̖◌֚b; a◌〪◌𐫦◌̖◌֚b; a◌〪◌𐫦◌̖◌֚b; ) LATIN SMALL LETTER A, MANICHAEAN ABBREVIATION MARK BELOW, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, LATIN SMALL LETTER B
+0061 0315 0300 05AE 10D24 0062;00E0 05AE 10D24 0315 0062;0061 05AE 0300 10D24 0315 0062;00E0 05AE 10D24 0315 0062;0061 05AE 0300 10D24 0315 0062; # (a◌̕◌̀◌֮◌𐴤b; à◌֮◌𐴤◌̕b; a◌֮◌̀◌𐴤◌̕b; à◌֮◌𐴤◌̕b; a◌֮◌̀◌𐴤◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, HANIFI ROHINGYA SIGN HARBAHAY, LATIN SMALL LETTER B
+0061 10D24 0315 0300 05AE 0062;0061 05AE 10D24 0300 0315 0062;0061 05AE 10D24 0300 0315 0062;0061 05AE 10D24 0300 0315 0062;0061 05AE 10D24 0300 0315 0062; # (a◌𐴤◌̕◌̀◌֮b; a◌֮◌𐴤◌̀◌̕b; a◌֮◌𐴤◌̀◌̕b; a◌֮◌𐴤◌̀◌̕b; a◌֮◌𐴤◌̀◌̕b; ) LATIN SMALL LETTER A, HANIFI ROHINGYA SIGN HARBAHAY, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
+0061 0315 0300 05AE 10D25 0062;00E0 05AE 10D25 0315 0062;0061 05AE 0300 10D25 0315 0062;00E0 05AE 10D25 0315 0062;0061 05AE 0300 10D25 0315 0062; # (a◌̕◌̀◌֮◌𐴥b; à◌֮◌𐴥◌̕b; a◌֮◌̀◌𐴥◌̕b; à◌֮◌𐴥◌̕b; a◌֮◌̀◌𐴥◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, HANIFI ROHINGYA SIGN TAHALA, LATIN SMALL LETTER B
+0061 10D25 0315 0300 05AE 0062;0061 05AE 10D25 0300 0315 0062;0061 05AE 10D25 0300 0315 0062;0061 05AE 10D25 0300 0315 0062;0061 05AE 10D25 0300 0315 0062; # (a◌𐴥◌̕◌̀◌֮b; a◌֮◌𐴥◌̀◌̕b; a◌֮◌𐴥◌̀◌̕b; a◌֮◌𐴥◌̀◌̕b; a◌֮◌𐴥◌̀◌̕b; ) LATIN SMALL LETTER A, HANIFI ROHINGYA SIGN TAHALA, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
+0061 0315 0300 05AE 10D26 0062;00E0 05AE 10D26 0315 0062;0061 05AE 0300 10D26 0315 0062;00E0 05AE 10D26 0315 0062;0061 05AE 0300 10D26 0315 0062; # (a◌̕◌̀◌֮◌𐴦b; à◌֮◌𐴦◌̕b; a◌֮◌̀◌𐴦◌̕b; à◌֮◌𐴦◌̕b; a◌֮◌̀◌𐴦◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, HANIFI ROHINGYA SIGN TANA, LATIN SMALL LETTER B
+0061 10D26 0315 0300 05AE 0062;0061 05AE 10D26 0300 0315 0062;0061 05AE 10D26 0300 0315 0062;0061 05AE 10D26 0300 0315 0062;0061 05AE 10D26 0300 0315 0062; # (a◌𐴦◌̕◌̀◌֮b; a◌֮◌𐴦◌̀◌̕b; a◌֮◌𐴦◌̀◌̕b; a◌֮◌𐴦◌̀◌̕b; a◌֮◌𐴦◌̀◌̕b; ) LATIN SMALL LETTER A, HANIFI ROHINGYA SIGN TANA, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
+0061 0315 0300 05AE 10D27 0062;00E0 05AE 10D27 0315 0062;0061 05AE 0300 10D27 0315 0062;00E0 05AE 10D27 0315 0062;0061 05AE 0300 10D27 0315 0062; # (a◌̕◌̀◌֮◌𐴧b; à◌֮◌𐴧◌̕b; a◌֮◌̀◌𐴧◌̕b; à◌֮◌𐴧◌̕b; a◌֮◌̀◌𐴧◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, HANIFI ROHINGYA SIGN TASSI, LATIN SMALL LETTER B
+0061 10D27 0315 0300 05AE 0062;0061 05AE 10D27 0300 0315 0062;0061 05AE 10D27 0300 0315 0062;0061 05AE 10D27 0300 0315 0062;0061 05AE 10D27 0300 0315 0062; # (a◌𐴧◌̕◌̀◌֮b; a◌֮◌𐴧◌̀◌̕b; a◌֮◌𐴧◌̀◌̕b; a◌֮◌𐴧◌̀◌̕b; a◌֮◌𐴧◌̀◌̕b; ) LATIN SMALL LETTER A, HANIFI ROHINGYA SIGN TASSI, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
+0061 059A 0316 302A 10F46 0062;0061 302A 0316 10F46 059A 0062;0061 302A 0316 10F46 059A 0062;0061 302A 0316 10F46 059A 0062;0061 302A 0316 10F46 059A 0062; # (a◌֚◌̖◌〪◌𐽆b; a◌〪◌̖◌𐽆◌֚b; a◌〪◌̖◌𐽆◌֚b; a◌〪◌̖◌𐽆◌֚b; a◌〪◌̖◌𐽆◌֚b; ) LATIN SMALL LETTER A, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, SOGDIAN COMBINING DOT BELOW, LATIN SMALL LETTER B
+0061 10F46 059A 0316 302A 0062;0061 302A 10F46 0316 059A 0062;0061 302A 10F46 0316 059A 0062;0061 302A 10F46 0316 059A 0062;0061 302A 10F46 0316 059A 0062; # (a◌𐽆◌֚◌̖◌〪b; a◌〪◌𐽆◌̖◌֚b; a◌〪◌𐽆◌̖◌֚b; a◌〪◌𐽆◌̖◌֚b; a◌〪◌𐽆◌̖◌֚b; ) LATIN SMALL LETTER A, SOGDIAN COMBINING DOT BELOW, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, LATIN SMALL LETTER B
+0061 059A 0316 302A 10F47 0062;0061 302A 0316 10F47 059A 0062;0061 302A 0316 10F47 059A 0062;0061 302A 0316 10F47 059A 0062;0061 302A 0316 10F47 059A 0062; # (a◌֚◌̖◌〪◌𐽇b; a◌〪◌̖◌𐽇◌֚b; a◌〪◌̖◌𐽇◌֚b; a◌〪◌̖◌𐽇◌֚b; a◌〪◌̖◌𐽇◌֚b; ) LATIN SMALL LETTER A, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, SOGDIAN COMBINING TWO DOTS BELOW, LATIN SMALL LETTER B
+0061 10F47 059A 0316 302A 0062;0061 302A 10F47 0316 059A 0062;0061 302A 10F47 0316 059A 0062;0061 302A 10F47 0316 059A 0062;0061 302A 10F47 0316 059A 0062; # (a◌𐽇◌֚◌̖◌〪b; a◌〪◌𐽇◌̖◌֚b; a◌〪◌𐽇◌̖◌֚b; a◌〪◌𐽇◌̖◌֚b; a◌〪◌𐽇◌̖◌֚b; ) LATIN SMALL LETTER A, SOGDIAN COMBINING TWO DOTS BELOW, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, LATIN SMALL LETTER B
+0061 0315 0300 05AE 10F48 0062;00E0 05AE 10F48 0315 0062;0061 05AE 0300 10F48 0315 0062;00E0 05AE 10F48 0315 0062;0061 05AE 0300 10F48 0315 0062; # (a◌̕◌̀◌֮◌𐽈b; à◌֮◌𐽈◌̕b; a◌֮◌̀◌𐽈◌̕b; à◌֮◌𐽈◌̕b; a◌֮◌̀◌𐽈◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, SOGDIAN COMBINING DOT ABOVE, LATIN SMALL LETTER B
+0061 10F48 0315 0300 05AE 0062;0061 05AE 10F48 0300 0315 0062;0061 05AE 10F48 0300 0315 0062;0061 05AE 10F48 0300 0315 0062;0061 05AE 10F48 0300 0315 0062; # (a◌𐽈◌̕◌̀◌֮b; a◌֮◌𐽈◌̀◌̕b; a◌֮◌𐽈◌̀◌̕b; a◌֮◌𐽈◌̀◌̕b; a◌֮◌𐽈◌̀◌̕b; ) LATIN SMALL LETTER A, SOGDIAN COMBINING DOT ABOVE, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
+0061 0315 0300 05AE 10F49 0062;00E0 05AE 10F49 0315 0062;0061 05AE 0300 10F49 0315 0062;00E0 05AE 10F49 0315 0062;0061 05AE 0300 10F49 0315 0062; # (a◌̕◌̀◌֮◌𐽉b; à◌֮◌𐽉◌̕b; a◌֮◌̀◌𐽉◌̕b; à◌֮◌𐽉◌̕b; a◌֮◌̀◌𐽉◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, SOGDIAN COMBINING TWO DOTS ABOVE, LATIN SMALL LETTER B
+0061 10F49 0315 0300 05AE 0062;0061 05AE 10F49 0300 0315 0062;0061 05AE 10F49 0300 0315 0062;0061 05AE 10F49 0300 0315 0062;0061 05AE 10F49 0300 0315 0062; # (a◌𐽉◌̕◌̀◌֮b; a◌֮◌𐽉◌̀◌̕b; a◌֮◌𐽉◌̀◌̕b; a◌֮◌𐽉◌̀◌̕b; a◌֮◌𐽉◌̀◌̕b; ) LATIN SMALL LETTER A, SOGDIAN COMBINING TWO DOTS ABOVE, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
+0061 0315 0300 05AE 10F4A 0062;00E0 05AE 10F4A 0315 0062;0061 05AE 0300 10F4A 0315 0062;00E0 05AE 10F4A 0315 0062;0061 05AE 0300 10F4A 0315 0062; # (a◌̕◌̀◌֮◌𐽊b; à◌֮◌𐽊◌̕b; a◌֮◌̀◌𐽊◌̕b; à◌֮◌𐽊◌̕b; a◌֮◌̀◌𐽊◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, SOGDIAN COMBINING CURVE ABOVE, LATIN SMALL LETTER B
+0061 10F4A 0315 0300 05AE 0062;0061 05AE 10F4A 0300 0315 0062;0061 05AE 10F4A 0300 0315 0062;0061 05AE 10F4A 0300 0315 0062;0061 05AE 10F4A 0300 0315 0062; # (a◌𐽊◌̕◌̀◌֮b; a◌֮◌𐽊◌̀◌̕b; a◌֮◌𐽊◌̀◌̕b; a◌֮◌𐽊◌̀◌̕b; a◌֮◌𐽊◌̀◌̕b; ) LATIN SMALL LETTER A, SOGDIAN COMBINING CURVE ABOVE, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
+0061 059A 0316 302A 10F4B 0062;0061 302A 0316 10F4B 059A 0062;0061 302A 0316 10F4B 059A 0062;0061 302A 0316 10F4B 059A 0062;0061 302A 0316 10F4B 059A 0062; # (a◌֚◌̖◌〪◌𐽋b; a◌〪◌̖◌𐽋◌֚b; a◌〪◌̖◌𐽋◌֚b; a◌〪◌̖◌𐽋◌֚b; a◌〪◌̖◌𐽋◌֚b; ) LATIN SMALL LETTER A, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, SOGDIAN COMBINING CURVE BELOW, LATIN SMALL LETTER B
+0061 10F4B 059A 0316 302A 0062;0061 302A 10F4B 0316 059A 0062;0061 302A 10F4B 0316 059A 0062;0061 302A 10F4B 0316 059A 0062;0061 302A 10F4B 0316 059A 0062; # (a◌𐽋◌֚◌̖◌〪b; a◌〪◌𐽋◌̖◌֚b; a◌〪◌𐽋◌̖◌֚b; a◌〪◌𐽋◌̖◌֚b; a◌〪◌𐽋◌̖◌֚b; ) LATIN SMALL LETTER A, SOGDIAN COMBINING CURVE BELOW, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, LATIN SMALL LETTER B
+0061 0315 0300 05AE 10F4C 0062;00E0 05AE 10F4C 0315 0062;0061 05AE 0300 10F4C 0315 0062;00E0 05AE 10F4C 0315 0062;0061 05AE 0300 10F4C 0315 0062; # (a◌̕◌̀◌֮◌𐽌b; à◌֮◌𐽌◌̕b; a◌֮◌̀◌𐽌◌̕b; à◌֮◌𐽌◌̕b; a◌֮◌̀◌𐽌◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, SOGDIAN COMBINING HOOK ABOVE, LATIN SMALL LETTER B
+0061 10F4C 0315 0300 05AE 0062;0061 05AE 10F4C 0300 0315 0062;0061 05AE 10F4C 0300 0315 0062;0061 05AE 10F4C 0300 0315 0062;0061 05AE 10F4C 0300 0315 0062; # (a◌𐽌◌̕◌̀◌֮b; a◌֮◌𐽌◌̀◌̕b; a◌֮◌𐽌◌̀◌̕b; a◌֮◌𐽌◌̀◌̕b; a◌֮◌𐽌◌̀◌̕b; ) LATIN SMALL LETTER A, SOGDIAN COMBINING HOOK ABOVE, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
+0061 059A 0316 302A 10F4D 0062;0061 302A 0316 10F4D 059A 0062;0061 302A 0316 10F4D 059A 0062;0061 302A 0316 10F4D 059A 0062;0061 302A 0316 10F4D 059A 0062; # (a◌֚◌̖◌〪◌𐽍b; a◌〪◌̖◌𐽍◌֚b; a◌〪◌̖◌𐽍◌֚b; a◌〪◌̖◌𐽍◌֚b; a◌〪◌̖◌𐽍◌֚b; ) LATIN SMALL LETTER A, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, SOGDIAN COMBINING HOOK BELOW, LATIN SMALL LETTER B
+0061 10F4D 059A 0316 302A 0062;0061 302A 10F4D 0316 059A 0062;0061 302A 10F4D 0316 059A 0062;0061 302A 10F4D 0316 059A 0062;0061 302A 10F4D 0316 059A 0062; # (a◌𐽍◌֚◌̖◌〪b; a◌〪◌𐽍◌̖◌֚b; a◌〪◌𐽍◌̖◌֚b; a◌〪◌𐽍◌̖◌֚b; a◌〪◌𐽍◌̖◌֚b; ) LATIN SMALL LETTER A, SOGDIAN COMBINING HOOK BELOW, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, LATIN SMALL LETTER B
+0061 059A 0316 302A 10F4E 0062;0061 302A 0316 10F4E 059A 0062;0061 302A 0316 10F4E 059A 0062;0061 302A 0316 10F4E 059A 0062;0061 302A 0316 10F4E 059A 0062; # (a◌֚◌̖◌〪◌𐽎b; a◌〪◌̖◌𐽎◌֚b; a◌〪◌̖◌𐽎◌֚b; a◌〪◌̖◌𐽎◌֚b; a◌〪◌̖◌𐽎◌֚b; ) LATIN SMALL LETTER A, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, SOGDIAN COMBINING LONG HOOK BELOW, LATIN SMALL LETTER B
+0061 10F4E 059A 0316 302A 0062;0061 302A 10F4E 0316 059A 0062;0061 302A 10F4E 0316 059A 0062;0061 302A 10F4E 0316 059A 0062;0061 302A 10F4E 0316 059A 0062; # (a◌𐽎◌֚◌̖◌〪b; a◌〪◌𐽎◌̖◌֚b; a◌〪◌𐽎◌̖◌֚b; a◌〪◌𐽎◌̖◌֚b; a◌〪◌𐽎◌̖◌֚b; ) LATIN SMALL LETTER A, SOGDIAN COMBINING LONG HOOK BELOW, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, LATIN SMALL LETTER B
+0061 059A 0316 302A 10F4F 0062;0061 302A 0316 10F4F 059A 0062;0061 302A 0316 10F4F 059A 0062;0061 302A 0316 10F4F 059A 0062;0061 302A 0316 10F4F 059A 0062; # (a◌֚◌̖◌〪◌𐽏b; a◌〪◌̖◌𐽏◌֚b; a◌〪◌̖◌𐽏◌֚b; a◌〪◌̖◌𐽏◌֚b; a◌〪◌̖◌𐽏◌֚b; ) LATIN SMALL LETTER A, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, SOGDIAN COMBINING RESH BELOW, LATIN SMALL LETTER B
+0061 10F4F 059A 0316 302A 0062;0061 302A 10F4F 0316 059A 0062;0061 302A 10F4F 0316 059A 0062;0061 302A 10F4F 0316 059A 0062;0061 302A 10F4F 0316 059A 0062; # (a◌𐽏◌֚◌̖◌〪b; a◌〪◌𐽏◌̖◌֚b; a◌〪◌𐽏◌̖◌֚b; a◌〪◌𐽏◌̖◌֚b; a◌〪◌𐽏◌̖◌֚b; ) LATIN SMALL LETTER A, SOGDIAN COMBINING RESH BELOW, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, LATIN SMALL LETTER B
+0061 059A 0316 302A 10F50 0062;0061 302A 0316 10F50 059A 0062;0061 302A 0316 10F50 059A 0062;0061 302A 0316 10F50 059A 0062;0061 302A 0316 10F50 059A 0062; # (a◌֚◌̖◌〪◌𐽐b; a◌〪◌̖◌𐽐◌֚b; a◌〪◌̖◌𐽐◌֚b; a◌〪◌̖◌𐽐◌֚b; a◌〪◌̖◌𐽐◌֚b; ) LATIN SMALL LETTER A, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, SOGDIAN COMBINING STROKE BELOW, LATIN SMALL LETTER B
+0061 10F50 059A 0316 302A 0062;0061 302A 10F50 0316 059A 0062;0061 302A 10F50 0316 059A 0062;0061 302A 10F50 0316 059A 0062;0061 302A 10F50 0316 059A 0062; # (a◌𐽐◌֚◌̖◌〪b; a◌〪◌𐽐◌̖◌֚b; a◌〪◌𐽐◌̖◌֚b; a◌〪◌𐽐◌̖◌֚b; a◌〪◌𐽐◌̖◌֚b; ) LATIN SMALL LETTER A, SOGDIAN COMBINING STROKE BELOW, HEBREW ACCENT YETIV, COMBINING GRAVE ACCENT BELOW, IDEOGRAPHIC LEVEL TONE MARK, LATIN SMALL LETTER B
0061 05B0 094D 3099 11046 0062;0061 3099 094D 11046 05B0 0062;0061 3099 094D 11046 05B0 0062;0061 3099 094D 11046 05B0 0062;0061 3099 094D 11046 05B0 0062; # (a◌ְ◌्◌゙◌𑁆b; a◌゙◌्◌𑁆◌ְb; a◌゙◌्◌𑁆◌ְb; a◌゙◌्◌𑁆◌ְb; a◌゙◌्◌𑁆◌ְb; ) LATIN SMALL LETTER A, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, BRAHMI VIRAMA, LATIN SMALL LETTER B
0061 11046 05B0 094D 3099 0062;0061 3099 11046 094D 05B0 0062;0061 3099 11046 094D 05B0 0062;0061 3099 11046 094D 05B0 0062;0061 3099 11046 094D 05B0 0062; # (a◌𑁆◌ְ◌्◌゙b; a◌゙◌𑁆◌्◌ְb; a◌゙◌𑁆◌्◌ְb; a◌゙◌𑁆◌्◌ְb; a◌゙◌𑁆◌्◌ְb; ) LATIN SMALL LETTER A, BRAHMI VIRAMA, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, LATIN SMALL LETTER B
0061 05B0 094D 3099 1107F 0062;0061 3099 094D 1107F 05B0 0062;0061 3099 094D 1107F 05B0 0062;0061 3099 094D 1107F 05B0 0062;0061 3099 094D 1107F 05B0 0062; # (a◌ְ◌्◌゙◌𑁿b; a◌゙◌्◌𑁿◌ְb; a◌゙◌्◌𑁿◌ְb; a◌゙◌्◌𑁿◌ְb; a◌゙◌्◌𑁿◌ְb; ) LATIN SMALL LETTER A, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, BRAHMI NUMBER JOINER, LATIN SMALL LETTER B
@@ -18361,6 +18397,8 @@ FFEE;FFEE;FFEE;25CB;25CB; # (○; ○; ○; ○; ○; ) HALFWIDTH WHITE CIRCLE
0061 112E9 3099 093C 0334 0062;0061 0334 112E9 093C 3099 0062;0061 0334 112E9 093C 3099 0062;0061 0334 112E9 093C 3099 0062;0061 0334 112E9 093C 3099 0062; # (a◌𑋩◌゙◌़◌̴b; a◌̴◌𑋩◌़◌゙b; a◌̴◌𑋩◌़◌゙b; a◌̴◌𑋩◌़◌゙b; a◌̴◌𑋩◌़◌゙b; ) LATIN SMALL LETTER A, KHUDAWADI SIGN NUKTA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, LATIN SMALL LETTER B
0061 05B0 094D 3099 112EA 0062;0061 3099 094D 112EA 05B0 0062;0061 3099 094D 112EA 05B0 0062;0061 3099 094D 112EA 05B0 0062;0061 3099 094D 112EA 05B0 0062; # (a◌ְ◌्◌゙◌𑋪b; a◌゙◌्◌𑋪◌ְb; a◌゙◌्◌𑋪◌ְb; a◌゙◌्◌𑋪◌ְb; a◌゙◌्◌𑋪◌ְb; ) LATIN SMALL LETTER A, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, KHUDAWADI SIGN VIRAMA, LATIN SMALL LETTER B
0061 112EA 05B0 094D 3099 0062;0061 3099 112EA 094D 05B0 0062;0061 3099 112EA 094D 05B0 0062;0061 3099 112EA 094D 05B0 0062;0061 3099 112EA 094D 05B0 0062; # (a◌𑋪◌ְ◌्◌゙b; a◌゙◌𑋪◌्◌ְb; a◌゙◌𑋪◌्◌ְb; a◌゙◌𑋪◌्◌ְb; a◌゙◌𑋪◌्◌ְb; ) LATIN SMALL LETTER A, KHUDAWADI SIGN VIRAMA, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, LATIN SMALL LETTER B
+0061 3099 093C 0334 1133B 0062;0061 0334 093C 1133B 3099 0062;0061 0334 093C 1133B 3099 0062;0061 0334 093C 1133B 3099 0062;0061 0334 093C 1133B 3099 0062; # (a◌゙◌़◌̴◌𑌻b; a◌̴◌़◌𑌻◌゙b; a◌̴◌़◌𑌻◌゙b; a◌̴◌़◌𑌻◌゙b; a◌̴◌़◌𑌻◌゙b; ) LATIN SMALL LETTER A, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, COMBINING BINDU BELOW, LATIN SMALL LETTER B
+0061 1133B 3099 093C 0334 0062;0061 0334 1133B 093C 3099 0062;0061 0334 1133B 093C 3099 0062;0061 0334 1133B 093C 3099 0062;0061 0334 1133B 093C 3099 0062; # (a◌𑌻◌゙◌़◌̴b; a◌̴◌𑌻◌़◌゙b; a◌̴◌𑌻◌़◌゙b; a◌̴◌𑌻◌़◌゙b; a◌̴◌𑌻◌़◌゙b; ) LATIN SMALL LETTER A, COMBINING BINDU BELOW, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, LATIN SMALL LETTER B
0061 3099 093C 0334 1133C 0062;0061 0334 093C 1133C 3099 0062;0061 0334 093C 1133C 3099 0062;0061 0334 093C 1133C 3099 0062;0061 0334 093C 1133C 3099 0062; # (a◌゙◌़◌̴◌𑌼b; a◌̴◌़◌𑌼◌゙b; a◌̴◌़◌𑌼◌゙b; a◌̴◌़◌𑌼◌゙b; a◌̴◌़◌𑌼◌゙b; ) LATIN SMALL LETTER A, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, GRANTHA SIGN NUKTA, LATIN SMALL LETTER B
0061 1133C 3099 093C 0334 0062;0061 0334 1133C 093C 3099 0062;0061 0334 1133C 093C 3099 0062;0061 0334 1133C 093C 3099 0062;0061 0334 1133C 093C 3099 0062; # (a◌𑌼◌゙◌़◌̴b; a◌̴◌𑌼◌़◌゙b; a◌̴◌𑌼◌़◌゙b; a◌̴◌𑌼◌़◌゙b; a◌̴◌𑌼◌़◌゙b; ) LATIN SMALL LETTER A, GRANTHA SIGN NUKTA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, LATIN SMALL LETTER B
0061 05B0 094D 3099 1134D 0062;0061 3099 094D 1134D 05B0 0062;0061 3099 094D 1134D 05B0 0062;0061 3099 094D 1134D 05B0 0062;0061 3099 094D 1134D 05B0 0062; # (a◌ְ◌्◌゙𑍍b; a◌゙◌्𑍍◌ְb; a◌゙◌्𑍍◌ְb; a◌゙◌्𑍍◌ְb; a◌゙◌्𑍍◌ְb; ) LATIN SMALL LETTER A, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, GRANTHA SIGN VIRAMA, LATIN SMALL LETTER B
@@ -18393,6 +18431,8 @@ FFEE;FFEE;FFEE;25CB;25CB; # (○; ○; ○; ○; ○; ) HALFWIDTH WHITE CIRCLE
0061 11442 05B0 094D 3099 0062;0061 3099 11442 094D 05B0 0062;0061 3099 11442 094D 05B0 0062;0061 3099 11442 094D 05B0 0062;0061 3099 11442 094D 05B0 0062; # (a◌𑑂◌ְ◌्◌゙b; a◌゙◌𑑂◌्◌ְb; a◌゙◌𑑂◌्◌ְb; a◌゙◌𑑂◌्◌ְb; a◌゙◌𑑂◌्◌ְb; ) LATIN SMALL LETTER A, NEWA SIGN VIRAMA, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, LATIN SMALL LETTER B
0061 3099 093C 0334 11446 0062;0061 0334 093C 11446 3099 0062;0061 0334 093C 11446 3099 0062;0061 0334 093C 11446 3099 0062;0061 0334 093C 11446 3099 0062; # (a◌゙◌़◌̴◌𑑆b; a◌̴◌़◌𑑆◌゙b; a◌̴◌़◌𑑆◌゙b; a◌̴◌़◌𑑆◌゙b; a◌̴◌़◌𑑆◌゙b; ) LATIN SMALL LETTER A, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, NEWA SIGN NUKTA, LATIN SMALL LETTER B
0061 11446 3099 093C 0334 0062;0061 0334 11446 093C 3099 0062;0061 0334 11446 093C 3099 0062;0061 0334 11446 093C 3099 0062;0061 0334 11446 093C 3099 0062; # (a◌𑑆◌゙◌़◌̴b; a◌̴◌𑑆◌़◌゙b; a◌̴◌𑑆◌़◌゙b; a◌̴◌𑑆◌़◌゙b; a◌̴◌𑑆◌़◌゙b; ) LATIN SMALL LETTER A, NEWA SIGN NUKTA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, LATIN SMALL LETTER B
+0061 0315 0300 05AE 1145E 0062;00E0 05AE 1145E 0315 0062;0061 05AE 0300 1145E 0315 0062;00E0 05AE 1145E 0315 0062;0061 05AE 0300 1145E 0315 0062; # (a◌̕◌̀◌֮◌𑑞b; à◌֮◌𑑞◌̕b; a◌֮◌̀◌𑑞◌̕b; à◌֮◌𑑞◌̕b; a◌֮◌̀◌𑑞◌̕b; ) LATIN SMALL LETTER A, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, NEWA SANDHI MARK, LATIN SMALL LETTER B
+0061 1145E 0315 0300 05AE 0062;0061 05AE 1145E 0300 0315 0062;0061 05AE 1145E 0300 0315 0062;0061 05AE 1145E 0300 0315 0062;0061 05AE 1145E 0300 0315 0062; # (a◌𑑞◌̕◌̀◌֮b; a◌֮◌𑑞◌̀◌̕b; a◌֮◌𑑞◌̀◌̕b; a◌֮◌𑑞◌̀◌̕b; a◌֮◌𑑞◌̀◌̕b; ) LATIN SMALL LETTER A, NEWA SANDHI MARK, COMBINING COMMA ABOVE RIGHT, COMBINING GRAVE ACCENT, HEBREW ACCENT ZINOR, LATIN SMALL LETTER B
0061 05B0 094D 3099 114C2 0062;0061 3099 094D 114C2 05B0 0062;0061 3099 094D 114C2 05B0 0062;0061 3099 094D 114C2 05B0 0062;0061 3099 094D 114C2 05B0 0062; # (a◌ְ◌्◌゙◌𑓂b; a◌゙◌्◌𑓂◌ְb; a◌゙◌्◌𑓂◌ְb; a◌゙◌्◌𑓂◌ְb; a◌゙◌्◌𑓂◌ְb; ) LATIN SMALL LETTER A, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, TIRHUTA SIGN VIRAMA, LATIN SMALL LETTER B
0061 114C2 05B0 094D 3099 0062;0061 3099 114C2 094D 05B0 0062;0061 3099 114C2 094D 05B0 0062;0061 3099 114C2 094D 05B0 0062;0061 3099 114C2 094D 05B0 0062; # (a◌𑓂◌ְ◌्◌゙b; a◌゙◌𑓂◌्◌ְb; a◌゙◌𑓂◌्◌ְb; a◌゙◌𑓂◌्◌ְb; a◌゙◌𑓂◌्◌ְb; ) LATIN SMALL LETTER A, TIRHUTA SIGN VIRAMA, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, LATIN SMALL LETTER B
0061 3099 093C 0334 114C3 0062;0061 0334 093C 114C3 3099 0062;0061 0334 093C 114C3 3099 0062;0061 0334 093C 114C3 3099 0062;0061 0334 093C 114C3 3099 0062; # (a◌゙◌़◌̴◌𑓃b; a◌̴◌़◌𑓃◌゙b; a◌̴◌़◌𑓃◌゙b; a◌̴◌़◌𑓃◌゙b; a◌̴◌़◌𑓃◌゙b; ) LATIN SMALL LETTER A, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, TIRHUTA SIGN NUKTA, LATIN SMALL LETTER B
@@ -18409,6 +18449,10 @@ FFEE;FFEE;FFEE;25CB;25CB; # (○; ○; ○; ○; ○; ) HALFWIDTH WHITE CIRCLE
0061 116B7 3099 093C 0334 0062;0061 0334 116B7 093C 3099 0062;0061 0334 116B7 093C 3099 0062;0061 0334 116B7 093C 3099 0062;0061 0334 116B7 093C 3099 0062; # (a◌𑚷◌゙◌़◌̴b; a◌̴◌𑚷◌़◌゙b; a◌̴◌𑚷◌़◌゙b; a◌̴◌𑚷◌़◌゙b; a◌̴◌𑚷◌़◌゙b; ) LATIN SMALL LETTER A, TAKRI SIGN NUKTA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, LATIN SMALL LETTER B
0061 05B0 094D 3099 1172B 0062;0061 3099 094D 1172B 05B0 0062;0061 3099 094D 1172B 05B0 0062;0061 3099 094D 1172B 05B0 0062;0061 3099 094D 1172B 05B0 0062; # (a◌ְ◌्◌゙◌𑜫b; a◌゙◌्◌𑜫◌ְb; a◌゙◌्◌𑜫◌ְb; a◌゙◌्◌𑜫◌ְb; a◌゙◌्◌𑜫◌ְb; ) LATIN SMALL LETTER A, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, AHOM SIGN KILLER, LATIN SMALL LETTER B
0061 1172B 05B0 094D 3099 0062;0061 3099 1172B 094D 05B0 0062;0061 3099 1172B 094D 05B0 0062;0061 3099 1172B 094D 05B0 0062;0061 3099 1172B 094D 05B0 0062; # (a◌𑜫◌ְ◌्◌゙b; a◌゙◌𑜫◌्◌ְb; a◌゙◌𑜫◌्◌ְb; a◌゙◌𑜫◌्◌ְb; a◌゙◌𑜫◌्◌ְb; ) LATIN SMALL LETTER A, AHOM SIGN KILLER, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, LATIN SMALL LETTER B
+0061 05B0 094D 3099 11839 0062;0061 3099 094D 11839 05B0 0062;0061 3099 094D 11839 05B0 0062;0061 3099 094D 11839 05B0 0062;0061 3099 094D 11839 05B0 0062; # (a◌ְ◌्◌゙◌𑠹b; a◌゙◌्◌𑠹◌ְb; a◌゙◌्◌𑠹◌ְb; a◌゙◌्◌𑠹◌ְb; a◌゙◌्◌𑠹◌ְb; ) LATIN SMALL LETTER A, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DOGRA SIGN VIRAMA, LATIN SMALL LETTER B
+0061 11839 05B0 094D 3099 0062;0061 3099 11839 094D 05B0 0062;0061 3099 11839 094D 05B0 0062;0061 3099 11839 094D 05B0 0062;0061 3099 11839 094D 05B0 0062; # (a◌𑠹◌ְ◌्◌゙b; a◌゙◌𑠹◌्◌ְb; a◌゙◌𑠹◌्◌ְb; a◌゙◌𑠹◌्◌ְb; a◌゙◌𑠹◌्◌ְb; ) LATIN SMALL LETTER A, DOGRA SIGN VIRAMA, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, LATIN SMALL LETTER B
+0061 3099 093C 0334 1183A 0062;0061 0334 093C 1183A 3099 0062;0061 0334 093C 1183A 3099 0062;0061 0334 093C 1183A 3099 0062;0061 0334 093C 1183A 3099 0062; # (a◌゙◌़◌̴◌𑠺b; a◌̴◌़◌𑠺◌゙b; a◌̴◌़◌𑠺◌゙b; a◌̴◌़◌𑠺◌゙b; a◌̴◌़◌𑠺◌゙b; ) LATIN SMALL LETTER A, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, DOGRA SIGN NUKTA, LATIN SMALL LETTER B
+0061 1183A 3099 093C 0334 0062;0061 0334 1183A 093C 3099 0062;0061 0334 1183A 093C 3099 0062;0061 0334 1183A 093C 3099 0062;0061 0334 1183A 093C 3099 0062; # (a◌𑠺◌゙◌़◌̴b; a◌̴◌𑠺◌़◌゙b; a◌̴◌𑠺◌़◌゙b; a◌̴◌𑠺◌़◌゙b; a◌̴◌𑠺◌़◌゙b; ) LATIN SMALL LETTER A, DOGRA SIGN NUKTA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, LATIN SMALL LETTER B
0061 05B0 094D 3099 11A34 0062;0061 3099 094D 11A34 05B0 0062;0061 3099 094D 11A34 05B0 0062;0061 3099 094D 11A34 05B0 0062;0061 3099 094D 11A34 05B0 0062; # (a◌ְ◌्◌゙◌𑨴b; a◌゙◌्◌𑨴◌ְb; a◌゙◌्◌𑨴◌ְb; a◌゙◌्◌𑨴◌ְb; a◌゙◌्◌𑨴◌ְb; ) LATIN SMALL LETTER A, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, ZANABAZAR SQUARE SIGN VIRAMA, LATIN SMALL LETTER B
0061 11A34 05B0 094D 3099 0062;0061 3099 11A34 094D 05B0 0062;0061 3099 11A34 094D 05B0 0062;0061 3099 11A34 094D 05B0 0062;0061 3099 11A34 094D 05B0 0062; # (a◌𑨴◌ְ◌्◌゙b; a◌゙◌𑨴◌्◌ְb; a◌゙◌𑨴◌्◌ְb; a◌゙◌𑨴◌्◌ְb; a◌゙◌𑨴◌्◌ְb; ) LATIN SMALL LETTER A, ZANABAZAR SQUARE SIGN VIRAMA, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, LATIN SMALL LETTER B
0061 05B0 094D 3099 11A47 0062;0061 3099 094D 11A47 05B0 0062;0061 3099 094D 11A47 05B0 0062;0061 3099 094D 11A47 05B0 0062;0061 3099 094D 11A47 05B0 0062; # (a◌ְ◌्◌゙◌𑩇b; a◌゙◌्◌𑩇◌ְb; a◌゙◌्◌𑩇◌ְb; a◌゙◌्◌𑩇◌ְb; a◌゙◌्◌𑩇◌ְb; ) LATIN SMALL LETTER A, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, ZANABAZAR SQUARE SUBJOINER, LATIN SMALL LETTER B
@@ -18423,6 +18467,8 @@ FFEE;FFEE;FFEE;25CB;25CB; # (○; ○; ○; ○; ○; ) HALFWIDTH WHITE CIRCLE
0061 11D44 05B0 094D 3099 0062;0061 3099 11D44 094D 05B0 0062;0061 3099 11D44 094D 05B0 0062;0061 3099 11D44 094D 05B0 0062;0061 3099 11D44 094D 05B0 0062; # (a◌𑵄◌ְ◌्◌゙b; a◌゙◌𑵄◌्◌ְb; a◌゙◌𑵄◌्◌ְb; a◌゙◌𑵄◌्◌ְb; a◌゙◌𑵄◌्◌ְb; ) LATIN SMALL LETTER A, MASARAM GONDI SIGN HALANTA, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, LATIN SMALL LETTER B
0061 05B0 094D 3099 11D45 0062;0061 3099 094D 11D45 05B0 0062;0061 3099 094D 11D45 05B0 0062;0061 3099 094D 11D45 05B0 0062;0061 3099 094D 11D45 05B0 0062; # (a◌ְ◌्◌゙◌𑵅b; a◌゙◌्◌𑵅◌ְb; a◌゙◌्◌𑵅◌ְb; a◌゙◌्◌𑵅◌ְb; a◌゙◌्◌𑵅◌ְb; ) LATIN SMALL LETTER A, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, MASARAM GONDI VIRAMA, LATIN SMALL LETTER B
0061 11D45 05B0 094D 3099 0062;0061 3099 11D45 094D 05B0 0062;0061 3099 11D45 094D 05B0 0062;0061 3099 11D45 094D 05B0 0062;0061 3099 11D45 094D 05B0 0062; # (a◌𑵅◌ְ◌्◌゙b; a◌゙◌𑵅◌्◌ְb; a◌゙◌𑵅◌्◌ְb; a◌゙◌𑵅◌्◌ְb; a◌゙◌𑵅◌्◌ְb; ) LATIN SMALL LETTER A, MASARAM GONDI VIRAMA, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, LATIN SMALL LETTER B
+0061 05B0 094D 3099 11D97 0062;0061 3099 094D 11D97 05B0 0062;0061 3099 094D 11D97 05B0 0062;0061 3099 094D 11D97 05B0 0062;0061 3099 094D 11D97 05B0 0062; # (a◌ְ◌्◌゙◌𑶗b; a◌゙◌्◌𑶗◌ְb; a◌゙◌्◌𑶗◌ְb; a◌゙◌्◌𑶗◌ְb; a◌゙◌्◌𑶗◌ְb; ) LATIN SMALL LETTER A, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, GUNJALA GONDI VIRAMA, LATIN SMALL LETTER B
+0061 11D97 05B0 094D 3099 0062;0061 3099 11D97 094D 05B0 0062;0061 3099 11D97 094D 05B0 0062;0061 3099 11D97 094D 05B0 0062;0061 3099 11D97 094D 05B0 0062; # (a◌𑶗◌ְ◌्◌゙b; a◌゙◌𑶗◌्◌ְb; a◌゙◌𑶗◌्◌ְb; a◌゙◌𑶗◌्◌ְb; a◌゙◌𑶗◌्◌ְb; ) LATIN SMALL LETTER A, GUNJALA GONDI VIRAMA, HEBREW POINT SHEVA, DEVANAGARI SIGN VIRAMA, COMBINING KATAKANA-HIRAGANA VOICED SOUND MARK, LATIN SMALL LETTER B
0061 093C 0334 16AF0 0062;0061 0334 16AF0 093C 0062;0061 0334 16AF0 093C 0062;0061 0334 16AF0 093C 0062;0061 0334 16AF0 093C 0062; # (a◌़◌̴◌𖫰b; a◌̴◌𖫰◌़b; a◌̴◌𖫰◌़b; a◌̴◌𖫰◌़b; a◌̴◌𖫰◌़b; ) LATIN SMALL LETTER A, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, BASSA VAH COMBINING HIGH TONE, LATIN SMALL LETTER B
0061 16AF0 093C 0334 0062;0061 16AF0 0334 093C 0062;0061 16AF0 0334 093C 0062;0061 16AF0 0334 093C 0062;0061 16AF0 0334 093C 0062; # (a◌𖫰◌़◌̴b; a◌𖫰◌̴◌़b; a◌𖫰◌̴◌़b; a◌𖫰◌̴◌़b; a◌𖫰◌̴◌़b; ) LATIN SMALL LETTER A, BASSA VAH COMBINING HIGH TONE, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, LATIN SMALL LETTER B
0061 093C 0334 16AF1 0062;0061 0334 16AF1 093C 0062;0061 0334 16AF1 093C 0062;0061 0334 16AF1 093C 0062;0061 0334 16AF1 093C 0062; # (a◌़◌̴◌𖫱b; a◌̴◌𖫱◌़b; a◌̴◌𖫱◌़b; a◌̴◌𖫱◌़b; a◌̴◌𖫱◌़b; ) LATIN SMALL LETTER A, DEVANAGARI SIGN NUKTA, COMBINING TILDE OVERLAY, BASSA VAH COMBINING LOW TONE, LATIN SMALL LETTER B
diff --git a/lib/stdlib/test/uri_string_SUITE.erl b/lib/stdlib/test/uri_string_SUITE.erl
index 4fc0d76be8..ddaead9c7c 100644
--- a/lib/stdlib/test/uri_string_SUITE.erl
+++ b/lib/stdlib/test/uri_string_SUITE.erl
@@ -862,9 +862,11 @@ transcode_negative(_Config) ->
compose_query(_Config) ->
[] = uri_string:compose_query([]),
"foo=1&bar=2" = uri_string:compose_query([{<<"foo">>,"1"}, {"bar", "2"}]),
+ "foo=1&bar" = uri_string:compose_query([{<<"foo">>,"1"}, {"bar", true}]),
"foo=1&b%C3%A4r=2" = uri_string:compose_query([{"foo","1"}, {"bär", "2"}],[{encoding,utf8}]),
"foo=1&b%C3%A4r=2" = uri_string:compose_query([{"foo","1"}, {"bär", "2"}],[{encoding,unicode}]),
"foo=1&b%E4r=2" = uri_string:compose_query([{"foo","1"}, {"bär", "2"}],[{encoding,latin1}]),
+ "foo&b%E4r=2" = uri_string:compose_query([{"foo",true}, {"bär", "2"}],[{encoding,latin1}]),
"foo+bar=1&%E5%90%88=2" = uri_string:compose_query([{"foo bar","1"}, {"合", "2"}]),
"foo+bar=1&%26%2321512%3B=2" =
uri_string:compose_query([{"foo bar","1"}, {"合", "2"}],[{encoding,latin1}]),
@@ -906,11 +908,13 @@ dissect_query(_Config) ->
[{"föo bar","1"},{"ö","2"}] =
uri_string:dissect_query("föo+bar=1&%C3%B6=2"),
[{<<"föo bar"/utf8>>,<<"1">>},{<<"ö"/utf8>>,<<"2">>}] =
- uri_string:dissect_query(<<"föo+bar=1&%C3%B6=2"/utf8>>).
+ uri_string:dissect_query(<<"föo+bar=1&%C3%B6=2"/utf8>>),
+ [{"foo1",true},{"bar","2"}] =
+ uri_string:dissect_query("foo1&bar=2"),
+ [{<<"foo1">>,<<"1">>},{<<"bar">>,true}] =
+ uri_string:dissect_query(<<"foo1=1&bar">>).
dissect_query_negative(_Config) ->
- {error,missing_value,"&"} =
- uri_string:dissect_query("foo1&bar=2"),
{error,invalid_percent_encoding,"%XX%B6"} = uri_string:dissect_query("foo=%XX%B6&amp;bar=2"),
{error,invalid_input,[153]} =
uri_string:dissect_query("foo=%99%B6&amp;bar=2"),