aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/Makefile4
-rw-r--r--lib/stdlib/test/array_SUITE.erl57
-rw-r--r--lib/stdlib/test/base64_SUITE.erl118
-rw-r--r--lib/stdlib/test/beam_lib_SUITE.erl47
-rw-r--r--lib/stdlib/test/binary_module_SUITE.erl1363
-rw-r--r--lib/stdlib/test/binref.erl588
-rw-r--r--lib/stdlib/test/c_SUITE.erl28
-rw-r--r--lib/stdlib/test/calendar_SUITE.erl52
-rw-r--r--lib/stdlib/test/dets_SUITE.erl208
-rw-r--r--lib/stdlib/test/dict_SUITE.erl32
-rw-r--r--lib/stdlib/test/dict_test_lib.erl2
-rw-r--r--lib/stdlib/test/digraph_SUITE.erl36
-rw-r--r--lib/stdlib/test/digraph_utils_SUITE.erl30
-rw-r--r--lib/stdlib/test/dummy1_h.erl15
-rw-r--r--lib/stdlib/test/dummy_h.erl2
-rw-r--r--lib/stdlib/test/edlin_expand_SUITE.erl35
-rw-r--r--lib/stdlib/test/epp_SUITE.erl225
-rw-r--r--lib/stdlib/test/erl_eval_SUITE.erl52
-rw-r--r--lib/stdlib/test/erl_eval_helper.erl2
-rw-r--r--lib/stdlib/test/erl_expand_records_SUITE.erl39
-rw-r--r--lib/stdlib/test/erl_internal_SUITE.erl32
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl349
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl274
-rw-r--r--lib/stdlib/test/erl_scan_SUITE.erl252
-rw-r--r--lib/stdlib/test/error_logger_forwarder.erl2
-rw-r--r--lib/stdlib/test/escript_SUITE.erl455
-rwxr-xr-xlib/stdlib/test/escript_SUITE_data/arg_overflow5
-rwxr-xr-xlib/stdlib/test/escript_SUITE_data/linebuf_overflow5
-rw-r--r--lib/stdlib/test/ets_SUITE.erl1344
-rw-r--r--lib/stdlib/test/ets_tough_SUITE.erl30
-rw-r--r--lib/stdlib/test/file_sorter_SUITE.erl49
-rw-r--r--lib/stdlib/test/filelib_SUITE.erl39
-rw-r--r--lib/stdlib/test/filename_SUITE.erl341
-rw-r--r--lib/stdlib/test/fixtable_SUITE.erl35
-rw-r--r--lib/stdlib/test/format_SUITE.erl31
-rw-r--r--lib/stdlib/test/gen_event_SUITE.erl91
-rw-r--r--lib/stdlib/test/gen_fsm_SUITE.erl104
-rw-r--r--lib/stdlib/test/gen_server_SUITE.erl184
-rw-r--r--lib/stdlib/test/id_transform_SUITE.erl30
-rw-r--r--lib/stdlib/test/io_SUITE.erl41
-rw-r--r--lib/stdlib/test/io_proto_SUITE.erl48
-rw-r--r--lib/stdlib/test/lists_SUITE.erl139
-rw-r--r--lib/stdlib/test/log_mf_h_SUITE.erl28
-rw-r--r--lib/stdlib/test/ms_transform_SUITE.erl137
-rw-r--r--lib/stdlib/test/naughty_child.erl2
-rw-r--r--lib/stdlib/test/proc_lib_SUITE.erl35
-rw-r--r--lib/stdlib/test/qlc_SUITE.erl121
-rw-r--r--lib/stdlib/test/queue_SUITE.erl31
-rw-r--r--lib/stdlib/test/random_SUITE.erl33
-rw-r--r--lib/stdlib/test/random_iolist.erl2
-rw-r--r--lib/stdlib/test/random_unicode_list.erl2
-rw-r--r--lib/stdlib/test/re_SUITE.erl57
-rw-r--r--lib/stdlib/test/select_SUITE.erl34
-rw-r--r--lib/stdlib/test/sets_SUITE.erl36
-rw-r--r--lib/stdlib/test/sets_test_lib.erl2
-rw-r--r--lib/stdlib/test/shell_SUITE.erl86
-rw-r--r--lib/stdlib/test/slave_SUITE.erl25
-rw-r--r--lib/stdlib/test/sofs_SUITE.erl73
-rw-r--r--lib/stdlib/test/stdlib.cover25
-rw-r--r--lib/stdlib/test/stdlib.spec5
-rw-r--r--lib/stdlib/test/stdlib_SUITE.erl37
-rw-r--r--lib/stdlib/test/string_SUITE.erl45
-rw-r--r--lib/stdlib/test/supervisor_1.erl2
-rw-r--r--lib/stdlib/test/supervisor_SUITE.erl277
-rw-r--r--lib/stdlib/test/supervisor_bridge_SUITE.erl29
-rw-r--r--lib/stdlib/test/sys_SUITE.erl29
-rw-r--r--lib/stdlib/test/tar_SUITE.erl34
-rw-r--r--lib/stdlib/test/timer_SUITE.erl25
-rw-r--r--lib/stdlib/test/timer_simple_SUITE.erl69
-rw-r--r--lib/stdlib/test/unicode_SUITE.erl33
-rw-r--r--lib/stdlib/test/win32reg_SUITE.erl26
-rw-r--r--lib/stdlib/test/y2k_SUITE.erl44
-rw-r--r--lib/stdlib/test/zip_SUITE.erl107
73 files changed, 6754 insertions, 1552 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index 9beac93eb8..3dd0a91870 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -9,6 +9,8 @@ MODULES= \
array_SUITE \
base64_SUITE \
beam_lib_SUITE \
+ binary_module_SUITE \
+ binref \
c_SUITE \
calendar_SUITE \
dets_SUITE \
@@ -131,7 +133,7 @@ release_spec: opt
release_tests_spec: make_emakefile
$(INSTALL_DIR) $(RELSYSDIR)
- $(INSTALL_DATA) stdlib.spec stdlib.spec.vxworks $(EMAKEFILE) \
+ $(INSTALL_DATA) stdlib.spec $(EMAKEFILE) \
$(ERL_FILES) $(COVERFILE) $(RELSYSDIR)
chmod -f -R u+w $(RELSYSDIR)
@tar cf - *_SUITE_data | (cd $(RELSYSDIR); tar xf -)
diff --git a/lib/stdlib/test/array_SUITE.erl b/lib/stdlib/test/array_SUITE.erl
index e7cfc65be1..a8b252f081 100644
--- a/lib/stdlib/test/array_SUITE.erl
+++ b/lib/stdlib/test/array_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2007-2009. All Rights Reserved.
+%% Copyright Ericsson AB 2007-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
@@ -19,7 +19,7 @@
-module(array_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
%% Default timetrap timeout (set in init_per_testcase).
%% This should be set relatively high (10-15 times the expected
@@ -27,8 +27,9 @@
-define(default_timeout, ?t:seconds(60)).
%% Test server specific exports
--export([all/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
-export([
new_test/1,
@@ -64,33 +65,37 @@
%%
%% all/1
%%
-all(doc) ->
- [];
-all(suite) ->
- [new_test,
- fix_test,
- relax_test,
- resize_test,
- set_get_test,
- to_list_test,
- sparse_to_list_test,
- from_list_test,
- to_orddict_test,
- sparse_to_orddict_test,
- from_orddict_test,
- map_test,
- sparse_map_test,
- foldl_test,
- sparse_foldl_test,
- foldr_test,
- sparse_foldr_test
- ].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [new_test, fix_test, relax_test, resize_test,
+ set_get_test, to_list_test, sparse_to_list_test,
+ from_list_test, to_orddict_test, sparse_to_orddict_test,
+ from_orddict_test, map_test, sparse_map_test,
+ foldl_test, sparse_foldl_test, foldr_test,
+ sparse_foldr_test].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
init_per_testcase(_Case, Config) ->
?line Dog=test_server:timetrap(?default_timeout),
[{watchdog, Dog}|Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog=?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
diff --git a/lib/stdlib/test/base64_SUITE.erl b/lib/stdlib/test/base64_SUITE.erl
index 44742063b3..c64a961ffa 100644
--- a/lib/stdlib/test/base64_SUITE.erl
+++ b/lib/stdlib/test/base64_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2007-2009. All Rights Reserved.
+%% Copyright Ericsson AB 2007-2011. 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
@@ -18,18 +18,19 @@
%%
-module(base64_SUITE).
--author('[email protected]').
--include("test_server.hrl").
+-include_lib("common_test/include/ct.hrl").
-include("test_server_line.hrl").
%% Test server specific exports
--export([all/1, init_per_testcase/2, end_per_testcase/2]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
+ init_per_testcase/2, end_per_testcase/2]).
%% Test cases must be exported.
-export([base64_encode/1, base64_decode/1, base64_otp_5635/1,
base64_otp_6279/1, big/1, illegal/1, mime_decode/1,
- roundtrip/1]).
+ mime_decode_to_string/1, roundtrip/1]).
init_per_testcase(_, Config) ->
Dog = test_server:timetrap(?t:minutes(2)),
@@ -44,14 +45,29 @@ end_per_testcase(_, Config) ->
%%-------------------------------------------------------------------------
%% Test cases starts here.
%%-------------------------------------------------------------------------
-all(doc) ->
- ["Test library functions for base64 encode and decode "
- "(taken from inets/test/http_format_SUITE)"];
-all(suite) ->
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
[base64_encode, base64_decode, base64_otp_5635,
- base64_otp_6279, big, illegal, mime_decode,
+ base64_otp_6279, big, illegal, mime_decode, mime_decode_to_string,
roundtrip].
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
%%-------------------------------------------------------------------------
base64_encode(doc) ->
@@ -59,7 +75,7 @@ base64_encode(doc) ->
base64_encode(suite) ->
[];
base64_encode(Config) when is_list(Config) ->
- %% Two pads
+ %% Two pads
<<"QWxhZGRpbjpvcGVuIHNlc2FtZQ==">> =
base64:encode("Aladdin:open sesame"),
%% One pad
@@ -77,8 +93,8 @@ base64_decode(doc) ->
base64_decode(suite) ->
[];
base64_decode(Config) when is_list(Config) ->
- %% Two pads
- <<"Aladdin:open sesame">> =
+ %% Two pads
+ <<"Aladdin:open sesame">> =
base64:decode("QWxhZGRpbjpvcGVuIHNlc2FtZQ=="),
%% One pad
<<"Hello World">> = base64:decode(<<"SGVsbG8gV29ybGQ=">>),
@@ -138,20 +154,85 @@ illegal(Config) when is_list(Config) ->
{'EXIT',{function_clause, _}} = (catch base64:decode("()")),
ok.
%%-------------------------------------------------------------------------
+%% mime_decode and mime_decode_to_string have different implementations
+%% so test both with the same input separately. Both functions have
+%% the same implementation for binary/string arguments.
mime_decode(doc) ->
["Test base64:mime_decode/1."];
mime_decode(suite) ->
[];
mime_decode(Config) when is_list(Config) ->
- %% Two pads
- <<"Aladdin:open sesame">> =
+ %% Test correct padding
+ <<"one">> = base64:mime_decode(<<"b25l">>),
+ <<"on">> = base64:mime_decode(<<"b24=">>),
+ <<"o">> = base64:mime_decode(<<"bw==">>),
+ %% Test 1 extra padding
+ <<"one">> = base64:mime_decode(<<"b25l= =">>),
+ <<"on">> = base64:mime_decode(<<"b24== =">>),
+ <<"o">> = base64:mime_decode(<<"bw=== =">>),
+ %% Test 2 extra padding
+ <<"one">> = base64:mime_decode(<<"b25l===">>),
+ <<"on">> = base64:mime_decode(<<"b24====">>),
+ <<"o">> = base64:mime_decode(<<"bw=====">>),
+ %% Test misc embedded padding
+ <<"one">> = base64:mime_decode(<<"b2=5l===">>),
+ <<"on">> = base64:mime_decode(<<"b=24====">>),
+ <<"o">> = base64:mime_decode(<<"b=w=====">>),
+ %% Test misc white space and illegals with embedded padding
+ <<"one">> = base64:mime_decode(<<" b~2=\r\n5()l===">>),
+ <<"on">> = base64:mime_decode(<<"\tb =2\"�4=�= ==">>),
+ <<"o">> = base64:mime_decode(<<"\nb=w=====">>),
+ %% Two pads
+ <<"Aladdin:open sesame">> =
base64:mime_decode("QWxhZGRpbjpvc()GVuIHNlc2FtZQ=="),
- %% One pad, followed by ignored text
- <<"Hello World">> = base64:mime_decode(<<"SGVsb)(G8gV29ybGQ=apa">>),
+ %% One pad to ignore, followed by more text
+ <<"Hello World!!">> = base64:mime_decode(<<"SGVsb)(G8gV29ybGQ=h IQ= =">>),
+ %% No pad
+ <<"Aladdin:open sesam">> =
+ base64:mime_decode("QWxhZGRpbjpvcG�\")(VuIHNlc2Ft"),
+ %% Encoded base 64 strings may be divided by non base 64 chars.
+ %% In this cases whitespaces.
+ <<"0123456789!@#0^&*();:<>,. []{}">> =
+ base64:mime_decode(
+ <<"MDEy MzQ1Njc4 \tOSFAIzBeJ \nio)(oKTs6 PD4sLi \r\nBbXXt9">>),
+ ok.
+
+%%-------------------------------------------------------------------------
+
+%% Repeat of mime_decode() tests
+mime_decode_to_string(doc) ->
+ ["Test base64:mime_decode_to_string/1."];
+mime_decode_to_string(suite) ->
+ [];
+mime_decode_to_string(Config) when is_list(Config) ->
+ %% Test correct padding
+ "one" = base64:mime_decode_to_string(<<"b25l">>),
+ "on" = base64:mime_decode_to_string(<<"b24=">>),
+ "o" = base64:mime_decode_to_string(<<"bw==">>),
+ %% Test 1 extra padding
+ "one" = base64:mime_decode_to_string(<<"b25l= =">>),
+ "on" = base64:mime_decode_to_string(<<"b24== =">>),
+ "o" = base64:mime_decode_to_string(<<"bw=== =">>),
+ %% Test 2 extra padding
+ "one" = base64:mime_decode_to_string(<<"b25l===">>),
+ "on" = base64:mime_decode_to_string(<<"b24====">>),
+ "o" = base64:mime_decode_to_string(<<"bw=====">>),
+ %% Test misc embedded padding
+ "one" = base64:mime_decode_to_string(<<"b2=5l===">>),
+ "on" = base64:mime_decode_to_string(<<"b=24====">>),
+ "o" = base64:mime_decode_to_string(<<"b=w=====">>),
+ %% Test misc white space and illegals with embedded padding
+ "one" = base64:mime_decode_to_string(<<" b~2=\r\n5()l===">>),
+ "on" = base64:mime_decode_to_string(<<"\tb =2\"�4=�= ==">>),
+ "o" = base64:mime_decode_to_string(<<"\nb=w=====">>),
+ %% Two pads
+ "Aladdin:open sesame" =
+ base64:mime_decode_to_string("QWxhZGRpbjpvc()GVuIHNlc2FtZQ=="),
+ %% One pad to ignore, followed by more text
+ "Hello World!!" = base64:mime_decode_to_string(<<"SGVsb)(G8gV29ybGQ=h IQ= =">>),
%% No pad
"Aladdin:open sesam" =
base64:mime_decode_to_string("QWxhZGRpbjpvcG�\")(VuIHNlc2Ft"),
-
%% Encoded base 64 strings may be divided by non base 64 chars.
%% In this cases whitespaces.
"0123456789!@#0^&*();:<>,. []{}" =
@@ -159,6 +240,7 @@ mime_decode(Config) when is_list(Config) ->
<<"MDEy MzQ1Njc4 \tOSFAIzBeJ \nio)(oKTs6 PD4sLi \r\nBbXXt9">>),
ok.
+%%-------------------------------------------------------------------------
roundtrip(Config) when is_list(Config) ->
Sizes = lists:seq(1, 255) ++ lists:seq(2400-5, 2440),
diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl
index bc867a3770..994abebc1a 100644
--- a/lib/stdlib/test/beam_lib_SUITE.erl
+++ b/lib/stdlib/test/beam_lib_SUITE.erl
@@ -1,6 +1,19 @@
%%
%% %CopyrightBegin%
%%
+%% Copyright Ericsson AB 1997-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(beam_lib_SUITE).
@@ -14,25 +27,45 @@
-define(t,test_server).
-define(privdir, "beam_lib_SUITE_priv").
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(format(S, A), ok).
-define(privdir, ?config(priv_dir, Conf)).
-endif.
--export([all/1, normal/1, error/1, cmp/1, cmp_literals/1, strip/1, otp_6711/1,
+-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,
building/1, md5/1, encrypted_abstr/1, encrypted_abstr_file/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
+
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [error, normal, cmp, cmp_literals, strip, otp_6711,
+ building, md5, encrypted_abstr, encrypted_abstr_file].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
-all(suite) ->
- [error, normal, cmp, cmp_literals, strip, otp_6711, building, md5,
- encrypted_abstr, encrypted_abstr_file].
init_per_testcase(_Case, Config) ->
Dog=?t:timetrap(?t:minutes(2)),
[{watchdog, Dog}|Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog=?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl
new file mode 100644
index 0000000000..f6bf874741
--- /dev/null
+++ b/lib/stdlib/test/binary_module_SUITE.erl
@@ -0,0 +1,1363 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 1997-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(binary_module_SUITE).
+
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
+ interesting/1,random_ref_comp/1,random_ref_sr_comp/1,
+ random_ref_fla_comp/1,parts/1, bin_to_list/1, list_to_bin/1,
+ copy/1, referenced/1,guard/1,encode_decode/1,badargs/1,longest_common_trap/1]).
+
+-export([random_number/1, make_unaligned/1]).
+
+
+
+%%-define(STANDALONE,1).
+
+-ifdef(STANDALONE).
+
+-define(line,erlang:display({?MODULE,?LINE}),).
+
+-else.
+
+-include_lib("test_server/include/test_server.hrl").
+-export([init_per_testcase/2, end_per_testcase/2]).
+% Default timetrap timeout (set in init_per_testcase).
+% Some of these testcases are really heavy...
+-define(default_timeout, ?t:minutes(20)).
+
+-endif.
+
+
+
+-ifdef(STANDALONE).
+-export([run/0]).
+
+run() ->
+ [ apply(?MODULE,X,[[]]) || X <- all(suite) ].
+
+-else.
+
+init_per_testcase(_Case, Config) ->
+ ?line Dog = ?t:timetrap(?default_timeout),
+ [{watchdog, Dog} | Config].
+
+end_per_testcase(_Case, Config) ->
+ ?line Dog = ?config(watchdog, Config),
+ ?line test_server:timetrap_cancel(Dog),
+ ok.
+-endif.
+
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [interesting, random_ref_fla_comp, random_ref_sr_comp,
+ random_ref_comp, parts, bin_to_list, list_to_bin, copy,
+ referenced, guard, encode_decode, badargs,
+ longest_common_trap].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
+-define(MASK_ERROR(EXPR),mask_error((catch (EXPR)))).
+
+
+badargs(doc) ->
+ ["Tests various badarg exceptions in the module"];
+badargs(Config) when is_list(Config) ->
+ ?line badarg = ?MASK_ERROR(binary:compile_pattern([<<1,2,3:3>>])),
+ ?line badarg = ?MASK_ERROR(binary:compile_pattern([<<1,2,3>>|<<1,2>>])),
+ ?line badarg = ?MASK_ERROR(binary:compile_pattern(<<1,2,3:3>>)),
+ ?line badarg = ?MASK_ERROR(binary:compile_pattern(<<>>)),
+ ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3:3>>,<<1>>)),
+ ?line badarg = ?MASK_ERROR(binary:matches(<<1,2,3:3>>,<<1>>)),
+ ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
+ [{scope,{0,1},1}])),
+ ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
+ [{scape,{0,1}}])),
+ ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
+ [{scope,{0,1,1}}])),
+ ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,[{scope,0,1}])),
+ ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,[{scope,[0,1]}])),
+ ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
+ [{scope,{0.1,1}}])),
+ ?line badarg = ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,
+ [{scope,{1,1.1}}])),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:match(<<1,2,3>>,<<1>>,
+ [{scope,{16#FF,
+ 16#FFFFFFFFFFFFFFFF}}])),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:match(<<1,2,3>>,<<1>>,
+ [{scope,{16#FFFFFFFFFFFFFFFF,
+ -16#7FFFFFFFFFFFFFFF-1}}])),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:match(<<1,2,3>>,<<1>>,
+ [{scope,{16#FFFFFFFFFFFFFFFF,
+ 16#7FFFFFFFFFFFFFFF}}])),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:part(<<1,2,3>>,{16#FF,
+ 16#FFFFFFFFFFFFFFFF})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:part(<<1,2,3>>,{16#FFFFFFFFFFFFFFFF,
+ -16#7FFFFFFFFFFFFFFF-1})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:part(<<1,2,3>>,{16#FFFFFFFFFFFFFFFF,
+ 16#7FFFFFFFFFFFFFFF})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:part(make_unaligned(<<1,2,3>>),{1,1,1})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary_part(make_unaligned(<<1,2,3>>),{1,1,1})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary_part(make_unaligned(<<1,2,3>>),{16#FFFFFFFFFFFFFFFF,
+ -16#7FFFFFFFFFFFFFFF-1})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary_part(make_unaligned(<<1,2,3>>),{16#FF,
+ 16#FFFFFFFFFFFFFFFF})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary_part(make_unaligned(<<1,2,3>>),{16#FFFFFFFFFFFFFFFF,
+ 16#7FFFFFFFFFFFFFFF})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary_part(make_unaligned(<<1,2,3>>),{16#FFFFFFFFFFFFFFFFFF,
+ -16#7FFF})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary_part(make_unaligned(<<1,2,3>>),{16#FF,
+ -16#7FFF})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:bin_to_list(<<1,2,3>>,{16#FF,
+ 16#FFFFFFFFFFFFFFFF})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:bin_to_list(<<1,2,3>>,{16#FFFFFFFFFFFFFFFF,
+ -16#7FFFFFFFFFFFFFFF-1})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:bin_to_list(<<1,2,3>>,{16#FFFFFFFFFFFFFFFF,
+ 16#7FFFFFFFFFFFFFFF})),
+ ?line [1,2,3] =
+ ?MASK_ERROR(
+ binary:bin_to_list(<<1,2,3>>)),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:bin_to_list(<<1,2,3>>,[])),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:bin_to_list(<<1,2,3>>,{1,2,3})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:bin_to_list(<<1,2,3>>,{1.0,1})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:bin_to_list(<<1,2,3>>,{1,1.0})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:bin_to_list(<<1,2,3:3>>,{1,1})),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:bin_to_list(<<1,2,3:3>>)),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:bin_to_list([1,2,3])),
+
+ ?line nomatch =
+ ?MASK_ERROR(binary:match(<<1,2,3>>,<<1>>,[{scope,{0,0}}])),
+ ?line badarg =
+ ?MASK_ERROR(binary:match(<<1,2,3>>,{bm,<<>>},[{scope,{0,1}}])),
+ ?line badarg =
+ ?MASK_ERROR(binary:match(<<1,2,3>>,[],[{scope,{0,1}}])),
+ ?line badarg =
+ ?MASK_ERROR(binary:match(<<1,2,3>>,{ac,<<>>},[{scope,{0,1}}])),
+ ?line {bm,BMMagic} = binary:compile_pattern([<<1,2,3>>]),
+ ?line {ac,ACMagic} = binary:compile_pattern([<<1,2,3>>,<<4,5>>]),
+ ?line badarg =
+ ?MASK_ERROR(binary:match(<<1,2,3>>,{bm,ACMagic},[{scope,{0,1}}])),
+ ?line badarg =
+ ?MASK_ERROR(binary:match(<<1,2,3>>,{ac,BMMagic},[{scope,{0,1}}])),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:match(<<1,2,3>>,
+ {bm,ets:match_spec_compile([{'_',[],['$_']}])},
+ [{scope,{0,1}}])),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:match(<<1,2,3>>,
+ {ac,ets:match_spec_compile([{'_',[],['$_']}])},
+ [{scope,{0,1}}])),
+ ?line [] =
+ ?MASK_ERROR(binary:matches(<<1,2,3>>,<<1>>,[{scope,{0,0}}])),
+ ?line badarg =
+ ?MASK_ERROR(binary:matches(<<1,2,3>>,{bm,<<>>},[{scope,{0,1}}])),
+ ?line badarg =
+ ?MASK_ERROR(binary:matches(<<1,2,3>>,[],[{scope,{0,1}}])),
+ ?line badarg =
+ ?MASK_ERROR(binary:matches(<<1,2,3>>,{ac,<<>>},[{scope,{0,1}}])),
+ ?line badarg =
+ ?MASK_ERROR(binary:matches(<<1,2,3>>,{bm,ACMagic},[{scope,{0,1}}])),
+ ?line badarg =
+ ?MASK_ERROR(binary:matches(<<1,2,3>>,{ac,BMMagic},[{scope,{0,1}}])),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:matches(<<1,2,3>>,
+ {bm,ets:match_spec_compile([{'_',[],['$_']}])},
+ [{scope,{0,1}}])),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:matches(<<1,2,3>>,
+ {ac,ets:match_spec_compile([{'_',[],['$_']}])},
+ [{scope,{0,1}}])),
+ ?line badarg =
+ ?MASK_ERROR(binary:longest_common_prefix(
+ [<<0:10000,1,2,4,1:3>>,
+ <<0:10000,1,2,3>>])),
+ ?line badarg =
+ ?MASK_ERROR(binary:longest_common_suffix(
+ [<<0:10000,1,2,4,1:3>>,
+ <<0:10000,1,2,3>>])),
+ ?line badarg =
+ ?MASK_ERROR(binary:encode_unsigned(-1)),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:encode_unsigned(-16#FFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFF)),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:first(<<1,2,4,1:3>>)),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:first([1,2,4])),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:last(<<1,2,4,1:3>>)),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:last([1,2,4])),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:at(<<1,2,4,1:3>>,2)),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:at(<<>>,2)),
+ ?line badarg =
+ ?MASK_ERROR(
+ binary:at([1,2,4],2)),
+ ok.
+
+longest_common_trap(doc) ->
+ ["Whitebox test to force special trap conditions in longest_common_{prefix,suffix}"];
+longest_common_trap(Config) when is_list(Config) ->
+ ?line erts_debug:set_internal_state(available_internal_state,true),
+ ?line io:format("oldlimit: ~p~n",
+ [erts_debug:set_internal_state(binary_loop_limit,10)]),
+ erlang:bump_reductions(10000000),
+ ?line _ = binary:longest_common_prefix(
+ [<<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0,0,0,0,0,0,0,0,0,0,0,0,0,0,1,0:10000,1,3,3>>,
+ <<0:10000,1,2,4>>]),
+ ?line _ = binary:longest_common_prefix(
+ [<<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0,0,0,0,0,0,0,0,0,0,0,0,0,0>>,
+ <<0:10000,1,2,4>>]),
+ erlang:bump_reductions(10000000),
+ ?line _ = binary:longest_common_suffix(
+ [<<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,3,3,0:10000,0,1,0,0,0,0,0,0,0,0,0,0,0,0,0,0>>,
+ <<1,2,4,0:10000>>]),
+ ?line _ = binary:longest_common_suffix(
+ [<<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<1,2,4,0:10000>>,
+ <<0,0,0,0,0,0,0,0,0,0,0,0,0,0>>,
+ <<1,2,4,0:10000>>]),
+ Subj = subj(),
+ Len = byte_size(Subj),
+ ?line Len = binary:longest_common_suffix(
+ [Subj,Subj,Subj]),
+ ?line io:format("limit was: ~p~n",
+ [erts_debug:set_internal_state(binary_loop_limit,
+ default)]),
+ ?line erts_debug:set_internal_state(available_internal_state,false),
+ ok.
+
+subj() ->
+ Me = self(),
+ spawn(fun() ->
+ X0 = iolist_to_binary([
+ "1234567890",
+ %lists:seq(16#21, 16#7e),
+ lists:duplicate(100, $x)
+ ]),
+ Me ! X0,
+ receive X -> X end
+ end),
+ X0 = receive A -> A end,
+ <<X1:32/binary,_/binary>> = X0,
+ Subject= <<X1/binary>>,
+ Subject.
+
+
+interesting(doc) ->
+ ["Try some interesting patterns"];
+interesting(Config) when is_list(Config) ->
+ X = do_interesting(binary),
+ X = do_interesting(binref).
+
+do_interesting(Module) ->
+ ?line {0,4} = Module:match(<<"123456">>,
+ Module:compile_pattern([<<"12">>,<<"1234">>,
+ <<"23">>,<<"3">>,
+ <<"34">>,<<"456">>,
+ <<"45">>,<<"6">>])),
+ ?line [{0,4},{5,1}] = Module:matches(<<"123456">>,
+ Module:compile_pattern([<<"12">>,<<"1234">>,
+ <<"23">>,<<"3">>,
+ <<"34">>,<<"456">>,
+ <<"45">>,<<"6">>])),
+ ?line [{0,4}] = Module:matches(<<"123456">>,
+ Module:compile_pattern([<<"12">>,<<"1234">>,
+ <<"23">>,<<"3">>,
+ <<"34">>,<<"456">>,
+ <<"45">>])),
+ ?line [{0,2},{2,2}] = Module:matches(<<"123456">>,
+ Module:compile_pattern([<<"12">>,
+ <<"23">>,<<"3">>,
+ <<"34">>,<<"456">>,
+ <<"45">>])),
+ ?line {1,4} = Module:match(<<"123456">>,
+ Module:compile_pattern([<<"34">>,<<"34">>,
+ <<"12347">>,<<"2345">>])),
+ ?line [{1,4}] = Module:matches(<<"123456">>,
+ Module:compile_pattern([<<"34">>,<<"34">>,
+ <<"12347">>,<<"2345">>])),
+ ?line [{2,2}] = Module:matches(<<"123456">>,
+ Module:compile_pattern([<<"34">>,<<"34">>,
+ <<"12347">>,<<"2346">>])),
+
+ ?line {0,4} = Module:match(<<"123456">>,
+ [<<"12">>,<<"1234">>,
+ <<"23">>,<<"3">>,
+ <<"34">>,<<"456">>,
+ <<"45">>,<<"6">>]),
+ ?line [{0,4},{5,1}] = Module:matches(<<"123456">>,
+ [<<"12">>,<<"1234">>,
+ <<"23">>,<<"3">>,
+ <<"34">>,<<"456">>,
+ <<"45">>,<<"6">>]),
+ ?line [{0,4}] = Module:matches(<<"123456">>,
+ [<<"12">>,<<"1234">>,
+ <<"23">>,<<"3">>,
+ <<"34">>,<<"456">>,
+ <<"45">>]),
+ ?line [{0,2},{2,2}] = Module:matches(<<"123456">>,
+ [<<"12">>,
+ <<"23">>,<<"3">>,
+ <<"34">>,<<"456">>,
+ <<"45">>]),
+ ?line {1,4} = Module:match(<<"123456">>,
+ [<<"34">>,<<"34">>,
+ <<"12347">>,<<"2345">>]),
+ ?line [{1,4}] = Module:matches(<<"123456">>,
+ [<<"34">>,<<"34">>,
+ <<"12347">>,<<"2345">>]),
+ ?line [{2,2}] = Module:matches(<<"123456">>,
+ [<<"34">>,<<"34">>,
+ <<"12347">>,<<"2346">>]),
+ ?line nomatch = Module:match(<<1,2,3,4>>,<<2>>,[{scope,{0,1}}]),
+ ?line {1,1} = Module:match(<<1,2,3,4>>,<<2>>,[{scope,{0,2}}]),
+ ?line nomatch = Module:match(<<1,2,3,4>>,<<2,3>>,[{scope,{0,2}}]),
+ ?line {1,2} = Module:match(<<1,2,3,4>>,<<2,3>>,[{scope,{0,3}}]),
+ ?line {1,2} = Module:match(<<1,2,3,4>>,<<2,3>>,[{scope,{0,4}}]),
+ ?line badarg = ?MASK_ERROR(Module:match(<<1,2,3,4>>,<<2,3>>,
+ [{scope,{0,5}}])),
+ ?line {1,2} = Module:match(<<1,2,3,4>>,<<2,3>>,[{scope,{4,-4}}]),
+ ?line {0,3} = Module:match(<<1,2,3,4>>,<<1,2,3>>,[{scope,{4,-4}}]),
+ ?line {0,4} = Module:match(<<1,2,3,4>>,<<1,2,3,4>>,[{scope,{4,-4}}]),
+ ?line badarg = ?MASK_ERROR(Module:match(<<1,2,3,4>>,<<1,2,3,4>>,
+ [{scope,{3,-4}}])),
+ ?line [] = Module:matches(<<1,2,3,4>>,<<2>>,[{scope,{0,1}}]),
+ ?line [{1,1}] = Module:matches(<<1,2,3,4>>,[<<2>>,<<3>>],[{scope,{0,2}}]),
+ ?line [] = Module:matches(<<1,2,3,4>>,<<2,3>>,[{scope,{0,2}}]),
+ ?line [{1,2}] = Module:matches(<<1,2,3,4>>,<<2,3>>,[{scope,{0,3}}]),
+ ?line [{1,2}] = Module:matches(<<1,2,3,4>>,<<2,3>>,[{scope,{0,4}}]),
+ ?line [{1,2}] = Module:matches(<<1,2,3,4>>,[<<2,3>>,<<4>>],
+ [{scope,{0,3}}]),
+ ?line [{1,2},{3,1}] = Module:matches(<<1,2,3,4>>,[<<2,3>>,<<4>>],
+ [{scope,{0,4}}]),
+ ?line badarg = ?MASK_ERROR(Module:matches(<<1,2,3,4>>,<<2,3>>,
+ [{scope,{0,5}}])),
+ ?line [{1,2}] = Module:matches(<<1,2,3,4>>,<<2,3>>,[{scope,{4,-4}}]),
+ ?line [{1,2},{3,1}] = Module:matches(<<1,2,3,4>>,[<<2,3>>,<<4>>],
+ [{scope,{4,-4}}]),
+ ?line [{0,3}] = Module:matches(<<1,2,3,4>>,<<1,2,3>>,[{scope,{4,-4}}]),
+ ?line [{0,4}] = Module:matches(<<1,2,3,4>>,<<1,2,3,4>>,[{scope,{4,-4}}]),
+ ?line badarg = ?MASK_ERROR(Module:matches(<<1,2,3,4>>,<<1,2,3,4>>,
+ [{scope,{3,-4}}])),
+ ?line badarg = ?MASK_ERROR(Module:matches(<<1,2,3,4>>,[<<1,2,3,4>>],
+ [{scope,{3,-4}}])),
+ ?line [<<1,2,3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,<<4,5>>),
+ ?line [<<1,2,3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>]),
+ ?line [<<1,2,3>>,<<6>>,<<8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>],[global]),
+ ?line [<<1,2,3>>,<<6>>,<<>>,<<>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],
+ [global]),
+ ?line [<<1,2,3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],
+ [global,trim]),
+ ?line [<<1,2,3,4,5,6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],
+ [global,trim,{scope,{0,4}}]),
+ ?line [<<1,2,3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],
+ [global,trim,{scope,{0,5}}]),
+ ?line badarg = ?MASK_ERROR(
+ Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global,trim,{scope,{0,5}}])),
+ ?line <<1,2,3,99,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,[]),
+ ?line <<1,2,3,99,6,99,99>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global]),
+ ?line <<1,2,3,99,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global,{scope,{0,5}}]),
+ ?line <<1,2,3,99,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global,{scope,{0,5}}]),
+ ?line <<1,2,3,99,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global,{scope,{0,5}}]),
+ ?line badarg = ?MASK_ERROR(Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global,{scope,{0,5}},
+ {insert,1}])),
+ ?line <<1,2,3,99,4,5,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<99>>,
+ [global,{scope,{0,5}},
+ {insert_replaced,1}]),
+ ?line <<1,2,3,9,4,5,9,6,7,8>> = Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],
+ <<9,9>>,
+ [global,{scope,{0,5}},
+ {insert_replaced,1}]),
+ ?line badarg = ?MASK_ERROR(Module:replace(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],<<>>,
+ [global,{scope,{0,5}},
+ {insert_replaced,1}])),
+ ?line 2 = Module:longest_common_prefix([<<1,2,4>>,<<1,2,3>>]),
+ ?line 2 = Module:longest_common_prefix([<<1,2,4>>,<<1,2>>]),
+ ?line 1 = Module:longest_common_prefix([<<1,2,4>>,<<1>>]),
+ ?line 0 = Module:longest_common_prefix([<<1,2,4>>,<<>>]),
+ ?line 1 = Module:longest_common_prefix([<<1,2,4>>,<<1,2,3>>,<<1,3,3>>]),
+ ?line 1 = Module:longest_common_prefix([<<1,2,4>>,<<1,2,3>>,<<1,3,3>>,<<1,2,4>>]),
+ ?line 1251 = Module:longest_common_prefix([<<0:10000,1,2,4>>,
+ <<0:10000,1,2,3>>,
+ <<0:10000,1,3,3>>,
+ <<0:10000,1,2,4>>]),
+ ?line 12501 = Module:longest_common_prefix([<<0:100000,1,2,4>>,
+ <<0:100000,1,2,3>>,
+ <<0:100000,1,3,3>>,
+ <<0:100000,1,2,4>>]),
+ ?line 1251 = Module:longest_common_prefix(
+ [make_unaligned(<<0:10000,1,2,4>>),
+ <<0:10000,1,2,3>>,
+ make_unaligned(<<0:10000,1,3,3>>),
+ <<0:10000,1,2,4>>]),
+ ?line 12501 = Module:longest_common_prefix(
+ [<<0:100000,1,2,4>>,
+ make_unaligned(<<0:100000,1,2,3>>),
+ <<0:100000,1,3,3>>,
+ make_unaligned(<<0:100000,1,2,4>>)]),
+ ?line 1250001 = Module:longest_common_prefix([<<0:10000000,1,2,4>>,
+ <<0:10000000,1,2,3>>,
+ <<0:10000000,1,3,3>>,
+ <<0:10000000,1,2,4>>]),
+ if % Too cruel for the reference implementation
+ Module =:= binary ->
+ ?line erts_debug:set_internal_state(available_internal_state,true),
+ ?line io:format("oldlimit: ~p~n",
+ [erts_debug:set_internal_state(
+ binary_loop_limit,100)]),
+ ?line 1250001 = Module:longest_common_prefix(
+ [<<0:10000000,1,2,4>>,
+ <<0:10000000,1,2,3>>,
+ <<0:10000000,1,3,3>>,
+ <<0:10000000,1,2,4>>]),
+ ?line io:format("limit was: ~p~n",
+ [erts_debug:set_internal_state(binary_loop_limit,
+ default)]),
+ ?line erts_debug:set_internal_state(available_internal_state,
+ false);
+ true ->
+ ok
+ end,
+ ?line 1 = Module:longest_common_suffix([<<0:100000000,1,2,4,5>>,
+ <<0:100000000,1,2,3,5>>,
+ <<0:100000000,1,3,3,5>>,
+ <<0:100000000,1,2,4,5>>]),
+ ?line 1 = Module:longest_common_suffix([<<1,2,4,5>>,
+ <<0:100000000,1,2,3,5>>,
+ <<0:100000000,1,3,3,5>>,
+ <<0:100000000,1,2,4,5>>]),
+ ?line 1 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<5,5>>,
+ <<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5>>]),
+ ?line 0 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<5,5>>,
+ <<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4>>]),
+ ?line 2 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<5,5>>,
+ <<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5,5>>]),
+ ?line 1 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<5>>,
+ <<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5,5>>]),
+ ?line 0 = Module:longest_common_suffix([<<1,2,4,5,5>>,<<>>,
+ <<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5,5>>]),
+ ?line 0 = Module:longest_common_suffix([<<>>,<<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5,5>>]),
+ ?line 0 = Module:longest_common_suffix([<<>>,<<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5,5>>]),
+ ?line 2 = Module:longest_common_suffix([<<5,5>>,<<0:100000000,1,3,3,5,5>>,
+ <<0:100000000,1,2,4,5,5>>]),
+ ?line 2 = Module:longest_common_suffix([<<5,5>>,<<5,5>>,<<4,5,5>>]),
+ ?line 2 = Module:longest_common_suffix([<<5,5>>,<<5,5>>,<<5,5>>]),
+ ?line 3 = Module:longest_common_suffix([<<4,5,5>>,<<4,5,5>>,<<4,5,5>>]),
+ ?line 0 = Module:longest_common_suffix([<<>>]),
+ ?line badarg = ?MASK_ERROR(Module:longest_common_suffix([])),
+ ?line badarg = ?MASK_ERROR(Module:longest_common_suffix([apa])),
+ ?line badarg = ?MASK_ERROR(Module:longest_common_suffix([[<<>>]])),
+ ?line badarg = ?MASK_ERROR(Module:longest_common_suffix([[<<0>>,
+ <<1:9>>]])),
+ ?line 0 = Module:longest_common_prefix([<<>>]),
+ ?line badarg = ?MASK_ERROR(Module:longest_common_prefix([])),
+ ?line badarg = ?MASK_ERROR(Module:longest_common_prefix([apa])),
+ ?line badarg = ?MASK_ERROR(Module:longest_common_prefix([[<<>>]])),
+ ?line badarg = ?MASK_ERROR(Module:longest_common_prefix([[<<0>>,
+ <<1:9>>]])),
+
+ ?line <<1:6,Bin:3/binary,_:2>> = <<1:6,1,2,3,1:2>>,
+ ?line <<1,2,3>> = Bin,
+ ?line 1 = Module:first(Bin),
+ ?line 1 = Module:first(<<1>>),
+ ?line 1 = Module:first(<<1,2,3>>),
+ ?line badarg = ?MASK_ERROR(Module:first(<<>>)),
+ ?line badarg = ?MASK_ERROR(Module:first(apa)),
+ ?line 3 = Module:last(Bin),
+ ?line 1 = Module:last(<<1>>),
+ ?line 3 = Module:last(<<1,2,3>>),
+ ?line badarg = ?MASK_ERROR(Module:last(<<>>)),
+ ?line badarg = ?MASK_ERROR(Module:last(apa)),
+ ?line 1 = Module:at(Bin,0),
+ ?line 1 = Module:at(<<1>>,0),
+ ?line 1 = Module:at(<<1,2,3>>,0),
+ ?line 2 = Module:at(<<1,2,3>>,1),
+ ?line 3 = Module:at(<<1,2,3>>,2),
+ ?line badarg = ?MASK_ERROR(Module:at(<<1,2,3>>,3)),
+ ?line badarg = ?MASK_ERROR(Module:at(<<1,2,3>>,-1)),
+ ?line badarg = ?MASK_ERROR(Module:at(<<1,2,3>>,apa)),
+ ?line "hejsan" = [ Module:at(<<"hejsan">>,I) || I <- lists:seq(0,5) ],
+
+ ?line badarg = ?MASK_ERROR(Module:bin_to_list(<<1,2,3>>,3,-4)),
+ ?line [1,2,3] = ?MASK_ERROR(Module:bin_to_list(<<1,2,3>>,3,-3)),
+
+ ?line badarg = ?MASK_ERROR(Module:decode_unsigned(<<1,2,1:2>>,big)),
+ ?line badarg = ?MASK_ERROR(Module:decode_unsigned(<<1,2,1:2>>,little)),
+ ?line badarg = ?MASK_ERROR(Module:decode_unsigned(apa)),
+ ?line badarg = ?MASK_ERROR(Module:decode_unsigned(125,little)),
+ ?line 0 = ?MASK_ERROR(Module:decode_unsigned(<<>>,little)),
+ ?line 0 = ?MASK_ERROR(Module:decode_unsigned(<<>>,big)),
+ ?line 0 = ?MASK_ERROR(Module:decode_unsigned(<<0>>,little)),
+ ?line 0 = ?MASK_ERROR(Module:decode_unsigned(<<0>>,big)),
+ ?line 0 = ?MASK_ERROR(Module:decode_unsigned(make_unaligned(<<0>>),
+ little)),
+ ?line 0 = ?MASK_ERROR(Module:decode_unsigned(make_unaligned(<<0>>),big)),
+ ?line badarg = ?MASK_ERROR(Module:encode_unsigned(apa)),
+ ?line badarg = ?MASK_ERROR(Module:encode_unsigned(125.3,little)),
+ ?line badarg = ?MASK_ERROR(Module:encode_unsigned({1},little)),
+ ?line badarg = ?MASK_ERROR(Module:encode_unsigned([1],little)),
+ ?line <<0>> = ?MASK_ERROR(Module:encode_unsigned(0,little)),
+ ?line <<0>> = ?MASK_ERROR(Module:encode_unsigned(0,big)),
+ ok.
+
+encode_decode(doc) ->
+ ["test binary:encode_unsigned/1,2 and binary:decode_unsigned/1,2"];
+encode_decode(Config) when is_list(Config) ->
+ ?line random:seed({1271,769940,559934}),
+ ?line ok = encode_decode_loop({1,200},1000), % Need to be long enough
+ % to create offheap binaries
+ ok.
+
+encode_decode_loop(_Range,0) ->
+ ok;
+encode_decode_loop(Range, X) ->
+ ?line N = random_number(Range),
+ ?line A = binary:encode_unsigned(N),
+ ?line B = binary:encode_unsigned(N,big),
+ ?line C = binref:encode_unsigned(N),
+ ?line D = binref:encode_unsigned(N,big),
+ ?line E = binary:encode_unsigned(N,little),
+ ?line F = binref:encode_unsigned(N,little),
+ ?line G = binary:decode_unsigned(A),
+ ?line H = binary:decode_unsigned(A,big),
+ ?line I = binref:decode_unsigned(A),
+ ?line J = binary:decode_unsigned(E,little),
+ ?line K = binref:decode_unsigned(E,little),
+ ?line L = binary:decode_unsigned(make_unaligned(A)),
+ ?line M = binary:decode_unsigned(make_unaligned(E),little),
+ ?line PaddedBig = <<0:48,A/binary>>,
+ ?line PaddedLittle = <<E/binary,0:48>>,
+ ?line O = binary:decode_unsigned(PaddedBig),
+ ?line P = binary:decode_unsigned(make_unaligned(PaddedBig)),
+ ?line Q = binary:decode_unsigned(PaddedLittle,little),
+ ?line R = binary:decode_unsigned(make_unaligned(PaddedLittle),little),
+ ?line S = binref:decode_unsigned(PaddedLittle,little),
+ ?line T = binref:decode_unsigned(PaddedBig),
+ case (((A =:= B) and (B =:= C) and (C =:= D)) and
+ ((E =:= F)) and
+ ((N =:= G) and (G =:= H) and (H =:= I) and
+ (I =:= J) and (J =:= K) and (K =:= L) and (L =:= M)) and
+ ((M =:= O) and (O =:= P) and (P =:= Q) and (Q =:= R) and
+ (R =:= S) and (S =:= T)))of
+ true ->
+ encode_decode_loop(Range,X-1);
+ _ ->
+ io:format("Failed to encode/decode ~w~n(Results ~p)~n",
+ [N,[A,B,C,D,E,F,G,H,I,J,K,L,M,x,O,P,Q,R,S,T]]),
+ exit(mismatch)
+ end.
+
+guard(doc) ->
+ ["Smoke test of the guard BIFs binary_part/2,3"];
+guard(Config) when is_list(Config) ->
+ {comment, "Guard tests are run in emulator test suite"}.
+
+referenced(doc) ->
+ ["Test refernced_byte_size/1 bif."];
+referenced(Config) when is_list(Config) ->
+ ?line badarg = ?MASK_ERROR(binary:referenced_byte_size([])),
+ ?line badarg = ?MASK_ERROR(binary:referenced_byte_size(apa)),
+ ?line badarg = ?MASK_ERROR(binary:referenced_byte_size({})),
+ ?line badarg = ?MASK_ERROR(binary:referenced_byte_size(1)),
+ ?line A = <<1,2,3>>,
+ ?line B = binary:copy(A,1000),
+ ?line 3 = binary:referenced_byte_size(A),
+ ?line 3000 = binary:referenced_byte_size(B),
+ ?line <<_:8,C:2/binary>> = A,
+ ?line 3 = binary:referenced_byte_size(C),
+ ?line 2 = binary:referenced_byte_size(binary:copy(C)),
+ ?line <<_:7,D:2/binary,_:1>> = A,
+ ?line 2 = binary:referenced_byte_size(binary:copy(D)),
+ ?line 3 = binary:referenced_byte_size(D),
+ ?line <<_:8,E:2/binary,_/binary>> = B,
+ ?line 3000 = binary:referenced_byte_size(E),
+ ?line 2 = binary:referenced_byte_size(binary:copy(E)),
+ ?line <<_:7,F:2/binary,_:1,_/binary>> = B,
+ ?line 2 = binary:referenced_byte_size(binary:copy(F)),
+ ?line 3000 = binary:referenced_byte_size(F),
+ ok.
+
+
+
+list_to_bin(doc) ->
+ ["Test list_to_bin/1 bif"];
+list_to_bin(Config) when is_list(Config) ->
+ %% Just some smoke_tests first, then go nuts with random cases
+ ?line badarg = ?MASK_ERROR(binary:list_to_bin({})),
+ ?line badarg = ?MASK_ERROR(binary:list_to_bin(apa)),
+ ?line badarg = ?MASK_ERROR(binary:list_to_bin(<<"apa">>)),
+ F1 = fun(L) ->
+ ?MASK_ERROR(binref:list_to_bin(L))
+ end,
+ F2 = fun(L) ->
+ ?MASK_ERROR(binary:list_to_bin(L))
+ end,
+ ?line random_iolist:run(1000,F1,F2),
+ ok.
+
+copy(doc) ->
+ ["Test copy/1,2 bif's"];
+copy(Config) when is_list(Config) ->
+ ?line <<1,2,3>> = binary:copy(<<1,2,3>>),
+ ?line RS = random_string({1,10000}),
+ ?line RS = RS2 = binary:copy(RS),
+ ?line false = erts_debug:same(RS,RS2),
+ ?line <<>> = ?MASK_ERROR(binary:copy(<<1,2,3>>,0)),
+ ?line badarg = ?MASK_ERROR(binary:copy(<<1,2,3:3>>,2)),
+ ?line badarg = ?MASK_ERROR(binary:copy([],0)),
+ ?line <<>> = ?MASK_ERROR(binary:copy(<<>>,0)),
+ ?line badarg = ?MASK_ERROR(binary:copy(<<1,2,3>>,1.0)),
+ ?line badarg = ?MASK_ERROR(binary:copy(<<1,2,3>>,
+ 16#FFFFFFFFFFFFFFFFFFFFFFFFFFFFFF)),
+ ?line <<>> = binary:copy(<<>>,10000),
+ ?line random:seed({1271,769940,559934}),
+ ?line ok = random_copy(3000),
+ ?line erts_debug:set_internal_state(available_internal_state,true),
+ ?line io:format("oldlimit: ~p~n",
+ [erts_debug:set_internal_state(binary_loop_limit,10)]),
+ ?line Subj = subj(),
+ ?line XX = binary:copy(Subj,1000),
+ ?line XX = binref:copy(Subj,1000),
+ ?line ok = random_copy(1000),
+ ?line kill_copy_loop(1000),
+ ?line io:format("limit was: ~p~n",
+ [erts_debug:set_internal_state(binary_loop_limit,
+ default)]),
+ ?line erts_debug:set_internal_state(available_internal_state,false),
+ ok.
+
+kill_copy_loop(0) ->
+ ok;
+kill_copy_loop(N) ->
+ {Pid,Ref} = spawn_monitor(fun() ->
+ ok = random_copy(1000)
+ end),
+ receive
+ after 10 ->
+ ok
+ end,
+ exit(Pid,kill),
+ receive
+ {'DOWN',Ref,process,Pid,_} ->
+ kill_copy_loop(N-1)
+ after 1000 ->
+ exit(did_not_die)
+ end.
+
+random_copy(0) ->
+ ok;
+random_copy(N) ->
+ Str = random_string({0,N}),
+ Num = random:uniform(N div 10+1),
+ A = ?MASK_ERROR(binary:copy(Str,Num)),
+ B = ?MASK_ERROR(binref:copy(Str,Num)),
+ C = ?MASK_ERROR(binary:copy(make_unaligned(Str),Num)),
+ case {(A =:= B), (B =:= C)} of
+ {true,true} ->
+ random_copy(N-1);
+ _ ->
+ io:format("Failed to pick copy ~s ~p times~n",
+ [Str,Num]),
+ io:format("A:~p,~nB:~p,~n,C:~p.~n",
+ [A,B,C]),
+ exit(mismatch)
+ end.
+
+bin_to_list(doc) ->
+ ["Test bin_to_list/1,2,3 bif's"];
+bin_to_list(Config) when is_list(Config) ->
+ %% Just some smoke_tests first, then go nuts with random cases
+ ?line X = <<1,2,3,4,0:1000000,5>>,
+ ?line Y = make_unaligned(X),
+ ?line LX = binary:bin_to_list(X),
+ ?line LX = binary:bin_to_list(X,0,byte_size(X)),
+ ?line LX = binary:bin_to_list(X,byte_size(X),-byte_size(X)),
+ ?line LX = binary:bin_to_list(X,{0,byte_size(X)}),
+ ?line LX = binary:bin_to_list(X,{byte_size(X),-byte_size(X)}),
+ ?line LY = binary:bin_to_list(Y),
+ ?line LY = binary:bin_to_list(Y,0,byte_size(Y)),
+ ?line LY = binary:bin_to_list(Y,byte_size(Y),-byte_size(Y)),
+ ?line LY = binary:bin_to_list(Y,{0,byte_size(Y)}),
+ ?line LY = binary:bin_to_list(Y,{byte_size(Y),-byte_size(Y)}),
+ ?line 1 = hd(LX),
+ ?line 5 = lists:last(LX),
+ ?line 1 = hd(LY),
+ ?line 5 = lists:last(LY),
+ ?line X = list_to_binary(LY),
+ ?line Y = list_to_binary(LY),
+ ?line X = list_to_binary(LY),
+ ?line [5] = lists:nthtail(byte_size(X)-1,LX),
+ ?line [0,5] = lists:nthtail(byte_size(X)-2,LX),
+ ?line [0,5] = lists:nthtail(byte_size(Y)-2,LY),
+ ?line random:seed({1271,769940,559934}),
+ ?line ok = random_bin_to_list(5000),
+ ok.
+
+random_bin_to_list(0) ->
+ ok;
+random_bin_to_list(N) ->
+ Str = random_string({1,N}),
+ Parts0 = random_parts(10,N),
+ Parts1 = Parts0 ++ [ {X+Y,-Y} || {X,Y} <- Parts0 ],
+ [ begin
+ try
+ true = ?MASK_ERROR(binary:bin_to_list(Str,Z)) =:=
+ ?MASK_ERROR(binref:bin_to_list(Str,Z)),
+ true = ?MASK_ERROR(binary:bin_to_list(Str,Z)) =:=
+ ?MASK_ERROR(binary:bin_to_list(make_unaligned(Str),Z))
+ catch
+ _:_ ->
+ io:format("Error, Str = <<\"~s\">>.~nZ = ~p.~n",
+ [Str,Z]),
+ exit(badresult)
+ end
+ end || Z <- Parts1 ],
+ [ begin
+ try
+ true = ?MASK_ERROR(binary:bin_to_list(Str,A,B)) =:=
+ ?MASK_ERROR(binref:bin_to_list(Str,A,B)),
+ true = ?MASK_ERROR(binary:bin_to_list(Str,A,B)) =:=
+ ?MASK_ERROR(binary:bin_to_list(make_unaligned(Str),A,B))
+ catch
+ _:_ ->
+ io:format("Error, Str = <<\"~s\">>.~nA = ~p.~nB = ~p.~n",
+ [Str,A,B]),
+ exit(badresult)
+ end
+ end || {A,B} <- Parts1 ],
+ random_bin_to_list(N-1).
+
+parts(doc) ->
+ ["Test the part/2,3 bif's"];
+parts(Config) when is_list(Config) ->
+ %% Some simple smoke tests to begin with
+ ?line Simple = <<1,2,3,4,5,6,7,8>>,
+ ?line <<1,2>> = binary:part(Simple,0,2),
+ ?line <<1,2>> = binary:part(Simple,{0,2}),
+ ?line Simple = binary:part(Simple,0,8),
+ ?line Simple = binary:part(Simple,{0,8}),
+ ?line badarg = ?MASK_ERROR(binary:part(Simple,0,9)),
+ ?line badarg = ?MASK_ERROR(binary:part(Simple,{0,9})),
+ ?line badarg = ?MASK_ERROR(binary:part(Simple,1,8)),
+ ?line badarg = ?MASK_ERROR(binary:part(Simple,{1,8})),
+ ?line badarg = ?MASK_ERROR(binary:part(Simple,{3,-4})),
+ ?line badarg = ?MASK_ERROR(binary:part(Simple,{3.0,1})),
+ ?line badarg = ?MASK_ERROR(
+ binary:part(Simple,{16#FFFFFFFFFFFFFFFFFFFFFFFFFFFFF
+ ,1})),
+ ?line <<2,3,4,5,6,7,8>> = binary:part(Simple,{1,7}),
+ ?line <<2,3,4,5,6,7,8>> = binary:part(Simple,{8,-7}),
+ ?line Simple = binary:part(Simple,{8,-8}),
+ ?line badarg = ?MASK_ERROR(binary:part(Simple,{1,-8})),
+ ?line badarg = ?MASK_ERROR(binary:part(Simple,{8,-9})),
+ ?line badarg = ?MASK_ERROR(binary:part(Simple,{0,-1})),
+ ?line <<>> = binary:part(Simple,{8,0}),
+ ?line badarg = ?MASK_ERROR(binary:part(Simple,{9,0})),
+ ?line badarg = ?MASK_ERROR(binary:part(Simple,{-1,0})),
+ ?line badarg = ?MASK_ERROR(binary:part(Simple,{7,2})),
+ ?line <<8>> = binary:part(Simple,{7,1}),
+ ?line random:seed({1271,769940,559934}),
+ ?line random_parts(5000),
+ ok.
+
+
+random_parts(0) ->
+ ok;
+random_parts(N) ->
+ Str = random_string({1,N}),
+ Parts0 = random_parts(10,N),
+ Parts1 = Parts0 ++ [ {X+Y,-Y} || {X,Y} <- Parts0 ],
+ [ begin
+ true = ?MASK_ERROR(binary:part(Str,Z)) =:=
+ ?MASK_ERROR(binref:part(Str,Z)),
+ true = ?MASK_ERROR(binary:part(Str,Z)) =:=
+ ?MASK_ERROR(erlang:binary_part(Str,Z)),
+ true = ?MASK_ERROR(binary:part(Str,Z)) =:=
+ ?MASK_ERROR(binary:part(make_unaligned(Str),Z))
+ end || Z <- Parts1 ],
+ random_parts(N-1).
+
+random_parts(0,_) ->
+ [];
+random_parts(X,N) ->
+ Pos = random:uniform(N),
+ Len = random:uniform((Pos * 12) div 10),
+ [{Pos,Len} | random_parts(X-1,N)].
+
+random_ref_comp(doc) ->
+ ["Test pseudorandomly generated cases against reference imlementation"];
+random_ref_comp(Config) when is_list(Config) ->
+ ?line put(success_counter,0),
+ ?line random:seed({1271,769940,559934}),
+ ?line do_random_match_comp(5000,{1,40},{30,1000}),
+ io:format("Number of successes: ~p~n",[get(success_counter)]),
+ ?line do_random_match_comp2(5000,{1,40},{30,1000}),
+ io:format("Number of successes: ~p~n",[get(success_counter)]),
+ ?line do_random_match_comp3(5000,{1,40},{30,1000}),
+ io:format("Number of successes: ~p~n",[get(success_counter)]),
+ ?line do_random_match_comp4(5000,{1,40},{30,1000}),
+ io:format("Number of successes: ~p~n",[get(success_counter)]),
+ ?line do_random_matches_comp(5000,{1,40},{30,1000}),
+ io:format("Number of successes: ~p~n",[get(success_counter)]),
+ ?line do_random_matches_comp2(5000,{1,40},{30,1000}),
+ io:format("Number of successes: ~p~n",[get(success_counter)]),
+ ?line do_random_matches_comp3(5,{1,40},{30,1000}),
+ ?line erts_debug:set_internal_state(available_internal_state,true),
+ ?line io:format("oldlimit: ~p~n",[ erts_debug:set_internal_state(binary_loop_limit,100)]),
+ ?line do_random_match_comp(5000,{1,40},{30,1000}),
+ ?line do_random_matches_comp3(5,{1,40},{30,1000}),
+ ?line io:format("limit was: ~p~n",[ erts_debug:set_internal_state(binary_loop_limit,default)]),
+ ?line erts_debug:set_internal_state(available_internal_state,false),
+ ok.
+
+random_ref_sr_comp(doc) ->
+ ["Test pseudorandomly generated cases against reference imlementation of split and replace"];
+random_ref_sr_comp(Config) when is_list(Config) ->
+ ?line put(success_counter,0),
+ ?line random:seed({1271,769940,559934}),
+ ?line do_random_split_comp(5000,{1,40},{30,1000}),
+ io:format("Number of successes: ~p~n",[get(success_counter)]),
+ ?line do_random_replace_comp(5000,{1,40},{30,1000}),
+ io:format("Number of successes: ~p~n",[get(success_counter)]),
+ ?line do_random_split_comp2(5000,{1,40},{30,1000}),
+ io:format("Number of successes: ~p~n",[get(success_counter)]),
+ ?line do_random_replace_comp2(5000,{1,40},{30,1000}),
+ io:format("Number of successes: ~p~n",[get(success_counter)]),
+ ok.
+random_ref_fla_comp(doc) ->
+ ["Test pseudorandomly generated cases against reference imlementation of split and replace"];
+random_ref_fla_comp(Config) when is_list(Config) ->
+ ?line put(success_counter,0),
+ ?line random:seed({1271,769940,559934}),
+ ?line do_random_first_comp(5000,{1,1000}),
+ ?line do_random_last_comp(5000,{1,1000}),
+ ?line do_random_at_comp(5000,{1,1000}),
+ io:format("Number of successes: ~p~n",[get(success_counter)]),
+ ok.
+
+do_random_first_comp(0,_) ->
+ ok;
+do_random_first_comp(N,Range) ->
+ S = random_string(Range),
+ A = ?MASK_ERROR(binref:first(S)),
+ B = ?MASK_ERROR(binary:first(S)),
+ C = ?MASK_ERROR(binary:first(make_unaligned(S))),
+ case {(A =:= B), (B =:= C)} of
+ {true,true} ->
+ do_random_first_comp(N-1,Range);
+ _ ->
+ io:format("Failed to pick first of ~s~n",
+ [S]),
+ io:format("A:~p,~nB:~p,~n,C:~p.~n",
+ [A,B,C]),
+ exit(mismatch)
+ end.
+
+do_random_last_comp(0,_) ->
+ ok;
+do_random_last_comp(N,Range) ->
+ S = random_string(Range),
+ A = ?MASK_ERROR(binref:last(S)),
+ B = ?MASK_ERROR(binary:last(S)),
+ C = ?MASK_ERROR(binary:last(make_unaligned(S))),
+ case {(A =:= B), (B =:= C)} of
+ {true,true} ->
+ do_random_last_comp(N-1,Range);
+ _ ->
+ io:format("Failed to pick last of ~s~n",
+ [S]),
+ io:format("A:~p,~nB:~p,~n,C:~p.~n",
+ [A,B,C]),
+ exit(mismatch)
+ end.
+do_random_at_comp(0,_) ->
+ ok;
+do_random_at_comp(N,{Min,Max}=Range) ->
+ S = random_string(Range),
+ XMax = Min + ((Max - Min) * 3) div 4,
+ Pos = random_length({Min,XMax}), %% some out of range
+ A = ?MASK_ERROR(binref:at(S,Pos)),
+ B = ?MASK_ERROR(binary:at(S,Pos)),
+ C = ?MASK_ERROR(binary:at(make_unaligned(S),Pos)),
+ if
+ A =/= badarg ->
+ put(success_counter,get(success_counter)+1);
+ true ->
+ ok
+ end,
+ case {(A =:= B), (B =:= C)} of
+ {true,true} ->
+ do_random_at_comp(N-1,Range);
+ _ ->
+ io:format("Failed to pick last of ~s~n",
+ [S]),
+ io:format("A:~p,~nB:~p,~n,C:~p.~n",
+ [A,B,C]),
+ exit(mismatch)
+ end.
+
+do_random_matches_comp(0,_,_) ->
+ ok;
+do_random_matches_comp(N,NeedleRange,HaystackRange) ->
+ NumNeedles = element(2,HaystackRange) div element(2,NeedleRange),
+ Needles = [random_string(NeedleRange) ||
+ _ <- lists:duplicate(NumNeedles,a)],
+ Haystack = random_string(HaystackRange),
+ true = do_matches_comp(Needles,Haystack),
+ do_random_matches_comp(N-1,NeedleRange,HaystackRange).
+
+do_random_matches_comp2(0,_,_) ->
+ ok;
+do_random_matches_comp2(N,NeedleRange,HaystackRange) ->
+ NumNeedles = element(2,HaystackRange) div element(2,NeedleRange),
+ Haystack = random_string(HaystackRange),
+ Needles = [random_substring(NeedleRange,Haystack) ||
+ _ <- lists:duplicate(NumNeedles,a)],
+ true = do_matches_comp(Needles,Haystack),
+ do_random_matches_comp2(N-1,NeedleRange,HaystackRange).
+
+do_random_matches_comp3(0,_,_) ->
+ ok;
+do_random_matches_comp3(N,NeedleRange,HaystackRange) ->
+ NumNeedles = element(2,HaystackRange) div element(2,NeedleRange),
+ Haystack = random_string(HaystackRange),
+ Needles = [random_substring(NeedleRange,Haystack) ||
+ _ <- lists:duplicate(NumNeedles,a)],
+ RefRes = binref:matches(Haystack,Needles),
+ true = do_matches_comp_loop(10000,Needles,Haystack, RefRes),
+ do_random_matches_comp3(N-1,NeedleRange,HaystackRange).
+
+do_matches_comp_loop(0,_,_,_) ->
+ true;
+do_matches_comp_loop(N, Needles, Haystack0,RR) ->
+ DummySize=N*8,
+ Haystack1 = <<0:DummySize,Haystack0/binary>>,
+ RR1=[{X+N,Y} || {X,Y} <- RR],
+ true = do_matches_comp2(Needles,Haystack1,RR1),
+ Haystack2 = <<Haystack0/binary,Haystack1/binary>>,
+ RR2 = RR ++ [{X2+N+byte_size(Haystack0),Y2} || {X2,Y2} <- RR],
+ true = do_matches_comp2(Needles,Haystack2,RR2),
+ do_matches_comp_loop(N-1, Needles, Haystack0,RR).
+
+
+do_matches_comp2(N,H,A) ->
+ C = ?MASK_ERROR(binary:matches(H,N)),
+ case (A =:= C) of
+ true ->
+ true;
+ _ ->
+ io:format("Failed to match ~p (needle) against ~s (haystack)~n",
+ [N,H]),
+ io:format("A:~p,~n,C:~p.~n",
+ [A,C]),
+ exit(mismatch)
+ end.
+do_matches_comp(N,H) ->
+ A = ?MASK_ERROR(binref:matches(H,N)),
+ B = ?MASK_ERROR(binref:matches(H,binref:compile_pattern(N))),
+ C = ?MASK_ERROR(binary:matches(H,N)),
+ D = ?MASK_ERROR(binary:matches(make_unaligned(H),
+ binary:compile_pattern([make_unaligned2(X) || X <- N]))),
+ if
+ A =/= nomatch ->
+ put(success_counter,get(success_counter)+1);
+ true ->
+ ok
+ end,
+ case {(A =:= B), (B =:= C),(C =:= D)} of
+ {true,true,true} ->
+ true;
+ _ ->
+ io:format("Failed to match ~p (needle) against ~s (haystack)~n",
+ [N,H]),
+ io:format("A:~p,~nB:~p,~n,C:~p,~n,D:~p.~n",
+ [A,B,C,D]),
+ exit(mismatch)
+ end.
+
+do_random_match_comp(0,_,_) ->
+ ok;
+do_random_match_comp(N,NeedleRange,HaystackRange) ->
+ Needle = random_string(NeedleRange),
+ Haystack = random_string(HaystackRange),
+ true = do_match_comp(Needle,Haystack),
+ do_random_match_comp(N-1,NeedleRange,HaystackRange).
+
+do_random_match_comp2(0,_,_) ->
+ ok;
+do_random_match_comp2(N,NeedleRange,HaystackRange) ->
+ Haystack = random_string(HaystackRange),
+ Needle = random_substring(NeedleRange,Haystack),
+ true = do_match_comp(Needle,Haystack),
+ do_random_match_comp2(N-1,NeedleRange,HaystackRange).
+
+do_random_match_comp3(0,_,_) ->
+ ok;
+do_random_match_comp3(N,NeedleRange,HaystackRange) ->
+ NumNeedles = element(2,HaystackRange) div element(2,NeedleRange),
+ Haystack = random_string(HaystackRange),
+ Needles = [random_substring(NeedleRange,Haystack) ||
+ _ <- lists:duplicate(NumNeedles,a)],
+ true = do_match_comp3(Needles,Haystack),
+ do_random_match_comp3(N-1,NeedleRange,HaystackRange).
+
+do_random_match_comp4(0,_,_) ->
+ ok;
+do_random_match_comp4(N,NeedleRange,HaystackRange) ->
+ NumNeedles = element(2,HaystackRange) div element(2,NeedleRange),
+ Haystack = random_string(HaystackRange),
+ Needles = [random_string(NeedleRange) ||
+ _ <- lists:duplicate(NumNeedles,a)],
+ true = do_match_comp3(Needles,Haystack),
+ do_random_match_comp4(N-1,NeedleRange,HaystackRange).
+
+do_match_comp(N,H) ->
+ A = ?MASK_ERROR(binref:match(H,N)),
+ B = ?MASK_ERROR(binref:match(H,binref:compile_pattern([N]))),
+ C = ?MASK_ERROR(binary:match(make_unaligned(H),N)),
+ D = ?MASK_ERROR(binary:match(H,binary:compile_pattern([N]))),
+ E = ?MASK_ERROR(binary:match(H,binary:compile_pattern(make_unaligned(N)))),
+ if
+ A =/= nomatch ->
+ put(success_counter,get(success_counter)+1);
+ true ->
+ ok
+ end,
+ case {(A =:= B), (B =:= C),(C =:= D),(D =:= E)} of
+ {true,true,true,true} ->
+ true;
+ _ ->
+ io:format("Failed to match ~s (needle) against ~s (haystack)~n",
+ [N,H]),
+ io:format("A:~p,~nB:~p,~n,C:~p,~n,D:~p,E:~p.~n",
+ [A,B,C,D,E]),
+ exit(mismatch)
+ end.
+
+do_match_comp3(N,H) ->
+ A = ?MASK_ERROR(binref:match(H,N)),
+ B = ?MASK_ERROR(binref:match(H,binref:compile_pattern(N))),
+ C = ?MASK_ERROR(binary:match(H,N)),
+ D = ?MASK_ERROR(binary:match(H,binary:compile_pattern(N))),
+ if
+ A =/= nomatch ->
+ put(success_counter,get(success_counter)+1);
+ true ->
+ ok
+ end,
+ case {(A =:= B), (B =:= C),(C =:= D)} of
+ {true,true,true} ->
+ true;
+ _ ->
+ io:format("Failed to match ~s (needle) against ~s (haystack)~n",
+ [N,H]),
+ io:format("A:~p,~nB:~p,~n,C:~p,~n,D:~p.~n",
+ [A,B,C,D]),
+ exit(mismatch)
+ end.
+
+do_random_split_comp(0,_,_) ->
+ ok;
+do_random_split_comp(N,NeedleRange,HaystackRange) ->
+ Haystack = random_string(HaystackRange),
+ Needle = random_substring(NeedleRange,Haystack),
+ true = do_split_comp(Needle,Haystack,[]),
+ true = do_split_comp(Needle,Haystack,[global]),
+ true = do_split_comp(Needle,Haystack,[global,trim]),
+ do_random_split_comp(N-1,NeedleRange,HaystackRange).
+do_random_split_comp2(0,_,_) ->
+ ok;
+do_random_split_comp2(N,NeedleRange,HaystackRange) ->
+ NumNeedles = element(2,HaystackRange) div element(2,NeedleRange),
+ Haystack = random_string(HaystackRange),
+ Needles = [random_substring(NeedleRange,Haystack) ||
+ _ <- lists:duplicate(NumNeedles,a)],
+ true = do_split_comp(Needles,Haystack,[]),
+ true = do_split_comp(Needles,Haystack,[global]),
+ do_random_split_comp2(N-1,NeedleRange,HaystackRange).
+
+do_split_comp(N,H,Opts) ->
+ A = ?MASK_ERROR(binref:split(H,N,Opts)),
+ D = ?MASK_ERROR(binary:split(H,binary:compile_pattern(N),Opts)),
+ if
+ (A =/= [N]) and is_list(A) ->
+ put(success_counter,get(success_counter)+1);
+ true ->
+ ok
+ end,
+ case (A =:= D) of
+ true ->
+ true;
+ _ ->
+ io:format("Failed to split ~n~p ~n(haystack) with ~n~p ~n(needle) "
+ "~nand options ~p~n",
+ [H,N,Opts]),
+ io:format("A:~p,D:~p.~n",
+ [A,D]),
+ exit(mismatch)
+ end.
+
+do_random_replace_comp(0,_,_) ->
+ ok;
+do_random_replace_comp(N,NeedleRange,HaystackRange) ->
+ Haystack = random_string(HaystackRange),
+ Needle = random_substring(NeedleRange,Haystack),
+ Repl = random_string(NeedleRange),
+ Insertat = random_length(NeedleRange), %Sometimes larger than Repl
+ true = do_replace_comp(Needle,Haystack,Repl,[]),
+ true = do_replace_comp(Needle,Haystack,Repl,[global]),
+ true = do_replace_comp(Needle,Haystack,Repl,
+ [global,{insert_replaced,Insertat}]),
+ do_random_replace_comp(N-1,NeedleRange,HaystackRange).
+do_random_replace_comp2(0,_,_) ->
+ ok;
+do_random_replace_comp2(N,NeedleRange,HaystackRange) ->
+ NumNeedles = element(2,HaystackRange) div element(2,NeedleRange),
+ Haystack = random_string(HaystackRange),
+ Needles = [random_substring(NeedleRange,Haystack) ||
+ _ <- lists:duplicate(NumNeedles,a)],
+ Repl = random_string(NeedleRange),
+ Insertat = random_length(NeedleRange), %Sometimes larger than Repl
+ true = do_replace_comp(Needles,Haystack,Repl,[]),
+ true = do_replace_comp(Needles,Haystack,Repl,[global]),
+ true = do_replace_comp(Needles,Haystack,Repl,
+ [global,{insert_replaced,Insertat}]),
+ do_random_replace_comp2(N-1,NeedleRange,HaystackRange).
+
+do_replace_comp(N,H,R,Opts) ->
+ A = ?MASK_ERROR(binref:replace(H,N,R,Opts)),
+ D = ?MASK_ERROR(binary:replace(H,binary:compile_pattern(N),R,Opts)),
+ if
+ (A =/= N) and is_binary(A) ->
+ put(success_counter,get(success_counter)+1);
+ true ->
+ ok
+ end,
+ case (A =:= D) of
+ true ->
+ true;
+ _ ->
+ io:format("Failed to replace ~s (haystack) by ~s (needle) "
+ "inserting ~s (replacement) and options ~p~n",
+ [H,N,R,Opts]),
+ io:format("A:~p,D:~p.~n",
+ [A,D]),
+ exit(mismatch)
+ end.
+
+one_random_number(N) ->
+ M = ((N - 1) rem 10) + 1,
+ element(M,{$0,$1,$2,$3,$4,$5,$6,$7,$8,$9}).
+
+one_random(N) ->
+ M = ((N - 1) rem 68) + 1,
+ element(M,{$a,$b,$c,$d,$e,$f,$g,$h,$i,$j,$k,$l,$m,$n,$o,$p,$q,$r,$s,$t,
+ $u,$v,$w,$x,$y,$z,$�,$�,$�,$A,$B,$C,$D,$E,$F,$G,$H,
+ $I,$J,$K,$L,$M,$N,$O,$P,$Q,$R,$S,$T,$U,$V,$W,$X,$Y,$Z,$�,
+ $�,$�,$0,$1,$2,$3,$4,$5,$6,$7,$8,$9}).
+
+random_number({Min,Max}) -> % Min and Max are *length* of number in
+ % decimal positions
+ X = random:uniform(Max - Min + 1) + Min - 1,
+ list_to_integer([one_random_number(random:uniform(10)) || _ <- lists:seq(1,X)]).
+
+
+random_length({Min,Max}) ->
+ random:uniform(Max - Min + 1) + Min - 1.
+random_string({Min,Max}) ->
+ X = random:uniform(Max - Min + 1) + Min - 1,
+ list_to_binary([one_random(random:uniform(68)) || _ <- lists:seq(1,X)]).
+random_substring({Min,Max},Hay) ->
+ X = random:uniform(Max - Min + 1) + Min - 1,
+ Y = byte_size(Hay),
+ Z = if
+ X > Y -> Y;
+ true -> X
+ end,
+ PMax = Y - Z,
+ Pos = random:uniform(PMax + 1) - 1,
+ <<_:Pos/binary,Res:Z/binary,_/binary>> = Hay,
+ Res.
+
+mask_error({'EXIT',{Err,_}}) ->
+ Err;
+mask_error(Else) ->
+ Else.
+
+make_unaligned(Bin0) when is_binary(Bin0) ->
+ Bin1 = <<0:3,Bin0/binary,31:5>>,
+ Sz = byte_size(Bin0),
+ <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
+ Bin.
+make_unaligned2(Bin0) when is_binary(Bin0) ->
+ Bin1 = <<31:5,Bin0/binary,0:3>>,
+ Sz = byte_size(Bin0),
+ <<31:5,Bin:Sz/binary,0:3>> = id(Bin1),
+ Bin.
+
+id(I) -> I.
diff --git a/lib/stdlib/test/binref.erl b/lib/stdlib/test/binref.erl
new file mode 100644
index 0000000000..6d96736ef3
--- /dev/null
+++ b/lib/stdlib/test/binref.erl
@@ -0,0 +1,588 @@
+-module(binref).
+
+-export([compile_pattern/1,match/2,match/3,matches/2,matches/3,
+ split/2,split/3,replace/3,replace/4,first/1,last/1,at/2,
+ part/2,part/3,copy/1,copy/2,encode_unsigned/1,encode_unsigned/2,
+ decode_unsigned/1,decode_unsigned/2,referenced_byte_size/1,
+ longest_common_prefix/1,longest_common_suffix/1,bin_to_list/1,
+ bin_to_list/2,bin_to_list/3,list_to_bin/1]).
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% compile_pattern, a dummy
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+compile_pattern(Pattern) when is_binary(Pattern) ->
+ {[Pattern]};
+compile_pattern(Pattern) ->
+ try
+ [ true = is_binary(P) || P <- Pattern ],
+ {Pattern}
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% match and matches
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+match(H,N) ->
+ match(H,N,[]).
+match(Haystack,Needle,Options) when is_binary(Needle) ->
+ match(Haystack,[Needle],Options);
+match(Haystack,{Needles},Options) ->
+ match(Haystack,Needles,Options);
+match(Haystack,Needles,Options) ->
+ try
+ true = is_binary(Haystack) and is_list(Needles), % badarg, not function_clause
+ case get_opts_match(Options,nomatch) of
+ nomatch ->
+ mloop(Haystack,Needles);
+ {A,B} when B > 0 ->
+ <<_:A/binary,SubStack:B/binary,_/binary>> = Haystack,
+ mloop(SubStack,Needles,A,B+A);
+ {A,B} when B < 0 ->
+ Start = A + B,
+ Len = -B,
+ <<_:Start/binary,SubStack:Len/binary,_/binary>> = Haystack,
+ mloop(SubStack,Needles,Start,Len+Start);
+ _ ->
+ nomatch
+ end
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+matches(H,N) ->
+ matches(H,N,[]).
+matches(Haystack,Needle,Options) when is_binary(Needle) ->
+ matches(Haystack,[Needle],Options);
+matches(Haystack,{Needles},Options) ->
+ matches(Haystack,Needles,Options);
+matches(Haystack,Needles,Options) ->
+ try
+ true = is_binary(Haystack) and is_list(Needles), % badarg, not function_clause
+ case get_opts_match(Options,nomatch) of
+ nomatch ->
+ msloop(Haystack,Needles);
+ {A,B} when B > 0 ->
+ <<_:A/binary,SubStack:B/binary,_/binary>> = Haystack,
+ msloop(SubStack,Needles,A,B+A);
+ {A,B} when B < 0 ->
+ Start = A + B,
+ Len = -B,
+ <<_:Start/binary,SubStack:Len/binary,_/binary>> = Haystack,
+ msloop(SubStack,Needles,Start,Len+Start);
+ _ ->
+ []
+ end
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+mloop(Haystack,Needles) ->
+ mloop(Haystack,Needles,0,byte_size(Haystack)).
+
+mloop(_Haystack,_Needles,N,M) when N >= M ->
+ nomatch;
+mloop(Haystack,Needles,N,M) ->
+ case mloop2(Haystack,Needles,N,nomatch) of
+ nomatch ->
+ % Not found
+ <<_:8,NewStack/binary>> = Haystack,
+ mloop(NewStack,Needles,N+1,M);
+ {N,Len} ->
+ {N,Len}
+ end.
+
+msloop(Haystack,Needles) ->
+ msloop(Haystack,Needles,0,byte_size(Haystack)).
+
+msloop(_Haystack,_Needles,N,M) when N >= M ->
+ [];
+msloop(Haystack,Needles,N,M) ->
+ case mloop2(Haystack,Needles,N,nomatch) of
+ nomatch ->
+ % Not found
+ <<_:8,NewStack/binary>> = Haystack,
+ msloop(NewStack,Needles,N+1,M);
+ {N,Len} ->
+ NewN = N+Len,
+ if
+ NewN >= M ->
+ [{N,Len}];
+ true ->
+ <<_:Len/binary,NewStack/binary>> = Haystack,
+ [{N,Len} | msloop(NewStack,Needles,NewN,M)]
+ end
+ end.
+
+mloop2(_Haystack,[],_N,Res) ->
+ Res;
+mloop2(Haystack,[Needle|Tail],N,Candidate) ->
+ NS = byte_size(Needle),
+ case Haystack of
+ <<Needle:NS/binary,_/binary>> ->
+ NewCandidate = case Candidate of
+ nomatch ->
+ {N,NS};
+ {N,ONS} when ONS < NS ->
+ {N,NS};
+ Better ->
+ Better
+ end,
+ mloop2(Haystack,Tail,N,NewCandidate);
+ _ ->
+ mloop2(Haystack,Tail,N,Candidate)
+ end.
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% split
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+split(H,N) ->
+ split(H,N,[]).
+split(Haystack,{Needles},Options) ->
+ split(Haystack, Needles, Options);
+split(Haystack,Needles0,Options) ->
+ try
+ Needles = if
+ is_list(Needles0) ->
+ Needles0;
+ is_binary(Needles0) ->
+ [Needles0];
+ true ->
+ exit(badtype)
+ end,
+ {Part,Global,Trim} = get_opts_split(Options,{nomatch,false,false}),
+ {Start,End,NewStack} =
+ case Part of
+ nomatch ->
+ {0,byte_size(Haystack),Haystack};
+ {A,B} when B >= 0 ->
+ <<_:A/binary,SubStack:B/binary,_/binary>> = Haystack,
+ {A,A+B,SubStack};
+ {A,B} when B < 0 ->
+ S = A + B,
+ L = -B,
+ <<_:S/binary,SubStack:L/binary,_/binary>> = Haystack,
+ {S,S+L,SubStack}
+ end,
+ MList = if
+ Global ->
+ msloop(NewStack,Needles,Start,End);
+ true ->
+ case mloop(NewStack,Needles,Start,End) of
+ nomatch ->
+ [];
+ X ->
+ [X]
+ end
+ end,
+ do_split(Haystack,MList,0,Trim)
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+do_split(H,[],N,true) when N >= byte_size(H) ->
+ [];
+do_split(H,[],N,_) ->
+ [part(H,{N,byte_size(H)-N})];
+do_split(H,[{A,B}|T],N,Trim) ->
+ case part(H,{N,A-N}) of
+ <<>> ->
+ Rest = do_split(H,T,A+B,Trim),
+ case {Trim, Rest} of
+ {true,[]} ->
+ [];
+ _ ->
+ [<<>> | Rest]
+ end;
+ Oth ->
+ [Oth | do_split(H,T,A+B,Trim)]
+ end.
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% replace
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+replace(H,N,R) ->
+ replace(H,N,R,[]).
+replace(Haystack,{Needles},Replacement,Options) ->
+ replace(Haystack,Needles,Replacement,Options);
+
+replace(Haystack,Needles0,Replacement,Options) ->
+ try
+ Needles = if
+ is_list(Needles0) ->
+ Needles0;
+ is_binary(Needles0) ->
+ [Needles0];
+ true ->
+ exit(badtype)
+ end,
+ true = is_binary(Replacement), % Make badarg instead of function clause
+ {Part,Global,Insert} = get_opts_replace(Options,{nomatch,false,[]}),
+ {Start,End,NewStack} =
+ case Part of
+ nomatch ->
+ {0,byte_size(Haystack),Haystack};
+ {A,B} when B >= 0 ->
+ <<_:A/binary,SubStack:B/binary,_/binary>> = Haystack,
+ {A,A+B,SubStack};
+ {A,B} when B < 0 ->
+ S = A + B,
+ L = -B,
+ <<_:S/binary,SubStack:L/binary,_/binary>> = Haystack,
+ {S,S+L,SubStack}
+ end,
+ MList = if
+ Global ->
+ msloop(NewStack,Needles,Start,End);
+ true ->
+ case mloop(NewStack,Needles,Start,End) of
+ nomatch ->
+ [];
+ X ->
+ [X]
+ end
+ end,
+ ReplList = case Insert of
+ [] ->
+ Replacement;
+ Y when is_integer(Y) ->
+ splitat(Replacement,0,[Y]);
+ Li when is_list(Li) ->
+ splitat(Replacement,0,lists:sort(Li))
+ end,
+ erlang:iolist_to_binary(do_replace(Haystack,MList,ReplList,0))
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+
+do_replace(H,[],_,N) ->
+ [part(H,{N,byte_size(H)-N})];
+do_replace(H,[{A,B}|T],Replacement,N) ->
+ [part(H,{N,A-N}),
+ if
+ is_list(Replacement) ->
+ do_insert(Replacement, part(H,{A,B}));
+ true ->
+ Replacement
+ end
+ | do_replace(H,T,Replacement,A+B)].
+
+do_insert([X],_) ->
+ [X];
+do_insert([H|T],R) ->
+ [H,R|do_insert(T,R)].
+
+splitat(H,N,[]) ->
+ [part(H,{N,byte_size(H)-N})];
+splitat(H,N,[I|T]) ->
+ [part(H,{N,I-N})|splitat(H,I,T)].
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% first, last and at
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+first(Subject) ->
+ try
+ <<A:8,_/binary>> = Subject,
+ A
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+last(Subject) ->
+ try
+ N = byte_size(Subject) - 1,
+ <<_:N/binary,A:8>> = Subject,
+ A
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+at(Subject,X) ->
+ try
+ <<_:X/binary,A:8,_/binary>> = Subject,
+ A
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+% bin_to_list
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+bin_to_list(Subject) ->
+ try
+ binary_to_list(Subject)
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+bin_to_list(Subject,T) ->
+ try
+ {A0,B0} = T,
+ {A,B} = if
+ B0 < 0 ->
+ {A0+B0,-B0};
+ true ->
+ {A0,B0}
+ end,
+ binary_to_list(Subject,A+1,A+B)
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+bin_to_list(Subject,A,B) ->
+ try
+ bin_to_list(Subject,{A,B})
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+% list_to_bin
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+list_to_bin(List) ->
+ try
+ erlang:list_to_binary(List)
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% longest_common_prefix
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+longest_common_prefix(LB) ->
+ try
+ true = is_list(LB) and (length(LB) > 0), % Make badarg instead of function clause
+ do_longest_common_prefix(LB,0)
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+do_longest_common_prefix(LB,X) ->
+ case do_lcp(LB,X,no) of
+ true ->
+ do_longest_common_prefix(LB,X+1);
+ false ->
+ X
+ end.
+do_lcp([],_,_) ->
+ true;
+do_lcp([Bin|_],X,_) when byte_size(Bin) =< X ->
+ false;
+do_lcp([Bin|T],X,no) ->
+ Ch = at(Bin,X),
+ do_lcp(T,X,Ch);
+do_lcp([Bin|T],X,Ch) ->
+ Ch2 = at(Bin,X),
+ if
+ Ch =:= Ch2 ->
+ do_lcp(T,X,Ch);
+ true ->
+ false
+ end.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% longest_common_suffix
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+longest_common_suffix(LB) ->
+ try
+ true = is_list(LB) and (length(LB) > 0), % Make badarg instead of function clause
+ do_longest_common_suffix(LB,0)
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+do_longest_common_suffix(LB,X) ->
+ case do_lcs(LB,X,no) of
+ true ->
+ do_longest_common_suffix(LB,X+1);
+ false ->
+ X
+ end.
+do_lcs([],_,_) ->
+ true;
+do_lcs([Bin|_],X,_) when byte_size(Bin) =< X ->
+ false;
+do_lcs([Bin|T],X,no) ->
+ Ch = at(Bin,byte_size(Bin) - 1 - X),
+ do_lcs(T,X,Ch);
+do_lcs([Bin|T],X,Ch) ->
+ Ch2 = at(Bin,byte_size(Bin) - 1 - X),
+ if
+ Ch =:= Ch2 ->
+ do_lcs(T,X,Ch);
+ true ->
+ false
+ end.
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% part
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+part(Subject,Part) ->
+ try
+ do_part(Subject,Part)
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+part(Subject,Pos,Len) ->
+ part(Subject,{Pos,Len}).
+
+do_part(Bin,{A,B}) when B >= 0 ->
+ <<_:A/binary,Sub:B/binary,_/binary>> = Bin,
+ Sub;
+do_part(Bin,{A,B}) when B < 0 ->
+ S = A + B,
+ L = -B,
+ <<_:S/binary,Sub:L/binary,_/binary>> = Bin,
+ Sub.
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% copy
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+copy(Subject) ->
+ copy(Subject,1).
+copy(Subject,N) ->
+ try
+ true = is_integer(N) and (N >= 0) and is_binary(Subject), % Badarg, not function clause
+ erlang:list_to_binary(lists:duplicate(N,Subject))
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% encode_unsigned
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+encode_unsigned(Unsigned) ->
+ encode_unsigned(Unsigned,big).
+encode_unsigned(Unsigned,Endian) ->
+ try
+ true = is_integer(Unsigned) and (Unsigned >= 0),
+ if
+ Unsigned =:= 0 ->
+ <<0>>;
+ true ->
+ case Endian of
+ big ->
+ list_to_binary(do_encode(Unsigned,[]));
+ little ->
+ list_to_binary(do_encode_r(Unsigned))
+ end
+ end
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+do_encode(0,L) ->
+ L;
+do_encode(N,L) ->
+ Byte = N band 255,
+ NewN = N bsr 8,
+ do_encode(NewN,[Byte|L]).
+
+do_encode_r(0) ->
+ [];
+do_encode_r(N) ->
+ Byte = N band 255,
+ NewN = N bsr 8,
+ [Byte|do_encode_r(NewN)].
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% decode_unsigned
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+decode_unsigned(Subject) ->
+ decode_unsigned(Subject,big).
+
+decode_unsigned(Subject,Endian) ->
+ try
+ true = is_binary(Subject),
+ case Endian of
+ big ->
+ do_decode(Subject,0);
+ little ->
+ do_decode_r(Subject,0)
+ end
+ catch
+ _:_ ->
+ erlang:error(badarg)
+ end.
+
+do_decode(<<>>,N) ->
+ N;
+do_decode(<<X:8,Bin/binary>>,N) ->
+ do_decode(Bin,(N bsl 8) bor X).
+
+do_decode_r(<<>>,N) ->
+ N;
+do_decode_r(Bin,N) ->
+ Sz = byte_size(Bin) - 1,
+ <<NewBin:Sz/binary,X>> = Bin,
+ do_decode_r(NewBin, (N bsl 8) bor X).
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% referenced_byte_size cannot
+%% be implemented in pure
+%% erlang
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+referenced_byte_size(Bin) when is_binary(Bin) ->
+ erlang:error(not_implemented);
+referenced_byte_size(_) ->
+ erlang:error(badarg).
+
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% Simple helper functions
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+%% Option "parsing"
+get_opts_match([],Part) ->
+ Part;
+get_opts_match([{scope,{A,B}} | T],_Part) ->
+ get_opts_match(T,{A,B});
+get_opts_match(_,_) ->
+ throw(badopt).
+
+get_opts_split([],{Part,Global,Trim}) ->
+ {Part,Global,Trim};
+get_opts_split([{scope,{A,B}} | T],{_Part,Global,Trim}) ->
+ get_opts_split(T,{{A,B},Global,Trim});
+get_opts_split([global | T],{Part,_Global,Trim}) ->
+ get_opts_split(T,{Part,true,Trim});
+get_opts_split([trim | T],{Part,Global,_Trim}) ->
+ get_opts_split(T,{Part,Global,true});
+get_opts_split(_,_) ->
+ throw(badopt).
+
+get_opts_replace([],{Part,Global,Insert}) ->
+ {Part,Global,Insert};
+get_opts_replace([{scope,{A,B}} | T],{_Part,Global,Insert}) ->
+ get_opts_replace(T,{{A,B},Global,Insert});
+get_opts_replace([global | T],{Part,_Global,Insert}) ->
+ get_opts_replace(T,{Part,true,Insert});
+get_opts_replace([{insert_replaced,N} | T],{Part,Global,_Insert}) ->
+ get_opts_replace(T,{Part,Global,N});
+get_opts_replace(_,_) ->
+ throw(badopt).
diff --git a/lib/stdlib/test/c_SUITE.erl b/lib/stdlib/test/c_SUITE.erl
index 2edbc7ab4c..e4c794ca84 100644
--- a/lib/stdlib/test/c_SUITE.erl
+++ b/lib/stdlib/test/c_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1998-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
@@ -17,18 +17,36 @@
%% %CopyrightEnd%
%%
-module(c_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
-export([c_1/1, c_2/1, c_3/1, c_4/1, nc_1/1, nc_2/1, nc_3/1, nc_4/1,
memory/1]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-import(c, [c/2, nc/2]).
-all(doc) -> ["Test cases for the 'c' module."];
-all(suite) ->
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
[c_1, c_2, c_3, c_4, nc_1, nc_2, nc_3, nc_4, memory].
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
%%% Write output to a directory other than current directory:
c_1(doc) ->
diff --git a/lib/stdlib/test/calendar_SUITE.erl b/lib/stdlib/test/calendar_SUITE.erl
index 10fb72c1b1..8192d035ca 100644
--- a/lib/stdlib/test/calendar_SUITE.erl
+++ b/lib/stdlib/test/calendar_SUITE.erl
@@ -18,29 +18,43 @@
%%
-module(calendar_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
--export([all/1,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
gregorian_days/1,
gregorian_seconds/1,
day_of_the_week/1,
day_of_the_week_calibrate/1,
leap_years/1,
last_day_of_the_month/1,
- local_time_to_universal_time_dst/1]).
+ local_time_to_universal_time_dst/1,
+ iso_week_number/1]).
-define(START_YEAR, 1947).
-define(END_YEAR, 2012).
-all(suite) -> [gregorian_days,
- gregorian_seconds,
- day_of_the_week,
- day_of_the_week_calibrate,
- leap_years,
- last_day_of_the_month,
- local_time_to_universal_time_dst];
+suite() -> [{ct_hooks,[ts_install_cth]}].
-all(doc) -> "This is the test suite for calendar.erl".
+all() ->
+ [gregorian_days, gregorian_seconds, day_of_the_week,
+ day_of_the_week_calibrate, leap_years,
+ last_day_of_the_month, local_time_to_universal_time_dst, iso_week_number].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
gregorian_days(doc) ->
"Tests that date_to_gregorian_days and gregorian_days_to_date "
@@ -156,6 +170,15 @@ local_time_to_universal_time_dst_x(Config) when is_list(Config) ->
{comment,"Bug in mktime() in this OS"}
end.
+iso_week_number(doc) ->
+ "Test the iso week number calculation for all three possibilities."
+ " When the date falls on the last week of the previous year,"
+ " when the date falls on a week within the given year and finally,"
+ " when the date falls on the first week of the next year.";
+iso_week_number(suite) ->
+ [];
+iso_week_number(Config) when is_list(Config) ->
+ ?line check_iso_week_number().
%%
%% LOCAL FUNCTIONS
@@ -245,7 +268,12 @@ check_last_day_of_the_month({SYr, SMon}, {EYr, EMon}) when SYr < EYr ->
check_last_day_of_the_month(_, _) ->
ok.
-
+%% check_iso_week_number
+%%
+check_iso_week_number() ->
+ ?line {2004, 53} = calendar:iso_week_number({2005, 1, 1}),
+ ?line {2007, 1} = calendar:iso_week_number({2007, 1, 1}),
+ ?line {2009, 1} = calendar:iso_week_number({2008, 12, 29}).
diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl
index 760e610e00..a37822ea9d 100644
--- a/lib/stdlib/test/dets_SUITE.erl
+++ b/lib/stdlib/test/dets_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1996-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
@@ -28,13 +28,15 @@
-define(privdir(_), "./dets_SUITE_priv").
-define(datadir(_), "./dets_SUITE_data").
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(format(S, A), ok).
-define(privdir(Conf), ?config(priv_dir, Conf)).
-define(datadir(Conf), ?config(data_dir, Conf)).
-endif.
--export([all/1, not_run/1, newly_started/1, basic_v8/1, basic_v9/1,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
+ not_run/1, newly_started/1, basic_v8/1, basic_v9/1,
open_v8/1, open_v9/1, sets_v8/1, sets_v9/1, bags_v8/1,
bags_v9/1, duplicate_bags_v8/1, duplicate_bags_v9/1,
access_v8/1, access_v9/1, dirty_mark/1, dirty_mark2/1,
@@ -50,13 +52,14 @@
otp_4208/1, otp_4989/1, many_clients/1, otp_4906/1, otp_5402/1,
simultaneous_open/1, insert_new/1, repair_continuation/1,
otp_5487/1, otp_6206/1, otp_6359/1, otp_4738/1, otp_7146/1,
- otp_8070/1]).
+ otp_8070/1, otp_8856/1, otp_8898/1, otp_8899/1, otp_8903/1,
+ otp_8923/1]).
-export([dets_dirty_loop/0]).
-export([histogram/1, sum_histogram/1, ave_histogram/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
%% Internal export.
-export([client/2]).
@@ -82,35 +85,51 @@ init_per_testcase(_Case, Config) ->
Dog=?t:timetrap(?t:minutes(15)),
[{watchdog, Dog}|Config].
-fin_per_testcase(_Case, _Config) ->
+end_per_testcase(_Case, _Config) ->
Dog=?config(watchdog, _Config),
test_server:timetrap_cancel(Dog),
ok.
-all(suite) ->
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
case os:type() of
- vxworks ->
- [not_run];
+ vxworks -> [not_run];
_ ->
- {req,[stdlib],
- [basic_v8, basic_v9, open_v8, open_v9, sets_v8, sets_v9,
- bags_v8, bags_v9, duplicate_bags_v8, duplicate_bags_v9,
- newly_started, open_file_v8, open_file_v9,
- init_table_v8, init_table_v9, repair_v8, repair_v9,
- access_v8, access_v9, oldbugs_v8, oldbugs_v9,
- unsafe_assumptions, truncated_segment_array_v8,
- truncated_segment_array_v9, dirty_mark, dirty_mark2,
- bag_next_v8, bag_next_v9, hash_v8b_v8c, phash, fold_v8,
- fold_v9, fixtable_v8, fixtable_v9, match_v8, match_v9,
- select_v8, select_v9, update_counter, badarg,
- cache_sets_v8, cache_sets_v9, cache_bags_v8,
- cache_bags_v9, cache_duplicate_bags_v8,
- cache_duplicate_bags_v9, otp_4208, otp_4989, many_clients,
- otp_4906, otp_5402, simultaneous_open, insert_new,
- repair_continuation, otp_5487, otp_6206, otp_6359, otp_4738,
- otp_7146, otp_8070]}
+ [basic_v8, basic_v9, open_v8, open_v9, sets_v8, sets_v9,
+ bags_v8, bags_v9, duplicate_bags_v8, duplicate_bags_v9,
+ newly_started, open_file_v8, open_file_v9,
+ init_table_v8, init_table_v9, repair_v8, repair_v9,
+ access_v8, access_v9, oldbugs_v8, oldbugs_v9,
+ unsafe_assumptions, truncated_segment_array_v8,
+ truncated_segment_array_v9, dirty_mark, dirty_mark2,
+ bag_next_v8, bag_next_v9, hash_v8b_v8c, phash, fold_v8,
+ fold_v9, fixtable_v8, fixtable_v9, match_v8, match_v9,
+ select_v8, select_v9, update_counter, badarg,
+ cache_sets_v8, cache_sets_v9, cache_bags_v8,
+ cache_bags_v9, cache_duplicate_bags_v8,
+ cache_duplicate_bags_v9, otp_4208, otp_4989,
+ many_clients, otp_4906, otp_5402, simultaneous_open,
+ insert_new, repair_continuation, otp_5487, otp_6206,
+ otp_6359, otp_4738, otp_7146, otp_8070, otp_8856, otp_8898,
+ otp_8899, otp_8903, otp_8923]
end.
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
not_run(suite) -> [];
not_run(Conf) when is_list(Conf) ->
{comment, "Not runnable VxWorks/NFS"}.
@@ -2935,6 +2954,57 @@ ets_init(Tab, N) ->
ets:insert(Tab, {N,N}),
ets_init(Tab, N - 1).
+otp_8898(doc) ->
+ ["OTP-8898. Truncated Dets file."];
+otp_8898(suite) ->
+ [];
+otp_8898(Config) when is_list(Config) ->
+ Tab = otp_8898,
+ ?line FName = filename(Tab, Config),
+
+ Server = self(),
+
+ ?line file:delete(FName),
+ ?line {ok, _} = dets:open_file(Tab,[{file, FName}]),
+ ?line [P1,P2,P3] = new_clients(3, Tab),
+
+ Seq = [{P1,[sync]},{P2,[{lookup,1,[]}]},{P3,[{insert,{1,b}}]}],
+ ?line atomic_requests(Server, Tab, [[]], Seq),
+ ?line true = get_replies([{P1,ok},{P2,ok},{P3,ok}]),
+ ?line ok = dets:close(Tab),
+ ?line {ok, _} = dets:open_file(Tab,[{file, FName}]),
+ ?line file:delete(FName),
+
+ ok.
+
+otp_8899(doc) ->
+ ["OTP-8899. Several clients. Updated Head was ignored."];
+otp_8899(suite) ->
+ [];
+otp_8899(Config) when is_list(Config) ->
+ Tab = many_clients,
+ ?line FName = filename(Tab, Config),
+
+ Server = self(),
+
+ ?line file:delete(FName),
+ ?line {ok, _} = dets:open_file(Tab,[{file, FName},{version,9}]),
+ ?line [P1,P2,P3,P4] = new_clients(4, Tab),
+
+ MC = [Tab],
+ Seq6a = [{P1,[{insert,[{used_to_be_skipped_by,match}]},
+ {lookup,1,[{1,a}]}]},
+ {P2,[{verbose,true,MC}]},
+ {P3,[{lookup,1,[{1,a}]}]}, {P4,[{verbose,true,MC}]}],
+ ?line atomic_requests(Server, Tab, [[{1,a},{2,b},{3,c}]], Seq6a),
+ ?line true = get_replies([{P1,ok}, {P2,ok}, {P3,ok}, {P4,ok}]),
+ ?line [{1,a},{2,b},{3,c},{used_to_be_skipped_by,match}] =
+ lists:sort(dets:match_object(Tab, '_')),
+ ?line _ = dets:close(Tab),
+ ?line file:delete(FName),
+
+ ok.
+
many_clients(doc) ->
["Several clients accessing a table simultaneously."];
many_clients(suite) ->
@@ -3071,6 +3141,11 @@ client(S, Tab) ->
eval([], _Tab) ->
ok;
+eval([{verbose,Bool,Expected} | L], Tab) ->
+ ?line case dets:verbose(Bool) of
+ Expected -> eval(L, Tab);
+ Error -> {error, {verbose,Error}}
+ end;
eval([sync | L], Tab) ->
?line case dets:sync(Tab) of
ok -> eval(L, Tab);
@@ -3701,6 +3776,87 @@ otp_8070(Config) when is_list(Config) ->
file:delete(File),
ok.
+otp_8856(doc) ->
+ ["OTP-8856. insert_new() bug."];
+otp_8856(suite) ->
+ [];
+otp_8856(Config) when is_list(Config) ->
+ Tab = otp_8856,
+ File = filename(Tab, Config),
+ file:delete(File),
+ Me = self(),
+ ?line {ok, _} = dets:open_file(Tab, [{type, bag}, {file, File}]),
+ spawn(fun()-> Me ! {1, dets:insert(Tab, [])} end),
+ spawn(fun()-> Me ! {2, dets:insert_new(Tab, [])} end),
+ ?line ok = dets:close(Tab),
+ ?line receive {1, ok} -> ok end,
+ ?line receive {2, true} -> ok end,
+ file:delete(File),
+
+ ?line {ok, _} = dets:open_file(Tab, [{type, set}, {file, File}]),
+ spawn(fun() -> dets:delete(Tab, 0) end),
+ spawn(fun() -> Me ! {3, dets:insert_new(Tab, {0,0})} end),
+ ?line ok = dets:close(Tab),
+ ?line receive {3, true} -> ok end,
+ file:delete(File),
+ ok.
+
+otp_8903(doc) ->
+ ["OTP-8903. bchunk/match/select bug."];
+otp_8903(suite) ->
+ [];
+otp_8903(Config) when is_list(Config) ->
+ Tab = otp_8903,
+ File = filename(Tab, Config),
+ ?line {ok,T} = dets:open_file(bug, [{file,File}]),
+ ?line ok = dets:insert(T, [{1,a},{2,b},{3,c}]),
+ ?line dets:safe_fixtable(T, true),
+ ?line {[_],C1} = dets:match_object(T, '_', 1),
+ ?line {BC1,_D} = dets:bchunk(T, start),
+ ?line ok = dets:close(T),
+ ?line {'EXIT', {badarg, _}} = (catch {foo,dets:match_object(C1)}),
+ ?line {'EXIT', {badarg, _}} = (catch {foo,dets:bchunk(T, BC1)}),
+ ?line {ok,T} = dets:open_file(bug, [{file,File}]),
+ ?line false = dets:info(T, safe_fixed),
+ ?line {'EXIT', {badarg, _}} = (catch {foo,dets:match_object(C1)}),
+ ?line {'EXIT', {badarg, _}} = (catch {foo,dets:bchunk(T, BC1)}),
+ ?line ok = dets:close(T),
+ file:delete(File),
+ ok.
+
+otp_8923(doc) ->
+ ["OTP-8923. rehash due to lookup after initialization."];
+otp_8923(suite) ->
+ [];
+otp_8923(Config) when is_list(Config) ->
+ Tab = otp_8923,
+ File = filename(Tab, Config),
+ %% Create a file with more than 256 keys:
+ file:delete(File),
+ Bin = list_to_binary([ 0 || _ <- lists:seq(1, 400) ]),
+ BigBin = list_to_binary([ 0 ||_ <- lists:seq(1, 4000)]),
+ Ets = ets:new(temp, [{keypos,1}]),
+ ?line [ true = ets:insert(Ets, {C,Bin}) || C <- lists:seq(1, 700) ],
+ ?line true = ets:insert(Ets, {helper_data,BigBin}),
+ ?line true = ets:insert(Ets, {prim_btree,BigBin}),
+ ?line true = ets:insert(Ets, {sec_btree,BigBin}),
+ %% Note: too few slots; re-hash will take place
+ ?line {ok, Tab} = dets:open_file(Tab, [{file,File}]),
+ ?line Tab = ets:to_dets(Ets, Tab),
+ ?line ok = dets:close(Tab),
+ ?line true = ets:delete(Ets),
+
+ ?line {ok,Ref} = dets:open_file(File),
+ ?line [{1,_}] = dets:lookup(Ref, 1),
+ ?line ok = dets:close(Ref),
+
+ ?line {ok,Ref2} = dets:open_file(File),
+ ?line [{helper_data,_}] = dets:lookup(Ref2, helper_data),
+ ?line ok = dets:close(Ref2),
+
+ file:delete(File),
+ ok.
+
%%
%% Parts common to several test cases
%%
diff --git a/lib/stdlib/test/dict_SUITE.erl b/lib/stdlib/test/dict_SUITE.erl
index 6a90870bda..396a8d4763 100644
--- a/lib/stdlib/test/dict_SUITE.erl
+++ b/lib/stdlib/test/dict_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %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
@@ -22,21 +22,41 @@
-module(dict_SUITE).
--export([all/1,init_per_testcase/2,fin_per_testcase/2,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
+ init_per_testcase/2,end_per_testcase/2,
create/1,store/1]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-import(lists, [foldl/3,reverse/1]).
-all(suite) ->
- [create,store].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [create, store].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?t:minutes(5)),
[{watchdog,Dog}|Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog = ?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
diff --git a/lib/stdlib/test/dict_test_lib.erl b/lib/stdlib/test/dict_test_lib.erl
index fd15baa5ff..92a75dad89 100644
--- a/lib/stdlib/test/dict_test_lib.erl
+++ b/lib/stdlib/test/dict_test_lib.erl
@@ -1,7 +1,7 @@
%%
%% %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
diff --git a/lib/stdlib/test/digraph_SUITE.erl b/lib/stdlib/test/digraph_SUITE.erl
index 6ef5b1ddef..4e7c468097 100644
--- a/lib/stdlib/test/digraph_SUITE.erl
+++ b/lib/stdlib/test/digraph_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1996-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
@@ -23,19 +23,41 @@
-ifdef(STANDALONE).
-define(line, put(line, ?LINE), ).
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-endif.
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
--export([opts/1, degree/1, path/1, cycle/1, misc/1, vertices/1,
- edges/1, data/1, tickets/1, otp_3522/1, otp_3630/1, otp_8066/1]).
+-export([opts/1, degree/1, path/1, cycle/1, vertices/1,
+ edges/1, data/1, otp_3522/1, otp_3630/1, otp_8066/1]).
-export([spawn_graph/2]).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-all(suite) -> {req, [stdlib], [opts, degree, path, cycle, misc, tickets]}.
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [opts, degree, path, cycle, {group, misc},
+ {group, tickets}].
+
+groups() ->
+ [{misc, [], [vertices, edges, data]},
+ {tickets, [], [otp_3522, otp_3630, otp_8066]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -147,7 +169,6 @@ cycle(Config) when is_list(Config) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-misc(suite) -> [vertices, edges, data].
vertices(doc) -> [];
vertices(suite) -> [];
@@ -210,7 +231,6 @@ data(Config) when is_list(Config) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-tickets(suite) -> [otp_3522, otp_3630, otp_8066].
otp_3522(doc) -> [];
otp_3522(suite) -> [];
diff --git a/lib/stdlib/test/digraph_utils_SUITE.erl b/lib/stdlib/test/digraph_utils_SUITE.erl
index d6d477b388..28daf0f0fb 100644
--- a/lib/stdlib/test/digraph_utils_SUITE.erl
+++ b/lib/stdlib/test/digraph_utils_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2000-2009. All Rights Reserved.
+%% Copyright Ericsson AB 2000-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
@@ -22,10 +22,11 @@
-ifdef(debug).
-define(line, put(line, ?LINE), ).
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-endif.
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
-export([simple/1, loop/1, isolated/1, topsort/1, subgraph/1,
condensation/1, tree/1]).
@@ -33,8 +34,27 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-all(suite) -> {req, [stdlib], [simple, loop, isolated, topsort,
- subgraph, condensation, tree]}.
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [simple, loop, isolated, topsort, subgraph,
+ condensation, tree].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
diff --git a/lib/stdlib/test/dummy1_h.erl b/lib/stdlib/test/dummy1_h.erl
index 4377d774a3..5b503d5984 100644
--- a/lib/stdlib/test/dummy1_h.erl
+++ b/lib/stdlib/test/dummy1_h.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 1996-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(dummy1_h).
@@ -21,7 +21,7 @@
%% Test event handler for gen_event_SUITE.erl
-export([init/1, handle_event/2, handle_call/2, handle_info/2,
- terminate/2]).
+ terminate/2, format_status/2]).
init(make_error) ->
{error, my_error};
@@ -67,4 +67,5 @@ terminate(remove_handler, Parent) ->
terminate(_Reason, _State) ->
ok.
-
+format_status(_Opt, [_PDict, _State]) ->
+ "dummy1_h handler state".
diff --git a/lib/stdlib/test/dummy_h.erl b/lib/stdlib/test/dummy_h.erl
index 01eb790a75..7546fe78a0 100644
--- a/lib/stdlib/test/dummy_h.erl
+++ b/lib/stdlib/test/dummy_h.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1996-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
diff --git a/lib/stdlib/test/edlin_expand_SUITE.erl b/lib/stdlib/test/edlin_expand_SUITE.erl
index 613bfd000e..514d22c4d2 100644
--- a/lib/stdlib/test/edlin_expand_SUITE.erl
+++ b/lib/stdlib/test/edlin_expand_SUITE.erl
@@ -17,13 +17,14 @@
%% %CopyrightEnd%
%%
-module(edlin_expand_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
-export([normal/1, quoted_fun/1, quoted_module/1, quoted_both/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
% Default timetrap timeout (set in init_per_testcase).
-define(default_timeout, ?t:minutes(1)).
@@ -31,16 +32,36 @@
init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog = ?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
-all(doc) ->
- ["Test cases for edlin_expand."];
-all(suite) ->
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
[normal, quoted_fun, quoted_module, quoted_both].
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ true = code:delete(expand_test),
+ true = code:delete(expand_test1),
+ true = code:delete('ExpandTestCaps'),
+ true = code:delete('ExpandTestCaps1'),
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
normal(doc) ->
[""];
normal(suite) ->
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index 9a3ae0baf5..195eeb5e89 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -17,13 +17,15 @@
%% %CopyrightEnd%
-module(epp_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
--export([rec_1/1, predef_mac/1,
- upcase_mac/1, upcase_mac_1/1, upcase_mac_2/1,
- variable/1, variable_1/1, otp_4870/1, otp_4871/1, otp_5362/1,
+-export([rec_1/1, predef_mac/1,
+ upcase_mac_1/1, upcase_mac_2/1,
+ variable_1/1, otp_4870/1, otp_4871/1, otp_5362/1,
pmod/1, not_circular/1, skip_header/1, otp_6277/1, otp_7702/1,
- otp_8130/1, overload_mac/1, otp_8388/1]).
+ otp_8130/1, overload_mac/1, otp_8388/1, otp_8470/1, otp_8503/1,
+ otp_8562/1, otp_8665/1, otp_8911/1]).
-export([epp_parse_erl_form/2]).
@@ -38,13 +40,13 @@
-define(config(A,B),config(A,B)).
%% -define(t, test_server).
-define(t, io).
-config(priv_dir, _) ->
+config(priv_dir, _) ->
filename:absname("./epp_SUITE_priv");
config(data_dir, _) ->
filename:absname("./epp_SUITE_data").
-else.
--include("test_server.hrl").
--export([init_per_testcase/2, fin_per_testcase/2]).
+-include_lib("test_server/include/test_server.hrl").
+-export([init_per_testcase/2, end_per_testcase/2]).
% Default timetrap timeout (set in init_per_testcase).
-define(default_timeout, ?t:minutes(1)).
@@ -52,18 +54,36 @@ config(data_dir, _) ->
init_per_testcase(_, Config) ->
?line Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
-fin_per_testcase(_, Config) ->
+end_per_testcase(_, Config) ->
Dog = ?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
-endif.
-all(doc) ->
- ["Test cases for epp."];
-all(suite) ->
- [rec_1, upcase_mac, predef_mac, variable, otp_4870, otp_4871, otp_5362,
- pmod, not_circular, skip_header, otp_6277, otp_7702, otp_8130,
- overload_mac, otp_8388].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [rec_1, {group, upcase_mac}, predef_mac,
+ {group, variable}, otp_4870, otp_4871, otp_5362, pmod,
+ not_circular, skip_header, otp_6277, otp_7702, otp_8130,
+ overload_mac, otp_8388, otp_8470, otp_8503, otp_8562,
+ otp_8665, otp_8911].
+
+groups() ->
+ [{upcase_mac, [], [upcase_mac_1, upcase_mac_2]},
+ {variable, [], [variable_1]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
rec_1(doc) ->
["Recursive macros hang or crash epp (OTP-1398)."];
@@ -126,10 +146,6 @@ check_errors([{error, Info} | Rest]) ->
check_errors([_ | Rest]) ->
check_errors(Rest).
-upcase_mac(doc) ->
- ["Check that uppercase macro names are implicitly quoted (OTP-2608)"];
-upcase_mac(suite) ->
- [upcase_mac_1, upcase_mac_2].
upcase_mac_1(doc) ->
[];
@@ -175,10 +191,6 @@ predef_mac(Config) when is_list(Config) ->
end,
ok.
-variable(doc) ->
- ["Check variable as first file component of the include directives."];
-variable(suite) ->
- [variable_1].
variable_1(doc) ->
[];
@@ -191,7 +203,7 @@ variable_1(Config) when is_list(Config) ->
%% variable_1.erl includes variable_1_include.hrl and
%% variable_1_include_dir.hrl.
?line {ok, List} = epp:parse_file(File, [], []),
- ?line {value, {attribute,_,a,{value1,value2}}} =
+ ?line {value, {attribute,_,a,{value1,value2}}} =
lists:keysearch(a,3,List),
ok.
@@ -218,13 +230,13 @@ otp_4871(Config) when is_list(Config) ->
%% Testing crash in erl_scan. Unfortunately there currently is
%% no known way to crash erl_scan so it is emulated by killing the
%% file io server. This assumes lots of things about how
- %% the processes are started and how monitors are set up,
+ %% the processes are started and how monitors are set up,
%% so there are some sanity checks before killing.
?line {ok,Epp} = epp:open(File, []),
timer:sleep(1),
?line {current_function,{epp,_,_}} = process_info(Epp, current_function),
?line {monitored_by,[Io]} = process_info(Epp, monitored_by),
- ?line {current_function,{file_io_server,_,_}} =
+ ?line {current_function,{file_io_server,_,_}} =
process_info(Io, current_function),
?line exit(Io, emulate_crash),
timer:sleep(1),
@@ -301,7 +313,7 @@ otp_5362(Config) when is_list(Config) ->
Back_hrl = [<<"
-file(\"">>,File_Back,<<"\", 2).
">>],
-
+
?line ok = file:write_file(File_Back, Back),
?line ok = file:write_file(File_Back_hrl, list_to_binary(Back_hrl)),
@@ -332,7 +344,7 @@ otp_5362(Config) when is_list(Config) ->
?line ok = file:write_file(File_Change, list_to_binary(Change)),
- ?line {ok, change_5362, ChangeWarnings} =
+ ?line {ok, change_5362, ChangeWarnings} =
compile:file(File_Change, Copts),
?line true = message_compare(
[{File_Change,[{{1002,21},erl_lint,{unused_var,'B'}}]},
@@ -440,9 +452,9 @@ skip_header(Config) when is_list(Config) ->
that should be skipped
-module(epp_test_skip_header).
-export([main/1]).
-
+
main(_) -> ?MODULE.
-
+
">>),
?line {ok, Fd} = file:open(File, [read]),
?line io:get_line(Fd, ''),
@@ -493,9 +505,9 @@ otp_7702(Config) when is_list(Config) ->
t() ->
?RECEIVE(foo, bar).">>,
?line ok = file:write_file(File, Contents),
- ?line {ok, file_7702, []} =
+ ?line {ok, file_7702, []} =
compile:file(File, [debug_info,return,{outdir,Dir}]),
-
+
BeamFile = filename:join(Dir, "file_7702.beam"),
{ok, AC} = beam_lib:chunks(BeamFile, [abstract_code]),
@@ -505,7 +517,7 @@ otp_7702(Config) when is_list(Config) ->
L
end,
Forms2 = [erl_lint:modify_line(Form, Fun) || Form <- Forms],
- ?line
+ ?line
[{attribute,1,file,_},
_,
_,
@@ -616,9 +628,9 @@ otp_8130(Config) when is_list(Config) ->
"t() -> 14 = (#file_info{size = 14})#file_info.size, ok.\n">>,
ok},
- {otp_8130_7,
+ {otp_8130_7_new,
<<"-record(b, {b}).\n"
- "-define(A, {{a,#b.b.\n"
+ "-define(A, {{a,#b.b).\n"
"t() -> {{a,2}} = ?A}}, ok.">>,
ok},
@@ -636,7 +648,7 @@ otp_8130(Config) when is_list(Config) ->
],
?line [] = run(Config, Ts),
-
+
Cs = [{otp_8130_c1,
<<"-define(M1(A), if\n"
"A =:= 1 -> B;\n"
@@ -680,7 +692,7 @@ otp_8130(Config) when is_list(Config) ->
<<"\n-include_lib(\"$apa/foo.hrl\").\n">>,
{errors,[{{2,2},epp,{include,lib,"$apa/foo.hrl"}}],[]}},
-
+
{otp_8130_c9,
<<"-define(S, ?S).\n"
"t() -> ?S.\n">>,
@@ -750,7 +762,14 @@ otp_8130(Config) when is_list(Config) ->
{otp_8130_c24,
<<"\n-include(\"no such file.erl\").\n">>,
- {errors,[{{2,2},epp,{include,file,"no such file.erl"}}],[]}}
+ {errors,[{{2,2},epp,{include,file,"no such file.erl"}}],[]}},
+
+ {otp_8130_7,
+ <<"-record(b, {b}).\n"
+ "-define(A, {{a,#b.b.\n"
+ "t() -> {{a,2}} = ?A}}, ok.">>,
+ {errors,[{{2,20},epp,missing_parenthesis},
+ {{3,19},epp,{undefined,'A',none}}],[]}}
],
?line [] = compile(Config, Cs),
@@ -767,7 +786,7 @@ otp_8130(Config) when is_list(Config) ->
?line Dir = ?config(priv_dir, Config),
?line File = filename:join(Dir, "otp_8130.erl"),
- ?line ok = file:write_file(File,
+ ?line ok = file:write_file(File,
"-module(otp_8130).\n"
"-define(a, 3.14).\n"
"t() -> ?a.\n"),
@@ -780,7 +799,7 @@ otp_8130(Config) when is_list(Config) ->
?line {eof,_} = epp:scan_erl_form(Epp),
?line ['BASE_MODULE','BASE_MODULE_STRING','BEAM','FILE','LINE',
'MACHINE','MODULE','MODULE_STRING',a] = macs(Epp),
- ?line epp:close(Epp),
+ ?line epp:close(Epp),
%% escript
ModuleStr = "any_name",
@@ -807,7 +826,7 @@ otp_8130(Config) when is_list(Config) ->
PreDefMacros = [{a,1},a],
?line {error,{redefine,a}} = epp:open(File, [], PreDefMacros)
end(),
-
+
?line {error,enoent} = epp:open("no such file", []),
?line {error,enoent} = epp:parse_file("no such file", [], []),
@@ -933,7 +952,7 @@ ifdef(Config) ->
<<"\n-if.\n"
"-endif.\n">>,
{errors,[{{2,2},epp,{'NYI','if'}}],[]}},
-
+
{define_c7,
<<"-ifndef(a).\n"
"-elif.\n"
@@ -1047,13 +1066,13 @@ overload_mac(Config) when is_list(Config) ->
"-undef(A).\n"
"t1() -> ?A.\n",
"t2() -> ?A(1).">>,
- {errors,[{{4,9},epp,{undefined,'A', none}},
- {{5,9},epp,{undefined,'A', 1}}],[]}},
+ {errors,[{{4,10},epp,{undefined,'A', none}},
+ {{5,10},epp,{undefined,'A', 1}}],[]}},
%% cannot overload predefined macros
{overload_mac_c2,
<<"-define(MODULE(X), X).">>,
- {errors,[{{1,9},epp,{redefine_predef,'MODULE'}}],[]}},
+ {errors,[{{1,50},epp,{redefine_predef,'MODULE'}}],[]}},
%% cannot overload macros with same arity
{overload_mac_c3,
@@ -1120,25 +1139,121 @@ otp_8388(Config) when is_list(Config) ->
{macro_1,
<<"-define(m(A), A).\n"
"t() -> ?m(,).\n">>,
- {errors,[{{2,11},epp,{arg_error,m}}],[]}},
+ {errors,[{{2,9},epp,{arg_error,m}}],[]}},
{macro_2,
<<"-define(m(A), A).\n"
"t() -> ?m(a,).\n">>,
- {errors,[{{2,12},epp,{arg_error,m}}],[]}},
+ {errors,[{{2,9},epp,{arg_error,m}}],[]}},
{macro_3,
<<"-define(LINE, a).\n">>,
- {errors,[{{1,9},epp,{redefine_predef,'LINE'}}],[]}},
+ {errors,[{{1,50},epp,{redefine_predef,'LINE'}}],[]}},
{macro_4,
<<"-define(A(B, C, D), {B,C,D}).\n"
"t() -> ?A(a,,3).\n">>,
- {errors,[{{2,8},epp,{mismatch,'A'}}],[]}},
+ {errors,[{{2,9},epp,{mismatch,'A'}}],[]}},
{macro_5,
<<"-define(Q, {?F0(), ?F1(,,4)}).\n">>,
- {errors,[{{1,24},epp,{arg_error,'F1'}}],[]}}
+ {errors,[{{1,62},epp,{arg_error,'F1'}}],[]}},
+ {macro_6,
+ <<"-define(FOO(X), ?BAR(X)).\n"
+ "-define(BAR(X), ?FOO(X)).\n"
+ "-undef(FOO).\n"
+ "test() -> ?BAR(1).\n">>,
+ {errors,[{{4,12},epp,{undefined,'FOO',1}}],[]}}
],
?line [] = compile(Config, Ts),
ok.
+otp_8470(doc) ->
+ ["OTP-8470. Bugfix (one request - two replies)."];
+otp_8470(suite) ->
+ [];
+otp_8470(Config) when is_list(Config) ->
+ Dir = ?config(priv_dir, Config),
+ C = <<"-file(\"erl_parse.yrl\", 486).\n"
+ "-file(\"erl_parse.yrl\", 488).\n">>,
+ ?line File = filename:join(Dir, "otp_8470.erl"),
+ ?line ok = file:write_file(File, C),
+ ?line {ok, _List} = epp:parse_file(File, [], []),
+ file:delete(File),
+ ?line receive _ -> fail() after 0 -> ok end,
+ ok.
+
+otp_8503(doc) ->
+ ["OTP-8503. Record with no fields is considered typed."];
+otp_8503(suite) ->
+ [];
+otp_8503(Config) when is_list(Config) ->
+ Dir = ?config(priv_dir, Config),
+ C = <<"-record(r, {}).">>,
+ ?line File = filename:join(Dir, "otp_8503.erl"),
+ ?line ok = file:write_file(File, C),
+ ?line {ok, List} = epp:parse_file(File, [], []),
+ ?line [_] = [F || {attribute,_,type,{{record,r},[],[]}}=F <- List],
+ file:delete(File),
+ ?line receive _ -> fail() after 0 -> ok end,
+ ok.
+
+otp_8562(doc) ->
+ ["OTP-8503. Record with no fields is considered typed."];
+otp_8562(suite) ->
+ [];
+otp_8562(Config) when is_list(Config) ->
+ Cs = [{otp_8562,
+ <<"-define(P(), {a,b}.\n"
+ "-define(P3, .\n">>,
+ {errors,[{{1,60},epp,missing_parenthesis},
+ {{2,13},epp,missing_parenthesis}], []}}
+ ],
+ ?line [] = compile(Config, Cs),
+ ok.
+
+otp_8911(doc) ->
+ ["OTP-8911. -file and file inclusion bug"];
+otp_8911(suite) ->
+ [];
+otp_8911(Config) when is_list(Config) ->
+ ?line {ok, CWD} = file:get_cwd(),
+ ?line ok = file:set_cwd(?config(priv_dir, Config)),
+
+ File = "i.erl",
+ Cont = <<"-module(i).
+ -compile(export_all).
+ -file(\"fil1\", 100).
+ -include(\"i1.erl\").
+ t() ->
+ a.
+ ">>,
+ ?line ok = file:write_file(File, Cont),
+ Incl = <<"-file(\"fil2\", 35).
+ t1() ->
+ b.
+ ">>,
+ File1 = "i1.erl",
+ ?line ok = file:write_file(File1, Incl),
+
+ ?line {ok, i} = cover:compile(File),
+ ?line a = i:t(),
+ ?line {ok,[{{i,6},1}]} = cover:analyse(i, calls, line),
+ ?line cover:stop(),
+
+ file:delete(File),
+ file:delete(File1),
+ ?line file:set_cwd(CWD),
+ ok.
+
+otp_8665(doc) ->
+ ["OTP-8665. Bugfix premature end."];
+otp_8665(suite) ->
+ [];
+otp_8665(Config) when is_list(Config) ->
+ Cs = [{otp_8562,
+ <<"-define(A, a)\n">>,
+ {errors,[{{1,54},epp,premature_end}],[]}}
+ ],
+ ?line [] = compile(Config, Cs),
+ ok.
+
check(Config, Tests) ->
eval_tests(Config, fun check_test/2, Tests).
@@ -1155,7 +1270,7 @@ eval_tests(Config, Fun, Tests) ->
case message_compare(E, Return) of
true ->
BadL;
- false ->
+ false ->
?t:format("~nTest ~p failed. Expected~n ~p~n"
"but got~n ~p~n", [N, E, Return]),
fail()
@@ -1170,9 +1285,9 @@ check_test(Config, Test) ->
?line File = filename:join(PrivDir, Filename),
?line ok = file:write_file(File, Test),
?line case epp:parse_file(File, [PrivDir], []) of
- {ok,Forms} ->
+ {ok,Forms} ->
[E || E={error,_} <- Forms];
- {error,Error} ->
+ {error,Error} ->
Error
end.
@@ -1187,7 +1302,7 @@ compile_test(Config, Test0) ->
{ok, Ws} -> warnings(File, Ws);
Else -> Else
end.
-
+
warnings(File, Ws) ->
case lists:append([W || {F, W} <- Ws, F =:= File]) of
[] -> [];
@@ -1231,7 +1346,7 @@ message_compare(T, T) ->
message_compare(T1, T2) ->
ln(T1) =:= T2.
-%% Replaces locations like {Line,Column} with Line.
+%% Replaces locations like {Line,Column} with Line.
ln({warnings,L}) ->
{warnings,ln0(L)};
ln({errors,EL,WL}) ->
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index c60a558fa1..6277b2c52e 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1998-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
@@ -17,7 +17,8 @@
%% %CopyrightEnd%
-module(erl_eval_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
-export([guard_1/1, guard_2/1,
match_pattern/1,
@@ -38,7 +39,8 @@
otp_8133/1,
funs/1,
try_catch/1,
- eval_expr_5/1]).
+ eval_expr_5/1,
+ zero_width/1]).
%%
%% Define to run outside of test server
@@ -57,26 +59,42 @@
config(priv_dir,_) ->
".".
-else.
--include("test_server.hrl").
--export([init_per_testcase/2, fin_per_testcase/2]).
+-include_lib("test_server/include/test_server.hrl").
+-export([init_per_testcase/2, end_per_testcase/2]).
% 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) ->
+end_per_testcase(_Case, Config) ->
Dog = ?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
-endif.
-all(doc) ->
- ["Test cases for the 'erl_eval' module."];
-all(suite) ->
- [guard_1, guard_2, match_pattern, string_plusplus, pattern_expr,
- match_bin, guard_3, guard_4,
- lc, simple_cases, unary_plus, apply_atom, otp_5269, otp_6539, otp_6543,
- otp_6787, otp_6977, otp_7550, otp_8133, funs, try_catch, eval_expr_5].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [guard_1, guard_2, match_pattern, string_plusplus,
+ pattern_expr, match_bin, guard_3, guard_4, lc,
+ simple_cases, unary_plus, apply_atom, otp_5269,
+ otp_6539, otp_6543, otp_6787, otp_6977, otp_7550,
+ otp_8133, funs, try_catch, eval_expr_5, zero_width].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
guard_1(doc) ->
["(OTP-2405)"];
@@ -1326,6 +1344,14 @@ eval_expr_5(Config) when is_list(Config) ->
ok
end.
+zero_width(Config) when is_list(Config) ->
+ ?line check(fun() ->
+ {'EXIT',{badarg,_}} = (catch <<not_a_number:0>>),
+ ok
+ end, "begin {'EXIT',{badarg,_}} = (catch <<not_a_number:0>>), "
+ "ok end.", ok),
+ ok.
+
%% Check the string in different contexts: as is; in fun; from compiled code.
check(F, String, Result) ->
check1(F, String, Result),
diff --git a/lib/stdlib/test/erl_eval_helper.erl b/lib/stdlib/test/erl_eval_helper.erl
index 7fdbabcb17..6863b40108 100644
--- a/lib/stdlib/test/erl_eval_helper.erl
+++ b/lib/stdlib/test/erl_eval_helper.erl
@@ -1,7 +1,7 @@
%%
%% %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
diff --git a/lib/stdlib/test/erl_expand_records_SUITE.erl b/lib/stdlib/test/erl_expand_records_SUITE.erl
index 1d621c65df..44c986640f 100644
--- a/lib/stdlib/test/erl_expand_records_SUITE.erl
+++ b/lib/stdlib/test/erl_expand_records_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %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
@@ -27,15 +27,17 @@
-define(privdir, "erl_expand_records_SUITE_priv").
-define(t, test_server).
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(privdir, ?config(priv_dir, Config)).
-endif.
--export([all/1, init_per_testcase/2, fin_per_testcase/2]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
+ init_per_testcase/2, end_per_testcase/2]).
-export([abstract_module/1, attributes/1, expr/1, guard/1,
init/1, pattern/1, strict/1, update/1,
- tickets/1, otp_5915/1, otp_7931/1, otp_5990/1,
+ otp_5915/1, otp_7931/1, otp_5990/1,
otp_7078/1, otp_7101/1]).
% Default timetrap timeout (set in init_per_testcase).
@@ -45,14 +47,33 @@ init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
-fin_per_testcase(_Case, _Config) ->
+end_per_testcase(_Case, _Config) ->
Dog = ?config(watchdog, _Config),
test_server:timetrap_cancel(Dog),
ok.
-all(suite) ->
- [abstract_module, attributes, expr, guard, init, pattern,
- strict, update, tickets].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [abstract_module, attributes, expr, guard, init,
+ pattern, strict, update, {group, tickets}].
+
+groups() ->
+ [{tickets, [],
+ [otp_5915, otp_7931, otp_5990, otp_7078, otp_7101]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
abstract_module(doc) ->
"Compile an abstract module.";
@@ -399,8 +420,6 @@ update(Config) when is_list(Config) ->
?line run(Config, Ts),
ok.
-tickets(suite) ->
- [otp_5915, otp_7931, otp_5990, otp_7078, otp_7101].
otp_5915(doc) ->
"Strict record tests in guards.";
diff --git a/lib/stdlib/test/erl_internal_SUITE.erl b/lib/stdlib/test/erl_internal_SUITE.erl
index 8f675c94ec..678e22c252 100644
--- a/lib/stdlib/test/erl_internal_SUITE.erl
+++ b/lib/stdlib/test/erl_internal_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1999-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
@@ -18,15 +18,35 @@
%%
-module(erl_internal_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
-export([behav/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
+
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [behav].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
-all(suite) -> [behav].
-define(default_timeout, ?t:minutes(2)).
@@ -34,7 +54,7 @@ init_per_testcase(_Case, Config) ->
?line Dog = test_server:timetrap(?default_timeout),
[{watchdog, Dog}|Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog=?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 8581b496aa..f980d52e4e 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-2010. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2011. 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
@@ -27,34 +27,37 @@
-define(privdir, "erl_lint_SUITE_priv").
-define(t, test_server).
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(datadir, ?config(data_dir, Conf)).
-define(privdir, ?config(priv_dir, Conf)).
-endif.
--export([all/1, init_per_testcase/2, fin_per_testcase/2]).
-
--export([unused_vars_warn/1,
- unused_vars_warn_basic/1,
- unused_vars_warn_lc/1,
- unused_vars_warn_rec/1,
- unused_vars_warn_fun/1,
- unused_vars_OTP_4858/1,
- export_vars_warn/1,
- shadow_vars/1,
- unused_import/1,
- unused_function/1,
- unsafe_vars/1,unsafe_vars2/1,
- unsafe_vars_try/1,
- guard/1, otp_4886/1, otp_4988/1, otp_5091/1, otp_5276/1, otp_5338/1,
- otp_5362/1, otp_5371/1, otp_7227/1, otp_5494/1, otp_5644/1, otp_5878/1,
- otp_5917/1, otp_6585/1, otp_6885/1, export_all/1,
- bif_clash/1,
- behaviour_basic/1, behaviour_multiple/1,
- otp_7550/1,
- otp_8051/1,
- format_warn/1,
- on_load/1, on_load_successful/1, on_load_failing/1
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
+ init_per_testcase/2, end_per_testcase/2]).
+
+-export([
+ unused_vars_warn_basic/1,
+ unused_vars_warn_lc/1,
+ unused_vars_warn_rec/1,
+ unused_vars_warn_fun/1,
+ unused_vars_OTP_4858/1,
+ export_vars_warn/1,
+ shadow_vars/1,
+ unused_import/1,
+ unused_function/1,
+ unsafe_vars/1,unsafe_vars2/1,
+ unsafe_vars_try/1,
+ guard/1, otp_4886/1, otp_4988/1, otp_5091/1, otp_5276/1, otp_5338/1,
+ otp_5362/1, otp_5371/1, otp_7227/1, otp_5494/1, otp_5644/1, otp_5878/1,
+ otp_5917/1, otp_6585/1, otp_6885/1, export_all/1,
+ bif_clash/1,
+ behaviour_basic/1, behaviour_multiple/1,
+ otp_7550/1,
+ otp_8051/1,
+ format_warn/1,
+ on_load_successful/1, on_load_failing/1,
+ too_many_arguments/1
]).
% Default timetrap timeout (set in init_per_testcase).
@@ -64,24 +67,44 @@ init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
-fin_per_testcase(_Case, _Config) ->
+end_per_testcase(_Case, _Config) ->
Dog = ?config(watchdog, _Config),
test_server:timetrap_cancel(Dog),
ok.
-all(suite) ->
- [unused_vars_warn, export_vars_warn,
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [{group, unused_vars_warn}, export_vars_warn,
shadow_vars, unused_import, unused_function,
- unsafe_vars, unsafe_vars2, unsafe_vars_try,
- guard, otp_4886, otp_4988, otp_5091, otp_5276, otp_5338,
- otp_5362, otp_5371, otp_7227, otp_5494, otp_5644, otp_5878, otp_5917, otp_6585,
- otp_6885, export_all, bif_clash,
- behaviour_basic, behaviour_multiple, otp_7550, otp_8051, format_warn,
- on_load].
+ unsafe_vars, unsafe_vars2, unsafe_vars_try, guard,
+ otp_4886, otp_4988, otp_5091, otp_5276, otp_5338,
+ otp_5362, otp_5371, otp_7227, otp_5494, otp_5644,
+ otp_5878, otp_5917, otp_6585, otp_6885, export_all,
+ bif_clash, behaviour_basic, behaviour_multiple,
+ otp_7550, otp_8051, format_warn, {group, on_load},
+ too_many_arguments].
+
+groups() ->
+ [{unused_vars_warn, [],
+ [unused_vars_warn_basic, unused_vars_warn_lc,
+ unused_vars_warn_rec, unused_vars_warn_fun,
+ unused_vars_OTP_4858]},
+ {on_load, [], [on_load_successful, on_load_failing]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
-unused_vars_warn(suite) ->
- [unused_vars_warn_basic, unused_vars_warn_lc, unused_vars_warn_rec,
- unused_vars_warn_fun, unused_vars_OTP_4858].
unused_vars_warn_basic(doc) ->
"Warnings for unused variables in some simple cases.";
@@ -1784,6 +1807,9 @@ otp_5362(Config) when is_list(Config) ->
{15,erl_lint,{undefined_field,ok,nix}},
{16,erl_lint,{field_name_is_variable,ok,'Var'}}]}},
+ %% Nowarn_bif_clash has changed behaviour as local functions
+ %% nowdays supersede auto-imported BIFs, why nowarn_bif_clash in itself generates an error
+ %% (OTP-8579) /PaN
{otp_5362_4,
<<"-compile(nowarn_deprecated_function).
-compile(nowarn_bif_clash).
@@ -1795,9 +1821,8 @@ otp_5362(Config) when is_list(Config) ->
warn_deprecated_function,
warn_bif_clash]},
{error,
- [{5,erl_lint,{call_to_redefined_bif,{spawn,1}}}],
- [{3,erl_lint,{redefine_bif,{spawn,1}}},
- {4,erl_lint,{deprecated,{erlang,hash,2},{erlang,phash2,2},
+ [{5,erl_lint,{call_to_redefined_old_bif,{spawn,1}}}],
+ [{4,erl_lint,{deprecated,{erlang,hash,2},{erlang,phash2,2},
"in a future release"}}]}},
{otp_5362_5,
@@ -1808,8 +1833,8 @@ otp_5362(Config) when is_list(Config) ->
spawn(A).
">>,
{[nowarn_unused_function]},
- {warnings,
- [{3,erl_lint,{redefine_bif,{spawn,1}}}]}},
+ {errors,
+ [{2,erl_lint,disallowed_nowarn_bif_clash}],[]}},
%% The special nowarn_X are not affected by general warn_X.
{otp_5362_6,
@@ -1822,8 +1847,8 @@ otp_5362(Config) when is_list(Config) ->
{[nowarn_unused_function,
warn_deprecated_function,
warn_bif_clash]},
- {warnings,
- [{3,erl_lint,{redefine_bif,{spawn,1}}}]}},
+ {errors,
+ [{2,erl_lint,disallowed_nowarn_bif_clash}],[]}},
{otp_5362_7,
<<"-export([spawn/1]).
@@ -1838,7 +1863,9 @@ otp_5362(Config) when is_list(Config) ->
spawn(A).
">>,
{[nowarn_unused_function]},
- {error,[{4,erl_lint,{bad_nowarn_bif_clash,{spawn,2}}}],
+ {error,[{3,erl_lint,disallowed_nowarn_bif_clash},
+ {4,erl_lint,disallowed_nowarn_bif_clash},
+ {4,erl_lint,{bad_nowarn_bif_clash,{spawn,2}}}],
[{5,erl_lint,{bad_nowarn_deprecated_function,{3,hash,-1}}},
{5,erl_lint,{bad_nowarn_deprecated_function,{erlang,hash,-1}}},
{5,erl_lint,{bad_nowarn_deprecated_function,{{a,b,c},hash,-1}}}]}
@@ -1865,7 +1892,21 @@ otp_5362(Config) when is_list(Config) ->
t() -> #a{}.
">>,
{[]},
- []}
+ []},
+
+ {otp_5362_10,
+ <<"-compile({nowarn_deprecated_function,{erlang,hash,2}}).
+ -compile({nowarn_bif_clash,{spawn,1}}).
+ -import(x,[spawn/1]).
+ spin(A) ->
+ erlang:hash(A, 3000),
+ spawn(A).
+ ">>,
+ {[nowarn_unused_function,
+ warn_deprecated_function,
+ warn_bif_clash]},
+ {errors,
+ [{2,erl_lint,disallowed_nowarn_bif_clash}],[]}}
],
@@ -2234,7 +2275,7 @@ otp_5878(Config) when is_list(Config) ->
{15,erl_lint,{undefined_field,r3,q}},
{17,erl_lint,{undefined_field,r,q}},
{21,erl_lint,illegal_guard_expr},
- {23,erl_lint,illegal_guard_expr}],
+ {23,erl_lint,{illegal_guard_local_call,{l,0}}}],
[]} =
run_test2(Config, Ill1, [warn_unused_record]),
@@ -2389,9 +2430,9 @@ bif_clash(Config) when is_list(Config) ->
N.
">>,
[],
- {errors,[{2,erl_lint,{call_to_redefined_bif,{size,1}}}],[]}},
+ {errors,[{2,erl_lint,{call_to_redefined_old_bif,{size,1}}}],[]}},
- %% Verify that (some) warnings can be turned off.
+ %% Verify that warnings can not be turned off in the old way.
{clash2,
<<"-export([t/1,size/1]).
t(X) ->
@@ -2400,17 +2441,198 @@ bif_clash(Config) when is_list(Config) ->
size({N,_}) ->
N.
- %% My own abs/1 function works on lists too.
- %% Unfortunately, it is not exported, so there will
- %% be a warning that can't be turned off.
+ %% My own abs/1 function works on lists too. From R14 this really works.
abs([H|T]) when $a =< H, H =< $z -> [H-($a-$A)|abs(T)];
abs([H|T]) -> [H|abs(T)];
abs([]) -> [];
abs(X) -> erlang:abs(X).
">>,
- {[nowarn_bif_clash]},
- {warnings,[{11,erl_lint,{redefine_bif,{abs,1}}},
- {11,erl_lint,{unused_function,{abs,1}}}]}}],
+ {[nowarn_unused_function,nowarn_bif_clash]},
+ {errors,[{erl_lint,disallowed_nowarn_bif_clash}],[]}},
+ %% As long as noone calls an overridden BIF, it's totally OK
+ {clash3,
+ <<"-export([size/1]).
+ size({N,_}) ->
+ N;
+ size(X) ->
+ erlang:size(X).
+ ">>,
+ [],
+ []},
+ %% But this is totally wrong - meaning of the program changed in R14, so this is an error
+ {clash4,
+ <<"-export([size/1]).
+ size({N,_}) ->
+ N;
+ size(X) ->
+ size(X).
+ ">>,
+ [],
+ {errors,[{5,erl_lint,{call_to_redefined_old_bif,{size,1}}}],[]}},
+ %% For a post R14 bif, its only a warning
+ {clash5,
+ <<"-export([binary_part/2]).
+ binary_part({B,_},{X,Y}) ->
+ binary_part(B,{X,Y});
+ binary_part(B,{X,Y}) ->
+ binary:part(B,X,Y).
+ ">>,
+ [],
+ {warnings,[{3,erl_lint,{call_to_redefined_bif,{binary_part,2}}}]}},
+ %% If you really mean to call yourself here, you can "unimport" size/1
+ {clash6,
+ <<"-export([size/1]).
+ -compile({no_auto_import,[size/1]}).
+ size([]) ->
+ 0;
+ size({N,_}) ->
+ N;
+ size([_|T]) ->
+ 1+size(T).
+ ">>,
+ [],
+ []},
+ %% Same for the post R14 autoimport warning
+ {clash7,
+ <<"-export([binary_part/2]).
+ -compile({no_auto_import,[binary_part/2]}).
+ binary_part({B,_},{X,Y}) ->
+ binary_part(B,{X,Y});
+ binary_part(B,{X,Y}) ->
+ binary:part(B,X,Y).
+ ">>,
+ [],
+ []},
+ %% but this doesn't mean the local function is allowed in a guard...
+ {clash8,
+ <<"-export([x/1]).
+ -compile({no_auto_import,[binary_part/2]}).
+ x(X) when binary_part(X,{1,2}) =:= <<1,2>> ->
+ hej.
+ binary_part({B,_},{X,Y}) ->
+ binary_part(B,{X,Y});
+ binary_part(B,{X,Y}) ->
+ binary:part(B,X,Y).
+ ">>,
+ [],
+ {errors,[{3,erl_lint,{illegal_guard_local_call,{binary_part,2}}}],[]}},
+ %% no_auto_import is not like nowarn_bif_clash, it actually removes the autoimport
+ {clash9,
+ <<"-export([x/1]).
+ -compile({no_auto_import,[binary_part/2]}).
+ x(X) ->
+ binary_part(X,{1,2}) =:= <<1,2>>.
+ ">>,
+ [],
+ {errors,[{4,erl_lint,{undefined_function,{binary_part,2}}}],[]}},
+ %% but we could import it again...
+ {clash10,
+ <<"-export([x/1]).
+ -compile({no_auto_import,[binary_part/2]}).
+ -import(erlang,[binary_part/2]).
+ x(X) ->
+ binary_part(X,{1,2}) =:= <<1,2>>.
+ ">>,
+ [],
+ []},
+ %% and actually use it in a guard...
+ {clash11,
+ <<"-export([x/1]).
+ -compile({no_auto_import,[binary_part/2]}).
+ -import(erlang,[binary_part/2]).
+ x(X) when binary_part(X,{0,1}) =:= <<0>> ->
+ binary_part(X,{1,2}) =:= <<1,2>>.
+ ">>,
+ [],
+ []},
+ %% but for non-obvious historical reasons, imported functions cannot be used in
+ %% fun construction without the module name...
+ {clash12,
+ <<"-export([x/1]).
+ -compile({no_auto_import,[binary_part/2]}).
+ -import(erlang,[binary_part/2]).
+ x(X) when binary_part(X,{0,1}) =:= <<0>> ->
+ binary_part(X,{1,2}) =:= fun binary_part/2.
+ ">>,
+ [],
+ {errors,[{5,erl_lint,{undefined_function,{binary_part,2}}}],[]}},
+ %% Not from erlang and not from anywhere else
+ {clash13,
+ <<"-export([x/1]).
+ -compile({no_auto_import,[binary_part/2]}).
+ -import(x,[binary_part/2]).
+ x(X) ->
+ binary_part(X,{1,2}) =:= fun binary_part/2.
+ ">>,
+ [],
+ {errors,[{5,erl_lint,{undefined_function,{binary_part,2}}}],[]}},
+ %% ...while real auto-import is OK.
+ {clash14,
+ <<"-export([x/1]).
+ x(X) when binary_part(X,{0,1}) =:= <<0>> ->
+ binary_part(X,{1,2}) =:= fun binary_part/2.
+ ">>,
+ [],
+ []},
+ %% Import directive clashing with old bif is an error, regardless of if it's called or not
+ {clash15,
+ <<"-export([x/1]).
+ -import(x,[abs/1]).
+ x(X) ->
+ binary_part(X,{1,2}).
+ ">>,
+ [],
+ {errors,[{2,erl_lint,{redefine_old_bif_import,{abs,1}}}],[]}},
+ %% For a new BIF, it's only a warning
+ {clash16,
+ <<"-export([x/1]).
+ -import(x,[binary_part/3]).
+ x(X) ->
+ abs(X).
+ ">>,
+ [],
+ {warnings,[{2,erl_lint,{redefine_bif_import,{binary_part,3}}}]}},
+ %% And, you cannot redefine already imported things that aren't auto-imported
+ {clash17,
+ <<"-export([x/1]).
+ -import(x,[binary_port/3]).
+ -import(y,[binary_port/3]).
+ x(X) ->
+ abs(X).
+ ">>,
+ [],
+ {errors,[{3,erl_lint,{redefine_import,{{binary_port,3},x}}}],[]}},
+ %% Not with local functions either
+ {clash18,
+ <<"-export([x/1]).
+ -import(x,[binary_port/3]).
+ binary_port(A,B,C) ->
+ binary_part(A,B,C).
+ x(X) ->
+ abs(X).
+ ">>,
+ [],
+ {errors,[{3,erl_lint,{define_import,{binary_port,3}}}],[]}},
+ %% Like clash8: Dont accept a guard if it's explicitly module-name called either
+ {clash19,
+ <<"-export([binary_port/3]).
+ -compile({no_auto_import,[binary_part/3]}).
+ -import(x,[binary_part/3]).
+ binary_port(A,B,C) when x:binary_part(A,B,C) ->
+ binary_part(A,B,C+1).
+ ">>,
+ [],
+ {errors,[{4,erl_lint,illegal_guard_expr}],[]}},
+ %% Not with local functions either
+ {clash20,
+ <<"-export([binary_port/3]).
+ -import(x,[binary_part/3]).
+ binary_port(A,B,C) ->
+ binary_part(A,B,C).
+ ">>,
+ [warn_unused_import],
+ {warnings,[{2,erl_lint,{redefine_bif_import,{binary_part,3}}}]}}
+ ],
?line [] = run(Config, Ts),
ok.
@@ -2632,8 +2854,6 @@ format_level(Level, Count, Config) ->
%% Test the -on_load(Name/0) directive.
-on_load(suite) ->
- [on_load_successful, on_load_failing].
on_load_successful(Config) when is_list(Config) ->
Ts = [{on_load_1,
@@ -2714,6 +2934,21 @@ on_load_failing(Config) when is_list(Config) ->
?line [] = run(Config, Ts),
ok.
+too_many_arguments(doc) ->
+ "Test that too many arguments is not accepted.";
+too_many_arguments(suite) -> [];
+too_many_arguments(Config) when is_list(Config) ->
+ Ts = [{too_many_1,
+ <<"f(_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_) -> ok.">>,
+ [],
+ {errors,
+ [{1,erl_lint,{too_many_arguments,256}}],[]}}
+ ],
+
+ ?line [] = run(Config, Ts),
+ ok.
+
+
run(Config, Tests) ->
F = fun({N,P,Ws,E}, BadL) ->
case catch run_test(Config, P, Ws) of
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index 0a119d1e38..e0f233fb2a 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2006-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 2006-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%
%%
%%%----------------------------------------------------------------
@@ -30,22 +30,25 @@
-define(privdir, "erl_pp_SUITE_priv").
-define(t, test_server).
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(datadir, ?config(data_dir, Config)).
-define(privdir, ?config(priv_dir, Config)).
-endif.
--export([all/1, init_per_testcase/2, fin_per_testcase/2]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
+ init_per_testcase/2, end_per_testcase/2]).
--export([expr/1, func/1, call/1, recs/1, try_catch/1, if_then/1,
- receive_after/1, bits/1, head_tail/1, package/1,
- cond1/1, block/1, case1/1, ops/1, messages/1,
- old_mnemosyne_syntax/1,
- attributes/1, import_export/1, misc_attrs/1,
- hook/1,
- neg_indent/1,
- tickets/1,
- otp_6321/1, otp_6911/1, otp_6914/1, otp_8150/1, otp_8238/1]).
+-export([ func/1, call/1, recs/1, try_catch/1, if_then/1,
+ receive_after/1, bits/1, head_tail/1, package/1,
+ cond1/1, block/1, case1/1, ops/1, messages/1,
+ old_mnemosyne_syntax/1,
+ import_export/1, misc_attrs/1,
+ hook/1,
+ neg_indent/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]).
%% Internal export.
-export([ehook/6]).
@@ -57,17 +60,40 @@ init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
-fin_per_testcase(_Case, _Config) ->
+end_per_testcase(_Case, _Config) ->
Dog = ?config(watchdog, _Config),
test_server:timetrap_cancel(Dog),
ok.
-all(suite) ->
- [expr, attributes, hook, neg_indent, tickets].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [{group, expr}, {group, attributes}, hook, neg_indent,
+ {group, tickets}].
+
+groups() ->
+ [{expr, [],
+ [func, call, recs, try_catch, if_then, receive_after,
+ bits, head_tail, package, cond1, block, case1, ops,
+ messages, old_mnemosyne_syntax]},
+ {attributes, [], [misc_attrs, import_export]},
+ {tickets, [],
+ [otp_6321, otp_6911, otp_6914, otp_8150, otp_8238,
+ otp_8473, otp_8522, otp_8567, otp_8664]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
-expr(suite) ->
- [func, call, recs, try_catch, if_then, receive_after, bits, head_tail,
- package, cond1, block, case1, ops, messages, old_mnemosyne_syntax].
func(suite) ->
[];
@@ -149,15 +175,15 @@ recs(Config) when is_list(Config) ->
(A#r1.a)#r.a > 3 -> 3
end(#r1{a = #r{a = 4}}),
7 = fun(A) when record(A#r3.a, r1) -> 7 end(#r3{}),
- [#r1{a = 2,b = 1}] =
+ [#r1{a = 2,b = 1}] =
fun() ->
- [A || A <- [#r1{a = 1, b = 3},
- #r2{a = 2,b = 1},
+ [A || A <- [#r1{a = 1, b = 3},
+ #r2{a = 2,b = 1},
#r1{a = 2, b = 1}],
- A#r1.a >
+ A#r1.a >
A#r1.b]
end(),
- {[_],b} =
+ {[_],b} =
fun(L) ->
%% A is checked only once:
R1 = [{A,B} || A <- L, A#r1.a, B <- L, A#r1.b],
@@ -176,7 +202,7 @@ recs(Config) when is_list(Config) ->
end(#r1{a = 2}),
%% The test done twice (an effect of doing the test as soon as possible).
- 3 = fun(A) when A#r1.a > 3,
+ 3 = fun(A) when A#r1.a > 3,
record(A, r1) -> 3
end(#r1{a = 5}),
@@ -250,18 +276,18 @@ recs(Config) when is_list(Config) ->
ok
end(),
- both = fun(A) when A#r.a, A#r.b -> both
+ both = fun(A) when A#r.a, A#r.b -> both
end(#r{a = true, b = true}),
ok = fun() ->
- F = fun(A, B) when ((A#r1.a) orelse (B#r2.a))
+ F = fun(A, B) when ((A#r1.a) orelse (B#r2.a))
or (B#r2.b) or (A#r1.b) ->
true;
(_, _) -> false
end,
- true = F(#r1{a = false, b = false},
+ true = F(#r1{a = false, b = false},
#r2{a = false, b = true}),
- false = F(#r1{a = true, b = true},
+ false = F(#r1{a = true, b = true},
#r1{a = false, b = true}),
ok
end(),
@@ -272,7 +298,7 @@ recs(Config) when is_list(Config) ->
<<"-record(r1, {a, b = foo:bar(kljlfjsdlf, kjlksdjf)}).
-record(r2, {c = #r1{}, d = #r1{a = bar:foo(kljklsjdf)}}).
- t() ->
+ t() ->
R = #r2{},
R#r2{c = R, d = #r1{}}.">>}
],
@@ -303,10 +329,10 @@ try_catch(Config) when is_list(Config) ->
{try_6,
<<"t() -> try 1=2 catch throw:{badmatch,2} -> 3 end.">>},
{try_7,
- <<"t() -> try 1=2 of 3 -> 4
+ <<"t() -> try 1=2 of 3 -> 4
catch error:{badmatch,2} -> 5 end.">>},
{try_8,
- <<"t() -> try 1=2
+ <<"t() -> try 1=2
catch error:{badmatch,2} -> 3
after put(try_catch, 4) end.">>},
{try_9,
@@ -370,7 +396,7 @@ receive_after(Config) when is_list(Config) ->
{X,Y};
Z ->
Z
- after
+ after
foo:bar() ->
{3,4}
end.">>}
@@ -428,7 +454,7 @@ head_tail(Config) when is_list(Config) ->
{list_4,
<<"t() -> [a].">>},
{list_5,
- <<"t() ->
+ <<"t() ->
[foo:bar(lkjljlskdfj, klsdajflds, sdafkljsdlfkjdas, kjlsdadjl),
bar:foo(kljlkjsdf, lkjsdlfj, [kljsfj, sdfdsfsad])].">>}
],
@@ -461,7 +487,7 @@ cond1(Config) when is_list(Config) ->
" true ->\n"
" {x,y}\n"
"end" = CChars,
-% ?line ok = pp_expr(<<"cond
+% ?line ok = pp_expr(<<"cond
% {foo,bar} ->
% [a,b];
% true ->
@@ -543,7 +569,7 @@ old_mnemosyne_syntax(Config) when is_list(Config) ->
" X <- table(tab),\n"
" X.foo = bar\n"
" ]\n"
- "end" =
+ "end" =
lists:flatten(erl_pp:expr(Q)),
R = {rule,12,sales,2,
@@ -558,13 +584,11 @@ old_mnemosyne_syntax(Config) when is_list(Config) ->
{atom,14,sales}}]}]},
?line "sales(E, employee) :-\n"
" E <- table(employee),\n"
- " E.salary = sales.\n" =
+ " E.salary = sales.\n" =
lists:flatten(erl_pp:form(R)),
ok.
-attributes(suite) ->
- [misc_attrs, import_export].
import_export(suite) ->
[];
@@ -659,7 +683,7 @@ hook(Config) when is_list(Config) ->
?line "INVALID-FORM:{foo,bar}:" = lists:flatten(erl_pp:expr({foo,bar})),
- %% A list (as before R6), not a list of lists.
+ %% A list (as before R6), not a list of lists.
G = [{op,1,'>',{atom,1,a},{foo,{atom,1,b}}}], % not a proper guard
GChars = lists:flatten(erl_pp:guard(G, H)),
G2 = [{op,1,'>',{atom,1,a},
@@ -676,23 +700,23 @@ hook(Config) when is_list(Config) ->
%% Note: no leading spaces before "begin".
Block = {block,0,[{match,0,{var,0,'A'},{integer,0,3}},
{atom,0,true}]},
- ?line "begin\n A =" ++ _ =
+ ?line "begin\n A =" ++ _ =
lists:flatten(erl_pp:expr(Block, 17, none)),
%% Special...
- ?line true =
+ ?line true =
"{some,value}" =:= lists:flatten(erl_pp:expr({value,0,{some,value}})),
%% Silly...
?line true =
- "if true -> 0 end" =:=
+ "if true -> 0 end" =:=
flat_expr({'if',0,[{clause,0,[],[],[{atom,0,0}]}]}),
%% More compatibility: before R6
OldIf = {'if',0,[{clause,0,[],[{atom,0,true}],[{atom,0,b}]}]},
NewIf = {'if',0,[{clause,0,[],[[{atom,0,true}]],[{atom,0,b}]}]},
OldIfChars = lists:flatten(erl_pp:expr(OldIf)),
- NewIfChars = lists:flatten(erl_pp:expr(NewIf)),
+ NewIfChars = lists:flatten(erl_pp:expr(NewIf)),
?line true = OldIfChars =:= NewIfChars,
ok.
@@ -705,7 +729,7 @@ remove_indentation(S) ->
ehook(HE, I, P, H, foo, bar) ->
hook(HE, I, P, H).
-hook({foo,E}, I, P, H) ->
+hook({foo,E}, I, P, H) ->
erl_pp:expr({call,0,{atom,0,foo},[E]}, I, P, H).
neg_indent(suite) ->
@@ -721,14 +745,14 @@ neg_indent(Config) when is_list(Config) ->
end">>),
?line ok = pp_expr(
<<"fun() ->
- F = fun(A, B) when ((A#r1.a) orelse (B#r2.a))
+ F = fun(A, B) when ((A#r1.a) orelse (B#r2.a))
or (B#r2.b) or (A#r1.b) ->
true;
(_, _) -> false
end,
- true = F(#r1{a = false, b = false},
+ true = F(#r1{a = false, b = false},
#r2{a = false, b = true}),
- false = F(#r1{a = true, b = true},
+ false = F(#r1{a = true, b = true},
#r1{a = false, b = true}),
ok
end()">>),
@@ -762,8 +786,6 @@ neg_indent(Config) when is_list(Config) ->
ok.
-tickets(suite) ->
- [otp_6321, otp_6911, otp_6914, otp_8150, otp_8238].
otp_6321(doc) ->
"OTP_6321. Bug fix of exprs().";
@@ -812,7 +834,7 @@ otp_8150(doc) ->
"OTP_8150. Types.";
otp_8150(suite) -> [];
otp_8150(Config) when is_list(Config) ->
- ?line _ = [{N,ok} = {N,pp_forms(B)} ||
+ ?line _ = [{N,ok} = {N,pp_forms(B)} ||
{N,B} <- type_examples()
],
ok.
@@ -846,7 +868,7 @@ type_examples() ->
{ex4,<<"-type t1() :: atom(). ">>},
{ex5,<<"-type t2() :: [t1()]. ">>},
{ex6,<<"-type t3(Atom) :: integer(Atom). ">>},
- {ex7,<<"-type t4() :: t3(foobar). ">>},
+ {ex7,<<"-type '\\'t::4'() :: t3('\\'foobar'). ">>},
{ex8,<<"-type t5() :: {t1(), t3(foo)}. ">>},
{ex9,<<"-type t6() :: 1 | 2 | 3 | 'foo' | 'bar'. ">>},
{ex10,<<"-type t7() :: []. ">>},
@@ -882,16 +904,16 @@ type_examples() ->
"1|2|3|4|a|b|c|d| "
"nonempty_maybe_improper_list(integer, any())]}. ">>},
{ex30,<<"-type t99() ::"
- "{t2(),t4(),t5(),t6(),t7(),t8(),t10(),t14(),"
+ "{t2(),'\\'t::4'(),t5(),t6(),t7(),t8(),t10(),t14(),"
"t15(),t20(),t21(), t22(),t25()}. ">>},
{ex31,<<"-spec t1(FooBar :: t99()) -> t99();"
"(t2()) -> t2();"
- "(t4()) -> t4() when is_subtype(t4(), t24);"
+ "('\\'t::4'()) -> '\\'t::4'() when is_subtype('\\'t::4'(), t24);"
"(t23()) -> t23() when is_subtype(t23(), atom()),"
" is_subtype(t23(), t14());"
"(t24()) -> t24() when is_subtype(t24(), atom()),"
" is_subtype(t24(), t14()),"
- " is_subtype(t24(), t4()).">>},
+ " is_subtype(t24(), '\\'t::4'()).">>},
{ex32,<<"-spec mod:t2() -> any(). ">>},
{ex33,<<"-opaque attributes_data() :: "
"[{'column', column()} | {'line', info_line()} |"
@@ -911,12 +933,126 @@ type_examples() ->
"f19 = 3 :: integer()|undefined,"
"f5 = 3 :: undefined|integer()}). ">>}].
+otp_8473(doc) ->
+ "OTP_8473. Bugfix abstract type 'fun'.";
+otp_8473(suite) -> [];
+otp_8473(Config) when is_list(Config) ->
+ Ex = [{ex1,<<"-type 'fun'(A) :: A.\n"
+ "-type funkar() :: 'fun'(fun((integer()) -> atom())).\n">>}],
+ ?line _ = [{N,ok} = {N,pp_forms(B)} ||
+ {N,B} <- Ex],
+ ok.
+
+otp_8522(doc) ->
+ "OTP_8522. Avoid duplicated 'undefined' in record field types.";
+otp_8522(suite) -> [];
+otp_8522(Config) when is_list(Config) ->
+ FileName = filename('otp_8522.erl', Config),
+ C = <<"-module(otp_8522).\n"
+ "-record(r, {f1 :: undefined,\n"
+ " f2 :: A :: undefined,\n"
+ " f3 :: (undefined),\n"
+ " f4 :: x | y | undefined | z,\n"
+ " f5 :: a}).\n">>,
+ ?line ok = file:write_file(FileName, C),
+ ?line {ok, _} = compile:file(FileName, [{outdir,?privdir},debug_info]),
+ BF = filename("otp_8522", Config),
+ ?line {ok, A} = beam_lib:chunks(BF, [abstract_code]),
+ ?line 5 = count_atom(A, undefined),
+ ok.
+
+count_atom(A, A) ->
+ 1;
+count_atom(T, A) when is_tuple(T) ->
+ count_atom(tuple_to_list(T), A);
+count_atom(L, A) when is_list(L) ->
+ lists:sum([count_atom(T, A) || T <- L]);
+count_atom(_, _) ->
+ 0.
+
+otp_8567(doc) ->
+ "OTP_8567. Avoid duplicated 'undefined' in record field types.";
+otp_8567(suite) -> [];
+otp_8567(Config) when is_list(Config) ->
+ FileName = filename('otp_8567.erl', Config),
+ C = <<"-module otp_8567.\n"
+ "-compile export_all.\n"
+ "-spec(a).\n"
+ "-record r, {a}.\n"
+ "-record s, {a :: integer()}.\n"
+ "-type t() :: {#r{},#s{}}.\n">>,
+ ?line ok = file:write_file(FileName, C),
+ ?line {error,[{_,[{3,erl_parse,["syntax error before: ","')'"]}]}],_} =
+ compile:file(FileName, [return]),
+
+ F = <<"-module(otp_8567).\n"
+ "-compile(export_all).\n"
+ "-record(t, {a}).\n"
+ "-record(u, {a :: integer()}).\n"
+ "-opaque ot() :: {#t{}, #u{}}.\n"
+ "-opaque(ot1() :: atom()).\n"
+ "-type a() :: integer().\n"
+ "-spec t() -> a().\n"
+ "t() ->\n"
+ " 3.\n"
+ "\n"
+ "-spec(t1/1 :: (ot()) -> ot1()).\n"
+ "t1(A) ->\n"
+ " A.\n"
+ "\n"
+ "-spec(t2 (ot()) -> ot1()).\n"
+ "t2(A) ->\n"
+ " A.\n"
+ "\n"
+ "-spec(otp_8567:t3/1 :: (ot()) -> ot1()).\n"
+ "t3(A) ->\n"
+ " A.\n"
+ "\n"
+ "-spec(otp_8567:t4 (ot()) -> ot1()).\n"
+ "t4(A) ->\n"
+ " A.\n">>,
+ ?line ok = pp_forms(F),
+
+ ok.
+
+otp_8664(doc) ->
+ "OTP_8664. Types with integer expressions.";
+otp_8664(suite) -> [];
+otp_8664(Config) when is_list(Config) ->
+ FileName = filename('otp_8664.erl', Config),
+ C1 = <<"-module(otp_8664).\n"
+ "-export([t/0]).\n"
+ "-define(A, -3).\n"
+ "-define(B, (?A*(-1 band (((2)))))).\n"
+ "-type t1() :: ?B | ?A.\n"
+ "-type t2() :: ?B-1 .. -?B.\n"
+ "-type t3() :: 9 band (8 - 3) | 1+2 | 5 band 3.\n"
+ "-type b1() :: <<_:_*(3-(-1))>>\n"
+ " | <<_:(-(?B))>>\n"
+ " | <<_:4>>.\n"
+ "-type u() :: 1 .. 2 | 3.. 4 | (8-3) ..6 | 5+0..6.\n"
+ "-type t() :: t1() | t2() | t3() | b1() | u().\n"
+ "-spec t() -> t().\n"
+ "t() -> 3.\n">>,
+ ?line ok = file:write_file(FileName, C1),
+ ?line {ok, _, []} = compile:file(FileName, [return]),
+
+ C2 = <<"-module(otp_8664).\n"
+ "-export([t/0]).\n"
+ "-spec t() -> 9 and 4.\n"
+ "t() -> 0.\n">>,
+ ?line ok = file:write_file(FileName, C2),
+ ?line {error,[{_,[{3,erl_lint,{type_syntax,integer}}]}],_} =
+ compile:file(FileName, [return]),
+
+ ok.
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
compile(Config, Tests) ->
F = fun({N,P}, BadL) ->
case catch compile_file(Config, P) of
- ok ->
+ ok ->
case pp_forms(P) of
ok ->
BadL;
@@ -924,8 +1060,8 @@ compile(Config, Tests) ->
?t:format("~nTest ~p failed.~n", [N]),
fail()
end;
- Bad ->
- ?t:format("~nTest ~p failed. got~n ~p~n",
+ Bad ->
+ ?t:format("~nTest ~p failed. got~n ~p~n",
[N, Bad]),
fail()
end
@@ -955,7 +1091,7 @@ compile_file(Config, Test0) ->
Error ->
Error
end.
-
+
compile_file(Config, Test0, Opts0) ->
FileName = filename('erl_pp_test.erl', Config),
Test = list_to_binary(["-module(erl_pp_test). "
@@ -964,7 +1100,7 @@ compile_file(Config, Test0, Opts0) ->
Opts = [export_all,return,nowarn_unused_record,{outdir,?privdir} | Opts0],
ok = file:write_file(FileName, Test),
case compile:file(FileName, Opts) of
- {ok, _M, _Ws} ->
+ {ok, _M, _Ws} ->
{ok, filename:rootname(FileName)};
Error -> Error
end.
@@ -991,7 +1127,7 @@ pp_forms(Bin, Hook) ->
end.
parse_and_pp_forms(String, Hook) ->
- lists:append(lists:map(fun(AF) -> erl_pp:form(AF, Hook)
+ lists:append(lists:map(fun(AF) -> erl_pp:form(AF, Hook)
end, parse_forms(String))).
parse_forms(Chars) ->
@@ -999,13 +1135,13 @@ parse_forms(Chars) ->
parse_forms2(String, [], 1, []).
parse_forms2([], _Cont, _Line, Forms) ->
- lists:reverse(Forms);
+ lists:reverse(Forms);
parse_forms2(String, Cont0, Line, Forms) ->
case erl_scan:tokens(Cont0, String, Line) of
{done, {ok, Tokens, EndLine}, Chars} ->
{ok, Form} = erl_parse:parse_form(Tokens),
parse_forms2(Chars, [], EndLine, [Form | Forms]);
- {more, Cont} when element(3, Cont) =:= [] ->
+ {more, Cont} when element(3, Cont) =:= [] ->
%% extra spaces after forms...
parse_forms2([], Cont, Line, Forms);
{more, Cont} ->
@@ -1023,10 +1159,10 @@ pp_expr(Bin, Hook) ->
PP2 = (catch parse_and_pp_expr(PPneg, 0, Hook)),
if
PP1 =:= PP2 -> % same line numbers
- case
+ case
(test_max_line(PP1) =:= ok) and (test_new_line(PPneg) =:= ok)
of
- true ->
+ true ->
ok;
false ->
not_ok
@@ -1059,7 +1195,7 @@ test_max_line(String) ->
end.
max_line(String) ->
- lists:max([0 | [length(Sub) ||
+ lists:max([0 | [length(Sub) ||
Sub <- string:tokens(String, "\n"),
string:substr(Sub, 1, 5) =/= "-file"]]).
diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl
index 32a06d15c7..75e908e97c 100644
--- a/lib/stdlib/test/erl_scan_SUITE.erl
+++ b/lib/stdlib/test/erl_scan_SUITE.erl
@@ -1,25 +1,26 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1998-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 1998-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(erl_scan_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
--export([error/1, error_1/1, error_2/1, iso88591/1, otp_7810/1]).
+-export([ error_1/1, error_2/1, iso88591/1, otp_7810/1]).
-import(lists, [nth/2,flatten/1]).
-import(io_lib, [print/1]).
@@ -34,19 +35,19 @@
-define(line, put(line, ?LINE), ).
-define(config(A,B),config(A,B)).
-define(t, test_server).
-%% config(priv_dir, _) ->
+%% config(priv_dir, _) ->
%% ".";
%% config(data_dir, _) ->
%% ".".
-else.
--include("test_server.hrl").
--export([init_per_testcase/2, fin_per_testcase/2]).
+-include_lib("test_server/include/test_server.hrl").
+-export([init_per_testcase/2, end_per_testcase/2]).
init_per_testcase(_Case, Config) when is_list(Config) ->
?line Dog=test_server:timetrap(test_server:seconds(1200)),
[{watchdog, Dog}|Config].
-
-fin_per_testcase(_Case, Config) ->
+
+end_per_testcase(_Case, Config) ->
Dog=?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
@@ -55,15 +56,27 @@ fin_per_testcase(_Case, Config) ->
% Default timetrap timeout (set in init_per_testcase).
-define(default_timeout, ?t:minutes(1)).
-all(doc) ->
- ["Test cases for the 'erl_scan' module."];
-all(suite) ->
- [error,iso88591,otp_7810].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [{group, error}, iso88591, otp_7810].
+
+groups() ->
+ [{error, [], [error_1, error_2]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
-error(doc) ->
- ["Error cases"];
-error(suite) ->
- [error_1, error_2].
error_1(doc) ->
["(OTP-2347)"];
@@ -97,7 +110,7 @@ assert_type(N, integer) when is_integer(N) ->
ok;
assert_type(N, atom) when is_atom(N) ->
ok.
-
+
check(String) ->
Error = erl_scan:string(String),
check_error(Error, erl_scan).
@@ -146,7 +159,7 @@ iso88591(Config) when is_list(Config) ->
ok -> ok %Aok
end.
-otp_7810(doc) ->
+otp_7810(doc) ->
["OTP-7810. White spaces, comments, and more.."];
otp_7810(suite) ->
[];
@@ -185,7 +198,7 @@ reserved_words() ->
'andalso', 'orelse', 'end', 'fun', 'if', 'let', 'of',
'query', 'receive', 'when', 'bnot', 'not', 'div',
'rem', 'band', 'and', 'bor', 'bxor', 'bsl', 'bsr',
- 'or', 'xor', 'spec'] , % 'spec' shouldn't be there...
+ 'or', 'xor'],
[begin
?line {RW, true} = {RW, erl_scan:reserved_word(RW)},
S = atom_to_list(RW),
@@ -203,7 +216,7 @@ atoms() ->
?line test_string("a@2", [{atom,1,a@2}]),
?line test_string([39,65,200,39], [{atom,1,'A�'}]),
?line test_string("�rlig �sten", [{atom,1,�rlig},{atom,1,�sten}]),
- ?line {ok,[{atom,_,'$a'}],{1,6}} =
+ ?line {ok,[{atom,_,'$a'}],{1,6}} =
erl_scan:string("'$\\a'", {1,1}),
?line test("'$\\a'"),
ok.
@@ -221,8 +234,8 @@ punctuations() ->
Three = ["/=:=", "<=:=", "==:=", ">=:="], % three tokens...
No = Three ++ L,
SL0 = [{S1++S2,{-length(S1),S1,S2}} ||
- S1 <- L,
- S2 <- L,
+ S1 <- L,
+ S2 <- L,
not lists:member(S1++S2, No)],
SL = family_list(SL0),
%% Two tokens. When there are several answers, the one with
@@ -244,21 +257,24 @@ punctuations() ->
{'\\',1},{'^',1},{'`',1},{'~',1}],
?line test_string("#&*+/:<>?@\\^`~", PTs2),
+ ?line test_string(".. ", [{'..',1}]),
+ ?line test("1 .. 2"),
+ ?line test_string("...", [{'...',1}]),
ok.
comments() ->
?line test("a %%\n b"),
?line {ok,[],1} = erl_scan:string("%"),
?line test("a %%\n b"),
- ?line {ok,[{atom,_,a},{atom,_,b}],{2,3}} =
+ ?line {ok,[{atom,_,a},{atom,_,b}],{2,3}} =
erl_scan:string("a %%\n b",{1,1}),
- ?line {ok,[{atom,_,a},{comment,_,"%%"},{atom,_,b}],{2,3}} =
+ ?line {ok,[{atom,_,a},{comment,_,"%%"},{atom,_,b}],{2,3}} =
erl_scan:string("a %%\n b",{1,1}, [return_comments]),
?line {ok,[{atom,_,a},
{white_space,_," "},
{white_space,_,"\n "},
{atom,_,b}],
- {2,3}} =
+ {2,3}} =
erl_scan:string("a %%\n b",{1,1},[return_white_spaces]),
?line {ok,[{atom,_,a},
{white_space,_," "},
@@ -275,14 +291,14 @@ errors() ->
?line {error,{1,erl_scan,char},1} = erl_scan:string("$"),
?line test_string([34,65,200,34], [{string,1,"A�"}]),
?line test_string("\\", [{'\\',1}]),
- ?line {'EXIT',_} =
+ ?line {'EXIT',_} =
(catch {foo, erl_scan:string('$\\a', {1,1})}), % type error
- ?line {'EXIT',_} =
+ ?line {'EXIT',_} =
(catch {foo, erl_scan:tokens([], '$\\a', {1,1})}), % type error
?line "{a,tuple}" = erl_scan:format_error({a,tuple}),
ok.
-
+
integers() ->
[begin
I = list_to_integer(S),
@@ -299,14 +315,14 @@ base_integers() ->
?line test_string(BS++"#"++S, Ts)
end || {BS,S} <- [{"2","11"}, {"5","23234"}, {"12","05a"},
{"16","abcdef"}, {"16","ABCDEF"}] ],
-
+
?line {error,{1,erl_scan,{base,1}},1} = erl_scan:string("1#000"),
-
+
?line test_string("12#bc", [{integer,1,11},{atom,1,c}]),
-
+
[begin
Str = BS ++ "#" ++ S,
- ?line {error,{1,erl_scan,{illegal,integer}},1} =
+ ?line {error,{1,erl_scan,{illegal,integer}},1} =
erl_scan:string(Str)
end || {BS,S} <- [{"3","3"},{"15","f"}, {"12","c"}] ],
@@ -323,8 +339,8 @@ floats() ->
end || FS <- ["1.0","001.17","3.31200","1.0e0","1.0E17",
"34.21E-18", "17.0E+14"]],
?line test_string("1.e2", [{integer,1,1},{'.',1},{atom,1,e2}]),
-
- ?line {error,{1,erl_scan,{illegal,float}},1} =
+
+ ?line {error,{1,erl_scan,{illegal,float}},1} =
erl_scan:string("1.0e400"),
[begin
?line {error,{1,erl_scan,{illegal,float}},1} = erl_scan:string(S)
@@ -345,16 +361,16 @@ dots() ->
{".a", {ok,[{'.',1},{atom,1,a}],1}}
],
?line [R = erl_scan:string(S) || {S, R} <- Dot],
-
+
?line {ok,[{dot,_}=T1],{1,2}} = erl_scan:string(".", {1,1}, text),
- ?line [{column,1},{length,1},{line,1},{text,"."}] =
+ ?line [{column,1},{length,1},{line,1},{text,"."}] =
erl_scan:token_info(T1, [column, length, line, text]),
?line {ok,[{dot,_}=T2],{1,3}} = erl_scan:string(".%", {1,1}, text),
- ?line [{column,1},{length,1},{line,1},{text,"."}] =
+ ?line [{column,1},{length,1},{line,1},{text,"."}] =
erl_scan:token_info(T2, [column, length, line, text]),
?line {ok,[{dot,_}=T3],{1,6}} =
erl_scan:string(".% �h", {1,1}, text),
- ?line [{column,1},{length,1},{line,1},{text,"."}] =
+ ?line [{column,1},{length,1},{line,1},{text,"."}] =
erl_scan:token_info(T3, [column, length, line, text]),
?line {error,{{1,2},erl_scan,char},{1,3}} =
erl_scan:string(".$", {1,1}),
@@ -376,10 +392,10 @@ dots() ->
?line {done,{ok,[{comment,_,"%. "},
{white_space,_,"\n"},
{dot,_}],
- {2,3}}, ""} =
+ {2,3}}, ""} =
erl_scan:tokens(C, "\n. ", {1,1}, return), % any loc, any options
- ?line [test_string(S, R) ||
+ ?line [test_string(S, R) ||
{S, R} <- [{".$\n", [{'.',1},{char,1,$\n}]},
{"$\\\n", [{char,1,$\n}]},
{"'\\\n'", [{atom,1,'\n'}]},
@@ -392,7 +408,7 @@ chars() ->
Ts = [{char,1,C}],
?line test_string(L, Ts)
end || C <- lists:seq(0, 255)],
-
+
%% Leading zeroes...
[begin
L = lists:flatten(io_lib:format("$\\~3.8.0b", [C])),
@@ -406,13 +422,13 @@ chars() ->
Ts = [{char,1,C band 2#11111}],
?line test_string(L, Ts)
end || C <- lists:seq(0, 255)],
-
+
[begin
L = "$\\" ++ [C],
Ts = [{char,1,V}],
?line test_string(L, Ts)
- end || {C,V} <- [{$n,$\n}, {$r,$\r}, {$t,$\t}, {$v,$\v},
- {$b,$\b}, {$f,$\f}, {$e,$\e}, {$s,$\s},
+ end || {C,V} <- [{$n,$\n}, {$r,$\r}, {$t,$\t}, {$v,$\v},
+ {$b,$\b}, {$f,$\f}, {$e,$\e}, {$s,$\s},
{$d,$\d}]],
EC = [$\n,$\r,$\t,$\v,$\b,$\f,$\e,$\s,$\d],
@@ -445,7 +461,7 @@ chars() ->
end || C <- lists:seq(0, 255) -- (No ++ [$\\])],
?line test_string("$\n", [{char,1,$\n}]),
- ?line {error,{{1,1},erl_scan,char},{1,4}} =
+ ?line {error,{{1,1},erl_scan,char},{1,4}} =
erl_scan:string("$\\^",{1,1}),
?line test_string("$\\\n", [{char,1,$\n}]),
%% Robert's scanner returns line 1:
@@ -453,7 +469,7 @@ chars() ->
?line test_string("$\n\n", [{char,1,$\n}]),
?line test("$\n\n"),
ok.
-
+
variables() ->
?line test_string(" \237_Aou�eiy��", [{var,1,'_Aou�eiy��'}]),
@@ -469,8 +485,8 @@ eof() ->
?line {done,{eof,2},eof} = erl_scan:tokens(C1, eof, 1),
{more, C2} = erl_scan:tokens([], "abra", 1),
%% An error before R13A.
- %% ?line {done,Err={error,{1,erl_scan,scan},1},eof} =
- ?line {done,{ok,[{atom,1,abra}],1},eof} =
+ %% ?line {done,Err={error,{1,erl_scan,scan},1},eof} =
+ ?line {done,{ok,[{atom,1,abra}],1},eof} =
erl_scan:tokens(C2, eof, 1),
%% With column.
@@ -478,7 +494,7 @@ eof() ->
?line {done,{eof,{2,1}},eof} = erl_scan:tokens(C3, eof, 1),
{more, C4} = erl_scan:tokens([], "abra", {1,1}),
%% An error before R13A.
- %% ?line {done,{error,{{1,1},erl_scan,scan},{1,5}},eof} =
+ %% ?line {done,{error,{{1,1},erl_scan,scan},{1,5}},eof} =
?line {done,{ok,[{atom,_,abra}],{1,5}},eof} =
erl_scan:tokens(C4, eof, 1),
@@ -486,7 +502,7 @@ eof() ->
%% the R12B scanner returns eof as LeftoverChars: (eof is correct)
?line {more, C5} = erl_scan:tokens([], "a", 1),
%% An error before R13A.
- %% ?line {done,{error,{1,erl_scan,scan},1},eof} =
+ %% ?line {done,{error,{1,erl_scan,scan},1},eof} =
?line {done,{ok,[{atom,1,a}],1},eof} =
erl_scan:tokens(C5,eof,1),
@@ -528,7 +544,7 @@ illegal() ->
erl_scan:tokens([], "foo "++Atom++". ", {1,1}),
?line {error,{{1,1},erl_scan,{illegal,atom}},{1,1003}} =
erl_scan:string(QAtom, {1,1}),
- ?line {done,{error,{{1,5},erl_scan,{illegal,atom}},{1,1007}},". "} =
+ ?line {done,{error,{{1,5},erl_scan,{illegal,atom}},{1,1007}},". "} =
erl_scan:tokens([], "foo "++QAtom++". ", {1,1}),
?line {error,{{1,1},erl_scan,{illegal,var}},{1,1001}} =
erl_scan:string(Var, {1,1}),
@@ -553,7 +569,7 @@ crashes() ->
?line {'EXIT',_} = (catch {foo, erl_scan:string("\"\\v"++[-1,$"])}), %$"
?line {'EXIT',_} = (catch {foo, erl_scan:string([$",-1,$"])}),
?line {'EXIT',_} = (catch {foo, erl_scan:string("% foo"++[-1])}),
- ?line {'EXIT',_} =
+ ?line {'EXIT',_} =
(catch {foo, erl_scan:string("% foo"++[-1],{1,1})}),
?line {'EXIT',_} = (catch {foo, erl_scan:string([a])}), % type error
@@ -564,7 +580,7 @@ crashes() ->
?line {'EXIT',_} = (catch {foo, erl_scan:string("\"\\v"++[a,$"])}), %$"
?line {'EXIT',_} = (catch {foo, erl_scan:string([$",a,$"])}),
?line {'EXIT',_} = (catch {foo, erl_scan:string("% foo"++[a])}),
- ?line {'EXIT',_} =
+ ?line {'EXIT',_} =
(catch {foo, erl_scan:string("% foo"++[a],{1,1})}),
?line {'EXIT',_} = (catch {foo, erl_scan:string([3.0])}), % type error
@@ -573,26 +589,26 @@ crashes() ->
options() ->
%% line and column are not options, but tested here
- ?line {ok,[{atom,1,foo},{white_space,1," "},{comment,1,"% bar"}], 1} =
+ ?line {ok,[{atom,1,foo},{white_space,1," "},{comment,1,"% bar"}], 1} =
erl_scan:string("foo % bar", 1, return),
- ?line {ok,[{atom,1,foo},{white_space,1," "}],1} =
+ ?line {ok,[{atom,1,foo},{white_space,1," "}],1} =
erl_scan:string("foo % bar", 1, return_white_spaces),
- ?line {ok,[{atom,1,foo},{comment,1,"% bar"}],1} =
+ ?line {ok,[{atom,1,foo},{comment,1,"% bar"}],1} =
erl_scan:string("foo % bar", 1, return_comments),
- ?line {ok,[{atom,17,foo}],17} =
+ ?line {ok,[{atom,17,foo}],17} =
erl_scan:string("foo % bar", 17),
- ?line {'EXIT',{function_clause,_}} =
- (catch {foo,
+ ?line {'EXIT',{function_clause,_}} =
+ (catch {foo,
erl_scan:string("foo % bar", {a,1}, [])}), % type error
- ?line {ok,[{atom,_,foo}],{17,18}} =
+ ?line {ok,[{atom,_,foo}],{17,18}} =
erl_scan:string("foo % bar", {17,9}, []),
- ?line {'EXIT',{function_clause,_}} =
+ ?line {'EXIT',{function_clause,_}} =
(catch {foo,
erl_scan:string("foo % bar", {1,0}, [])}), % type error
- ?line {ok,[{foo,1}],1} =
+ ?line {ok,[{foo,1}],1} =
erl_scan:string("foo % bar",1, [{reserved_word_fun,
fun(W) -> W =:= foo end}]),
- ?line {'EXIT',{badarg,_}} =
+ ?line {'EXIT',{badarg,_}} =
(catch {foo,
erl_scan:string("foo % bar",1, % type error
[{reserved_word_fun,
@@ -618,14 +634,14 @@ more_options() ->
token_info() ->
?line {ok,[T1],_} = erl_scan:string("foo", {1,18}, [text]),
- {'EXIT',{badarg,_}} =
+ {'EXIT',{badarg,_}} =
(catch {foo, erl_scan:token_info(T1, foo)}), % type error
?line {line,1} = erl_scan:token_info(T1, line),
?line {column,18} = erl_scan:token_info(T1, column),
?line {length,3} = erl_scan:token_info(T1, length),
?line {text,"foo"} = erl_scan:token_info(T1, text),
?line [{category,atom},{column,18},{length,3},{line,1},
- {symbol,foo},{text,"foo"}] =
+ {symbol,foo},{text,"foo"}] =
erl_scan:token_info(T1),
?line [{length,3},{column,18}] =
erl_scan:token_info(T1, [length, column]),
@@ -648,9 +664,9 @@ token_info() ->
?line {category,'='} = erl_scan:token_info(T3, category),
?line [{symbol,'='}] = erl_scan:token_info(T3, [symbol]),
ok.
-
+
attributes_info() ->
- ?line {'EXIT',_} =
+ ?line {'EXIT',_} =
(catch {foo,erl_scan:attributes_info(foo)}), % type error
?line [{line,18}] = erl_scan:attributes_info(18),
?line {location,19} = erl_scan:attributes_info(19, location),
@@ -717,9 +733,9 @@ set_attribute() ->
?line [{line,{17,11}},{text,"foo"}] =
erl_scan:attributes_info(A7, [line,column,text]),
- ?line {'EXIT',_} =
+ ?line {'EXIT',_} =
(catch {foo, erl_scan:set_attribute(line, [], F2)}), % type error
- ?line {'EXIT',{badarg,_}} =
+ ?line {'EXIT',{badarg,_}} =
(catch {foo, erl_scan:set_attribute(column, [], F2)}), % type error
ok.
@@ -790,14 +806,14 @@ unicode() ->
?line {ok,[{char,1,83},{integer,1,45}],1} =
erl_scan:string("$\\12345"), % not unicode
- ?line {error,{1,erl_scan,{illegal,character}},1} =
+ ?line {error,{1,erl_scan,{illegal,character}},1} =
erl_scan:string([1089]),
- ?line {error,{{1,1},erl_scan,{illegal,character}},{1,2}} =
+ ?line {error,{{1,1},erl_scan,{illegal,character}},{1,2}} =
erl_scan:string([1089], {1,1}),
?line {error,{1,erl_scan,{illegal,character}},1} =
- %% ?line {error,{1,erl_scan,{illegal,atom}},1} =
+ %% ?line {error,{1,erl_scan,{illegal,atom}},1} =
erl_scan:string("'a"++[1089]++"b'"),
- ?line {error,{{1,3},erl_scan,{illegal,character}},{1,4}} =
+ ?line {error,{{1,3},erl_scan,{illegal,character}},{1,4}} =
erl_scan:string("'a"++[1089]++"b'", {1,1}),
?line test("\"a"++[1089]++"b\""),
?line {ok,[{char,1,1}],1} = erl_scan:string([$$,$\\,$^,1089]),
@@ -822,7 +838,7 @@ unicode() ->
?line {ok,[{integer,1,16#aaa}],1} = erl_scan:string(Qs),
?line {ok,[Q2],{1,9}} = erl_scan:string("$\\x{aaa}", {1,1}, text),
?line [{category,integer},{column,1},{length,8},
- {line,1},{symbol,16#aaa},{text,Qs}] =
+ {line,1},{symbol,16#aaa},{text,Qs}] =
erl_scan:token_info(Q2),
U1 = "\"\\x{aaa}\"",
@@ -830,11 +846,11 @@ unicode() ->
?line [{category,'['},{column,1},{length,1},{line,1},
{symbol,'['},{text,"\""}] = erl_scan:token_info(T1, Tags),
?line [{category,integer},{column,2},{length,7},
- {line,1},{symbol,16#aaa},{text,"\\x{aaa}"}] =
+ {line,1},{symbol,16#aaa},{text,"\\x{aaa}"}] =
erl_scan:token_info(T2, Tags),
?line [{category,']'},{column,9},{length,1},{line,1},
{symbol,']'},{text,"\""}] = erl_scan:token_info(T3, Tags),
- ?line {ok,[{'[',1},{integer,1,16#aaa},{']',1}],1} =
+ ?line {ok,[{'[',1},{integer,1,16#aaa},{']',1}],1} =
erl_scan:string(U1, 1),
U2 = "\"\\x41\\x{fff}\\x42\"",
@@ -844,7 +860,7 @@ unicode() ->
U3 = "\"a\n\\x{fff}\n\"",
?line {ok,[{'[',1},{char,1,$a},{',',1},{char,1,$\n},
{',',2},{integer,2,16#fff},{',',2},{char,2,$\n},
- {']',3}],3} =
+ {']',3}],3} =
erl_scan:string(U3, 1),
U4 = "\"\\^\n\\x{aaa}\\^\n\"",
@@ -867,10 +883,10 @@ unicode() ->
{char,_,$d},{']',_}],{1,8}} = erl_scan:string(Str1, {1,1}),
?line test(Str1),
Comment = "%% "++[1089],
- ?line {ok,[{comment,1,[$%,$%,$\s,1089]}],1} =
+ ?line {ok,[{comment,1,[$%,$%,$\s,1089]}],1} =
erl_scan:string(Comment, 1, return),
- ?line {ok,[{comment,_,[$%,$%,$\s,1089]}],{1,5}} =
- erl_scan:string(Comment, {1,1}, return),
+ ?line {ok,[{comment,_,[$%,$%,$\s,1089]}],{1,5}} =
+ erl_scan:string(Comment, {1,1}, return),
ok.
more_chars() ->
@@ -885,7 +901,7 @@ more_chars() ->
erl_scan:tokens(C1, eof, 1),
?line {ok,[{char,1,123},{atom,1,a},{'}',1}],1} =
erl_scan:string("$\\{a}"),
-
+
?line {error,{{1,1},erl_scan,char},{1,4}} =
erl_scan:string("$\\x", {1,1}),
?line {error,{{1,1},erl_scan,char},{1,5}} =
@@ -893,12 +909,12 @@ more_chars() ->
?line {more, C3} = erl_scan:tokens([], "$\\x", {1,1}),
?line {done,{error,{{1,1},erl_scan,char},{1,4}},eof} =
erl_scan:tokens(C3, eof, 1),
- ?line {error,{{1,1},erl_scan,char},{1,5}} =
+ ?line {error,{{1,1},erl_scan,char},{1,5}} =
erl_scan:string("$\\x{",{1,1}),
?line {more, C2} = erl_scan:tokens([], "$\\x{", {1,1}),
- ?line {done,{error,{{1,1},erl_scan,char},{1,5}},eof} =
+ ?line {done,{error,{{1,1},erl_scan,char},{1,5}},eof} =
erl_scan:tokens(C2, eof, 1),
- ?line {error,{1,erl_scan,{illegal,character}},1} =
+ ?line {error,{1,erl_scan,{illegal,character}},1} =
erl_scan:string("$\\x{g}"),
?line {error,{{1,1},erl_scan,{illegal,character}},{1,5}} =
erl_scan:string("$\\x{g}", {1,1}),
@@ -924,12 +940,12 @@ more_chars() ->
?line test("$\\x{10FFFF}"),
?line test("$\\x{10ffff}"),
?line test("\"$\n \\{1}\""),
- ?line {error,{1,erl_scan,{illegal,character}},1} =
+ ?line {error,{1,erl_scan,{illegal,character}},1} =
erl_scan:string("$\\x{110000}"),
- ?line {error,{{1,1},erl_scan,{illegal,character}},{1,12}} =
+ ?line {error,{{1,1},erl_scan,{illegal,character}},{1,12}} =
erl_scan:string("$\\x{110000}", {1,1}),
- ?line {error,{{1,1},erl_scan,{illegal,character}},{1,4}} =
+ ?line {error,{{1,1},erl_scan,{illegal,character}},{1,4}} =
erl_scan:string("$\\xfg", {1,1}),
?line test("$\\xffg"),
@@ -953,11 +969,11 @@ test(String) ->
{Wtokens, Wend},
{Ctokens, Cend},
{CWtokens, CWend},
- {CWtokens2, _}] =
+ {CWtokens2, _}] =
[scan_string_with_column(String, X) ||
- X <- [[],
- [return_white_spaces],
- [return_comments],
+ X <- [[],
+ [return_white_spaces],
+ [return_comments],
[return],
[return]]], % for white space compaction test
@@ -969,7 +985,7 @@ test(String) ->
{none,Tokens} = {none, filter_tokens(CWtokens, [white_space,comment])},
{comments,Ctokens} =
{comments,filter_tokens(CWtokens, [white_space])},
- {white_spaces,Wtokens} =
+ {white_spaces,Wtokens} =
{white_spaces,filter_tokens(CWtokens, [comment])},
%% Use token attributes to extract parts from the original string,
@@ -991,9 +1007,9 @@ test(String) ->
%% Line attribute only:
[Simple,Wsimple,Csimple,WCsimple] = Simples =
[element(2, erl_scan:string(String, 1, Opts)) ||
- Opts <- [[],
- [return_white_spaces],
- [return_comments],
+ Opts <- [[],
+ [return_white_spaces],
+ [return_comments],
[return]]],
{consistent,true} = {consistent,consistent_attributes(Simples)},
{simple_wc,WCsimple} = {simple_wc,simplify(CWtokens)},
@@ -1004,19 +1020,19 @@ test(String) ->
%% Line attribute only, with text:
[SimpleTxt,WsimpleTxt,CsimpleTxt,WCsimpleTxt] = SimplesTxt =
[element(2, erl_scan:string(String, 1, [text|Opts])) ||
- Opts <- [[],
- [return_white_spaces],
- [return_comments],
+ Opts <- [[],
+ [return_white_spaces],
+ [return_comments],
[return]]],
TextTxt = get_text(WCsimpleTxt),
{text_txt,TextTxt,String} = {text_txt,String,TextTxt},
- {consistent_txt,true} =
+ {consistent_txt,true} =
{consistent_txt,consistent_attributes(SimplesTxt)},
- {simple_txt,SimpleTxt} =
+ {simple_txt,SimpleTxt} =
{simple_txt,filter_tokens(WCsimpleTxt, [white_space,comment])},
- {simple_c_txt,CsimpleTxt} =
+ {simple_c_txt,CsimpleTxt} =
{simple_c_txt,filter_tokens(WCsimpleTxt, [white_space])},
- {simple_w_txt,WsimpleTxt} =
+ {simple_w_txt,WsimpleTxt} =
{simple_w_txt,filter_tokens(WCsimpleTxt, [comment])},
ok.
@@ -1024,18 +1040,18 @@ test(String) ->
test_white_space_compaction(Tokens, Tokens2) when Tokens =:= Tokens2 ->
[WS, WS2] = [select_tokens(Ts, [white_space]) || Ts <- [Tokens, Tokens2]],
test_wsc(WS, WS2).
-
+
test_wsc([], []) ->
ok;
test_wsc([Token|Tokens], [Token2|Tokens2]) ->
- [Text, Text2] = [Text ||
- {text, Text} <-
+ [Text, Text2] = [Text ||
+ {text, Text} <-
[erl_scan:token_info(T, text) ||
T <- [Token, Token2]]],
Sz = erts_debug:size(Text),
Sz2 = erts_debug:size({Text, Text2}),
IsCompacted = Sz2 < 2*Sz+erts_debug:size({a,a}),
- ToBeCompacted = is_compacted(Text),
+ ToBeCompacted = is_compacted(Text),
if
IsCompacted =:= ToBeCompacted ->
test_wsc(Tokens, Tokens2);
@@ -1050,14 +1066,14 @@ is_compacted("\n\r") ->
is_compacted("\n\f") ->
true;
is_compacted([$\n|String]) ->
- all_spaces(String)
+ all_spaces(String)
orelse
all_tabs(String);
is_compacted(String) ->
all_spaces(String)
orelse
all_tabs(String).
-
+
all_spaces(L) ->
all_same(L, $\s).
@@ -1078,7 +1094,7 @@ newlines_first([Token|Tokens]) ->
_ ->
Nnls =:= 0
end,
- if
+ if
OK -> newlines_first(Tokens);
true -> OK
end.
@@ -1097,7 +1113,7 @@ simplify([]) ->
get_text(Tokens) ->
lists:flatten(
- [T ||
+ [T ||
Token <- Tokens,
({text,T} = erl_scan:token_info(Token, text)) =/= []]).
@@ -1108,7 +1124,7 @@ test_decorated_tokens(String, Tokens) ->
token_attrs(Tokens) ->
[{L,C,Len,T} ||
Token <- Tokens,
- ([{line,L},{column,C},{length,Len},{text,T}] =
+ ([{line,L},{column,C},{length,Len},{text,T}] =
erl_scan:token_info(Token, [line,column,length,text])) =/= []].
test_strings([], _S, Line, Column) ->
@@ -1150,7 +1166,7 @@ scan_string_with_column(String, Options0) ->
{ok, Ts1, End1} = erl_scan:string(String, StartLoc, Options),
TString = String ++ ". ",
{ok,Ts2,End2} = scan_tokens(TString, Options, [], StartLoc),
- {ok, Ts3, End3} =
+ {ok, Ts3, End3} =
scan_tokens_1({more, []}, TString, Options, [], StartLoc),
{end_2,End2,End3} = {end_2,End3,End2},
{EndLine1,EndColumn1} = End1,
@@ -1190,8 +1206,8 @@ consistent_attributes([Ts | TsL]) ->
L = [T || T <- Ts, is_integer(element(2, T))],
case L of
[] ->
- TagsL = [[Tag || {Tag,_} <-
- erl_scan:attributes_info(element(2, T))] ||
+ TagsL = [[Tag || {Tag,_} <-
+ erl_scan:attributes_info(element(2, T))] ||
T <- Ts],
case lists:usort(TagsL) of
[_] ->
diff --git a/lib/stdlib/test/error_logger_forwarder.erl b/lib/stdlib/test/error_logger_forwarder.erl
index 7d99d07860..5703ac769a 100644
--- a/lib/stdlib/test/error_logger_forwarder.erl
+++ b/lib/stdlib/test/error_logger_forwarder.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2009. All Rights Reserved.
+%% 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
diff --git a/lib/stdlib/test/escript_SUITE.erl b/lib/stdlib/test/escript_SUITE.erl
index 70aae54d62..447d6fb629 100644
--- a/lib/stdlib/test/escript_SUITE.erl
+++ b/lib/stdlib/test/escript_SUITE.erl
@@ -1,55 +1,71 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2007-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 2007-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(escript_SUITE).
-export([
- all/1,
+ all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
init_per_testcase/2,
- fin_per_testcase/2,
+ end_per_testcase/2,
basic/1,
- errors/1,
+ errors/1,
strange_name/1,
emulator_flags/1,
module_script/1,
beam_script/1,
archive_script/1,
- epp/1
+ epp/1,
+ create_and_extract/1,
+ foldl/1,
+ overflow/1,
+ verify_sections/3
]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
+-include_lib("kernel/include/file.hrl").
+
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [basic, errors, strange_name, emulator_flags,
+ module_script, beam_script, archive_script, epp,
+ create_and_extract, foldl, overflow].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
-all(suite) ->
- [
- basic,
- errors,
- strange_name,
- emulator_flags,
- module_script,
- beam_script,
- archive_script,
- epp
- ].
+end_per_group(_GroupName, Config) ->
+ Config.
init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?t:minutes(1)),
[{watchdog,Dog}|Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog = ?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
@@ -68,11 +84,11 @@ basic(Config) when is_list(Config) ->
?line run(Dir, "factorial_warning 20",
[data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\n"
"factorial 20 = 2432902008176640000\nExitCode:0">>]),
- ?line run(Dir, "-s", "factorial_warning",
+ ?line run_with_opts(Dir, "-s", "factorial_warning",
[data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
- ?line run(Dir, "-s -i", "factorial_warning",
+ ?line run_with_opts(Dir, "-s -i", "factorial_warning",
[data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
- ?line run(Dir, "-c -s", "factorial_warning",
+ ?line run_with_opts(Dir, "-c -s", "factorial_warning",
[data_dir,<<"factorial_warning:12: Warning: function bar/0 is unused\nExitCode:0">>]),
?line run(Dir, "filesize "++filename:join(?config(data_dir, Config),"filesize"),
[data_dir,<<"filesize:11: Warning: function id/1 is unused\n324\nExitCode:0">>]),
@@ -100,7 +116,7 @@ errors(Config) when is_list(Config) ->
[data_dir,<<"lint_error:6: function main/1 already defined\n">>,
data_dir,"lint_error:8: variable 'ExitCode' is unbound\n",
<<"escript: There were compilation errors.\nExitCode:127">>]),
- ?line run(Dir, "-s", "lint_error",
+ ?line run_with_opts(Dir, "-s", "lint_error",
[data_dir,<<"lint_error:6: function main/1 already defined\n">>,
data_dir,"lint_error:8: variable 'ExitCode' is unbound\n",
<<"escript: There were compilation errors.\nExitCode:127">>]),
@@ -140,31 +156,31 @@ module_script(Config) when is_list(Config) ->
OrigFile = filename:join([Data,"emulator_flags"]),
{ok, OrigBin} = file:read_file(OrigFile),
?line [Shebang, Mode, Flags | Source] = string:tokens(binary_to_list(OrigBin), "\n"),
- ?line {ok, OrigFI} = file:read_file_info(OrigFile),
+ ?line {ok, OrigFI} = file:read_file_info(OrigFile),
%% Write source file
Priv = ?config(priv_dir, Config),
Dir = filename:absname(Priv), % Get rid of trailing slash.
Base = "module_script",
ErlFile = filename:join([Priv, Base ++ ".erl"]),
- ErlCode = ["-module(", Base, ").\n",
+ ErlCode = ["\n-module(", Base, ").\n",
"-export([main/1]).\n\n",
string:join(Source, "\n"),
"\n"],
?line ok = file:write_file(ErlFile, ErlCode),
-
+
%%%%%%%
%% Create and run scripts without emulator flags
%% With shebang
NoArgsBase = Base ++ "_no_args_with_shebang",
NoArgsFile = filename:join([Priv, NoArgsBase]),
- ?line ok = file:write_file(NoArgsFile,
+ ?line ok = file:write_file(NoArgsFile,
[Shebang, "\n",
ErlCode]),
?line ok = file:write_file_info(NoArgsFile, OrigFI),
-
- ?line run(Dir, NoArgsBase ++ " -arg1 arg2 arg3",
+
+ ?line run(Dir, NoArgsBase ++ " -arg1 arg2 arg3",
[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
"nostick:[]\n"
"mnesia:[]\n"
@@ -172,7 +188,7 @@ module_script(Config) when is_list(Config) ->
"unknown:[]\n"
"ExitCode:0">>]),
- ?line run(Dir, "", NoArgsBase ++ " -arg1 arg2 arg3",
+ ?line run_with_opts(Dir, "", NoArgsBase ++ " -arg1 arg2 arg3",
[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
"nostick:[]\n"
"mnesia:[]\n"
@@ -183,33 +199,33 @@ module_script(Config) when is_list(Config) ->
%% Without shebang
NoArgsBase2 = Base ++ "_no_args_without_shebang",
NoArgsFile2 = filename:join([Priv, NoArgsBase2]),
- ?line ok = file:write_file(NoArgsFile2,
+ ?line ok = file:write_file(NoArgsFile2,
["Something else than shebang!!!", "\n",
ErlCode]),
?line ok = file:write_file_info(NoArgsFile2, OrigFI),
-
- ?line run(Dir, "", NoArgsBase2 ++ " -arg1 arg2 arg3",
+
+ ?line run_with_opts(Dir, "", NoArgsBase2 ++ " -arg1 arg2 arg3",
[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
"nostick:[]\n"
"mnesia:[]\n"
"ERL_FLAGS=false\n"
"unknown:[]\n"
"ExitCode:0">>]),
-
+
%% Plain module without header
NoArgsBase3 = Base ++ "_no_args_without_header",
NoArgsFile3 = filename:join([Priv, NoArgsBase3]),
?line ok = file:write_file(NoArgsFile3, [ErlCode]),
?line ok = file:write_file_info(NoArgsFile3, OrigFI),
-
- ?line run(Dir, "", NoArgsBase3 ++ " -arg1 arg2 arg3",
+
+ ?line run_with_opts(Dir, "", NoArgsBase3 ++ " -arg1 arg2 arg3",
[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
"nostick:[]\n"
"mnesia:[]\n"
"ERL_FLAGS=false\n"
"unknown:[]\n"
"ExitCode:0">>]),
-
+
%%%%%%%
%% Create and run scripts with emulator flags
@@ -217,12 +233,12 @@ module_script(Config) when is_list(Config) ->
ArgsBase = Base ++ "_args_with_shebang",
ArgsFile = filename:join([Priv, ArgsBase]),
?line ok = file:write_file(ArgsFile,
- [Shebang, "\n",
+ [Shebang, "\n",
Mode, "\n",
Flags, "\n",
ErlCode]),
- ?line ok = file:write_file_info(ArgsFile, OrigFI),
-
+ ?line ok = file:write_file_info(ArgsFile, OrigFI),
+
?line run(Dir, ArgsBase ++ " -arg1 arg2 arg3",
[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
"nostick:[{nostick,[]}]\n"
@@ -242,32 +258,32 @@ beam_script(Config) when is_list(Config) ->
OrigFile = filename:join([Data,"emulator_flags"]),
{ok, OrigBin} = file:read_file(OrigFile),
?line [Shebang, Mode, Flags | Source] = string:tokens(binary_to_list(OrigBin), "\n"),
- ?line {ok, OrigFI} = file:read_file_info(OrigFile),
+ ?line {ok, OrigFI} = file:read_file_info(OrigFile),
%% Write source file
Priv = ?config(priv_dir, Config),
Dir = filename:absname(Priv), % Get rid of trailing slash.
Base = "beam_script",
ErlFile = filename:join([Priv, Base ++ ".erl"]),
- ?line ok = file:write_file(ErlFile,
- ["-module(", Base, ").\n",
+ ?line ok = file:write_file(ErlFile,
+ ["\n-module(", Base, ").\n",
"-export([main/1]).\n\n",
string:join(Source, "\n"),
"\n"]),
%% Compile the code
?line {ok, _Mod, BeamCode} = compile:file(ErlFile, [binary]),
-
+
%%%%%%%
%% Create and run scripts without emulator flags
%% With shebang
NoArgsBase = Base ++ "_no_args_with_shebang",
NoArgsFile = filename:join([Priv, NoArgsBase]),
- ?line ok = file:write_file(NoArgsFile,
+ ?line ok = file:write_file(NoArgsFile,
[Shebang, "\n",
BeamCode]),
- ?line ok = file:write_file_info(NoArgsFile, OrigFI),
+ ?line ok = file:write_file_info(NoArgsFile, OrigFI),
?line run(Dir, NoArgsBase ++ " -arg1 arg2 arg3",
[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
@@ -277,7 +293,7 @@ beam_script(Config) when is_list(Config) ->
"unknown:[]\n"
"ExitCode:0">>]),
- ?line run(Dir, "", NoArgsBase ++ " -arg1 arg2 arg3",
+ ?line run_with_opts(Dir, "", NoArgsBase ++ " -arg1 arg2 arg3",
[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
"nostick:[]\n"
"mnesia:[]\n"
@@ -288,12 +304,12 @@ beam_script(Config) when is_list(Config) ->
%% Without shebang
NoArgsBase2 = Base ++ "_no_args_without_shebang",
NoArgsFile2 = filename:join([Priv, NoArgsBase2]),
- ?line ok = file:write_file(NoArgsFile2,
+ ?line ok = file:write_file(NoArgsFile2,
["Something else than shebang!!!", "\n",
BeamCode]),
- ?line ok = file:write_file_info(NoArgsFile2, OrigFI),
+ ?line ok = file:write_file_info(NoArgsFile2, OrigFI),
- ?line run(Dir, "", NoArgsBase2 ++ " -arg1 arg2 arg3",
+ ?line run_with_opts(Dir, "", NoArgsBase2 ++ " -arg1 arg2 arg3",
[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
"nostick:[]\n"
"mnesia:[]\n"
@@ -305,9 +321,9 @@ beam_script(Config) when is_list(Config) ->
NoArgsBase3 = Base ++ "_no_args_without_header",
NoArgsFile3 = filename:join([Priv, NoArgsBase3]),
?line ok = file:write_file(NoArgsFile3, [BeamCode]),
- ?line ok = file:write_file_info(NoArgsFile3, OrigFI),
+ ?line ok = file:write_file_info(NoArgsFile3, OrigFI),
- ?line run(Dir, "", NoArgsBase3 ++ " -arg1 arg2 arg3",
+ ?line run_with_opts(Dir, "", NoArgsBase3 ++ " -arg1 arg2 arg3",
[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
"nostick:[]\n"
"mnesia:[]\n"
@@ -322,12 +338,12 @@ beam_script(Config) when is_list(Config) ->
ArgsBase = Base ++ "_args",
ArgsFile = filename:join([Priv, ArgsBase]),
?line ok = file:write_file(ArgsFile,
- [Shebang, "\n",
+ [Shebang, "\n",
Mode, "\n",
Flags, "\n",
BeamCode]),
- ?line ok = file:write_file_info(ArgsFile, OrigFI),
-
+ ?line ok = file:write_file_info(ArgsFile, OrigFI),
+
?line run(Dir, ArgsBase ++ " -arg1 arg2 arg3",
[<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
"nostick:[{nostick,[]}]\n"
@@ -356,13 +372,13 @@ archive_script(Config) when is_list(Config) ->
?line ok = compile_app(TopDir, "archive_script_dict"),
?line ok = compile_app(TopDir, "archive_script_dummy"),
?line {ok, MainFiles} = file:list_dir(TopDir),
- ?line ok = compile_files(MainFiles, TopDir, TopDir),
-
+ ?line ok = compile_files(MainFiles, TopDir, TopDir),
+
%% Create the archive
{ok, TopFiles} = file:list_dir(TopDir),
?line {ok, {_, ArchiveBin}} = zip:create(Archive, TopFiles,
[memory, {compress, []}, {cwd, TopDir}]),
-
+
%% Read the source script
OrigFile = filename:join([DataDir, "emulator_flags"]),
{ok, OrigBin} = file:read_file(OrigFile),
@@ -371,73 +387,73 @@ archive_script(Config) when is_list(Config) ->
Flags = "%%! -archive_script_dict foo bar"
" -archive_script_dict foo"
" -archive_script_dummy bar",
- ?line {ok, OrigFI} = file:read_file_info(OrigFile),
-
+ ?line {ok, OrigFI} = file:read_file_info(OrigFile),
+
%%%%%%%
%% Create and run scripts without emulator flags
- MainBase = "archive_script_main",
- MainScript = filename:join([PrivDir, MainBase]),
+ MainBase = "archive_script_main",
+ MainScript = filename:join([PrivDir, MainBase]),
%% With shebang
- ?line ok = file:write_file(MainScript,
+ ?line ok = file:write_file(MainScript,
[Shebang, "\n",
Flags, "\n",
ArchiveBin]),
- ?line ok = file:write_file_info(MainScript, OrigFI),
-
+ ?line ok = file:write_file_info(MainScript, OrigFI),
+
?line run(PrivDir, MainBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
"dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
"dummy:[{archive_script_dummy,[\"bar\"]}]\n"
"priv:{ok,<<\"Some private data...\\n\">>}\n"
"ExitCode:0">>]),
- ?line run(PrivDir, "", MainBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ ?line run_with_opts(PrivDir, "", MainBase ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
"dict:[{archive_script_dict,[\"foo\",\"bar\"]},{archive_script_dict,[\"foo\"]}]\n"
"dummy:[{archive_script_dummy,[\"bar\"]}]\n"
"priv:{ok,<<\"Some private data...\\n\">>}\n"
"ExitCode:0">>]),
-
+
?line ok = file:rename(MainScript, MainScript ++ "_with_shebang"),
%% Without shebang (no flags)
- ?line ok = file:write_file(MainScript,
+ ?line ok = file:write_file(MainScript,
["Something else than shebang!!!", "\n",
ArchiveBin]),
- ?line ok = file:write_file_info(MainScript, OrigFI),
-
- ?line run(PrivDir, "", MainBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ ?line ok = file:write_file_info(MainScript, OrigFI),
+
+ ?line run_with_opts(PrivDir, "", MainBase ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
"dict:[]\n"
"dummy:[]\n"
"priv:{ok,<<\"Some private data...\\n\">>}\n"
"ExitCode:0">>]),
?line ok = file:rename(MainScript, MainScript ++ "_without_shebang"),
-
+
%% Plain archive without header (no flags)
-
+
?line ok = file:write_file(MainScript, [ArchiveBin]),
- ?line ok = file:write_file_info(MainScript, OrigFI),
-
- ?line run(PrivDir, "", MainBase ++ " -arg1 arg2 arg3",
- [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
+ ?line ok = file:write_file_info(MainScript, OrigFI),
+
+ ?line run_with_opts(PrivDir, "", MainBase ++ " -arg1 arg2 arg3",
+ [<<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n"
"dict:[]\n"
"dummy:[]\n"
"priv:{ok,<<\"Some private data...\\n\">>}\n"
"ExitCode:0">>]),
?line ok = file:rename(MainScript, MainScript ++ "_without_header"),
-
+
%%%%%%%
%% Create and run scripts with emulator flags
AltBase = "archive_script_alternate_main",
AltScript = filename:join([PrivDir, AltBase]),
- ?line ok = file:write_file(AltScript,
+ ?line ok = file:write_file(AltScript,
[Shebang, "\n",
Mode, "\n",
Flags, " -escript main archive_script_main2\n",
ArchiveBin]),
- ?line ok = file:write_file_info(AltScript, OrigFI),
+ ?line ok = file:write_file_info(AltScript, OrigFI),
?line run(PrivDir, AltBase ++ " -arg1 arg2 arg3",
[<<"main2:[\"-arg1\",\"arg2\",\"arg3\"]\n"
@@ -445,7 +461,7 @@ archive_script(Config) when is_list(Config) ->
"dummy:[{archive_script_dummy,[\"bar\"]}]\n"
"priv:{ok,<<\"Some private data...\\n\">>}\n"
"ExitCode:0">>]),
-
+
ok.
compile_app(TopDir, AppName) ->
@@ -482,6 +498,265 @@ epp(Config) when is_list(Config) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+create_and_extract(Config) when is_list(Config) ->
+ {NewFile, FileInfo,
+ EmuArg, Source,
+ _ErlBase, ErlCode,
+ _BeamBase, BeamCode,
+ ArchiveBin} =
+ prepare_creation("create_and_extract", Config),
+
+ Bodies =
+ [[{source, ErlCode}],
+ [{beam, BeamCode}],
+ [{archive, ArchiveBin}]],
+
+ %% Verify all combinations of scripts with shebangs
+ [verify_sections(NewFile, FileInfo, S ++ C ++ E ++ B) ||
+ S <- [[{shebang, default}],
+ [{shebang, "/usr/bin/env escript"}]],
+ C <- [[],
+ [{comment, undefined}],
+ [{comment, default}],
+ [{comment, "This is a nonsense comment"}]],
+ E <- [[],
+ [{emu_args, undefined}],
+ [{emu_args, EmuArg}]],
+ B <- [[{source, Source}] | Bodies]],
+
+ %% Verify all combinations of scripts without shebangs
+ [verify_sections(NewFile, FileInfo, S ++ C ++ E ++ B) ||
+ S <- [[], [{shebang, undefined}]],
+ C <- [[], [{comment, undefined}]],
+ E <- [[], [{emu_args, undefined}]],
+ B <- Bodies],
+
+ %% Verify the compile_source option
+ file:delete(NewFile),
+ ?line ok = escript:create(NewFile, [{source, Source}]),
+ ?line {ok, [_, _, _, {source, Source}]} = escript:extract(NewFile, []),
+ ?line {ok, [_, _, _, {source, BeamCode2}]} =
+ escript:extract(NewFile, [compile_source]),
+ verify_sections(NewFile, FileInfo,
+ [{shebang, default},
+ {comment, default},
+ {beam, BeamCode2}]),
+
+ file:delete(NewFile),
+ ok.
+
+prepare_creation(Base, Config) ->
+ %% Read the source
+ PrivDir = ?config(priv_dir, Config),
+ DataDir = ?config(data_dir, Config),
+ OrigFile = filename:join([DataDir,"emulator_flags"]),
+ ?line {ok, FileInfo} = file:read_file_info(OrigFile),
+ NewFile = filename:join([PrivDir, Base]),
+ ?line {ok, [{shebang, default},
+ {comment, _},
+ {emu_args, EmuArg},
+ {source, Source}]} =
+ escript:extract(OrigFile, []),
+
+ %% Compile the code
+ ErlFile = NewFile ++ ".erl",
+ ErlCode = list_to_binary(["\n-module(", Base, ").\n",
+ "-export([main/1]).\n\n",
+ Source, "\n\n"]),
+ ?line ok = file:write_file(ErlFile, ErlCode),
+
+ %% Compile the code
+ ?line {ok, _Mod, BeamCode} =
+ compile:file(ErlFile, [binary, debug_info]),
+
+ %% Create an archive
+ ?line {ok, {_, ArchiveBin}} =
+ zip:create("dummy_archive_name",
+ [{Base ++ ".erl", ErlCode},
+ {Base ++ ".beam", BeamCode}],
+ [{compress, []}, memory]),
+ {NewFile, FileInfo,
+ EmuArg, Source,
+ Base ++ ".erl", ErlCode,
+ Base ++ ".beam", BeamCode,
+ ArchiveBin}.
+
+verify_sections(File, FileInfo, Sections) ->
+ io:format("~p:verify_sections(\n\t~p,\n\t~p,\n\t~p).\n",
+ [?MODULE, File, FileInfo, Sections]),
+
+ %% Create
+ file:delete(File),
+ ?line ok = escript:create(File, Sections),
+ ?line ok = file:write_file_info(File, FileInfo),
+
+ %% Run
+ Dir = filename:absname(filename:dirname(File)),
+ Base = filename:basename(File),
+
+ HasArg = fun(Tag) ->
+ case lists:keysearch(Tag, 1, Sections) of
+ false -> false;
+ {value, {_, undefined}} -> false;
+ {value, _} -> true
+ end
+ end,
+ ExpectedMain = <<"main:[\"-arg1\",\"arg2\",\"arg3\"]\n">>,
+ ExpectedOutput =
+ case HasArg(emu_args) of
+ true ->
+ <<"nostick:[{nostick,[]}]\n"
+ "mnesia:[{mnesia,[\"dir\",\"a/directory\"]},{mnesia,[\"debug\",\"verbose\"]}]\n"
+ "ERL_FLAGS=false\n"
+ "unknown:[]\n"
+ "ExitCode:0">>;
+ false ->
+ <<"nostick:[]\nmnesia:[]\nERL_FLAGS=false\nunknown:[]\nExitCode:0">>
+ end,
+
+ InputArgs = Base ++ " -arg1 arg2 arg3",
+ Expected = <<ExpectedMain/binary, ExpectedOutput/binary>>,
+ case HasArg(shebang) of
+ true ->
+ ?line run(Dir, InputArgs, [Expected]);
+ false ->
+ ?line run_with_opts(Dir, [], InputArgs, [Expected])
+ end,
+
+ %% Verify
+ ?line {ok, Bin} = escript:create(binary, Sections),
+ ?line {ok, Read} = file:read_file(File),
+ ?line Bin = Read, % Assert
+
+ Normalized = normalize_sections(Sections),
+ ?line {ok, Extracted} = escript:extract(File, []),
+ io:format("Normalized; ~p\n", [Normalized]),
+ io:format("Extracted ; ~p\n", [Extracted]),
+ ?line Normalized = Extracted, % Assert
+ ok.
+
+normalize_sections(Sections) ->
+ AtomToTuple =
+ fun(Val) ->
+ if
+ is_atom(Val) -> {Val, default};
+ true -> Val
+ end
+ end,
+ case lists:map(AtomToTuple, [{K, V} || {K, V} <- Sections, V =/= undefined]) of
+ [{shebang, Shebang} | Rest] ->
+ [{shebang, Shebang} |
+ case Rest of
+ [{comment, Comment} | Rest2] ->
+ [{comment, Comment} |
+ case Rest2 of
+ [{emu_args, EmuArgs}, Body] ->
+ [{emu_args, EmuArgs}, Body];
+ [Body] ->
+ [{emu_args, undefined}, Body]
+ end
+ ];
+ [{emu_args, EmuArgs}, Body] ->
+ [{comment, undefined}, {emu_args, EmuArgs}, Body];
+ [Body] ->
+ [{comment, undefined}, {emu_args, undefined}, Body]
+ end
+ ];
+ [Body] ->
+ [{shebang, undefined}, {comment, undefined}, {emu_args, undefined}, Body]
+ end.
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+foldl(Config) when is_list(Config) ->
+ {NewFile, _FileInfo,
+ _EmuArg, _Source,
+ ErlBase, ErlCode,
+ BeamBase, _BeamCode,
+ ArchiveBin} =
+ prepare_creation("foldl", Config),
+
+ Collect = fun(Name, GetInfo, GetBin, Acc) ->
+ [{Name, GetInfo(), GetBin()} | Acc]
+ end,
+
+ %% Get line numbers and the file attribute right
+ SourceFile = NewFile ++ ".erl",
+ <<_:1/binary, ErlCode2/binary>> = ErlCode,
+ ?line ok = file:write_file(SourceFile, ErlCode2),
+ ?line {ok, _Mod, BeamCode} =
+ compile:file(SourceFile, [binary, debug_info]),
+
+ %% Verify source script
+ ?line ok = escript:create(SourceFile, [{source, ErlCode}]),
+ ?line {ok, [{".", _, BeamCode2}]}
+ = escript_foldl(Collect, [], SourceFile),
+
+ ?line {ok, Abstr} = beam_lib:chunks(BeamCode, [abstract_code]),
+ ?line {ok, Abstr2} = beam_lib:chunks(BeamCode2, [abstract_code]),
+ %% io:format("abstr1=~p\n", [Abstr]),
+ %% io:format("abstr2=~p\n", [Abstr2]),
+ ?line Abstr = Abstr2, % Assert
+
+ %% Verify beam script
+ ?line ok = escript:create(NewFile, [{beam, BeamCode}]),
+ ?line {ok, [{".", _, BeamCode}]}
+ = escript_foldl(Collect, [], NewFile),
+
+ %% Verify archive scripts
+ ?line ok = escript:create(NewFile, [{archive, ArchiveBin}]),
+ ?line {ok, [{BeamBase, #file_info{}, _},
+ {ErlBase, #file_info{}, _}]}
+ = escript_foldl(Collect, [], NewFile),
+
+ ArchiveFiles = [{ErlBase, ErlCode}, {BeamBase, BeamCode}],
+ ?line ok = escript:create(NewFile, [{archive, ArchiveFiles, []}]),
+ ?line {ok, [{BeamBase, _, _},
+ {ErlBase, _, _}]}
+ = escript_foldl(Collect, [], NewFile),
+
+ ok.
+
+escript_foldl(Fun, Acc, File) ->
+ code:ensure_loaded(zip),
+ case erlang:function_exported(zip, foldl, 3) of
+ true ->
+ emulate_escript_foldl(Fun, Acc, File);
+ false ->
+ escript:foldl(Fun, Acc, File)
+ end.
+
+emulate_escript_foldl(Fun, Acc, File) ->
+ case escript:extract(File, [compile_source]) of
+ {ok, [_Shebang, _Comment, _EmuArgs, Body]} ->
+ case Body of
+ {source, BeamCode} ->
+ GetInfo = fun() -> file:read_file_info(File) end,
+ GetBin = fun() -> BeamCode end,
+ {ok, Fun(".", GetInfo, GetBin, Acc)};
+ {beam, BeamCode} ->
+ GetInfo = fun() -> file:read_file_info(File) end,
+ GetBin = fun() -> BeamCode end,
+ {ok, Fun(".", GetInfo, GetBin, Acc)};
+ {archive, ArchiveBin} ->
+ zip:foldl(Fun, Acc, {File, ArchiveBin})
+ end;
+ {error, Reason} ->
+ {error, Reason}
+ end.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+overflow(Config) when is_list(Config) ->
+ Data = ?config(data_dir, Config),
+ Dir = filename:absname(Data), %Get rid of trailing slash.
+ ?line run(Dir, "arg_overflow",
+ [<<"ExitCode:0">>]),
+ ?line run(Dir, "linebuf_overflow",
+ [<<"ExitCode:0">>]),
+ ok.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
run(Dir, Cmd0, Expected0) ->
Expected = iolist_to_binary(expected_output(Expected0, Dir)),
Cmd = case os:type() of
@@ -490,7 +765,7 @@ run(Dir, Cmd0, Expected0) ->
end,
do_run(Dir, Cmd, Expected).
-run(Dir, Opts, Cmd0, Expected) ->
+run_with_opts(Dir, Opts, Cmd0, Expected) ->
Cmd = case os:type() of
{win32,_} -> "escript " ++ Opts ++ " " ++ filename:nativename(Dir) ++ "\\" ++ Cmd0;
_ -> "escript " ++ Opts ++ " " ++ Dir ++ "/" ++ Cmd0
@@ -533,8 +808,8 @@ expected_output([data_dir|T], Data) ->
[filename:nativename(Data)++Slash|expected_output(T, Data)];
expected_output([H|T], Data) ->
[H|expected_output(T, Data)];
-expected_output([], _) ->
+expected_output([], _) ->
[];
-expected_output(Bin, _) when is_binary(Bin) ->
+expected_output(Bin, _) when is_binary(Bin) ->
Bin.
diff --git a/lib/stdlib/test/escript_SUITE_data/arg_overflow b/lib/stdlib/test/escript_SUITE_data/arg_overflow
new file mode 100755
index 0000000000..dd5accc051
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/arg_overflow
@@ -0,0 +1,5 @@
+#! /usr/bin/env escript
+%% -*- erlang -*-
+%%!x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x x
+main(_) ->
+ halt(0).
diff --git a/lib/stdlib/test/escript_SUITE_data/linebuf_overflow b/lib/stdlib/test/escript_SUITE_data/linebuf_overflow
new file mode 100755
index 0000000000..33133c1ce9
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/linebuf_overflow
@@ -0,0 +1,5 @@
+#! /usr/bin/env escript
+%% -*- erlang -*-
+%%!xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
+main(_) ->
+ halt(0).
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 13c87ca005..9d348b5f1a 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2011. 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
@@ -18,24 +18,25 @@
%%
-module(ets_SUITE).
--export([all/1]).
--export([new/1,default/1,setbag/1,badnew/1,verybadnew/1,named/1,keypos2/1,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
+-export([default/1,setbag/1,badnew/1,verybadnew/1,named/1,keypos2/1,
privacy/1,privacy_owner/2]).
--export([insert/1,empty/1,badinsert/1]).
--export([lookup/1,time_lookup/1,badlookup/1,lookup_order/1]).
--export([delete/1,delete_elem/1,delete_tab/1,delete_large_tab/1,
+-export([empty/1,badinsert/1]).
+-export([time_lookup/1,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]).
-export([match_delete3/1]).
-export([firstnext/1,firstnext_concurrent/1]).
-export([slot/1]).
--export([match/1, match1/1, match2/1, match_object/1, match_object2/1]).
--export([misc/1, dups/1, misc1/1, safe_fixtable/1, info/1, tab2list/1]).
--export([files/1, tab2file/1, tab2file2/1, tab2file3/1, tabfile_ext1/1,
+-export([ match1/1, match2/1, match_object/1, match_object2/1]).
+-export([ dups/1, misc1/1, safe_fixtable/1, info/1, tab2list/1]).
+-export([ tab2file/1, tab2file2/1, tabfile_ext1/1,
tabfile_ext2/1, tabfile_ext3/1, tabfile_ext4/1]).
--export([heavy/1, heavy_lookup/1, heavy_lookup_element/1]).
--export([lookup_element/1, lookup_element_mult/1]).
--export([fold/1]).
+-export([ heavy_lookup/1, heavy_lookup_element/1, heavy_concurrent/1]).
+-export([ lookup_element_mult/1]).
+-export([]).
-export([foldl_ordered/1, foldr_ordered/1, foldl/1, foldr/1, fold_empty/1]).
-export([t_delete_object/1, t_init_table/1, t_whitebox/1,
t_delete_all_objects/1, t_insert_list/1, t_test_ms/1,
@@ -59,25 +60,26 @@
-export([otp_7665/1]).
-export([meta_wb/1]).
-export([grow_shrink/1, grow_pseudo_deleted/1, shrink_pseudo_deleted/1]).
--export([meta_smp/1,
+-export([
meta_lookup_unnamed_read/1, meta_lookup_unnamed_write/1,
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, otp_8166/1]).
+-export([smp_insert/1, smp_fixed_delete/1, smp_unfix_fix/1, smp_select_delete/1,
+ otp_8166/1, otp_8732/1]).
-export([exit_large_table_owner/1,
exit_many_large_table_owner/1,
exit_many_tables_owner/1,
exit_many_many_tables_owner/1]).
-export([write_concurrency/1, heir/1, give_away/1, setopts/1]).
--export([bad_table/1]).
+-export([bad_table/1, types/1]).
--export([init_per_testcase/2, fin_per_testcase/2, end_per_suite/1]).
+-export([init_per_testcase/2, end_per_testcase/2]).
%% Convenience for manual testing
-export([random_test/0]).
% internal exports
-export([dont_make_worse_sub/0, make_better_sub1/0, make_better_sub2/0]).
--export([t_repair_continuation_do/1, default_do/1, t_bucket_disappears_do/1,
+-export([t_repair_continuation_do/1, t_bucket_disappears_do/1,
select_fail_do/1, whitebox_1/1, whitebox_2/1, t_delete_all_objects_do/1,
t_delete_object_do/1, t_init_table_do/1, t_insert_list_do/1,
update_element_opts/1, update_element_opts/4, update_element/4, update_element_do/4,
@@ -89,10 +91,17 @@
match_delete_do/1, match_delete3_do/1, firstnext_do/1,
slot_do/1, match1_do/1, match2_do/1, match_object_do/1, match_object2_do/1,
misc1_do/1, safe_fixtable_do/1, info_do/1, dups_do/1, heavy_lookup_do/1,
- heavy_lookup_element_do/1, member_do/1, otp_5340_do/1, otp_7665_do/1, meta_wb_do/1
+ heavy_lookup_element_do/1, member_do/1, otp_5340_do/1, otp_7665_do/1, meta_wb_do/1,
+ do_heavy_concurrent/1, tab2file2_do/2, exit_large_table_owner_do/2,
+ types_do/1, sleeper/0, rpc_externals/0, memory_do/1,
+ ms_tracee_dummy/1, ms_tracee_dummy/2, ms_tracee_dummy/3, ms_tracee_dummy/4
]).
--include("test_server.hrl").
+-export([t_select_reverse/1]).
+
+-include_lib("test_server/include/test_server.hrl").
+
+-define(m(A,B), ?line assert_eq(A,B)).
init_per_testcase(Case, Config) ->
Seed = {S1,S2,S3} = random:seed0(), %now(),
@@ -103,44 +112,80 @@ init_per_testcase(Case, Config) ->
Dog=test_server:timetrap(test_server:minutes(20)),
[{watchdog, Dog}, {test_case, Case} | Config].
-fin_per_testcase(_Func, Config) ->
+end_per_testcase(_Func, Config) ->
Dog=?config(watchdog, Config),
wait_for_test_procs(true),
test_server:timetrap_cancel(Dog).
-
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [{group, new}, {group, insert}, {group, lookup},
+ {group, delete}, firstnext, firstnext_concurrent, slot,
+ {group, match}, t_match_spec_run,
+ {group, lookup_element}, {group, misc}, {group, files},
+ {group, heavy}, ordered, ordered_match,
+ interface_equality, fixtable_next, fixtable_insert,
+ rename, rename_unnamed, evil_rename, update_element,
+ update_counter, evil_update_counter, partly_bound,
+ match_heavy, {group, fold}, member, t_delete_object,
+ t_init_table, t_whitebox, t_delete_all_objects,
+ t_insert_list, t_test_ms, t_select_delete, t_ets_dets,
+ memory, t_select_reverse, t_bucket_disappears,
+ select_fail, t_insert_new, t_repair_continuation,
+ otp_5340, otp_6338, otp_6842_select_1000, otp_7665,
+ 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_delete,
+ otp_8166, exit_large_table_owner,
+ exit_many_large_table_owner, exit_many_tables_owner,
+ exit_many_many_tables_owner, write_concurrency, heir,
+ give_away, setopts, bad_table, types].
+
+groups() ->
+ [{new, [],
+ [default, setbag, badnew, verybadnew, named, keypos2,
+ privacy]},
+ {insert, [], [empty, badinsert]},
+ {lookup, [], [time_lookup, badlookup, lookup_order]},
+ {lookup_element, [], [lookup_element_mult]},
+ {delete, [],
+ [delete_elem, delete_tab, delete_large_tab,
+ delete_large_named_table, evil_delete, table_leak,
+ baddelete, match_delete, match_delete3]},
+ {match, [],
+ [match1, match2, match_object, match_object2]},
+ {misc, [],
+ [misc1, safe_fixtable, info, dups, tab2list]},
+ {files, [],
+ [tab2file, tab2file2, tabfile_ext1,
+ tabfile_ext2, tabfile_ext3, tabfile_ext4]},
+ {heavy, [],
+ [heavy_lookup, heavy_lookup_element, heavy_concurrent]},
+ {fold, [],
+ [foldl_ordered, foldr_ordered, foldl, foldr,
+ fold_empty]},
+ {meta_smp, [],
+ [meta_lookup_unnamed_read, meta_lookup_unnamed_write,
+ meta_lookup_named_read, meta_lookup_named_write,
+ meta_newdel_unnamed, meta_newdel_named]}].
+
+init_per_suite(Config) ->
+ Config.
end_per_suite(_Config) ->
stop_spawn_logger(),
catch erts_debug:set_internal_state(available_internal_state, false).
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
-all(suite) ->
- [
- new,insert,lookup,delete,firstnext,firstnext_concurrent,slot,match,
- t_match_spec_run,
- lookup_element, misc,files, heavy,
- ordered, ordered_match, interface_equality,
- fixtable_next, fixtable_insert, rename, rename_unnamed, evil_rename,
- update_element, update_counter, evil_update_counter, partly_bound,
- match_heavy, fold, member,
- t_delete_object, t_init_table, t_whitebox,
- t_delete_all_objects, t_insert_list, t_test_ms,
- t_select_delete, t_ets_dets, memory,
- t_bucket_disappears,
- select_fail,t_insert_new, t_repair_continuation, otp_5340, otp_6338,
- otp_6842_select_1000, otp_7665,
- meta_wb,
- grow_shrink, grow_pseudo_deleted, shrink_pseudo_deleted,
- meta_smp,
- smp_insert, smp_fixed_delete, smp_unfix_fix, 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, give_away, setopts,
- bad_table
- ].
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -153,7 +198,7 @@ t_bucket_disappears(Config) when is_list(Config) ->
t_bucket_disappears_do(Opts) ->
?line EtsMem = etsmem(),
- ?line ets:new(abcd, [named_table, public, {keypos, 2} | Opts]),
+ ?line ets_new(abcd, [named_table, public, {keypos, 2} | Opts]),
?line ets:insert(abcd, {abcd,1,2}),
?line ets:insert(abcd, {abcd,2,2}),
?line ets:insert(abcd, {abcd,3,2}),
@@ -171,29 +216,180 @@ t_match_spec_run(suite) ->
t_match_spec_run(doc) ->
["Check ets:match_spec_run/2."];
t_match_spec_run(Config) when is_list(Config) ->
+ init_externals(),
?line EtsMem = etsmem(),
- ?line [2,3] = ets:match_spec_run([{1},{2},{3}],
- ets:match_spec_compile(
- [{{'$1'},[{'>','$1',1}],['$1']}])),
+
+ t_match_spec_run_test([{1},{2},{3}],
+ [{{'$1'},[{'>','$1',1}],['$1']}],
+ [2,3]),
+
?line Huge = [{X} || X <- lists:seq(1,2500)],
?line L = lists:seq(2476,2500),
- ?line L = ets:match_spec_run(Huge,
- ets:match_spec_compile(
- [{{'$1'},[{'>','$1',2475}],['$1']}])),
+ t_match_spec_run_test(Huge, [{{'$1'},[{'>','$1',2475}],['$1']}], L),
+
?line L2 = [{X*16#FFFFFFF} || X <- L],
- ?line L2 = ets:match_spec_run(Huge,
- ets:match_spec_compile(
- [{{'$1'},
- [{'>','$1',2475}],
- [{{{'*','$1',16#FFFFFFF}}}]}])),
- ?line [500,1000,1500,2000,2500] =
- ets:match_spec_run(Huge,
- ets:match_spec_compile(
- [{{'$1'},
- [{'=:=',{'rem','$1',500},0}],
- ['$1']}])),
+ t_match_spec_run_test(Huge,
+ [{{'$1'}, [{'>','$1',2475}], [{{{'*','$1',16#FFFFFFF}}}]}],
+ L2),
+
+ t_match_spec_run_test(Huge, [{{'$1'}, [{'=:=',{'rem','$1',500},0}], ['$1']}],
+ [500,1000,1500,2000,2500]),
+
+ %% More matching fun with several match clauses and guards,
+ %% applied to a variety of terms.
+ Fun = fun(Term) ->
+ CTerm = {const, Term},
+
+ N_List = [{Term, "0", "v-element"},
+ {"=hidden_node", "0", Term},
+ {"0", Term, Term},
+ {"something", Term, "something else"},
+ {"guard and res", Term, 872346},
+ {Term, {'and',Term,'again'}, 3.14},
+ {Term, {'and',Term,'again'}, "m&g"},
+ {Term, {'and',Term,'again'}, "m&g&r"},
+ {[{second,Term}, 'and', "tail"], Term, ['and',"tail"]}],
+
+ N_MS = [{{'$1','$2','$3'},
+ [{'=:=','$1',CTerm}, {'=:=','$2',{const,"0"}}],
+ [{{"Guard only for $1",'$3'}}]},
+
+ {{'$3','$1','$4'},
+ [{'=:=','$3',"=hidden_node"}, {'=:=','$1',{const,"0"}}],
+ [{{"Result only for $4",'$4'}}]},
+
+ {{'$2','$1','$1'},
+ [{'=:=','$2',{const,"0"}}],
+ [{{"Match only for $1",'$2'}}]},
+
+ {{'$2',Term,['$3'|'_']},
+ [{is_list,'$2'},{'=:=','$3',$s}],
+ [{{"Matching term",'$2'}}]},
+
+ {{'$1','$2',872346},
+ [{'=:=','$2',CTerm}, {is_list,'$1'}],
+ [{{"Guard and result",'$2'}}]},
+
+ {{'$1', {'and','$1','again'}, '$2'},
+ [{is_float,'$2'}],
+ [{{"Match and result",'$1'}}]},
+
+ {{'$1', {'and','$1','again'}, '$2'},
+ [{'=:=','$1',CTerm}, {'=:=', '$2', "m&g"}],
+ [{{"Match and guard",'$2'}}]},
+
+ {{'$1', {'and','$1','again'}, "m&g&r"},
+ [{'=:=','$1',CTerm}],
+ [{{"Match, guard and result",'$1'}}]},
+
+ {{'$1', '$2', '$3'},
+ [{'=:=','$1',[{{second,'$2'}} | '$3']}],
+ [{{"Building guard"}}]}
+ ],
+
+ N_Result = [{"Guard only for $1", "v-element"},
+ {"Result only for $4", Term},
+ {"Match only for $1", "0"},
+ {"Matching term","something"},
+ {"Guard and result",Term},
+ {"Match and result",Term},
+ {"Match and guard","m&g"},
+ {"Match, guard and result",Term},
+ {"Building guard"}],
+
+ F = fun(N_MS_Perm) ->
+ t_match_spec_run_test(N_List, N_MS_Perm, N_Result)
+ end,
+ repeat_for_permutations(F, N_MS)
+ end,
+
+ test_terms(Fun, skip_refc_check),
+
?line verify_etsmem(EtsMem).
+t_match_spec_run_test(List, MS, Result) ->
+
+ %%io:format("ms = ~p\n",[MS]),
+
+ ?m(Result, ets:match_spec_run(List, ets:match_spec_compile(MS))),
+
+ %% Check that ets:select agree
+ Tab = ets:new(xxx, [bag]),
+ ets:insert(Tab, List),
+ SRes = lists:sort(Result),
+ ?m(SRes, lists:sort(ets:select(Tab, MS))),
+ ets:delete(Tab),
+
+ %% Check that tracing agree
+ Self = self(),
+ {Tracee, MonRef} = spawn_monitor(fun() -> ms_tracee(Self, List) end),
+ receive {Tracee, ready} -> ok end,
+
+ MST = lists:map(fun(Clause) -> ms_clause_ets_to_trace(Clause) end, MS),
+
+ %%io:format("MS = ~p\nMST= ~p\n",[MS,MST]),
+
+ erlang:trace_pattern({?MODULE,ms_tracee_dummy,'_'}, MST , [local]),
+ erlang:trace(Tracee, true, [call]),
+ Tracee ! start,
+ TRes = ms_tracer_collect(Tracee, MonRef, []),
+ %erlang:trace(Tracee, false, [call]),
+ %Tracee ! stop,
+ case TRes of
+ SRes -> ok;
+ _ ->
+ io:format("TRACE MATCH FAILED\n"),
+ io:format("Input = ~p\nMST = ~p\nExpected = ~p\nGot = ~p\n", [List, MST, SRes, TRes]),
+ ?t:fail("TRACE MATCH FAILED")
+ end,
+ ok.
+
+
+
+ms_tracer_collect(Tracee, Ref, Acc) ->
+ receive
+ {trace, Tracee, call, _Args, [Msg]} ->
+ %io:format("trace Args=~p Msg=~p\n", [_Args, Msg]),
+ ms_tracer_collect(Tracee, Ref, [Msg | Acc]);
+
+ {'DOWN', Ref, process, Tracee, _} ->
+ %io:format("monitor DOWN for ~p\n", [Tracee]),
+ TDRef = erlang:trace_delivered(Tracee),
+ ms_tracer_collect(Tracee, TDRef, Acc);
+
+ {trace_delivered, Tracee, Ref} ->
+ %%io:format("trace delivered for ~p\n", [Tracee]),
+ lists:sort(Acc);
+
+ Other ->
+ io:format("Unexpected message = ~p\n", [Other]),
+ ?t:fail("Unexpected tracer msg")
+ end.
+
+
+ms_tracee(Parent, CallArgList) ->
+ %io:format("ms_tracee ~p started with ArgList = ~p\n", [self(), CallArgList]),
+ Parent ! {self(), ready},
+ receive start -> ok end,
+ lists:foreach(fun(Args) ->
+ erlang:apply(?MODULE, ms_tracee_dummy, tuple_to_list(Args))
+ end, CallArgList).
+ %%receive stop -> ok end.
+
+
+
+ms_tracee_dummy(_) -> ok.
+ms_tracee_dummy(_,_) -> ok.
+ms_tracee_dummy(_,_,_) -> ok.
+ms_tracee_dummy(_,_,_,_) -> ok.
+
+ms_clause_ets_to_trace({Head, Guard, Body}) ->
+ {tuple_to_list(Head), Guard, [{message, Body}]}.
+
+assert_eq(A,A) -> ok;
+assert_eq(A,B) ->
+ io:format("FAILED MATCH:\n~p\n =/=\n~p\n",[A,B]),
+ ?t:fail("assert_eq failed").
t_repair_continuation(suite) ->
@@ -209,7 +405,7 @@ t_repair_continuation_do(Opts) ->
?line MS = [{'_',[],[true]}],
?line MS2 = [{{{'$1','_'},'_'},[],['$1']}],
(fun() ->
- ?line T = ets:new(x,[ordered_set|Opts]),
+ ?line T = ets_new(x,[ordered_set|Opts]),
?line F = fun(0,_)->ok;(N,F) -> ets:insert(T,{N,N}), F(N-1,F) end,
?line F(1000,F),
?line {_,C} = ets:select(T,MS,5),
@@ -221,7 +417,7 @@ t_repair_continuation_do(Opts) ->
?line true = ets:delete(T)
end)(),
(fun() ->
- ?line T = ets:new(x,[ordered_set|Opts]),
+ ?line T = ets_new(x,[ordered_set|Opts]),
?line F = fun(0,_)->ok;(N,F) -> ets:insert(T,{N,N}), F(N-1,F) end,
?line F(1000,F),
?line {_,C} = ets:select(T,MS,1001),
@@ -233,7 +429,7 @@ t_repair_continuation_do(Opts) ->
end)(),
(fun() ->
- ?line T = ets:new(x,[ordered_set|Opts]),
+ ?line T = ets_new(x,[ordered_set|Opts]),
?line F = fun(0,_)->ok;(N,F) ->
ets:insert(T,{integer_to_list(N),N}),
F(N-1,F)
@@ -248,7 +444,7 @@ t_repair_continuation_do(Opts) ->
?line true = ets:delete(T)
end)(),
(fun() ->
- ?line T = ets:new(x,[ordered_set|Opts]),
+ ?line T = ets_new(x,[ordered_set|Opts]),
?line F = fun(0,_)->ok;(N,F) ->
ets:insert(T,{{integer_to_list(N),N},N}),
F(N-1,F)
@@ -264,7 +460,7 @@ t_repair_continuation_do(Opts) ->
end)(),
(fun() ->
- ?line T = ets:new(x,[set|Opts]),
+ ?line T = ets_new(x,[set|Opts]),
?line F = fun(0,_)->ok;(N,F) ->
ets:insert(T,{N,N}),
F(N-1,F)
@@ -279,7 +475,7 @@ t_repair_continuation_do(Opts) ->
?line true = ets:delete(T)
end)(),
(fun() ->
- ?line T = ets:new(x,[set|Opts]),
+ ?line T = ets_new(x,[set|Opts]),
?line F = fun(0,_)->ok;(N,F) ->
ets:insert(T,{integer_to_list(N),N}),
F(N-1,F)
@@ -294,7 +490,7 @@ t_repair_continuation_do(Opts) ->
?line true = ets:delete(T)
end)(),
(fun() ->
- ?line T = ets:new(x,[bag|Opts]),
+ ?line T = ets_new(x,[bag|Opts]),
?line F = fun(0,_)->ok;(N,F) ->
ets:insert(T,{integer_to_list(N),N}),
F(N-1,F)
@@ -309,7 +505,7 @@ t_repair_continuation_do(Opts) ->
?line true = ets:delete(T)
end)(),
(fun() ->
- ?line T = ets:new(x,[duplicate_bag|Opts]),
+ ?line T = ets_new(x,[duplicate_bag|Opts]),
?line F = fun(0,_)->ok;(N,F) ->
ets:insert(T,{integer_to_list(N),N}),
F(N-1,F)
@@ -327,21 +523,22 @@ t_repair_continuation_do(Opts) ->
?line true = ets:is_compiled_ms(ets:match_spec_compile(MS)),
?line verify_etsmem(EtsMem).
-new(suite) -> [default,setbag,badnew,verybadnew,named,keypos2,privacy].
default(doc) ->
- ["Test case to check that a new ets table is defined as a `set' and "
- "`protected'"];
+ ["Check correct default vaules of a new ets table"];
default(suite) -> [];
default(Config) when is_list(Config) ->
%% Default should be set,protected
- repeat_for_opts(default_do).
-
-default_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Def = ets:new(def,Opts),
+ ?line Def = ets_new(def,[]),
?line set = ets:info(Def,type),
?line protected = ets:info(Def,protection),
+ Compressed = erlang:system_info(ets_always_compress),
+ ?line Compressed = ets:info(Def,compressed),
+ Self = self(),
+ ?line Self = ets:info(Def,owner),
+ ?line none = ets:info(Def, heir),
+ ?line false = ets:info(Def,named_table),
?line ets:delete(Def),
?line verify_etsmem(EtsMem).
@@ -355,7 +552,7 @@ select_fail(Config) when is_list(Config) ->
?line verify_etsmem(EtsMem).
select_fail_do(Opts) ->
- ?line T = ets:new(x,Opts),
+ ?line T = ets_new(x,Opts),
?line ets:insert(T,{a,a}),
?line case (catch
ets:select(T,[{{a,'_'},[],[{snuffla}]}])) of
@@ -378,20 +575,27 @@ select_fail_do(Opts) ->
-define(S(T),ets:info(T,memory)).
-define(TAB_STRUCT_SZ, erts_debug:get_internal_state('DbTable_words')).
--define(NORMAL_TAB_STRUCT_SZ, 26). %% SunOS5.8, 32-bit, non smp, private heap
+%%-define(NORMAL_TAB_STRUCT_SZ, 26). %% SunOS5.8, 32-bit, non smp, private heap
%%
%% The hardcoded expected memory sizes (in words) are the ones we expect on:
%% SunOS5.8, 32-bit, non smp, private heap
%%
-memory(doc) ->
- ["Whitebox test of ets:info(X,memory)"];
-memory(suite) ->
- [];
+memory(doc) -> ["Whitebox test of ets:info(X,memory)"];
+memory(suite) -> [];
memory(Config) when is_list(Config) ->
?line erts_debug:set_internal_state(available_internal_state, true),
?line ok = chk_normal_tab_struct_size(),
- ?line L = [T1,T2,T3,T4] = fill_sets_int(1000),
- ?line XRes1 = adjust_xmem(L, {16862,16072,16072,16078}),
+ repeat_for_opts(memory_do,[compressed]),
+ ?line catch erts_debug:set_internal_state(available_internal_state, false).
+
+memory_do(Opts) ->
+ ?line L = [T1,T2,T3,T4] = fill_sets_int(1000,Opts),
+ XR1 = case mem_mode(T1) of
+ {normal,_} -> {13836,13046,13046,13052}; %{13862,13072,13072,13078};
+ {compressed,4} -> {11041,10251,10251,10252}; %{11067,10277,10277,10278};
+ {compressed,8} -> {10050,9260,9260,9260} %{10076,9286,9286,9286}
+ end,
+ ?line XRes1 = adjust_xmem(L, XR1),
?line Res1 = {?S(T1),?S(T2),?S(T3),?S(T4)},
?line lists:foreach(fun(T) ->
Before = ets:info(T,size),
@@ -402,7 +606,12 @@ memory(Config) when is_list(Config) ->
[Key, ets:info(T,type), Before, ets:info(T,size), Objs])
end,
L),
- ?line XRes2 = adjust_xmem(L, {16849,16060,16048,16054}),
+ XR2 = case mem_mode(T1) of
+ {normal,_} -> {13826,13037,13028,13034}; %{13852,13063,13054,13060};
+ {compressed,4} -> {11031,10242,10233,10234}; %{11057,10268,10259,10260};
+ {compressed,8} -> {10040,9251,9242,9242} %10066,9277,9268,9268}
+ end,
+ ?line XRes2 = adjust_xmem(L, XR2),
?line Res2 = {?S(T1),?S(T2),?S(T3),?S(T4)},
?line lists:foreach(fun(T) ->
Before = ets:info(T,size),
@@ -413,13 +622,18 @@ memory(Config) when is_list(Config) ->
[Key, ets:info(T,type), Before, ets:info(T,size), Objs])
end,
L),
- ?line XRes3 = adjust_xmem(L, {16836,16048,16024,16030}),
+ XR3 = case mem_mode(T1) of
+ {normal,_} -> {13816,13028,13010,13016}; %{13842,13054,13036,13042};
+ {compressed,4} -> {11021,10233,10215,10216}; %{11047,10259,10241,10242};
+ {compressed,8} -> {10030,9242,9224,9224} %{10056,9268,9250,9250}
+ end,
+ ?line XRes3 = adjust_xmem(L, XR3),
?line Res3 = {?S(T1),?S(T2),?S(T3),?S(T4)},
?line lists:foreach(fun(T) ->
?line ets:delete_all_objects(T)
end,
L),
- ?line XRes4 = adjust_xmem(L, {76,286,286,286}),
+ ?line XRes4 = adjust_xmem(L, {50,260,260,260}), %{76,286,286,286}),
?line Res4 = {?S(T1),?S(T2),?S(T3),?S(T4)},
lists:foreach(fun(T) ->
?line ets:delete(T)
@@ -430,9 +644,9 @@ memory(Config) when is_list(Config) ->
?line ets:select_delete(T,[{'_',[],[true]}])
end,
L2),
- ?line XRes5 = adjust_xmem(L2, {76,286,286,286}),
+ ?line XRes5 = adjust_xmem(L2, {50,260,260,260}), %{76,286,286,286}),
?line Res5 = {?S(T11),?S(T12),?S(T13),?S(T14)},
- ?line ?t:format("XRes1 = ~p~n"
+ ?line io:format("XRes1 = ~p~n"
" Res1 = ~p~n~n"
"XRes2 = ~p~n"
" Res2 = ~p~n~n"
@@ -452,9 +666,15 @@ memory(Config) when is_list(Config) ->
?line XRes3 = Res3,
?line XRes4 = Res4,
?line XRes5 = Res5,
- ?line catch erts_debug:set_internal_state(available_internal_state, false),
?line ok.
+mem_mode(T) ->
+ {case ets:info(T,compressed) of
+ true -> compressed;
+ false -> normal
+ end,
+ erlang:system_info(wordsize)}.
+
chk_normal_tab_struct_size() ->
?line System = {os:type(),
os:version(),
@@ -462,36 +682,58 @@ chk_normal_tab_struct_size() ->
erlang:system_info(smp_support),
erlang:system_info(heap_type)},
?line ?t:format("System = ~p~n", [System]),
- ?line ?t:format("?NORMAL_TAB_STRUCT_SZ=~p~n", [?NORMAL_TAB_STRUCT_SZ]),
+ %%?line ?t:format("?NORMAL_TAB_STRUCT_SZ=~p~n", [?NORMAL_TAB_STRUCT_SZ]),
?line ?t:format("?TAB_STRUCT_SZ=~p~n", [?TAB_STRUCT_SZ]),
- ?line case System of
- {{unix, sunos}, {5, 8, 0}, 4, false, private} ->
- ?line ?NORMAL_TAB_STRUCT_SZ = ?TAB_STRUCT_SZ,
- ?line ok;
- _ ->
- ?line ok
- end.
-
-adjust_xmem([T1,T2,T3,T4], {A0,B0,C0,D0} = Mem0) ->
+ ok.
+% ?line case System of
+% {{unix, sunos}, {5, 8, 0}, 4, false, private} ->
+% ?line ?NORMAL_TAB_STRUCT_SZ = ?TAB_STRUCT_SZ,
+% ?line ok;
+% _ ->
+% ?line ok
+% end.
+
+-define(DB_TREE_STACK_NEED,50). % The static stack for a tree, in halfword pointers are two internal words
+ % so the stack gets twice as big
+-define(DB_HASH_SIZEOF_EXTSEG,260). % The segment size in words, in halfword this will be twice as large.
+
+adjust_xmem([T1,T2,T3,T4], {A0,B0,C0,D0} = _Mem0) ->
%% Adjust for 64-bit, smp, and os:
%% Table struct size may differ.
- Mem1 = case ?TAB_STRUCT_SZ of
- ?NORMAL_TAB_STRUCT_SZ ->
- Mem0;
- TabStructSz ->
- TabDiff = TabStructSz - ?NORMAL_TAB_STRUCT_SZ,
- {A0+TabDiff, B0+TabDiff, C0+TabDiff, D0+TabDiff}
- end,
+
+% Mem1 = case ?TAB_STRUCT_SZ of
+% ?NORMAL_TAB_STRUCT_SZ ->
+% Mem0;
+% TabStructSz ->
+% TabDiff = TabStructSz - ?NORMAL_TAB_STRUCT_SZ,
+% {A0+TabDiff, B0+TabDiff, C0+TabDiff, D0+TabDiff}
+% end,
+
+ TabDiff = ?TAB_STRUCT_SZ,
+ Mem1 = {A0+TabDiff, B0+TabDiff, C0+TabDiff, D0+TabDiff},
+
+ Mem2 = case {erlang:system_info({wordsize,internal}),erlang:system_info({wordsize,external})} of
+ %% Halfword, corrections for regular pointers occupying two internal words.
+ {4,8} ->
+ {A1,B1,C1,D1} = Mem1,
+ {A1+4*ets:info(T1, size)+?DB_TREE_STACK_NEED,
+ B1+3*ets:info(T2, size)+?DB_HASH_SIZEOF_EXTSEG,
+ C1+3*ets:info(T3, size)+?DB_HASH_SIZEOF_EXTSEG,
+ D1+3*ets:info(T4, size)+?DB_HASH_SIZEOF_EXTSEG};
+ _ ->
+ Mem1
+ end,
+
%% Adjust for hybrid and shared heaps:
%% Each record is one word smaller.
- Mem2 = case erlang:system_info(heap_type) of
- private ->
- Mem1;
- _ ->
- {A1,B1,C1,D1} = Mem1,
- {A1-ets:info(T1, size),B1-ets:info(T2, size),
- C1-ets:info(T3, size),D1-ets:info(T4, size)}
- end,
+ %%Mem2 = case erlang:system_info(heap_type) of
+ %% private ->
+ %% Mem1;
+ %% _ ->
+ %% {A1,B1,C1,D1} = Mem1,
+ %% {A1-ets:info(T1, size),B1-ets:info(T2, size),
+ %% C1-ets:info(T3, size),D1-ets:info(T4, size)}
+ %% end,
%%{Mem2,{ets:info(T1,stats),ets:info(T2,stats),ets:info(T3,stats),ets:info(T4,stats)}}.
Mem2.
@@ -510,7 +752,7 @@ t_whitebox(Config) when is_list(Config) ->
?line verify_etsmem(EtsMem).
whitebox_1(Opts) ->
- ?line T=ets:new(x,[bag | Opts]),
+ ?line T=ets_new(x,[bag | Opts]),
?line ets:insert(T,[{du,glade},{ta,en}]),
?line ets:insert(T,[{hej,hopp2},{du,glade2},{ta,en2}]),
?line {_,C}=ets:match(T,{ta,'$1'},1),
@@ -520,8 +762,8 @@ whitebox_1(Opts) ->
ok.
whitebox_2(Opts) ->
- ?line T=ets:new(x,[ordered_set, {keypos,2} | Opts]),
- ?line T2=ets:new(x,[set, {keypos,2}| Opts]),
+ ?line T=ets_new(x,[ordered_set, {keypos,2} | Opts]),
+ ?line T2=ets_new(x,[set, {keypos,2}| Opts]),
?line 0 = ets:select_delete(T,[{{hej},[],[true]}]),
?line 0 = ets:select_delete(T,[{{hej,hopp},[],[true]}]),
?line 0 = ets:select_delete(T2,[{{hej},[],[true]}]),
@@ -543,7 +785,7 @@ t_ets_dets(Config, Opts) ->
?line (catch file:delete(Fname)),
?line {ok,DTab} = dets:open_file(testdets_1,
[{file, Fname}]),
- ?line ETab = ets:new(x,Opts),
+ ?line ETab = ets_new(x,Opts),
?line filltabint(ETab,3000),
?line DTab = ets:to_dets(ETab,DTab),
?line ets:delete_all_objects(ETab),
@@ -555,7 +797,7 @@ t_ets_dets(Config, Opts) ->
(catch ets:to_dets(ETab,DTab)),
?line {'EXIT',{badarg,[{ets,from_dets,[ETab,DTab]}|_]}} =
(catch ets:from_dets(ETab,DTab)),
- ?line ETab2 = ets:new(x,Opts),
+ ?line ETab2 = ets_new(x,Opts),
?line filltabint(ETab2,3000),
?line dets:close(DTab),
?line {'EXIT',{badarg,[{ets,to_dets,[ETab2,DTab]}|_]}} =
@@ -576,7 +818,7 @@ t_delete_all_objects(Config) when is_list(Config) ->
?line verify_etsmem(EtsMem).
t_delete_all_objects_do(Opts) ->
- ?line T=ets:new(x,Opts),
+ ?line T=ets_new(x,Opts),
?line filltabint(T,4000),
?line O=ets:first(T),
?line ets:next(T,O),
@@ -605,7 +847,7 @@ t_delete_object(Config) when is_list(Config) ->
?line verify_etsmem(EtsMem).
t_delete_object_do(Opts) ->
- ?line T = ets:new(x,Opts),
+ ?line T = ets_new(x,Opts),
?line filltabint(T,4000),
?line del_one_by_one_set(T,1,4001),
?line filltabint(T,4000),
@@ -622,19 +864,19 @@ t_delete_object_do(Opts) ->
?line 3999 = ets:info(T,size),
?line 0 = ets:info(T,kept_objects),
?line ets:delete(T),
- ?line T1 = ets:new(x,[ordered_set | Opts]),
+ ?line T1 = ets_new(x,[ordered_set | Opts]),
?line filltabint(T1,4000),
?line del_one_by_one_set(T1,1,4001),
?line filltabint(T1,4000),
?line del_one_by_one_set(T1,4000,0),
?line ets:delete(T1),
- ?line T2 = ets:new(x,[bag | Opts]),
+ ?line T2 = ets_new(x,[bag | Opts]),
?line filltabint2(T2,4000),
?line del_one_by_one_bag(T2,1,4001),
?line filltabint2(T2,4000),
?line del_one_by_one_bag(T2,4000,0),
?line ets:delete(T2),
- ?line T3 = ets:new(x,[duplicate_bag | Opts]),
+ ?line T3 = ets_new(x,[duplicate_bag | Opts]),
?line filltabint3(T3,4000),
?line del_one_by_one_dbag_1(T3,1,4001),
?line filltabint3(T3,4000),
@@ -681,7 +923,7 @@ t_init_table(Config) when is_list(Config)->
?line verify_etsmem(EtsMem).
t_init_table_do(Opts) ->
- ?line T = ets:new(x,[duplicate_bag | Opts]),
+ ?line T = ets_new(x,[duplicate_bag | Opts]),
?line filltabint(T,4000),
?line ets:init_table(T, make_init_fun(1)),
?line del_one_by_one_dbag_1(T,4000,0),
@@ -763,7 +1005,7 @@ t_insert_list(Config) when is_list(Config) ->
?line verify_etsmem(EtsMem).
t_insert_list_do(Opts) ->
- ?line T = ets:new(x,[duplicate_bag | Opts]),
+ ?line T = ets_new(x,[duplicate_bag | Opts]),
?line do_fill_dbag_using_lists(T,4000),
?line del_one_by_one_dbag_2(T,4000,0),
?line ets:delete(T).
@@ -786,6 +1028,67 @@ t_test_ms(Config) when is_list(Config) ->
?line true = (if is_list(String) -> true; true -> false end),
?line verify_etsmem(EtsMem).
+t_select_reverse(doc) ->
+ ["Test the select reverse BIF's"];
+t_select_reverse(suite) ->
+ [];
+t_select_reverse(Config) when is_list(Config) ->
+ ?line Table = ets_new(xxx, [ordered_set]),
+ ?line filltabint(Table,1000),
+ ?line A = lists:reverse(ets:select(Table,[{{'$1', '_'},
+ [{'>',
+ {'rem',
+ '$1', 5},
+ 2}],
+ ['$_']}])),
+ ?line A = ets:select_reverse(Table,[{{'$1', '_'},
+ [{'>',
+ {'rem',
+ '$1', 5},
+ 2}],
+ ['$_']}]),
+ ?line A = reverse_chunked(Table,[{{'$1', '_'},
+ [{'>',
+ {'rem',
+ '$1', 5},
+ 2}],
+ ['$_']}],3),
+ % A set/bag/duplicate_bag should get the same result regardless
+ % of select or select_reverse
+ ?line Table2 = ets_new(xxx, [set]),
+ ?line filltabint(Table2,1000),
+ ?line Table3 = ets_new(xxx, [bag]),
+ ?line filltabint(Table3,1000),
+ ?line Table4 = ets_new(xxx, [duplicate_bag]),
+ ?line filltabint(Table4,1000),
+ ?line lists:map(fun(Tab) ->
+ B = ets:select(Tab,[{{'$1', '_'},
+ [{'>',
+ {'rem',
+ '$1', 5},
+ 2}],
+ ['$_']}]),
+ B = ets:select_reverse(Tab,[{{'$1', '_'},
+ [{'>',
+ {'rem',
+ '$1', 5},
+ 2}],
+ ['$_']}])
+ end,[Table2, Table3, Table4]),
+ ok.
+
+
+
+reverse_chunked(T,MS,N) ->
+ do_reverse_chunked(ets:select_reverse(T,MS,N),[]).
+
+do_reverse_chunked('$end_of_table',Acc) ->
+ lists:reverse(Acc);
+do_reverse_chunked({L,C},Acc) ->
+ NewAcc = lists:reverse(L)++Acc,
+ do_reverse_chunked(ets:select_reverse(C), NewAcc).
+
+
t_select_delete(doc) ->
["Test the ets:select_delete/2 and ets:select_count/2 BIF's"];
t_select_delete(suite) ->
@@ -1064,8 +1367,8 @@ random_test() ->
do_random_test() ->
?line EtsMem = etsmem(),
- ?line OrdSet = ets:new(xxx,[ordered_set]),
- ?line Set = ets:new(xxx,[]),
+ ?line OrdSet = ets_new(xxx,[ordered_set]),
+ ?line Set = ets_new(xxx,[]),
?line do_n_times(fun() ->
?line Key = create_random_string(25),
?line Value = create_random_tuple(25),
@@ -1269,8 +1572,8 @@ update_element_opts(Opts) ->
update_element_opts(Tuple,KeyPos,UpdPos,Opts) ->
- Set = ets:new(set,[{keypos,KeyPos} | Opts]),
- OrdSet = ets:new(ordered_set,[ordered_set,{keypos,KeyPos} | Opts]),
+ Set = ets_new(set,[{keypos,KeyPos} | Opts]),
+ OrdSet = ets_new(ordered_set,[ordered_set,{keypos,KeyPos} | Opts]),
update_element(Set,Tuple,KeyPos,UpdPos),
update_element(OrdSet,Tuple,KeyPos,UpdPos),
true = ets:delete(Set),
@@ -1278,7 +1581,7 @@ update_element_opts(Tuple,KeyPos,UpdPos,Opts) ->
ok.
update_element(T,Tuple,KeyPos,UpdPos) ->
- KeyList = [Key || Key <- lists:seq(1,100)],
+ KeyList = [17,"seventeen",<<"seventeen">>,{17},list_to_binary(lists:seq(1,100)),make_ref(), self()],
lists:foreach(fun(Key) ->
TupleWithKey = setelement(KeyPos,Tuple,Key),
update_element_do(T,TupleWithKey,Key,UpdPos)
@@ -1292,6 +1595,8 @@ update_element_do(Tab,Tuple,Key,UpdPos) ->
% This will try all combinations of {fromValue,toValue}
%
% IMPORTANT: size(Values) must be a prime number for this to work!!!
+
+ %io:format("update_element_do for key=~p\n",[Key]),
Big32 = 16#12345678,
Big64 = 16#123456789abcdef0,
Values = { 623, -27, 0, Big32, -Big32, Big64, -Big64, Big32*Big32,
@@ -1312,14 +1617,6 @@ update_element_do(Tab,Tuple,Key,UpdPos) ->
(ToIx, [], Pos, _Rand, _MeF) ->
{Pos, element(ToIx+1,Values)} % single {pos,value} arg
end,
-
- NewTupleF = fun({Pos,Val}, Tpl, _MeF) ->
- setelement(Pos, Tpl, Val);
- ([{Pos,Val} | Tail], Tpl, MeF) ->
- MeF(Tail,setelement(Pos, Tpl, Val),MeF);
- ([], Tpl, _MeF) ->
- Tpl
- end,
UpdateF = fun(ToIx,Rand) ->
PosValArg = PosValArgF(ToIx,[],UpdPos,Rand,PosValArgF),
@@ -1327,7 +1624,7 @@ update_element_do(Tab,Tuple,Key,UpdPos) ->
ArgHash = erlang:phash2({Tab,Key,PosValArg}),
?line true = ets:update_element(Tab, Key, PosValArg),
?line ArgHash = erlang:phash2({Tab,Key,PosValArg}),
- NewTuple = NewTupleF(PosValArg,Tuple,NewTupleF),
+ NewTuple = update_tuple(PosValArg,Tuple),
?line [NewTuple] = ets:lookup(Tab,Key)
end,
@@ -1355,9 +1652,18 @@ update_element_do(Tab,Tuple,Key,UpdPos) ->
?line Checksum = (Length-1)*Length*(Length+1) div 2, % if Length is a prime
ok.
+update_tuple({Pos,Val}, Tpl) ->
+ setelement(Pos, Tpl, Val);
+update_tuple([{Pos,Val} | Tail], Tpl) ->
+ update_tuple(Tail,setelement(Pos, Tpl, Val));
+update_tuple([], Tpl) ->
+ Tpl.
+
+
+
update_element_neg(Opts) ->
- Set = ets:new(set,Opts),
- OrdSet = ets:new(ordered_set,[ordered_set | Opts]),
+ Set = ets_new(set,Opts),
+ OrdSet = ets_new(ordered_set,[ordered_set | Opts]),
update_element_neg_do(Set),
update_element_neg_do(OrdSet),
ets:delete(Set),
@@ -1365,8 +1671,8 @@ update_element_neg(Opts) ->
ets:delete(OrdSet),
?line {'EXIT',{badarg,_}} = (catch ets:update_element(OrdSet,key,{2,1})),
- ?line Bag = ets:new(bag,[bag | Opts]),
- ?line DBag = ets:new(duplicate_bag,[duplicate_bag | Opts]),
+ ?line Bag = ets_new(bag,[bag | Opts]),
+ ?line DBag = ets_new(duplicate_bag,[duplicate_bag | Opts]),
?line {'EXIT',{badarg,_}} = (catch ets:update_element(Bag,key,{2,1})),
?line {'EXIT',{badarg,_}} = (catch ets:update_element(DBag,key,{2,1})),
true = ets:delete(Bag),
@@ -1416,8 +1722,8 @@ update_counter(Config) when is_list(Config) ->
?line verify_etsmem(EtsMem).
update_counter_do(Opts) ->
- Set = ets:new(set,Opts),
- OrdSet = ets:new(ordered_set,[ordered_set | Opts]),
+ Set = ets_new(set,Opts),
+ OrdSet = ets_new(ordered_set,[ordered_set | Opts]),
update_counter_for(Set),
update_counter_for(OrdSet),
ets:delete(Set),
@@ -1438,6 +1744,7 @@ update_counter_for(T) ->
(Obj, Times, Arg3, Myself) ->
?line {NewObj, Ret} = uc_mimic(Obj,Arg3),
ArgHash = erlang:phash2({T,a,Arg3}),
+ %%io:format("update_counter(~p, ~p, ~p) expecting ~p\n",[T,a,Arg3,Ret]),
?line Ret = ets:update_counter(T,a,Arg3),
?line ArgHash = erlang:phash2({T,a,Arg3}),
%%io:format("NewObj=~p~n ",[NewObj]),
@@ -1563,8 +1870,8 @@ uc_adder(Init, {_Pos, Add, Thres, Warp}) ->
end.
update_counter_neg(Opts) ->
- Set = ets:new(set,Opts),
- OrdSet = ets:new(ordered_set,[ordered_set | Opts]),
+ Set = ets_new(set,Opts),
+ OrdSet = ets_new(ordered_set,[ordered_set | Opts]),
update_counter_neg_for(Set),
update_counter_neg_for(OrdSet),
ets:delete(Set),
@@ -1572,8 +1879,8 @@ update_counter_neg(Opts) ->
ets:delete(OrdSet),
?line {'EXIT',{badarg,_}} = (catch ets:update_counter(OrdSet,key,1)),
- ?line Bag = ets:new(bag,[bag | Opts]),
- ?line DBag = ets:new(duplicate_bag,[duplicate_bag | Opts]),
+ ?line Bag = ets_new(bag,[bag | Opts]),
+ ?line DBag = ets_new(duplicate_bag,[duplicate_bag | Opts]),
?line {'EXIT',{badarg,_}} = (catch ets:update_counter(Bag,key,1)),
?line {'EXIT',{badarg,_}} = (catch ets:update_counter(DBag,key,1)),
true = ets:delete(Bag),
@@ -1646,7 +1953,7 @@ wait_for_all(Pids0) ->
end.
evil_counter(I,Opts) ->
- T = ets:new(a, Opts),
+ T = ets_new(a, Opts),
Start0 = case I rem 3 of
0 -> 16#12345678;
1 -> 16#12345678FFFFFFFF;
@@ -1654,7 +1961,7 @@ evil_counter(I,Opts) ->
end,
Start = Start0 + random:uniform(100000),
ets:insert(T, {dracula,Start}),
- Iter = 90000,
+ Iter = 40000,
End = Start + Iter,
End = evil_counter_1(Iter, T),
ets:delete(T).
@@ -1675,7 +1982,7 @@ fixtable_next(Config) when is_list(Config) ->
fixtable_next_do(Opts) ->
?line EtsMem = etsmem(),
- ?line do_fixtable_next(ets:new(set,[public | Opts])),
+ ?line do_fixtable_next(ets_new(set,[public | Opts])),
?line verify_etsmem(EtsMem).
do_fixtable_next(Tab) ->
@@ -1756,24 +2063,24 @@ write_concurrency(doc) -> ["The 'write_concurrency' option"];
write_concurrency(suite) -> [];
write_concurrency(Config) when is_list(Config) ->
?line EtsMem = etsmem(),
- Yes1 = ets:new(foo,[public,{write_concurrency,true}]),
- Yes2 = ets:new(foo,[protected,{write_concurrency,true}]),
- No1 = ets:new(foo,[private,{write_concurrency,true}]),
+ Yes1 = ets_new(foo,[public,{write_concurrency,true}]),
+ Yes2 = ets_new(foo,[protected,{write_concurrency,true}]),
+ No1 = ets_new(foo,[private,{write_concurrency,true}]),
- Yes3 = ets:new(foo,[bag,public,{write_concurrency,true}]),
- Yes4 = ets:new(foo,[bag,protected,{write_concurrency,true}]),
- No2 = ets:new(foo,[bag,private,{write_concurrency,true}]),
+ Yes3 = ets_new(foo,[bag,public,{write_concurrency,true}]),
+ Yes4 = ets_new(foo,[bag,protected,{write_concurrency,true}]),
+ No2 = ets_new(foo,[bag,private,{write_concurrency,true}]),
- Yes5 = ets:new(foo,[duplicate_bag,public,{write_concurrency,true}]),
- Yes6 = ets:new(foo,[duplicate_bag,protected,{write_concurrency,true}]),
- No3 = ets:new(foo,[duplicate_bag,private,{write_concurrency,true}]),
+ Yes5 = ets_new(foo,[duplicate_bag,public,{write_concurrency,true}]),
+ 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}]),
+ 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}]),
+ No7 = ets_new(foo,[public,{write_concurrency,false}]),
+ No8 = ets_new(foo,[protected,{write_concurrency,false}]),
?line YesMem = ets:info(Yes1,memory),
?line NoHashMem = ets:info(No1,memory),
@@ -1800,10 +2107,10 @@ write_concurrency(Config) when is_list(Config) ->
?line true = YesMem =:= NoHashMem
end,
- ?line {'EXIT',{badarg,_}} = (catch ets:new(foo,[public,{write_concurrency,foo}])),
- ?line {'EXIT',{badarg,_}} = (catch ets:new(foo,[public,{write_concurrency}])),
- ?line {'EXIT',{badarg,_}} = (catch ets:new(foo,[public,{write_concurrency,true,foo}])),
- ?line {'EXIT',{badarg,_}} = (catch ets:new(foo,[public,write_concurrency])),
+ ?line {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency,foo}])),
+ ?line {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency}])),
+ ?line {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency,true,foo}])),
+ ?line {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,write_concurrency])),
lists:foreach(fun(T) -> ets:delete(T) end,
[Yes1,Yes2,Yes3,Yes4,Yes5,Yes6,
@@ -1880,7 +2187,7 @@ heir_founder(Master, HeirData, Opts) ->
none -> {heir,none};
_ -> {heir, Heir, HeirData}
end,
- ?line T = ets:new(foo,[named_table, private, HeirTpl | Opts]),
+ ?line T = ets_new(foo,[named_table, private, HeirTpl | Opts]),
?line true = ets:insert(T,{key,1}),
?line [{key,1}] = ets:lookup(T,key),
Self = self(),
@@ -1952,7 +2259,7 @@ give_away(Config) when is_list(Config) ->
repeat_for_opts(give_away_do).
give_away_do(Opts) ->
- ?line T = ets:new(foo,[named_table, private | Opts]),
+ ?line T = ets_new(foo,[named_table, private | Opts]),
?line true = ets:insert(T,{key,1}),
?line [{key,1}] = ets:lookup(T,key),
Parent = self(),
@@ -1978,7 +2285,7 @@ give_away_do(Opts) ->
?line undefined = ets:info(T),
%% Give and then kill receiver to get back
- ?line T2 = ets:new(foo,[private | Opts]),
+ ?line T2 = ets_new(foo,[private | Opts]),
?line true = ets:insert(T2,{key,1}),
?line ets:setopts(T2,{heir,self(),"Som en gummiboll..."}),
?line {Receiver2,Mref2} = spawn_monitor(fun()-> give_away_receiver(T2,Parent) end),
@@ -2000,7 +2307,7 @@ give_away_do(Opts) ->
?line give_me = receive_any(),
?line {'EXIT',{badarg,_}} = (catch ets:give_away(T2,ReceiverNeg,"A deleted table")),
- ?line T3 = ets:new(foo,[public | Opts]),
+ ?line T3 = ets_new(foo,[public | Opts]),
spawn_link(fun()-> {'EXIT',{badarg,_}} = (catch ets:give_away(T3,ReceiverNeg,"From non owner")),
Parent ! done
end),
@@ -2035,7 +2342,7 @@ setopts(Config) when is_list(Config) ->
setopts_do(Opts) ->
Self = self(),
- ?line T = ets:new(foo,[named_table, private | Opts]),
+ ?line T = ets_new(foo,[named_table, private | Opts]),
?line none = ets:info(T,heir),
Heir = spawn_link(fun()->heir_heir(Self) end),
?line ets:setopts(T,{heir,Heir,"Data"}),
@@ -2088,10 +2395,10 @@ bad_table(Config) when is_list(Config) ->
bad_table_do(Opts, DummyFile) ->
Parent = self(),
- {Pid,Mref} = spawn_opt(fun()-> ets:new(priv,[private,named_table | Opts]),
- Priv = ets:new(priv,[private | Opts]),
- ets:new(prot,[protected,named_table | Opts]),
- Prot = ets:new(prot,[protected | Opts]),
+ {Pid,Mref} = spawn_opt(fun()-> ets_new(priv,[private,named_table | Opts]),
+ Priv = ets_new(priv,[private | Opts]),
+ ets_new(prot,[protected,named_table | Opts]),
+ Prot = ets_new(prot,[protected | Opts]),
Parent ! {self(),Priv,Prot},
die_please = receive_any()
end,
@@ -2149,11 +2456,11 @@ bad_table_do(Opts, DummyFile) ->
bad_table_op({Opts,Priv,Prot}, Op) ->
%%io:format("Doing Op=~p on ~p's\n",[Op,Type]),
- T1 = ets:new(noname,Opts),
+ T1 = ets_new(noname,Opts),
bad_table_call(noname,Op),
ets:delete(T1),
bad_table_call(T1,Op),
- T2 = ets:new(named,[named_table | Opts]),
+ T2 = ets_new(named,[named_table | Opts]),
ets:delete(T2),
bad_table_call(named,Op),
bad_table_call(T2,Op),
@@ -2187,7 +2494,7 @@ rename(Config) when is_list(Config) ->
rename_do(Opts) ->
?line EtsMem = etsmem(),
- ets:new(foobazz,[named_table, public | Opts]),
+ ets_new(foobazz,[named_table, public | Opts]),
ets:insert(foobazz,{foo,bazz}),
ungermanbazz = ets:rename(foobazz,ungermanbazz),
{'EXIT',{badarg, _}} = (catch ets:lookup(foobazz,foo)),
@@ -2205,7 +2512,7 @@ rename_unnamed(Config) when is_list(Config) ->
rename_unnamed_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(bonkz,[public | Opts]),
+ ?line Tab = ets_new(bonkz,[public | Opts]),
?line {'EXIT',{badarg, _}} = (catch ets:insert(bonkz,{foo,bazz})),
?line bonkz = ets:info(Tab, name),
?line Tab = ets:rename(Tab, tjabonkz),
@@ -2224,7 +2531,7 @@ evil_rename(Config) when is_list(Config) ->
evil_rename_1(Old, New, Flags) ->
?line process_flag(trap_exit, true),
- ?line Old = ets:new(Old, Flags),
+ ?line Old = ets_new(Old, Flags),
?line Fixer = fun() -> ets:safe_fixtable(Old, true) end,
?line crazy_fixtable(15000, Fixer),
?line erlang:yield(),
@@ -2234,7 +2541,7 @@ evil_rename_1(Old, New, Flags) ->
ok.
crazy_fixtable(N, Fixer) ->
- Dracula = ets:new(count_dracula, [public]),
+ Dracula = ets_new(count_dracula, [public]),
ets:insert(Dracula, {count,0}),
SpawnFun = fun() ->
Fixer(),
@@ -2268,7 +2575,7 @@ evil_creater_destroyer() ->
ets:delete(T1).
evil_create_fixed_tab() ->
- T = ets:new(arne, [public]),
+ T = ets_new(arne, [public]),
ets:safe_fixtable(T, true),
T.
@@ -2282,8 +2589,8 @@ interface_equality(Config) when is_list(Config) ->
interface_equality_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Set = ets:new(set,[set | Opts]),
- ?line OrderedSet = ets:new(ordered_set,[ordered_set | Opts]),
+ ?line Set = ets_new(set,[set | Opts]),
+ ?line OrderedSet = ets_new(ordered_set,[ordered_set | Opts]),
?line F = fun(X,T,FF) -> case X of
0 -> true;
_ ->
@@ -2362,7 +2669,7 @@ ordered_match_do(Opts) ->
FF(X-1,T,FF)
end
end,
- ?line T1 = ets:new(xxx,[ordered_set| Opts]),
+ ?line T1 = ets_new(xxx,[ordered_set| Opts]),
?line F(3000,T1,F),
?line [[3,3],[3,3],[3,3]] = ets:match(T1, {'_','_','$1','$2',3}),
?line F2 = fun(X,Rem,Res,FF) -> case X of
@@ -2400,7 +2707,7 @@ ordered(Config) when is_list(Config) ->
ordered_do(Opts) ->
?line EtsMem = etsmem(),
- ?line T = ets:new(oset, [ordered_set | Opts]),
+ ?line T = ets_new(oset, [ordered_set | Opts]),
?line InsList = [
25,26,27,28,
5,6,7,8,
@@ -2461,8 +2768,8 @@ setbag(doc) -> ["Small test case for both set and bag type ets tables."];
setbag(suite) -> [];
setbag(Config) when is_list(Config) ->
?line EtsMem = etsmem(),
- ?line Set = ets:new(set,[set]),
- ?line Bag = ets:new(bag,[bag]),
+ ?line Set = ets_new(set,[set]),
+ ?line Bag = ets_new(bag,[bag]),
?line Key = {foo,bar},
%% insert some value
@@ -2482,15 +2789,15 @@ setbag(Config) when is_list(Config) ->
?line verify_etsmem(EtsMem).
badnew(doc) ->
- ["Test case to check proper return values for illegal ets:new() calls."];
+ ["Test case to check proper return values for illegal ets_new() calls."];
badnew(suite) -> [];
badnew(Config) when is_list(Config) ->
?line EtsMem = etsmem(),
- ?line {'EXIT',{badarg,_}} = (catch ets:new(12,[])),
- ?line {'EXIT',{badarg,_}} = (catch ets:new({a,b},[])),
- ?line {'EXIT',{badarg,_}} = (catch ets:new(name,[foo])),
- ?line {'EXIT',{badarg,_}} = (catch ets:new(name,{bag})),
- ?line {'EXIT',{badarg,_}} = (catch ets:new(name,bag)),
+ ?line {'EXIT',{badarg,_}} = (catch ets_new(12,[])),
+ ?line {'EXIT',{badarg,_}} = (catch ets_new({a,b},[])),
+ ?line {'EXIT',{badarg,_}} = (catch ets_new(name,[foo])),
+ ?line {'EXIT',{badarg,_}} = (catch ets_new(name,{bag})),
+ ?line {'EXIT',{badarg,_}} = (catch ets_new(name,bag)),
?line verify_etsmem(EtsMem).
verybadnew(doc) ->
@@ -2499,7 +2806,7 @@ verybadnew(doc) ->
verybadnew(suite) -> [];
verybadnew(Config) when is_list(Config) ->
?line EtsMem = etsmem(),
- ?line {'EXIT',{badarg,_}} = (catch ets:new(verybad,[set|protected])),
+ ?line {'EXIT',{badarg,_}} = (catch ets_new(verybad,[set|protected])),
?line verify_etsmem(EtsMem).
named(doc) -> ["Small check to see if named tables work."];
@@ -2576,9 +2883,9 @@ privacy_check(Pub,Prot,Priv) ->
?line [] = ets:lookup(Prot,foo).
privacy_owner(Boss, Opts) ->
- ets:new(pub, [public,named_table | Opts]),
- ets:new(prot,[protected,named_table | Opts]),
- ets:new(priv,[private,named_table | Opts]),
+ ets_new(pub, [public,named_table | Opts]),
+ ets_new(prot,[protected,named_table | Opts]),
+ ets_new(priv,[private,named_table | Opts]),
Boss ! ok,
privacy_owner_loop(Boss).
@@ -2605,8 +2912,6 @@ rotate_tuple(Tuple, N) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-insert(doc) -> ["Test proper and improper inserts into a table."];
-insert(suite) -> [empty,badinsert].
empty(doc) ->
["Check lookup in an empty table and lookup of a non-existing key"];
@@ -2616,7 +2921,7 @@ empty(Config) when is_list(Config) ->
empty_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(foo,Opts),
+ ?line Tab = ets_new(foo,Opts),
?line [] = ets:lookup(Tab,key),
?line true = ets:insert(Tab,{key2,val}),
?line [] = ets:lookup(Tab,key),
@@ -2633,10 +2938,10 @@ badinsert_do(Opts) ->
?line EtsMem = etsmem(),
?line {'EXIT',{badarg,_}} = (catch ets:insert(foo,{key,val})),
- ?line Tab = ets:new(foo,Opts),
+ ?line Tab = ets_new(foo,Opts),
?line {'EXIT',{badarg,_}} = (catch ets:insert(Tab,{})),
- ?line Tab3 = ets:new(foo,[{keypos,3}| Opts]),
+ ?line Tab3 = ets_new(foo,[{keypos,3}| Opts]),
?line {'EXIT',{badarg,_}} = (catch ets:insert(Tab3,{a,b})),
?line {'EXIT',{badarg,_}} = (catch ets:insert(Tab,[key,val2])),
@@ -2646,8 +2951,6 @@ badinsert_do(Opts) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-lookup(doc) -> ["Some tests for lookups (timing, bad lookups, etc.)."];
-lookup(suite) -> [time_lookup,badlookup,lookup_order].
time_lookup(doc) -> ["Lookup timing."];
time_lookup(suite) -> [];
@@ -2660,7 +2963,7 @@ time_lookup(Config) when is_list(Config) ->
"~p ets lookups/s",[Values]))}.
time_lookup_do(Opts) ->
- ?line Tab = ets:new(foo,Opts),
+ ?line Tab = ets_new(foo,Opts),
?line fill_tab(Tab,foo),
?line ets:insert(Tab,{{a,key},foo}),
?line {Time,_} = ?t:timecall(test_server,do_times,
@@ -2675,7 +2978,7 @@ badlookup(suite) -> [];
badlookup(Config) when is_list(Config) ->
?line EtsMem = etsmem(),
?line {'EXIT',{badarg,_}} = (catch ets:lookup(foo,key)),
- ?line Tab = ets:new(foo,[]),
+ ?line Tab = ets_new(foo,[]),
?line ets:delete(Tab),
?line {'EXIT',{badarg,_}} = (catch ets:lookup(Tab,key)),
?line verify_etsmem(EtsMem).
@@ -2700,7 +3003,7 @@ lookup_order_2(Opts, Fixed) ->
Pair = [{A,B},{B,A},{A,C},{C,A},{B,C},{C,B}],
Combos = [{D1,D2,D3} || D1<-ABC, D2<-Pair, D3<-Pair],
lists:foreach(fun({D1,{D2a,D2b},{D3a,D3b}}) ->
- T = ets:new(foo,Opts),
+ T = ets_new(foo,Opts),
case Fixed of
true -> ets:safe_fixtable(T,true);
false -> ok
@@ -2774,8 +3077,6 @@ fill_tab(Tab,Val) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-lookup_element(doc) -> ["Some tests for lookup_element."];
-lookup_element(suite) -> [lookup_element_mult].
lookup_element_mult(doc) -> ["Multiple return elements (OTP-2386)"];
lookup_element_mult(suite) -> [];
@@ -2784,10 +3085,12 @@ lookup_element_mult(Config) when is_list(Config) ->
lookup_element_mult_do(Opts) ->
?line EtsMem = etsmem(),
- ?line T = ets:new(service, [bag, {keypos, 2} | Opts]),
+ ?line T = ets_new(service, [bag, {keypos, 2} | Opts]),
?line D = lists:reverse(lem_data()),
?line lists:foreach(fun(X) -> ets:insert(T, X) end, D),
?line ok = lem_crash_3(T),
+ ?line ets:insert(T, {0, "heap_key"}),
+ ?line ets:lookup_element(T, "heap_key", 2),
?line true = ets:delete(T),
?line verify_etsmem(EtsMem).
@@ -2815,11 +3118,6 @@ lem_crash_3(T) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-delete(doc) ->
- ["Check delete functionality (proper/improper deletes)"];
-delete(suite) ->
- [delete_elem,delete_tab,delete_large_tab,delete_large_named_table,evil_delete,
- table_leak,baddelete,match_delete,match_delete3].
delete_elem(doc) ->
["Check delete of an element inserted in a `filled' table."];
@@ -2829,7 +3127,7 @@ delete_elem(Config) when is_list(Config) ->
delete_elem_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(foo,Opts),
+ ?line Tab = ets_new(foo,Opts),
?line fill_tab(Tab,foo),
?line ets:insert(Tab,{{b,key},foo}),
?line ets:insert(Tab,{{c,key},foo}),
@@ -2849,17 +3147,17 @@ delete_tab(Config) when is_list(Config) ->
delete_tab_do(Opts) ->
Name = foo,
?line EtsMem = etsmem(),
- ?line Name = ets:new(Name, [named_table | Opts]),
+ ?line Name = ets_new(Name, [named_table | Opts]),
?line true = ets:delete(foo),
%% The name should be available again.
- ?line Name = ets:new(Name, [named_table | Opts]),
+ ?line Name = ets_new(Name, [named_table | Opts]),
?line true = ets:delete(Name),
?line verify_etsmem(EtsMem).
delete_large_tab(doc) ->
"Check that ets:delete/1 works and that other processes can run.";
delete_large_tab(Config) when is_list(Config) ->
- ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
+ ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)],
?line EtsMem = etsmem(),
repeat_for_opts(fun(Opts) -> delete_large_tab_do(Opts,Data) end),
?line verify_etsmem(EtsMem).
@@ -2871,7 +3169,7 @@ delete_large_tab_do(Opts,Data) ->
delete_large_tab_1(Name, Flags, Data, Fix) ->
- ?line Tab = ets:new(Name, Flags),
+ ?line Tab = ets_new(Name, Flags),
?line ets:insert(Tab, Data),
case Fix of
@@ -2938,7 +3236,7 @@ delete_large_named_table_do(Opts,Data) ->
?line delete_large_named_table_1(foo_hash, [named_table | Opts], Data, true).
delete_large_named_table_1(Name, Flags, Data, Fix) ->
- ?line Tab = ets:new(Name, Flags),
+ ?line Tab = ets_new(Name, Flags),
?line ets:insert(Tab, Data),
case Fix of
@@ -2951,7 +3249,7 @@ delete_large_named_table_1(Name, Flags, Data, Fix) ->
Pid = spawn_link(fun() ->
receive
{trace,Parent,call,_} ->
- ets:new(Name, [named_table])
+ ets_new(Name, [named_table])
end
end),
?line erlang:trace(self(), true, [call,{tracer,Pid}]),
@@ -2985,7 +3283,7 @@ evil_delete_do(Opts,Data) ->
evil_delete_not_owner(Name, Flags, Data, Fix) ->
io:format("Not owner: ~p, fix = ~p", [Name,Fix]),
- ?line Tab = ets:new(Name, [public|Flags]),
+ ?line Tab = ets_new(Name, [public|Flags]),
?line ets:insert(Tab, Data),
case Fix of
false -> ok;
@@ -3010,7 +3308,7 @@ evil_delete_not_owner(Name, Flags, Data, Fix) ->
evil_delete_owner(Name, Flags, Data, Fix) ->
?line Fun = fun() ->
- ?line Tab = ets:new(Name, [public|Flags]),
+ ?line Tab = ets_new(Name, [public|Flags]),
?line ets:insert(Tab, Data),
case Fix of
false -> ok;
@@ -3037,48 +3335,60 @@ exit_large_table_owner(doc) ->
exit_large_table_owner(suite) ->
[];
exit_large_table_owner(Config) when is_list(Config) ->
- ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
+ %%?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
+ ?line FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok};
+ (I) -> Do({erlang:phash2(I, 16#ffffff),I}),
+ {true, I+1}
+ end, 1)
+ end,
?line EtsMem = etsmem(),
- repeat_for_opts(fun(Opts) -> exit_large_table_owner_do(Opts,Data,Config) end),
+ repeat_for_opts({exit_large_table_owner_do,{FEData,Config}}),
?line verify_etsmem(EtsMem).
-exit_large_table_owner_do(Opts,Data,Config) ->
- ?line verify_rescheduling_exit(Config, Data, [named_table | Opts], true, 1, 1),
- ?line verify_rescheduling_exit(Config, Data, Opts, false, 1, 1).
+exit_large_table_owner_do(Opts,{FEData,Config}) ->
+ ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], true, 1, 1),
+ ?line verify_rescheduling_exit(Config, FEData, Opts, false, 1, 1).
exit_many_large_table_owner(doc) -> [];
exit_many_large_table_owner(suite) -> [];
exit_many_large_table_owner(Config) when is_list(Config) ->
- ?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
+ %%?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
+ ?line FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok};
+ (I) -> Do({erlang:phash2(I, 16#ffffff),I}),
+ {true, I+1}
+ end, 1)
+ end,
?line EtsMem = etsmem(),
- repeat_for_opts(fun(Opts) -> exit_many_large_table_owner_do(Opts,Data,Config) end),
+ repeat_for_opts(fun(Opts) -> exit_many_large_table_owner_do(Opts,FEData,Config) end),
?line verify_etsmem(EtsMem).
-exit_many_large_table_owner_do(Opts,Data,Config) ->
- ?line verify_rescheduling_exit(Config, Data, Opts, true, 1, 4),
- ?line verify_rescheduling_exit(Config, Data, [named_table | Opts], false, 1, 4).
+exit_many_large_table_owner_do(Opts,FEData,Config) ->
+ ?line verify_rescheduling_exit(Config, FEData, Opts, true, 1, 4),
+ ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], false, 1, 4).
exit_many_tables_owner(doc) -> [];
exit_many_tables_owner(suite) -> [];
exit_many_tables_owner(Config) when is_list(Config) ->
+ NoData = fun(_Do) -> ok end,
?line EtsMem = etsmem(),
- ?line verify_rescheduling_exit(Config, [], [named_table], false, 1000, 1),
- ?line verify_rescheduling_exit(Config, [], [named_table,{write_concurrency,true}], false, 1000, 1),
+ ?line verify_rescheduling_exit(Config, NoData, [named_table], false, 1000, 1),
+ ?line verify_rescheduling_exit(Config, NoData, [named_table,{write_concurrency,true}], false, 1000, 1),
?line verify_etsmem(EtsMem).
exit_many_many_tables_owner(doc) -> [];
exit_many_many_tables_owner(suite) -> [];
exit_many_many_tables_owner(Config) when is_list(Config) ->
?line Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 50)],
- repeat_for_opts(fun(Opts) -> exit_many_many_tables_owner_do(Opts,Data,Config) end).
+ ?line FEData = fun(Do) -> lists:foreach(Do, Data) end,
+ repeat_for_opts(fun(Opts) -> exit_many_many_tables_owner_do(Opts,FEData,Config) end).
-exit_many_many_tables_owner_do(Opts,Data,Config) ->
- ?line verify_rescheduling_exit(Config, Data, [named_table | Opts], true, 200, 5),
- ?line verify_rescheduling_exit(Config, Data, Opts, false, 200, 5),
+exit_many_many_tables_owner_do(Opts,FEData,Config) ->
+ ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], true, 200, 5),
+ ?line verify_rescheduling_exit(Config, FEData, Opts, false, 200, 5),
?line wait_for_test_procs(),
?line EtsMem = etsmem(),
- ?line verify_rescheduling_exit(Config, Data, Opts, true, 200, 5),
- ?line verify_rescheduling_exit(Config, Data, [named_table | Opts], false, 200, 5),
+ ?line verify_rescheduling_exit(Config, FEData, Opts, true, 200, 5),
+ ?line verify_rescheduling_exit(Config, FEData, [named_table | Opts], false, 200, 5),
?line verify_etsmem(EtsMem).
@@ -3121,7 +3431,7 @@ vre_fix_tables(Tab) ->
receive Go -> ok end,
ok.
-verify_rescheduling_exit(Config, Data, Flags, Fix, NOTabs, NOProcs) ->
+verify_rescheduling_exit(Config, ForEachData, Flags, Fix, NOTabs, NOProcs) ->
?line NoFix = 5,
?line TestCase = atom_to_list(?config(test_case, Config)),
?line Parent = self(),
@@ -3136,8 +3446,8 @@ verify_rescheduling_exit(Config, Data, Flags, Fix, NOTabs, NOProcs) ->
++ "-" ++ integer_to_list(A)
++ "-" ++ integer_to_list(B)
++ "-" ++ integer_to_list(C)),
- Tab = ets:new(Name, Flags),
- ets:insert(Tab, Data),
+ Tab = ets_new(Name, Flags),
+ ForEachData(fun(Data) -> ets:insert(Tab, Data) end),
case Fix of
false -> ok;
true ->
@@ -3145,10 +3455,10 @@ verify_rescheduling_exit(Config, Data, Flags, Fix, NOTabs, NOProcs) ->
vre_fix_tables(Tab)
end,
lists:seq(1,NoFix)),
- lists:foreach(fun({K,_}) ->
- ets:delete(Tab, K)
- end,
- Data)
+ KeyPos = ets:info(Tab,keypos),
+ ForEachData(fun(Data) ->
+ ets:delete(Tab, element(KeyPos,Data))
+ end)
end
end,
NOTabs),
@@ -3195,7 +3505,7 @@ table_leak(Config) when is_list(Config) ->
table_leak_1(_,0) -> ok;
table_leak_1(Opts,N) ->
- ?line T = ets:new(fooflarf, Opts),
+ ?line T = ets_new(fooflarf, Opts),
?line true = ets:delete(T),
table_leak_1(Opts,N-1).
@@ -3205,7 +3515,7 @@ baddelete(suite) -> [];
baddelete(Config) when is_list(Config) ->
?line EtsMem = etsmem(),
?line {'EXIT',{badarg,_}} = (catch ets:delete(foo)),
- ?line Tab = ets:new(foo,[]),
+ ?line Tab = ets_new(foo,[]),
?line true = ets:delete(Tab),
?line {'EXIT',{badarg,_}} = (catch ets:delete(Tab)),
?line verify_etsmem(EtsMem).
@@ -3220,7 +3530,7 @@ match_delete(Config) when is_list(Config) ->
match_delete_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(kad,Opts),
+ ?line Tab = ets_new(kad,Opts),
?line fill_tab(Tab,foo),
?line ets:insert(Tab,{{c,key},bar}),
?line _ = ets:match_delete(Tab,{'_',foo}),
@@ -3264,7 +3574,7 @@ firstnext(Config) when is_list(Config) ->
firstnext_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(foo,Opts),
+ ?line Tab = ets_new(foo,Opts),
?line [] = firstnext_collect(Tab,ets:first(Tab),[]),
?line fill_tab(Tab,foo),
?line Len = length(ets:tab2list(Tab)),
@@ -3287,10 +3597,10 @@ firstnext_concurrent(Config) when is_list(Config) ->
[dynamic_go() || _ <- lists:seq(1, 2)],
receive
after 5000 -> ok
- end.
+ end.
ets_init(Tab, N) ->
- ets:new(Tab, [named_table,public,ordered_set]),
+ ets_new(Tab, [named_table,public,ordered_set]),
cycle(Tab, lists:seq(1,N+1)).
cycle(_Tab, [H|T]) when H > length(T)-> ok;
@@ -3323,7 +3633,7 @@ slot(Config) when is_list(Config) ->
slot_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(foo,Opts),
+ ?line Tab = ets_new(foo,Opts),
?line fill_tab(Tab,foo),
?line Elts = ets:info(Tab,size),
?line Elts = slot_loop(Tab,0,0),
@@ -3342,7 +3652,6 @@ slot_loop(Tab,SlotNo,EltsSoFar) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-match(suite) -> [match1, match2, match_object, match_object2].
match1(suite) -> [];
match1(Config) when is_list(Config) ->
@@ -3350,7 +3659,7 @@ match1(Config) when is_list(Config) ->
match1_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(foo,Opts),
+ ?line Tab = ets_new(foo,Opts),
?line fill_tab(Tab,foo),
?line [] = ets:match(Tab,{}),
?line ets:insert(Tab,{{one,4},4}),
@@ -3415,7 +3724,7 @@ match_object(Config) when is_list(Config) ->
match_object_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(foobar, Opts),
+ ?line Tab = ets_new(foobar, Opts),
?line fill_tab(Tab, foo),
?line ets:insert(Tab, {{one, 4}, 4}),
?line ets:insert(Tab,{{one,5},5}),
@@ -3459,7 +3768,7 @@ match_object2(Config) when is_list(Config) ->
match_object2_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(foo, [bag, {keypos, 2} | Opts]),
+ ?line Tab = ets_new(foo, [bag, {keypos, 2} | Opts]),
?line fill_tab2(Tab, 0, 13005), % match_db_object does 1000
% elements per pass, might
% change in the future.
@@ -3477,7 +3786,6 @@ match_object2_do(Opts) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-misc(suite) -> [misc1, safe_fixtable, info, dups, tab2list].
tab2list(doc) -> ["Tests tab2list (OTP-3319)"];
tab2list(suite) -> [];
@@ -3498,7 +3806,7 @@ misc1(Config) when is_list(Config) ->
misc1_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(foo,Opts),
+ ?line Tab = ets_new(foo,Opts),
?line true = lists:member(Tab,ets:all()),
?line ets:delete(Tab),
?line false = lists:member(Tab,ets:all()),
@@ -3517,7 +3825,7 @@ safe_fixtable(Config) when is_list(Config) ->
safe_fixtable_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(foo, Opts),
+ ?line Tab = ets_new(foo, Opts),
?line fill_tab(Tab, foobar),
?line true = ets:safe_fixtable(Tab, true),
?line receive after 1 -> ok end,
@@ -3556,7 +3864,7 @@ info_do(Opts) ->
?line EtsMem = etsmem(),
?line MeMyselfI=self(),
?line ThisNode=node(),
- ?line Tab = ets:new(foobar, [{keypos, 2} | Opts]),
+ ?line Tab = ets_new(foobar, [{keypos, 2} | Opts]),
%% Note: ets:info/1 used to return a tuple, but from R11B onwards it
%% returns a list.
@@ -3610,15 +3918,12 @@ dups_do(Opts) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-files(suite) -> [tab2file, tab2file2, tab2file3, tabfile_ext1, tabfile_ext2,
- tabfile_ext3, tabfile_ext4].
-
tab2file(doc) -> ["Check the ets:tab2file function on an empty "
"ets table."];
tab2file(suite) -> [];
tab2file(Config) when is_list(Config) ->
%% Write an empty ets table to a file, read back and check properties.
- ?line Tab = ets:new(ets_SUITE_foo_tab, [named_table, set, private,
+ ?line Tab = ets_new(ets_SUITE_foo_tab, [named_table, set, private,
{keypos, 2}]),
?line FName = filename:join([?config(priv_dir, Config),"tab2file_case"]),
?line ok = ets:tab2file(Tab, FName),
@@ -3634,51 +3939,36 @@ tab2file(Config) when is_list(Config) ->
?line verify_etsmem(EtsMem).
tab2file2(doc) -> ["Check the ets:tab2file function on a ",
- "filled set type ets table."];
+ "filled set/bag type ets table."];
tab2file2(suite) -> [];
-tab2file2(Config) when is_list(Config) ->
- %% Try the same on a filled set table.
- ?line EtsMem = etsmem(),
- ?line Tab = ets:new(ets_SUITE_foo_tab, [named_table, set, private,
- {keypos, 2}]),
- ?line FName = filename:join([?config(priv_dir, Config),"tab2file2_case"]),
- ?line ok = fill_tab2(Tab, 0, 10000), % Fill up the table (grucho mucho!)
- ?line Len = length(ets:tab2list(Tab)),
- ?line ok = ets:tab2file(Tab, FName),
- ?line true = ets:delete(Tab),
- %
- ?line {ok, Tab2} = ets:file2tab(FName),
- ?line private = ets:info(Tab2, protection),
- ?line true = ets:info(Tab2, named_table),
- ?line 2 = ets:info(Tab2, keypos),
- ?line set = ets:info(Tab2, type),
- ?line Len = length(ets:tab2list(Tab2)),
- ?line true = ets:delete(Tab2),
- ?line verify_etsmem(EtsMem).
+tab2file2(Config) when is_list(Config) ->
+ repeat_for_opts({tab2file2_do,Config}, [[set,bag],compressed]).
-tab2file3(doc) -> ["Check the ets:tab2file function on a ",
- "filled bag type ets table."];
-tab2file3(suite) -> [];
-tab2file3(Config) when is_list(Config) ->
- %% Try the same on a filled bag table.
+tab2file2_do(Opts, Config) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(ets_SUITE_foo_tab, [named_table, bag, private,
- {keypos, 2}]),
- ?line FName = filename:join([?config(priv_dir, Config),"tab2file3_case"]),
+ ?line Tab = ets_new(ets_SUITE_foo_tab, [named_table, private,
+ {keypos, 2} | Opts]),
+ ?line FName = filename:join([?config(priv_dir, Config),"tab2file2_case"]),
?line ok = fill_tab2(Tab, 0, 10000), % Fill up the table (grucho mucho!)
?line Len = length(ets:tab2list(Tab)),
?line Mem = ets:info(Tab, memory),
+ ?line Type = ets:info(Tab, type),
+ %%io:format("org tab: ~p\n",[ets:info(Tab)]),
?line ok = ets:tab2file(Tab, FName),
?line true = ets:delete(Tab),
+ ?line EtsMem4 = etsmem(),
+
?line {ok, Tab2} = ets:file2tab(FName),
+ %%io:format("loaded tab: ~p\n",[ets:info(Tab2)]),
?line private = ets:info(Tab2, protection),
?line true = ets:info(Tab2, named_table),
?line 2 = ets:info(Tab2, keypos),
- ?line bag = ets:info(Tab2, type),
+ ?line Type = ets:info(Tab2, type),
?line Len = length(ets:tab2list(Tab2)),
?line Mem = ets:info(Tab2, memory),
?line true = ets:delete(Tab2),
+ io:format("Between = ~p\n", [EtsMem4]),
?line verify_etsmem(EtsMem).
-define(test_list, [8,5,4,1,58,125,255, 250, 245, 240, 235,
@@ -3722,7 +4012,7 @@ tabfile_ext1_do(Opts,Config) ->
?line FName = filename:join([?config(priv_dir, Config),"nisse.dat"]),
?line FName2 = filename:join([?config(priv_dir, Config),"countflip.dat"]),
L = lists:seq(1,10),
- T = ets:new(x,Opts),
+ T = ets_new(x,Opts),
Name = make_ref(),
[ets:insert(T,{X,integer_to_list(X)}) || X <- L],
ok = ets:tab2file(T,FName,[{extended_info,[object_count]}]),
@@ -3762,7 +4052,7 @@ tabfile_ext2_do(Opts,Config) ->
?line FName = filename:join([?config(priv_dir, Config),"olle.dat"]),
?line FName2 = filename:join([?config(priv_dir, Config),"bitflip.dat"]),
L = lists:seq(1,10),
- T = ets:new(x,Opts),
+ T = ets_new(x,Opts),
Name = make_ref(),
[ets:insert(T,{X,integer_to_list(X)}) || X <- L],
ok = ets:tab2file(T,FName,[{extended_info,[md5sum]}]),
@@ -3800,7 +4090,7 @@ tabfile_ext3(Config) when is_list(Config) ->
?line FName2 = filename:join([?config(priv_dir, Config),"ncountflip.dat"]),
L = lists:seq(1,10),
Name = make_ref(),
- ?MODULE = ets:new(?MODULE,[named_table]),
+ ?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),
@@ -3832,7 +4122,7 @@ tabfile_ext4(doc) ->
tabfile_ext4(Config) when is_list(Config) ->
?line FName = filename:join([?config(priv_dir, Config),"bauta.dat"]),
LL = lists:seq(1,10000),
- TL = ets:new(x,[]),
+ 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]}]),
@@ -3877,7 +4167,6 @@ make_sub_binary(List, Num) when is_list(List) ->
{_,B} = split_binary(Bin, N+1),
B.
-heavy(suite) -> [heavy_lookup, heavy_lookup_element].
%% Lookup stuff like crazy...
heavy_lookup(doc) -> ["Performs multiple lookups for every key ",
@@ -3888,7 +4177,7 @@ heavy_lookup(Config) when is_list(Config) ->
heavy_lookup_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(foobar_table, [set, protected, {keypos, 2} | Opts]),
+ ?line Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]),
?line ok = fill_tab2(Tab, 0, 7000),
?line ?t:do_times(50, ?MODULE, do_lookup, [Tab, 6999]),
?line true = ets:delete(Tab),
@@ -3911,7 +4200,7 @@ heavy_lookup_element(Config) when is_list(Config) ->
heavy_lookup_element_do(Opts) ->
?line EtsMem = etsmem(),
- ?line Tab = ets:new(foobar_table, [set, protected, {keypos, 2} | Opts]),
+ ?line Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]),
?line ok = fill_tab2(Tab, 0, 7000),
case os:type() of
vxworks ->
@@ -3940,9 +4229,44 @@ do_lookup_element(Tab, N, M) ->
end.
-fold(suite) -> [foldl_ordered, foldr_ordered,
- foldl, foldr,
- fold_empty].
+heavy_concurrent(Config) when is_list(Config) ->
+ repeat_for_opts(do_heavy_concurrent).
+
+do_heavy_concurrent(Opts) ->
+ ?line Size = 10000,
+ ?line EtsMem = etsmem(),
+ ?line Tab = ets_new(blupp, [set, public, {keypos, 2} | Opts]),
+ ?line ok = fill_tab2(Tab, 0, Size),
+ ?line Procs = lists:map(
+ fun (N) ->
+ spawn_link(
+ fun () ->
+ do_heavy_concurrent_proc(Tab, Size, N)
+ end)
+ end,
+ lists:seq(1, 500)),
+ ?line lists:foreach(fun (P) ->
+ M = erlang:monitor(process, P),
+ receive
+ {'DOWN', M, process, P, _} ->
+ ok
+ end
+ end,
+ Procs),
+ ?line true = ets:delete(Tab),
+ ?line verify_etsmem(EtsMem).
+
+do_heavy_concurrent_proc(_Tab, 0, _Offs) ->
+ done;
+do_heavy_concurrent_proc(Tab, N, Offs) when (N+Offs) rem 100 == 0 ->
+ Data = {"here", are, "S O M E ", data, "toooooooooooooooooo", insert,
+ make_ref(), make_ref(), make_ref()},
+ true=ets:insert(Tab, {{self(),Data}, N}),
+ do_heavy_concurrent_proc(Tab, N-1, Offs);
+do_heavy_concurrent_proc(Tab, N, Offs) ->
+ _ = ets:lookup(Tab, N),
+ do_heavy_concurrent_proc(Tab, N-1, Offs).
+
fold_empty(doc) ->
[];
@@ -4012,7 +4336,7 @@ member(Config) when is_list(Config) ->
member_do(Opts) ->
?line EtsMem = etsmem(),
- ?line T = ets:new(xxx, Opts),
+ ?line T = ets_new(xxx, Opts),
?line false = ets:member(T,hej),
?line E = fun(0,_F)->ok;
(N,F) ->
@@ -4037,7 +4361,7 @@ member_do(Opts) ->
build_table(L1,L2,Num) ->
- T = ets:new(xxx, [ordered_set]
+ T = ets_new(xxx, [ordered_set]
),
lists:foreach(
fun(X1) ->
@@ -4059,7 +4383,7 @@ build_table(L1,L2,Num) ->
T.
build_table2(L1,L2,Num) ->
- T = ets:new(xxx, [ordered_set]
+ T = ets_new(xxx, [ordered_set]
),
lists:foreach(
fun(X1) ->
@@ -4190,7 +4514,7 @@ do_n_times(Fun,N) ->
do_n_times(Fun,N-1).
make_table(Name, Options, Elements) ->
- T = ets:new(Name, Options),
+ T = ets_new(Name, Options),
lists:foreach(fun(E) -> ets:insert(T, E) end, Elements),
T.
filltabint(Tab,0) ->
@@ -4254,13 +4578,13 @@ xfilltabstr(Tab,N) ->
fill_sets_int(N) ->
fill_sets_int(N,[]).
fill_sets_int(N,Opts) ->
- Tab1 = ets:new(xxx, [ordered_set|Opts]),
+ Tab1 = ets_new(xxx, [ordered_set|Opts]),
filltabint(Tab1,N),
- Tab2 = ets:new(xxx, [set|Opts]),
+ Tab2 = ets_new(xxx, [set|Opts]),
filltabint(Tab2,N),
- Tab3 = ets:new(xxx, [bag|Opts]),
+ Tab3 = ets_new(xxx, [bag|Opts]),
filltabint2(Tab3,N),
- Tab4 = ets:new(xxx, [duplicate_bag|Opts]),
+ Tab4 = ets_new(xxx, [duplicate_bag|Opts]),
filltabint3(Tab4,N),
[Tab1,Tab2,Tab3,Tab4].
@@ -4412,7 +4736,7 @@ gen_dets_filename(Config,N) ->
"testdets_" ++ integer_to_list(N) ++ ".dets").
otp_6842_select_1000(Config) when is_list(Config) ->
- ?line Tab = ets:new(xxx,[ordered_set]),
+ ?line Tab = ets_new(xxx,[ordered_set]),
?line [ets:insert(Tab,{X,X}) || X <- lists:seq(1,10000)],
?line AllTrue = lists:duplicate(10,true),
?line AllTrue =
@@ -4445,7 +4769,7 @@ check_seq(A,B,C) ->
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]),
+ 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).
@@ -4456,7 +4780,7 @@ otp_5340(Config) when is_list(Config) ->
otp_5340_do(Opts) ->
N = 3000,
- T = ets:new(otp_5340, [bag,public | Opts]),
+ T = ets_new(otp_5340, [bag,public | Opts]),
Ids = [1,2,3,4,5],
[w(T, N, Id) || Id <- Ids],
verify(T, Ids),
@@ -4492,7 +4816,7 @@ otp_7665(Config) when is_list(Config) ->
repeat_for_opts(otp_7665_do).
otp_7665_do(Opts) ->
- Tab = ets:new(otp_7665,[bag | Opts]),
+ Tab = ets_new(otp_7665,[bag | Opts]),
Min = 0,
Max = 10,
lists:foreach(fun(N)-> otp_7665_act(Tab,Min,Max,N) end,
@@ -4555,7 +4879,7 @@ meta_wb_do(Opts) ->
Names).
meta_wb_new(Name, _, Tabs, Opts) ->
- case (catch ets:new(Name,[named_table|Opts])) of
+ case (catch ets_new(Name,[named_table|Opts])) of
Name ->
?line false = lists:member(Name, Tabs),
[Name | Tabs];
@@ -4603,7 +4927,7 @@ grow_shrink_0([N|Ns], EtsMem) ->
grow_shrink_0([], _) -> ok.
grow_shrink_1(N, Flags) ->
- ?line T = ets:new(a, Flags),
+ ?line T = ets_new(a, Flags),
?line grow_shrink_2(N, N, T),
?line ets:delete(T).
@@ -4633,7 +4957,7 @@ grow_pseudo_deleted_do() ->
grow_pseudo_deleted_do(Type) ->
process_flag(scheduler,1),
Self = self(),
- ?line T = ets:new(kalle,[Type,public,{write_concurrency,true}]),
+ ?line T = ets_new(kalle,[Type,public,{write_concurrency,true}]),
Mod = 7, Mult = 10000,
filltabint(T,Mod*Mult),
?line true = ets:safe_fixtable(T,true),
@@ -4675,7 +4999,7 @@ shrink_pseudo_deleted_do() ->
shrink_pseudo_deleted_do(Type) ->
process_flag(scheduler,1),
Self = self(),
- ?line T = ets:new(kalle,[Type,public,{write_concurrency,true}]),
+ ?line T = ets_new(kalle,[Type,public,{write_concurrency,true}]),
Half = 10000,
filltabint(T,Half*2),
?line true = ets:safe_fixtable(T,true),
@@ -4704,17 +5028,10 @@ shrink_pseudo_deleted_do(Type) ->
process_flag(scheduler,0).
-meta_smp(suite) ->
- [meta_lookup_unnamed_read,
- meta_lookup_unnamed_write,
- meta_lookup_named_read,
- meta_lookup_named_write,
- meta_newdel_unnamed,
- meta_newdel_named].
meta_lookup_unnamed_read(suite) -> [];
meta_lookup_unnamed_read(Config) when is_list(Config) ->
- InitF = fun(_) -> Tab = ets:new(unnamed,[]),
+ InitF = fun(_) -> Tab = ets_new(unnamed,[]),
true = ets:insert(Tab,{key,data}),
Tab
end,
@@ -4727,7 +5044,7 @@ meta_lookup_unnamed_read(Config) when is_list(Config) ->
meta_lookup_unnamed_write(suite) -> [];
meta_lookup_unnamed_write(Config) when is_list(Config) ->
- InitF = fun(_) -> Tab = ets:new(unnamed,[]),
+ InitF = fun(_) -> Tab = ets_new(unnamed,[]),
{Tab,0}
end,
ExecF = fun({Tab,N}) -> true = ets:insert(Tab,{key,N}),
@@ -4740,7 +5057,7 @@ meta_lookup_unnamed_write(Config) when is_list(Config) ->
meta_lookup_named_read(suite) -> [];
meta_lookup_named_read(Config) when is_list(Config) ->
InitF = fun([ProcN|_]) -> Name = list_to_atom(integer_to_list(ProcN)),
- Tab = ets:new(Name,[named_table]),
+ Tab = ets_new(Name,[named_table]),
true = ets:insert(Tab,{key,data}),
Tab
end,
@@ -4754,7 +5071,7 @@ meta_lookup_named_read(Config) when is_list(Config) ->
meta_lookup_named_write(suite) -> [];
meta_lookup_named_write(Config) when is_list(Config) ->
InitF = fun([ProcN|_]) -> Name = list_to_atom(integer_to_list(ProcN)),
- Tab = ets:new(Name,[named_table]),
+ Tab = ets_new(Name,[named_table]),
{Tab,0}
end,
ExecF = fun({Tab,N}) -> true = ets:insert(Tab,{key,N}),
@@ -4767,7 +5084,7 @@ meta_lookup_named_write(Config) when is_list(Config) ->
meta_newdel_unnamed(suite) -> [];
meta_newdel_unnamed(Config) when is_list(Config) ->
InitF = fun(_) -> ok end,
- ExecF = fun(_) -> Tab = ets:new(unnamed,[]),
+ ExecF = fun(_) -> Tab = ets_new(unnamed,[]),
true = ets:delete(Tab)
end,
FiniF = fun(_) -> ok end,
@@ -4777,7 +5094,7 @@ meta_newdel_named(suite) -> [];
meta_newdel_named(Config) when is_list(Config) ->
InitF = fun([ProcN|_]) -> list_to_atom(integer_to_list(ProcN))
end,
- ExecF = fun(Name) -> Name = ets:new(Name,[named_table]),
+ ExecF = fun(Name) -> Name = ets_new(Name,[named_table]),
true = ets:delete(Name),
Name
end,
@@ -4787,7 +5104,7 @@ meta_newdel_named(Config) when is_list(Config) ->
smp_insert(doc) -> ["Concurrent insert's on same table"];
smp_insert(suite) -> [];
smp_insert(Config) when is_list(Config) ->
- ets:new(smp_insert,[named_table,public,{write_concurrency,true}]),
+ ets_new(smp_insert,[named_table,public,{write_concurrency,true}]),
InitF = fun(_) -> ok end,
ExecF = fun(_) -> true = ets:insert(smp_insert,{random:uniform(10000)})
end,
@@ -4802,7 +5119,7 @@ smp_fixed_delete(Config) when is_list(Config) ->
only_if_smp(fun()->smp_fixed_delete_do() end).
smp_fixed_delete_do() ->
- T = ets:new(foo,[public,{write_concurrency,true}]),
+ T = ets_new(foo,[public,{write_concurrency,true}]),
%%Mem = ets:info(T,memory),
NumOfObjs = 100000,
filltabint(T,NumOfObjs),
@@ -4838,7 +5155,7 @@ smp_unfix_fix(Config) when is_list(Config) ->
smp_unfix_fix_do() ->
process_flag(scheduler,1),
Parent = self(),
- T = ets:new(foo,[public,{write_concurrency,true}]),
+ T = ets_new(foo,[public,{write_concurrency,true}]),
%%Mem = ets:info(T,memory),
NumOfObjs = 100000,
Deleted = 50000,
@@ -4898,7 +5215,7 @@ otp_8166_do(WC) ->
%% Bug scenario: One process segv while reading the table because another
%% process is doing unfix without write-lock at the end of a trapping match_object.
process_flag(scheduler,1),
- T = ets:new(foo,[public, {write_concurrency,WC}]),
+ T = ets_new(foo,[public, {write_concurrency,WC}]),
NumOfObjs = 3000, %% Need more than 1000 live objects for match_object to trap one time
Deleted = NumOfObjs div 2,
filltabint(T,NumOfObjs),
@@ -5010,14 +5327,20 @@ verify_table_load(T) ->
end.
-
-
+otp_8732(doc) -> ["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"}),
+ ?line [] = ets:match(Tab,{'_',nomatch}), %% Will hang if bug not fixed
+ ok.
+
smp_select_delete(suite) -> [];
smp_select_delete(doc) ->
["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}]),
+ T = ets_new(smp_select_delete,[named_table,public,{write_concurrency,true}]),
Mod = 17,
Zeros = erlang:make_tuple(Mod,0),
InitF = fun(_) -> Zeros end,
@@ -5070,6 +5393,39 @@ smp_select_delete(Config) when is_list(Config) ->
?line false = ets:info(T,fixed),
ets:delete(T).
+types(doc) -> ["Test different types"];
+types(Config) when is_list(Config) ->
+ init_externals(),
+ repeat_for_opts(types_do,[[set,ordered_set],compressed]).
+
+types_do(Opts) ->
+ EtsMem = etsmem(),
+ ?line T = ets_new(xxx,Opts),
+ Fun = fun(Term) ->
+ ets:insert(T,{Term}),
+ ?line [{Term}] = ets:lookup(T,Term),
+ ets:insert(T,{Term,xxx}),
+ ?line [{Term,xxx}] = ets:lookup(T,Term),
+ ets:insert(T,{Term,"xxx"}),
+ ?line [{Term,"xxx"}] = ets:lookup(T,Term),
+ ets:insert(T,{xxx,Term}),
+ ?line [{xxx,Term}] = ets:lookup(T,xxx),
+ ets:insert(T,{"xxx",Term}),
+ ?line [{"xxx",Term}] = ets:lookup(T,"xxx"),
+ ets:delete_all_objects(T),
+ ?line 0 = ets:info(T,size)
+ end,
+ test_terms(Fun, strict),
+ ets:delete(T),
+ ?line verify_etsmem(EtsMem).
+
+
+
+
+%
+% Utility functions:
+%
+
add_lists(L1,L2) ->
add_lists(L1,L2,[]).
add_lists([],[],Acc) ->
@@ -5134,7 +5490,29 @@ my_tab_to_list(_Ts,'$end_of_table', Acc) -> lists:reverse(Acc);
my_tab_to_list(Ts,Key, Acc) ->
my_tab_to_list(Ts,ets:next(Ts,Key),[ets:lookup(Ts, Key)| Acc]).
+wait_for_all_schedulers_online_to_execute() ->
+ PMs = lists:map(fun (Sched) ->
+ spawn_opt(fun () -> ok end,
+ [monitor, {scheduler, Sched}])
+ end,
+ lists:seq(1,erlang:system_info(schedulers_online))),
+ lists:foreach(fun ({P, M}) ->
+ receive
+ {'DOWN', M, process, P, _} -> ok
+ end
+ end,
+ PMs),
+ ok.
+
etsmem() ->
+ %% Wait until it is guaranteed that all already scheduled
+ %% deallocations of DbTable structures have completed.
+ wait_for_all_schedulers_online_to_execute(),
+
+ 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()),
+ Mem =
{try erlang:memory(ets) catch error:notsup -> notsup end,
case erlang:system_info({allocator,ets_alloc}) of
false -> undefined;
@@ -5153,12 +5531,13 @@ etsmem() ->
{value,{_,BlSz,_,_}} = lists:keysearch(blocks_size, 1, L),
{Bl0+Bl,BlSz0+BlSz}
end, {0,0}, MSBCS)
- end}.
+ end},
+ {Mem,AllTabs}.
-verify_etsmem(MemInfo) ->
+verify_etsmem({MemInfo,AllTabs}) ->
wait_for_test_procs(),
case etsmem() of
- MemInfo ->
+ {MemInfo,_} ->
io:format("Ets mem info: ~p", [MemInfo]),
case MemInfo of
{ErlMem,EtsAlloc} when ErlMem == notsup; EtsAlloc == undefined ->
@@ -5167,12 +5546,15 @@ verify_etsmem(MemInfo) ->
_ ->
ok
end;
- Other ->
+ {MemInfo2, AllTabs2} ->
io:format("Expected: ~p", [MemInfo]),
- io:format("Actual: ~p", [Other]),
+ io:format("Actual: ~p", [MemInfo2]),
+ io:format("Changed tables before: ~p\n",[AllTabs -- AllTabs2]),
+ io:format("Changed tables after: ~p\n", [AllTabs2 -- AllTabs]),
?t:fail()
end.
+
start_loopers(N, Prio, Fun, State) ->
lists:map(fun (_) ->
my_spawn_opt(fun () -> looper(Fun, State) end,
@@ -5277,6 +5659,20 @@ repeat_while(Fun, Arg0) ->
{false,Ret} -> Ret
end.
+%% Some (but not all) permutations of List
+repeat_for_permutations(Fun, List) ->
+ repeat_for_permutations(Fun, List, length(List)-1).
+repeat_for_permutations(Fun, List, 0) ->
+ Fun(List);
+repeat_for_permutations(Fun, List, N) ->
+ {A,B} = lists:split(N, List),
+ L1 = B++A,
+ L2 = lists:reverse(L1),
+ L3 = B++lists:reverse(A),
+ L4 = lists:reverse(B)++A,
+ Fun(L1), Fun(L2), Fun(L3), Fun(L4),
+ repeat_for_permutations(Fun, List, N-1).
+
receive_any() ->
receive M ->
io:format("Process ~p got msg ~p\n", [self(),M]),
@@ -5332,22 +5728,232 @@ only_if_smp(Schedulers, Func) ->
{true,_} -> Func()
end.
+%% Copy-paste from emulator/test/binary_SUITE.erl
+-define(heap_binary_size, 64).
+test_terms(Test_Func, Mode) ->
+ garbage_collect(),
+ ?line Pib0 = process_info(self(),binary),
+
+ ?line Test_Func(atom),
+ ?line Test_Func(''),
+ ?line Test_Func('a'),
+ ?line Test_Func('ab'),
+ ?line Test_Func('abc'),
+ ?line Test_Func('abcd'),
+ ?line Test_Func('abcde'),
+ ?line Test_Func('abcdef'),
+ ?line Test_Func('abcdefg'),
+ ?line Test_Func('abcdefgh'),
+
+ ?line Test_Func(fun() -> ok end),
+ X = id([a,{b,c},c]),
+ Y = id({x,y,z}),
+ Z = id(1 bsl 8*257),
+ ?line Test_Func(fun() -> X end),
+ ?line Test_Func(fun() -> {X,Y} end),
+ ?line Test_Func([fun() -> {X,Y,Z} end,
+ fun() -> {Z,X,Y} end,
+ fun() -> {Y,Z,X} end]),
+
+ ?line Test_Func({trace_ts,{even_bigger,{some_data,fun() -> ok end}},{1,2,3}}),
+ ?line Test_Func({trace_ts,{even_bigger,{some_data,<<1,2,3,4,5,6,7,8,9,10>>}},
+ {1,2,3}}),
+
+ ?line Test_Func(1),
+ ?line Test_Func(42),
+ ?line Test_Func(-23),
+ ?line Test_Func(256),
+ ?line Test_Func(25555),
+ ?line Test_Func(-3333),
+
+ ?line Test_Func(1.0),
+
+ ?line Test_Func(183749783987483978498378478393874),
+ ?line Test_Func(-37894183749783987483978498378478393874),
+ Very_Big = very_big_num(),
+ ?line Test_Func(Very_Big),
+ ?line Test_Func(-Very_Big+1),
+
+ ?line Test_Func([]),
+ ?line Test_Func("abcdef"),
+ ?line Test_Func([a, b, 1, 2]),
+ ?line Test_Func([a|b]),
+
+ ?line Test_Func({}),
+ ?line Test_Func({1}),
+ ?line Test_Func({a, b}),
+ ?line Test_Func({a, b, c}),
+ ?line Test_Func(list_to_tuple(lists:seq(0, 255))),
+ ?line Test_Func(list_to_tuple(lists:seq(0, 256))),
+
+ ?line Test_Func(make_ref()),
+ ?line Test_Func([make_ref(), make_ref()]),
+
+ ?line Test_Func(make_port()),
+
+ ?line Test_Func(make_pid()),
+ ?line Test_Func(make_ext_pid()),
+ ?line Test_Func(make_ext_port()),
+ ?line Test_Func(make_ext_ref()),
+
+ Bin0 = list_to_binary(lists:seq(0, 14)),
+ ?line Test_Func(Bin0),
+ Bin1 = list_to_binary(lists:seq(0, ?heap_binary_size)),
+ ?line Test_Func(Bin1),
+ Bin2 = list_to_binary(lists:seq(0, ?heap_binary_size+1)),
+ ?line Test_Func(Bin2),
+ Bin3 = list_to_binary(lists:seq(0, 255)),
+ garbage_collect(),
+ Pib = process_info(self(),binary),
+ ?line Test_Func(Bin3),
+ garbage_collect(),
+ case Mode of
+ strict -> ?line Pib = process_info(self(),binary);
+ skip_refc_check -> ok
+ end,
+
+ ?line Test_Func(make_unaligned_sub_binary(Bin0)),
+ ?line Test_Func(make_unaligned_sub_binary(Bin1)),
+ ?line Test_Func(make_unaligned_sub_binary(Bin2)),
+ ?line Test_Func(make_unaligned_sub_binary(Bin3)),
+
+ ?line Test_Func(make_sub_binary(lists:seq(42, 43))),
+ ?line Test_Func(make_sub_binary([42,43,44])),
+ ?line Test_Func(make_sub_binary([42,43,44,45])),
+ ?line Test_Func(make_sub_binary([42,43,44,45,46])),
+ ?line Test_Func(make_sub_binary([42,43,44,45,46,47])),
+ ?line Test_Func(make_sub_binary([42,43,44,45,46,47,48])),
+ ?line Test_Func(make_sub_binary(lists:seq(42, 49))),
+ ?line Test_Func(make_sub_binary(lists:seq(0, 14))),
+ ?line Test_Func(make_sub_binary(lists:seq(0, ?heap_binary_size))),
+ ?line Test_Func(make_sub_binary(lists:seq(0, ?heap_binary_size+1))),
+ ?line Test_Func(make_sub_binary(lists:seq(0, 255))),
+
+ ?line Test_Func(make_unaligned_sub_binary(lists:seq(42, 43))),
+ ?line Test_Func(make_unaligned_sub_binary([42,43,44])),
+ ?line Test_Func(make_unaligned_sub_binary([42,43,44,45])),
+ ?line Test_Func(make_unaligned_sub_binary([42,43,44,45,46])),
+ ?line Test_Func(make_unaligned_sub_binary([42,43,44,45,46,47])),
+ ?line Test_Func(make_unaligned_sub_binary([42,43,44,45,46,47,48])),
+ ?line Test_Func(make_unaligned_sub_binary(lists:seq(42, 49))),
+ ?line Test_Func(make_unaligned_sub_binary(lists:seq(0, 14))),
+ ?line Test_Func(make_unaligned_sub_binary(lists:seq(0, ?heap_binary_size))),
+ ?line Test_Func(make_unaligned_sub_binary(lists:seq(0, ?heap_binary_size+1))),
+ ?line Test_Func(make_unaligned_sub_binary(lists:seq(0, 255))),
+
+ %% Bit level binaries.
+ ?line Test_Func(<<1:1>>),
+ ?line Test_Func(<<2:2>>),
+ ?line Test_Func(<<42:10>>),
+ ?line Test_Func(list_to_bitstring([<<5:6>>|lists:seq(0, 255)])),
+
+ ?line Test_Func(F = fun(A) -> 42*A end),
+ ?line Test_Func(lists:duplicate(32, F)),
+
+ ?line Test_Func(FF = fun binary_SUITE:all/1),
+ ?line Test_Func(lists:duplicate(32, FF)),
+
+ garbage_collect(),
+ case Mode of
+ strict -> ?line Pib0 = process_info(self(),binary);
+ skip_refc_check -> ok
+ end,
+ ok.
+
+
+id(I) -> I.
+
+very_big_num() ->
+ very_big_num(33, 1).
+
+very_big_num(Left, Result) when Left > 0 ->
+ ?line very_big_num(Left-1, Result*256);
+very_big_num(0, Result) ->
+ ?line Result.
+
+make_port() ->
+ ?line open_port({spawn, efile}, [eof]).
+
+make_pid() ->
+ ?line spawn_link(?MODULE, sleeper, []).
+
+sleeper() ->
+ ?line receive after infinity -> ok end.
+
+make_ext_pid() ->
+ {Pid, _, _} = get(externals),
+ Pid.
+
+make_ext_port() ->
+ {_, Port, _} = get(externals),
+ Port.
+make_ext_ref() ->
+ {_, _, Ref} = get(externals),
+ Ref.
+
+init_externals() ->
+ case get(externals) of
+ undefined ->
+ SysDistSz = ets:info(sys_dist,size),
+ ?line Pa = filename:dirname(code:which(?MODULE)),
+ ?line {ok, Node} = test_server:start_node(plopp, slave, [{args, " -pa " ++ Pa}]),
+ ?line Res = case rpc:call(Node, ?MODULE, rpc_externals, []) of
+ {badrpc, {'EXIT', E}} ->
+ test_server:fail({rpcresult, E});
+ R -> R
+ end,
+ ?line test_server:stop_node(Node),
+
+ %% Wait for table 'sys_dist' to stabilize
+ repeat_while(fun() ->
+ case ets:info(sys_dist,size) of
+ SysDistSz -> false;
+ Sz ->
+ io:format("Waiting for sys_dist to revert size from ~p to size ~p\n",
+ [Sz, SysDistSz]),
+ receive after 1000 -> true end
+ end
+ end),
+ put(externals, Res);
+
+ {_,_,_} -> ok
+ end.
+
+rpc_externals() ->
+ {self(), make_port(), make_ref()}.
+
+make_sub_binary(Bin) when is_binary(Bin) ->
+ {_,B} = split_binary(list_to_binary([0,1,3,Bin]), 3),
+ B;
+make_sub_binary(List) ->
+ make_sub_binary(list_to_binary(List)).
+
+make_unaligned_sub_binary(Bin0) when is_binary(Bin0) ->
+ Bin1 = <<0:3,Bin0/binary,31:5>>,
+ Sz = size(Bin0),
+ <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
+ Bin;
+make_unaligned_sub_binary(List) ->
+ make_unaligned_sub_binary(list_to_binary(List)).
%% Repeat test function with different combination of table options
%%
repeat_for_opts(F) ->
- repeat_for_opts(F, [write_concurrency]).
+ repeat_for_opts(F, [write_concurrency, read_concurrency, compressed]).
repeat_for_opts(F, OptGenList) when is_atom(F) ->
repeat_for_opts(fun(Opts) -> ?MODULE:F(Opts) end, OptGenList);
+repeat_for_opts({F,Args}, OptGenList) when is_atom(F) ->
+ repeat_for_opts(fun(Opts) -> ?MODULE:F(Opts,Args) end, OptGenList);
repeat_for_opts(F, OptGenList) ->
repeat_for_opts(F, OptGenList, []).
repeat_for_opts(F, [], Acc) ->
- lists:map(fun(Opts) ->
- io:format("Calling with options ~p\n",[Opts]),
- F(Opts)
- end, Acc);
+ lists:map(fun(Opts) ->
+ OptList = lists:filter(fun(E) -> E =/= void end, Opts),
+ io:format("Calling with options ~p\n",[OptList]),
+ F(OptList)
+ 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) ->
@@ -5356,6 +5962,10 @@ 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(write_concurrency) -> [{write_concurrency,false},{write_concurrency,true}].
-
+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).
diff --git a/lib/stdlib/test/ets_tough_SUITE.erl b/lib/stdlib/test/ets_tough_SUITE.erl
index 4c8d941f13..0386a0272a 100644
--- a/lib/stdlib/test/ets_tough_SUITE.erl
+++ b/lib/stdlib/test/ets_tough_SUITE.erl
@@ -17,13 +17,33 @@
%% %CopyrightEnd%
%%
-module(ets_tough_SUITE).
--export([all/1,ex1/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,ex1/1]).
-export([init/1,terminate/2,handle_call/3,handle_info/2]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
-compile([export_all]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
+
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [ex1].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
-all(suite) -> [ex1].
-define(DEBUG(X),debug_disabled).
@@ -34,7 +54,7 @@ init_per_testcase(_Func, Config) ->
Dog=test_server:timetrap(test_server:seconds(300)),
[{watchdog, Dog}|Config].
-fin_per_testcase(_Func, Config) ->
+end_per_testcase(_Func, Config) ->
Dog=?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ets:delete(?GLOBAL_PARAMS).
diff --git a/lib/stdlib/test/file_sorter_SUITE.erl b/lib/stdlib/test/file_sorter_SUITE.erl
index c00ed91fe7..9ca2460a05 100644
--- a/lib/stdlib/test/file_sorter_SUITE.erl
+++ b/lib/stdlib/test/file_sorter_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2001-2009. All Rights Reserved.
+%% Copyright Ericsson AB 2001-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
@@ -27,12 +27,13 @@
-define(t,test_server).
-define(privdir(_), "./file_sorter_SUITE_priv").
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(format(S, A), ok).
-define(privdir(Conf), ?config(priv_dir, Conf)).
-endif.
--export([all/1, basic/1, badarg/1,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2, basic/1, badarg/1,
term_sort/1, term_keysort/1,
binary_term_sort/1, binary_term_keysort/1,
binary_sort/1,
@@ -44,30 +45,42 @@
binary_check/1,
inout/1, misc/1, many/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
init_per_testcase(_Case, Config) ->
Dog=?t:timetrap(?t:minutes(2)),
[{watchdog, Dog}|Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog=?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
-all(suite) ->
- {req,[stdlib,kernel],
- [basic, badarg,
- term_sort, term_keysort,
- binary_term_sort, binary_term_keysort,
- binary_sort,
- term_merge, term_keymerge,
- binary_term_merge, binary_term_keymerge,
- binary_merge,
- term_check, binary_term_keycheck,
- binary_term_check, binary_term_keycheck,
- binary_check,
- inout, misc, many]}.
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [basic, badarg, term_sort, term_keysort,
+ binary_term_sort, binary_term_keysort, binary_sort,
+ term_merge, term_keymerge, binary_term_merge,
+ binary_term_keymerge, binary_merge, term_check,
+ binary_term_keycheck, binary_term_check,
+ binary_term_keycheck, binary_check, inout, misc, many].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
basic(doc) ->
["Basic test case."];
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index d54741051f..628e741870 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -19,27 +19,47 @@
-module(filelib_SUITE).
--export([all/1,init_per_testcase/2,fin_per_testcase/2,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
+ init_per_testcase/2,end_per_testcase/2,
wildcard_one/1,wildcard_two/1,wildcard_errors/1,
fold_files/1,otp_5960/1,ensure_dir_eexist/1]).
-import(lists, [foreach/2]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-include_lib("kernel/include/file.hrl").
init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?t:minutes(5)),
[{watchdog,Dog}|Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog = ?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
-all(suite) ->
- [wildcard_one,wildcard_two,wildcard_errors,fold_files,otp_5960,
- ensure_dir_eexist].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [wildcard_one, wildcard_two, wildcard_errors,
+ fold_files, otp_5960, ensure_dir_eexist].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
wildcard_one(Config) when is_list(Config) ->
?line {ok,OldCwd} = file:get_cwd(),
@@ -53,8 +73,11 @@ wildcard_one(Config) when is_list(Config) ->
wildcard_two(Config) when is_list(Config) ->
?line Dir = filename:join(?config(priv_dir, Config), "wildcard_two"),
+ ?line DirB = unicode:characters_to_binary(Dir, file:native_name_encoding()),
?line ok = file:make_dir(Dir),
- ?line do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc, Dir) end),
+ ?line do_wildcard_1(Dir, fun(Wc) -> io:format("~p~n",[{Wc,Dir, X = filelib:wildcard(Wc, Dir)}]),X end),
+ ?line do_wildcard_1(Dir, fun(Wc) -> io:format("~p~n",[{Wc,DirB, X = filelib:wildcard(Wc, DirB)}]),
+ [unicode:characters_to_list(Y,file:native_name_encoding()) || Y <- X] end),
?line do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc, Dir++"/") end),
case os:type() of
{win32,_} ->
@@ -253,5 +276,7 @@ ensure_dir_eexist(Config) when is_list(Config) ->
%% There already is a file with the name of the directory
%% we want to create.
?line NeedFile = filename:join(Name, "file"),
+ ?line NeedFileB = filename:join(Name, <<"file">>),
?line {error, eexist} = filelib:ensure_dir(NeedFile),
+ ?line {error, eexist} = filelib:ensure_dir(NeedFileB),
ok.
diff --git a/lib/stdlib/test/filename_SUITE.erl b/lib/stdlib/test/filename_SUITE.erl
index ab6521f37b..a72af3448b 100644
--- a/lib/stdlib/test/filename_SUITE.erl
+++ b/lib/stdlib/test/filename_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1997-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
@@ -17,17 +17,44 @@
%% %CopyrightEnd%
%%
-module(filename_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
-export([absname/1, absname_2/1,
basename_1/1, basename_2/1,
dirname/1, extension/1, join/1, t_nativename/1]).
-export([pathtype/1,rootname/1,split/1,find_src/1]).
--include("test_server.hrl").
+-export([absname_bin/1, absname_bin_2/1,
+ basename_bin_1/1, basename_bin_2/1,
+ dirname_bin/1, extension_bin/1, join_bin/1]).
+-export([pathtype_bin/1,rootname_bin/1,split_bin/1]).
-all(suite) ->
+-include_lib("test_server/include/test_server.hrl").
+
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
[absname, absname_2, basename_1, basename_2, dirname,
extension,
- join, pathtype, rootname, split, t_nativename, find_src].
+ join, pathtype, rootname, split, t_nativename, find_src,
+ absname_bin, absname_bin_2, basename_bin_1, basename_bin_2, dirname_bin,
+ extension_bin,
+ join_bin, pathtype_bin, rootname_bin, split_bin].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -457,3 +484,307 @@ find_src(Config) when is_list(Config) ->
%% Try to find the source for a preloaded module.
?line {error,{preloaded,init}} = filename:find_src(init),
ok.
+
+%%
+%%
+%% With binaries
+%%
+%%
+
+absname_bin(Config) when is_list(Config) ->
+ case os:type() of
+ {win32, _} ->
+ ?line [Drive|_] = ?config(priv_dir, Config),
+ ?line Temp = filename:join([Drive|":/"], "temp"),
+ ?line case file:make_dir(Temp) of
+ ok -> ok;
+ {error,eexist} -> ok
+ end,
+ ?line {ok,Cwd} = file:get_cwd(),
+ ?line ok = file:set_cwd(Temp),
+ ?line <<Drive:8,":/temp/foo">> = filename:absname(<<"foo">>),
+ ?line <<Drive:8,":/temp/../ebin">> = filename:absname(<<"../ebin">>),
+ ?line <<Drive:8,":/erlang">> = filename:absname(<<"/erlang">>),
+ ?line <<Drive:8,":/erlang/src">> = filename:absname(<<"/erlang/src">>),
+ ?line <<Drive:8,":/erlang/src">> = filename:absname(<<"\\erlang\\src">>),
+ ?line <<Drive:8,":/temp/erlang">> = filename:absname(<<Drive:8,":erlang">>),
+ ?line <<Drive:8,":/temp/erlang/src">> =
+ filename:absname(<<Drive:8,":erlang/src">>),
+ ?line <<Drive:8,":/temp/erlang/src">> =
+ filename:absname(<<Drive:8,":erlang\\src\\">>),
+ ?line <<"a:/erlang">> = filename:absname(<<"a:erlang">>),
+
+ ?line file:set_cwd(<<Drive:8,":/">>),
+ ?line <<Drive:8,":/foo">> = filename:absname(<<"foo">>),
+ ?line <<Drive:8,":/../ebin">> = filename:absname(<<"../ebin">>),
+ ?line <<Drive:8,":/erlang">> = filename:absname(<<"/erlang">>),
+ ?line <<Drive:8,":/erlang/src">> = filename:absname(<<"/erlang/src">>),
+ ?line <<Drive:8,":/erlang/src">> = filename:absname(<<"\\erlang\\\\src">>),
+ ?line <<Drive:8,":/erlang">> = filename:absname(<<Drive:8,":erlang">>),
+ ?line <<Drive:8,":/erlang/src">> = filename:absname(<<Drive:8,":erlang/src">>),
+ ?line <<"a:/erlang">> = filename:absname(<<"a:erlang">>),
+
+ ?line file:set_cwd(Cwd),
+ ok;
+ {unix, _} ->
+ ?line ok = file:set_cwd(<<"/usr">>),
+ ?line <<"/usr/foo">> = filename:absname(<<"foo">>),
+ ?line <<"/usr/../ebin">> = filename:absname(<<"../ebin">>),
+
+ ?line file:set_cwd(<<"/">>),
+ ?line <<"/foo">> = filename:absname(<<"foo">>),
+ ?line <<"/../ebin">> = filename:absname(<<"../ebin">>),
+ ?line <<"/erlang">> = filename:absname(<<"/erlang">>),
+ ?line <<"/erlang/src">> = filename:absname(<<"/erlang/src">>),
+ ?line <<"/erlang/src">> = filename:absname(<<"/erlang///src">>),
+ ok
+ end.
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+absname_bin_2(Config) when is_list(Config) ->
+ case os:type() of
+ {win32, _} ->
+ ?line [Drive|_] = ?config(priv_dir, Config),
+ ?line <<Drive:8,":/temp/foo">> = filename:absname(<<"foo">>, <<Drive:8,":/temp">>),
+ ?line <<Drive:8,":/temp/../ebin">> = filename:absname(<<"../ebin">>,
+ <<Drive:8,":/temp">>),
+ ?line <<Drive:8,":/erlang">> = filename:absname(<<"/erlang">>, <<Drive:8,":/temp">>),
+ ?line <<Drive:8,":/erlang/src">> = filename:absname(<<"/erlang/src">>,
+ <<Drive:8,":/temp">>),
+ ?line <<Drive:8,":/erlang/src">> = filename:absname(<<"\\erlang\\src">>,
+ <<Drive:8,":/temp">>),
+ ?line <<Drive:8,":/temp/erlang">> = filename:absname(<<Drive:8,":erlang">>,
+ <<Drive:8,":/temp">>),
+ ?line <<Drive:8,":/temp/erlang/src">> = filename:absname(<<Drive:8,":erlang/src">>,
+ <<Drive:8,":/temp">>),
+ ?line <<Drive:8,":/temp/erlang/src">> =
+ filename:absname(<<Drive:8,":erlang\\src\\">>, <<Drive:8,":/temp">>),
+ ?line <<"a:/erlang">> = filename:absname(<<"a:erlang">>, <<Drive:8,":/temp">>),
+
+ ?line file:set_cwd(<<Drive:8,":/">>),
+ ?line <<Drive:8,":/foo">> = filename:absname(foo, <<Drive:8,":/">>),
+ ?line <<Drive:8,":/foo">> = filename:absname(<<"foo">>, <<Drive:8,":/">>),
+ ?line <<Drive:8,":/../ebin">> = filename:absname(<<"../ebin">>, <<Drive:8,":/">>),
+ ?line <<Drive:8,":/erlang">> = filename:absname(<<"/erlang">>, <<Drive:8,":/">>),
+ ?line <<Drive:8,":/erlang/src">> = filename:absname(<<"/erlang/src">>,
+ <<Drive:8,":/">>),
+ ?line <<Drive:8,":/erlang/src">> = filename:absname(<<"\\erlang\\\\src">>,
+ <<Drive:8,":/">>),
+ ?line <<Drive:8,":/erlang">> = filename:absname(<<Drive:8,":erlang">>,
+ <<Drive:8,":/">>),
+ ?line <<Drive:8,":/erlang/src">> = filename:absname(<<Drive:8,":erlang/src">>,
+ <<Drive:8,":/">>),
+ ?line <<"a:/erlang">> = filename:absname(<<"a:erlang">>, <<Drive:8,":/">>),
+
+ ok;
+ {unix, _} ->
+ ?line <<"/usr/foo">> = filename:absname(<<"foo">>, <<"/usr">>),
+ ?line <<"/usr/../ebin">> = filename:absname(<<"../ebin">>, <<"/usr">>),
+
+ ?line <<"/foo">> = filename:absname(<<"foo">>, <<"/">>),
+ ?line <<"/../ebin">> = filename:absname(<<"../ebin">>, <<"/">>),
+ ?line <<"/erlang">> = filename:absname(<<"/erlang">>, <<"/">>),
+ ?line <<"/erlang/src">> = filename:absname(<<"/erlang/src">>, <<"/">>),
+ ?line <<"/erlang/src">> = filename:absname(<<"/erlang///src">>, <<"/">>),
+ ok
+ end.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+basename_bin_1(Config) when is_list(Config) ->
+ ?line Dog = test_server:timetrap(test_server:seconds(10)),
+ ?line <<".">> = filename:basename(<<".">>),
+ ?line <<"foo">> = filename:basename(<<"foo">>),
+ ?line <<"foo">> = filename:basename(<<"/usr/foo">>),
+ ?line <<"foo.erl">> = filename:basename(<<"A:usr/foo.erl">>),
+ ?line case os:type() of
+ {win32, _} ->
+ ?line <<"foo">> = filename:basename(<<"A:\\usr\\foo">>),
+ ?line <<"foo">> = filename:basename(<<"A:foo">>);
+ {unix, _} ->
+ ?line <<"strange\\but\\true">> =
+ filename:basename(<<"strange\\but\\true">>)
+ end,
+ ?line test_server:timetrap_cancel(Dog),
+ ok.
+
+basename_bin_2(Config) when is_list(Config) ->
+ ?line Dog = test_server:timetrap(test_server:seconds(10)),
+ ?line <<".">> = filename:basename(<<".">>, <<".erl">>),
+ ?line <<"foo">> = filename:basename(<<"foo.erl">>, <<".erl">>),
+ ?line <<"foo.erl">> = filename:basename(<<"/usr/foo.erl">>, <<".hrl">>),
+ ?line <<"foo.erl">> = filename:basename(<<"/usr.hrl/foo.erl">>, <<".hrl">>),
+ ?line <<"foo">> = filename:basename(<<"/usr.hrl/foo">>, <<".hrl">>),
+ ?line <<"foo">> = filename:basename(<<"usr/foo/">>, <<".erl">>),
+ ?line <<"foo.erl">> = filename:basename(<<"usr/foo.erl/">>, <<".erl">>),
+ ?line case os:type() of
+ {win32, _} ->
+ ?line <<"foo">> = filename:basename(<<"A:foo">>, <<".erl">>),
+ ?line <<"foo.erl">> = filename:basename(<<"a:\\usr\\foo.erl">>,
+ <<".hrl">>),
+ ?line <<"foo.erl">> = filename:basename(<<"c:\\usr.hrl\\foo.erl">>,
+ <<".hrl">>),
+ ?line <<"foo">> = filename:basename(<<"A:\\usr\\foo">>, <<".hrl">>);
+ {unix, _} ->
+ ?line <<"strange\\but\\true">> =
+ filename:basename(<<"strange\\but\\true.erl">>, <<".erl">>),
+ ?line <<"strange\\but\\true">> =
+ filename:basename(<<"strange\\but\\true">>, <<".erl">>)
+ end,
+ ?line test_server:timetrap_cancel(Dog),
+ ok.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+dirname_bin(Config) when is_list(Config) ->
+ case os:type() of
+ {win32,_} ->
+ ?line <<"A:/usr">> = filename:dirname(<<"A:/usr/foo.erl">>),
+ ?line <<"A:usr">> = filename:dirname(<<"A:usr/foo.erl">>),
+ ?line <<"/usr">> = filename:dirname(<<"\\usr\\foo.erl">>),
+ ?line <<"/">> = filename:dirname(<<"\\usr">>),
+ ?line <<"A:">> = filename:dirname(<<"A:">>);
+ vxworks ->
+ ?line <<"net:/usr">> = filename:dirname(<<"net:/usr/foo.erl">>),
+ ?line <<"/disk0:/usr">> = filename:dirname(<<"/disk0:/usr/foo.erl">>),
+ ?line <<"/usr">> = filename:dirname(<<"\\usr\\foo.erl">>),
+ ?line <<"/usr">> = filename:dirname(<<"\\usr">>),
+ ?line <<"net:">> = filename:dirname(<<"net:">>);
+ _ -> true
+ end,
+ ?line <<"usr">> = filename:dirname(<<"usr///foo.erl">>),
+ ?line <<".">> = filename:dirname(<<"foo.erl">>),
+ ?line <<".">> = filename:dirname(<<".">>),
+ case os:type() of
+ vxworks ->
+ ?line <<"/">> = filename:dirname(<<"/">>),
+ ?line <<"/usr">> = filename:dirname(<<"/usr">>);
+ _ ->
+ ?line <<"/">> = filename:dirname(<<"/">>),
+ ?line <<"/">> = filename:dirname(<<"/usr">>)
+ end,
+ ok.
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+extension_bin(Config) when is_list(Config) ->
+ ?line <<".erl">> = filename:extension(<<"A:/usr/foo.erl">>),
+ ?line <<".erl">> = filename:extension(<<"A:/usr/foo.nisse.erl">>),
+ ?line <<".erl">> = filename:extension(<<"A:/usr.bar/foo.nisse.erl">>),
+ ?line <<"">> = filename:extension(<<"A:/usr.bar/foo">>),
+ ?line <<"">> = filename:extension(<<"A:/usr/foo">>),
+ ?line case os:type() of
+ {win32, _} ->
+ ?line <<"">> = filename:extension(<<"A:\\usr\\foo">>),
+ ?line <<".erl">> =
+ filename:extension(<<"A:/usr.bar/foo.nisse.erl">>),
+ ?line <<"">> = filename:extension(<<"A:/usr.bar/foo">>),
+ ok;
+ vxworks ->
+ ?line <<"">> = filename:extension(<<"/disk0:\\usr\\foo">>),
+ ?line <<".erl">> =
+ filename:extension(<<"net:/usr.bar/foo.nisse.erl">>),
+ ?line <<"">> = filename:extension(<<"net:/usr.bar/foo">>),
+ ok;
+ _ -> ok
+ end.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+join_bin(Config) when is_list(Config) ->
+ ?line <<"/">> = filename:join([<<"/">>]),
+ ?line <<"/">> = filename:join([<<"//">>]),
+ ?line <<"usr/foo.erl">> = filename:join(<<"usr">>,<<"foo.erl">>),
+ ?line <<"/src/foo.erl">> = filename:join(usr, <<"/src/foo.erl">>),
+ ?line <<"/src/foo.erl">> = filename:join([<<"/src/">>,'foo.erl']),
+ ?line <<"/src/foo.erl">> = filename:join(<<"usr">>, ["/sr", 'c/foo.erl']),
+ ?line <<"/src/foo.erl">> = filename:join(<<"usr">>, <<"/src/foo.erl">>),
+
+ %% Make sure that redundant slashes work too.
+ ?line <<"a/b/c/d/e/f/g">> = filename:join([<<"a//b/c/////d//e/f/g">>]),
+ ?line <<"a/b/c/d/e/f/g">> = filename:join([<<"a//b/c/">>, <<"d//e/f/g">>]),
+ ?line <<"a/b/c/d/e/f/g">> = filename:join([<<"a//b/c">>, <<"d//e/f/g">>]),
+ ?line <<"/d/e/f/g">> = filename:join([<<"a//b/c">>, <<"/d//e/f/g">>]),
+ ?line <<"/d/e/f/g">> = filename:join([<<"a//b/c">>, <<"//d//e/f/g">>]),
+
+ ?line <<"foo/bar">> = filename:join([$f,$o,$o,$/,[]], <<"bar">>),
+
+ ?line case os:type() of
+ {win32, _} ->
+ ?line <<"d:/">> = filename:join([<<"D:/">>]),
+ ?line <<"d:/">> = filename:join([<<"D:\\">>]),
+ ?line <<"d:/abc">> = filename:join([<<"D:/">>, <<"abc">>]),
+ ?line <<"d:abc">> = filename:join([<<"D:">>, <<"abc">>]),
+ ?line <<"a/b/c/d/e/f/g">> =
+ filename:join([<<"a//b\\c//\\/\\d/\\e/f\\g">>]),
+ ?line <<"a:usr/foo.erl">> =
+ filename:join([<<"A:">>,<<"usr">>,<<"foo.erl">>]),
+ ?line <<"/usr/foo.erl">> =
+ filename:join([<<"A:">>,<<"/usr">>,<<"foo.erl">>]),
+ ?line <<"c:usr">> = filename:join(<<"A:">>,<<"C:usr">>),
+ ?line <<"a:usr">> = filename:join(<<"A:">>,<<"usr">>),
+ ?line <<"c:/usr">> = filename:join(<<"A:">>, <<"C:/usr">>),
+ ?line <<"c:/usr/foo.erl">> =
+ filename:join([<<"A:">>,<<"C:/usr">>,<<"foo.erl">>]),
+ ?line <<"c:usr/foo.erl">> =
+ filename:join([<<"A:">>,<<"C:usr">>,<<"foo.erl">>]),
+ ?line <<"d:/foo">> = filename:join([$D, $:, $/, []], <<"foo">>),
+ ok;
+ {unix, _} ->
+ ok
+ end.
+
+pathtype_bin(Config) when is_list(Config) ->
+ ?line relative = filename:pathtype(<<"..">>),
+ ?line relative = filename:pathtype(<<"foo">>),
+ ?line relative = filename:pathtype(<<"foo/bar">>),
+ ?line relative = filename:pathtype('foo/bar'),
+ case os:type() of
+ {win32, _} ->
+ ?line volumerelative = filename:pathtype(<<"/usr/local/bin">>),
+ ?line volumerelative = filename:pathtype(<<"A:usr/local/bin">>),
+ ok;
+ {unix, _} ->
+ ?line absolute = filename:pathtype(<<"/">>),
+ ?line absolute = filename:pathtype(<<"/usr/local/bin">>),
+ ok
+ end.
+
+rootname_bin(Config) when is_list(Config) ->
+ ?line <<"/jam.src/kalle">> = filename:rootname(<<"/jam.src/kalle">>),
+ ?line <<"/jam.src/foo">> = filename:rootname(<<"/jam.src/foo.erl">>),
+ ?line <<"/jam.src/foo">> = filename:rootname(<<"/jam.src/foo.erl">>, <<".erl">>),
+ ?line <<"/jam.src/foo.jam">> = filename:rootname(<<"/jam.src/foo.jam">>, <<".erl">>),
+ ?line <<"/jam.src/foo.jam">> = filename:rootname(["/jam.sr",'c/foo.j',"am"],<<".erl">>),
+ ?line <<"/jam.src/foo.jam">> = filename:rootname(["/jam.sr",'c/foo.j'|am],<<".erl">>),
+ ok.
+
+split_bin(Config) when is_list(Config) ->
+ case os:type() of
+ vxworks ->
+ ?line [<<"/usr">>,<<"local">>,<<"bin">>] = filename:split(<<"/usr/local/bin">>);
+ _ ->
+ ?line [<<"/">>,<<"usr">>,<<"local">>,<<"bin">>] = filename:split(<<"/usr/local/bin">>)
+ end,
+ ?line [<<"foo">>,<<"bar">>]= filename:split(<<"foo/bar">>),
+ ?line [<<"foo">>, <<"bar">>, <<"hello">>]= filename:split(<<"foo////bar//hello">>),
+ case os:type() of
+ {win32,_} ->
+ ?line [<<"a:/">>,<<"msdev">>,<<"include">>] =
+ filename:split(<<"a:/msdev/include">>),
+ ?line [<<"a:/">>,<<"msdev">>,<<"include">>] =
+ filename:split(<<"A:/msdev/include">>),
+ ?line [<<"msdev">>,<<"include">>] =
+ filename:split(<<"msdev\\include">>),
+ ?line [<<"a:/">>,<<"msdev">>,<<"include">>] =
+ filename:split(<<"a:\\msdev\\include">>),
+ ?line [<<"a:">>,<<"msdev">>,<<"include">>] =
+ filename:split(<<"a:msdev\\include">>),
+ ok;
+ _ ->
+ ok
+ end.
+
diff --git a/lib/stdlib/test/fixtable_SUITE.erl b/lib/stdlib/test/fixtable_SUITE.erl
index 1940ee147e..c2160d8ba7 100644
--- a/lib/stdlib/test/fixtable_SUITE.erl
+++ b/lib/stdlib/test/fixtable_SUITE.erl
@@ -21,22 +21,41 @@
%%%----------------------------------------------------------------------
-module(fixtable_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
%%% Test cases
-export([multiple_fixes/1, multiple_processes/1,
other_process_deletes/1, owner_dies/1,
other_process_closes/1,insert_same_key/1]).
-export([fixbag/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
%%% Internal exports
-export([command_loop/0,start_commander/0]).
-all(suite) -> {req, [stdlib],
- [multiple_fixes, multiple_processes,
- other_process_deletes, owner_dies,
- other_process_closes,insert_same_key,fixbag]}.
+suite() -> [{ct_hooks,[ts_install_cth]}].
--include("test_server.hrl").
+all() ->
+ [multiple_fixes, multiple_processes,
+ other_process_deletes, owner_dies, other_process_closes,
+ insert_same_key, fixbag].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
+-include_lib("test_server/include/test_server.hrl").
%%% I wrote this thinking I would use more than one temporary at a time, but
%%% I wasn't... Well, maybe in the future...
@@ -53,7 +72,7 @@ init_per_testcase(_Func, Config) ->
Dog=test_server:timetrap(test_server:seconds(60)),
[{watchdog, Dog}|Config].
-fin_per_testcase(_Func, Config) ->
+end_per_testcase(_Func, Config) ->
Dog=?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
lists:foreach(fun(X) ->
diff --git a/lib/stdlib/test/format_SUITE.erl b/lib/stdlib/test/format_SUITE.erl
index 1c9e953003..c1a896abe8 100644
--- a/lib/stdlib/test/format_SUITE.erl
+++ b/lib/stdlib/test/format_SUITE.erl
@@ -17,13 +17,14 @@
%% %CopyrightEnd%
%%
-module(format_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
-export([hang_1/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
% Default timetrap timeout (set in init_per_testcase).
-define(default_timeout, ?t:minutes(1)).
@@ -31,16 +32,32 @@
init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog = ?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
-all(doc) ->
- ["Test cases for io:format/[2,3]."];
-all(suite) ->
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
[hang_1].
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
hang_1(doc) ->
["Bad args can hang (OTP-2400)"];
hang_1(suite) ->
diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl
index 8cbffaca56..8fa2f4e3a3 100644
--- a/lib/stdlib/test/gen_event_SUITE.erl
+++ b/lib/stdlib/test/gen_event_SUITE.erl
@@ -18,14 +18,39 @@
%%
-module(gen_event_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
--export([all/1]).
--export([start/1, test_all/1, add_handler/1, add_sup_handler/1,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
+-export([start/1, add_handler/1, add_sup_handler/1,
delete_handler/1, swap_handler/1, swap_sup_handler/1,
- notify/1, sync_notify/1, call/1, info/1, hibernate/1]).
+ notify/1, sync_notify/1, call/1, info/1, hibernate/1,
+ call_format_status/1, error_format_status/1]).
+
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [start, {group, test_all}, hibernate,
+ call_format_status, error_format_status].
+
+groups() ->
+ [{test_all, [],
+ [add_handler, add_sup_handler, delete_handler,
+ swap_handler, swap_sup_handler, notify, sync_notify,
+ call, info]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
-all(suite) -> {req, [stdlib], [start, test_all, hibernate]}.
%% --------------------------------------
%% Start an event manager.
@@ -169,9 +194,6 @@ hibernate(Config) when is_list(Config) ->
ok.
-test_all(suite) -> [add_handler, add_sup_handler, delete_handler,
- swap_handler, swap_sup_handler, notify,
- sync_notify, call, info].
add_handler(doc) -> [];
add_handler(suite) -> [];
@@ -844,3 +866,56 @@ info(Config) when is_list(Config) ->
?line ok = gen_event:stop(my_dummy_handler),
ok.
+
+call_format_status(suite) ->
+ [];
+call_format_status(doc) ->
+ ["Test that sys:get_status/1,2 calls format_status/2"];
+call_format_status(Config) when is_list(Config) ->
+ ?line {ok, Pid} = gen_event:start({local, my_dummy_handler}),
+ %% State here intentionally differs from what we expect from format_status
+ State = self(),
+ FmtState = "dummy1_h handler state",
+ ?line ok = gen_event:add_handler(my_dummy_handler, dummy1_h, [State]),
+ ?line Status1 = sys:get_status(Pid),
+ ?line Status2 = sys:get_status(Pid, 5000),
+ ?line ok = gen_event:stop(Pid),
+ ?line {status, Pid, _, [_, _, Pid, [], Data1]} = Status1,
+ ?line HandlerInfo1 = proplists:get_value(items, Data1),
+ ?line {"Installed handlers", [{_,dummy1_h,_,FmtState,_}]} = HandlerInfo1,
+ ?line {status, Pid, _, [_, _, Pid, [], Data2]} = Status2,
+ ?line HandlerInfo2 = proplists:get_value(items, Data2),
+ ?line {"Installed handlers", [{_,dummy1_h,_,FmtState,_}]} = HandlerInfo2,
+ ok.
+
+error_format_status(suite) ->
+ [];
+error_format_status(doc) ->
+ ["Test that a handler error calls format_status/2"];
+error_format_status(Config) when is_list(Config) ->
+ ?line error_logger_forwarder:register(),
+ OldFl = process_flag(trap_exit, true),
+ State = self(),
+ ?line {ok, Pid} = gen_event:start({local, my_dummy_handler}),
+ ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy1_h, [State]),
+ ?line ok = gen_event:notify(my_dummy_handler, do_crash),
+ ?line receive
+ {gen_event_EXIT,dummy1_h,{'EXIT',_}} -> ok
+ after 5000 ->
+ ?t:fail(exit_gen_event)
+ end,
+ FmtState = "dummy1_h handler state",
+ receive
+ {error,_GroupLeader, {Pid,
+ "** gen_event handler"++_,
+ [dummy1_h,my_dummy_handler,do_crash,
+ FmtState, _]}} ->
+ ok;
+ Other ->
+ ?line io:format("Unexpected: ~p", [Other]),
+ ?line ?t:fail()
+ end,
+ ?t:messages_get(),
+ ?line ok = gen_event:stop(Pid),
+ process_flag(trap_exit, OldFl),
+ ok.
diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl
index 23c1d9a193..9d9e1f8dd8 100644
--- a/lib/stdlib/test/gen_fsm_SUITE.erl
+++ b/lib/stdlib/test/gen_fsm_SUITE.erl
@@ -1,36 +1,37 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 1996-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(gen_fsm_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
%% Test cases
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
--export([start/1, start1/1, start2/1, start3/1, start4/1 , start5/1, start6/1,
+-export([ start1/1, start2/1, start3/1, start4/1 , start5/1, start6/1,
start7/1, start8/1, start9/1, start10/1, start11/1]).
--export([abnormal/1, abnormal1/1, abnormal2/1]).
+-export([ abnormal1/1, abnormal2/1]).
-export([shutdown/1]).
--export([sys/1, sys1/1, call_format_status/1]).
+-export([ sys1/1, call_format_status/1, error_format_status/1]).
-export([hibernate/1,hiber_idle/3,hiber_wakeup/3,hiber_idle/2,hiber_wakeup/2]).
@@ -53,13 +54,31 @@
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-all(suite) ->
- [start, abnormal, shutdown, sys, hibernate, enter_loop].
-
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [{group, start}, {group, abnormal}, shutdown,
+ {group, sys}, hibernate, enter_loop].
+groups() ->
+ [{start, [],
+ [start1, start2, start3, start4, start5, start6, start7,
+ start8, start9, start10, start11]},
+ {abnormal, [], [abnormal1, abnormal2]},
+ {sys, [],
+ [sys1, call_format_status, error_format_status]}].
-start(suite) -> [start1, start2, start3, start4, start5, start6, start7,
- start8, start9, start10, start11].
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
%% anonymous
start1(Config) when is_list(Config) ->
@@ -239,7 +258,6 @@ start11(Config) when is_list(Config) ->
test_server:messages_get(),
ok.
-abnormal(suite) -> [abnormal1, abnormal2].
%% Check that time outs in calls work
abnormal1(suite) -> [];
@@ -305,7 +323,6 @@ shutdown(Config) when is_list(Config) ->
ok.
-sys(suite) -> [sys1, call_format_status].
sys1(Config) when is_list(Config) ->
?line {ok, Pid} =
@@ -320,10 +337,53 @@ sys1(Config) when is_list(Config) ->
call_format_status(Config) when is_list(Config) ->
?line {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, [], []),
?line Status = sys:get_status(Pid),
- ?line {status, Pid, _Mod, [_PDict, running, _Parent, _, Data]} = Status,
+ ?line {status, Pid, _Mod, [_PDict, running, _, _, Data]} = Status,
?line [format_status_called | _] = lists:reverse(Data),
- ?line stop_it(Pid).
+ ?line stop_it(Pid),
+ %% check that format_status can handle a name being an atom (pid is
+ %% already checked by the previous test)
+ ?line {ok, Pid2} = gen_fsm:start({local, gfsm}, gen_fsm_SUITE, [], []),
+ ?line Status2 = sys:get_status(gfsm),
+ ?line {status, Pid2, _Mod, [_PDict2, running, _, _, Data2]} = Status2,
+ ?line [format_status_called | _] = lists:reverse(Data2),
+ ?line stop_it(Pid2),
+
+ %% check that format_status can handle a name being a term other than a
+ %% pid or atom
+ GlobalName1 = {global, "CallFormatStatus"},
+ ?line {ok, Pid3} = gen_fsm:start(GlobalName1, gen_fsm_SUITE, [], []),
+ ?line Status3 = sys:get_status(GlobalName1),
+ ?line {status, Pid3, _Mod, [_PDict3, running, _, _, Data3]} = Status3,
+ ?line [format_status_called | _] = lists:reverse(Data3),
+ ?line stop_it(Pid3),
+ GlobalName2 = {global, {name, "term"}},
+ ?line {ok, Pid4} = gen_fsm:start(GlobalName2, gen_fsm_SUITE, [], []),
+ ?line Status4 = sys:get_status(GlobalName2),
+ ?line {status, Pid4, _Mod, [_PDict4, running, _, _, Data4]} = Status4,
+ ?line [format_status_called | _] = lists:reverse(Data4),
+ ?line stop_it(Pid4).
+
+error_format_status(Config) when is_list(Config) ->
+ ?line error_logger_forwarder:register(),
+ OldFl = process_flag(trap_exit, true),
+ StateData = "called format_status",
+ ?line {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []),
+ %% bad return value in the gen_fsm loop
+ ?line {'EXIT',{{bad_return_value, badreturn},_}} =
+ (catch gen_fsm:sync_send_event(Pid, badreturn)),
+ receive
+ {error,_GroupLeader,{Pid,
+ "** State machine"++_,
+ [Pid,{_,_,badreturn},idle,StateData,_]}} ->
+ ok;
+ Other ->
+ ?line io:format("Unexpected: ~p", [Other]),
+ ?line ?t:fail()
+ end,
+ ?t:messages_get(),
+ process_flag(trap_exit, OldFl),
+ ok.
%% Hibernation
hibernate(suite) -> [];
@@ -704,6 +764,8 @@ init(hiber) ->
{ok, hiber_idle, []};
init(hiber_now) ->
{ok, hiber_idle, [], hibernate};
+init({state_data, StateData}) ->
+ {ok, idle, StateData};
init(_) ->
{ok, idle, state_data}.
@@ -844,5 +906,7 @@ handle_sync_event(stop_shutdown_reason, _From, _State, Data) ->
handle_sync_event({get, _Pid}, _From, State, Data) ->
{reply, {state, State, Data}, State, Data}.
-format_status(_Opt, [_Pdict, _StateData]) ->
+format_status(terminate, [_Pdict, StateData]) ->
+ StateData;
+format_status(normal, [_Pdict, _StateData]) ->
[format_status_called].
diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl
index 6efdce78a1..5a248d7c10 100644
--- a/lib/stdlib/test/gen_server_SUITE.erl
+++ b/lib/stdlib/test/gen_server_SUITE.erl
@@ -1,36 +1,38 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 1996-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(gen_server_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-include_lib("kernel/include/inet.hrl").
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
-export([start/1, crash/1, call/1, cast/1, cast_fast/1,
info/1, abcast/1, multicall/1, multicall_down/1,
call_remote1/1, call_remote2/1, call_remote3/1,
call_remote_n1/1, call_remote_n2/1, call_remote_n3/1, spec_init/1,
spec_init_local_registered_parent/1,
spec_init_global_registered_parent/1,
- otp_5854/1, hibernate/1, otp_7669/1, call_format_status/1
+ otp_5854/1, hibernate/1, otp_7669/1, call_format_status/1,
+ error_format_status/1, call_with_huge_message_queue/1
]).
% spawn export
@@ -44,21 +46,55 @@
-export([init/1, handle_call/3, handle_cast/2,
handle_info/2, terminate/2, format_status/2]).
-all(suite) ->
- [start, crash, call, cast, cast_fast, info,
- abcast, multicall, multicall_down, call_remote1,
- call_remote2, call_remote3, call_remote_n1,
- call_remote_n2, call_remote_n3, spec_init,
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [start, crash, call, cast, cast_fast, info, abcast,
+ multicall, multicall_down, call_remote1, call_remote2,
+ call_remote3, call_remote_n1, call_remote_n2,
+ call_remote_n3, spec_init,
spec_init_local_registered_parent,
- spec_init_global_registered_parent,
- otp_5854, hibernate, otp_7669, call_format_status].
+ spec_init_global_registered_parent, otp_5854, hibernate,
+ otp_7669, call_format_status, error_format_status,
+ call_with_huge_message_queue].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
-define(default_timeout, ?t:minutes(1)).
+init_per_testcase(Case, Config) when Case == call_remote1;
+ Case == call_remote2;
+ Case == call_remote3;
+ Case == call_remote_n1;
+ Case == call_remote_n2;
+ Case == call_remote_n3 ->
+ {ok,N} = start_node(hubba),
+ ?line Dog = ?t:timetrap(?default_timeout),
+ [{node,N},{watchdog, Dog} | Config];
init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
+ case proplists:get_value(node, Config) of
+ undefined ->
+ ok;
+ N ->
+ test_server:stop_node(N)
+ end,
Dog = ?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
@@ -291,8 +327,8 @@ start_node(Name) ->
call_remote1(suite) -> [];
call_remote1(Config) when is_list(Config) ->
- ?line N = hubba,
- ?line {ok, Node} = start_node(N),
+ N = hubba,
+ ?line Node = proplists:get_value(node,Config),
?line {ok, Pid} = rpc:call(Node, gen_server, start,
[{global, N}, ?MODULE, [], []]),
?line ok = (catch gen_server:call({global, N}, started_p, infinity)),
@@ -305,7 +341,7 @@ call_remote1(Config) when is_list(Config) ->
call_remote2(suite) -> [];
call_remote2(Config) when is_list(Config) ->
?line N = hubba,
- ?line {ok, Node} = start_node(N),
+ ?line Node = proplists:get_value(node,Config),
?line {ok, Pid} = rpc:call(Node, gen_server, start,
[{global, N}, ?MODULE, [], []]),
@@ -318,8 +354,7 @@ call_remote2(Config) when is_list(Config) ->
call_remote3(suite) -> [];
call_remote3(Config) when is_list(Config) ->
- ?line N = hubba,
- ?line {ok, Node} = start_node(N),
+ ?line Node = proplists:get_value(node,Config),
?line {ok, Pid} = rpc:call(Node, gen_server, start,
[{local, piller}, ?MODULE, [], []]),
@@ -337,7 +372,7 @@ call_remote3(Config) when is_list(Config) ->
call_remote_n1(suite) -> [];
call_remote_n1(Config) when is_list(Config) ->
?line N = hubba,
- ?line {ok, Node} = start_node(N),
+ ?line Node = proplists:get_value(node,Config),
?line {ok, _Pid} = rpc:call(Node, gen_server, start,
[{global, N}, ?MODULE, [], []]),
?line _ = test_server:stop_node(Node),
@@ -349,7 +384,7 @@ call_remote_n1(Config) when is_list(Config) ->
call_remote_n2(suite) -> [];
call_remote_n2(Config) when is_list(Config) ->
?line N = hubba,
- ?line {ok, Node} = start_node(N),
+ ?line Node = proplists:get_value(node,Config),
?line {ok, Pid} = rpc:call(Node, gen_server, start,
[{global, N}, ?MODULE, [], []]),
@@ -361,8 +396,7 @@ call_remote_n2(Config) when is_list(Config) ->
call_remote_n3(suite) -> [];
call_remote_n3(Config) when is_list(Config) ->
- ?line N = hubba,
- ?line {ok, Node} = start_node(N),
+ ?line Node = proplists:get_value(node,Config),
?line {ok, _Pid} = rpc:call(Node, gen_server, start,
[{local, piller}, ?MODULE, [], []]),
@@ -895,15 +929,105 @@ call_format_status(doc) ->
["Test that sys:get_status/1,2 calls format_status/2"];
call_format_status(Config) when is_list(Config) ->
?line {ok, Pid} = gen_server:start_link({local, call_format_status},
- gen_server_SUITE, [], []),
+ ?MODULE, [], []),
?line Status1 = sys:get_status(call_format_status),
?line {status, Pid, _Mod, [_PDict, running, _Parent, _, Data1]} = Status1,
?line [format_status_called | _] = lists:reverse(Data1),
?line Status2 = sys:get_status(call_format_status, 5000),
?line {status, Pid, _Mod, [_PDict, running, _Parent, _, Data2]} = Status2,
?line [format_status_called | _] = lists:reverse(Data2),
+
+ %% check that format_status can handle a name being a pid (atom is
+ %% already checked by the previous test)
+ ?line {ok, Pid3} = gen_server:start_link(gen_server_SUITE, [], []),
+ ?line Status3 = sys:get_status(Pid3),
+ ?line {status, Pid3, _Mod, [_PDict3, running, _Parent, _, Data3]} = Status3,
+ ?line [format_status_called | _] = lists:reverse(Data3),
+
+ %% check that format_status can handle a name being a term other than a
+ %% pid or atom
+ GlobalName1 = {global, "CallFormatStatus"},
+ ?line {ok, Pid4} = gen_server:start_link(GlobalName1,
+ gen_server_SUITE, [], []),
+ ?line Status4 = sys:get_status(Pid4),
+ ?line {status, Pid4, _Mod, [_PDict4, running, _Parent, _, Data4]} = Status4,
+ ?line [format_status_called | _] = lists:reverse(Data4),
+ GlobalName2 = {global, {name, "term"}},
+ ?line {ok, Pid5} = gen_server:start_link(GlobalName2,
+ gen_server_SUITE, [], []),
+ ?line Status5 = sys:get_status(GlobalName2),
+ ?line {status, Pid5, _Mod, [_PDict5, running, _Parent, _, Data5]} = Status5,
+ ?line [format_status_called | _] = lists:reverse(Data5),
+ ok.
+
+%% Verify that error termination correctly calls our format_status/2 fun
+%%
+error_format_status(suite) ->
+ [];
+error_format_status(doc) ->
+ ["Test that an error termination calls format_status/2"];
+error_format_status(Config) when is_list(Config) ->
+ ?line error_logger_forwarder:register(),
+ OldFl = process_flag(trap_exit, true),
+ State = "called format_status",
+ ?line {ok, Pid} = gen_server:start_link(?MODULE, {state, State}, []),
+ ?line {'EXIT',{crashed,_}} = (catch gen_server:call(Pid, crash)),
+ receive
+ {'EXIT', Pid, crashed} ->
+ ok
+ end,
+ receive
+ {error,_GroupLeader,{Pid,
+ "** Generic server"++_,
+ [Pid,crash,State,crashed]}} ->
+ ok;
+ Other ->
+ ?line io:format("Unexpected: ~p", [Other]),
+ ?line ?t:fail()
+ end,
+ ?t:messages_get(),
+ process_flag(trap_exit, OldFl),
ok.
+%% Test that the time for a huge message queue is not
+%% significantly slower than with an empty message queue.
+call_with_huge_message_queue(Config) when is_list(Config) ->
+ ?line Pid = spawn_link(fun echo_loop/0),
+
+ ?line {Time,ok} = tc(fun() -> calls(10, Pid) end),
+
+ ?line [self() ! {msg,N} || N <- lists:seq(1, 500000)],
+ erlang:garbage_collect(),
+ ?line {NewTime,ok} = tc(fun() -> calls(10, Pid) end),
+ io:format("Time for empty message queue: ~p", [Time]),
+ io:format("Time for huge message queue: ~p", [NewTime]),
+
+ case (NewTime+1) / (Time+1) of
+ Q when Q < 10 ->
+ ok;
+ Q ->
+ io:format("Q = ~p", [Q]),
+ ?line ?t:fail()
+ end,
+ ok.
+
+calls(0, _) -> ok;
+calls(N, Pid) ->
+ {ultimate_answer,42} = call(Pid, {ultimate_answer,42}),
+ calls(N-1, Pid).
+
+call(Pid, Msg) ->
+ gen_server:call(Pid, Msg, infinity).
+
+tc(Fun) ->
+ timer:tc(erlang, apply, [Fun,[]]).
+
+echo_loop() ->
+ receive
+ {'$gen_call',{Pid,Ref},Msg} ->
+ Pid ! {Ref,Msg},
+ echo_loop()
+ end.
%%--------------------------------------------------------------
%% Help functions to spec_init_*
@@ -1064,5 +1188,7 @@ terminate({From, stopped_info}, _State) ->
terminate(_Reason, _State) ->
ok.
-format_status(_Opt, [_PDict, _State]) ->
- [format_status_called].
+format_status(terminate, [_PDict, State]) ->
+ State;
+format_status(normal, [_PDict, _State]) ->
+ format_status_called.
diff --git a/lib/stdlib/test/id_transform_SUITE.erl b/lib/stdlib/test/id_transform_SUITE.erl
index 95ee509833..da52f43728 100644
--- a/lib/stdlib/test/id_transform_SUITE.erl
+++ b/lib/stdlib/test/id_transform_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2003-2009. All Rights Reserved.
+%% Copyright Ericsson AB 2003-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
@@ -21,17 +21,37 @@
-include_lib("kernel/include/file.hrl").
--export([all/1,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
id_transform/1]).
-export([check/2,check2/1,g/0,f/1,t/1,t1/1,t2/1,t3/1,t4/1,
t5/1,t6/1,apa/1,new_fun/0]).
-% Serves as test...
+ % Serves as test...
-hej(hopp).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
+
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [id_transform].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
-all(suite) -> [id_transform].
id_transform(doc) -> "Test erl_id_trans.";
id_transform(Config) when is_list(Config) ->
diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl
index 73efeb004a..497fd3c562 100644
--- a/lib/stdlib/test/io_SUITE.erl
+++ b/lib/stdlib/test/io_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1999-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
@@ -18,9 +18,10 @@
%%
-module(io_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
-export([error_1/1, float_g/1, otp_5403/1, otp_5813/1, otp_6230/1,
otp_6282/1, otp_6354/1, otp_6495/1, otp_6517/1, otp_6502/1,
@@ -37,7 +38,7 @@
-define(t, test_server).
-define(privdir(_), "./io_SUITE_priv").
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(format(S, A), ok).
-define(privdir(Conf), ?config(priv_dir, Conf)).
-endif.
@@ -49,17 +50,35 @@
init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
-fin_per_testcase(_Case, _Config) ->
+end_per_testcase(_Case, _Config) ->
Dog = ?config(watchdog, _Config),
test_server:timetrap_cancel(Dog),
ok.
-all(doc) ->
- ["Test cases for io."];
-all(suite) ->
- [error_1,float_g,otp_5403,otp_5813,otp_6230,otp_6282,otp_6354,otp_6495,
- otp_6517,otp_6502,manpage,otp_6708,otp_7084,otp_7421,
- io_lib_collect_line_3_wb,cr_whitespace_in_string,io_fread_newlines].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [error_1, float_g, otp_5403, otp_5813, otp_6230,
+ otp_6282, otp_6354, otp_6495, otp_6517, otp_6502,
+ manpage, otp_6708, otp_7084, otp_7421,
+ io_lib_collect_line_3_wb, cr_whitespace_in_string,
+ io_fread_newlines].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
error_1(doc) ->
["Error cases for output"];
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index 93159fbd5b..3474f41ee6 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -17,16 +17,21 @@
%% %CopyrightEnd%
%%
-module(io_proto_SUITE).
+-compile(r12).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
--export([setopts_getopts/1,unicode_options/1,unicode_options_gen/1, binary_options/1, bc_with_r12/1,
- bc_with_r12_gl/1, read_modes_gl/1,bc_with_r12_ogl/1, read_modes_ogl/1, broken_unicode/1,eof_on_pipe/1,unicode_prompt/1]).
+-export([setopts_getopts/1,unicode_options/1,unicode_options_gen/1,
+ binary_options/1, bc_with_r12/1,
+ bc_with_r12_gl/1, read_modes_gl/1,bc_with_r12_ogl/1,
+ read_modes_ogl/1, broken_unicode/1,eof_on_pipe/1,unicode_prompt/1]).
--export([io_server_proxy/1,start_io_server_proxy/0, proxy_getall/1, proxy_setnext/2, proxy_quit/1]).
+-export([io_server_proxy/1,start_io_server_proxy/0, proxy_getall/1,
+ proxy_setnext/2, proxy_quit/1]).
%% For spawn
-export([toerl_server/3,hold_the_line/3,answering_machine1/3,
answering_machine2/3]).
@@ -41,7 +46,7 @@
-define(t, test_server).
-define(privdir(_), "./io_SUITE_priv").
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(privdir(Conf), ?config(priv_dir, Conf)).
-endif.
@@ -72,19 +77,36 @@ init_per_testcase(_Case, Config) ->
end,
os:putenv("TERM","vt100"),
[{watchdog, Dog}, {term, Term} | Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog = ?config(watchdog, Config),
Term = ?config(term,Config),
os:putenv("TERM",Term),
test_server:timetrap_cancel(Dog),
ok.
-all(doc) ->
- ["Test cases for the io_protocol."];
-all(suite) ->
- [setopts_getopts, unicode_options, unicode_options_gen, binary_options, bc_with_r12,
- bc_with_r12_gl,bc_with_r12_ogl, read_modes_gl, read_modes_ogl,
- broken_unicode,eof_on_pipe,unicode_prompt].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [setopts_getopts, unicode_options, unicode_options_gen,
+ binary_options, bc_with_r12, bc_with_r12_gl,
+ bc_with_r12_ogl, read_modes_gl, read_modes_ogl,
+ broken_unicode, eof_on_pipe, unicode_prompt].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
-record(state, {
diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl
index 0089e874c8..1fc9de09c3 100644
--- a/lib/stdlib/test/lists_SUITE.erl
+++ b/lib/stdlib/test/lists_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1997-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
@@ -21,7 +21,7 @@
%%%-----------------------------------------------------------------
-module(lists_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
% Default timetrap timeout (set in init_per_testcase).
@@ -30,36 +30,37 @@
-define(default_timeout, ?t:minutes(4)).
% Test server specific exports
--export([all/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
% Test cases must be exported.
-export([member/1, reverse/1,
keymember/1, keysearch_keyfind/1,
keystore/1, keytake/1,
- append/1, append_1/1, append_2/1,
- seq/1, seq_loop/1, seq_2/1, seq_3/1, seq_2_e/1, seq_3_e/1,
- sublist/1, flatten/1,
+ append_1/1, append_2/1,
+ seq_loop/1, seq_2/1, seq_3/1, seq_2_e/1, seq_3_e/1,
+
sublist_2/1, sublist_3/1, sublist_2_e/1, sublist_3_e/1,
flatten_1/1, flatten_2/1, flatten_1_e/1, flatten_2_e/1,
dropwhile/1,
- sort/1, sort_1/1, sort_stable/1, merge/1, rmerge/1, sort_rand/1,
- usort/1, usort_1/1, usort_stable/1, umerge/1, rumerge/1,usort_rand/1,
+ sort_1/1, sort_stable/1, merge/1, rmerge/1, sort_rand/1,
+ usort_1/1, usort_stable/1, umerge/1, rumerge/1,usort_rand/1,
keymerge/1, rkeymerge/1,
- keysort/1, keysort_1/1, keysort_i/1, keysort_stable/1,
+ keysort_1/1, keysort_i/1, keysort_stable/1,
keysort_rand/1, keysort_error/1,
ukeymerge/1, rukeymerge/1,
- ukeysort/1, ukeysort_1/1, ukeysort_i/1, ukeysort_stable/1,
+ ukeysort_1/1, ukeysort_i/1, ukeysort_stable/1,
ukeysort_rand/1, ukeysort_error/1,
funmerge/1, rfunmerge/1,
- funsort/1, funsort_1/1, funsort_stable/1, funsort_rand/1,
+ funsort_1/1, funsort_stable/1, funsort_rand/1,
funsort_error/1,
ufunmerge/1, rufunmerge/1,
- ufunsort/1, ufunsort_1/1, ufunsort_stable/1, ufunsort_rand/1,
+ ufunsort_1/1, ufunsort_stable/1, ufunsort_rand/1,
ufunsort_error/1,
zip_unzip/1, zip_unzip3/1, zipwith/1, zipwith3/1,
filter_partition/1,
- tickets/1, otp_5939/1, otp_6023/1, otp_6606/1, otp_7230/1,
+ otp_5939/1, otp_6023/1, otp_6606/1, otp_7230/1,
suffix/1, subtract/1]).
%% Sort randomized lists until stopped.
@@ -76,21 +77,59 @@
%%
%% all/1
%%
-all(doc) ->
- [];
-all(suite) ->
- [append, reverse, member, keymember, keysearch_keyfind, keystore, keytake,
- dropwhile,
- sort, usort, keysort, ukeysort,
- funsort, ufunsort, sublist, flatten, seq,
- zip_unzip, zip_unzip3, zipwith, zipwith3,
- filter_partition, tickets, suffix, subtract].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [{group, append}, reverse, member, keymember,
+ keysearch_keyfind, keystore, keytake, dropwhile, {group,sort},
+ {group, usort}, {group, keysort}, {group, ukeysort},
+ {group, funsort}, {group, ufunsort}, {group, sublist},
+ {group, flatten}, {group, seq}, zip_unzip, zip_unzip3,
+ zipwith, zipwith3, filter_partition, {group, tickets},
+ suffix, subtract].
+
+groups() ->
+ [{append, [], [append_1, append_2]},
+ {usort, [],
+ [umerge, rumerge, usort_1, usort_rand, usort_stable]},
+ {keysort, [],
+ [keymerge, rkeymerge, keysort_1, keysort_rand,
+ keysort_i, keysort_stable, keysort_error]},
+ {sort,[],[merge, rmerge, sort_1, sort_rand]},
+ {ukeysort, [],
+ [ukeymerge, rukeymerge, ukeysort_1, ukeysort_rand,
+ ukeysort_i, ukeysort_stable, ukeysort_error]},
+ {funsort, [],
+ [funmerge, rfunmerge, funsort_1, funsort_stable,
+ funsort_error, funsort_rand]},
+ {ufunsort, [],
+ [ufunmerge, rufunmerge, ufunsort_1, ufunsort_stable,
+ ufunsort_error, ufunsort_rand]},
+ {seq, [], [seq_loop, seq_2, seq_3, seq_2_e, seq_3_e]},
+ {sublist, [],
+ [sublist_2, sublist_3, sublist_2_e, sublist_3_e]},
+ {flatten, [],
+ [flatten_1, flatten_2, flatten_1_e, flatten_2_e]},
+ {tickets, [], [otp_5939, otp_6023, otp_6606, otp_7230]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
init_per_testcase(_Case, Config) ->
?line Dog=test_server:timetrap(?default_timeout),
[{watchdog, Dog}|Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog=?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
@@ -98,10 +137,6 @@ fin_per_testcase(_Case, Config) ->
%
% Test cases starts here.
%
-append(doc) ->
- ["Tests lists:append/1 & lists:append/2"];
-append(suite) ->
- [append_1, append_2].
append_1(doc) -> [];
append_1(suite) -> [];
@@ -346,12 +381,6 @@ keytake(Config) when is_list(Config) ->
?line false = lists:keytake(4, 2, L),
ok.
-sort(doc) ->
- ["Tests merge functions and lists:sort/1"];
-sort(suite) ->
- %% [merge, rmerge, sort_1, sort_rand, sort_stable].
- [merge, rmerge, sort_1, sort_rand].
-
merge(doc) -> ["merge functions"];
merge(suite) -> [];
merge(Config) when is_list(Config) ->
@@ -536,10 +565,6 @@ expl_pid([{I,F} | T], L) when is_function(F) ->
expl_pid([], L) ->
L.
-usort(doc) ->
- ["Tests unique merge functions and lists:usort/1"];
-usort(suite) ->
- [umerge, rumerge, usort_1, usort_rand, usort_stable].
usort_1(suite) -> [];
usort_1(doc) -> [""];
@@ -750,11 +775,6 @@ ucheck_stability(L) ->
U = lists:usort(L),
check_stab(L, U, S, "usort/1", "ukeysort/2").
-keysort(doc) ->
- ["Tests lists:keysort/2"];
-keysort(suite) ->
- [keymerge, rkeymerge,
- keysort_1, keysort_rand, keysort_i, keysort_stable, keysort_error].
keymerge(doc) -> ["Key merge two lists."];
keymerge(suite) -> [];
@@ -946,11 +966,6 @@ keycompare(I, J, A, B) when element(I, A) == element(I, B),
element(J, A) =< element(J, B) ->
ok.
-ukeysort(doc) ->
- ["Tests lists:ukeysort/2"];
-ukeysort(suite) ->
- [ukeymerge, rukeymerge,
- ukeysort_1, ukeysort_rand, ukeysort_i, ukeysort_stable, ukeysort_error].
ukeymerge(suite) -> [];
ukeymerge(doc) -> ["Merge two lists while removing duplicates."];
@@ -1240,11 +1255,6 @@ ukeycompare(I, J, A, B) when A =/= B,
ok.
-funsort(doc) ->
- ["Tests lists:sort/2"];
-funsort(suite) ->
- [funmerge, rfunmerge,
- funsort_1, funsort_stable, funsort_error, funsort_rand].
funmerge(doc) -> ["Merge two lists using a fun."];
funmerge(suite) -> [];
@@ -1377,11 +1387,6 @@ funsort_check(I, Input, Expected) ->
?line Expected = funsort(I, Input),
check_sorted(I, Input, Expected).
-ufunsort(doc) ->
- ["Tests lists:usort/2"];
-ufunsort(suite) ->
- [ufunmerge, rufunmerge,
- ufunsort_1, ufunsort_stable, ufunsort_error, ufunsort_rand].
ufunmerge(suite) -> [];
ufunmerge(doc) -> ["Merge two lists while removing duplicates using a fun."];
@@ -2076,12 +2081,6 @@ rkeymerge2_2(_I, T1, _E1, [], M, H1) ->
%%%------------------------------------------------------------
-seq(doc) ->
- ["Tests lists:seq/3"];
-seq(suite) ->
- [
- seq_loop,
- seq_2, seq_3, seq_2_e, seq_3_e].
seq_loop(doc) ->
["Test for infinite loop (OTP-2404)."];
@@ -2229,10 +2228,6 @@ property(From, To, Step) ->
%%%------------------------------------------------------------
-sublist(doc) ->
- ["Tests lists:sublist/[2,3]"];
-sublist(suite) ->
- [sublist_2, sublist_3, sublist_2_e, sublist_3_e].
-define(sublist_error2(X,Y), ?line {'EXIT', _} = (catch lists:sublist(X,Y))).
-define(sublist_error3(X,Y,Z), ?line {'EXIT', _} = (catch lists:sublist(X,Y,Z))).
@@ -2326,10 +2321,6 @@ sublist_3_e(Config) when is_list(Config) ->
%%%------------------------------------------------------------
-flatten(doc) ->
- ["Tests lists:flatten/[1,2]"];
-flatten(suite) ->
- [flatten_1, flatten_2, flatten_1_e, flatten_2_e].
-define(flatten_error1(X), ?line {'EXIT', _} = (catch lists:flatten(X))).
-define(flatten_error2(X,Y), ?line {'EXIT', _} = (catch lists:flatten(X,Y))).
@@ -2489,10 +2480,6 @@ filpart(F, All, Exp) ->
Other = lists:filter(fun(E) -> not F(E) end, All),
{Exp,Other} = lists:partition(F, All).
-tickets(doc) ->
- ["Ticktes."];
-tickets(suite) ->
- [otp_5939, otp_6023, otp_6606, otp_7230].
otp_5939(doc) -> ["OTP-5939. Guard tests added."];
otp_5939(suite) -> [];
diff --git a/lib/stdlib/test/log_mf_h_SUITE.erl b/lib/stdlib/test/log_mf_h_SUITE.erl
index 640261f665..688be31e64 100644
--- a/lib/stdlib/test/log_mf_h_SUITE.erl
+++ b/lib/stdlib/test/log_mf_h_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1996-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
@@ -18,12 +18,32 @@
%%
-module(log_mf_h_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-include_lib("kernel/include/file.hrl").
--export([all/1, test/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2, test/1]).
+
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [test].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
-all(suite) -> [test].
%%-----------------------------------------------------------------
diff --git a/lib/stdlib/test/ms_transform_SUITE.erl b/lib/stdlib/test/ms_transform_SUITE.erl
index 79a0a9af89..f747d09f3c 100644
--- a/lib/stdlib/test/ms_transform_SUITE.erl
+++ b/lib/stdlib/test/ms_transform_SUITE.erl
@@ -19,9 +19,10 @@
-module(ms_transform_SUITE).
-author('[email protected]').
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
-export([basic_ets/1]).
-export([basic_dbg/1]).
-export([from_shell/1]).
@@ -37,20 +38,122 @@
-export([andalso_orelse/1]).
-export([float_1_function/1]).
-export([action_function/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([warnings/1]).
+-export([init_per_testcase/2, end_per_testcase/2]).
init_per_testcase(_Func, Config) ->
Dog=test_server:timetrap(test_server:seconds(360)),
[{watchdog, Dog}|Config].
-fin_per_testcase(_Func, Config) ->
+end_per_testcase(_Func, Config) ->
Dog=?config(watchdog, Config),
test_server:timetrap_cancel(Dog).
-all(suite) -> [from_shell,basic_ets,basic_dbg,records,record_index,multipass,
- bitsyntax, record_defaults, andalso_orelse,
- float_1_function, action_function,
- top_match, old_guards, autoimported, semicolon].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [from_shell, basic_ets, basic_dbg, records,
+ record_index, multipass, bitsyntax, record_defaults,
+ andalso_orelse, float_1_function, action_function,
+ warnings, top_match, old_guards, autoimported,
+ semicolon].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
+%% This may be subject to change
+-define(WARN_NUMBER_SHADOW,50).
+warnings(suite) ->
+ [];
+warnings(doc) ->
+ ["Check that shadowed variables in fun head generate warning"];
+warnings(Config) when is_list(Config) ->
+ ?line setup(Config),
+ Prog = <<"A=5, "
+ "ets:fun2ms(fun({A,B}) "
+ " when is_integer(A) and (A+5 > B) -> "
+ " A andalso B "
+ " end)">>,
+ ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}]}] =
+ compile_ww(Prog),
+ Prog2 = <<"C=5, "
+ "ets:fun2ms(fun({A,B} = C) "
+ " when is_integer(A) and (A+5 > B) -> "
+ " {A andalso B,C} "
+ " end)">>,
+ ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] =
+ compile_ww(Prog2),
+ Rec3 = <<"-record(a,{a,b,c,d=foppa}).">>,
+ Prog3 = <<"A=3,C=5, "
+ "ets:fun2ms(fun(#a{a = A, b = B} = C) "
+ " when is_integer(A) and (A+5 > B) -> "
+ " {A andalso B,C} "
+ " end)">>,
+ ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}},
+ {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] =
+ compile_ww(Rec3,Prog3),
+ Rec4 = <<"-record(a,{a,b,c,d=foppa}).">>,
+ Prog4 = <<"A=3,C=5, "
+ "F = fun(B) -> B*3 end,"
+ "erlang:display(F(A)),"
+ "ets:fun2ms(fun(#a{a = A, b = B} = C) "
+ " when is_integer(A) and (A+5 > B) -> "
+ " {A andalso B,C} "
+ " end)">>,
+ ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}},
+ {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] =
+ compile_ww(Rec4,Prog4),
+ Rec5 = <<"-record(a,{a,b,c,d=foppa}).">>,
+ Prog5 = <<"A=3,C=5, "
+ "F = fun(B) -> B*3 end,"
+ "erlang:display(F(A)),"
+ "B = ets:fun2ms(fun(#a{a = A, b = B} = C) "
+ " when is_integer(A) and (A+5 > B) -> "
+ " {A andalso B,C} "
+ " end)">>,
+ ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}},
+ {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] =
+ compile_ww(Rec5,Prog5),
+ Prog6 = <<" X=bar, "
+ " A = case X of"
+ " foo ->"
+ " foo;"
+ " Y ->"
+ " ets:fun2ms(fun(Y) ->" % This is a warning
+ " 3*Y"
+ " end)"
+ " end,"
+ " ets:fun2ms(fun(Y) ->" % Y out of "scope" here, so no warning
+ " {3*Y,A}"
+ " end)">>,
+ ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] =
+ compile_ww(Prog6),
+ Prog7 = <<" X=bar, "
+ " A = case X of"
+ " foo ->"
+ " Y = foo;"
+ " Y ->"
+ " bar"
+ " end,"
+ " ets:fun2ms(fun(Y) ->" % Y exported from case and safe, so warn
+ " {3*Y,A}"
+ " end)">>,
+ ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] =
+ compile_ww(Prog7),
+ ok.
andalso_orelse(suite) ->
[];
@@ -721,6 +824,24 @@ compile_and_run(Records,Expr) ->
code:load_binary(tmp,FN,Bin),
tmp:tmp().
+compile_ww(Expr) ->
+ compile_ww(<<>>,Expr).
+compile_ww(Records,Expr) ->
+ Prog = <<
+ "-module(tmp).\n",
+ "-include_lib(\"stdlib/include/ms_transform.hrl\").\n",
+ "-export([tmp/0]).\n",
+ Records/binary,"\n",
+ "tmp() ->\n",
+ Expr/binary,".\n">>,
+ FN=temp_name(),
+ file:write_file(FN,Prog),
+ {ok,Forms} = epp:parse_file(FN,"",""),
+ {ok,tmp,_Bin,Wlist} = compile:forms(Forms,[return_warnings,
+ nowarn_unused_vars,
+ nowarn_unused_record]),
+ Wlist.
+
do_eval(String) ->
{done,{ok,T,_},[]} = erl_scan:tokens(
[],
diff --git a/lib/stdlib/test/naughty_child.erl b/lib/stdlib/test/naughty_child.erl
index b56130929c..b939436bfc 100644
--- a/lib/stdlib/test/naughty_child.erl
+++ b/lib/stdlib/test/naughty_child.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2002-2009. All Rights Reserved.
+%% Copyright Ericsson AB 2002-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
diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl
index 2fd7725335..25a385950e 100644
--- a/lib/stdlib/test/proc_lib_SUITE.erl
+++ b/lib/stdlib/test/proc_lib_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1996-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
@@ -23,10 +23,12 @@
%%
%%-define(STANDALONE,1).
--export([all/1, crash/1, sync_start/1, sync_start_nolink/1, sync_start_link/1,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
+ crash/1, sync_start_nolink/1, sync_start_link/1,
spawn_opt/1, sp1/0, sp2/0, sp3/1, sp4/2, sp5/1,
hibernate/1]).
--export([tickets/1, otp_6345/1]).
+-export([ otp_6345/1]).
-export([hib_loop/1, awaken/1]).
@@ -40,12 +42,32 @@
-ifdef(STANDALONE).
-define(line, noop, ).
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-endif.
-all(suite) -> [crash, sync_start, spawn_opt, hibernate, tickets].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [crash, {group, sync_start}, spawn_opt, hibernate,
+ {group, tickets}].
+
+groups() ->
+ [{tickets, [], [otp_6345]},
+ {sync_start, [], [sync_start_nolink, sync_start_link]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
-tickets(suite) -> [otp_6345].
%%-----------------------------------------------------------------
%% We don't have to test that spwn and spawn_link actually spawns
@@ -127,7 +149,6 @@ crash(Config) when is_list(Config) ->
ok
end.
-sync_start(suite) -> [sync_start_nolink, sync_start_link].
sync_start_nolink(Config) when is_list(Config) ->
_Pid = spawn_link(?MODULE, sp5, [self()]),
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index ff11ebc6bf..05d8c5f8e3 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -1,25 +1,26 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2004-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 2004-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%
%%
%%%----------------------------------------------------------------
%%% Purpose:Test Suite for the 'qlc' module.
%%%-----------------------------------------------------------------
-module(qlc_SUITE).
+-compile(r12).
-define(QLC, qlc).
-define(QLCs, "qlc").
@@ -42,7 +43,7 @@
-define(testcase, current_testcase). % don't know
-define(t, test_server).
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(datadir, ?config(data_dir, Config)).
-define(privdir, ?config(priv_dir, Config)).
-define(testcase, ?config(?TESTCASE, Config)).
@@ -50,36 +51,33 @@
-include_lib("stdlib/include/ms_transform.hrl").
--export([all/1, init_per_testcase/2, fin_per_testcase/2]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
+ init_per_testcase/2, end_per_testcase/2]).
--export([parse_transform/1,
- badarg/1, nested_qlc/1, unused_var/1, lc/1, fun_clauses/1,
- filter_var/1, single/1, exported_var/1, generator_vars/1,
- nomatch/1, errors/1, pattern/1,
+-export([
+ badarg/1, nested_qlc/1, unused_var/1, lc/1, fun_clauses/1,
+ filter_var/1, single/1, exported_var/1, generator_vars/1,
+ nomatch/1, errors/1, pattern/1,
- evaluation/1,
- eval/1, cursor/1, fold/1, eval_unique/1, eval_cache/1, append/1,
- evaluator/1, string_to_handle/1, table/1, process_dies/1,
- sort/1, keysort/1, filesort/1, cache/1, cache_list/1, filter/1,
- info/1, nested_info/1, lookup1/1, lookup2/1, lookup_rec/1,
- indices/1, pre_fun/1, skip_filters/1,
+ eval/1, cursor/1, fold/1, eval_unique/1, eval_cache/1, append/1,
+ evaluator/1, string_to_handle/1, table/1, process_dies/1,
+ sort/1, keysort/1, filesort/1, cache/1, cache_list/1, filter/1,
+ info/1, nested_info/1, lookup1/1, lookup2/1, lookup_rec/1,
+ indices/1, pre_fun/1, skip_filters/1,
- table_impls/1,
- ets/1, dets/1,
+ ets/1, dets/1,
- join/1,
- join_option/1, join_filter/1, join_lookup/1, join_merge/1,
- join_sort/1, join_complex/1,
+ join_option/1, join_filter/1, join_lookup/1, join_merge/1,
+ join_sort/1, join_complex/1,
- tickets/1,
- otp_5644/1, otp_5195/1, otp_6038_bug/1, otp_6359/1, otp_6562/1,
- otp_6590/1, otp_6673/1, otp_6964/1, otp_7114/1, otp_7238/1,
- otp_7232/1, otp_7552/1, otp_6674/1, otp_7714/1,
+ otp_5644/1, otp_5195/1, otp_6038_bug/1, otp_6359/1, otp_6562/1,
+ otp_6590/1, otp_6673/1, otp_6964/1, otp_7114/1, otp_7238/1,
+ otp_7232/1, otp_7552/1, otp_6674/1, otp_7714/1,
- manpage/1,
+ manpage/1,
- compat/1,
- backward/1, forward/1]).
+ backward/1, forward/1]).
%% Internal exports.
-export([bad_table_throw/1, bad_table_exit/1, default_table/1, bad_table/1,
@@ -113,17 +111,50 @@ init_per_testcase(Case, Config) ->
?line Dog = ?t:timetrap(?default_timeout),
[{?TESTCASE, Case}, {watchdog, Dog} | Config].
-fin_per_testcase(_Case, _Config) ->
+end_per_testcase(_Case, _Config) ->
Dog = ?config(watchdog, _Config),
test_server:timetrap_cancel(Dog),
ok.
-all(suite) ->
- [parse_transform, evaluation, table_impls, join, tickets, manpage, compat].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [{group, parse_transform}, {group, evaluation},
+ {group, table_impls}, {group, join}, {group, tickets},
+ manpage, {group, compat}].
+
+groups() ->
+ [{parse_transform, [],
+ [badarg, nested_qlc, unused_var, lc, fun_clauses,
+ filter_var, single, exported_var, generator_vars,
+ nomatch, errors, pattern]},
+ {evaluation, [],
+ [eval, cursor, fold, eval_unique, eval_cache, append,
+ evaluator, string_to_handle, table, process_dies, sort,
+ keysort, filesort, cache, cache_list, filter, info,
+ nested_info, lookup1, lookup2, lookup_rec, indices,
+ pre_fun, skip_filters]},
+ {table_impls, [], [ets, dets]},
+ {join, [],
+ [join_option, join_filter, join_lookup, join_merge,
+ join_sort, join_complex]},
+ {tickets, [],
+ [otp_5644, otp_5195, otp_6038_bug, otp_6359, otp_6562,
+ otp_6590, otp_6673, otp_6964, otp_7114, otp_7232,
+ otp_7238, otp_7552, otp_6674, otp_7714]},
+ {compat, [], [backward, forward]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
-parse_transform(suite) ->
- [badarg, nested_qlc, unused_var, lc, fun_clauses, filter_var,
- single, exported_var, generator_vars, nomatch, errors, pattern].
+end_per_group(_GroupName, Config) ->
+ Config.
badarg(doc) ->
"Badarg.";
@@ -460,11 +491,6 @@ pattern(Config) when is_list(Config) ->
-record(k, {t,v}).\n">>, Ts),
ok.
-evaluation(suite) ->
- [eval, cursor, fold, eval_unique, eval_cache, append, evaluator,
- string_to_handle, table, process_dies, sort, keysort, filesort, cache,
- cache_list, filter, info, nested_info, lookup1, lookup2, lookup_rec,
- indices, pre_fun, skip_filters].
eval(doc) ->
"eval/2";
@@ -3183,7 +3209,9 @@ lookup2(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{1,b},{2,3}])">>,
- {warnings,[{{3,48},qlc,nomatch_filter}]}},
+ {warnings,[{2,sys_core_fold,nomatch_guard},
+ {3,qlc,nomatch_filter},
+ {3,sys_core_fold,{eval_failure,badarg}}]}},
<<"etsc(fun(E) ->
Q = qlc:q([X || {X} <- ets:table(E), element(1,{X}) =:= 1]),
@@ -4294,8 +4322,6 @@ skip_filters(Config) when is_list(Config) ->
ok.
-table_impls(suite) ->
- [ets, dets].
ets(doc) ->
"ets:table/1,2.";
@@ -4442,9 +4468,6 @@ dets(Config) when is_list(Config) ->
_ = file:delete(Fname),
ok.
-join(suite) ->
- [join_option, join_filter, join_lookup, join_merge,
- join_sort, join_complex].
join_option(doc) ->
"The 'join' option (any, lookup, merge, nested_loop). Also cache/unique.";
@@ -5726,10 +5749,6 @@ join_complex(Config) when is_list(Config) ->
ok.
-tickets(suite) ->
- [otp_5644, otp_5195, otp_6038_bug, otp_6359, otp_6562, otp_6590,
- otp_6673, otp_6964, otp_7114, otp_7232, otp_7238, otp_7552, otp_6674,
- otp_7714].
otp_5644(doc) ->
"OTP-5644. Handle the new language element M:F/A.";
@@ -7375,8 +7394,6 @@ gb_iter(I0, N, EFun) ->
end.
">>.
-compat(suite) ->
- [backward, forward].
backward(doc) ->
"OTP-6674. Join info and extra constants.";
diff --git a/lib/stdlib/test/queue_SUITE.erl b/lib/stdlib/test/queue_SUITE.erl
index 2cd6b52311..4095b62643 100644
--- a/lib/stdlib/test/queue_SUITE.erl
+++ b/lib/stdlib/test/queue_SUITE.erl
@@ -17,13 +17,14 @@
%% %CopyrightEnd%
%%
-module(queue_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
-export([do/1, to_list/1, io_test/1, op_test/1, error/1, oops/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
% Default timetrap timeout (set in init_per_testcase).
-define(default_timeout, ?t:minutes(1)).
@@ -31,16 +32,32 @@
init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog = ?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
-all(doc) ->
- ["Test cases for queue."];
-all(suite) ->
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
[do, to_list, io_test, op_test, error, oops].
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
do(doc) ->
[""];
do(suite) ->
diff --git a/lib/stdlib/test/random_SUITE.erl b/lib/stdlib/test/random_SUITE.erl
index 8f1c304705..6164301e38 100644
--- a/lib/stdlib/test/random_SUITE.erl
+++ b/lib/stdlib/test/random_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2000-2009. All Rights Reserved.
+%% Copyright Ericsson AB 2000-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
@@ -17,13 +17,14 @@
%% %CopyrightEnd%
-module(random_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
-export([interval_1/1, seed0/1, seed/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
% Default timetrap timeout (set in init_per_testcase).
-define(default_timeout, ?t:minutes(1)).
@@ -31,16 +32,32 @@
init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog = ?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
-all(doc) ->
- ["Test cases for random."];
-all(suite) ->
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
[interval_1, seed0, seed].
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
seed0(doc) ->
["Test that seed is set implicitly, and always the same."];
seed0(suite) ->
diff --git a/lib/stdlib/test/random_iolist.erl b/lib/stdlib/test/random_iolist.erl
index 4bce347d9a..8f21b5a3b3 100644
--- a/lib/stdlib/test/random_iolist.erl
+++ b/lib/stdlib/test/random_iolist.erl
@@ -1,7 +1,7 @@
%%
%% %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
diff --git a/lib/stdlib/test/random_unicode_list.erl b/lib/stdlib/test/random_unicode_list.erl
index 3e83383b08..b8bd719b89 100644
--- a/lib/stdlib/test/random_unicode_list.erl
+++ b/lib/stdlib/test/random_unicode_list.erl
@@ -1,7 +1,7 @@
%%
%% %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
diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl
index 02683f9f1a..b82835854e 100644
--- a/lib/stdlib/test/re_SUITE.erl
+++ b/lib/stdlib/test/re_SUITE.erl
@@ -18,12 +18,41 @@
%%
-module(re_SUITE).
--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,pcre_cve_2008_2371/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2, 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,pcre_cve_2008_2371/1,
+ pcre_compile_workspace_overflow/1,re_infinite_loop/1]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-include_lib("kernel/include/file.hrl").
-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_cve_2008_2371].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [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_cve_2008_2371,
+ pcre_compile_workspace_overflow, re_infinite_loop].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
pcre(doc) ->
["Run all applicable tests from the PCRE testsuites."];
@@ -544,3 +573,25 @@ pcre_cve_2008_2371(Config) when is_list(Config) ->
%% Make sure it doesn't crash the emulator.
re:compile(<<"(?i)[\xc3\xa9\xc3\xbd]|[\xc3\xa9\xc3\xbdA]">>, [unicode]),
ok.
+
+pcre_compile_workspace_overflow(doc) ->
+ "Patch from http://vcs.pcre.org/viewvc/code/trunk/pcre_compile.c?r1=504&r2=505&view=patch";
+pcre_compile_workspace_overflow(Config) when is_list(Config) ->
+ N = 819,
+ ?line {error,{"internal error: overran compiling workspace",799}} =
+ re:compile([lists:duplicate(N, $(), lists:duplicate(N, $))]),
+ ok.
+re_infinite_loop(doc) ->
+ "Make sure matches that really loop infinitely actually fail";
+re_infinite_loop(Config) when is_list(Config) ->
+ Dog = ?t:timetrap(?t:minutes(1)),
+ ?line Str =
+ "http:/www.flickr.com/slideShow/index.gne?group_id=&user_id=69845378@N0",
+ ?line EMail_regex = "[a-z0-9!#$%&'*+/=?^_`{|}~-]+"
+ ++ "(\.[a-z0-9!#$%&'*+/=?^_`{|}~-]+)*"
+ ++ "@.*([a-z0-9](?:[a-z0-9-]*[a-z0-9])?\.)+"
+ ++ "([a-zA-Z]{2}|com|org|net|gov|mil"
+ ++ "|biz|info|mobi|name|aero|jobs|museum)",
+ ?line nomatch = re:run(Str, EMail_regex),
+ ?t:timetrap_cancel(Dog),
+ ok.
diff --git a/lib/stdlib/test/select_SUITE.erl b/lib/stdlib/test/select_SUITE.erl
index 6900f1a8f5..af67b798b0 100644
--- a/lib/stdlib/test/select_SUITE.erl
+++ b/lib/stdlib/test/select_SUITE.erl
@@ -37,7 +37,7 @@
-export([config/2]).
-define(fmt(A,B),io:format(A,B)).
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(fmt(A,B),test_server:format(A,B)).
-endif.
@@ -58,23 +58,41 @@ config(priv_dir,_) ->
".".
-else.
%% When run in test server.
--export([all/1,select_test/1,init_per_testcase/2, fin_per_testcase/2,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,select_test/1,
+ init_per_testcase/2, end_per_testcase/2,
return_values/1]).
init_per_testcase(_Case, Config) when is_list(Config) ->
?line Dog=test_server:timetrap(test_server:seconds(1200)),
[{watchdog, Dog}|Config].
-
-fin_per_testcase(_Case, Config) ->
+
+end_per_testcase(_Case, Config) ->
Dog=?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
-all(doc) ->
- ["Test ets:select"];
-all(suite) ->
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
[return_values, select_test].
-
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
select_test(suite) ->
[];
select_test(doc) ->
diff --git a/lib/stdlib/test/sets_SUITE.erl b/lib/stdlib/test/sets_SUITE.erl
index c9f1a03598..bce23c7b12 100644
--- a/lib/stdlib/test/sets_SUITE.erl
+++ b/lib/stdlib/test/sets_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2004-2009. All Rights Reserved.
+%% Copyright Ericsson AB 2004-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
@@ -22,13 +22,15 @@
-module(sets_SUITE).
--export([all/1,init_per_testcase/2,fin_per_testcase/2,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
+ init_per_testcase/2,end_per_testcase/2,
create/1,add_element/1,del_element/1,
subtract/1,intersection/1,union/1,is_subset/1,
is_set/1,fold/1,filter/1,
take_smallest/1,take_largest/1]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-import(lists, [foldl/3,reverse/1]).
@@ -36,15 +38,33 @@ init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?t:minutes(5)),
[{watchdog,Dog}|Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog = ?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
-all(suite) ->
- [create,add_element,del_element,subtract,
- intersection,union,is_subset,is_set,fold,filter,
- take_smallest,take_largest].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [create, add_element, del_element, subtract,
+ intersection, union, is_subset, is_set, fold, filter,
+ take_smallest, take_largest].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
create(Config) when is_list(Config) ->
test_all(fun create_1/1).
diff --git a/lib/stdlib/test/sets_test_lib.erl b/lib/stdlib/test/sets_test_lib.erl
index 6b6fb00550..bdfb0d59d2 100644
--- a/lib/stdlib/test/sets_test_lib.erl
+++ b/lib/stdlib/test/sets_test_lib.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2004-2009. All Rights Reserved.
+%% Copyright Ericsson AB 2004-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
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index 588342d46a..4f8c9dffd3 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -17,21 +17,22 @@
%% %CopyrightEnd%
%%
-module(shell_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
-export([forget/1, records/1, known_bugs/1, otp_5226/1, otp_5327/1,
- otp_5435/1, otp_5195/1, otp_5915/1, otp_5916/1,
- bits/1, bs_match_misc_SUITE/1, bs_match_int_SUITE/1,
- bs_match_tail_SUITE/1, bs_match_bin_SUITE/1,
- bs_construct_SUITE/1,
- refman/1, refman_bit_syntax/1,
- progex/1, progex_bit_syntax/1, progex_records/1,
- progex_lc/1, progex_funs/1,
- tickets/1, otp_5990/1, otp_6166/1, otp_6554/1, otp_6785/1,
- otp_7184/1, otp_7232/1, otp_8393/1]).
-
--export([restricted/1, start_restricted_from_shell/1,
- start_restricted_on_command_line/1,restricted_local/1]).
+ otp_5435/1, otp_5195/1, otp_5915/1, otp_5916/1,
+ bs_match_misc_SUITE/1, bs_match_int_SUITE/1,
+ bs_match_tail_SUITE/1, bs_match_bin_SUITE/1,
+ bs_construct_SUITE/1,
+ refman_bit_syntax/1,
+ progex_bit_syntax/1, progex_records/1,
+ progex_lc/1, progex_funs/1,
+ otp_5990/1, otp_6166/1, otp_6554/1, otp_6785/1,
+ otp_7184/1, otp_7232/1, otp_8393/1]).
+
+-export([ start_restricted_from_shell/1,
+ start_restricted_on_command_line/1,restricted_local/1]).
%% Internal export.
-export([otp_5435_2/0, prompt1/1, prompt2/1, prompt3/1, prompt4/1,
@@ -50,8 +51,8 @@
config(priv_dir,_) ->
".".
-else.
--include("test_server.hrl").
--export([init_per_testcase/2, fin_per_testcase/2]).
+-include_lib("test_server/include/test_server.hrl").
+-export([init_per_testcase/2, end_per_testcase/2]).
% Default timetrap timeout (set in init_per_testcase).
-define(default_timeout, ?t:minutes(2)).
init_per_testcase(_Case, Config) ->
@@ -60,7 +61,7 @@ init_per_testcase(_Case, Config) ->
?line code:add_patha(?config(priv_dir,Config)),
[{orig_path,OrigPath}, {watchdog, Dog} | Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
?line Dog = ?config(watchdog, Config),
?line test_server:timetrap_cancel(Dog),
?line OrigPath = ?config(orig_path,Config),
@@ -71,18 +72,44 @@ fin_per_testcase(_Case, Config) ->
ok.
-endif.
-all(doc) ->
- ["Test cases for the 'shell' module."];
-all(suite) ->
- [forget, records, known_bugs, otp_5226, otp_5327, otp_5435, otp_5195,
- otp_5915, otp_5916, bits, refman, progex, tickets, restricted].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [forget, records, known_bugs, otp_5226, otp_5327,
+ otp_5435, otp_5195, otp_5915, otp_5916, {group, bits},
+ {group, refman}, {group, progex}, {group, tickets},
+ {group, restricted}].
+
+groups() ->
+ [{restricted, [],
+ [start_restricted_from_shell,
+ start_restricted_on_command_line, restricted_local]},
+ {bits, [],
+ [bs_match_misc_SUITE, bs_match_tail_SUITE,
+ bs_match_bin_SUITE, bs_construct_SUITE]},
+ {refman, [], [refman_bit_syntax]},
+ {progex, [],
+ [progex_bit_syntax, progex_records, progex_lc,
+ progex_funs]},
+ {tickets, [],
+ [otp_5990, otp_6166, otp_6554, otp_6785, otp_7184,
+ otp_7232, otp_8393]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
-record(state, {bin, reply, leader}).
-restricted(doc) ->
- ["Test restricted_shell"];
-restricted(suite) ->
- [start_restricted_from_shell,start_restricted_on_command_line,restricted_local].
start_restricted_from_shell(doc) ->
["Test that a restricted shell can be started from the normal shell"];
@@ -797,9 +824,6 @@ otp_5916(Config) when is_list(Config) ->
[ok] = scan(C),
ok.
-bits(suite) ->
- [bs_match_misc_SUITE, % bs_match_int_SUITE/,
- bs_match_tail_SUITE, bs_match_bin_SUITE, bs_construct_SUITE].
bs_match_misc_SUITE(doc) ->
["OTP-5327. Adopted from parts of emulator/test/bs_match_misc_SUITE.erl."];
@@ -1520,8 +1544,6 @@ evaluate(Str, Vars) ->
Result
end.
-refman(suite) ->
- [refman_bit_syntax].
refman_bit_syntax(doc) ->
["Bit syntax examples from the Reference Manual. OTP-5237."];
@@ -1564,8 +1586,6 @@ refman_bit_syntax(Config) when is_list(Config) ->
?line <<2,4,6>> = << << (X*2) >> || <<X>> <= << 1,2,3 >> >>,
ok.
-progex(suite) ->
- [progex_bit_syntax, progex_records, progex_lc, progex_funs].
-define(IP_VERSION, 4).
-define(IP_MIN_HDR_LEN, 5).
@@ -2256,8 +2276,6 @@ progex_funs(Config) when is_list(Config) ->
?line [ok] = scan(Test2_shell),
ok.
-tickets(suite) ->
- [otp_5990, otp_6166, otp_6554, otp_6785, otp_7184, otp_7232, otp_8393].
otp_5990(doc) ->
"OTP-5990. {erlang,is_record}.";
diff --git a/lib/stdlib/test/slave_SUITE.erl b/lib/stdlib/test/slave_SUITE.erl
index 5c1282fe9b..12325dcca9 100644
--- a/lib/stdlib/test/slave_SUITE.erl
+++ b/lib/stdlib/test/slave_SUITE.erl
@@ -18,18 +18,37 @@
%%
-module(slave_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
--export([all/1, t_start/1, t_start_link/1,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2, t_start/1, t_start_link/1,
start_link_nodedown/1, errors/1]).
%% Internal exports.
-export([fun_init/1, test_errors/1]).
-export([timeout_test/1, auth_test/1, rsh_test/1, start_a_slave/3]).
-all(suite) ->
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
[t_start_link, start_link_nodedown, t_start, errors].
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
t_start_link(suite) -> [];
t_start_link(Config) when is_list(Config) ->
?line Dog = test_server:timetrap(test_server:seconds(20)),
diff --git a/lib/stdlib/test/sofs_SUITE.erl b/lib/stdlib/test/sofs_SUITE.erl
index d60cfc6895..e1eaf7f8ec 100644
--- a/lib/stdlib/test/sofs_SUITE.erl
+++ b/lib/stdlib/test/sofs_SUITE.erl
@@ -26,13 +26,14 @@
-define(config(X,Y), foo).
-define(t, test_server).
-else.
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(format(S, A), ok).
-endif.
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
--export([sofs/1, from_term_1/1, set_1/1, from_sets_1/1, relation_1/1,
+-export([ from_term_1/1, set_1/1, from_sets_1/1, relation_1/1,
a_function_1/1, family_1/1, projection/1,
relation_to_family_1/1, domain_1/1, range_1/1, image/1,
inverse_image/1, inverse_1/1, converse_1/1, no_elements_1/1,
@@ -47,7 +48,7 @@
multiple_relative_product/1, digraph/1, constant_function/1,
misc/1]).
--export([sofs_family/1, family_specification/1,
+-export([ family_specification/1,
family_domain_1/1, family_range_1/1,
family_to_relation_1/1,
union_of_family_1/1, intersection_of_family_1/1,
@@ -81,18 +82,56 @@
union/1, union/2, family_to_digraph/1, family_to_digraph/2,
digraph_to_family/1, digraph_to_family/2]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
-compile({inline,[{eval,2}]}).
-all(suite) ->
- [sofs, sofs_family].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [{group, sofs}, {group, sofs_family}].
+
+groups() ->
+ [{sofs, [],
+ [from_term_1, set_1, from_sets_1, relation_1,
+ a_function_1, family_1, relation_to_family_1, domain_1,
+ range_1, image, inverse_image, inverse_1, converse_1,
+ no_elements_1, substitution, restriction, drestriction,
+ projection, strict_relation_1, extension,
+ weak_relation_1, to_sets_1, specification, union_1,
+ intersection_1, difference, symdiff,
+ symmetric_partition, is_sofs_set_1, is_set_1, is_equal,
+ is_subset, is_a_function_1, is_disjoint, join,
+ canonical, composite_1, relative_product_1,
+ relative_product_2, product_1, partition_1, partition_3,
+ multiple_relative_product, digraph, constant_function,
+ misc]},
+ {sofs_family, [],
+ [family_specification, family_domain_1, family_range_1,
+ family_to_relation_1, union_of_family_1,
+ intersection_of_family_1, family_projection,
+ family_difference, family_intersection_1,
+ family_intersection_2, family_union_1, family_union_2,
+ partition_family]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
init_per_testcase(_Case, Config) ->
Dog=?t:timetrap(?t:minutes(2)),
[{watchdog, Dog}|Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog=?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
@@ -100,18 +139,6 @@ fin_per_testcase(_Case, Config) ->
%% [{2,b},{1,a,b}] == lists:sort([{2,b},{1,a,b}])
%% [{1,a,b},{2,b}] == lists:keysort(1,[{2,b},{1,a,b}])
-sofs(suite) ->
- [from_term_1, set_1, from_sets_1, relation_1, a_function_1,
- family_1, relation_to_family_1, domain_1, range_1, image,
- inverse_image, inverse_1, converse_1, no_elements_1,
- substitution, restriction, drestriction, projection,
- strict_relation_1, extension, weak_relation_1, to_sets_1,
- specification, union_1, intersection_1, difference, symdiff,
- symmetric_partition, is_sofs_set_1, is_set_1, is_equal,
- is_subset, is_a_function_1, is_disjoint, join, canonical,
- composite_1, relative_product_1, relative_product_2, product_1,
- partition_1, partition_3, multiple_relative_product, digraph,
- constant_function, misc].
from_term_1(suite) -> [];
from_term_1(doc) -> [""];
@@ -1934,12 +1961,6 @@ relational_restriction(R) ->
Fun = fun(S) -> no_elements(S) > 1 end,
family_to_relation(family_specification(Fun, relation_to_family(R))).
-sofs_family(suite) ->
- [family_specification, family_domain_1, family_range_1,
- family_to_relation_1, union_of_family_1, intersection_of_family_1,
- family_projection, family_difference,
- family_intersection_1, family_intersection_2,
- family_union_1, family_union_2, partition_family].
family_specification(suite) -> [];
family_specification(doc) -> [""];
diff --git a/lib/stdlib/test/stdlib.cover b/lib/stdlib/test/stdlib.cover
index b98d949889..61f4f064b9 100644
--- a/lib/stdlib/test/stdlib.cover
+++ b/lib/stdlib/test/stdlib.cover
@@ -1,10 +1,17 @@
%% -*- erlang -*-
-{exclude,
- [erl_parse,
- ets,
- filename,
- gen_event,
- gen_server,
- gen,
- lists,
- proc_lib]}.
+{incl_app,stdlib,details}.
+
+{excl_mods,stdlib,
+ [erl_parse,
+ erl_eval,
+ ets,
+ filename,
+ gen_event,
+ gen_server,
+ gen,
+ lists,
+ io,
+ io_lib,
+ io_lib_format,
+ io_lib_pretty,
+ proc_lib]}.
diff --git a/lib/stdlib/test/stdlib.spec b/lib/stdlib/test/stdlib.spec
index bbfb43bd15..3768e494b2 100644
--- a/lib/stdlib/test/stdlib.spec
+++ b/lib/stdlib/test/stdlib.spec
@@ -1,4 +1 @@
-{topcase, {dir, "../stdlib_test"}}.
-%{skip,{dets_SUITE,open_file_1,"Crashes Windows tests"}}.
-%{skip,{dets_SUITE,fold,"Crashes Windows tests"}}.
-%{skip,{dets_SUITE,match,"Crashes Windows tests"}}.
+{suites,"../stdlib_test",all}.
diff --git a/lib/stdlib/test/stdlib_SUITE.erl b/lib/stdlib/test/stdlib_SUITE.erl
index d46a2caf90..0cca030b3d 100644
--- a/lib/stdlib/test/stdlib_SUITE.erl
+++ b/lib/stdlib/test/stdlib_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2011. 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
@@ -20,7 +20,7 @@
%%% Purpose:Stdlib application test suite.
%%%-----------------------------------------------------------------
-module(stdlib_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
% Default timetrap timeout (set in init_per_testcase).
@@ -28,8 +28,9 @@
-define(application, stdlib).
% Test server specific exports
--export([all/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
% Test cases must be exported.
-export([app_test/1]).
@@ -38,15 +39,31 @@
%%
%% all/1
%%
-all(doc) ->
- [];
-all(suite) ->
- [?cases].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [app_test].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
init_per_testcase(_Case, Config) ->
?line Dog=test_server:timetrap(?default_timeout),
[{watchdog, Dog}|Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog=?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
@@ -58,7 +75,7 @@ app_test(suite) ->
[];
app_test(doc) ->
["Application consistency test."];
-app_test(Config) when list(Config) ->
+app_test(Config) when is_list(Config) ->
?t:app_test(stdlib),
ok.
diff --git a/lib/stdlib/test/string_SUITE.erl b/lib/stdlib/test/string_SUITE.erl
index 3171b87c44..7e52441a67 100644
--- a/lib/stdlib/test/string_SUITE.erl
+++ b/lib/stdlib/test/string_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2004-2009. All Rights Reserved.
+%% Copyright Ericsson AB 2004-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
@@ -20,15 +20,16 @@
%%% Purpose: string test suite.
%%%-----------------------------------------------------------------
-module(string_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
% Default timetrap timeout (set in init_per_testcase).
-define(default_timeout, ?t:minutes(1)).
% Test server specific exports
--export([all/1]).
--export([init_per_testcase/2, fin_per_testcase/2]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2]).
+-export([init_per_testcase/2, end_per_testcase/2]).
% Test cases must be exported.
-export([len/1,equal/1,concat/1,chr_rchr/1,str_rstr/1]).
@@ -40,19 +41,34 @@
%%
%% all/1
%%
-all(doc) ->
- [];
-all(suite) ->
- [len,equal,concat,chr_rchr,str_rstr,
- span_cspan,substr,tokens,chars,
- copies,words,strip,sub_word,left_right,
- sub_string,centre, join,
- to_integer,to_float,to_upper_to_lower].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [len, equal, concat, chr_rchr, str_rstr, span_cspan,
+ substr, tokens, chars, copies, words, strip, sub_word,
+ left_right, sub_string, centre, join, to_integer,
+ to_float, to_upper_to_lower].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
init_per_testcase(_Case, Config) ->
?line Dog=test_server:timetrap(?default_timeout),
[{watchdog, Dog}|Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog=?config(watchdog, Config),
test_server:timetrap_cancel(Dog),
ok.
@@ -240,7 +256,8 @@ copies(Config) when is_list(Config) ->
?line "." = string:copies(".", 1),
?line 30 = length(string:copies("123", 10)),
%% invalid arg type
- ?line {'EXIT',_} = (catch string:chars("hej", -1)),
+ ?line {'EXIT',_} = (catch string:copies("hej", -1)),
+ ?line {'EXIT',_} = (catch string:copies("hej", 2.0)),
ok.
words(suite) ->
diff --git a/lib/stdlib/test/supervisor_1.erl b/lib/stdlib/test/supervisor_1.erl
index 297550b230..3198be0fed 100644
--- a/lib/stdlib/test/supervisor_1.erl
+++ b/lib/stdlib/test/supervisor_1.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1996-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
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index 039ea298c4..6e927da2ab 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2011. 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
@@ -20,49 +20,104 @@
-module(supervisor_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
%% Testserver specific export
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2, init_per_testcase/2,
+ end_per_testcase/2]).
%% Indirect spawn export
-export([init/1]).
%% API tests
--export([sup_start/1, sup_start_normal/1, sup_start_ignore_init/1,
+-export([ sup_start_normal/1, sup_start_ignore_init/1,
sup_start_ignore_child/1, sup_start_error_return/1,
- sup_start_fail/1, sup_stop/1, sup_stop_infinity/1,
+ sup_start_fail/1, sup_stop_infinity/1,
sup_stop_timeout/1, sup_stop_brutal_kill/1, child_adm/1,
child_adm_simple/1, child_specs/1, extra_return/1]).
%% Tests concept permanent, transient and temporary
--export([normal_termination/1, permanent_normal/1, transient_normal/1,
- temporary_normal/1, abnormal_termination/1,
+-export([ permanent_normal/1, transient_normal/1,
+ temporary_normal/1,
permanent_abnormal/1, transient_abnormal/1,
temporary_abnormal/1]).
%% Restart strategy tests
--export([restart_one_for_one/1, one_for_one/1,
- one_for_one_escalation/1, restart_one_for_all/1, one_for_all/1,
- one_for_all_escalation/1, restart_simple_one_for_one/1,
+-export([ one_for_one/1,
+ one_for_one_escalation/1, one_for_all/1,
+ one_for_all_escalation/1,
simple_one_for_one/1, simple_one_for_one_escalation/1,
- restart_rest_for_one/1, rest_for_one/1, rest_for_one_escalation/1,
+ rest_for_one/1, rest_for_one_escalation/1,
simple_one_for_one_extra/1]).
%% Misc tests
--export([child_unlink/1, tree/1, count_children_memory/1]).
+-export([child_unlink/1, tree/1, count_children_memory/1,
+ do_not_save_start_parameters_for_temporary_children/1]).
%-------------------------------------------------------------------------
-all(suite) ->
- {req,[stdlib],
- [sup_start, sup_stop, child_adm,
- child_adm_simple, extra_return, child_specs,
- restart_one_for_one, restart_one_for_all,
- restart_simple_one_for_one, restart_rest_for_one,
- normal_termination, abnormal_termination, child_unlink, tree,
- count_children_memory]}.
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [{group, sup_start}, {group, sup_stop}, child_adm,
+ child_adm_simple, extra_return, child_specs,
+ {group, restart_one_for_one},
+ {group, restart_one_for_all},
+ {group, restart_simple_one_for_one},
+ {group, restart_rest_for_one},
+ {group, normal_termination},
+ {group, abnormal_termination}, child_unlink, tree,
+ count_children_memory, do_not_save_start_parameters_for_temporary_children].
+
+groups() ->
+ [{sup_start, [],
+ [sup_start_normal, sup_start_ignore_init,
+ sup_start_ignore_child, sup_start_error_return,
+ sup_start_fail]},
+ {sup_stop, [],
+ [sup_stop_infinity, sup_stop_timeout,
+ sup_stop_brutal_kill]},
+ {normal_termination, [],
+ [permanent_normal, transient_normal, temporary_normal]},
+ {abnormal_termination, [],
+ [permanent_abnormal, transient_abnormal,
+ temporary_abnormal]},
+ {restart_one_for_one, [],
+ [one_for_one, one_for_one_escalation]},
+ {restart_one_for_all, [],
+ [one_for_all, one_for_all_escalation]},
+ {restart_simple_one_for_one, [],
+ [simple_one_for_one, simple_one_for_one_extra,
+ simple_one_for_one_escalation]},
+ {restart_rest_for_one, [],
+ [rest_for_one, rest_for_one_escalation]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+init_per_testcase(count_children_memory, Config) ->
+ MemoryState = erlang:system_info(allocator),
+ case count_children_allocator_test(MemoryState) of
+ true -> Config;
+ false ->
+ {skip, "+Meamin used during test; erlang:memory/1 not available"}
+ end;
+init_per_testcase(_Case, Config) ->
+ Config.
+
+end_per_testcase(_Case, _Config) ->
+ ok.
start(InitResult) ->
supervisor:start_link({local, sup_test}, ?MODULE, InitResult).
@@ -81,19 +136,8 @@ get_child_counts(Supervisor) ->
proplists:get_value(supervisors, Counts),
proplists:get_value(workers, Counts)].
-
%-------------------------------------------------------------------------
-%
% Test cases starts here.
-%
-%-------------------------------------------------------------------------
-
-sup_start(doc) ->
- ["Test start of a supervisor."];
-sup_start(suite) ->
- [sup_start_normal, sup_start_ignore_init, sup_start_ignore_child,
- sup_start_error_return, sup_start_fail].
-
%-------------------------------------------------------------------------
sup_start_normal(doc) ->
["Tests that the supervisor process starts correctly and that it "
@@ -192,12 +236,6 @@ sup_start_fail(Config) when is_list(Config) ->
end,
ok.
%-------------------------------------------------------------------------
-sup_stop(doc) ->
- ["Tests that the supervisor shoutdowns its children if it is "
- "shutdown itself."];
-sup_stop(suite) -> [sup_stop_infinity, sup_stop_timeout, sup_stop_brutal_kill].
-
-%-------------------------------------------------------------------------
sup_stop_infinity(doc) ->
["See sup_stop/1 when Shutdown = infinity, this walue is only allowed "
@@ -549,11 +587,6 @@ child_specs(Config) when is_list(Config) ->
?line ok = supervisor:check_childspecs([C3]),
?line ok = supervisor:check_childspecs([C4]),
ok.
-%-------------------------------------------------------------------------
-normal_termination(doc) ->
- ["Testes the supervisors behaviour if a child dies with reason normal"];
-normal_termination(suite) ->
- [permanent_normal, transient_normal, temporary_normal].
%-------------------------------------------------------------------------
permanent_normal(doc) ->
@@ -615,11 +648,6 @@ temporary_normal(Config) when is_list(Config) ->
?line [1,0,0,1] = get_child_counts(sup_test),
ok.
-%-------------------------------------------------------------------------
-abnormal_termination(doc) ->
- ["Testes the supervisors behaviour if a child dies with reason abnormal"];
-abnormal_termination(suite) ->
- [permanent_abnormal, transient_abnormal, temporary_abnormal].
%-------------------------------------------------------------------------
permanent_abnormal(doc) ->
@@ -688,12 +716,6 @@ temporary_abnormal(Config) when is_list(Config) ->
ok.
%-------------------------------------------------------------------------
-restart_one_for_one(doc) ->
- ["Test that the one_for_one strategy works."];
-
-restart_one_for_one(suite) -> [one_for_one, one_for_one_escalation].
-
-%-------------------------------------------------------------------------
one_for_one(doc) ->
["Test the one_for_one base case."];
one_for_one(suite) -> [];
@@ -772,13 +794,6 @@ one_for_one_escalation(Config) when is_list(Config) ->
end,
ok.
%-------------------------------------------------------------------------
-restart_one_for_all(doc) ->
- ["Test that the one_for_all strategy works."];
-
-restart_one_for_all(suite) ->
- [one_for_all, one_for_all_escalation].
-
-%-------------------------------------------------------------------------
one_for_all(doc) ->
["Test the one_for_all base case."];
one_for_all(suite) -> [];
@@ -866,14 +881,6 @@ one_for_all_escalation(Config) when is_list(Config) ->
ok.
%-------------------------------------------------------------------------
-restart_simple_one_for_one(doc) ->
- ["Test that the simple_one_for_one strategy works."];
-
-restart_simple_one_for_one(suite) ->
- [simple_one_for_one, simple_one_for_one_extra,
- simple_one_for_one_escalation].
-
-%-------------------------------------------------------------------------
simple_one_for_one(doc) ->
["Test the simple_one_for_one base case."];
simple_one_for_one(suite) -> [];
@@ -990,11 +997,6 @@ simple_one_for_one_escalation(Config) when is_list(Config) ->
end,
ok.
%-------------------------------------------------------------------------
-restart_rest_for_one(doc) ->
- ["Test that the rest_for_one strategy works."];
-restart_rest_for_one(suite) -> [rest_for_one, rest_for_one_escalation].
-
-%-------------------------------------------------------------------------
rest_for_one(doc) ->
["Test the rest_for_one base case."];
rest_for_one(suite) -> [];
@@ -1267,26 +1269,10 @@ tree(Config) when is_list(Config) ->
ok.
%-------------------------------------------------------------------------
-count_children_allocator_test(MemoryState) ->
- Allocators = [temp_alloc, eheap_alloc, binary_alloc, ets_alloc,
- driver_alloc, sl_alloc, ll_alloc, fix_alloc, std_alloc,
- sys_alloc],
- MemoryStateList = element(4, MemoryState),
- AllocTypes = [lists:keyfind(Alloc, 1, MemoryStateList)
- || Alloc <- Allocators],
- AllocStates = [lists:keyfind(e, 1, AllocValue)
- || {_Type, AllocValue} <- AllocTypes],
- lists:all(fun(State) -> State == {e, true} end, AllocStates).
-
count_children_memory(doc) ->
- ["Test that which_children eats memory, but count_children does not."];
+ ["Test that count_children does not eat memory."];
count_children_memory(suite) ->
- MemoryState = erlang:system_info(allocator),
- case count_children_allocator_test(MemoryState) of
- true -> [];
- false ->
- {skip, "+Meamin used during test; erlang:memory/1 not available"}
- end;
+ [];
count_children_memory(Config) when is_list(Config) ->
process_flag(trap_exit, true),
Child = {child, {supervisor_1, start_child, []}, temporary, 1000,
@@ -1299,7 +1285,7 @@ count_children_memory(Config) when is_list(Config) ->
Children = supervisor:which_children(sup_test),
_Size2 = erlang:memory(processes_used),
ChildCount = get_child_counts(sup_test),
- Size3 = erlang:memory(processes_used),
+ _Size3 = erlang:memory(processes_used),
[supervisor:start_child(sup_test, []) || _Ignore2 <- lists:seq(1,1000)],
@@ -1323,8 +1309,8 @@ count_children_memory(Config) when is_list(Config) ->
?line ChildCount3 = ChildCount2,
%% count_children consumes memory using an accumulator function,
- %% but the space can be reclaimed incrementally, whereas
- %% which_children generates a return list.
+ %% but the space can be reclaimed incrementally,
+ %% which_children may generate garbage that will be reclaimed later.
case (Size5 =< Size4) of
true -> ok;
false ->
@@ -1336,19 +1322,98 @@ count_children_memory(Config) when is_list(Config) ->
?line test_server:fail({count_children, used_more_memory})
end,
- case Size4 > Size3 of
- true -> ok;
- false ->
- ?line test_server:fail({which_children, used_no_memory})
- end,
- case Size6 > Size5 of
- true -> ok;
- false ->
- ?line test_server:fail({which_children, used_no_memory})
- end,
-
[exit(Pid, kill) || {undefined, Pid, worker, _Modules} <- Children3],
test_server:sleep(100),
?line [1,0,0,0] = get_child_counts(sup_test),
-
ok.
+count_children_allocator_test(MemoryState) ->
+ Allocators = [temp_alloc, eheap_alloc, binary_alloc, ets_alloc,
+ driver_alloc, sl_alloc, ll_alloc, fix_alloc, std_alloc,
+ sys_alloc],
+ MemoryStateList = element(4, MemoryState),
+ AllocTypes = [lists:keyfind(Alloc, 1, MemoryStateList)
+ || Alloc <- Allocators],
+ AllocStates = [lists:keyfind(e, 1, AllocValue)
+ || {_Type, AllocValue} <- AllocTypes],
+ lists:all(fun(State) -> State == {e, true} end, AllocStates).
+%-------------------------------------------------------------------------
+do_not_save_start_parameters_for_temporary_children(doc) ->
+ ["Temporary children shall not be restarted so they should not "
+ "save start parameters, as it potentially can "
+ "take up a huge amount of memory for no purpose."];
+do_not_save_start_parameters_for_temporary_children(suite) ->
+ [];
+do_not_save_start_parameters_for_temporary_children(Config) when is_list(Config) ->
+ process_flag(trap_exit, true),
+ dont_save_start_parameters_for_temporary_children(one_for_all),
+ dont_save_start_parameters_for_temporary_children(one_for_one),
+ dont_save_start_parameters_for_temporary_children(rest_for_one),
+ dont_save_start_parameters_for_temporary_children(simple_one_for_one).
+
+dont_save_start_parameters_for_temporary_children(simple_one_for_one = Type) ->
+ Permanent = {child, {supervisor_1, start_child, []},
+ permanent, 1000, worker, []},
+ Transient = {child, {supervisor_1, start_child, []},
+ transient, 1000, worker, []},
+ Temporary = {child, {supervisor_1, start_child, []},
+ temporary, 1000, worker, []},
+ {ok, Sup1} = supervisor:start_link(?MODULE, {ok, {{Type, 2, 3600}, [Permanent]}}),
+ {ok, Sup2} = supervisor:start_link(?MODULE, {ok, {{Type, 2, 3600}, [Transient]}}),
+ {ok, Sup3} = supervisor:start_link(?MODULE, {ok, {{Type, 2, 3600}, [Temporary]}}),
+
+ LargeList = lists:duplicate(10, "Potentially large"),
+
+ start_children(Sup1, [LargeList], 100),
+ start_children(Sup2, [LargeList], 100),
+ start_children(Sup3, [LargeList], 100),
+
+ [{memory,Mem1}] = process_info(Sup1, [memory]),
+ [{memory,Mem2}] = process_info(Sup2, [memory]),
+ [{memory,Mem3}] = process_info(Sup3, [memory]),
+
+ true = (Mem3 < Mem1) and (Mem3 < Mem2),
+
+ exit(Sup1, shutdown),
+ exit(Sup2, shutdown),
+ exit(Sup3, shutdown);
+
+dont_save_start_parameters_for_temporary_children(Type) ->
+ {ok, Sup1} = supervisor:start_link(?MODULE, {ok, {{Type, 2, 3600}, []}}),
+ {ok, Sup2} = supervisor:start_link(?MODULE, {ok, {{Type, 2, 3600}, []}}),
+ {ok, Sup3} = supervisor:start_link(?MODULE, {ok, {{Type, 2, 3600}, []}}),
+
+ LargeList = lists:duplicate(10, "Potentially large"),
+
+ Permanent = {child1, {supervisor_1, start_child, [LargeList]},
+ permanent, 1000, worker, []},
+ Transient = {child2, {supervisor_1, start_child, [LargeList]},
+ transient, 1000, worker, []},
+ Temporary = {child3, {supervisor_1, start_child, [LargeList]},
+ temporary, 1000, worker, []},
+
+ start_children(Sup1, Permanent, 100),
+ start_children(Sup2, Transient, 100),
+ start_children(Sup3, Temporary, 100),
+
+ [{memory,Mem1}] = process_info(Sup1, [memory]),
+ [{memory,Mem2}] = process_info(Sup2, [memory]),
+ [{memory,Mem3}] = process_info(Sup3, [memory]),
+
+ true = (Mem3 < Mem1) and (Mem3 < Mem2),
+
+ exit(Sup1, shutdown),
+ exit(Sup2, shutdown),
+ exit(Sup3, shutdown).
+
+start_children(_,_, 0) ->
+ ok;
+start_children(Sup, Args, N) ->
+ Spec = child_spec(Args, N),
+ {ok, _, _} = supervisor:start_child(Sup, Spec),
+ start_children(Sup, Args, N-1).
+
+child_spec([_|_] = SimpleOneForOneArgs, _) ->
+ SimpleOneForOneArgs;
+child_spec({Name, MFA, RestartType, Shutdown, Type, Modules}, N) ->
+ NewName = list_to_atom((atom_to_list(Name) ++ integer_to_list(N))),
+ {NewName, MFA, RestartType, Shutdown, Type, Modules}.
diff --git a/lib/stdlib/test/supervisor_bridge_SUITE.erl b/lib/stdlib/test/supervisor_bridge_SUITE.erl
index b23bac2d44..407968747c 100644
--- a/lib/stdlib/test/supervisor_bridge_SUITE.erl
+++ b/lib/stdlib/test/supervisor_bridge_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1996-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
@@ -17,16 +17,37 @@
%% %CopyrightEnd%
%%
-module(supervisor_bridge_SUITE).
--export([all/1,starting/1,mini_terminate/1,mini_die/1,badstart/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,starting/1,
+ mini_terminate/1,mini_die/1,badstart/1]).
-export([client/1,init/1,internal_loop_init/1,terminate/2]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(bridge_name,supervisor_bridge_SUITE_server).
-define(work_bridge_name,work_supervisor_bridge_SUITE_server).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-all(suite) -> [starting,mini_terminate,mini_die,badstart].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [starting, mini_terminate, mini_die, badstart].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
diff --git a/lib/stdlib/test/sys_SUITE.erl b/lib/stdlib/test/sys_SUITE.erl
index e44fd56403..dcb2380910 100644
--- a/lib/stdlib/test/sys_SUITE.erl
+++ b/lib/stdlib/test/sys_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1996-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
@@ -17,9 +17,11 @@
%% %CopyrightEnd%
%%
-module(sys_SUITE).
--export([all/1,log/1,log_to_file/1,stats/1,trace/1,suspend/1,install/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,log/1,log_to_file/1,
+ stats/1,trace/1,suspend/1,install/1]).
-export([handle_call/3,terminate/2,init/1]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(server,sys_SUITE_server).
@@ -29,7 +31,26 @@
%% system messages at all.
-all(suite) -> [log,log_to_file,stats,trace,suspend,install].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [log, log_to_file, stats, trace, suspend, install].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl
index 7646f4c249..84c3915749 100644
--- a/lib/stdlib/test/tar_SUITE.erl
+++ b/lib/stdlib/test/tar_SUITE.erl
@@ -18,21 +18,39 @@
%%
-module(tar_SUITE).
--export([all/1, borderline/1, atomic/1, long_names/1,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2, borderline/1, atomic/1, long_names/1,
create_long_names/1, bad_tar/1, errors/1, extract_from_binary/1,
extract_from_binary_compressed/1,
extract_from_open_file/1, symlinks/1, open_add_close/1, cooked_compressed/1,
memory/1]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-include_lib("kernel/include/file.hrl").
-all(suite) -> [borderline, atomic, long_names, create_long_names,
- bad_tar, errors,
- extract_from_binary, extract_from_binary_compressed,
- extract_from_open_file,
- symlinks, open_add_close, cooked_compressed,
- memory].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [borderline, atomic, long_names, create_long_names,
+ bad_tar, errors, extract_from_binary,
+ extract_from_binary_compressed, extract_from_open_file,
+ symlinks, open_add_close, cooked_compressed, memory].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
borderline(doc) ->
["Test creating, listing and extracting one file from an archive",
diff --git a/lib/stdlib/test/timer_SUITE.erl b/lib/stdlib/test/timer_SUITE.erl
index 5f38c91c64..cc05e3d832 100644
--- a/lib/stdlib/test/timer_SUITE.erl
+++ b/lib/stdlib/test/timer_SUITE.erl
@@ -18,12 +18,12 @@
%%
-module(timer_SUITE).
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2]).
-export([do_big_test/1]).
-export([big_test/1, collect/3, i_t/3, a_t/2]).
-export([do_nrev/1, internal_watchdog/2]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
%% Test suite for timer module. This is a really nasty test it runs a
%% lot of timeouts and then checks in the end if any of them was
@@ -51,7 +51,26 @@
%% amount of load. The test suite should also include tests that test the
%% interface of the timer module.
-all(suite) -> [do_big_test].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [do_big_test].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
%% ------------------------------------------------------- %%
diff --git a/lib/stdlib/test/timer_simple_SUITE.erl b/lib/stdlib/test/timer_simple_SUITE.erl
index 021a22c61b..afe6699920 100644
--- a/lib/stdlib/test/timer_simple_SUITE.erl
+++ b/lib/stdlib/test/timer_simple_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1997-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
@@ -21,7 +21,8 @@
-module(timer_simple_SUITE).
%% external
--export([all/1,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
init_per_testcase/2,
apply_after/1,
send_after1/1,
@@ -49,31 +50,35 @@
timer/4,
timer/5]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-define(MAXREF, (1 bsl 18)).
-define(REFMARG, 30).
-all(doc) -> "Test of the timer module.";
-all(suite) ->
- [apply_after,
- send_after1,
- send_after2,
- send_after3,
- exit_after1,
- exit_after2,
- kill_after1,
- kill_after2,
- apply_interval,
- send_interval1,
- send_interval2,
- send_interval3,
- send_interval4,
- cancel1,
- cancel2,
- tc,
- unique_refs,
- timer_perf].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [apply_after, send_after1, send_after2, send_after3,
+ exit_after1, exit_after2, kill_after1, kill_after2,
+ apply_interval, send_interval1, send_interval2,
+ send_interval3, send_interval4, cancel1, cancel2, tc,
+ unique_refs, timer_perf].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
init_per_testcase(_, Config) when is_list(Config) ->
timer:start(),
@@ -224,11 +229,19 @@ cancel2(Config) when is_list(Config) ->
tc(doc) -> "Test sleep/1 and tc/3.";
tc(suite) -> [];
tc(Config) when is_list(Config) ->
- % This should both sleep and tc
- ?line {Res, ok} = timer:tc(timer, sleep, [500]),
- ?line ok = if
- Res < 500*1000 -> {too_early, Res}; % Too early
- Res > 800*1000 -> {too_late, Res}; % Too much time
+ % This should both sleep and tc/3
+ ?line {Res1, ok} = timer:tc(timer, sleep, [500]),
+ ?line ok = if
+ Res1 < 500*1000 -> {too_early, Res1}; % Too early
+ Res1 > 800*1000 -> {too_late, Res1}; % Too much time
+ true -> ok
+ end,
+
+ % This should both sleep and tc/2
+ ?line {Res2, ok} = timer:tc(fun(T) -> timer:sleep(T) end, [500]),
+ ?line ok = if
+ Res2 < 500*1000 -> {too_early, Res2}; % Too early
+ Res2 > 800*1000 -> {too_late, Res2}; % Too much time
true -> ok
end,
diff --git a/lib/stdlib/test/unicode_SUITE.erl b/lib/stdlib/test/unicode_SUITE.erl
index 141ac64606..3cca1ab894 100644
--- a/lib/stdlib/test/unicode_SUITE.erl
+++ b/lib/stdlib/test/unicode_SUITE.erl
@@ -18,11 +18,12 @@
%%
-module(unicode_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
--export([all/1,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
init_per_testcase/2,
- fin_per_testcase/2,
+ end_per_testcase/2,
utf8_illegal_sequences_bif/1,
utf16_illegal_sequences_bif/1,
random_lists/1,
@@ -34,12 +35,32 @@ init_per_testcase(Case, Config) when is_atom(Case), is_list(Config) ->
Dog=?t:timetrap(?t:minutes(20)),
[{watchdog, Dog}|Config].
-fin_per_testcase(_Case, Config) ->
+end_per_testcase(_Case, Config) ->
Dog = ?config(watchdog, Config),
?t:timetrap_cancel(Dog).
-all(suite) ->
- [utf8_illegal_sequences_bif,utf16_illegal_sequences_bif,random_lists,roundtrips,latin1,exceptions].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [utf8_illegal_sequences_bif,
+ utf16_illegal_sequences_bif, random_lists, roundtrips,
+ latin1, exceptions].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
exceptions(Config) when is_list(Config) ->
diff --git a/lib/stdlib/test/win32reg_SUITE.erl b/lib/stdlib/test/win32reg_SUITE.erl
index c8cc82f61e..f54cd2dcca 100644
--- a/lib/stdlib/test/win32reg_SUITE.erl
+++ b/lib/stdlib/test/win32reg_SUITE.erl
@@ -18,22 +18,34 @@
%%
-module(win32reg_SUITE).
--export([all/1,long/1,evil_write/1]).
--export([ostype/1,fini/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,long/1,evil_write/1]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-all(suite) ->
- [{conf,ostype,[long,evil_write],fini}].
+suite() -> [{ct_hooks,[ts_install_cth]}].
-ostype(Config) when is_list(Config) ->
+all() ->
+ [long, evil_write].
+
+groups() ->
+ [].
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
+init_per_suite(Config) when is_list(Config) ->
case os:type() of
{win32, _} ->
Config;
_ ->
{skip,"Doesn't run on UNIX."}
end.
-fini(Config) when is_list(Config) ->
+end_per_suite(Config) when is_list(Config) ->
Config.
long(doc) -> "Test long keys and entries (OTP-3446).";
diff --git a/lib/stdlib/test/y2k_SUITE.erl b/lib/stdlib/test/y2k_SUITE.erl
index a574d5e36e..0ea51355e2 100644
--- a/lib/stdlib/test/y2k_SUITE.erl
+++ b/lib/stdlib/test/y2k_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2009. All Rights Reserved.
+%% Copyright Ericsson AB 1998-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
@@ -21,30 +21,38 @@
-module(y2k_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
--export([all/1,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
date_1999_01_01/1, date_1999_02_28/1,
date_1999_09_09/1, date_2000_01_01/1,
date_2000_02_29/1, date_2001_01_01/1,
date_2001_02_29/1, date_2004_02_29/1
]).
-all(doc) ->
- "This is the test suite for year 2000. Eight dates according "
- "to Ericsson Corporate Millennium Test Specification "
- "(LME/DT-98:1097 are tested.";
-
-all(suite) ->
- [date_1999_01_01,
- date_1999_02_28,
- date_1999_09_09,
- date_2000_01_01,
- date_2000_02_29,
- date_2001_01_01,
- date_2001_02_29,
- date_2004_02_29
- ].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [date_1999_01_01, date_1999_02_28, date_1999_09_09,
+ date_2000_01_01, date_2000_02_29, date_2001_01_01,
+ date_2001_02_29, date_2004_02_29].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
date_1999_01_01(doc) ->
"#1 : 1999-01-01: test roll-over from 1998-12-31 to 1999-01-01.";
diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl
index 12ca655000..895019ab96 100644
--- a/lib/stdlib/test/zip_SUITE.erl
+++ b/lib/stdlib/test/zip_SUITE.erl
@@ -18,24 +18,43 @@
%%
-module(zip_SUITE).
--export([all/1, borderline/1, atomic/1,
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2, borderline/1, atomic/1,
bad_zip/1, unzip_from_binary/1, unzip_to_binary/1,
zip_to_binary/1,
unzip_options/1, zip_options/1, list_dir_options/1, aliases/1,
openzip_api/1, zip_api/1, unzip_jar/1,
- compress_control/1]).
+ compress_control/1,
+ foldl/1]).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
-include("test_server_line.hrl").
-include_lib("kernel/include/file.hrl").
-include_lib("stdlib/include/zip.hrl").
-all(suite) -> [borderline, atomic, bad_zip,
- unzip_from_binary, unzip_to_binary,
- zip_to_binary,
- unzip_options, zip_options, list_dir_options, aliases,
- openzip_api, zip_api, unzip_jar,
- compress_control].
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [borderline, atomic, bad_zip, unzip_from_binary,
+ unzip_to_binary, zip_to_binary, unzip_options,
+ zip_options, list_dir_options, aliases, openzip_api,
+ zip_api, unzip_jar, compress_control, foldl].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
borderline(doc) ->
["Test creating, listing and extracting one file from an archive "
@@ -110,17 +129,17 @@ get_data(Port, Expect) ->
{Port, {data, Bytes}} ->
get_data(Port, match_output(Bytes, Expect, Port));
{Port, eof} ->
- Port ! {self(), close},
+ Port ! {self(), close},
receive
{Port, closed} ->
true
- end,
+ end,
receive
- {'EXIT', Port, _} ->
+ {'EXIT', Port, _} ->
ok
after 1 -> % force context switch
ok
- end,
+ end,
match_output(eof, Expect, Port)
end.
@@ -290,7 +309,7 @@ unzip_options(Config) when is_list(Config) ->
DataDir = ?config(data_dir, Config),
PrivDir = ?config(priv_dir, Config),
Long = filename:join(DataDir, "abc.zip"),
-
+
%% create a temp directory
Subdir = filename:join(PrivDir, "t"),
ok = file:make_dir(Subdir),
@@ -303,7 +322,7 @@ unzip_options(Config) when is_list(Config) ->
%% Verify.
?line true = (length(FList) =:= length(RetList)),
- ?line lists:foreach(fun(F)-> {ok,B} = file:read_file(filename:join(DataDir, F)),
+ ?line lists:foreach(fun(F)-> {ok,B} = file:read_file(filename:join(DataDir, F)),
{ok,B} = file:read_file(filename:join(Subdir, F)) end,
FList),
?line lists:foreach(fun(F)-> ok = file:delete(F) end,
@@ -321,7 +340,7 @@ unzip_jar(Config) when is_list(Config) ->
DataDir = ?config(data_dir, Config),
PrivDir = ?config(priv_dir, Config),
JarFile = filename:join(DataDir, "test.jar"),
-
+
%% create a temp directory
Subdir = filename:join(PrivDir, "jartest"),
ok = file:make_dir(Subdir),
@@ -479,7 +498,7 @@ unzip_to_binary(Config) when is_list(Config) ->
DataDir = ?config(data_dir, Config),
PrivDir = ?config(priv_dir, Config),
- delete_all_in(PrivDir),
+ delete_all_in(PrivDir),
file:set_cwd(PrivDir),
Long = filename:join(DataDir, "abc.zip"),
@@ -595,17 +614,17 @@ do_delete_files([],Cnt) ->
Cnt;
do_delete_files([Item|Rest], Cnt) ->
case file:delete(Item) of
- ok ->
+ ok ->
DelCnt = 1;
{error,eperm} ->
file:change_mode(Item, 8#777),
DelCnt = delete_files(filelib:wildcard(filename:join(Item, "*"))),
- file:del_dir(Item);
+ file:del_dir(Item);
{error,eacces} ->
%% We'll see about that!
file:change_mode(Item, 8#777),
case file:delete(Item) of
- ok ->
+ ok ->
DelCnt = 1;
{error,_} ->
erlang:yield(),
@@ -643,22 +662,22 @@ compress_control(Config) when is_list(Config) ->
],
test_compress_control(Dir,
- Files,
+ Files,
[{compress, []}],
[]),
test_compress_control(Dir,
- Files,
+ Files,
[{uncompress, all}],
[]),
test_compress_control(Dir,
- Files,
+ Files,
[{uncompress, []}],
[".txt", ".exe", ".zip", ".lzh", ".arj"]),
test_compress_control(Dir,
- Files,
+ Files,
[],
[".txt", ".exe"]),
@@ -686,7 +705,7 @@ test_compress_control(Dir, Files, ZipOptions, Expected) ->
create_files(Files),
{ok, Zip} = zip:create(Zip, [Dir], ZipOptions),
-
+
{ok, OpenZip} = zip:openzip_open(Zip, [memory]),
{ok,[#zip_comment{comment = ""} | ZipList]} = zip:openzip_list_dir(OpenZip),
io:format("compress_control: -> ~p -> ~p\n -> ~pn", [Expected, ZipOptions, ZipList]),
@@ -698,19 +717,19 @@ test_compress_control(Dir, Files, ZipOptions, Expected) ->
delete_files(lists:reverse(Names)), % Remove plain files before directories
ok.
-
+
verify_compression([{Name, Kind, _Filler} | Files], ZipList, OpenZip, ZipOptions, Expected) ->
{Name2, BinSz} =
case Kind of
- dir ->
+ dir ->
{Name ++ "/", 0};
- _ ->
+ _ ->
{ok, {Name, Bin}} = zip:openzip_get(Name, OpenZip),
{Name, size(Bin)}
end,
{Name2, {value, ZipFile}} = {Name2, lists:keysearch(Name2, #zip_file.name, ZipList)},
#zip_file{info = #file_info{size = InfoSz, type = InfoType}, comp_size = InfoCompSz} = ZipFile,
-
+
Ext = filename:extension(Name),
IsComp = is_compressed(Ext, Kind, ZipOptions),
ExpComp = lists:member(Ext, Expected),
@@ -757,3 +776,33 @@ extensions([H | T], Old) ->
extensions([], Old) ->
Old.
+foldl(Config) ->
+ PrivDir = ?config(priv_dir, Config),
+ File = filename:join([PrivDir, "foldl.zip"]),
+
+ FooBin = <<"FOO">>,
+ BarBin = <<"BAR">>,
+ Files = [{"foo", FooBin}, {"bar", BarBin}],
+ ?line {ok, {File, Bin}} = zip:create(File, Files, [memory]),
+ ZipFun = fun(N, I, B, Acc) -> [{N, B(), I()} | Acc] end,
+ ?line {ok, FileSpec} = zip:foldl(ZipFun, [], {File, Bin}),
+ ?line [{"bar", BarBin, #file_info{}}, {"foo", FooBin, #file_info{}}] = FileSpec,
+ ?line {ok, {File, Bin}} = zip:create(File, lists:reverse(FileSpec), [memory]),
+ ?line {foo_bin, FooBin} =
+ try
+ zip:foldl(fun("foo", _, B, _) -> throw(B()); (_, _, _, Acc) -> Acc end, [], {File, Bin})
+ catch
+ throw:FooBin ->
+ {foo_bin, FooBin}
+ end,
+ ?line ok = file:write_file(File, Bin),
+ ?line {ok, FileSpec} = zip:foldl(ZipFun, [], File),
+
+ ?line {error, einval} = zip:foldl(fun() -> ok end, [], File),
+ ?line {error, einval} = zip:foldl(ZipFun, [], 42),
+ ?line {error, einval} = zip:foldl(ZipFun, [], {File, 42}),
+
+ ?line ok = file:delete(File),
+ ?line {error, enoent} = zip:foldl(ZipFun, [], File),
+
+ ok.