File 3341-Inline-funs-that-are-immediately-used.patch of Package erlang

From 72675baaa9fd30e9823da20e07452acd91a6b196 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 7 May 2020 14:48:18 +0200
Subject: [PATCH] Inline funs that are immediately used

Funs can be used to hide local variables. Example:

    a() ->
        A = fun() -> A = 21, 2 * A end(),
        foo:bar(A).

To avoid the slight runtime cost for such use of funs, teach the
compiler to inline funs that are used only once immediately after
creation.

Resolves #4019.
---
 lib/compiler/src/sys_core_fold.erl            | 39 ++++++++++++++++++-
 lib/compiler/test/fun_SUITE.erl               |  7 +++-
 .../test/int_eval_SUITE_data/stacktrace.erl   |  4 +-
 lib/stdlib/test/qlc_SUITE.erl                 | 11 ++++--
 4 files changed, 52 insertions(+), 9 deletions(-)

diff --git a/lib/compiler/src/sys_core_fold.erl b/lib/compiler/src/sys_core_fold.erl
index f5e26cdd08..49a3d57959 100644
--- a/lib/compiler/src/sys_core_fold.erl
+++ b/lib/compiler/src/sys_core_fold.erl
@@ -274,7 +274,7 @@ expr(#c_let{}=Let0, Ctxt, Sub) ->
 	    %% The argument for the let is "simple", i.e. has no
 	    %% complex structures such as let or seq that can be entered.
 	    ?ASSERT(verify_scope(Let, Sub)),
-	    opt_simple_let(Let, Ctxt, Sub);
+	    opt_fun_call(opt_simple_let(Let, Ctxt, Sub));
 	Expr ->
 	    %% The let body was successfully moved into the let argument.
 	    %% Now recursively re-process the new expression.
@@ -2172,6 +2172,43 @@ is_safe_bool_expr_list([C|Cs], BoolVars) ->
     end;
 is_safe_bool_expr_list([], _) -> true.
 
+opt_fun_call(#c_let{vars=[#c_var{name=V}],arg=#c_fun{}=FunDef,body=Body}=Let) ->
+    try do_opt_fun_call(V, FunDef, Body) of
+        impossible -> Let;
+        Expr -> Expr
+    catch
+        throw:impossible ->
+            Let
+    end;
+opt_fun_call(Expr) -> Expr.
+
+do_opt_fun_call(V, FunDef, #c_apply{op=#c_var{name=V},args=CallArgs}) ->
+    Values = core_lib:make_values(CallArgs),
+    simplify_fun_call(V, Values, FunDef, CallArgs);
+do_opt_fun_call(V, FunDef, #c_let{arg=#c_apply{op=#c_var{name=V},args=CallArgs},
+                                  body=Rest}=Let) ->
+    Values = core_lib:make_values([Rest|CallArgs]),
+    Inlined = simplify_fun_call(V, Values, FunDef, CallArgs),
+    Let#c_let{arg=Inlined};
+do_opt_fun_call(V, FunDef, #c_seq{arg=#c_apply{op=#c_var{name=V},args=CallArgs},
+                                  body=Rest}=Seq) ->
+    Values = core_lib:make_values([Rest|CallArgs]),
+    Inlined = simplify_fun_call(V, Values, FunDef, CallArgs),
+    Seq#c_seq{arg=Inlined};
+do_opt_fun_call(_, _, _) -> impossible.
+
+simplify_fun_call(V, Values, #c_fun{vars=Vars,body=FunBody}, CallArgs) ->
+    case not core_lib:is_var_used(V, Values) andalso length(Vars) =:= length(CallArgs) of
+        true ->
+            %% Safe to inline.
+            #c_let{vars=Vars,
+                   arg=core_lib:make_values(CallArgs),
+                   body=FunBody};
+        false ->
+            %% The fun is used more than once or there is an arity mismatch.
+            throw(impossible)
+    end.
+
 %% simplify_let(Let, Sub) -> Expr | impossible
 %%  If the argument part of an let contains a complex expression, such
 %%  as a let or a sequence, move the original let body into the complex
diff --git a/lib/compiler/test/fun_SUITE.erl b/lib/compiler/test/fun_SUITE.erl
index 2b8d60a885..387ed90ee6 100644
--- a/lib/compiler/test/fun_SUITE.erl
+++ b/lib/compiler/test/fun_SUITE.erl
@@ -56,12 +56,14 @@ end_per_group(_GroupName, Config) ->
 
 %%% The help functions below are copied from emulator:bs_construct_SUITE.
 
--define(T(B, L), {B, ??B, L}).
+-define(T(B, L), {fun() -> B end(), ??B, L}).
 
 l1() ->
     [
      ?T((begin A = 3, F = fun(A) -> 1; (_) -> 2 end, F(2) end), 1),
-     ?T((begin G = fun(1=0) -> ok end, {'EXIT',_} = (catch G(2)), ok end), ok)
+     ?T((begin G = fun(1=0) -> ok end, {'EXIT',_} = (catch G(2)), ok end), ok),
+     ?T((begin F = fun(_, 1) -> 1; (F, N) -> N * F(F, N-1) end, F(F, 5) end), 120),
+     ?T((begin F = fun(_, 1) -> 1; (F, N) -> N * F(F, N-1) end, F(F, 1), ok end), ok)
     ].
 
 test1(Config) when is_list(Config) ->
@@ -241,6 +243,7 @@ dup2() ->
 
 badarity(Config) when is_list(Config) ->
     {'EXIT',{{badarity,{_,[]}},_}} = (catch (fun badarity/1)()),
+    {'EXIT',{{badarity,_},_}} = (catch fun() -> 42 end(0)),
     ok.
 
 badfun(_Config) ->
diff --git a/lib/debugger/test/int_eval_SUITE_data/stacktrace.erl b/lib/debugger/test/int_eval_SUITE_data/stacktrace.erl
index 591841ada3..61230eb598 100644
--- a/lib/debugger/test/int_eval_SUITE_data/stacktrace.erl
+++ b/lib/debugger/test/int_eval_SUITE_data/stacktrace.erl
@@ -106,10 +106,10 @@ do_fun(Bool) ->
     F(Bool).					%Tail-recursive
 
 do_fun2(Bool) ->
-    F = fun(true) ->
+    F = fun(true, _) ->
 		cons(Bool)			%Tail-recursive
 	end,
-    F(Bool),					%Not tail-recursive
+    F(Bool, F),                                 %Not tail-recursive. (The fun is not inlined)
     ?LINE.
 
 cons(Bool) ->
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index 8cb4067b1d..067e398840 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -2382,10 +2382,12 @@ filter(Config) when is_list(Config) ->
                       false = lookup_keys(QH)
               end, [{1,1},{2,2},{3,3}])">>,
 
-       <<"fun(Z) ->
+       {cres,
+        <<"fun(Z) ->
             Q = qlc:q([X || Z < 2, X <- [1,2,3]]),
             [] = qlc:e(Q)
-          end(3)">>,
+           end(3)">>, [], {warnings,[{{2,31},sys_core_fold,no_clause_match},
+                                     {{2,31},sys_core_fold,nomatch_guard}]}},
 
        <<"H = qlc:q([{P1,A,P2,B,P3,C} ||
                   P1={A,_} <- [{1,a},{2,b}],
@@ -3095,13 +3097,14 @@ lookup2(Config) when is_list(Config) ->
         %% {warnings,[{{4,35},qlc,nomatch_filter}]}},
         []},
 
-       <<"F = fun(U) ->
+       {cres,
+        <<"F = fun(U) ->
                 Q = qlc:q([X || {X} <- [a,b,c], 
                                  X =:= if U -> true; true -> false end]),
                 [] = qlc:eval(Q),
                 false = lookup_keys(Q)
               end,
-          F(apa)">>,
+           F(apa)">>, [], {warnings,[{{3,43},sys_core_fold,nomatch_guard}]}},
 
        {cres,
         <<"etsc(fun(E) ->
-- 
2.26.2

openSUSE Build Service is sponsored by