File 4342-xref-drop-pre-R13-experimental-code.patch of Package erlang
From e8236f66c20e6ead3b0960fb49e356ddf4f2a0e0 Mon Sep 17 00:00:00 2001
From: Richard Carlsson <carlsson.richard@gmail.com>
Date: Sat, 27 Dec 2025 18:49:47 +0100
Subject: [PATCH 2/2] xref: drop pre-R13 experimental code
---
lib/tools/src/xref_base.erl | 36 +++------------
lib/tools/src/xref_reader.erl | 46 ++------------------
lib/tools/test/xref_SUITE.erl | 16 +++----
lib/tools/test/xref_SUITE_data/read/read.erl | 37 +++++++++-------
4 files changed, 36 insertions(+), 99 deletions(-)
diff --git a/lib/tools/src/xref_base.erl b/lib/tools/src/xref_base.erl
index 3071974430..9efe4a2eb6 100644
--- a/lib/tools/src/xref_base.erl
+++ b/lib/tools/src/xref_base.erl
@@ -907,7 +907,6 @@ depr_desc(_) -> undefined.
%% Assumes:
%% L U X is a subset of dom DefAt
%% dom CallAt = LC U XC
-%% Attrs is collected from the attribute 'xref' (experimental).
do_add_module(S, XMod, Unres, Data) ->
#xref{mode = Mode} = S,
Mode = S#xref.mode,
@@ -916,31 +915,22 @@ do_add_module(S, XMod, Unres, Data) ->
{ok, Ms, Bad, NS}.
prepare_module(_Mode = functions, XMod, Unres0, Data) ->
- {DefAt0, LPreCAt0, XPreCAt0, LC0, XC0, X0, Attrs, Depr, OL0} = Data,
- %% Bad is a list of bad values of 'xref' attributes.
- {ALC0,AXC0,Bad0} = Attrs,
+ {DefAt0, LPreCAt0, XPreCAt0, LC0, XC0, X0, _, Depr, OL0} = Data,
FT = [tspec(func)],
FET = [tspec(fun_edge)],
PCA = [tspec(pre_call_at)],
- XPreCAt1 = xref_utils:xset(XPreCAt0, PCA),
- LPreCAt1 = xref_utils:xset(LPreCAt0, PCA),
+ XPreCAt = xref_utils:xset(XPreCAt0, PCA),
+ LPreCAt = xref_utils:xset(LPreCAt0, PCA),
DefAt = xref_utils:xset(DefAt0, [tspec(def_at)]),
X1 = xref_utils:xset(X0, FT),
- XC1 = xref_utils:xset(XC0, FET),
- LC1 = xref_utils:xset(LC0, FET),
- AXC1 = xref_utils:xset(AXC0, PCA),
- ALC1 = xref_utils:xset(ALC0, PCA),
+ XC = xref_utils:xset(XC0, FET),
+ LC = xref_utils:xset(LC0, FET),
UnresCalls = xref_utils:xset(Unres0, PCA),
Unres = domain(UnresCalls),
OL1 = xref_utils:xset(OL0, FT),
DefinedFuns = domain(DefAt),
- {AXC, ALC, Bad1, LPreCAt2, XPreCAt2} =
- extra_edges(AXC1, ALC1, Bad0, DefinedFuns),
- Bad = map(fun(B) -> {xref_attr, B} end, Bad1),
- LPreCAt = union(LPreCAt1, LPreCAt2),
- XPreCAt = union(XPreCAt1, XPreCAt2),
NoCalls = no_elements(LPreCAt) + no_elements(XPreCAt),
LCallAt = relation_to_family(LPreCAt),
XCallAt = relation_to_family(XPreCAt),
@@ -948,14 +938,12 @@ prepare_module(_Mode = functions, XMod, Unres0, Data) ->
%% Local and exported functions with no definitions are removed.
L = difference(DefinedFuns, X1),
X = difference(DefinedFuns, L),
- XC = union(XC1, AXC),
- LC = union(LC1, ALC),
{DF1,DF_11,DF_21,DF_31,DBad} = depr_mod(Depr, X),
{EE, ECallAt} = inter_graph(X, L, LC, XC, CallAt),
{ok, {functions, XMod, [DefAt,L,X,LCallAt,XCallAt,CallAt,LC,XC,EE,ECallAt,
OL1,DF1,DF_11,DF_21,DF_31], NoCalls, Unres},
- DBad++Bad};
+ DBad};
prepare_module(_Mode = modules, XMod, _Unres, Data) ->
{X0, I0, Depr} = Data,
X1 = xref_utils:xset(X0, [tspec(func)]),
@@ -1030,18 +1018,6 @@ depr_mod({Depr,Bad0}, X) ->
Bad = map(fun(B) -> {depr_attr, B} end, usort(Bad2++Bad0)),
{DF,DF_1,DF_2,DF_3,Bad}.
-%% Extra edges gathered from the attribute 'xref' (experimental)
-extra_edges(CAX, CAL, Bad0, F) ->
- AXC0 = domain(CAX),
- ALC0 = domain(CAL),
- AXC = restriction(AXC0, F),
- ALC = restriction(2, restriction(ALC0, F), F),
- LPreCAt2 = restriction(CAL, ALC),
- XPreCAt2 = restriction(CAX, AXC),
- Bad = Bad0 ++ to_external(difference(AXC0, AXC))
- ++ to_external(difference(ALC0, ALC)),
- {AXC, ALC, Bad, LPreCAt2, XPreCAt2}.
-
no_info(X, L, LC, XC, EE, Unres, NoCalls, NoUnresCalls) ->
NoUnres = no_elements(Unres),
[{no_calls, {NoCalls-NoUnresCalls, NoUnresCalls}},
diff --git a/lib/tools/src/xref_reader.erl b/lib/tools/src/xref_reader.erl
index 47eed9ce08..82dcda0ce8 100644
--- a/lib/tools/src/xref_reader.erl
+++ b/lib/tools/src/xref_reader.erl
@@ -42,10 +42,6 @@
% (for coping with list comprehension)
matches=[], % records other bound variables
unresolved=[], % unresolved calls, {{mfa(),mfa()},Line}
- %% experimental; -xref(FunEdge) is recognized.
- lattrs=[], % local calls, {{mfa(),mfa()},Line}
- xattrs=[], % external calls, -"-
- battrs=[], % badly formed xref attributes, term().
on_load % function name
}).
@@ -53,8 +49,7 @@
%% -> {ok, Module, {DefAt, LCallAt, XCallAt, LC, XC, X, Attrs, Depr, OL},
%% Unresolved}} | EXIT
-%% Attrs = {ALC, AXC, Bad}
-%% ALC, AXC and Bad are extracted from the attribute 'xref'. An experiment.
+%% Attrs = {[], [], []} (no longer used)
module(Module, Forms, CollectBuiltins, X, DF) ->
Attrs = [{Attr,V} || {attribute,_Anno,Attr,V} <- Forms],
IsAbstract = xref_utils:is_abstract_module(Attrs),
@@ -69,19 +64,15 @@ forms([], S) ->
#xrefr{module = M, def_at = DefAt,
l_call_at = LCallAt, x_call_at = XCallAt,
el = LC, ex = XC, x = X, df = Depr, on_load = OnLoad,
- lattrs = AL, xattrs = AX, battrs = B, unresolved = U} = S,
+ unresolved = U} = S,
OL = case OnLoad of
undefined -> [];
F ->
[{M, F, 0}]
end,
- Attrs = {lists:reverse(AL), lists:reverse(AX), lists:reverse(B)},
+ Attrs = {[], [], []},
{ok, M, {DefAt, LCallAt, XCallAt, LC, XC, X, Attrs, Depr, OL}, U}.
-form({attribute, Anno, xref, Calls}, S) -> % experimental
- #xrefr{module = M, function = Fun,
- lattrs = L, xattrs = X, battrs = B} = S,
- attr(Calls, erl_anno:line(Anno), M, Fun, L, X, B, S);
form({attribute, _, on_load, {F, 0}}, S) ->
S#xrefr{on_load = F};
form({attribute, _Anno, _Attr, _Val}, S) ->
@@ -124,37 +115,6 @@ clauses([{clause, _Anno, _H, G, B} | Cs], FunVars, Matches, S) ->
clauses([], _FunVars, _Matches, S) ->
S.
-attr(NotList, Ln, M, Fun, AL, AX, B, S) when not is_list(NotList) ->
- attr([NotList], Ln, M, Fun, AL, AX, B, S);
-attr([E={From, To} | As], Ln, M, Fun, AL, AX, B, S) ->
- case mfa(From, M) of
- {_, _, MFA} when MFA =:= Fun; [] =:= Fun ->
- attr(From, To, Ln, M, Fun, AL, AX, B, S, As, E);
- {_, _, _} ->
- attr(As, Ln, M, Fun, AL, AX, [E | B], S);
- _ ->
- attr(Fun, E, Ln, M, Fun, AL, AX, B, S, As, E)
- end;
-attr([To | As], Ln, M, Fun, AL, AX, B, S) ->
- attr(Fun, To, Ln, M, Fun, AL, AX, B, S, As, To);
-attr([], _Ln, _M, _Fun, AL, AX, B, S) ->
- S#xrefr{lattrs = AL, xattrs = AX, battrs = B}.
-
-attr(From, To, Ln, M, Fun, AL, AX, B, S, As, E) ->
- case {mfa(From, M), mfa(To, M)} of
- {{true,_,F}, {_,external,T}} ->
- attr(As, Ln, M, Fun, AL, [{{F,T},Ln} | AX], B, S);
- {{true,_,F}, {_,local,T}} ->
- attr(As, Ln, M, Fun, [{{F,T},Ln} | AL], AX, B, S);
- _ -> attr(As, Ln, M, Fun, AL, AX, [E | B], S)
- end.
-
-mfa({F,A}, M) when is_atom(F), is_integer(A) ->
- {true, local, {M,F,A}};
-mfa(MFA={M,F,A}, M1) when is_atom(M), is_atom(F), is_integer(A) ->
- {M=:=M1, external, MFA};
-mfa(_, _M) -> false.
-
expr({'if', _Anno, Cs}, S) ->
clauses(Cs, S);
expr({'case', _Anno, E, Cs}, S) ->
diff --git a/lib/tools/test/xref_SUITE.erl b/lib/tools/test/xref_SUITE.erl
index 653c38acc7..d8585ff4a4 100644
--- a/lib/tools/test/xref_SUITE.erl
+++ b/lib/tools/test/xref_SUITE.erl
@@ -1010,8 +1010,8 @@ do_read(File) ->
%% What is expected when xref_SUITE_data/read/read.erl is added:
read_expected() ->
%% Line positions in xref_SUITE_data/read/read.erl:
- POS1 = 28, POS2 = POS1+10, POS3 = POS2+6, POS4 = POS3+6, POS5 = POS4+10,
- POS6 = POS5+5, POS7 = POS6+6, POS8 = POS7+6, POS9 = POS8+8,
+ POS0 = 26, POS1 = POS0+9, POS2 = POS1+10, POS3 = POS2+6, POS4 = POS3+6,
+ POS5 = POS4+10, POS6 = POS5+5, POS7 = POS6+6, POS8 = POS7+6, POS9 = POS8+8,
POS10 = POS9+10, POS11 = POS10+7, POS12 = POS11+8, POS13 = POS12+10,
POS14 = POS13+18, POS15 = POS14+23,
@@ -1058,8 +1058,8 @@ read_expected() ->
{POS13+3,{FF,{'$M_EXPR','$F_EXPR',-1}}},
{POS14+8,{{read,bi,0},{'$M_EXPR','$F_EXPR',1}}}],
- O1 = [{20,{{read,lc,0},{ets,new,0}}},
- {21,{{read,lc,0},{ets,tab2list,1}}},
+ O1 = [{POS0+1,{{read,lc,0},{ets,new,0}}},
+ {POS0+2,{{read,lc,0},{ets,tab2list,1}}},
{POS1+1,{FF,{erlang,spawn,1}}},
{POS1+1,{FF,{mod17,fun17,0}}},
{POS1+2,{FF,{erlang,spawn,1}}},
@@ -1128,13 +1128,7 @@ read_expected() ->
{POS14+11,{{read,bi,0},{erlang,module_info,0}}},
{POS14+17,{{read,bi,0},{read,bi,0}}}],
- OK = case Version of
- abstract_v2 ->
- [{16,{FF,{read,'$F_EXPR',178}}},
- {17,{FF,{modul,'$F_EXPR',179}}}]
- ++
- O1
- end,
+ OK = O1,
%% When builtins =:= true:
OKB1 = [{POS13+1,{FF,{erts_debug,apply,4}}},
diff --git a/lib/tools/test/xref_SUITE_data/read/read.erl b/lib/tools/test/xref_SUITE_data/read/read.erl
index 5f388194b0..fe616750c1 100644
--- a/lib/tools/test/xref_SUITE_data/read/read.erl
+++ b/lib/tools/test/xref_SUITE_data/read/read.erl
@@ -1,22 +1,29 @@
+%% %CopyrightBegin%
+%%
+%% SPDX-License-Identifier: Apache-2.0
+%%
+%% Copyright Ericsson AB 2000-2025. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+
-module(read).
-export([lc/0, funfuns/0, bi/0]).
--xref({xx,ff,22}).
--xref({{all,0},{no,0}}).
--xref([{{all,0},{i,0}},{{all,0},{x2,5}}]).
--xref([apa]).
--xref({all,0}).
--xref([{{{all},0},{no,0}},{{all,0},{m,x2,5}}]).
--xref([{{a,14},{q,f,17}}]).
--xref({{i,f,17},{g,18}}).
--xref({{j,f,17},{i,g,18}}).
-
--xref({{funfuns,0},{'$F_EXPR',177}}).
--xref({{funfuns,0},{?MODULE,'$F_EXPR',178}}).
--xref({{funfuns,0},{modul,'$F_EXPR',179}}).
-
lc() ->
+ %% POS0=26
Tab = ets:new(),
[Mt||{_M,Mt} <- ets:tab2list(Tab)].
@@ -25,7 +32,7 @@ funfuns() ->
%% Spawn...
- %% Recognized. POS1=28.
+ %% Recognized. POS1=POS0+9.
spawn(fun() -> mod17:fun17() end),
spawn(fun local/0),
spawn(fun binary_to_term/1), % builtin, not collected
--
2.51.0