Skip to content

Commit

Permalink
fixup! fixup! Fix fault handling of writing to tty
Browse files Browse the repository at this point in the history
  • Loading branch information
garazdawi committed Aug 18, 2022
1 parent d418564 commit 0678580
Show file tree
Hide file tree
Showing 2 changed files with 15 additions and 24 deletions.
10 changes: 6 additions & 4 deletions erts/emulator/nifs/common/prim_tty_nif.c
Original file line number Diff line number Diff line change
Expand Up @@ -591,12 +591,14 @@ static ERL_NIF_TERM tty_create(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv
tty->ofd = 1;
#else
tty->ifd = GetStdHandle(STD_INPUT_HANDLE);
if (tty->ifd == INVALID_HANDLE_VALUE) {
return make_errno_error(env, "GetStdHandle");
if (tty->ifd == INVALID_HANDLE_VALUE || tty->ifd == NULL) {
tty->ifd = CreateFile("nul", GENERIC_READ, 0,
NULL, OPEN_EXISTING, FILE_ATTRIBUTE_NORMAL, NULL);
}
tty->ofd = GetStdHandle(STD_OUTPUT_HANDLE);
if (tty->ofd == INVALID_HANDLE_VALUE) {
return make_errno_error(env, "GetStdHandle");
if (tty->ofd == INVALID_HANDLE_VALUE || tty->ofd == NULL) {
tty->ofd = CreateFile("nul", GENERIC_WRITE, 0,
NULL, OPEN_EXISTING, FILE_ATTRIBUTE_NORMAL, NULL);
}
if (GetConsoleMode(tty->ofd, &tty->dwOriginalOutMode))
{
Expand Down
29 changes: 9 additions & 20 deletions lib/kernel/src/user_drv.erl
Original file line number Diff line number Diff line change
Expand Up @@ -352,10 +352,9 @@ server(info, {Requester, set_unicode_state, Bool}, #state{ tty = TTYState } = St
server(info, {Requester, get_terminal_state}, _State) ->
Requester ! {self(), get_terminal_state, prim_tty:isatty(stdout) },
keep_state_and_data;
server(info, Req, State = #state{ user = User, current_group = Curr, write = WriteRef })
server(info, Req, State = #state{ user = User, current_group = Curr })
when element(1,Req) =:= User orelse element(1,Req) =:= Curr,
tuple_size(Req) =:= 2 orelse tuple_size(Req) =:= 3,
is_reference(WriteRef) ->
tuple_size(Req) =:= 2 orelse tuple_size(Req) =:= 3 ->
%% We match {User|Curr,_}|{User|Curr,_,_}
{NewTTYState, NewQueue} = handle_req(Req, State#state.tty, State#state.queue),
{keep_state, State#state{ tty = NewTTYState, queue = NewQueue }};
Expand All @@ -368,23 +367,13 @@ server(info, {WriteRef, ok}, State = #state{ write = WriteRef,
{NewTTYState, NewQueue} = handle_req(next, State#state.tty, {false, IOQ}),
{keep_state, State#state{ tty = NewTTYState, queue = NewQueue }};
server(info, {'DOWN', MonitorRef, _, _, Reason},
#state{ queue = {{Origin, MonitorRef, Reply}, _IOQ} } = State) ->
%% The writer process died
case init:get_argument(detached) of
{ok, _} ->
%% If we are detached, we drop queue and set writer to undefined,
%% that way all future writes are just dropped.
Origin ! {reply, Reply, ok},
{keep_state, State#state{ queue = {false, queue:new()},
write = undefined }};
error ->
%% If we are not detached, we send the correct error to the caller and
%% then stop this process. This will bring down all linked groups (including 'user').
%% All writes from now on will throw badarg terminated.
Origin ! {reply, Reply, {error, Reason}},
?LOG_INFO("Failed to write to standard out (~p)", [Reason]),
stop
end;
#state{ queue = {{Origin, MonitorRef, Reply}, _IOQ} }) ->
%% The writer process died we send the correct error to the caller and
%% then stop this process. This will bring down all linked groups (including 'user').
%% All writes from now on will throw badarg terminated.
Origin ! {reply, Reply, {error, Reason}},
?LOG_INFO("Failed to write to standard out (~p)", [Reason]),
stop;
server(info,{Requester, {put_chars_sync, _, _, Reply}}, _State) ->
%% This is a sync request from an unknown or inactive group.
%% We need to ack the Req otherwise originating process will hang forever.
Expand Down

0 comments on commit 0678580

Please sign in to comment.