File 0479-Fix-internal-consistency-failure-for-is_function-2.patch of Package erlang

From 8be2c32fe0534d863c6ce6d7665011a162fc39ec Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 20 Nov 2018 13:05:51 +0100
Subject: [PATCH] Fix internal consistency failure for is_function/2

There could be an internal consistency failure when using is_function/2,
because an optimization did not take into account that is_function/2 can fail.

https://bugs.erlang.org/browse/ERL-778
---
 lib/compiler/src/beam_utils.erl        |  5 ++++-
 lib/compiler/test/beam_utils_SUITE.erl | 23 +++++++++++++++++++++--
 2 files changed, 25 insertions(+), 3 deletions(-)

diff --git a/lib/compiler/src/beam_utils.erl b/lib/compiler/src/beam_utils.erl
index 6e23003fc7..6b2ab5a2a4 100644
--- a/lib/compiler/src/beam_utils.erl
+++ b/lib/compiler/src/beam_utils.erl
@@ -620,8 +620,11 @@ check_liveness_block_2(R, {gc_bif,Op,{f,Lbl}}, Ss, St) ->
     check_liveness_block_3(R, Lbl, St);
 check_liveness_block_2(R, {bif,Op,{f,Lbl}}, Ss, St) ->
     Arity = length(Ss),
+
+    %% Note that is_function/2 is a type test but is not safe.
     case erl_internal:comp_op(Op, Arity) orelse
-	erl_internal:new_type_test(Op, Arity) of
+	(erl_internal:new_type_test(Op, Arity) andalso
+         erl_bifs:is_safe(erlang, Op, Arity)) of
 	true ->
 	    {killed,St};
 	false ->
diff --git a/lib/compiler/test/beam_utils_SUITE.erl b/lib/compiler/test/beam_utils_SUITE.erl
index ac19305d69..ff0f72d519 100644
--- a/lib/compiler/test/beam_utils_SUITE.erl
+++ b/lib/compiler/test/beam_utils_SUITE.erl
@@ -24,6 +24,7 @@
 	 apply_fun/1,apply_mf/1,bs_init/1,bs_save/1,
 	 is_not_killed/1,is_not_used_at/1,
 	 select/1,y_catch/1,otp_8949_b/1,liveopt/1,coverage/1,
+	 unsafe_is_function/1,
 	 y_registers/1]).
 -export([id/1]).
 
@@ -46,6 +47,7 @@ groups() ->
        otp_8949_b,
        liveopt,
        coverage,
+       unsafe_is_function,
        y_registers
       ]}].
 
@@ -375,6 +377,25 @@ is_used_fr(X, Y) ->
 do(A, B) -> {A,B}.
 appointment(#{"resolution" := Url}) ->
     do(receive _ -> Url end, #{true => Url}).
+
+%% ERL-778.
+unsafe_is_function(Config) ->
+    {undefined,any} = unsafe_is_function(undefined, any),
+    {ok,any} = unsafe_is_function(fun() -> ok end, any),
+    {'EXIT',{{case_clause,_},_}} = (catch unsafe_is_function(fun(_) -> ok end, any)),
+    ok.
+
+unsafe_is_function(F, M) ->
+    %% There would be an internal consistency failure:
+    %%   Instruction: {bif,is_function,{f,0},[{x,0},{integer,0}],{x,2}}
+    %%   Error:       {uninitialized_reg,{y,0}}:
+
+    NewValue = case is_function(F, 0) of
+                true -> F();
+                false when F =:= undefined -> undefined
+            end,
+    {NewValue,M}.
+
 
 %% The identity function.
 id(I) -> I.
-- 
2.16.4

openSUSE Build Service is sponsored by