diff options
Diffstat (limited to 'lib/stdlib/src')
| -rw-r--r-- | lib/stdlib/src/ms_transform.erl | 17 | ||||
| -rw-r--r-- | lib/stdlib/src/random.erl | 42 | ||||
| -rw-r--r-- | lib/stdlib/src/supervisor.erl | 123 | 
3 files changed, 150 insertions, 32 deletions
| diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl index 48e22e53fa..63b397f3a5 100644 --- a/lib/stdlib/src/ms_transform.erl +++ b/lib/stdlib/src/ms_transform.erl @@ -333,17 +333,18 @@ form({function,Line,Name0,Arity0,Clauses0}) ->  form(AnyOther) ->      AnyOther.  function(Name, Arity, Clauses0) -> -    {Clauses1,_} = clauses(Clauses0,gb_sets:new()), +    Clauses1 = clauses(Clauses0),      {Name,Arity,Clauses1}. -clauses([C0|Cs],Bound) -> -    {C1,Bound1} = clause(C0,Bound), -    {C2,Bound2} = clauses(Cs,Bound1), -    {[C1|C2],Bound2}; -clauses([],Bound) -> {[],Bound}. +clauses([C0|Cs]) -> +    C1 = clause(C0,gb_sets:new()), +    C2 = clauses(Cs), +    [C1|C2]; +clauses([]) -> []. +  clause({clause,Line,H0,G0,B0},Bound) ->      {H1,Bound1} = copy(H0,Bound), -    {B1,Bound2} = copy(B0,Bound1), -    {{clause,Line,H1,G0,B1},Bound2}. +    {B1,_Bound2} = copy(B0,Bound1), +    {clause,Line,H1,G0,B1}.  copy({call,Line,{remote,_Line2,{atom,_Line3,ets},{atom,_Line4,fun2ms}},        As0},Bound) -> diff --git a/lib/stdlib/src/random.erl b/lib/stdlib/src/random.erl index dbb524cc74..d7b51a151c 100644 --- a/lib/stdlib/src/random.erl +++ b/lib/stdlib/src/random.erl @@ -26,6 +26,10 @@  -export([seed/0, seed/1, seed/3, uniform/0, uniform/1,  	 uniform_s/1, uniform_s/2, seed0/0]). +-define(PRIME1, 30269). +-define(PRIME2, 30307). +-define(PRIME3, 30323). +  %%-----------------------------------------------------------------------  %% The type of the state @@ -44,7 +48,11 @@ seed0() ->  -spec seed() -> ran().  seed() -> -    reseed(seed0()). +    case seed_put(seed0()) of +	undefined -> seed0(); +	{_,_,_} = Tuple -> Tuple +    end.	 +  %% seed({A1, A2, A3})   %%  Seed random number generation  @@ -66,17 +74,15 @@ seed({A1, A2, A3}) ->        A3 :: integer().  seed(A1, A2, A3) -> -    put(random_seed,  -	{abs(A1) rem 30269, abs(A2) rem 30307, abs(A3) rem 30323}). +    seed_put({(abs(A1) rem (?PRIME1-1)) + 1,   % Avoid seed numbers that are +	      (abs(A2) rem (?PRIME2-1)) + 1,   % even divisors of the +	      (abs(A3) rem (?PRIME3-1)) + 1}). % corresponding primes. --spec reseed(ran()) -> ran(). - -reseed({A1, A2, A3}) -> -    case seed(A1, A2, A3) of -	undefined -> seed0(); -	{_,_,_} = Tuple -> Tuple -    end.	 +-spec seed_put(ran()) -> 'undefined' | ran(). +      +seed_put(Seed) -> +    put(random_seed, Seed).  %% uniform()  %%  Returns a random float between 0 and 1. @@ -88,11 +94,11 @@ uniform() ->  		       undefined -> seed0();  		       Tuple -> Tuple  		   end, -    B1 = (A1*171) rem 30269, -    B2 = (A2*172) rem 30307, -    B3 = (A3*170) rem 30323, +    B1 = (A1*171) rem ?PRIME1, +    B2 = (A2*172) rem ?PRIME2, +    B3 = (A3*170) rem ?PRIME3,      put(random_seed, {B1,B2,B3}), -    R = A1/30269 + A2/30307 + A3/30323, +    R = B1/?PRIME1 + B2/?PRIME2 + B3/?PRIME3,      R - trunc(R).  %% uniform(N) -> I @@ -116,10 +122,10 @@ uniform(N) when is_integer(N), N >= 1 ->        State1 :: ran().  uniform_s({A1, A2, A3}) -> -    B1 = (A1*171) rem 30269, -    B2 = (A2*172) rem 30307, -    B3 = (A3*170) rem 30323, -    R = A1/30269 + A2/30307 + A3/30323, +    B1 = (A1*171) rem ?PRIME1, +    B2 = (A2*172) rem ?PRIME2, +    B3 = (A3*170) rem ?PRIME3, +    R = B1/?PRIME1 + B2/?PRIME2 + B3/?PRIME3,      {R - trunc(R), {B1,B2,B3}}.  %% uniform_s(N, State) -> {I, NewState} diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl index 9da0d52f8c..f20ea18fd0 100644 --- a/lib/stdlib/src/supervisor.erl +++ b/lib/stdlib/src/supervisor.erl @@ -515,9 +515,12 @@ handle_info(Msg, State) ->  %%  -spec terminate(term(), state()) -> 'ok'. +terminate(_Reason, #state{children=[Child]} = State) when ?is_simple(State) -> +    terminate_dynamic_children(Child, dynamics_db(Child#child.restart_type, +                                                  State#state.dynamics), +                               State#state.name);  terminate(_Reason, State) -> -    terminate_children(State#state.children, State#state.name), -    ok. +    terminate_children(State#state.children, State#state.name).  %%  %% Change code for the supervisor. @@ -830,8 +833,109 @@ monitor_child(Pid) ->  	    %% that will be handled in shutdown/2.   	    ok         end. -     -    + + +%%----------------------------------------------------------------- +%% Func: terminate_dynamic_children/3 +%% Args: Child    = child_rec() +%%       Dynamics = ?DICT() | ?SET() +%%       SupName  = {local, atom()} | {global, atom()} | {pid(),Mod} +%% Returns: ok +%% +%% +%% Shutdown all dynamic children. This happens when the supervisor is +%% stopped. Because the supervisor can have millions of dynamic children, we +%% can have an significative overhead here. +%%----------------------------------------------------------------- +terminate_dynamic_children(Child, Dynamics, SupName) -> +    {Pids, EStack0} = monitor_dynamic_children(Child, Dynamics), +    Sz = ?SETS:size(Pids), +    EStack = case Child#child.shutdown of +                 brutal_kill -> +                     ?SETS:fold(fun(P, _) -> exit(P, kill) end, ok, Pids), +                     wait_dynamic_children(Child, Pids, Sz, undefined, EStack0); +                 infinity -> +                     ?SETS:fold(fun(P, _) -> exit(P, shutdown) end, ok, Pids), +                     wait_dynamic_children(Child, Pids, Sz, undefined, EStack0); +                 Time -> +                     ?SETS:fold(fun(P, _) -> exit(P, shutdown) end, ok, Pids), +                     TRef = erlang:start_timer(Time, self(), kill), +                     wait_dynamic_children(Child, Pids, Sz, TRef, EStack0) +             end, +    %% Unrool stacked errors and report them +    ?DICT:fold(fun(Reason, Ls, _) -> +                       report_error(shutdown_error, Reason, +                                    Child#child{pid=Ls}, SupName) +               end, ok, EStack). + + +monitor_dynamic_children(#child{restart_type=temporary}, Dynamics) -> +    ?SETS:fold(fun(P, {Pids, EStack}) -> +                       case monitor_child(P) of +                           ok -> +                               {?SETS:add_element(P, Pids), EStack}; +                           {error, normal} -> +                               {Pids, EStack}; +                           {error, Reason} -> +                               {Pids, ?DICT:append(Reason, P, EStack)} +                       end +               end, {?SETS:new(), ?DICT:new()}, Dynamics); +monitor_dynamic_children(#child{restart_type=RType}, Dynamics) -> +    ?DICT:fold(fun(P, _, {Pids, EStack}) -> +                       case monitor_child(P) of +                           ok -> +                               {?SETS:add_element(P, Pids), EStack}; +                           {error, normal} when RType =/= permanent -> +                               {Pids, EStack}; +                           {error, Reason} -> +                               {Pids, ?DICT:append(Reason, P, EStack)} +                       end +               end, {?SETS:new(), ?DICT:new()}, Dynamics). + + +wait_dynamic_children(_Child, _Pids, 0, undefined, EStack) -> +    EStack; +wait_dynamic_children(_Child, _Pids, 0, TRef, EStack) -> +	%% If the timer has expired before its cancellation, we must empty the +	%% mail-box of the 'timeout'-message. +    erlang:cancel_timer(TRef), +    receive +        {timeout, TRef, kill} -> +            EStack +    after 0 -> +            EStack +    end; +wait_dynamic_children(#child{shutdown=brutal_kill} = Child, Pids, Sz, +                      TRef, EStack) -> +    receive +        {'DOWN', _MRef, process, Pid, killed} -> +            wait_dynamic_children(Child, ?SETS:del_element(Pid, Pids), Sz-1, +                                  TRef, EStack); + +        {'DOWN', _MRef, process, Pid, Reason} -> +            wait_dynamic_children(Child, ?SETS:del_element(Pid, Pids), Sz-1, +                                  TRef, ?DICT:append(Reason, Pid, EStack)) +    end; +wait_dynamic_children(#child{restart_type=RType} = Child, Pids, Sz, +                      TRef, EStack) -> +    receive +        {'DOWN', _MRef, process, Pid, shutdown} -> +            wait_dynamic_children(Child, ?SETS:del_element(Pid, Pids), Sz-1, +                                  TRef, EStack); + +        {'DOWN', _MRef, process, Pid, normal} when RType =/= permanent -> +            wait_dynamic_children(Child, ?SETS:del_element(Pid, Pids), Sz-1, +                                  TRef, EStack); + +        {'DOWN', _MRef, process, Pid, Reason} -> +            wait_dynamic_children(Child, ?SETS:del_element(Pid, Pids), Sz-1, +                                  TRef, ?DICT:append(Reason, Pid, EStack)); + +        {timeout, TRef, kill} -> +            ?SETS:fold(fun(P, _) -> exit(P, kill) end, ok, Pids), +            wait_dynamic_children(Child, Pids, Sz-1, undefined, EStack) +    end. +  %%-----------------------------------------------------------------  %% Child/State manipulating functions.  %%----------------------------------------------------------------- @@ -1053,7 +1157,7 @@ validRestartType(RestartType) -> throw({invalid_restart_type, RestartType}).  validShutdown(Shutdown, _)     when is_integer(Shutdown), Shutdown > 0 -> true; -validShutdown(infinity, supervisor)    -> true; +validShutdown(infinity, _)             -> true;  validShutdown(brutal_kill, _)          -> true;  validShutdown(Shutdown, _)             -> throw({invalid_shutdown, Shutdown}). @@ -1134,12 +1238,19 @@ report_error(Error, Reason, Child, SupName) ->      error_logger:error_report(supervisor_report, ErrorMsg). -extract_child(Child) -> +extract_child(Child) when is_pid(Child#child.pid) ->      [{pid, Child#child.pid},       {name, 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) -> +    [{nb_children, length(Child#child.pid)}, +     {name, Child#child.name}, +     {mfargs, Child#child.mfargs}, +     {restart_type, Child#child.restart_type}, +     {shutdown, Child#child.shutdown},       {child_type, Child#child.child_type}].  report_progress(Child, SupName) -> | 
