Skip to content

Commit

Permalink
Merge branch 'lukas/kernel/add-prompt-redraw-option/OTP-19213' into m…
Browse files Browse the repository at this point in the history
…aint-26

* lukas/kernel/add-prompt-redraw-option/OTP-19213:
  kernel: Add possibility to disable prompt redrawing
  • Loading branch information
Erlang/OTP committed Sep 4, 2024
2 parents d5b27cb + 49ae08a commit ba0e816
Show file tree
Hide file tree
Showing 4 changed files with 64 additions and 8 deletions.
11 changes: 8 additions & 3 deletions lib/kernel/src/group.erl
Original file line number Diff line number Diff line change
Expand Up @@ -827,9 +827,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
Expand Down
18 changes: 13 additions & 5 deletions lib/kernel/src/prim_tty.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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.
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -631,15 +635,19 @@ handle_request(State, {expand_with_trim, Binary}) ->
handle_request(State,
{expand, iolist_to_binary(["\r\n",string:trim(Binary, both)])});
%% 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),
Expand Down
36 changes: 36 additions & 0 deletions lib/kernel/test/interactive_shell_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
remsh_basic/1, remsh_error/1, remsh_longnames/1, remsh_no_epmd/1,
remsh_expand_compatibility_25/1, remsh_expand_compatibility_later_version/1,
Expand Down Expand Up @@ -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,
Expand Down Expand Up @@ -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) ->
Expand Down
7 changes: 7 additions & 0 deletions lib/stdlib/doc/src/stdlib_app.xml
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,13 @@
<p>Sets where the tab expansion text should appear in the shell.
The default is <c>below</c>.</p>
</item>
<tag><marker id="shell_redraw_prompt_on_output"/><c>shell_redraw_prompt_on_output = boolean()</c></tag>
<item>
<p>Sets whether the shell should redraw the prompt when it receives output from other processes.
This setting can be useful if you use <c>run_erl</c> 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 <c>true</c>.</p>
</item>
<tag><marker id="shell_history_length"/><c>shell_history_length = integer() >= 0</c></tag>
<item>
<p>Can be used to determine how many commands are saved by the Erlang
Expand Down

0 comments on commit ba0e816

Please sign in to comment.