aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/supervisor_SUITE.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test/supervisor_SUITE.erl')
-rw-r--r--lib/stdlib/test/supervisor_SUITE.erl171
1 files changed, 83 insertions, 88 deletions
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index 4ee323ee62..988e98aca4 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -20,33 +20,35 @@
-module(supervisor_SUITE).
--include("test_server.hrl").
+-include_lib("test_server/include/test_server.hrl").
%% Testserver specific export
--export([all/1]).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2, init_per_testcase/2,
+ end_per_testcase/2]).
%% Indirect spawn export
-export([init/1]).
%% API tests
--export([sup_start/1, sup_start_normal/1, sup_start_ignore_init/1,
+-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/1, sup_stop_infinity/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]).
%% Tests concept permanent, transient and temporary
--export([normal_termination/1, permanent_normal/1, transient_normal/1,
- temporary_normal/1, abnormal_termination/1,
+-export([ permanent_normal/1, transient_normal/1,
+ temporary_normal/1,
permanent_abnormal/1, transient_abnormal/1,
temporary_abnormal/1]).
%% Restart strategy tests
--export([restart_one_for_one/1, one_for_one/1,
- one_for_one_escalation/1, restart_one_for_all/1, one_for_all/1,
- one_for_all_escalation/1, restart_simple_one_for_one/1,
+-export([ one_for_one/1,
+ one_for_one_escalation/1, one_for_all/1,
+ one_for_all_escalation/1,
simple_one_for_one/1, simple_one_for_one_escalation/1,
- restart_rest_for_one/1, rest_for_one/1, rest_for_one_escalation/1,
+ rest_for_one/1, rest_for_one_escalation/1,
simple_one_for_one_extra/1]).
%% Misc tests
@@ -55,15 +57,67 @@
%-------------------------------------------------------------------------
-all(suite) ->
- {req,[stdlib],
- [sup_start, sup_stop, child_adm,
- child_adm_simple, extra_return, child_specs,
- restart_one_for_one, restart_one_for_all,
- restart_simple_one_for_one, restart_rest_for_one,
- normal_termination, abnormal_termination, child_unlink, tree,
- count_children_memory, do_not_save_start_parameters_for_temporary_children]}.
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [{group, sup_start}, {group, sup_stop}, child_adm,
+ child_adm_simple, extra_return, child_specs,
+ {group, restart_one_for_one},
+ {group, restart_one_for_all},
+ {group, restart_simple_one_for_one},
+ {group, restart_rest_for_one},
+ {group, normal_termination},
+ {group, abnormal_termination}, child_unlink, tree,
+ count_children_memory, do_not_save_start_parameters_for_temporary_children].
+
+groups() ->
+ [{sup_start, [],
+ [sup_start_normal, sup_start_ignore_init,
+ sup_start_ignore_child, sup_start_error_return,
+ sup_start_fail]},
+ {sup_stop, [],
+ [sup_stop_infinity, sup_stop_timeout,
+ sup_stop_brutal_kill]},
+ {normal_termination, [],
+ [permanent_normal, transient_normal, temporary_normal]},
+ {abnormal_termination, [],
+ [permanent_abnormal, transient_abnormal,
+ temporary_abnormal]},
+ {restart_one_for_one, [],
+ [one_for_one, one_for_one_escalation]},
+ {restart_one_for_all, [],
+ [one_for_all, one_for_all_escalation]},
+ {restart_simple_one_for_one, [],
+ [simple_one_for_one, simple_one_for_one_extra,
+ simple_one_for_one_escalation]},
+ {restart_rest_for_one, [],
+ [rest_for_one, rest_for_one_escalation]}].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+init_per_testcase(count_children_memory, Config) ->
+ MemoryState = erlang:system_info(allocator),
+ case count_children_allocator_test(MemoryState) of
+ true -> Config;
+ false ->
+ {skip, "+Meamin used during test; erlang:memory/1 not available"}
+ end;
+init_per_testcase(_Case, Config) ->
+ Config.
+
+end_per_testcase(_Case, _Config) ->
+ ok.
start(InitResult) ->
supervisor:start_link({local, sup_test}, ?MODULE, InitResult).
@@ -82,19 +136,8 @@ get_child_counts(Supervisor) ->
proplists:get_value(supervisors, Counts),
proplists:get_value(workers, Counts)].
-
%-------------------------------------------------------------------------
-%
% Test cases starts here.
-%
-%-------------------------------------------------------------------------
-
-sup_start(doc) ->
- ["Test start of a supervisor."];
-sup_start(suite) ->
- [sup_start_normal, sup_start_ignore_init, sup_start_ignore_child,
- sup_start_error_return, sup_start_fail].
-
%-------------------------------------------------------------------------
sup_start_normal(doc) ->
["Tests that the supervisor process starts correctly and that it "
@@ -193,12 +236,6 @@ sup_start_fail(Config) when is_list(Config) ->
end,
ok.
%-------------------------------------------------------------------------
-sup_stop(doc) ->
- ["Tests that the supervisor shoutdowns its children if it is "
- "shutdown itself."];
-sup_stop(suite) -> [sup_stop_infinity, sup_stop_timeout, sup_stop_brutal_kill].
-
-%-------------------------------------------------------------------------
sup_stop_infinity(doc) ->
["See sup_stop/1 when Shutdown = infinity, this walue is only allowed "
@@ -550,11 +587,6 @@ child_specs(Config) when is_list(Config) ->
?line ok = supervisor:check_childspecs([C3]),
?line ok = supervisor:check_childspecs([C4]),
ok.
-%-------------------------------------------------------------------------
-normal_termination(doc) ->
- ["Testes the supervisors behaviour if a child dies with reason normal"];
-normal_termination(suite) ->
- [permanent_normal, transient_normal, temporary_normal].
%-------------------------------------------------------------------------
permanent_normal(doc) ->
@@ -616,11 +648,6 @@ temporary_normal(Config) when is_list(Config) ->
?line [1,0,0,1] = get_child_counts(sup_test),
ok.
-%-------------------------------------------------------------------------
-abnormal_termination(doc) ->
- ["Testes the supervisors behaviour if a child dies with reason abnormal"];
-abnormal_termination(suite) ->
- [permanent_abnormal, transient_abnormal, temporary_abnormal].
%-------------------------------------------------------------------------
permanent_abnormal(doc) ->
@@ -689,12 +716,6 @@ temporary_abnormal(Config) when is_list(Config) ->
ok.
%-------------------------------------------------------------------------
-restart_one_for_one(doc) ->
- ["Test that the one_for_one strategy works."];
-
-restart_one_for_one(suite) -> [one_for_one, one_for_one_escalation].
-
-%-------------------------------------------------------------------------
one_for_one(doc) ->
["Test the one_for_one base case."];
one_for_one(suite) -> [];
@@ -773,13 +794,6 @@ one_for_one_escalation(Config) when is_list(Config) ->
end,
ok.
%-------------------------------------------------------------------------
-restart_one_for_all(doc) ->
- ["Test that the one_for_all strategy works."];
-
-restart_one_for_all(suite) ->
- [one_for_all, one_for_all_escalation].
-
-%-------------------------------------------------------------------------
one_for_all(doc) ->
["Test the one_for_all base case."];
one_for_all(suite) -> [];
@@ -867,14 +881,6 @@ one_for_all_escalation(Config) when is_list(Config) ->
ok.
%-------------------------------------------------------------------------
-restart_simple_one_for_one(doc) ->
- ["Test that the simple_one_for_one strategy works."];
-
-restart_simple_one_for_one(suite) ->
- [simple_one_for_one, simple_one_for_one_extra,
- simple_one_for_one_escalation].
-
-%-------------------------------------------------------------------------
simple_one_for_one(doc) ->
["Test the simple_one_for_one base case."];
simple_one_for_one(suite) -> [];
@@ -991,11 +997,6 @@ simple_one_for_one_escalation(Config) when is_list(Config) ->
end,
ok.
%-------------------------------------------------------------------------
-restart_rest_for_one(doc) ->
- ["Test that the rest_for_one strategy works."];
-restart_rest_for_one(suite) -> [rest_for_one, rest_for_one_escalation].
-
-%-------------------------------------------------------------------------
rest_for_one(doc) ->
["Test the rest_for_one base case."];
rest_for_one(suite) -> [];
@@ -1268,26 +1269,10 @@ tree(Config) when is_list(Config) ->
ok.
%-------------------------------------------------------------------------
-count_children_allocator_test(MemoryState) ->
- Allocators = [temp_alloc, eheap_alloc, binary_alloc, ets_alloc,
- driver_alloc, sl_alloc, ll_alloc, fix_alloc, std_alloc,
- sys_alloc],
- MemoryStateList = element(4, MemoryState),
- AllocTypes = [lists:keyfind(Alloc, 1, MemoryStateList)
- || Alloc <- Allocators],
- AllocStates = [lists:keyfind(e, 1, AllocValue)
- || {_Type, AllocValue} <- AllocTypes],
- lists:all(fun(State) -> State == {e, true} end, AllocStates).
-
count_children_memory(doc) ->
["Test that count_children does not eat memory."];
count_children_memory(suite) ->
- MemoryState = erlang:system_info(allocator),
- case count_children_allocator_test(MemoryState) of
- true -> [];
- false ->
- {skip, "+Meamin used during test; erlang:memory/1 not available"}
- end;
+ [];
count_children_memory(Config) when is_list(Config) ->
process_flag(trap_exit, true),
Child = {child, {supervisor_1, start_child, []}, temporary, 1000,
@@ -1341,6 +1326,16 @@ count_children_memory(Config) when is_list(Config) ->
test_server:sleep(100),
?line [1,0,0,0] = get_child_counts(sup_test),
ok.
+count_children_allocator_test(MemoryState) ->
+ Allocators = [temp_alloc, eheap_alloc, binary_alloc, ets_alloc,
+ driver_alloc, sl_alloc, ll_alloc, fix_alloc, std_alloc,
+ sys_alloc],
+ MemoryStateList = element(4, MemoryState),
+ AllocTypes = [lists:keyfind(Alloc, 1, MemoryStateList)
+ || Alloc <- Allocators],
+ AllocStates = [lists:keyfind(e, 1, AllocValue)
+ || {_Type, AllocValue} <- AllocTypes],
+ lists:all(fun(State) -> State == {e, true} end, AllocStates).
%-------------------------------------------------------------------------
do_not_save_start_parameters_for_temporary_children(doc) ->
["Temporary children shall not be restarted so they should not"