diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/binary_module_SUITE.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/test/dets_SUITE.erl | 41 | ||||
-rw-r--r-- | lib/stdlib/test/supervisor_SUITE.erl | 57 | ||||
-rw-r--r-- | lib/stdlib/test/unicode_SUITE.erl | 12 |
4 files changed, 35 insertions, 79 deletions
diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl index d5a0fe21b4..32cec0db6f 100644 --- a/lib/stdlib/test/binary_module_SUITE.erl +++ b/lib/stdlib/test/binary_module_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2013. All Rights Reserved. +%% Copyright Ericsson AB 1997-2014. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -40,7 +40,7 @@ -export([init_per_testcase/2, end_per_testcase/2]). % Default timetrap timeout (set in init_per_testcase). % Some of these testcases are really heavy... --define(default_timeout, ?t:minutes(20)). +-define(default_timeout, ?t:minutes(30)). -endif. diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl index 00a5da42ad..6be37cbecf 100644 --- a/lib/stdlib/test/dets_SUITE.erl +++ b/lib/stdlib/test/dets_SUITE.erl @@ -3953,15 +3953,6 @@ otp_11709(Config) when is_list(Config) -> %% Parts common to several test cases %% -start_node_rel(Name, Rel, How) -> - Release = [{release, atom_to_list(Rel)}], - Pa = filename:dirname(code:which(?MODULE)), - test_server:start_node(Name, How, - [{args, - " -kernel net_setuptime 100 " - " -pa " ++ Pa}, - {erl, Release}]). - crash(File, Where) -> crash(File, Where, 10). @@ -4352,7 +4343,7 @@ check_badarg({'EXIT', {badarg, [{M,F,Args,_} | _]}}, M, F, Args) -> check_badarg({'EXIT', {badarg, [{M,F,A,_} | _]}}, M, F, Args) -> true = test_server:is_native(M) andalso length(Args) =:= A. -check_pps(P0) -> +check_pps({Ports0,Procs0} = P0) -> case pps() of P0 -> ok; @@ -4364,22 +4355,28 @@ check_pps(P0) -> case pps() of P0 -> ok; - P1 -> - io:format("failure, got ~p~n, expected ~p\n", [P1, P0]), - {Ports0,Procs0} = P0, - {Ports1,Procs1} = P1, - show("Old ports", Ports0 -- Ports1), - show("New ports", Ports1 -- Ports0), - show("Old procs", Procs0 -- Procs1), - show("New procs", Procs1 -- Procs0), - ?t:fail() - end + {Ports1,Procs1} = P1 -> + case {Ports1 -- Ports0, Procs1 -- Procs0} of + {[], []} -> ok; + {PortsDiff,ProcsDiff} -> + io:format("failure, got ~p~n, expected ~p\n", [P1, P0]), + show("Old port", Ports0 -- Ports1), + show("New port", PortsDiff), + show("Old proc", Procs0 -- Procs1), + show("New proc", ProcsDiff), + ?t:fail() + end + end end. show(_S, []) -> ok; -show(S, L) -> - io:format("~s: ~p~n", [S, L]). +show(S, [Pid|Pids]) when is_pid(Pid) -> + io:format("~s: ~p~n", [S, erlang:process_info(Pid)]), + show(S, Pids); +show(S, [Port|Ports]) when is_port(Port)-> + io:format("~s: ~p~n", [S, erlang:port_info(Port)]), + show(S, Ports). pps() -> dets:start(), diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl index ac5a34c3bc..836ea7c030 100644 --- a/lib/stdlib/test/supervisor_SUITE.erl +++ b/lib/stdlib/test/supervisor_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-2014. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -60,7 +60,7 @@ simple_one_for_one_extra/1, simple_one_for_one_shutdown/1]). %% Misc tests --export([child_unlink/1, tree/1, count_children_memory/1, +-export([child_unlink/1, tree/1, count_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, @@ -82,7 +82,7 @@ all() -> {group, normal_termination}, {group, shutdown_termination}, {group, abnormal_termination}, child_unlink, tree, - count_children_memory, do_not_save_start_parameters_for_temporary_children, + count_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]. @@ -129,23 +129,10 @@ init_per_group(_GroupName, Config) -> end_per_group(_GroupName, Config) -> Config. -init_per_testcase(count_children_memory, Config) -> - try erlang:memory() of - _ -> - erts_debug:set_internal_state(available_internal_state, true), - Dog = ?t:timetrap(?TIMEOUT), - [{watchdog,Dog}|Config] - catch error:notsup -> - {skip, "+Meamin used during test; erlang:memory/1 not available"} - end; init_per_testcase(_Case, Config) -> Dog = ?t:timetrap(?TIMEOUT), [{watchdog,Dog}|Config]. -end_per_testcase(count_children_memory, Config) -> - catch erts_debug:set_internal_state(available_internal_state, false), - ?t:timetrap_cancel(?config(watchdog,Config)), - ok; end_per_testcase(_Case, Config) -> ?t:timetrap_cancel(?config(watchdog,Config)), ok. @@ -1249,34 +1236,24 @@ tree(Config) when is_list(Config) -> [0,0,0,0] = get_child_counts(NewSup2). %%------------------------------------------------------------------------- -%% Test that count_children does not eat memory. -count_children_memory(Config) when is_list(Config) -> +%% Test count_children +count_children(Config) when is_list(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]}}), [supervisor:start_child(sup_test, []) || _Ignore <- lists:seq(1,1000)], - garbage_collect(), - _Size1 = proc_memory(), Children = supervisor:which_children(sup_test), - _Size2 = proc_memory(), ChildCount = get_child_counts(sup_test), - _Size3 = proc_memory(), [supervisor:start_child(sup_test, []) || _Ignore2 <- lists:seq(1,1000)], - garbage_collect(), - Children2 = supervisor:which_children(sup_test), - Size4 = proc_memory(), ChildCount2 = get_child_counts(sup_test), - Size5 = proc_memory(), + Children2 = supervisor:which_children(sup_test), - garbage_collect(), - Children3 = supervisor:which_children(sup_test), - Size6 = proc_memory(), ChildCount3 = get_child_counts(sup_test), - Size7 = proc_memory(), + Children3 = supervisor:which_children(sup_test), 1000 = length(Children), [1,1000,0,1000] = ChildCount, @@ -1285,27 +1262,9 @@ count_children_memory(Config) when is_list(Config) -> Children3 = Children2, ChildCount3 = ChildCount2, - %% count_children consumes memory using an accumulator function, - %% but the space can be reclaimed incrementally, - %% which_children may generate garbage that will be reclaimed later. - case (Size5 =< Size4) of - true -> ok; - false -> - test_server:fail({count_children, used_more_memory,Size4,Size5}) - end, - case Size7 =< Size6 of - true -> ok; - false -> - test_server:fail({count_children, used_more_memory,Size6,Size7}) - end, - [terminate(SupPid, Pid, child, kill) || {undefined, Pid, worker, _Modules} <- Children3], [1,0,0,0] = get_child_counts(sup_test). -proc_memory() -> - erts_debug:set_internal_state(wait, deallocations), - erlang:memory(processes_used). - %%------------------------------------------------------------------------- %% Temporary children shall not be restarted so they should not save %% start parameters, as it potentially can take up a huge amount of @@ -1483,7 +1442,7 @@ simple_one_for_one_scale_many_temporary_children(_Config) -> if T1 > 0 -> Scaling = T2 div T1, - if Scaling > 20 -> + if Scaling > 50 -> %% The scaling shoul be linear (i.e.10, really), but we %% give some extra here to avoid failing the test %% unecessarily. diff --git a/lib/stdlib/test/unicode_SUITE.erl b/lib/stdlib/test/unicode_SUITE.erl index e2d789bbe6..10b29d0d28 100644 --- a/lib/stdlib/test/unicode_SUITE.erl +++ b/lib/stdlib/test/unicode_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2008-2013. All Rights Reserved. +%% Copyright Ericsson AB 2008-2014. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -98,7 +98,7 @@ ex_binaries_errors_utf8(Config) when is_list(Config) -> unicode:characters_to_list(Chomped), BrokenPart = iolist_to_binary(DeepBrokenPart2) end || X <- lists:seq(1,OKLen) ] - end || N <- lists:seq(1,20) ], + end || N <- lists:seq(1,21,4) ], ok. ex_binaries_errors_utf16_little(Config) when is_list(Config) -> @@ -124,7 +124,7 @@ ex_binaries_errors_utf16_little(Config) when is_list(Config) -> unicode:characters_to_list(Chomped,{utf16,little}), BrokenPart = iolist_to_binary(DeepBrokenPart2) end || X <- lists:seq(1,OKLen) ] - end || N <- lists:seq(1,15) ], + end || N <- lists:seq(1,16,3) ], ok. ex_binaries_errors_utf16_big(Config) when is_list(Config) -> BrokenPart = << <<X:16/big>> || X <- lists:seq(16#DC00,16#DFFF) >>, @@ -149,7 +149,7 @@ ex_binaries_errors_utf16_big(Config) when is_list(Config) -> unicode:characters_to_list(Chomped,{utf16,big}), BrokenPart = iolist_to_binary(DeepBrokenPart2) end || X <- lists:seq(1,OKLen) ] - end || N <- lists:seq(1,15) ], + end || N <- lists:seq(1,16,3) ], ok. ex_binaries_errors_utf32_big(Config) when is_list(Config) -> @@ -175,7 +175,7 @@ ex_binaries_errors_utf32_big(Config) when is_list(Config) -> unicode:characters_to_list(Chomped,{utf32,big}), BrokenPart = iolist_to_binary(DeepBrokenPart2) end || X <- lists:seq(1,OKLen) ] - end || N <- lists:seq(1,15) ], + end || N <- lists:seq(1,16,3) ], ok. ex_binaries_errors_utf32_little(Config) when is_list(Config) -> @@ -201,7 +201,7 @@ ex_binaries_errors_utf32_little(Config) when is_list(Config) -> unicode:characters_to_list(Chomped,{utf32,little}), BrokenPart = iolist_to_binary(DeepBrokenPart2) end || X <- lists:seq(1,OKLen) ] - end || N <- lists:seq(1,15) ], + end || N <- lists:seq(1,16,3) ], ok. |