File 6191-os-Add-exception_on_failure-to-os-cmd-2.patch of Package erlang
From df9ee9a8d792f4a7cc6d465f132ec67dc39fef31 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= <lukas@erlang.org>
Date: Mon, 18 Nov 2024 16:07:42 +0100
Subject: [PATCH] os: Add exception_on_failure to os:cmd/2
exception_on_failure make os:cmd/2 fail when the command
exits with a failure reason. Before this change the user
had to check the output from the command to know if it
failed or not, now an exception will be thrown instead.
I decided to not implement it as a different return value
as that would change the return signature of os:cmd/2 depending
on which options are passed which makes it a lot more
difficult for static analysis tools to know what this
function can return.
---
lib/kernel/src/os.erl | 90 +++++++++++++++++++++++++++---------
lib/kernel/test/os_SUITE.erl | 36 ++++++++++++++-
2 files changed, 101 insertions(+), 25 deletions(-)
diff --git a/lib/kernel/doc/src/os.xml b/lib/kernel/doc/src/os.xml
index bba2b84736..6a1e2ad58b 100644
--- a/lib/kernel/doc/src/os.xml
+++ b/lib/kernel/doc/src/os.xml
@@ -103,6 +103,11 @@
See the <seemfa marker="#cmd/2"><c>os:cmd/2</c></seemfa>
documentation for more details.</p>
</item>
+ <tag><c>exception_on_failure</c></tag>
+ <item>
+ <p>If set to true, <c>cmd/2</c> will throw an error exception if
+ the command exits with a non-zero exit code.</p>
+ </item>
</taglist>
</desc>
</datatype>
@@ -132,13 +137,27 @@ DirOut = os:cmd("dir"), % on Win32 platf
<taglist>
<tag><c>max_size</c></tag>
<item>
- <p>The maximum size of the data returned by the <c>os:cmd</c> call.
+ <p>The maximum size of the data returned by the <c>os:cmd/2</c> call.
This option is a safety feature that should be used when the command
executed can return a very large, possibly infinite, result.</p>
+ <p><em>Example:</em></p>
<code type="none">
> os:cmd("cat /dev/zero", #{ max_size => 20 }).
[0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0]</code>
</item>
+ <tag><c>exception_on_failure</c></tag>
+ <item>
+ <p>If set to true, <c>os:cmd/2</c> will throw an error exception
+ if the command exits with a non-zero exit code. The exception reason
+ looks like this: <c>{command_failed, ResultBeforeFailure, ExitCode}</c>
+ where <c>ResultBeforeFailure</c> is the result written to stdout
+ by the command before the error happened and <c>ExitCode</c>
+ is the exit code from the command.</p>
+ <p><em>Example:</em></p>
+ <code type="none">
+> catch os:cmd("echo hello && exit 123", #{ exception_on_failure => true }).
+{'EXIT',{{command_failed,"hello\n",123}, [{os,cmd,2,[{file,"os.erl"},{line,579}]},</code>
+ </item>
</taglist>
</desc>
</func>
diff --git a/lib/kernel/src/os.erl b/lib/kernel/src/os.erl
index bba2b84736..6a1e2ad58b 100644
--- a/lib/kernel/src/os.erl
+++ b/lib/kernel/src/os.erl
@@ -35,7 +35,8 @@
system_time/1, timestamp/0]).
-type os_command() :: atom() | io_lib:chars().
--type os_command_opts() :: #{ max_size => non_neg_integer() | infinity }.
+-type os_command_opts() :: #{ max_size => non_neg_integer() | infinity,
+ exception_on_failure => boolean() }.
-export_type([os_command/0, os_command_opts/0]).
@@ -555,6 +556,8 @@ cmd(Cmd, Opts) ->
try
do_cmd(Cmd, Opts)
catch
+ throw:{command_failed, Result, ExitStatus} ->
+ error({command_failed, Result, ExitStatus});
throw:badopt ->
badarg_with_cause([Cmd, Opts], badopt);
throw:{open_port, Reason} ->
@@ -565,7 +568,8 @@ cmd(Cmd, Opts) ->
do_cmd(Cmd, Opts) ->
MaxSize = get_option(max_size, Opts, infinity),
- {SpawnCmd, SpawnOpts, SpawnInput, Eot} = mk_cmd(os:type(), validate(Cmd)),
+ ExceptionOnFailure = get_option(exception_on_failure, Opts, false),
+ {SpawnCmd, SpawnOpts, SpawnInput, Eot} = mk_cmd(os:type(), validate(Cmd), ExceptionOnFailure),
Port = try open_port({spawn, SpawnCmd}, [binary, stderr_to_stdout,
stream, in, hide | SpawnOpts])
catch error:Reason ->
@@ -573,12 +577,17 @@ do_cmd(Cmd, Opts) ->
end,
MonRef = erlang:monitor(port, Port),
true = port_command(Port, SpawnInput),
- Bytes = get_data(Port, MonRef, Eot, [], 0, MaxSize),
+ {Bytes, ExitStatus} = get_data(Port, MonRef, Eot, [], 0, MaxSize, ExceptionOnFailure),
demonitor(MonRef, [flush]),
String = unicode:characters_to_list(Bytes),
- if %% Convert to unicode list if possible otherwise return bytes
- is_list(String) -> String;
- true -> binary_to_list(Bytes)
+ Result =
+ if %% Convert to unicode list if possible otherwise return bytes
+ is_list(String) -> String;
+ true -> binary_to_list(iolist_to_binary(Bytes))
+ end,
+ if ExceptionOnFailure, ExitStatus =/= 0 ->
+ throw({command_failed, Result, ExitStatus});
+ true -> Result
end.
get_option(Opt, Options, Default) ->
@@ -590,15 +599,16 @@ get_option(Opt, Options, Default) ->
-define(KERNEL_OS_CMD_SHELL_KEY, kernel_os_cmd_shell).
-mk_cmd({win32,_}, Cmd) ->
+mk_cmd({win32,_}, Cmd, ExitStatus) ->
Shell = persistent_term:get(?KERNEL_OS_CMD_SHELL_KEY),
Command = lists:concat([Shell, " /c", Cmd]),
- {Command, [], [], <<>>};
-mk_cmd(_,Cmd) ->
+ {Command, [exit_status || ExitStatus], [], <<>>};
+mk_cmd(_,Cmd, ExitStatus) ->
%% Have to send command in like this in order to make sh commands like
%% cd and ulimit available.
Shell = persistent_term:get(?KERNEL_OS_CMD_SHELL_KEY),
- {Shell ++ " -s unix:cmd", [out],
+ EchoExitStatus = ["$?\^D" || ExitStatus],
+ {Shell ++ " -s unix:cmd", [out] ++ [exit_status || ExitStatus],
%% We insert a new line after the command, in case the command
%% contains a comment character.
%%
@@ -613,7 +623,8 @@ mk_cmd(_,Cmd) ->
%%
%% I tried changing this to be "better", but got bombarded with
%% backwards incompatibility bug reports, so leave this as it is.
- ["(", unicode:characters_to_binary(Cmd), "\n) </dev/null; echo \"\^D\"\n"],
+ ["(", unicode:characters_to_binary(Cmd), "\n) </dev/null; "
+ "echo \"\^D",EchoExitStatus,"\"\n"],
<<$\^D>>}.
internal_init_cmd_shell() ->
@@ -686,31 +697,45 @@ validate3([List|Rest]) when is_list(List) ->
validate3(List),
validate3(Rest).
-get_data(Port, MonRef, Eot, Sofar, Size, Max) ->
+get_data(Port, MonRef, Eot, Sofar, Size, Max, ExitStatus) ->
receive
{Port, {data, Bytes}} ->
case eot(Bytes, Eot, Size, Max) of
more ->
get_data(Port, MonRef, Eot, [Sofar, Bytes],
- Size + byte_size(Bytes), Max);
- Last ->
+ Size + byte_size(Bytes), Max, ExitStatus);
+ {Last, Remain} ->
catch port_close(Port),
flush_until_down(Port, MonRef),
- iolist_to_binary([Sofar, Last])
+ Result = [Sofar, Last],
+ case ExitStatus andalso eot(Remain, Eot, byte_size(Remain), Max) of
+ {ExitCode, _} ->
+ {Result, binary_to_integer(ExitCode)};
+ _ ->
+ {Result, 0}
+ end
end;
+ {Port, {exit_status, N}} ->
+ %% exit_status will always arrive before 'DOWN' and 'EXIT'
+ flush_until_down(Port, MonRef),
+ flush_exit(Port),
+ {Sofar, N};
{'DOWN', MonRef, _, _, _} ->
+ %% We get 'DOWN' if someone does exit/2 on the port... we treat this
+ %% as if a SIGKILL was sent to the command
flush_exit(Port),
- iolist_to_binary(Sofar)
+ {Sofar, 128 + 9}
end.
eot(Bs, <<>>, Size, Max) when Size + byte_size(Bs) < Max ->
more;
eot(Bs, <<>>, Size, Max) ->
- binary:part(Bs, {0, Max - Size});
+ {binary:part(Bs, {0, Max - Size}), <<>>};
eot(Bs, Eot, Size, Max) ->
case binary:match(Bs, Eot) of
{Pos, _} when Size + Pos < Max ->
- binary:part(Bs,{0, Pos});
+ {binary:part(Bs, 0, Pos), %% Everything until Eot
+ binary:part(Bs, Pos + 1, byte_size(Bs) - (Pos + 1))}; %% Everything after Eot
_ ->
eot(Bs, <<>>, Size, Max)
end.
diff --git a/lib/kernel/test/os_SUITE.erl b/lib/kernel/test/os_SUITE.erl
index fe3d81d622..8ea2f90a0c 100644
--- a/lib/kernel/test/os_SUITE.erl
+++ b/lib/kernel/test/os_SUITE.erl
@@ -28,9 +28,11 @@
find_executable/1, unix_comment_in_command/1, deep_list_command/1,
large_output_command/1, background_command/0, background_command/1,
message_leak/1, close_stdin/0, close_stdin/1, max_size_command/1,
- perf_counter_api/1, error_info/1, os_cmd_shell/1,os_cmd_shell_peer/1]).
+ cmd_exception/1, os_cmd_shell/1, os_cmd_shell_peer/1,
+ perf_counter_api/1, error_info/1]).
-include_lib("common_test/include/ct.hrl").
+-include_lib("stdlib/include/assert.hrl").
suite() ->
[{ct_hooks,[ts_install_cth]},
@@ -43,7 +45,8 @@ all() ->
find_executable, unix_comment_in_command, deep_list_command,
large_output_command, background_command, message_leak,
close_stdin, max_size_command, perf_counter_api,
- error_info, os_cmd_shell, os_cmd_shell_peer].
+ error_info, os_cmd_shell, os_cmd_shell_peer,
+ cmd_exception].
groups() ->
[].
@@ -204,6 +207,35 @@ bad_command(Config) when is_list(Config) ->
ok.
+cmd_exception(Config) when is_list(Config) ->
+
+ {Osfamily, Ostype} = os:type(),
+
+ %% command failed
+ {Res, 3} = cmd_exception_test("echo abc && exit 3"),
+ Osfamily =:= unix andalso ?assertEqual("abc\n", Res),
+ Osfamily =:= win32 andalso ?assertEqual("abc \r\n", Res),
+
+ %% Syntax error
+ {_, ExitCode} = cmd_exception_test("{)"),
+ Osfamily =:= unix andalso Ostype =/= sunos andalso ?assertEqual(2, ExitCode),
+ Osfamily =:= unix andalso Ostype =:= sunos andalso ?assertEqual(3, ExitCode),
+ Osfamily =:= win32 andalso ?assertEqual(1, ExitCode),
+
+ ok.
+
+cmd_exception_test(Cmd) ->
+ Out = os:cmd(Cmd), %% Check that no exception is generated when the option is not given
+ try
+ os:cmd(Cmd, #{ exception_on_failure => true}),
+ ct:fail("Should not succeed")
+ catch error:{command_failed, ErrorOut, Reason} ->
+ %% Check that the output is the same
+ ?assertEqual(Out, ErrorOut),
+ {ErrorOut, Reason}
+ end.
+
+
find_executable(Config) when is_list(Config) ->
case os:type() of
{win32, _} ->
--
2.43.0