aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test/supervisor_SUITE.erl
diff options
context:
space:
mode:
authorHans Bolinder <[email protected]>2011-11-14 13:49:35 +0100
committerHans Bolinder <[email protected]>2011-11-14 14:10:58 +0100
commit4db61fcf79516ff9cd6fd04c89376f063ccae7e8 (patch)
tree77ad0bbadc2096664d649f7896fe9a0882b39192 /lib/stdlib/test/supervisor_SUITE.erl
parentfeb6c1dece891c7cb46c24bbdf9082c758c7830e (diff)
downloadotp-4db61fcf79516ff9cd6fd04c89376f063ccae7e8.tar.gz
otp-4db61fcf79516ff9cd6fd04c89376f063ccae7e8.tar.bz2
otp-4db61fcf79516ff9cd6fd04c89376f063ccae7e8.zip
Remove all use of global:safe_whereis_name/1
Calls to global:whereis_name/1 have been substituted for calls to global:safe_whereis_name/1 since the latter is not safe at all. The reason for not doing this earlier is that setting a global lock masked out a bug concerning the restart of supervised children. The bug has now been fixed by a modification of global:whereis_name/1. (Thanks to Ulf Wiger for code contribution.)
Diffstat (limited to 'lib/stdlib/test/supervisor_SUITE.erl')
-rw-r--r--lib/stdlib/test/supervisor_SUITE.erl95
1 files changed, 92 insertions, 3 deletions
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index da6996cc9f..d3d140abbc 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -29,7 +29,8 @@
end_per_testcase/2]).
%% Internal export
--export([init/1, terminate_all_children/1]).
+-export([init/1, terminate_all_children/1,
+ middle9212/0, gen_server9212/0, handle_info/2]).
%% API tests
-export([ sup_start_normal/1, sup_start_ignore_init/1,
@@ -58,7 +59,8 @@
-export([child_unlink/1, tree/1, count_children_memory/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]).
+ simple_one_for_one_scale_many_temporary_children/1,
+ simple_global_supervisor/1]).
%%-------------------------------------------------------------------------
@@ -77,7 +79,8 @@ all() ->
{group, abnormal_termination}, child_unlink, tree,
count_children_memory, 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_one_for_one_scale_many_temporary_children, temporary_bystander,
+ simple_global_supervisor].
groups() ->
[{sup_start, [],
@@ -1388,6 +1391,92 @@ terminate_all_children([]) ->
done.
+%%-------------------------------------------------------------------------
+%% OTP-9212. Restart of global supervisor.
+simple_global_supervisor(_Config) ->
+ kill_supervisor(),
+ kill_worker(),
+ exit_worker(),
+ restart_worker(),
+ ok.
+
+kill_supervisor() ->
+ {Top, Sup2_1, Server_1} = start9212(),
+
+ %% Killing a supervisor isn't really supported, but try it anyway...
+ exit(Sup2_1, kill),
+ timer:sleep(200),
+ Sup2_2 = global:whereis_name(sup2),
+ Server_2 = global:whereis_name(server),
+ true = is_pid(Sup2_2),
+ true = is_pid(Server_2),
+ true = Sup2_1 =/= Sup2_2,
+ true = Server_1 =/= Server_2,
+
+ stop9212(Top).
+
+handle_info({fail, With, After}, _State) ->
+ timer:sleep(After),
+ erlang:error(With).
+
+kill_worker() ->
+ {Top, _Sup2, Server_1} = start9212(),
+ exit(Server_1, kill),
+ timer:sleep(200),
+ Server_2 = global:whereis_name(server),
+ true = is_pid(Server_2),
+ true = Server_1 =/= Server_2,
+ stop9212(Top).
+
+exit_worker() ->
+ %% Very much the same as kill_worker().
+ {Top, _Sup2, Server_1} = start9212(),
+ Server_1 ! {fail, normal, 0},
+ timer:sleep(200),
+ Server_2 = global:whereis_name(server),
+ true = is_pid(Server_2),
+ true = Server_1 =/= Server_2,
+ stop9212(Top).
+
+restart_worker() ->
+ {Top, _Sup2, Server_1} = start9212(),
+ ok = supervisor:terminate_child({global, sup2}, child),
+ {ok, _Child} = supervisor:restart_child({global, sup2}, child),
+ Server_2 = global:whereis_name(server),
+ true = is_pid(Server_2),
+ true = Server_1 =/= Server_2,
+ stop9212(Top).
+
+start9212() ->
+ Middle = {middle,{?MODULE,middle9212,[]}, permanent,2000,supervisor,[]},
+ InitResult = {ok, {{one_for_all,3,60}, [Middle]}},
+ {ok, TopPid} = start_link(InitResult),
+
+ Sup2 = global:whereis_name(sup2),
+ Server = global:whereis_name(server),
+ true = is_pid(Sup2),
+ true = is_pid(Server),
+ {TopPid, Sup2, Server}.
+
+stop9212(Top) ->
+ Old = process_flag(trap_exit, true),
+ exit(Top, kill),
+ timer:sleep(200),
+ undefined = global:whereis_name(sup2),
+ undefined = global:whereis_name(server),
+ check_exit([Top]),
+ _ = process_flag(trap_exit, Old),
+ ok.
+
+middle9212() ->
+ Child = {child, {?MODULE,gen_server9212,[]},permanent, 2000, worker, []},
+ InitResult = {ok, {{one_for_all,3,60}, [Child]}},
+ supervisor:start_link({global,sup2}, ?MODULE, InitResult).
+
+gen_server9212() ->
+ InitResult = {ok, []},
+ gen_server:start_link({global,server}, ?MODULE, InitResult, []).
+
%%-------------------------------------------------------------------------
terminate(Pid, Reason) when Reason =/= supervisor ->