File 2773-Fold-is_function-1-2-during-compilation.patch of Package erlang

From 5ba1635518459f581811b30f386fdf1f21f54178 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Micha=C5=82=20Muska=C5=82a?= <michal@muskala.eu>
Date: Sat, 17 Feb 2018 09:33:17 +0100
Subject: [PATCH] Fold is_function/1,2 during compilation

This can often appear in code after inlining some higher-order
functions.

* mark is_function/2 as pure
* track function types in sys_core_fold
* use those types to eval is_function/1,2 at compile-time when possible
---
 lib/compiler/src/erl_bifs.erl         |  3 ++-
 lib/compiler/src/sys_core_fold.erl    | 30 ++++++++++++++++++++++++++++--
 lib/compiler/test/core_fold_SUITE.erl | 17 +++++++++++++++++
 3 files changed, 47 insertions(+), 3 deletions(-)

diff --git a/lib/compiler/src/erl_bifs.erl b/lib/compiler/src/erl_bifs.erl
index a7452aebc8..71ab0e872a 100644
--- a/lib/compiler/src/erl_bifs.erl
+++ b/lib/compiler/src/erl_bifs.erl
@@ -91,6 +91,7 @@ is_pure(erlang, is_bitstring, 1) -> true;
 %% erlang:is_builtin/3 depends on the state (i.e. the version of the emulator).
 is_pure(erlang, is_float, 1) -> true;
 is_pure(erlang, is_function, 1) -> true;
+is_pure(erlang, is_function, 2) -> true;
 is_pure(erlang, is_integer, 1) -> true;
 is_pure(erlang, is_list, 1) -> true;
 is_pure(erlang, is_map, 1) -> true;
diff --git a/lib/compiler/src/sys_core_fold.erl b/lib/compiler/src/sys_core_fold.erl
index a13bdedaf9..3ce9a5fb27 100644
--- a/lib/compiler/src/sys_core_fold.erl
+++ b/lib/compiler/src/sys_core_fold.erl
@@ -99,7 +99,7 @@
               t=#{} :: map(),                       %Types
               in_guard=false}).                     %In guard or not.
 
--type type_info() :: cerl:cerl() | 'bool' | 'integer'.
+-type type_info() :: cerl:cerl() | 'bool' | 'integer' | {'fun', pos_integer()}.
 -type yes_no_maybe() :: 'yes' | 'no' | 'maybe'.
 -type sub() :: #sub{}.
 
@@ -883,6 +883,10 @@ fold_non_lit_args(Call, erlang, setelement, [Arg1,Arg2,Arg3], _) ->
     eval_setelement(Call, Arg1, Arg2, Arg3);
 fold_non_lit_args(Call, erlang, is_record, [Arg1,Arg2,Arg3], Sub) ->
     eval_is_record(Call, Arg1, Arg2, Arg3, Sub);
+fold_non_lit_args(Call, erlang, is_function, [Arg1], Sub) ->
+    eval_is_function_1(Call, Arg1, Sub);
+fold_non_lit_args(Call, erlang, is_function, [Arg1,Arg2], Sub) ->
+    eval_is_function_2(Call, Arg1, Arg2, Sub);
 fold_non_lit_args(Call, erlang, N, Args, Sub) ->
     NumArgs = length(Args),
     case erl_internal:comp_op(N, NumArgs) of
@@ -898,6 +902,22 @@ fold_non_lit_args(Call, erlang, N, Args, Sub) ->
     end;
 fold_non_lit_args(Call, _, _, _, _) -> Call.
 
+eval_is_function_1(Call, Arg1, Sub) ->
+    case get_type(Arg1, Sub) of
+        none -> Call;
+        {'fun',_} -> #c_literal{anno=cerl:get_ann(Call),val=true};
+        _ -> #c_literal{anno=cerl:get_ann(Call),val=false}
+    end.
+
+eval_is_function_2(Call, Arg1, #c_literal{val=Arity}, Sub)
+  when is_integer(Arity), Arity > 0 ->
+    case get_type(Arg1, Sub) of
+        none -> Call;
+        {'fun',Arity} -> #c_literal{anno=cerl:get_ann(Call),val=true};
+        _ -> #c_literal{anno=cerl:get_ann(Call),val=false}
+    end;
+eval_is_function_2(Call, _Arg1, _Arg2, _Sub) -> Call.
+
 %% Evaluate a relational operation using type information.
 eval_rel_op(Call, Op, [#c_var{name=V},#c_var{name=V}], _) ->
     Bool = erlang:Op(same, same),
@@ -3120,6 +3140,10 @@ update_types_2(V, [#c_tuple{}=P], Types) ->
     Types#{V=>P};
 update_types_2(V, [#c_literal{val=Bool}], Types) when is_boolean(Bool) ->
     Types#{V=>bool};
+update_types_2(V, [#c_fun{vars=Vars}], Types) ->
+    Types#{V=>{'fun',length(Vars)}};
+update_types_2(V, [#c_var{name={_,Arity}}], Types) ->
+    Types#{V=>{'fun',Arity}};
 update_types_2(V, [Type], Types) when is_atom(Type) ->
     Types#{V=>Type};
 update_types_2(_, _, Types) -> Types.
@@ -3138,6 +3162,8 @@ kill_types2(V, [{_,#c_tuple{}=Tuple}=Entry|Tdb]) ->
 	false -> [Entry|kill_types2(V, Tdb)];
 	true -> kill_types2(V, Tdb)
     end;
+kill_types2(V, [{_, {'fun',_}}=Entry|Tdb]) ->
+    [Entry|kill_types2(V, Tdb)];
 kill_types2(V, [{_,Atom}=Entry|Tdb]) when is_atom(Atom) ->
     [Entry|kill_types2(V, Tdb)];
 kill_types2(_, []) -> [].
diff --git a/lib/compiler/test/core_fold_SUITE.erl b/lib/compiler/test/core_fold_SUITE.erl
index ab7f36abf7..00b0e4ad42 100644
--- a/lib/compiler/test/core_fold_SUITE.erl
+++ b/lib/compiler/test/core_fold_SUITE.erl
@@ -278,6 +278,8 @@ coverage(Config) when is_list(Config) ->
     a = cover_remove_non_vars_alias({a,b,c}),
     error = cover_will_match_lit_list(),
     {ok,[a]} = cover_is_safe_bool_expr(a),
+    false = cover_is_safe_bool_expr2(a),
+    ok = cover_eval_is_function(fun id/1),
 
     ok = cover_opt_guard_try(#cover_opt_guard_try{list=[a]}),
     error = cover_opt_guard_try(#cover_opt_guard_try{list=[]}),
@@ -341,6 +343,15 @@ cover_is_safe_bool_expr(X) ->
 	    false
     end.
 
+cover_is_safe_bool_expr2(X) ->
+    try
+	V = [X],
+    is_function(V, 1)
+    catch
+	_:_ ->
+	    false
+    end.
+
 cover_opt_guard_try(Msg) ->
     if
 	length(Msg#cover_opt_guard_try.list) =/= 1 ->
@@ -349,6 +360,12 @@ cover_opt_guard_try(Msg) ->
 	    ok
     end.
 
+cover_eval_is_function(X) ->
+    case X of
+        {a,_} -> is_function(X);
+        _ -> ok
+    end.
+
 bsm_an_inlined(<<_:8>>, _) -> ok;
 bsm_an_inlined(_, _) -> error.
 
-- 
2.16.4

openSUSE Build Service is sponsored by