Skip to content

Commit

Permalink
kernel: Log when tty reader/writer crashes
Browse files Browse the repository at this point in the history
If the tty reader or writer crashes for some reason we
should log that so that we can debug what has happened.
  • Loading branch information
garazdawi committed Feb 8, 2024
1 parent 78ebd83 commit b1d4ec0
Show file tree
Hide file tree
Showing 2 changed files with 55 additions and 31 deletions.
14 changes: 13 additions & 1 deletion lib/kernel/src/prim_tty.erl
Original file line number Diff line number Diff line change
Expand Up @@ -109,7 +109,7 @@
handle_signal/2, window_size/1, handle_request/2, write/2, write/3,
npwcwidth/1, npwcwidth/2,
ansi_regexp/0, ansi_color/2]).
-export([reader_stop/1, disable_reader/1, enable_reader/1]).
-export([reader_stop/1, disable_reader/1, enable_reader/1, is_reader/2, is_writer/2]).

-nifs([isatty/1, tty_create/0, tty_init/3, tty_set/1, setlocale/1,
tty_select/3, tty_window_size/1, tty_encoding/1, write_nif/2, read_nif/2, isprint/1,
Expand Down Expand Up @@ -427,6 +427,18 @@ handles(#state{ reader = {_ReaderPid, ReaderRef},
writer = {_WriterPid, WriterRef}}) ->
#{ read => ReaderRef, write => WriterRef }.

-spec is_reader(pid(), state()) -> boolean().
is_reader(#state{ reader = {ReaderPid, _} }, ReaderPid) ->
true;
is_reader(_, _) ->
false.

-spec is_writer(pid(), state()) -> boolean().
is_writer(#state{ writer = {WriterPid, _} }, WriterPid) ->
true;
is_writer(_, _) ->
false.

-spec unicode(state()) -> boolean().
unicode(State) ->
State#state.unicode.
Expand Down
72 changes: 42 additions & 30 deletions lib/kernel/src/user_drv.erl
Original file line number Diff line number Diff line change
Expand Up @@ -442,7 +442,7 @@ server(info, {ReadHandle,{data,UTF8Binary}}, State = #state{ read = ReadHandle }
end;
server(info, {ReadHandle,eof}, State = #state{ read = ReadHandle }) ->
State#state.current_group ! {self(), eof},
keep_state_and_data;
{keep_state, State#state{ read = undefined }};
server(info,{ReadHandle,{signal,Signal}}, State = #state{ tty = TTYState, read = ReadHandle }) ->
{keep_state, State#state{ tty = prim_tty:handle_signal(TTYState, Signal) }};

Expand Down Expand Up @@ -528,36 +528,48 @@ server(info, {'EXIT', EditorPort, _R},
Requester ! {self(), {editor_data, string:chomp(Unicode)}},
ok = prim_tty:enable_reader(TTYState),
{keep_state, State#state{editor = undefined}};
server(info,{'EXIT', Group, Reason}, State) -> % shell and group leader exit
case gr_cur_pid(State#state.groups) of
Group when Reason =/= die, Reason =/= terminated -> % current shell exited
Reqs = [if
Reason =/= normal ->
{put_chars,unicode,<<"*** ERROR: ">>};
true -> % exit not caused by error
{put_chars,unicode,<<"*** ">>}
end,
{put_chars,unicode,<<"Shell process terminated! ">>}],
Gr1 = gr_del_pid(State#state.groups, Group),
case gr_get_info(State#state.groups, Group) of
{Ix,{shell,start,Params}} -> % 3-tuple == local shell
NewTTyState = io_requests(Reqs ++ [{put_chars,unicode,<<"***\n">>}],
State#state.tty),
%% restart group leader and shell, same index
NewGroup = group:start(self(), {shell,start,Params}),
{ok,Gr2} = gr_set_cur(gr_set_num(Gr1, Ix, NewGroup,
{shell,start,Params}), Ix),
{keep_state, State#state{ tty = NewTTyState,
current_group = NewGroup,
groups = Gr2 }};
_ -> % remote shell
NewTTYState = io_requests(
Reqs ++ [{put_chars,unicode,<<"(^G to start new job) ***\n">>}],
State#state.tty),
{keep_state, State#state{ tty = NewTTYState, groups = Gr1 }}
server(info,{'EXIT', Group, Reason}, State) ->
case gr_get_info(State#state.groups, Group) of
undefined ->
Rdr = [?LOG_ERROR("Reader crashed (~p)", [Reason]) || prim_tty:is_reader(State#state.tty, Group)],
Wrt = [?LOG_ERROR("Writer crashed (~p)", [Reason]) || prim_tty:is_writer(State#state.tty, Group)],
case Rdr ++ Wrt of
[] ->
keep_state_and_data;
_ ->
stop
end;
_ -> % not current, just remove it
{keep_state, State#state{ groups = gr_del_pid(State#state.groups, Group) }}
GroupInfo -> % shell and group leader exit
case gr_cur_pid(State#state.groups) of
Group when Reason =/= die, Reason =/= terminated -> % current shell exited
Reqs = [if
Reason =/= normal ->
{put_chars,unicode,<<"*** ERROR: ">>};
true -> % exit not caused by error
{put_chars,unicode,<<"*** ">>}
end,
{put_chars,unicode,<<"Shell process terminated! ">>}],
Gr1 = gr_del_pid(State#state.groups, Group),
case GroupInfo of
{Ix,{shell,start,Params}} -> % 3-tuple == local shell
NewTTyState = io_requests(Reqs ++ [{put_chars,unicode,<<"***\n">>}],
State#state.tty),
%% restart group leader and shell, same index
NewGroup = group:start(self(), {shell,start,Params}),
{ok,Gr2} = gr_set_cur(gr_set_num(Gr1, Ix, NewGroup,
{shell,start,Params}), Ix),
{keep_state, State#state{ tty = NewTTyState,
current_group = NewGroup,
groups = Gr2 }};
_ -> % remote shell
NewTTYState = io_requests(
Reqs ++ [{put_chars,unicode,<<"(^G to start new job) ***\n">>}],
State#state.tty),
{keep_state, State#state{ tty = NewTTYState, groups = Gr1 }}
end;
_ ->
{keep_state, State#state{ groups = gr_del_pid(State#state.groups, Group) }}
end
end;
server(_, _, _) ->
keep_state_and_data.
Expand Down

0 comments on commit b1d4ec0

Please sign in to comment.