diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/base64_SUITE.erl | 41 | ||||
-rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 282 | ||||
-rw-r--r-- | lib/stdlib/test/gen_statem_SUITE.erl | 36 | ||||
-rw-r--r-- | lib/stdlib/test/proc_lib_SUITE.erl | 31 | ||||
-rw-r--r-- | lib/stdlib/test/rand_SUITE.erl | 208 | ||||
-rw-r--r-- | lib/stdlib/test/tar_SUITE.erl | 26 |
6 files changed, 414 insertions, 210 deletions
diff --git a/lib/stdlib/test/base64_SUITE.erl b/lib/stdlib/test/base64_SUITE.erl index 9176a3664a..d0abe5c961 100644 --- a/lib/stdlib/test/base64_SUITE.erl +++ b/lib/stdlib/test/base64_SUITE.erl @@ -23,9 +23,7 @@ -include_lib("common_test/include/ct.hrl"). %% Test server specific exports --export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, - init_per_group/2,end_per_group/2, - init_per_testcase/2, end_per_testcase/2]). +-export([all/0, suite/0, groups/0, group/1]). %% Test cases must be exported. -export([base64_encode/1, base64_decode/1, base64_otp_5635/1, @@ -33,41 +31,26 @@ mime_decode_to_string/1, roundtrip_1/1, roundtrip_2/1, roundtrip_3/1, roundtrip_4/1]). -init_per_testcase(_, Config) -> - Config. - -end_per_testcase(_, _Config) -> - ok. - %%------------------------------------------------------------------------- %% Test cases starts here. %%------------------------------------------------------------------------- + suite() -> [{ct_hooks,[ts_install_cth]}, {timetrap,{minutes,4}}]. -all() -> +all() -> [base64_encode, base64_decode, base64_otp_5635, base64_otp_6279, big, illegal, mime_decode, mime_decode_to_string, {group, roundtrip}]. -groups() -> +groups() -> [{roundtrip, [parallel], [roundtrip_1, roundtrip_2, roundtrip_3, roundtrip_4]}]. -init_per_suite(Config) -> - Config. - -end_per_suite(_Config) -> - ok. - -init_per_group(_GroupName, Config) -> - Config. - -end_per_group(_GroupName, Config) -> - Config. - - +group(roundtrip) -> + %% valgrind needs a lot of time + [{timetrap,{minutes,10}}]. %%------------------------------------------------------------------------- %% Test base64:encode/1. @@ -78,9 +61,9 @@ base64_encode(Config) when is_list(Config) -> %% One pad <<"SGVsbG8gV29ybGQ=">> = base64:encode(<<"Hello World">>), %% No pad - "QWxhZGRpbjpvcGVuIHNlc2Ft" = + "QWxhZGRpbjpvcGVuIHNlc2Ft" = base64:encode_to_string("Aladdin:open sesam"), - + "MDEyMzQ1Njc4OSFAIzBeJiooKTs6PD4sLiBbXXt9" = base64:encode_to_string(<<"0123456789!@#0^&*();:<>,. []{}">>), ok. @@ -93,7 +76,7 @@ base64_decode(Config) when is_list(Config) -> %% One pad <<"Hello World">> = base64:decode(<<"SGVsbG8gV29ybGQ=">>), %% No pad - <<"Aladdin:open sesam">> = + <<"Aladdin:open sesam">> = base64:decode("QWxhZGRpbjpvcGVuIHNlc2Ft"), Alphabet = list_to_binary(lists:seq(0, 255)), @@ -208,7 +191,7 @@ mime_decode_to_string(Config) when is_list(Config) -> %% One pad to ignore, followed by more text "Hello World!!" = base64:mime_decode_to_string(<<"SGVsb)(G8gV29ybGQ=h IQ= =">>), %% No pad - "Aladdin:open sesam" = + "Aladdin:open sesam" = base64:mime_decode_to_string("QWxhZGRpbjpvcG¤\")(VuIHNlc2Ft"), %% Encoded base 64 strings may be divided by non base 64 chars. %% In this cases whitespaces. @@ -314,7 +297,7 @@ interleaved_ws_roundtrip_1([], Base64List, Bin, List) -> random_byte_list(0, Acc) -> Acc; -random_byte_list(N, Acc) -> +random_byte_list(N, Acc) -> random_byte_list(N-1, [rand:uniform(255)|Acc]). make_big_binary(N) -> diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 9a14c7014c..f68d5eca3f 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -19,7 +19,7 @@ %% -module(ets_SUITE). --export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, +-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2]). -export([default/1,setbag/1,badnew/1,verybadnew/1,named/1,keypos2/1, privacy/1,privacy_owner/2]). @@ -31,15 +31,14 @@ -export([match_delete3/1]). -export([firstnext/1,firstnext_concurrent/1]). -export([slot/1]). --export([ match1/1, match2/1, match_object/1, match_object2/1]). --export([ dups/1, misc1/1, safe_fixtable/1, info/1, tab2list/1]). --export([ tab2file/1, tab2file2/1, tabfile_ext1/1, - tabfile_ext2/1, tabfile_ext3/1, tabfile_ext4/1, badfile/1]). --export([ heavy_lookup/1, heavy_lookup_element/1, heavy_concurrent/1]). --export([ lookup_element_mult/1]). --export([]). +-export([match1/1, match2/1, match_object/1, match_object2/1]). +-export([dups/1, misc1/1, safe_fixtable/1, info/1, tab2list/1]). +-export([tab2file/1, tab2file2/1, tabfile_ext1/1, + tabfile_ext2/1, tabfile_ext3/1, tabfile_ext4/1, badfile/1]). +-export([heavy_lookup/1, heavy_lookup_element/1, heavy_concurrent/1]). +-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, +-export([t_delete_object/1, t_init_table/1, t_whitebox/1, t_delete_all_objects/1, t_insert_list/1, t_test_ms/1, t_select_delete/1,t_ets_dets/1]). @@ -61,8 +60,7 @@ -export([otp_7665/1]). -export([meta_wb/1]). -export([grow_shrink/1, grow_pseudo_deleted/1, shrink_pseudo_deleted/1]). --export([ - meta_lookup_unnamed_read/1, meta_lookup_unnamed_write/1, +-export([meta_lookup_unnamed_read/1, meta_lookup_unnamed_write/1, 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, @@ -95,7 +93,7 @@ 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, + 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, @@ -129,7 +127,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}, {timetrap,{minutes,5}}]. -all() -> +all() -> [{group, new}, {group, insert}, {group, lookup}, {group, delete}, firstnext, firstnext_concurrent, slot, {group, match}, t_match_spec_run, @@ -161,7 +159,7 @@ all() -> memory_check_summary]. % MUST BE LAST -groups() -> +groups() -> [{new, [], [default, setbag, badnew, verybadnew, named, keypos2, privacy]}, @@ -249,6 +247,7 @@ t_bucket_disappears_do(Opts) -> %% Check ets:match_spec_run/2. t_match_spec_run(Config) when is_list(Config) -> + ct:timetrap({minutes,30}), %% valgrind needs a lot init_externals(), EtsMem = etsmem(), @@ -703,7 +702,7 @@ adjust_xmem([_T1,_T2,_T3,_T4], {A0,B0,C0,D0} = _Mem0, EstCnt) -> {A0+TabSz, B0+HTabSz, C0+HTabSz, D0+HTabSz}. %% Misc. whitebox tests -t_whitebox(Config) when is_list(Config) -> +t_whitebox(Config) when is_list(Config) -> EtsMem = etsmem(), repeat_for_opts(whitebox_1), repeat_for_opts(whitebox_1), @@ -1044,6 +1043,7 @@ do_reverse_chunked({L,C},Acc) -> %% Test the ets:select_delete/2 and ets:select_count/2 BIFs. t_select_delete(Config) when is_list(Config) -> + ct:timetrap({minutes,30}), %% valgrind needs a lot EtsMem = etsmem(), Tables = fill_sets_int(10000) ++ fill_sets_int(10000,[{write_concurrency,true}]), lists:foreach @@ -1489,15 +1489,15 @@ update_element(Config) when is_list(Config) -> verify_etsmem(EtsMem). update_element_opts(Opts) -> - TupleCases = [{{key,val}, 1 ,2}, - {{val,key}, 2, 1}, - {{key,val}, 1 ,[2]}, + TupleCases = [{{key,val}, 1 ,2}, + {{val,key}, 2, 1}, + {{key,val}, 1 ,[2]}, {{key,val,val}, 1, [2,3]}, {{val,key,val,val}, 2, [3,4,1]}, {{val,val,key,val}, 3, [1,4,1,2]}, % update pos1 twice {{val,val,val,key}, 4, [2,1,2,3]}],% update pos2 twice - lists:foreach(fun({Tuple,KeyPos,UpdPos}) -> update_element_opts(Tuple,KeyPos,UpdPos,Opts) end, + lists:foreach(fun({Tuple,KeyPos,UpdPos}) -> update_element_opts(Tuple,KeyPos,UpdPos,Opts) end, TupleCases), update_element_neg(Opts). @@ -1513,9 +1513,9 @@ update_element_opts(Tuple,KeyPos,UpdPos,Opts) -> true = ets:delete(OrdSet), ok. -update_element(T,Tuple,KeyPos,UpdPos) -> +update_element(T,Tuple,KeyPos,UpdPos) -> KeyList = [17,"seventeen",<<"seventeen">>,{17},list_to_binary(lists:seq(1,100)),make_ref(), self()], - lists:foreach(fun(Key) -> + lists:foreach(fun(Key) -> TupleWithKey = setelement(KeyPos,Tuple,Key), update_element_do(T,TupleWithKey,Key,UpdPos) end, @@ -1550,29 +1550,29 @@ update_element_do(Tab,Tuple,Key,UpdPos) -> {Pos, element(ToIx+1,Values)} % single {pos,value} arg end, - UpdateF = fun(ToIx,Rand) -> - PosValArg = PosValArgF(ToIx,[],UpdPos,Rand,PosValArgF), - %%io:format("update_element(~p)~n",[PosValArg]), - ArgHash = erlang:phash2({Tab,Key,PosValArg}), - true = ets:update_element(Tab, Key, PosValArg), - ArgHash = erlang:phash2({Tab,Key,PosValArg}), - NewTuple = update_tuple(PosValArg,Tuple), - [NewTuple] = ets:lookup(Tab,Key) + UpdateF = fun(ToIx,Rand) -> + PosValArg = PosValArgF(ToIx,[],UpdPos,Rand,PosValArgF), + %%io:format("update_element(~p)~n",[PosValArg]), + ArgHash = erlang:phash2({Tab,Key,PosValArg}), + true = ets:update_element(Tab, Key, PosValArg), + ArgHash = erlang:phash2({Tab,Key,PosValArg}), + NewTuple = update_tuple(PosValArg,Tuple), + [NewTuple] = ets:lookup(Tab,Key) end, - LoopF = fun(_FromIx, Incr, _Times, Checksum, _MeF) when Incr >= Length -> + LoopF = fun(_FromIx, Incr, _Times, Checksum, _MeF) when Incr >= Length -> Checksum; % done - (FromIx, Incr, 0, Checksum, MeF) -> + (FromIx, Incr, 0, Checksum, MeF) -> MeF(FromIx, Incr+1, Length, Checksum, MeF); - (FromIx, Incr, Times, Checksum, MeF) -> + (FromIx, Incr, Times, Checksum, MeF) -> ToIx = (FromIx + Incr) rem Length, UpdateF(ToIx,Checksum), - if + if Incr =:= 0 -> UpdateF(ToIx,Checksum); % extra update to same value true -> true - end, + end, MeF(ToIx, Incr, Times-1, Checksum+ToIx+1, MeF) end, @@ -1616,7 +1616,7 @@ update_element_neg_do(T) -> Object = {key, 0, "Hej"}, true = ets:insert(T,Object), - UpdateF = fun(Arg3) -> + UpdateF = fun(Arg3) -> ArgHash = erlang:phash2({T,key,Arg3}), {'EXIT',{badarg,_}} = (catch ets:update_element(T,key,Arg3)), ArgHash = erlang:phash2({T,key,Arg3}), @@ -1691,7 +1691,7 @@ update_counter_for(T) -> true = ets:lookup(T, b) =:= [setelement(1, NewObj, b)], ets:delete(T, b), Myself(NewObj,Times-1,Arg3,Myself) - end, + end, LoopF = fun(Obj, Times, Arg3) -> %%io:format("Loop start:\nObj = ~p\nArg3=~p\n",[Obj,Arg3]), @@ -1800,7 +1800,7 @@ uc_mimic(Obj, [Pits|Tail], Acc) -> uc_adder(Init, {_Pos, Add}) -> Init + Add; -uc_adder(Init, {_Pos, Add, Thres, Warp}) -> +uc_adder(Init, {_Pos, Add, Thres, Warp}) -> case Init + Add of X when X > Thres, Add > 0 -> Warp; @@ -1832,7 +1832,7 @@ update_counter_neg_for(T) -> Object = {key,0,false,1}, true = ets:insert(T,Object), - UpdateF = fun(Arg3) -> + UpdateF = fun(Arg3) -> ArgHash = erlang:phash2({T,key,Arg3}), {'EXIT',{badarg,_}} = (catch ets:update_counter(T,key,Arg3)), ArgHash = erlang:phash2({T,key,Arg3}), @@ -1972,15 +1972,16 @@ fixtable_next_do(Opts) -> verify_etsmem(EtsMem). do_fixtable_next(Tab) -> - F = fun(X,T,FF) -> case X of - 0 -> true; - _ -> - ets:insert(T, {X, - integer_to_list(X), - X rem 10}), - FF(X-1,T,FF) - end - end, + F = fun(X,T,FF) -> + case X of + 0 -> true; + _ -> + ets:insert(T, {X, + integer_to_list(X), + X rem 10}), + FF(X-1,T,FF) + end + end, F(100,Tab,F), ets:safe_fixtable(Tab,true), First = ets:first(Tab), @@ -1995,7 +1996,7 @@ do_fixtable_next(Tab) -> %% Check inserts of deleted keys in fixed bags. fixtable_insert(Config) when is_list(Config) -> - Combos = [[Type,{write_concurrency,WC}] || Type<- [bag,duplicate_bag], + Combos = [[Type,{write_concurrency,WC}] || Type<- [bag,duplicate_bag], WC <- [false,true]], lists:foreach(fun(Opts) -> fixtable_insert_do(Opts) end, Combos), @@ -2111,7 +2112,7 @@ heir_do(Opts) -> %% Different types of heir data and link/monitor relations TestFun = fun(Arg) -> {EtsMem,Arg} end, - Combos = [{Data,Mode} || Data<-[foo_data, <<"binary">>, + Combos = [{Data,Mode} || Data<-[foo_data, <<"binary">>, lists:seq(1,10), {17,TestFun,self()}, "The busy heir"], Mode<-[none,link,monitor]], @@ -2151,7 +2152,7 @@ heir_do(Opts) -> Founder4 ! {go, Heir4}, {'DOWN', MrefH4, process, Heir4, normal} = receive_any(), erts_debug:set_internal_state(next_pid, NextPidIx), - DoppelGanger = spawn_monitor_with_pid(Heir4, + DoppelGanger = spawn_monitor_with_pid(Heir4, fun()-> die_please = receive_any() end), Founder4 ! die_please, {'DOWN', MrefF4, process, Founder4, normal} = receive_any(), @@ -2164,12 +2165,12 @@ heir_do(Opts) -> failed -> io:format("Failed to spawn process with pid ~p\n", [Heir4]), true % try again - end + end end), verify_etsmem(EtsMem). -heir_founder(Master, HeirData, Opts) -> +heir_founder(Master, HeirData, Opts) -> {go,Heir} = receive_any(), HeirTpl = case Heir of none -> {heir,none}; @@ -2242,7 +2243,7 @@ heir_1(HeirData,Mode,Opts) -> {'DOWN', Mref, process, Heir, normal} = receive_any(). %% Test ets:give_way/3. -give_away(Config) when is_list(Config) -> +give_away(Config) when is_list(Config) -> repeat_for_opts(give_away_do). give_away_do(Opts) -> @@ -2381,7 +2382,7 @@ bad_table(Config) when is_list(Config) -> ok. bad_table_do(Opts, DummyFile) -> - Parent = self(), + Parent = self(), {Pid,Mref} = my_spawn_opt(fun()-> ets_new(priv,[private,named_table | Opts]), Priv = ets_new(priv,[private | Opts]), ets_new(prot,[protected,named_table | Opts]), @@ -2436,7 +2437,7 @@ bad_table_do(Opts, DummyFile) -> ], Info = {Opts, Priv, Prot}, lists:foreach(fun(Op) -> bad_table_op(Info, Op) end, - OpList), + OpList), Pid ! die_please, {'DOWN', Mref, process, Pid, normal} = receive_any(), ok. @@ -2571,14 +2572,14 @@ interface_equality_do(Opts) -> Set = ets_new(set,[set | Opts]), OrderedSet = ets_new(ordered_set,[ordered_set | Opts]), F = fun(X,T,FF) -> case X of - 0 -> true; - _ -> - ets:insert(T, {X, - integer_to_list(X), - X rem 10}), - FF(X-1,T,FF) - end - end, + 0 -> true; + _ -> + ets:insert(T, {X, + integer_to_list(X), + X rem 10}), + FF(X-1,T,FF) + end + end, F(100,Set,F), F(100,OrderedSet,F), equal_results(ets, insert, Set, OrderedSet, [{a,"a"}]), @@ -2647,20 +2648,20 @@ ordered_match_do(Opts) -> F(3000,T1,F), [[3,3],[3,3],[3,3]] = ets:match(T1, {'_','_','$1','$2',3}), F2 = fun(X,Rem,Res,FF) -> case X of - 0 -> []; - _ -> + 0 -> []; + _ -> case X rem Rem of Res -> FF(X-1,Rem,Res,FF) ++ [{X, - integer_to_list(X), + integer_to_list(X), X rem 10, X rem 100, X rem 1000}]; _ -> FF(X-1,Rem,Res,FF) end - end + end end, OL1 = F2(3000,100,2,F2), OL1 = ets:match_object(T1, {'_','_','_',2,'_'}), @@ -2738,7 +2739,7 @@ pick_all_backwards(T) -> %% Small test case for both set and bag type ets tables. -setbag(Config) when is_list(Config) -> +setbag(Config) when is_list(Config) -> EtsMem = etsmem(), Set = ets_new(set,[set]), Bag = ets_new(bag,[bag]), @@ -2815,7 +2816,7 @@ privacy_do(Opts) -> privacy_check(pub,prot,priv), - Owner ! {shift,1,{pub,prot,priv}}, + Owner ! {shift,1,{pub,prot,priv}}, receive {Pub1,Prot1,Priv1} -> ok = privacy_check(Pub1,Prot1,Priv1), @@ -2954,7 +2955,7 @@ badlookup(Config) when is_list(Config) -> verify_etsmem(EtsMem). %% Test that lookup returns objects in order of insertion for bag and dbag. -lookup_order(Config) when is_list(Config) -> +lookup_order(Config) when is_list(Config) -> EtsMem = etsmem(), repeat_for_opts(lookup_order_do, [write_concurrency,[bag,duplicate_bag]]), verify_etsmem(EtsMem), @@ -2976,7 +2977,7 @@ lookup_order_2(Opts, Fixed) -> case Fixed of true -> ets:safe_fixtable(T,true); false -> ok - end, + end, S10 = {T,[],key}, S20 = check_insert(S10,A), S30 = check_insert(S20,B), @@ -2988,7 +2989,7 @@ lookup_order_2(Opts, Fixed) -> S80 = check_delete(S70,D2b), S90 = check_insert(S80,D2a), SA0 = check_delete(S90,D3a), - SB0 = check_delete(SA0,D3b), + SB0 = check_delete(SA0,D3b), check_insert_new(SB0,D3b), true = ets:delete(T) @@ -3001,7 +3002,7 @@ check_insert({T,List0,Key},Val) -> ets:insert(T,{Key,Val}), List1 = case (ets:info(T,type) =:= bag andalso lists:member({Key,Val},List0)) of - true -> List0; + true -> List0; false -> [{Key,Val} | List0] end, check_check({T,List1,Key}). @@ -3034,8 +3035,6 @@ check_check(S={T,List,Key}) -> Items = length(List), S. - - fill_tab(Tab,Val) -> ets:insert(Tab,{key,Val}), ets:insert(Tab,{{a,144},Val}), @@ -3063,13 +3062,11 @@ lookup_element_mult_do(Opts) -> verify_etsmem(EtsMem). lem_data() -> - [ - {service,'eddie2@boromir',{150,236,14,103},httpd88,self()}, + [{service,'eddie2@boromir',{150,236,14,103},httpd88,self()}, {service,'eddie2@boromir',{150,236,14,103},httpd80,self()}, {service,'eddie3@boromir',{150,236,14,107},httpd88,self()}, {service,'eddie3@boromir',{150,236,14,107},httpd80,self()}, - {service,'eddie4@boromir',{150,236,14,108},httpd88,self()} - ]. + {service,'eddie4@boromir',{150,236,14,108},httpd88,self()}]. lem_crash(T) -> L = ets:lookup_element(T, 'eddie2@boromir', 3), @@ -3120,6 +3117,7 @@ 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,30}), %% valgrind needs a lot Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)], EtsMem = etsmem(), repeat_for_opts(fun(Opts) -> delete_large_tab_do(Opts,Data) end), @@ -3142,7 +3140,7 @@ delete_large_tab_1(Name, Flags, Data, Fix) -> lists:foreach(fun({K,_}) -> ets:delete(Tab, K) end, Data) end, - {priority, Prio} = process_info(self(), priority), + {priority, Prio} = process_info(self(), priority), Deleter = self(), [SchedTracer] = start_loopers(1, @@ -3189,7 +3187,7 @@ delete_large_tab_1(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) -> +delete_large_named_table(Config) when is_list(Config) -> Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 200000)], EtsMem = etsmem(), repeat_for_opts(fun(Opts) -> delete_large_named_table_do(Opts,Data) end), @@ -3562,7 +3560,7 @@ dyn_lookup(T) -> dyn_lookup(T, ets:first(T)). dyn_lookup(_T, '$end_of_table') -> []; dyn_lookup(T, K) -> - NextKey=ets:next(T,K), + NextKey = ets:next(T,K), case ets:next(T,K) of NextKey -> dyn_lookup(T, NextKey); @@ -4081,9 +4079,9 @@ tabfile_ext2_do(Opts,Config) -> Name = make_ref(), [ets:insert(T,{X,integer_to_list(X)}) || X <- L], ok = ets:tab2file(T,FName,[{extended_info,[md5sum]}]), - true = lists:sort(ets:tab2list(T)) =:= + true = lists:sort(ets:tab2list(T)) =:= lists:sort(ets:tab2list(element(2,ets:file2tab(FName)))), - true = lists:sort(ets:tab2list(T)) =:= + true = lists:sort(ets:tab2list(T)) =:= lists:sort(ets:tab2list( element(2,ets:file2tab(FName,[{verify,true}])))), {ok, Name} = disk_log:open([{name,Name},{file,FName}]), @@ -4098,9 +4096,9 @@ tabfile_ext2_do(Opts,Config) -> ets:tab2list( element(2,ets:file2tab(FName2)))), {error,checksum_error} = ets:file2tab(FName2,[{verify,true}]), - {value,{extended_info,[md5sum]}} = + {value,{extended_info,[md5sum]}} = lists:keysearch(extended_info,1,element(2,ets:tabfile_info(FName2))), - {value,{extended_info,[md5sum]}} = + {value,{extended_info,[md5sum]}} = lists:keysearch(extended_info,1,element(2,ets:tabfile_info(FName))), file:delete(FName), file:delete(FName2), @@ -4145,15 +4143,14 @@ tabfile_ext4(Config) when is_list(Config) -> Name2 = make_ref(), [ets:insert(TL,{X,integer_to_list(X)}) || X <- LL], ok = ets:tab2file(TL,FName,[{extended_info,[md5sum]}]), - {ok, Name2} = disk_log:open([{name, Name2}, {file, FName}, + {ok, Name2} = disk_log:open([{name, Name2}, {file, FName}, {mode, read_only}]), {C,[_|_]} = disk_log:chunk(Name2,start), {_,[_|_]} = disk_log:chunk(Name2,C), disk_log:close(Name2), - true = lists:sort(ets:tab2list(TL)) =:= + true = lists:sort(ets:tab2list(TL)) =:= lists:sort(ets:tab2list(element(2,ets:file2tab(FName)))), - Res = [ - begin + Res = [begin {ok,FD} = file:open(FName,[binary,read,write]), {ok, Bin} = file:pread(FD,0,1000), <<B1:N/binary,Ch:8,B2/binary>> = Bin, @@ -4163,7 +4160,7 @@ tabfile_ext4(Config) when is_list(Config) -> ok = file:close(FD), X = case ets:file2tab(FName) of {ok,TL2} -> - true = lists:sort(ets:tab2list(TL)) =/= + true = lists:sort(ets:tab2list(TL)) =/= lists:sort(ets:tab2list(TL2)); _ -> totally_broken @@ -4171,7 +4168,7 @@ tabfile_ext4(Config) when is_list(Config) -> {error,Y} = ets:file2tab(FName,[{verify,true}]), ets:tab2file(TL,FName,[{extended_info,[md5sum]}]), {X,Y} - end || N <- lists:seq(500,600) ], + end || N <- lists:seq(500,600)], io:format("~p~n",[Res]), file:delete(FName), ok. @@ -4402,16 +4399,14 @@ member_do(Opts) -> build_table(L1,L2,Num) -> - T = ets_new(xxx, [ordered_set] - ), + T = ets_new(xxx, [ordered_set]), lists:foreach( fun(X1) -> lists:foreach( fun(X2) -> F = fun(FF,N) -> - ets:insert(T,{{X1,X2,N}, - X1, X2, N}), - case N of + ets:insert(T,{{X1,X2,N}, X1, X2, N}), + case N of 0 -> ok; _ -> @@ -4424,16 +4419,14 @@ build_table(L1,L2,Num) -> T. build_table2(L1,L2,Num) -> - T = ets_new(xxx, [ordered_set] - ), + T = ets_new(xxx, [ordered_set]), lists:foreach( fun(X1) -> lists:foreach( fun(X2) -> F = fun(FF,N) -> - ets:insert(T,{{N,X1,X2}, - N, X1, X2}), - case N of + ets:insert(T,{{N,X1,X2}, N, X1, X2}), + case N of 0 -> ok; _ -> @@ -4724,7 +4717,7 @@ del_one_by_one_dbag_3(T,From,To) -> N = (ets:info(T,size) + 1), Obj2 = {From, integer_to_list(From)}, ets:delete_object(T,Obj2), - N = (ets:info(T,size) + 2) + N = (ets:info(T,size) + 2) end, Next = if From < To -> @@ -4771,14 +4764,14 @@ gen_dets_filename(Config,N) -> filename:join(proplists:get_value(priv_dir,Config), "testdets_" ++ integer_to_list(N) ++ ".dets"). -otp_6842_select_1000(Config) when is_list(Config) -> +otp_6842_select_1000(Config) when is_list(Config) -> Tab = ets_new(xxx,[ordered_set]), [ets:insert(Tab,{X,X}) || X <- lists:seq(1,10000)], AllTrue = lists:duplicate(10,true), AllTrue = [ length( element(1, - ets:select(Tab,[{'_',[],['$_']}],X*1000))) =:= + ets:select(Tab,[{'_',[],['$_']}],X*1000))) =:= X*1000 || X <- lists:seq(1,10) ], Sequences = [[1000,1000,1000,1000,1000,1000,1000,1000,1000,1000], [2000,2000,2000,2000,2000], @@ -4804,7 +4797,13 @@ check_seq(A,B,C) -> false. otp_6338(Config) when is_list(Config) -> - L = binary_to_term(<<131,108,0,0,0,2,104,2,108,0,0,0,2,103,100,0,19,112,112,98,49,95,98,115,49,50,64,98,108,97,100,101,95,48,95,53,0,0,33,50,0,0,0,4,1,98,0,0,23,226,106,100,0,4,101,120,105,116,104,2,108,0,0,0,2,104,2,100,0,3,115,98,109,100,0,19,112,112,98,50,95,98,115,49,50,64,98,108,97,100,101,95,48,95,56,98,0,0,18,231,106,100,0,4,114,101,99,118,106>>), + L = binary_to_term(<<131,108,0,0,0,2,104,2,108,0,0,0,2,103,100,0,19,112,112, + 98,49,95,98,115,49,50,64,98,108,97,100,101,95,48,95,53, + 0,0,33,50,0,0,0,4,1,98,0,0,23,226,106,100,0,4,101,120, + 105,116,104,2,108,0,0,0,2,104,2,100,0,3,115,98,109,100, + 0,19,112,112,98,50,95,98,115,49,50,64,98,108,97,100, + 101,95,48,95,56,98,0,0,18,231,106,100,0,4,114,101,99, + 118,106>>), T = ets_new(xxx,[ordered_set]), lists:foreach(fun(X) -> ets:insert(T,X) end,L), [[4839,recv]] = ets:match(T,{[{sbm,ppb2_bs12@blade_0_8},'$1'],'$2'}), @@ -4823,7 +4822,7 @@ otp_5340_do(Opts) -> ets:delete(T). w(_,0, _) -> ok; -w(T,N, Id) -> +w(T,N, Id) -> ets:insert(T, {N, Id}), w(T,N-1,Id). @@ -4913,7 +4912,7 @@ meta_wb_new(Name, _, Tabs, Opts) -> case (catch ets_new(Name,[named_table|Opts])) of Name -> false = lists:member(Name, Tabs), - [Name | Tabs]; + [Name | Tabs]; {'EXIT',{badarg,_}} -> true = lists:member(Name, Tabs), Tabs @@ -5088,7 +5087,7 @@ meta_lookup_unnamed_read(Config) when is_list(Config) -> Tab end, ExecF = fun(Tab) -> [{key,data}] = ets:lookup(Tab,key), - Tab + Tab end, FiniF = fun(Tab) -> true = ets:delete(Tab) end, @@ -5112,7 +5111,7 @@ meta_lookup_named_read(Config) when is_list(Config) -> Tab end, ExecF = fun(Tab) -> [{key,data}] = ets:lookup(Tab,key), - Tab + Tab end, FiniF = fun(Tab) -> true = ets:delete(Tab) end, @@ -5171,9 +5170,9 @@ smp_fixed_delete_do() -> ets:safe_fixtable(T,true), Buckets = num_of_buckets(T), InitF = fun([ProcN,NumOfProcs|_]) -> {ProcN,NumOfProcs} end, - ExecF = fun({Key,_}) when Key > NumOfObjs -> + ExecF = fun({Key,_}) when Key > NumOfObjs -> [end_of_work]; - ({Key,Increment}) -> + ({Key,Increment}) -> true = ets:delete(T,Key), {Key+Increment,Increment} end, @@ -5202,7 +5201,7 @@ smp_unfix_fix_do() -> T = ets_new(foo,[public,{write_concurrency,true}]), %%Mem = ets:info(T,memory), NumOfObjs = 100000, - Deleted = 50000, + Deleted = 50000, filltabint(T,NumOfObjs), ets:safe_fixtable(T,true), Buckets = num_of_buckets(T), @@ -5215,7 +5214,7 @@ smp_unfix_fix_do() -> true = ets:info(T,fixed), Deleted = get_kept_objects(T), - {Child, Mref} = + {Child, Mref} = my_spawn_opt( fun()-> true = ets:info(T,fixed), @@ -5274,22 +5273,19 @@ otp_8166_do(WC) -> NumOfObjs = 3000, %% Need more than 1000 live objects for match_object to trap one time Deleted = NumOfObjs div 2, filltabint(T,NumOfObjs), - {ReaderPid, ReaderMref} = - my_spawn_opt(fun()-> otp_8166_reader(T,NumOfObjs) end, - [link, monitor, {scheduler,2}]), - {ZombieCrPid, ZombieCrMref} = - my_spawn_opt(fun()-> otp_8166_zombie_creator(T,Deleted) end, - [link, monitor, {scheduler,3}]), + {ReaderPid, ReaderMref} = my_spawn_opt(fun()-> otp_8166_reader(T,NumOfObjs) end, + [link, monitor, {scheduler,2}]), + {ZombieCrPid, ZombieCrMref} = my_spawn_opt(fun()-> otp_8166_zombie_creator(T,Deleted) end, + [link, monitor, {scheduler,3}]), repeat(fun() -> ZombieCrPid ! {loop, self()}, zombies_created = receive_any(), otp_8166_trapper(T, 10, ZombieCrPid) - end, - 100), + end, 100), ReaderPid ! quit, {'DOWN', ReaderMref, process, ReaderPid, normal} = receive_any(), - ZombieCrPid ! quit, + ZombieCrPid ! quit, {'DOWN', ZombieCrMref, process, ZombieCrPid, normal} = receive_any(), false = ets:info(T,fixed), 0 = get_kept_objects(T), @@ -5299,7 +5295,7 @@ otp_8166_do(WC) -> %% Keep reading the table otp_8166_reader(T, NumOfObjs) -> - repeat_while(fun(0) -> + repeat_while(fun(0) -> receive quit -> {false,done} after 0 -> {true,NumOfObjs} end; @@ -5313,14 +5309,14 @@ otp_8166_reader(T, NumOfObjs) -> otp_8166_trapper(T, Try, ZombieCrPid) -> [] = ets:match_object(T,{'_',"Pink Unicorn"}), case {ets:info(T,fixed),Try} of - {true,1} -> + {true,1} -> io:format("failed to provoke unsafe unfix, give up...\n",[]), ZombieCrPid ! unfix; - {true,_} -> + {true,_} -> io:format("trapper too fast, trying again...\n",[]), otp_8166_trapper(T, Try-1, ZombieCrPid); {false,_} -> done - end. + end. %% Fixate table and create some pseudo-deleted objects (zombies) @@ -5340,7 +5336,7 @@ otp_8166_zombie_creator(T,Deleted) -> repeat_while(fun() -> case ets:info(T,safe_fixed_monotonic_time) of {_,[_P1,_P2]} -> false; - _ -> + _ -> receive unfix -> false after 0 -> true end @@ -5397,7 +5393,7 @@ smp_select_delete(Config) when is_list(Config) -> Mod = 17, Zeros = erlang:make_tuple(Mod,0), InitF = fun(_) -> Zeros end, - ExecF = fun(Diffs0) -> + ExecF = fun(Diffs0) -> case rand:uniform(20) of 1 -> Mod = 17, @@ -5419,7 +5415,7 @@ smp_select_delete(Config) when is_list(Config) -> Diffs1; false -> Diffs0 end - end + end end, FiniF = fun(Result) -> Result end, Results = run_workers_do(InitF,ExecF,FiniF,20000), @@ -5430,7 +5426,7 @@ smp_select_delete(Config) when is_list(Config) -> 0, TotCnts), io:format("LeftInTab = ~p\n",[LeftInTab]), LeftInTab = ets:info(T,size), - lists:foldl(fun(Cnt,Eq) -> + lists:foldl(fun(Cnt,Eq) -> WasCnt = ets:select_count(T, [{{'_', '$1'}, [{'=:=', {'rem', '$1', Mod}, Eq}], @@ -5438,7 +5434,7 @@ smp_select_delete(Config) when is_list(Config) -> io:format("~p: ~p =?= ~p\n",[Eq,Cnt,WasCnt]), Cnt = WasCnt, Eq+1 - end, + end, 0, TotCnts), %% May fail as select_delete does not shrink table (enough) %%verify_table_load(T), @@ -5477,8 +5473,8 @@ types_do(Opts) -> %% OTP-9932: Memory overwrite when inserting large integers in compressed bag. %% Will crash with segv on 64-bit opt if not fixed. otp_9932(Config) when is_list(Config) -> - T = ets:new(xxx, [bag, compressed]), - Fun = fun(N) -> + T = ets:new(xxx, [bag, compressed]), + Fun = fun(N) -> Key = {1316110174588445 bsl N,1316110174588583 bsl N}, S = {Key, Key}, true = ets:insert(T, S), @@ -5494,9 +5490,9 @@ otp_9932(Config) when is_list(Config) -> %% write_concurrency table. otp_9423(Config) when is_list(Config) -> InitF = fun(_) -> {0,0} end, - ExecF = fun({S,F}) -> - receive - stop -> + ExecF = fun({S,F}) -> + receive + stop -> io:format("~p got stop\n", [self()]), [end_of_work | {"Succeded=",S,"Failed=",F}] after 0 -> @@ -5592,12 +5588,12 @@ take(Config) when is_list(Config) -> %% Utility functions: %% -add_lists(L1,L2) -> +add_lists(L1,L2) -> add_lists(L1,L2,[]). add_lists([],[],Acc) -> lists:reverse(Acc); add_lists([E1|T1], [E2|T2], Acc) -> - add_lists(T1, T2, [E1+E2 | Acc]). + add_lists(T1, T2, [E1+E2 | Acc]). run_workers(InitF,ExecF,FiniF,Laps) -> run_workers(InitF,ExecF,FiniF,Laps, 0). @@ -5643,9 +5639,9 @@ worker_loop(infinite, ExecF, State) -> worker_loop(N, ExecF, State) -> worker_loop(N-1,ExecF,ExecF(State)). -wait_pids(Pids) -> +wait_pids(Pids) -> wait_pids(Pids,[]). -wait_pids([],Acc) -> +wait_pids([],Acc) -> Acc; wait_pids(Pids, Acc) -> receive @@ -5682,7 +5678,7 @@ etsmem() -> wait_for_memory_deallocations(), AllTabs = lists:map(fun(T) -> {T,ets:info(T,name),ets:info(T,size), - ets:info(T,memory),ets:info(T,type)} + ets:info(T,memory),ets:info(T,type)} end, ets:all()), EtsAllocInfo = erlang:system_info({allocator,ets_alloc}), @@ -5912,7 +5908,7 @@ receive_any() -> receive_any_spinning() -> receive_any_spinning(1000000). receive_any_spinning(Loops) -> - receive_any_spinning(Loops,Loops,1). + receive_any_spinning(Loops,Loops,1). receive_any_spinning(Loops,0,Tries) -> receive M -> io:format("Spinning process ~p got msg ~p after ~p tries\n", [self(),M,Tries]), diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl index 28f9ab81fe..8f2ba0cab2 100644 --- a/lib/stdlib/test/gen_statem_SUITE.erl +++ b/lib/stdlib/test/gen_statem_SUITE.erl @@ -505,10 +505,10 @@ abnormal2(Config) -> {ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []), %% bad return value in the gen_statem loop - {{bad_return_from_state_function,badreturn},_} = + {{{bad_return_from_state_function,badreturn},_},_} = ?EXPECT_FAILURE(gen_statem:call(Pid, badreturn), Reason), receive - {'EXIT',Pid,{bad_return_from_state_function,badreturn}} -> ok + {'EXIT',Pid,{{bad_return_from_state_function,badreturn},_}} -> ok after 5000 -> ct:fail(gen_statem_did_not_die) end, @@ -742,26 +742,40 @@ state_timeout(_Config) -> %% Verify that {state_timeout,0,_} %% comes after next_event and that %% {timeout,0,_} is cancelled by - %% {state_timeout,0,_} + %% pending {state_timeout,0,_} {keep_state, {ok,2,Data}, [{timeout,0,3}]}; - (state_timeout, 2, {ok,2,{Time,From}}) -> - {next_state, state3, 3, + (state_timeout, 2, {ok,2,Data}) -> + %% Verify that timeout 0's are processed + %% in order + {keep_state, {ok,3,Data}, + [{timeout,0,4},{state_timeout,0,5}]}; + (timeout, 4, {ok,3,Data}) -> + %% Verify that timeout 0 is cancelled by + %% enqueued state_timeout 0 and that + %% multiple state_timeout 0 can be enqueued + {keep_state, {ok,4,Data}, + [{state_timeout,0,6},{timeout,0,7}]}; + (state_timeout, 5, {ok,4,Data}) -> + {keep_state, {ok,5,Data}}; + (state_timeout, 6, {ok,5,{Time,From}}) -> + {next_state, state3, 6, [{reply,From,ok}, - {state_timeout,Time,3}]} + {state_timeout,Time,8}]} end, state3 => fun - (info, message_to_self, 3) -> - {keep_state, '3'}; - ({call,From}, check, '3') -> + (info, message_to_self, 6) -> + {keep_state, 7}; + ({call,From}, check, 7) -> {keep_state, From}; - (state_timeout, 3, From) -> + (state_timeout, 8, From) -> {stop_and_reply, normal, {reply,From,ok}} end}, {ok,STM} = gen_statem:start_link(?MODULE, {map_statem,Machine,[]}, []), + sys:trace(STM, true), TRef = erlang:start_timer(1000, self(), kull), ok = gen_statem:call(STM, {go,500}), ok = gen_statem:call(STM, check), @@ -887,7 +901,7 @@ error_format_status(Config) -> gen_statem:start( ?MODULE, start_arg(Config, {data,Data}), []), %% bad return value in the gen_statem loop - {{bad_return_from_state_function,badreturn},_} = + {{{bad_return_from_state_function,badreturn},_},_} = ?EXPECT_FAILURE(gen_statem:call(Pid, badreturn), Reason), receive {error,_, diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl index 416650e27e..a53e99afc9 100644 --- a/lib/stdlib/test/proc_lib_SUITE.erl +++ b/lib/stdlib/test/proc_lib_SUITE.erl @@ -26,7 +26,7 @@ -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2, - crash/1, sync_start_nolink/1, sync_start_link/1, + crash/1, stacktrace/1, sync_start_nolink/1, sync_start_link/1, spawn_opt/1, sp1/0, sp2/0, sp3/1, sp4/2, sp5/1, hibernate/1, stop/1, t_format/1]). -export([ otp_6345/1, init_dont_hang/1]). @@ -50,7 +50,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> - [crash, {group, sync_start}, spawn_opt, hibernate, + [crash, stacktrace, {group, sync_start}, spawn_opt, hibernate, {group, tickets}, stop, t_format]. groups() -> @@ -198,6 +198,31 @@ match_info(Tuple1, Tuple2) when tuple_size(Tuple1) =:= tuple_size(Tuple2) -> match_info(_, _) -> throw(no_match). +stacktrace(Config) when is_list(Config) -> + process_flag(trap_exit, true), + %% Errors. + Pid1 = proc_lib:spawn_link(fun() -> 1 = 2 end), + receive + {'EXIT',Pid1,{{badmatch,2},_Stack1}} -> ok + after 500 -> + ct:fail(error) + end, + %% Exits. + Pid2 = proc_lib:spawn_link(fun() -> exit(bye) end), + receive + {'EXIT',Pid2,bye} -> ok + after 500 -> + ct:fail(exit) + end, + %% Throws. + Pid3 = proc_lib:spawn_link(fun() -> throw(ball) end), + receive + {'EXIT',Pid3,{{nocatch,ball},_Stack3}} -> ok + after 500 -> + ct:fail(throw) + end, + ok. + sync_start_nolink(Config) when is_list(Config) -> _Pid = spawn_link(?MODULE, sp5, [self()]), receive @@ -457,7 +482,7 @@ stop(_Config) -> %% System message is handled, but process dies with other reason %% than the given (in system_terminate/4 below) Pid5 = proc_lib:spawn(SysMsgProc), - {'EXIT',{badmatch,2}} = (catch proc_lib:stop(Pid5,crash,infinity)), + {'EXIT',{{badmatch,2},_Stacktrace}} = (catch proc_lib:stop(Pid5,crash,infinity)), false = erlang:is_process_alive(Pid5), %% Local registered name diff --git a/lib/stdlib/test/rand_SUITE.erl b/lib/stdlib/test/rand_SUITE.erl index cb778c96d4..8e7ac223a7 100644 --- a/lib/stdlib/test/rand_SUITE.erl +++ b/lib/stdlib/test/rand_SUITE.erl @@ -18,13 +18,18 @@ %% %CopyrightEnd% -module(rand_SUITE). --export([all/0, suite/0,groups/0]). +-compile({nowarn_deprecated_function,[{random,seed,1}, + {random,uniform_s,1}, + {random,uniform_s,2}]}). + +-export([all/0, suite/0, groups/0, group/1]). -export([interval_int/1, interval_float/1, seed/1, api_eq/1, reference/1, basic_stats_uniform_1/1, basic_stats_uniform_2/1, basic_stats_normal/1, - plugin/1, measure/1]). + plugin/1, measure/1, + reference_jump_state/1, reference_jump_procdict/1]). -export([test/0, gen/1]). @@ -41,24 +46,35 @@ all() -> api_eq, reference, {group, basic_stats}, - plugin, measure]. + plugin, measure, + {group, reference_jump} + ]. groups() -> [{basic_stats, [parallel], - [basic_stats_uniform_1, basic_stats_uniform_2, basic_stats_normal]}]. + [basic_stats_uniform_1, basic_stats_uniform_2, basic_stats_normal]}, + {reference_jump, [parallel], + [reference_jump_state, reference_jump_procdict]}]. + +group(basic_stats) -> + %% valgrind needs a lot of time + [{timetrap,{minutes,10}}]; +group(reference_jump) -> + %% valgrind needs a lot of time + [{timetrap,{minutes,10}}]. %% A simple helper to test without test_server during dev test() -> Tests = all(), lists:foreach(fun(Test) -> - try - ok = ?MODULE:Test([]), - io:format("~p: ok~n", [Test]) - catch _:Reason -> - io:format("Failed: ~p: ~p ~p~n", - [Test, Reason, erlang:get_stacktrace()]) - end - end, Tests). + try + ok = ?MODULE:Test([]), + io:format("~p: ok~n", [Test]) + catch _:Reason -> + io:format("Failed: ~p: ~p ~p~n", + [Test, Reason, erlang:get_stacktrace()]) + end + end, Tests). algs() -> [exs64, exsplus, exs1024]. @@ -220,7 +236,7 @@ interval_float_1(N) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -%% Check if exs64 algorithm generates the proper sequence. +%% Check if each algorithm generates the proper sequence. reference(Config) when is_list(Config) -> [reference_1(Alg) || Alg <- algs()], ok. @@ -234,7 +250,7 @@ reference_1(Alg) -> io:format("Failed: ~p~n",[Alg]), io:format("Length ~p ~p~n",[length(Refval), length(Testval)]), io:format("Head ~p ~p~n",[hd(Refval), hd(Testval)]), - ok + exit(wrong_value) end. gen(Algo) -> @@ -426,6 +442,112 @@ measure_2(N, State0, Fun) when N > 0 -> measure_2(0, _, _) -> ok. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%% The jump sequence tests has two parts +%% for those with the functional API (jump/1) +%% and for those with the internal state +%% in process dictionary (jump/0). + +-define(LOOP_JUMP, (?LOOP div 1000)). + +%% Check if each algorithm generates the proper jump sequence +%% with the functional API. +reference_jump_state(Config) when is_list(Config) -> + [reference_jump_1(Alg) || Alg <- algs()], + ok. + +reference_jump_1(Alg) -> + Refval = reference_jump_val(Alg), + Testval = gen_jump_1(Alg), + case Refval =:= Testval of + true -> ok; + false -> + io:format("Failed: ~p~n",[Alg]), + io:format("Length ~p ~p~n",[length(Refval), length(Testval)]), + io:format("Head ~p ~p~n",[hd(Refval), hd(Testval)]), + exit(wrong_value) + end. + +gen_jump_1(Algo) -> + Seed = case Algo of + exsplus -> %% Printed with orig 'C' code and this seed + rand:seed_s({exsplus, [12345678|12345678]}); + exs1024 -> %% Printed with orig 'C' code and this seed + rand:seed_s({exs1024, {lists:duplicate(16, 12345678), []}}); + exs64 -> %% Test exception of not_implemented notice + try rand:jump(rand:seed_s(exs64)) + catch + error:not_implemented -> not_implemented + end; + _ -> % unimplemented + not_implemented + end, + case Seed of + not_implemented -> [not_implemented]; + S -> gen_jump_1(?LOOP_JUMP, S, []) + end. + +gen_jump_1(N, State0 = {#{max:=Max}, _}, Acc) when N > 0 -> + {_, State1} = rand:uniform_s(Max, State0), + {Random, State2} = rand:uniform_s(Max, rand:jump(State1)), + case N rem (?LOOP_JUMP div 100) of + 0 -> gen_jump_1(N-1, State2, [Random|Acc]); + _ -> gen_jump_1(N-1, State2, Acc) + end; +gen_jump_1(_, _, Acc) -> lists:reverse(Acc). + +%% Check if each algorithm generates the proper jump sequence +%% with the internal state in the process dictionary. +reference_jump_procdict(Config) when is_list(Config) -> + [reference_jump_0(Alg) || Alg <- algs()], + ok. + +reference_jump_0(Alg) -> + Refval = reference_jump_val(Alg), + Testval = gen_jump_0(Alg), + case Refval =:= Testval of + true -> ok; + false -> + io:format("Failed: ~p~n",[Alg]), + io:format("Length ~p ~p~n",[length(Refval), length(Testval)]), + io:format("Head ~p ~p~n",[hd(Refval), hd(Testval)]), + exit(wrong_value) + end. + +gen_jump_0(Algo) -> + Seed = case Algo of + exsplus -> %% Printed with orig 'C' code and this seed + rand:seed({exsplus, [12345678|12345678]}); + exs1024 -> %% Printed with orig 'C' code and this seed + rand:seed({exs1024, {lists:duplicate(16, 12345678), []}}); + exs64 -> %% Test exception of not_implemented notice + try + _ = rand:seed(exs64), + rand:jump() + catch + error:not_implemented -> not_implemented + end; + _ -> % unimplemented + not_implemented + end, + case Seed of + not_implemented -> [not_implemented]; + S -> + {Seedmap=#{}, _} = S, + Max = maps:get(max, Seedmap), + gen_jump_0(?LOOP_JUMP, Max, []) + end. + +gen_jump_0(N, Max, Acc) when N > 0 -> + _ = rand:uniform(Max), + _ = rand:jump(), + Random = rand:uniform(Max), + case N rem (?LOOP_JUMP div 100) of + 0 -> gen_jump_0(N-1, Max, [Random|Acc]); + _ -> gen_jump_0(N-1, Max, Acc) + end; +gen_jump_0(_, _, Acc) -> lists:reverse(Acc). + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %%% Data reference_val(exs64) -> [16#3737ad0c703ff6c3,16#3868a78fe71adbbd,16#1f01b62b4338b605,16#50876a917437965f, @@ -507,3 +629,61 @@ reference_val(exsplus) -> 16#36f715a249f4ec2,16#1c27629826c50d3,16#914d9a6648726a,16#27f5bf5ce2301e8, 16#3dd493b8012970f,16#be13bed1e00e5c,16#ceef033b74ae10,16#3da38c6a50abe03, 16#15cbd1a421c7a8c,16#22794e3ec6ef3b1,16#26154d26e7ea99f,16#3a66681359a6ab6]. + +%%% + +reference_jump_val(exsplus) -> + [82445318862816932, 145810727464480743, 16514517716894509, 247642377064868650, + 162385642339156908, 251810707075252101, 82288275771998924, 234412731596926322, + 49960883129071044, 200690077681656596, 213743196668671647, 131182800982967108, + 144200072021941728, 263557425008503277, 194858522616874272, 185869394820993172, + 80384502675241453, 262654144824057588, 90033295011291362, 4494510449302659, + 226005372746479588, 116780561309220553, 47048528594475843, 39168929349768743, + 139615163424415552, 55330632656603925, 237575574720486569, 102381140288455025, + 18452933910354323, 150248612130579752, 269358096791922740, 61313433522002187, + 160327361842676597, 185187983548528938, 57378981505594193, 167510799293984067, + 105117045862954303, 176126685946302943, 123590876906828803, 69185336947273487, + 9098689247665808, 49906154674145057, 131575138412788650, 161843880211677185, + 30743946051071186, 187578920583823612, 45008401528636978, 122454158686456658, + 111195992644229524, 17962783958752862, 13579507636941108, 130137843317798663, + 144202635170576832, 132539563255093922, 159785575703967124, 187241848364816640, + 183044737781926478, 12921559769912263, 83553932242922001, 96698298841984688, + 281664320227537824, 224233030818578263, 77812932110318774, 169729351013291728, + 164475402723178734, 242780633011249051, 51095111179609125, 19249189591963554, + 221412426221439180, 265700202856282653, 265342254311932308, 241218503498385511, + 255400887248486575, 212083616929812076, 227947034485840579, 268261881651571692, + 104846262373404908, 49690734329496661, 213259196633566308, 186966479726202436, + 282157378232384574, 11272948584603747, 166540426999573480, 50628164001018755, + 65235580992800860, 230664399047956956, 64575592354687978, 40519393736078511, + 108341851194332747, 115426411532008961, 120656817002338193, 234537867870809797, + 12504080415362731, 45083100453836317, 270968267812126657, 93505647407734103, + 252852934678537969, 258758309277167202, 74250882143432077, 141629095984552833]; + +reference_jump_val(exs1024) -> + [2655961906500790629, 17003395417078685063, 10466831598958356428, 7603399148503548021, + 1650550950190587188, 12294992315080723704, 15743995773860389219, 5492181000145247327, + 14118165228742583601, 1024386975263610703, 10124872895886669513, 6445624517813169301, + 6238575554686562601, 14108646153524288915, 11804141635807832816, 8421575378006186238, + 6354993374304550369, 838493020029548163, 14759355804308819469, 12212491527912522022, + 16943204735100571602, 198964074252287588, 7325922870779721649, 15853102065526570574, + 16294058349151823341, 6153379962047409781, 15874031679495957261, 17299265255608442340, + 984658421210027171, 17408042033939375278, 3326465916992232353, 5222817718770538733, + 13262385796795170510, 15648751121811336061, 6718721549566546451, 7353765235619801875, + 16110995049882478788, 14559143407227563441, 4189805181268804683, 10938587948346538224, + 1635025506014383478, 12619562911869525411, 17469465615861488695, 125252234176411528, + 2004192558503448853, 13175467866790974840, 17712272336167363518, 1710549840100880318, + 17486892343528340916, 5337910082227550967, 8333082060923612691, 6284787745504163856, + 8072221024586708290, 6077032673910717705, 11495200863352251610, 11722792537523099594, + 14642059504258647996, 8595733246938141113, 17223366528010341891, 17447739753327015776, + 6149800490736735996, 11155866914574313276, 7123864553063709909, 15982886296520662323, + 5775920250955521517, 8624640108274906072, 8652974210855988961, 8715770416136907275, + 11841689528820039868, 10991309078149220415, 11758038663970841716, 7308750055935299261, + 15939068400245256963, 6920341533033919644, 8017706063646646166, 15814376391419160498, + 13529376573221932937, 16749061963269842448, 14639730709921425830, 3265850480169354066, + 4569394597532719321, 16594515239012200038, 13372824240764466517, 16892840440503406128, + 11260004846380394643, 2441660009097834955, 10566922722880085440, 11463315545387550692, + 5252492021914937692, 10404636333478845345, 11109538423683960387, 5525267334484537655, + 17936751184378118743, 4224632875737239207, 15888641556987476199, 9586888813112229805, + 9476861567287505094, 14909536929239540332, 17996844556292992842, 2699310519182298856]; + +reference_jump_val(exs64) -> [not_implemented]. diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl index 64dd41e75a..6f3979bb77 100644 --- a/lib/stdlib/test/tar_SUITE.erl +++ b/lib/stdlib/test/tar_SUITE.erl @@ -720,20 +720,25 @@ memory(Config) when is_list(Config) -> %% Test filenames with characters outside the US ASCII range. unicode(Config) when is_list(Config) -> - PrivDir = proplists:get_value(priv_dir, Config), - do_unicode(PrivDir), + run_unicode_node(Config, "+fnu"), case has_transparent_naming() of true -> - Pa = filename:dirname(code:which(?MODULE)), - Node = start_node(unicode, "+fnl -pa "++Pa), - ok = rpc:call(Node, erlang, apply, - [fun() -> do_unicode(PrivDir) end,[]]), - true = test_server:stop_node(Node), - ok; + run_unicode_node(Config, "+fnl"); false -> ok end. +run_unicode_node(Config, Option) -> + PrivDir = proplists:get_value(priv_dir, Config), + Pa = filename:dirname(code:which(?MODULE)), + Args = Option ++ " -pa "++Pa, + io:format("~s\n", [Args]), + Node = start_node(unicode, Args), + ok = rpc:call(Node, erlang, apply, + [fun() -> do_unicode(PrivDir) end,[]]), + true = test_server:stop_node(Node), + ok. + has_transparent_naming() -> case os:type() of {unix,darwin} -> false; @@ -745,10 +750,11 @@ do_unicode(PrivDir) -> ok = file:set_cwd(PrivDir), ok = file:make_dir("unicöde"), - Names = unicode_create_files(), + Names = lists:sort(unicode_create_files()), Tar = "unicöde.tar", ok = erl_tar:create(Tar, ["unicöde"], []), - {ok,Names} = erl_tar:table(Tar, []), + {ok,Names0} = erl_tar:table(Tar, []), + Names = lists:sort(Names0), _ = [ok = file:delete(Name) || Name <- Names], ok = erl_tar:extract(Tar), _ = [{ok,_} = file:read_file(Name) || Name <- Names], |