File 3361-eunit-Remove-fun_parent-1-as-it-relies-on-undocument.patch of Package erlang

From 16124d13e2b4b82ae14be49005e9a56342ca35dc Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Tue, 18 Jan 2022 08:37:16 +0100
Subject: [PATCH] eunit: Remove fun_parent/1, as it relies on undocumented
 behavior

---
 lib/eunit/src/eunit_data.erl |  4 ++--
 lib/eunit/src/eunit_lib.erl  | 23 +----------------------
 2 files changed, 3 insertions(+), 24 deletions(-)

diff --git a/lib/eunit/src/eunit_data.erl b/lib/eunit/src/eunit_data.erl
index 702d3a5687..e36f6cad13 100644
--- a/lib/eunit/src/eunit_data.erl
+++ b/lib/eunit/src/eunit_data.erl
@@ -391,7 +391,7 @@ parse({with, X, As}=T) when is_list(As) ->
     case As of
 	[A | As1] ->
 	    check_arity(A, 1, T),
-	    {data, [{eunit_lib:fun_parent(A), fun () -> A(X) end},
+	    {data, [{erlang:fun_info_mfa(A), fun () -> A(X) end},
 		    {with, X, As1}]};
 	[] ->
 	    {data, []}
@@ -439,7 +439,7 @@ parse_simple(F) ->
 
 parse_function(F) when is_function(F) ->
     check_arity(F, 0, F),
-    #test{f = F, location = eunit_lib:fun_parent(F)};
+    #test{f = F, location = erlang:fun_info_mfa(F)};
 parse_function({test, M, F}) when is_atom(M), is_atom(F) ->
     #test{f = eunit_test:mf_wrapper(M, F), location = {M, F, 0}};
 parse_function({M, F}) when is_atom(M), is_atom(F) ->
diff --git a/lib/eunit/src/eunit_lib.erl b/lib/eunit/src/eunit_lib.erl
index c7555597c2..e3129eb30f 100644
--- a/lib/eunit/src/eunit_lib.erl
+++ b/lib/eunit/src/eunit_lib.erl
@@ -32,7 +32,7 @@
 -include("eunit_internal.hrl").
 
 
--export([dlist_next/1, uniq/1, fun_parent/1, is_string/1, command/1,
+-export([dlist_next/1, uniq/1, is_string/1, command/1,
 	 command/2, command/3, trie_new/0, trie_store/2, trie_match/2,
 	 split_node/1, consult_file/1, list_dir/1, format_exit_term/1,
 	 format_exception/1, format_exception/2, format_error/1, format_error/2,
@@ -377,27 +377,6 @@ split_node_1([], As) ->  split_node_2(As, "localhost").
 split_node_2(As, Cs) ->
     {list_to_atom(lists:reverse(As)), list_to_atom(Cs)}.
 
-%% ---------------------------------------------------------------------
-%% Get the name of the containing function for a fun. (This is encoded
-%% in the name of the generated function that implements the fun.)
-fun_parent(F) ->
-    {module, M} = erlang:fun_info(F, module),
-    {name, N} = erlang:fun_info(F, name),
-    case erlang:fun_info(F, type) of
-	{type, external} ->
-	    {arity, A} = erlang:fun_info(F, arity),
-	    {M, N, A};
-	{type, local} ->
-            [$-|S] = atom_to_list(N),
-            [S2, T] = string:split(S, "/", trailing),
-            {M, list_to_atom(S2), element(1, string:to_integer(T))}
-    end.
-
--ifdef(TEST).
-fun_parent_test() ->
-    {?MODULE,fun_parent_test,0} = fun_parent(fun (A) -> {ok,A} end).
--endif.
-
 %% ---------------------------------------------------------------------
 %% Ye olde uniq function
 
-- 
2.31.1

openSUSE Build Service is sponsored by