diff options
Diffstat (limited to 'lib/stdlib/test/ets_SUITE.erl')
-rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 225 |
1 files changed, 190 insertions, 35 deletions
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 716b4f9732..aa2e352c29 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2017. All Rights Reserved. +%% Copyright Ericsson AB 1996-2018. 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. @@ -55,6 +55,7 @@ -export([t_repair_continuation/1]). -export([t_match_spec_run/1]). -export([t_bucket_disappears/1]). +-export([t_named_select/1]). -export([otp_5340/1]). -export([otp_6338/1]). -export([otp_6842_select_1000/1]). @@ -65,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, - smp_select_replace/1, otp_8166/1, otp_8732/1]). + smp_select_replace/1, otp_8166/1, otp_8732/1, delete_unfix_race/1]). -export([exit_large_table_owner/1, exit_many_large_table_owner/1, exit_many_tables_owner/1, @@ -78,6 +79,7 @@ -export([ets_all/1]). -export([massive_ets_all/1]). -export([take/1]). +-export([whereis_table/1]). -export([init_per_testcase/2, end_per_testcase/2]). %% Convenience for manual testing @@ -85,6 +87,7 @@ -export([t_select_reverse/1]). +-include_lib("stdlib/include/ms_transform.hrl"). % ets:fun2ms -include_lib("common_test/include/ct.hrl"). -define(m(A,B), assert_eq(A,B)). @@ -124,6 +127,7 @@ all() -> 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, + t_named_select, select_fail, t_insert_new, t_repair_continuation, otp_5340, otp_6338, otp_6842_select_1000, otp_7665, otp_8732, meta_wb, grow_shrink, grow_pseudo_deleted, @@ -138,7 +142,9 @@ all() -> otp_9423, ets_all, massive_ets_all, - take]. + take, + whereis_table, + delete_unfix_race]. groups() -> [{new, [], @@ -170,10 +176,12 @@ groups() -> init_per_suite(Config) -> erts_debug:set_internal_state(available_internal_state, true), + erts_debug:set_internal_state(ets_force_trap, true), Config. end_per_suite(_Config) -> stop_spawn_logger(), + erts_debug:set_internal_state(ets_force_trap, false), catch erts_debug:set_internal_state(available_internal_state, false), ok. @@ -204,6 +212,38 @@ t_bucket_disappears_do(Opts) -> true = ets:delete(abcd), verify_etsmem(EtsMem). +%% OTP-21: Test that select/1 fails if named table was deleted and recreated +%% and succeeds if table was renamed. +t_named_select(_Config) -> + repeat_for_opts(fun t_named_select_do/1). + +t_named_select_do(Opts) -> + EtsMem = etsmem(), + T = t_name_tid_select, + ets_new(T, [named_table | Opts]), + ets:insert(T, {1,11}), + ets:insert(T, {2,22}), + ets:insert(T, {3,33}), + MS = [{{'$1', 22}, [], ['$1']}], + {[2], Cont1} = ets:select(T, MS, 1), + ets:delete(T), + {'EXIT',{badarg,_}} = (catch ets:select(Cont1)), + ets_new(T, [named_table | Opts]), + {'EXIT',{badarg,_}} = (catch ets:select(Cont1)), + + true = ets:insert_new(T, {1,22}), + true = ets:insert_new(T, {2,22}), + true = ets:insert_new(T, {4,22}), + {[A,B], Cont2} = ets:select(T, MS, 2), + ets:rename(T, abcd), + {[C], '$end_of_table'} = ets:select(Cont2), + 7 = A + B + C, + + true = ets:delete(abcd), + verify_etsmem(EtsMem). + + + %% Check ets:match_spec_run/2. t_match_spec_run(Config) when is_list(Config) -> @@ -699,7 +739,7 @@ whitebox_2(Opts) -> ets:delete(T2), ok. -select_bound_chunk(Config) -> +select_bound_chunk(_Config) -> repeat_for_opts(fun select_bound_chunk_do/1, [all_types]). select_bound_chunk_do(Opts) -> @@ -777,7 +817,60 @@ t_delete_all_objects_do(Opts) -> 4000 = ets:info(T,size), true = ets:delete_all_objects(T), 0 = ets:info(T,size), - ets:delete(T). + ets:delete(T), + + %% Test delete_all_objects is atomic + T2 = ets:new(t_delete_all_objects, [public | Opts]), + Self = self(), + Inserters = [spawn_link(fun() -> inserter(T2, 100*1000, 1, Self) end) || _ <- [1,2,3,4]], + [receive {Ipid, running} -> ok end || Ipid <- Inserters], + + ets:delete_all_objects(T2), + erlang:yield(), + [Ipid ! stop || Ipid <- Inserters], + Result = [receive {Ipid, stopped, Highest} -> {Ipid,Highest} end || Ipid <- Inserters], + + %% Verify unbroken sequences of objects inserted _after_ ets:delete_all_objects. + Sum = lists:foldl(fun({Ipid, Highest}, AccSum) -> + %% ets:fun2ms(fun({{K,Ipid}}) when K =< Highest -> true end), + AliveMS = [{{{'$1',Ipid}},[{'=<','$1',{const,Highest}}],[true]}], + Alive = ets:select_count(T2, AliveMS), + Lowest = Highest - (Alive-1), + + %% ets:fun2ms(fun({{K,Ipid}}) when K < Lowest -> true end) + DeletedMS = [{{{'$1',Ipid}},[{'<','$1',{const,Lowest}}],[true]}], + 0 = ets:select_count(T2, DeletedMS), + AccSum + Alive + end, + 0, + Result), + ok = case ets:info(T2, size) of + Sum -> ok; + Size -> + io:format("Sum = ~p\nSize = ~p\n", [Sum, Size]), + {Sum,Size} + end, + + ets:delete(T2). + +inserter(_, 0, _, _) -> + ok; +inserter(T, N, Next, Papa) -> + case Next of + 10*1000 -> + Papa ! {self(), running}; + _ -> + ok + end, + + ets:insert(T, {{Next, self()}}), + receive + stop -> + Papa ! {self(), stopped, Next}, + ok + after 0 -> + inserter(T, N-1, Next+1, Papa) + end. %% Test ets:delete_object/2. @@ -1702,7 +1795,7 @@ do_random_test() -> ets:delete(Set), verify_etsmem(EtsMem). -%% Ttest various variants of update_element. +%% Test various variants of update_element. update_element(Config) when is_list(Config) -> EtsMem = etsmem(), repeat_for_opts(fun update_element_opts/1), @@ -2303,13 +2396,8 @@ write_concurrency(Config) when is_list(Config) -> NoHashMem = ets:info(No7,memory), NoHashMem = ets:info(No8,memory), - case erlang:system_info(smp_support) of - true -> - true = YesMem > NoHashMem, - true = YesMem > NoTreeMem; - false -> - true = YesMem =:= NoHashMem - end, + true = YesMem > NoHashMem, + true = YesMem > NoTreeMem, {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency,foo}])), {'EXIT',{badarg,_}} = (catch ets_new(foo,[public,{write_concurrency}])), @@ -3672,7 +3760,7 @@ verify_rescheduling_exit(Config, ForEachData, Flags, Fix, NOTabs, NOProcs) -> XScheds = count_exit_sched(TP), io:format("~p XScheds=~p~n", [TP, XScheds]), - true = XScheds >= 5 + true = XScheds >= 3 end, TPs), stop_loopers(LPs), @@ -4124,6 +4212,7 @@ info_do(Opts) -> {value, {keypos, 2}} = lists:keysearch(keypos, 1, Res), {value, {protection, protected}} = lists:keysearch(protection, 1, Res), + {value, {id, Tab}} = lists:keysearch(id, 1, Res), true = ets:delete(Tab), undefined = ets:info(non_existing_table_xxyy), undefined = ets:info(non_existing_table_xxyy,type), @@ -5421,6 +5510,46 @@ smp_fixed_delete_do() -> %%verify_table_load(T), ets:delete(T). +%% ERL-720 +%% Provoke race between ets:delete and table unfix (by select_count) +%% that caused ets_misc memory counter to indicate false leak. +delete_unfix_race(Config) when is_list(Config) -> + EtsMem = etsmem(), + Table = ets:new(t,[set,public,{write_concurrency,true}]), + InsertOp = + fun() -> + receive stop -> + false + after 0 -> + ets:insert(Table, {rand:uniform(10)}), + true + end + end, + DeleteOp = + fun() -> + receive stop -> + false + after 0 -> + ets:delete(Table, rand:uniform(10)), + true + end + end, + SelectOp = + fun() -> + ets:select_count(Table, ets:fun2ms(fun(X) -> true end)) + end, + Main = self(), + Ins = spawn(fun()-> repeat_while(InsertOp), Main ! self() end), + Del = spawn(fun()-> repeat_while(DeleteOp), Main ! self() end), + spawn(fun()-> + repeat(SelectOp, 10000), + Del ! stop, + Ins ! stop + end), + [receive Pid -> ok end || Pid <- [Ins,Del]], + ets:delete(Table), + verify_etsmem(EtsMem). + num_of_buckets(T) -> element(1,ets:info(T,stats)). @@ -5917,6 +6046,36 @@ take(Config) when is_list(Config) -> ets:delete(T3), ok. +whereis_table(Config) when is_list(Config) -> + %% Do we return 'undefined' when the named table doesn't exist? + undefined = ets:whereis(whereis_test), + + %% Does the tid() refer to the same table as the name? + whereis_test = ets:new(whereis_test, [named_table]), + Tid = ets:whereis(whereis_test), + + ets:insert(whereis_test, [{hello}, {there}]), + + [[{hello}],[{there}]] = ets:match(whereis_test, '$1'), + [[{hello}],[{there}]] = ets:match(Tid, '$1'), + + true = ets:delete_all_objects(Tid), + + [] = ets:match(whereis_test, '$1'), + [] = ets:match(Tid, '$1'), + + %% Does the name disappear when deleted through the tid()? + true = ets:delete(Tid), + undefined = ets:info(whereis_test), + {'EXIT',{badarg, _}} = (catch ets:match(whereis_test, '$1')), + + %% Is the old tid() broken when the table is re-created with the same + %% name? + whereis_test = ets:new(whereis_test, [named_table]), + [] = ets:match(whereis_test, '$1'), + {'EXIT',{badarg, _}} = (catch ets:match(Tid, '$1')), + + ok. %% %% Utility functions: @@ -5932,16 +6091,11 @@ add_lists([E1|T1], [E2|T2], Acc) -> 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 -> - 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"} + 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. run_sched_workers(InitF,ExecF,FiniF,Laps) -> @@ -6116,20 +6270,23 @@ spawn_logger(Procs) -> ok; (Proc) -> Mon = erlang:monitor(process, Proc), - receive + ok = receive {'DOWN', Mon, _, _, _} -> ok after 0 -> case Kill of true -> exit(Proc, kill); - _ -> - erlang:display({"Waiting for 'DOWN' from", Proc, - process_info(Proc), - pid_status(Proc)}) + _ -> ok end, receive {'DOWN', Mon, _, _, _} -> ok + after 5000 -> + io:format("Waiting for 'DOWN' from ~w, status=~w\n" + "info = ~p\n", [Proc, + pid_status(Proc), + process_info(Proc)]), + timeout end end end, Procs), @@ -6265,11 +6422,9 @@ spawn_monitor_with_pid(Pid, Fun, N) -> only_if_smp(Func) -> only_if_smp(2, Func). only_if_smp(Schedulers, Func) -> - case {erlang:system_info(smp_support), - erlang:system_info(schedulers_online)} of - {false,_} -> {skip,"No smp support"}; - {true,N} when N < Schedulers -> {skip,"Too few schedulers online"}; - {true,_} -> Func() + case erlang:system_info(schedulers_online) of + N when N < Schedulers -> {skip,"Too few schedulers online"}; + _ -> Func() end. %% Copy-paste from emulator/test/binary_SUITE.erl @@ -6415,7 +6570,7 @@ very_big_num(0, Result) -> Result. make_port() -> - open_port({spawn, "efile"}, [eof]). + hd(erlang:ports()). make_pid() -> spawn_link(fun sleeper/0). |