File 0289-kernel-Add-possibility-to-disable-prompt-redrawing.patch of Package erlang
From 49ae08aa2707432527c834eea2c0a16b263b0dcb Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Fri, 30 Aug 2024 10:02:13 +0200
Subject: [PATCH] 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.
---
lib/kernel/src/group.erl | 11 +++++--
lib/kernel/src/prim_tty.erl | 18 ++++++++---
lib/kernel/test/interactive_shell_SUITE.erl | 36 +++++++++++++++++++++
lib/stdlib/doc/src/stdlib_app.xml | 7 ++++
4 files changed, 64 insertions(+), 8 deletions(-)
diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl
index 1792ffe2fb..eb2025abb7 100644
--- a/lib/kernel/src/group.erl
+++ b/lib/kernel/src/group.erl
@@ -818,9 +818,14 @@ more_data(What, Cont0, Drv, Shell, Ls, Encoding) ->
get_line1(edlin:edit_line(eof, Cont0), Drv, Shell, Ls, Encoding);
{io_request,From,ReplyAs,Req} when is_pid(From) ->
{more_chars,Cont,_More} = edlin:edit_line([], Cont0),
- send_drv_reqs(Drv, edlin:erase_line()),
- io_request(Req, From, ReplyAs, Drv, Shell, []), %WRONG!!!
- send_drv_reqs(Drv, edlin:redraw_line(Cont)),
+ case application:get_env(stdlib, shell_redraw_prompt_on_output, true) of
+ true ->
+ send_drv_reqs(Drv, edlin:erase_line()),
+ io_request(Req, From, ReplyAs, Drv, Shell, []),
+ send_drv_reqs(Drv, edlin:redraw_line(Cont));
+ false ->
+ io_request(Req, From, ReplyAs, Drv, Shell, [])
+ end,
get_line1({more_chars,Cont,[]}, Drv, Shell, Ls, Encoding);
{reply,{From,ReplyAs},Reply} ->
%% We take care of replies from puts here as well
diff --git a/lib/kernel/src/prim_tty.erl b/lib/kernel/src/prim_tty.erl
index 5b402c0236..c5891eeb97 100644
--- a/lib/kernel/src/prim_tty.erl
+++ b/lib/kernel/src/prim_tty.erl
@@ -137,6 +137,7 @@
reader :: {pid(), reference()} | undefined,
writer :: {pid(), reference()} | undefined,
options,
+ redraw_prompt_on_output = true,
unicode = true :: boolean(),
lines_before = [], %% All lines before the current line in reverse order
lines_after = [], %% All lines after the current line.
@@ -236,8 +237,11 @@ init(UserOptions) when is_map(UserOptions) ->
IOEncoding =:= unicode -> true;
true -> UnicodeSupported
end,
+ RedrawPrompt = application:get_env(stdlib, shell_redraw_prompt_on_output, true),
{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{ tty = TTY, unicode = UnicodeMode, options = Options,
+ ansi_regexp = ANSI_RE_MP,
+ redraw_prompt_on_output = RedrawPrompt }).
init_term(State = #state{ tty = TTY, options = Options }) ->
TTYState =
case maps:get(tty, Options) of
@@ -631,15 +635,19 @@ handle_request(State, {expand, Expand, N}) ->
{_, NewState} = insert_buf(State#state{buffer_expand = []}, Expand),
handle_request(NewState#state{buffer_expand_limit = N}, redraw_prompt);
%% putc prints Binary and overwrites any existing characters
-handle_request(State = #state{ unicode = U }, {putc, Binary}) ->
+handle_request(State = #state{ redraw_prompt_on_output = RedrawOnOutput,
+ unicode = U }, {putc, Binary}) ->
%% Todo should handle invalid unicode?
%% print above the prompt if we have a prompt.
%% otherwise print on the current line.
- case {State#state.lines_before,{State#state.buffer_before, State#state.buffer_after}, State#state.lines_after} of
- {[],{[],[]},[]} ->
+ if State#state.lines_before =:= [] andalso
+ State#state.buffer_before =:= [] andalso
+ State#state.buffer_after =:= [] andalso
+ State#state.lines_after =:= [];
+ not RedrawOnOutput ->
{PutBuffer, _} = insert_buf(State, Binary),
{[encode(PutBuffer, U)], State};
- _ ->
+ true ->
{Delete, DeletedState} = handle_request(State, delete_line),
{PutBuffer, _} = insert_buf(DeletedState, Binary),
{Redraw, _} = handle_request(State, redraw_prompt_pre_deleted),
diff --git a/lib/kernel/test/interactive_shell_SUITE.erl b/lib/kernel/test/interactive_shell_SUITE.erl
index c3a685622b..17b92b8d60 100644
--- a/lib/kernel/test/interactive_shell_SUITE.erl
+++ b/lib/kernel/test/interactive_shell_SUITE.erl
@@ -59,6 +59,7 @@
shell_expand_location_below/1,
shell_update_window_unicode_wrap/1,
shell_receive_standard_out/1,
+ shell_receive_user_output/1,
shell_standard_error_nlcr/1, shell_clear/1,
shell_format/1, shell_help/1,
remsh_basic/1, remsh_error/1, remsh_longnames/1, remsh_no_epmd/1,
@@ -136,6 +137,7 @@ groups() ->
shell_update_window, shell_small_window_multiline_navigation, shell_huge_input,
shell_support_ansi_input,
shell_receive_standard_out,
+ shell_receive_user_output,
shell_standard_error_nlcr,
shell_expand_location_above,
shell_expand_location_below,
@@ -987,6 +989,40 @@ shell_receive_standard_out(Config) ->
ok
after
stop_tty(Term)
+ end,
+ Term2 = start_tty([{args,["-stdlib","shell_redraw_prompt_on_output","false"]}|Config]),
+ try
+ send_tty(Term2,"my_fun(5) -> ok; my_fun(N) -> receive after 100 -> io:format(\"~p\\n\", [N]), my_fun(N+1) end.\n"),
+ send_tty(Term2,"spawn(shell_default, my_fun, [0]). ABC\n"),
+ timer:sleep(1000),
+ check_location(Term2, {0,-18}), %% Check that the prompt is not redrawn, cursor is at the beginning of the line
+ check_content(Term2, "..0\\s+1\\s+2\\s+3\\s+4"),
+ ok
+ after
+ stop_tty(Term2)
+ end.
+shell_receive_user_output(Config) ->
+ Term = start_tty(Config),
+ try
+ send_tty(Term,"my_fun(5) -> ok; my_fun(N) -> timer:sleep(100), io:format(user, \"~p\\n\", [N]), my_fun(N+1).\n"),
+ send_tty(Term, "spawn(shell_default, my_fun, [0]). ABC\n"),
+ timer:sleep(1000),
+ check_location(Term, {0, 0}), %% Check that we are at the same location relative to the start.
+ check_content(Term, "3\\s+4\\s+.+>\\sABC"),
+ ok
+ after
+ stop_tty(Term)
+ end,
+ Term2 = start_tty([{args,["-stdlib","shell_redraw_prompt_on_output","false"]}|Config]),
+ try
+ send_tty(Term2,"my_fun(5) -> ok; my_fun(N) -> timer:sleep(100), io:format(user, \"~p\\n\", [N]), my_fun(N+1).\n"),
+ send_tty(Term2,"spawn(shell_default, my_fun, [0]). ABC\n"),
+ timer:sleep(1000),
+ check_location(Term2, {0,-18}), %% Check that we are at the same location relative to the start.
+ check_content(Term2, "..0\\s+1\\s+2\\s+3\\s+4"),
+ ok
+ after
+ stop_tty(Term2)
end.
%% Test that the shell works when invalid utf-8 (aka latin1) is sent to it
shell_invalid_unicode(Config) ->
diff --git a/lib/stdlib/doc/stdlib_app.md b/lib/stdlib/doc/stdlib_app.md
index e12bc8b17f..96696b76a4 100644
--- a/lib/stdlib/doc/stdlib_app.md
+++ b/lib/stdlib/doc/stdlib_app.md
@@ -45,6 +45,13 @@ For more information about configuration
`below`. This will open a pager below the cursor that is scrollable one line
at a time with `Up/Down` arrow keys or 5 lines at a time with `PgUp/PgDn`.
+- **`shell_redraw_prompt_on_output = boolean()`{:
+ #shell_redraw_prompt_on_output }** - Sets whether the shell should redraw
+ the prompt when it receives output from other processes. This setting can be
+ useful if you use `run_erl` to for logging as redrawing the prompt will emit
+ a lot of ANSI escape characters that you normally do not want in a log.
+ The default is `true`.
+
- **`shell_history_length = integer() >= 0`{: #shell_history_length }** - Can be
used to determine how many commands are saved by the Erlang shell. See
`m:edlin` for more.
--
2.43.0