File 3152-kernel-Add-stdin-stdout-and-stderr-to-io-getopts.patch of Package erlang

From 77ae38dd9fe5f4bd351e309c6e193192ece3b61e Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Wed, 17 Apr 2024 17:08:09 +0200
Subject: [PATCH 2/2] kernel: Add stdin, stdout and stderr to io:getopts

---
 lib/kernel/src/group.erl           |  9 ++++----
 lib/kernel/src/user_drv.erl        |  8 +++++--
 lib/ssh/src/ssh_cli.erl            |  2 +-
 lib/stdlib/src/io.erl              | 17 +++++++++-----
 lib/stdlib/test/io_proto_SUITE.erl | 37 ++++++++++++++++++++++++++++--
 5 files changed, 58 insertions(+), 15 deletions(-)

diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl
index a422fa2fd4..d5f067c352 100644
--- a/lib/kernel/src/group.erl
+++ b/lib/kernel/src/group.erl
@@ -199,8 +199,8 @@ set_unicode_state(Drv,Bool) ->
 get_terminal_state(Drv) ->
     Drv ! {self(),get_terminal_state},
     receive
-	{Drv,get_terminal_state,UniState} ->
-	    UniState;
+	{Drv,get_terminal_state,Terminal} ->
+	    Terminal;
 	{Drv,get_terminal_state,error} ->
 	    {error, internal}
     after 2000 ->
@@ -467,8 +467,9 @@ getopts(Drv,Buf) ->
 			true -> unicode;
 			_ -> latin1
 		     end},
-    Tty = {terminal, get_terminal_state(Drv)},
-    {ok,[Exp,Echo,Bin,Uni,Tty],Buf}.
+    Terminal = get_terminal_state(Drv),
+    Tty = {terminal, maps:get(stdout, Terminal)},
+    {ok,[Exp,Echo,Bin,Uni,Tty|maps:to_list(Terminal)],Buf}.
 
 %% get_chars_*(Prompt, Module, Function, XtraArgument, Drv, Buffer)
 %%  Gets characters from the input Drv until as the applied function
diff --git a/lib/kernel/src/user_drv.erl b/lib/kernel/src/user_drv.erl
index 2b210e95fb..d7fd617aee 100644
--- a/lib/kernel/src/user_drv.erl
+++ b/lib/kernel/src/user_drv.erl
@@ -467,7 +467,9 @@ server(info, {Requester, set_unicode_state, Bool}, #state{ tty = TTYState } = St
     Requester ! {self(), set_unicode_state, OldUnicode},
     {keep_state, State#state{ tty = NewTTYState }};
 server(info, {Requester, get_terminal_state}, _State) ->
-    Requester ! {self(), get_terminal_state, prim_tty:isatty(stdout) },
+    Requester ! {self(), get_terminal_state, #{ stdin => prim_tty:isatty(stdin),
+                                                stdout => prim_tty:isatty(stdout),
+                                                stderr => prim_tty:isatty(stderr) } },
     keep_state_and_data;
 server(info, {Requester, {open_editor, Buffer}}, #state{tty = TTYState } = State) ->
     case open_editor(TTYState, Buffer) of
@@ -670,7 +672,9 @@ switch_loop(info, {Requester, get_unicode_state}, {_Cont, #state{ tty = TTYState
     Requester ! {self(), get_unicode_state, prim_tty:unicode(TTYState) },
     keep_state_and_data;
 switch_loop(info, {Requester, get_terminal_state}, _State) ->
-    Requester ! {self(), get_terminal_state, prim_tty:isatty(stdout) },
+    Requester ! {self(), get_terminal_state, #{ stdin => prim_tty:isatty(stdin),
+                                                stdout => prim_tty:isatty(stdout),
+                                                stderr => prim_tty:isatty(stderr) } },
     keep_state_and_data;
 switch_loop(timeout, _, {_Cont, State}) ->
     {keep_state_and_data,
diff --git a/lib/ssh/src/ssh_cli.erl b/lib/ssh/src/ssh_cli.erl
index 7b6f1df294..5eb3e41980 100644
--- a/lib/ssh/src/ssh_cli.erl
+++ b/lib/ssh/src/ssh_cli.erl
@@ -283,7 +283,7 @@ handle_msg({Group, get_unicode_state}, State) ->
     {ok, State};
 
 handle_msg({Group, get_terminal_state}, State) ->
-    Group ! {self(), get_terminal_state, true},
+    Group ! {self(), get_terminal_state, #{ stdout => true, stdin => true }},
     {ok, State};
 
 handle_msg({Group, tty_geometry}, #state{group = Group,
diff --git a/lib/stdlib/doc/src/io.xml b/lib/stdlib/doc/src/io.xml
index cc7617272f..068c99e996 100644
--- a/lib/stdlib/doc/src/io.xml
+++ b/lib/stdlib/doc/src/io.xml
@@ -880,14 +880,18 @@ enter><input>:</input>   <input>alan</in
  {echo,true},
  {binary,false},
  {encoding,unicode},
- {terminal,true}]</pre>
+ {terminal,true},
+ {stdout,true},
+ {stderr,true},
+ {stdin,true}]</pre>
       <p>This example is, as can be seen, run in an environment where the
         terminal supports Unicode input and output.</p>
-      <p>The <c>terminal</c> option is read only and indicates whether
+      <p>The <c>stdin</c>, <c>stdout</c> and <c>stderr</c> options are read only and indicates whether
         the output stream is a terminal or not. When it is a terminal,
         most systems that Erlang runs on allows the use of
         <url href="https://en.wikipedia.org/wiki/ANSI_escape_code">ANSI escape codes</url>
         to control what the terminal outputs.</p>
+      <p><c>terminal</c> is an alias for <c>stdout</c>.</p>
       <p>See <seemfa marker="#setopts/1"><c>setopts/1</c></seemfa> for a description
         of the other options.</p>
       </desc>
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index fbb529523e..7c4b7d867b 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -52,6 +52,8 @@
 
 -export([get_until_eof/2]).
 
+-include_lib("stdlib/include/assert.hrl").
+
 %%-define(debug, true).
 
 -ifdef(debug).
@@ -276,7 +278,15 @@ setopts_getopts(Config) when is_list(Config) ->
                {expect, "[\n ]ok"},
                {putline, "io:get_line('')."},
                {putline, "hej"},
-               {expect, "\\Q<<\"hej\\n\">>\\E"}
+               {expect, "\\Q<<\"hej\\n\">>\\E"},
+               {putline, "proplists:get_value(terminal,io:getopts())."},
+               {expect, "true"},
+               {putline, "proplists:get_value(stdin,io:getopts())."},
+               {expect, "true"},
+               {putline, "proplists:get_value(stdout,io:getopts())."},
+               {expect, "true"},
+               {putline, "proplists:get_value(stderr,io:getopts())."},
+               {expect, "true"}
               ],[]);
         _ ->
             ok
@@ -295,8 +305,31 @@ setopts_getopts(Config) when is_list(Config) ->
        {expect, "[\n ]ok"},
        {putline, "io:get_line('')."},
        {putline, "hej"},
-       {expect, "\\Q<<\"hej\\n\">>\\E"}
+       {expect, "\\Q<<\"hej\\n\">>\\E"},
+       {putline, "proplists:get_value(terminal,io:getopts())."},
+       {expect, "true"},
+       {putline, "proplists:get_value(stdin,io:getopts())."},
+       {expect, "true"},
+       {putline, "proplists:get_value(stdout,io:getopts())."},
+       {expect, "true"},
+       {putline, "proplists:get_value(stderr,io:getopts())."},
+       {expect, "true"}
       ],[],"",["-oldshell"]),
+
+    %% Test that terminal options when used in non-terminal
+    %% are returned as they should
+    Erl = ct:get_progname(),
+    Str = os:cmd(Erl ++ " -noshell -eval \"io:format(~s'~p.',[io:getopts()])\" -s init stop"),
+    maybe
+        {ok, T, _} ?= erl_scan:string(Str),
+        {ok, Opts} ?= erl_parse:parse_term(T),
+        ?assertEqual(false, proplists:get_value(terminal,Opts)),
+        ?assertEqual(false, proplists:get_value(stdin,Opts)),
+        ?assertEqual(false, proplists:get_value(stdout,Opts)),
+        ?assertEqual(false, proplists:get_value(stderr,Opts))
+    else
+        _ -> ct:fail({failed_to_parse, Str})
+    end,
     ok.
 
 %% Test that reading from stdin using file:read works when io is in binary mode
-- 
2.35.3

openSUSE Build Service is sponsored by