⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 xref_base.erl

📁 OTP是开放电信平台的简称
💻 ERL
📖 第 1 页 / 共 4 页
字号:
    %% {EE, ECallAt} = inter_graph(X, L, LC, XC, LCallAt, XCallAt),    Self = self(),    Fun = fun() -> inter_graph(Self, X, L, LC, XC, CallAt) end,     {EE, ECallAt} = 	xref_utils:subprocess(Fun, [link, {min_heap_size,100000}]),    [DefAt2,L2,X2,LCallAt2,XCallAt2,CallAt2,LC2,XC2,EE2,ECallAt2,     DF2,DF_12,DF_22,DF_32] =	pack([DefAt,L,X,LCallAt,XCallAt,CallAt,LC,XC,EE,ECallAt,              DF1,DF_11,DF_21,DF_31]),    %% Foo = [DefAt2,L2,X2,LCallAt2,XCallAt2,CallAt2,LC2,XC2,EE2,ECallAt2,    %%        DF2,DF_12,DF_22,DF_32],    %% io:format("{~p, ~p, ~p},~n", [M, pack:lsize(Foo), pack:usize(Foo)]),    LU = range(LC2),    LPredefined = predefined_funs(LU),    MS = xref_utils:xset(M, atom),    T = from_sets({MS,DefAt2,L2,X2,LCallAt2,XCallAt2,CallAt2,		   LC2,XC2,LU,EE2,ECallAt2,Unres,LPredefined,                   DF2,DF_12,DF_22,DF_32}),    NoUnres = XMod#xref_mod.no_unresolved,    Info = no_info(X2, L2, LC2, XC2, EE2, Unres, NoCalls, NoUnres),    XMod1 = XMod#xref_mod{data = T, info = Info},    S1 = S#xref{modules = dict:store(M, XMod1, S#xref.modules)},    {ok, [M], DBad++Bad, take_down(S1)};do_add_module(S, M, XMod, _Unres, Data) when S#xref.mode =:= modules ->    {X0, I0, Depr} = Data,    X1 = xref_utils:xset(X0, [tspec(func)]),    I1 = xref_utils:xset(I0, [tspec(func)]),    {DF1,DF_11,DF_21,DF_31,DBad} = depr_mod(Depr, X1),    [X2,I2,DF2,DF_12,DF_22,DF_32] = pack([X1,I1,DF1,DF_11,DF_21,DF_31]),    MS = xref_utils:xset(M, atom),    T = from_sets({MS, X2, I2, DF2, DF_12, DF_22, DF_32}),    Info = [],    XMod1 = XMod#xref_mod{data = T, info = Info},    S1 = S#xref{modules = dict:store(M, XMod1, S#xref.modules)},    {ok, [M], DBad, take_down(S1)}.depr_mod({Depr,Bad0}, X) ->    %% Bad0 are badly formed deprecated attributes.    %% Here deprecated functions that are neither BIFs nor exported    %% are deemed bad. do_set_up filters away BIFs if necessary.    {DF_10,DF_20,DF_30,DF0} = Depr,    FT = [tspec(func)],    DF1 = xref_utils:xset(DF0, FT),    DF_11 = xref_utils:xset(DF_10, FT),    DF_21 = xref_utils:xset(DF_20, FT),    DF_31 = xref_utils:xset(DF_30, FT),    All = union(from_sets([DF1,DF_11,DF_21,DF_31])),    Fun = {external, fun({M,F,A}) -> xref_utils:is_builtin(M, F, A) end},    XB = union(X, specification(Fun, All)),    DF_1 = intersection(DF_11, XB),    DF_2 = union(intersection(DF_21, XB), DF_1),    DF_3 = union(intersection(DF_31, XB), DF_2),    DF = union(intersection(DF1, XB), DF_3),    Bad1 = difference(All, XB),    Bad2 = to_external(difference(Bad1, predefined_funs(Bad1))),    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}},      {no_function_calls, {no_elements(LC), no_elements(XC)-NoUnres, NoUnres}},     {no_functions, {no_elements(L), no_elements(X)}},     %% Note: this is overwritten in do_set_up():     {no_inter_function_calls, no_elements(EE)}].inter_graph(Pid, X, L, LC, XC, CallAt) ->    Pid ! {self(), inter_graph(X, L, LC, XC, CallAt)}.%% Inter Call Graph.%inter_graph(_X, _L, _LC, _XC, _CallAt) ->%    {empty_set(), empty_set()};inter_graph(X, L, LC, XC, CallAt) ->    G = xref_utils:relation_to_graph(LC),    Reachable0 = digraph_utils:reachable_neighbours(to_external(X), G),    Reachable = xref_utils:xset(Reachable0, [tspec(func)]),    % XL includes exports and locals that are not used by any exports    % (the locals are tacitly ignored in the comments below).    XL = union(difference(L, Reachable), X),    % Immediate local calls between the module's own exports are qualified.    LEs = restriction(restriction(2, LC, XL), XL),    % External calls to the module's exports are qualified.    XEs = restriction(XC, XL),    Es = union(LEs, XEs),    E1 = to_external(restriction(difference(LC, LEs), XL)),    R0 = xref_utils:xset(reachable(E1, G, []), 			 [{tspec(func), tspec(fun_edge)}]),    true = digraph:delete(G),        % RL is a set of indirect local calls to exports.    RL = restriction(R0, XL),    % RX is a set of indirect external calls to exports.    RX = relative_product1(R0, XC),    R = union(RL, converse(RX)),    EE0 = projection({external, fun({Ee2,{Ee1,_L}}) -> {Ee1,Ee2} end}, R),    EE = union(Es, EE0),    % The first call in each chain, {e1,l}, contributes with the line    % number(s) l.    SFun = {external, fun({Ee2,{Ee1,Ls}}) -> {{Ee1,Ls},{Ee1,Ee2}} end},    ECallAt1 = relative_product1(projection(SFun, R), CallAt),    ECallAt2 = union(ECallAt1, restriction(CallAt, Es)),    ECallAt = family_union(relation_to_family(ECallAt2)),    ?FORMAT("XL=~p~nXEs=~p~nLEs=~p~nE1=~p~nR0=~p~nRL=~p~nRX=~p~nR=~p~n"	    "EE=~p~nECallAt1=~p~nECallAt2=~p~nECallAt=~p~n~n",	    [XL, XEs, LEs, E1, R0, RL, RX, R, EE, 	     ECallAt1, ECallAt2, ECallAt]),    {EE, ECallAt}.%% -> set of {V2,{V1,L1}}reachable([E = {_X, L} | Xs], G, R) ->    Ns = digraph_utils:reachable([L], G),    reachable(Xs, G, reach(Ns, E, R));reachable([], _G, R) ->    R.reach([N | Ns], E, L) ->    reach(Ns, E, [{N, E} | L]);reach([], _E, L) ->    L.tspec(func)        -> {atom, atom, atom};tspec(fun_edge)    -> {tspec(func), tspec(func)};tspec(def_at)      -> {tspec(func), atom};tspec(pre_call_at) -> {tspec(fun_edge), atom}.%% -> {ok, OldXrefRel, NewState} | throw(Error)do_remove_release(S, RelName) ->    case dict:find(RelName, S#xref.releases) of	error ->	    throw_error({no_such_release, RelName});	{ok, XRel} ->	    S1 = take_down(S),	    S2 = remove_rel(S1, RelName),	    {ok, XRel, S2}    end.%% -> {ok, OldXrefApp, NewState} | throw(Error)do_remove_application(S, AppName) ->    case dict:find(AppName, S#xref.applications) of	error ->	    throw_error({no_such_application, AppName});	{ok, XApp} ->	    S1 = take_down(S),	    S2 = remove_apps(S1, [AppName]),	    {ok, XApp, S2}    end.%% -> {ok, OldXMod, NewState} | throw(Error)do_remove_module(S, Module) ->    case dict:find(Module, S#xref.modules) of	error ->	    throw_error({no_such_module, Module});	{ok, XMod} ->	    S1 = take_down(S),	    {ok, XMod, remove_modules(S1, [Module])}    end.remove_rel(S, RelName) ->    Rels = [RelName],    Fun = fun({A,XApp}, L) when XApp#xref_app.rel_name =:= Rels ->		  [A | L];	     (_, L) -> L	  end,    Apps = foldl(Fun, [], dict:to_list(S#xref.applications)),    S1 = remove_apps(S, Apps),    NewReleases = remove_erase(Rels, S1#xref.releases),    S1#xref{releases = NewReleases}.remove_apps(S, Apps) ->    Fun = fun({M,XMod}, L) ->		  case XMod#xref_mod.app_name of		      [] -> L;		      [AppName] -> [{AppName,M} | L]		  end	  end,    Ms = foldl(Fun, [], dict:to_list(S#xref.modules)),    Modules = to_external(image(relation(Ms), set(Apps))),    S1 = remove_modules(S, Modules),    NewApplications = remove_erase(Apps, S1#xref.applications),    S1#xref{applications = NewApplications}.remove_modules(S, Modules) ->    NewModules = remove_erase(Modules, S#xref.modules),    S#xref{modules = NewModules}.remove_erase([K | Ks], D) ->    remove_erase(Ks, dict:erase(K, D));remove_erase([], D) ->    D.do_add_libraries(Path, Verbose, State) ->    message(Verbose, lib_search, []),    {C, E} = xref_utils:list_path(Path, [?Suffix]),        message(Verbose, done, []),    MDs = to_external(relation_to_family(relation(C))),    %% message(Verbose, lib_check, []),    Reply = check_file(MDs, [], E, Path, State),    %% message(Verbose, done, []),    Reply.%%check_file([{_M, [{_N, Dir, File} | _]} | MDs], L, E, Path, State) ->%%    case beam_lib:version(filename:join(Dir, File)) of%%	{ok, {Module, _Version}} ->%%	    XLib = #xref_lib{name = Module, dir = Dir},%%	    check_file(MDs, [{Module,XLib} | L], E, Path, State);%%	Error ->%%	    check_file(MDs, L, [Error | E], Path, State)%%    end;check_file([{Module, [{_N, Dir, _File} | _]} | MDs], L, E, Path, State) ->    XLib = #xref_lib{name = Module, dir = Dir},    check_file(MDs, [{Module,XLib} | L], E, Path, State);check_file([], L, [], Path, State) ->    D = dict:from_list(L),    State1 = State#xref{library_path = Path, libraries = D},    %% Take down everything, that's simplest.    NewState = take_down(State1),    {ok, NewState};check_file([], _L, [E | _], _Path, _State) ->    E.%% -> {ok, NewState} | Error%% Finding libraries may fail.do_set_up(S, _VerboseOpt) when S#xref.variables =/= not_set_up ->    {ok, S};do_set_up(S, VerboseOpt) ->    message(VerboseOpt, set_up, []),    Reply = (catch do_set_up(S)),    message(VerboseOpt, done, []),    Reply.%% If data has been supplied using add_module/9 (and that is the only%% sanctioned way), then DefAt, L, X, LCallAt, XCallAt, CallAt, XC, LC, %% and LU are  guaranteed to be functions (with all supplied %% modules as domain (disregarding unknown modules, that is, modules %% not supplied but hosting unknown functions)).%% As a consequence, V and E are also functions. V is defined for unknown%% modules also.%% UU is also a function (thanks to sofs:family_difference/2...).%% XU on the other hand can be a partial function (that is, not defined %% for all modules). U is derived from XU, so U is also partial.%% The inverse variables - LC_1, XC_1, E_1 and EE_1 - are all partial.%% B is also partial.do_set_up(S) when S#xref.mode =:= functions ->    ModDictList = dict:to_list(S#xref.modules),    [DefAt0, L, X0, LCallAt, XCallAt, CallAt, LC, XC, LU,      EE0, ECallAt, UC, LPredefined,     Mod_DF,Mod_DF_1,Mod_DF_2,Mod_DF_3] = make_families(ModDictList, 18),        {XC_1, XU, XPredefined} = do_set_up_1(XC),    LC_1 = user_family(union_of_family(LC)),    E_1 = family_union(XC_1, LC_1),    Predefined = family_union(XPredefined, LPredefined),    %% Add "hidden" functions to the exports.    X1 = family_union(X0, Predefined),    F1 = family_union(L, X1),    V = family_union(F1, XU),    E = family_union(LC, XC),    M = domain(V),    M2A = make_M2A(ModDictList),    {A2R,A} = make_A2R(S#xref.applications),    R = set(dict:fetch_keys(S#xref.releases)),    %% Converting from edges of functions to edges of modules.    VEs = union_of_family(E),    Fun = {external, fun({{M1,_F1,_A1},{M2,_F2,_A2}}) -> {M1,M2} end},    ME = projection(Fun, VEs),    ME2AE = multiple_relative_product({M2A, M2A}, ME),    AE = range(ME2AE),    AE2RE = multiple_relative_product({A2R, A2R}, AE),    RE = range(AE2RE),    AM = domain(F1),    %% Undef is the union of U0 and Lib:    {Undef, U0, Lib, Lib_DF, Lib_DF_1, Lib_DF_2, Lib_DF_3} = 	make_libs(XU, F1, AM, S#xref.library_path, S#xref.libraries),    {B, U} = make_builtins(U0),    X1_B = family_union(X1, B),    F = family_union(F1, Lib),    DF = family_union(family_intersection(Mod_DF, X1_B), Lib_DF),    DF_1 = family_union(family_intersection(Mod_DF_1, X1_B), Lib_DF_1),    DF_2 = family_union(family_intersection(Mod_DF_2, X1_B), Lib_DF_2),    DF_3 = family_union(family_intersection(Mod_DF_3, X1_B), Lib_DF_3),    % If we have 'used' too, then there will be a set LU U XU...    UU = family_difference(family_difference(F1, LU), XU),    DefAt = make_defat(Undef, DefAt0),    LM = domain(Lib),    UM = difference(difference(domain(U), AM), LM),    X = family_union(X1, Lib),    %% Inter Call Graph. Calls to exported functions (library    %% functions inclusive) as well as calls within modules. This is a    %% way to discard calls to local functions in other modules.    EE_conv = converse(union_of_family(EE0)),    EE_exported = restriction(EE_conv, union_of_family(X)),    EE_local =       specification({external, fun({{M1,_,_},{M2,_,_}}) -> M1 =:= M2 end},                    EE_conv),    EE_0 = converse(union(EE_local, EE_exported)),    EE_1 = user_family(EE_0),    EE1 = partition_family({external, fun({{M1,_,_}, _MFA2}) -> M1 end},                            EE_0),    %% Make sure EE is defined for all modules:    EE = family_union(family_difference(EE0, EE0), EE1),    IFun =        fun({Mod,EE_M}, XMods) ->                IMFun =                  fun(XrefMod) ->                         [NoCalls, NoFunctionCalls,                           NoFunctions,  _NoInter] = XrefMod#xref_mod.info,                         NewInfo = [NoCalls, NoFunctionCalls, NoFunctions,                                     {no_inter_function_calls,length(EE_M)}],                         XrefMod#xref_mod{info = NewInfo}                 end,               dict:update(Mod, IMFun,XMods)       end,    XrefMods1 = foldl(IFun, S#xref.modules, to_external(EE)),    S1 = S#xref{modules = XrefMods1},    UC_1 = user_family(union_of_family(UC)),    ?FORMAT("DefAt ~p~n", [DefAt]),    ?FORMAT("U=~p~nLib=~p~nB=~p~nLU=~p~nXU=~p~nUU=~p~n", [U,Lib,B,LU,XU,UU]),    ?FORMAT("E_1=~p~nLC_1=~p~nXC_1=~p~n", [E_1,LC_1,XC_1]),    ?FORMAT("EE=~p~nEE_1=~p~nECallAt=~p~n", [EE, EE_1, ECallAt]),    ?FORMAT("DF=~p~nDF_1=~p~nDF_2=~p~nDF_3=~p~n", [DF, DF_1, DF_2, DF_3]),    Vs = [{'L',L}, {'X',X},{'F',F},{'U',U},{'B',B},{'UU',UU},	  {'XU',XU},{'LU',LU},{'V',V},{v,V},	  {'LC',{LC,LC_1}},{'XC',{XC,XC_1}},{'E',{E,E_1}},{e,{E,E_1}},	  {'EE',{EE,EE_1}},{'UC',{UC,UC_1}},	  {'M',M},{'A',A},{'R',R},	  {'AM',AM},{'UM',UM},{'LM',LM},	  {'ME',ME},{'AE',AE},{'RE',RE},          {'DF',DF},{'DF_1',DF_1},{'DF_2',DF_2},{'DF_3',DF_3},	  {me2ae, ME2AE},{ae, AE2RE},{m2a, M2A},{a2r, A2R},	  {def_at, DefAt}, {call_at, CallAt}, {e_call_at, ECallAt},	  {l_call_at, LCallAt}, {x_call_at, XCallAt}],    finish_set_up(S1, Vs);do_set_up(S) when S#xref.mode =:= modules ->    ModDictList = dict:to_list(S#xref.modules),    [X0, I0, Mod_DF, Mod_DF_1, Mod_DF_2, Mod_DF_3] =         make_families(ModDictList, 7),    I = union_of_family(I0),    AM = domain(X0),        {XU, Predefined} = make_predefined(I, AM),    %% Add "hidden" functions to the exports.    X1 = family_union(X0, Predefined),    V = family_union(X1, XU),    M = union(AM, domain(XU)),    M2A = make_M2A(ModDictList),    {A2R,A} = make_A2R(S#xref.applications),    R = set(dict:fetch_keys(S#xref.releases)),        ME = projection({external, fun({M1,{M2,_F2,_A2}}) -> {M1,M2} end}, 		    family_to_relation(I0)),    ME2AE = multiple_relative_product({M2A, M2A}, ME),    AE = range(ME2AE),    AE2RE = multiple_relative_product({A2R, A2R}, AE),    RE = range(AE2RE),    %% Undef is the union of U0 and Lib:    {_Undef, U0, Lib, Lib_DF, Lib_DF_1, Lib_DF_2, Lib_DF_3} = 	make_libs(XU, X1, AM, S#xref.library_path, S#xref.libraries),    {B, U} = make_builtins(U0),    X1_B = family_union(X1, B),    DF = family_union(family_intersection(Mod_DF, X1_B), Lib_DF),    DF_1 = family_union(family_intersection(Mod_DF_1, X1_B), Lib_DF_1),    DF_2 = family_union(family_intersection(Mod_DF_2, X1_B), Lib_DF_2),    DF_3 = family_union(family_intersection(Mod_DF_3, X1_B), Lib_DF_3),    LM = domain(Lib),    UM = difference(difference(domain(U), AM), LM),    X = family_union(X1, Lib),    Empty = empty_set(),    Vs = [{'X',X},{'U',U},{'B',B},{'XU',XU},{v,V}, 	  {e,{Empty,Empty}},	  {'M',M},{'A',A},{'R',R},	  {'AM',AM},{'UM',UM},{'LM',LM},	  {'ME',ME},{'AE',AE},{'RE',RE},          {'DF',DF},{'DF_1',DF_1},{'DF_2',DF_2},{'DF_3',DF_3},	  {me2ae, ME2AE},{ae, AE2RE},{m2a, M2A},{a2r, A2R},	  {def_at, Empty}, {call_at, Empty}, {e_call_at, Empty},	  {l_call_at, Empty}, {x_call_at, Empty}],    finish_set_up(S, Vs).finish_set_up(S, Vs) ->    T = do_finish_set_up(Vs, dict:new()),    S1 = S#xref{variables = T},    %% io:format("~p <= state <= ~p~n", [pack:lsize(S), pack:usize(S)]),    {ok, S1}.    do_finish_set_up([{Key, Value} | Vs], T) ->    {Type, OType} = var_type(Key),    Val = #xref_var{name = Key, value = Value, vtype = predef, 		    otype = OType, type = Type},    T1 = dict:store(Key, Val, T),    do_finish_set_up(Vs, T1);do_finish_set_up([], T) ->    T.var_type('B')    -> {function, vertex};var_type('F')    -> {function, vertex};var_type('L')    -> {function, vertex};var_type('LU')   -> {function, vertex};var_type('U')    -> {function, vertex};var_type('UU')   -> {function, vertex};var_type('V')    -> {function, vertex};var_type('X')    -> {function, vertex};var_type('XU')   -> {function, vertex};var_type('DF')   -> {function, vertex};var_type('DF_1') -> {function, vertex};var_type('DF_2') -> {function, vertex};var_type('DF_3') -> {function, vertex};var_type('A')    -> {application, vertex};

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -