aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/ets_SUITE.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test/ets_SUITE.erl')
-rw-r--r--lib/stdlib/test/ets_SUITE.erl844
1 files changed, 621 insertions, 223 deletions
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 00e02a06cc..5b7a4eca55 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1996-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.
@@ -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,
@@ -39,8 +39,9 @@
-export([lookup_element_mult/1]).
-export([foldl_ordered/1, foldr_ordered/1, foldl/1, foldr/1, fold_empty/1]).
-export([t_delete_object/1, t_init_table/1, t_whitebox/1,
+ select_bound_chunk/1,
t_delete_all_objects/1, t_insert_list/1, t_test_ms/1,
- t_select_delete/1,t_ets_dets/1]).
+ t_select_delete/1,t_select_replace/1,t_select_replace_next_bug/1,t_ets_dets/1]).
-export([ordered/1, ordered_match/1, interface_equality/1,
fixtable_next/1, fixtable_insert/1, rename/1, rename_unnamed/1, evil_rename/1,
@@ -57,6 +58,7 @@
-export([otp_5340/1]).
-export([otp_6338/1]).
-export([otp_6842_select_1000/1]).
+-export([select_mbuf_trapping/1]).
-export([otp_7665/1]).
-export([meta_wb/1]).
-export([grow_shrink/1, grow_pseudo_deleted/1, shrink_pseudo_deleted/1]).
@@ -64,7 +66,7 @@
meta_lookup_named_read/1, meta_lookup_named_write/1,
meta_newdel_unnamed/1, meta_newdel_named/1]).
-export([smp_insert/1, smp_fixed_delete/1, smp_unfix_fix/1, smp_select_delete/1,
- otp_8166/1, otp_8732/1]).
+ smp_select_replace/1, otp_8166/1, otp_8732/1]).
-export([exit_large_table_owner/1,
exit_many_large_table_owner/1,
exit_many_tables_owner/1,
@@ -75,46 +77,25 @@
-export([otp_9423/1]).
-export([otp_10182/1]).
-export([ets_all/1]).
--export([memory_check_summary/1]).
+-export([massive_ets_all/1]).
-export([take/1]).
-export([init_per_testcase/2, end_per_testcase/2]).
%% Convenience for manual testing
-export([random_test/0]).
-%% internal exports
--export([dont_make_worse_sub/0, make_better_sub1/0, make_better_sub2/0]).
--export([t_repair_continuation_do/1, 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").
-define(m(A,B), assert_eq(A,B)).
+-define(heap_binary_size, 64).
init_per_testcase(Case, Config) ->
rand:seed(exsplus),
io:format("*** SEED: ~p ***\n", [rand:export_seed()]),
start_spawn_logger(),
wait_for_test_procs(), %% Ensure previous case cleaned up
- put('__ETS_TEST_CASE__', Case),
[{test_case, Case} | Config].
end_per_testcase(_Func, _Config) ->
@@ -139,15 +120,18 @@ all() ->
update_counter_with_default, partly_bound,
update_counter_table_growth,
match_heavy, {group, fold}, member, t_delete_object,
+ select_bound_chunk,
t_init_table, t_whitebox, t_delete_all_objects,
- t_insert_list, t_test_ms, t_select_delete, t_ets_dets,
- memory, t_select_reverse, t_bucket_disappears,
+ t_insert_list, t_test_ms, t_select_delete, t_select_replace,
+ t_select_replace_next_bug,
+ t_ets_dets, memory, t_select_reverse, t_bucket_disappears,
select_fail, t_insert_new, t_repair_continuation,
otp_5340, otp_6338, otp_6842_select_1000, otp_7665,
+ select_mbuf_trapping,
otp_8732, meta_wb, grow_shrink, grow_pseudo_deleted,
shrink_pseudo_deleted, {group, meta_smp}, smp_insert,
- smp_fixed_delete, smp_unfix_fix, smp_select_delete,
- otp_8166, exit_large_table_owner,
+ smp_fixed_delete, smp_unfix_fix, smp_select_replace,
+ smp_select_delete, otp_8166, exit_large_table_owner,
exit_many_large_table_owner, exit_many_tables_owner,
exit_many_many_tables_owner, write_concurrency, heir,
give_away, setopts, bad_table, types,
@@ -155,9 +139,8 @@ all() ->
otp_9932,
otp_9423,
ets_all,
- take,
-
- memory_check_summary]. % MUST BE LAST
+ massive_ets_all,
+ take].
groups() ->
[{new, [],
@@ -202,33 +185,12 @@ init_per_group(_GroupName, Config) ->
end_per_group(_GroupName, Config) ->
Config.
-%% Test that we did not have "too many" failed verify_etsmem()'s
-%% in the test suite.
-%% verify_etsmem() may give a low number of false positives
-%% as concurrent activities, such as lingering processes
-%% from earlier test suites, may do unrelated ets (de)allocations.
-memory_check_summary(_Config) ->
- case whereis(ets_test_spawn_logger) of
- undefined ->
- ct:fail("No spawn logger exist");
- _ ->
- ets_test_spawn_logger ! {self(), get_failed_memchecks},
- receive {get_failed_memchecks, FailedMemchecks} -> ok end,
- io:format("Failed memchecks: ~p\n",[FailedMemchecks]),
- NoFailedMemchecks = length(FailedMemchecks),
- if NoFailedMemchecks > 3 ->
- ct:fail("Too many failed (~p) memchecks", [NoFailedMemchecks]);
- true ->
- ok
- end
- end.
-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% 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 +358,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 +385,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 +531,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 +558,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 +584,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 +600,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 +621,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 +659,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) ->
@@ -739,6 +701,15 @@ whitebox_2(Opts) ->
ets:delete(T2),
ok.
+select_bound_chunk(Config) ->
+ repeat_for_opts(fun select_bound_chunk_do/1, [all_types]).
+
+select_bound_chunk_do(Opts) ->
+ T = ets:new(x, Opts),
+ ets:insert(T, [{key, 1}]),
+ {[{key, 1}], '$end_of_table'} = ets:select(T, [{{key,1},[],['$_']}], 100000),
+ ok.
+
%% Test ets:to/from_dets.
t_ets_dets(Config) when is_list(Config) ->
@@ -780,7 +751,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 +785,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 +858,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 +934,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) ->
@@ -1180,6 +1151,250 @@ t_select_delete(Config) when is_list(Config) ->
lists:foreach(fun(Tab) -> ets:delete(Tab) end,Tables),
verify_etsmem(EtsMem).
+%% Tests the ets:select_replace/2 BIF
+t_select_replace(Config) when is_list(Config) ->
+ EtsMem = etsmem(),
+ Tables = fill_sets_int(10000) ++ fill_sets_int(10000, [{write_concurrency,true}]),
+
+ TestFun = fun (Table, TableType) when TableType =:= bag ->
+ % Operation not supported; bag implementation
+ % presented both semantic consistency and performance issues.
+ 10000 = ets:select_delete(Table, [{'_',[],[true]}]);
+
+ (Table, TableType) ->
+ % Invalid replacement doesn't keep the key
+ MatchSpec1 = [{{'$1', '$2'},
+ [{'=:=', {'band', '$1', 2#11}, 2#11},
+ {'=/=', {'hd', '$2'}, $x}],
+ [{{'$2', '$1'}}]}],
+ {'EXIT',{badarg,_}} = (catch ets:select_replace(Table, MatchSpec1)),
+
+ % Invalid replacement doesn't keep the key (even though it would be the same value)
+ MatchSpec2 = [{{'$1', '$2'},
+ [{'=:=', {'band', '$1', 2#11}, 2#11}],
+ [{{{'+', '$1', 0}, '$2'}}]},
+ {{'$1', '$2'},
+ [{'=/=', {'band', '$1', 2#11}, 2#11}],
+ [{{{'-', '$1', 0}, '$2'}}]}],
+ {'EXIT',{badarg,_}} = (catch ets:select_replace(Table, MatchSpec2)),
+
+ % Invalid replacement changes key to float equivalent
+ MatchSpec3 = [{{'$1', '$2'},
+ [{'=:=', {'band', '$1', 2#11}, 2#11},
+ {'=/=', {'hd', '$2'}, $x}],
+ [{{{'*', '$1', 1.0}, '$2'}}]}],
+ {'EXIT',{badarg,_}} = (catch ets:select_replace(Table, MatchSpec3)),
+
+ % Replacements are differently-sized tuples
+ MatchSpec4_A = [{{'$1','$2'},
+ [{'<', {'rem', '$1', 5}, 2}],
+ [{{'$1', [$x | '$2'], stuff}}]}],
+ MatchSpec4_B = [{{'$1','$2','_'},
+ [],
+ [{{'$1','$2'}}]}],
+ 4000 = ets:select_replace(Table, MatchSpec4_A),
+ 4000 = ets:select_replace(Table, MatchSpec4_B),
+
+ % Replacement is the same tuple
+ MatchSpec5 = [{{'$1', '$2'},
+ [{'>', {'rem', '$1', 5}, 3}],
+ ['$_']}],
+ 2000 = ets:select_replace(Table, MatchSpec5),
+
+ % Replacement reconstructs an equal tuple
+ MatchSpec6 = [{{'$1', '$2'},
+ [{'>', {'rem', '$1', 5}, 3}],
+ [{{'$1', '$2'}}]}],
+ 2000 = ets:select_replace(Table, MatchSpec6),
+
+ % Replacement uses {element,KeyPos,T} for key
+ 2000 = ets:select_replace(Table,
+ [{{'$1', '$2'},
+ [{'>', {'rem', '$1', 5}, 3}],
+ [{{{element, 1, '$_'}, '$2'}}]}]),
+
+ % Replacement uses wrong {element,KeyPos,T} for key
+ {'EXIT',{badarg,_}} = (catch ets:select_replace(Table,
+ [{{'$1', '$2'},
+ [],
+ [{{{element, 2, '$_'}, '$2'}}]}])),
+
+ check(Table,
+ fun ({N, [$x, C | _]}) when ((N rem 5) < 2) -> (C >= $0) andalso (C =< $9);
+ ({N, [C | _]}) when is_float(N) -> (C >= $0) andalso (C =< $9);
+ ({N, [C | _]}) when ((N rem 5) > 3) -> (C >= $0) andalso (C =< $9);
+ ({_, [C | _]}) -> (C >= $0) andalso (C =< $9)
+ end,
+ 10000),
+
+ % Replace unbound range (>)
+ MatchSpec7 = [{{'$1', '$2'},
+ [{'>', '$1', 7000}],
+ [{{'$1', {{gt_range, '$2'}}}}]}],
+ 3000 = ets:select_replace(Table, MatchSpec7),
+
+ % Replace unbound range (<)
+ MatchSpec8 = [{{'$1', '$2'},
+ [{'<', '$1', 3000}],
+ [{{'$1', {{le_range, '$2'}}}}]}],
+ case TableType of
+ ordered_set -> 2999 = ets:select_replace(Table, MatchSpec8);
+ set -> 2999 = ets:select_replace(Table, MatchSpec8);
+ duplicate_bag -> 2998 = ets:select_replace(Table, MatchSpec8)
+ end,
+
+ % Replace bound range
+ MatchSpec9 = [{{'$1', '$2'},
+ [{'>=', '$1', 3001},
+ {'<', '$1', 7000}],
+ [{{'$1', {{range, '$2'}}}}]}],
+ case TableType of
+ ordered_set -> 3999 = ets:select_replace(Table, MatchSpec9);
+ set -> 3999 = ets:select_replace(Table, MatchSpec9);
+ duplicate_bag -> 3998 = ets:select_replace(Table, MatchSpec9)
+ end,
+
+ % Replace particular keys
+ MatchSpec10 = [{{'$1', '$2'},
+ [{'==', '$1', 3000}],
+ [{{'$1', {{specific1, '$2'}}}}]},
+ {{'$1', '$2'},
+ [{'==', '$1', 7000}],
+ [{{'$1', {{specific2, '$2'}}}}]}],
+ case TableType of
+ ordered_set -> 2 = ets:select_replace(Table, MatchSpec10);
+ set -> 2 = ets:select_replace(Table, MatchSpec10);
+ duplicate_bag -> 4 = ets:select_replace(Table, MatchSpec10)
+ end,
+
+ check(Table,
+ fun ({N, {gt_range, _}}) -> N > 7000;
+ ({N, {le_range, _}}) -> N < 3000;
+ ({N, {range, _}}) -> (N >= 3001) andalso (N < 7000);
+ ({N, {specific1, _}}) -> N == 3000;
+ ({N, {specific2, _}}) -> N == 7000
+ end,
+ 10000),
+
+ 10000 = ets:select_delete(Table, [{'_',[],[true]}]),
+ check(Table, fun (_) -> false end, 0)
+ end,
+
+ lists:foreach(
+ fun(Table) ->
+ TestFun(Table, ets:info(Table, type)),
+ ets:delete(Table)
+ end,
+ Tables),
+
+ %% Test key-safe match-specs are accepted
+ BigNum = (123 bsl 123),
+ RefcBin = list_to_binary(lists:seq(1,?heap_binary_size+1)),
+ Terms = [a, "hej", 123, 1.23, BigNum , <<"123">>, RefcBin, TestFun, self()],
+ EqPairs = fun(X,Y) ->
+ [{ '$1', '$1'},
+ { {X, Y}, {{X, Y}}},
+ { {'$1', Y}, {{'$1', Y}}},
+ { {{X, Y}}, {{{{X, Y}}}}},
+ { {X}, {{X}}},
+ { X, {const, X}},
+ { {X,Y}, {const, {X,Y}}},
+ { {X}, {const, {X}}},
+ { {X, Y}, {{X, {const, Y}}}},
+ { {X, {Y,'$1'}}, {{{const, X}, {{Y,'$1'}}}}},
+ { [X, Y | '$1'], [X, Y | '$1']},
+ { [{X, '$1'}, Y], [{{X, '$1'}}, Y]},
+ { [{X, Y} | '$1'], [{const, {X, Y}} | '$1']},
+ { [$p,$r,$e,$f,$i,$x | '$1'], [$p,$r,$e,$f,$i,$x | '$1']},
+ { {[{X,Y}]}, {{[{{X,Y}}]}}},
+ { {[{X,Y}]}, {{{const, [{X,Y}]}}}},
+ { {[{X,Y}]}, {{[{const,{X,Y}}]}}}
+ ]
+ end,
+
+ T2 = ets:new(x, []),
+ [lists:foreach(fun({A, B}) ->
+ %% just check that matchspec is accepted
+ 0 = ets:select_replace(T2, [{{A, '$2', '$3'}, [], [{{B, '$3', '$2'}}]}])
+ end,
+ EqPairs(X,Y)) || X <- Terms, Y <- Terms],
+
+ %% Test key-unsafe matchspecs are rejected
+ NeqPairs = fun(X, Y) ->
+ [{'$1', '$2'},
+ {{X, Y}, {X, Y}},
+ {{{X, Y}}, {{{X, Y}}}},
+ {{X}, {{{X}}}},
+ {{const, X}, {const, X}},
+ {{const, {X,Y}}, {const, {X,Y}}},
+ {'$1', {const, '$1'}},
+ {{X}, {const, {{X}}}},
+ {{X, {Y,'$1'}}, {{{const, X}, {Y,'$1'}}}},
+ {[X, Y | '$1'], [X, Y]},
+ {[X, Y], [X, Y | '$1']},
+ {[{X, '$1'}, Y], [{X, '$1'}, Y]},
+ {[$p,$r,$e,$f,$i,$x | '$1'], [$p,$r,$e,$f,$I,$x | '$1']},
+ { {[{X,Y}]}, {{[{X,Y}]}}},
+ { {[{X,Y}]}, {{{const, [{{X,Y}}]}}}},
+ { {[{X,Y}]}, {{[{const,{{X,Y}}}]}}},
+ {'_', '_'},
+ {'$_', '$_'},
+ {'$$', '$$'},
+ {#{}, #{}},
+ {#{X => '$1'}, #{X => '$1'}}
+ ]
+ end,
+
+ [lists:foreach(fun({A, B}) ->
+ %% just check that matchspec is rejected
+ {'EXIT',{badarg,_}} = (catch ets:select_replace(T2, [{{A, '$2', '$3'}, [], [{{B, '$3', '$2'}}]}]))
+ end,
+ NeqPairs(X,Y)) || X <- Terms, Y <- Terms],
+
+
+ %% Wrap entire tuple with 'const'
+ [[begin
+ Old = {Key, 1, 2},
+ ets:insert(T2, Old),
+ 1 = ets:select_replace(T2, [{Old, [], [{const, New}]}]),
+ [New] = ets:lookup(T2, Key),
+ ets:delete(T2, Key)
+ end || New <- [{Key, 1, 2}, {Key, 3, 4}, {Key, 1}, {Key, 1, 2, 3}, {Key}]
+ ]
+ || Key <- [{1, tuple}, {nested, {tuple, {a,b}}} | Terms]],
+
+ %% 'const' wrap does not work with maps or variables in keys
+ [[begin
+ Old = {Key, 1, 2},
+ {'EXIT',{badarg,_}} = (catch ets:select_replace(T2, [{Old, [], [{const, New}]}]))
+ end || New <- [{Key, 1, 2}, {Key, 3, 4}, {Key, 1}, {Key, 1, 2, 3}, {Key}]
+ ]
+ || Key <- [#{a => 1}, {nested, #{a => 1}}, '$1']],
+
+
+ ets:delete(T2),
+
+ verify_etsmem(EtsMem).
+
+%% OTP-15346: Bug caused select_replace of bound key to corrupt static stack
+%% used by ets:next and ets:prev.
+t_select_replace_next_bug(Config) when is_list(Config) ->
+ T = ets:new(k, [ordered_set]),
+ [ets:insert(T, {I, value}) || I <- lists:seq(1,10)],
+ 1 = ets:first(T),
+
+ %% Make sure select_replace does not leave pointer
+ %% to deallocated {2,value} in static stack.
+ MS = [{{2,value}, [], [{{2,"new_value"}}]}],
+ 1 = ets:select_replace(T, MS),
+
+ %% This would crash or give wrong result at least on DEBUG emulator
+ %% where deallocated memory is overwritten.
+ 2 = ets:next(T, 1),
+
+ ets:delete(T).
+
+
%% Test that partly bound keys gives faster matches.
partly_bound(Config) when is_list(Config) ->
case os:type() of
@@ -1193,7 +1408,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 +1420,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 +1707,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 +1869,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 +2090,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 +2124,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 +2137,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 +2175,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 +2186,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 +2327,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 +2467,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 +2548,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 +2698,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 +2713,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 +2789,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 +2853,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 +2899,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 +3025,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 +3111,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 +3124,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 +3148,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 +3182,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 +3274,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 +3312,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 +3330,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 +3522,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 +3704,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 +3722,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 +3747,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 +3805,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 +3830,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 +3866,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 +3893,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 +3993,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 +4029,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 +4047,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 +4105,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 +4137,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 +4203,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 +4469,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 +4492,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 +4520,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 +4532,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 +4605,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 +4674,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) ->
[];
@@ -4811,9 +5044,64 @@ otp_6338(Config) when is_list(Config) ->
[[4839,recv]] = ets:match(T,{[{sbm,ppb2_bs12@blade_0_8},'$1'],'$2'}),
ets:delete(T).
+%% OTP-15660: Verify select not doing excessive trapping
+%% when process have mbuf heap fragments.
+select_mbuf_trapping(Config) when is_list(Config) ->
+ select_mbuf_trapping_do(set),
+ select_mbuf_trapping_do(ordered_set).
+
+select_mbuf_trapping_do(Type) ->
+ T = ets:new(xxx, [Type]),
+ NKeys = 50,
+ [ets:insert(T, {K, value}) || K <- lists:seq(1,NKeys)],
+
+ {priority, Prio} = process_info(self(), priority),
+ Tracee = self(),
+ [SchedTracer]
+ = start_loopers(1, Prio,
+ fun (SC) ->
+ receive
+ {trace, Tracee, out, _} ->
+ SC+1;
+ done ->
+ Tracee ! {schedule_count, SC},
+ exit(normal)
+ end
+ end,
+ 0),
+
+ erlang:garbage_collect(),
+ 1 = erlang:trace(self(), true, [running,{tracer,SchedTracer}]),
+
+ %% Artificially create an mbuf heap fragment
+ MbufTerm = "Frag me up",
+ MbufTerm = erts_debug:set_internal_state(mbuf, MbufTerm),
+
+ Keys = ets:select(T, [{{'$1', value}, [], ['$1']}]),
+ NKeys = length(Keys),
+
+ 1 = erlang:trace(self(), false, [running]),
+ Ref = erlang:trace_delivered(Tracee),
+ receive
+ {trace_delivered, Tracee, Ref} ->
+ SchedTracer ! done
+ end,
+ receive
+ {schedule_count, N} ->
+ io:format("~p context switches: ~p", [Type,N]),
+ if
+ N < 3 -> ok;
+ true -> ct:fail(failed)
+ end
+ end,
+ true = ets:delete(T),
+ ok.
+
+
+
%% 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 +5137,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 +5167,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).
@@ -5093,7 +5381,7 @@ meta_lookup_unnamed_read(Config) when is_list(Config) ->
end,
FiniF = fun(Tab) -> true = ets:delete(Tab)
end,
- run_workers(InitF,ExecF,FiniF,10000).
+ run_smp_workers(InitF,ExecF,FiniF,10000).
meta_lookup_unnamed_write(Config) when is_list(Config) ->
InitF = fun(_) -> Tab = ets_new(unnamed,[]),
@@ -5104,7 +5392,7 @@ meta_lookup_unnamed_write(Config) when is_list(Config) ->
end,
FiniF = fun({Tab,_}) -> true = ets:delete(Tab)
end,
- run_workers(InitF,ExecF,FiniF,10000).
+ run_smp_workers(InitF,ExecF,FiniF,10000).
meta_lookup_named_read(Config) when is_list(Config) ->
InitF = fun([ProcN|_]) -> Name = list_to_atom(integer_to_list(ProcN)),
@@ -5117,7 +5405,7 @@ meta_lookup_named_read(Config) when is_list(Config) ->
end,
FiniF = fun(Tab) -> true = ets:delete(Tab)
end,
- run_workers(InitF,ExecF,FiniF,10000).
+ run_smp_workers(InitF,ExecF,FiniF,10000).
meta_lookup_named_write(Config) when is_list(Config) ->
InitF = fun([ProcN|_]) -> Name = list_to_atom(integer_to_list(ProcN)),
@@ -5129,7 +5417,7 @@ meta_lookup_named_write(Config) when is_list(Config) ->
end,
FiniF = fun({Tab,_}) -> true = ets:delete(Tab)
end,
- run_workers(InitF,ExecF,FiniF,10000).
+ run_smp_workers(InitF,ExecF,FiniF,10000).
meta_newdel_unnamed(Config) when is_list(Config) ->
InitF = fun(_) -> ok end,
@@ -5137,7 +5425,7 @@ meta_newdel_unnamed(Config) when is_list(Config) ->
true = ets:delete(Tab)
end,
FiniF = fun(_) -> ok end,
- run_workers(InitF,ExecF,FiniF,10000).
+ run_smp_workers(InitF,ExecF,FiniF,10000).
meta_newdel_named(Config) when is_list(Config) ->
InitF = fun([ProcN|_]) -> list_to_atom(integer_to_list(ProcN))
@@ -5147,7 +5435,7 @@ meta_newdel_named(Config) when is_list(Config) ->
Name
end,
FiniF = fun(_) -> ok end,
- run_workers(InitF,ExecF,FiniF,10000).
+ run_smp_workers(InitF,ExecF,FiniF,10000).
%% Concurrent insert's on same table.
smp_insert(Config) when is_list(Config) ->
@@ -5156,7 +5444,7 @@ smp_insert(Config) when is_list(Config) ->
ExecF = fun(_) -> true = ets:insert(smp_insert,{rand:uniform(10000)})
end,
FiniF = fun(_) -> ok end,
- run_workers(InitF,ExecF,FiniF,100000),
+ run_smp_workers(InitF,ExecF,FiniF,100000),
verify_table_load(smp_insert),
ets:delete(smp_insert).
@@ -5179,7 +5467,7 @@ smp_fixed_delete_do() ->
{Key+Increment,Increment}
end,
FiniF = fun(_) -> ok end,
- run_workers_do(InitF,ExecF,FiniF,NumOfObjs),
+ run_sched_workers(InitF,ExecF,FiniF,NumOfObjs),
0 = ets:info(T,size),
true = ets:info(T,fixed),
Buckets = num_of_buckets(T),
@@ -5359,12 +5647,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;
@@ -5420,7 +5708,7 @@ smp_select_delete(Config) when is_list(Config) ->
end
end,
FiniF = fun(Result) -> Result end,
- Results = run_workers_do(InitF,ExecF,FiniF,20000),
+ Results = run_sched_workers(InitF,ExecF,FiniF,20000),
TotCnts = lists:foldl(fun(Diffs, Sum) -> add_lists(Sum,tuple_to_list(Diffs)) end,
lists:duplicate(Mod, 0), Results),
io:format("TotCnts = ~p\n",[TotCnts]),
@@ -5438,16 +5726,56 @@ 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),
ets:delete(T).
+smp_select_replace(Config) when is_list(Config) ->
+ repeat_for_opts(fun smp_select_replace_do/1,
+ [[set,ordered_set,duplicate_bag]]).
+
+smp_select_replace_do(Opts) ->
+ T = ets_new(smp_select_replace,
+ [public, {write_concurrency, true} | Opts]),
+ ObjCount = 20,
+ InitF = fun (_) -> 0 end,
+ ExecF = fun (Cnt0) ->
+ CounterId = rand:uniform(ObjCount),
+ Match = [{{'$1', '$2'},
+ [{'=:=', '$1', CounterId}],
+ [{{'$1', {'+', '$2', 1}}}]}],
+ Cnt1 = case ets:select_replace(T, Match) of
+ 1 -> Cnt0+1;
+ 0 ->
+ ets:insert_new(T, {CounterId, 0}),
+ Cnt0
+ end,
+ receive stop ->
+ [end_of_work | Cnt1]
+ after 0 ->
+ Cnt1
+ end
+ end,
+ FiniF = fun (Cnt) -> Cnt end,
+ Pids = run_sched_workers(InitF, ExecF, FiniF, infinite),
+ receive after 3*1000 -> ok end,
+ [P ! stop || P <- Pids],
+ Results = wait_pids(Pids),
+ FinalCounts = ets:select(T, [{{'_', '$1'}, [], ['$1']}]),
+ Total = lists:sum(FinalCounts),
+ Total = lists:sum(Results),
+ ObjCount = ets:select_delete(T, [{{'_', '_'}, [], [true]}]),
+ 0 = ets:info(T, size),
+ true = ets:delete(T),
+ ok.
+
%% 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(),
@@ -5506,7 +5834,7 @@ otp_9423(Config) when is_list(Config) ->
end
end,
FiniF = fun(R) -> R end,
- case run_workers(InitF, ExecF, FiniF, infinite, 1) of
+ case run_smp_workers(InitF, ExecF, FiniF, infinite, 1) of
Pids when is_list(Pids) ->
%%[P ! start || P <- Pids],
repeat(fun() -> ets:new(otp_9423, [named_table, public, {write_concurrency,true}]),
@@ -5547,6 +5875,68 @@ ets_all_run() ->
false = lists:member(Table, ets:all()),
ets_all_run().
+create_tables(N) ->
+ create_tables(N, []).
+
+create_tables(0, Ts) ->
+ Ts;
+create_tables(N, Ts) ->
+ create_tables(N-1, [ets:new(tjo, [])|Ts]).
+
+massive_ets_all(Config) when is_list(Config) ->
+ Me = self(),
+ InitTables = lists:sort(ets:all()),
+ io:format("InitTables=~p~n", [InitTables]),
+ PMs0 = lists:map(fun (Sid) ->
+ my_spawn_opt(fun () ->
+ Ts = create_tables(250),
+ Me ! {self(), up, Ts},
+ receive {Me, die} -> ok end
+ end,
+ [link, monitor, {scheduler, Sid}])
+ end,
+ lists:seq(1, erlang:system_info(schedulers_online))),
+ AllRes = lists:sort(lists:foldl(fun ({P, _M}, Ts) ->
+ receive
+ {P, up, PTs} ->
+ PTs ++ Ts
+ end
+ end,
+ InitTables,
+ PMs0)),
+ AllRes = lists:sort(ets:all()),
+ PMs1 = lists:map(fun (_) ->
+ my_spawn_opt(fun () ->
+ AllRes = lists:sort(ets:all())
+ end,
+ [link, monitor])
+ end, lists:seq(1, 50)),
+ lists:foreach(fun ({P, M}) ->
+ receive
+ {'DOWN', M, process, P, _} ->
+ ok
+ end
+ end, PMs1),
+ PMs2 = lists:map(fun (_) ->
+ my_spawn_opt(fun () ->
+ _ = ets:all()
+ end,
+ [link, monitor])
+ end, lists:seq(1, 50)),
+ lists:foreach(fun ({P, _M}) ->
+ P ! {Me, die}
+ end, PMs0),
+ lists:foreach(fun ({P, M}) ->
+ receive
+ {'DOWN', M, process, P, _} ->
+ ok
+ end
+ end, PMs0 ++ PMs2),
+ EndTables = lists:sort(ets:all()),
+ io:format("EndTables=~p~n", [EndTables]),
+ InitTables = EndTables,
+ ok.
+
take(Config) when is_list(Config) ->
%% Simple test for set tables.
@@ -5596,23 +5986,27 @@ add_lists([],[],Acc) ->
add_lists([E1|T1], [E2|T2], Acc) ->
add_lists(T1, T2, [E1+E2 | Acc]).
-run_workers(InitF,ExecF,FiniF,Laps) ->
- run_workers(InitF,ExecF,FiniF,Laps, 0).
-run_workers(InitF,ExecF,FiniF,Laps, Exclude) ->
+run_smp_workers(InitF,ExecF,FiniF,Laps) ->
+ run_smp_workers(InitF,ExecF,FiniF,Laps, 0).
+run_smp_workers(InitF,ExecF,FiniF,Laps, Exclude) ->
case erlang:system_info(smp_support) of
true ->
- run_workers_do(InitF,ExecF,FiniF,Laps, Exclude);
+ case erlang:system_info(schedulers_online) of
+ N when N > Exclude ->
+ run_workers_do(InitF,ExecF,FiniF,Laps, N - Exclude);
+ _ ->
+ {skipped, "Too few schedulers online"}
+ end;
false ->
{skipped,"No smp support"}
end.
-run_workers_do(InitF,ExecF,FiniF,Laps) ->
- run_workers_do(InitF,ExecF,FiniF,Laps, 0).
-run_workers_do(InitF,ExecF,FiniF,Laps, Exclude) ->
- NumOfProcs = case erlang:system_info(schedulers) of
- N when (N > Exclude) -> N - Exclude
- end,
- io:format("smp starting ~p workers\n",[NumOfProcs]),
+run_sched_workers(InitF,ExecF,FiniF,Laps) ->
+ run_workers_do(InitF,ExecF,FiniF,Laps,
+ erlang:system_info(schedulers)).
+
+run_workers_do(InitF,ExecF,FiniF,Laps, NumOfProcs) ->
+ io:format("starting ~p workers\n",[NumOfProcs]),
Seeds = [{ProcN,rand:uniform(9999)} || ProcN <- lists:seq(1,NumOfProcs)],
Parent = self(),
Pids = [my_spawn_link(fun()-> worker(Seed,InitF,ExecF,FiniF,Laps,Parent,NumOfProcs) end)
@@ -5716,25 +6110,39 @@ etsmem() ->
end},
{Mem,AllTabs}.
-verify_etsmem({MemInfo,AllTabs}) ->
+
+verify_etsmem(MI) ->
wait_for_test_procs(),
+ verify_etsmem(MI, 1).
+
+verify_etsmem({MemInfo,AllTabs}, Try) ->
case etsmem() of
{MemInfo,_} ->
io:format("Ets mem info: ~p", [MemInfo]),
- case MemInfo of
- {ErlMem,EtsAlloc} when ErlMem == notsup; EtsAlloc == undefined ->
+ case {MemInfo, Try} 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
+ {_, 1} ->
+ ok;
+ _ ->
+ {comment, "Transient memory discrepancy"}
end;
+
{MemInfo2, AllTabs2} ->
io:format("Expected: ~p", [MemInfo]),
io:format("Actual: ~p", [MemInfo2]),
io:format("Changed tables before: ~p\n",[AllTabs -- AllTabs2]),
io:format("Changed tables after: ~p\n", [AllTabs2 -- AllTabs]),
- ets_test_spawn_logger ! {failed_memcheck, get('__ETS_TEST_CASE__')},
- {comment, "Failed memory check"}
+ case Try < 2 of
+ true ->
+ io:format("\nThis discrepancy could be caused by an "
+ "inconsistent memory \"snapshot\""
+ "\nTry again...\n", []),
+ verify_etsmem({MemInfo, AllTabs}, Try+1);
+ false ->
+ ct:fail("Failed memory check")
+ end
end.
@@ -5756,10 +6164,10 @@ stop_loopers(Loopers) ->
looper(Fun, State) ->
looper(Fun, Fun(State)).
-spawn_logger(Procs, FailedMemchecks) ->
+spawn_logger(Procs) ->
receive
{new_test_proc, Proc} ->
- spawn_logger([Proc|Procs], FailedMemchecks);
+ spawn_logger([Proc|Procs]);
{sync_test_procs, Kill, From} ->
lists:foreach(fun (Proc) when From == Proc ->
ok;
@@ -5783,14 +6191,7 @@ spawn_logger(Procs, FailedMemchecks) ->
end
end, Procs),
From ! test_procs_synced,
- spawn_logger([From], FailedMemchecks);
-
- {failed_memcheck, TestCase} ->
- spawn_logger(Procs, [TestCase|FailedMemchecks]);
-
- {Pid, get_failed_memchecks} ->
- Pid ! {get_failed_memchecks, FailedMemchecks},
- spawn_logger(Procs, FailedMemchecks)
+ spawn_logger([From])
end.
pid_status(Pid) ->
@@ -5806,7 +6207,7 @@ start_spawn_logger() ->
case whereis(ets_test_spawn_logger) of
Pid when is_pid(Pid) -> true;
_ -> register(ets_test_spawn_logger,
- spawn_opt(fun () -> spawn_logger([], []) end,
+ spawn_opt(fun () -> spawn_logger([]) end,
[{priority, max}]))
end.
@@ -5831,12 +6232,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
@@ -5933,7 +6330,6 @@ only_if_smp(Schedulers, Func) ->
end.
%% Copy-paste from emulator/test/binary_SUITE.erl
--define(heap_binary_size, 64).
test_terms(Test_Func, Mode) ->
garbage_collect(),
Pib0 = process_info(self(),binary),
@@ -6079,7 +6475,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 +6611,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 +6647,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.