File 0190-stdlib-fix-automatic-newline-in-shell.patch of Package erlang
From 2e55a2b167c142ea62be4ee76d2cb582cdc466bf Mon Sep 17 00:00:00 2001
From: Fredrik Frantzen <frazze@erlang.org>
Date: Tue, 28 Oct 2025 13:35:22 +0100
Subject: [PATCH] stdlib: fix automatic newline in shell
---
lib/kernel/src/prim_tty.erl | 16 +++++++++++++++-
lib/kernel/test/interactive_shell_SUITE.erl | 14 +++++++++++++-
2 files changed, 28 insertions(+), 2 deletions(-)
diff --git a/lib/kernel/src/prim_tty.erl b/lib/kernel/src/prim_tty.erl
index a945780171..f438f9f816 100644
--- a/lib/kernel/src/prim_tty.erl
+++ b/lib/kernel/src/prim_tty.erl
@@ -831,7 +831,8 @@ handle_request(State = #state{ unicode = U }, {putc, Binary}) ->
end,
Moves = move_cursor(State, State#state.cols, ToCol)
end,
- Binary1 = if PutcBufferState#state.putc_buffer =:= <<>> ->
+ BinaryNoAnsi = remove_ansi_sequences(PutcBufferState#state.putc_buffer),
+ Binary1 = if BinaryNoAnsi =:= <<>> ->
%% Binary has a real new line at the end
Binary;
true ->
@@ -1014,6 +1015,19 @@ handle_request(State, Req) ->
erlang:display({unhandled_request, Req}),
{"", State}.
+remove_ansi_sequences(<<27,Bin/binary>>) ->
+ Bins = binary:split(Bin, <<27>>, [global]),
+ remove_ansi_sequences1([<<27,B/binary>> || B <- Bins],[]);
+remove_ansi_sequences(Bin) ->
+ [Acc|Bins] = binary:split(Bin, <<27>>, [global]),
+ remove_ansi_sequences1([<<27,B/binary>> || B <- Bins],[Acc]).
+remove_ansi_sequences1([Bin|Bins], Acc) ->
+ {match, [{0, N}]} = re:run(Bin, ansi_regexp()),
+ <<_:N/binary, AnsiRest/binary>> = Bin,
+ remove_ansi_sequences1(Bins, [AnsiRest|Acc]);
+remove_ansi_sequences1([], Acc) ->
+ list_to_binary(lists:reverse(Acc)).
+
last_or_empty([]) -> [];
last_or_empty([H]) -> H;
last_or_empty(L) -> [H|_] = lists:reverse(L), H.
diff --git a/lib/kernel/test/interactive_shell_SUITE.erl b/lib/kernel/test/interactive_shell_SUITE.erl
index 38d4cb8df7..9a6841f20b 100644
--- a/lib/kernel/test/interactive_shell_SUITE.erl
+++ b/lib/kernel/test/interactive_shell_SUITE.erl
@@ -72,7 +72,8 @@
remsh_expand_compatibility_25/1, remsh_expand_compatibility_later_version/1,
external_editor/1, external_editor_visual/1,
external_editor_unicode/1, shell_ignore_pager_commands/1,
- shell_escape_sequence_end_of_prompt_followed_by_unicode/1]).
+ shell_escape_sequence_end_of_prompt_followed_by_unicode/1,
+ shell_output_automatic_newline_ansi_escape_sequence/1]).
-export([get_until/2]).
@@ -159,6 +160,7 @@ groups() ->
[{group,tty_tests},
shell_invalid_unicode,
shell_escape_sequence_end_of_prompt_followed_by_unicode,
+ shell_output_automatic_newline_ansi_escape_sequence,
external_editor_unicode
%% unicode wrapping does not work right yet
%% shell_unicode_wrap,
@@ -1418,7 +1420,17 @@ shell_escape_sequence_end_of_prompt_followed_by_unicode(Config) ->
shell_test_lib:stop_tty(Term),
ok
end.
+shell_output_automatic_newline_ansi_escape_sequence(Config) ->
+ Term = start_tty(Config),
+ try
+ shell_test_lib:send_tty(Term,"spawn(fun() -> receive after 1000 -> ok end, io:put_chars([\"omg\\n\", <<27,91,48,109>>]) end).\n"),
+ shell_test_lib:check_content(Term, "omg\n\\("),
+ ok
+ after
+ shell_test_lib:stop_tty(Term),
+ ok
+ end.
%% Test the we can handle invalid ansi escape chars.
%% tmux cannot handle this... so we test this using to_erl
shell_invalid_ansi(_Config) ->
--
2.51.0