diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 50 | ||||
-rw-r--r-- | lib/stdlib/test/ms_transform_SUITE.erl | 101 |
2 files changed, 146 insertions, 5 deletions
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 5f26b7d431..5d7e558601 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -33,7 +33,7 @@ -export([misc/1, dups/1, misc1/1, safe_fixtable/1, info/1, tab2list/1]). -export([files/1, tab2file/1, tab2file2/1, tab2file3/1, tabfile_ext1/1, tabfile_ext2/1, tabfile_ext3/1, tabfile_ext4/1]). --export([heavy/1, heavy_lookup/1, heavy_lookup_element/1]). +-export([heavy/1, heavy_lookup/1, heavy_lookup_element/1, heavy_concurrent/1]). -export([lookup_element/1, lookup_element_mult/1]). -export([fold/1]). -export([foldl_ordered/1, foldr_ordered/1, foldl/1, foldr/1, fold_empty/1]). @@ -90,7 +90,8 @@ match_delete_do/1, match_delete3_do/1, firstnext_do/1, slot_do/1, match1_do/1, match2_do/1, match_object_do/1, match_object2_do/1, misc1_do/1, safe_fixtable_do/1, info_do/1, dups_do/1, heavy_lookup_do/1, - heavy_lookup_element_do/1, member_do/1, otp_5340_do/1, otp_7665_do/1, meta_wb_do/1 + heavy_lookup_element_do/1, member_do/1, otp_5340_do/1, otp_7665_do/1, meta_wb_do/1, + do_heavy_concurrent/1 ]). -include("test_server.hrl"). @@ -3878,7 +3879,7 @@ make_sub_binary(List, Num) when is_list(List) -> {_,B} = split_binary(Bin, N+1), B. -heavy(suite) -> [heavy_lookup, heavy_lookup_element]. +heavy(suite) -> [heavy_lookup, heavy_lookup_element, heavy_concurrent]. %% Lookup stuff like crazy... heavy_lookup(doc) -> ["Performs multiple lookups for every key ", @@ -3941,6 +3942,44 @@ do_lookup_element(Tab, N, M) -> end. +heavy_concurrent(Config) -> + repeat_for_opts(do_heavy_concurrent). + +do_heavy_concurrent(Opts) -> + ?line Size = 20000, + ?line EtsMem = etsmem(), + ?line Tab = ets:new(blupp, [set, public, {keypos, 2} | Opts]), + ?line ok = fill_tab2(Tab, 0, Size), + ?line Procs = lists:map( + fun (N) -> + spawn_link( + fun () -> + do_heavy_concurrent_proc(Tab, Size, N) + end) + end, + lists:seq(1, 500)), + ?line lists:foreach(fun (P) -> + M = erlang:monitor(process, P), + receive + {'DOWN', Mon, process, P, _} -> + ok + end + end, + Procs), + ?line true = ets:delete(Tab), + ?line verify_etsmem(EtsMem). + +do_heavy_concurrent_proc(_Tab, 0, _Offs) -> + done; +do_heavy_concurrent_proc(Tab, N, Offs) when (N+Offs) rem 100 == 0 -> + Data = {"here", are, "S O M E ", data, "toooooooooooooooooo", insert, + make_ref(), make_ref(), make_ref()}, + true=ets:insert(Tab, {{self(),Data}, N}), + do_heavy_concurrent_proc(Tab, N-1, Offs); +do_heavy_concurrent_proc(Tab, N, Offs) -> + _ = ets:lookup(Tab, N), + do_heavy_concurrent_proc(Tab, N-1, Offs). + fold(suite) -> [foldl_ordered, foldr_ordered, foldl, foldr, fold_empty]. @@ -5343,7 +5382,7 @@ only_if_smp(Schedulers, Func) -> %% Repeat test function with different combination of table options %% repeat_for_opts(F) -> - repeat_for_opts(F, [write_concurrency]). + repeat_for_opts(F, [write_concurrency, read_concurrency]). repeat_for_opts(F, OptGenList) when is_atom(F) -> repeat_for_opts(fun(Opts) -> ?MODULE:F(Opts) end, OptGenList); @@ -5363,6 +5402,7 @@ repeat_for_opts(F, [Atom | Tail], AccList) when is_atom(Atom) -> repeat_for_opts(F, [repeat_for_opts_atom2list(Atom) | Tail ], AccList). repeat_for_opts_atom2list(all_types) -> [set,ordered_set,bag,duplicate_bag]; -repeat_for_opts_atom2list(write_concurrency) -> [{write_concurrency,false},{write_concurrency,true}]. +repeat_for_opts_atom2list(write_concurrency) -> [{write_concurrency,false},{write_concurrency,true}]; +repeat_for_opts_atom2list(read_concurrency) -> [{read_concurrency,false},{read_concurrency,true}]. diff --git a/lib/stdlib/test/ms_transform_SUITE.erl b/lib/stdlib/test/ms_transform_SUITE.erl index 79a0a9af89..2d90d5b823 100644 --- a/lib/stdlib/test/ms_transform_SUITE.erl +++ b/lib/stdlib/test/ms_transform_SUITE.erl @@ -37,6 +37,7 @@ -export([andalso_orelse/1]). -export([float_1_function/1]). -export([action_function/1]). +-export([warnings/1]). -export([init_per_testcase/2, fin_per_testcase/2]). init_per_testcase(_Func, Config) -> @@ -50,8 +51,90 @@ fin_per_testcase(_Func, Config) -> all(suite) -> [from_shell,basic_ets,basic_dbg,records,record_index,multipass, bitsyntax, record_defaults, andalso_orelse, float_1_function, action_function, + warnings, top_match, old_guards, autoimported, semicolon]. +%% This may be subject to change +-define(WARN_NUMBER_SHADOW,50). +warnings(suite) -> + []; +warnings(doc) -> + ["Check that shadowed variables in fun head generate warning"]; +warnings(Config) when is_list(Config) -> + ?line setup(Config), + Prog = <<"A=5, " + "ets:fun2ms(fun({A,B}) " + " when is_integer(A) and (A+5 > B) -> " + " A andalso B " + " end)">>, + ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}]}] = + compile_ww(Prog), + Prog2 = <<"C=5, " + "ets:fun2ms(fun({A,B} = C) " + " when is_integer(A) and (A+5 > B) -> " + " {A andalso B,C} " + " end)">>, + ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] = + compile_ww(Prog2), + Rec3 = <<"-record(a,{a,b,c,d=foppa}).">>, + Prog3 = <<"A=3,C=5, " + "ets:fun2ms(fun(#a{a = A, b = B} = C) " + " when is_integer(A) and (A+5 > B) -> " + " {A andalso B,C} " + " end)">>, + ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}, + {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] = + compile_ww(Rec3,Prog3), + Rec4 = <<"-record(a,{a,b,c,d=foppa}).">>, + Prog4 = <<"A=3,C=5, " + "F = fun(B) -> B*3 end," + "erlang:display(F(A))," + "ets:fun2ms(fun(#a{a = A, b = B} = C) " + " when is_integer(A) and (A+5 > B) -> " + " {A andalso B,C} " + " end)">>, + ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}, + {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] = + compile_ww(Rec4,Prog4), + Rec5 = <<"-record(a,{a,b,c,d=foppa}).">>, + Prog5 = <<"A=3,C=5, " + "F = fun(B) -> B*3 end," + "erlang:display(F(A))," + "B = ets:fun2ms(fun(#a{a = A, b = B} = C) " + " when is_integer(A) and (A+5 > B) -> " + " {A andalso B,C} " + " end)">>, + ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}, + {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] = + compile_ww(Rec5,Prog5), + Prog6 = <<" X=bar, " + " A = case X of" + " foo ->" + " foo;" + " Y ->" + " ets:fun2ms(fun(Y) ->" % This is a warning + " 3*Y" + " end)" + " end," + " ets:fun2ms(fun(Y) ->" % Y out of "scope" here, so no warning + " {3*Y,A}" + " end)">>, + ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] = + compile_ww(Prog6), + Prog7 = <<" X=bar, " + " A = case X of" + " foo ->" + " Y = foo;" + " Y ->" + " bar" + " end," + " ets:fun2ms(fun(Y) ->" % Y exported from case and safe, so warn + " {3*Y,A}" + " end)">>, + ?line [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] = + compile_ww(Prog7), + ok. + andalso_orelse(suite) -> []; andalso_orelse(doc) -> @@ -721,6 +804,24 @@ compile_and_run(Records,Expr) -> code:load_binary(tmp,FN,Bin), tmp:tmp(). +compile_ww(Expr) -> + compile_ww(<<>>,Expr). +compile_ww(Records,Expr) -> + Prog = << + "-module(tmp).\n", + "-include_lib(\"stdlib/include/ms_transform.hrl\").\n", + "-export([tmp/0]).\n", + Records/binary,"\n", + "tmp() ->\n", + Expr/binary,".\n">>, + FN=temp_name(), + file:write_file(FN,Prog), + {ok,Forms} = epp:parse_file(FN,"",""), + {ok,tmp,_Bin,Wlist} = compile:forms(Forms,[return_warnings, + nowarn_unused_vars, + nowarn_unused_record]), + Wlist. + do_eval(String) -> {done,{ok,T,_},[]} = erl_scan:tokens( [], |