File 0471-stdlib-Handle-bad-I-O-server-in-escripts.patch of Package erlang
From f8be50f70bfccaf868d144c3b80f75ee41887c33 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Mon, 26 Aug 2019 16:08:13 +0200
Subject: [PATCH] stdlib: Handle bad I/O server in escripts
See also ERL-992.
---
lib/stdlib/src/escript.erl | 29 ++++++++++++++++--------
lib/stdlib/test/escript_SUITE.erl | 17 +++++++++++---
lib/stdlib/test/escript_SUITE_data/bad_io_server | 11 +++++++++
3 files changed, 44 insertions(+), 13 deletions(-)
create mode 100755 lib/stdlib/test/escript_SUITE_data/bad_io_server
diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl
index 3f14894b55..4e9ba1cc16 100644
--- a/lib/stdlib/src/escript.erl
+++ b/lib/stdlib/src/escript.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2007-2018. All Rights Reserved.
+%% Copyright Ericsson AB 2007-2019. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -281,11 +281,11 @@ start(EscriptOptions) ->
end
catch
throw:Str ->
- io:format("escript: ~ts\n", [Str]),
+ put_chars(io_lib:format("escript: ~ts\n", [Str])),
my_halt(127);
_:Reason:Stk ->
- io:format("escript: Internal error: ~tp\n", [Reason]),
- io:format("~tp\n", [Stk]),
+ put_chars(io_lib:format("escript: Internal error: ~tp\n", [Reason])),
+ put_chars(io_lib:format("~tp\n", [Stk])),
my_halt(127)
end.
@@ -885,13 +885,22 @@ format_exception(Class, Reason, StackTrace) ->
erl_error:format_exception(1, Class, Reason, StackTrace, StackFun, PF, Enc).
encoding() ->
- [{encoding, Encoding}] = enc(),
- Encoding.
+ case io:getopts() of
+ {error, _}=_Err ->
+ latin1;
+ Opts ->
+ case lists:keyfind(encoding, 1, Opts) of
+ false -> latin1;
+ {encoding, Encoding} -> Encoding
+ end
+ end.
-enc() ->
- case lists:keyfind(encoding, 1, io:getopts()) of
- false -> [{encoding,latin1}]; % should never happen
- Enc -> [Enc]
+put_chars(String) ->
+ try
+ io:put_chars(String)
+ catch
+ _:_ ->
+ erlang:display(lists:flatten(String))
end.
a0() ->
diff --git a/lib/stdlib/test/escript_SUITE.erl b/lib/stdlib/test/escript_SUITE.erl
index 0b9106a99c..8ffd01f2b2 100644
--- a/lib/stdlib/test/escript_SUITE.erl
+++ b/lib/stdlib/test/escript_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2007-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2007-2019. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -38,7 +38,8 @@
foldl/1,
overflow/1,
verify_sections/3,
- unicode/1
+ unicode/1,
+ bad_io_server/1
]).
-include_lib("common_test/include/ct.hrl").
@@ -53,7 +54,7 @@ all() ->
emulator_flags_no_shebang, two_lines,
module_script, beam_script, archive_script, epp,
create_and_extract, foldl, overflow,
- archive_script_file_access, unicode].
+ archive_script_file_access, unicode, bad_io_server].
groups() ->
[].
@@ -950,6 +951,16 @@ overflow(Config) when is_list(Config) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% OTP-16006, ERL-992
+bad_io_server(Config) when is_list(Config) ->
+ Data = proplists:get_value(data_dir, Config),
+ Dir = filename:absname(Data), %Get rid of trailing slash.
+ run(Dir, "bad_io_server",
+ [<<"\"escript: exception error: an error occurred when evaluating"
+ " an arithmetic expression\\n in operator '/'/2\\n "
+ "called as '\\x{400}' / 0\\n\"\r\nExitCode:127">>]),
+ ok.
+
run(Dir, Cmd0, Expected0) ->
Expected = iolist_to_binary(expected_output(Expected0, Dir)),
Cmd = case os:type() of
diff --git a/lib/stdlib/test/escript_SUITE_data/bad_io_server b/lib/stdlib/test/escript_SUITE_data/bad_io_server
new file mode 100755
index 0000000000..4a6e81c935
--- /dev/null
+++ b/lib/stdlib/test/escript_SUITE_data/bad_io_server
@@ -0,0 +1,11 @@
+#!/usr/bin/env escript
+%% -*- erlang -*-
+
+-export([main/1]).
+
+main(_) ->
+ ok = io:setopts([{encoding,unicode}]),
+ _D = erlang:system_flag(backtrace_depth, 0),
+ group_leader(spawn(fun() -> ok end), self()),
+ _ = '\x{400}'/0,
+ ok.
--
2.16.4