aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/dets.erl9
-rw-r--r--lib/stdlib/src/epp.erl3
-rw-r--r--lib/stdlib/src/gen.erl31
-rw-r--r--lib/stdlib/src/gen_event.erl18
-rw-r--r--lib/stdlib/src/gen_fsm.erl11
-rw-r--r--lib/stdlib/src/gen_server.erl25
-rw-r--r--lib/stdlib/src/io.erl6
-rw-r--r--lib/stdlib/src/supervisor.erl27
-rw-r--r--lib/stdlib/src/sys.erl32
9 files changed, 114 insertions, 48 deletions
diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl
index 45aef0ea80..50812cc532 100644
--- a/lib/stdlib/src/dets.erl
+++ b/lib/stdlib/src/dets.erl
@@ -1246,13 +1246,8 @@ req(Proc, R) ->
{'DOWN', Ref, process, Proc, _Info} ->
badarg;
{Proc, Reply} ->
- erlang:demonitor(Ref),
- receive
- {'DOWN', Ref, process, Proc, _Reason} ->
- Reply
- after 0 ->
- Reply
- end
+ erlang:demonitor(Ref, [flush]),
+ Reply
end.
%% Inlined.
diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index 0a1caa7178..e31cd63f69 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -1339,8 +1339,7 @@ epp_reply(From, Rep) ->
wait_epp_reply(Epp, Mref) ->
receive
{epp_reply,Epp,Rep} ->
- erlang:demonitor(Mref),
- receive {'DOWN',Mref,_,_,_} -> ok after 0 -> ok end,
+ erlang:demonitor(Mref, [flush]),
Rep;
{'DOWN',Mref,_,_,E} ->
receive {epp_reply,Epp,Rep} -> Rep
diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl
index 42555aedd7..5df5530ba1 100644
--- a/lib/stdlib/src/gen.erl
+++ b/lib/stdlib/src/gen.erl
@@ -17,6 +17,7 @@
%% %CopyrightEnd%
%%
-module(gen).
+-compile({inline,[get_node/1]}).
%%%-----------------------------------------------------------------
%%% This module implements the really generic stuff of the generic
@@ -194,16 +195,6 @@ call({_Name, Node}=Process, Label, Request, Timeout)
end.
do_call(Process, Label, Request, Timeout) ->
- %% We trust the arguments to be correct, i.e
- %% Process is either a local or remote pid,
- %% or a {Name, Node} tuple (of atoms) and in this
- %% case this node (node()) _is_ distributed and Node =/= node().
- Node = case Process of
- {_S, N} when is_atom(N) ->
- N;
- _ when is_pid(Process) ->
- node(Process)
- end,
try erlang:monitor(process, Process) of
Mref ->
%% If the monitor/2 call failed to set up a connection to a
@@ -222,15 +213,12 @@ do_call(Process, Label, Request, Timeout) ->
erlang:demonitor(Mref, [flush]),
{ok, Reply};
{'DOWN', Mref, _, _, noconnection} ->
+ Node = get_node(Process),
exit({nodedown, Node});
{'DOWN', Mref, _, _, Reason} ->
exit(Reason)
after Timeout ->
- erlang:demonitor(Mref),
- receive
- {'DOWN', Mref, _, _, _} -> true
- after 0 -> true
- end,
+ erlang:demonitor(Mref, [flush]),
exit(timeout)
end
catch
@@ -241,6 +229,7 @@ do_call(Process, Label, Request, Timeout) ->
%% Do the best possible with monitor_node/2.
%% This code may hang indefinitely if the Process
%% does not exist. It is only used for featureweak remote nodes.
+ Node = get_node(Process),
monitor_node(Node, true),
receive
{nodedown, Node} ->
@@ -253,6 +242,18 @@ do_call(Process, Label, Request, Timeout) ->
end
end.
+get_node(Process) ->
+ %% We trust the arguments to be correct, i.e
+ %% Process is either a local or remote pid,
+ %% or a {Name, Node} tuple (of atoms) and in this
+ %% case this node (node()) _is_ distributed and Node =/= node().
+ case Process of
+ {_S, N} when is_atom(N) ->
+ N;
+ _ when is_pid(Process) ->
+ node(Process)
+ end.
+
wait_resp(Node, Tag, Timeout) ->
receive
{Tag, Reply} ->
diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl
index 2b8ba86909..bfebf29080 100644
--- a/lib/stdlib/src/gen_event.erl
+++ b/lib/stdlib/src/gen_event.erl
@@ -229,6 +229,24 @@ wake_hib(Parent, ServerName, MSL, Debug) ->
fetch_msg(Parent, ServerName, MSL, Debug, Hib) ->
receive
+ {system, From, get_state} ->
+ States = [{Mod,Id,State} || #handler{module=Mod, id=Id, state=State} <- MSL],
+ sys:handle_system_msg(get_state, From, Parent, ?MODULE, Debug,
+ {States, [ServerName, MSL, Hib]}, Hib);
+ {system, From, {replace_state, StateFun}} ->
+ {NMSL, NStates} =
+ lists:unzip([begin
+ Cur = {Mod,Id,State},
+ try
+ NState = {Mod,Id,NS} = StateFun(Cur),
+ {HS#handler{state=NS}, NState}
+ catch
+ _:_ ->
+ {HS, Cur}
+ end
+ end || #handler{module=Mod, id=Id, state=State}=HS <- MSL]),
+ sys:handle_system_msg(replace_state, From, Parent, ?MODULE, Debug,
+ {NStates, [ServerName, NMSL, Hib]}, Hib);
{system, From, Req} ->
sys:handle_system_msg(Req, From, Parent, ?MODULE, Debug,
[ServerName, MSL, Hib],Hib);
diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl
index e480e2ac11..d9411e58cf 100644
--- a/lib/stdlib/src/gen_fsm.erl
+++ b/lib/stdlib/src/gen_fsm.erl
@@ -422,6 +422,17 @@ wake_hib(Parent, Name, StateName, StateData, Mod, Debug) ->
decode_msg(Msg,Parent, Name, StateName, StateData, Mod, Time, Debug, Hib) ->
case Msg of
+ {system, From, get_state} ->
+ Misc = [Name, StateName, StateData, Mod, Time],
+ sys:handle_system_msg(get_state, From, Parent, ?MODULE, Debug,
+ {{StateName, StateData}, Misc}, Hib);
+ {system, From, {replace_state, StateFun}} ->
+ State = {StateName, StateData},
+ NState = {NStateName, NStateData} = try StateFun(State)
+ catch _:_ -> State end,
+ NMisc = [Name, NStateName, NStateData, Mod, Time],
+ sys:handle_system_msg(replace_state, From, Parent, ?MODULE, Debug,
+ {NState, NMisc}, Hib);
{system, From, Req} ->
sys:handle_system_msg(Req, From, Parent, ?MODULE, Debug,
[Name, StateName, StateData, Mod, Time], Hib);
diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl
index 04308a51b7..30a81ade49 100644
--- a/lib/stdlib/src/gen_server.erl
+++ b/lib/stdlib/src/gen_server.erl
@@ -372,6 +372,13 @@ wake_hib(Parent, Name, State, Mod, Debug) ->
decode_msg(Msg, Parent, Name, State, Mod, Time, Debug, Hib) ->
case Msg of
+ {system, From, get_state} ->
+ sys:handle_system_msg(get_state, From, Parent, ?MODULE, Debug,
+ {State, [Name, State, Mod, Time]}, Hib);
+ {system, From, {replace_state, StateFun}} ->
+ NState = try StateFun(State) catch _:_ -> State end,
+ sys:handle_system_msg(replace_state, From, Parent, ?MODULE, Debug,
+ {NState, [Name, NState, Mod, Time]}, Hib);
{system, From, Req} ->
sys:handle_system_msg(Req, From, Parent, ?MODULE, Debug,
[Name, State, Mod, Time], Hib);
@@ -465,11 +472,11 @@ rec_nodes(Tag, [{N,R}|Tail], Name, Badnodes, Replies, Time, TimerId ) ->
{'DOWN', R, _, _, _} ->
rec_nodes(Tag, Tail, Name, [N|Badnodes], Replies, Time, TimerId);
{{Tag, N}, Reply} -> %% Tag is bound !!!
- unmonitor(R),
+ erlang:demonitor(R, [flush]),
rec_nodes(Tag, Tail, Name, Badnodes,
[{N,Reply}|Replies], Time, TimerId);
{timeout, TimerId, _} ->
- unmonitor(R),
+ erlang:demonitor(R, [flush]),
%% Collect all replies that already have arrived
rec_nodes_rest(Tag, Tail, Name, [N|Badnodes], Replies)
end;
@@ -520,10 +527,10 @@ rec_nodes_rest(Tag, [{N,R}|Tail], Name, Badnodes, Replies) ->
{'DOWN', R, _, _, _} ->
rec_nodes_rest(Tag, Tail, Name, [N|Badnodes], Replies);
{{Tag, N}, Reply} -> %% Tag is bound !!!
- unmonitor(R),
+ erlang:demonitor(R, [flush]),
rec_nodes_rest(Tag, Tail, Name, Badnodes, [{N,Reply}|Replies])
after 0 ->
- unmonitor(R),
+ erlang:demonitor(R, [flush]),
rec_nodes_rest(Tag, Tail, Name, [N|Badnodes], Replies)
end;
rec_nodes_rest(Tag, [N|Tail], Name, Badnodes, Replies) ->
@@ -565,16 +572,6 @@ start_monitor(Node, Name) when is_atom(Node), is_atom(Name) ->
end
end.
-%% Cancels a monitor started with Ref=erlang:monitor(_, _).
-unmonitor(Ref) when is_reference(Ref) ->
- erlang:demonitor(Ref),
- receive
- {'DOWN', Ref, _, _, _} ->
- true
- after 0 ->
- true
- end.
-
%%% ---------------------------------------------------
%%% Message handling functions
%%% ---------------------------------------------------
diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl
index c92e9e3ade..53728237ca 100644
--- a/lib/stdlib/src/io.erl
+++ b/lib/stdlib/src/io.erl
@@ -598,11 +598,7 @@ default_output() ->
wait_io_mon_reply(From, Mref) ->
receive
{io_reply, From, Reply} ->
- erlang:demonitor(Mref),
- receive
- {'DOWN', Mref, _, _, _} -> true
- after 0 -> true
- end,
+ erlang:demonitor(Mref, [flush]),
Reply;
{'EXIT', From, _What} ->
receive
diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index 9f93747c3e..54328cd9ff 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -63,7 +63,9 @@
%%--------------------------------------------------------------------------
-record(child, {% pid is undefined when child is not running
- pid = undefined :: child() | {restarting,pid()} | [pid()],
+ pid = undefined :: child()
+ | {restarting, pid() | undefined}
+ | [pid()],
name :: child_id(),
mfargs :: mfargs(),
restart_type :: restart(),
@@ -752,6 +754,9 @@ restart(Child, State) ->
end,
timer:apply_after(0,?MODULE,try_again_restart,[self(),Id]),
{ok,NState2};
+ {try_again, NState2, #child{name=ChName}} ->
+ timer:apply_after(0,?MODULE,try_again_restart,[self(),ChName]),
+ {ok,NState2};
Other ->
Other
end;
@@ -798,10 +803,16 @@ restart(rest_for_one, Child, State) ->
case start_children(ChAfter2, State#state.name) of
{ok, ChAfter3} ->
{ok, State#state{children = ChAfter3 ++ ChBefore}};
- {error, ChAfter3, _Reason} ->
+ {error, ChAfter3, {failed_to_start_child, ChName, _Reason}}
+ when ChName =:= Child#child.name ->
NChild = Child#child{pid=restarting(Child#child.pid)},
NState = State#state{children = ChAfter3 ++ ChBefore},
- {try_again, replace_child(NChild,NState)}
+ {try_again, replace_child(NChild,NState)};
+ {error, ChAfter3, {failed_to_start_child, ChName, _Reason}} ->
+ NChild = lists:keyfind(ChName, #child.name, ChAfter3),
+ NChild2 = NChild#child{pid=?restarting(undefined)},
+ NState = State#state{children = ChAfter3 ++ ChBefore},
+ {try_again, replace_child(NChild2,NState), NChild2}
end;
restart(one_for_all, Child, State) ->
Children1 = del_child(Child#child.pid, State#state.children),
@@ -809,10 +820,16 @@ restart(one_for_all, Child, State) ->
case start_children(Children2, State#state.name) of
{ok, NChs} ->
{ok, State#state{children = NChs}};
- {error, NChs, _Reason} ->
+ {error, NChs, {failed_to_start_child, ChName, _Reason}}
+ when ChName =:= Child#child.name ->
NChild = Child#child{pid=restarting(Child#child.pid)},
NState = State#state{children = NChs},
- {try_again, replace_child(NChild,NState)}
+ {try_again, replace_child(NChild,NState)};
+ {error, NChs, {failed_to_start_child, ChName, _Reason}} ->
+ NChild = lists:keyfind(ChName, #child.name, NChs),
+ NChild2 = NChild#child{pid=?restarting(undefined)},
+ NState = State#state{children = NChs},
+ {try_again, replace_child(NChild2,NState), NChild2}
end.
restarting(Pid) when is_pid(Pid) -> ?restarting(Pid);
diff --git a/lib/stdlib/src/sys.erl b/lib/stdlib/src/sys.erl
index 2d6287814e..bffeb44179 100644
--- a/lib/stdlib/src/sys.erl
+++ b/lib/stdlib/src/sys.erl
@@ -21,6 +21,8 @@
%% External exports
-export([suspend/1, suspend/2, resume/1, resume/2,
get_status/1, get_status/2,
+ get_state/1, get_state/2,
+ replace_state/2, replace_state/3,
change_code/4, change_code/5,
log/2, log/3, trace/2, trace/3, statistics/2, statistics/3,
log_to_file/2, log_to_file/3, no_debug/1, no_debug/2,
@@ -97,6 +99,32 @@ get_status(Name) -> send_system_msg(Name, get_status).
| (Misc :: term()).
get_status(Name, Timeout) -> send_system_msg(Name, get_status, Timeout).
+-spec get_state(Name) -> State when
+ Name :: name(),
+ State :: term().
+get_state(Name) -> send_system_msg(Name, get_state).
+
+-spec get_state(Name, Timeout) -> State when
+ Name :: name(),
+ Timeout :: timeout(),
+ State :: term().
+get_state(Name, Timeout) -> send_system_msg(Name, get_state, Timeout).
+
+-spec replace_state(Name, StateFun) -> NewState when
+ Name :: name(),
+ StateFun :: fun((State :: term()) -> NewState :: term()),
+ NewState :: term().
+replace_state(Name, StateFun) ->
+ send_system_msg(Name, {replace_state, StateFun}).
+
+-spec replace_state(Name, StateFun, Timeout) -> NewState when
+ Name :: name(),
+ StateFun :: fun((State :: term()) -> NewState :: term()),
+ Timeout :: timeout(),
+ NewState :: term().
+replace_state(Name, StateFun, Timeout) ->
+ send_system_msg(Name, {replace_state, StateFun}, Timeout).
+
-spec change_code(Name, Module, OldVsn, Extra) -> 'ok' | {error, Reason} when
Name :: name(),
Module :: module(),
@@ -362,6 +390,10 @@ do_cmd(_, suspend, _Parent, _Mod, Debug, Misc) ->
{suspended, ok, Debug, Misc};
do_cmd(_, resume, _Parent, _Mod, Debug, Misc) ->
{running, ok, Debug, Misc};
+do_cmd(SysState, get_state, _Parent, _Mod, Debug, {State, Misc}) ->
+ {SysState, State, Debug, Misc};
+do_cmd(SysState, replace_state, _Parent, _Mod, Debug, {State, Misc}) ->
+ {SysState, State, Debug, Misc};
do_cmd(SysState, get_status, Parent, Mod, Debug, Misc) ->
Res = get_status(SysState, Parent, Mod, Debug, Misc),
{SysState, Res, Debug, Misc};