summaryrefslogtreecommitdiff
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.erl59
1 files changed, 37 insertions, 22 deletions
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index 78d7e7d7bc..a9cf48e997 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2021. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2023. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -200,7 +200,7 @@ start_link(InitResult) ->
%% Simulate different supervisors callback.
init(fail) ->
- erlang:error({badmatch,2});
+ erlang:error(fail);
init(InitResult) ->
InitResult.
@@ -227,7 +227,7 @@ sup_start_normal(Config) when is_list(Config) ->
sup_start_ignore_init(Config) when is_list(Config) ->
process_flag(trap_exit, true),
ignore = start_link(ignore),
- check_exit_reason(normal).
+ check_no_exit(100).
%%-------------------------------------------------------------------------
%% Tests what happens if init-callback returns ignore.
@@ -325,15 +325,20 @@ sup_start_ignore_permanent_child_start_child_simple(Config)
%% 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).
+ %% The bad return is processed in supervisor:init/1
+ InitResult = invalid,
+ {error, {bad_return, {?MODULE, init, InitResult}}} =
+ start_link(InitResult),
+ check_no_exit(100).
%%-------------------------------------------------------------------------
%% 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).
+ %% The exception is processed in gen_server:init_it/2
+ ErrorReason = fail,
+ {error, {ErrorReason, _Stacktrace}} = start_link(ErrorReason),
+ check_no_exit(100).
%%-------------------------------------------------------------------------
%% Test what happens when the start function for a child returns
@@ -706,11 +711,15 @@ child_adm(Config) when is_list(Config) ->
process_flag(trap_exit, true),
Child = {child1, {supervisor_1, start_child, []}, permanent, 1000,
worker, []},
- {ok, _Pid} = start_link({ok, {{one_for_one, 2, 3600}, [Child]}}),
+ {ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, [Child]}}),
+
+ %% Test that supervisors of static nature are hibernated after start
+ {current_function, {erlang, hibernate, 3}} =
+ process_info(Pid, current_function),
+
[{child1, CPid, worker, []}] = supervisor:which_children(sup_test),
[1,1,0,1] = get_child_counts(sup_test),
link(CPid),
-
%% Start of an already runnig process
{error,{already_started, CPid}} =
supervisor:start_child(sup_test, Child),
@@ -771,7 +780,13 @@ child_adm(Config) when is_list(Config) ->
child_adm_simple(Config) when is_list(Config) ->
Child = {child, {supervisor_1, start_child, []}, permanent, 1000,
worker, []},
- {ok, _Pid} = start_link({ok, {{simple_one_for_one, 2, 3600}, [Child]}}),
+ {ok, Pid} = start_link({ok, {{simple_one_for_one, 2, 3600}, [Child]}}),
+
+ %% Test that supervisors of dynamic nature are not hibernated after start
+ {current_function, {_, Function, _}} =
+ process_info(Pid, current_function),
+ true = Function =/= hibernate,
+
%% In simple_one_for_one all children are added dynamically
[] = supervisor:which_children(sup_test),
[1,0,0,0] = get_child_counts(sup_test),
@@ -2618,7 +2633,7 @@ order_of_children(_Config) ->
[{ok,[_]} = dbg:p(P,procs) || P <- Expected1],
terminate(Pid3, abnormal),
receive {exited,ExitedPids1} ->
- dbg:stop_clear(),
+ dbg:stop(),
case ExitedPids1 of
Expected1 -> ok;
_ -> ct:fail({faulty_termination_order,
@@ -2626,7 +2641,7 @@ order_of_children(_Config) ->
{got,ExitedPids1}})
end
after 3000 ->
- dbg:stop_clear(),
+ dbg:stop(),
ct:fail({shutdown_fail,timeout})
end,
@@ -2647,7 +2662,7 @@ order_of_children(_Config) ->
[{ok,[_]} = dbg:p(P,procs) || P <- Expected2],
exit(SupPid,shutdown),
receive {exited,ExitedPids2} ->
- dbg:stop_clear(),
+ dbg:stop(),
case ExitedPids2 of
Expected2 -> ok;
_ -> ct:fail({faulty_termination_order,
@@ -2655,7 +2670,7 @@ order_of_children(_Config) ->
{got,ExitedPids2}})
end
after 3000 ->
- dbg:stop_clear(),
+ dbg:stop(),
ct:fail({shutdown_fail,timeout})
end,
ok.
@@ -3739,18 +3754,18 @@ check_exit([Pid | Pids], Timeout) ->
error
end.
-check_exit_reason(Reason) ->
+check_exit_reason(Pid, Reason) when is_pid(Pid) ->
receive
- {'EXIT', _, Reason} ->
+ {'EXIT', Pid, Reason} ->
ok;
- {'EXIT', _, Else} ->
+ {'EXIT', Pid, Else} ->
ct:fail({bad_exit_reason, Else})
end.
-check_exit_reason(Pid, Reason) ->
+check_no_exit(Timeout) ->
receive
- {'EXIT', Pid, Reason} ->
- ok;
- {'EXIT', Pid, Else} ->
- ct:fail({bad_exit_reason, Else})
+ {'EXIT', Pid, _} = Exit when is_pid(Pid) ->
+ ct:fail({unexpected_message, Exit})
+ after Timeout ->
+ ok
end.