aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/Makefile1
-rw-r--r--lib/stdlib/test/base64_SUITE.erl2
-rw-r--r--lib/stdlib/test/beam_lib_SUITE.erl45
-rw-r--r--lib/stdlib/test/dets_SUITE.erl811
-rw-r--r--lib/stdlib/test/dets_SUITE_data/version_8.dets (renamed from lib/stdlib/test/dets_SUITE_data/version_r2d.dets)bin33885 -> 35143 bytes
-rw-r--r--lib/stdlib/test/dict_SUITE.erl27
-rw-r--r--lib/stdlib/test/dict_test_lib.erl20
-rw-r--r--lib/stdlib/test/epp_SUITE.erl16
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl140
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl44
-rw-r--r--lib/stdlib/test/erl_scan_SUITE.erl21
-rw-r--r--lib/stdlib/test/error_logger_h_SUITE.erl4
-rw-r--r--lib/stdlib/test/ets_SUITE.erl330
-rw-r--r--lib/stdlib/test/ets_tough_SUITE.erl58
-rw-r--r--lib/stdlib/test/filelib_SUITE.erl55
-rw-r--r--lib/stdlib/test/filename_SUITE.erl8
-rw-r--r--lib/stdlib/test/gen_event_SUITE.erl126
-rw-r--r--lib/stdlib/test/gen_server_SUITE.erl14
-rw-r--r--lib/stdlib/test/gen_statem_SUITE.erl8
-rw-r--r--lib/stdlib/test/io_SUITE.erl25
-rw-r--r--lib/stdlib/test/io_proto_SUITE.erl2
-rw-r--r--lib/stdlib/test/lists_SUITE.erl2
-rw-r--r--lib/stdlib/test/math_SUITE.erl92
-rw-r--r--lib/stdlib/test/proc_lib_SUITE.erl31
-rw-r--r--lib/stdlib/test/qlc_SUITE.erl24
-rw-r--r--lib/stdlib/test/rand_SUITE.erl182
-rw-r--r--lib/stdlib/test/random_iolist.erl38
-rw-r--r--lib/stdlib/test/random_unicode_list.erl38
-rw-r--r--lib/stdlib/test/re_testoutput1_replacement_test.erl2
-rw-r--r--lib/stdlib/test/re_testoutput1_split_test.erl2
-rw-r--r--lib/stdlib/test/run_pcre_tests.erl73
-rw-r--r--lib/stdlib/test/shell_SUITE.erl15
-rw-r--r--lib/stdlib/test/sofs_SUITE.erl9
-rw-r--r--lib/stdlib/test/tar_SUITE.erl178
-rw-r--r--lib/stdlib/test/tar_SUITE_data/bsd.tarbin0 -> 9216 bytes
-rw-r--r--lib/stdlib/test/tar_SUITE_data/gnu.tarbin0 -> 30720 bytes
-rw-r--r--lib/stdlib/test/tar_SUITE_data/pax_mtime.tarbin0 -> 10240 bytes
-rw-r--r--lib/stdlib/test/tar_SUITE_data/sparse00.tar (renamed from lib/stdlib/test/dets_SUITE_data/version_r3b02.dets)bin34484 -> 61440 bytes
-rw-r--r--lib/stdlib/test/tar_SUITE_data/sparse01.tar (renamed from lib/stdlib/test/dets_SUITE_data/dets_test_v8b.dets)bin37396 -> 61440 bytes
-rw-r--r--lib/stdlib/test/tar_SUITE_data/sparse01_empty.tarbin0 -> 10240 bytes
-rw-r--r--lib/stdlib/test/tar_SUITE_data/sparse10.tar (renamed from lib/stdlib/test/dets_SUITE_data/dets_test_v8b_little_endian.dets)bin37396 -> 61440 bytes
-rw-r--r--lib/stdlib/test/tar_SUITE_data/sparse10_empty.tarbin0 -> 10240 bytes
-rw-r--r--lib/stdlib/test/tar_SUITE_data/star.tarbin0 -> 10240 bytes
-rw-r--r--lib/stdlib/test/tar_SUITE_data/v7.tarbin0 -> 10240 bytes
-rw-r--r--lib/stdlib/test/timer_SUITE.erl2
-rw-r--r--lib/stdlib/test/timer_simple_SUITE.erl2
-rw-r--r--lib/stdlib/test/zip_SUITE.erl2
47 files changed, 1313 insertions, 1136 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index 28c35aed55..deac04aa66 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -52,6 +52,7 @@ MODULES= \
io_proto_SUITE \
lists_SUITE \
log_mf_h_SUITE \
+ math_SUITE \
ms_transform_SUITE \
proc_lib_SUITE \
qlc_SUITE \
diff --git a/lib/stdlib/test/base64_SUITE.erl b/lib/stdlib/test/base64_SUITE.erl
index d0abe5c961..6ddc67464c 100644
--- a/lib/stdlib/test/base64_SUITE.erl
+++ b/lib/stdlib/test/base64_SUITE.erl
@@ -82,7 +82,7 @@ base64_decode(Config) when is_list(Config) ->
Alphabet = list_to_binary(lists:seq(0, 255)),
Alphabet = base64:decode(base64:encode(Alphabet)),
- %% Encoded base 64 strings may be devided by non base 64 chars.
+ %% Encoded base 64 strings may be divided by non base 64 chars.
%% In this cases whitespaces.
"0123456789!@#0^&*();:<>,. []{}" =
base64:decode_to_string(
diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl
index 4521ecc0ef..279e15f703 100644
--- a/lib/stdlib/test/beam_lib_SUITE.erl
+++ b/lib/stdlib/test/beam_lib_SUITE.erl
@@ -81,12 +81,8 @@ normal(Conf) when is_list(Conf) ->
NoOfTables = length(ets:all()),
P0 = pps(),
- CompileFlags = [{outdir,PrivDir}, debug_info],
- {ok,_} = compile:file(Source, CompileFlags),
- {ok, Binary} = file:read_file(BeamFile),
-
- do_normal(BeamFile),
- do_normal(Binary),
+ do_normal(Source, PrivDir, BeamFile, []),
+ do_normal(Source, PrivDir, BeamFile, [no_utf8_atoms]),
{ok,_} = compile:file(Source, [{outdir,PrivDir}, no_debug_info]),
{ok, {simple, [{abstract_code, no_abstract_code}]}} =
@@ -101,7 +97,15 @@ normal(Conf) when is_list(Conf) ->
true = (P0 == pps()),
ok.
-do_normal(BeamFile) ->
+do_normal(Source, PrivDir, BeamFile, Opts) ->
+ CompileFlags = [{outdir,PrivDir}, debug_info | Opts],
+ {ok,_} = compile:file(Source, CompileFlags),
+ {ok, Binary} = file:read_file(BeamFile),
+
+ do_normal(BeamFile, Opts),
+ do_normal(Binary, Opts).
+
+do_normal(BeamFile, Opts) ->
Imports = {imports, [{erlang, get_module_info, 1},
{erlang, get_module_info, 2},
{lists, member, 2}]},
@@ -130,20 +134,31 @@ do_normal(BeamFile) ->
beam_lib:chunks(BeamFile, [abstract_code]),
%% Test reading optional chunks.
- All = ["Atom", "Code", "StrT", "ImpT", "ExpT", "FunT", "LitT"],
+ All = ["Atom", "Code", "StrT", "ImpT", "ExpT", "FunT", "LitT", "AtU8"],
{ok,{simple,Chunks}} = beam_lib:chunks(BeamFile, All, [allow_missing_chunks]),
- verify_simple(Chunks).
+ case {verify_simple(Chunks),Opts} of
+ {{missing_chunk, AtomBin}, []} when is_binary(AtomBin) -> ok;
+ {{AtomBin, missing_chunk}, [no_utf8_atoms]} when is_binary(AtomBin) -> ok
+ end,
-verify_simple([{"Atom", AtomBin},
+ %% Make sure that reading the atom chunk works when the 'allow_missing_chunks'
+ %% option is used.
+ Some = ["Code",atoms,"ExpT","LitT"],
+ {ok,{simple,SomeChunks}} = beam_lib:chunks(BeamFile, Some, [allow_missing_chunks]),
+ [{"Code",<<_/binary>>},{atoms,[_|_]},{"ExpT",<<_/binary>>},{"LitT",missing_chunk}] =
+ SomeChunks.
+
+verify_simple([{"Atom", PlainAtomChunk},
{"Code", CodeBin},
{"StrT", StrBin},
{"ImpT", ImpBin},
{"ExpT", ExpBin},
{"FunT", missing_chunk},
- {"LitT", missing_chunk}])
- when is_binary(AtomBin), is_binary(CodeBin), is_binary(StrBin),
+ {"LitT", missing_chunk},
+ {"AtU8", AtU8Chunk}])
+ when is_binary(CodeBin), is_binary(StrBin),
is_binary(ImpBin), is_binary(ExpBin) ->
- ok.
+ {PlainAtomChunk, AtU8Chunk}.
%% Read invalid beam files.
error(Conf) when is_list(Conf) ->
@@ -211,7 +226,7 @@ last_chunk(Bin) ->
do_error(BeamFile, ACopy) ->
%% evil tests
Chunks = chunk_info(BeamFile),
- {value, {_, AtomStart, _}} = lists:keysearch("Atom", 1, Chunks),
+ {value, {_, AtomStart, _}} = lists:keysearch("AtU8", 1, Chunks),
{value, {_, ImportStart, _}} = lists:keysearch("ImpT", 1, Chunks),
{value, {_, AbstractStart, _}} = lists:keysearch("Abst", 1, Chunks),
{value, {_, AttributesStart, _}} =
@@ -234,7 +249,7 @@ do_error(BeamFile, ACopy) ->
verify(not_a_beam_file, beam_lib:info(BF7)),
BF8 = set_byte(ACopy, BeamFile, 13, 17),
- verify(missing_chunk, beam_lib:chunks(BF8, ["Atom"])),
+ verify(missing_chunk, beam_lib:chunks(BF8, ["AtU8"])),
BF9 = set_byte(ACopy, BeamFile, CompileInfoStart+10, 17),
verify(invalid_chunk, beam_lib:chunks(BF9, [compile_info])).
diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl
index 8948f496c4..95c9b47465 100644
--- a/lib/stdlib/test/dets_SUITE.erl
+++ b/lib/stdlib/test/dets_SUITE.erl
@@ -35,26 +35,18 @@
-endif.
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
- init_per_group/2,end_per_group/2,
- 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,
- bag_next_v8/1, bag_next_v9/1, oldbugs_v8/1, oldbugs_v9/1,
- unsafe_assumptions/1, truncated_segment_array_v8/1,
- truncated_segment_array_v9/1, open_file_v8/1, open_file_v9/1,
- init_table_v8/1, init_table_v9/1, repair_v8/1, repair_v9/1,
- hash_v8b_v8c/1, phash/1, fold_v8/1, fold_v9/1, fixtable_v8/1,
- fixtable_v9/1, match_v8/1, match_v9/1, select_v8/1,
- select_v9/1, update_counter/1, badarg/1, cache_sets_v8/1,
- cache_sets_v9/1, cache_bags_v8/1, cache_bags_v9/1,
- cache_duplicate_bags_v8/1, cache_duplicate_bags_v9/1,
+ init_per_group/2,end_per_group/2, newly_started/1, basic/1,
+ open/1, sets/1, bags/1, duplicate_bags/1, access/1, dirty_mark/1,
+ dirty_mark2/1, bag_next/1, oldbugs/1,
+ truncated_segment_array/1, open_file/1, init_table/1, repair/1,
+ phash/1, fold/1, fixtable/1, match/1, select/1, update_counter/1,
+ badarg/1, cache_sets/1, cache_bags/1, cache_duplicate_bags/1,
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_8856/1, otp_8898/1, otp_8899/1, otp_8903/1,
otp_8923/1, otp_9282/1, otp_11245/1, otp_11709/1, otp_13229/1,
- otp_13260/1]).
+ otp_13260/1, otp_13830/1]).
-export([dets_dirty_loop/0]).
@@ -73,8 +65,7 @@
-define(DETS_SERVER, dets).
-%% HEADSZ taken from dets_v8.erl and dets_v9.erl.
--define(HEADSZ_v8, 40).
+%% HEADSZ taken from dets_v9.erl.
-define(HEADSZ_v9, (56+28*4+16)).
-define(NO_KEYS_POS_v9, 36).
-define(CLOSED_PROPERLY_POS, 8).
@@ -94,24 +85,16 @@ suite() ->
all() ->
[
- 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,
+ basic, open, sets, bags, duplicate_bags, newly_started, open_file,
+ init_table, repair, access, oldbugs,
+ truncated_segment_array, dirty_mark, dirty_mark2, bag_next,
+ phash, fold, fixtable, match, select, update_counter, badarg,
+ cache_sets, cache_bags, cache_duplicate_bags, 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, otp_9282, otp_11245, otp_11709,
- otp_13229, otp_13260
+ otp_13229, otp_13260, otp_13830
].
groups() ->
@@ -137,20 +120,12 @@ newly_started(Config) when is_list(Config) ->
test_server:stop_node(Node),
ok.
-%% Basic test case.
-basic_v8(Config) when is_list(Config) ->
- basic(Config, 8).
-
-%% Basic test case.
-basic_v9(Config) when is_list(Config) ->
- basic(Config, 9).
-
-basic(Config, Version) ->
+basic(Config) when is_list(Config) ->
Tab = dets_basic_test,
FName = filename(Tab, Config),
P0 = pps(),
- {ok, _} = dets:open_file(Tab,[{file, FName},{version,Version}]),
+ {ok, _} = dets:open_file(Tab,[{file, FName}]),
ok = dets:insert(Tab,{mazda,japan}),
ok = dets:insert(Tab,{toyota,japan}),
ok = dets:insert(Tab,{suzuki,japan}),
@@ -174,13 +149,7 @@ basic(Config, Version) ->
ok.
-open_v8(Config) when is_list(Config) ->
- open(Config, 8).
-
-open_v9(Config) when is_list(Config) ->
- open(Config, 9).
-
-open(Config, Version) ->
+open(Config) when is_list(Config) ->
%% Running this test twice means that the Dets server is restarted
%% twice. dets_sup specifies a maximum of 4 restarts in an hour.
%% If this becomes a problem, one should consider running this
@@ -194,14 +163,14 @@ open(Config, Version) ->
Data = make_data(1),
P0 = pps(),
- Tabs = open_files(1, All, Version),
+ Tabs = open_files(1, All),
initialize(Tabs, Data),
check(Tabs, Data),
foreach(fun(Tab) -> ok = dets:close(Tab) end, Tabs),
%% Now reopen the files
?format("Reopening closed files \n", []),
- Tabs = open_files(1, All, Version),
+ Tabs = open_files(1, All),
?format("Checking contents of reopened files \n", []),
check(Tabs, Data),
%% crash the dets server
@@ -216,7 +185,7 @@ open(Config, Version) ->
%% Now reopen the files again
?format("Reopening crashed files \n", []),
- open_files(1, All, Version),
+ open_files(1, All),
?format("Checking contents of repaired files \n", []),
check(Tabs, Data),
@@ -266,20 +235,13 @@ bad(_Tab, _Item) ->
exit(badtab).
%% Perform traversal and match testing on set type dets tables.
-sets_v8(Config) when is_list(Config) ->
- sets(Config, 8).
-
-%% Perform traversal and match testing on set type dets tables.
-sets_v9(Config) when is_list(Config) ->
- sets(Config, 9).
-
-sets(Config, Version) ->
+sets(Config) when is_list(Config) ->
{Sets, _, _} = args(Config),
Data = make_data(1),
delete_files(Sets),
P0 = pps(),
- Tabs = open_files(1, Sets, Version),
+ Tabs = open_files(1, Sets),
Bigger = [{17,q,w,w}, {48,q,w,w,w,w,w,w}], % 48 requires a bigger buddy
initialize(Tabs, Data++Bigger++Data), % overwrite
Len = length(Data),
@@ -302,19 +264,12 @@ sets(Config, Version) ->
ok.
%% Perform traversal and match testing on bag type dets tables.
-bags_v8(Config) when is_list(Config) ->
- bags(Config, 8).
-
-%% Perform traversal and match testing on bag type dets tables.
-bags_v9(Config) when is_list(Config) ->
- bags(Config, 9).
-
-bags(Config, Version) ->
+bags(Config) when is_list(Config) ->
{_, Bags, _} = args(Config),
Data = make_data(1, bag), %% gives twice as many objects
delete_files(Bags),
P0 = pps(),
- Tabs = open_files(1, Bags, Version),
+ Tabs = open_files(1, Bags),
initialize(Tabs, Data++Data),
Len = length(Data),
foreach(fun(Tab) -> trav_test(Data, Len, Tab) end, Tabs),
@@ -336,19 +291,12 @@ bags(Config, Version) ->
%% Perform traversal and match testing on duplicate_bag type dets tables.
-duplicate_bags_v8(Config) when is_list(Config) ->
- duplicate_bags(Config, 8).
-
-%% Perform traversal and match testing on duplicate_bag type dets tables.
-duplicate_bags_v9(Config) when is_list(Config) ->
- duplicate_bags(Config, 9).
-
-duplicate_bags(Config, Version) when is_list(Config) ->
+duplicate_bags(Config) when is_list(Config) ->
{_, _, Dups} = args(Config),
Data = make_data(1, duplicate_bag), %% gives twice as many objects
delete_files(Dups),
P0 = pps(),
- Tabs = open_files(1, Dups, Version),
+ Tabs = open_files(1, Dups),
initialize(Tabs, Data),
Len = length(Data),
foreach(fun(Tab) -> trav_test(Data, Len, Tab) end, Tabs),
@@ -369,13 +317,7 @@ duplicate_bags(Config, Version) when is_list(Config) ->
ok.
-access_v8(Config) when is_list(Config) ->
- access(Config, 8).
-
-access_v9(Config) when is_list(Config) ->
- access(Config, 9).
-
-access(Config, Version) ->
+access(Config) when is_list(Config) ->
Args_acc = [[{ram_file, true}, {access, read}],
[{access, read}]],
Args = [[{ram_file, true}],
@@ -388,9 +330,9 @@ access(Config, Version) ->
P0 = pps(),
{error, {file_error,_,enoent}} = dets:open_file('1', hd(Args_acc_1)),
- Tabs = open_files(1, Args_1, Version),
+ Tabs = open_files(1, Args_1),
close_all(Tabs),
- Tabs = open_files(1, Args_acc_1, Version),
+ Tabs = open_files(1, Args_acc_1),
foreach(fun(Tab) ->
{error, {access_mode,_}} = dets:insert(Tab, {1,2}),
@@ -522,16 +464,12 @@ dets_dirty_loop() ->
%% Check that bags and next work as expected.
-bag_next_v8(Config) when is_list(Config) ->
- bag_next(Config, 8).
-
-%% Check that bags and next work as expected.
-bag_next_v9(Config) when is_list(Config) ->
+bag_next(Config) when is_list(Config) ->
Tab = dets_bag_next_test,
FName = filename(Tab, Config),
%% first and next crash upon error
- dets:open_file(Tab,[{file, FName}, {type, bag},{version,9}]),
+ dets:open_file(Tab,[{file, FName}, {type, bag}]),
ok = dets:insert(Tab, [{1,1},{2,2},{3,3},{4,4}]),
FirstKey = dets:first(Tab),
NextKey = dets:next(Tab, FirstKey),
@@ -548,13 +486,8 @@ bag_next_v9(Config) when is_list(Config) ->
dets:close(Tab),
file:delete(FName),
- bag_next(Config, 9).
-
-bag_next(Config, Version) ->
- Tab = dets_bag_next_test,
- FName = filename(Tab, Config),
P0 = pps(),
- dets:open_file(Tab,[{file, FName}, {type, bag},{version,Version}]),
+ dets:open_file(Tab,[{file, FName}, {type, bag}]),
dets:insert(Tab,{698,hopp}),
dets:insert(Tab,{186,hopp}),
dets:insert(Tab,{hej,hopp}),
@@ -578,17 +511,10 @@ bag_next(Config, Version) ->
check_pps(P0),
ok.
-oldbugs_v8(Config) when is_list(Config) ->
- oldbugs(Config, 8).
-
-oldbugs_v9(Config) when is_list(Config) ->
- oldbugs(Config, 9).
-
-oldbugs(Config, Version) ->
+oldbugs(Config) when is_list(Config) ->
FName = filename(dets_suite_oldbugs_test, Config),
P0 = pps(),
- {ok, ob} = dets:open_file(ob, [{version, Version},
- {type, bag}, {file, FName}]),
+ {ok, ob} = dets:open_file(ob, [{type, bag}, {file, FName}]),
ok = dets:insert(ob, {1, 2}),
ok = dets:insert(ob, {1,3}),
ok = dets:insert(ob, {1, 2}),
@@ -598,56 +524,19 @@ oldbugs(Config, Version) ->
check_pps(P0),
ok.
-%% Test that shrinking an object and then expanding it works.
-unsafe_assumptions(Config) when is_list(Config) ->
- FName = filename(dets_suite_unsafe_assumptions_test, Config),
- file:delete(FName),
- P0 = pps(),
- {ok, a} = dets:open_file(a, [{version,8},{file, FName}]),
- O0 = {2,false},
- O1 = {1, false},
- O2 = {1, true},
- O3 = {1, duplicate(20,false)},
- O4 = {1, duplicate(25,false)}, % same 2-log as O3
- ok = dets:insert(a, O1),
- ok = dets:insert(a, O0),
- true = [O1,O0] =:= sort(get_all_objects(a)),
- true = [O1,O0] =:= sort(get_all_objects_fast(a)),
- ok = dets:insert(a, O2),
- true = [O2,O0] =:= sort(get_all_objects(a)),
- true = [O2,O0] =:= sort(get_all_objects_fast(a)),
- ok = dets:insert(a, O3),
- true = [O3,O0] =:= sort(get_all_objects(a)),
- true = [O3,O0] =:= sort(get_all_objects_fast(a)),
- ok = dets:insert(a, O4),
- true = [O4,O0] =:= sort(get_all_objects(a)),
- true = [O4,O0] =:= sort(get_all_objects_fast(a)),
- ok = dets:close(a),
- file:delete(FName),
- check_pps(P0),
- ok.
-
-%% Test that a file where the segment array has been truncated
-%% is possible to repair.
-truncated_segment_array_v8(Config) when is_list(Config) ->
- trunc_seg_array(Config, 8).
-
%% Test that a file where the segment array has been truncated
%% is possible to repair.
-truncated_segment_array_v9(Config) when is_list(Config) ->
- trunc_seg_array(Config, 9).
-
-trunc_seg_array(Config, V) ->
+truncated_segment_array(Config) when is_list(Config) ->
TabRef = dets_suite_truncated_segment_array_test,
Fname = filename(TabRef, Config),
%% Create file that needs to be repaired
file:delete(Fname),
P0 = pps(),
- {ok, TabRef} = dets:open_file(TabRef, [{file, Fname},{version,V}]),
+ {ok, TabRef} = dets:open_file(TabRef, [{file, Fname}]),
ok = dets:close(TabRef),
%% Truncate the file
- HeadSize = headsz(V),
+ HeadSize = headsz(),
truncate(Fname, HeadSize + 10),
%% Open the truncated file
@@ -660,19 +549,13 @@ trunc_seg_array(Config, V) ->
ok.
%% Test open_file/1.
-open_file_v8(Config) when is_list(Config) ->
- open_1(Config, 8).
-
-%% Test open_file/1.
-open_file_v9(Config) when is_list(Config) ->
+open_file(Config) when is_list(Config) ->
T = open_v9,
Fname = filename(T, Config),
- {ok, _} = dets:open_file(T, [{file,Fname},{version,9}]),
- 9 = dets:info(T, version),
+ {ok, _} = dets:open_file(T, [{file,Fname}]),
+ 9 = dets:info(T, version), % Backwards compatibility.
true = [self()] =:= dets:info(T, users),
- {ok, _} = dets:open_file(T, [{file,Fname},{version,9}]),
- {error,incompatible_arguments} =
- dets:open_file(T, [{file,Fname},{version,8}]),
+ {ok, _} = dets:open_file(T, [{file,Fname}]),
true = [self(),self()] =:= dets:info(T, users),
ok = dets:close(T),
true = [self()] =:= dets:info(T, users),
@@ -680,9 +563,9 @@ open_file_v9(Config) when is_list(Config) ->
undefined = ets:info(T, users),
file:delete(Fname),
- open_1(Config, 9).
+ open_1(Config).
-open_1(Config, V) ->
+open_1(Config) ->
TabRef = open_file_1_test,
Fname = filename(TabRef, Config),
file:delete(Fname),
@@ -694,8 +577,8 @@ open_1(Config, V) ->
{error,{not_a_dets_file,Fname}} = dets:open_file(Fname),
file:delete(Fname),
- HeadSize = headsz(V),
- {ok, TabRef} = dets:open_file(TabRef, [{file, Fname},{version,V}]),
+ HeadSize = headsz(),
+ {ok, TabRef} = dets:open_file(TabRef, [{file, Fname}]),
ok = dets:close(TabRef),
truncate(Fname, HeadSize + 10),
true = dets:is_dets_file(Fname),
@@ -705,7 +588,7 @@ open_1(Config, V) ->
file:delete(Fname),
%% truncated file header, invalid type
- {ok, TabRef} = dets:open_file(TabRef, [{file,Fname},{version,V}]),
+ {ok, TabRef} = dets:open_file(TabRef, [{file,Fname}]),
ok = ins(TabRef, 3000),
ok = dets:close(TabRef),
TypePos = 12,
@@ -714,7 +597,7 @@ open_1(Config, V) ->
truncate(Fname, HeadSize - 10),
{error,{not_a_dets_file,Fname}} = dets:open_file(Fname),
{error,{not_a_dets_file,Fname}} =
- dets:open_file(TabRef, [{file,Fname},{version,V}]),
+ dets:open_file(TabRef, [{file,Fname}]),
file:delete(Fname),
{error,{file_error,{foo,bar},_}} = dets:is_dets_file({foo,bar}),
@@ -722,35 +605,30 @@ open_1(Config, V) ->
ok.
%% Test initialize_table/2 and from_ets/2.
-init_table_v8(Config) when is_list(Config) ->
- init_table(Config, 8).
-
-%% Test initialize_table/2 and from_ets/2.
-init_table_v9(Config) when is_list(Config) ->
+init_table(Config) when is_list(Config) ->
%% Objects are returned in "time order".
T = init_table_v9,
Fname = filename(T, Config),
file:delete(Fname),
L = [{1,a},{2,b},{1,c},{2,c},{1,c},{2,a},{1,b}],
Input = init([L]),
- {ok, _} = dets:open_file(T, [{file,Fname},{version,9},
- {type,duplicate_bag}]),
+ {ok, _} = dets:open_file(T, [{file,Fname},{type,duplicate_bag}]),
ok = dets:init_table(T, Input),
[{1,a},{1,c},{1,c},{1,b}] = dets:lookup(T, 1),
[{2,b},{2,c},{2,a}] = dets:lookup(T, 2),
ok = dets:close(T),
file:delete(Fname),
- init_table(Config, 9),
+ init_table_1(Config),
fast_init_table(Config).
-init_table(Config, V) ->
+init_table_1(Config) ->
TabRef = init_table_test,
Fname = filename(TabRef, Config),
file:delete(Fname),
P0 = pps(),
- Args = [{file,Fname},{version,V},{auto_save,120000}],
+ Args = [{file,Fname},{auto_save,120000}],
{ok, _} = dets:open_file(TabRef, Args),
{'EXIT', _} =
(catch dets:init_table(TabRef, fun(foo) -> bar end)),
@@ -800,13 +678,13 @@ init_table(Config, V) ->
file:delete(Fname),
L1 = [[{1,a},{2,b}],[],[{3,c}],[{4,d}],[]],
- bulk_init(L1, set, 4, Config, V),
+ bulk_init(L1, set, 4, Config),
L2 = [[{1,a},{2,b}],[],[{2,q},{3,c}],[{4,d}],[{4,e},{2,q}]],
- bulk_init(L2, set, 4, Config, V),
- bulk_init(L2, bag, 6, Config, V),
- bulk_init(L2, duplicate_bag, 7, Config, V),
- bulk_init(L1, set, 4, 512, Config, V),
- bulk_init([], set, 0, 10000, Config, V),
+ bulk_init(L2, set, 4, Config),
+ bulk_init(L2, bag, 6, Config),
+ bulk_init(L2, duplicate_bag, 7, Config),
+ bulk_init(L1, set, 4, 512, Config),
+ bulk_init([], set, 0, 10000, Config),
file:delete(Fname),
%% Initiate a file that contains a lot of objects.
@@ -834,16 +712,16 @@ init_table(Config, V) ->
check_pps(P0),
ok.
-bulk_init(Ls, Type, N, Config, V) ->
- bulk_init(Ls, Type, N, 256, Config, V).
+bulk_init(Ls, Type, N, Config) ->
+ bulk_init(Ls, Type, N, 256, Config).
-bulk_init(Ls, Type, N, Est, Config, V) ->
+bulk_init(Ls, Type, N, Est, Config) ->
T = init_table_test,
Fname = filename(T, Config),
file:delete(Fname),
Input = init(Ls),
Args = [{ram_file,false}, {type,Type},{keypos,1},{file,Fname},
- {estimated_no_objects, Est},{version,V}],
+ {estimated_no_objects, Est}],
{ok, T} = dets:open_file(T, Args),
ok = dets:init_table(T, Input),
All = sort(get_all_objects(T)),
@@ -882,18 +760,17 @@ init_fun(I, N) ->
end.
fast_init_table(Config) ->
- V = 9,
TabRef = init_table_test,
Fname = filename(TabRef, Config),
file:delete(Fname),
P0 = pps(),
- Args = [{file,Fname},{version,V},{auto_save,120000}],
+ Args = [{file,Fname},{auto_save,120000}],
Source = init_table_test_source,
SourceFname = filename(Source, Config),
file:delete(SourceFname),
- SourceArgs = [{file,SourceFname},{version,V},{auto_save,120000}],
+ SourceArgs = [{file,SourceFname},{auto_save,120000}],
{ok, Source} = dets:open_file(Source, SourceArgs),
@@ -1015,13 +892,13 @@ fast_init_table(Config) ->
file:delete(SourceFname),
L1 = [{1,a},{2,b},{3,c},{4,d}],
- fast_bulk_init(L1, set, 4, 4, Config, V),
+ fast_bulk_init(L1, set, 4, 4, Config),
L2 = [{1,a},{2,b},{2,q},{3,c},{4,d},{4,e},{2,q}],
- fast_bulk_init(L2, set, 4, 4, Config, V),
- fast_bulk_init(L2, bag, 6, 4, Config, V),
- fast_bulk_init(L2, duplicate_bag, 7, 4, Config, V),
- fast_bulk_init(L1, set, 4, 4, 512, Config, V),
- fast_bulk_init([], set, 0, 0, 10000, Config, V),
+ fast_bulk_init(L2, set, 4, 4, Config),
+ fast_bulk_init(L2, bag, 6, 4, Config),
+ fast_bulk_init(L2, duplicate_bag, 7, 4, Config),
+ fast_bulk_init(L1, set, 4, 4, 512, Config),
+ fast_bulk_init([], set, 0, 0, 10000, Config),
file:delete(Fname),
%% Initiate a file that contains a lot of objects.
@@ -1112,16 +989,16 @@ fast_init_table(Config) ->
check_pps(P0),
ok.
-fast_bulk_init(L, Type, N, NoKeys, Config, V) ->
- fast_bulk_init(L, Type, N, NoKeys, 256, Config, V).
+fast_bulk_init(L, Type, N, NoKeys, Config) ->
+ fast_bulk_init(L, Type, N, NoKeys, 256, Config).
-fast_bulk_init(L, Type, N, NoKeys, Est, Config, V) ->
+fast_bulk_init(L, Type, N, NoKeys, Est, Config) ->
T = init_table_test,
Fname = filename(T, Config),
file:delete(Fname),
Args0 = [{ram_file,false}, {type,Type},{keypos,1},
- {estimated_no_objects, Est},{version,V}],
+ {estimated_no_objects, Est}],
Args = [{file,Fname} | Args0],
S = init_table_test_source,
SFname = filename(S, Config),
@@ -1189,35 +1066,7 @@ items(I, N, C, L) ->
items(I+1, N, C-1, [{I, item(I)} | L]).
%% Test open_file and repair.
-repair_v8(Config) when is_list(Config) ->
- repair(Config, 8).
-
-%% Test open_file and repair.
-repair_v9(Config) when is_list(Config) ->
- %% Convert from format 9 to format 8.
- T = convert_98,
- Fname = filename(T, Config),
- file:delete(Fname),
- {ok, _} = dets:open_file(T, [{file,Fname},{version,9},
- {type,duplicate_bag}]),
- 9 = dets:info(T, version),
- true = is_binary(dets:info(T, bchunk_format)),
- ok = dets:insert(T, [{1,a},{2,b},{1,c},{2,c},{1,c},{2,a},{1,b}]),
- dets:close(T),
- {error, {version_mismatch, _}} =
- dets:open_file(T, [{file,Fname},{version,8},{type,duplicate_bag}]),
- {ok, _} = dets:open_file(T, [{file,Fname},{version,8},
- {type,duplicate_bag},{repair,force}]),
- 8 = dets:info(T, version),
- true = undefined =:= dets:info(T, bchunk_format),
- [{1,a},{1,b},{1,c},{1,c}] = sort(dets:lookup(T, 1)),
- [{2,a},{2,b},{2,c}] = sort(dets:lookup(T, 2)),
- 7 = dets:info(T, no_objects),
- no_keys_test(T),
- _ = histogram(T, silent),
- ok = dets:close(T),
- file:delete(Fname),
-
+repair(Config) when is_list(Config) ->
%% The short lived format 9(a).
%% Not very throughly tested here.
A9 = a9,
@@ -1238,13 +1087,13 @@ repair_v9(Config) when is_list(Config) ->
ok = dets:close(A9),
file:delete(Version9aT),
- repair(Config, 9).
+ repair_1(Config).
-repair(Config, V) ->
+repair_1(Config) ->
TabRef = repair_test,
Fname = filename(TabRef, Config),
file:delete(Fname),
- HeadSize = headsz(V),
+ HeadSize = headsz(),
P0 = pps(),
{'EXIT', {badarg, _}} =
@@ -1255,7 +1104,7 @@ repair(Config, V) ->
dets:open_file(TabRef, [{file, Fname}, {access, read}]),
%% compacting, and some kind of test that free lists are saved OK on file
- {ok, TabRef} = dets:open_file(TabRef, [{file,Fname},{version,V}]),
+ {ok, TabRef} = dets:open_file(TabRef, [{file,Fname}]),
0 = dets:info(TabRef, size),
ok = ins(TabRef, 30000),
ok = del(TabRef, 30000, 3),
@@ -1268,38 +1117,20 @@ repair(Config, V) ->
20000 = count_objects_quite_fast(Ref3), % actually a test of match
no_keys_test(Ref3),
ok = dets:close(Ref3),
- if
- V =:= 8 ->
- {ok, TabRef} = dets:open_file(TabRef,
- [{file, Fname},{version,V},{access,read}]),
- ok = dets:close(TabRef),
- io:format("Expect compacting repair:~n"),
- {ok, TabRef} = dets:open_file(TabRef,
- [{file, Fname},{version,V}]),
- 20000 = dets:info(TabRef, size),
- _ = histogram(TabRef, silent),
- ok = dets:close(TabRef);
- true ->
- ok
- end,
{error,{keypos_mismatch,Fname}} =
dets:open_file(TabRef, [{file, Fname},{keypos,17}]),
{error,{type_mismatch,Fname}} =
dets:open_file(TabRef, [{file, Fname},{type,duplicate_bag}]),
%% make one of the temporary files unwritable
- TmpFile = if
- V =:= 8 ->
- Fname ++ ".TMP.10000";
- true -> Fname ++ ".TMP.1"
- end,
+ TmpFile = Fname ++ ".TMP.1",
file:delete(TmpFile),
{ok, TmpFd} = file:open(TmpFile, [read,write]),
ok = file:close(TmpFd),
unwritable(TmpFile),
- {error,{file_error,TmpFile,eacces}} = dets:fsck(Fname, V),
+ {error,{file_error,TmpFile,eacces}} = dets:fsck(Fname),
{ok, _} = dets:open_file(TabRef,
- [{repair,false},{file, Fname},{version,V}]),
+ [{repair,false},{file, Fname}]),
20000 = length(get_all_objects(TabRef)),
_ = histogram(TabRef, silent),
20000 = length(get_all_objects_fast(TabRef)),
@@ -1318,68 +1149,15 @@ repair(Config, V) ->
file:delete(Fname),
%% truncated file header
- {ok, TabRef} = dets:open_file(TabRef, [{file,Fname},{version,V}]),
+ {ok, TabRef} = dets:open_file(TabRef, [{file,Fname}]),
ok = ins(TabRef, 100),
ok = dets:close(TabRef),
file:delete(Fname),
- %% version bump (v8)
- Version7S = filename:join(?datadir(Config), "version_r2d.dets"),
- Version7T = filename('v2.dets', Config),
- {ok, _} = file:copy(Version7S, Version7T),
- {error,{version_bump, Version7T}} = dets:open_file(Version7T),
- {error,{version_bump, Version7T}} =
- dets:open_file(Version7T, [{file,Version7T},{repair,false}]),
- {error,{version_bump, Version7T}} =
- dets:open_file(Version7T, [{file, Version7T}, {access, read}]),
- io:format("Expect upgrade:~n"),
- {ok, _} = dets:open_file(Version7T,
- [{file, Version7T},{version, V}]),
- [{1,a},{2,b}] = sort(get_all_objects(Version7T)),
- [{1,a},{2,b}] = sort(get_all_objects_fast(Version7T)),
- Phash = if
- V =:= 8 -> phash;
- true -> phash2
- end,
- Phash = dets:info(Version7T, hash),
- _ = histogram(Version7T, silent),
- ok = dets:close(Version7T),
- {ok, _} = dets:open_file(Version7T, [{file, Version7T}]),
- Phash = dets:info(Version7T, hash),
- ok = dets:close(Version7T),
- file:delete(Version7T),
-
- %% converting free lists
- Version8aS = filename:join(?datadir(Config), "version_r3b02.dets"),
- Version8aT = filename('v3.dets', Config),
- {ok, _} = file:copy(Version8aS, Version8aT),
- %% min_no_slots and max_no_slots are ignored - no repair is taking place
- {ok, _} = dets:open_file(version_8a,
- [{file, Version8aT},{min_no_slots,1000},
- {max_no_slots,100000}]),
- [{1,b},{2,a},{a,1},{b,2}] = sort(get_all_objects(version_8a)),
- [{1,b},{2,a},{a,1},{b,2}] = sort(get_all_objects_fast(version_8a)),
- ok = ins(version_8a, 1000),
- 1002 = dets:info(version_8a, size),
- no_keys_test(version_8a),
- All8a = sort(get_all_objects(version_8a)),
- 1002 = length(All8a),
- FAll8a = sort(get_all_objects_fast(version_8a)),
- true = sort(All8a) =:= sort(FAll8a),
- ok = del(version_8a, 300, 3),
- 902 = dets:info(version_8a, size),
- no_keys_test(version_8a),
- All8a2 = sort(get_all_objects(version_8a)),
- 902 = length(All8a2),
- FAll8a2 = sort(get_all_objects_fast(version_8a)),
- true = sort(All8a2) =:= sort(FAll8a2),
- _ = histogram(version_8a, silent),
- ok = dets:close(version_8a),
- file:delete(Version8aT),
-
+ %% FIXME.
%% will fail unless the slots are properly sorted when repairing (v8)
BArgs = [{file, Fname},{type,duplicate_bag},
- {delayed_write,{3000,10000}},{version,V}],
+ {delayed_write,{3000,10000}}],
{ok, TabRef} = dets:open_file(TabRef, BArgs),
Seq = seq(1, 500),
Small = map(fun(X) -> {X,X} end, Seq),
@@ -1393,18 +1171,14 @@ repair(Config, V) ->
io:format("Expect forced repair:~n"),
{ok, _} =
dets:open_file(TabRef, [{repair,force},{min_no_slots,2000} | BArgs]),
- if
- V =:= 9 ->
- {MinNoSlots,_,MaxNoSlots} = dets:info(TabRef, no_slots),
- ok = dets:close(TabRef),
- io:format("Expect compaction:~n"),
- {ok, _} =
- dets:open_file(TabRef, [{repair,force},
- {min_no_slots,MinNoSlots},
- {max_no_slots,MaxNoSlots} | BArgs]);
- true ->
- ok
- end,
+
+ {MinNoSlots,_,MaxNoSlots} = dets:info(TabRef, no_slots),
+ ok = dets:close(TabRef),
+ io:format("Expect compaction:~n"),
+ {ok, _} =
+ dets:open_file(TabRef, [{repair,force},
+ {min_no_slots,MinNoSlots},
+ {max_no_slots,MaxNoSlots} | BArgs]),
All2 = get_all_objects(TabRef),
true = All =:= sort(All2),
FAll2 = get_all_objects_fast(TabRef),
@@ -1418,35 +1192,15 @@ repair(Config, V) ->
file:delete(Fname),
%% object bigger than segments, the "hole" is taken care of
- {ok, TabRef} = dets:open_file(TabRef, [{file, Fname},{version,V}]),
+ {ok, TabRef} = dets:open_file(TabRef, [{file, Fname}]),
Tuple = erlang:make_tuple(1000, foobar), % > 2 kB
ok = dets:insert(TabRef, Tuple),
%% at least one full segment (objects smaller than 2 kB):
ins(TabRef, 2000),
ok = dets:close(TabRef),
- if
- V =:= 8 ->
- %% first estimated number of objects is wrong, repair once more
- {ok, Fd} = file:open(Fname, [read,write]),
- NoPos = HeadSize - 8, % no_objects
- file:pwrite(Fd, NoPos, <<0:32>>), % NoItems
- ok = file:close(Fd),
- dets:fsck(Fname, V),
- {ok, _} =
- dets:open_file(TabRef,
- [{repair,false},{file, Fname},{version,V}]),
- 2001 = length(get_all_objects(TabRef)),
- _ = histogram(TabRef, silent),
- 2001 = length(get_all_objects_fast(TabRef)),
- ok = dets:close(TabRef);
- true ->
- ok
- end,
-
{ok, _} =
- dets:open_file(TabRef,
- [{repair,false},{file, Fname},{version,V}]),
+ dets:open_file(TabRef, [{repair,false},{file, Fname}]),
{ok, ObjPos} = dets:where(TabRef, {66,{item,number,66}}),
ok = dets:close(TabRef),
%% Damaged object.
@@ -1454,25 +1208,24 @@ repair(Config, V) ->
crash(Fname, ObjPos+Pos),
io:format(
"Expect forced repair (possibly after attempted compaction):~n"),
- {ok, _} =
- dets:open_file(TabRef, [{repair,force},{file, Fname},{version,V}]),
+ {ok, _} = dets:open_file(TabRef, [{repair,force},{file, Fname}]),
true = dets:info(TabRef, size) < 2001,
ok = dets:close(TabRef),
file:delete(Fname),
%% The file is smaller than the padded object.
- {ok, TabRef} = dets:open_file(TabRef, [{file,Fname},{version,V}]),
+ {ok, TabRef} = dets:open_file(TabRef, [{file,Fname}]),
ok = dets:insert(TabRef, Tuple),
ok = dets:close(TabRef),
io:format("Expect forced repair or compaction:~n"),
{ok, _} =
- dets:open_file(TabRef, [{repair,force},{file, Fname},{version,V}]),
+ dets:open_file(TabRef, [{repair,force},{file, Fname}]),
true = 1 =:= dets:info(TabRef, size),
ok = dets:close(TabRef),
file:delete(Fname),
%% Damaged free lists.
- {ok, TabRef} = dets:open_file(TabRef, [{file,Fname},{version,V}]),
+ {ok, TabRef} = dets:open_file(TabRef, [{file,Fname}]),
ok = ins(TabRef, 300),
ok = dets:sync(TabRef),
ok = del(TabRef, 300, 3),
@@ -1481,48 +1234,42 @@ repair(Config, V) ->
ok = dets:close(TabRef),
crash(Fname, FileSize+20),
%% Used to return bad_freelists, but that changed in OTP-9622
- {ok, TabRef} =
- dets:open_file(TabRef, [{file,Fname},{version,V}]),
+ {ok, TabRef} = dets:open_file(TabRef, [{file,Fname}]),
ok = dets:close(TabRef),
file:delete(Fname),
%% File not closed, opening with read and read_write access tried.
- {ok, TabRef} = dets:open_file(TabRef, [{file,Fname},{version,V}]),
+ {ok, TabRef} = dets:open_file(TabRef, [{file,Fname}]),
ok = ins(TabRef, 300),
ok = dets:close(TabRef),
crash(Fname, ?CLOSED_PROPERLY_POS+3, ?NOT_PROPERLY_CLOSED),
{error, {not_closed, Fname}} =
- dets:open_file(foo, [{file,Fname},{version,V},{repair,force},
+ dets:open_file(foo, [{file,Fname},{repair,force},
{access,read}]),
{error, {not_closed, Fname}} =
- dets:open_file(foo, [{file,Fname},{version,V},{repair,true},
+ dets:open_file(foo, [{file,Fname},{repair,true},
{access,read}]),
io:format("Expect repair:~n"),
{ok, TabRef} =
- dets:open_file(TabRef, [{file,Fname},{version,V},{repair,true},
+ dets:open_file(TabRef, [{file,Fname},{repair,true},
{access,read_write}]),
ok = dets:close(TabRef),
crash(Fname, ?CLOSED_PROPERLY_POS+3, ?NOT_PROPERLY_CLOSED),
io:format("Expect forced repair:~n"),
{ok, TabRef} =
- dets:open_file(TabRef, [{file,Fname},{version,V},{repair,force},
+ dets:open_file(TabRef, [{file,Fname},{repair,force},
{access,read_write}]),
ok = dets:close(TabRef),
file:delete(Fname),
%% The size of an object is huge.
- {ok, TabRef} = dets:open_file(TabRef, [{file,Fname},{version,V}]),
+ {ok, TabRef} = dets:open_file(TabRef, [{file,Fname}]),
ok = dets:insert(TabRef, [{1,2,3},{2,3,4}]),
{ok, ObjPos2} = dets:where(TabRef, {1,2,3}),
ok = dets:close(TabRef),
- ObjPos3 = if
- V =:= 8 -> ObjPos2 + 4;
- V =:= 9 -> ObjPos2
- end,
- crash(Fname, ObjPos3, 255),
+ crash(Fname, ObjPos2, 255),
io:format("Expect forced repair:~n"),
- {ok, TabRef} =
- dets:open_file(TabRef, [{file,Fname},{version,V},{repair,force}]),
+ {ok, TabRef} = dets:open_file(TabRef, [{file,Fname},{repair,force}]),
ok = dets:close(TabRef),
file:delete(Fname),
@@ -1530,82 +1277,6 @@ repair(Config, V) ->
ok.
-%% Test the use of different hashing algorithms in v8b and v8c of the
-%% Dets file format.
-hash_v8b_v8c(Config) when is_list(Config) ->
- Source =
- filename:join(?datadir(Config), "dets_test_v8b.dets"),
- %% Little endian version of old file (there is an endianess bug in
- %% the old hash). This is all about version 8 of the dets file format.
-
- P0 = pps(),
- SourceLE =
- filename:join(?datadir(Config),
- "dets_test_v8b_little_endian.dets"),
- Target1 = filename('oldhash1.dets', Config),
- Target1LE = filename('oldhash1le.dets', Config),
- Target2 = filename('oldhash2.dets', Config),
- {ok, Bin} = file:read_file(Source),
- {ok, BinLE} = file:read_file(SourceLE),
- ok = file:write_file(Target1,Bin),
- ok = file:write_file(Target1LE,BinLE),
- ok = file:write_file(Target2,Bin),
- {ok, d1} = dets:open_file(d1,[{file,Target1}]),
- {ok, d1le} = dets:open_file(d1le,[{file,Target1LE}]),
- {ok, d2} = dets:open_file(d2,[{file,Target2},{repair,force},
- {version,8}]),
- FF = fun(N,_F,_T) when N > 16#FFFFFFFFFFFFFFFF ->
- ok;
- (N,F,T) ->
- V = integer_to_list(N),
- case dets:lookup(T,N) of
- [{N,V}] ->
- F(N*2,F,T);
- _Error ->
- exit({failed,{lookup,T,N}})
- end
- end,
- Mess = case (catch FF(1,FF,d1)) of
- {'EXIT', {failed, {lookup,_,_}}} ->
- ok = dets:close(d1),
- FF(1,FF,d1le),
- hash = dets:info(d1le,hash),
- dets:insert(d1le,{33333333333,hejsan}),
- [{33333333333,hejsan}] =
- dets:lookup(d1le,33333333333),
- ok = dets:close(d1le),
- {ok, d1le} = dets:open_file(d1le,
- [{file,Target1LE}]),
- [{33333333333,hejsan}] =
- dets:lookup(d1le,33333333333),
- FF(1,FF,d1le),
- ok = dets:close(d1le),
- "Seems to be a little endian machine";
- {'EXIT', Fault} ->
- exit(Fault);
- _ ->
- ok = dets:close(d1le),
- hash = dets:info(d1,hash),
- dets:insert(d1,{33333333333,hejsan}),
- [{33333333333,hejsan}] =
- dets:lookup(d1,33333333333),
- ok = dets:close(d1),
- {ok, d1} = dets:open_file(d1,[{file,Target1}]),
- [{33333333333,hejsan}] =
- dets:lookup(d1,33333333333),
- FF(1,FF,d1),
- ok = dets:close(d1),
- "Seems to be a big endian machine"
- end,
- FF(1,FF,d2),
- phash = dets:info(d2,hash),
- ok = dets:close(d2),
- file:delete(Target1),
- file:delete(Target1LE),
- file:delete(Target2),
- check_pps(P0),
- {comment, Mess}.
-
%% Test version 9(b) with erlang:phash/2 as hash function.
phash(Config) when is_list(Config) ->
T = phash,
@@ -1643,9 +1314,10 @@ phash(Config) when is_list(Config) ->
ok = dets:close(T),
%% One cannot use the bchunk format when copying between a phash
- %% table and a phash2 table. (There is no test for the case an R9
- %% (or later) node (using phash2) copies a table to an R8 node
- %% (using phash).) See also the comment on HASH_PARMS in dets_v9.erl.
+ %% table and a phash2 table. (There is no test for the case an
+ %% Erlang/OTP R9 (or later) node (using phash2) copies a table to
+ %% an Erlang/OTP R8 node (using phash).) See also the comment on
+ %% HASH_PARMS in dets_v9.erl.
{ok, _} = file:copy(Phash_v9bS, Fname),
{ok, T} = dets:open_file(T, [{file, Fname}]),
Type = dets:info(T, type),
@@ -1653,7 +1325,7 @@ phash(Config) when is_list(Config) ->
Input = init_bchunk(T),
T2 = phash_table,
Fname2 = filename(T2, Config),
- Args = [{type,Type},{keypos,KeyPos},{version,9},{file,Fname2}],
+ Args = [{type,Type},{keypos,KeyPos},{file,Fname2}],
{ok, T2} = dets:open_file(T2, Args),
{error, {init_fun, _}} =
dets:init_table(T2, Input, {format,bchunk}),
@@ -1665,21 +1337,14 @@ phash(Config) when is_list(Config) ->
ok.
%% Test foldl, foldr, to_ets.
-fold_v8(Config) when is_list(Config) ->
- fold(Config, 8).
-
-%% Test foldl, foldr, to_ets.
-fold_v9(Config) when is_list(Config) ->
- fold(Config, 9).
-
-fold(Config, Version) ->
+fold(Config) when is_list(Config) ->
T = test_table,
N = 100,
Fname = filename(T, Config),
file:delete(Fname),
P0 = pps(),
- Args = [{version, Version}, {file,Fname}, {estimated_no_objects, N}],
+ Args = [{file,Fname}, {estimated_no_objects, N}],
{ok, _} = dets:open_file(T, Args),
ok = ins(T, N),
@@ -1721,10 +1386,7 @@ fold(Config, Version) ->
ok = dets:close(T),
%% Damaged object.
- Pos = if
- Version =:= 8 -> 12;
- Version =:= 9 -> 8
- end,
+ Pos = 8,
crash(Fname, ObjPos+Pos),
{ok, _} = dets:open_file(T, Args),
io:format("Expect corrupt table:~n"),
@@ -1738,18 +1400,11 @@ fold(Config, Version) ->
ok.
%% Add objects to a fixed table.
-fixtable_v8(Config) when is_list(Config) ->
- fixtable(Config, 8).
-
-%% Add objects to a fixed table.
-fixtable_v9(Config) when is_list(Config) ->
- fixtable(Config, 9).
-
-fixtable(Config, Version) when is_list(Config) ->
+fixtable(Config) when is_list(Config) ->
T = fixtable,
Fname = filename(fixtable, Config),
file:delete(Fname),
- Args = [{version,Version},{file,Fname}],
+ Args = [{file,Fname}],
P0 = pps(),
{ok, _} = dets:open_file(T, Args),
@@ -1832,21 +1487,13 @@ fixtable(Config, Version) when is_list(Config) ->
ok.
%% Matching objects of a fixed table.
-match_v8(Config) when is_list(Config) ->
- match(Config, 8).
-
-%% Matching objects of a fixed table.
-match_v9(Config) when is_list(Config) ->
- match(Config, 9).
-
-match(Config, Version) ->
+match(Config) when is_list(Config) ->
T = match,
Fname = filename(match, Config),
file:delete(Fname),
P0 = pps(),
- Args = [{version, Version}, {file,Fname}, {type, duplicate_bag},
- {estimated_no_objects,550}],
+ Args = [{file,Fname}, {type, duplicate_bag}, {estimated_no_objects,550}],
{ok, _} = dets:open_file(T, Args),
ok = dets:insert(T, {1, a, b}),
ok = dets:insert(T, {1, b, a}),
@@ -1901,7 +1548,7 @@ match(Config, Version) ->
{_, TmpCont} = dets:match_object(T, '_', 200),
{_, TmpCont1} = dets:match_object(TmpCont),
{TTL, _} = dets:match_object(TmpCont1),
- DI = if Version =:= 8 -> last(TTL); Version =:= 9 -> hd(TTL) end,
+ DI = hd(TTL),
dets:safe_fixtable(T, true),
{L1, C20} = dets:match_object(T, '_', 200),
true = 200 =< length(L1),
@@ -1957,8 +1604,7 @@ match(Config, Version) ->
ok = dets:close(T),
%% Damaged size of object.
- %% In v8, there is a next pointer before the size.
- CrashPos = if Version =:= 8 -> 5; Version =:= 9 -> 1 end,
+ CrashPos = 1,
crash(Fname, ObjPos2+CrashPos),
{ok, _} = dets:open_file(T, Args),
case dets:insert_new(T, Obj) of % OTP-12024
@@ -1986,7 +1632,7 @@ match(Config, Version) ->
ok = dets:close(T),
%% match_delete finds an error
- CrashPos3 = if Version =:= 8 -> 12; Version =:= 9 -> 16 end,
+ CrashPos3 = 16,
crash(Fname, ObjPos3+CrashPos3),
{ok, _} = dets:open_file(T, Args),
bad_object(dets:match_delete(T, Spec), Fname),
@@ -2008,21 +1654,13 @@ match(Config, Version) ->
ok.
%% Selecting objects of a fixed table.
-select_v8(Config) when is_list(Config) ->
- select(Config, 8).
-
-%% Selecting objects of a fixed table.
-select_v9(Config) when is_list(Config) ->
- select(Config, 9).
-
-select(Config, Version) ->
+select(Config) when is_list(Config) ->
T = select,
Fname = filename(select, Config),
file:delete(Fname),
P0 = pps(),
- Args = [{version,Version}, {file,Fname}, {type, duplicate_bag},
- {estimated_no_objects,550}],
+ Args = [{file,Fname}, {type, duplicate_bag},{estimated_no_objects,550}],
{ok, _} = dets:open_file(T, Args),
ok = dets:insert(T, {1, a, b}),
ok = dets:insert(T, {1, b, a}),
@@ -2074,7 +1712,7 @@ select(Config, Version) ->
{_, TmpCont} = dets:match_object(T, '_', 200),
{_, TmpCont1} = dets:match_object(TmpCont),
{TTL, _} = dets:match_object(TmpCont1),
- DI = if Version =:= 8 -> last(TTL); Version =:= 9 -> hd(TTL) end,
+ DI = hd(TTL),
dets:safe_fixtable(T, true),
{L1, C20} = dets:select(T, AllSpec, 200),
true = 200 =< length(L1),
@@ -2281,28 +1919,21 @@ badarg(Config) when is_list(Config) ->
ok.
%% Test the write cache for sets.
-cache_sets_v8(Config) when is_list(Config) ->
- cache_sets(Config, 8).
-
-%% Test the write cache for sets.
-cache_sets_v9(Config) when is_list(Config) ->
- cache_sets(Config, 9).
-
-cache_sets(Config, Version) ->
+cache_sets(Config) when is_list(Config) ->
Small = 2,
- cache_sets(Config, {0,0}, false, Small, Version),
- cache_sets(Config, {0,0}, true, Small, Version),
- cache_sets(Config, {5000,5000}, false, Small, Version),
- cache_sets(Config, {5000,5000}, true, Small, Version),
+ cache_sets(Config, {0,0}, false, Small),
+ cache_sets(Config, {0,0}, true, Small),
+ cache_sets(Config, {5000,5000}, false, Small),
+ cache_sets(Config, {5000,5000}, true, Small),
%% Objects of size greater than 2 kB.
Big = 1200,
- cache_sets(Config, {0,0}, false, Big, Version),
- cache_sets(Config, {0,0}, true, Big, Version),
- cache_sets(Config, {5000,5000}, false, Big, Version),
- cache_sets(Config, {5000,5000}, true, Big, Version),
+ cache_sets(Config, {0,0}, false, Big),
+ cache_sets(Config, {0,0}, true, Big),
+ cache_sets(Config, {5000,5000}, false, Big),
+ cache_sets(Config, {5000,5000}, true, Big),
ok.
-cache_sets(Config, DelayedWrite, Extra, Sz, Version) ->
+cache_sets(Config, DelayedWrite, Extra, Sz) ->
%% Extra = bool(). Insert tuples until the tested key is not alone.
%% Sz = integer(). Size of the inserted tuples.
@@ -2311,9 +1942,8 @@ cache_sets(Config, DelayedWrite, Extra, Sz, Version) ->
file:delete(Fname),
P0 = pps(),
- {ok, _} =
- dets:open_file(T,[{version, Version}, {file,Fname}, {type,set},
- {delayed_write, DelayedWrite}]),
+ {ok, _} = dets:open_file(T,[{file,Fname}, {type,set},
+ {delayed_write, DelayedWrite}]),
Dups = 1,
{Key, OtherKeys} =
@@ -2430,28 +2060,21 @@ cache_sets(Config, DelayedWrite, Extra, Sz, Version) ->
ok.
%% Test the write cache for bags.
-cache_bags_v8(Config) when is_list(Config) ->
- cache_bags(Config, 8).
-
-%% Test the write cache for bags.
-cache_bags_v9(Config) when is_list(Config) ->
- cache_bags(Config, 9).
-
-cache_bags(Config, Version) ->
+cache_bags(Config) when is_list(Config) ->
Small = 2,
- cache_bags(Config, {0,0}, false, Small, Version),
- cache_bags(Config, {0,0}, true, Small, Version),
- cache_bags(Config, {5000,5000}, false, Small, Version),
- cache_bags(Config, {5000,5000}, true, Small, Version),
+ cache_bags(Config, {0,0}, false, Small),
+ cache_bags(Config, {0,0}, true, Small),
+ cache_bags(Config, {5000,5000}, false, Small),
+ cache_bags(Config, {5000,5000}, true, Small),
%% Objects of size greater than 2 kB.
Big = 1200,
- cache_bags(Config, {0,0}, false, Big, Version),
- cache_bags(Config, {0,0}, true, Big, Version),
- cache_bags(Config, {5000,5000}, false, Big, Version),
- cache_bags(Config, {5000,5000}, true, Big, Version),
+ cache_bags(Config, {0,0}, false, Big),
+ cache_bags(Config, {0,0}, true, Big),
+ cache_bags(Config, {5000,5000}, false, Big),
+ cache_bags(Config, {5000,5000}, true, Big),
ok.
-cache_bags(Config, DelayedWrite, Extra, Sz, Version) ->
+cache_bags(Config, DelayedWrite, Extra, Sz) ->
%% Extra = bool(). Insert tuples until the tested key is not alone.
%% Sz = integer(). Size of the inserted tuples.
@@ -2460,9 +2083,8 @@ cache_bags(Config, DelayedWrite, Extra, Sz, Version) ->
file:delete(Fname),
P0 = pps(),
- {ok, _} =
- dets:open_file(T,[{version, Version}, {file,Fname}, {type,bag},
- {delayed_write, DelayedWrite}]),
+ {ok, _} = dets:open_file(T,[{file,Fname}, {type,bag},
+ {delayed_write, DelayedWrite}]),
Dups = 1,
{Key, OtherKeys} =
@@ -2588,8 +2210,7 @@ cache_bags(Config, DelayedWrite, Extra, Sz, Version) ->
R1 = {index_test,1,2,3,4},
R2 = {index_test,2,2,13,14},
R3 = {index_test,1,12,13,14},
- {ok, _} = dets:open_file(T,[{version,Version},{type,bag},
- {keypos,2},{file,Fname}]),
+ {ok, _} = dets:open_file(T,[{type,bag}, {keypos,2},{file,Fname}]),
ok = dets:insert(T,R1),
ok = dets:sync(T),
ok = dets:insert(T,R2),
@@ -2606,27 +2227,20 @@ cache_bags(Config, DelayedWrite, Extra, Sz, Version) ->
ok.
%% Test the write cache for duplicate bags.
-cache_duplicate_bags_v8(Config) when is_list(Config) ->
- cache_duplicate_bags(Config, 8).
-
-%% Test the write cache for duplicate bags.
-cache_duplicate_bags_v9(Config) when is_list(Config) ->
- cache_duplicate_bags(Config, 9).
-
-cache_duplicate_bags(Config, Version) ->
+cache_duplicate_bags(Config) when is_list(Config) ->
Small = 2,
- cache_dup_bags(Config, {0,0}, false, Small, Version),
- cache_dup_bags(Config, {0,0}, true, Small, Version),
- cache_dup_bags(Config, {5000,5000}, false, Small, Version),
- cache_dup_bags(Config, {5000,5000}, true, Small, Version),
+ cache_dup_bags(Config, {0,0}, false, Small),
+ cache_dup_bags(Config, {0,0}, true, Small),
+ cache_dup_bags(Config, {5000,5000}, false, Small),
+ cache_dup_bags(Config, {5000,5000}, true, Small),
%% Objects of size greater than 2 kB.
Big = 1200,
- cache_dup_bags(Config, {0,0}, false, Big, Version),
- cache_dup_bags(Config, {0,0}, true, Big, Version),
- cache_dup_bags(Config, {5000,5000}, false, Big, Version),
- cache_dup_bags(Config, {5000,5000}, true, Big, Version).
+ cache_dup_bags(Config, {0,0}, false, Big),
+ cache_dup_bags(Config, {0,0}, true, Big),
+ cache_dup_bags(Config, {5000,5000}, false, Big),
+ cache_dup_bags(Config, {5000,5000}, true, Big).
-cache_dup_bags(Config, DelayedWrite, Extra, Sz, Version) ->
+cache_dup_bags(Config, DelayedWrite, Extra, Sz) ->
%% Extra = bool(). Insert tuples until the tested key is not alone.
%% Sz = integer(). Size of the inserted tuples.
@@ -2635,10 +2249,8 @@ cache_dup_bags(Config, DelayedWrite, Extra, Sz, Version) ->
file:delete(Fname),
P0 = pps(),
- {ok, _} =
- dets:open_file(T,[{version, Version}, {file,Fname},
- {type,duplicate_bag},
- {delayed_write, DelayedWrite}]),
+ {ok, _} = dets:open_file(T,[{file,Fname}, {type,duplicate_bag},
+ {delayed_write, DelayedWrite}]),
Dups = 2,
{Key, OtherKeys} =
@@ -2869,7 +2481,7 @@ otp_8899(Config) when is_list(Config) ->
Server = self(),
file:delete(FName),
- {ok, _} = dets:open_file(Tab,[{file, FName},{version,9}]),
+ {ok, _} = dets:open_file(Tab,[{file, FName}]),
[P1,P2,P3,P4] = new_clients(4, Tab),
MC = [Tab],
@@ -2895,7 +2507,7 @@ many_clients(Config) when is_list(Config) ->
file:delete(FName),
P0 = pps(),
- {ok, _} = dets:open_file(Tab,[{file, FName},{version,9}]),
+ {ok, _} = dets:open_file(Tab,[{file, FName}]),
[P1,P2,P3,P4] = new_clients(4, Tab),
%% dets:init_table/2 is used for making sure that all processes
@@ -2954,14 +2566,14 @@ many_clients(Config) when is_list(Config) ->
file:delete(FName),
%% Check that errors are handled correctly by the streaming operators.
- {ok, _} = dets:open_file(Tab,[{file, FName},{version,9}]),
+ {ok, _} = dets:open_file(Tab,[{file, FName}]),
ok = ins(Tab, 100),
Obj = {66,{item,number,66}},
{ok, ObjPos} = dets:where(Tab, Obj),
ok = dets:close(Tab),
%% Damaged object.
crash(FName, ObjPos+12),
- {ok, _} = dets:open_file(Tab,[{file, FName},{version,9}]),
+ {ok, _} = dets:open_file(Tab,[{file, FName}]),
BadObject1 = dets:lookup_keys(Tab, [65,66,67,68,69]),
bad_object(BadObject1, FName),
_Error = dets:close(Tab),
@@ -3400,8 +3012,13 @@ repair_continuation(Config) ->
MS = [{'_',[],[true]}],
- {[true], C1} = dets:select(Tab, MS, 1),
- C2 = binary_to_term(term_to_binary(C1)),
+ SRes = term_to_binary(dets:select(Tab, MS, 1)),
+ %% Get rid of compiled match spec
+ lists:foreach(fun (P) ->
+ garbage_collect(P)
+ end, processes()),
+ {[true], C2} = binary_to_term(SRes),
+
{'EXIT', {badarg, _}} = (catch dets:select(C2)),
C3 = dets:repair_continuation(C2, MS),
{[true], C4} = dets:select(C3),
@@ -3415,18 +3032,13 @@ repair_continuation(Config) ->
%% OTP-5487. Growth of read-only table (again).
otp_5487(Config) ->
- otp_5487(Config, 9),
- otp_5487(Config, 8),
- ok.
-
-otp_5487(Config, Version) ->
Tab = otp_5487,
Fname = filename(otp_5487, Config),
file:delete(Fname),
Ets = ets:new(otp_5487, [public, set]),
lists:foreach(fun(I) -> ets:insert(Ets, {I,I+1}) end,
lists:seq(0,1000)),
- {ok, _} = dets:open_file(Tab, [{file,Fname},{version,Version}]),
+ {ok, _} = dets:open_file(Tab, [{file,Fname}]),
ok = dets:from_ets(Tab, Ets),
ok = dets:sync(Tab),
ok = dets:close(Tab),
@@ -3470,14 +3082,12 @@ otp_6359(Config) ->
%% OTP-4738. ==/2 and =:=/2.
otp_4738(Config) ->
- %% Version 8 has not been corrected.
- %% (The constant -12857447 is for version 9 only.)
- otp_4738_set(9, Config),
- otp_4738_bag(9, Config),
- otp_4738_dupbag(9, Config),
+ otp_4738_set(Config),
+ otp_4738_bag(Config),
+ otp_4738_dupbag(Config),
ok.
-otp_4738_dupbag(Version, Config) ->
+otp_4738_dupbag(Config) ->
Tab = otp_4738,
File = filename(Tab, Config),
file:delete(File),
@@ -3485,7 +3095,7 @@ otp_4738_dupbag(Version, Config) ->
F = float(I),
One = 1,
FOne = float(One),
- Args = [{file,File},{type,duplicate_bag},{version,Version}],
+ Args = [{file,File},{type,duplicate_bag}],
{ok, Tab} = dets:open_file(Tab, Args),
ok = dets:insert(Tab, [{I,One},{F,One},{I,FOne},{F,FOne}]),
ok = dets:sync(Tab),
@@ -3530,7 +3140,7 @@ otp_4738_dupbag(Version, Config) ->
file:delete(File),
ok.
-otp_4738_bag(Version, Config) ->
+otp_4738_bag(Config) ->
Tab = otp_4738,
File = filename(Tab, Config),
file:delete(File),
@@ -3538,7 +3148,7 @@ otp_4738_bag(Version, Config) ->
F = float(I),
One = 1,
FOne = float(One),
- Args = [{file,File},{type,bag},{version,Version}],
+ Args = [{file,File},{type,bag}],
{ok, Tab} = dets:open_file(Tab, Args),
ok = dets:insert(Tab, [{I,One},{F,One},{I,FOne},{F,FOne}]),
ok = dets:sync(Tab),
@@ -3561,11 +3171,11 @@ otp_4738_bag(Version, Config) ->
ok = dets:close(Tab),
file:delete(File).
-otp_4738_set(Version, Config) ->
+otp_4738_set(Config) ->
Tab = otp_4738,
File = filename(Tab, Config),
file:delete(File),
- Args = [{file,File},{type,set},{version,Version}],
+ Args = [{file,File},{type,set}],
%% I and F share the same slot.
I = -12857447,
@@ -3864,6 +3474,19 @@ wait_for_close(Tab) ->
wait_for_close(Tab)
end.
+%% OTP-13830. Format 8 is no longer supported.
+otp_13830(Config) ->
+ Tab = otp_13830,
+ File8 = filename:join(?datadir(Config), "version_8.dets"),
+ {error,{format_8_no_longer_supported,_}} =
+ dets:open_file(Tab, [{file, File8}]),
+ File = filename(Tab, Config),
+ %% Check the 'version' option, for backwards compatibility:
+ {ok, Tab} = dets:open_file(Tab, [{file, File}, {version, 9}]),
+ ok = dets:close(Tab),
+ {ok, Tab} = dets:open_file(Tab, [{file, File}, {version, default}]),
+ ok = dets:close(Tab).
+
%%
%% Parts common to several test cases
%%
@@ -4000,9 +3623,7 @@ match_test(Data, Tab) ->
%% Utilities
%%
-headsz(8) ->
- ?HEADSZ_v8;
-headsz(_) ->
+headsz() ->
?HEADSZ_v9.
unwritable(Fname) ->
@@ -4030,13 +3651,13 @@ filename(Name, Config) when is_atom(Name) ->
filename(Name, _Config) ->
filename:join(?privdir(_Config), Name).
-open_files(_Name, [], _Version) ->
+open_files(_Name, []) ->
[];
-open_files(Name0, [Args | Tail], Version) ->
+open_files(Name0, [Args | Tail]) ->
?format("init ~p~n", [Args]),
Name = list_to_atom(integer_to_list(Name0)),
- {ok, Name} = dets:open_file(Name, [{version,Version} | Args]),
- [Name | open_files(Name0+1, Tail, Version)].
+ {ok, Name} = dets:open_file(Name, Args),
+ [Name | open_files(Name0+1, Tail)].
close_all(Tabs) -> foreach(fun(Tab) -> ok = dets:close(Tab) end, Tabs).
@@ -4137,20 +3758,15 @@ no_keys_test([T | Ts]) ->
no_keys_test([]) ->
ok;
no_keys_test(T) ->
- case dets:info(T, version) of
- 8 ->
- ok;
- 9 ->
- Kp = dets:info(T, keypos),
- All = dets:match_object(T, '_'),
- L = lists:map(fun(X) -> element(Kp, X) end, All),
- NoKeys = length(lists:usort(L)),
- case {dets:info(T, no_keys), NoKeys} of
- {N, N} ->
- ok;
- {N1, N2} ->
- exit({no_keys_test, N1, N2})
- end
+ Kp = dets:info(T, keypos),
+ All = dets:match_object(T, '_'),
+ L = lists:map(fun(X) -> element(Kp, X) end, All),
+ NoKeys = length(lists:usort(L)),
+ case {dets:info(T, no_keys), NoKeys} of
+ {N, N} ->
+ ok;
+ {N1, N2} ->
+ exit({no_keys_test, N1, N2})
end.
safe_get_all_objects(Tab) ->
@@ -4182,7 +3798,6 @@ count_objs_1({Ts,C}, N) when is_list(Ts) ->
get_all_objects_fast(Tab) ->
dets:match_object(Tab, '_').
-%% Relevant for version 8.
histogram(Tab) ->
OnePercent = case dets:info(Tab, no_slots) of
undefined -> undefined;
@@ -4244,10 +3859,6 @@ ave_histogram([{S,N1} | H], N) ->
ave_histogram([], N) ->
N.
-bad_object({error,{bad_object,FileName}}, FileName) ->
- ok; % Version 8, no debug.
-bad_object({error,{{bad_object,_,_},FileName}}, FileName) ->
- ok; % Version 8, debug...
bad_object({error,{{bad_object,_}, FileName}}, FileName) ->
ok; % No debug.
bad_object({error,{{{bad_object,_,_},_,_,_}, FileName}}, FileName) ->
diff --git a/lib/stdlib/test/dets_SUITE_data/version_r2d.dets b/lib/stdlib/test/dets_SUITE_data/version_8.dets
index 327072f99e..278187e85c 100644
--- a/lib/stdlib/test/dets_SUITE_data/version_r2d.dets
+++ b/lib/stdlib/test/dets_SUITE_data/version_8.dets
Binary files differ
diff --git a/lib/stdlib/test/dict_SUITE.erl b/lib/stdlib/test/dict_SUITE.erl
index 47358d729f..e99af9ad42 100644
--- a/lib/stdlib/test/dict_SUITE.erl
+++ b/lib/stdlib/test/dict_SUITE.erl
@@ -23,10 +23,10 @@
-module(dict_SUITE).
--export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/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,
- create/1,store/1,iterate/1]).
+ create/1,store/1,iterate/1,remove/1]).
-include_lib("common_test/include/ct.hrl").
@@ -37,7 +37,7 @@ suite() ->
{timetrap,{minutes,5}}].
all() ->
- [create, store, iterate].
+ [create, store, remove, iterate].
groups() ->
[].
@@ -92,6 +92,27 @@ store_1(List, M) ->
end,
D0.
+remove(_Config) ->
+ test_all([{0,87}], fun remove_1/2).
+
+remove_1(List0, M) ->
+ %% Make sure that keys are unique. Randomize key order.
+ List1 = orddict:from_list(List0),
+ List2 = lists:sort([{rand:uniform(),E} || E <- List1]),
+ List = [E || {_,E} <- List2],
+ D0 = M(from_list, List),
+ remove_2(List, D0, M).
+
+remove_2([{Key,Val}|T], D0, M) ->
+ {Val,D1} = M(take, {Key,D0}),
+ error = M(take, {Key,D1}),
+ D2 = M(erase, {Key,D0}),
+ true = M(equal, {D1,D2}),
+ remove_2(T, D1, M);
+remove_2([], D, M) ->
+ true = M(is_empty, D),
+ D.
+
%%%
%%% Test specifics for gb_trees.
%%%
diff --git a/lib/stdlib/test/dict_test_lib.erl b/lib/stdlib/test/dict_test_lib.erl
index 7c4c3572ae..f6fef7bdf4 100644
--- a/lib/stdlib/test/dict_test_lib.erl
+++ b/lib/stdlib/test/dict_test_lib.erl
@@ -33,7 +33,9 @@ new(Mod, Eq) ->
(iterator, S) -> Mod:iterator(S);
(iterator_from, {Start, S}) -> Mod:iterator_from(Start, S);
(next, I) -> Mod:next(I);
- (to_list, D) -> to_list(Mod, D)
+ (to_list, D) -> to_list(Mod, D);
+ (erase, {K,D}) -> erase(Mod, K, D);
+ (take, {K,D}) -> take(Mod, K, D)
end.
empty(Mod) ->
@@ -67,3 +69,19 @@ enter(Mod, Key, Val, Dict) ->
true ->
Mod:store(Key, Val, Dict)
end.
+
+erase(Mod, Key, Val) when Mod =:= dict; Mod =:= orddict ->
+ Mod:erase(Key, Val);
+erase(gb_trees, Key, Val) ->
+ gb_trees:delete_any(Key, Val).
+
+take(gb_trees, Key, Val) ->
+ Res = try
+ gb_trees:take(Key, Val)
+ catch
+ error:_ ->
+ error
+ end,
+ Res = gb_trees:take_any(Key, Val);
+take(Mod, Key, Val) ->
+ Mod:take(Key, Val).
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index 4078513e38..71d6820c47 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -306,7 +306,7 @@ otp_5362(Config) when is_list(Config) ->
File_Back_hrl = filename:join(Dir, "back_5362.hrl"),
Back = <<"-module(back_5362).
- -compile(export_all).
+ -export([foo/1]).
-file(?FILE, 1).
-include(\"back_5362.hrl\").
@@ -334,7 +334,7 @@ otp_5362(Config) when is_list(Config) ->
-file(?FILE, 100).
- -compile(export_all).
+ -export([foo/1,bar/1]).
-file(\"other.file\", ?LINE). % like an included file...
foo(A) -> % line 105
@@ -362,7 +362,7 @@ otp_5362(Config) when is_list(Config) ->
Blank = <<"-module(blank_5362).
- -compile(export_all).
+ -export([q/1,a/1,b/1,c/1]).
-
file(?FILE, 18). q(Q) -> foo. % line 18
@@ -1258,7 +1258,7 @@ do_otp_8911(Config) ->
File = "i.erl",
Cont = <<"-module(i).
- -compile(export_all).
+ -export([t/0]).
-file(\"fil1\", 100).
-include(\"i1.erl\").
t() ->
@@ -1391,7 +1391,7 @@ otp_11728(Config) when is_list(Config) ->
HrlFile = filename:join(Dir, "otp_11728.hrl"),
ok = file:write_file(HrlFile, H),
C = <<"-module(otp_11728).
- -compile(export_all).
+ -export([function_name/0]).
-include(\"otp_11728.hrl\").
@@ -1599,12 +1599,12 @@ check_test(Config, Test) ->
end.
compile_test(Config, Test0) ->
- Test = [<<"-module(epp_test). -compile(export_all). ">>, Test0],
+ Test = [<<"-module(epp_test). ">>, Test0],
Filename = "epp_test.erl",
PrivDir = proplists:get_value(priv_dir, Config),
File = filename:join(PrivDir, Filename),
ok = file:write_file(File, Test),
- Opts = [export_all,return,nowarn_unused_record,{outdir,PrivDir}],
+ Opts = [export_all,nowarn_export_all,return,nowarn_unused_record,{outdir,PrivDir}],
case compile_file(File, Opts) of
{ok, Ws} -> warnings(File, Ws);
Else -> Else
@@ -1653,7 +1653,7 @@ unopaque_forms(Forms) ->
[erl_parse:anno_to_term(Form) || Form <- Forms].
run_test(Config, Test0) ->
- Test = [<<"-module(epp_test). -compile(export_all). ">>, Test0],
+ Test = [<<"-module(epp_test). -export([t/0]). ">>, Test0],
Filename = "epp_test.erl",
PrivDir = proplists:get_value(priv_dir, Config),
File = filename:join(PrivDir, Filename),
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index d916eb3eef..df38edf393 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-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2017. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -64,7 +64,7 @@
predef/1,
maps/1,maps_type/1,maps_parallel_match/1,
otp_11851/1,otp_11879/1,otp_13230/1,
- record_errors/1]).
+ record_errors/1, otp_xxxxx/1]).
suite() ->
[{ct_hooks,[ts_install_cth]},
@@ -84,7 +84,7 @@ all() ->
too_many_arguments, basic_errors, bin_syntax_errors, predef,
maps, maps_type, maps_parallel_match,
otp_11851, otp_11879, otp_13230,
- record_errors].
+ record_errors, otp_xxxxx].
groups() ->
[{unused_vars_warn, [],
@@ -1554,7 +1554,15 @@ guard(Config) when is_list(Config) ->
[],
{errors,[{1,erl_lint,illegal_guard_expr},
{2,erl_lint,illegal_guard_expr}],
- []}}
+ []}},
+ {guard10,
+ <<"is_port(_) -> false.
+ t(P) when port(P) -> ok.
+ ">>,
+ [],
+ {error,
+ [{2,erl_lint,{obsolete_guard_overridden,port}}],
+ [{2,erl_lint,{obsolete_guard,{port,1}}}]}}
],
[] = run(Config, Ts1),
ok.
@@ -1855,7 +1863,7 @@ otp_5276(Config) when is_list(Config) ->
%% OTP-5917. Check the 'deprecated' attributed.
otp_5917(Config) when is_list(Config) ->
Ts = [{otp_5917_1,
- <<"-compile(export_all).
+ <<"-export([t/0]).
-deprecated({t,0}).
@@ -1870,7 +1878,7 @@ otp_5917(Config) when is_list(Config) ->
%% OTP-6585. Check the deprecated guards list/1, pid/1, ....
otp_6585(Config) when is_list(Config) ->
Ts = [{otp_6585_1,
- <<"-compile(export_all).
+ <<"-export([t/0]).
-record(r, {}).
@@ -1994,22 +2002,22 @@ otp_5362(Config) when is_list(Config) ->
<<"-compile(nowarn_deprecated_function).
-compile(nowarn_bif_clash).
spawn(A) ->
- erlang:hash(A, 3000),
+ erlang:now(),
spawn(A).
">>,
- {[nowarn_unused_function,
+ {[nowarn_unused_function,
warn_deprecated_function,
warn_bif_clash]},
{error,
[{5,erl_lint,{call_to_redefined_old_bif,{spawn,1}}}],
- [{4,erl_lint,{deprecated,{erlang,hash,2},{erlang,phash2,2},
- "a future release"}}]}},
-
+ [{4,erl_lint,{deprecated,{erlang,now,0},
+ "Deprecated BIF. See the \"Time and Time Correction in Erlang\" "
+ "chapter of the ERTS User's Guide for more information."}}]}},
{otp_5362_5,
<<"-compile(nowarn_deprecated_function).
-compile(nowarn_bif_clash).
spawn(A) ->
- erlang:hash(A, 3000),
+ erlang:now(),
spawn(A).
">>,
{[nowarn_unused_function]},
@@ -2018,37 +2026,37 @@ otp_5362(Config) when is_list(Config) ->
%% The special nowarn_X are not affected by general warn_X.
{otp_5362_6,
- <<"-compile({nowarn_deprecated_function,{erlang,hash,2}}).
+ <<"-compile({nowarn_deprecated_function,{erlang,now,0}}).
-compile({nowarn_bif_clash,{spawn,1}}).
spawn(A) ->
- erlang:hash(A, 3000),
+ erlang:now(),
spawn(A).
">>,
- {[nowarn_unused_function,
- warn_deprecated_function,
+ {[nowarn_unused_function,
+ warn_deprecated_function,
warn_bif_clash]},
{errors,
[{2,erl_lint,disallowed_nowarn_bif_clash}],[]}},
{otp_5362_7,
<<"-export([spawn/1]).
- -compile({nowarn_deprecated_function,{erlang,hash,2}}).
+ -compile({nowarn_deprecated_function,{erlang,now,0}}).
-compile({nowarn_bif_clash,{spawn,1}}).
-compile({nowarn_bif_clash,{spawn,2}}). % bad
-compile([{nowarn_deprecated_function,
- [{erlang,hash,-1},{3,hash,-1}]}, % 2 bad
- {nowarn_deprecated_function, {{a,b,c},hash,-1}}]). % bad
+ [{erlang,now,-1},{3,now,-1}]}, % 2 bad
+ {nowarn_deprecated_function, {{a,b,c},now,-1}}]). % bad
spawn(A) ->
- erlang:hash(A, 3000),
+ erlang:now(),
spawn(A).
">>,
{[nowarn_unused_function]},
{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}}}]}
+ [{5,erl_lint,{bad_nowarn_deprecated_function,{3,now,-1}}},
+ {5,erl_lint,{bad_nowarn_deprecated_function,{erlang,now,-1}}},
+ {5,erl_lint,{bad_nowarn_deprecated_function,{{a,b,c},now,-1}}}]}
},
{otp_5362_8,
@@ -2056,14 +2064,15 @@ otp_5362(Config) when is_list(Config) ->
-compile(warn_deprecated_function).
-compile(warn_bif_clash).
spawn(A) ->
- erlang:hash(A, 3000),
+ erlang:now(),
spawn(A).
">>,
{[nowarn_unused_function,
{nowarn_bif_clash,{spawn,1}}]}, % has no effect
{warnings,
- [{5,erl_lint,{deprecated,{erlang,hash,2},{erlang,phash2,2},
- "a future release"}}]}},
+ [{5,erl_lint,{deprecated,{erlang,now,0},
+ "Deprecated BIF. See the \"Time and Time Correction in Erlang\" "
+ "chapter of the ERTS User's Guide for more information."}}]}},
{otp_5362_9,
<<"-include_lib(\"stdlib/include/qlc.hrl\").
@@ -2075,11 +2084,11 @@ otp_5362(Config) when is_list(Config) ->
[]},
{otp_5362_10,
- <<"-compile({nowarn_deprecated_function,{erlang,hash,2}}).
+ <<"-compile({nowarn_deprecated_function,{erlang,now,0}}).
-compile({nowarn_bif_clash,{spawn,1}}).
-import(x,[spawn/1]).
spin(A) ->
- erlang:hash(A, 3000),
+ erlang:now(),
spawn(A).
">>,
{[nowarn_unused_function,
@@ -2089,11 +2098,11 @@ otp_5362(Config) when is_list(Config) ->
[{2,erl_lint,disallowed_nowarn_bif_clash}],[]}},
{call_deprecated_function,
- <<"t(X) -> erlang:hash(X, 2000).">>,
+ <<"t(X) -> crypto:md5(X).">>,
[],
{warnings,
- [{1,erl_lint,{deprecated,{erlang,hash,2},
- {erlang,phash2,2},"a future release"}}]}},
+ [{1,erl_lint,{deprecated,{crypto,md5,1},
+ {crypto,hash,2}, "a future release"}}]}},
{call_removed_function,
<<"t(X) -> regexp:match(X).">>,
@@ -2540,7 +2549,7 @@ otp_5878(Config) when is_list(Config) ->
{function,9,t,0,[{clause,9,[],[],[{record,10,r,[]}]}]},
{eof,11}],
{error,[{"rec.erl",[{7,erl_lint,old_abstract_code}]}],[]} =
- compile:forms(OldAbstract, [return, report]),
+ compile_forms(OldAbstract, [return, report]),
ok.
@@ -2619,7 +2628,7 @@ otp_11772(Config) when is_list(Config) ->
Ts = <<"
-module(newly).
- -compile(export_all).
+ -export([t/0]).
%% Built-in:
-type node() :: node().
@@ -2644,7 +2653,7 @@ otp_11771(Config) when is_list(Config) ->
Ts = <<"
-module(newly).
- -compile(export_all).
+ -export([t/0]).
%% No longer allowed in 17.0:
-type arity() :: atom().
@@ -2671,7 +2680,7 @@ otp_11872(Config) when is_list(Config) ->
Ts = <<"
-module(map).
- -compile(export_all).
+ -export([t/0]).
-export_type([map/0, product/0]).
@@ -2694,9 +2703,9 @@ export_all(Config) when is_list(Config) ->
id(I) -> I.
">>,
- [] = run_test2(Config, Ts, []),
+ [] = run_test2(Config, Ts, [nowarn_export_all]),
{warnings,[{2,erl_lint,export_all}]} =
- run_test2(Config, Ts, [warn_export_all]),
+ run_test2(Config, Ts, []),
ok.
%% Test warnings for functions that clash with BIFs.
@@ -2997,7 +3006,7 @@ behaviour_basic(Config) when is_list(Config) ->
{behaviour4,
<<"-behavior(application). %% Test callbacks with export_all
- -compile(export_all).
+ -compile([export_all, nowarn_export_all]).
stop(_) -> ok.
">>,
[],
@@ -3839,9 +3848,13 @@ otp_11879(_Config) ->
[{1,erl_lint,{spec_fun_undefined,{f,1}}},
{2,erl_lint,spec_wrong_arity},
{22,erl_lint,callback_wrong_arity}]}],
- []} = compile:forms(Fs, [return,report]),
+ []} = compile_forms(Fs, [return,report]),
ok.
+compile_forms(Terms, Opts) ->
+ Forms = [erl_parse:anno_from_term(Term) || Term <- Terms],
+ compile:forms(Forms, Opts).
+
%% OTP-13230: -deprecated without -module.
otp_13230(Config) when is_list(Config) ->
Abstr = <<"-deprecated([{frutt,0,next_version}]).">>,
@@ -3861,6 +3874,55 @@ record_errors(Config) when is_list(Config) ->
{3,erl_lint,{redefine_field,r,a}}],[]}}],
run(Config, Ts).
+otp_xxxxx(Config) ->
+ Ts = [{constraint1,
+ <<"-export([t/1]).
+ -spec t(X) -> X when is_subtype(integer()).
+ t(a) -> foo:bar().
+ ">>,
+ [],
+ {errors,
+ [{2,erl_parse,"unsupported constraint " ++ ["is_subtype"]}],
+ []}},
+ {constraint2,
+ <<"-export([t/1]).
+ -spec t(X) -> X when bad_atom(X, integer()).
+ t(a) -> foo:bar().
+ ">>,
+ [],
+ {errors,
+ [{2,erl_parse,"unsupported constraint " ++ ["bad_atom"]}],
+ []}},
+ {constraint3,
+ <<"-export([t/1]).
+ -spec t(X) -> X when is_subtype(bad_variable, integer()).
+ t(a) -> foo:bar().
+ ">>,
+ [],
+ {errors,[{2,erl_parse,"bad type variable"}],[]}},
+ {constraint4,
+ <<"-export([t/1]).
+ -spec t(X) -> X when is_subtype(atom(), integer()).
+ t(a) -> foo:bar().
+ ">>,
+ [],
+ {errors,[{2,erl_parse,"bad type variable"}],[]}},
+ {constraint5,
+ <<"-export([t/1]).
+ -spec t(X) -> X when is_subtype(X, integer()).
+ t(a) -> foo:bar().
+ ">>,
+ [],
+ []},
+ {constraint6,
+ <<"-export([t/1]).
+ -spec t(X) -> X when X :: integer().
+ t(a) -> foo:bar().
+ ">>,
+ [],
+ []}],
+ run(Config, Ts).
+
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 a103f6dc53..1a028204b4 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2017. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -825,12 +825,13 @@ type_examples() ->
%% is_subtype(V, T) syntax, we need a few examples of the syntax.
{ex31,<<"-spec t1(FooBar :: t99()) -> t99();"
"(t2()) -> t2();"
- "('\\'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(), '\\'t::4'()).">>},
+ "('\\'t::4'()) -> {'\\'t::4'(), B}"
+ " when is_subtype(B, '\\'t::4'());"
+ "(t23()) -> C when is_subtype(C, atom()),"
+ " is_subtype(C, t14());"
+ "(t24()) -> D when is_subtype(D, atom()),"
+ " is_subtype(D, t14()),"
+ " is_subtype(D, '\\'t::4'()).">>},
{ex32,<<"-spec mod:t2() -> any(). ">>},
{ex33,<<"-opaque attributes_data() :: "
"[{'column', column()} | {'line', info_line()} |"
@@ -1067,10 +1068,10 @@ otp_11100(Config) when is_list(Config) ->
%% There are a few places where the added code ("options(none)")
%% doesn't make a difference (pp:bit_elem_type/1 is an example).
+ A1 = erl_anno:new(1),
%% Cannot trigger the use of the hook function with export/import.
"-export([{fy,a}/b]).\n" =
- pf({attribute,1,export,[{{fy,a},b}]}),
- A1 = erl_anno:new(1),
+ pf({attribute,A1,export,[{{fy,a},b}]}),
"-type foo() :: integer(INVALID-FORM:{foo,bar}:).\n" =
pf({attribute,A1,type,{foo,{type,A1,integer,[{foo,bar}]},[]}}),
pf({attribute,A1,type,
@@ -1099,10 +1100,11 @@ otp_11100(Config) when is_list(Config) ->
%% OTP-11861. behaviour_info() and -callback.
otp_11861(Config) when is_list(Config) ->
+ A3 = erl_anno:new(3),
"-optional_callbacks([bar/0]).\n" =
- pf({attribute,3,optional_callbacks,[{bar,0}]}),
+ pf({attribute,A3,optional_callbacks,[{bar,0}]}),
"-optional_callbacks([{bar,1,bad}]).\n" =
- pf({attribute,4,optional_callbacks,[{bar,1,bad}]}),
+ pf({attribute,A3,optional_callbacks,[{bar,1,bad}]}),
ok.
pf(Form) ->
@@ -1166,19 +1168,21 @@ compile(Config, Tests) ->
lists:foldl(F, [], Tests).
compile_file(Config, Test0) ->
- case compile_file(Config, Test0, ['E']) of
+ Test = ["-module(erl_pp_test).\n",
+ "-compile(export_all).\n",
+ Test0],
+ case compile_file(Config, Test, ['E']) of
{ok, RootFile} ->
File = RootFile ++ ".E",
{ok, Bin0} = file:read_file(File),
- Bin = strip_module_info(Bin0),
%% A very simple check: just try to compile the output.
- case compile_file(Config, Bin, []) of
+ case compile_file(Config, Bin0, []) of
{ok, RootFile2} ->
File2 = RootFile2 ++ ".E",
{ok, Bin1} = file:read_file(File2),
case Bin0 =:= Bin1 of
true ->
- test_max_line(binary_to_list(Bin));
+ test_max_line(binary_to_list(Bin0));
false ->
{error, file_contents_modified, {Bin0, Bin1}}
end;
@@ -1189,11 +1193,8 @@ compile_file(Config, Test0) ->
Error
end.
-compile_file(Config, Test0, Opts0) ->
+compile_file(Config, Test, Opts0) ->
FileName = filename('erl_pp_test.erl', Config),
- Test = list_to_binary(["-module(erl_pp_test). "
- "-compile(export_all). ",
- Test0]),
Opts = [export_all,return,nowarn_unused_record,{outdir,?privdir} | Opts0],
ok = file:write_file(FileName, Test),
case compile:file(FileName, Opts) of
@@ -1202,11 +1203,6 @@ compile_file(Config, Test0, Opts0) ->
Error -> Error
end.
-strip_module_info(Bin) ->
- {match, [{Start,_Len}|_]} = re:run(Bin, "module_info"),
- <<R:Start/binary,_/binary>> = Bin,
- R.
-
flat_expr1(Expr0) ->
Expr = erl_parse:new_anno(Expr0),
lists:flatten(erl_pp:expr(Expr)).
diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl
index 4ae734eb65..aca5b1e54f 100644
--- a/lib/stdlib/test/erl_scan_SUITE.erl
+++ b/lib/stdlib/test/erl_scan_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2017. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -772,10 +772,9 @@ unicode() ->
erl_scan:string([1089]),
{error,{{1,1},erl_scan,{illegal,character}},{1,2}} =
erl_scan:string([1089], {1,1}),
- {error,{1,erl_scan,{illegal,atom}},1} =
- erl_scan:string("'a"++[1089]++"b'", 1),
- {error,{{1,1},erl_scan,{illegal,atom}},{1,6}} =
- erl_scan:string("'a"++[1089]++"b'", {1,1}),
+ {error,{{1,3},erl_scan,{illegal,character}},{1,4}} =
+ erl_scan:string("'a" ++ [999999999] ++ "c'", {1,1}),
+
test("\"a"++[1089]++"b\""),
{ok,[{char,1,1}],1} =
erl_scan_string([$$,$\\,$^,1089], 1),
@@ -786,8 +785,8 @@ unicode() ->
erl_scan:format_error(Error),
{error,{{1,1},erl_scan,_},{1,11}} =
erl_scan:string("\"qa\\x{aaa}",{1,1}),
- {error,{{1,1},erl_scan,{illegal,atom}},{1,12}} =
- erl_scan:string("'qa\\x{aaa}'",{1,1}),
+ {error,{{1,1},erl_scan,_},{1,11}} =
+ erl_scan:string("'qa\\x{aaa}",{1,1}),
{ok,[{char,1,1089}],1} =
erl_scan_string([$$,1089], 1),
@@ -904,10 +903,10 @@ more_chars() ->
%% OTP-10302. Unicode characters scanner/parser.
otp_10302(Config) when is_list(Config) ->
%% From unicode():
- {error,{1,erl_scan,{illegal,atom}},1} =
- erl_scan:string("'a"++[1089]++"b'", 1),
- {error,{{1,1},erl_scan,{illegal,atom}},{1,12}} =
- erl_scan:string("'qa\\x{aaa}'",{1,1}),
+ {ok,[{atom,1,'aсb'}],1} =
+ erl_scan_string("'a"++[1089]++"b'", 1),
+ {ok,[{atom,{1,1},'qaપ'}],{1,12}} =
+ erl_scan_string("'qa\\x{aaa}'",{1,1}),
{ok,[{char,1,1089}],1} = erl_scan_string([$$,1089], 1),
{ok,[{char,1,1089}],1} = erl_scan_string([$$,$\\,1089],1),
diff --git a/lib/stdlib/test/error_logger_h_SUITE.erl b/lib/stdlib/test/error_logger_h_SUITE.erl
index 2a34c7764f..30f96e0522 100644
--- a/lib/stdlib/test/error_logger_h_SUITE.erl
+++ b/lib/stdlib/test/error_logger_h_SUITE.erl
@@ -297,13 +297,13 @@ match_format(Tag, [Format,Args], [Head|Lines], AtNode, Depth) ->
iolist_to_binary(S)
end,
Expected0 = binary:split(Bin, <<"\n">>, [global,trim]),
- Expected = Expected0 ++ AtNode,
+ Expected = AtNode ++ Expected0,
match_term_lines(Expected, Lines).
match_term(Tag, [Arg], [Head|Lines], AtNode, Depth) ->
match_head(Tag, Head),
Expected0 = match_term_get_expected(Arg, Depth),
- Expected = Expected0 ++ AtNode,
+ Expected = AtNode ++ Expected0,
match_term_lines(Expected, Lines).
match_term_get_expected(List, Depth) when is_list(List) ->
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 00e02a06cc..8581440d58 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -22,7 +22,7 @@
-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]).
+ privacy/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,
@@ -82,27 +82,6 @@
%% 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, 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,
- update_element_neg/1, update_element_neg_do/1, update_counter_do/1, update_counter_neg/1,
- evil_update_counter_do/1, fixtable_next_do/1, heir_do/1, give_away_do/1, setopts_do/1,
- rename_do/1, rename_unnamed_do/1, interface_equality_do/1, ordered_match_do/1,
- ordered_do/1, privacy_do/1, empty_do/1, badinsert_do/1, time_lookup_do/1,
- lookup_order_do/1, lookup_element_mult_do/1, delete_tab_do/1, delete_elem_do/1,
- 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,
- do_heavy_concurrent/1, tab2file2_do/2, exit_large_table_owner_do/2,
- types_do/1, sleeper/0, memory_do/1, update_counter_with_default_do/1,
- update_counter_table_growth_do/1,
- ms_tracee_dummy/1, ms_tracee_dummy/2, ms_tracee_dummy/3, ms_tracee_dummy/4
- ]).
-
-export([t_select_reverse/1]).
-include_lib("common_test/include/ct.hrl").
@@ -216,7 +195,7 @@ memory_check_summary(_Config) ->
receive {get_failed_memchecks, FailedMemchecks} -> ok end,
io:format("Failed memchecks: ~p\n",[FailedMemchecks]),
NoFailedMemchecks = length(FailedMemchecks),
- if NoFailedMemchecks > 3 ->
+ if NoFailedMemchecks > 1 ->
ct:fail("Too many failed (~p) memchecks", [NoFailedMemchecks]);
true ->
ok
@@ -228,7 +207,7 @@ memory_check_summary(_Config) ->
%% Test that a disappearing bucket during select of a non-fixed table works.
t_bucket_disappears(Config) when is_list(Config) ->
- repeat_for_opts(t_bucket_disappears_do).
+ repeat_for_opts(fun t_bucket_disappears_do/1).
t_bucket_disappears_do(Opts) ->
EtsMem = etsmem(),
@@ -396,11 +375,16 @@ ms_tracer_collect(Tracee, Ref, Acc) ->
ms_tracee(Parent, CallArgList) ->
Parent ! {self(), ready},
receive start -> ok end,
- lists:foreach(fun(Args) ->
- erlang:apply(?MODULE, ms_tracee_dummy, tuple_to_list(Args))
- end, CallArgList).
-
-
+ F = fun({A1}) ->
+ ms_tracee_dummy(A1);
+ ({A1,A2}) ->
+ ms_tracee_dummy(A1, A2);
+ ({A1,A2,A3}) ->
+ ms_tracee_dummy(A1, A2, A3);
+ ({A1,A2,A3,A4}) ->
+ ms_tracee_dummy(A1, A2, A3, A4)
+ end,
+ lists:foreach(F, CallArgList).
ms_tracee_dummy(_) -> ok.
ms_tracee_dummy(_,_) -> ok.
@@ -418,7 +402,7 @@ assert_eq(A,B) ->
%% Test ets:repair_continuation/2.
t_repair_continuation(Config) when is_list(Config) ->
- repeat_for_opts(t_repair_continuation_do).
+ repeat_for_opts(fun t_repair_continuation_do/1).
t_repair_continuation_do(Opts) ->
@@ -564,7 +548,8 @@ default(Config) when is_list(Config) ->
%% Test that select fails even if nothing can match.
select_fail(Config) when is_list(Config) ->
EtsMem = etsmem(),
- repeat_for_opts(select_fail_do, [all_types,write_concurrency]),
+ repeat_for_opts(fun select_fail_do/1,
+ [all_types,write_concurrency]),
verify_etsmem(EtsMem).
select_fail_do(Opts) ->
@@ -590,27 +575,21 @@ 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
-%%
-%% The hardcoded expected memory sizes (in words) are the ones we expect on:
-%% SunOS5.8, 32-bit, non smp, private heap
-%%
%% Whitebox test of ets:info(X, memory).
memory(Config) when is_list(Config) ->
ok = chk_normal_tab_struct_size(),
- repeat_for_opts(memory_do,[compressed]),
+ repeat_for_opts(fun memory_do/1, [compressed]),
catch erts_debug:set_internal_state(available_internal_state, false).
memory_do(Opts) ->
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}
+ {normal,_} -> {13836, 15346, 15346, 15346+6};
+ {compressed,4} -> {11041, 12551, 12551, 12551+1};
+ {compressed,8} -> {10050, 11560, 11560, 11560}
end,
- XRes1 = adjust_xmem(L, XR1),
+ XRes1 = adjust_xmem(L, XR1, 1),
Res1 = {?S(T1),?S(T2),?S(T3),?S(T4)},
lists:foreach(fun(T) ->
Before = ets:info(T,size),
@@ -622,11 +601,11 @@ memory_do(Opts) ->
end,
L),
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}
+ {normal,_} -> {13826, 15337, 15337-9, 15337-3};
+ {compressed,4} -> {11031, 12542, 12542-9, 12542-8};
+ {compressed,8} -> {10040, 11551, 11551-9, 11551-9}
end,
- XRes2 = adjust_xmem(L, XR2),
+ XRes2 = adjust_xmem(L, XR2, 1),
Res2 = {?S(T1),?S(T2),?S(T3),?S(T4)},
lists:foreach(fun(T) ->
Before = ets:info(T,size),
@@ -638,17 +617,17 @@ memory_do(Opts) ->
end,
L),
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}
+ {normal,_} -> {13816, 15328, 15328-18, 15328-12};
+ {compressed,4} -> {11021, 12533, 12533-18, 12533-17};
+ {compressed,8} -> {10030, 11542, 11542-18, 11542-18}
end,
- XRes3 = adjust_xmem(L, XR3),
+ XRes3 = adjust_xmem(L, XR3, 1),
Res3 = {?S(T1),?S(T2),?S(T3),?S(T4)},
lists:foreach(fun(T) ->
ets:delete_all_objects(T)
end,
L),
- XRes4 = adjust_xmem(L, {50,260,260,260}), %{76,286,286,286}),
+ XRes4 = adjust_xmem(L, {50, 256, 256, 256}, 0),
Res4 = {?S(T1),?S(T2),?S(T3),?S(T4)},
lists:foreach(fun(T) ->
ets:delete(T)
@@ -659,7 +638,7 @@ memory_do(Opts) ->
ets:select_delete(T,[{'_',[],[true]}])
end,
L2),
- XRes5 = adjust_xmem(L2, {50,260,260,260}), %{76,286,286,286}),
+ XRes5 = adjust_xmem(L2, {50, 256, 256, 256}, 0),
Res5 = {?S(T11),?S(T12),?S(T13),?S(T14)},
io:format("XRes1 = ~p~n"
" Res1 = ~p~n~n"
@@ -697,25 +676,25 @@ chk_normal_tab_struct_size() ->
erlang:system_info(smp_support),
erlang:system_info(heap_type)},
io:format("System = ~p~n", [System]),
- io:format("?TAB_STRUCT_SZ=~p~n", [?TAB_STRUCT_SZ]),
ok.
-adjust_xmem([_T1,_T2,_T3,_T4], {A0,B0,C0,D0} = _Mem0) ->
+adjust_xmem([_T1,_T2,_T3,_T4], {A0,B0,C0,D0} = _Mem0, EstCnt) ->
%% Adjust for 64-bit, smp, and os:
%% Table struct size may differ.
- TabDiff = ?TAB_STRUCT_SZ,
- {A0+TabDiff, B0+TabDiff, C0+TabDiff, D0+TabDiff}.
+ {TabSz, EstSz} = erts_debug:get_internal_state('DbTable_words'),
+ HTabSz = TabSz + EstCnt*EstSz,
+ {A0+TabSz, B0+HTabSz, C0+HTabSz, D0+HTabSz}.
%% Misc. whitebox tests
t_whitebox(Config) when is_list(Config) ->
EtsMem = etsmem(),
- repeat_for_opts(whitebox_1),
- repeat_for_opts(whitebox_1),
- repeat_for_opts(whitebox_1),
- repeat_for_opts(whitebox_2),
- repeat_for_opts(whitebox_2),
- repeat_for_opts(whitebox_2),
+ repeat_for_opts(fun whitebox_1/1),
+ repeat_for_opts(fun whitebox_1/1),
+ repeat_for_opts(fun whitebox_1/1),
+ repeat_for_opts(fun whitebox_2/1),
+ repeat_for_opts(fun whitebox_2/1),
+ repeat_for_opts(fun whitebox_2/1),
verify_etsmem(EtsMem).
whitebox_1(Opts) ->
@@ -780,7 +759,7 @@ check_badarg({'EXIT', {badarg, [{M,F,A,_} | _]}}, M, F, Args) ->
%% Test ets:delete_all_objects/1.
t_delete_all_objects(Config) when is_list(Config) ->
EtsMem = etsmem(),
- repeat_for_opts(t_delete_all_objects_do),
+ repeat_for_opts(fun t_delete_all_objects_do/1),
verify_etsmem(EtsMem).
get_kept_objects(T) ->
@@ -814,7 +793,7 @@ t_delete_all_objects_do(Opts) ->
%% Test ets:delete_object/2.
t_delete_object(Config) when is_list(Config) ->
EtsMem = etsmem(),
- repeat_for_opts(t_delete_object_do),
+ repeat_for_opts(fun t_delete_object_do/1),
verify_etsmem(EtsMem).
t_delete_object_do(Opts) ->
@@ -887,7 +866,7 @@ make_init_fun(N) ->
%% Test ets:init_table/2.
t_init_table(Config) when is_list(Config)->
EtsMem = etsmem(),
- repeat_for_opts(t_init_table_do),
+ repeat_for_opts(fun t_init_table_do/1),
verify_etsmem(EtsMem).
t_init_table_do(Opts) ->
@@ -963,7 +942,7 @@ t_insert_new(Config) when is_list(Config) ->
%% Test ets:insert/2 with list of objects.
t_insert_list(Config) when is_list(Config) ->
EtsMem = etsmem(),
- repeat_for_opts(t_insert_list_do),
+ repeat_for_opts(fun t_insert_list_do/1),
verify_etsmem(EtsMem).
t_insert_list_do(Opts) ->
@@ -1193,7 +1172,7 @@ partly_bound(Config) when is_list(Config) ->
end.
dont_make_worse() ->
- seventyfive_percent_success({?MODULE,dont_make_worse_sub,[]},0,0,10).
+ seventyfive_percent_success(fun dont_make_worse_sub/0, 0, 0, 10).
dont_make_worse_sub() ->
T = build_table([a,b],[a,b],15000),
@@ -1205,8 +1184,9 @@ dont_make_worse_sub() ->
ok.
make_better() ->
- fifty_percent_success({?MODULE,make_better_sub2,[]},0,0,10),
- fifty_percent_success({?MODULE,make_better_sub1,[]},0,0,10).
+ fifty_percent_success(fun make_better_sub2/0, 0, 0, 10),
+ fifty_percent_success(fun make_better_sub1/0, 0, 0, 10).
+
make_better_sub1() ->
T = build_table2([a,b],[a,b],15000),
T1 = time_match_object(T,{'_',1500,a,a}, [{{1500,a,a},1500,a,a}]),
@@ -1491,7 +1471,7 @@ do_random_test() ->
%% Ttest various variants of update_element.
update_element(Config) when is_list(Config) ->
EtsMem = etsmem(),
- repeat_for_opts(update_element_opts),
+ repeat_for_opts(fun update_element_opts/1),
verify_etsmem(EtsMem).
update_element_opts(Opts) ->
@@ -1653,7 +1633,7 @@ update_element_neg_do(T) ->
%% test various variants of update_counter.
update_counter(Config) when is_list(Config) ->
EtsMem = etsmem(),
- repeat_for_opts(update_counter_do),
+ repeat_for_opts(fun update_counter_do/1),
verify_etsmem(EtsMem).
update_counter_do(Opts) ->
@@ -1874,7 +1854,7 @@ evil_update_counter(Config) when is_list(Config) ->
ordsets:module_info(),
rand:module_info(),
- repeat_for_opts(evil_update_counter_do).
+ repeat_for_opts(fun evil_update_counter_do/1).
evil_update_counter_do(Opts) ->
EtsMem = etsmem(),
@@ -1908,7 +1888,7 @@ evil_counter(I,Opts) ->
end,
Start = Start0 + rand:uniform(100000),
ets:insert(T, {dracula,Start}),
- Iter = 40000,
+ Iter = 40000 div syrup_factor(),
End = Start + Iter,
End = evil_counter_1(Iter, T),
ets:delete(T).
@@ -1921,7 +1901,7 @@ evil_counter_1(Iter, T) ->
evil_counter_1(Iter-1, T).
update_counter_with_default(Config) when is_list(Config) ->
- repeat_for_opts(update_counter_with_default_do).
+ repeat_for_opts(fun update_counter_with_default_do/1).
update_counter_with_default_do(Opts) ->
T1 = ets_new(a, [set | Opts]),
@@ -1959,7 +1939,7 @@ update_counter_with_default_do(Opts) ->
ok.
update_counter_table_growth(_Config) ->
- repeat_for_opts(update_counter_table_growth_do).
+ repeat_for_opts(fun update_counter_table_growth_do/1).
update_counter_table_growth_do(Opts) ->
Set = ets_new(b, [set | Opts]),
@@ -1970,7 +1950,8 @@ update_counter_table_growth_do(Opts) ->
%% Check that a first-next sequence always works on a fixed table.
fixtable_next(Config) when is_list(Config) ->
- repeat_for_opts(fixtable_next_do, [write_concurrency,all_types]).
+ repeat_for_opts(fun fixtable_next_do/1,
+ [write_concurrency,all_types]).
fixtable_next_do(Opts) ->
EtsMem = etsmem(),
@@ -2110,7 +2091,7 @@ write_concurrency(Config) when is_list(Config) ->
%% The 'heir' option.
heir(Config) when is_list(Config) ->
- repeat_for_opts(heir_do).
+ repeat_for_opts(fun heir_do/1).
heir_do(Opts) ->
EtsMem = etsmem(),
@@ -2250,7 +2231,7 @@ heir_1(HeirData,Mode,Opts) ->
%% Test ets:give_way/3.
give_away(Config) when is_list(Config) ->
- repeat_for_opts(give_away_do).
+ repeat_for_opts(fun give_away_do/1).
give_away_do(Opts) ->
T = ets_new(foo,[named_table, private | Opts]),
@@ -2331,7 +2312,7 @@ give_away_receiver(T, Giver) ->
%% Test ets:setopts/2.
setopts(Config) when is_list(Config) ->
- repeat_for_opts(setopts_do,[write_concurrency,all_types]).
+ repeat_for_opts(fun setopts_do/1, [write_concurrency,all_types]).
setopts_do(Opts) ->
Self = self(),
@@ -2481,7 +2462,7 @@ bad_table_call(T,{F,Args,_,{return,Return}}) ->
%% Check rename of ets tables.
rename(Config) when is_list(Config) ->
- repeat_for_opts(rename_do, [write_concurrency, all_types]).
+ repeat_for_opts(fun rename_do/1, [write_concurrency, all_types]).
rename_do(Opts) ->
EtsMem = etsmem(),
@@ -2496,7 +2477,8 @@ rename_do(Opts) ->
%% Check rename of unnamed ets table.
rename_unnamed(Config) when is_list(Config) ->
- repeat_for_opts(rename_unnamed_do,[write_concurrency,all_types]).
+ repeat_for_opts(fun rename_unnamed_do/1,
+ [write_concurrency,all_types]).
rename_unnamed_do(Opts) ->
EtsMem = etsmem(),
@@ -2571,7 +2553,7 @@ evil_create_fixed_tab() ->
%% Tests that the return values and errors are equal for set's and
%% ordered_set's where applicable.
interface_equality(Config) when is_list(Config) ->
- repeat_for_opts(interface_equality_do).
+ repeat_for_opts(fun interface_equality_do/1).
interface_equality_do(Opts) ->
EtsMem = etsmem(),
@@ -2635,7 +2617,7 @@ maybe_sort(Any) ->
%% Test match, match_object and match_delete in ordered set's.
ordered_match(Config) when is_list(Config)->
- repeat_for_opts(ordered_match_do).
+ repeat_for_opts(fun ordered_match_do/1).
ordered_match_do(Opts) ->
EtsMem = etsmem(),
@@ -2681,7 +2663,7 @@ ordered_match_do(Opts) ->
%% Test basic functionality in ordered_set's.
ordered(Config) when is_list(Config) ->
- repeat_for_opts(ordered_do).
+ repeat_for_opts(fun ordered_do/1).
ordered_do(Opts) ->
EtsMem = etsmem(),
@@ -2807,12 +2789,13 @@ keypos2(Config) when is_list(Config) ->
%% Privacy check. Check that a named(public/private/protected) table
%% cannot be read by the wrong process(es).
privacy(Config) when is_list(Config) ->
- repeat_for_opts(privacy_do).
+ repeat_for_opts(fun privacy_do/1).
privacy_do(Opts) ->
EtsMem = etsmem(),
process_flag(trap_exit,true),
- Owner = my_spawn_link(?MODULE,privacy_owner,[self(),Opts]),
+ Parent = self(),
+ Owner = my_spawn_link(fun() -> privacy_owner(Parent, Opts) end),
receive
{'EXIT',Owner,Reason} ->
exit({privacy_test,Reason});
@@ -2892,7 +2875,7 @@ rotate_tuple(Tuple, N) ->
%% Check lookup in an empty table and lookup of a non-existing key.
empty(Config) when is_list(Config) ->
- repeat_for_opts(empty_do).
+ repeat_for_opts(fun empty_do/1).
empty_do(Opts) ->
EtsMem = etsmem(),
@@ -2905,7 +2888,7 @@ empty_do(Opts) ->
%% Check proper return values for illegal insert operations.
badinsert(Config) when is_list(Config) ->
- repeat_for_opts(badinsert_do).
+ repeat_for_opts(fun badinsert_do/1).
badinsert_do(Opts) ->
EtsMem = etsmem(),
@@ -2929,7 +2912,7 @@ badinsert_do(Opts) ->
time_lookup(Config) when is_list(Config) ->
%% just for timing, really
EtsMem = etsmem(),
- Values = repeat_for_opts(time_lookup_do),
+ Values = repeat_for_opts(fun time_lookup_do/1),
verify_etsmem(EtsMem),
{comment,lists:flatten(io_lib:format(
"~p ets lookups/s",[Values]))}.
@@ -2963,7 +2946,8 @@ badlookup(Config) when is_list(Config) ->
%% Test that lookup returns objects in order of insertion for bag and dbag.
lookup_order(Config) when is_list(Config) ->
EtsMem = etsmem(),
- repeat_for_opts(lookup_order_do, [write_concurrency,[bag,duplicate_bag]]),
+ repeat_for_opts(fun lookup_order_do/1,
+ [write_concurrency,[bag,duplicate_bag]]),
verify_etsmem(EtsMem),
ok.
@@ -3054,7 +3038,7 @@ fill_tab(Tab,Val) ->
%% OTP-2386. Multiple return elements.
lookup_element_mult(Config) when is_list(Config) ->
- repeat_for_opts(lookup_element_mult_do).
+ repeat_for_opts(fun lookup_element_mult_do/1).
lookup_element_mult_do(Opts) ->
EtsMem = etsmem(),
@@ -3092,7 +3076,8 @@ lem_crash_3(T) ->
%% Check delete of an element inserted in a `filled' table.
delete_elem(Config) when is_list(Config) ->
- repeat_for_opts(delete_elem_do, [write_concurrency, all_types]).
+ repeat_for_opts(fun delete_elem_do/1,
+ [write_concurrency, all_types]).
delete_elem_do(Opts) ->
EtsMem = etsmem(),
@@ -3109,7 +3094,8 @@ delete_elem_do(Opts) ->
%% Check that ets:delete() works and releases the name of the
%% deleted table.
delete_tab(Config) when is_list(Config) ->
- repeat_for_opts(delete_tab_do,[write_concurrency,all_types]).
+ repeat_for_opts(fun delete_tab_do/1,
+ [write_concurrency,all_types]).
delete_tab_do(Opts) ->
Name = foo,
@@ -3300,23 +3286,29 @@ evil_delete_owner(Name, Flags, Data, Fix) ->
exit_large_table_owner(Config) when is_list(Config) ->
%%Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
- FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok};
+ Laps = 500000 div syrup_factor(),
+ FEData = fun(Do) -> repeat_while(fun(I) when I =:= Laps -> {false,ok};
(I) -> Do({erlang:phash2(I, 16#ffffff),I}),
{true, I+1}
end, 1)
end,
EtsMem = etsmem(),
- repeat_for_opts({exit_large_table_owner_do,{FEData,Config}}),
+ repeat_for_opts(fun(Opts) ->
+ exit_large_table_owner_do(Opts,
+ FEData,
+ Config)
+ end),
verify_etsmem(EtsMem).
-exit_large_table_owner_do(Opts,{FEData,Config}) ->
+exit_large_table_owner_do(Opts, FEData, Config) ->
verify_rescheduling_exit(Config, FEData, [named_table | Opts], true, 1, 1),
verify_rescheduling_exit(Config, FEData, Opts, false, 1, 1).
exit_many_large_table_owner(Config) when is_list(Config) ->
ct:timetrap({minutes,30}), %% valgrind needs a lot
%%Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)],
- FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok};
+ Laps = 500000 div syrup_factor(),
+ FEData = fun(Do) -> repeat_while(fun(I) when I =:= Laps -> {false,ok};
(I) -> Do({erlang:phash2(I, 16#ffffff),I}),
{true, I+1}
end, 1)
@@ -3476,7 +3468,8 @@ baddelete(Config) when is_list(Config) ->
%% Check that match_delete works. Also tests tab2list function.
match_delete(Config) when is_list(Config) ->
EtsMem = etsmem(),
- repeat_for_opts(match_delete_do,[write_concurrency,all_types]),
+ repeat_for_opts(fun match_delete_do/1,
+ [write_concurrency,all_types]),
verify_etsmem(EtsMem).
match_delete_do(Opts) ->
@@ -3493,7 +3486,7 @@ match_delete_do(Opts) ->
%% OTP-3005: check match_delete with constant argument.
match_delete3(Config) when is_list(Config) ->
- repeat_for_opts(match_delete3_do).
+ repeat_for_opts(fun match_delete3_do/1).
match_delete3_do(Opts) ->
EtsMem = etsmem(),
@@ -3518,7 +3511,7 @@ match_delete3_do(Opts) ->
%% Test ets:first/1 & ets:next/2.
firstnext(Config) when is_list(Config) ->
- repeat_for_opts(firstnext_do).
+ repeat_for_opts(fun firstnext_do/1).
firstnext_do(Opts) ->
EtsMem = etsmem(),
@@ -3576,7 +3569,7 @@ dyn_lookup(T, K) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
slot(Config) when is_list(Config) ->
- repeat_for_opts(slot_do).
+ repeat_for_opts(fun slot_do/1).
slot_do(Opts) ->
EtsMem = etsmem(),
@@ -3601,7 +3594,7 @@ slot_loop(Tab,SlotNo,EltsSoFar) ->
match1(Config) when is_list(Config) ->
- repeat_for_opts(match1_do).
+ repeat_for_opts(fun match1_do/1).
match1_do(Opts) ->
EtsMem = etsmem(),
@@ -3637,7 +3630,7 @@ match1_do(Opts) ->
%% Test match with specified keypos bag table.
match2(Config) when is_list(Config) ->
- repeat_for_opts(match2_do).
+ repeat_for_opts(fun match2_do/1).
match2_do(Opts) ->
EtsMem = etsmem(),
@@ -3664,7 +3657,7 @@ match2_do(Opts) ->
%% Some ets:match_object tests.
match_object(Config) when is_list(Config) ->
- repeat_for_opts(match_object_do).
+ repeat_for_opts(fun match_object_do/1).
match_object_do(Opts) ->
EtsMem = etsmem(),
@@ -3764,7 +3757,7 @@ match_object_do(Opts) ->
%% Tests that db_match_object does not generate a `badarg' when
%% resuming a search with no previous matches.
match_object2(Config) when is_list(Config) ->
- repeat_for_opts(match_object2_do).
+ repeat_for_opts(fun match_object2_do/1).
match_object2_do(Opts) ->
EtsMem = etsmem(),
@@ -3800,7 +3793,7 @@ tab2list(Config) when is_list(Config) ->
%% Simple general small test. If this fails, ets is in really bad
%% shape.
misc1(Config) when is_list(Config) ->
- repeat_for_opts(misc1_do).
+ repeat_for_opts(fun misc1_do/1).
misc1_do(Opts) ->
EtsMem = etsmem(),
@@ -3818,7 +3811,7 @@ misc1_do(Opts) ->
%% Check the safe_fixtable function.
safe_fixtable(Config) when is_list(Config) ->
- repeat_for_opts(safe_fixtable_do).
+ repeat_for_opts(fun safe_fixtable_do/1).
safe_fixtable_do(Opts) ->
EtsMem = etsmem(),
@@ -3876,7 +3869,7 @@ safe_fixtable_do(Opts) ->
%% Tests ets:info result for required tuples.
info(Config) when is_list(Config) ->
- repeat_for_opts(info_do).
+ repeat_for_opts(fun info_do/1).
info_do(Opts) ->
EtsMem = etsmem(),
@@ -3908,7 +3901,7 @@ info_do(Opts) ->
%% Test various duplicate_bags stuff.
dups(Config) when is_list(Config) ->
- repeat_for_opts(dups_do).
+ repeat_for_opts(fun dups_do/1).
dups_do(Opts) ->
EtsMem = etsmem(),
@@ -3974,7 +3967,9 @@ tab2file_do(FName, Opts) ->
%% Check the ets:tab2file function on a filled set/bag type ets table.
tab2file2(Config) when is_list(Config) ->
- repeat_for_opts({tab2file2_do,Config}, [[set,bag],compressed]).
+ repeat_for_opts(fun(Opts) ->
+ tab2file2_do(Opts, Config)
+ end, [[set,bag],compressed]).
tab2file2_do(Opts, Config) ->
EtsMem = etsmem(),
@@ -4238,7 +4233,7 @@ make_sub_binary(List, Num) when is_list(List) ->
%% Perform multiple lookups for every key in a large table.
heavy_lookup(Config) when is_list(Config) ->
- repeat_for_opts(heavy_lookup_do).
+ repeat_for_opts(fun heavy_lookup_do/1).
heavy_lookup_do(Opts) ->
EtsMem = etsmem(),
@@ -4261,14 +4256,15 @@ do_lookup(Tab, N) ->
%% Perform multiple lookups for every element in a large table.
heavy_lookup_element(Config) when is_list(Config) ->
- repeat_for_opts(heavy_lookup_element_do).
+ repeat_for_opts(fun heavy_lookup_element_do/1).
heavy_lookup_element_do(Opts) ->
EtsMem = etsmem(),
Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]),
ok = fill_tab2(Tab, 0, 7000),
%% lookup ALL elements 50 times
- _ = [do_lookup_element(Tab, 6999, 1) || _ <- lists:seq(1, 50)],
+ Laps = 50 div syrup_factor(),
+ _ = [do_lookup_element(Tab, 6999, 1) || _ <- lists:seq(1, Laps)],
true = ets:delete(Tab),
verify_etsmem(EtsMem).
@@ -4288,10 +4284,11 @@ do_lookup_element(Tab, N, M) ->
heavy_concurrent(Config) when is_list(Config) ->
ct:timetrap({minutes,30}), %% valgrind needs a lot of time
- repeat_for_opts(do_heavy_concurrent).
+ repeat_for_opts(fun do_heavy_concurrent/1).
do_heavy_concurrent(Opts) ->
Size = 10000,
+ Laps = 10000 div syrup_factor(),
EtsMem = etsmem(),
Tab = ets_new(blupp, [set, public, {keypos, 2} | Opts]),
ok = fill_tab2(Tab, 0, Size),
@@ -4299,7 +4296,7 @@ do_heavy_concurrent(Opts) ->
fun (N) ->
my_spawn_link(
fun () ->
- do_heavy_concurrent_proc(Tab, Size, N)
+ do_heavy_concurrent_proc(Tab, Laps, N)
end)
end,
lists:seq(1, 500)),
@@ -4372,7 +4369,7 @@ foldr_ordered(Config) when is_list(Config) ->
%% Test ets:member BIF.
member(Config) when is_list(Config) ->
- repeat_for_opts(member_do, [write_concurrency, all_types]).
+ repeat_for_opts(fun member_do/1, [write_concurrency, all_types]).
member_do(Opts) ->
EtsMem = etsmem(),
@@ -4441,40 +4438,40 @@ build_table2(L1,L2,Num) ->
T.
time_match_object(Tab,Match, Res) ->
- T1 = erlang:monotonic_time(micro_seconds),
+ T1 = erlang:monotonic_time(microsecond),
Res = ets:match_object(Tab,Match),
- T2 = erlang:monotonic_time(micro_seconds),
+ T2 = erlang:monotonic_time(microsecond),
T2 - T1.
time_match(Tab,Match) ->
- T1 = erlang:monotonic_time(micro_seconds),
+ T1 = erlang:monotonic_time(microsecond),
ets:match(Tab,Match),
- T2 = erlang:monotonic_time(micro_seconds),
+ T2 = erlang:monotonic_time(microsecond),
T2 - T1.
seventyfive_percent_success(_,S,Fa,0) ->
true = (S > ((S + Fa) * 0.75));
-seventyfive_percent_success({M,F,A},S,Fa,N) ->
- case (catch apply(M,F,A)) of
- {'EXIT', _} ->
- seventyfive_percent_success({M,F,A},S,Fa+1,N-1);
- _ ->
- seventyfive_percent_success({M,F,A},S+1,Fa,N-1)
+seventyfive_percent_success(F, S, Fa, N) when is_function(F, 0) ->
+ try F() of
+ _ ->
+ seventyfive_percent_success(F, S+1, Fa, N-1)
+ catch error:_ ->
+ seventyfive_percent_success(F, S, Fa+1, N-1)
end.
fifty_percent_success(_,S,Fa,0) ->
true = (S > ((S + Fa) * 0.5));
-fifty_percent_success({M,F,A},S,Fa,N) ->
- case (catch apply(M,F,A)) of
- {'EXIT', _} ->
- fifty_percent_success({M,F,A},S,Fa+1,N-1);
- _ ->
- fifty_percent_success({M,F,A},S+1,Fa,N-1)
+fifty_percent_success(F, S, Fa, N) when is_function(F, 0) ->
+ try F() of
+ _ ->
+ fifty_percent_success(F, S+1, Fa, N-1)
+ catch
+ error:_ ->
+ fifty_percent_success(F, S, Fa+1, N-1)
end.
-
create_random_string(0) ->
[];
@@ -4813,7 +4810,7 @@ otp_6338(Config) when is_list(Config) ->
%% Elements could come in the wrong order in a bag if a rehash occurred.
otp_5340(Config) when is_list(Config) ->
- repeat_for_opts(otp_5340_do).
+ repeat_for_opts(fun otp_5340_do/1).
otp_5340_do(Opts) ->
N = 3000,
@@ -4849,7 +4846,7 @@ verify2(_Err, _) ->
%% delete_object followed by delete on fixed bag failed to delete objects.
otp_7665(Config) when is_list(Config) ->
- repeat_for_opts(otp_7665_do).
+ repeat_for_opts(fun otp_7665_do/1).
otp_7665_do(Opts) ->
Tab = ets_new(otp_7665,[bag | Opts]),
@@ -4879,7 +4876,7 @@ otp_7665_act(Tab,Min,Max,DelNr) ->
%% Whitebox testing of meta name table hashing.
meta_wb(Config) when is_list(Config) ->
EtsMem = etsmem(),
- repeat_for_opts(meta_wb_do),
+ repeat_for_opts(fun meta_wb_do/1),
verify_etsmem(EtsMem).
@@ -5359,12 +5356,12 @@ verify_table_load(T) ->
Stats = ets:info(T,stats),
{Buckets,AvgLen,StdDev,ExpSD,_MinLen,_MaxLen,_} = Stats,
ok = if
- AvgLen > 7 ->
+ AvgLen > 1.2 ->
io:format("Table overloaded: Stats=~p\n~p\n",
[Stats, ets:info(T)]),
false;
- Buckets>256, AvgLen < 6 ->
+ Buckets>256, AvgLen < 0.47 ->
io:format("Table underloaded: Stats=~p\n~p\n",
[Stats, ets:info(T)]),
false;
@@ -5438,7 +5435,8 @@ smp_select_delete(Config) when is_list(Config) ->
Eq+1
end,
0, TotCnts),
- verify_table_load(T),
+ %% May fail as select_delete does not shrink table (enough)
+ %%verify_table_load(T),
LeftInTab = ets:select_delete(T, [{{'$1','$1'}, [], [true]}]),
0 = ets:info(T,size),
false = ets:info(T,fixed),
@@ -5447,7 +5445,7 @@ smp_select_delete(Config) when is_list(Config) ->
%% Test different types.
types(Config) when is_list(Config) ->
init_externals(),
- repeat_for_opts(types_do,[[set,ordered_set],compressed]).
+ repeat_for_opts(fun types_do/1, [[set,ordered_set],compressed]).
types_do(Opts) ->
EtsMem = etsmem(),
@@ -5714,27 +5712,45 @@ etsmem() ->
{Bl0+Bl,BlSz0+BlSz}
end, {0,0}, CS)
end},
- {Mem,AllTabs}.
+ {Mem,AllTabs, erts_debug:get_internal_state('DbTable_meta')}.
-verify_etsmem({MemInfo,AllTabs}) ->
+verify_etsmem(EtsMem) ->
wait_for_test_procs(),
+ verify_etsmem(EtsMem, false).
+
+verify_etsmem({MemInfo,AllTabs,MetaState}=EtsMem, Adjusted) ->
case etsmem() of
- {MemInfo,_} ->
+ {MemInfo,_,_} ->
io:format("Ets mem info: ~p", [MemInfo]),
case MemInfo of
{ErlMem,EtsAlloc} when ErlMem == notsup; EtsAlloc == undefined ->
%% Use 'erl +Mea max' to do more complete memory leak testing.
{comment,"Incomplete or no mem leak testing"};
_ ->
- ok
+ case Adjusted of
+ true ->
+ {comment, "Meta state adjusted"};
+ false ->
+ ok
+ end
end;
- {MemInfo2, AllTabs2} ->
+
+ {MemInfo2, AllTabs2, MetaState2} ->
io:format("Expected: ~p", [MemInfo]),
io:format("Actual: ~p", [MemInfo2]),
io:format("Changed tables before: ~p\n",[AllTabs -- AllTabs2]),
io:format("Changed tables after: ~p\n", [AllTabs2 -- AllTabs]),
- ets_test_spawn_logger ! {failed_memcheck, get('__ETS_TEST_CASE__')},
- {comment, "Failed memory check"}
+ io:format("Meta state before: ~p\n", [MetaState]),
+ io:format("Meta state after: ~p\n", [MetaState2]),
+ case {MetaState =:= MetaState2, Adjusted} of
+ {false, false} ->
+ io:format("Adjust meta state and retry...\n\n",[]),
+ {ok,ok} = erts_debug:set_internal_state('DbTable_meta', MetaState),
+ verify_etsmem(EtsMem, true);
+ _ ->
+ ets_test_spawn_logger ! {failed_memcheck, get('__ETS_TEST_CASE__')},
+ {comment, "Failed memory check"}
+ end
end.
@@ -5831,12 +5847,8 @@ log_test_proc(Proc) when is_pid(Proc) ->
Proc.
my_spawn(Fun) -> log_test_proc(spawn(Fun)).
-%%my_spawn(M,F,A) -> log_test_proc(spawn(M,F,A)).
-%%my_spawn(N,M,F,A) -> log_test_proc(spawn(N,M,F,A)).
my_spawn_link(Fun) -> log_test_proc(spawn_link(Fun)).
-my_spawn_link(M,F,A) -> log_test_proc(spawn_link(M,F,A)).
-%%my_spawn_link(N,M,F,A) -> log_test_proc(spawn_link(N,M,F,A)).
my_spawn_opt(Fun,Opts) ->
case spawn_opt(Fun,Opts) of
@@ -6079,7 +6091,7 @@ make_port() ->
open_port({spawn, "efile"}, [eof]).
make_pid() ->
- spawn_link(?MODULE, sleeper, []).
+ spawn_link(fun sleeper/0).
sleeper() ->
receive after infinity -> ok end.
@@ -6215,11 +6227,7 @@ make_unaligned_sub_binary(List) ->
repeat_for_opts(F) ->
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) when is_function(F, 1) ->
repeat_for_opts(F, OptGenList, []).
repeat_for_opts(F, [], Acc) ->
@@ -6255,5 +6263,11 @@ do_tc(Do, Report) ->
T1 = erlang:monotonic_time(),
Do(),
T2 = erlang:monotonic_time(),
- Elapsed = erlang:convert_time_unit(T2 - T1, native, milli_seconds),
+ Elapsed = erlang:convert_time_unit(T2 - T1, native, millisecond),
Report(Elapsed).
+
+syrup_factor() ->
+ case erlang:system_info(build_type) of
+ valgrind -> 20;
+ _ -> 1
+ end.
diff --git a/lib/stdlib/test/ets_tough_SUITE.erl b/lib/stdlib/test/ets_tough_SUITE.erl
index 49aba7a529..0abce3200f 100644
--- a/lib/stdlib/test/ets_tough_SUITE.erl
+++ b/lib/stdlib/test/ets_tough_SUITE.erl
@@ -19,10 +19,15 @@
%%
-module(ets_tough_SUITE).
-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]).
+ init_per_group/2,end_per_group/2,
+ ex1/1]).
-export([init_per_testcase/2, end_per_testcase/2]).
--compile([export_all]).
+
+%% gen_server behavior.
+-behavior(gen_server).
+-export([init/1,terminate/2,handle_call/3,handle_cast/2,
+ handle_info/2,code_change/3]).
+
-include_lib("common_test/include/ct.hrl").
suite() ->
@@ -235,33 +240,6 @@ random_element(T) ->
I = rand:uniform(tuple_size(T)),
element(I,T).
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-
-show_table(N) ->
- FileName = ["etsdump.",integer_to_list(N)],
- case file:open(FileName,read) of
- {ok,Fd} ->
- show_entries(Fd);
- _ ->
- error
- end.
-
-show_entries(Fd) ->
- case phys_read_len(Fd) of
- {ok,Len} ->
- case phys_read_entry(Fd,Len) of
- {ok,ok} ->
- ok;
- {ok,{Key,Val}} ->
- io:format("~w\n",[{Key,Val}]),
- show_entries(Fd);
- _ ->
- error
- end;
- _ ->
- error
- end.
-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -378,20 +356,6 @@ dget_class(ServerPid,Class,Condition) ->
derase_class(ServerPid,Class) ->
gen_server:call(ServerPid,{handle_delete_class,Class}, infinity).
-%%% dmodify(ServerPid,Application) -> ok
-%%%
-%%% Applies a function on every instance in the database.
-%%% The user provided function must always return one of the
-%%% terms {ok,NewItem}, true, or false.
-%%% Aug 96, this is only used to reset all timestamp values
-%%% in the database.
-%%% The function is supplied as Application = {Mod, Fun, ExtraArgs},
-%%% where the instance will be prepended to ExtraArgs before each
-%%% call is made.
-
-dmodify(ServerPid,Application) ->
- gen_server:call(ServerPid,{handle_dmodify,Application}, infinity).
-
%%% ddump_first(ServerPid,DumpDir) -> {dump_more,Ticket} | already_dumping
%%%
%%% Starts dumping the database. This call redirects all database updates
@@ -643,9 +607,15 @@ handle_call(stop,_From,Admin) ->
?ets_delete(Admin), % Make sure table is gone before reply is sent.
{stop, normal, ok, []}.
+handle_cast(_Req, Admin) ->
+ {noreply, Admin}.
+
handle_info({'EXIT',_Pid,_Reason},Admin) ->
{stop,normal,Admin}.
+code_change(_OldVsn, StateData, _Extra) ->
+ {ok, StateData}.
+
handle_delete(Class, Key, Admin) ->
handle_call({handle_delete,Class,Key},from,Admin).
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index 4f8936edbf..87fba815d2 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -25,7 +25,8 @@
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,ensure_dir_symlink/1,
- wildcard_symlink/1, is_file_symlink/1, file_props_symlink/1]).
+ wildcard_symlink/1, is_file_symlink/1, file_props_symlink/1,
+ find_source/1]).
-import(lists, [foreach/2]).
@@ -45,7 +46,8 @@ suite() ->
all() ->
[wildcard_one, wildcard_two, wildcard_errors,
fold_files, otp_5960, ensure_dir_eexist, ensure_dir_symlink,
- wildcard_symlink, is_file_symlink, file_props_symlink].
+ wildcard_symlink, is_file_symlink, file_props_symlink,
+ find_source].
groups() ->
[].
@@ -503,3 +505,52 @@ file_props_symlink(Config) ->
FileSize = filelib:file_size(Alias, erl_prim_loader),
FileSize = filelib:file_size(Alias, prim_file)
end.
+
+find_source(Config) when is_list(Config) ->
+ BeamFile = code:which(lists),
+ BeamName = filename:basename(BeamFile),
+ BeamDir = filename:dirname(BeamFile),
+ SrcName = filename:basename(BeamFile, ".beam") ++ ".erl",
+
+ {ok, BeamFile} = filelib:find_file(BeamName, BeamDir),
+ {ok, BeamFile} = filelib:find_file(BeamName, BeamDir, []),
+ {ok, BeamFile} = filelib:find_file(BeamName, BeamDir, [{"",""},{"ebin","src"}]),
+ {error, not_found} = filelib:find_file(BeamName, BeamDir, [{"ebin","src"}]),
+
+ {ok, SrcFile} = filelib:find_file(SrcName, BeamDir),
+ {ok, SrcFile} = filelib:find_file(SrcName, BeamDir, []),
+ {ok, SrcFile} = filelib:find_file(SrcName, BeamDir, [{"foo","bar"},{"ebin","src"}]),
+ {error, not_found} = filelib:find_file(SrcName, BeamDir, [{"",""}]),
+
+ {ok, SrcFile} = filelib:find_source(BeamFile),
+ {ok, SrcFile} = filelib:find_source(BeamName, BeamDir),
+ {ok, SrcFile} = filelib:find_source(BeamName, BeamDir,
+ [{".erl",".yrl",[{"",""}]},
+ {".beam",".erl",[{"ebin","src"}]}]),
+ {error, not_found} = filelib:find_source(BeamName, BeamDir,
+ [{".erl",".yrl",[{"",""}]}]),
+
+ {ok, ParserErl} = filelib:find_source(code:which(erl_parse)),
+ {ok, ParserYrl} = filelib:find_source(ParserErl),
+ "lry." ++ _ = lists:reverse(ParserYrl),
+ {ok, ParserYrl} = filelib:find_source(ParserErl,
+ [{".beam",".erl",[{"ebin","src"}]},
+ {".erl",".yrl",[{"",""}]}]),
+
+ %% find_source automatically checks the local directory regardless of rules
+ {ok, ParserYrl} = filelib:find_source(ParserErl),
+ {ok, ParserYrl} = filelib:find_source(ParserErl,
+ [{".beam",".erl",[{"ebin","src"}]}]),
+
+ %% find_file does not check the local directory unless in the rules
+ ParserYrlName = filename:basename(ParserYrl),
+ ParserYrlDir = filename:dirname(ParserYrl),
+ {ok, ParserYrl} = filelib:find_file(ParserYrlName, ParserYrlDir,
+ [{"",""}]),
+ {error, not_found} = filelib:find_file(ParserYrlName, ParserYrlDir,
+ [{"ebin","src"}]),
+
+ %% local directory is in the default list for find_file
+ {ok, ParserYrl} = filelib:find_file(ParserYrlName, ParserYrlDir),
+ {ok, ParserYrl} = filelib:find_file(ParserYrlName, ParserYrlDir, []),
+ ok.
diff --git a/lib/stdlib/test/filename_SUITE.erl b/lib/stdlib/test/filename_SUITE.erl
index d48b75fde8..dc3daa56c1 100644
--- a/lib/stdlib/test/filename_SUITE.erl
+++ b/lib/stdlib/test/filename_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1997-2017. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2016. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -423,8 +423,10 @@ t_nativename(Config) when is_list(Config) ->
find_src(Config) when is_list(Config) ->
{Source,_} = filename:find_src(file),
["file"|_] = lists:reverse(filename:split(Source)),
- {_,_} = filename:find_src(init, [{".","."}, {"ebin","src"}]),
-
+ {Source,_} = filename:find_src(file, [{"",""}, {"ebin","src"}]),
+ {Source,_} = filename:find_src(Source),
+ {Source,_} = filename:find_src(Source ++ ".erl"),
+
%% Try to find the source for a preloaded module.
{error,{preloaded,init}} = filename:find_src(init),
diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl
index 4415c2d09d..9a7400c84e 100644
--- a/lib/stdlib/test/gen_event_SUITE.erl
+++ b/lib/stdlib/test/gen_event_SUITE.erl
@@ -21,22 +21,24 @@
-include_lib("common_test/include/ct.hrl").
--export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/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,
call_format_status/1, call_format_status_anon/1,
- error_format_status/1, get_state/1, replace_state/1]).
+ error_format_status/1, get_state/1, replace_state/1,
+ start_opt/1]).
suite() -> [{ct_hooks,[ts_install_cth]}].
-all() ->
+all() ->
[start, {group, test_all}, hibernate,
call_format_status, call_format_status_anon, error_format_status,
- get_state, replace_state].
+ get_state, replace_state,
+ start_opt].
-groups() ->
+groups() ->
[{test_all, [],
[add_handler, add_sup_handler, delete_handler,
swap_handler, swap_sup_handler, notify, sync_notify,
@@ -59,6 +61,9 @@ end_per_group(_GroupName, Config) ->
%% Start an event manager.
%% --------------------------------------
+-define(LMGR, {local, my_dummy_name}).
+-define(GMGR, {global, my_dummy_name}).
+
start(Config) when is_list(Config) ->
OldFl = process_flag(trap_exit, true),
@@ -72,40 +77,36 @@ start(Config) when is_list(Config) ->
[] = gen_event:which_handlers(Pid1),
ok = gen_event:stop(Pid1),
- {ok, Pid2} = gen_event:start({local, my_dummy_name}),
+ {ok, Pid2} = gen_event:start(?LMGR),
[] = gen_event:which_handlers(my_dummy_name),
[] = gen_event:which_handlers(Pid2),
ok = gen_event:stop(my_dummy_name),
- {ok, Pid3} = gen_event:start_link({local, my_dummy_name}),
+ {ok, Pid3} = gen_event:start_link(?LMGR),
[] = gen_event:which_handlers(my_dummy_name),
[] = gen_event:which_handlers(Pid3),
ok = gen_event:stop(my_dummy_name),
- {ok, Pid4} = gen_event:start_link({global, my_dummy_name}),
- [] = gen_event:which_handlers({global, my_dummy_name}),
+ {ok, Pid4} = gen_event:start_link(?GMGR),
+ [] = gen_event:which_handlers(?GMGR),
[] = gen_event:which_handlers(Pid4),
- ok = gen_event:stop({global, my_dummy_name}),
+ ok = gen_event:stop(?GMGR),
{ok, Pid5} = gen_event:start_link({via, dummy_via, my_dummy_name}),
[] = gen_event:which_handlers({via, dummy_via, my_dummy_name}),
[] = gen_event:which_handlers(Pid5),
ok = gen_event:stop({via, dummy_via, my_dummy_name}),
- {ok, _} = gen_event:start_link({local, my_dummy_name}),
- {error, {already_started, _}} =
- gen_event:start_link({local, my_dummy_name}),
- {error, {already_started, _}} =
- gen_event:start({local, my_dummy_name}),
+ {ok, _} = gen_event:start_link(?LMGR),
+ {error, {already_started, _}} = gen_event:start_link(?LMGR),
+ {error, {already_started, _}} = gen_event:start(?LMGR),
ok = gen_event:stop(my_dummy_name),
- {ok, Pid6} = gen_event:start_link({global, my_dummy_name}),
- {error, {already_started, _}} =
- gen_event:start_link({global, my_dummy_name}),
- {error, {already_started, _}} =
- gen_event:start({global, my_dummy_name}),
+ {ok, Pid6} = gen_event:start_link(?GMGR),
+ {error, {already_started, _}} = gen_event:start_link(?GMGR),
+ {error, {already_started, _}} = gen_event:start(?GMGR),
- ok = gen_event:stop({global, my_dummy_name}, shutdown, 10000),
+ ok = gen_event:stop(?GMGR, shutdown, 10000),
receive
{'EXIT', Pid6, shutdown} -> ok
after 10000 ->
@@ -113,10 +114,8 @@ start(Config) when is_list(Config) ->
end,
{ok, Pid7} = gen_event:start_link({via, dummy_via, my_dummy_name}),
- {error, {already_started, _}} =
- gen_event:start_link({via, dummy_via, my_dummy_name}),
- {error, {already_started, _}} =
- gen_event:start({via, dummy_via, my_dummy_name}),
+ {error, {already_started, _}} = gen_event:start_link({via, dummy_via, my_dummy_name}),
+ {error, {already_started, _}} = gen_event:start({via, dummy_via, my_dummy_name}),
exit(Pid7, shutdown),
receive
@@ -128,6 +127,83 @@ start(Config) when is_list(Config) ->
process_flag(trap_exit, OldFl),
ok.
+start_opt(Config) when is_list(Config) ->
+ OldFl = process_flag(trap_exit, true),
+
+ dummy_via:reset(),
+
+ {ok, Pid0} = gen_event:start([]), %anonymous
+ [] = gen_event:which_handlers(Pid0),
+ ok = gen_event:stop(Pid0),
+
+ {ok, Pid1} = gen_event:start_link([]), %anonymous
+ [] = gen_event:which_handlers(Pid1),
+ ok = gen_event:stop(Pid1),
+
+ {ok, Pid2} = gen_event:start(?LMGR, []),
+ [] = gen_event:which_handlers(my_dummy_name),
+ [] = gen_event:which_handlers(Pid2),
+ ok = gen_event:stop(my_dummy_name),
+
+ {ok, Pid3} = gen_event:start_link(?LMGR, []),
+ [] = gen_event:which_handlers(my_dummy_name),
+ [] = gen_event:which_handlers(Pid3),
+ ok = gen_event:stop(my_dummy_name),
+
+ {ok, Pid4} = gen_event:start_link(?GMGR, []),
+ [] = gen_event:which_handlers(?GMGR),
+ [] = gen_event:which_handlers(Pid4),
+ ok = gen_event:stop(?GMGR),
+
+ {ok, Pid5} = gen_event:start_link({via, dummy_via, my_dummy_name}, []),
+ [] = gen_event:which_handlers({via, dummy_via, my_dummy_name}),
+ [] = gen_event:which_handlers(Pid5),
+ ok = gen_event:stop({via, dummy_via, my_dummy_name}),
+
+ {ok, _} = gen_event:start_link(?LMGR, []),
+ {error, {already_started, _}} = gen_event:start_link(?LMGR, []),
+ {error, {already_started, _}} = gen_event:start(?LMGR, []),
+ ok = gen_event:stop(my_dummy_name),
+
+ {ok, Pid7} = gen_event:start_link(?GMGR),
+ {error, {already_started, _}} = gen_event:start_link(?GMGR, []),
+ {error, {already_started, _}} = gen_event:start(?GMGR, []),
+
+ ok = gen_event:stop(?GMGR, shutdown, 10000),
+ receive
+ {'EXIT', Pid7, shutdown} -> ok
+ after 10000 ->
+ ct:fail(exit_gen_event)
+ end,
+
+ {ok, Pid8} = gen_event:start_link({via, dummy_via, my_dummy_name}),
+ {error, {already_started, _}} = gen_event:start_link({via, dummy_via, my_dummy_name}, []),
+ {error, {already_started, _}} = gen_event:start({via, dummy_via, my_dummy_name}, []),
+
+ exit(Pid8, shutdown),
+ receive
+ {'EXIT', Pid8, shutdown} -> ok
+ after 10000 ->
+ ct:fail(exit_gen_event)
+ end,
+
+ %% test spawn_opt
+ MinHeapSz = 10000,
+ {ok, Pid9} = gen_event:start_link(?LMGR, [{spawn_opt, [{min_heap_size, MinHeapSz}]}]),
+ {error, {already_started, _}} = gen_event:start_link(?LMGR, []),
+ {error, {already_started, _}} = gen_event:start(?LMGR, []),
+ {heap_size, HeapSz} = erlang:process_info(Pid9, heap_size),
+ true = HeapSz > MinHeapSz,
+ ok = gen_event:stop(my_dummy_name),
+
+ %% test debug opt
+ {ok, _} = gen_event:start_link(?LMGR, [{debug,[debug]}]),
+ {error, {already_started, _}} = gen_event:start_link(?LMGR, []),
+ {error, {already_started, _}} = gen_event:start(?LMGR, []),
+ ok = gen_event:stop(my_dummy_name),
+
+ process_flag(trap_exit, OldFl),
+ ok.
hibernate(Config) when is_list(Config) ->
{ok,Pid} = gen_event:start({local, my_dummy_handler}),
diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl
index 338cd3dc0a..6888cb8c58 100644
--- a/lib/stdlib/test/gen_server_SUITE.erl
+++ b/lib/stdlib/test/gen_server_SUITE.erl
@@ -375,12 +375,14 @@ crash(Config) when is_list(Config) ->
%% from gen_server.
{ok,Pid4} = gen_server:start(?MODULE, {state,state4}, []),
{'EXIT',{crashed,_}} = (catch gen_server:call(Pid4, crash)),
+ ClientPid = self(),
receive
{error,_GroupLeader4,{Pid4,
"** Generic server"++_,
[Pid4,crash,{formatted, state4},
{crashed,[{?MODULE,handle_call,3,_}
- |_Stacktrace]}]}} ->
+ |_Stacktrace]},
+ ClientPid, [_|_] = _ClientStack]}} ->
ok;
Other4a ->
io:format("Unexpected: ~p", [Other4a]),
@@ -1115,12 +1117,14 @@ error_format_status(Config) when is_list(Config) ->
{'EXIT', Pid, crashed} ->
ok
end,
+ ClientPid = self(),
receive
{error,_GroupLeader,{Pid,
"** Generic server"++_,
[Pid,crash,{formatted, State},
{crashed,[{?MODULE,handle_call,3,_}
- |_Stacktrace]}]}} ->
+ |_Stacktrace]},
+ ClientPid, [_|_] = _ClientStack]}} ->
ok;
Other ->
io:format("Unexpected: ~p", [Other]),
@@ -1138,12 +1142,14 @@ terminate_crash_format(Config) when is_list(Config) ->
{ok, Pid} = gen_server:start_link(?MODULE, {state, State}, []),
gen_server:call(Pid, stop),
receive {'EXIT', Pid, {crash, terminate}} -> ok end,
+ ClientPid = self(),
receive
{error,_GroupLeader,{Pid,
"** Generic server"++_,
[Pid,stop, {formatted, State},
- {{crash, terminate},[{?MODULE,terminate,2,_}
- |_Stacktrace]}]}} ->
+ {{crash, terminate},
+ [{?MODULE,terminate,2,_}|_Stacktrace]},
+ ClientPid, [_|_] = _ClientStack]}} ->
ok;
Other ->
io:format("Unexpected: ~p", [Other]),
diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl
index 99ac0c3951..ac27c9fc79 100644
--- a/lib/stdlib/test/gen_statem_SUITE.erl
+++ b/lib/stdlib/test/gen_statem_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2016-2017. All Rights Reserved.
+%% Copyright Ericsson AB 2016. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -505,10 +505,10 @@ abnormal2(Config) ->
{ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []),
%% bad return value in the gen_statem loop
- {{bad_return_from_state_function,badreturn},_} =
+ {{{bad_return_from_state_function,badreturn},_},_} =
?EXPECT_FAILURE(gen_statem:call(Pid, badreturn), Reason),
receive
- {'EXIT',Pid,{bad_return_from_state_function,badreturn}} -> ok
+ {'EXIT',Pid,{{bad_return_from_state_function,badreturn},_}} -> ok
after 5000 ->
ct:fail(gen_statem_did_not_die)
end,
@@ -984,7 +984,7 @@ error_format_status(Config) ->
gen_statem:start(
?MODULE, start_arg(Config, {data,Data}), []),
%% bad return value in the gen_statem loop
- {{bad_return_from_state_function,badreturn},_} =
+ {{{bad_return_from_state_function,badreturn},_},_} =
?EXPECT_FAILURE(gen_statem:call(Pid, badreturn), Reason),
receive
{error,_,
diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl
index 6e99619324..d546e8fad2 100644
--- a/lib/stdlib/test/io_SUITE.erl
+++ b/lib/stdlib/test/io_SUITE.erl
@@ -30,7 +30,7 @@
io_lib_print_binary_depth_one/1, otp_10302/1, otp_10755/1,
otp_10836/1, io_lib_width_too_small/1,
io_with_huge_message_queue/1, format_string/1,
- maps/1, coverage/1, otp_14175/1]).
+ maps/1, coverage/1, otp_14178_unicode_atoms/1, otp_14175/1]).
-export([pretty/2]).
@@ -61,7 +61,7 @@ all() ->
printable_range, bad_printable_range,
io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836,
io_lib_width_too_small, io_with_huge_message_queue,
- format_string, maps, coverage, otp_14175].
+ format_string, maps, coverage, otp_14178_unicode_atoms, otp_14175].
%% Error cases for output.
error_1(Config) when is_list(Config) ->
@@ -2107,6 +2107,27 @@ coverage(_Config) ->
ok.
+%% Test UTF-8 atoms.
+otp_14178_unicode_atoms(_Config) ->
+ "atom" = fmt("~ts", ['atom']),
+ "кирилли́ческий атом" = fmt("~ts", ['кирилли́ческий атом']),
+ [16#10FFFF] = fmt("~ts", ['\x{10FFFF}']),
+
+ %% ~s must not accept code points greater than 255.
+ bad_io_lib_format("~s", ['\x{100}']),
+ bad_io_lib_format("~s", ['кирилли́ческий атом']),
+
+ ok.
+
+bad_io_lib_format(F, S) ->
+ try io_lib:format(F, S) of
+ _ ->
+ ct:fail({should_fail,F,S})
+ catch
+ error:badarg ->
+ ok
+ end.
+
otp_14175(_Config) ->
"..." = p(#{}, 0),
"#{}" = p(#{}, 1),
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index 1e286a9306..db321d7490 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -1715,7 +1715,7 @@ toerl_loop(Port,Acc) ->
end.
millistamp() ->
- erlang:monotonic_time(milli_seconds).
+ erlang:monotonic_time(millisecond).
get_data_within(Port, X, Acc) when X =< 0 ->
?dbg({get_data_within, X, Acc, ?LINE}),
diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl
index 531e97e8d6..5f2d8f0f4e 100644
--- a/lib/stdlib/test/lists_SUITE.erl
+++ b/lib/stdlib/test/lists_SUITE.erl
@@ -121,7 +121,7 @@ groups() ->
{zip, [parallel], [zip_unzip, zip_unzip3, zipwith, zipwith3]},
{misc, [parallel], [reverse, member, dropwhile, takewhile,
filter_partition, suffix, subtract, join,
- hof]}
+ hof, droplast]}
].
init_per_suite(Config) ->
diff --git a/lib/stdlib/test/math_SUITE.erl b/lib/stdlib/test/math_SUITE.erl
new file mode 100644
index 0000000000..2b29e44228
--- /dev/null
+++ b/lib/stdlib/test/math_SUITE.erl
@@ -0,0 +1,92 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2007-2016. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+-module(math_SUITE).
+
+-include_lib("common_test/include/ct.hrl").
+
+%% Test server specific exports
+-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
+-export([floor_ceil/1]).
+
+
+suite() ->
+ [{ct_hooks,[ts_install_cth]},
+ {timetrap,{minutes,1}}].
+
+all() ->
+ [floor_ceil].
+
+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) ->
+ Config.
+
+end_per_testcase(_Case, _Config) ->
+ ok.
+
+floor_ceil(_Config) ->
+ MinusZero = 0.0/(-1.0),
+ -43.0 = do_floor_ceil(-42.1),
+ -43.0 = do_floor_ceil(-42.7),
+ 0.0 = do_floor_ceil(MinusZero),
+ 10.0 = do_floor_ceil(10.1),
+ 10.0 = do_floor_ceil(10.9),
+
+ -533.0 = do_floor_ceil(-533.0),
+ 453555.0 = do_floor_ceil(453555.0),
+
+ -58.0 = do_floor_ceil(-58),
+ 777.0 = do_floor_ceil(777),
+
+ ok.
+
+do_floor_ceil(Val) ->
+ Floor = math:floor(Val),
+ Ceil = math:ceil(Val),
+
+ true = is_float(Floor),
+ true = is_float(Ceil),
+
+ if
+ Floor =:= Ceil ->
+ Floor;
+ true ->
+ 1.0 = Ceil - Floor,
+ Floor
+ end.
diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl
index 416650e27e..a53e99afc9 100644
--- a/lib/stdlib/test/proc_lib_SUITE.erl
+++ b/lib/stdlib/test/proc_lib_SUITE.erl
@@ -26,7 +26,7 @@
-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,
+ crash/1, stacktrace/1, sync_start_nolink/1, sync_start_link/1,
spawn_opt/1, sp1/0, sp2/0, sp3/1, sp4/2, sp5/1,
hibernate/1, stop/1, t_format/1]).
-export([ otp_6345/1, init_dont_hang/1]).
@@ -50,7 +50,7 @@
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
- [crash, {group, sync_start}, spawn_opt, hibernate,
+ [crash, stacktrace, {group, sync_start}, spawn_opt, hibernate,
{group, tickets}, stop, t_format].
groups() ->
@@ -198,6 +198,31 @@ match_info(Tuple1, Tuple2) when tuple_size(Tuple1) =:= tuple_size(Tuple2) ->
match_info(_, _) ->
throw(no_match).
+stacktrace(Config) when is_list(Config) ->
+ process_flag(trap_exit, true),
+ %% Errors.
+ Pid1 = proc_lib:spawn_link(fun() -> 1 = 2 end),
+ receive
+ {'EXIT',Pid1,{{badmatch,2},_Stack1}} -> ok
+ after 500 ->
+ ct:fail(error)
+ end,
+ %% Exits.
+ Pid2 = proc_lib:spawn_link(fun() -> exit(bye) end),
+ receive
+ {'EXIT',Pid2,bye} -> ok
+ after 500 ->
+ ct:fail(exit)
+ end,
+ %% Throws.
+ Pid3 = proc_lib:spawn_link(fun() -> throw(ball) end),
+ receive
+ {'EXIT',Pid3,{{nocatch,ball},_Stack3}} -> ok
+ after 500 ->
+ ct:fail(throw)
+ end,
+ ok.
+
sync_start_nolink(Config) when is_list(Config) ->
_Pid = spawn_link(?MODULE, sp5, [self()]),
receive
@@ -457,7 +482,7 @@ stop(_Config) ->
%% System message is handled, but process dies with other reason
%% than the given (in system_terminate/4 below)
Pid5 = proc_lib:spawn(SysMsgProc),
- {'EXIT',{badmatch,2}} = (catch proc_lib:stop(Pid5,crash,infinity)),
+ {'EXIT',{{badmatch,2},_Stacktrace}} = (catch proc_lib:stop(Pid5,crash,infinity)),
false = erlang:is_process_alive(Pid5),
%% Local registered name
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index 846c2c56f4..2b5d52287e 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -58,7 +58,7 @@
-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,
+ nomatch/1, errors/1, pattern/1, overridden_bif/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,
@@ -126,7 +126,7 @@ groups() ->
[{parse_transform, [],
[badarg, nested_qlc, unused_var, lc, fun_clauses,
filter_var, single, exported_var, generator_vars,
- nomatch, errors, pattern]},
+ nomatch, errors, pattern, overridden_bif]},
{evaluation, [],
[eval, cursor, fold, eval_unique, eval_cache, append,
evaluator, string_to_handle, table, process_dies, sort,
@@ -468,6 +468,23 @@ pattern(Config) when is_list(Config) ->
-record(k, {t,v}).\n">>, Ts),
ok.
+%% Override a guard BIF with an imported or local function.
+overridden_bif(Config) ->
+ Ts = [
+ <<"[2] = qlc:e(qlc:q([P || P <- [1,2,3], port(P)])),
+ [10] = qlc:e(qlc:q([P || P <- [0,9,10,11,12],
+ (is_reference(P) andalso P > 5)])),
+ Empty = gb_sets:empty(), Single = gb_sets:singleton(42),
+ GbSets = [Empty,Single],
+ [Single] = qlc:e(qlc:q([S || S <- GbSets, size(S) =/= 0]))
+ ">>
+ ],
+ run(Config, "-import(gb_sets, [size/1]).
+ -compile({no_auto_import, [size/1, is_reference/1]}).
+ port(N) -> N rem 2 =:= 0.
+ is_reference(N) -> N rem 10 =:= 0.\n", Ts),
+ ok.
+
%% eval/2
eval(Config) when is_list(Config) ->
@@ -7929,7 +7946,6 @@ compile(Config, Tests, Fun) ->
compile_file(Config, Test0, Opts0) ->
{File, Mod} = compile_file_mod(Config),
Test = list_to_binary(["-module(", atom_to_list(Mod), "). "
- "-compile(export_all). "
"-import(qlc_SUITE, [i/1,i/2,format_info/2]). "
"-import(qlc_SUITE, [etsc/2, etsc/3]). "
"-import(qlc_SUITE, [create_ets/2]). "
@@ -7939,7 +7955,7 @@ compile_file(Config, Test0, Opts0) ->
"-import(qlc_SUITE, [lookup_keys/1]). "
"-include_lib(\"stdlib/include/qlc.hrl\"). ",
Test0]),
- Opts = [export_all,return,nowarn_unused_record,{outdir,?privdir}|Opts0],
+ Opts = [export_all,nowarn_export_all,return,nowarn_unused_record,{outdir,?privdir}|Opts0],
ok = file:write_file(File, Test),
case compile:file(File, Opts) of
{ok, _M, Ws} -> warnings(File, Ws);
diff --git a/lib/stdlib/test/rand_SUITE.erl b/lib/stdlib/test/rand_SUITE.erl
index 47e7c4f03d..fe5eaccda5 100644
--- a/lib/stdlib/test/rand_SUITE.erl
+++ b/lib/stdlib/test/rand_SUITE.erl
@@ -28,7 +28,8 @@
api_eq/1, reference/1,
basic_stats_uniform_1/1, basic_stats_uniform_2/1,
basic_stats_normal/1,
- plugin/1, measure/1]).
+ plugin/1, measure/1,
+ reference_jump_state/1, reference_jump_procdict/1]).
-export([test/0, gen/1]).
@@ -45,14 +46,21 @@ all() ->
api_eq,
reference,
{group, basic_stats},
- plugin, measure].
+ plugin, measure,
+ {group, reference_jump}
+ ].
groups() ->
[{basic_stats, [parallel],
- [basic_stats_uniform_1, basic_stats_uniform_2, basic_stats_normal]}].
+ [basic_stats_uniform_1, basic_stats_uniform_2, basic_stats_normal]},
+ {reference_jump, [parallel],
+ [reference_jump_state, reference_jump_procdict]}].
group(basic_stats) ->
%% valgrind needs a lot of time
+ [{timetrap,{minutes,10}}];
+group(reference_jump) ->
+ %% valgrind needs a lot of time
[{timetrap,{minutes,10}}].
%% A simple helper to test without test_server during dev
@@ -228,7 +236,7 @@ interval_float_1(N) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% Check if exs64 algorithm generates the proper sequence.
+%% Check if each algorithm generates the proper sequence.
reference(Config) when is_list(Config) ->
[reference_1(Alg) || Alg <- algs()],
ok.
@@ -242,7 +250,7 @@ reference_1(Alg) ->
io:format("Failed: ~p~n",[Alg]),
io:format("Length ~p ~p~n",[length(Refval), length(Testval)]),
io:format("Head ~p ~p~n",[hd(Refval), hd(Testval)]),
- ok
+ exit(wrong_value)
end.
gen(Algo) ->
@@ -434,6 +442,112 @@ measure_2(N, State0, Fun) when N > 0 ->
measure_2(0, _, _) -> ok.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% The jump sequence tests has two parts
+%% for those with the functional API (jump/1)
+%% and for those with the internal state
+%% in process dictionary (jump/0).
+
+-define(LOOP_JUMP, (?LOOP div 1000)).
+
+%% Check if each algorithm generates the proper jump sequence
+%% with the functional API.
+reference_jump_state(Config) when is_list(Config) ->
+ [reference_jump_1(Alg) || Alg <- algs()],
+ ok.
+
+reference_jump_1(Alg) ->
+ Refval = reference_jump_val(Alg),
+ Testval = gen_jump_1(Alg),
+ case Refval =:= Testval of
+ true -> ok;
+ false ->
+ io:format("Failed: ~p~n",[Alg]),
+ io:format("Length ~p ~p~n",[length(Refval), length(Testval)]),
+ io:format("Head ~p ~p~n",[hd(Refval), hd(Testval)]),
+ exit(wrong_value)
+ end.
+
+gen_jump_1(Algo) ->
+ Seed = case Algo of
+ exsplus -> %% Printed with orig 'C' code and this seed
+ rand:seed_s({exsplus, [12345678|12345678]});
+ exs1024 -> %% Printed with orig 'C' code and this seed
+ rand:seed_s({exs1024, {lists:duplicate(16, 12345678), []}});
+ exs64 -> %% Test exception of not_implemented notice
+ try rand:jump(rand:seed_s(exs64))
+ catch
+ error:not_implemented -> not_implemented
+ end;
+ _ -> % unimplemented
+ not_implemented
+ end,
+ case Seed of
+ not_implemented -> [not_implemented];
+ S -> gen_jump_1(?LOOP_JUMP, S, [])
+ end.
+
+gen_jump_1(N, State0 = {#{max:=Max}, _}, Acc) when N > 0 ->
+ {_, State1} = rand:uniform_s(Max, State0),
+ {Random, State2} = rand:uniform_s(Max, rand:jump(State1)),
+ case N rem (?LOOP_JUMP div 100) of
+ 0 -> gen_jump_1(N-1, State2, [Random|Acc]);
+ _ -> gen_jump_1(N-1, State2, Acc)
+ end;
+gen_jump_1(_, _, Acc) -> lists:reverse(Acc).
+
+%% Check if each algorithm generates the proper jump sequence
+%% with the internal state in the process dictionary.
+reference_jump_procdict(Config) when is_list(Config) ->
+ [reference_jump_0(Alg) || Alg <- algs()],
+ ok.
+
+reference_jump_0(Alg) ->
+ Refval = reference_jump_val(Alg),
+ Testval = gen_jump_0(Alg),
+ case Refval =:= Testval of
+ true -> ok;
+ false ->
+ io:format("Failed: ~p~n",[Alg]),
+ io:format("Length ~p ~p~n",[length(Refval), length(Testval)]),
+ io:format("Head ~p ~p~n",[hd(Refval), hd(Testval)]),
+ exit(wrong_value)
+ end.
+
+gen_jump_0(Algo) ->
+ Seed = case Algo of
+ exsplus -> %% Printed with orig 'C' code and this seed
+ rand:seed({exsplus, [12345678|12345678]});
+ exs1024 -> %% Printed with orig 'C' code and this seed
+ rand:seed({exs1024, {lists:duplicate(16, 12345678), []}});
+ exs64 -> %% Test exception of not_implemented notice
+ try
+ _ = rand:seed(exs64),
+ rand:jump()
+ catch
+ error:not_implemented -> not_implemented
+ end;
+ _ -> % unimplemented
+ not_implemented
+ end,
+ case Seed of
+ not_implemented -> [not_implemented];
+ S ->
+ {Seedmap=#{}, _} = S,
+ Max = maps:get(max, Seedmap),
+ gen_jump_0(?LOOP_JUMP, Max, [])
+ end.
+
+gen_jump_0(N, Max, Acc) when N > 0 ->
+ _ = rand:uniform(Max),
+ _ = rand:jump(),
+ Random = rand:uniform(Max),
+ case N rem (?LOOP_JUMP div 100) of
+ 0 -> gen_jump_0(N-1, Max, [Random|Acc]);
+ _ -> gen_jump_0(N-1, Max, Acc)
+ end;
+gen_jump_0(_, _, Acc) -> lists:reverse(Acc).
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%% Data
reference_val(exs64) ->
[16#3737ad0c703ff6c3,16#3868a78fe71adbbd,16#1f01b62b4338b605,16#50876a917437965f,
@@ -515,3 +629,61 @@ reference_val(exsplus) ->
16#36f715a249f4ec2,16#1c27629826c50d3,16#914d9a6648726a,16#27f5bf5ce2301e8,
16#3dd493b8012970f,16#be13bed1e00e5c,16#ceef033b74ae10,16#3da38c6a50abe03,
16#15cbd1a421c7a8c,16#22794e3ec6ef3b1,16#26154d26e7ea99f,16#3a66681359a6ab6].
+
+%%%
+
+reference_jump_val(exsplus) ->
+ [82445318862816932, 145810727464480743, 16514517716894509, 247642377064868650,
+ 162385642339156908, 251810707075252101, 82288275771998924, 234412731596926322,
+ 49960883129071044, 200690077681656596, 213743196668671647, 131182800982967108,
+ 144200072021941728, 263557425008503277, 194858522616874272, 185869394820993172,
+ 80384502675241453, 262654144824057588, 90033295011291362, 4494510449302659,
+ 226005372746479588, 116780561309220553, 47048528594475843, 39168929349768743,
+ 139615163424415552, 55330632656603925, 237575574720486569, 102381140288455025,
+ 18452933910354323, 150248612130579752, 269358096791922740, 61313433522002187,
+ 160327361842676597, 185187983548528938, 57378981505594193, 167510799293984067,
+ 105117045862954303, 176126685946302943, 123590876906828803, 69185336947273487,
+ 9098689247665808, 49906154674145057, 131575138412788650, 161843880211677185,
+ 30743946051071186, 187578920583823612, 45008401528636978, 122454158686456658,
+ 111195992644229524, 17962783958752862, 13579507636941108, 130137843317798663,
+ 144202635170576832, 132539563255093922, 159785575703967124, 187241848364816640,
+ 183044737781926478, 12921559769912263, 83553932242922001, 96698298841984688,
+ 281664320227537824, 224233030818578263, 77812932110318774, 169729351013291728,
+ 164475402723178734, 242780633011249051, 51095111179609125, 19249189591963554,
+ 221412426221439180, 265700202856282653, 265342254311932308, 241218503498385511,
+ 255400887248486575, 212083616929812076, 227947034485840579, 268261881651571692,
+ 104846262373404908, 49690734329496661, 213259196633566308, 186966479726202436,
+ 282157378232384574, 11272948584603747, 166540426999573480, 50628164001018755,
+ 65235580992800860, 230664399047956956, 64575592354687978, 40519393736078511,
+ 108341851194332747, 115426411532008961, 120656817002338193, 234537867870809797,
+ 12504080415362731, 45083100453836317, 270968267812126657, 93505647407734103,
+ 252852934678537969, 258758309277167202, 74250882143432077, 141629095984552833];
+
+reference_jump_val(exs1024) ->
+ [2655961906500790629, 17003395417078685063, 10466831598958356428, 7603399148503548021,
+ 1650550950190587188, 12294992315080723704, 15743995773860389219, 5492181000145247327,
+ 14118165228742583601, 1024386975263610703, 10124872895886669513, 6445624517813169301,
+ 6238575554686562601, 14108646153524288915, 11804141635807832816, 8421575378006186238,
+ 6354993374304550369, 838493020029548163, 14759355804308819469, 12212491527912522022,
+ 16943204735100571602, 198964074252287588, 7325922870779721649, 15853102065526570574,
+ 16294058349151823341, 6153379962047409781, 15874031679495957261, 17299265255608442340,
+ 984658421210027171, 17408042033939375278, 3326465916992232353, 5222817718770538733,
+ 13262385796795170510, 15648751121811336061, 6718721549566546451, 7353765235619801875,
+ 16110995049882478788, 14559143407227563441, 4189805181268804683, 10938587948346538224,
+ 1635025506014383478, 12619562911869525411, 17469465615861488695, 125252234176411528,
+ 2004192558503448853, 13175467866790974840, 17712272336167363518, 1710549840100880318,
+ 17486892343528340916, 5337910082227550967, 8333082060923612691, 6284787745504163856,
+ 8072221024586708290, 6077032673910717705, 11495200863352251610, 11722792537523099594,
+ 14642059504258647996, 8595733246938141113, 17223366528010341891, 17447739753327015776,
+ 6149800490736735996, 11155866914574313276, 7123864553063709909, 15982886296520662323,
+ 5775920250955521517, 8624640108274906072, 8652974210855988961, 8715770416136907275,
+ 11841689528820039868, 10991309078149220415, 11758038663970841716, 7308750055935299261,
+ 15939068400245256963, 6920341533033919644, 8017706063646646166, 15814376391419160498,
+ 13529376573221932937, 16749061963269842448, 14639730709921425830, 3265850480169354066,
+ 4569394597532719321, 16594515239012200038, 13372824240764466517, 16892840440503406128,
+ 11260004846380394643, 2441660009097834955, 10566922722880085440, 11463315545387550692,
+ 5252492021914937692, 10404636333478845345, 11109538423683960387, 5525267334484537655,
+ 17936751184378118743, 4224632875737239207, 15888641556987476199, 9586888813112229805,
+ 9476861567287505094, 14909536929239540332, 17996844556292992842, 2699310519182298856];
+
+reference_jump_val(exs64) -> [not_implemented].
diff --git a/lib/stdlib/test/random_iolist.erl b/lib/stdlib/test/random_iolist.erl
index 555f063e0a..b62cf5b82b 100644
--- a/lib/stdlib/test/random_iolist.erl
+++ b/lib/stdlib/test/random_iolist.erl
@@ -24,17 +24,13 @@
-module(random_iolist).
--export([run/3, run2/3, standard_seed/0, compare/3, compare2/3,
+-export([run/3, standard_seed/0, compare/3,
random_iolist/1]).
run(Iter,Fun1,Fun2) ->
standard_seed(),
compare(Iter,Fun1,Fun2).
-run2(Iter,Fun1,Fun2) ->
- standard_seed(),
- compare2(Iter,Fun1,Fun2).
-
random_byte() ->
rand:uniform(256) - 1.
@@ -150,16 +146,6 @@ do_comp(List,F1,F2) ->
_ ->
true
end.
-
-do_comp(List,List2,F1,F2) ->
- X = F1(List,List2),
- Y = F2(List,List2),
- case X =:= Y of
- false ->
- exit({not_matching,List,List2,X,Y});
- _ ->
- true
- end.
compare(0,Fun1,Fun2) ->
do_comp(<<>>,Fun1,Fun2),
@@ -172,25 +158,3 @@ compare(N,Fun1,Fun2) ->
L = random_iolist(N),
do_comp(L,Fun1,Fun2),
compare(N-1,Fun1,Fun2).
-
-compare2(0,Fun1,Fun2) ->
- L = random_iolist(100),
- do_comp(<<>>,L,Fun1,Fun2),
- do_comp(L,<<>>,Fun1,Fun2),
- do_comp(<<>>,<<>>,Fun1,Fun2),
- do_comp([],L,Fun1,Fun2),
- do_comp(L,[],Fun1,Fun2),
- do_comp([],[],Fun1,Fun2),
- do_comp([[]|<<>>],L,Fun1,Fun2),
- do_comp(L,[[]|<<>>],Fun1,Fun2),
- do_comp([[]|<<>>],[[]|<<>>],Fun1,Fun2),
- do_comp([<<>>,[]|<<>>],L,Fun1,Fun2),
- do_comp(L,[<<>>,[]|<<>>],Fun1,Fun2),
- do_comp([<<>>,[]|<<>>],[<<>>,[]|<<>>],Fun1,Fun2),
- true;
-
-compare2(N,Fun1,Fun2) ->
- L = random_iolist(N),
- L2 = random_iolist(N),
- do_comp(L,L2,Fun1,Fun2),
- compare2(N-1,Fun1,Fun2).
diff --git a/lib/stdlib/test/random_unicode_list.erl b/lib/stdlib/test/random_unicode_list.erl
index 8db2fa8b56..2eeb28113d 100644
--- a/lib/stdlib/test/random_unicode_list.erl
+++ b/lib/stdlib/test/random_unicode_list.erl
@@ -24,7 +24,7 @@
-module(random_unicode_list).
--export([run/3, run/4, run2/3, standard_seed/0, compare/4, compare2/3,
+-export([run/3, run/4, standard_seed/0, compare/4,
random_unicode_list/2]).
run(I,F1,F2) ->
@@ -33,10 +33,6 @@ run(Iter,Fun1,Fun2,Enc) ->
standard_seed(),
compare(Iter,Fun1,Fun2,Enc).
-run2(Iter,Fun1,Fun2) ->
- standard_seed(),
- compare2(Iter,Fun1,Fun2).
-
int_to_utf8(I) when I =< 16#7F ->
<<I>>;
int_to_utf8(I) when I =< 16#7FF ->
@@ -225,16 +221,6 @@ do_comp(List,F1,F2) ->
_ ->
true
end.
-
-do_comp(List,List2,F1,F2) ->
- X = F1(List,List2),
- Y = F2(List,List2),
- case X =:= Y of
- false ->
- exit({not_matching,List,List2,X,Y});
- _ ->
- true
- end.
compare(0,Fun1,Fun2,_Enc) ->
do_comp(<<>>,Fun1,Fun2),
@@ -247,25 +233,3 @@ compare(N,Fun1,Fun2,Enc) ->
L = random_unicode_list(N,Enc),
do_comp(L,Fun1,Fun2),
compare(N-1,Fun1,Fun2,Enc).
-
-compare2(0,Fun1,Fun2) ->
- L = random_unicode_list(100,utf8),
- do_comp(<<>>,L,Fun1,Fun2),
- do_comp(L,<<>>,Fun1,Fun2),
- do_comp(<<>>,<<>>,Fun1,Fun2),
- do_comp([],L,Fun1,Fun2),
- do_comp(L,[],Fun1,Fun2),
- do_comp([],[],Fun1,Fun2),
- do_comp([[]|<<>>],L,Fun1,Fun2),
- do_comp(L,[[]|<<>>],Fun1,Fun2),
- do_comp([[]|<<>>],[[]|<<>>],Fun1,Fun2),
- do_comp([<<>>,[]|<<>>],L,Fun1,Fun2),
- do_comp(L,[<<>>,[]|<<>>],Fun1,Fun2),
- do_comp([<<>>,[]|<<>>],[<<>>,[]|<<>>],Fun1,Fun2),
- true;
-
-compare2(N,Fun1,Fun2) ->
- L = random_unicode_list(N,utf8),
- L2 = random_unicode_list(N,utf8),
- do_comp(L,L2,Fun1,Fun2),
- compare2(N-1,Fun1,Fun2).
diff --git a/lib/stdlib/test/re_testoutput1_replacement_test.erl b/lib/stdlib/test/re_testoutput1_replacement_test.erl
index a40800d760..563e0001e4 100644
--- a/lib/stdlib/test/re_testoutput1_replacement_test.erl
+++ b/lib/stdlib/test/re_testoutput1_replacement_test.erl
@@ -18,7 +18,7 @@
%% %CopyrightEnd%
%%
-module(re_testoutput1_replacement_test).
--compile(export_all).
+-export([run/0]).
-compile(no_native).
%% This file is generated by running run_pcre_tests:gen_repl_test("re_SUITE_data/testoutput1")
run() ->
diff --git a/lib/stdlib/test/re_testoutput1_split_test.erl b/lib/stdlib/test/re_testoutput1_split_test.erl
index 02987971fa..b39cb53a55 100644
--- a/lib/stdlib/test/re_testoutput1_split_test.erl
+++ b/lib/stdlib/test/re_testoutput1_split_test.erl
@@ -18,7 +18,7 @@
%% %CopyrightEnd%
%%
-module(re_testoutput1_split_test).
--compile(export_all).
+-export([run/0]).
-compile(no_native).
%% This file is generated by running run_pcre_tests:gen_split_test("re_SUITE_data/testoutput1")
join([]) -> [];
diff --git a/lib/stdlib/test/run_pcre_tests.erl b/lib/stdlib/test/run_pcre_tests.erl
index ae56db59d6..b62674d6e0 100644
--- a/lib/stdlib/test/run_pcre_tests.erl
+++ b/lib/stdlib/test/run_pcre_tests.erl
@@ -18,8 +18,7 @@
%% %CopyrightEnd%
%%
-module(run_pcre_tests).
-
--compile(export_all).
+-export([test/1,gen_split_test/1,gen_repl_test/1]).
test(RootDir) ->
put(verbose,false),
@@ -119,49 +118,6 @@ test([{RE0,Line,Options0,Tests}|T],PreCompile,XMode,REAsList) ->
end
end.
-loopexec(_,_,X,Y,_,_) when X > Y ->
- {match,[]};
-loopexec(P,Chal,X,Y,Unicode,Xopt) ->
- case re:run(Chal,P,[{offset,X}]++Xopt) of
- nomatch ->
- {match,[]};
- {match,[{A,B}|More]} ->
- {match,Rest} =
- case B>0 of
- true ->
- loopexec(P,Chal,A+B,Y,Unicode,Xopt);
- false ->
- {match,M} = case re:run(Chal,P,[{offset,X},notempty,anchored]++Xopt) of
- nomatch ->
- {match,[]};
- {match,Other} ->
- {match,fixup(Chal,Other,0)}
- end,
- NewA = forward(Chal,A,1,Unicode),
- {match,MM} = loopexec(P,Chal,NewA,Y,Unicode,Xopt),
- {match,M ++ MM}
- end,
- {match,fixup(Chal,[{A,B}|More],0)++Rest}
- end.
-
-forward(_Chal,A,0,_) ->
- A;
-forward(_Chal,A,N,false) ->
- A+N;
-forward(Chal,A,N,true) ->
- <<_:A/binary,Tl/binary>> = Chal,
- Forw = case Tl of
- <<1:1,1:1,0:1,_:5,_/binary>> ->
- 2;
- <<1:1,1:1,1:1,0:1,_:4,_/binary>> ->
- 3;
- <<1:1,1:1,1:1,1:1,0:1,_:3,_/binary>> ->
- 4;
- _ ->
- 1
- end,
- forward(Chal,A+Forw,N-1,true).
-
contains_eightbit(<<>>) ->
false;
contains_eightbit(<<X:8,_/binary>>) when X >= 128 ->
@@ -201,23 +157,6 @@ clean_duplicates([X|T],L) ->
end.
-global_fixup(_,nomatch) ->
- nomatch;
-global_fixup(P,{match,M}) ->
- {match,lists:flatten(global_fixup2(P,M))}.
-
-global_fixup2(_,[]) ->
- [];
-global_fixup2(P,[H|T]) ->
- [gfixup_one(P,0,H)|global_fixup2(P,T)].
-
-gfixup_one(_,_,[]) ->
- [];
-gfixup_one(P,I,[{Start,Len}|T]) ->
- <<_:Start/binary,R:Len/binary,_/binary>> = P,
- [{I,R}|gfixup_one(P,I+1,T)].
-
-
press([]) ->
[];
press([H|T]) ->
@@ -981,7 +920,7 @@ gen_split_test(OneFile) ->
ErlFileName = ErlModule++".erl",
{ok,F}= file:open(ErlFileName,[write]),
io:format(F,"-module(~s).~n",[ErlModule]),
- io:format(F,"-compile(export_all).~n",[]),
+ io:format(F,"-export([run/0]).~n",[]),
io:format(F,"-compile(no_native).~n",[]),
io:format(F,"%% This file is generated by running ~w:gen_split_test(~p)~n",
[?MODULE,OneFile]),
@@ -1024,7 +963,7 @@ dumponesplit(F,{RE,Line,O,TS}) ->
"$x =~~ s/\\\\/\\\\\\\\/g; $x =~~ s/\\\"/\\\\\"/g; "
"print \" <<\\\"$x\\\">> = "
"iolist_to_binary(join(re:split(\\\"~s\\\","
- "\\\"~s\\\",~p))), \\n\";'~n",
+ "\\\"~s\\\",~p))),\\n\";'~n",
[zsafe(safe(RE)),
SSS,
ysafe(safe(Str)),
@@ -1035,7 +974,7 @@ dumponesplit(F,{RE,Line,O,TS}) ->
"$x =~~ s/\\\\/\\\\\\\\/g; $x =~~ s/\\\"/\\\\\"/g; "
"print \" <<\\\"$x\\\">> = "
"iolist_to_binary(join(re:split(\\\"~s\\\","
- "\\\"~s\\\",~p))), \\n\";'~n",
+ "\\\"~s\\\",~p))),\\n\";'~n",
[zsafe(safe(RE)),
SSS,
ysafe(safe(Str)),
@@ -1046,7 +985,7 @@ dumponesplit(F,{RE,Line,O,TS}) ->
"$x =~~ s/\\\\/\\\\\\\\/g; $x =~~ s/\\\"/\\\\\"/g; "
"print \" <<\\\"$x\\\">> = "
"iolist_to_binary(join(re:split(\\\"~s\\\","
- "\\\"~s\\\",~p))), \\n\";'~n",
+ "\\\"~s\\\",~p))),\\n\";'~n",
[zsafe(safe(RE)),
SSS,
ysafe(safe(Str)),
@@ -1071,7 +1010,7 @@ gen_repl_test(OneFile) ->
ErlFileName = ErlModule++".erl",
{ok,F}= file:open(ErlFileName,[write]),
io:format(F,"-module(~s).~n",[ErlModule]),
- io:format(F,"-compile(export_all).~n",[]),
+ io:format(F,"-export([run/0]).~n",[]),
io:format(F,"-compile(no_native).~n",[]),
io:format(F,"%% This file is generated by running ~w:gen_repl_test(~p)~n",
[?MODULE,OneFile]),
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index 80585ca359..4864bc3d72 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -282,7 +282,7 @@ restricted_local(Config) when is_list(Config) ->
comm_err(<<"begin F=fun() -> hello end, foo(F) end.">>),
"exception error: undefined shell command banan/1" =
comm_err(<<"begin F=fun() -> hello end, banan(F) end.">>),
- "{error,"++_ = t(<<"begin F=fun() -> hello end, c(F) end.">>),
+ "Recompiling "++_ = t(<<"c(shell_SUITE).">>),
"exception exit: restricted shell does not allow l(" ++ _ =
comm_err(<<"begin F=fun() -> hello end, l(F) end.">>),
"exception error: variable 'F' is unbound" =
@@ -573,7 +573,7 @@ otp_5327(Config) when is_list(Config) ->
(catch evaluate(<<"<<32/unit:8>>.">>, [])),
ok.
-%% OTP-5435. sys_pre_expand not in the path.
+%% OTP-5435. compiler application not in the path.
otp_5435(Config) when is_list(Config) ->
true = <<103133:64/float>> =:=
evaluate(<<"<<103133:64/float>> = <<103133:64/float>>.">>, []),
@@ -591,8 +591,9 @@ start_node(Name) ->
otp_5435_2() ->
true = code:del_path(compiler),
- %% sys_pre_expand can no longer be found
- %% OTP-5876. But erl_expand_records can!
+ %% Make sure record evaluation is not dependent on the compiler
+ %% application being in the path.
+ %% OTP-5876.
[{attribute,_,record,{bar,_}},ok] =
scan(<<"rd(foo,{bar}),
rd(bar,{foo = (#foo{})#foo.bar}),
@@ -1793,7 +1794,7 @@ Test1_shell =
Test2 =
<<"-module(recs).
-record(person, {name, age, phone = [], dict = []}).
--compile(export_all).
+-export([t/0]).
t() -> ok.
@@ -1960,7 +1961,7 @@ ok.
progex_funs(Config) when is_list(Config) ->
Test1 =
<<"-module(funs).
- -compile(export_all).
+ -export([t/0]).
double([H|T]) -> [2*H|double(T)];
double([]) -> [].
@@ -3030,7 +3031,7 @@ run_file(Config, Module, Test) ->
ok.
compile_file(Config, File, Test, Opts0) ->
- Opts = [export_all,return,{outdir,proplists:get_value(priv_dir, Config)}|Opts0],
+ Opts = [export_all,nowarn_export_all,return,{outdir,proplists:get_value(priv_dir, Config)}|Opts0],
ok = file:write_file(File, Test),
case compile:file(File, Opts) of
{ok, _M, _Ws} -> ok;
diff --git a/lib/stdlib/test/sofs_SUITE.erl b/lib/stdlib/test/sofs_SUITE.erl
index 13c12ad2f2..f67bf16f0f 100644
--- a/lib/stdlib/test/sofs_SUITE.erl
+++ b/lib/stdlib/test/sofs_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2001-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2001-2017. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -1837,11 +1837,8 @@ digraph(Conf) when is_list(Conf) ->
ok.
digraph_fail(ExitReason, Fail) ->
- {'EXIT', {ExitReason, [{sofs,family_to_digraph,A,_}|_]}} = Fail,
- case {test_server:is_native(sofs),A} of
- {false,[_,_]} -> ok;
- {true,2} -> ok
- end.
+ {'EXIT', {ExitReason, [{sofs,family_to_digraph,2,_}|_]}} = Fail,
+ ok.
constant_function(Conf) when is_list(Conf) ->
E = empty_set(),
diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl
index 6f3979bb77..d6b6d3f80c 100644
--- a/lib/stdlib/test/tar_SUITE.erl
+++ b/lib/stdlib/test/tar_SUITE.erl
@@ -22,9 +22,10 @@
-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_binary_compressed/1, extract_filtered/1,
extract_from_open_file/1, symlinks/1, open_add_close/1, cooked_compressed/1,
- memory/1,unicode/1]).
+ memory/1,unicode/1,read_other_implementations/1,
+ sparse/1, init/1]).
-include_lib("common_test/include/ct.hrl").
-include_lib("kernel/include/file.hrl").
@@ -35,7 +36,10 @@ 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, unicode].
+ extract_filtered,
+ symlinks, open_add_close, cooked_compressed, memory, unicode,
+ read_other_implementations,
+ sparse,init].
groups() ->
[].
@@ -84,17 +88,30 @@ borderline(Config) when is_list(Config) ->
ok.
borderline_test(Size, TempDir) ->
- Archive = filename:join(TempDir, "ar_"++integer_to_list(Size)++".tar"),
- Name = filename:join(TempDir, "file_"++integer_to_list(Size)),
io:format("Testing size ~p", [Size]),
+ borderline_test(Size, TempDir, true),
+ borderline_test(Size, TempDir, false),
+ ok.
+
+borderline_test(Size, TempDir, IsUstar) ->
+ Prefix = case IsUstar of
+ true ->
+ "file_";
+ false ->
+ lists:duplicate(100, $f) ++ "ile_"
+ end,
+ SizeList = integer_to_list(Size),
+ Archive = filename:join(TempDir, "ar_"++ SizeList ++".tar"),
+ Name = filename:join(TempDir, Prefix++SizeList),
%% Create a file and archive it.
X0 = erlang:monotonic_time(),
- file:write_file(Name, random_byte_list(X0, Size)),
+ ok = file:write_file(Name, random_byte_list(X0, Size)),
ok = erl_tar:create(Archive, [Name]),
ok = file:delete(Name),
%% Verify listing and extracting.
+ IsUstar = is_ustar(Archive),
{ok, [Name]} = erl_tar:table(Archive),
ok = erl_tar:extract(Archive, [verbose]),
@@ -103,7 +120,12 @@ borderline_test(Size, TempDir) ->
true = match_byte_list(X0, binary_to_list(Bin)),
%% Verify that Unix tar can read it.
- tar_tf(Archive, Name),
+ case IsUstar of
+ true ->
+ tar_tf(Archive, Name);
+ false ->
+ ok
+ end,
ok.
@@ -336,6 +358,7 @@ create_long_names() ->
ok = erl_tar:tt(TarName),
%% Extract and verify.
+ true = is_ustar(TarName),
ExtractDir = "extract_dir",
ok = file:make_dir(ExtractDir),
ok = erl_tar:extract(TarName, [{cwd,ExtractDir}]),
@@ -357,7 +380,7 @@ make_dirs([], Dir) ->
%% Try erl_tar:table/2 and erl_tar:extract/2 on some corrupted tar files.
bad_tar(Config) when is_list(Config) ->
try_bad("bad_checksum", bad_header, Config),
- try_bad("bad_octal", bad_header, Config),
+ try_bad("bad_octal", invalid_tar_checksum, Config),
try_bad("bad_too_short", eof, Config),
try_bad("bad_even_shorter", eof, Config),
ok.
@@ -370,8 +393,10 @@ try_bad(Name0, Reason, Config) ->
Name = Name0 ++ ".tar",
io:format("~nTrying ~s", [Name]),
Full = filename:join(DataDir, Name),
- Opts = [verbose, {cwd, PrivDir}],
+ Dest = filename:join(PrivDir, Name0),
+ Opts = [verbose, {cwd, Dest}],
Expected = {error, Reason},
+ io:fwrite("Expected: ~p\n", [Expected]),
case {erl_tar:table(Full, Opts), erl_tar:extract(Full, Opts)} of
{Expected, Expected} ->
io:format("Result: ~p", [Expected]),
@@ -493,6 +518,27 @@ extract_from_binary_compressed(Config) when is_list(Config) ->
ok.
+%% Test extracting a tar archive from a binary.
+extract_filtered(Config) when is_list(Config) ->
+ DataDir = proplists:get_value(data_dir, Config),
+ PrivDir = proplists:get_value(priv_dir, Config),
+ Long = filename:join(DataDir, "no_fancy_stuff.tar"),
+ ExtractDir = filename:join(PrivDir, "extract_from_binary"),
+ ok = file:make_dir(ExtractDir),
+
+ ok = erl_tar:extract(Long, [{cwd,ExtractDir},{files,["no_fancy_stuff/EPLICENCE"]}]),
+
+ %% Verify.
+ Dir = filename:join(ExtractDir, "no_fancy_stuff"),
+ true = filelib:is_dir(Dir),
+ false = filelib:is_file(filename:join(Dir, "a_dir_list")),
+ true = filelib:is_file(filename:join(Dir, "EPLICENCE")),
+
+ %% Clean up.
+ delete_files([ExtractDir]),
+
+ ok.
+
%% Test extracting a tar archive from an open file.
extract_from_open_file(Config) when is_list(Config) ->
DataDir = proplists:get_value(data_dir, Config),
@@ -573,6 +619,7 @@ symlinks(Dir, BadSymlink, PointsTo) ->
ok = file:write_file(AFile, ALine),
ok = file:make_symlink(AFile, GoodSymlink),
ok = erl_tar:create(Tar, [BadSymlink, GoodSymlink, AFile], [verbose]),
+ true = is_ustar(Tar),
%% List contents of tar file.
@@ -581,6 +628,7 @@ symlinks(Dir, BadSymlink, PointsTo) ->
%% Also create another archive with the dereference flag.
ok = erl_tar:create(DerefTar, [AFile, GoodSymlink], [dereference, verbose]),
+ true = is_ustar(DerefTar),
%% Extract files to a new directory.
@@ -619,13 +667,50 @@ long_symlink(Dir) ->
ok = file:set_cwd(Dir),
AFile = "long_symlink",
- FarTooLong = "/tmp/aarrghh/this/path/is/far/longer/than/one/hundred/characters/which/is/the/maximum/number/of/characters/allowed",
- ok = file:make_symlink(FarTooLong, AFile),
- {error,Error} = erl_tar:create(Tar, [AFile], [verbose]),
- io:format("Error: ~s\n", [erl_tar:format_error(Error)]),
- {FarTooLong,symbolic_link_too_long} = Error,
+ RequiresPAX = "/tmp/aarrghh/this/path/is/far/longer/than/one/hundred/characters/which/is/the/maximum/number/of/characters/allowed",
+ ok = file:make_symlink(RequiresPAX, AFile),
+ ok = erl_tar:create(Tar, [AFile], [verbose]),
+ false = is_ustar(Tar),
+ NewDir = filename:join(Dir, "extracted"),
+ _ = file:make_dir(NewDir),
+ ok = erl_tar:extract(Tar, [{cwd, NewDir}, verbose]),
+ ok = file:set_cwd(NewDir),
+ {ok, #file_info{type=symlink}} = file:read_link_info(AFile),
+ {ok, RequiresPAX} = file:read_link(AFile),
+ ok.
+
+init(Config) when is_list(Config) ->
+ PrivDir = proplists:get_value(priv_dir, Config),
+ ok = file:set_cwd(PrivDir),
+ Dir = filename:join(PrivDir, "init"),
+ ok = file:make_dir(Dir),
+
+ [{FileOne,_,_}|_] = oac_files(),
+ TarOne = filename:join(Dir, "archive1.tar"),
+ {ok,Fd} = file:open(TarOne, [write]),
+
+ %% If the arity of the fun is wrong, badarg should be returned
+ {error, badarg} = erl_tar:init(Fd, write, fun file_op_bad/1),
+
+ %% Otherwise we should be good to go
+ {ok, Tar} = erl_tar:init(Fd, write, fun file_op/2),
+ ok = erl_tar:add(Tar, FileOne, []),
+ ok = erl_tar:close(Tar),
+ {ok, [FileOne]} = erl_tar:table(TarOne),
ok.
+file_op_bad(_) ->
+ throw({error, should_never_be_called}).
+
+file_op(write, {Fd, Data}) ->
+ file:write(Fd, Data);
+file_op(position, {Fd, Pos}) ->
+ file:position(Fd, Pos);
+file_op(read2, {Fd, Size}) ->
+ file:read(Fd, Size);
+file_op(close, Fd) ->
+ file:close(Fd).
+
open_add_close(Config) when is_list(Config) ->
PrivDir = proplists:get_value(priv_dir, Config),
ok = file:set_cwd(PrivDir),
@@ -643,17 +728,26 @@ open_add_close(Config) when is_list(Config) ->
TarOne = filename:join(Dir, "archive1.tar"),
{ok,AD} = erl_tar:open(TarOne, [write]),
ok = erl_tar:add(AD, FileOne, []),
- ok = erl_tar:add(AD, FileTwo, "second file", []),
- ok = erl_tar:add(AD, FileThree, [verbose]),
+
+ %% Add with {NameInArchive,Name}
+ ok = erl_tar:add(AD, {"second file", FileTwo}, []),
+
+ %% Add with {binary, Bin}
+ {ok,FileThreeBin} = file:read_file(FileThree),
+ ok = erl_tar:add(AD, {FileThree, FileThreeBin}, [verbose]),
+
+ %% Add with Name
ok = erl_tar:add(AD, FileThree, "chunked", [{chunks,11411},verbose]),
ok = erl_tar:add(AD, ADir, [verbose]),
ok = erl_tar:add(AD, AnotherDir, [verbose]),
ok = erl_tar:close(AD),
+ true = is_ustar(TarOne),
ok = erl_tar:t(TarOne),
ok = erl_tar:tt(TarOne),
- {ok,[FileOne,"second file",FileThree,"chunked",ADir,SomeContent]} = erl_tar:table(TarOne),
+ Expected = {ok,[FileOne,"second file",FileThree,"chunked",ADir,SomeContent]},
+ Expected = erl_tar:table(TarOne),
delete_files(["oac_file","oac_small","oac_big",Dir,AnotherDir,ADir]),
@@ -718,6 +812,41 @@ memory(Config) when is_list(Config) ->
ok = delete_files([Name1,Name2]),
ok.
+read_other_implementations(Config) when is_list(Config) ->
+ DataDir = proplists:get_value(data_dir, Config),
+ Files = ["v7.tar", "gnu.tar", "bsd.tar",
+ "star.tar", "pax_mtime.tar"],
+ do_read_other_implementations(Files, DataDir).
+
+do_read_other_implementations([], _DataDir) ->
+ ok;
+do_read_other_implementations([File|Rest], DataDir) ->
+ io:format("~nTrying ~s", [File]),
+ Full = filename:join(DataDir, File),
+ {ok, _} = erl_tar:table(Full),
+ {ok, _} = erl_tar:extract(Full, [memory]),
+ do_read_other_implementations(Rest, DataDir).
+
+
+%% Test handling of sparse files
+sparse(Config) when is_list(Config) ->
+ DataDir = proplists:get_value(data_dir, Config),
+ PrivDir = proplists:get_value(priv_dir, Config),
+ Sparse01Empty = "sparse01_empty.tar",
+ Sparse01 = "sparse01.tar",
+ Sparse10Empty = "sparse10_empty.tar",
+ Sparse10 = "sparse10.tar",
+ do_sparse([Sparse01Empty, Sparse01, Sparse10Empty, Sparse10], DataDir, PrivDir).
+
+do_sparse([], _DataDir, _PrivDir) ->
+ ok;
+do_sparse([Name|Rest], DataDir, PrivDir) ->
+ io:format("~nTrying sparse file ~s", [Name]),
+ Full = filename:join(DataDir, Name),
+ {ok, [_]} = erl_tar:table(Full),
+ {ok, _} = erl_tar:extract(Full, [memory]),
+ do_sparse(Rest, DataDir, PrivDir).
+
%% Test filenames with characters outside the US ASCII range.
unicode(Config) when is_list(Config) ->
run_unicode_node(Config, "+fnu"),
@@ -753,6 +882,9 @@ do_unicode(PrivDir) ->
Names = lists:sort(unicode_create_files()),
Tar = "unicöde.tar",
ok = erl_tar:create(Tar, ["unicöde"], []),
+
+ %% Unicode filenames require PAX format.
+ false = is_ustar(Tar),
{ok,Names0} = erl_tar:table(Tar, []),
Names = lists:sort(Names0),
_ = [ok = file:delete(Name) || Name <- Names],
@@ -850,3 +982,15 @@ start_node(Name, Args) ->
ct:log("Node ~p started~n", [Node]),
Node
end.
+
+%% Test that the given tar file is a plain USTAR archive,
+%% without any PAX extensions.
+is_ustar(File) ->
+ {ok,Bin} = file:read_file(File),
+ <<_:257/binary,"ustar",0,_/binary>> = Bin,
+ <<_:156/binary,Type:8,_/binary>> = Bin,
+ case Type of
+ $x -> false;
+ $g -> false;
+ _ -> true
+ end.
diff --git a/lib/stdlib/test/tar_SUITE_data/bsd.tar b/lib/stdlib/test/tar_SUITE_data/bsd.tar
new file mode 100644
index 0000000000..8c31864be0
--- /dev/null
+++ b/lib/stdlib/test/tar_SUITE_data/bsd.tar
Binary files differ
diff --git a/lib/stdlib/test/tar_SUITE_data/gnu.tar b/lib/stdlib/test/tar_SUITE_data/gnu.tar
new file mode 100644
index 0000000000..60268065c1
--- /dev/null
+++ b/lib/stdlib/test/tar_SUITE_data/gnu.tar
Binary files differ
diff --git a/lib/stdlib/test/tar_SUITE_data/pax_mtime.tar b/lib/stdlib/test/tar_SUITE_data/pax_mtime.tar
new file mode 100644
index 0000000000..1b6e80ffac
--- /dev/null
+++ b/lib/stdlib/test/tar_SUITE_data/pax_mtime.tar
Binary files differ
diff --git a/lib/stdlib/test/dets_SUITE_data/version_r3b02.dets b/lib/stdlib/test/tar_SUITE_data/sparse00.tar
index 058cd15b31..61a04de90b 100644
--- a/lib/stdlib/test/dets_SUITE_data/version_r3b02.dets
+++ b/lib/stdlib/test/tar_SUITE_data/sparse00.tar
Binary files differ
diff --git a/lib/stdlib/test/dets_SUITE_data/dets_test_v8b.dets b/lib/stdlib/test/tar_SUITE_data/sparse01.tar
index d0aa20fe06..61a04de90b 100644
--- a/lib/stdlib/test/dets_SUITE_data/dets_test_v8b.dets
+++ b/lib/stdlib/test/tar_SUITE_data/sparse01.tar
Binary files differ
diff --git a/lib/stdlib/test/tar_SUITE_data/sparse01_empty.tar b/lib/stdlib/test/tar_SUITE_data/sparse01_empty.tar
new file mode 100644
index 0000000000..efa6d060f4
--- /dev/null
+++ b/lib/stdlib/test/tar_SUITE_data/sparse01_empty.tar
Binary files differ
diff --git a/lib/stdlib/test/dets_SUITE_data/dets_test_v8b_little_endian.dets b/lib/stdlib/test/tar_SUITE_data/sparse10.tar
index bf490afa1a..61a04de90b 100644
--- a/lib/stdlib/test/dets_SUITE_data/dets_test_v8b_little_endian.dets
+++ b/lib/stdlib/test/tar_SUITE_data/sparse10.tar
Binary files differ
diff --git a/lib/stdlib/test/tar_SUITE_data/sparse10_empty.tar b/lib/stdlib/test/tar_SUITE_data/sparse10_empty.tar
new file mode 100644
index 0000000000..efa6d060f4
--- /dev/null
+++ b/lib/stdlib/test/tar_SUITE_data/sparse10_empty.tar
Binary files differ
diff --git a/lib/stdlib/test/tar_SUITE_data/star.tar b/lib/stdlib/test/tar_SUITE_data/star.tar
new file mode 100644
index 0000000000..b0631e3b13
--- /dev/null
+++ b/lib/stdlib/test/tar_SUITE_data/star.tar
Binary files differ
diff --git a/lib/stdlib/test/tar_SUITE_data/v7.tar b/lib/stdlib/test/tar_SUITE_data/v7.tar
new file mode 100644
index 0000000000..9918e006bb
--- /dev/null
+++ b/lib/stdlib/test/tar_SUITE_data/v7.tar
Binary files differ
diff --git a/lib/stdlib/test/timer_SUITE.erl b/lib/stdlib/test/timer_SUITE.erl
index 5fc95b16a6..9062cbae80 100644
--- a/lib/stdlib/test/timer_SUITE.erl
+++ b/lib/stdlib/test/timer_SUITE.erl
@@ -353,7 +353,7 @@ res_combine({error,Es}, [{error,E}|T]) ->
system_time() ->
- erlang:monotonic_time(milli_seconds).
+ erlang:monotonic_time(millisecond).
%% ------------------------------------------------------- %%
diff --git a/lib/stdlib/test/timer_simple_SUITE.erl b/lib/stdlib/test/timer_simple_SUITE.erl
index ff5116b8b6..1a582ae95a 100644
--- a/lib/stdlib/test/timer_simple_SUITE.erl
+++ b/lib/stdlib/test/timer_simple_SUITE.erl
@@ -457,7 +457,7 @@ append([],X) ->
X.
system_time() ->
- erlang:monotonic_time(micro_seconds).
+ erlang:monotonic_time(microsecond).
%% ------------------------------------------------------- %%
diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl
index 1dfcda4ed0..f0feda217a 100644
--- a/lib/stdlib/test/zip_SUITE.erl
+++ b/lib/stdlib/test/zip_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2017. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2016. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.