Skip to content

Commit

Permalink
erts: Async auto-connect for monitor/2
Browse files Browse the repository at this point in the history
  • Loading branch information
sverker committed Nov 15, 2017
1 parent 3f5f226 commit 17e198d
Show file tree
Hide file tree
Showing 2 changed files with 10 additions and 34 deletions.
23 changes: 6 additions & 17 deletions erts/emulator/beam/bif.c
Expand Up @@ -790,31 +790,20 @@ remote_monitor(Process *p, Eterm bifarg1, Eterm bifarg2,
BIF_RETTYPE ret;
int code;

ASSERT(dep);
erts_proc_lock(p, ERTS_PROC_LOCK_LINK);
code = erts_dsig_prepare(&dsd, &dep,
p, (ERTS_PROC_LOCK_MAIN | ERTS_PROC_LOCK_LINK),
ERTS_DSP_RLOCK, 0, 0);
ERTS_DSP_RLOCK, 0, 1);
switch (code) {
case ERTS_DSIG_PREP_PENDING:
/*
* Must wait for connection to know if node supports monitor.
* Damn these synchronous errors.
*/
erts_smp_de_runlock(dep);
/* fall through */
case ERTS_DSIG_PREP_NOT_ALIVE:
case ERTS_DSIG_PREP_NOT_CONNECTED:
erts_proc_unlock(p, ERTS_PROC_LOCK_LINK);
ERTS_BIF_PREP_TRAP2(ret, dmonitor_p_trap, p, bifarg1, bifarg2);
break;
case ERTS_DSIG_PREP_PENDING:
case ERTS_DSIG_PREP_CONNECTED:
if (!(dep->flags & DFLAG_DIST_MONITOR)
|| (byname && !(dep->flags & DFLAG_DIST_MONITOR_NAME))) {
erts_de_runlock(dep);
erts_proc_unlock(p, ERTS_PROC_LOCK_LINK);
ERTS_BIF_PREP_ERROR(ret, p, BADARG);
}
else {
{
Eterm p_trgt, p_name, d_name, mon_ref;

mon_ref = erts_make_ref(p);
Expand Down Expand Up @@ -917,17 +906,17 @@ BIF_RETTYPE monitor_2(BIF_ALIST_2)
if (!erts_is_alive && remote_node != am_Noname) {
goto badarg; /* Remote monitor from (this) undistributed node */
}
dep = erts_sysname_to_connected_dist_entry(remote_node);
dep = erts_find_or_insert_dist_entry(remote_node);
if (dep == erts_this_dist_entry) {
ret = local_name_monitor(BIF_P, BIF_ARG_1, name);
} else {
ret = remote_monitor(BIF_P, BIF_ARG_1, BIF_ARG_2, dep, name, 1);
}
erts_deref_dist_entry(dep);
} else {
badarg:
ERTS_BIF_PREP_ERROR(ret, BIF_P, BADARG);
}

return ret;
}

Expand Down
21 changes: 4 additions & 17 deletions erts/preloaded/src/erlang.erl
Expand Up @@ -3367,23 +3367,10 @@ dsend({Name, Node}, Msg, Opts) ->

-spec erlang:dmonitor_p('process', pid() | {atom(),atom()}) -> reference().
dmonitor_p(process, ProcSpec) ->
%% ProcSpec = pid() | {atom(),atom()}
%% ProcSpec CANNOT be an atom because a locally registered process
%% is never handled here.
Node = case ProcSpec of
{S,N} when erlang:is_atom(S),
erlang:is_atom(N),
N =/= erlang:node() -> N;
_ when erlang:is_pid(ProcSpec) -> erlang:node(ProcSpec)
end,
case net_kernel:connect(Node) of
true ->
erlang:monitor(process, ProcSpec);
false ->
Ref = erlang:make_ref(),
erlang:self() ! {'DOWN', Ref, process, ProcSpec, noconnection},
Ref
end.
%% Only called when auto-connect attempt failed early in VM
Ref = erlang:make_ref(),
erlang:self() ! {'DOWN', Ref, process, ProcSpec, noconnection},
Ref.

%%
%% Trap function used when modified timing has been enabled.
Expand Down

0 comments on commit 17e198d

Please sign in to comment.