aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/supervisor_SUITE.erl
diff options
context:
space:
mode:
authorBjörn Gustavsson <[email protected]>2015-04-22 13:04:30 +0200
committerBjörn Gustavsson <[email protected]>2015-04-22 14:11:44 +0200
commit47e7f00fe52ceb675c94a4800c297ce98d6bee30 (patch)
tree603f83634f2b1f04c4c249ea536796372c968cb6 /lib/stdlib/test/supervisor_SUITE.erl
parent5201e1852b034a6566828e1ba267c2afaa017933 (diff)
downloadotp-47e7f00fe52ceb675c94a4800c297ce98d6bee30.tar.gz
otp-47e7f00fe52ceb675c94a4800c297ce98d6bee30.tar.bz2
otp-47e7f00fe52ceb675c94a4800c297ce98d6bee30.zip
supervisor: Correct restart handling
fbaa0bec replaced the use of now/0 with erlang:monotonic_time/1 but at the same time introduced a bug in inPeriod/3 so that it would always return 'true' (the subtraction Time - Now would always result in a non-positive number that would always be less than Period). The symptoms of the bug is that when a child has been restarted the maximum number of times allowed, the supervisor will terminate, regardless of how much time that elapses between the restarts. There was no test case that detected this problem. Add the missing test case to ensure that this bug stays killed. Reported-by: Rafał Studnicki
Diffstat (limited to 'lib/stdlib/test/supervisor_SUITE.erl')
-rw-r--r--lib/stdlib/test/supervisor_SUITE.erl37
1 files changed, 36 insertions, 1 deletions
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index c98654aef7..9dcf19707c 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -53,7 +53,8 @@
temporary_abnormal/1, temporary_bystander/1]).
%% Restart strategy tests
--export([ one_for_one/1,
+-export([ multiple_restarts/1,
+ one_for_one/1,
one_for_one_escalation/1, one_for_all/1,
one_for_all_escalation/1, one_for_all_other_child_fails_restart/1,
simple_one_for_one/1, simple_one_for_one_escalation/1,
@@ -78,6 +79,7 @@ suite() ->
all() ->
[{group, sup_start}, {group, sup_start_map}, {group, sup_stop}, child_adm,
child_adm_simple, extra_return, child_specs, sup_flags,
+ multiple_restarts,
{group, restart_one_for_one},
{group, restart_one_for_all},
{group, restart_simple_one_for_one},
@@ -873,6 +875,39 @@ temporary_bystander(_Config) ->
[{child1, _, _, _}] = supervisor:which_children(SupPid2).
%%-------------------------------------------------------------------------
+%% Test restarting a process multiple times, being careful not
+%% to exceed the maximum restart frquency.
+multiple_restarts(Config) when is_list(Config) ->
+ process_flag(trap_exit, true),
+ Child1 = #{id => child1,
+ start => {supervisor_1, start_child, []},
+ restart => permanent,
+ shutdown => brutal_kill,
+ type => worker,
+ modules => []},
+ SupFlags = #{strategy => one_for_one,
+ intensity => 1,
+ period => 1},
+ {ok, SupPid} = start_link({ok, {SupFlags, []}}),
+ {ok, CPid1} = supervisor:start_child(sup_test, Child1),
+
+ %% Terminate the process several times, but being careful
+ %% not to exceed the maximum restart intensity.
+ terminate(SupPid, CPid1, child1, abnormal),
+ _ = [begin
+ receive after 2100 -> ok end,
+ [{_, Pid, _, _}|_] = supervisor:which_children(sup_test),
+ terminate(SupPid, Pid, child1, abnormal)
+ end || _ <- [1,2,3]],
+
+ %% Verify that the supervisor is still alive and clean up.
+ ok = supervisor:terminate_child(SupPid, child1),
+ ok = supervisor:delete_child(SupPid, child1),
+ exit(SupPid, kill),
+ ok.
+
+
+%%-------------------------------------------------------------------------
%% Test the one_for_one base case.
one_for_one(Config) when is_list(Config) ->
process_flag(trap_exit, true),