File 0044-Propagate-exceptions-fully-when-using-proc_lib.patch of Package erlang

From 798f09de48b1a7abe43d54d6fa0377ad15c3f6aa Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Lo=C3=AFc=20Hoguin?= <essen@ninenines.eu>
Date: Fri, 3 Jun 2016 12:13:09 +0200
Subject: [PATCH] Propagate exceptions fully when using proc_lib

This makes proc_lib behaves like a normal process as far
as the propagation of exceptions is concerned.

Before this commit, the following difference could be
observed:

  6> spawn_link(fun() -> ssl:send(a,b) end).
  <0.43.0>
  7> flush().
  Shell got {'EXIT',<0.43.0>,
             {function_clause,
              [{ssl,send,[a,b],[{file,"..."},{line,275}]}]}}
  ok

  8> proc_lib:spawn_link(fun() -> ssl:send(a,b) end).
  <0.46.0>
  9> flush().
  Shell got {'EXIT',<0.46.0>,function_clause}

After this commit, we get the following instead:

  3> flush().
  Shell got {'EXIT',<0.61.0>,
             {function_clause,
              [{ssl,send,[a,b],[{file,"..."},{line,275}]},
               {proc_lib,init_p,3,[{file,"..."},{line,232}]}]}}

The stacktrace will show minor differences of course
but the form is now the same as without proc_lib.

The rationale behind this commit is that:

* We now have a single form regardless of how the process
  was started

* We can use the stacktrace to programmatically alter behavior
  (for example an HTTP server identifying problems in input
  decoding to send back a generic 400, or a 500 otherwise)

* We can access the stacktrace to print it somewhere (for
  example an HTTP server could send it back to the client
  when a debug mode is enabled)
---
 lib/stdlib/doc/src/proc_lib.xml      |  6 ++++++
 lib/stdlib/src/proc_lib.erl          | 19 +++++++++++++------
 lib/stdlib/test/gen_statem_SUITE.erl |  6 +++---
 lib/stdlib/test/proc_lib_SUITE.erl   | 31 ++++++++++++++++++++++++++++---
 4 files changed, 50 insertions(+), 12 deletions(-)

diff --git a/lib/stdlib/doc/src/proc_lib.xml b/lib/stdlib/doc/src/proc_lib.xml
index da03c39..e64b2ce 100644
--- a/lib/stdlib/doc/src/proc_lib.xml
+++ b/lib/stdlib/doc/src/proc_lib.xml
@@ -66,6 +66,12 @@
       <seealso marker="sasl:error_logging">SASL Error Logging</seealso>
       in the SASL User's Guide.</p>
 
+    <p>Unlike in "plain Erlang", <c>proc_lib</c> processes will not generate
+      <em>error reports</em>, which are written to the terminal by the
+      emulator and do not require SASL to be started. All exceptions are
+      converted to <em>exits</em> which are ignored by the default
+      <c>error_logger</c> handler.</p>
+
     <p>The crash report contains the previously stored information, such
       as ancestors and initial function, the termination reason, and
       information about other processes that terminate as a result
diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl
index 3dc1848..363705b 100644
--- a/lib/stdlib/src/proc_lib.erl
+++ b/lib/stdlib/src/proc_lib.erl
@@ -232,7 +232,7 @@ init_p(Parent, Ancestors, Fun) when is_function(Fun) ->
 	Fun()
     catch
 	Class:Reason ->
-	    exit_p(Class, Reason)
+	    exit_p(Class, Reason, erlang:get_stacktrace())
     end.
 
 -spec init_p(pid(), [pid()], atom(), atom(), [term()]) -> term().
@@ -247,7 +247,7 @@ init_p_do_apply(M, F, A) ->
 	apply(M, F, A) 
     catch
 	Class:Reason ->
-	    exit_p(Class, Reason)
+	    exit_p(Class, Reason, erlang:get_stacktrace())
     end.
 
 -spec wake_up(atom(), atom(), [term()]) -> term().
@@ -257,22 +257,29 @@ wake_up(M, F, A) when is_atom(M), is_atom(F), is_list(A) ->
 	apply(M, F, A) 
     catch
 	Class:Reason ->
-	    exit_p(Class, Reason)
+	    exit_p(Class, Reason, erlang:get_stacktrace())
     end.
 
-exit_p(Class, Reason) ->
+exit_p(Class, Reason, Stacktrace) ->
     case get('$initial_call') of
 	{M,F,A} when is_atom(M), is_atom(F), is_integer(A) ->
 	    MFA = {M,F,make_dummy_args(A, [])},
 	    crash_report(Class, Reason, MFA),
-	    exit(Reason);
+	    erlang:raise(exit, exit_reason(Class, Reason, Stacktrace), Stacktrace);
 	_ ->
 	    %% The process dictionary has been cleared or
 	    %% possibly modified.
 	    crash_report(Class, Reason, []),
-	    exit(Reason)
+	    erlang:raise(exit, exit_reason(Class, Reason, Stacktrace), Stacktrace)
     end.
 
+exit_reason(error, Reason, Stacktrace) ->
+    {Reason, Stacktrace};
+exit_reason(exit, Reason, _Stacktrace) ->
+    Reason;
+exit_reason(throw, Reason, Stacktrace) ->
+    {{nocatch, Reason}, Stacktrace}.
+
 -spec start(Module, Function, Args) -> Ret when
       Module :: module(),
       Function :: atom(),
diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl
index 28f9ab8..300baaf 100644
--- a/lib/stdlib/test/gen_statem_SUITE.erl
+++ b/lib/stdlib/test/gen_statem_SUITE.erl
@@ -505,10 +505,10 @@ abnormal2(Config) ->
     {ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []),
 
     %% bad return value in the gen_statem loop
-    {{bad_return_from_state_function,badreturn},_} =
+    {{{bad_return_from_state_function,badreturn},_},_} =
 	?EXPECT_FAILURE(gen_statem:call(Pid, badreturn), Reason),
     receive
-	{'EXIT',Pid,{bad_return_from_state_function,badreturn}} -> ok
+	{'EXIT',Pid,{{bad_return_from_state_function,badreturn},_}} -> ok
     after 5000 ->
 	    ct:fail(gen_statem_did_not_die)
     end,
@@ -887,7 +887,7 @@ error_format_status(Config) ->
 	gen_statem:start(
 	  ?MODULE, start_arg(Config, {data,Data}), []),
     %% bad return value in the gen_statem loop
-    {{bad_return_from_state_function,badreturn},_} =
+    {{{bad_return_from_state_function,badreturn},_},_} =
 	?EXPECT_FAILURE(gen_statem:call(Pid, badreturn), Reason),
     receive
 	{error,_,
diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl
index 416650e..a53e99a 100644
--- a/lib/stdlib/test/proc_lib_SUITE.erl
+++ b/lib/stdlib/test/proc_lib_SUITE.erl
@@ -26,7 +26,7 @@
 
 -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 	 init_per_group/2,end_per_group/2, 
-	 crash/1, sync_start_nolink/1, sync_start_link/1,
+	 crash/1, stacktrace/1, sync_start_nolink/1, sync_start_link/1,
          spawn_opt/1, sp1/0, sp2/0, sp3/1, sp4/2, sp5/1,
 	 hibernate/1, stop/1, t_format/1]).
 -export([ otp_6345/1, init_dont_hang/1]).
@@ -50,7 +50,7 @@
 suite() -> [{ct_hooks,[ts_install_cth]}].
 
 all() -> 
-    [crash, {group, sync_start}, spawn_opt, hibernate,
+    [crash, stacktrace, {group, sync_start}, spawn_opt, hibernate,
      {group, tickets}, stop, t_format].
 
 groups() -> 
@@ -198,6 +198,31 @@ match_info(Tuple1, Tuple2) when tuple_size(Tuple1) =:= tuple_size(Tuple2) ->
 match_info(_, _) ->
     throw(no_match).
 
+stacktrace(Config) when is_list(Config) ->
+    process_flag(trap_exit, true),
+    %% Errors.
+    Pid1 = proc_lib:spawn_link(fun() -> 1 = 2 end),
+    receive
+	{'EXIT',Pid1,{{badmatch,2},_Stack1}} -> ok
+    after 500 ->
+	ct:fail(error)
+    end,
+    %% Exits.
+    Pid2 = proc_lib:spawn_link(fun() -> exit(bye) end),
+    receive
+	{'EXIT',Pid2,bye} -> ok
+    after 500 ->
+	ct:fail(exit)
+    end,
+    %% Throws.
+    Pid3 = proc_lib:spawn_link(fun() -> throw(ball) end),
+    receive
+	{'EXIT',Pid3,{{nocatch,ball},_Stack3}} -> ok
+    after 500 ->
+	ct:fail(throw)
+    end,
+    ok.
+
 sync_start_nolink(Config) when is_list(Config) ->
     _Pid = spawn_link(?MODULE, sp5, [self()]),
     receive
@@ -457,7 +482,7 @@ stop(_Config) ->
     %% System message is handled, but process dies with other reason
     %% than the given (in system_terminate/4 below)
     Pid5 = proc_lib:spawn(SysMsgProc),
-    {'EXIT',{badmatch,2}} = (catch proc_lib:stop(Pid5,crash,infinity)),
+    {'EXIT',{{badmatch,2},_Stacktrace}} = (catch proc_lib:stop(Pid5,crash,infinity)),
     false = erlang:is_process_alive(Pid5),
 
     %% Local registered name
-- 
2.10.2

openSUSE Build Service is sponsored by