diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/erl_lint_SUITE.erl | 19 | ||||
-rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 16 | ||||
-rw-r--r-- | lib/stdlib/test/supervisor_1.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/test/supervisor_2.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/test/supervisor_SUITE.erl | 290 | ||||
-rw-r--r-- | lib/stdlib/test/tar_SUITE.erl | 4 |
6 files changed, 169 insertions, 164 deletions
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index 9041adbe5c..e4c7fd5b02 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -2631,7 +2631,24 @@ bif_clash(Config) when is_list(Config) -> binary_part(A,B,C). ">>, [warn_unused_import], - {warnings,[{2,erl_lint,{redefine_bif_import,{binary_part,3}}}]}} + {warnings,[{2,erl_lint,{redefine_bif_import,{binary_part,3}}}]}}, + %% Don't accept call to a guard BIF if there is a local definition + %% or an import with the same name. + {clash21, + <<"-export([is_list/1]). + -import(x, [is_tuple/1]). + x(T) when is_tuple(T) -> ok; + x(T) when is_list(T) -> ok. + y(T) when is_tuple(T) =:= true -> ok; + y(T) when is_list(T) =:= true -> ok. + is_list(_) -> + ok. + ">>, + [{no_auto_import,[{is_tuple,1}]}], + {errors,[{3,erl_lint,{illegal_guard_local_call,{is_tuple,1}}}, + {4,erl_lint,{illegal_guard_local_call,{is_list,1}}}, + {5,erl_lint,{illegal_guard_local_call,{is_tuple,1}}}, + {6,erl_lint,{illegal_guard_local_call,{is_list,1}}}],[]}} ], ?line [] = run(Config, Ts), diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 0e8849b5b3..101828fdef 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -74,7 +74,7 @@ -export([bad_table/1, types/1]). -export([otp_9423/1]). --export([init_per_testcase/2]). +-export([init_per_testcase/2, end_per_testcase/2]). %% Convenience for manual testing -export([random_test/0]). @@ -2385,6 +2385,8 @@ setopts_do(Opts) -> ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,{protection,private,false})), ?line {'EXIT',{badarg,_}} = (catch ets:setopts(T,protection)), ?line ets:delete(T), + unlink(Heir), + exit(Heir, bang), ok. bad_table(doc) -> ["All kinds of operations with bad table argument"]; @@ -5645,7 +5647,8 @@ spawn_logger(Procs) -> true -> exit(Proc, kill); _ -> ok end, - erlang:display(process_info(Proc)), + erlang:display({"Waiting for 'DOWN' from", Proc, + process_info(Proc), pid_status(Proc)}), receive {'DOWN', Mon, _, _, _} -> ok @@ -5656,6 +5659,15 @@ spawn_logger(Procs) -> spawn_logger([From]) end. +pid_status(Pid) -> + try + erts_debug:get_internal_state({process_status, Pid}) + catch + error:undef -> + erts_debug:set_internal_state(available_internal_state, true), + pid_status(Pid) + end. + start_spawn_logger() -> case whereis(ets_test_spawn_logger) of Pid when is_pid(Pid) -> true; diff --git a/lib/stdlib/test/supervisor_1.erl b/lib/stdlib/test/supervisor_1.erl index f819594c46..777a48e38b 100644 --- a/lib/stdlib/test/supervisor_1.erl +++ b/lib/stdlib/test/supervisor_1.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 diff --git a/lib/stdlib/test/supervisor_2.erl b/lib/stdlib/test/supervisor_2.erl index 67aacf5a9c..60d037f4e0 100644 --- a/lib/stdlib/test/supervisor_2.erl +++ b/lib/stdlib/test/supervisor_2.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. 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 diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl index d3d140abbc..71b76c093f 100644 --- a/lib/stdlib/test/supervisor_SUITE.erl +++ b/lib/stdlib/test/supervisor_SUITE.erl @@ -34,8 +34,10 @@ %% API tests -export([ sup_start_normal/1, sup_start_ignore_init/1, - sup_start_ignore_child/1, sup_start_error_return/1, - sup_start_fail/1, sup_stop_infinity/1, + sup_start_ignore_child/1, sup_start_ignore_temporary_child/1, + sup_start_ignore_temporary_child_start_child/1, + sup_start_ignore_temporary_child_start_child_simple/1, + sup_start_error_return/1, sup_start_fail/1, sup_stop_infinity/1, sup_stop_timeout/1, sup_stop_brutal_kill/1, child_adm/1, child_adm_simple/1, child_specs/1, extra_return/1]). @@ -85,8 +87,10 @@ all() -> groups() -> [{sup_start, [], [sup_start_normal, sup_start_ignore_init, - sup_start_ignore_child, sup_start_error_return, - sup_start_fail]}, + sup_start_ignore_child, sup_start_ignore_temporary_child, + sup_start_ignore_temporary_child_start_child, + sup_start_ignore_temporary_child_start_child_simple, + sup_start_error_return, sup_start_fail]}, {sup_stop, [], [sup_stop_infinity, sup_stop_timeout, sup_stop_brutal_kill]}, @@ -158,29 +162,23 @@ get_child_counts(Supervisor) -> %%------------------------------------------------------------------------- %% Test cases starts here. -%%------------------------------------------------------------------------- -sup_start_normal(doc) -> - ["Tests that the supervisor process starts correctly and that it " - "can be terminated gracefully."]; -sup_start_normal(suite) -> []; +%% ------------------------------------------------------------------------- +%% Tests that the supervisor process starts correctly and that it can +%% be terminated gracefully. sup_start_normal(Config) when is_list(Config) -> process_flag(trap_exit, true), {ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), terminate(Pid, shutdown). %%------------------------------------------------------------------------- -sup_start_ignore_init(doc) -> - ["Tests what happens if init-callback returns ignore"]; -sup_start_ignore_init(suite) -> []; +%% Tests what happens if init-callback returns ignore. sup_start_ignore_init(Config) when is_list(Config) -> process_flag(trap_exit, true), ignore = start_link(ignore), check_exit_reason(normal). %%------------------------------------------------------------------------- -sup_start_ignore_child(doc) -> - ["Tests what happens if init-callback returns ignore"]; -sup_start_ignore_child(suite) -> []; +%% Tests what happens if init-callback returns ignore. sup_start_ignore_child(Config) when is_list(Config) -> process_flag(trap_exit, true), {ok, _Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), @@ -197,30 +195,75 @@ sup_start_ignore_child(Config) when is_list(Config) -> [2,1,0,2] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -sup_start_error_return(doc) -> - ["Tests what happens if init-callback returns a invalid value"]; -sup_start_error_return(suite) -> []; +%% Tests what happens if child's init-callback returns ignore for a +%% temporary child when ChildSpec is returned directly from supervisor +%% init callback. +%% Child spec shall NOT be saved!!! +sup_start_ignore_temporary_child(Config) when is_list(Config) -> + process_flag(trap_exit, true), + Child1 = {child1, {supervisor_1, start_child, [ignore]}, + temporary, 1000, worker, []}, + Child2 = {child2, {supervisor_1, start_child, []}, temporary, + 1000, worker, []}, + {ok, _Pid} = start_link({ok, {{one_for_one, 2, 3600}, [Child1,Child2]}}), + + [{child2, CPid2, worker, []}] = supervisor:which_children(sup_test), + true = is_pid(CPid2), + [1,1,0,1] = get_child_counts(sup_test). + +%%------------------------------------------------------------------------- +%% Tests what happens if child's init-callback returns ignore for a +%% temporary child when child is started with start_child/2. +%% Child spec shall NOT be saved!!! +sup_start_ignore_temporary_child_start_child(Config) when is_list(Config) -> + process_flag(trap_exit, true), + {ok, _Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), + Child1 = {child1, {supervisor_1, start_child, [ignore]}, + temporary, 1000, worker, []}, + Child2 = {child2, {supervisor_1, start_child, []}, temporary, + 1000, worker, []}, + + {ok, undefined} = supervisor:start_child(sup_test, Child1), + {ok, CPid2} = supervisor:start_child(sup_test, Child2), + + [{child2, CPid2, worker, []}] = supervisor:which_children(sup_test), + [1,1,0,1] = get_child_counts(sup_test). + +%%------------------------------------------------------------------------- +%% Tests what happens if child's init-callback returns ignore for a +%% temporary child when child is started with start_child/2, and the +%% supervisor is simple_one_for_one. +%% Child spec shall NOT be saved!!! +sup_start_ignore_temporary_child_start_child_simple(Config) + when is_list(Config) -> + process_flag(trap_exit, true), + Child1 = {child1, {supervisor_1, start_child, [ignore]}, + temporary, 1000, worker, []}, + {ok, _Pid} = start_link({ok, {{simple_one_for_one, 2, 3600}, [Child1]}}), + + {ok, undefined} = supervisor:start_child(sup_test, []), + {ok, CPid2} = supervisor:start_child(sup_test, []), + + [{undefined, CPid2, worker, []}] = supervisor:which_children(sup_test), + [1,1,0,1] = get_child_counts(sup_test). + +%%------------------------------------------------------------------------- +%% Tests what happens if init-callback returns a invalid value. sup_start_error_return(Config) when is_list(Config) -> process_flag(trap_exit, true), {error, Term} = start_link(invalid), check_exit_reason(Term). %%------------------------------------------------------------------------- -sup_start_fail(doc) -> - ["Tests what happens if init-callback fails"]; -sup_start_fail(suite) -> []; +%% Tests what happens if init-callback fails. sup_start_fail(Config) when is_list(Config) -> process_flag(trap_exit, true), {error, Term} = start_link(fail), check_exit_reason(Term). %%------------------------------------------------------------------------- - -sup_stop_infinity(doc) -> - ["See sup_stop/1 when Shutdown = infinity, this walue is allowed " - "for children of type supervisor _AND_ worker"]; -sup_stop_infinity(suite) -> []; - +%% See sup_stop/1 when Shutdown = infinity, this walue is allowed for +%% children of type supervisor _AND_ worker. sup_stop_infinity(Config) when is_list(Config) -> process_flag(trap_exit, true), {ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), @@ -238,11 +281,7 @@ sup_stop_infinity(Config) when is_list(Config) -> check_exit_reason(CPid2, shutdown). %%------------------------------------------------------------------------- - -sup_stop_timeout(doc) -> - ["See sup_stop/1 when Shutdown = 1000"]; -sup_stop_timeout(suite) -> []; - +%% See sup_stop/1 when Shutdown = 1000 sup_stop_timeout(Config) when is_list(Config) -> process_flag(trap_exit, true), {ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), @@ -264,10 +303,7 @@ sup_stop_timeout(Config) when is_list(Config) -> %%------------------------------------------------------------------------- -sup_stop_brutal_kill(doc) -> - ["See sup_stop/1 when Shutdown = brutal_kill"]; -sup_stop_brutal_kill(suite) -> []; - +%% See sup_stop/1 when Shutdown = brutal_kill sup_stop_brutal_kill(Config) when is_list(Config) -> process_flag(trap_exit, true), {ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), @@ -286,14 +322,10 @@ sup_stop_brutal_kill(Config) when is_list(Config) -> check_exit_reason(CPid2, killed). %%------------------------------------------------------------------------- -extra_return(doc) -> - ["The start function provided to start a child may " - "return {ok, Pid} or {ok, Pid, Info}, if it returns " - "the later check that the supervisor ignores the Info, " - "and includes it unchanged in return from start_child/2 " - "and restart_child/2"]; -extra_return(suite) -> []; - +%% The start function provided to start a child may return {ok, Pid} +%% or {ok, Pid, Info}, if it returns the latter check that the +%% supervisor ignores the Info, and includes it unchanged in return +%% from start_child/2 and restart_child/2. extra_return(Config) when is_list(Config) -> process_flag(trap_exit, true), Child = {child1, {supervisor_1, start_child, [extra_return]}, @@ -333,12 +365,10 @@ extra_return(Config) when is_list(Config) -> ok. %%------------------------------------------------------------------------- -child_adm(doc)-> - ["Test API functions start_child/2, terminate_child/2, delete_child/2 " - "restart_child/2, which_children/1, count_children/1. Only correct " - "childspecs are used, handling of incorrect childspecs is tested in " - "child_specs/1"]; -child_adm(suite) -> []; +%% Test API functions start_child/2, terminate_child/2, delete_child/2 +%% restart_child/2, which_children/1, count_children/1. Only correct +%% childspecs are used, handling of incorrect childspecs is tested in +%% child_specs/1. child_adm(Config) when is_list(Config) -> process_flag(trap_exit, true), Child = {child1, {supervisor_1, start_child, []}, permanent, 1000, @@ -402,11 +432,9 @@ child_adm(Config) when is_list(Config) -> = (catch supervisor:count_children(foo)), ok. %%------------------------------------------------------------------------- -child_adm_simple(doc) -> - ["The API functions terminate_child/2, delete_child/2 " - "restart_child/2 are not valid for a simple_one_for_one supervisor " - "check that the correct error message is returned."]; -child_adm_simple(suite) -> []; +%% The API functions terminate_child/2, delete_child/2 restart_child/2 +%% are not valid for a simple_one_for_one supervisor check that the +%% correct error message is returned. child_adm_simple(Config) when is_list(Config) -> Child = {child, {supervisor_1, start_child, []}, permanent, 1000, worker, []}, @@ -454,9 +482,7 @@ child_adm_simple(Config) when is_list(Config) -> ok. %%------------------------------------------------------------------------- -child_specs(doc) -> - ["Tests child specs, invalid formats should be rejected."]; -child_specs(suite) -> []; +%% Tests child specs, invalid formats should be rejected. child_specs(Config) when is_list(Config) -> process_flag(trap_exit, true), {ok, _Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), @@ -507,9 +533,7 @@ child_specs(Config) when is_list(Config) -> ok. %%------------------------------------------------------------------------- -permanent_normal(doc) -> - ["A permanent child should always be restarted"]; -permanent_normal(suite) -> []; +%% A permanent child should always be restarted. permanent_normal(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000, @@ -529,10 +553,8 @@ permanent_normal(Config) when is_list(Config) -> [1,1,0,1] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -transient_normal(doc) -> - ["A transient child should not be restarted if it exits with " - "reason normal"]; -transient_normal(suite) -> []; +%% A transient child should not be restarted if it exits with reason +%% normal. transient_normal(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, transient, 1000, @@ -546,9 +568,7 @@ transient_normal(Config) when is_list(Config) -> [1,0,0,1] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -temporary_normal(doc) -> - ["A temporary process should never be restarted"]; -temporary_normal(suite) -> []; +%% A temporary process should never be restarted. temporary_normal(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, temporary, 1000, @@ -562,9 +582,7 @@ temporary_normal(Config) when is_list(Config) -> [0,0,0,0] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -permanent_shutdown(doc) -> - ["A permanent child should always be restarted"]; -permanent_shutdown(suite) -> []; +%% A permanent child should always be restarted. permanent_shutdown(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000, @@ -596,10 +614,8 @@ permanent_shutdown(Config) when is_list(Config) -> [1,1,0,1] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -transient_shutdown(doc) -> - ["A transient child should not be restarted if it exits with " - "reason shutdown or {shutdown,Term}"]; -transient_shutdown(suite) -> []; +%% A transient child should not be restarted if it exits with reason +%% shutdown or {shutdown,Term}. transient_shutdown(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, transient, 1000, @@ -620,9 +636,7 @@ transient_shutdown(Config) when is_list(Config) -> [1,0,0,1] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -temporary_shutdown(doc) -> - ["A temporary process should never be restarted"]; -temporary_shutdown(suite) -> []; +%% A temporary process should never be restarted. temporary_shutdown(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, temporary, 1000, @@ -643,9 +657,7 @@ temporary_shutdown(Config) when is_list(Config) -> [0,0,0,0] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -permanent_abnormal(doc) -> - ["A permanent child should always be restarted"]; -permanent_abnormal(suite) -> []; +%% A permanent child should always be restarted. permanent_abnormal(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000, @@ -664,10 +676,7 @@ permanent_abnormal(Config) when is_list(Config) -> [1,1,0,1] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -transient_abnormal(doc) -> - ["A transient child should be restarted if it exits with " - "reason abnormal"]; -transient_abnormal(suite) -> []; +%% A transient child should be restarted if it exits with reason abnormal. transient_abnormal(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, transient, 1000, @@ -686,9 +695,7 @@ transient_abnormal(Config) when is_list(Config) -> [1,1,0,1] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -temporary_abnormal(doc) -> - ["A temporary process should never be restarted"]; -temporary_abnormal(suite) -> []; +%% A temporary process should never be restarted. temporary_abnormal(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), Child1 = {child1, {supervisor_1, start_child, []}, temporary, 1000, @@ -701,11 +708,9 @@ temporary_abnormal(Config) when is_list(Config) -> [0,0,0,0] = get_child_counts(sup_test). %%------------------------------------------------------------------------- -temporary_bystander(doc) -> - ["A temporary process killed as part of a rest_for_one or one_for_all " - "restart strategy should not be restarted given its args are not " - " saved. Otherwise the supervisor hits its limit and crashes."]; -temporary_bystander(suite) -> []; +%% A temporary process killed as part of a rest_for_one or one_for_all +%% restart strategy should not be restarted given its args are not +%% saved. Otherwise the supervisor hits its limit and crashes. temporary_bystander(_Config) -> Child1 = {child1, {supervisor_1, start_child, []}, permanent, 100, worker, []}, @@ -732,9 +737,7 @@ temporary_bystander(_Config) -> [{child1, _, _, _}] = supervisor:which_children(SupPid2). %%------------------------------------------------------------------------- -one_for_one(doc) -> - ["Test the one_for_one base case."]; -one_for_one(suite) -> []; +%% Test the one_for_one base case. one_for_one(Config) when is_list(Config) -> process_flag(trap_exit, true), Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000, @@ -764,9 +767,7 @@ one_for_one(Config) when is_list(Config) -> check_exit([SupPid]). %%------------------------------------------------------------------------- -one_for_one_escalation(doc) -> - ["Test restart escalation on a one_for_one supervisor."]; -one_for_one_escalation(suite) -> []; +%% Test restart escalation on a one_for_one supervisor. one_for_one_escalation(Config) when is_list(Config) -> process_flag(trap_exit, true), @@ -786,9 +787,7 @@ one_for_one_escalation(Config) when is_list(Config) -> %%------------------------------------------------------------------------- -one_for_all(doc) -> - ["Test the one_for_all base case."]; -one_for_all(suite) -> []; +%% Test the one_for_all base case. one_for_all(Config) when is_list(Config) -> process_flag(trap_exit, true), @@ -824,9 +823,7 @@ one_for_all(Config) when is_list(Config) -> %%------------------------------------------------------------------------- -one_for_all_escalation(doc) -> - ["Test restart escalation on a one_for_all supervisor."]; -one_for_all_escalation(suite) -> []; +%% Test restart escalation on a one_for_all supervisor. one_for_all_escalation(Config) when is_list(Config) -> process_flag(trap_exit, true), @@ -845,9 +842,7 @@ one_for_all_escalation(Config) when is_list(Config) -> %%------------------------------------------------------------------------- -simple_one_for_one(doc) -> - ["Test the simple_one_for_one base case."]; -simple_one_for_one(suite) -> []; +%% Test the simple_one_for_one base case. simple_one_for_one(Config) when is_list(Config) -> process_flag(trap_exit, true), Child = {child, {supervisor_1, start_child, []}, permanent, 1000, @@ -878,10 +873,8 @@ simple_one_for_one(Config) when is_list(Config) -> %%------------------------------------------------------------------------- -simple_one_for_one_shutdown(doc) -> - ["Test simple_one_for_one children shutdown accordingly to the " - "supervisor's shutdown strategy."]; -simple_one_for_one_shutdown(suite) -> []; +%% Test simple_one_for_one children shutdown accordingly to the +%% supervisor's shutdown strategy. simple_one_for_one_shutdown(Config) when is_list(Config) -> process_flag(trap_exit, true), ShutdownTime = 1000, @@ -909,10 +902,8 @@ simple_one_for_one_shutdown(Config) when is_list(Config) -> %%------------------------------------------------------------------------- -simple_one_for_one_extra(doc) -> - ["Tests automatic restart of children " - "who's start function return extra info."]; -simple_one_for_one_extra(suite) -> []; +%% Tests automatic restart of children who's start function return +%% extra info. simple_one_for_one_extra(Config) when is_list(Config) -> process_flag(trap_exit, true), Child = {child, {supervisor_1, start_child, [extra_info]}, @@ -937,9 +928,7 @@ simple_one_for_one_extra(Config) when is_list(Config) -> check_exit([SupPid]). %%------------------------------------------------------------------------- -simple_one_for_one_escalation(doc) -> - ["Test restart escalation on a simple_one_for_one supervisor."]; -simple_one_for_one_escalation(suite) -> []; +%% Test restart escalation on a simple_one_for_one supervisor. simple_one_for_one_escalation(Config) when is_list(Config) -> process_flag(trap_exit, true), Child = {child, {supervisor_1, start_child, []}, permanent, 1000, @@ -954,9 +943,7 @@ simple_one_for_one_escalation(Config) when is_list(Config) -> check_exit([SupPid, CPid2]). %%------------------------------------------------------------------------- -rest_for_one(doc) -> - ["Test the rest_for_one base case."]; -rest_for_one(suite) -> []; +%% Test the rest_for_one base case. rest_for_one(Config) when is_list(Config) -> process_flag(trap_exit, true), Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000, @@ -1004,9 +991,7 @@ rest_for_one(Config) when is_list(Config) -> check_exit([SupPid]). %%------------------------------------------------------------------------- -rest_for_one_escalation(doc) -> - ["Test restart escalation on a rest_for_one supervisor."]; -rest_for_one_escalation(suite) -> []; +%% Test restart escalation on a rest_for_one supervisor. rest_for_one_escalation(Config) when is_list(Config) -> process_flag(trap_exit, true), Child1 = {child1, {supervisor_1, start_child, []}, permanent, 1000, @@ -1023,11 +1008,8 @@ rest_for_one_escalation(Config) when is_list(Config) -> check_exit([CPid2, SupPid]). %%------------------------------------------------------------------------- -child_unlink(doc)-> - ["Test that the supervisor does not hang forever if " - "the child unliks and then is terminated by the supervisor."]; -child_unlink(suite) -> - []; +%% Test that the supervisor does not hang forever if the child unliks +%% and then is terminated by the supervisor. child_unlink(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), @@ -1052,10 +1034,7 @@ child_unlink(Config) when is_list(Config) -> test_server:fail(supervisor_hangs) end. %%------------------------------------------------------------------------- -tree(doc) -> - ["Test a basic supervison tree."]; -tree(suite) -> - []; +%% Test a basic supervison tree. tree(Config) when is_list(Config) -> process_flag(trap_exit, true), @@ -1131,11 +1110,9 @@ tree(Config) when is_list(Config) -> [] = supervisor:which_children(NewSup2), [0,0,0,0] = get_child_counts(NewSup2). + %%------------------------------------------------------------------------- -count_children_memory(doc) -> - ["Test that count_children does not eat memory."]; -count_children_memory(suite) -> - []; +%% Test that count_children does not eat memory. count_children_memory(Config) when is_list(Config) -> process_flag(trap_exit, true), Child = {child, {supervisor_1, start_child, []}, temporary, 1000, @@ -1177,12 +1154,12 @@ count_children_memory(Config) when is_list(Config) -> case (Size5 =< Size4) of true -> ok; false -> - test_server:fail({count_children, used_more_memory}) + 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}) + test_server:fail({count_children, used_more_memory,Size6,Size7}) end, [terminate(SupPid, Pid, child, kill) || {undefined, Pid, worker, _Modules} <- Children3], @@ -1193,12 +1170,9 @@ proc_memory() -> erlang:memory(processes_used). %%------------------------------------------------------------------------- -do_not_save_start_parameters_for_temporary_children(doc) -> - ["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."]; -do_not_save_start_parameters_for_temporary_children(suite) -> - []; +%% 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. do_not_save_start_parameters_for_temporary_children(Config) when is_list(Config) -> process_flag(trap_exit, true), dont_save_start_parameters_for_temporary_children(one_for_all), @@ -1220,11 +1194,8 @@ child_spec({Name, MFA, RestartType, Shutdown, Type, Modules}, N) -> {NewName, MFA, RestartType, Shutdown, Type, Modules}. %%------------------------------------------------------------------------- -do_not_save_child_specs_for_temporary_children(doc) -> - ["Temporary children shall not be restarted so supervisors should " - "not save their spec when they terminate"]; -do_not_save_child_specs_for_temporary_children(suite) -> - []; +%% Temporary children shall not be restarted so supervisors should not +%% save their spec when they terminate. do_not_save_child_specs_for_temporary_children(Config) when is_list(Config) -> process_flag(trap_exit, true), dont_save_child_specs_for_temporary_children(one_for_all, kill), @@ -1373,13 +1344,18 @@ simple_one_for_one_scale_many_temporary_children(_Config) -> 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}); + if T1 > 0 -> + 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; true -> + %% Means T2 div T1 -> infinity ok end. diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl index 65ccdcb7a8..5bc34e35af 100644 --- a/lib/stdlib/test/tar_SUITE.erl +++ b/lib/stdlib/test/tar_SUITE.erl @@ -766,9 +766,9 @@ run_in_short_tempdir(Config, Fun) -> %% We need a base directory with a much shorter pathname than %% priv_dir. We KNOW that priv_dir is located four levels below %% the directory that common_test puts the ct_run.* directories - %% in. That fact is not documented, but an usually reliable source + %% in. That fact is not documented, but a usually reliable source %% assured me that the directory structure is unlikely to change - %% in future versions of common_test because of backward + %% in future versions of common_test because of backwards %% compatibility (tools developed by users of common_test depend %% on the current directory layout). Base = lists:foldl(fun(_, D) -> |