Skip to content

Commit

Permalink
[erts] Introduce erl_drv_command_error()
Browse files Browse the repository at this point in the history
  • Loading branch information
rickard-green committed Feb 14, 2023
1 parent d4e7154 commit b79ce55
Show file tree
Hide file tree
Showing 14 changed files with 390 additions and 12 deletions.
33 changes: 33 additions & 0 deletions erts/doc/src/erl_driver.xml
Original file line number Diff line number Diff line change
Expand Up @@ -2049,6 +2049,39 @@ r = driver_async(myPort, &myKey, myData, myFunc); ]]></code>
</desc>
</func>

<func>
<name since="OTP @OTP-18464@"><ret>int</ret>
<nametext>erl_drv_command_error(ErlDrvPort port,
char *error_reason)</nametext></name>
<fsummary>Generate an error exception in a port_command() call</fsummary>
<desc>
<p>
Generate an <c>error</c> exception, with the reason
<c>error_reason</c> as an atom, in a call to the
<seemfa marker="erlang#port_command/2">
<c>erlang:port_command/2</c></seemfa> BIF or the
<seemfa marker="erlang#port_command/3">
<c>erlang:port_command/3</c></seemfa> BIF. The error can only be
generated from the drivers <seecref marker="driver_entry#outputv">
<c>outputv()</c></seecref> or <seecref marker="driver_entry#output">
<c>output()</c></seecref> callbacks, which implements port command,
when the port command has been initiated via one of the synchronous
<c>port_command()</c> BIFs. When the port command has been
initiated by the asynchronous <c>Port ! {Owner, {command, Data}}</c>
construct, this call will fail and <em>no</em> exception will be
generated.
</p>
<p>
<c>error_reason</c> needs to be a null terminated latin1 string. If
the string is longer than 255 characters (excluding the null
termination character), it will be truncated to 255 characters.
</p>
<p>
Returns zero on success and a non-zero integer on failure.
</p>
</desc>
</func>

<func>
<name since=""><ret>void</ret><nametext>erl_drv_cond_broadcast(ErlDrvCond
*cnd)</nametext></name>
Expand Down
14 changes: 14 additions & 0 deletions erts/doc/src/erlang.xml
Original file line number Diff line number Diff line change
Expand Up @@ -5655,7 +5655,16 @@ receive_replies(ReqId, N, Acc) ->
<item>
<p>If <c><anno>Data</anno></c> is an invalid I/O list.</p>
</item>
<tag><c>Error</c></tag>
<item>
<p>Where <c>Error</c> is an atom defined by the driver code
executed by the port.</p>
</item>
</taglist>
<p>Note that the <c><anno>Port</anno> ! {PortOwner, {command, Data}}</c>
construct <em>only</em> can fail with a <c>badarg</c> <c>error</c>
exception if <c>Port</c> is an atom which is not registered as a port
or a process.</p>
<warning>
<p>Do not send data to an unknown port. Any undefined behavior is
possible (including node crash) depending on how the port driver
Expand Down Expand Up @@ -5719,6 +5728,11 @@ receive_replies(ReqId, N, Acc) ->
driver of the port does not allow forcing through
a busy port.
</item>
<tag><c>Error</c></tag>
<item>
<p>Where <c>Error</c> is an atom defined by the driver code
executed by the port.</p>
</item>
</taglist>
<warning>
<p>Do not send data to an unknown port. Any undefined behavior is
Expand Down
17 changes: 15 additions & 2 deletions erts/emulator/beam/erl_bif_port.c
Original file line number Diff line number Diff line change
Expand Up @@ -197,6 +197,8 @@ BIF_RETTYPE erts_internal_port_command_3(BIF_ALIST_3)
#ifdef DEBUG
ref = NIL;
#endif
ASSERT(prt->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);
prt->cmd_error = ERTS_PORT_CMD_ERROR_ALLOWED;

switch (erts_port_output(BIF_P, flags, prt, prt->common.id,
BIF_ARG_2, &ref)) {
Expand All @@ -209,6 +211,7 @@ BIF_RETTYPE erts_internal_port_command_3(BIF_ALIST_3)
if (flags & ERTS_PORT_SIG_FLG_NOSUSPEND)
ERTS_BIF_PREP_RET(res, am_false);
else {
prt->cmd_error = ERTS_PORT_CMD_ERROR_NOT_ALLOWED;
erts_suspend(BIF_P, ERTS_PROC_LOCK_MAIN, prt);
ERTS_BIF_YIELD3(BIF_TRAP_EXPORT(BIF_erts_internal_port_command_3),
BIF_P, BIF_ARG_1, BIF_ARG_2, BIF_ARG_3);
Expand All @@ -218,19 +221,29 @@ BIF_RETTYPE erts_internal_port_command_3(BIF_ALIST_3)
ASSERT(!(flags & ERTS_PORT_SIG_FLG_FORCE));
/* Fall through... */
case ERTS_PORT_OP_SCHEDULED:
prt->cmd_error = ERTS_PORT_CMD_ERROR_NOT_ALLOWED;
ASSERT(is_internal_ordinary_ref(ref));
/* Signal order preserved by reply... */
BIF_RET(ref);
break;
case ERTS_PORT_OP_DONE:
ERTS_BIF_PREP_RET(res, am_true);
case ERTS_PORT_OP_DONE: {
Eterm result = am_true;
if (prt->cmd_error != ERTS_PORT_CMD_ERROR_ALLOWED) {
Eterm *hp = HAlloc(BIF_P, 3);
ASSERT(is_atom(prt->cmd_error));
result = TUPLE2(hp, am_error, prt->cmd_error);
}
ERTS_BIF_PREP_RET(res, result);
break;
}
default:
ERTS_INTERNAL_ERROR("Unexpected erts_port_output() result");
break;
}
}

prt->cmd_error = ERTS_PORT_CMD_ERROR_NOT_ALLOWED;

state = erts_atomic32_read_acqb(&BIF_P->state);
if (state & ERTS_PSFLG_EXITING) {
KILL_CATCHES(BIF_P); /* Must exit */
Expand Down
5 changes: 4 additions & 1 deletion erts/emulator/beam/erl_driver.h
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@

#define ERL_DRV_EXTENDED_MARKER (0xfeeeeeed)
#define ERL_DRV_EXTENDED_MAJOR_VERSION 3
#define ERL_DRV_EXTENDED_MINOR_VERSION 3
#define ERL_DRV_EXTENDED_MINOR_VERSION 4

/*
* The emulator will refuse to load a driver with a major version
Expand Down Expand Up @@ -622,6 +622,9 @@ EXTERN char *driver_dl_error(void);
EXTERN int erl_drv_putenv(const char *key, char *value);
EXTERN int erl_drv_getenv(const char *key, char *value, size_t *value_size);

/* port_command() synchronous error... */
EXTERN int erl_drv_command_error(ErlDrvPort dprt, char *string);

/* spawn start init ack */
EXTERN void erl_drv_init_ack(ErlDrvPort ix, ErlDrvData res);

Expand Down
3 changes: 3 additions & 0 deletions erts/emulator/beam/erl_port.h
Original file line number Diff line number Diff line change
Expand Up @@ -151,6 +151,7 @@ struct _erl_drv_port {
erts_atomic_t run_queue;
erts_atomic_t connected; /* A connected process */
Eterm caller; /* Current caller. */
Eterm cmd_error;
erts_atomic_t data; /* Data associated with port. */
Uint bytes_in; /* Number of bytes read */
Uint bytes_out; /* Number of bytes written */
Expand All @@ -176,6 +177,8 @@ struct _erl_drv_port {
} *async_open_port; /* Reference used with async open port */
};

#define ERTS_PORT_CMD_ERROR_NOT_ALLOWED THE_NON_VALUE
#define ERTS_PORT_CMD_ERROR_ALLOWED NIL

void erts_init_port_data(Port *);
void erts_cleanup_port_data(Port *);
Expand Down
66 changes: 61 additions & 5 deletions erts/emulator/beam/io.c
Original file line number Diff line number Diff line change
Expand Up @@ -651,7 +651,10 @@ erts_open_driver(erts_driver_t* driver, /* Pointer to driver. */
else
ERTS_OPEN_DRIVER_RET(NULL, -3, SYSTEM_LIMIT);
}


port->caller = NIL;
port->cmd_error = ERTS_PORT_CMD_ERROR_NOT_ALLOWED;

if (IS_TRACED_FL(port, F_TRACE_PORTS)) {
trace_port_open(port,
pid,
Expand Down Expand Up @@ -1406,6 +1409,7 @@ static int
port_sig_outputv(Port *prt, erts_aint32_t state, int op, ErtsProc2PortSigData *sigdp)
{
Eterm reply;
Eterm tmp_heap[3];

switch (op) {
case ERTS_PROC2PORT_SIG_EXEC:
Expand All @@ -1416,13 +1420,23 @@ port_sig_outputv(Port *prt, erts_aint32_t state, int op, ErtsProc2PortSigData *s
if (state & ERTS_PORT_SFLGS_INVALID_LOOKUP)
reply = am_badarg;
else {
call_driver_outputv(sigdp->flags & ERTS_P2P_SIG_DATA_FLG_BANG_OP,
int bang_op = sigdp->flags & ERTS_P2P_SIG_DATA_FLG_BANG_OP;
ASSERT(prt->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);
if (!bang_op)
prt->cmd_error = ERTS_PORT_CMD_ERROR_ALLOWED;
call_driver_outputv(bang_op,
sigdp->caller,
sigdp->u.outputv.from,
prt,
prt->drv_ptr,
sigdp->u.outputv.evp);
reply = am_true;
if (bang_op || prt->cmd_error == ERTS_PORT_CMD_ERROR_ALLOWED)
reply = am_true;
else {
ASSERT(is_atom(prt->cmd_error));
reply = TUPLE2(&tmp_heap[0], am_error, prt->cmd_error);
}
prt->cmd_error = ERTS_PORT_CMD_ERROR_NOT_ALLOWED;
}
break;
case ERTS_PROC2PORT_SIG_ABORT_NOSUSPEND:
Expand Down Expand Up @@ -1513,6 +1527,7 @@ static int
port_sig_output(Port *prt, erts_aint32_t state, int op, ErtsProc2PortSigData *sigdp)
{
Eterm reply;
Eterm tmp_heap[3];

switch (op) {
case ERTS_PROC2PORT_SIG_EXEC:
Expand All @@ -1523,14 +1538,24 @@ port_sig_output(Port *prt, erts_aint32_t state, int op, ErtsProc2PortSigData *si
if (state & ERTS_PORT_SFLGS_INVALID_LOOKUP)
reply = am_badarg;
else {
call_driver_output(sigdp->flags & ERTS_P2P_SIG_DATA_FLG_BANG_OP,
int bang_op = sigdp->flags & ERTS_P2P_SIG_DATA_FLG_BANG_OP;
ASSERT(prt->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);
if (!bang_op)
prt->cmd_error = ERTS_PORT_CMD_ERROR_ALLOWED;
call_driver_output(bang_op,
sigdp->caller,
sigdp->u.output.from,
prt,
prt->drv_ptr,
sigdp->u.output.bufp,
sigdp->u.output.size);
reply = am_true;
if (bang_op || prt->cmd_error == ERTS_PORT_CMD_ERROR_ALLOWED)
reply = am_true;
else {
ASSERT(is_atom(prt->cmd_error));
reply = TUPLE2(&tmp_heap[0], am_error, prt->cmd_error);
}
prt->cmd_error = ERTS_PORT_CMD_ERROR_NOT_ALLOWED;
}
break;
case ERTS_PROC2PORT_SIG_ABORT_NOSUSPEND:
Expand Down Expand Up @@ -2156,6 +2181,8 @@ call_deliver_port_exit(int bang_op,
* behave accordingly...
*/

ASSERT(prt->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);

if (state & ERTS_PORT_SFLGS_INVALID_LOOKUP)
return ERTS_PORT_OP_DROPPED;

Expand Down Expand Up @@ -2315,6 +2342,8 @@ set_port_connected(int bang_op,
* behave accordingly...
*/

ASSERT(prt->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);

if (state & ERTS_PORT_SFLGS_INVALID_LOOKUP)
return ERTS_PORT_OP_DROPPED;

Expand Down Expand Up @@ -2475,6 +2504,7 @@ erts_port_connect(Process *c_p,
static void
port_unlink_failure(Port *prt, Eterm port_id, ErtsSigUnlinkOp *sulnk)
{
ASSERT(prt->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);
erts_proc_sig_send_unlink_ack(prt ? &prt->common : NULL, port_id, sulnk);
}

Expand All @@ -2486,6 +2516,8 @@ port_unlink(Port *prt, erts_aint32_t state, ErtsSigUnlinkOp *sulnk)
} else {
ErtsILink *ilnk;

ASSERT(prt->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);

ilnk = (ErtsILink *) erts_link_tree_lookup(ERTS_P_LINKS(prt),
sulnk->from);

Expand Down Expand Up @@ -2573,6 +2605,7 @@ port_unlink_ack(Port *prt, erts_aint32_t state, ErtsSigUnlinkOp *sulnk)
port_unlink_ack_failure(prt->common.id, sulnk);
else {
ErtsILink *ilnk;
ASSERT(prt->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);
ilnk = (ErtsILink *) erts_link_tree_lookup(ERTS_P_LINKS(prt),
sulnk->from);
if (ilnk && ilnk->unlinking == sulnk->id) {
Expand Down Expand Up @@ -2640,6 +2673,7 @@ erts_port_unlink_ack(Process *c_p, Port *prt, ErtsSigUnlinkOp *sulnk)
static void
port_link_failure(Port *port, Eterm port_id, ErtsLink *lnk)
{
ASSERT(port->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);
erts_proc_sig_send_link_exit(&port->common, port_id, lnk, am_noproc, NIL);
}

Expand All @@ -2650,6 +2684,7 @@ port_link(Port *prt, erts_aint32_t state, ErtsLink *nlnk)
port_link_failure(prt, prt->common.id, nlnk);
} else {
ErtsLink *lnk;
ASSERT(prt->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);
lnk = erts_link_tree_lookup_insert(&ERTS_P_LINKS(prt), nlnk);
if (lnk)
erts_link_release(nlnk);
Expand Down Expand Up @@ -2718,6 +2753,7 @@ static void
port_monitor_failure(Port *prt, Eterm port_id, ErtsMonitor *mon)
{
ASSERT(prt == NULL || prt->common.id == port_id);
ASSERT(prt->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);
erts_proc_sig_send_monitor_down(prt ? &prt->common : NULL, port_id,
mon, am_noproc);
}
Expand All @@ -2729,6 +2765,7 @@ static void
port_monitor(Port *prt, erts_aint32_t state, ErtsMonitor *mon)
{
ASSERT(prt);
ASSERT(prt->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);

if (state & ERTS_PORT_SFLGS_INVALID_LOOKUP) {
port_monitor_failure(prt, prt->common.id, mon);
Expand Down Expand Up @@ -2807,6 +2844,7 @@ port_demonitor(Port *port, erts_aint32_t state, ErtsMonitor *mon)
ErtsMonitorData *mdp = erts_monitor_to_data(mon);
ASSERT(port && mon);
ASSERT(erts_monitor_is_origin(mon));
ASSERT(port->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);
if (!erts_monitor_is_in_table(&mdp->u.target))
erts_monitor_release(mon);
else {
Expand All @@ -2819,6 +2857,7 @@ static int
port_sig_demonitor(Port *prt, erts_aint32_t state, int op,
ErtsProc2PortSigData *sigdp)
{
ASSERT(prt->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED);
if (op == ERTS_PROC2PORT_SIG_EXEC)
port_demonitor(prt, state, sigdp->u.demonitor.mon);
else
Expand Down Expand Up @@ -7715,6 +7754,23 @@ erl_drv_getenv(const char *key, char *value, size_t *value_size)
}
}

int
erl_drv_command_error(ErlDrvPort dprt, char *string)
{
Port *prt = erts_drvport2port(dprt);
if (prt == ERTS_INVALID_ERL_DRV_PORT)
return ESRCH;
if (!string)
return EINVAL;
if (prt->cmd_error == ERTS_PORT_CMD_ERROR_NOT_ALLOWED)
return EACCES;
prt->cmd_error = erts_atom_put((byte *) string,
sys_strlen(string),
ERTS_ATOM_ENC_LATIN1,
!0);
return 0;
}

/* get heart_port
* used by erl_crash_dump
* - uses the fact that heart_port is registered when starting heart
Expand Down
5 changes: 5 additions & 0 deletions erts/emulator/sys/win32/erl_win_dyn_driver.h
Original file line number Diff line number Diff line change
Expand Up @@ -151,6 +151,8 @@ WDD_TYPEDEF(void, erl_drv_thread_exit, (void *resp));
WDD_TYPEDEF(int, erl_drv_thread_join, (ErlDrvTid, void **respp));
WDD_TYPEDEF(int, erl_drv_putenv, (const char *key, char *value));
WDD_TYPEDEF(int, erl_drv_getenv, (const char *key, char *value, size_t *value_size));
WDD_TYPEDEF(int, erl_drv_command_error, (ErlDrvPort dprt, char *string));


typedef struct {
WDD_FTYPE(null_func) *null_func;
Expand Down Expand Up @@ -259,6 +261,7 @@ typedef struct {
WDD_FTYPE(erl_drv_thread_join) *erl_drv_thread_join;
WDD_FTYPE(erl_drv_putenv) *erl_drv_putenv;
WDD_FTYPE(erl_drv_getenv) *erl_drv_getenv;
WDD_FTYPE(erl_drv_command_error) *erl_drv_command_error;
/* Add new calls here */
} TWinDynDriverCallbacks;

Expand Down Expand Up @@ -379,6 +382,7 @@ extern TWinDynDriverCallbacks WinDynDriverCallbacks;
#define erl_drv_thread_join (WinDynDriverCallbacks.erl_drv_thread_join)
#define erl_drv_putenv (WinDynDriverCallbacks.erl_drv_putenv)
#define erl_drv_getenv (WinDynDriverCallbacks.erl_drv_getenv)
#define erl_drv_command_error (WinDynDriverCallbacks.erl_drv_command_error)

/* The only variable in the interface... */
#define driver_term_nil (driver_mk_term_nil())
Expand Down Expand Up @@ -510,6 +514,7 @@ do { \
((W).erl_drv_thread_join) = erl_drv_thread_join; \
((W).erl_drv_putenv) = erl_drv_putenv; \
((W).erl_drv_getenv) = erl_drv_getenv; \
((W).erl_drv_command_error) = erl_drv_command_error; \
} while (0)


Expand Down
Loading

0 comments on commit b79ce55

Please sign in to comment.