File 0405-erl_eval-Support-the-fun-Name-Arity-syntax-for-creat.patch of Package erlang

From 4ad645d55b2cd25bf7689a0180d84e6dc13de7fc Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Fri, 25 Oct 2024 08:50:50 +0200
Subject: [PATCH 1/2] erl_eval: Support the fun Name/Arity syntax for creating
 a fun

Attempting to create a fun referering to either an auto-imported
BIF or a local fun defined in shell would fail:

    1> fun is_atom/1.
    ** exception error: undefined function erl_eval:is_atom/1
    2> id(I) -> I.
    ok
    3> fun id/1.
    ** exception error: undefined function erl_eval:id/1

This commit adds support for defining a fun based on either
an auto-imported BIF:

    1> F = fun is_atom/1.
    fun erlang:is_atom/1
    2> F(a).
    true
    3> F(42).
    false

Or on a local function defined in the shell:

    1> I = fun id/1.
    #Fun<erl_eval.42.18682967>
    2> I(42).
    ** exception error: undefined shell command id/1
    3> id(I) -> I.
    ok
    4> I(42).
    42

As shown in the example, it not necessary that the local fun is
defined at the time the fun is created; only that it is defined when
the fun is called.

Closes #8963
---
 lib/debugger/test/erl_eval_SUITE.erl |  1 -
 lib/stdlib/src/erl_eval.erl          | 21 +++++++++++++++---
 lib/stdlib/test/erl_eval_SUITE.erl   | 32 +++++++++++++++++++++++++---
 3 files changed, 47 insertions(+), 7 deletions(-)

diff --git a/lib/debugger/test/erl_eval_SUITE.erl b/lib/debugger/test/erl_eval_SUITE.erl
index 8907856583..4977b33ee7 100644
--- a/lib/debugger/test/erl_eval_SUITE.erl
+++ b/lib/debugger/test/erl_eval_SUITE.erl
@@ -948,7 +948,6 @@ funs(Config) when is_list(Config) ->
     error_check("apply(timer, sleep, [1]).", got_it, none, EFH),
     error_check("begin F = fun(T) -> timer:sleep(T) end,F(1) end.",
                       got_it, none, EFH),
-    error_check("fun c/1.", undef),
     error_check("fun a:b/0().", undef),
 
     MaxArgs = 20,
diff --git a/lib/stdlib/src/erl_eval.erl b/lib/stdlib/src/erl_eval.erl
index 0989f43ed9..560c56136c 100644
--- a/lib/stdlib/src/erl_eval.erl
+++ b/lib/stdlib/src/erl_eval.erl
@@ -489,9 +489,24 @@ expr({'fun',_Anno,{function,Mod0,Name0,Arity0}}, Bs0, Lf, Ef, RBs, FUVs) ->
     {[Mod,Name,Arity],Bs} = expr_list([Mod0,Name0,Arity0], Bs0, Lf, Ef, FUVs),
     F = erlang:make_fun(Mod, Name, Arity),
     ret_expr(F, Bs, RBs);
-expr({'fun',Anno,{function,Name,Arity}}, Bs0, _Lf, Ef, RBs, _FUVs) -> % R8
-    %% Don't know what to do...
-    apply_error(undef, [{?MODULE,Name,Arity}|?STACKTRACE], Anno, Bs0, Ef, RBs);
+expr({'fun',Anno,{function,Name,Arity}}, Bs0, Lf, Ef, RBs, FUVs) -> % R8
+    case erl_internal:bif(Name, Arity) of
+        true ->
+            %% Auto-imported BIF. Create an external fun.
+            ret_expr(fun erlang:Name/Arity, Bs0, RBs);
+        false ->
+            %% A local function assumed to be defined in the shell.
+            %% Create a wrapper fun that will call the local fun.
+            %% Calling the fun will succeed if the local fun is
+            %% defined when the call is made.
+            Args = [{var,Anno,list_to_atom("@arg" ++ [V])} ||
+                       V <- lists:seq($a, $a+Arity-1)],
+            H = Args,
+            G = [{atom,Anno,true}],
+            B = [{call,Anno,{atom,Anno,Name},Args}],
+            Cs = [{clause,Anno,H,G,B}],
+            expr({'fun',Anno,{clauses,Cs}}, Bs0, Lf, Ef, RBs, FUVs)
+    end;
 expr({'fun',Anno,{clauses,Cs}} = Ex, Bs, Lf, Ef, RBs, FUVs) ->
     {En,NewFUVs} = fun_used_bindings(Ex, Cs, Bs, FUVs),
     Info = {Anno,En,Lf,Ef,NewFUVs,Cs},
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index e28dd788bb..3cecbda635 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -68,6 +68,7 @@
 -export([count_down/2, count_down_fun/0, do_apply/2, 
          local_func/3, local_func_value/2]).
 -export([simple/0]).
+-export([my_div/2]).
 
 -ifdef(STANDALONE).
 -define(config(A,B),config(A,B)).
@@ -1217,8 +1218,6 @@ custom_stacktrace(Config) when is_list(Config) ->
     backtrace_check("#unknown.index.", {undef_record,unknown},
                     [erl_eval, mystack(1)], none, EFH),
 
-    backtrace_check("fun foo/2.", undef,
-                    [{erl_eval, foo, 2}, erl_eval, mystack(1)], none, EFH),
     backtrace_check("foo(1, 2).", undef,
                     [{erl_eval, foo, 2}, erl_eval, mystack(1)], none, EFH),
 
@@ -1369,7 +1368,6 @@ funs(Config) when is_list(Config) ->
     error_check("begin F = fun(T) -> timer:sleep(T) end,F(1) end.",
                       got_it, none, AnnEFH),
 
-    error_check("fun c/1.", undef),
     error_check("fun a:b/0().", undef),
 
     MaxArgs = 20,
@@ -1387,8 +1385,36 @@ funs(Config) when is_list(Config) ->
     %% Test that {M,F} is not accepted as a fun.
     error_check("{" ?MODULE_STRING ",module_info}().",
 		{badfun,{?MODULE,module_info}}),
+
+    %% Test defining and calling a fun based on an auto-imported BIF.
+    check(fun() ->
+                  F = fun is_binary/1,
+                  true = F(<<>>),
+                  false = F(a)
+          end,
+          ~S"""
+           F = fun is_binary/1,
+           true = F(<<>>),
+           false = F(a).
+           """,
+          false, ['F'], lfh(), none),
+
+    %% Test defining and calling a local fun defined in the shell.
+    check(fun() ->
+                  D = fun my_div/2,
+                  3 = D(15, 5)
+          end,
+          ~S"""
+           D = fun my_div/2,
+           3 = D(15, 5).
+           """,
+          3, ['D'], lfh(), efh()),
+
     ok.
 
+my_div(A, B) ->
+    A div B.
+
 run_many_args({S, As}) ->
     apply(eval_string(S), As) =:= As.
 
-- 
2.43.0

openSUSE Build Service is sponsored by