Skip to content

Commit

Permalink
Merge branch 'lukas/kernel/fix-reading-characters-from-stdin-maint-26…
Browse files Browse the repository at this point in the history
…/OTP-18640/OTP-18657' into maint

* lukas/kernel/fix-reading-characters-from-stdin-maint-26/OTP-18640/OTP-18657:
  Update primary bootstrap
  tty: Add cover spec for tty
  kernel: Make group and prim_tty not get purged by cover
  kernel: Support sending byte stream on standard in
  kernel: group:edit_line with echo needs to handle binaries
  stdlib: Fix eof handling in io_lib:collect_chars
  Revert "Merge pull request #6881 from sile/fix-escript-binary-stdin-bug"
  • Loading branch information
garazdawi committed Jun 20, 2023
2 parents f112796 + 2b1ce5d commit 65d7d12
Show file tree
Hide file tree
Showing 14 changed files with 298 additions and 73 deletions.
Binary file modified bootstrap/lib/kernel/ebin/group.beam
Binary file not shown.
Binary file modified bootstrap/lib/kernel/ebin/prim_tty.beam
Binary file not shown.
Binary file modified bootstrap/lib/kernel/ebin/user_drv.beam
Binary file not shown.
Binary file modified bootstrap/lib/stdlib/ebin/io_lib.beam
Binary file not shown.
20 changes: 19 additions & 1 deletion lib/kernel/doc/src/kernel_app.xml
Original file line number Diff line number Diff line change
Expand Up @@ -614,7 +614,25 @@ MaxT = NetTickTime + NetTickTime / NetTickIntensity</code>
</p>

</item>
</taglist>
<tag><marker id="standard_io_encoding"/><c>standard_io_encoding = Encoding</c></tag>
<item>
<p>Set whether bytes sent or received via standard_io should be interpreted as unicode or latin1.
By default input and output is interpreted as Unicode if it is supported on the host. With this flag
you may configure the encoding on startup.</p>
<p>This works similarly to <seemfa marker="stdlib:io#setopts/2"><c>io:setopts(standard_io, {encoding, Encoding})</c></seemfa>
but is applied before any bytes on standard_io may have been read.</p>
<p>Encoding is one of:</p>
<taglist>
<tag><c>unicode</c></tag>
<item><p>Configure standard_io to use unicode mode.</p></item>
<tag><c>latin1</c></tag>
<item><p>Configure standard_io to use latin1 mode.</p></item>
<tag><c>_</c></tag>
<item><p>Anything other than unicode or latin1 will be ignored and the system will
configure the encoding by itself, typically unicode on modern systems.</p></item>
</taglist>
</item>
</taglist>
</section>

<section>
Expand Down
89 changes: 48 additions & 41 deletions lib/kernel/src/group.erl
Original file line number Diff line number Diff line change
Expand Up @@ -20,9 +20,16 @@
-module(group).

%% A group leader process for user io.
%% This process receives input data from user_drv in this format
%% {Drv,{data,unicode:charlist()}}
%% It then keeps that data as unicode in its state and converts it
%% to latin1/unicode on a per request basis. If any data is left after
%% a request, that data is again kept as unicode.

-export([start/2, start/3, whereis_shell/0, server/4]).

-export([server_loop/3]).

start(Drv, Shell) ->
start(Drv, Shell, []).

Expand Down Expand Up @@ -108,26 +115,29 @@ start_shell1(Fun) ->
exit(Error) % let the group process crash
end.

-spec server_loop(UserDrv :: pid(), Shell:: pid(),
Buffer :: unicode:chardata()) ->
no_return().
server_loop(Drv, Shell, Buf0) ->
receive
{io_request,From,ReplyAs,Req} when is_pid(From) ->
%% This io_request may cause a transition to a couple of
%% selective receive loops elsewhere in this module.
Buf = io_request(Req, From, ReplyAs, Drv, Shell, Buf0),
server_loop(Drv, Shell, Buf);
?MODULE:server_loop(Drv, Shell, Buf);
{reply,{From,ReplyAs},Reply} ->
io_reply(From, ReplyAs, Reply),
server_loop(Drv, Shell, Buf0);
?MODULE:server_loop(Drv, Shell, Buf0);
{driver_id,ReplyTo} ->
ReplyTo ! {self(),driver_id,Drv},
server_loop(Drv, Shell, Buf0);
?MODULE:server_loop(Drv, Shell, Buf0);
{Drv, echo, Bool} ->
put(echo, Bool),
server_loop(Drv, Shell, Buf0);
?MODULE:server_loop(Drv, Shell, Buf0);
{'EXIT',Drv,interrupt} ->
%% Send interrupt to the shell.
exit_shell(interrupt),
server_loop(Drv, Shell, Buf0);
?MODULE:server_loop(Drv, Shell, Buf0);
{'EXIT',Drv,R} ->
exit(R);
{'EXIT',Shell,R} ->
Expand All @@ -139,7 +149,7 @@ server_loop(Drv, Shell, Buf0) ->
(tuple_size(NotDrvTuple) =/= 2) orelse
(element(1, NotDrvTuple) =/= Drv) ->
%% Ignore this unknown message.
server_loop(Drv, Shell, Buf0)
?MODULE:server_loop(Drv, Shell, Buf0)
end.

exit_shell(Reason) ->
Expand Down Expand Up @@ -497,13 +507,14 @@ get_chars_loop(Pbs, M, F, Xa, Drv, Shell, Buf0, State, LineCont0, Encoding) ->
true ->
get_line(Buf0, Pbs, LineCont0, Drv, Shell, Encoding);
false ->
%% get_line_echo_off only deals with lists
%% and does not need encoding...
get_line_echo_off(Buf0, Pbs, Drv, Shell)
%% get_line_echo_off only deals with lists,
%% so convert to list before calling it.
get_line_echo_off(cast(Buf0, list, Encoding), Pbs, Drv, Shell)
end,
case Result of
{done,LineCont1,Buf} ->
get_chars_apply(Pbs, M, F, Xa, Drv, Shell, Buf, State, LineCont1, Encoding);
get_chars_apply(Pbs, M, F, Xa, Drv, Shell, append(Buf, [], Encoding),
State, LineCont1, Encoding);

interrupted ->
{error,{error,interrupted},[]};
Expand Down Expand Up @@ -537,10 +548,8 @@ get_chars_apply(Pbs, M, F, Xa, Drv, Shell, Buf, State0, LineCont, Encoding) ->

get_chars_n_loop(Pbs, M, F, Xa, Drv, Shell, Buf0, State, Encoding) ->
try M:F(State, cast(Buf0, get(read_mode), Encoding), Encoding, Xa) of
{stop,Result,eof} ->
{ok,Result,eof};
{stop,Result,Rest} ->
{ok,Result,append(Rest, [], Encoding)};
{ok, Result, append(Rest,[],Encoding)};
State1 ->
case get_chars_echo_off(Pbs, Drv, Shell) of
interrupted ->
Expand Down Expand Up @@ -604,13 +613,12 @@ get_line1({undefined,{_A,Mode,Char},Cs,Cont,Rs}, Drv, Shell, Ls0, Encoding)
send_drv_reqs(Drv, edlin:erase_line()),
{more_chars,Ncont,Nrs} = edlin:start(edlin:prompt(Cont)),
send_drv_reqs(Drv, Nrs),
get_line1(edlin:edit_line1(string:to_graphemes(lists:sublist(Lcs,
1,
length(Lcs)-1)),
Ncont),
Drv,
Shell,
Ls, Encoding)
get_line1(
edlin:edit_line1(
string:to_graphemes(
lists:sublist(Lcs, 1, length(Lcs)-1)),
Ncont),
Drv, Shell, Ls, Encoding)
end;
get_line1({undefined,{_A,Mode,Char},Cs,Cont,Rs}, Drv, Shell, Ls0, Encoding)
when Mode =:= none, Char =:= $\^N;
Expand Down Expand Up @@ -800,7 +808,8 @@ more_data(What, Cont0, Drv, Shell, Ls, Encoding) ->
send_drv_reqs(Drv, edlin:redraw_line(Cont0)),
more_data(What, Cont0, Drv, Shell, Ls, Encoding);
{Drv,{data,Cs}} ->
get_line1(edlin:edit_line(Cs, Cont0), Drv, Shell, Ls, Encoding);
get_line1(edlin:edit_line(cast(Cs, list), Cont0),
Drv, Shell, Ls, Encoding);
{Drv,eof} ->
get_line1(edlin:edit_line(eof, Cont0), Drv, Shell, Ls, Encoding);
{io_request,From,ReplyAs,Req} when is_pid(From) ->
Expand Down Expand Up @@ -831,7 +840,7 @@ get_line_echo_off(Chars, Pbs, Drv, Shell) ->
get_line_echo_off1({Chars,[]}, Drv, Shell) ->
receive
{Drv,{data,Cs}} ->
get_line_echo_off1(edit_line(Cs, Chars), Drv, Shell);
get_line_echo_off1(edit_line(cast(Cs, list), Chars), Drv, Shell);
{Drv,eof} ->
get_line_echo_off1(edit_line(eof, Chars), Drv, Shell);
{io_request,From,ReplyAs,Req} when is_pid(From) ->
Expand Down Expand Up @@ -860,7 +869,7 @@ get_chars_echo_off(Pbs, Drv, Shell) ->
get_chars_echo_off1(Drv, Shell) ->
receive
{Drv, {data, Cs}} ->
Cs;
cast(Cs, list);
{Drv, eof} ->
eof;
{io_request,From,ReplyAs,Req} when is_pid(From) ->
Expand Down Expand Up @@ -1008,7 +1017,7 @@ get_password_line(Chars, Drv, Shell) ->
get_password1({Chars,[]}, Drv, Shell) ->
receive
{Drv,{data,Cs}} ->
get_password1(edit_password(Cs,Chars),Drv,Shell);
get_password1(edit_password(Cs,cast(Chars,list)),Drv,Shell);
{io_request,From,ReplyAs,Req} when is_pid(From) ->
io_request(Req, From, ReplyAs, Drv, Shell, []), %WRONG!!!
%% I guess the reason the above line is wrong is that Buf is
Expand Down Expand Up @@ -1048,20 +1057,18 @@ edit_password([Char|Cs],Chars) ->
prompt_bytes(Prompt, Encoding) ->
lists:flatten(io_lib:format_prompt(Prompt, Encoding)).

cast(L, binary,latin1) when is_list(L) ->
list_to_binary(L);
cast(L, list, latin1) when is_list(L) ->
binary_to_list(list_to_binary(L)); %% Exception if not bytes
cast(L, binary,unicode) when is_list(L) ->
unicode:characters_to_binary(L,utf8);
cast(Other, _, _) ->
Other.

append(B, L, latin1) when is_binary(B) ->
binary_to_list(B)++L;
append(B, L, unicode) when is_binary(B) ->
unicode:characters_to_list(B,utf8)++L;
append(L1, L2, _) when is_list(L1) ->
L1++L2;
append(_Eof, L, _) ->
L.
cast(Buf, Type) ->
cast(Buf, Type, utf8).
cast(eof, _, _) ->
eof;
cast(L, binary, ToEnc) ->
unicode:characters_to_binary(L, utf8, ToEnc);
cast(L, list, _ToEnc) ->
unicode:characters_to_list(L, utf8).

append(eof, [], _) ->
eof;
append(eof, L, _) ->
L;
append(B, L, FromEnc) ->
unicode:characters_to_list(B, FromEnc) ++ L.
46 changes: 31 additions & 15 deletions lib/kernel/src/prim_tty.erl
Original file line number Diff line number Diff line change
Expand Up @@ -115,6 +115,8 @@
sizeof_wchar/0, tgetent_nif/1, tgetnum_nif/1, tgetflag_nif/1, tgetstr_nif/1,
tgoto_nif/1, tgoto_nif/2, tgoto_nif/3, tty_read_signal/2]).

-export([reader_loop/6, writer_loop/2]).

%% Exported in order to remove "unused function" warning
-export([sizeof_wchar/0, wcswidth/1, tgoto/1, tgoto/2, tgoto/3]).

Expand Down Expand Up @@ -219,7 +221,7 @@ init(UserOptions) when is_map(UserOptions) ->
{ok, TTY} = tty_create(),

%% Initialize the locale to see if we support utf-8 or not
UnicodeMode =
UnicodeSupported =
case setlocale(TTY) of
primitive ->
lists:any(
Expand All @@ -229,6 +231,11 @@ init(UserOptions) when is_map(UserOptions) ->
UnicodeLocale when is_boolean(UnicodeLocale) ->
UnicodeLocale
end,
IOEncoding = application:get_env(kernel, standard_io_encoding, default),
UnicodeMode = if IOEncoding =:= latin1 -> false;
IOEncoding =:= unicode -> true;
true -> UnicodeSupported
end,
{ok, ANSI_RE_MP} = re:compile(?ANSI_REGEXP, [unicode]),
init_term(#state{ tty = TTY, unicode = UnicodeMode, options = Options, ansi_regexp = ANSI_RE_MP }).
init_term(State = #state{ tty = TTY, options = Options }) ->
Expand Down Expand Up @@ -256,7 +263,12 @@ init_term(State = #state{ tty = TTY, options = Options }) ->
ReaderState =
case {maps:get(input, Options), TTYState#state.reader} of
{true, undefined} ->
{ok, Reader} = proc_lib:start_link(?MODULE, reader, [[State#state.tty, self()]]),
DefaultReaderEncoding = if State#state.unicode -> utf8;
not State#state.unicode -> latin1
end,
{ok, Reader} = proc_lib:start_link(
?MODULE, reader,
[[State#state.tty, DefaultReaderEncoding, self()]]),
WriterState#state{ reader = Reader };
{true, _} ->
WriterState;
Expand Down Expand Up @@ -425,13 +437,17 @@ call(Pid, Msg) ->
{error, Reason}
end.

reader([TTY, Parent]) ->
reader([TTY, Encoding, Parent]) ->
register(user_drv_reader, self()),
ReaderRef = make_ref(),
SignalRef = make_ref(),

ok = tty_select(TTY, SignalRef, ReaderRef),
proc_lib:init_ack({ok, {self(), ReaderRef}}),
FromEnc = tty_encoding(TTY),
FromEnc = case tty_encoding(TTY) of
utf8 -> Encoding;
Else -> Else
end,
reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, <<>>).

reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc) ->
Expand All @@ -441,20 +457,20 @@ reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc) ->
receive
{EnableAlias, enable} ->
EnableAlias ! {EnableAlias, ok},
reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc)
?MODULE:reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc)
end;
{select, TTY, SignalRef, ready_input} ->
{ok, Signal} = tty_read_signal(TTY, SignalRef),
Parent ! {ReaderRef,{signal,Signal}},
reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc);
?MODULE:reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc);
{Alias, {set_unicode_state, _}} when FromEnc =:= {utf16, little} ->
%% Ignore requests on windows when in console mode
Alias ! {Alias, true},
reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc);
?MODULE:reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc);
{Alias, {set_unicode_state, Bool}} ->
Alias ! {Alias, FromEnc =/= latin1},
NewFromEnc = if Bool -> utf8; not Bool -> latin1 end,
reader_loop(TTY, Parent, SignalRef, ReaderRef, NewFromEnc, Acc);
?MODULE:reader_loop(TTY, Parent, SignalRef, ReaderRef, NewFromEnc, Acc);
{_Alias, stop} ->
ok;
{select, TTY, ReaderRef, ready_input} ->
Expand All @@ -470,7 +486,7 @@ reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc) ->
reader_loop(TTY, Parent, SignalRef, ReaderRef, tty_encoding(TTY), Acc);
{ok, <<>>} ->
%% EAGAIN or EINTR
reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc);
?MODULE:reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc);
{ok, UtfXBytes} ->

{Bytes, NewAcc, NewFromEnc} =
Expand All @@ -485,7 +501,7 @@ reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc) ->
Alias ! {Alias, true}
end,
receive
{Parent, set_unicode_state, true} -> ok
{Parent, set_unicode_state, _} -> ok
end,
Latin1Chars = unicode:characters_to_binary(Error, latin1, utf8),
{<<B/binary,Latin1Chars/binary>>, <<>>, latin1};
Expand All @@ -495,7 +511,7 @@ reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc) ->
{B, <<>>, FromEnc}
end,
Parent ! {ReaderRef, {data, Bytes}},
reader_loop(TTY, Parent, SignalRef, ReaderRef, NewFromEnc, NewAcc)
?MODULE:reader_loop(TTY, Parent, SignalRef, ReaderRef, NewFromEnc, NewAcc)
end
end.

Expand All @@ -517,18 +533,18 @@ write(#state{ writer = {WriterPid, _WriterRef}}, Chars, From) ->
writer_loop(TTY, WriterRef) ->
receive
{write, []} ->
writer_loop(TTY, WriterRef);
?MODULE:writer_loop(TTY, WriterRef);
{write, Chars} ->
_ = write_nif(TTY, Chars),
writer_loop(TTY, WriterRef);
?MODULE:writer_loop(TTY, WriterRef);
{write, From, []} ->
From ! {WriterRef, ok},
writer_loop(TTY, WriterRef);
?MODULE:writer_loop(TTY, WriterRef);
{write, From, Chars} ->
case write_nif(TTY, Chars) of
ok ->
From ! {WriterRef, ok},
writer_loop(TTY, WriterRef);
?MODULE:writer_loop(TTY, WriterRef);
{error, Reason} ->
exit(self(), Reason)
end
Expand Down
5 changes: 2 additions & 3 deletions lib/kernel/src/user_drv.erl
Original file line number Diff line number Diff line change
Expand Up @@ -421,8 +421,7 @@ server({call, From}, {start_shell, _Args}, _State) ->
keep_state_and_data;
server(info, {ReadHandle,{data,UTF8Binary}}, State = #state{ read = ReadHandle })
when State#state.current_group =:= State#state.user ->
State#state.current_group !
{self(), {data, unicode:characters_to_list(UTF8Binary, utf8)}},
State#state.current_group ! {self(), {data,UTF8Binary}},
keep_state_and_data;
server(info, {ReadHandle,{data,UTF8Binary}}, State = #state{ read = ReadHandle }) ->
case contains_ctrl_g_or_ctrl_c(UTF8Binary) of
Expand All @@ -435,7 +434,7 @@ server(info, {ReadHandle,{data,UTF8Binary}}, State = #state{ read = ReadHandle }
keep_state_and_data;
none ->
State#state.current_group !
{self(), {data, unicode:characters_to_list(UTF8Binary, utf8)}},
{self(), {data, UTF8Binary}},
keep_state_and_data
end;
server(info, {ReadHandle,eof}, State = #state{ read = ReadHandle }) ->
Expand Down
2 changes: 1 addition & 1 deletion lib/kernel/test/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -153,7 +153,7 @@ TARGET_FILES= $(MODULES:%=$(EBIN)/%.$(EMULATOR))
INSTALL_PROGS= $(TARGET_FILES)

EMAKEFILE=Emakefile
COVERFILE=kernel.cover logger.cover
COVERFILE=kernel.cover logger.cover tty.cover

# ----------------------------------------------------
# Release directory specification
Expand Down
3 changes: 3 additions & 0 deletions lib/kernel/test/tty.cover
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
%% -*- erlang -*-
{incl_mods,[prim_tty, user_drv, group, shell, edlin, edlin_expand, io_lib]}.

Loading

0 comments on commit 65d7d12

Please sign in to comment.