aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/dets_SUITE.erl26
-rw-r--r--lib/stdlib/test/erl_eval_SUITE.erl2
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl2
-rw-r--r--lib/stdlib/test/sofs_SUITE.erl27
-rw-r--r--lib/stdlib/test/supervisor_SUITE.erl51
-rw-r--r--lib/stdlib/test/timer_simple_SUITE.erl31
6 files changed, 116 insertions, 23 deletions
diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl
index 9fcc9e6aaf..698070368f 100644
--- a/lib/stdlib/test/dets_SUITE.erl
+++ b/lib/stdlib/test/dets_SUITE.erl
@@ -53,7 +53,7 @@
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_8923/1, otp_9282/1]).
-export([dets_dirty_loop/0]).
@@ -112,7 +112,7 @@ 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_8899, otp_8903, otp_8923, otp_9282]
end.
groups() ->
@@ -3857,6 +3857,28 @@ otp_8923(Config) when is_list(Config) ->
file:delete(File),
ok.
+otp_9282(doc) ->
+ ["OTP-9282. The name of a table can be an arbitrary term"];
+otp_9282(suite) ->
+ [];
+otp_9282(Config) when is_list(Config) ->
+ some_calls(make_ref(), Config),
+ some_calls({a,typical,name}, Config),
+ some_calls(fun() -> a_funny_name end, Config),
+ ok.
+
+some_calls(Tab, Config) ->
+ File = filename(ref, Config),
+ ?line {ok,T} = dets:open_file(Tab, [{file,File}]),
+ ?line T = Tab,
+ ?line false = dets:info(T, safe_fixed),
+ ?line File = dets:info(T, filename),
+ ?line ok = dets:insert(Tab, [{3,0}]),
+ ?line [{3,0}] = dets:lookup(Tab, 3),
+ ?line [{3,0}] = dets:traverse(Tab, fun(X) -> {continue, X} end),
+ ?line ok = dets:close(T),
+ file:delete(File).
+
%%
%% Parts common to several test cases
%%
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index 4b59cee99e..0bcf3c5b71 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -1199,7 +1199,7 @@ local_func(F, As0, Bs0) when is_atom(F) ->
lfh_value_extra() ->
%% Not documented.
- {value, fun(F, As) -> local_func_value(F, As) end, []}.
+ {value, fun(F, As, a1, a2) -> local_func_value(F, As) end, [a1, a2]}.
lfh_value() ->
{value, fun(F, As) -> local_func_value(F, As) end}.
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index bc811355ab..280c95b1aa 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -1161,7 +1161,7 @@ parse_forms2(String, Cont0, Line, Forms) ->
{done, {ok, Tokens, EndLine}, Chars} ->
{ok, Form} = erl_parse:parse_form(Tokens),
parse_forms2(Chars, [], EndLine, [Form | Forms]);
- {more, Cont} when element(3, Cont) =:= [] ->
+ {more, Cont} when element(4, Cont) =:= [] ->
%% extra spaces after forms...
parse_forms2([], Cont, Line, Forms);
{more, Cont} ->
diff --git a/lib/stdlib/test/sofs_SUITE.erl b/lib/stdlib/test/sofs_SUITE.erl
index 01de1f0600..d6f88a655e 100644
--- a/lib/stdlib/test/sofs_SUITE.erl
+++ b/lib/stdlib/test/sofs_SUITE.erl
@@ -1602,19 +1602,15 @@ relative_product_2(Conf) when is_list(Conf) ->
from_term([{{a},b}])}, ER)),
?line {'EXIT', {badarg, _}} = (catch relative_product({}, ER)),
- ?line eval(relative_product({relation([{a,b}])},
- from_term([],[{{atom},atom}])),
- ER),
- ?line eval(relative_product({relation([{a,b}]),relation([{a,1}])},
- from_term([{{b,1},{tjo,hej,sa}}])),
- from_term([{a,{tjo,hej,sa}}])),
- ?line eval(relative_product({relation([{a,b}]), ER},
- from_term([{{a,b},b}])),
- ER),
- ?line eval(relative_product({relation([{a,b},{c,a}]),
- relation([{a,1},{a,2}])},
- from_term([{{b,1},b1},{{b,2},b2}])),
- relation([{a,b1},{a,b2}])),
+ ?line relprod2({relation([{a,b}])}, from_term([],[{{atom},atom}]), ER),
+ ?line relprod2({relation([{a,b}]),relation([{a,1}])},
+ from_term([{{b,1},{tjo,hej,sa}}]),
+ from_term([{a,{tjo,hej,sa}}])),
+ ?line relprod2({relation([{a,b}]), ER}, from_term([{{a,b},b}]), ER),
+ ?line relprod2({relation([{a,b},{c,a}]),
+ relation([{a,1},{a,2}])},
+ from_term([{{b,1},b1},{{b,2},b2}]),
+ relation([{a,b1},{a,b2}])),
?line eval(relative_product({relation([{a,b}]), ER}),
from_term([],[{atom,{atom,atom}}])),
?line eval(relative_product({from_term([{{a,[a,b]},[a]}]),
@@ -1622,6 +1618,11 @@ relative_product_2(Conf) when is_list(Conf) ->
from_term([{{a,[a,b]},{[a],[[a,b]]}}])),
ok.
+relprod2(A1T, A2, R) ->
+ %% A tuple as first argument is the old interface:
+ eval(relative_product(A1T, A2), R),
+ eval(relative_product(tuple_to_list(A1T), A2), R).
+
product_1(suite) -> [];
product_1(doc) -> [""];
product_1(Conf) when is_list(Conf) ->
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index cc271bd047..c79a5002fb 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -28,8 +28,8 @@
init_per_group/2,end_per_group/2, init_per_testcase/2,
end_per_testcase/2]).
-%% Indirect spawn export
--export([init/1]).
+%% Internal export
+-export([init/1, terminate_all_children/1]).
%% API tests
-export([ sup_start_normal/1, sup_start_ignore_init/1,
@@ -55,7 +55,8 @@
%% Misc tests
-export([child_unlink/1, tree/1, count_children_memory/1,
do_not_save_start_parameters_for_temporary_children/1,
- do_not_save_child_specs_for_temporary_children/1]).
+ do_not_save_child_specs_for_temporary_children/1,
+ simple_one_for_one_scale_many_temporary_children/1]).
%%-------------------------------------------------------------------------
@@ -72,7 +73,8 @@ all() ->
{group, normal_termination},
{group, abnormal_termination}, child_unlink, tree,
count_children_memory, do_not_save_start_parameters_for_temporary_children,
- do_not_save_child_specs_for_temporary_children].
+ do_not_save_child_specs_for_temporary_children,
+ simple_one_for_one_scale_many_temporary_children].
groups() ->
[{sup_start, [],
@@ -1201,6 +1203,47 @@ restarted(Sup, {Id,_,_,_,_,_} = ChildSpec, TerminateHow) ->
{error, {already_started, _}} = supervisor:start_child(Sup, ChildSpec).
+%%-------------------------------------------------------------------------
+%% OTP-9242: Pids for dynamic temporary children were saved as a list,
+%% which caused bad scaling when adding/deleting many processes.
+simple_one_for_one_scale_many_temporary_children(_Config) ->
+ process_flag(trap_exit, true),
+ Child = {child, {supervisor_1, start_child, []}, temporary, 1000,
+ worker, []},
+ {ok, _SupPid} = start_link({ok, {{simple_one_for_one, 2, 3600}, [Child]}}),
+
+ C1 = [begin
+ {ok,P} = supervisor:start_child(sup_test,[]),
+ P
+ end || _<- lists:seq(1,1000)],
+ {T1,done} = timer:tc(?MODULE,terminate_all_children,[C1]),
+
+ C2 = [begin
+ {ok,P} = supervisor:start_child(sup_test,[]),
+ P
+ end || _<- lists:seq(1,10000)],
+ {T2,done} = timer:tc(?MODULE,terminate_all_children,[C2]),
+
+ Scaling = T2 div T1,
+ if Scaling > 20 ->
+ %% The scaling shoul be linear (i.e.10, really), but we
+ %% give some extra here to avoid failing the test
+ %% unecessarily.
+ ?t:fail({bad_scaling,Scaling});
+ true ->
+ ok
+ end.
+
+
+terminate_all_children([C|Cs]) ->
+ ok = supervisor:terminate_child(sup_test,C),
+ terminate_all_children(Cs);
+terminate_all_children([]) ->
+ done.
+
+
+
+%%-------------------------------------------------------------------------
terminate(Pid, Reason) when Reason =/= supervisor ->
terminate(dummy, Pid, dummy, Reason).
diff --git a/lib/stdlib/test/timer_simple_SUITE.erl b/lib/stdlib/test/timer_simple_SUITE.erl
index 852afa1a4d..dc751aad16 100644
--- a/lib/stdlib/test/timer_simple_SUITE.erl
+++ b/lib/stdlib/test/timer_simple_SUITE.erl
@@ -229,7 +229,7 @@ cancel2(Config) when is_list(Config) ->
tc(doc) -> "Test sleep/1 and tc/3.";
tc(suite) -> [];
tc(Config) when is_list(Config) ->
- % This should both sleep and tc/3
+ %% This should test both sleep and tc/3
?line {Res1, ok} = timer:tc(timer, sleep, [500]),
?line ok = if
Res1 < 500*1000 -> {too_early, Res1}; % Too early
@@ -237,13 +237,40 @@ tc(Config) when is_list(Config) ->
true -> ok
end,
- % This should both sleep and tc/2
+ %% tc/2
?line {Res2, ok} = timer:tc(fun(T) -> timer:sleep(T) end, [500]),
?line ok = if
Res2 < 500*1000 -> {too_early, Res2}; % Too early
Res2 > 800*1000 -> {too_late, Res2}; % Too much time
true -> ok
end,
+
+ %% tc/1
+ ?line {Res3, ok} = timer:tc(fun() -> timer:sleep(500) end),
+ ?line ok = if
+ Res3 < 500*1000 -> {too_early, Res3}; % Too early
+ Res3 > 800*1000 -> {too_late, Res3}; % Too much time
+ true -> ok
+ end,
+
+ %% Check that timer:tc don't catch errors
+ ?line ok = try timer:tc(erlang, exit, [foo])
+ catch exit:foo -> ok
+ end,
+
+ ?line ok = try timer:tc(fun(Reason) -> 1 = Reason end, [foo])
+ catch error:{badmatch,_} -> ok
+ end,
+
+ ?line ok = try timer:tc(fun() -> throw(foo) end)
+ catch foo -> ok
+ end,
+
+ %% Check that return values are propageted
+ Self = self(),
+ ?line {_, Self} = timer:tc(erlang, self, []),
+ ?line {_, Self} = timer:tc(fun(P) -> P end, [self()]),
+ ?line {_, Self} = timer:tc(fun() -> self() end),
?line Sec = timer:seconds(4),
?line Min = timer:minutes(4),