aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/base64_SUITE.erl2
-rw-r--r--lib/stdlib/test/binary_module_SUITE.erl40
-rw-r--r--lib/stdlib/test/dets_SUITE.erl92
-rw-r--r--lib/stdlib/test/dict_SUITE.erl16
-rw-r--r--lib/stdlib/test/epp_SUITE.erl79
-rw-r--r--lib/stdlib/test/erl_anno_SUITE.erl72
-rw-r--r--lib/stdlib/test/erl_eval_SUITE.erl23
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl76
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl17
-rw-r--r--lib/stdlib/test/erl_scan_SUITE.erl279
-rw-r--r--lib/stdlib/test/ets_SUITE.erl133
-rw-r--r--lib/stdlib/test/ets_tough_SUITE.erl10
-rw-r--r--lib/stdlib/test/filelib_SUITE.erl2
-rw-r--r--lib/stdlib/test/filename_SUITE.erl35
-rw-r--r--lib/stdlib/test/lists_SUITE.erl22
-rw-r--r--lib/stdlib/test/queue_SUITE.erl10
-rw-r--r--lib/stdlib/test/random_iolist.erl16
-rw-r--r--lib/stdlib/test/random_unicode_list.erl18
-rw-r--r--lib/stdlib/test/run_pcre_tests.erl10
-rw-r--r--lib/stdlib/test/select_SUITE.erl21
-rw-r--r--lib/stdlib/test/sets_SUITE.erl22
-rw-r--r--lib/stdlib/test/supervisor_SUITE.erl52
-rw-r--r--lib/stdlib/test/supervisor_deadlock.erl14
-rw-r--r--lib/stdlib/test/timer_SUITE.erl24
24 files changed, 566 insertions, 519 deletions
diff --git a/lib/stdlib/test/base64_SUITE.erl b/lib/stdlib/test/base64_SUITE.erl
index 75eebba6c6..f750145ef0 100644
--- a/lib/stdlib/test/base64_SUITE.erl
+++ b/lib/stdlib/test/base64_SUITE.erl
@@ -340,7 +340,7 @@ interleaved_ws_roundtrip_1([], Base64List, Bin, List) ->
random_byte_list(0, Acc) ->
Acc;
random_byte_list(N, Acc) ->
- random_byte_list(N-1, [random:uniform(255)|Acc]).
+ random_byte_list(N-1, [rand:uniform(255)|Acc]).
make_big_binary(N) ->
list_to_binary(mbb(N, [])).
diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl
index 70c946bdb9..8a2df2bf85 100644
--- a/lib/stdlib/test/binary_module_SUITE.erl
+++ b/lib/stdlib/test/binary_module_SUITE.erl
@@ -536,6 +536,12 @@ do_interesting(Module) ->
?line [<<3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
[<<1>>,<<2>>,<<4>>,<<5>>,<<7>>,<<8>>],
[global,trim_all]),
+ [<<>>] = binary:split(<<>>, <<",">>, []),
+ [] = binary:split(<<>>, <<",">>, [trim]),
+ [] = binary:split(<<>>, <<",">>, [trim_all]),
+ [] = binary:split(<<>>, <<",">>, [global,trim]),
+ [] = binary:split(<<>>, <<",">>, [global,trim_all]),
+
?line badarg = ?MASK_ERROR(
Module:replace(<<1,2,3,4,5,6,7,8>>,
[<<4,5>>,<<7>>,<<8>>],<<99>>,
@@ -710,7 +716,7 @@ do_interesting(Module) ->
encode_decode(doc) ->
["test binary:encode_unsigned/1,2 and binary:decode_unsigned/1,2"];
encode_decode(Config) when is_list(Config) ->
- ?line random:seed({1271,769940,559934}),
+ rand:seed(exsplus, {1271,769940,559934}),
?line ok = encode_decode_loop({1,200},1000), % Need to be long enough
% to create offheap binaries
ok.
@@ -817,7 +823,7 @@ copy(Config) when is_list(Config) ->
?line badarg = ?MASK_ERROR(binary:copy(<<1,2,3>>,
16#FFFFFFFFFFFFFFFFFFFFFFFFFFFFFF)),
?line <<>> = binary:copy(<<>>,10000),
- ?line random:seed({1271,769940,559934}),
+ rand:seed(exsplus, {1271,769940,559934}),
?line ok = random_copy(3000),
?line erts_debug:set_internal_state(available_internal_state,true),
?line io:format("oldlimit: ~p~n",
@@ -855,7 +861,7 @@ random_copy(0) ->
ok;
random_copy(N) ->
Str = random_string({0,N}),
- Num = random:uniform(N div 10+1),
+ Num = rand:uniform(N div 10+1),
A = ?MASK_ERROR(binary:copy(Str,Num)),
B = ?MASK_ERROR(binref:copy(Str,Num)),
C = ?MASK_ERROR(binary:copy(make_unaligned(Str),Num)),
@@ -896,7 +902,7 @@ bin_to_list(Config) when is_list(Config) ->
?line [5] = lists:nthtail(byte_size(X)-1,LX),
?line [0,5] = lists:nthtail(byte_size(X)-2,LX),
?line [0,5] = lists:nthtail(byte_size(Y)-2,LY),
- ?line random:seed({1271,769940,559934}),
+ rand:seed(exsplus, {1271,769940,559934}),
?line ok = random_bin_to_list(5000),
ok.
@@ -963,7 +969,7 @@ parts(Config) when is_list(Config) ->
?line badarg = ?MASK_ERROR(binary:part(Simple,{-1,0})),
?line badarg = ?MASK_ERROR(binary:part(Simple,{7,2})),
?line <<8>> = binary:part(Simple,{7,1}),
- ?line random:seed({1271,769940,559934}),
+ rand:seed(exsplus, {1271,769940,559934}),
?line random_parts(5000),
ok.
@@ -987,15 +993,15 @@ random_parts(N) ->
random_parts(0,_) ->
[];
random_parts(X,N) ->
- Pos = random:uniform(N),
- Len = random:uniform((Pos * 12) div 10),
+ Pos = rand:uniform(N),
+ Len = rand:uniform((Pos * 12) div 10),
[{Pos,Len} | random_parts(X-1,N)].
random_ref_comp(doc) ->
["Test pseudorandomly generated cases against reference imlementation"];
random_ref_comp(Config) when is_list(Config) ->
put(success_counter,0),
- random:seed({1271,769940,559934}),
+ rand:seed(exsplus, {1271,769940,559934}),
Nr = {1,40},
Hr = {30,1000},
I1 = 1500,
@@ -1025,7 +1031,7 @@ random_ref_sr_comp(doc) ->
["Test pseudorandomly generated cases against reference imlementation of split and replace"];
random_ref_sr_comp(Config) when is_list(Config) ->
put(success_counter,0),
- random:seed({1271,769940,559934}),
+ rand:seed(exsplus, {1271,769940,559934}),
Nr = {1,40},
Hr = {30,1000},
I1 = 1500,
@@ -1043,7 +1049,7 @@ random_ref_fla_comp(doc) ->
["Test pseudorandomly generated cases against reference imlementation of split and replace"];
random_ref_fla_comp(Config) when is_list(Config) ->
?line put(success_counter,0),
- ?line random:seed({1271,769940,559934}),
+ rand:seed(exsplus, {1271,769940,559934}),
?line do_random_first_comp(5000,{1,1000}),
?line do_random_last_comp(5000,{1,1000}),
?line do_random_at_comp(5000,{1,1000}),
@@ -1377,24 +1383,24 @@ one_random(N) ->
random_number({Min,Max}) -> % Min and Max are *length* of number in
% decimal positions
- X = random:uniform(Max - Min + 1) + Min - 1,
- list_to_integer([one_random_number(random:uniform(10)) || _ <- lists:seq(1,X)]).
+ X = rand:uniform(Max - Min + 1) + Min - 1,
+ list_to_integer([one_random_number(rand:uniform(10)) || _ <- lists:seq(1,X)]).
random_length({Min,Max}) ->
- random:uniform(Max - Min + 1) + Min - 1.
+ rand:uniform(Max - Min + 1) + Min - 1.
random_string({Min,Max}) ->
- X = random:uniform(Max - Min + 1) + Min - 1,
- list_to_binary([one_random(random:uniform(68)) || _ <- lists:seq(1,X)]).
+ X = rand:uniform(Max - Min + 1) + Min - 1,
+ list_to_binary([one_random(rand:uniform(68)) || _ <- lists:seq(1,X)]).
random_substring({Min,Max},Hay) ->
- X = random:uniform(Max - Min + 1) + Min - 1,
+ X = rand:uniform(Max - Min + 1) + Min - 1,
Y = byte_size(Hay),
Z = if
X > Y -> Y;
true -> X
end,
PMax = Y - Z,
- Pos = random:uniform(PMax + 1) - 1,
+ Pos = rand:uniform(PMax + 1) - 1,
<<_:Pos/binary,Res:Z/binary,_/binary>> = Hay,
Res.
diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl
index 7f5e06524a..ad8829c471 100644
--- a/lib/stdlib/test/dets_SUITE.erl
+++ b/lib/stdlib/test/dets_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2016. 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.
@@ -53,7 +53,8 @@
simultaneous_open/1, insert_new/1, repair_continuation/1,
otp_5487/1, otp_6206/1, otp_6359/1, otp_4738/1, otp_7146/1,
otp_8070/1, otp_8856/1, otp_8898/1, otp_8899/1, otp_8903/1,
- otp_8923/1, otp_9282/1, otp_11245/1, otp_11709/1]).
+ otp_8923/1, otp_9282/1, otp_11245/1, otp_11709/1, otp_13229/1,
+ otp_13260/1]).
-export([dets_dirty_loop/0]).
@@ -110,7 +111,8 @@ all() ->
many_clients, otp_4906, otp_5402, simultaneous_open,
insert_new, repair_continuation, otp_5487, otp_6206,
otp_6359, otp_4738, otp_7146, otp_8070, otp_8856, otp_8898,
- otp_8899, otp_8903, otp_8923, otp_9282, otp_11245, otp_11709
+ otp_8899, otp_8903, otp_8923, otp_9282, otp_11245, otp_11709,
+ otp_13229, otp_13260
].
groups() ->
@@ -1876,9 +1878,33 @@ fixtable(Config, Version) when is_list(Config) ->
{ok, _} = dets:open_file(T, [{type, duplicate_bag} | Args]),
%% In a fixed table, delete and re-insert an object.
ok = dets:insert(T, {1, a, b}),
+ SysBefore = erlang:timestamp(),
+ MonBefore = erlang:monotonic_time(),
dets:safe_fixtable(T, true),
+ MonAfter = erlang:monotonic_time(),
+ SysAfter = erlang:timestamp(),
+ Self = self(),
+ {FixMonTime,[{Self,1}]} = dets:info(T,safe_fixed_monotonic_time),
+ {FixSysTime,[{Self,1}]} = dets:info(T,safe_fixed),
+ true = is_integer(FixMonTime),
+ true = MonBefore =< FixMonTime,
+ true = FixMonTime =< MonAfter,
+ {FstMs,FstS,FstUs} = FixSysTime,
+ true = is_integer(FstMs),
+ true = is_integer(FstS),
+ true = is_integer(FstUs),
+ case erlang:system_info(time_warp_mode) of
+ no_time_warp ->
+ true = timer:now_diff(FixSysTime, SysBefore) >= 0,
+ true = timer:now_diff(SysAfter, FixSysTime) >= 0;
+ _ ->
+ %% ets:info(Tab,safe_fixed) not timewarp safe...
+ ignore
+ end,
ok = dets:match_delete(T, {1, a, b}),
ok = dets:insert(T, {1, a, b}),
+ {FixMonTime,[{Self,1}]} = dets:info(T,safe_fixed_monotonic_time),
+ {FixSysTime,[{Self,1}]} = dets:info(T,safe_fixed),
dets:safe_fixtable(T, false),
1 = length(dets:match_object(T, '_')),
@@ -3988,6 +4014,66 @@ otp_11709(Config) when is_list(Config) ->
_ = file:delete(File),
ok.
+otp_13229(doc) ->
+ ["OTP-13229. open_file() exits with badarg when given binary file name."];
+otp_13229(_Config) ->
+ F = <<"binfile.tab">>,
+ try dets:open_file(name, [{file, F}]) of
+ R ->
+ exit({open_succeeded, R})
+ catch
+ error:badarg ->
+ ok
+ end.
+
+otp_13260(doc) ->
+ ["OTP-13260. Race when opening a table."];
+otp_13260(Config) ->
+ [ok] = lists:usort([otp_13260_1(Config) || _ <- lists:seq(1, 3)]),
+ ok.
+
+otp_13260_1(Config) ->
+ Tab = otp_13260,
+ File = filename(Tab, Config),
+ N = 20,
+ P = self(),
+ Pids = [spawn_link(fun() -> counter(P, Tab, File) end) ||
+ _ <- lists:seq(1, N)],
+ Rs = rec(Pids),
+ true = lists:all(fun(R) -> is_integer(R) end, Rs),
+ wait_for_close(Tab).
+
+rec([]) ->
+ [];
+rec([Pid | Pids]) ->
+ receive {Pid, R} ->
+ [R | rec(Pids)]
+ end.
+
+%% One may have to run the test several times to trigger the bug.
+counter(P, Tab, File) ->
+ Key = key,
+ N = case catch dets:update_counter(Tab, Key, 1) of
+ {'EXIT', _} ->
+ {ok, Tab} = dets:open_file(Tab, [{file, File}]),
+ ok = dets:insert(Tab, {Key, 1}),
+ dets:update_counter(Tab, Key, 1);
+ N1 when is_integer(N1) ->
+ N1;
+ DetsBug ->
+ DetsBug
+ end,
+ P ! {self(), N}.
+
+wait_for_close(Tab) ->
+ case dets:info(Tab, owner) of
+ undefined ->
+ ok;
+ _ ->
+ timer:sleep(100),
+ wait_for_close(Tab)
+ end.
+
%%
%% Parts common to several test cases
%%
diff --git a/lib/stdlib/test/dict_SUITE.erl b/lib/stdlib/test/dict_SUITE.erl
index 648154ebbe..aff73b176d 100644
--- a/lib/stdlib/test/dict_SUITE.erl
+++ b/lib/stdlib/test/dict_SUITE.erl
@@ -108,7 +108,7 @@ iterate_1(M) ->
M(empty, []).
iterate_2(M) ->
- random:seed(1, 2, 42),
+ rand:seed(exsplus, {1,2,42}),
iter_tree(M, 1000).
iter_tree(_M, 0) ->
@@ -117,7 +117,7 @@ iter_tree(M, N) ->
L = [{I, I} || I <- lists:seq(1, N)],
T = M(from_list, L),
L = lists:reverse(iterate_tree(M, T)),
- R = random:uniform(N),
+ R = rand:uniform(N),
KV = lists:reverse(iterate_tree_from(M, R, T)),
KV = [P || P={K,_} <- L, K >= R],
iter_tree(M, N-1).
@@ -156,7 +156,7 @@ test_all(Tester) ->
spawn_tester(M, Tester) ->
Parent = self(),
spawn_link(fun() ->
- random:seed(1, 2, 42),
+ rand:seed(exsplus, {1,2,42}),
S = Tester(M),
Res = {M(size, S),lists:sort(M(to_list, S))},
Parent ! {result,self(),Res}
@@ -194,12 +194,12 @@ rnd_list_1(0, Acc) ->
Acc;
rnd_list_1(N, Acc) ->
Key = atomic_rnd_term(),
- Value = random:uniform(100),
+ Value = rand:uniform(100),
rnd_list_1(N-1, [{Key,Value}|Acc]).
atomic_rnd_term() ->
- case random:uniform(3) of
- 1 -> list_to_atom(integer_to_list($\s+random:uniform(94))++"rnd");
- 2 -> random:uniform();
- 3 -> random:uniform(50)-37
+ case rand:uniform(3) of
+ 1 -> list_to_atom(integer_to_list($\s+rand:uniform(94))++"rnd");
+ 2 -> rand:uniform();
+ 3 -> rand:uniform(50)-37
end.
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index 4e5df661b3..4c007e76ad 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -27,7 +27,7 @@
pmod/1, not_circular/1, skip_header/1, otp_6277/1, otp_7702/1,
otp_8130/1, overload_mac/1, otp_8388/1, otp_8470/1, otp_8503/1,
otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1, otp_10820/1,
- otp_11728/1, encoding/1]).
+ otp_11728/1, encoding/1, extends/1]).
-export([epp_parse_erl_form/2]).
@@ -70,7 +70,7 @@ all() ->
not_circular, skip_header, otp_6277, otp_7702, otp_8130,
overload_mac, otp_8388, otp_8470, otp_8503, otp_8562,
otp_8665, otp_8911, otp_10302, otp_10820, otp_11728,
- encoding].
+ encoding, extends].
groups() ->
[{upcase_mac, [], [upcase_mac_1, upcase_mac_2]},
@@ -621,6 +621,10 @@ otp_8130(Config) when is_list(Config) ->
" 2 end,\n"
" 7),\n"
" {2,7} =\n"
+ " ?M1(begin 1 = fun _Name () -> 1 end(),\n"
+ " 2 end,\n"
+ " 7),\n"
+ " {2,7} =\n"
" ?M1(begin 1 = fun t0/0(),\n"
" 2 end,\n"
" 7),\n"
@@ -645,6 +649,9 @@ otp_8130(Config) when is_list(Config) ->
" ?M1(begin yes = try 1 of 1 -> yes after foo end,\n"
" 2 end,\n"
" 7),\n"
+ " {[42],7} =\n"
+ " ?M1([42],\n"
+ " 7),\n"
"ok.\n">>,
ok},
@@ -728,11 +735,16 @@ otp_8130(Config) when is_list(Config) ->
{errors,[{{2,2},epp,{include,lib,"$apa/foo.hrl"}}],[]}},
- {otp_8130_c9,
+ {otp_8130_c9a,
<<"-define(S, ?S).\n"
"t() -> ?S.\n">>,
{errors,[{{2,9},epp,{circular,'S', none}}],[]}},
+ {otp_8130_c9b,
+ <<"-define(S(), ?S()).\n"
+ "t() -> ?S().\n">>,
+ {errors,[{{2,9},epp,{circular,'S', 0}}],[]}},
+
{otp_8130_c10,
<<"\n-file.">>,
{errors,[{{2,2},epp,{bad,file}}],[]}},
@@ -799,6 +811,10 @@ otp_8130(Config) when is_list(Config) ->
<<"\n-include(\"no such file.erl\").\n">>,
{errors,[{{2,2},epp,{include,file,"no such file.erl"}}],[]}},
+ {otp_8130_c25,
+ <<"\n-define(A.\n">>,
+ {errors,[{{2,2},epp,{bad,define}}],[]}},
+
{otp_8130_7,
<<"-record(b, {b}).\n"
"-define(A, {{a,#b.b.\n"
@@ -826,14 +842,14 @@ otp_8130(Config) when is_list(Config) ->
"-define(a, 3.14).\n"
"t() -> ?a.\n"),
?line {ok,Epp} = epp:open(File, []),
- ?line ['BASE_MODULE','BASE_MODULE_STRING','BEAM','FILE','LINE',
- 'MACHINE','MODULE','MODULE_STRING'] = macs(Epp),
+ PreDefMacs = macs(Epp),
+ ['BASE_MODULE','BASE_MODULE_STRING','BEAM','FILE','LINE',
+ 'MACHINE','MODULE','MODULE_STRING'] = PreDefMacs,
?line {ok,[{'-',_},{atom,_,file}|_]} = epp:scan_erl_form(Epp),
?line {ok,[{'-',_},{atom,_,module}|_]} = epp:scan_erl_form(Epp),
?line {ok,[{atom,_,t}|_]} = epp:scan_erl_form(Epp),
?line {eof,_} = epp:scan_erl_form(Epp),
- ?line ['BASE_MODULE','BASE_MODULE_STRING','BEAM','FILE','LINE',
- 'MACHINE','MODULE','MODULE_STRING',a] = macs(Epp),
+ [a] = macs(Epp) -- PreDefMacs,
?line epp:close(Epp),
%% escript
@@ -1476,6 +1492,20 @@ encoding(Config) when is_list(Config) ->
epp_parse_file(ErlFile, [{default_encoding,utf8},extra]),
ok.
+extends(Config) ->
+ Cs = [{extends_c1,
+ <<"-extends(some.other.module).\n">>,
+ {errors,[{1,erl_parse,["syntax error before: ","'.'"]}],[]}}],
+ [] = compile(Config, Cs),
+
+ Ts = [{extends_1,
+ <<"-extends(some_other_module).\n"
+ "t() -> {?BASE_MODULE,?BASE_MODULE_STRING}.\n">>,
+ {some_other_module,"some_other_module"}}],
+
+ [] = run(Config, Ts),
+ ok.
+
check(Config, Tests) ->
eval_tests(Config, fun check_test/2, Tests).
@@ -1504,15 +1534,17 @@ eval_tests(Config, Fun, Tests) ->
check_test(Config, Test) ->
Filename = "epp_test.erl",
- ?line PrivDir = ?config(priv_dir, Config),
- ?line File = filename:join(PrivDir, Filename),
- ?line ok = file:write_file(File, Test),
- ?line case epp:parse_file(File, [PrivDir], []) of
- {ok,Forms} ->
- [E || E={error,_} <- Forms];
- {error,Error} ->
- Error
- end.
+ PrivDir = ?config(priv_dir, Config),
+ File = filename:join(PrivDir, Filename),
+ ok = file:write_file(File, Test),
+ case epp:parse_file(File, [PrivDir], []) of
+ {ok,Forms} ->
+ Errors = [E || E={error,_} <- Forms],
+ call_format_error([E || {error,E} <- Errors]),
+ Errors;
+ {error,Error} ->
+ Error
+ end.
compile_test(Config, Test0) ->
Test = [<<"-module(epp_test). -compile(export_all). ">>, Test0],
@@ -1528,8 +1560,11 @@ compile_test(Config, Test0) ->
warnings(File, Ws) ->
case lists:append([W || {F, W} <- Ws, F =:= File]) of
- [] -> [];
- L -> {warnings, L}
+ [] ->
+ [];
+ L ->
+ call_format_error(L),
+ {warnings, L}
end.
compile_file(File, Opts) ->
@@ -1540,12 +1575,20 @@ compile_file(File, Opts) ->
end.
errs([{File,Es}|L], File) ->
+ call_format_error(Es),
Es ++ errs(L, File);
errs([_|L], File) ->
errs(L, File);
errs([], _File) ->
[].
+%% Smoke test and coverage of format_error/1.
+call_format_error([{_,M,E}|T]) ->
+ _ = M:format_error(E),
+ call_format_error(T);
+call_format_error([]) ->
+ ok.
+
epp_parse_file(File, Opts) ->
case epp:parse_file(File, Opts) of
{ok, Forms} ->
diff --git a/lib/stdlib/test/erl_anno_SUITE.erl b/lib/stdlib/test/erl_anno_SUITE.erl
index 66b02151a0..0369455846 100644
--- a/lib/stdlib/test/erl_anno_SUITE.erl
+++ b/lib/stdlib/test/erl_anno_SUITE.erl
@@ -34,7 +34,7 @@
init_per_testcase/2, end_per_testcase/2]).
-export([new/1, is_anno/1, generated/1, end_location/1, file/1,
- line/1, location/1, record/1, text/1, bad/1, neg_line/1]).
+ line/1, location/1, record/1, text/1, bad/1]).
-export([parse_abstract/1, mapfold_anno/1]).
@@ -43,7 +43,7 @@ all() ->
groups() ->
[{anno, [], [new, is_anno, generated, end_location, file,
- line, location, record, text, bad, neg_line]},
+ line, location, record, text, bad]},
{parse, [], [parse_abstract, mapfold_anno]}].
suite() -> [{ct_hooks,[ts_install_cth]}].
@@ -229,74 +229,6 @@ bad(_Config) ->
(catch erl_anno:record(bad)), % 1st arg not opaque
ok.
-neg_line(doc) ->
- ["Test negative line numbers (OTP 18)"];
-neg_line(_Config) ->
- neg_line1(false),
- neg_line1(true),
- ok.
-
-neg_line1(TextToo) ->
- Minus8_0 = erl_anno:new(-8),
- Plus8_0 = erl_anno:new(8),
- Minus8C_0 = erl_anno:new({-8, 17}),
- Plus8C_0 = erl_anno:new({8, 17}),
-
- [Minus8, Plus8, Minus8C, Plus8C] =
- [case TextToo of
- true ->
- erl_anno:set_text("foo", A);
- false ->
- A
- end || A <- [Minus8_0, Plus8_0, Minus8C_0, Plus8C_0]],
-
- tst(-3, erl_anno:set_location(3, Minus8)),
- tst(-3, erl_anno:set_location(-3, Plus8)),
- tst(-3, erl_anno:set_location(-3, Minus8)),
- tst({-3,9}, erl_anno:set_location({3, 9}, Minus8)),
- tst({-3,9}, erl_anno:set_location({-3, 9}, Plus8)),
- tst({-3,9}, erl_anno:set_location({-3, 9}, Minus8)),
- tst(-3, erl_anno:set_location(3, Minus8C)),
- tst(-3, erl_anno:set_location(-3, Plus8C)),
- tst(-3, erl_anno:set_location(-3, Minus8C)),
- tst({-3,9}, erl_anno:set_location({3, 9}, Minus8C)),
- tst({-3,9}, erl_anno:set_location({-3, 9}, Plus8C)),
- tst({-3,9}, erl_anno:set_location({-3, 9}, Minus8C)),
-
- tst(-8, erl_anno:set_generated(true, Plus8)),
- tst(-8, erl_anno:set_generated(true, Minus8)),
- tst({-8,17}, erl_anno:set_generated(true, Plus8C)),
- tst({-8,17}, erl_anno:set_generated(true, Minus8C)),
- tst(8, erl_anno:set_generated(false, Plus8)),
- tst(8, erl_anno:set_generated(false, Minus8)),
- tst({8,17}, erl_anno:set_generated(false, Plus8C)),
- tst({8,17}, erl_anno:set_generated(false, Minus8C)),
-
- tst(-3, erl_anno:set_line(3, Minus8)),
- tst(-3, erl_anno:set_line(-3, Plus8)),
- tst(-3, erl_anno:set_line(-3, Minus8)),
- tst({-3,17}, erl_anno:set_line(3, Minus8C)),
- tst({-3,17}, erl_anno:set_line(-3, Plus8C)),
- tst({-3,17}, erl_anno:set_line(-3, Minus8C)),
- ok.
-
-tst(Term, Anno) ->
- ?format("Term: ~p\n", [Term]),
- ?format("Anno: ~p\n", [Anno]),
- case anno_to_term(Anno) of
- Term ->
- ok;
- Else ->
- case lists:keyfind(location, 1, Else) of
- {location, Term} ->
- ok;
- _Else2 ->
- ?format("Else2 ~p\n", [_Else2]),
- io:format("expected ~p\n got ~p\n", [Term, Else]),
- exit({Term, Else})
- end
- end.
-
parse_abstract(doc) ->
["Test erl_parse:new_anno/1, erl_parse:anno_to_term/1"
", and erl_parse:anno_from_term/1"];
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index b9c4ad0a46..c21c4e61ee 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2016. 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.
@@ -39,6 +39,7 @@
otp_7550/1,
otp_8133/1,
otp_10622/1,
+ otp_13228/1,
funs/1,
try_catch/1,
eval_expr_5/1,
@@ -83,7 +84,8 @@ all() ->
pattern_expr, match_bin, guard_3, guard_4, guard_5, lc,
simple_cases, unary_plus, apply_atom, otp_5269,
otp_6539, otp_6543, otp_6787, otp_6977, otp_7550,
- otp_8133, otp_10622, funs, try_catch, eval_expr_5, zero_width,
+ otp_8133, otp_10622, otp_13228,
+ funs, try_catch, eval_expr_5, zero_width,
eep37, eep43].
groups() ->
@@ -1042,6 +1044,13 @@ otp_10622(Config) when is_list(Config) ->
ok.
+otp_13228(doc) ->
+ ["OTP-13228. ERL-32: non-local function handler bug."];
+otp_13228(_Config) ->
+ LFH = {value, fun(foo, [io_fwrite]) -> worked end},
+ EFH = {value, fun({io, fwrite}, [atom]) -> io_fwrite end},
+ {value, worked, []} = parse_and_run("foo(io:fwrite(atom)).", LFH, EFH).
+
funs(doc) ->
["Simple cases, just to cover some code."];
funs(suite) ->
@@ -1483,6 +1492,16 @@ eep43(Config) when is_list(Config) ->
" #{ K1 := 1, K2 := 2, K3 := 3, {2,2} := 4} = Map "
"end.",
#{ 1 => 1, <<42:301>> => 2, {3,<<42:301>>} => 3, {2,2} => 4}),
+ check(fun () ->
+ X = key,
+ (fun(#{X := value}) -> true end)(#{X => value})
+ end,
+ "begin "
+ " X = key, "
+ " (fun(#{X := value}) -> true end)(#{X => value}) "
+ "end.",
+ true),
+
error_check("[camembert]#{}.", {badmap,[camembert]}),
error_check("[camembert]#{nonexisting:=v}.", {badmap,[camembert]}),
error_check("#{} = 1.", {badmatch,1}),
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 5347ccaf1f..c5e2e5609d 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2015. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2016. 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.
@@ -65,7 +65,7 @@
too_many_arguments/1,
basic_errors/1,bin_syntax_errors/1,
predef/1,
- maps/1,maps_type/1,otp_11851/1,otp_12195/1
+ maps/1,maps_type/1,otp_11851/1,otp_11879/1,otp_13230/1
]).
% Default timetrap timeout (set in init_per_testcase).
@@ -94,7 +94,7 @@ all() ->
bif_clash, behaviour_basic, behaviour_multiple, otp_11861,
otp_7550, otp_8051, format_warn, {group, on_load},
too_many_arguments, basic_errors, bin_syntax_errors, predef,
- maps, maps_type, otp_11851, otp_12195].
+ maps, maps_type, otp_11851, otp_11879, otp_13230].
groups() ->
[{unused_vars_warn, [],
@@ -1296,12 +1296,16 @@ unsized_binary_in_bin_gen_pattern(Config) when is_list(Config) ->
Ts = [{unsized_binary_in_bin_gen_pattern,
<<"t({bc,binary,Bin}) ->
<< <<X,Tail/binary>> || <<X,Tail/binary>> <= Bin >>;
+ t({bc,bytes,Bin}) ->
+ << <<X,Tail/binary>> || <<X,Tail/bytes>> <= Bin >>;
t({bc,bits,Bin}) ->
<< <<X,Tail/bits>> || <<X,Tail/bits>> <= Bin >>;
t({bc,bitstring,Bin}) ->
<< <<X,Tail/bits>> || <<X,Tail/bitstring>> <= Bin >>;
t({lc,binary,Bin}) ->
[ {X,Tail} || <<X,Tail/binary>> <= Bin ];
+ t({lc,bytes,Bin}) ->
+ [ {X,Tail} || <<X,Tail/bytes>> <= Bin ];
t({lc,bits,Bin}) ->
[ {X,Tail} || <<X,Tail/bits>> <= Bin ];
t({lc,bitstring,Bin}) ->
@@ -1313,7 +1317,9 @@ unsized_binary_in_bin_gen_pattern(Config) when is_list(Config) ->
{6,erl_lint,unsized_binary_in_bin_gen_pattern},
{8,erl_lint,unsized_binary_in_bin_gen_pattern},
{10,erl_lint,unsized_binary_in_bin_gen_pattern},
- {12,erl_lint,unsized_binary_in_bin_gen_pattern}],
+ {12,erl_lint,unsized_binary_in_bin_gen_pattern},
+ {14,erl_lint,unsized_binary_in_bin_gen_pattern},
+ {16,erl_lint,unsized_binary_in_bin_gen_pattern}],
[]}}],
[] = run(Config, Ts),
ok.
@@ -3843,38 +3849,36 @@ otp_11851(Config) when is_list(Config) ->
[] = run(Config, Ts),
ok.
-otp_12195(doc) ->
- "OTP-12195: Check obsolete types (tailor made for OTP 18).";
-otp_12195(Config) when is_list(Config) ->
- Ts = [{otp_12195_1,
- <<"-export_type([r1/0]).
- -type r1() :: erl_scan:line()
- | erl_scan:column()
- | erl_scan:location()
- | erl_anno:line().">>,
- [],
- {warnings,[{2,erl_lint,
- {deprecated_type,{erl_scan,line,0},
- "deprecated (will be removed in OTP 19); "
- "use erl_anno:line() instead"}},
- {3,erl_lint,
- {deprecated_type,{erl_scan,column,0},
- "deprecated (will be removed in OTP 19); use "
- "erl_anno:column() instead"}},
- {4,erl_lint,
- {deprecated_type,{erl_scan,location,0},
- "deprecated (will be removed in OTP 19); "
- "use erl_anno:location() instead"}}]}},
- {otp_12195_2,
- <<"-export_type([r1/0]).
- -compile(nowarn_deprecated_type).
- -type r1() :: erl_scan:line()
- | erl_scan:column()
- | erl_scan:location()
- | erl_anno:line().">>,
- [],
- []}],
- [] = run(Config, Ts),
+otp_11879(doc) ->
+ "OTP-11879: The -spec f/a :: (As) -> B; syntax removed, "
+ "and is_subtype/2 deprecated";
+otp_11879(_Config) ->
+ Fs = [{attribute,0,file,{"file.erl",0}},
+ {attribute,0,module,m},
+ {attribute,1,spec,
+ {{f,1},
+ [{type,2,'fun',[{type,3,product,[{var,4,'V1'},
+ {var,5,'V1'}]},
+ {type,6,integer,[]}]}]}},
+ {attribute,20,callback,
+ {{cb,21},
+ [{type,22,'fun',[{type,23,product,[{var,24,'V1'},
+ {var,25,'V1'}]},
+ {type,6,integer,[]}]}]}}],
+ {error,[{"file.erl",
+ [{1,erl_lint,{spec_fun_undefined,{f,1}}},
+ {2,erl_lint,spec_wrong_arity},
+ {22,erl_lint,callback_wrong_arity}]}],
+ []} = compile:forms(Fs, [return,report]),
+ ok.
+
+otp_13230(doc) ->
+ "OTP-13230: -deprecated without -module";
+otp_13230(Config) when is_list(Config) ->
+ Abstr = <<"-deprecated([{frutt,0,next_version}]).">>,
+ {errors,[{1,erl_lint,undefined_module},
+ {1,erl_lint,{bad_deprecated,{frutt,0}}}],
+ []} = run_test2(Config, Abstr, []),
ok.
run(Config, Tests) ->
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index 92e2764c65..8a128b3815 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -876,6 +876,9 @@ type_examples() ->
{ex30,<<"-type t99() ::"
"{t2(),'\\'t::4'(),t5(),t6(),t7(),t8(),t10(),t14(),"
"t15(),t20(),t21(), t22(),t25()}. ">>},
+ %% Writing constraints as is_subtype(V, T) is not supported since
+ %% Erlang/OTP 19.0, but as long as the parser recognizes the
+ %% is_subtype(V, T) syntax, we need a few examples of the syntax.
{ex31,<<"-spec t1(FooBar :: t99()) -> t99();"
"(t2()) -> t2();"
"('\\'t::4'()) -> '\\'t::4'() when is_subtype('\\'t::4'(), t24);"
@@ -928,7 +931,9 @@ otp_8522(Config) when is_list(Config) ->
?line {ok, _} = compile:file(FileName, [{outdir,?privdir},debug_info]),
BF = filename("otp_8522", Config),
?line {ok, A} = beam_lib:chunks(BF, [abstract_code]),
- ?line 5 = count_atom(A, undefined),
+ %% OTP-12719: Since 'undefined' is no longer added by the Erlang
+ %% Parser, the number of 'undefined' is 4. It used to be 5.
+ ?line 4 = count_atom(A, undefined),
ok.
count_atom(A, A) ->
@@ -998,18 +1003,10 @@ otp_8567(Config) when is_list(Config) ->
"t() ->\n"
" 3.\n"
"\n"
- "-spec(t1/1 :: (ot()) -> ot1()).\n"
- "t1(A) ->\n"
- " A.\n"
- "\n"
"-spec(t2 (ot()) -> ot1()).\n"
"t2(A) ->\n"
" A.\n"
"\n"
- "-spec(otp_8567:t3/1 :: (ot()) -> ot1()).\n"
- "t3(A) ->\n"
- " A.\n"
- "\n"
"-spec(otp_8567:t4 (ot()) -> ot1()).\n"
"t4(A) ->\n"
" A.\n">>,
@@ -1065,7 +1062,7 @@ otp_9147(Config) when is_list(Config) ->
?line {ok, Bin} = file:read_file(PFileName),
%% The parentheses around "F1 :: a | b" are new (bugfix).
?line true =
- lists:member("-record(undef,{f1 :: undefined | (F1 :: a | b)}).",
+ lists:member("-record(undef,{f1 :: F1 :: a | b}).",
string:tokens(binary_to_list(Bin), "\n")),
ok.
diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl
index 12ea3d128c..db669aae99 100644
--- a/lib/stdlib/test/erl_scan_SUITE.erl
+++ b/lib/stdlib/test/erl_scan_SUITE.erl
@@ -191,8 +191,7 @@ otp_7810(Config) when is_list(Config) ->
?line ok = more_chars(),
?line ok = more_options(),
- ?line ok = attributes_info(),
- ?line ok = set_attribute(),
+ ?line ok = anno_info(),
ok.
@@ -269,7 +268,7 @@ punctuations() ->
comments() ->
?line test("a %%\n b"),
- {ok,[],1} = erl_scan_string("%"),
+ ?line {ok,[],1} = erl_scan_string("%"),
?line test("a %%\n b"),
{ok,[{atom,{1,1},a},{atom,{2,2},b}],{2,3}} =
erl_scan_string("a %%\n b", {1,1}),
@@ -338,7 +337,7 @@ base_integers() ->
erl_scan:string(Str)
end || {BS,S} <- [{"3","3"},{"15","f"}, {"12","c"}] ],
- {ok,[{integer,1,239},{'@',1}],1} = erl_scan_string("16#ef@"),
+ ?line {ok,[{integer,1,239},{'@',1}],1} = erl_scan_string("16#ef@"),
{ok,[{integer,{1,1},239},{'@',{1,6}}],{1,7}} =
erl_scan_string("16#ef@", {1,1}, []),
{ok,[{integer,{1,1},14},{atom,{1,5},g@}],{1,7}} =
@@ -387,20 +386,15 @@ dots() ->
R2 = erl_scan_string(S, {1,1}, [])
end || {S, R, R2} <- Dot],
- ?line {ok,[{dot,_}=T1],{1,2}} = erl_scan:string(".", {1,1}, text),
- ?line [{column,1},{length,1},{line,1},{text,"."}] =
- erl_scan:token_info(T1, [column, length, line, text]),
- ?line {ok,[{dot,_}=T2],{1,3}} = erl_scan:string(".%", {1,1}, text),
- ?line [{column,1},{length,1},{line,1},{text,"."}] =
- erl_scan:token_info(T2, [column, length, line, text]),
- ?line {ok,[{dot,_}=T3],{1,6}} =
+ {ok,[{dot,_}=T1],{1,2}} = erl_scan:string(".", {1,1}, text),
+ [1, 1, "."] = token_info(T1),
+ {ok,[{dot,_}=T2],{1,3}} = erl_scan:string(".%", {1,1}, text),
+ [1, 1, "."] = token_info(T2),
+ {ok,[{dot,_}=T3],{1,6}} =
erl_scan:string(".% öh", {1,1}, text),
- ?line [{column,1},{length,1},{line,1},{text,"."}] =
- erl_scan:token_info(T3, [column, length, line, text]),
- ?line {error,{{1,2},erl_scan,char},{1,3}} =
- erl_scan:string(".$", {1,1}),
- ?line {error,{{1,2},erl_scan,char},{1,4}} =
- erl_scan:string(".$\\", {1,1}),
+ [1, 1, "."] = token_info(T3),
+ {error,{{1,2},erl_scan,char},{1,3}} = erl_scan:string(".$", {1,1}),
+ {error,{{1,2},erl_scan,char},{1,4}} = erl_scan:string(".$\\", {1,1}),
test_string(". ", [{dot,{1,1}}]),
test_string(". ", [{dot,{1,1}}]),
@@ -413,18 +407,18 @@ dots() ->
test_string(".a", [{'.',{1,1}},{atom,{1,2},a}]),
test_string("%. \n. ", [{dot,{2,1}}]),
- ?line {more,C} = erl_scan:tokens([], "%. ",{1,1}, return),
+ {more,C} = erl_scan:tokens([], "%. ",{1,1}, return),
{done,{ok,[{comment,{1,1},"%. "},
{white_space,{1,4},"\n"},
{dot,{2,1}}],
{2,3}}, ""} =
erl_scan_tokens(C, "\n. ", {1,1}, return), % any loc, any options
- ?line [test_string(S, R) ||
- {S, R} <- [{".$\n", [{'.',{1,1}},{char,{1,2},$\n}]},
- {"$\\\n", [{char,{1,1},$\n}]},
- {"'\\\n'", [{atom,{1,1},'\n'}]},
- {"$\n", [{char,{1,1},$\n}]}] ],
+ [test_string(S, R) ||
+ {S, R} <- [{".$\n", [{'.',{1,1}},{char,{1,2},$\n}]},
+ {"$\\\n", [{char,{1,1},$\n}]},
+ {"'\\\n'", [{atom,{1,1},'\n'}]},
+ {"$\n", [{char,{1,1},$\n}]}] ],
ok.
chars() ->
@@ -540,8 +534,8 @@ eof() ->
%% A dot followed by eof is special:
?line {more, C} = erl_scan:tokens([], "a.", 1),
- {done,{ok,[{atom,1,a},{dot,1}],1},eof} = erl_scan_tokens(C,eof,1),
- {ok,[{atom,1,foo},{dot,1}],1} = erl_scan_string("foo."),
+ ?line {done,{ok,[{atom,1,a},{dot,1}],1},eof} = erl_scan_tokens(C,eof,1),
+ ?line {ok,[{atom,1,foo},{dot,1}],1} = erl_scan_string("foo."),
%% With column.
{more, CCol} = erl_scan:tokens([], "a.", {1,1}),
@@ -655,145 +649,72 @@ options() ->
ok.
more_options() ->
- ?line {ok,[{atom,A1,foo}],{19,20}} =
+ {ok,[{atom,_,foo}=T1],{19,20}} =
erl_scan:string("foo", {19,17},[]),
- ?line [{column,17},{line,19}] = erl_scan:attributes_info(A1),
- ?line {done,{ok,[{atom,A2,foo},{dot,_}],{19,22}},[]} =
+ {19,17} = erl_scan:location(T1),
+ {done,{ok,[{atom,_,foo}=T2,{dot,_}],{19,22}},[]} =
erl_scan:tokens([], "foo. ", {19,17}, [bad_opt]), % type error
- ?line [{column,17},{line,19}] = erl_scan:attributes_info(A2),
- ?line {ok,[{atom,A3,foo}],{19,20}} =
+ {19,17} = erl_scan:location(T2),
+ {ok,[{atom,_,foo}=T3],{19,20}} =
erl_scan:string("foo", {19,17},[text]),
- ?line [{column,17},{length,3},{line,19},{text,"foo"}] =
- erl_scan:attributes_info(A3),
+ {19,17} = erl_scan:location(T3),
+ "foo" = erl_scan:text(T3),
- ?line {ok,[{atom,A4,foo}],1} = erl_scan:string("foo", 1, [text]),
- ?line [{length,3},{line,1},{text,"foo"}] = erl_scan:attributes_info(A4),
+ {ok,[{atom,_,foo}=T4],1} = erl_scan:string("foo", 1, [text]),
+ 1 = erl_scan:line(T4),
+ 1 = erl_scan:location(T4),
+ "foo" = erl_scan:text(T4),
ok.
token_info() ->
- ?line {ok,[T1],_} = erl_scan:string("foo", {1,18}, [text]),
+ {ok,[T1],_} = erl_scan:string("foo", {1,18}, [text]),
{'EXIT',{badarg,_}} =
- (catch {foo, erl_scan:token_info(T1, foo)}), % type error
- ?line {line,1} = erl_scan:token_info(T1, line),
- ?line {column,18} = erl_scan:token_info(T1, column),
- ?line {length,3} = erl_scan:token_info(T1, length),
- ?line {text,"foo"} = erl_scan:token_info(T1, text),
- ?line [{category,atom},{column,18},{length,3},{line,1},
- {symbol,foo},{text,"foo"}] =
- erl_scan:token_info(T1),
- ?line [{length,3},{column,18}] =
- erl_scan:token_info(T1, [length, column]),
- ?line [{location,{1,18}}] =
- erl_scan:token_info(T1, [location]),
- ?line {category,atom} = erl_scan:token_info(T1, category),
- ?line [{symbol,foo}] = erl_scan:token_info(T1, [symbol]),
-
- ?line {ok,[T2],_} = erl_scan:string("foo", 1, []),
- ?line {line,1} = erl_scan:token_info(T2, line),
- ?line undefined = erl_scan:token_info(T2, column),
- ?line undefined = erl_scan:token_info(T2, length),
- ?line undefined = erl_scan:token_info(T2, text),
- ?line {location,1} = erl_scan:token_info(T2, location),
- ?line [{category,atom},{line,1},{symbol,foo}] = erl_scan:token_info(T2),
- ?line [{line,1}] = erl_scan:token_info(T2, [length, line]),
-
- ?line {ok,[T3],_} = erl_scan:string("=", 1, []),
- ?line [{line,1}] = erl_scan:token_info(T3, [column, line]),
- ?line {category,'='} = erl_scan:token_info(T3, category),
- ?line [{symbol,'='}] = erl_scan:token_info(T3, [symbol]),
+ (catch {foo, erl_scan:category(foo)}), % type error
+ {'EXIT',{badarg,_}} =
+ (catch {foo, erl_scan:symbol(foo)}), % type error
+ atom = erl_scan:category(T1),
+ foo = erl_scan:symbol(T1),
+
+ {ok,[T2],_} = erl_scan:string("foo", 1, []),
+ 1 = erl_scan:line(T2),
+ undefined = erl_scan:column(T2),
+ undefined = erl_scan:text(T2),
+ 1 = erl_scan:location(T2),
+
+ {ok,[T3],_} = erl_scan:string("=", 1, []),
+ '=' = erl_scan:category(T3),
+ '=' = erl_scan:symbol(T3),
ok.
-attributes_info() ->
- ?line {'EXIT',_} =
- (catch {foo,erl_scan:attributes_info(foo)}), % type error
- [{line,18}] = erl_scan:attributes_info(erl_anno:new(18)),
- {location,19} =
- erl_scan:attributes_info(erl_anno:new(19), location),
- ?line {ok,[{atom,A0,foo}],_} = erl_scan:string("foo", 19, [text]),
- ?line {location,19} = erl_scan:attributes_info(A0, location),
-
- ?line {ok,[{atom,A3,foo}],_} = erl_scan:string("foo", {1,3}, [text]),
- ?line {line,1} = erl_scan:attributes_info(A3, line),
- ?line {column,3} = erl_scan:attributes_info(A3, column),
- ?line {location,{1,3}} = erl_scan:attributes_info(A3, location),
- ?line {text,"foo"} = erl_scan:attributes_info(A3, text),
-
- ?line {ok,[{atom,A4,foo}],_} = erl_scan:string("foo", 2, [text]),
- ?line {line,2} = erl_scan:attributes_info(A4, line),
- ?line undefined = erl_scan:attributes_info(A4, column),
- ?line {location,2} = erl_scan:attributes_info(A4, location),
- ?line {text,"foo"} = erl_scan:attributes_info(A4, text),
-
- ?line {ok,[{atom,A5,foo}],_} = erl_scan:string("foo", {1,3}, []),
- ?line {line,1} = erl_scan:attributes_info(A5, line),
- ?line {column,3} = erl_scan:attributes_info(A5, column),
- ?line {location,{1,3}} = erl_scan:attributes_info(A5, location),
- ?line undefined = erl_scan:attributes_info(A5, text),
-
- ?line undefined = erl_scan:attributes_info([], line), % type error
+anno_info() ->
+ {'EXIT',_} =
+ (catch {foo,erl_scan:line(foo)}), % type error
+ {ok,[{atom,_,foo}=T0],_} = erl_scan:string("foo", 19, [text]),
+ 19 = erl_scan:location(T0),
+ 19 = erl_scan:end_location(T0),
+
+ {ok,[{atom,_,foo}=T3],_} = erl_scan:string("foo", {1,3}, [text]),
+ 1 = erl_scan:line(T3),
+ 3 = erl_scan:column(T3),
+ {1,3} = erl_scan:location(T3),
+ {1,6} = erl_scan:end_location(T3),
+ "foo" = erl_scan:text(T3),
+
+ {ok,[{atom,_,foo}=T4],_} = erl_scan:string("foo", 2, [text]),
+ 2 = erl_scan:line(T4),
+ undefined = erl_scan:column(T4),
+ 2 = erl_scan:location(T4),
+ "foo" = erl_scan:text(T4),
+
+ {ok,[{atom,_,foo}=T5],_} = erl_scan:string("foo", {1,3}, []),
+ 1 = erl_scan:line(T5),
+ 3 = erl_scan:column(T5),
+ {1,3} = erl_scan:location(T5),
+ undefined = erl_scan:text(T5),
ok.
-set_attribute() ->
- F = fun(Line) -> -Line end,
- Anno2 = erl_anno:new(2),
- A0 = erl_scan:set_attribute(line, Anno2, F),
- {line, -2} = erl_scan:attributes_info(A0, line),
- ?line {ok,[{atom,A1,foo}],_} = erl_scan:string("foo", {9,17}),
- ?line A2 = erl_scan:set_attribute(line, A1, F),
- ?line {line,-9} = erl_scan:attributes_info(A2, line),
- ?line {location,{-9,17}} = erl_scan:attributes_info(A2, location),
- ?line [{line,-9},{column,17}] =
- erl_scan:attributes_info(A2, [line,column,text]),
-
- F2 = fun(Line) -> {17,Line} end,
- ?line Attr1 = erl_scan:set_attribute(line, 2, F2),
- ?line {line,{17,2}} = erl_scan:attributes_info(Attr1, line),
- ?line undefined = erl_scan:attributes_info(Attr1, column),
- ?line {location,{17,2}} = % a bit mixed up
- erl_scan:attributes_info(Attr1, location),
-
- ?line A3 = erl_scan:set_attribute(line, A1, F2),
- ?line {line,{17,9}} = erl_scan:attributes_info(A3, line),
- ?line {location,{{17,9},17}} = erl_scan:attributes_info(A3, location),
- ?line [{line,{17,9}},{column,17}] =
- erl_scan:attributes_info(A3, [line,column,text]),
-
- ?line {ok,[{atom,A4,foo}],_} = erl_scan:string("foo", {9,17}, [text]),
- ?line A5 = erl_scan:set_attribute(line, A4, F),
- ?line {line,-9} = erl_scan:attributes_info(A5, line),
- ?line {location,{-9,17}} = erl_scan:attributes_info(A5, location),
- ?line [{line,-9},{column,17},{text,"foo"}] =
- erl_scan:attributes_info(A5, [line,column,text]),
-
- ?line {ok,[{atom,A6,foo}],_} = erl_scan:string("foo", 11, [text]),
- ?line A7 = erl_scan:set_attribute(line, A6, F2),
- %% Incompatible with pre 18:
- %% {line,{17,11}} = erl_scan:attributes_info(A7, line),
- {line,17} = erl_scan:attributes_info(A7, line),
- ?line {location,{17,11}} = % mixed up
- erl_scan:attributes_info(A7, location),
- %% Incompatible with pre 18:
- %% [{line,{17,11}},{text,"foo"}] =
- %% erl_scan:attributes_info(A7, [line,column,text]),
- [{line,17},{column,11},{text,"foo"}] =
- erl_scan:attributes_info(A7, [line,column,text]),
-
- ?line {'EXIT',_} =
- (catch {foo, erl_scan:set_attribute(line, [], F2)}), % type error
- ?line {'EXIT',{badarg,_}} =
- (catch {foo, erl_scan:set_attribute(column, [], F2)}), % type error
-
- Attr10 = erl_anno:new(8),
- Attr20 = erl_scan:set_attribute(line, Attr10,
- fun(L) -> {nos,'X',L} end),
- %% OTP-9412
- Attr30 = erl_scan:set_attribute(line, Attr20,
- fun({nos,_V,VL}) -> VL end),
- 8 = erl_anno:to_term(Attr30),
- ok.
-
column_errors() ->
?line {error,{{1,1},erl_scan,{string,$',""}},{1,3}} = % $'
erl_scan:string("'\\",{1,1}),
@@ -892,14 +813,13 @@ unicode() ->
erl_scan_string(Qs, 1),
{ok,[Q2],{1,9}} =
erl_scan:string("$\\x{aaa}", {1,1}, [text]),
- [{category,char},{column,1},{length,8},
- {line,1},{symbol,16#aaa},{text,Qs}] =
- erl_scan:token_info(Q2),
+ [{category,char},{column,1},{line,1},{symbol,16#aaa},{text,Qs}] =
+ token_info_long(Q2),
U1 = "\"\\x{aaa}\"",
- {ok,[{string,A1,[2730]}],{1,10}} = erl_scan:string(U1, {1,1}, [text]),
- [{line,1},{column,1},{text,"\"\\x{aaa}\""}] =
- erl_scan:attributes_info(A1, [line, column, text]),
+ {ok,[{string,_,[2730]}=T1],{1,10}} = erl_scan:string(U1, {1,1}, [text]),
+ {1,1} = erl_scan:location(T1),
+ "\"\\x{aaa}\"" = erl_scan:text(T1),
{ok,[{string,1,[2730]}],1} = erl_scan_string(U1, 1),
U2 = "\"\\x41\\x{fff}\\x42\"",
@@ -1012,16 +932,13 @@ otp_10302(Config) when is_list(Config) ->
Qs = "$\\x{aaa}",
{ok,[{char,1,2730}],1} = erl_scan_string(Qs, 1),
{ok,[Q2],{1,9}} = erl_scan:string(Qs,{1,1},[text]),
- [{category,char},{column,1},{length,8},
- {line,1},{symbol,16#aaa},{text,Qs}] =
- erl_scan:token_info(Q2),
-
- Tags = [category, column, length, line, symbol, text],
+ [{category,char},{column,1},{line,1},{symbol,16#aaa},{text,Qs}] =
+ token_info_long(Q2),
U1 = "\"\\x{aaa}\"",
{ok,[T1],{1,10}} = erl_scan:string(U1, {1,1}, [text]),
- [{category,string},{column,1},{length,9},{line,1},
- {symbol,[16#aaa]},{text,U1}] = erl_scan:token_info(T1, Tags),
+ [{category,string},{column,1},{line,1},{symbol,[16#aaa]},{text,U1}] =
+ token_info_long(T1),
U2 = "\"\\x41\\x{fff}\\x42\"",
{ok,[{string,1,[65,4095,66]}],1} = erl_scan_string(U2, 1),
@@ -1353,9 +1270,7 @@ test_wsc([], []) ->
ok;
test_wsc([Token|Tokens], [Token2|Tokens2]) ->
[Text, Text2] = [Text ||
- {text, Text} <-
- [erl_scan:token_info(T, text) ||
- T <- [Token, Token2]]],
+ Text <- [erl_scan:text(T) || T <- [Token, Token2]]],
Sz = erts_debug:size(Text),
Sz2 = erts_debug:size({Text, Text2}),
IsCompacted = Sz2 < 2*Sz+erts_debug:size({a,a}),
@@ -1394,7 +1309,7 @@ all_same(L, Char) ->
newlines_first([]) ->
ok;
newlines_first([Token|Tokens]) ->
- {text,Text} = erl_scan:token_info(Token, text),
+ Text = erl_scan:text(Token),
Nnls = length([C || C <- Text, C =:= $\n]),
OK = case Text of
[$\n|_] ->
@@ -1414,7 +1329,7 @@ select_tokens(Tokens, Tags) ->
lists:filter(fun(T) -> lists:member(element(1, T), Tags) end, Tokens).
simplify([Token|Tokens]) ->
- {line,Line} = erl_scan:token_info(Token, line),
+ Line = erl_scan:line(Token),
[setelement(2, Token, erl_anno:new(Line)) | simplify(Tokens)];
simplify([]) ->
[].
@@ -1423,17 +1338,31 @@ get_text(Tokens) ->
lists:flatten(
[T ||
Token <- Tokens,
- ({text,T} = erl_scan:token_info(Token, text)) =/= []]).
+ (T = erl_scan:text(Token)) =/= []]).
test_decorated_tokens(String, Tokens) ->
ToksAttrs = token_attrs(Tokens),
test_strings(ToksAttrs, String, 1, 1).
token_attrs(Tokens) ->
- [{L,C,Len,T} ||
+ [{L,C,length(T),T} ||
Token <- Tokens,
- ([{line,L},{column,C},{length,Len},{text,T}] =
- erl_scan:token_info(Token, [line,column,length,text])) =/= []].
+ ([C,L,T] = token_info(Token)) =/= []].
+
+token_info(T) ->
+ Column = erl_scan:column(T),
+ Line = erl_scan:line(T),
+ Text = erl_scan:text(T),
+ [Column, Line, Text].
+
+token_info_long(T) ->
+ Column = erl_scan:column(T),
+ Line = erl_scan:line(T),
+ Text = erl_scan:text(T),
+ Category = erl_scan:category(T),
+ Symbol = erl_scan:symbol(T),
+ [{category,Category},{column,Column},{line,Line},
+ {symbol,Symbol},{text,Text}].
test_strings([], _S, Line, Column) ->
{Line,Column};
@@ -1514,8 +1443,7 @@ consistent_attributes([Ts | TsL]) ->
L = [T || T <- Ts, is_integer(element(2, T))],
case L of
[] ->
- TagsL = [[Tag || {Tag,_} <-
- erl_scan:attributes_info(element(2, T))] ||
+ TagsL = [[Tag || {Tag,_} <- defined(token_info_long(T))] ||
T <- Ts],
case lists:usort(TagsL) of
[_] ->
@@ -1531,6 +1459,9 @@ consistent_attributes([Ts | TsL]) ->
Ts
end.
+defined(L) ->
+ [{T,V} || {T,V} <- L, V =/= undefined].
+
family_list(L) ->
sofs:to_external(family(L)).
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index ae431d66d9..39d9ddaaa7 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -112,9 +112,8 @@
-define(m(A,B), ?line assert_eq(A,B)).
init_per_testcase(Case, Config) ->
- Seed = {S1,S2,S3} = random:seed0(), %now(),
- random:seed(S1,S2,S3),
- io:format("*** SEED: ~p ***\n", [Seed]),
+ rand:seed(exsplus),
+ io:format("*** SEED: ~p ***\n", [rand:export_seed()]),
start_spawn_logger(),
wait_for_test_procs(), %% Ensure previous case cleaned up
Dog=test_server:timetrap(test_server:minutes(20)),
@@ -731,10 +730,6 @@ chk_normal_tab_struct_size() ->
% ?line ok
% end.
--define(DB_TREE_STACK_NEED,50). % The static stack for a tree, in halfword pointers are two internal words
- % so the stack gets twice as big
--define(DB_HASH_SIZEOF_EXTSEG,260). % The segment size in words, in halfword this will be twice as large.
-
adjust_xmem([T1,T2,T3,T4], {A0,B0,C0,D0} = _Mem0) ->
%% Adjust for 64-bit, smp, and os:
%% Table struct size may differ.
@@ -748,19 +743,7 @@ adjust_xmem([T1,T2,T3,T4], {A0,B0,C0,D0} = _Mem0) ->
% end,
TabDiff = ?TAB_STRUCT_SZ,
- Mem1 = {A0+TabDiff, B0+TabDiff, C0+TabDiff, D0+TabDiff},
-
- case {erlang:system_info({wordsize,internal}),erlang:system_info({wordsize,external})} of
- %% Halfword, corrections for regular pointers occupying two internal words.
- {4,8} ->
- {A1,B1,C1,D1} = Mem1,
- {A1+4*ets:info(T1, size)+?DB_TREE_STACK_NEED,
- B1+3*ets:info(T2, size)+?DB_HASH_SIZEOF_EXTSEG,
- C1+3*ets:info(T3, size)+?DB_HASH_SIZEOF_EXTSEG,
- D1+3*ets:info(T4, size)+?DB_HASH_SIZEOF_EXTSEG};
- _ ->
- Mem1
- end.
+ {A0+TabDiff, B0+TabDiff, C0+TabDiff, D0+TabDiff}.
t_whitebox(doc) ->
["Diverse whitebox testes"];
@@ -1346,7 +1329,7 @@ drop_match() ->
ets_match(Tab,Expr) ->
- case random:uniform(2) of
+ case rand:uniform(2) of
1 ->
ets:match(Tab,Expr);
_ ->
@@ -1355,14 +1338,14 @@ ets_match(Tab,Expr) ->
match_chunked(Tab,Expr) ->
match_chunked_collect(ets:match(Tab,Expr,
- random:uniform(1999) + 1)).
+ rand:uniform(1999) + 1)).
match_chunked_collect('$end_of_table') ->
[];
match_chunked_collect({Results, Continuation}) ->
Results ++ match_chunked_collect(ets:match(Continuation)).
ets_match_object(Tab,Expr) ->
- case random:uniform(2) of
+ case rand:uniform(2) of
1 ->
ets:match_object(Tab,Expr);
_ ->
@@ -1371,7 +1354,7 @@ ets_match_object(Tab,Expr) ->
match_object_chunked(Tab,Expr) ->
match_object_chunked_collect(ets:match_object(Tab,Expr,
- random:uniform(1999) + 1)).
+ rand:uniform(1999) + 1)).
match_object_chunked_collect('$end_of_table') ->
[];
match_object_chunked_collect({Results, Continuation}) ->
@@ -1383,19 +1366,15 @@ random_test() ->
?line ReadDir = get(where_to_read),
?line WriteDir = get(where_to_write),
?line (catch file:make_dir(WriteDir)),
- ?line Seed = case file:consult(filename:join([ReadDir,
- "preset_random_seed.txt"])) of
- {ok,[X]} ->
- X;
- _ ->
- {A,B,C} = erlang:timestamp(),
- random:seed(A,B,C),
- get(random_seed)
- end,
- put(random_seed,Seed),
- ?line {ok, F} = file:open(filename:join([WriteDir,
- "last_random_seed.txt"]),
- [write]),
+ case file:consult(filename:join([ReadDir,"preset_random_seed.txt"])) of
+ {ok,[X]} ->
+ rand:seed(X);
+ _ ->
+ rand:seed(exsplus)
+ end,
+ Seed = rand:export_seed(),
+ {ok,F} = file:open(filename:join([WriteDir,"last_random_seed.txt"]),
+ [write]),
io:format(F,"~p. ~n",[Seed]),
file:close(F),
io:format("Random seed ~p written to ~s, copy to ~s to rerun with "
@@ -1417,7 +1396,7 @@ do_random_test() ->
end, 5000),
?line io:format("~nData inserted~n"),
?line do_n_times(fun() ->
- ?line I = random:uniform(25),
+ I = rand:uniform(25),
?line Key = create_random_string(I) ++ '_',
?line L1 = ets_match_object(OrdSet,{Key,'_'}),
?line L2 = lists:sort(ets_match_object(Set,{Key,'_'})),
@@ -1977,7 +1956,7 @@ evil_update_counter(Config) when is_list(Config) ->
gb_sets:module_info(),
math:module_info(),
ordsets:module_info(),
- random:module_info(),
+ rand:module_info(),
repeat_for_opts(evil_update_counter_do).
@@ -2011,7 +1990,7 @@ evil_counter(I,Opts) ->
1 -> 16#12345678FFFFFFFF;
2 -> 16#7777777777FFFFFFFF863648726743
end,
- Start = Start0 + random:uniform(100000),
+ Start = Start0 + rand:uniform(100000),
ets:insert(T, {dracula,Start}),
Iter = 40000,
End = Start + Iter,
@@ -3989,15 +3968,37 @@ safe_fixtable_do(Opts) ->
?line true = ets:safe_fixtable(Tab, true),
?line receive after 1 -> ok end,
?line true = ets:safe_fixtable(Tab, false),
- ?line false = ets:info(Tab,safe_fixed),
- ?line true = ets:safe_fixtable(Tab, true),
+ false = ets:info(Tab,safe_fixed_monotonic_time),
+ false = ets:info(Tab,safe_fixed),
+ SysBefore = erlang:timestamp(),
+ MonBefore = erlang:monotonic_time(),
+ true = ets:safe_fixtable(Tab, true),
+ MonAfter = erlang:monotonic_time(),
+ SysAfter = erlang:timestamp(),
Self = self(),
- ?line {{_,_,_},[{Self,1}]} = ets:info(Tab,safe_fixed),
+ {FixMonTime,[{Self,1}]} = ets:info(Tab,safe_fixed_monotonic_time),
+ {FixSysTime,[{Self,1}]} = ets:info(Tab,safe_fixed),
+ true = is_integer(FixMonTime),
+ true = MonBefore =< FixMonTime,
+ true = FixMonTime =< MonAfter,
+ {FstMs,FstS,FstUs} = FixSysTime,
+ true = is_integer(FstMs),
+ true = is_integer(FstS),
+ true = is_integer(FstUs),
+ case erlang:system_info(time_warp_mode) of
+ no_time_warp ->
+ true = timer:now_diff(FixSysTime, SysBefore) >= 0,
+ true = timer:now_diff(SysAfter, FixSysTime) >= 0;
+ _ ->
+ %% ets:info(Tab,safe_fixed) not timewarp safe...
+ ignore
+ end,
%% Test that an unjustified 'unfix' is a no-op.
{Pid,MRef} = my_spawn_monitor(fun() -> true = ets:safe_fixtable(Tab,false) end),
{'DOWN', MRef, process, Pid, normal} = receive M -> M end,
- ?line true = ets:info(Tab,fixed),
- ?line {{_,_,_},[{Self,1}]} = ets:info(Tab,safe_fixed),
+ true = ets:info(Tab,fixed),
+ {FixMonTime,[{Self,1}]} = ets:info(Tab,safe_fixed_monotonic_time),
+ {FixSysTime,[{Self,1}]} = ets:info(Tab,safe_fixed),
%% badarg's
?line {'EXIT', {badarg, _}} = (catch ets:safe_fixtable(Tab, foobar)),
?line true = ets:info(Tab,fixed),
@@ -4043,6 +4044,7 @@ info_do(Opts) ->
?line undefined = ets:info(non_existing_table_xxyy,type),
?line undefined = ets:info(non_existing_table_xxyy,node),
?line undefined = ets:info(non_existing_table_xxyy,named_table),
+ ?line undefined = ets:info(non_existing_table_xxyy,safe_fixed_monotonic_time),
?line undefined = ets:info(non_existing_table_xxyy,safe_fixed),
?line verify_etsmem(EtsMem).
@@ -4661,11 +4663,11 @@ create_random_string(0) ->
[];
create_random_string(OfLength) ->
- C = case random:uniform(2) of
+ C = case rand:uniform(2) of
1 ->
- (random:uniform($Z - $A + 1) - 1) + $A;
+ (rand:uniform($Z - $A + 1) - 1) + $A;
_ ->
- (random:uniform($z - $a + 1) - 1) + $a
+ (rand:uniform($z - $a + 1) - 1) + $a
end,
[C | create_random_string(OfLength - 1)].
@@ -4676,7 +4678,7 @@ create_random_tuple(OfLength) ->
end,create_random_string(OfLength))).
create_partly_bound_tuple(OfLength) ->
- case random:uniform(2) of
+ case rand:uniform(2) of
1 ->
create_partly_bound_tuple1(OfLength);
_ ->
@@ -4685,14 +4687,14 @@ create_partly_bound_tuple(OfLength) ->
create_partly_bound_tuple1(OfLength) ->
T0 = create_random_tuple(OfLength),
- I = random:uniform(OfLength),
+ I = rand:uniform(OfLength),
setelement(I,T0,'$1').
set_n_random_elements(T0,0,_,_) ->
T0;
set_n_random_elements(T0,N,OfLength,GenFun) ->
- I = random:uniform(OfLength),
+ I = rand:uniform(OfLength),
What = GenFun(I),
case element(I,T0) of
What ->
@@ -4706,12 +4708,12 @@ make_dollar_atom(I) ->
list_to_atom([$$] ++ integer_to_list(I)).
create_partly_bound_tuple2(OfLength) ->
T0 = create_random_tuple(OfLength),
- I = random:uniform(OfLength - 1),
+ I = rand:uniform(OfLength - 1),
set_n_random_elements(T0,I,OfLength,fun make_dollar_atom/1).
create_partly_bound_tuple3(OfLength) ->
T0 = create_random_tuple(OfLength),
- I = random:uniform(OfLength - 1),
+ I = rand:uniform(OfLength - 1),
set_n_random_elements(T0,I,OfLength,fun(_) -> '_' end).
do_n_times(_,0) ->
@@ -5074,11 +5076,12 @@ meta_wb_do(Opts) ->
io:format("Colliding names = ~p\n",[Names]),
F = fun(0,_,_) -> ok;
- (N,Tabs,Me) -> Name1 = lists:nth(random:uniform(Len),Names),
- Name2 = lists:nth(random:uniform(Len),Names),
- Op = element(random:uniform(3),OpFuns),
- NTabs = Op(Name1, Name2, Tabs, Opts),
- Me(N-1,NTabs,Me)
+ (N,Tabs,Me) ->
+ Name1 = lists:nth(rand:uniform(Len), Names),
+ Name2 = lists:nth(rand:uniform(Len), Names),
+ Op = element(rand:uniform(3),OpFuns),
+ NTabs = Op(Name1, Name2, Tabs, Opts),
+ Me(N-1, NTabs, Me)
end,
F(Len*100, [], F),
@@ -5344,7 +5347,7 @@ smp_insert(suite) -> [];
smp_insert(Config) when is_list(Config) ->
ets_new(smp_insert,[named_table,public,{write_concurrency,true}]),
InitF = fun(_) -> ok end,
- ExecF = fun(_) -> true = ets:insert(smp_insert,{random:uniform(10000)})
+ ExecF = fun(_) -> true = ets:insert(smp_insert,{rand:uniform(10000)})
end,
FiniF = fun(_) -> ok end,
run_workers(InitF,ExecF,FiniF,100000),
@@ -5532,7 +5535,7 @@ otp_8166_zombie_creator(T,Deleted) ->
[{'=<','$1', Deleted}],
[true]}]),
Pid ! zombies_created,
- repeat_while(fun() -> case ets:info(T,safe_fixed) of
+ repeat_while(fun() -> case ets:info(T,safe_fixed_monotonic_time) of
{_,[_P1,_P2]} ->
false;
_ ->
@@ -5595,10 +5598,10 @@ smp_select_delete(Config) when is_list(Config) ->
Zeros = erlang:make_tuple(Mod,0),
InitF = fun(_) -> Zeros end,
ExecF = fun(Diffs0) ->
- case random:uniform(20) of
+ case rand:uniform(20) of
1 ->
Mod = 17,
- Eq = random:uniform(Mod) - 1,
+ Eq = rand:uniform(Mod) - 1,
Deleted = ets:select_delete(T,
[{{'_', '$1'},
[{'=:=', {'rem', '$1', Mod}, Eq}],
@@ -5607,7 +5610,7 @@ smp_select_delete(Config) when is_list(Config) ->
element(Eq+1,Diffs0) - Deleted),
Diffs1;
_ ->
- Key = random:uniform(10000),
+ Key = rand:uniform(10000),
Eq = Key rem Mod,
?line case ets:insert_new(T,{Key,Key}) of
true ->
@@ -5811,7 +5814,7 @@ run_workers_do(InitF,ExecF,FiniF,Laps, Exclude) ->
N when (N > Exclude) -> N - Exclude
end,
io:format("smp starting ~p workers\n",[NumOfProcs]),
- Seeds = [{ProcN,random:uniform(9999)} || ProcN <- lists:seq(1,NumOfProcs)],
+ Seeds = [{ProcN,rand:uniform(9999)} || ProcN <- lists:seq(1,NumOfProcs)],
Parent = self(),
Pids = [my_spawn_link(fun()-> worker(Seed,InitF,ExecF,FiniF,Laps,Parent,NumOfProcs) end)
|| Seed <- Seeds],
@@ -5822,7 +5825,7 @@ run_workers_do(InitF,ExecF,FiniF,Laps, Exclude) ->
worker({ProcN,Seed}, InitF, ExecF, FiniF, Laps, Parent, NumOfProcs) ->
io:format("smp worker ~p, seed=~p~n",[self(),Seed]),
- random:seed(Seed,Seed,Seed),
+ rand:seed(exsplus, {Seed,Seed,Seed}),
State1 = InitF([ProcN, NumOfProcs]),
State2 = worker_loop(Laps, ExecF, State1),
Result = FiniF(State2),
diff --git a/lib/stdlib/test/ets_tough_SUITE.erl b/lib/stdlib/test/ets_tough_SUITE.erl
index c6f24fc670..8a7f2b1ec2 100644
--- a/lib/stdlib/test/ets_tough_SUITE.erl
+++ b/lib/stdlib/test/ets_tough_SUITE.erl
@@ -92,7 +92,7 @@ ex1_sub(Config) ->
ok.
prep(Config) ->
- random:seed(),
+ rand:seed(exsplus),
put(dump_ticket,none),
DumpDir = filename:join(?config(priv_dir,Config), "ets_tough"),
file:make_dir(DumpDir),
@@ -221,19 +221,19 @@ random_class() ->
random_element(Classes).
random_key() ->
- random:uniform(8).
+ rand:uniform(8).
random_value() ->
- case random:uniform(5) of
+ case rand:uniform(5) of
1 -> ok;
2 -> {data,random_key()};
3 -> {foo,bar,random_class()};
- 4 -> random:uniform(1000);
+ 4 -> rand:uniform(1000);
5 -> {recursive,random_value()}
end.
random_element(T) ->
- I = random:uniform(tuple_size(T)),
+ I = rand:uniform(tuple_size(T)),
element(I,T).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index 01b798faef..c39ff842ee 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -318,7 +318,7 @@ same_lists(Expected0, Actual0, BaseDir) ->
mkfiles([H|T], Dir) ->
Name = filename:join(Dir, H),
- Garbage = [31+random:uniform(95) || _ <- lists:seq(1, random:uniform(1024))],
+ Garbage = [31+rand:uniform(95) || _ <- lists:seq(1, rand:uniform(1024))],
file:write_file(Name, Garbage),
[Name|mkfiles(T, Dir)];
mkfiles([], _) -> [].
diff --git a/lib/stdlib/test/filename_SUITE.erl b/lib/stdlib/test/filename_SUITE.erl
index fd47da8150..4372e77df9 100644
--- a/lib/stdlib/test/filename_SUITE.erl
+++ b/lib/stdlib/test/filename_SUITE.erl
@@ -97,20 +97,11 @@ absname(Config) when is_list(Config) ->
?line file:set_cwd(Cwd),
ok;
- Type ->
- case Type of
- {unix, _} ->
- ?line ok = file:set_cwd("/usr"),
- ?line "/usr/foo" = filename:absname(foo),
- ?line "/usr/foo" = filename:absname("foo"),
- ?line "/usr/../ebin" = filename:absname("../ebin");
- {ose, _} ->
- ?line ok = file:set_cwd("/romfs"),
- ?line "/romfs/foo" = filename:absname(foo),
- ?line "/romfs/foo" = filename:absname("foo"),
- ?line "/romfs/../ebin" = filename:absname("../ebin")
- end,
-
+ {unix, _} ->
+ ?line ok = file:set_cwd("/usr"),
+ ?line "/usr/foo" = filename:absname(foo),
+ ?line "/usr/foo" = filename:absname("foo"),
+ ?line "/usr/../ebin" = filename:absname("../ebin"),
?line file:set_cwd("/"),
?line "/foo" = filename:absname(foo),
?line "/foo" = filename:absname("foo"),
@@ -494,18 +485,10 @@ absname_bin(Config) when is_list(Config) ->
?line file:set_cwd(Cwd),
ok;
- Type ->
- case Type of
- {unix,_} ->
- ?line ok = file:set_cwd(<<"/usr">>),
- ?line <<"/usr/foo">> = filename:absname(<<"foo">>),
- ?line <<"/usr/../ebin">> = filename:absname(<<"../ebin">>);
- {ose,_} ->
- ?line ok = file:set_cwd(<<"/romfs">>),
- ?line <<"/romfs/foo">> = filename:absname(<<"foo">>),
- ?line <<"/romfs/../ebin">> = filename:absname(<<"../ebin">>)
- end,
-
+ {unix, _} ->
+ ?line ok = file:set_cwd(<<"/usr">>),
+ ?line <<"/usr/foo">> = filename:absname(<<"foo">>),
+ ?line <<"/usr/../ebin">> = filename:absname(<<"../ebin">>),
?line file:set_cwd(<<"/">>),
?line <<"/foo">> = filename:absname(<<"foo">>),
?line <<"/../ebin">> = filename:absname(<<"../ebin">>),
diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl
index a0f7fd2744..bd68c93779 100644
--- a/lib/stdlib/test/lists_SUITE.erl
+++ b/lib/stdlib/test/lists_SUITE.erl
@@ -1677,8 +1677,7 @@ check_stab(L, U, S, US, SS) ->
%%% Element 3 in the tuple is the position of the tuple in the list.
biglist(N) ->
- {A, B, C} = get_seed(),
- random:seed(A, B, C),
+ rand:seed(exsplus),
biglist(N, []).
biglist(0, L) ->
@@ -1694,8 +1693,7 @@ biglist(N, L) ->
%%% No sequence number.
ubiglist(N) ->
- {A, B, C} = get_seed(),
- random:seed(A, B, C),
+ rand:seed(exsplus),
ubiglist(N, []).
ubiglist(0, L) ->
@@ -1719,8 +1717,7 @@ urandom_tuple(N, I) ->
%%% sequence number.
bigfunlist(N) ->
- {A, B, C} = get_seed(),
- random:seed(A, B, C),
+ rand:seed(exsplus),
bigfunlist_1(N).
bigfunlist_1(N) when N < 30000 -> % Now (R8) max 32000 different pids.
@@ -1754,21 +1751,13 @@ make_fun(Pid) ->
fun_pid(Fun) ->
erlang:fun_info(Fun, pid).
-get_seed() ->
- case random:seed() of
- undefined ->
- erlang:timestamp();
- Tuple ->
- Tuple
- end.
-
random_tuple(N, Seq) ->
R1 = randint(N),
R2 = randint(N),
{R1, R2, Seq}.
randint(N) ->
- trunc(random:uniform() * N).
+ trunc(rand:uniform() * N).
%% The first "duplicate" is kept.
no_dups([]) ->
@@ -1830,8 +1819,7 @@ sort_loop_1(Pid) ->
end.
sloop(N) ->
- {A, B, C} = get_seed(),
- random:seed(A, B, C),
+ rand:seed(exsplus),
sloop(N, #state{}).
sloop(N, S) ->
diff --git a/lib/stdlib/test/queue_SUITE.erl b/lib/stdlib/test/queue_SUITE.erl
index c965a8b218..5165ac3a3a 100644
--- a/lib/stdlib/test/queue_SUITE.erl
+++ b/lib/stdlib/test/queue_SUITE.erl
@@ -470,7 +470,7 @@ oops(suite) ->
oops(Config) when is_list(Config) ->
?line N = 3142,
?line Optab = optab(),
- ?line Seed0 = random:seed0(),
+ ?line Seed0 = rand:seed(exsplus, {1,2,4}),
?line {Is,Seed} = random_list(N, tuple_size(Optab), Seed0, []),
?line io:format("~p ", [Is]),
?line QA = queue:new(),
@@ -562,20 +562,20 @@ args([], _, Seed, R) ->
args([q|Ts], [Q|Qs]=Qss, Seed, R) ->
args(Ts, if Qs =:= [] -> Qss; true -> Qs end, Seed, [Q|R]);
args([l|Ts], Qs, Seed0, R) ->
- {N,Seed1} = random:uniform_s(17, Seed0),
+ {N,Seed1} = rand:uniform_s(17, Seed0),
{L,Seed} = random_list(N, 4711, Seed1, []),
args(Ts, Qs, Seed, [L|R]);
args([t|Ts], Qs, Seed0, R) ->
- {T,Seed} = random:uniform_s(4711, Seed0),
+ {T,Seed} = rand:uniform_s(4711, Seed0),
args(Ts, Qs, Seed, [T|R]);
args([n|Ts], Qs, Seed0, R) ->
- {N,Seed} = random:uniform_s(17, Seed0),
+ {N,Seed} = rand:uniform_s(17, Seed0),
args(Ts, Qs, Seed, [N|R]).
random_list(0, _, Seed, R) ->
{R,Seed};
random_list(N, M, Seed0, R) ->
- {X,Seed} = random:uniform_s(M, Seed0),
+ {X,Seed} = rand:uniform_s(M, Seed0),
random_list(N-1, M, Seed, [X|R]).
call(Func, As) ->
diff --git a/lib/stdlib/test/random_iolist.erl b/lib/stdlib/test/random_iolist.erl
index 9a0f034e72..6da7da04de 100644
--- a/lib/stdlib/test/random_iolist.erl
+++ b/lib/stdlib/test/random_iolist.erl
@@ -36,7 +36,7 @@ run2(Iter,Fun1,Fun2) ->
compare2(Iter,Fun1,Fun2).
random_byte() ->
- random:uniform(256) - 1.
+ rand:uniform(256) - 1.
random_list(0,Acc) ->
Acc;
@@ -45,7 +45,7 @@ random_list(N,Acc) ->
random_binary(N) ->
B = list_to_binary(random_list(N,[])),
- case {random:uniform(2),size(B)} of
+ case {rand:uniform(2),size(B)} of
{2,M} when M > 1 ->
S = M-1,
<<_:3,C:S/binary,_:5>> = B,
@@ -57,7 +57,7 @@ random_list(N) ->
random_list(N,[]).
front() ->
- case random:uniform(10) of
+ case rand:uniform(10) of
10 ->
false;
_ ->
@@ -65,7 +65,7 @@ front() ->
end.
any_type() ->
- case random:uniform(10) of
+ case rand:uniform(10) of
1 ->
list;
2 ->
@@ -77,7 +77,7 @@ any_type() ->
end.
tail_type() ->
- case random:uniform(5) of
+ case rand:uniform(5) of
1 ->
list;
2 ->
@@ -90,9 +90,9 @@ random_length(N) ->
UpperLimit = 255,
case N of
M when M > UpperLimit ->
- random:uniform(UpperLimit+1) - 1;
+ rand:uniform(UpperLimit+1) - 1;
_ ->
- random:uniform(N+1) - 1
+ rand:uniform(N+1) - 1
end.
random_iolist(0,Acc) ->
@@ -139,7 +139,7 @@ random_iolist(N) ->
standard_seed() ->
- random:seed(1201,855653,380975).
+ rand:seed(exsplus, {1201,855653,380975}).
do_comp(List,F1,F2) ->
X = F1(List),
diff --git a/lib/stdlib/test/random_unicode_list.erl b/lib/stdlib/test/random_unicode_list.erl
index ecafe42318..3bc86a8430 100644
--- a/lib/stdlib/test/random_unicode_list.erl
+++ b/lib/stdlib/test/random_unicode_list.erl
@@ -85,7 +85,7 @@ int_to_utf32_little(I) ->
id(I) -> I.
random_char() ->
- case random:uniform(16#10FFFF+1) - 1 of
+ case rand:uniform(16#10FFFF+1) - 1 of
X when X >= 16#D800,
X =< 16#DFFF ->
random_char();
@@ -116,13 +116,13 @@ random_binary(N,Enc) ->
int_to(Enc,X)
end,
L)),
- case {random:uniform(3),size(B)} of
+ case {rand:uniform(3),size(B)} of
{2,M} when M > 1 ->
B2 = id(<<1:3,B/binary,1:5>>),
<<_:3,C:M/binary,_:5>> = B2,
C;
{3,M} when M > 1 ->
- X = random:uniform(M+1)-1,
+ X = rand:uniform(M+1)-1,
<<B1:X/binary,B2/binary>> = B,
[B1,B2];
_ ->
@@ -132,7 +132,7 @@ random_list(N) ->
random_list(N,[]).
front() ->
- case random:uniform(10) of
+ case rand:uniform(10) of
10 ->
false;
_ ->
@@ -140,7 +140,7 @@ front() ->
end.
any_type() ->
- case random:uniform(10) of
+ case rand:uniform(10) of
1 ->
list;
2 ->
@@ -152,7 +152,7 @@ any_type() ->
end.
tail_type() ->
- case random:uniform(5) of
+ case rand:uniform(5) of
1 ->
list;
2 ->
@@ -165,9 +165,9 @@ random_length(N) ->
UpperLimit = 255,
case N of
M when M > UpperLimit ->
- random:uniform(UpperLimit+1) - 1;
+ rand:uniform(UpperLimit+1) - 1;
_ ->
- random:uniform(N+1) - 1
+ rand:uniform(N+1) - 1
end.
random_unicode_list(0,Acc,_Enc) ->
@@ -214,7 +214,7 @@ random_unicode_list(N,Enc) ->
standard_seed() ->
- random:seed(1201,855653,380975).
+ rand:seed(exsplus, {1201,855653,380975}).
do_comp(List,F1,F2) ->
X = F1(List),
diff --git a/lib/stdlib/test/run_pcre_tests.erl b/lib/stdlib/test/run_pcre_tests.erl
index 1fdc777470..b7d1df39b8 100644
--- a/lib/stdlib/test/run_pcre_tests.erl
+++ b/lib/stdlib/test/run_pcre_tests.erl
@@ -1083,7 +1083,7 @@ dumponesplit(F,{RE,Line,O,TS}) ->
%% Generate replacement tests from indatafile,
%% you will need perl on the machine
gen_repl_test(OneFile) ->
- random:seed(1219,687731,62804),
+ rand:seed(exsplus, {1219,687731,62804}),
{ok,Bin} = file:read_file(OneFile),
Lines = splitfile(0,Bin,1),
Structured = stru(Lines),
@@ -1237,15 +1237,15 @@ btr(_) ->
ranchar() ->
- case random:uniform(10) of
+ case rand:uniform(10) of
9 -> $&;
10 -> <<"\\1">>;
N when N < 5 ->
- random:uniform($Z-$A)+$A-1;
+ rand:uniform($Z-$A)+$A-1;
M when M < 9 ->
- random:uniform($z-$a)+$a-1
+ rand:uniform($z-$a)+$a-1
end.
ranstring() ->
- iolist_to_binary([ranchar() || _ <- lists:duplicate(random:uniform(20),0) ]).
+ iolist_to_binary([ranchar() || _ <- lists:duplicate(rand:uniform(20),0) ]).
diff --git a/lib/stdlib/test/select_SUITE.erl b/lib/stdlib/test/select_SUITE.erl
index ead64ffc75..6796676179 100644
--- a/lib/stdlib/test/select_SUITE.erl
+++ b/lib/stdlib/test/select_SUITE.erl
@@ -212,11 +212,10 @@ init_random(Config) ->
{ok,[X]} ->
X;
_ ->
- {A,B,C} = erlang:timestamp(),
- random:seed(A,B,C),
- get(random_seed)
+ rand:seed(exsplus),
+ rand:export_seed()
end,
- put(random_seed,Seed),
+ rand:seed(Seed),
{ok, F} = file:open(filename:join([WriteDir, "last_random_seed2.txt"]),
[write]),
io:format(F,"~p. ~n",[Seed]),
@@ -224,11 +223,11 @@ init_random(Config) ->
ok.
create_random_key(N,Type) ->
- gen_key(random:uniform(N),Type).
+ gen_key(rand:uniform(N),Type).
create_pb_key(N,list) ->
- X = random:uniform(N),
- case random:uniform(4) of
+ X = rand:uniform(N),
+ case rand:uniform(4) of
3 -> {[X, X+1, '_'], fun([Z,Z1,P1]) ->
[Z,Z1,P1] =:= [X,X+1,P1] end};
2 -> {[X, '_', '_'], fun([Z,P1,P2]) -> [Z,P1,P2] =:= [X,P1,P2] end};
@@ -237,14 +236,14 @@ create_pb_key(N,list) ->
_ -> {[X, '$1', '$2'], fun([Z,P1,P2]) -> [Z,P1,P2] =:= [X,P1,P2] end}
end;
create_pb_key(N, tuple) ->
- X = random:uniform(N),
- case random:uniform(2) of
+ X = rand:uniform(N),
+ case rand:uniform(2) of
1 -> {{X, X+1, '$1'},fun({Z,Z1,P1}) -> {Z,Z1,P1} =:= {X,X+1,P1} end};
_ -> {{X, '$1', '$2'},fun({Z,P1,P2}) -> {Z,P1,P2} =:= {X,P1,P2} end}
end;
create_pb_key(N, complex) ->
- X = random:uniform(N),
- case random:uniform(2) of
+ X = rand:uniform(N),
+ case rand:uniform(2) of
1 -> {{[X, X+1], '$1'}, fun({[Z,Z1],P1}) ->
{[Z,Z1],P1} =:= {[X,X+1],P1} end};
_ -> {{[X, '$1'], '$2'},fun({[Z,P1],P2}) ->
diff --git a/lib/stdlib/test/sets_SUITE.erl b/lib/stdlib/test/sets_SUITE.erl
index 972a812072..e7fc5595a9 100644
--- a/lib/stdlib/test/sets_SUITE.erl
+++ b/lib/stdlib/test/sets_SUITE.erl
@@ -107,9 +107,9 @@ add_element_del([H|T], M, S, Del, []) ->
add_element_del(T, M, M(add_element, {H,S}), Del, [H]);
add_element_del([H|T], M, S0, Del, Inserted) ->
S1 = M(add_element, {H,S0}),
- case random:uniform(3) of
+ case rand:uniform(3) of
1 ->
- OldEl = lists:nth(random:uniform(length(Inserted)), Inserted),
+ OldEl = lists:nth(rand:uniform(length(Inserted)), Inserted),
S = M(del_element, {OldEl,S1}),
add_element_del(T, M, S, [OldEl|Del], [H|Inserted]);
_ ->
@@ -438,7 +438,7 @@ iterate_1(M) ->
M(empty, []).
iterate_2(M) ->
- random:seed(1, 2, 42),
+ rand:seed(exsplus, {1,2,42}),
iter_set(M, 1000).
iter_set(_M, 0) ->
@@ -447,7 +447,7 @@ iter_set(M, N) ->
L = [I || I <- lists:seq(1, N)],
T = M(from_list, L),
L = lists:reverse(iterate_set(M, T)),
- R = random:uniform(N),
+ R = rand:uniform(N),
S = lists:reverse(iterate_set(M, R, T)),
S = [E || E <- L, E >= R],
iter_set(M, N-1).
@@ -481,7 +481,7 @@ sets_mods() ->
test_all(Tester) ->
Res = [begin
- random:seed(1, 2, 42),
+ rand:seed(exsplus, {1,2,42}),
S = Tester(M),
{M(size, S),lists:sort(M(to_list, S))}
end || M <- sets_mods()],
@@ -492,7 +492,7 @@ test_all([{Low,High}|T], Tester) ->
test_all([Sz|T], Tester) when is_integer(Sz) ->
List = rnd_list(Sz),
Res = [begin
- random:seed(19, 2, Sz),
+ rand:seed(exsplus, {19,2,Sz}),
S = Tester(List, M),
{M(size, S),lists:sort(M(to_list, S))}
end || M <- sets_mods()],
@@ -512,10 +512,10 @@ rnd_list(Sz) ->
rnd_list_1(Sz, []).
atomic_rnd_term() ->
- case random:uniform(3) of
- 1 -> list_to_atom(integer_to_list($\s+random:uniform(94))++"rnd");
- 2 -> random:uniform();
- 3 -> random:uniform(50)-37
+ case rand:uniform(3) of
+ 1 -> list_to_atom(integer_to_list($\s+rand:uniform(94))++"rnd");
+ 2 -> rand:uniform();
+ 3 -> rand:uniform(50)-37
end.
rnd_list_1(0, Acc) -> Acc;
@@ -543,7 +543,7 @@ remove_some(List0, P) ->
end.
remove_some([H|T], P, Acc) ->
- case random:uniform() of
+ case rand:uniform() of
F when F < P -> %Remove.
remove_some(T, P, Acc);
_ ->
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index 8cb2a5194a..903ca76575 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -67,6 +67,7 @@
%% Misc tests
-export([child_unlink/1, tree/1, count_children/1,
+ count_restarting_children/1,
do_not_save_start_parameters_for_temporary_children/1,
do_not_save_child_specs_for_temporary_children/1,
simple_one_for_one_scale_many_temporary_children/1,
@@ -90,7 +91,8 @@ all() ->
{group, normal_termination},
{group, shutdown_termination},
{group, abnormal_termination}, child_unlink, tree,
- count_children, do_not_save_start_parameters_for_temporary_children,
+ count_children, count_restarting_children,
+ do_not_save_start_parameters_for_temporary_children,
do_not_save_child_specs_for_temporary_children,
simple_one_for_one_scale_many_temporary_children, temporary_bystander,
simple_global_supervisor, hanging_restart_loop, hanging_restart_loop_simple,
@@ -1459,6 +1461,54 @@ count_children(Config) when is_list(Config) ->
[1,0,0,0] = get_child_counts(sup_test).
%%-------------------------------------------------------------------------
+%% Test count_children when some children are restarting
+count_restarting_children(Config) when is_list(Config) ->
+ process_flag(trap_exit, true),
+ Child = {child, {supervisor_deadlock, start_child_noreg, []},
+ permanent, brutal_kill, worker, []},
+ %% 2 sek delay on failing restart (see supervisor_deadlock.erl) ->
+ %% MaxR=20, MaxT=10 should ensure a restart loop when starting and
+ %% restarting 3 instances of the child (as below)
+ {ok, SupPid} = start_link({ok, {{simple_one_for_one, 20, 10}, [Child]}}),
+
+ %% Ets table with state read by supervisor_deadlock.erl
+ ets:new(supervisor_deadlock,[set,named_table,public]),
+ ets:insert(supervisor_deadlock,{fail_start,false}),
+
+ [1,0,0,0] = get_child_counts(SupPid),
+ {ok, Ch1_1} = supervisor:start_child(SupPid, []),
+ [1,1,0,1] = get_child_counts(SupPid),
+ {ok, Ch1_2} = supervisor:start_child(SupPid, []),
+ [1,2,0,2] = get_child_counts(SupPid),
+ {ok, Ch1_3} = supervisor:start_child(SupPid, []),
+ [1,3,0,3] = get_child_counts(SupPid),
+
+ supervisor_deadlock:restart_child(Ch1_1),
+ supervisor_deadlock:restart_child(Ch1_2),
+ supervisor_deadlock:restart_child(Ch1_3),
+ test_server:sleep(400),
+ [1,3,0,3] = get_child_counts(SupPid),
+ [Ch2_1, Ch2_2, Ch2_3] = [C || {_,C,_,_} <- supervisor:which_children(SupPid)],
+
+ ets:insert(supervisor_deadlock,{fail_start,true}),
+ supervisor_deadlock:restart_child(Ch2_1),
+ supervisor_deadlock:restart_child(Ch2_2),
+ test_server:sleep(4000), % allow restart to happen before proceeding
+ [1,1,0,3] = get_child_counts(SupPid),
+
+ ets:insert(supervisor_deadlock,{fail_start,false}),
+ test_server:sleep(4000), % allow restart to happen before proceeding
+ [1,3,0,3] = get_child_counts(SupPid),
+
+ ok = supervisor:terminate_child(SupPid, Ch2_3),
+ [1,2,0,2] = get_child_counts(SupPid),
+ [Ch3_1, Ch3_2] = [C || {_,C,_,_} <- supervisor:which_children(SupPid)],
+ ok = supervisor:terminate_child(SupPid, Ch3_1),
+ [1,1,0,1] = get_child_counts(SupPid),
+ ok = supervisor:terminate_child(SupPid, Ch3_2),
+ [1,0,0,0] = get_child_counts(SupPid).
+
+%%-------------------------------------------------------------------------
%% Temporary children shall not be restarted so they should not save
%% start parameters, as it potentially can take up a huge amount of
%% memory for no purpose.
diff --git a/lib/stdlib/test/supervisor_deadlock.erl b/lib/stdlib/test/supervisor_deadlock.erl
index 288547a972..8d3d1c6f30 100644
--- a/lib/stdlib/test/supervisor_deadlock.erl
+++ b/lib/stdlib/test/supervisor_deadlock.erl
@@ -11,9 +11,11 @@ init([child]) ->
%% terminates immediately
{ok, []};
[{fail_start, true}] ->
- %% Restart frequency is MaxR=8, MaxT=10, so this will
- %% ensure that restart intensity is not reached -> restart
- %% loop
+ %% A restart frequency of MaxR=8, MaxT=10 should ensure
+ %% that restart intensity is not reached -> restart loop.
+ %% (Note that if we use simple_one_for_one, and start
+ %% 'many' child instances, the restart frequency must be
+ %% ajusted accordingly.)
timer:sleep(2000), % NOTE: this could be a gen_server call timeout
{stop, error}
@@ -41,5 +43,11 @@ code_change(_OldVsn, State, _Extra) ->
start_child() ->
gen_server:start_link({local, ?MODULE}, ?MODULE, [child], []).
+start_child_noreg() ->
+ gen_server:start_link(?MODULE, [child], []).
+
restart_child() ->
gen_server:cast(supervisor_deadlock, restart).
+
+restart_child(Pid) ->
+ gen_server:cast(Pid, restart).
diff --git a/lib/stdlib/test/timer_SUITE.erl b/lib/stdlib/test/timer_SUITE.erl
index 057d82fb65..10dcfad76f 100644
--- a/lib/stdlib/test/timer_SUITE.erl
+++ b/lib/stdlib/test/timer_SUITE.erl
@@ -80,8 +80,6 @@ report_result(Error) -> ?line test_server:fail(Error).
big_test(N) ->
C = start_collect(),
system_time(), system_time(), system_time(),
- random:seed(erlang:timestamp()),
- random:uniform(100),random:uniform(100),random:uniform(100),
big_loop(C, N, []),
@@ -127,17 +125,17 @@ big_loop(C, N, Pids) ->
after 0 ->
%% maybe start an interval timer test
- Pids1 = maybe_start_i_test(Pids, C, random:uniform(4)),
+ Pids1 = maybe_start_i_test(Pids, C, rand:uniform(4)),
%% start 1-4 "after" tests
- Pids2 = start_after_test(Pids1, C, random:uniform(4)),
+ Pids2 = start_after_test(Pids1, C, rand:uniform(4)),
%%Pids2=Pids1,
%% wait a little while
- timer:sleep(random:uniform(200)*3),
+ timer:sleep(rand:uniform(200)*3),
%% spawn zero, one or two nrev to get some load ;-/
- Pids3 = start_nrev(Pids2, random:uniform(100)),
+ Pids3 = start_nrev(Pids2, rand:uniform(100)),
big_loop(C, N-1, Pids3)
end.
@@ -148,20 +146,20 @@ start_nrev(Pids, N) when N < 25 ->
start_nrev(Pids, N) when N < 75 ->
[spawn_link(timer_SUITE, do_nrev, [1])|Pids];
start_nrev(Pids, _N) ->
- NrevPid1 = spawn_link(timer_SUITE, do_nrev, [random:uniform(1000)*10]),
+ NrevPid1 = spawn_link(timer_SUITE, do_nrev, [rand:uniform(1000)*10]),
NrevPid2 = spawn_link(timer_SUITE, do_nrev, [1]),
[NrevPid1,NrevPid2|Pids].
start_after_test(Pids, C, 1) ->
- TO1 = random:uniform(100)*47,
+ TO1 = rand:uniform(100)*47,
[s_a_t(C, TO1)|Pids];
start_after_test(Pids, C, 2) ->
- TO1 = random:uniform(100)*47,
- TO2 = TO1 div random:uniform(3) + 101,
+ TO1 = rand:uniform(100)*47,
+ TO2 = TO1 div rand:uniform(3) + 101,
[s_a_t(C, TO1),s_a_t(C, TO2)|Pids];
start_after_test(Pids, C, N) ->
- TO1 = random:uniform(100)*47,
+ TO1 = rand:uniform(100)*47,
start_after_test([s_a_t(C, TO1)|Pids], C, N-1).
s_a_t(C, TimeOut) ->
@@ -187,8 +185,8 @@ a_t(C, TimeOut) ->
maybe_start_i_test(Pids, C, 1) ->
%% ok do it
- TOI = random:uniform(53)*49,
- CountI = random:uniform(10) + 3, % at least 4 times
+ TOI = rand:uniform(53)*49,
+ CountI = rand:uniform(10) + 3, % at least 4 times
[spawn_link(timer_SUITE, i_t, [C, TOI, CountI])|Pids];
maybe_start_i_test(Pids, _C, _) ->
Pids.