aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/supervisor_SUITE.erl
diff options
context:
space:
mode:
authorSiri Hansen <[email protected]>2014-06-27 15:53:18 +0200
committerSiri Hansen <[email protected]>2014-10-08 09:33:57 +0200
commitc1acfc6283d3146d6f10dfd8c4b96a330f7da19f (patch)
tree60e9e496d947d730eaf6294ac84456fe58930b01 /lib/stdlib/test/supervisor_SUITE.erl
parent610c746c0795ec9a96f960ea6461ef56d6d2ee24 (diff)
downloadotp-c1acfc6283d3146d6f10dfd8c4b96a330f7da19f.tar.gz
otp-c1acfc6283d3146d6f10dfd8c4b96a330f7da19f.tar.bz2
otp-c1acfc6283d3146d6f10dfd8c4b96a330f7da19f.zip
Add more tests of supervisor
Add tests of code_change/3 and error handling of supervisor flags.
Diffstat (limited to 'lib/stdlib/test/supervisor_SUITE.erl')
-rw-r--r--lib/stdlib/test/supervisor_SUITE.erl145
1 files changed, 140 insertions, 5 deletions
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index 836ea7c030..37ac8a18aa 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -39,7 +39,7 @@
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]).
+ child_adm_simple/1, child_specs/1, extra_return/1, sup_flags/1]).
%% Tests concept permanent, transient and temporary
-export([ permanent_normal/1, transient_normal/1,
@@ -65,7 +65,7 @@
do_not_save_child_specs_for_temporary_children/1,
simple_one_for_one_scale_many_temporary_children/1,
simple_global_supervisor/1, hanging_restart_loop/1,
- hanging_restart_loop_simple/1]).
+ hanging_restart_loop_simple/1, code_change/1, code_change_simple/1]).
%%-------------------------------------------------------------------------
@@ -74,7 +74,7 @@ suite() ->
all() ->
[{group, sup_start}, {group, sup_stop}, child_adm,
- child_adm_simple, extra_return, child_specs,
+ child_adm_simple, extra_return, child_specs, sup_flags,
{group, restart_one_for_one},
{group, restart_one_for_all},
{group, restart_simple_one_for_one},
@@ -85,7 +85,8 @@ all() ->
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].
+ simple_global_supervisor, hanging_restart_loop, hanging_restart_loop_simple,
+ code_change, code_change_simple].
groups() ->
[{sup_start, [],
@@ -479,7 +480,7 @@ child_adm_simple(Config) when is_list(Config) ->
%% 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}, []}}),
+ {ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
{error, _} = supervisor:start_child(sup_test, hej),
%% Bad child specs
@@ -509,6 +510,7 @@ child_specs(Config) when is_list(Config) ->
{error, {invalid_modules,dy}}
= supervisor:start_child(sup_test, B5),
+ {error, {badarg, _}} = supervisor:check_childspecs(B1), % should be list
{error, {invalid_mfa,mfa}} = supervisor:check_childspecs([B1]),
{error, {invalid_restart_type,prmanent}} =
supervisor:check_childspecs([B2]),
@@ -524,6 +526,40 @@ child_specs(Config) when is_list(Config) ->
ok = supervisor:check_childspecs([C3]),
ok = supervisor:check_childspecs([C4]),
ok = supervisor:check_childspecs([C5]),
+
+ {error,{duplicate_child_name,child}} = supervisor:check_childspecs([C1,C2]),
+
+ terminate(Pid, shutdown),
+
+ %% Faulty child specs in supervisor start
+ {error, {start_spec, {invalid_mfa, mfa}}} =
+ start_link({ok, {{one_for_one, 2, 3600}, [B1]}}),
+ {error, {start_spec, {invalid_restart_type, prmanent}}} =
+ start_link({ok, {{simple_one_for_one, 2, 3600}, [B2]}}),
+
+ %% simple_one_for_one needs exactly one child
+ {error,{bad_start_spec,[]}} =
+ start_link({ok, {{simple_one_for_one, 2, 3600}, []}}),
+ {error,{bad_start_spec,[C1,C2]}} =
+ start_link({ok, {{simple_one_for_one, 2, 3600}, [C1,C2]}}),
+
+ ok.
+
+%%-------------------------------------------------------------------------
+%% Test error handling of supervisor flags
+sup_flags(_Config) ->
+ process_flag(trap_exit,true),
+ {error,{supervisor_data,{invalid_strategy,_}}} =
+ start_link({ok, {{none_for_one, 2, 3600}, []}}),
+ {error,{supervisor_data,{invalid_intensity,_}}} =
+ start_link({ok, {{one_for_one, infinity, 3600}, []}}),
+ {error,{supervisor_data,{invalid_period,_}}} =
+ start_link({ok, {{one_for_one, 2, 0}, []}}),
+ {error,{supervisor_data,{invalid_period,_}}} =
+ start_link({ok, {{one_for_one, 2, infinity}, []}}),
+ {error,{supervisor_data,{invalid_type,_}}} =
+ start_link({ok, {{one_for_one, 2}, []}}),
+
ok.
%%-------------------------------------------------------------------------
@@ -1647,6 +1683,105 @@ hanging_restart_loop_simple(Config) when is_list(Config) ->
ok.
%%-------------------------------------------------------------------------
+%% Test the code_change function
+code_change(_Config) ->
+ process_flag(trap_exit, true),
+
+ SupFlags = {one_for_one, 0, 1},
+ {ok, Pid} = start_link({ok, {SupFlags, []}}),
+ [] = supervisor:which_children(Pid),
+
+ %% Change supervisor flags
+ S1 = sys:get_state(Pid),
+ ok = fake_upgrade(Pid,{ok, {{one_for_one, 1, 3}, []}}),
+ S2 = sys:get_state(Pid),
+ true = (S1 /= S2),
+
+ %% Faulty childspec
+ FaultyChild = {child1, permanent, brutal_kill, worker, []}, % missing start
+ {error,{error,{invalid_child_spec,FaultyChild}}} =
+ fake_upgrade(Pid,{ok,{SupFlags,[FaultyChild]}}),
+
+ %% Add child1 and child2
+ Child1 = {child1, {supervisor_1, start_child, []},
+ permanent, 2000, worker, []},
+ Child2 = {child2, {supervisor_1, start_child, []},
+ permanent, brutal_kill, worker, []},
+ ok = fake_upgrade(Pid,{ok,{SupFlags,[Child1,Child2]}}),
+ %% Children are not automatically started
+ {ok,_} = supervisor:restart_child(Pid,child1),
+ {ok,_} = supervisor:restart_child(Pid,child2),
+ [{child2,_,_,_},{child1,_,_,_}] = supervisor:which_children(Pid),
+
+ %% Change child1, remove child2 and add child3
+ Child11 = {child1, {supervisor_1, start_child, []},
+ permanent, 1000, worker, []},
+ Child3 = {child3, {supervisor_1, start_child, []},
+ permanent, brutal_kill, worker, []},
+ ok = fake_upgrade(Pid,{ok, {SupFlags, [Child11,Child3]}}),
+ %% Children are not deleted on upgrade, so it is ok that child2 is
+ %% still here
+ [{child2,_,_,_},{child3,_,_,_},{child1,_,_,_}] =
+ supervisor:which_children(Pid),
+
+ %% Ignore during upgrade
+ ok = fake_upgrade(Pid,ignore),
+
+ %% Error during upgrade
+ {error, faulty_return} = fake_upgrade(Pid,faulty_return),
+
+ %% Faulty flags
+ {error,{error, {invalid_intensity,faulty_intensity}}} =
+ fake_upgrade(Pid,{ok, {{one_for_one,faulty_intensity,1}, []}}),
+ {error,{error,{bad_flags, faulty_flags}}} =
+ fake_upgrade(Pid,{ok, {faulty_flags, []}}),
+
+ terminate(Pid,shutdown).
+
+code_change_simple(_Config) ->
+ process_flag(trap_exit, true),
+
+ SimpleChild1 = {child1,{supervisor_1, start_child, []}, permanent,
+ brutal_kill, worker, []},
+ SimpleFlags = {simple_one_for_one, 0, 1},
+ {ok, SimplePid} = start_link({ok, {SimpleFlags,[SimpleChild1]}}),
+ %% Change childspec
+ SimpleChild11 = {child1,{supervisor_1, start_child, []}, permanent,
+ 1000, worker, []},
+ ok = fake_upgrade(SimplePid,{ok,{SimpleFlags,[SimpleChild11]}}),
+
+ %% Attempt to add child
+ SimpleChild2 = {child2,{supervisor_1, start_child, []}, permanent,
+ brutal_kill, worker, []},
+
+ {error, {error, {ok,[_,_]}}} =
+ fake_upgrade(SimplePid,{ok,{SimpleFlags,[SimpleChild1,SimpleChild2]}}),
+
+ %% Attempt to remove child
+ {error, {error, {ok,[]}}} = fake_upgrade(SimplePid,{ok,{SimpleFlags,[]}}),
+
+ terminate(SimplePid,shutdown),
+ ok.
+
+fake_upgrade(Pid,NewInitReturn) ->
+ ok = sys:suspend(Pid),
+
+ %% Update state to fake code change
+ %% The #state record in supervisor.erl holds the arguments given
+ %% to the callback init function. By replacing these arguments the
+ %% init function will return something new and by that fake a code
+ %% change (see init function above in this module).
+ Fun = fun(State) ->
+ Size = size(State), % 'args' is the last field in #state.
+ setelement(Size,State,NewInitReturn)
+ end,
+ sys:replace_state(Pid,Fun),
+
+ R = sys:change_code(Pid,gen_server,dummy_vsn,[]),
+ ok = sys:resume(Pid),
+ R.
+
+%%-------------------------------------------------------------------------
terminate(Pid, Reason) when Reason =/= supervisor ->
terminate(dummy, Pid, dummy, Reason).