aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/ExpandTestCaps.erl32
-rw-r--r--lib/stdlib/test/ExpandTestCaps1.erl44
-rw-r--r--lib/stdlib/test/Makefile5
-rw-r--r--lib/stdlib/test/edlin_expand_SUITE.erl156
-rw-r--r--lib/stdlib/test/expand_test.erl32
-rw-r--r--lib/stdlib/test/expand_test1.erl44
-rw-r--r--lib/stdlib/test/filelib_SUITE.erl10
-rw-r--r--lib/stdlib/test/io_proto_SUITE.erl40
-rw-r--r--lib/stdlib/test/re_SUITE.erl30
-rw-r--r--lib/stdlib/test/re_SUITE_data/mod_testoutput8877
-rw-r--r--lib/stdlib/test/run_pcre_tests.erl50
11 files changed, 1277 insertions, 43 deletions
diff --git a/lib/stdlib/test/ExpandTestCaps.erl b/lib/stdlib/test/ExpandTestCaps.erl
new file mode 100644
index 0000000000..96c4115354
--- /dev/null
+++ b/lib/stdlib/test/ExpandTestCaps.erl
@@ -0,0 +1,32 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2010. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module('ExpandTestCaps').
+
+-export([a_fun_name/1,
+ a_less_fun_name/1,
+ b_comes_after_a/1]).
+
+a_fun_name(X) ->
+ X.
+
+a_less_fun_name(X) ->
+ X.
+
+b_comes_after_a(X) ->
+ X.
diff --git a/lib/stdlib/test/ExpandTestCaps1.erl b/lib/stdlib/test/ExpandTestCaps1.erl
new file mode 100644
index 0000000000..09ee9f81c4
--- /dev/null
+++ b/lib/stdlib/test/ExpandTestCaps1.erl
@@ -0,0 +1,44 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2010. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module('ExpandTestCaps1').
+
+-export([a_fun_name/1,
+ a_less_fun_name/1,
+ b_comes_after_a/1,
+ 'Quoted_fun_name'/0,
+ 'Quoted_fun_too'/0,
+ '#weird-fun-name'/0]).
+
+a_fun_name(X) ->
+ X.
+
+a_less_fun_name(X) ->
+ X.
+
+b_comes_after_a(X) ->
+ X.
+
+'Quoted_fun_name'() ->
+ whoopee.
+
+'Quoted_fun_too'() ->
+ too.
+
+'#weird-fun-name'() ->
+ weird.
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index 7a87eef5f3..ac8cbba375 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -18,6 +18,7 @@ MODULES= \
digraph_utils_SUITE \
dummy1_h \
dummy_h \
+ edlin_expand_SUITE \
epp_SUITE \
erl_eval_helper \
erl_eval_SUITE \
@@ -29,6 +30,10 @@ MODULES= \
escript_SUITE \
ets_SUITE \
ets_tough_SUITE \
+ expand_test \
+ expand_test1 \
+ ExpandTestCaps \
+ ExpandTestCaps1 \
filelib_SUITE \
file_sorter_SUITE \
filename_SUITE \
diff --git a/lib/stdlib/test/edlin_expand_SUITE.erl b/lib/stdlib/test/edlin_expand_SUITE.erl
new file mode 100644
index 0000000000..613bfd000e
--- /dev/null
+++ b/lib/stdlib/test/edlin_expand_SUITE.erl
@@ -0,0 +1,156 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2010. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(edlin_expand_SUITE).
+-export([all/1]).
+
+-export([normal/1, quoted_fun/1, quoted_module/1, quoted_both/1]).
+
+-export([init_per_testcase/2, fin_per_testcase/2]).
+
+-include("test_server.hrl").
+
+% Default timetrap timeout (set in init_per_testcase).
+-define(default_timeout, ?t:minutes(1)).
+
+init_per_testcase(_Case, Config) ->
+ ?line Dog = ?t:timetrap(?default_timeout),
+ [{watchdog, Dog} | Config].
+fin_per_testcase(_Case, Config) ->
+ Dog = ?config(watchdog, Config),
+ test_server:timetrap_cancel(Dog),
+ ok.
+
+all(doc) ->
+ ["Test cases for edlin_expand."];
+all(suite) ->
+ [normal, quoted_fun, quoted_module, quoted_both].
+
+normal(doc) ->
+ [""];
+normal(suite) ->
+ [];
+normal(Config) when is_list(Config) ->
+ ?line {module,expand_test} = c:l(expand_test),
+ % These tests might fail if another module with the prefix "expand_" happens
+ % to also be loaded.
+ ?line {yes, "test:", []} = edlin_expand:expand(lists:reverse("expand_")),
+ ?line {no, [], []} = edlin_expand:expand(lists:reverse("expandXX_")),
+ ?line {no,[],
+ [{"a_fun_name",1},
+ {"a_less_fun_name",1},
+ {"b_comes_after_a",1},
+ {"module_info",0},
+ {"module_info",1}]} = edlin_expand:expand(lists:reverse("expand_test:")),
+ ?line {yes,[],[{"a_fun_name",1},
+ {"a_less_fun_name",1}]} = edlin_expand:expand(
+ lists:reverse("expand_test:a_")),
+ ok.
+
+quoted_fun(doc) ->
+ ["Normal module name, some function names using quoted atoms"];
+quoted_fun(suite) ->
+ [];
+quoted_fun(Config) when is_list(Config) ->
+ ?line {module,expand_test} = c:l(expand_test),
+ ?line {module,expand_test1} = c:l(expand_test1),
+ %% should be no colon after test this time
+ ?line {yes, "test", []} = edlin_expand:expand(lists:reverse("expand_")),
+ ?line {no, [], []} = edlin_expand:expand(lists:reverse("expandXX_")),
+ ?line {no,[],[{"'#weird-fun-name'",0},
+ {"'Quoted_fun_name'",0},
+ {"'Quoted_fun_too'",0},
+ {"a_fun_name",1},
+ {"a_less_fun_name",1},
+ {"b_comes_after_a",1},
+ {"module_info",0},
+ {"module_info",1}]} = edlin_expand:expand(
+ lists:reverse("expand_test1:")),
+ ?line {yes,"_",[]} = edlin_expand:expand(
+ lists:reverse("expand_test1:a")),
+ ?line {yes,[],[{"a_fun_name",1},
+ {"a_less_fun_name",1}]} = edlin_expand:expand(
+ lists:reverse("expand_test1:a_")),
+ ?line {yes,[],
+ [{"'#weird-fun-name'",0},
+ {"'Quoted_fun_name'",0},
+ {"'Quoted_fun_too'",0}]} = edlin_expand:expand(
+ lists:reverse("expand_test1:'")),
+ ?line {yes,"uoted_fun_",[]} = edlin_expand:expand(
+ lists:reverse("expand_test1:'Q")),
+ ?line {yes,[],
+ [{"'Quoted_fun_name'",0},
+ {"'Quoted_fun_too'",0}]} = edlin_expand:expand(
+ lists:reverse("expand_test1:'Quoted_fun_")),
+ ?line {yes,"weird-fun-name'(",[]} = edlin_expand:expand(
+ lists:reverse("expand_test1:'#")),
+ ok.
+
+quoted_module(doc) ->
+ [""];
+quoted_module(suite) ->
+ [];
+quoted_module(Config) when is_list(Config) ->
+ ?line {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'),
+ ?line {yes, "Caps':", []} = edlin_expand:expand(lists:reverse("'ExpandTest")),
+ ?line {no,[],
+ [{"a_fun_name",1},
+ {"a_less_fun_name",1},
+ {"b_comes_after_a",1},
+ {"module_info",0},
+ {"module_info",1}]} = edlin_expand:expand(lists:reverse("'ExpandTestCaps':")),
+ ?line {yes,[],[{"a_fun_name",1},
+ {"a_less_fun_name",1}]} = edlin_expand:expand(
+ lists:reverse("'ExpandTestCaps':a_")),
+ ok.
+
+quoted_both(suite) ->
+ [];
+quoted_both(Config) when is_list(Config) ->
+ ?line {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'),
+ ?line {module,'ExpandTestCaps1'} = c:l('ExpandTestCaps1'),
+ %% should be no colon (or quote) after test this time
+ ?line {yes, "Caps", []} = edlin_expand:expand(lists:reverse("'ExpandTest")),
+ ?line {no,[],[{"'#weird-fun-name'",0},
+ {"'Quoted_fun_name'",0},
+ {"'Quoted_fun_too'",0},
+ {"a_fun_name",1},
+ {"a_less_fun_name",1},
+ {"b_comes_after_a",1},
+ {"module_info",0},
+ {"module_info",1}]} = edlin_expand:expand(
+ lists:reverse("'ExpandTestCaps1':")),
+ ?line {yes,"_",[]} = edlin_expand:expand(
+ lists:reverse("'ExpandTestCaps1':a")),
+ ?line {yes,[],[{"a_fun_name",1},
+ {"a_less_fun_name",1}]} = edlin_expand:expand(
+ lists:reverse("'ExpandTestCaps1':a_")),
+ ?line {yes,[],
+ [{"'#weird-fun-name'",0},
+ {"'Quoted_fun_name'",0},
+ {"'Quoted_fun_too'",0}]} = edlin_expand:expand(
+ lists:reverse("'ExpandTestCaps1':'")),
+ ?line {yes,"uoted_fun_",[]} = edlin_expand:expand(
+ lists:reverse("'ExpandTestCaps1':'Q")),
+ ?line {yes,[],
+ [{"'Quoted_fun_name'",0},
+ {"'Quoted_fun_too'",0}]} = edlin_expand:expand(
+ lists:reverse("'ExpandTestCaps1':'Quoted_fun_")),
+ ?line {yes,"weird-fun-name'(",[]} = edlin_expand:expand(
+ lists:reverse("'ExpandTestCaps1':'#")),
+ ok.
diff --git a/lib/stdlib/test/expand_test.erl b/lib/stdlib/test/expand_test.erl
new file mode 100644
index 0000000000..63e4bc3aa0
--- /dev/null
+++ b/lib/stdlib/test/expand_test.erl
@@ -0,0 +1,32 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2010. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(expand_test).
+
+-export([a_fun_name/1,
+ a_less_fun_name/1,
+ b_comes_after_a/1]).
+
+a_fun_name(X) ->
+ X.
+
+a_less_fun_name(X) ->
+ X.
+
+b_comes_after_a(X) ->
+ X.
diff --git a/lib/stdlib/test/expand_test1.erl b/lib/stdlib/test/expand_test1.erl
new file mode 100644
index 0000000000..11b6fec0f3
--- /dev/null
+++ b/lib/stdlib/test/expand_test1.erl
@@ -0,0 +1,44 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2010. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(expand_test1).
+
+-export([a_fun_name/1,
+ a_less_fun_name/1,
+ b_comes_after_a/1,
+ 'Quoted_fun_name'/0,
+ 'Quoted_fun_too'/0,
+ '#weird-fun-name'/0]).
+
+a_fun_name(X) ->
+ X.
+
+a_less_fun_name(X) ->
+ X.
+
+b_comes_after_a(X) ->
+ X.
+
+'Quoted_fun_name'() ->
+ whoopee.
+
+'Quoted_fun_too'() ->
+ too.
+
+'#weird-fun-name'() ->
+ weird.
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index d6abc1fba3..d54741051f 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2005-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 2005-2010. All Rights Reserved.
+%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index 46407193d7..59aa175c73 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 2009-2010. All Rights Reserved.
+%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
-module(io_proto_SUITE).
@@ -48,9 +48,12 @@
-ifdef(debug).
-define(format(S, A), io:format(S, A)).
-define(dbg(Data),io:format(standard_error, "DBG: ~p\r\n",[Data])).
+-define(RM_RF(Dir),begin io:format(standard_error, "Not Removed: ~p\r\n",[Dir]),
+ ok end).
-else.
-define(format(S, A), ok).
-define(dbg(Data),noop).
+-define(RM_RF(Dir),rm_rf(Dir)).
-endif.
@@ -197,6 +200,15 @@ setopts_getopts(Config) when is_list(Config) ->
{getline_re, ".*<<\"hej\\\\n\">>"}
],[],[],"-oldshell"),
ok.
+
+
+get_lc_ctype() ->
+ case {os:type(),os:version()} of
+ {{unix,sunos},{5,N,_}} when N =< 8 ->
+ "iso_8859_1";
+ _ ->
+ "ISO-8859-1"
+ end.
unicode_options(suite) ->
[];
@@ -369,7 +381,7 @@ unicode_options(Config) when is_list(Config) ->
{getline,
binary_to_list(unicode:characters_to_binary(
[1024],unicode,utf8))}
- ],[],"LC_CTYPE=\"ISO-8859-1\"; export LC_CTYPE; "),
+ ],[],"LC_CTYPE=\""++get_lc_ctype()++"\"; export LC_CTYPE; "),
?line rtnode([{putline,""},
{putline, "2."},
{getline_re, ".*2."},
@@ -384,7 +396,7 @@ unicode_options(Config) when is_list(Config) ->
{getline_re,
".*"++binary_to_list(unicode:characters_to_binary(
[1024],unicode,utf8))}
- ],[],"LC_CTYPE=\"ISO-8859-1\"; export LC_CTYPE; ",
+ ],[],"LC_CTYPE=\""++get_lc_ctype()++"\"; export LC_CTYPE; ",
" -oldshell "),
ok.
@@ -974,7 +986,7 @@ answering_machine1(OthNode,OthReg,Me) ->
{putline, TestDataUtf},
{getline_re, ".*Okej"}
- ],Me,"LC_CTYPE=\"ISO-8859-1\"; export LC_CTYPE; "),
+ ],Me,"LC_CTYPE=\""++get_lc_ctype()++"\"; export LC_CTYPE; "),
O = list_to_atom(OthReg),
O ! {self(),done},
ok.
@@ -1045,7 +1057,7 @@ answering_machine2(OthNode,OthReg,Me) ->
{putline, TestDataUtf},
{getline_re, ".*Okej"}
- ],Me,"LC_CTYPE=\"ISO-8859-1\"; export LC_CTYPE; "," -oldshell "),
+ ],Me,"LC_CTYPE=\""++get_lc_ctype()++"\"; export LC_CTYPE; "," -oldshell "),
O = list_to_atom(OthReg),
O ! {self(),done},
ok.
@@ -1087,7 +1099,9 @@ read_modes_gl_1(_Config,Machine) ->
[MyNodeList, "io_proto_suite", N2List]),
?line GL = receive X when is_pid(X) -> X end,
+ ?dbg({group_leader,X}),
%% get_line
+ ?line receive after 500 -> ok end, % Dont clash with the new shell...
?line "Hej\n" = io:get_line(GL,"Prompt\n"),
?line io:setopts(GL,[binary]),
?line io:format(GL,"Okej~n",[]),
@@ -1287,7 +1301,7 @@ rtnode(Commands,Nodename,ErlPrefix,Extra) ->
?line ok
end,
?line wait_for_runerl_server(SPid),
- ?line ok = rm_rf(Tempdir),
+ ?line ok = ?RM_RF(Tempdir),
?line ok = Res
end
end.
@@ -1308,7 +1322,7 @@ timeout(normal) ->
%% stop_noshell_node(Node) ->
%% test_server:stop_node(Node).
-
+-ifndef(debug).
rm_rf(Dir) ->
try
{ok,List} = file:list_dir(Dir),
@@ -1324,7 +1338,7 @@ rm_rf(Dir) ->
catch
_:Exception -> {error, {Exception,Dir}}
end.
-
+-endif.
get_and_put(_CPid,[],_) ->
ok;
@@ -1527,6 +1541,8 @@ start_runerl_node(RunErl,Erl,Tempdir,Nodename,Extra) ->
" "++Extra
end,
spawn(fun() ->
+ ?dbg(RunErl++" "++Tempdir++"/ "++Tempdir++" \""++
+ Erl++XArg++XXArg++"\""),
os:cmd(RunErl++" "++Tempdir++"/ "++Tempdir++" \""++
Erl++XArg++XXArg++"\"")
end).
diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl
index 98eb66d1fb..fa50ba3b7a 100644
--- a/lib/stdlib/test/re_SUITE.erl
+++ b/lib/stdlib/test/re_SUITE.erl
@@ -1,29 +1,29 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 2008-2010. All Rights Reserved.
+%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
-module(re_SUITE).
--export([all/1, pcre/1,compile_options/1,run_options/1,combined_options/1,replace_autogen/1,global_capture/1,replace_return/1,split_autogen/1,split_options/1,split_specials/1,error_handling/1]).
+-export([all/1, pcre/1,compile_options/1,run_options/1,combined_options/1,replace_autogen/1,global_capture/1,replace_input_types/1,replace_return/1,split_autogen/1,split_options/1,split_specials/1,error_handling/1]).
-include("test_server.hrl").
-include_lib("kernel/include/file.hrl").
-all(suite) -> [pcre,compile_options,run_options,combined_options,replace_autogen,global_capture,replace_return,split_autogen,split_options,split_specials,error_handling].
+all(suite) -> [pcre,compile_options,run_options,combined_options,replace_autogen,global_capture,replace_input_types,replace_return,split_autogen,split_options,split_specials,error_handling].
pcre(doc) ->
["Run all applicable tests from the PCRE testsuites."];
@@ -268,7 +268,17 @@ global_capture(Config) when is_list(Config) ->
?line {match,[[{3,5},{5,3}],[{11,4},{12,3}]]} = re:run("ABC�bcdABCabcdA",".(?<FOO>bcd)",[global,{capture,all,index},unicode]),
?t:timetrap_cancel(Dog),
ok.
-
+
+replace_input_types(doc) ->
+ ["Tests replace with different input types"];
+replace_input_types(Config) when is_list(Config) ->
+ Dog = ?t:timetrap(?t:minutes(3)),
+ ?line <<"abcd">> = re:replace("abcd","Z","X",[{return,binary},unicode]),
+ ?line <<"abcd">> = re:replace("abcd","\x{400}","X",[{return,binary},unicode]),
+ ?line <<"a",208,128,"cd">> = re:replace(<<"abcd">>,"b","\x{400}",[{return,binary},unicode]),
+ ?t:timetrap_cancel(Dog),
+ ok.
+
replace_return(doc) ->
["Tests return options of replace together with global searching"];
replace_return(Config) when is_list(Config) ->
@@ -289,6 +299,10 @@ replace_return(Config) when is_list(Config) ->
?line <<"iXk">> = re:replace("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\9X",[{return,binary}]),
?line <<"jXk">> = re:replace("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\10X",[{return,binary}]),
?line <<"Xk">> = re:replace("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\11X",[{return,binary}]),
+ ?line "a\x{400}bcX" = re:replace("a\x{400}bcd","d","X",[global,{return,list},unicode]),
+ ?line <<"a",208,128,"bcX">> = re:replace("a\x{400}bcd","d","X",[global,{return,binary},unicode]),
+ ?line "a\x{400}bcd" = re:replace("a\x{400}bcd","Z","X",[global,{return,list},unicode]),
+ ?line <<"a",208,128,"bcd">> = re:replace("a\x{400}bcd","Z","X",[global,{return,binary},unicode]),
?t:timetrap_cancel(Dog),
ok.
diff --git a/lib/stdlib/test/re_SUITE_data/mod_testoutput8 b/lib/stdlib/test/re_SUITE_data/mod_testoutput8
new file mode 100644
index 0000000000..b7e7b02d6c
--- /dev/null
+++ b/lib/stdlib/test/re_SUITE_data/mod_testoutput8
@@ -0,0 +1,877 @@
+/-- Do not use the \x{} construct except with patterns that have the --/
+/-- /8 option set, because PCRE doesn't recognize them as UTF-8 unless --/
+No match
+/-- that option is set. However, the latest Perls recognize them always. --/
+No match
+
+\x{100}ab/8
+ \x{100}ab
+ 0: \x{100}ab
+
+/a\x{100}*b/8
+ ab
+ 0: ab
+ a\x{100}b
+ 0: a\x{100}b
+ a\x{100}\x{100}b
+ 0: a\x{100}\x{100}b
+
+/a\x{100}+b/8
+ a\x{100}b
+ 0: a\x{100}b
+ a\x{100}\x{100}b
+ 0: a\x{100}\x{100}b
+ *** Failers
+No match
+ ab
+No match
+
+/\bX/8
+ Xoanon
+ 0: X
+ +Xoanon
+ 0: X
+ \x{300}Xoanon
+ 0: X
+ *** Failers
+No match
+ YXoanon
+No match
+
+/\BX/8
+ YXoanon
+ 0: X
+ *** Failers
+No match
+ Xoanon
+No match
+ +Xoanon
+No match
+ \x{300}Xoanon
+No match
+
+/X\b/8
+ X+oanon
+ 0: X
+ ZX\x{300}oanon
+ 0: X
+ FAX
+ 0: X
+ *** Failers
+No match
+ Xoanon
+No match
+
+/X\B/8
+ Xoanon
+ 0: X
+ *** Failers
+No match
+ X+oanon
+No match
+ ZX\x{300}oanon
+No match
+ FAX
+No match
+
+/[^a]/8
+ abcd
+ 0: b
+ a\x{100}
+ 0: \x{100}
+
+/^[abc\x{123}\x{400}-\x{402}]{2,3}\d/8
+ ab99
+ 0: ab9
+ \x{123}\x{123}45
+ 0: \x{123}\x{123}4
+ \x{400}\x{401}\x{402}6
+ 0: \x{400}\x{401}\x{402}6
+ *** Failers
+No match
+ d99
+No match
+ \x{123}\x{122}4
+No match
+ \x{400}\x{403}6
+No match
+ \x{400}\x{401}\x{402}\x{402}6
+No match
+
+/abc/8
+ �]
+Error -10
+ �
+Error -10
+ ���
+Error -10
+ ���\?
+No match
+
+/a.b/8
+ acb
+ 0: acb
+ a\x7fb
+ 0: a\x{7f}b
+ a\x{100}b
+ 0: a\x{100}b
+ *** Failers
+No match
+ a\nb
+No match
+
+/^[a\x{c0}]/8
+ *** Failers
+No match
+ \x{100}
+No match
+
+/(?<=aXb)cd/8
+ aXbcd
+ 0: cd
+
+/(?<=a\x{100}b)cd/8
+ a\x{100}bcd
+ 0: cd
+
+/(?<=a\x{100000}b)cd/8
+ a\x{100000}bcd
+ 0: cd
+
+/(?:\x{100}){3}b/8
+ \x{100}\x{100}\x{100}b
+ 0: \x{100}\x{100}\x{100}b
+ *** Failers
+No match
+ \x{100}\x{100}b
+No match
+
+/\x{ab}/8
+ \x{ab}
+ 0: \x{ab}
+ \xc2\xab
+ 0: \x{ab}
+ *** Failers
+No match
+ \x00{ab}
+No match
+
+/^[^a]{2}/8
+ \x{100}bc
+ 0: \x{100}b
+
+/^[^a]{2,}/8
+ \x{100}bcAa
+ 0: \x{100}bcA
+
+/^[^a]{2,}?/8
+ \x{100}bca
+ 0: \x{100}b
+
+/^[^a]{2}/8i
+ \x{100}bc
+ 0: \x{100}b
+
+/^[^a]{2,}/8i
+ \x{100}bcAa
+ 0: \x{100}bc
+
+/^[^a]{2,}?/8iU
+ \x{100}bca
+ 0: \x{100}bc
+
+/\x{100}{0,0}/8
+ abcd
+ 0:
+
+/\x{100}?/8
+ abcd
+ 0:
+ \x{100}\x{100}
+ 0: \x{100}
+
+/\x{100}{0,3}/8
+ \x{100}\x{100}
+ 0: \x{100}\x{100}
+ \x{100}\x{100}\x{100}\x{100}
+ 0: \x{100}\x{100}\x{100}
+
+/\x{100}*/8
+ abce
+ 0:
+ \x{100}\x{100}\x{100}\x{100}
+ 0: \x{100}\x{100}\x{100}\x{100}
+
+/\x{100}{1,1}/8
+ abcd\x{100}\x{100}\x{100}\x{100}
+ 0: \x{100}
+
+/\x{100}{1,3}/8
+ abcd\x{100}\x{100}\x{100}\x{100}
+ 0: \x{100}\x{100}\x{100}
+
+/\x{100}+/8
+ abcd\x{100}\x{100}\x{100}\x{100}
+ 0: \x{100}\x{100}\x{100}\x{100}
+
+/\x{100}{3}/8
+ abcd\x{100}\x{100}\x{100}XX
+ 0: \x{100}\x{100}\x{100}
+
+/\x{100}{3,5}/8
+ abcd\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}XX
+ 0: \x{100}\x{100}\x{100}\x{100}\x{100}
+
+/\x{100}{3,}/8
+ abcd\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}XX
+ 0: \x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}
+
+/(?<=a\x{100}{2}b)X/8
+ Xyyya\x{100}\x{100}bXzzz
+ 0: X
+
+/\D*/8
+ aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
+ 0: aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
+
+/\D*/8
+ \x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}
+ 0: \x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}\x{100}
+
+/\D/8
+ 1X2
+ 0: X
+ 1\x{100}2
+ 0: \x{100}
+
+/>\S/8
+ > >X Y
+ 0: >X
+ > >\x{100} Y
+ 0: >\x{100}
+
+/\d/8
+ \x{100}3
+ 0: 3
+
+/\s/8
+ \x{100} X
+ 0:
+
+/\D+/8
+ 12abcd34
+ 0: abcd
+ *** Failers
+ 0: *** Failers
+ 1234
+No match
+
+/\d+/8
+ 12abcd34
+ 0: 12
+ *** Failers
+No match
+
+/\d{2,3}/8
+ 12abcd34
+ 0: 12
+ 1234abcd
+ 0: 123
+ *** Failers
+No match
+ 1.4
+No match
+
+/\S+/8
+ 12abcd34
+ 0: 12abcd34
+ *** Failers
+ 0: ***
+ \ \
+No match
+
+/>\s+</8
+ 12> <34
+ 0: > <
+ *** Failers
+No match
+
+/>\s{2,3}</8
+ ab> <cd
+ 0: > <
+ ab> <ce
+ 0: > <
+ *** Failers
+No match
+ ab> <cd
+No match
+
+/>\s{2,3}?</8
+ ab> <cd
+ 0: > <
+ ab> <ce
+ 0: > <
+ *** Failers
+No match
+ ab> <cd
+No match
+
+/\w+/8
+ 12 34
+ 0: 12
+ *** Failers
+ 0: Failers
+ +++=*!
+No match
+
+/\w{2,3}/8
+ ab cd
+ 0: ab
+ abcd ce
+ 0: abc
+ *** Failers
+ 0: Fai
+ a.b.c
+No match
+
+/\W+/8
+ 12====34
+ 0: ====
+ *** Failers
+ 0: ***
+ abcd
+No match
+
+/\W{2,3}/8
+ ab====cd
+ 0: ===
+ ab==cd
+ 0: ==
+ *** Failers
+ 0: ***
+ a.b.c
+No match
+
+/\W{2,3}?/8U
+ ab====cd
+ 0: ===
+ ab==cd
+ 0: ==
+ *** Failers
+ 0: ***
+ a.b.c
+No match
+
+/[\x{100}]/8
+ \x{100}
+ 0: \x{100}
+ Z\x{100}
+ 0: \x{100}
+ \x{100}Z
+ 0: \x{100}
+ *** Failers
+No match
+
+/[Z\x{100}]/8
+ Z\x{100}
+ 0: Z
+ \x{100}
+ 0: \x{100}
+ \x{100}Z
+ 0: \x{100}
+ *** Failers
+No match
+
+/[\x{100}\x{200}]/8
+ ab\x{100}cd
+ 0: \x{100}
+ ab\x{200}cd
+ 0: \x{200}
+ *** Failers
+No match
+
+/[\x{100}-\x{200}]/8
+ ab\x{100}cd
+ 0: \x{100}
+ ab\x{200}cd
+ 0: \x{200}
+ ab\x{111}cd
+ 0: \x{111}
+ *** Failers
+No match
+
+/[z-\x{200}]/8
+ ab\x{100}cd
+ 0: \x{100}
+ ab\x{200}cd
+ 0: \x{200}
+ ab\x{111}cd
+ 0: \x{111}
+ abzcd
+ 0: z
+ ab|cd
+ 0: |
+ *** Failers
+No match
+
+/[Q\x{100}\x{200}]/8
+ ab\x{100}cd
+ 0: \x{100}
+ ab\x{200}cd
+ 0: \x{200}
+ Q?
+ 0: Q
+ *** Failers
+No match
+
+/[Q\x{100}-\x{200}]/8
+ ab\x{100}cd
+ 0: \x{100}
+ ab\x{200}cd
+ 0: \x{200}
+ ab\x{111}cd
+ 0: \x{111}
+ Q?
+ 0: Q
+ *** Failers
+No match
+
+/[Qz-\x{200}]/8
+ ab\x{100}cd
+ 0: \x{100}
+ ab\x{200}cd
+ 0: \x{200}
+ ab\x{111}cd
+ 0: \x{111}
+ abzcd
+ 0: z
+ ab|cd
+ 0: |
+ Q?
+ 0: Q
+ *** Failers
+No match
+
+/[\x{100}\x{200}]{1,3}/8
+ ab\x{100}cd
+ 0: \x{100}
+ ab\x{200}cd
+ 0: \x{200}
+ ab\x{200}\x{100}\x{200}\x{100}cd
+ 0: \x{200}\x{100}\x{200}
+ *** Failers
+No match
+
+/[\x{100}\x{200}]{1,3}?/8U
+ ab\x{100}cd
+ 0: \x{100}
+ ab\x{200}cd
+ 0: \x{200}
+ ab\x{200}\x{100}\x{200}\x{100}cd
+ 0: \x{200}\x{100}\x{200}
+ *** Failers
+No match
+
+/[Q\x{100}\x{200}]{1,3}/8
+ ab\x{100}cd
+ 0: \x{100}
+ ab\x{200}cd
+ 0: \x{200}
+ ab\x{200}\x{100}\x{200}\x{100}cd
+ 0: \x{200}\x{100}\x{200}
+ *** Failers
+No match
+
+/[Q\x{100}\x{200}]{1,3}?/8U
+ ab\x{100}cd
+ 0: \x{100}
+ ab\x{200}cd
+ 0: \x{200}
+ ab\x{200}\x{100}\x{200}\x{100}cd
+ 0: \x{200}\x{100}\x{200}
+ *** Failers
+No match
+
+/(?<=[\x{100}\x{200}])X/8
+ abc\x{200}X
+ 0: X
+ abc\x{100}X
+ 0: X
+ *** Failers
+No match
+ X
+No match
+
+/(?<=[Q\x{100}\x{200}])X/8
+ abc\x{200}X
+ 0: X
+ abc\x{100}X
+ 0: X
+ abQX
+ 0: X
+ *** Failers
+No match
+ X
+No match
+
+/(?<=[\x{100}\x{200}]{3})X/8
+ abc\x{100}\x{200}\x{100}X
+ 0: X
+ *** Failers
+No match
+ abc\x{200}X
+No match
+ X
+No match
+
+/[^\x{100}\x{200}]X/8
+ AX
+ 0: AX
+ \x{150}X
+ 0: \x{150}X
+ \x{500}X
+ 0: \x{500}X
+ *** Failers
+No match
+ \x{100}X
+No match
+ \x{200}X
+No match
+
+/[^Q\x{100}\x{200}]X/8
+ AX
+ 0: AX
+ \x{150}X
+ 0: \x{150}X
+ \x{500}X
+ 0: \x{500}X
+ *** Failers
+No match
+ \x{100}X
+No match
+ \x{200}X
+No match
+ QX
+No match
+
+/[^\x{100}-\x{200}]X/8
+ AX
+ 0: AX
+ \x{500}X
+ 0: \x{500}X
+ *** Failers
+No match
+ \x{100}X
+No match
+ \x{150}X
+No match
+ \x{200}X
+No match
+
+/[z-\x{100}]/8i
+ z
+ 0: z
+ Z
+ 0: Z
+ \x{100}
+ 0: \x{100}
+ *** Failers
+No match
+ \x{102}
+No match
+ y
+No match
+
+/[\xFF]/
+ >\xff<
+ 0: \xff
+
+/[\xff]/8
+ >\x{ff}<
+ 0: \x{ff}
+
+/[^\xFF]/
+ XYZ
+ 0: X
+
+/[^\xff]/8
+ XYZ
+ 0: X
+ \x{123}
+ 0: \x{123}
+
+/^[ac]*b/8
+ xb
+No match
+
+/^[ac\x{100}]*b/8
+ xb
+No match
+
+/^[^x]*b/8i
+ xb
+No match
+
+/^[^x]*b/8
+ xb
+No match
+
+/^\d*b/8
+ xb
+No match
+
+/^\x{85}$/8i
+ \x{85}
+ 0: \x{85}
+
+/^abc./mgx8<any>
+ abc1 \x0aabc2 \x0babc3xx \x0cabc4 \x0dabc5xx \x0d\x0aabc6 \x{0085}abc7 \x{2028}abc8 \x{2029}abc9 JUNK
+ 0: abc1
+ 0: abc2
+ 0: abc3
+ 0: abc4
+ 0: abc5
+ 0: abc6
+ 0: abc7
+ 0: abc8
+ 0: abc9
+
+/abc.$/mgx8<any>
+ abc1\x0a abc2\x0b abc3\x0c abc4\x0d abc5\x0d\x0a abc6\x{0085} abc7\x{2028} abc8\x{2029} abc9
+ 0: abc1
+ 0: abc2
+ 0: abc3
+ 0: abc4
+ 0: abc5
+ 0: abc6
+ 0: abc7
+ 0: abc8
+ 0: abc9
+
+/^a\Rb/8<bsr_unicode>
+ a\nb
+ 0: a\x{0a}b
+ a\rb
+ 0: a\x{0d}b
+ a\r\nb
+ 0: a\x{0d}\x{0a}b
+ a\x0bb
+ 0: a\x{0b}b
+ a\x0cb
+ 0: a\x{0c}b
+ a\x{85}b
+ 0: a\x{85}b
+ a\x{2028}b
+ 0: a\x{2028}b
+ a\x{2029}b
+ 0: a\x{2029}b
+ ** Failers
+No match
+ a\n\rb
+No match
+
+/^a\R*b/8<bsr_unicode>
+ ab
+ 0: ab
+ a\nb
+ 0: a\x{0a}b
+ a\rb
+ 0: a\x{0d}b
+ a\r\nb
+ 0: a\x{0d}\x{0a}b
+ a\x0bb
+ 0: a\x{0b}b
+ a\x0c\x{2028}\x{2029}b
+ 0: a\x{0c}\x{2028}\x{2029}b
+ a\x{85}b
+ 0: a\x{85}b
+ a\n\rb
+ 0: a\x{0a}\x{0d}b
+ a\n\r\x{85}\x0cb
+ 0: a\x{0a}\x{0d}\x{85}\x{0c}b
+
+/^a\R+b/8<bsr_unicode>
+ a\nb
+ 0: a\x{0a}b
+ a\rb
+ 0: a\x{0d}b
+ a\r\nb
+ 0: a\x{0d}\x{0a}b
+ a\x0bb
+ 0: a\x{0b}b
+ a\x0c\x{2028}\x{2029}b
+ 0: a\x{0c}\x{2028}\x{2029}b
+ a\x{85}b
+ 0: a\x{85}b
+ a\n\rb
+ 0: a\x{0a}\x{0d}b
+ a\n\r\x{85}\x0cb
+ 0: a\x{0a}\x{0d}\x{85}\x{0c}b
+ ** Failers
+No match
+ ab
+No match
+
+/^a\R{1,3}b/8<bsr_unicode>
+ a\nb
+ 0: a\x{0a}b
+ a\n\rb
+ 0: a\x{0a}\x{0d}b
+ a\n\r\x{85}b
+ 0: a\x{0a}\x{0d}\x{85}b
+ a\r\n\r\nb
+ 0: a\x{0d}\x{0a}\x{0d}\x{0a}b
+ a\r\n\r\n\r\nb
+ 0: a\x{0d}\x{0a}\x{0d}\x{0a}\x{0d}\x{0a}b
+ a\n\r\n\rb
+ 0: a\x{0a}\x{0d}\x{0a}\x{0d}b
+ a\n\n\r\nb
+ 0: a\x{0a}\x{0a}\x{0d}\x{0a}b
+ ** Failers
+No match
+ a\n\n\n\rb
+No match
+ a\r
+No match
+
+/\h+\V?\v{3,4}/8
+ \x09\x20\x{a0}X\x0a\x0b\x0c\x0d\x0a
+ 0: \x{09} \x{a0}X\x{0a}\x{0b}\x{0c}\x{0d}
+
+/\V?\v{3,4}/8
+ \x20\x{a0}X\x0a\x0b\x0c\x0d\x0a
+ 0: X\x{0a}\x{0b}\x{0c}\x{0d}
+
+/\h+\V?\v{3,4}/8
+ >\x09\x20\x{a0}X\x0a\x0a\x0a<
+ 0: \x{09} \x{a0}X\x{0a}\x{0a}\x{0a}
+
+/\V?\v{3,4}/8
+ >\x09\x20\x{a0}X\x0a\x0a\x0a<
+ 0: X\x{0a}\x{0a}\x{0a}
+
+/\H\h\V\v/8
+ X X\x0a
+ 0: X X\x{0a}
+ X\x09X\x0b
+ 0: X\x{09}X\x{0b}
+ ** Failers
+No match
+ \x{a0} X\x0a
+No match
+
+/\H*\h+\V?\v{3,4}/8
+ \x09\x20\x{a0}X\x0a\x0b\x0c\x0d\x0a
+ 0: \x{09} \x{a0}X\x{0a}\x{0b}\x{0c}\x{0d}
+ \x09\x20\x{a0}\x0a\x0b\x0c\x0d\x0a
+ 0: \x{09} \x{a0}\x{0a}\x{0b}\x{0c}\x{0d}
+ \x09\x20\x{a0}\x0a\x0b\x0c
+ 0: \x{09} \x{a0}\x{0a}\x{0b}\x{0c}
+ ** Failers
+No match
+ \x09\x20\x{a0}\x0a\x0b
+No match
+
+/\H\h\V\v/8
+ \x{3001}\x{3000}\x{2030}\x{2028}
+ 0: \x{3001}\x{3000}\x{2030}\x{2028}
+ X\x{180e}X\x{85}
+ 0: X\x{180e}X\x{85}
+ ** Failers
+No match
+ \x{2009} X\x0a
+No match
+
+/\H*\h+\V?\v{3,4}/8
+ \x{1680}\x{180e}\x{2007}X\x{2028}\x{2029}\x0c\x0d\x0a
+ 0: \x{1680}\x{180e}\x{2007}X\x{2028}\x{2029}\x{0c}\x{0d}
+ \x09\x{205f}\x{a0}\x0a\x{2029}\x0c\x{2028}\x0a
+ 0: \x{09}\x{205f}\x{a0}\x{0a}\x{2029}\x{0c}\x{2028}
+ \x09\x20\x{202f}\x0a\x0b\x0c
+ 0: \x{09} \x{202f}\x{0a}\x{0b}\x{0c}
+ ** Failers
+No match
+ \x09\x{200a}\x{a0}\x{2028}\x0b
+No match
+
+/a\Rb/I8<bsr_anycrlf>
+Capturing subpattern count = 0
+Options: bsr_anycrlf utf8
+First char = 'a'
+Need char = 'b'
+ a\rb
+ 0: a\x{0d}b
+ a\nb
+ 0: a\x{0a}b
+ a\r\nb
+ 0: a\x{0d}\x{0a}b
+ ** Failers
+No match
+ a\x{85}b
+No match
+ a\x0bb
+No match
+
+/a\Rb/I8<bsr_unicode>
+Capturing subpattern count = 0
+Options: bsr_unicode utf8
+First char = 'a'
+Need char = 'b'
+ a\rb
+ 0: a\x{0d}b
+ a\nb
+ 0: a\x{0a}b
+ a\r\nb
+ 0: a\x{0d}\x{0a}b
+ a\x{85}b
+ 0: a\x{85}b
+ a\x0bb
+ 0: a\x{0b}b
+ ** Failers
+No match
+ a\x{85}b\<bsr_anycrlf>
+No match
+ a\x0bb\<bsr_anycrlf>
+No match
+
+/a\R?b/I8<bsr_anycrlf>
+Capturing subpattern count = 0
+Options: bsr_anycrlf utf8
+First char = 'a'
+Need char = 'b'
+ a\rb
+ 0: a\x{0d}b
+ a\nb
+ 0: a\x{0a}b
+ a\r\nb
+ 0: a\x{0d}\x{0a}b
+ ** Failers
+No match
+ a\x{85}b
+No match
+ a\x0bb
+No match
+
+/a\R?b/I8<bsr_unicode>
+Capturing subpattern count = 0
+Options: bsr_unicode utf8
+First char = 'a'
+Need char = 'b'
+ a\rb
+ 0: a\x{0d}b
+ a\nb
+ 0: a\x{0a}b
+ a\r\nb
+ 0: a\x{0d}\x{0a}b
+ a\x{85}b
+ 0: a\x{85}b
+ a\x0bb
+ 0: a\x{0b}b
+ ** Failers
+No match
+ a\x{85}b\<bsr_anycrlf>
+No match
+ a\x0bb\<bsr_anycrlf>
+No match
+
+/ End of testinput 8 /
diff --git a/lib/stdlib/test/run_pcre_tests.erl b/lib/stdlib/test/run_pcre_tests.erl
index 0ef3986918..8c6424e708 100644
--- a/lib/stdlib/test/run_pcre_tests.erl
+++ b/lib/stdlib/test/run_pcre_tests.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 2008-2010. All Rights Reserved.
+%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
-module(run_pcre_tests).
@@ -25,7 +25,7 @@ test(RootDir) ->
erts_debug:set_internal_state(available_internal_state,true),
io:format("oldlimit: ~p~n",[ erts_debug:set_internal_state(re_loop_limit,10)]),
Testfiles0 = ["testoutput1", "testoutput2", "testoutput3", "testoutput4",
- "testoutput5", "testoutput6", "testoutput10"],
+ "testoutput5", "testoutput6","mod_testoutput8","testoutput10"],
Testfiles = [ filename:join([RootDir,FN]) || FN <- Testfiles0 ],
Res = [ begin io:format("~s~n",[X]), t(X) end || X <- Testfiles ],
io:format("limit was: ~p~n",[ erts_debug:set_internal_state(re_loop_limit,default)]),
@@ -42,12 +42,14 @@ t(OneFile,Num) ->
put(error_limit,Num),
put(skipped,0),
Res =
- [test(Structured,true,index),
- test(Structured,false,index),
- test(Structured,true,binary),
- test(Structured,false,binary),
- test(Structured,true,list),
- test(Structured,false,list)],
+ [test(Structured,true,index,false),
+ test(Structured,false,index,false),
+ test(Structured,true,index,true),
+ test(Structured,false,index,true),
+ test(Structured,true,binary,false),
+ test(Structured,false,binary,false),
+ test(Structured,true,list,false),
+ test(Structured,false,list,false)],
{lists:sum(Res),length(Structured)*6,get(skipped)}.
@@ -63,11 +65,21 @@ pick_exec_options([Opt|T]) ->
pick_exec_options([]) ->
{[],[]}.
-test([],_,_) ->
+test([],_,_,_) ->
0;
-test([{RE,Line,Options0,Tests}|T],PreCompile,XMode) ->
+test([{RE0,Line,Options0,Tests}|T],PreCompile,XMode,REAsList) ->
%io:format("."),
%case RE of <<>> -> io:format("Empty re:~w~n",[Line]); _ -> ok end,
+ Unicode = lists:member(unicode,Options0),
+ RE = case REAsList of
+ true ->
+ if
+ Unicode -> unicode:characters_to_list(RE0);
+ true -> binary_to_list(RE0)
+ end;
+ false ->
+ RE0
+ end,
{Options,ExecOptions} = pick_exec_options(Options0),
{Cres, Xopt} = case PreCompile of
true ->
@@ -80,7 +92,7 @@ test([{RE,Line,Options0,Tests}|T],PreCompile,XMode) ->
%erlang:display({testrun,RE,P,Tests,ExecOptions,Xopt,XMode}),
case (catch testrun(RE,P,Tests,ExecOptions,Xopt,XMode)) of
N when is_integer(N) ->
- N + test(T,PreCompile,XMode);
+ N + test(T,PreCompile,XMode,REAsList);
limit ->
io:format("Error limit reached.~n"),
1;
@@ -91,12 +103,12 @@ test([{RE,Line,Options0,Tests}|T],PreCompile,XMode) ->
_ ->
put(skipped,1)
end,
- test(T,PreCompile,XMode)
+ test(T,PreCompile,XMode,REAsList)
end;
{error,Err} ->
io:format("Compile error(~w): ~w~n",[Line,Err]),
case get(error_limit) of
- infinite -> 1 + test(T,PreCompile,XMode);
+ infinite -> 1 + test(T,PreCompile,XMode,REAsList);
X ->
case X-1 of
Y when Y =< 0 ->
@@ -104,7 +116,7 @@ test([{RE,Line,Options0,Tests}|T],PreCompile,XMode) ->
1;
Y ->
put(error_limit,Y),
- 1 + test(T,PreCompile,XMode)
+ 1 + test(T,PreCompile,XMode,REAsList)
end
end
end.
@@ -549,6 +561,8 @@ tr_option($N) ->
[no_auto_capture];
tr_option($8) ->
[unicode];
+tr_option($U) ->
+ [ungreedy];
tr_option($g) ->
[{exec_option,g}];
tr_option(_) ->