diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/Makefile | 8 | ||||
-rw-r--r-- | lib/stdlib/test/erl_lint_SUITE.erl | 20 | ||||
-rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 513 | ||||
-rw-r--r-- | lib/stdlib/test/lists_SUITE.erl | 63 |
4 files changed, 411 insertions, 193 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile index bbe3cefa42..712b1b92fb 100644 --- a/lib/stdlib/test/Makefile +++ b/lib/stdlib/test/Makefile @@ -99,11 +99,9 @@ MODULES= \ maps_SUITE \ zzz_SUITE -ERL_FILES= $(MODULES:%=%.erl) +ERTS_MODULES= erts_test_utils -TARGET_FILES= $(MODULES:%=$(EBIN)/%.$(EMULATOR)) - -INSTALL_PROGS= $(TARGET_FILES) +ERL_FILES= $(MODULES:%=%.erl) $(ERTS_MODULES:%=$(ERL_TOP)/erts/emulator/test/%.erl) # ---------------------------------------------------- # Release directory specification @@ -128,7 +126,7 @@ COVERFILE=stdlib.cover # ---------------------------------------------------- make_emakefile: - $(ERL_TOP)/make/make_emakefile $(ERL_COMPILE_FLAGS) -o$(EBIN) $(MODULES) \ + $(ERL_TOP)/make/make_emakefile $(ERL_COMPILE_FLAGS) -o$(EBIN) $(MODULES) $(ERTS_MODULES) \ > $(EMAKEFILE) tests debug opt: make_emakefile diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index c1613a7273..e6ed55bf2d 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -67,7 +67,8 @@ record_errors/1, otp_11879_cont/1, non_latin1_module/1, otp_14323/1, stacktrace_syntax/1, - otp_14285/1, otp_14378/1]). + otp_14285/1, otp_14378/1, + external_funs/1]). suite() -> [{ct_hooks,[ts_install_cth]}, @@ -88,7 +89,7 @@ all() -> maps, maps_type, maps_parallel_match, otp_11851, otp_11879, otp_13230, record_errors, otp_11879_cont, non_latin1_module, otp_14323, - stacktrace_syntax, otp_14285, otp_14378]. + stacktrace_syntax, otp_14285, otp_14378, external_funs]. groups() -> [{unused_vars_warn, [], @@ -4134,6 +4135,21 @@ otp_14285(Config) -> run(Config, Ts), ok. +external_funs(Config) when is_list(Config) -> + Ts = [{external_funs_1, + %% ERL-762: Unused variable warning not being emitted. + <<"f() -> + BugVar = process_info(self()), + if true -> fun m:f/1 end. + f(M, F) -> + BugVar = process_info(self()), + if true -> fun M:F/1 end.">>, + [], + {warnings,[{2,erl_lint,{unused_var,'BugVar'}}, + {5,erl_lint,{unused_var,'BugVar'}}]}}], + run(Config, Ts), + ok. + format_error(E) -> lists:flatten(erl_lint:format_error(E)). diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 2c0692855f..22c77aa172 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -66,6 +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, + smp_ordered_iteration/1, smp_select_replace/1, otp_8166/1, otp_8732/1, delete_unfix_race/1]). -export([throughput_benchmark/0, test_throughput_benchmark/1]). -export([exit_large_table_owner/1, @@ -133,7 +134,8 @@ all() -> otp_5340, otp_6338, otp_6842_select_1000, otp_7665, otp_8732, meta_wb, grow_shrink, grow_pseudo_deleted, shrink_pseudo_deleted, {group, meta_smp}, smp_insert, - smp_fixed_delete, smp_unfix_fix, smp_select_replace, + smp_fixed_delete, smp_unfix_fix, smp_select_replace, + smp_ordered_iteration, smp_select_delete, otp_8166, exit_large_table_owner, exit_many_large_table_owner, exit_many_tables_owner, exit_many_many_tables_owner, write_concurrency, heir, @@ -796,15 +798,16 @@ t_delete_all_objects(Config) when is_list(Config) -> get_kept_objects(T) -> case ets:info(T,stats) of - false -> - 0; {_,_,_,_,_,_,KO} -> - KO + KO; + _ -> + 0 end. t_delete_all_objects_do(Opts) -> - T=ets_new(x,Opts), - filltabint(T,4000), + KeyRange = 4000, + T=ets_new(x, Opts, KeyRange), + filltabint(T,KeyRange), O=ets:first(T), ets:next(T,O), ets:safe_fixtable(T,true), @@ -813,13 +816,13 @@ t_delete_all_objects_do(Opts) -> 0 = ets:info(T,size), case ets:info(T,type) of ordered_set -> ok; - _ -> 4000 = get_kept_objects(T) + _ -> KeyRange = get_kept_objects(T) end, ets:safe_fixtable(T,false), 0 = ets:info(T,size), 0 = get_kept_objects(T), - filltabint(T,4000), - 4000 = ets:info(T,size), + filltabint(T, KeyRange), + KeyRange = ets:info(T,size), true = ets:delete_all_objects(T), 0 = ets:info(T,size), ets:delete(T), @@ -3104,18 +3107,18 @@ setbag(Config) when is_list(Config) -> %% Test case to check proper return values for illegal ets_new() calls. badnew(Config) when is_list(Config) -> EtsMem = etsmem(), - {'EXIT',{badarg,_}} = (catch ets_new(12,[])), - {'EXIT',{badarg,_}} = (catch ets_new({a,b},[])), - {'EXIT',{badarg,_}} = (catch ets_new(name,[foo])), - {'EXIT',{badarg,_}} = (catch ets_new(name,{bag})), - {'EXIT',{badarg,_}} = (catch ets_new(name,bag)), + {'EXIT',{badarg,_}} = (catch ets:new(12,[])), + {'EXIT',{badarg,_}} = (catch ets:new({a,b},[])), + {'EXIT',{badarg,_}} = (catch ets:new(name,[foo])), + {'EXIT',{badarg,_}} = (catch ets:new(name,{bag})), + {'EXIT',{badarg,_}} = (catch ets:new(name,bag)), verify_etsmem(EtsMem). %% OTP-2314. Test case to check that a non-proper list does not %% crash the emulator. verybadnew(Config) when is_list(Config) -> EtsMem = etsmem(), - {'EXIT',{badarg,_}} = (catch ets_new(verybad,[set|protected])), + {'EXIT',{badarg,_}} = (catch ets:new(verybad,[set|protected])), verify_etsmem(EtsMem). %% Small check to see if named tables work. @@ -3464,9 +3467,11 @@ delete_tab_do(Opts) -> %% Check that ets:delete/1 works and that other processes can run. delete_large_tab(Config) when is_list(Config) -> ct:timetrap({minutes,60}), %% valgrind needs a lot - Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)], + KeyRange = 16#ffffff, + Data = [{erlang:phash2(I, KeyRange),I} || I <- lists:seq(1, 200000)], EtsMem = etsmem(), - repeat_for_opts(fun(Opts) -> delete_large_tab_do(Opts,Data) end), + repeat_for_opts(fun(Opts) -> delete_large_tab_do(key_range(Opts,KeyRange), + Data) end), verify_etsmem(EtsMem). delete_large_tab_do(Opts,Data) -> @@ -3542,9 +3547,13 @@ delete_large_tab_2(Name, Flags, Data, Fix) -> %% Delete a large name table and try to create a new table with %% the same name in another process. delete_large_named_table(Config) when is_list(Config) -> - Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)], + KeyRange = 16#ffffff, + Data = [{erlang:phash2(I, KeyRange),I} || I <- lists:seq(1, 200000)], EtsMem = etsmem(), - repeat_for_opts(fun(Opts) -> delete_large_named_table_do(Opts,Data) end), + repeat_for_opts(fun(Opts) -> + delete_large_named_table_do(key_range(Opts,KeyRange), + Data) + end), verify_etsmem(EtsMem), ok. @@ -3585,8 +3594,12 @@ delete_large_named_table_2(Name, Flags, Data, Fix) -> %% Delete a large table, and kill the process during the delete. evil_delete(Config) when is_list(Config) -> - Data = [{I,I*I} || I <- lists:seq(1, 100000)], - repeat_for_opts(fun(Opts) -> evil_delete_do(Opts,Data) end). + KeyRange = 100000, + Data = [{I,I*I} || I <- lists:seq(1, KeyRange)], + repeat_for_opts(fun(Opts) -> + evil_delete_do(key_range(Opts,KeyRange), + Data) + end). evil_delete_do(Opts,Data) -> EtsMem = etsmem(), @@ -4154,19 +4167,12 @@ match_object2(Config) when is_list(Config) -> match_object2_do(Opts) -> EtsMem = etsmem(), - Tab = ets_new(foo, [bag, {keypos, 2} | Opts]), - fill_tab2(Tab, 0, 13005), % match_db_object does 1000 + KeyRange = 13005, + Tab = ets_new(foo, [{keypos, 2} | Opts], KeyRange), + fill_tab2(Tab, 0, KeyRange), % match_db_object does 1000 % elements per pass, might % change in the future. - case catch ets:match_object(Tab, {hej, '$1'}) of - {'EXIT', _} -> - ets:delete(Tab), - ct:fail("match_object EXIT:ed"); - [] -> - io:format("Nothing matched."); - List -> - io:format("Matched:~p~n",[List]) - end, + [] = ets:match_object(Tab, {hej, '$1'}), ets:delete(Tab), verify_etsmem(EtsMem). @@ -4411,10 +4417,11 @@ tab2file2(Config) when is_list(Config) -> tab2file2_do(Opts, Config) -> EtsMem = etsmem(), - Tab = ets_new(ets_SUITE_foo_tab, [named_table, private, - {keypos, 2} | Opts]), + KeyRange = 10000, + Tab = ets_new(ets_SUITE_foo_tab, [named_table, private, {keypos, 2} | Opts], + KeyRange), FName = filename:join([proplists:get_value(priv_dir, Config),"tab2file2_case"]), - ok = fill_tab2(Tab, 0, 10000), % Fill up the table (grucho mucho!) + ok = fill_tab2(Tab, 0, KeyRange), % Fill up the table (grucho mucho!) Len = length(ets:tab2list(Tab)), Mem = ets:info(Tab, memory), Type = ets:info(Tab, type), @@ -4473,8 +4480,9 @@ tabfile_ext1(Config) when is_list(Config) -> tabfile_ext1_do(Opts,Config) -> FName = filename:join([proplists:get_value(priv_dir, Config),"nisse.dat"]), FName2 = filename:join([proplists:get_value(priv_dir, Config),"countflip.dat"]), - L = lists:seq(1,10), - T = ets_new(x,Opts), + KeyRange = 10, + L = lists:seq(1,KeyRange), + T = ets_new(x,Opts,KeyRange), Name = make_ref(), [ets:insert(T,{X,integer_to_list(X)}) || X <- L], ok = ets:tab2file(T,FName,[{extended_info,[object_count]}]), @@ -4511,8 +4519,9 @@ tabfile_ext2(Config) when is_list(Config) -> tabfile_ext2_do(Opts,Config) -> FName = filename:join([proplists:get_value(priv_dir, Config),"olle.dat"]), FName2 = filename:join([proplists:get_value(priv_dir, Config),"bitflip.dat"]), - L = lists:seq(1,10), - T = ets_new(x,Opts), + KeyRange = 10, + L = lists:seq(1, KeyRange), + T = ets_new(x, Opts, KeyRange), Name = make_ref(), [ets:insert(T,{X,integer_to_list(X)}) || X <- L], ok = ets:tab2file(T,FName,[{extended_info,[md5sum]}]), @@ -4681,9 +4690,10 @@ heavy_lookup(Config) when is_list(Config) -> heavy_lookup_do(Opts) -> EtsMem = etsmem(), - Tab = ets_new(foobar_table, [{keypos, 2} | Opts]), - ok = fill_tab2(Tab, 0, 7000), - _ = [do_lookup(Tab, 6999) || _ <- lists:seq(1, 50)], + KeyRange = 7000, + Tab = ets_new(foobar_table, [{keypos, 2} | Opts], KeyRange), + ok = fill_tab2(Tab, 0, KeyRange), + _ = [do_lookup(Tab, KeyRange-1) || _ <- lists:seq(1, 50)], true = ets:delete(Tab), verify_etsmem(EtsMem). @@ -4704,11 +4714,12 @@ heavy_lookup_element(Config) when is_list(Config) -> heavy_lookup_element_do(Opts) -> EtsMem = etsmem(), - Tab = ets_new(foobar_table, [{keypos, 2} | Opts]), - ok = fill_tab2(Tab, 0, 7000), + KeyRange = 7000, + Tab = ets_new(foobar_table, [{keypos, 2} | Opts], KeyRange), + ok = fill_tab2(Tab, 0, KeyRange), %% lookup ALL elements 50 times Laps = 50 div syrup_factor(), - _ = [do_lookup_element(Tab, 6999, 1) || _ <- lists:seq(1, Laps)], + _ = [do_lookup_element(Tab, KeyRange-1, 1) || _ <- lists:seq(1, Laps)], true = ets:delete(Tab), verify_etsmem(EtsMem). @@ -4731,11 +4742,11 @@ heavy_concurrent(Config) when is_list(Config) -> repeat_for_opts_all_set_table_types(fun do_heavy_concurrent/1). do_heavy_concurrent(Opts) -> - Size = 10000, + KeyRange = 10000, Laps = 10000 div syrup_factor(), EtsMem = etsmem(), - Tab = ets_new(blupp, [public, {keypos, 2} | Opts]), - ok = fill_tab2(Tab, 0, Size), + Tab = ets_new(blupp, [public, {keypos, 2} | Opts], KeyRange), + ok = fill_tab2(Tab, 0, KeyRange), Procs = lists:map( fun (N) -> my_spawn_link( @@ -5014,6 +5025,7 @@ filltabint(Tab,0) -> filltabint(Tab,N) -> ets:insert(Tab,{N,integer_to_list(N)}), filltabint(Tab,N-1). + filltabint2(Tab,0) -> Tab; filltabint2(Tab,N) -> @@ -5230,8 +5242,9 @@ gen_dets_filename(Config,N) -> otp_6842_select_1000(Config) when is_list(Config) -> repeat_for_opts_all_ord_set_table_types( fun(Opts) -> - Tab = ets_new(xxx,Opts), - [ets:insert(Tab,{X,X}) || X <- lists:seq(1,10000)], + KeyRange = 10000, + Tab = ets_new(xxx, Opts, KeyRange), + [ets:insert(Tab,{X,X}) || X <- lists:seq(1,KeyRange)], AllTrue = lists:duplicate(10,true), AllTrue = [ length( @@ -5420,7 +5433,7 @@ grow_shrink(Config) when is_list(Config) -> fun(Opts) -> EtsMem = etsmem(), - Set = ets_new(a, Opts), + Set = ets_new(a, Opts, 5000), grow_shrink_0(0, 3071, 3000, 5000, Set), ets:delete(Set), @@ -5449,14 +5462,13 @@ grow_shrink_3(N, ShrinkTo, T) -> true = ets:delete(T, N), grow_shrink_3(N-1, ShrinkTo, T). -%% Grow a table that still contains pseudo-deleted objects. +%% Grow a hash table that still contains pseudo-deleted objects. grow_pseudo_deleted(Config) when is_list(Config) -> only_if_smp(fun() -> grow_pseudo_deleted_do() end). grow_pseudo_deleted_do() -> lists:foreach(fun(Type) -> grow_pseudo_deleted_do(Type) end, - [set,cat_ord_set,stim_cat_ord_set, - ordered_set,bag,duplicate_bag]). + [set,bag,duplicate_bag]). grow_pseudo_deleted_do(Type) -> process_flag(scheduler,1), @@ -5471,12 +5483,7 @@ grow_pseudo_deleted_do(Type) -> [true]}]), Left = Mult*(Mod-1), Left = ets:info(T,size), - case Type of - cat_ord_set -> ok; - stim_cat_ord_set -> ok; - ordered_set -> ok; - _ -> Mult = get_kept_objects(T) - end, + Mult = get_kept_objects(T), filltabstr(T,Mult), my_spawn_opt( fun() -> @@ -5508,14 +5515,13 @@ grow_pseudo_deleted_do(Type) -> ets:delete(T), process_flag(scheduler,0). -%% Shrink a table that still contains pseudo-deleted objects. +%% Shrink a hash table that still contains pseudo-deleted objects. shrink_pseudo_deleted(Config) when is_list(Config) -> only_if_smp(fun()->shrink_pseudo_deleted_do() end). shrink_pseudo_deleted_do() -> lists:foreach(fun(Type) -> shrink_pseudo_deleted_do(Type) end, - [set,cat_ord_set,stim_cat_ord_set, - ordered_set,bag,duplicate_bag]). + [set,bag,duplicate_bag]). shrink_pseudo_deleted_do(Type) -> process_flag(scheduler,1), @@ -5529,12 +5535,7 @@ shrink_pseudo_deleted_do(Type) -> [{'>', '$1', Half}], [true]}]), Half = ets:info(T,size), - case Type of - cat_ord_set -> ok; - stim_cat_ord_set -> ok; - ordered_set -> ok; - _ -> Half = get_kept_objects(T) - end, + Half = get_kept_objects(T), my_spawn_opt( fun()-> true = ets:info(T,fixed), Self ! start, @@ -5638,9 +5639,11 @@ smp_insert(Config) when is_list(Config) -> [[set,ordered_set,stim_cat_ord_set]]). smp_insert_do(Opts) -> - ets_new(smp_insert,[named_table,public,{write_concurrency,true}|Opts]), + KeyRange = 10000, + ets_new(smp_insert,[named_table,public,{write_concurrency,true}|Opts], + KeyRange), InitF = fun(_) -> ok end, - ExecF = fun(_) -> true = ets:insert(smp_insert,{rand:uniform(10000)}) + ExecF = fun(_) -> true = ets:insert(smp_insert,{rand:uniform(KeyRange)}) end, FiniF = fun(_) -> ok end, run_smp_workers(InitF,ExecF,FiniF,100000), @@ -5649,41 +5652,36 @@ smp_insert_do(Opts) -> %% Concurrent deletes on same fixated table. smp_fixed_delete(Config) when is_list(Config) -> - only_if_smp(fun()-> - repeat_for_opts(fun smp_fixed_delete_do/1, - [[set,ordered_set,stim_cat_ord_set]]) - end). - -smp_fixed_delete_do(Opts) -> - begin - T = ets_new(foo,[public,{write_concurrency,true}|Opts]), - %%Mem = ets:info(T,memory), - NumOfObjs = 100000, - filltabint(T,NumOfObjs), - ets:safe_fixtable(T,true), - Buckets = num_of_buckets(T), - InitF = fun([ProcN,NumOfProcs|_]) -> {ProcN,NumOfProcs} end, - ExecF = fun({Key,_}) when Key > NumOfObjs -> - [end_of_work]; - ({Key,Increment}) -> - true = ets:delete(T,Key), - {Key+Increment,Increment} - end, - FiniF = fun(_) -> ok end, - run_sched_workers(InitF,ExecF,FiniF,NumOfObjs), - 0 = ets:info(T,size), - true = ets:info(T,fixed), - Buckets = num_of_buckets(T), - case ets:info(T,type) of - set -> NumOfObjs = get_kept_objects(T); - _ -> ok - end, - ets:safe_fixtable(T,false), - %% Will fail as unfix does not shrink the table: - %%Mem = ets:info(T,memory), - %%verify_table_load(T), - ets:delete(T) - end. + only_if_smp(fun() -> smp_fixed_delete_do() end). + +smp_fixed_delete_do() -> + T = ets_new(foo,[public,{write_concurrency,true}]), + %%Mem = ets:info(T,memory), + NumOfObjs = 100000, + filltabint(T,NumOfObjs), + ets:safe_fixtable(T,true), + Buckets = num_of_buckets(T), + InitF = fun([ProcN,NumOfProcs|_]) -> {ProcN,NumOfProcs} end, + ExecF = fun({Key,_}) when Key > NumOfObjs -> + [end_of_work]; + ({Key,Increment}) -> + true = ets:delete(T,Key), + {Key+Increment,Increment} + end, + FiniF = fun(_) -> ok end, + run_sched_workers(InitF,ExecF,FiniF,NumOfObjs), + 0 = ets:info(T,size), + true = ets:info(T,fixed), + Buckets = num_of_buckets(T), + case ets:info(T,type) of + set -> NumOfObjs = get_kept_objects(T); + _ -> ok + end, + ets:safe_fixtable(T,false), + %% Will fail as unfix does not shrink the table: + %%Mem = ets:info(T,memory), + %%verify_table_load(T), + ets:delete(T). %% ERL-720 %% Provoke race between ets:delete and table unfix (by select_count) @@ -5928,8 +5926,10 @@ verify_table_load(T) -> otp_8732(Config) when is_list(Config) -> repeat_for_all_ord_set_table_types( fun(Opts) -> - Tab = ets_new(noname,Opts), - filltabstr(Tab,999), + KeyRange = 999, + KeyFun = fun(K) -> integer_to_list(K) end, + Tab = ets_new(noname,Opts, KeyRange, KeyFun), + filltabstr(Tab, KeyRange), ets:insert(Tab,{[],"nasty NIL object"}), [] = ets:match(Tab,{'_',nomatch}) %% Will hang if bug not fixed end), @@ -5939,11 +5939,14 @@ otp_8732(Config) when is_list(Config) -> %% Run concurrent select_delete (and inserts) on same table. smp_select_delete(Config) when is_list(Config) -> repeat_for_opts(fun smp_select_delete_do/1, - [[set,ordered_set,stim_cat_ord_set], read_concurrency, compressed]). + [[set,ordered_set,stim_cat_ord_set], + read_concurrency, compressed]). smp_select_delete_do(Opts) -> + KeyRange = 10000, begin % indentation - T = ets_new(smp_select_delete,[named_table,public,{write_concurrency,true}|Opts]), + T = ets_new(smp_select_delete,[named_table,public,{write_concurrency,true}|Opts], + KeyRange), Mod = 17, Zeros = erlang:make_tuple(Mod,0), InitF = fun(_) -> Zeros end, @@ -5960,7 +5963,7 @@ smp_select_delete_do(Opts) -> element(Eq+1,Diffs0) - Deleted), Diffs1; _ -> - Key = rand:uniform(10000), + Key = rand:uniform(KeyRange), Eq = Key rem Mod, case ets:insert_new(T,{Key,Key}) of true -> @@ -6004,12 +6007,13 @@ smp_select_replace(Config) when is_list(Config) -> [[set,ordered_set,stim_cat_ord_set,duplicate_bag]]). smp_select_replace_do(Opts) -> + KeyRange = 20, T = ets_new(smp_select_replace, - [public, {write_concurrency, true} | Opts]), - ObjCount = 20, + [public, {write_concurrency, true} | Opts], + KeyRange), InitF = fun (_) -> 0 end, ExecF = fun (Cnt0) -> - CounterId = rand:uniform(ObjCount), + CounterId = rand:uniform(KeyRange), Match = [{{'$1', '$2'}, [{'=:=', '$1', CounterId}], [{{'$1', {'+', '$2', 1}}}]}], @@ -6033,11 +6037,138 @@ smp_select_replace_do(Opts) -> FinalCounts = ets:select(T, [{{'_', '$1'}, [], ['$1']}]), Total = lists:sum(FinalCounts), Total = lists:sum(Results), - ObjCount = ets:select_delete(T, [{{'_', '_'}, [], [true]}]), + KeyRange = ets:select_delete(T, [{{'_', '_'}, [], [true]}]), 0 = ets:info(T, size), true = ets:delete(T), ok. +%% Iterate ordered_set with write_concurrency +%% and make sure we hit all "stable" long lived keys +%% while "volatile" objects are randomly inserted and deleted. +smp_ordered_iteration(Config) when is_list(Config) -> + repeat_for_opts(fun smp_ordered_iteration_do/1, + [[cat_ord_set,stim_cat_ord_set]]). + + +smp_ordered_iteration_do(Opts) -> + KeyRange = 1000, + OffHeap = erts_test_utils:mk_ext_pid({a@b,1}, 4711, 1), + KeyFun = fun(K, Type) -> + {K div 10, K rem 10, Type, OffHeap} + end, + StimKeyFun = fun(K) -> + KeyFun(K, element(rand:uniform(3), + {stable, other, volatile})) + end, + T = ets_new(smp_ordered_iteration, [public, {write_concurrency,true} | Opts], + KeyRange, StimKeyFun), + NStable = KeyRange div 4, + prefill_table(T, KeyRange, NStable, fun(K) -> {KeyFun(K, stable), 0} end), + NStable = ets:info(T, size), + NVolatile = KeyRange div 2, + prefill_table(T, KeyRange, NVolatile, fun(K) -> {KeyFun(K, volatile), 0} end), + + InitF = fun (_) -> #{insert => 0, delete => 0, + select_delete_bk => 0, select_delete_pbk => 0, + select_replace_bk => 0, select_replace_pbk => 0} + end, + ExecF = fun (Counters) -> + K = rand:uniform(KeyRange), + Key = KeyFun(K, volatile), + Acc = case rand:uniform(22) of + R when R =< 10 -> + ets:insert(T, {Key}), + incr_counter(insert, Counters); + R when R =< 15 -> + ets:delete(T, Key), + incr_counter(delete, Counters); + R when R =< 19 -> + %% Delete bound key + ets:select_delete(T, [{{Key, '_'}, [], [true]}]), + incr_counter(select_delete_bk, Counters); + R when R =< 20 -> + %% Delete partially bound key + ets:select_delete(T, [{{{K div 10, '_', volatile, '_'}, '_'}, [], [true]}]), + incr_counter(select_delete_pbk, Counters); + R when R =< 21 -> + %% Replace bound key + ets:select_replace(T, [{{Key, '$1'}, [], + [{{{const,Key}, {'+','$1',1}}}]}]), + incr_counter(select_replace_bk, Counters); + _ -> + %% Replace partially bound key + ets:select_replace(T, [{{{K div 10, '_', volatile, '_'}, '$1'}, [], + [{{{element,1,'$_'}, {'+','$1',1}}}]}]), + incr_counter(select_replace_pbk, Counters) + end, + receive stop -> + [end_of_work | Acc] + after 0 -> + Acc + end + end, + FiniF = fun (Acc) -> Acc end, + Pids = run_sched_workers(InitF, ExecF, FiniF, infinite), + timer:send_after(1000, stop), + + Log2ChunkMax = math:log2(NStable*2), + Rounds = fun Loop(N) -> + MS = [{{{'_', '_', stable, '_'}, '_'}, [], [true]}], + NStable = ets:select_count(T, MS), + NStable = count_stable(T, next, ets:first(T), 0), + NStable = count_stable(T, prev, ets:last(T), 0), + NStable = length(ets:select(T, MS)), + NStable = length(ets:select_reverse(T, MS)), + Chunk = round(math:pow(2, rand:uniform()*Log2ChunkMax)), + NStable = ets_select_chunks_count(T, MS, Chunk), + receive stop -> N + after 0 -> Loop(N+1) + end + end (1), + [P ! stop || P <- Pids], + Results = wait_pids(Pids), + io:format("Ops = ~p\n", [maps_sum(Results)]), + io:format("Diff = ~p\n", [ets:info(T,size) - NStable - NVolatile]), + io:format("Stats = ~p\n", [ets:info(T,stats)]), + io:format("Rounds = ~p\n", [Rounds]), + true = ets:delete(T), + + %% Verify no leakage of offheap key data + ok = erts_test_utils:check_node_dist(), + ok. + +incr_counter(Name, Counters) -> + Counters#{Name => maps:get(Name, Counters, 0) + 1}. + +count_stable(T, Next, {_, _, stable, _}=Key, N) -> + count_stable(T, Next, ets:Next(T, Key), N+1); +count_stable(T, Next, {_, _, volatile, _}=Key, N) -> + count_stable(T, Next, ets:Next(T, Key), N); +count_stable(_, _, '$end_of_table', N) -> + N. + +ets_select_chunks_count(T, MS, Chunk) -> + ets_select_chunks_count(ets:select(T, MS, Chunk), 0). + +ets_select_chunks_count('$end_of_table', N) -> + N; +ets_select_chunks_count({List, Continuation}, N) -> + ets_select_chunks_count(ets:select(Continuation), + length(List) + N). + +maps_sum([Ma | Tail]) when is_map(Ma) -> + maps_sum([lists:sort(maps:to_list(Ma)) | Tail]); +maps_sum([La, Mb | Tail]) -> + Lab = lists:zipwith(fun({K,Va}, {K,Vb}) -> {K,Va+Vb} end, + La, + lists:sort(maps:to_list(Mb))), + maps_sum([Lab | Tail]); +maps_sum([L]) -> + L. + + + + %% Test different types. types(Config) when is_list(Config) -> init_externals(), @@ -6307,19 +6438,18 @@ do_work(WorksDoneSoFar, Table, ProbHelpTab, Range, Operations) -> do_work(WorksDoneSoFar + 1, Table, ProbHelpTab, Range, Operations) end. -prefill_table(T, KeyRange, Num) -> +prefill_table(T, KeyRange, Num, ObjFun) -> Seed = rand:uniform(KeyRange), %%io:format("prefill_table: Seed = ~p\n", [Seed]), RState = unique_rand_start(KeyRange, Seed), - prefill_table_loop(T, RState, Num), - Num = ets:info(T, size). + prefill_table_loop(T, RState, Num, ObjFun). -prefill_table_loop(_, _, 0) -> +prefill_table_loop(_, _, 0, _) -> ok; -prefill_table_loop(T, RS0, N) -> +prefill_table_loop(T, RS0, N, ObjFun) -> {Key, RS1} = unique_rand_next(RS0), - ets:insert(T, {Key}), - prefill_table_loop(T, RS1, N-1). + ets:insert(T, ObjFun(Key)), + prefill_table_loop(T, RS1, N-1, ObjFun). throughput_benchmark() -> throughput_benchmark(false, not_set, not_set). @@ -6445,7 +6575,9 @@ throughput_benchmark(TestMode, BenchmarkRunMs, RecoverTimeMs) -> Range, Duration, RecoverTime) -> ProbHelpTab = CalculateOpsProbHelpTab(Scenario, 0), Table = ets:new(t, TableConfig), - prefill_table(Table, Range, Range div 2), + Nobj = Range div 2, + prefill_table(Table, Range, Nobj, fun(K) -> {K} end), + Nobj = ets:info(Table, size), SafeFixTableIfRequired(Table, Scenario, true), ParentPid = self(), ChildPids = @@ -7324,20 +7456,37 @@ is_redundant_opts_combo(Opts) -> lists:member(private, Opts) orelse lists:member(protected, Opts)). -ets_new(Name, Opts) -> - ReplaceStimOrdSetHelper = - fun (MOpts) -> - lists:map(fun (I) -> - case I of - stim_cat_ord_set -> ordered_set; - cat_ord_set -> ordered_set; - _ -> I - end - end, MOpts) - end, +%% Add fake table option with info about key range. +%% Will be consumed by ets_new and used for stim_cat_ord_set. +key_range(Opts, KeyRange) -> + [{key_range, KeyRange} | Opts]. + +ets_new(Name, Opts0) -> + {KeyRange, Opts1} = case lists:keytake(key_range, 1, Opts0) of + {value, {key_range, KR}, Rest1} -> + {KR, Rest1}; + false -> + {1000*1000, Opts0} + end, + ets_new(Name, Opts1, KeyRange). + +ets_new(Name, Opts, KeyRange) -> + ets_new(Name, Opts, KeyRange, fun id/1). + +ets_new(Name, Opts0, KeyRange, KeyFun) -> + {CATree, Stimulate, RevOpts} = + lists:foldl(fun(cat_ord_set, {false, false, Lacc}) -> + {true, false, [ordered_set | Lacc]}; + (stim_cat_ord_set, {false, false, Lacc}) -> + {true, true, [ordered_set | Lacc]}; + (Other, {CAT, STIM, Lacc}) -> + {CAT, STIM, [Other | Lacc]} + end, + {false, false, []}, + Opts0), + Opts = lists:reverse(RevOpts), EtsNewHelper = - fun (MOpts) -> - UseOpts = ReplaceStimOrdSetHelper(MOpts), + fun (UseOpts) -> case get(ets_new_opts) of UseOpts -> silence; %% suppress identical table opts spam @@ -7347,8 +7496,7 @@ ets_new(Name, Opts) -> end, ets:new(Name, UseOpts) end, - case (lists:member(stim_cat_ord_set, Opts) or - lists:member(cat_ord_set, Opts)) andalso + case CATree andalso (not lists:member({write_concurrency, false}, Opts)) andalso (not lists:member(private, Opts)) andalso (not lists:member(protected, Opts)) of @@ -7364,62 +7512,54 @@ ets_new(Name, Opts) -> false -> [public|NewOpts1] end, T = EtsNewHelper(NewOpts2), - case lists:member(stim_cat_ord_set, Opts) of - true -> stimulate_contention(T); - false -> ok + case Stimulate of + false -> ok; + true -> stimulate_contention(T, KeyRange, KeyFun) end, T; false -> EtsNewHelper(Opts) end. -% This function do the following to the input ETS table: -% 1. Perform a number of concurrent insert operations -% 2. Remove all inserted items -% % The purpose of this function is to stimulate fine grained locking in % tables of types ordered_set with the write_concurrency options -% turned on. Such tables are implemented as CA trees* and thus -% activates fine grained locking only when lock contention is -% detected. -% -% A Contention Adapting Approach to Concurrent Ordered Sets -% Journal of Parallel and Distributed Computing, 2018 -% Kjell Winblad and Konstantinos Sagonas -% https://doi.org/10.1016/j.jpdc.2017.11.007 -stimulate_contention(T) -> - NrOfSchedulers = erlang:system_info(schedulers), - ParentPid = self(), - KeyRange = 100000, - ChildPids = - lists:map(fun(_N) -> - spawn(fun() -> - receive start -> ok end, - stimulate_contention_do_inserts(T, KeyRange, 0), - ParentPid ! done - end) - end, lists:seq(1, NrOfSchedulers)), - lists:foreach(fun(Pid) -> Pid ! start end, ChildPids), - timer:sleep(100), - lists:foreach(fun(Pid) -> Pid ! stop end, ChildPids), - lists:foreach(fun(_P) -> receive done -> ok end end, ChildPids), - lists:foreach(fun(N) -> ets:delete(T, N) end, lists:seq(0, KeyRange)). - - - -stimulate_contention_do_inserts(T, KeyRange, 0) -> - OpsBetweenStopCheck = 10000, - receive - stop -> ok - after - 0 -> stimulate_contention_do_inserts(T, KeyRange, OpsBetweenStopCheck) - end; -stimulate_contention_do_inserts(T, KeyRange, OpsToNextStopCheck) -> - R = trunc(KeyRange * rand:uniform()), - ets:insert(T,{R,R,R}), - stimulate_contention_do_inserts(T, KeyRange, OpsToNextStopCheck - 1). - +% turned on. The erts_debug feature 'ets_force_split' is used to easier +% generate a routing tree with fine grained locking without having to +% provoke lots of actual lock contentions. +stimulate_contention(Tid, KeyRange, KeyFun) -> + T = case Tid of + A when is_atom(A) -> ets:whereis(A); + _ -> Tid + end, + erts_debug:set_internal_state(ets_force_split, {T, true}), + Num = case KeyRange > 50 of + true -> 50; + false -> KeyRange + end, + Seed = rand:uniform(KeyRange), + %%io:format("prefill_table: Seed = ~p\n", [Seed]), + RState = unique_rand_start(KeyRange, Seed), + stim_inserter_loop(T, RState, Num, KeyFun), + Num = ets:info(T, size), + ets:match_delete(T, {'$1','$1','$1'}), + 0 = ets:info(T, size), + erts_debug:set_internal_state(ets_force_split, {T, false}), + case ets:info(T,stats) of + {0, _, _} -> + io:format("No routing nodes in table?\n" + "Debug feature 'ets_force_split' does not seem to work.\n", []), + ct:fail("No ets_force_split?"); + Stats -> + io:format("stimulated ordered_set: ~p\n", [Stats]) + end. +stim_inserter_loop(_, _, 0, _) -> + ok; +stim_inserter_loop(T, RS0, N, KeyFun) -> + {K, RS1} = unique_rand_next(RS0), + Key = KeyFun(K), + ets:insert(T, {Key, Key, Key}), + stim_inserter_loop(T, RS1, N-1, KeyFun). do_tc(Do, Report) -> T1 = erlang:monotonic_time(), @@ -7478,4 +7618,5 @@ dquad(Prime, X, Seed) -> %% Primes where P rem 4 == 3. primes_3mod4() -> [103, 211, 503, 1019, 2003, 5003, 10007, 20011, 50023, - 100003, 200003, 500083, 1000003, 2000003]. + 100003, 200003, 500083, 1000003, 2000003, 5000011, + 10000019, 20000003, 50000047, 100000007]. diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl index af94fc79bc..5dab6f6697 100644 --- a/lib/stdlib/test/lists_SUITE.erl +++ b/lib/stdlib/test/lists_SUITE.erl @@ -158,6 +158,20 @@ append_2(Config) when is_list(Config) -> "abcdef"=lists:append("abc", "def"), [hej, du]=lists:append([hej], [du]), [10, [elem]]=lists:append([10], [[elem]]), + + %% Trapping, both crashing and otherwise. + [append_trapping_1(N) || N <- lists:seq(0, 20)], + + ok. + +append_trapping_1(N) -> + List = lists:duplicate(N + (1 bsl N), gurka), + ImproperList = List ++ crash, + + {'EXIT',_} = (catch (ImproperList ++ [])), + + [3, 2, 1 | List] = lists:reverse(List ++ [1, 2, 3]), + ok. %% Tests the lists:reverse() implementation. The function is @@ -2597,6 +2611,20 @@ subtract(Config) when is_list(Config) -> {'EXIT',_} = (catch sub([a|b], [])), {'EXIT',_} = (catch sub([a|b], [a])), + %% Trapping, both crashing and otherwise. + [sub_trapping(N) || N <- lists:seq(0, 18)], + + %% The current implementation chooses which algorithm to use based on + %% certain thresholds, and we need proper coverage for all corner cases. + [sub_thresholds(N) || N <- lists:seq(0, 32)], + + %% Trapping, both crashing and otherwise. + [sub_trapping(N) || N <- lists:seq(0, 18)], + + %% The current implementation chooses which algorithm to use based on + %% certain thresholds, and we need proper coverage for all corner cases. + [sub_thresholds(N) || N <- lists:seq(0, 32)], + ok. sub_non_matching(A, B) -> @@ -2606,6 +2634,41 @@ sub(A, B) -> Res = A -- B, Res = lists:subtract(A, B). +sub_trapping(N) -> + List = lists:duplicate(N + (1 bsl N), gurka), + ImproperList = List ++ crash, + + {'EXIT',_} = (catch sub_trapping_1(ImproperList, [])), + {'EXIT',_} = (catch sub_trapping_1(List, ImproperList)), + + List = List -- lists:duplicate(N + (1 bsl N), gaffel), + ok = sub_trapping_1(List, []). + +sub_trapping_1([], _) -> ok; +sub_trapping_1(L, R) -> sub_trapping_1(L -- R, [gurka | R]). + +sub_thresholds(N) -> + %% This needs to be long enough to cause trapping. + OtherLen = 1 bsl 18, + Other = lists:seq(0, OtherLen - 1), + + Disjoint = lists:seq(-N, -1), + Subset = lists:seq(1, N), + + %% LHS is disjoint from RHS, so all elements must be retained. + Disjoint = Disjoint -- Other, + + %% LHS is covered by RHS, so all elements must be removed. + [] = Subset -- Other, + + %% RHS is disjoint from LHS, so all elements must be retained. + Other = Other -- Disjoint, + + %% RHS is covered by LHS, so N elements must be removed. + N = OtherLen - length(Other -- Subset), + + ok. + %% Test lists:droplast/1 droplast(Config) when is_list(Config) -> [] = lists:droplast([x]), |