Skip to content

Commit 49ae08a

Browse files
committed
kernel: Add possibility to disable prompt redrawing
When stdout is used as both a terminal and as the main logging mechanism, redrawing the prompt will cause a lot of ANSI characters to be printed to the log when the prompt is redrawn. So we add this options for systems that have a hard time migrating away. It is only available in Erlang/OTP 26 as a temporary measure as in the long run no system should be using stdout as a logging mechanism and terminal at the same time.
1 parent c1805ad commit 49ae08a

File tree

4 files changed

+64
-8
lines changed

4 files changed

+64
-8
lines changed

lib/kernel/src/group.erl

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -818,9 +818,14 @@ more_data(What, Cont0, Drv, Shell, Ls, Encoding) ->
818818
get_line1(edlin:edit_line(eof, Cont0), Drv, Shell, Ls, Encoding);
819819
{io_request,From,ReplyAs,Req} when is_pid(From) ->
820820
{more_chars,Cont,_More} = edlin:edit_line([], Cont0),
821-
send_drv_reqs(Drv, edlin:erase_line()),
822-
io_request(Req, From, ReplyAs, Drv, Shell, []), %WRONG!!!
823-
send_drv_reqs(Drv, edlin:redraw_line(Cont)),
821+
case application:get_env(stdlib, shell_redraw_prompt_on_output, true) of
822+
true ->
823+
send_drv_reqs(Drv, edlin:erase_line()),
824+
io_request(Req, From, ReplyAs, Drv, Shell, []),
825+
send_drv_reqs(Drv, edlin:redraw_line(Cont));
826+
false ->
827+
io_request(Req, From, ReplyAs, Drv, Shell, [])
828+
end,
824829
get_line1({more_chars,Cont,[]}, Drv, Shell, Ls, Encoding);
825830
{reply,{From,ReplyAs},Reply} ->
826831
%% We take care of replies from puts here as well

lib/kernel/src/prim_tty.erl

Lines changed: 13 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -137,6 +137,7 @@
137137
reader :: {pid(), reference()} | undefined,
138138
writer :: {pid(), reference()} | undefined,
139139
options,
140+
redraw_prompt_on_output = true,
140141
unicode = true :: boolean(),
141142
lines_before = [], %% All lines before the current line in reverse order
142143
lines_after = [], %% All lines after the current line.
@@ -236,8 +237,11 @@ init(UserOptions) when is_map(UserOptions) ->
236237
IOEncoding =:= unicode -> true;
237238
true -> UnicodeSupported
238239
end,
240+
RedrawPrompt = application:get_env(stdlib, shell_redraw_prompt_on_output, true),
239241
{ok, ANSI_RE_MP} = re:compile(?ANSI_REGEXP, [unicode]),
240-
init_term(#state{ tty = TTY, unicode = UnicodeMode, options = Options, ansi_regexp = ANSI_RE_MP }).
242+
init_term(#state{ tty = TTY, unicode = UnicodeMode, options = Options,
243+
ansi_regexp = ANSI_RE_MP,
244+
redraw_prompt_on_output = RedrawPrompt }).
241245
init_term(State = #state{ tty = TTY, options = Options }) ->
242246
TTYState =
243247
case maps:get(tty, Options) of
@@ -631,15 +635,19 @@ handle_request(State, {expand_with_trim, Binary}) ->
631635
handle_request(State,
632636
{expand, iolist_to_binary(["\r\n",string:trim(Binary, both)])});
633637
%% putc prints Binary and overwrites any existing characters
634-
handle_request(State = #state{ unicode = U }, {putc, Binary}) ->
638+
handle_request(State = #state{ redraw_prompt_on_output = RedrawOnOutput,
639+
unicode = U }, {putc, Binary}) ->
635640
%% Todo should handle invalid unicode?
636641
%% print above the prompt if we have a prompt.
637642
%% otherwise print on the current line.
638-
case {State#state.lines_before,{State#state.buffer_before, State#state.buffer_after}, State#state.lines_after} of
639-
{[],{[],[]},[]} ->
643+
if State#state.lines_before =:= [] andalso
644+
State#state.buffer_before =:= [] andalso
645+
State#state.buffer_after =:= [] andalso
646+
State#state.lines_after =:= [];
647+
not RedrawOnOutput ->
640648
{PutBuffer, _} = insert_buf(State, Binary),
641649
{[encode(PutBuffer, U)], State};
642-
_ ->
650+
true ->
643651
{Delete, DeletedState} = handle_request(State, delete_line),
644652
{PutBuffer, _} = insert_buf(DeletedState, Binary),
645653
{Redraw, _} = handle_request(State, redraw_prompt_pre_deleted),

lib/kernel/test/interactive_shell_SUITE.erl

Lines changed: 36 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -59,6 +59,7 @@
5959
shell_expand_location_below/1,
6060
shell_update_window_unicode_wrap/1,
6161
shell_receive_standard_out/1,
62+
shell_receive_user_output/1,
6263
shell_standard_error_nlcr/1, shell_clear/1,
6364
remsh_basic/1, remsh_error/1, remsh_longnames/1, remsh_no_epmd/1,
6465
remsh_expand_compatibility_25/1, remsh_expand_compatibility_later_version/1,
@@ -136,6 +137,7 @@ groups() ->
136137
shell_update_window, shell_small_window_multiline_navigation, shell_huge_input,
137138
shell_support_ansi_input,
138139
shell_receive_standard_out,
140+
shell_receive_user_output,
139141
shell_standard_error_nlcr,
140142
shell_expand_location_above,
141143
shell_expand_location_below,
@@ -987,6 +989,40 @@ shell_receive_standard_out(Config) ->
987989
ok
988990
after
989991
stop_tty(Term)
992+
end,
993+
Term2 = start_tty([{args,["-stdlib","shell_redraw_prompt_on_output","false"]}|Config]),
994+
try
995+
send_tty(Term2,"my_fun(5) -> ok; my_fun(N) -> receive after 100 -> io:format(\"~p\\n\", [N]), my_fun(N+1) end.\n"),
996+
send_tty(Term2,"spawn(shell_default, my_fun, [0]). ABC\n"),
997+
timer:sleep(1000),
998+
check_location(Term2, {0,-18}), %% Check that the prompt is not redrawn, cursor is at the beginning of the line
999+
check_content(Term2, "..0\\s+1\\s+2\\s+3\\s+4"),
1000+
ok
1001+
after
1002+
stop_tty(Term2)
1003+
end.
1004+
shell_receive_user_output(Config) ->
1005+
Term = start_tty(Config),
1006+
try
1007+
send_tty(Term,"my_fun(5) -> ok; my_fun(N) -> timer:sleep(100), io:format(user, \"~p\\n\", [N]), my_fun(N+1).\n"),
1008+
send_tty(Term, "spawn(shell_default, my_fun, [0]). ABC\n"),
1009+
timer:sleep(1000),
1010+
check_location(Term, {0, 0}), %% Check that we are at the same location relative to the start.
1011+
check_content(Term, "3\\s+4\\s+.+>\\sABC"),
1012+
ok
1013+
after
1014+
stop_tty(Term)
1015+
end,
1016+
Term2 = start_tty([{args,["-stdlib","shell_redraw_prompt_on_output","false"]}|Config]),
1017+
try
1018+
send_tty(Term2,"my_fun(5) -> ok; my_fun(N) -> timer:sleep(100), io:format(user, \"~p\\n\", [N]), my_fun(N+1).\n"),
1019+
send_tty(Term2,"spawn(shell_default, my_fun, [0]). ABC\n"),
1020+
timer:sleep(1000),
1021+
check_location(Term2, {0,-18}), %% Check that we are at the same location relative to the start.
1022+
check_content(Term2, "..0\\s+1\\s+2\\s+3\\s+4"),
1023+
ok
1024+
after
1025+
stop_tty(Term2)
9901026
end.
9911027
%% Test that the shell works when invalid utf-8 (aka latin1) is sent to it
9921028
shell_invalid_unicode(Config) ->

lib/stdlib/doc/src/stdlib_app.xml

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -62,6 +62,13 @@
6262
<p>Sets where the tab expansion text should appear in the shell.
6363
The default is <c>below</c>.</p>
6464
</item>
65+
<tag><marker id="shell_redraw_prompt_on_output"/><c>shell_redraw_prompt_on_output = boolean()</c></tag>
66+
<item>
67+
<p>Sets whether the shell should redraw the prompt when it receives output from other processes.
68+
This setting can be useful if you use <c>run_erl</c> to for logging as redrawing the prompt will
69+
emit a lot of ANSI escape characters that you normally do not want in a log.
70+
The default is <c>true</c>.</p>
71+
</item>
6572
<tag><marker id="shell_history_length"/><c>shell_history_length = integer() >= 0</c></tag>
6673
<item>
6774
<p>Can be used to determine how many commands are saved by the Erlang

0 commit comments

Comments
 (0)