diff --git a/bootstrap/lib/kernel/ebin/group.beam b/bootstrap/lib/kernel/ebin/group.beam
index 73c53767c409..1ee8fa4aac04 100644
Binary files a/bootstrap/lib/kernel/ebin/group.beam and b/bootstrap/lib/kernel/ebin/group.beam differ
diff --git a/bootstrap/lib/kernel/ebin/prim_tty.beam b/bootstrap/lib/kernel/ebin/prim_tty.beam
index 24237adab26c..31eb5dbf4a4d 100644
Binary files a/bootstrap/lib/kernel/ebin/prim_tty.beam and b/bootstrap/lib/kernel/ebin/prim_tty.beam differ
diff --git a/bootstrap/lib/kernel/ebin/user_drv.beam b/bootstrap/lib/kernel/ebin/user_drv.beam
index 6ddb0fd0ba16..cd65cfc9af79 100644
Binary files a/bootstrap/lib/kernel/ebin/user_drv.beam and b/bootstrap/lib/kernel/ebin/user_drv.beam differ
diff --git a/bootstrap/lib/stdlib/ebin/io_lib.beam b/bootstrap/lib/stdlib/ebin/io_lib.beam
index 8fac910ca5c4..4b4412eed45e 100644
Binary files a/bootstrap/lib/stdlib/ebin/io_lib.beam and b/bootstrap/lib/stdlib/ebin/io_lib.beam differ
diff --git a/lib/kernel/doc/src/kernel_app.xml b/lib/kernel/doc/src/kernel_app.xml
index 17edb810020a..2f023f3daeaf 100644
--- a/lib/kernel/doc/src/kernel_app.xml
+++ b/lib/kernel/doc/src/kernel_app.xml
@@ -614,7 +614,25 @@ MaxT = NetTickTime + NetTickTime / NetTickIntensity
-
+ standard_io_encoding = Encoding
+ -
+
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.
+ This works similarly to io:setopts(standard_io, {encoding, Encoding})
+ but is applied before any bytes on standard_io may have been read.
+ Encoding is one of:
+
+ unicode
+ Configure standard_io to use unicode mode.
+ latin1
+ Configure standard_io to use latin1 mode.
+ _
+ Anything other than unicode or latin1 will be ignored and the system will
+ configure the encoding by itself, typically unicode on modern systems.
+
+
+
diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl
index ca7251d7ecca..53beae6e4fe1 100644
--- a/lib/kernel/src/group.erl
+++ b/lib/kernel/src/group.erl
@@ -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, []).
@@ -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} ->
@@ -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) ->
@@ -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},[]};
@@ -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 ->
@@ -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;
@@ -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) ->
@@ -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) ->
@@ -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) ->
@@ -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
@@ -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.
diff --git a/lib/kernel/src/prim_tty.erl b/lib/kernel/src/prim_tty.erl
index a03e746cc99f..1319b75e23f9 100644
--- a/lib/kernel/src/prim_tty.erl
+++ b/lib/kernel/src/prim_tty.erl
@@ -115,6 +115,8 @@
sizeof_wchar/0, tgetent_nif/1, tgetnum_nif/1, tgetflag_nif/1, tgetstr_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/2, tgoto/3]).
@@ -218,7 +220,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(
@@ -228,6 +230,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 }) ->
@@ -252,7 +259,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;
@@ -421,14 +433,15 @@ 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 = case os:type() of
- {unix, _} -> utf8;
+ {unix, _} -> Encoding;
{win32, _} ->
case isatty(stdin) of
true ->
@@ -436,7 +449,7 @@ reader([TTY, Parent]) ->
_ ->
%% When not reading from a console
%% the data read is utf8 encoded
- utf8
+ Encoding
end
end,
reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, <<>>).
@@ -448,20 +461,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
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} ->
@@ -471,7 +484,7 @@ reader_loop(TTY, Parent, SignalRef, ReaderRef, FromEnc, Acc) ->
ok;
{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} =
@@ -486,7 +499,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),
{<>, <<>>, latin1};
@@ -496,7 +509,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.
@@ -518,18 +531,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
diff --git a/lib/kernel/src/user_drv.erl b/lib/kernel/src/user_drv.erl
index 25ebcbdd681b..0bc27e76ee88 100644
--- a/lib/kernel/src/user_drv.erl
+++ b/lib/kernel/src/user_drv.erl
@@ -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
@@ -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 }) ->
diff --git a/lib/kernel/test/Makefile b/lib/kernel/test/Makefile
index 0d88e3555e25..1d1c17776d92 100644
--- a/lib/kernel/test/Makefile
+++ b/lib/kernel/test/Makefile
@@ -150,7 +150,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
diff --git a/lib/kernel/test/tty.cover b/lib/kernel/test/tty.cover
new file mode 100644
index 000000000000..cf4d26ea8e1a
--- /dev/null
+++ b/lib/kernel/test/tty.cover
@@ -0,0 +1,3 @@
+%% -*- erlang -*-
+{incl_mods,[prim_tty, user_drv, group, shell, edlin, edlin_expand, io_lib]}.
+
diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl
index 5f45165968f2..87010361c050 100644
--- a/lib/stdlib/src/io_lib.erl
+++ b/lib/stdlib/src/io_lib.erl
@@ -809,41 +809,51 @@ collect_chars(Tag, Data, N) ->
%% Now we are aware of encoding...
collect_chars(start, Data, unicode, N) when is_binary(Data), is_integer(N) ->
{Size,Npos} = count_and_find_utf8(Data,N),
- if Size >= N ->
+ if Size > N ->
{B1,B2} = split_binary(Data, Npos),
{stop,B1,B2};
Size < N ->
- {binary,[Data],N-Size}
+ {binary,[Data],N-Size};
+ true ->
+ {stop,Data,<<>>}
end;
collect_chars(start, Data, latin1, N) when is_binary(Data), is_integer(N) ->
Size = byte_size(Data),
- if Size >= N ->
+ if Size > N ->
{B1,B2} = split_binary(Data, N),
{stop,B1,B2};
Size < N ->
- {binary,[Data],N-Size}
+ {binary,[Data],N-Size};
+ true ->
+ {stop,Data,<<>>}
end;
collect_chars(start,Data,_,N) when is_list(Data), is_integer(N) ->
collect_chars_list([], N, Data);
collect_chars(start, eof, _,_) ->
{stop,eof,eof};
+collect_chars({binary,[<<>>],_N}, eof, _,_) ->
+ {stop,eof,eof};
collect_chars({binary,Stack,_N}, eof, _,_) ->
{stop,binrev(Stack),eof};
collect_chars({binary,Stack,N}, Data,unicode, _) when is_integer(N) ->
{Size,Npos} = count_and_find_utf8(Data,N),
- if Size >= N ->
+ if Size > N ->
{B1,B2} = split_binary(Data, Npos),
{stop,binrev(Stack, [B1]),B2};
Size < N ->
- {binary,[Data|Stack],N-Size}
+ {binary,[Data|Stack],N-Size};
+ true ->
+ {stop,binrev(Stack, [Data]),<<>>}
end;
collect_chars({binary,Stack,N}, Data,latin1, _) when is_integer(N) ->
Size = byte_size(Data),
- if Size >= N ->
+ if Size > N ->
{B1,B2} = split_binary(Data, N),
{stop,binrev(Stack, [B1]),B2};
Size < N ->
- {binary,[Data|Stack],N-Size}
+ {binary,[Data|Stack],N-Size};
+ true ->
+ {stop,binrev(Stack, [Data]),<<>>}
end;
collect_chars({list,Stack,N}, Data, _,_) when is_integer(N) ->
collect_chars_list(Stack, N, Data);
@@ -871,6 +881,8 @@ collect_chars1(N, [], Stack) ->
collect_chars_list(Stack, 0, Data) ->
{stop,lists:reverse(Stack, []),Data};
+collect_chars_list([], _N, eof) ->
+ {stop,eof,eof};
collect_chars_list(Stack, _N, eof) ->
{stop,lists:reverse(Stack, []),eof};
collect_chars_list(Stack, N, []) ->
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index 259715700448..98a7a03caa63 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -133,7 +133,7 @@ ERL_COMPILE_FLAGS := $(filter-out +deterministic,$(ERL_COMPILE_FLAGS))
EBIN = .
EMAKEFILE=Emakefile
-COVERFILE=stdlib.cover
+COVERFILE=stdlib.cover tty.cover
# ----------------------------------------------------
# Targets
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index 368fdbdf0135..2e6ba632e0c0 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -25,7 +25,12 @@
-export([setopts_getopts/1,unicode_options/1,unicode_options_gen/1,
binary_options/1, read_modes_gl/1,
read_modes_ogl/1, broken_unicode/1,eof_on_pipe/1,
- unicode_prompt/1, shell_slogan/1, raw_stdout/1, raw_stdout_isatty/1]).
+ unicode_prompt/1, shell_slogan/1, raw_stdout/1, raw_stdout_isatty/1,
+ file_read_stdin_binary_mode/1, file_read_stdin_list_mode/1,
+ io_get_chars_stdin_binary_mode/1, io_get_chars_stdin_list_mode/1,
+ io_get_chars_file_read_stdin_binary_mode/1,
+ file_read_stdin_latin1_mode/1
+ ]).
-export([io_server_proxy/1,start_io_server_proxy/0, proxy_getall/1,
@@ -35,7 +40,7 @@
-export([uprompt/1, slogan/0, session_slogan/0]).
--export([write_raw_to_stdout/0]).
+-export([write_raw_to_stdout/0, read_raw_from_stdin/1]).
%%-define(debug, true).
@@ -53,7 +58,14 @@ all() ->
[setopts_getopts, unicode_options, unicode_options_gen,
binary_options, read_modes_gl, read_modes_ogl,
broken_unicode, eof_on_pipe, unicode_prompt,
- shell_slogan, raw_stdout, raw_stdout_isatty].
+ shell_slogan, raw_stdout, raw_stdout_isatty,
+ file_read_stdin_binary_mode,
+ file_read_stdin_list_mode,
+ io_get_chars_stdin_binary_mode,
+ io_get_chars_stdin_list_mode,
+ io_get_chars_file_read_stdin_binary_mode,
+ file_read_stdin_latin1_mode
+ ].
groups() ->
[].
@@ -269,6 +281,163 @@ setopts_getopts(Config) when is_list(Config) ->
],[],"",["-oldshell"]),
ok.
+%% Test that reading from stdin using file:read works when io is in binary mode
+file_read_stdin_binary_mode(_Config) ->
+ {ok, P, ErlPort} = start_stdin_node(fun() -> file:read(standard_io, 3) end, [binary]),
+
+ erlang:port_command(ErlPort, "abc"),
+ {ok, "got: <<\"abc\">>\n"} = gen_tcp:recv(P, 0),
+ erlang:port_command(ErlPort, "def"),
+ {ok, "got: <<\"def\">>\n"} = gen_tcp:recv(P, 0),
+ ErlPort ! {self(), close},
+ {ok, "got: eof"} = gen_tcp:recv(P, 0),
+
+ ok.
+
+%% Test that reading from stdin using file:read works when io is in binary mode
+file_read_stdin_list_mode(_Config) ->
+ {ok, P, ErlPort} = start_stdin_node(fun() -> file:read(standard_io, 3) end, [list]),
+
+ erlang:port_command(ErlPort, "abc"),
+ {ok, "got: \"abc\"\n"} = gen_tcp:recv(P, 0),
+ erlang:port_command(ErlPort, "def"),
+ {ok, "got: \"def\"\n"} = gen_tcp:recv(P, 0),
+ ErlPort ! {self(), close},
+ {ok, "got: eof"} = gen_tcp:recv(P, 0),
+
+ ok.
+
+%% Test that reading from stdin using file:read works when io is in binary mode
+io_get_chars_stdin_binary_mode(_Config) ->
+ {ok, P, ErlPort} = start_stdin_node(
+ fun() ->
+ case io:get_chars(standard_io, "", 1) of
+ eof -> eof;
+ Chars -> {ok, Chars}
+ end
+ end, [binary]),
+
+ erlang:port_command(ErlPort, "x\n"),
+ {ok, "got: <<\"x\">>\n"} = gen_tcp:recv(P, 0),
+ {ok, "got: <<\"\\n\">>\n"} = gen_tcp:recv(P, 0),
+ ErlPort ! {self(), close},
+ {ok, "got: eof"} = gen_tcp:recv(P, 0),
+
+ ok.
+
+%% Test that reading from stdin using file:read works when io is in binary mode
+io_get_chars_stdin_list_mode(_Config) ->
+ {ok, P, ErlPort} = start_stdin_node(
+ fun() -> case io:get_chars(standard_io, "", 1) of
+ eof -> eof;
+ Chars -> {ok, Chars}
+ end
+ end, [list]),
+
+ erlang:port_command(ErlPort, "x\n"),
+ {ok, "got: \"x\"\n"} = gen_tcp:recv(P, 0),
+ {ok, "got: \"\\n\"\n"} = gen_tcp:recv(P, 0),
+ ErlPort ! {self(), close},
+ {ok, "got: eof"} = gen_tcp:recv(P, 0),
+
+ ok.
+
+%% Test that mixing io:get_chars and file:read works when stdin is in binary mode.
+io_get_chars_file_read_stdin_binary_mode(_Config) ->
+ {ok, P, ErlPort} = start_stdin_node(
+ fun() -> case file:read(standard_io, 1) of
+ eof -> eof;
+ {ok, Chars} ->
+ case io:get_line(standard_io, "") of
+ eof -> Chars;
+ Line ->
+ {ok, [Chars, Line]}
+ end
+ end
+ end, [binary]),
+
+ erlang:port_command(ErlPort, "1\n"),
+ {ok, "got: [<<\"1\">>,<<\"\\n\">>]\n"} = gen_tcp:recv(P, 0),
+ ErlPort ! {self(), close},
+ {ok, "got: eof"} = gen_tcp:recv(P, 0),
+
+ ok.
+
+%% Test that reading from stdin using file:read_line works when io is not utf8
+file_read_stdin_latin1_mode(_Config) ->
+ {ok, P, ErlPort} = start_stdin_node(
+ fun() -> file:read_line(standard_io) end,
+ [binary],
+ "-kernel standard_io_encoding latin1"),
+
+ %% Invalid utf8
+ erlang:port_command(ErlPort, <<192,128,10,192,128,10,192,128,10>>),
+
+ {ok, "got: <<192,128,10>>\n"} = gen_tcp:recv(P, 0, 5000),
+ {ok, "got: <<192,128,10>>\n"} = gen_tcp:recv(P, 0, 5000),
+ {ok, "got: <<192,128,10>>\n"} = gen_tcp:recv(P, 0, 5000),
+ ErlPort ! {self(), close},
+ {ok, "got: eof"} = gen_tcp:recv(P, 0, 5000),
+
+ {ok, P2, ErlPort2} = start_stdin_node(
+ fun() -> file:read(standard_io, 5) end,
+ [binary],
+ "-kernel standard_io_encoding latin1"),
+
+ %% Valid utf8
+ erlang:port_command(ErlPort2, <<"duπaduπaduπa"/utf8>>),
+
+ {ok, "got: <<100,117,207,128,97>>\n"} = gen_tcp:recv(P2, 0, 5000),
+ {ok, "got: <<100,117,207,128,97>>\n"} = gen_tcp:recv(P2, 0, 5000),
+ {ok, "got: <<100,117,207,128,97>>\n"} = gen_tcp:recv(P2, 0, 5000),
+ ErlPort2 ! {self(), close},
+ {ok, "got: eof"} = gen_tcp:recv(P2, 0, 5000),
+
+ ok.
+
+start_stdin_node(ReadFun, IoOptions) ->
+ start_stdin_node(ReadFun, IoOptions, "").
+start_stdin_node(ReadFun, IoOptions, ExtraArgs) ->
+ {ok, L} = gen_tcp:listen(0,[{active, false},{packet,4}]),
+ {ok, Port} = inet:port(L),
+ Cmd = lists:append(
+ [ct:get_progname(),
+ " -noshell ",
+ ExtraArgs,
+ " -pa ", filename:dirname(code:which(?MODULE)),
+ " -s ", atom_to_list(?MODULE), " read_raw_from_stdin ", integer_to_list(Port)]),
+ ct:log("~p~n", [Cmd]),
+ ErlPort = open_port({spawn, Cmd}, [stream, eof]),
+ {ok, P} = gen_tcp:accept(L),
+ gen_tcp:send(P, term_to_binary(IoOptions)),
+ gen_tcp:send(P, term_to_binary(ReadFun)),
+ {ok, P, ErlPort}.
+
+read_raw_from_stdin([Port]) ->
+ try
+ {ok, P} = gen_tcp:connect(localhost, list_to_integer(atom_to_list(Port)),
+ [binary, {packet, 4}, {active, false}]),
+ {ok, OptionsBin} = gen_tcp:recv(P, 0),
+ io:setopts(standard_io, binary_to_term(OptionsBin)),
+ {ok, ReadFunBin} = gen_tcp:recv(P, 0),
+ spawn(fun() ->
+ gen_tcp:recv(P, 0),
+ init:stop("crash")
+ end),
+ read_raw_from_stdin(binary_to_term(ReadFunBin), P)
+ catch E:R:ST ->
+ io:format(standard_error, "~p ~p",[Port,{E,R,ST}])
+ end.
+read_raw_from_stdin(ReadFun, P) ->
+ case ReadFun() of
+ eof ->
+ gen_tcp:send(P, "got: eof"),
+ init:stop();
+ {ok, Char} ->
+ gen_tcp:send(P, unicode:characters_to_binary(
+ io_lib:format("got: ~p\n",[Char]))),
+ read_raw_from_stdin(ReadFun, P)
+ end.
get_lc_ctype() ->
case {os:type(),os:version()} of
diff --git a/lib/stdlib/test/tty.cover b/lib/stdlib/test/tty.cover
new file mode 120000
index 000000000000..841833897bae
--- /dev/null
+++ b/lib/stdlib/test/tty.cover
@@ -0,0 +1 @@
+../../../lib/kernel/test/tty.cover
\ No newline at end of file