diff options
Diffstat (limited to 'lib/stdlib/src/supervisor.erl')
-rw-r--r-- | lib/stdlib/src/supervisor.erl | 177 |
1 files changed, 124 insertions, 53 deletions
diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl index ede2742875..658c00dc77 100644 --- a/lib/stdlib/src/supervisor.erl +++ b/lib/stdlib/src/supervisor.erl @@ -25,7 +25,7 @@ start_child/2, restart_child/2, delete_child/2, terminate_child/2, which_children/1, count_children/1, - check_childspecs/1]). + check_childspecs/1, get_childspec/2]). %% Internal exports -export([init/1, handle_call/3, handle_cast/2, handle_info/2, @@ -34,7 +34,7 @@ %%-------------------------------------------------------------------------- --export_type([child_spec/0, startchild_ret/0, strategy/0]). +-export_type([sup_flags/0, child_spec/0, startchild_ret/0, strategy/0]). %%-------------------------------------------------------------------------- @@ -53,7 +53,13 @@ | {'global', Name :: atom()} | {'via', Module :: module(), Name :: any()} | pid(). --type child_spec() :: {Id :: child_id(), +-type child_spec() :: #{id => child_id(), % mandatory + start => mfargs(), % mandatory + restart => restart(), % optional + shutdown => shutdown(), % optional + type => worker(), % optional + modules => modules()} % optional + | {Id :: child_id(), StartFunc :: mfargs(), Restart :: restart(), Shutdown :: shutdown(), @@ -63,6 +69,23 @@ -type strategy() :: 'one_for_all' | 'one_for_one' | 'rest_for_one' | 'simple_one_for_one'. +-type sup_flags() :: #{strategy => strategy(), % optional + intensity => non_neg_integer(), % optional + period => pos_integer()} % optional + | {RestartStrategy :: strategy(), + Intensity :: non_neg_integer(), + Period :: pos_integer()}. + +%%-------------------------------------------------------------------------- +%% Defaults +-define(default_flags, #{strategy => one_for_one, + intensity => 1, + period => 5}). +-define(default_child_spec, #{restart => permanent, + type => worker}). +%% Default 'shutdown' is 5000 for workers and infinity for supervisors. +%% Default 'modules' is [M], where M comes from the child's start {M,F,A}. + %%-------------------------------------------------------------------------- -record(child, {% pid is undefined when child is not running @@ -96,10 +119,7 @@ -define(is_simple(State), State#state.strategy =:= simple_one_for_one). -callback init(Args :: term()) -> - {ok, {{RestartStrategy :: strategy(), - MaxR :: non_neg_integer(), - MaxT :: non_neg_integer()}, - [ChildSpec :: child_spec()]}} + {ok, {SupFlags :: sup_flags(), [ChildSpec :: child_spec()]}} | ignore. -define(restarting(_Pid_), {restarting,_Pid_}). @@ -178,6 +198,14 @@ delete_child(Supervisor, Name) -> terminate_child(Supervisor, Name) -> call(Supervisor, {terminate_child, Name}). +-spec get_childspec(SupRef, Id) -> Result when + SupRef :: sup_ref(), + Id :: pid() | child_id(), + Result :: {'ok', child_spec()} | {'error', Error}, + Error :: 'not_found'. +get_childspec(Supervisor, Name) -> + call(Supervisor, {get_childspec, Name}). + -spec which_children(SupRef) -> [{Id,Child,Type,Modules}] when SupRef :: sup_ref(), Id :: child_id() | undefined, @@ -431,6 +459,14 @@ handle_call({delete_child, Name}, _From, State) -> {reply, {error, not_found}, State} end; +handle_call({get_childspec, Name}, _From, State) -> + case get_child(Name, State, ?is_simple(State)) of + {value, Child} -> + {reply, {ok, child_to_spec(Child)}, State}; + false -> + {reply, {error, not_found}, State} + end; + handle_call(which_children, _From, #state{children = [#child{restart_type = temporary, child_type = CT, modules = Mods}]} = @@ -610,13 +646,11 @@ terminate(_Reason, State) -> code_change(_, State, _) -> case (State#state.module):init(State#state.args) of {ok, {SupFlags, StartSpec}} -> - case catch check_flags(SupFlags) of - ok -> - {Strategy, MaxIntensity, Period} = SupFlags, - update_childspec(State#state{strategy = Strategy, - intensity = MaxIntensity, - period = Period}, - StartSpec); + case set_flags(SupFlags, State) of + {ok, State1} -> + update_childspec(State1, StartSpec); + {invalid_type, SupFlags} -> + {error, {bad_flags, SupFlags}}; % backwards compatibility Error -> {error, Error} end; @@ -626,14 +660,6 @@ code_change(_, State, _) -> Error end. -check_flags({Strategy, MaxIntensity, Period}) -> - validStrategy(Strategy), - validIntensity(MaxIntensity), - validPeriod(Period), - ok; -check_flags(What) -> - {bad_flags, What}. - update_childspec(State, StartSpec) when ?is_simple(State) -> case check_startspec(StartSpec) of {ok, [Child]} -> @@ -1188,25 +1214,36 @@ remove_child(Child, State) -> %% Returns: {ok, state()} | Error %%----------------------------------------------------------------- init_state(SupName, Type, Mod, Args) -> - case catch init_state1(SupName, Type, Mod, Args) of - {ok, State} -> - {ok, State}; - Error -> - Error + set_flags(Type, #state{name = supname(SupName,Mod), + module = Mod, + args = Args}). + +set_flags(Flags, State) -> + try check_flags(Flags) of + #{strategy := Strategy, intensity := MaxIntensity, period := Period} -> + {ok, State#state{strategy = Strategy, + intensity = MaxIntensity, + period = Period}} + catch + Thrown -> Thrown end. -init_state1(SupName, {Strategy, MaxIntensity, Period}, Mod, Args) -> +check_flags(SupFlags) when is_map(SupFlags) -> + do_check_flags(maps:merge(?default_flags,SupFlags)); +check_flags({Strategy, MaxIntensity, Period}) -> + check_flags(#{strategy => Strategy, + intensity => MaxIntensity, + period => Period}); +check_flags(What) -> + throw({invalid_type, What}). + +do_check_flags(#{strategy := Strategy, + intensity := MaxIntensity, + period := Period} = Flags) -> validStrategy(Strategy), validIntensity(MaxIntensity), validPeriod(Period), - {ok, #state{name = supname(SupName,Mod), - strategy = Strategy, - intensity = MaxIntensity, - period = Period, - module = Mod, - args = Args}}; -init_state1(_SupName, Type, _, _) -> - {invalid_type, Type}. + Flags. validStrategy(simple_one_for_one) -> true; validStrategy(one_for_one) -> true; @@ -1227,14 +1264,7 @@ supname(N, _) -> N. %%% ------------------------------------------------------ %%% Check that the children start specification is valid. -%%% Shall be a six (6) tuple -%%% {Name, Func, RestartType, Shutdown, ChildType, Modules} -%%% where Name is an atom -%%% Func is {Mod, Fun, Args} == {atom(), atom(), list()} -%%% RestartType is permanent | temporary | transient -%%% Shutdown = integer() > 0 | infinity | brutal_kill -%%% ChildType = supervisor | worker -%%% Modules = [atom()] | dynamic +%%% Input: [child_spec()] %%% Returns: {ok, [child_rec()]} | Error %%% ------------------------------------------------------ @@ -1244,6 +1274,9 @@ check_startspec([ChildSpec|T], Res) -> case check_childspec(ChildSpec) of {ok, Child} -> case lists:keymember(Child#child.name, #child.name, Res) of + %% The error message duplicate_child_name is kept for + %% backwards compatibility, although + %% duplicate_child_id would be more correct. true -> {duplicate_child_name, Child#child.name}; false -> check_startspec(T, [Child | Res]) end; @@ -1252,16 +1285,41 @@ check_startspec([ChildSpec|T], Res) -> check_startspec([], Res) -> {ok, lists:reverse(Res)}. +check_childspec(ChildSpec) when is_map(ChildSpec) -> + catch do_check_childspec(maps:merge(?default_child_spec,ChildSpec)); check_childspec({Name, Func, RestartType, Shutdown, ChildType, Mods}) -> - catch check_childspec(Name, Func, RestartType, Shutdown, ChildType, Mods); + check_childspec(#{id => Name, + start => Func, + restart => RestartType, + shutdown => Shutdown, + type => ChildType, + modules => Mods}); check_childspec(X) -> {invalid_child_spec, X}. -check_childspec(Name, Func, RestartType, Shutdown, ChildType, Mods) -> +do_check_childspec(#{restart := RestartType, + type := ChildType} = ChildSpec)-> + Name = case ChildSpec of + #{id := N} -> N; + _ -> throw(missing_id) + end, + Func = case ChildSpec of + #{start := F} -> F; + _ -> throw(missing_start) + end, validName(Name), validFunc(Func), validRestartType(RestartType), validChildType(ChildType), - validShutdown(Shutdown, ChildType), + Shutdown = case ChildSpec of + #{shutdown := S} -> S; + #{type := worker} -> 5000; + #{type := supervisor} -> infinity + end, + validShutdown(Shutdown), + Mods = case ChildSpec of + #{modules := Ms} -> Ms; + _ -> {M,_,_} = Func, [M] + end, validMods(Mods), {ok, #child{name = Name, mfargs = Func, restart_type = RestartType, shutdown = Shutdown, child_type = ChildType, modules = Mods}}. @@ -1282,11 +1340,11 @@ validRestartType(temporary) -> true; validRestartType(transient) -> true; validRestartType(RestartType) -> throw({invalid_restart_type, RestartType}). -validShutdown(Shutdown, _) +validShutdown(Shutdown) when is_integer(Shutdown), Shutdown > 0 -> true; -validShutdown(infinity, _) -> true; -validShutdown(brutal_kill, _) -> true; -validShutdown(Shutdown, _) -> throw({invalid_shutdown, Shutdown}). +validShutdown(infinity) -> true; +validShutdown(brutal_kill) -> true; +validShutdown(Shutdown) -> throw({invalid_shutdown, Shutdown}). validMods(dynamic) -> true; validMods(Mods) when is_list(Mods) -> @@ -1299,6 +1357,19 @@ validMods(Mods) when is_list(Mods) -> Mods); validMods(Mods) -> throw({invalid_modules, Mods}). +child_to_spec(#child{name = Name, + mfargs = Func, + restart_type = RestartType, + shutdown = Shutdown, + child_type = ChildType, + modules = Mods}) -> + #{id => Name, + start => Func, + restart => RestartType, + shutdown => Shutdown, + type => ChildType, + modules => Mods}. + %%% ------------------------------------------------------ %%% Add a new restart and calculate if the max restart %%% intensity has been reached (in that case the supervisor @@ -1367,14 +1438,14 @@ report_error(Error, Reason, Child, SupName) -> extract_child(Child) when is_list(Child#child.pid) -> [{nb_children, length(Child#child.pid)}, - {name, Child#child.name}, + {id, Child#child.name}, {mfargs, Child#child.mfargs}, {restart_type, Child#child.restart_type}, {shutdown, Child#child.shutdown}, {child_type, Child#child.child_type}]; extract_child(Child) -> [{pid, Child#child.pid}, - {name, Child#child.name}, + {id, Child#child.name}, {mfargs, Child#child.mfargs}, {restart_type, Child#child.restart_type}, {shutdown, Child#child.shutdown}, |