File 0549-Send-exit-status-from-ssh_cli.patch of Package erlang
From fe40cd5cfe635b9bc101dab7577d53a02c11d5c0 Mon Sep 17 00:00:00 2001
From: Svilen Ivanov <isvilen@applicata.bg>
Date: Wed, 16 Sep 2020 11:19:40 +0300
Subject: [PATCH] Send exit status from ssh_cli
Make sure that ssh_cli module always send exit-status message,
so SSH clients can use it to check for successful command execution.
---
 lib/ssh/src/ssh_cli.erl          | 16 ++++--
 lib/ssh/test/ssh_basic_SUITE.erl | 92 +++++++++++++++++++++++++++++++-
 2 files changed, 103 insertions(+), 5 deletions(-)
diff --git a/lib/ssh/src/ssh_cli.erl b/lib/ssh/src/ssh_cli.erl
index fd2c2943f6..be60cb126e 100644
--- a/lib/ssh/src/ssh_cli.erl
+++ b/lib/ssh/src/ssh_cli.erl
@@ -231,10 +231,19 @@ handle_msg({Group, Req}, #state{group = Group, buf = Buf, pty = Pty,
     write_chars(ConnectionHandler, ChannelId, Chars),
     {ok, State#state{buf = NewBuf}};
 
-handle_msg({'EXIT', Group, _Reason}, #state{group = Group,
+handle_msg({'EXIT', Group, Reason}, #state{group = Group,
 					    cm = ConnectionHandler,
 					    channel = ChannelId} = State) ->
     ssh_connection:send_eof(ConnectionHandler, ChannelId),
+    ExitStatus = case Reason of
+                     normal ->
+                         0;
+                     {exit_status, V} when is_integer(V) ->
+                         V;
+                     _ ->
+                         ?EXEC_ERROR_STATUS
+                 end,
+    ssh_connection:exit_status(ConnectionHandler, ChannelId, ExitStatus),
     {stop, ChannelId, State};
 
 handle_msg(_, State) ->
@@ -620,11 +629,10 @@ exec_in_self_group(ConnectionHandler, ChannelId, WantReply, State, Fun) ->
                                end
                           of
                               {ok,Str} ->
-                                  write_chars(ConnectionHandler, ChannelId, t2str(Str)),
-                                  ssh_connection:exit_status(ConnectionHandler, ChannelId, 0);
+                                  write_chars(ConnectionHandler, ChannelId, t2str(Str));
                               {error, Str} ->
                                   write_chars(ConnectionHandler, ChannelId, 1, "**Error** "++t2str(Str)),
-                                  ssh_connection:exit_status(ConnectionHandler, ChannelId, ?EXEC_ERROR_STATUS)
+                                  exit({exit_status, ?EXEC_ERROR_STATUS})
                           end
                   end)
         end,
diff --git a/lib/ssh/test/ssh_basic_SUITE.erl b/lib/ssh/test/ssh_basic_SUITE.erl
index db3a4f7699..6f7b3a79fc 100644
--- a/lib/ssh/test/ssh_basic_SUITE.erl
+++ b/lib/ssh/test/ssh_basic_SUITE.erl
@@ -132,7 +132,7 @@ groups() ->
      {p_basic, [?PARALLEL], [send, peername_sockname,
                             exec, exec_compressed, 
                             exec_with_io_out, exec_with_io_in,
-                            cli,
+                            cli, cli_exit_normal, cli_exit_status,
                             idle_time_client, idle_time_server, openssh_zlib_basic_test, 
                             misc_ssh_options, inet_option, inet6_option]}
     ].
@@ -851,6 +851,94 @@ cli(Config) when is_list(Config) ->
 	30000 -> ct:fail("timeout ~p:~p",[?MODULE,?LINE])
     end.
 
+%%-----------------------------------------------------------------------------
+%%% Test that SSH client receives exit-status 0 on successful command execution
+cli_exit_normal(Config) when is_list(Config) ->
+    process_flag(trap_exit, true),
+    SystemDir = filename:join(proplists:get_value(priv_dir, Config), system),
+    UserDir = proplists:get_value(priv_dir, Config),
+
+    {_Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, SystemDir},{user_dir, UserDir},
+                           {password, "morot"},
+                           {ssh_cli, {ssh_cli, [fun (_) -> spawn(fun () -> ok end) end]}},
+                           {subsystems, []},
+                           {failfun, fun ssh_test_lib:failfun/2}]),
+    ct:sleep(500),
+
+    ConnectionRef = ssh_test_lib:connect(Host, Port, [{silently_accept_hosts, true},
+                              {user, "foo"},
+                              {password, "morot"},
+                              {user_interaction, false},
+                              {user_dir, UserDir}]),
+
+    {ok, ChannelId} = ssh_connection:session_channel(ConnectionRef, infinity),
+    ssh_connection:shell(ConnectionRef, ChannelId),
+
+    receive
+        {ssh_cm, ConnectionRef,{eof, ChannelId}} ->
+            ok
+    after
+    30000 -> ct:fail("timeout ~p:~p",[?MODULE,?LINE])
+    end,
+
+    receive
+        {ssh_cm, ConnectionRef,{exit_status,ChannelId,0}} ->
+            ok
+    after
+    30000 -> ct:fail("timeout ~p:~p",[?MODULE,?LINE])
+    end,
+
+    receive
+        {ssh_cm, ConnectionRef,{closed, ChannelId}} ->
+            ok
+    after
+    30000 -> ct:fail("timeout ~p:~p",[?MODULE,?LINE])
+    end.
+
+%%---------------------------------------------------------
+%%% Test that SSH client receives user provided exit-status
+cli_exit_status(Config) when is_list(Config) ->
+    process_flag(trap_exit, true),
+    SystemDir = filename:join(proplists:get_value(priv_dir, Config), system),
+    UserDir = proplists:get_value(priv_dir, Config),
+
+    {_Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, SystemDir},{user_dir, UserDir},
+                           {password, "morot"},
+                           {ssh_cli, {ssh_cli, [fun (_) -> spawn(fun () -> exit({exit_status, 7}) end) end]}},
+                           {subsystems, []},
+                           {failfun, fun ssh_test_lib:failfun/2}]),
+    ct:sleep(500),
+
+    ConnectionRef = ssh_test_lib:connect(Host, Port, [{silently_accept_hosts, true},
+                              {user, "foo"},
+                              {password, "morot"},
+                              {user_interaction, false},
+                              {user_dir, UserDir}]),
+
+    {ok, ChannelId} = ssh_connection:session_channel(ConnectionRef, infinity),
+    ssh_connection:shell(ConnectionRef, ChannelId),
+
+    receive
+        {ssh_cm, ConnectionRef,{eof, ChannelId}} ->
+            ok
+    after
+    30000 -> ct:fail("timeout ~p:~p",[?MODULE,?LINE])
+    end,
+
+    receive
+        {ssh_cm, ConnectionRef,{exit_status,ChannelId,7}} ->
+            ok
+    after
+    30000 -> ct:fail("timeout ~p:~p",[?MODULE,?LINE])
+    end,
+
+    receive
+        {ssh_cm, ConnectionRef,{closed, ChannelId}} ->
+            ok
+    after
+    30000 -> ct:fail("timeout ~p:~p",[?MODULE,?LINE])
+    end.
+
 %%--------------------------------------------------------------------
 %%% Test that get correct error message if you try to start a daemon
 %%% on an adress that already runs a daemon see also seq10667
-- 
2.26.2