File 3151-kernel-Remove-handling-for-special-characters-when-n.patch of Package erlang

From e3e4f63453f7aab941a39013b0c026f32a88c954 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Wed, 17 Apr 2024 17:04:40 +0200
Subject: [PATCH 1/2] kernel: Remove handling for special characters when
 -noshell is passed

---
 lib/kernel/src/group.erl           | 45 ++++++++++++++++++++++++------
 lib/kernel/src/user_drv.erl        |  3 +-
 lib/stdlib/test/io_proto_SUITE.erl | 15 ++++++++++
 3 files changed, 54 insertions(+), 9 deletions(-)

diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl
index 0cfe702b98..a422fa2fd4 100644
--- a/lib/kernel/src/group.erl
+++ b/lib/kernel/src/group.erl
@@ -48,12 +48,20 @@ server(Ancestors, Drv, Shell, Options) ->
     edlin:init(),
     put(read_mode, list),
     put(user_drv, Drv),
+
     ExpandFun = normalize_expand_fun(Options, fun edlin_expand:expand/2),
     put(expand_fun, ExpandFun),
-    Echo = proplists:get_value(echo, Options, true),
-    put(echo, Echo),
-    Dumb = proplists:get_value(dumb, Options, false),
-    put(dumb, Dumb),
+
+    %% echo can be set to false by -oldshell and ssh_cli
+    put(echo, proplists:get_value(echo, Options, true)),
+
+    %% dumb can be set to true by ssh_cli
+    put(dumb, proplists:get_value(dumb, Options, false)),
+
+    %% noshell can be set to true by user_drv
+    put(noshell, proplists:get_value(noshell, Options, false)),
+
+    %% expand_below can be set by user_drv and ssh_cli
     put(expand_below, proplists:get_value(expand_below, Options, true)),
 
     DefaultGroupHistory =
@@ -981,6 +989,20 @@ format_expression1(Buffer, FormatingCommand) ->
               end,
     string:chomp(Unicode).
 
+%% Edit line is used in echo=false mode which has two users
+%% Either we are running in "oldshell" or we run using "noshell".
+%%
+%% For "oldshell" we need to take care of certain special characters
+%% that can be entered, but for "noshell" we don't want to do any of
+%% that.
+edit_line(Input, State) ->
+    case get(noshell) of
+        false ->
+            edit_line(Input, State, []);
+        true ->
+            edit_line_raw(Input, State, [])
+    end.
+
 %% We support line editing for the ICANON mode except the following
 %% line editing characters, which already has another meaning in
 %% echo-on mode (See Advanced Programming in the Unix Environment, 2nd ed,
@@ -990,8 +1012,6 @@ format_expression1(Buffer, FormatingCommand) ->
 %% - ^d in posix/icanon mode: eof, delete-forward in edlin
 %% - ^r in posix/icanon mode: reprint (silly in echo-off mode :-))
 %% - ^w in posix/icanon mode: word-erase (produces a beep in edlin)
-edit_line(Input, State) ->
-    edit_line(Input, State, []).
 edit_line(eof, [], _) ->
     eof;
 edit_line(eof, Chars, Rs) ->
@@ -1011,10 +1031,19 @@ edit_line([CtrlChar|Cs],Chars, Rs) when CtrlChar < 32 ->
 edit_line([Char|Cs],Chars, Rs) ->
     edit_line(Cs,[Char|Chars], [{put_chars, unicode, [Char]}|Rs]).
 
+edit_line_raw(eof, [], _) ->
+    eof;
+edit_line_raw(eof, Chars, Rs) ->
+    {Chars,eof, lists:reverse(Rs)};
+edit_line_raw([],Chars, Rs) ->
+    {Chars,[],lists:reverse(Rs)};
+edit_line_raw([NL|Cs],Chars, Rs) when NL =:= $\n ->
+    {[$\n | Chars], remainder_after_nl(Cs), lists:reverse([{put_chars, unicode, "\n"}|Rs])};
+edit_line_raw([Char|Cs],Chars, Rs) ->
+    edit_line_raw(Cs,[Char|Chars], [{put_chars, unicode, [Char]}|Rs]).
+
 remainder_after_nl("") -> done;
 remainder_after_nl(Cs) -> Cs.
-    
-
 
 get_line_timeout(blink) -> 1000;
 get_line_timeout(more_chars) -> infinity.
diff --git a/lib/kernel/src/user_drv.erl b/lib/kernel/src/user_drv.erl
index 3aa12f8b36..2b210e95fb 100644
--- a/lib/kernel/src/user_drv.erl
+++ b/lib/kernel/src/user_drv.erl
@@ -351,7 +351,8 @@ init_shell(State, Slogan) ->
 start_user() ->
     case whereis(user) of
 	undefined ->
-	    User = group:start(self(), {}, [{echo,false}]),
+	    User = group:start(self(), {}, [{echo,false},
+                                            {noshell,true}]),
 	    register(user, User),
 	    User;
 	User ->
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index 02bbf1cc06..fbb529523e 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -29,6 +29,7 @@
          file_read_stdin_binary_mode/1, file_read_stdin_list_mode/1,
          file_read_stdin_unicode_translation_error_binary_mode/1,
          file_read_stdin_unicode_translation_error_list_mode/1,
+         file_read_line_stdin_cr_without_nl/1,
          file_read_line_stdin_unicode_translation_error_binary_mode/1,
          file_read_line_stdin_unicode_translation_error_list_mode/1,
          io_get_chars_stdin_binary_mode/1, io_get_chars_stdin_list_mode/1,
@@ -348,6 +349,20 @@ file_read_stdin_unicode_translation_error_list_mode(_Config) ->
 
     ok.
 
+%% Test that reading from stdin using file:read_line works when \r is sent without \n
+file_read_line_stdin_cr_without_nl(_Config) ->
+    {ok, P, ErlPort} = start_stdin_node(fun() -> file:read_line(standard_io) end, []),
+
+    erlang:port_command(ErlPort, "abc\r"),
+    {error,timeout} = gen_tcp:recv(P, 0, 2000),
+    erlang:port_command(ErlPort, "def\r\n"),
+    {ok, ~S'got: <<"abc\rdef\r\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 returns
 %% correct error when in binary mode
 file_read_line_stdin_unicode_translation_error_binary_mode(_Config) ->
-- 
2.35.3

openSUSE Build Service is sponsored by