aboutsummaryrefslogtreecommitdiffstats
path: root/lib/tools/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/tools/src')
-rw-r--r--lib/tools/src/cover.erl587
-rw-r--r--lib/tools/src/eprof.erl757
-rw-r--r--lib/tools/src/xref_base.erl176
-rw-r--r--lib/tools/src/xref_compiler.erl135
-rw-r--r--lib/tools/src/xref_reader.erl52
-rw-r--r--lib/tools/src/xref_utils.erl2
6 files changed, 939 insertions, 770 deletions
diff --git a/lib/tools/src/cover.erl b/lib/tools/src/cover.erl
index 6501e05a6e..230f0e9428 100644
--- a/lib/tools/src/cover.erl
+++ b/lib/tools/src/cover.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2001-2010. All Rights Reserved.
+%% Copyright Ericsson AB 2001-2011. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -35,23 +35,37 @@
%% remote_process_loop/1.
%%
%% TABLES
-%% Each nodes has an ets table named 'cover_internal_data_table'
-%% (?COVER_TABLE). This table contains the coverage data and is
-%% continously updated when cover compiled code is executed.
+%% Each nodes has two tables: cover_internal_data_table (?COVER_TABLE) and.
+%% cover_internal_clause_table (?COVER_CLAUSE_TABLE).
+%% ?COVER_TABLE contains the bump data i.e. the data about which lines
+%% have been executed how many times.
+%% ?COVER_CLAUSE_TABLE contains information about which clauses in which modules
+%% cover is currently collecting statistics.
%%
-%% The main node owns a table named
-%% 'cover_collected_remote_data_table' (?COLLECTION_TABLE). This table
-%% contains data which is collected from remote nodes (either when a
-%% remote node is stopped with cover:stop/1 or when analysing. When
-%% analysing, data is even moved from the ?COVER_TABLE on the main
-%% node to the ?COLLECTION_TABLE.
+%% The main node owns tables named
+%% 'cover_collected_remote_data_table' (?COLLECTION_TABLE) and
+%% 'cover_collected_remote_clause_table' (?COLLECTION_CLAUSE_TABLE).
+%% These tables contain data which is collected from remote nodes (either when a
+%% remote node is stopped with cover:stop/1 or when analysing). When
+%% analysing, data is even moved from the COVER tables on the main
+%% node to the COLLECTION tables.
%%
%% The main node also has a table named 'cover_binary_code_table'
%% (?BINARY_TABLE). This table contains the binary code for each cover
%% compiled module. This is necessary so that the code can be loaded
%% on remote nodes that are started after the compilation.
%%
-
+%% PARELLALISM
+%% To take advantage of SMP when doing the cover analysis both the data
+%% collection and analysis has been parallelized. One process is spawned for
+%% each node when collecting data, and on the remote node when collecting data
+%% one process is spawned per module.
+%%
+%% When analyzing data it is possible to issue multiple analyse(_to_file)/X
+%% calls at once. They are however all calls (for backwardscompatability
+%% reasons) so the user of cover will have to spawn several processes to to the
+%% calls ( or use async_analyse_to_file ).
+%%
%% External exports
-export([start/0, start/1,
@@ -61,6 +75,9 @@
analyse/1, analyse/2, analyse/3, analyze/1, analyze/2, analyze/3,
analyse_to_file/1, analyse_to_file/2, analyse_to_file/3,
analyze_to_file/1, analyze_to_file/2, analyze_to_file/3,
+ async_analyse_to_file/1,async_analyse_to_file/2,
+ async_analyse_to_file/3, async_analyze_to_file/1,
+ async_analyze_to_file/2, async_analyze_to_file/3,
export/1, export/2, import/1,
modules/0, imported/0, imported_modules/0, which_nodes/0, is_compiled/1,
reset/1, reset/0,
@@ -100,8 +117,10 @@
}).
-define(COVER_TABLE, 'cover_internal_data_table').
+-define(COVER_CLAUSE_TABLE, 'cover_internal_clause_table').
-define(BINARY_TABLE, 'cover_binary_code_table').
-define(COLLECTION_TABLE, 'cover_collected_remote_data_table').
+-define(COLLECTION_CLAUSE_TABLE, 'cover_collected_remote_clause_table').
-define(TAG, cover_compiled).
-define(SERVER, cover_server).
@@ -114,6 +133,8 @@
true -> ?BLOCK(Expr)
end).
+-define(SPAWN_DBG(Tag,Value),put(Tag,Value)).
+
-include_lib("stdlib/include/ms_transform.hrl").
%%%----------------------------------------------------------------------
@@ -127,7 +148,10 @@ start() ->
case whereis(?SERVER) of
undefined ->
Starter = self(),
- Pid = spawn(fun() -> init_main(Starter) end),
+ Pid = spawn(fun() ->
+ ?SPAWN_DBG(start,[]),
+ init_main(Starter)
+ end),
Ref = erlang:monitor(process,Pid),
Return =
receive
@@ -382,6 +406,30 @@ analyze_to_file(Module, OptOrOut) -> analyse_to_file(Module, OptOrOut).
analyze_to_file(Module, OutFile, Options) ->
analyse_to_file(Module, OutFile, Options).
+async_analyse_to_file(Module) ->
+ do_spawn(?MODULE, analyse_to_file, [Module]).
+async_analyse_to_file(Module, OutFileOrOpts) ->
+ do_spawn(?MODULE, analyse_to_file, [Module, OutFileOrOpts]).
+async_analyse_to_file(Module, OutFile, Options) ->
+ do_spawn(?MODULE, analyse_to_file, [Module, OutFile, Options]).
+
+do_spawn(M,F,A) ->
+ spawn_link(fun() ->
+ case apply(M,F,A) of
+ {ok, _} ->
+ ok;
+ {error, Reason} ->
+ exit(Reason)
+ end
+ end).
+
+async_analyze_to_file(Module) ->
+ async_analyse_to_file(Module).
+async_analyze_to_file(Module, OutFileOrOpts) ->
+ async_analyse_to_file(Module, OutFileOrOpts).
+async_analyze_to_file(Module, OutFile, Options) ->
+ async_analyse_to_file(Module, OutFile, Options).
+
outfilename(Module,Opts) ->
case lists:member(html,Opts) of
true ->
@@ -500,6 +548,8 @@ remote_call(Node,Request) ->
Return
end.
+remote_reply(Proc,Reply) when is_pid(Proc) ->
+ Proc ! {?SERVER,Reply};
remote_reply(MainNode,Reply) ->
{?SERVER,MainNode} ! {?SERVER,Reply}.
@@ -509,9 +559,15 @@ remote_reply(MainNode,Reply) ->
init_main(Starter) ->
register(?SERVER,self()),
- ets:new(?COVER_TABLE, [set, public, named_table]),
+ %% Having write concurrancy here gives a 40% performance boost
+ %% when collect/1 is called.
+ ets:new(?COVER_TABLE, [set, public, named_table
+ ,{write_concurrency, true}
+ ]),
+ ets:new(?COVER_CLAUSE_TABLE, [set, public, named_table]),
ets:new(?BINARY_TABLE, [set, named_table]),
ets:new(?COLLECTION_TABLE, [set, public, named_table]),
+ ets:new(?COLLECTION_CLAUSE_TABLE, [set, public, named_table]),
process_flag(trap_exit,true),
Starter ! {?SERVER,started},
main_process_loop(#main_state{}).
@@ -593,40 +649,10 @@ main_process_loop(State) ->
end;
{From, {export,OutFile,Module}} ->
- case file:open(OutFile,[write,binary,raw]) of
- {ok,Fd} ->
- Reply =
- case Module of
- '_' ->
- export_info(State#main_state.imported),
- collect(State#main_state.nodes),
- do_export_table(State#main_state.compiled,
- State#main_state.imported,
- Fd);
- _ ->
- export_info(Module,State#main_state.imported),
- case is_loaded(Module, State) of
- {loaded, File} ->
- [{Module,Clauses}] =
- ets:lookup(?COVER_TABLE,Module),
- collect(Module, Clauses,
- State#main_state.nodes),
- do_export_table([{Module,File}],[],Fd);
- {imported, File, ImportFiles} ->
- %% don't know if I should allow this -
- %% export a module which is only imported
- Imported = [{Module,File,ImportFiles}],
- do_export_table([],Imported,Fd);
- _NotLoaded ->
- {error,{not_cover_compiled,Module}}
- end
- end,
- file:close(Fd),
- reply(From, Reply);
- {error,Reason} ->
- reply(From, {error, {cant_open_file,OutFile,Reason}})
-
- end,
+ spawn(fun() ->
+ ?SPAWN_DBG(export,{OutFile, Module}),
+ do_export(Module, OutFile, From, State)
+ end),
main_process_loop(State);
{From, {import,File}} ->
@@ -692,107 +718,73 @@ main_process_loop(State) ->
unregister(?SERVER),
reply(From, ok);
- {From, {Request, Module}} ->
- case is_loaded(Module, State) of
- {loaded, File} ->
- {Reply,State1} =
- case Request of
- {analyse, Analysis, Level} ->
- analyse_info(Module,State#main_state.imported),
- [{Module,Clauses}] =
- ets:lookup(?COVER_TABLE,Module),
- collect(Module,Clauses,State#main_state.nodes),
- R = do_analyse(Module, Analysis, Level, Clauses),
- {R,State};
-
- {analyse_to_file, OutFile, Opts} ->
- R = case find_source(File) of
- {beam,_BeamFile} ->
- {error,no_source_code_found};
- ErlFile ->
- Imported = State#main_state.imported,
- analyse_info(Module,Imported),
- [{Module,Clauses}] =
- ets:lookup(?COVER_TABLE,Module),
- collect(Module, Clauses,
- State#main_state.nodes),
- HTML = lists:member(html,Opts),
- do_analyse_to_file(Module,OutFile,
- ErlFile,HTML)
- end,
- {R,State};
-
- is_compiled ->
- {{file, File},State};
-
- reset ->
- R = do_reset_main_node(Module,
- State#main_state.nodes),
- Imported =
- remove_imported(Module,
- State#main_state.imported),
- {R,State#main_state{imported=Imported}}
- end,
- reply(From, Reply),
- main_process_loop(State1);
-
- {imported,File,_ImportFiles} ->
- {Reply,State1} =
- case Request of
- {analyse, Analysis, Level} ->
- analyse_info(Module,State#main_state.imported),
- [{Module,Clauses}] =
- ets:lookup(?COLLECTION_TABLE,Module),
- R = do_analyse(Module, Analysis, Level, Clauses),
- {R,State};
-
- {analyse_to_file, OutFile, Opts} ->
- R = case find_source(File) of
- {beam,_BeamFile} ->
- {error,no_source_code_found};
- ErlFile ->
- Imported = State#main_state.imported,
- analyse_info(Module,Imported),
- HTML = lists:member(html,Opts),
- do_analyse_to_file(Module,OutFile,
- ErlFile,HTML)
- end,
- {R,State};
-
- is_compiled ->
- {false,State};
-
- reset ->
- R = do_reset_collection_table(Module),
- Imported =
- remove_imported(Module,
- State#main_state.imported),
- {R,State#main_state{imported=Imported}}
- end,
- reply(From, Reply),
- main_process_loop(State1);
-
- NotLoaded ->
- Reply =
- case Request of
- is_compiled ->
- false;
- _ ->
- {error, {not_cover_compiled,Module}}
- end,
- Compiled =
- case NotLoaded of
- unloaded ->
- do_clear(Module),
- remote_unload(State#main_state.nodes,[Module]),
- update_compiled([Module],
- State#main_state.compiled);
- false ->
- State#main_state.compiled
+ {From, {{analyse, Analysis, Level}, Module}} ->
+ S = try
+ Loaded = is_loaded(Module, State),
+ spawn(fun() ->
+ ?SPAWN_DBG(analyse,{Module,Analysis, Level}),
+ do_parallel_analysis(
+ Module, Analysis, Level,
+ Loaded, From, State)
+ end),
+ State
+ catch throw:Reason ->
+ reply(From,{error, {not_cover_compiled,Module}}),
+ not_loaded(Module, Reason, State)
+ end,
+ main_process_loop(S);
+
+ {From, {{analyse_to_file, OutFile, Opts},Module}} ->
+ S = try
+ Loaded = is_loaded(Module, State),
+ spawn(fun() ->
+ ?SPAWN_DBG(analyse_to_file,
+ {Module,OutFile, Opts}),
+ do_parallel_analysis_to_file(
+ Module, OutFile, Opts,
+ Loaded, From, State)
+ end),
+ State
+ catch throw:Reason ->
+ reply(From,{error, {not_cover_compiled,Module}}),
+ not_loaded(Module, Reason, State)
+ end,
+ main_process_loop(S);
+
+ {From, {is_compiled, Module}} ->
+ S = try is_loaded(Module, State) of
+ {loaded, File} ->
+ reply(From,{file, File}),
+ State;
+ {imported,_File,_ImportFiles} ->
+ reply(From,false),
+ State
+ catch throw:Reason ->
+ reply(From,false),
+ not_loaded(Module, Reason, State)
+ end,
+ main_process_loop(S);
+
+ {From, {reset, Module}} ->
+ S = try
+ Loaded = is_loaded(Module,State),
+ R = case Loaded of
+ {loaded, _File} ->
+ do_reset_main_node(
+ Module, State#main_state.nodes);
+ {imported, _File, _} ->
+ do_reset_collection_table(Module)
end,
- reply(From, Reply),
- main_process_loop(State#main_state{compiled=Compiled})
- end;
+ Imported =
+ remove_imported(Module,
+ State#main_state.imported),
+ reply(From, R),
+ State#main_state{imported=Imported}
+ catch throw:Reason ->
+ reply(From,{error, {not_cover_compiled,Module}}),
+ not_loaded(Module, Reason, State)
+ end,
+ main_process_loop(S);
{'EXIT',Pid,_Reason} ->
%% Exit is trapped on the main node only, so this will only happen
@@ -807,17 +799,17 @@ main_process_loop(State) ->
main_process_loop(State)
end.
-
-
-
-
%%%----------------------------------------------------------------------
%%% cover_server on remote node
%%%----------------------------------------------------------------------
init_remote(Starter,MainNode) ->
register(?SERVER,self()),
- ets:new(?COVER_TABLE, [set, public, named_table]),
+ ets:new(?COVER_TABLE, [set, public, named_table
+ %% write_concurrency here makes otp_8270 break :(
+ %,{write_concurrency, true}
+ ]),
+ ets:new(?COVER_CLAUSE_TABLE, [set, public, named_table]),
Starter ! {self(),started},
remote_process_loop(#remote_state{main_node=MainNode}).
@@ -843,29 +835,14 @@ remote_process_loop(State) ->
remote_process_loop(State);
{remote,collect,Module,CollectorPid} ->
- MS =
- case Module of
- '_' -> ets:fun2ms(fun({M,C}) when is_atom(M) -> C end);
- _ -> ets:fun2ms(fun({M,C}) when M=:=Module -> C end)
- end,
- AllClauses = lists:flatten(ets:select(?COVER_TABLE,MS)),
-
- %% Sending clause by clause in order to avoid large lists
- lists:foreach(
- fun({M,F,A,C,_L}) ->
- Pattern =
- {#bump{module=M, function=F, arity=A, clause=C}, '_'},
- Bumps = ets:match_object(?COVER_TABLE, Pattern),
- %% Reset
- lists:foreach(fun({Bump,_N}) ->
- ets:insert(?COVER_TABLE, {Bump,0})
- end,
- Bumps),
- CollectorPid ! {chunk,Bumps}
- end,
- AllClauses),
- CollectorPid ! done,
- remote_reply(State#remote_state.main_node, ok),
+ self() ! {remote,collect,Module,CollectorPid, ?SERVER};
+
+ {remote,collect,Module,CollectorPid,From} ->
+ spawn(fun() ->
+ ?SPAWN_DBG(remote_collect,
+ {Module, CollectorPid, From}),
+ do_collect(Module, CollectorPid, From)
+ end),
remote_process_loop(State);
{remote,stop} ->
@@ -894,6 +871,33 @@ remote_process_loop(State) ->
end.
+do_collect(Module, CollectorPid, From) ->
+ AllMods =
+ case Module of
+ '_' -> ets:tab2list(?COVER_CLAUSE_TABLE);
+ _ -> ets:lookup(?COVER_CLAUSE_TABLE, Module)
+ end,
+
+ %% Sending clause by clause in order to avoid large lists
+ pmap(
+ fun({_Mod,Clauses}) ->
+ lists:map(fun(Clause) ->
+ send_collected_data(Clause, CollectorPid)
+ end,Clauses)
+ end,AllMods),
+ CollectorPid ! done,
+ remote_reply(From, ok).
+
+send_collected_data({M,F,A,C,_L}, CollectorPid) ->
+ Pattern =
+ {#bump{module=M, function=F, arity=A, clause=C}, '_'},
+ Bumps = ets:match_object(?COVER_TABLE, Pattern),
+ %% Reset
+ lists:foreach(fun({Bump,_N}) ->
+ ets:insert(?COVER_TABLE, {Bump,0})
+ end,
+ Bumps),
+ CollectorPid ! {chunk,Bumps}.
reload_originals([{Module,_File}|Compiled]) ->
do_reload_original(Module),
@@ -932,6 +936,9 @@ load_compiled([{Module,File,Binary,InitialTable}|Compiled],Acc) ->
load_compiled([],Acc) ->
Acc.
+insert_initial_data([Item|Items]) when is_atom(element(1,Item)) ->
+ ets:insert(?COVER_CLAUSE_TABLE, Item),
+ insert_initial_data(Items);
insert_initial_data([Item|Items]) ->
ets:insert(?COVER_TABLE, Item),
insert_initial_data(Items);
@@ -957,7 +964,10 @@ remote_start(MainNode) ->
case whereis(?SERVER) of
undefined ->
Starter = self(),
- Pid = spawn(fun() -> init_remote(Starter,MainNode) end),
+ Pid = spawn(fun() ->
+ ?SPAWN_DBG(remote_start,{MainNode}),
+ init_remote(Starter,MainNode)
+ end),
Ref = erlang:monitor(process,Pid),
Return =
receive
@@ -972,14 +982,25 @@ remote_start(MainNode) ->
{error,{already_started,Pid}}
end.
-%% Load a set of cover compiled modules on remote nodes
-remote_load_compiled(Nodes,Compiled0) ->
- Compiled = lists:map(fun get_data_for_remote_loading/1,Compiled0),
+%% Load a set of cover compiled modules on remote nodes,
+%% We do it ?MAX_MODS modules at a time so that we don't
+%% run out of memory on the cover_server node.
+-define(MAX_MODS, 10).
+remote_load_compiled(Nodes,Compiled) ->
+ remote_load_compiled(Nodes, Compiled, [], 0).
+remote_load_compiled(_Nodes, [], [], _ModNum) ->
+ ok;
+remote_load_compiled(Nodes, Compiled, Acc, ModNum)
+ when Compiled == []; ModNum == ?MAX_MODS ->
lists:foreach(
fun(Node) ->
- remote_call(Node,{remote,load_compiled,Compiled})
+ remote_call(Node,{remote,load_compiled,Acc})
end,
- Nodes).
+ Nodes),
+ remote_load_compiled(Nodes, Compiled, [], 0);
+remote_load_compiled(Nodes, [MF | Rest], Acc, ModNum) ->
+ remote_load_compiled(
+ Nodes, Rest, [get_data_for_remote_loading(MF) | Acc], ModNum + 1).
%% Read all data needed for loading a cover compiled module on a remote node
%% Binary is the beam code for the module and InitialTable is the initial
@@ -987,15 +1008,15 @@ remote_load_compiled(Nodes,Compiled0) ->
get_data_for_remote_loading({Module,File}) ->
[{Module,Binary}] = ets:lookup(?BINARY_TABLE,Module),
%%! The InitialTable list will be long if the module is big - what to do??
- InitialTable = ets:select(?COVER_TABLE,ms(Module)),
- {Module,File,Binary,InitialTable}.
+ InitialBumps = ets:select(?COVER_TABLE,ms(Module)),
+ InitialClauses = ets:lookup(?COVER_CLAUSE_TABLE,Module),
+
+ {Module,File,Binary,InitialBumps ++ InitialClauses}.
%% Create a match spec which returns the clause info {Module,InitInfo} and
%% all #bump keys for the given module with 0 number of calls.
ms(Module) ->
- ets:fun2ms(fun({Module,InitInfo}) ->
- {Module,InitInfo};
- ({Key,_}) when is_record(Key,bump),Key#bump.module=:=Module ->
+ ets:fun2ms(fun({Key,_}) when Key#bump.module=:=Module ->
{Key,0}
end).
@@ -1017,27 +1038,30 @@ remote_reset(Module,Nodes) ->
%% Collect data from remote nodes - used for analyse or stop(Node)
remote_collect(Module,Nodes,Stop) ->
- CollectorPid = spawn(fun() -> collector_proc(length(Nodes)) end),
- lists:foreach(
- fun(Node) ->
- remote_call(Node,{remote,collect,Module,CollectorPid}),
- if Stop -> remote_call(Node,{remote,stop});
- true -> ok
- end
- end,
- Nodes).
+ pmap(fun(Node) ->
+ ?SPAWN_DBG(remote_collect,
+ {Module, Nodes, Stop}),
+ do_collection(Node, Module, Stop)
+ end,
+ Nodes).
+
+do_collection(Node, Module, Stop) ->
+ CollectorPid = spawn(fun collector_proc/0),
+ remote_call(Node,{remote,collect,Module,CollectorPid, self()}),
+ if Stop -> remote_call(Node,{remote,stop});
+ true -> ok
+ end.
%% Process which receives chunks of data from remote nodes - either when
%% analysing or when stopping cover on the remote nodes.
-collector_proc(0) ->
- ok;
-collector_proc(N) ->
+collector_proc() ->
+ ?SPAWN_DBG(collector_proc, []),
receive
{chunk,Chunk} ->
insert_in_collection_table(Chunk),
- collector_proc(N);
+ collector_proc();
done ->
- collector_proc(N-1)
+ ok
end.
insert_in_collection_table([{Key,Val}|Chunk]) ->
@@ -1052,7 +1076,13 @@ insert_in_collection_table(Key,Val) ->
ets:update_counter(?COLLECTION_TABLE,
Key,Val);
false ->
- ets:insert(?COLLECTION_TABLE,{Key,Val})
+ %% Make sure that there are no race conditions from ets:member
+ case ets:insert_new(?COLLECTION_TABLE,{Key,Val}) of
+ false ->
+ insert_in_collection_table(Key,Val);
+ _ ->
+ ok
+ end
end.
@@ -1073,14 +1103,15 @@ analyse_info(Module,Imported) ->
export_info(_Module,[]) ->
ok;
-export_info(Module,Imported) ->
- imported_info("Export",Module,Imported).
+export_info(_Module,_Imported) ->
+ %% Do not print that the export includes imported modules
+ ok.
export_info([]) ->
ok;
-export_info(Imported) ->
- AllImportFiles = get_all_importfiles(Imported,[]),
- io:format("Export includes data from imported files\n~p\n",[AllImportFiles]).
+export_info(_Imported) ->
+ %% Do not print that the export includes imported modules
+ ok.
get_all_importfiles([{_M,_F,ImportFiles}|Imported],Acc) ->
NewAcc = do_get_all_importfiles(ImportFiles,Acc),
@@ -1153,14 +1184,14 @@ is_loaded(Module, State) ->
{ok, File} ->
case code:which(Module) of
?TAG -> {loaded, File};
- _ -> unloaded
+ _ -> throw(unloaded)
end;
false ->
case get_file(Module,State#main_state.imported) of
{ok,File,ImportFiles} ->
{imported, File, ImportFiles};
false ->
- false
+ throw(not_loaded)
end
end.
@@ -1259,7 +1290,7 @@ do_compile_beam(Module,Beam) ->
%% Store info about all function clauses in database
InitInfo = reverse(Vars#vars.init_info),
- ets:insert(?COVER_TABLE, {Module, InitInfo}),
+ ets:insert(?COVER_CLAUSE_TABLE, {Module, InitInfo}),
%% Store binary code so it can be loaded on remote nodes
ets:insert(?BINARY_TABLE, {Module, Binary}),
@@ -1793,9 +1824,8 @@ common_elems(L1, L2) ->
%% Collect data for all modules
collect(Nodes) ->
%% local node
- MS = ets:fun2ms(fun({M,C}) when is_atom(M) -> {M,C} end),
- AllClauses = ets:select(?COVER_TABLE,MS),
- move_modules(AllClauses),
+ AllClauses = ets:tab2list(?COVER_CLAUSE_TABLE),
+ pmap(fun move_modules/1,AllClauses),
%% remote nodes
remote_collect('_',Nodes,false).
@@ -1803,7 +1833,7 @@ collect(Nodes) ->
%% Collect data for one module
collect(Module,Clauses,Nodes) ->
%% local node
- move_modules([{Module,Clauses}]),
+ move_modules({Module,Clauses}),
%% remote nodes
remote_collect(Module,Nodes,false).
@@ -1811,12 +1841,9 @@ collect(Module,Clauses,Nodes) ->
%% When analysing, the data from the local ?COVER_TABLE is moved to the
%% ?COLLECTION_TABLE. Resetting data in ?COVER_TABLE
-move_modules([{Module,Clauses}|AllClauses]) ->
- ets:insert(?COLLECTION_TABLE,{Module,Clauses}),
- move_clauses(Clauses),
- move_modules(AllClauses);
-move_modules([]) ->
- ok.
+move_modules({Module,Clauses}) ->
+ ets:insert(?COLLECTION_CLAUSE_TABLE,{Module,Clauses}),
+ move_clauses(Clauses).
move_clauses([{M,F,A,C,_L}|Clauses]) ->
Pattern = {#bump{module=M, function=F, arity=A, clause=C}, '_'},
@@ -1855,6 +1882,22 @@ find_source(File0) ->
end
end.
+do_parallel_analysis(Module, Analysis, Level, Loaded, From, State) ->
+ analyse_info(Module,State#main_state.imported),
+ C = case Loaded of
+ {loaded, _File} ->
+ [{Module,Clauses}] =
+ ets:lookup(?COVER_CLAUSE_TABLE,Module),
+ collect(Module,Clauses,State#main_state.nodes),
+ Clauses;
+ _ ->
+ [{Module,Clauses}] =
+ ets:lookup(?COLLECTION_CLAUSE_TABLE,Module),
+ Clauses
+ end,
+ R = do_analyse(Module, Analysis, Level, C),
+ reply(From, R).
+
%% do_analyse(Module, Analysis, Level, Clauses)-> {ok,Answer} | {error,Error}
%% Clauses = [{Module,Function,Arity,Clause,Lines}]
do_analyse(Module, Analysis, line, _Clauses) ->
@@ -1931,6 +1974,28 @@ merge_functions([{_MFA,R}|Functions], MFun, Result) ->
merge_functions([], _MFun, Result) ->
Result.
+do_parallel_analysis_to_file(Module, OutFile, Opts, Loaded, From, State) ->
+ File = case Loaded of
+ {loaded, File0} ->
+ [{Module,Clauses}] =
+ ets:lookup(?COVER_CLAUSE_TABLE,Module),
+ collect(Module, Clauses,
+ State#main_state.nodes),
+ File0;
+ {imported, File0, _} ->
+ File0
+ end,
+ case find_source(File) of
+ {beam,_BeamFile} ->
+ reply(From, {error,no_source_code_found});
+ ErlFile ->
+ analyse_info(Module,State#main_state.imported),
+ HTML = lists:member(html,Opts),
+ R = do_analyse_to_file(Module,OutFile,
+ ErlFile,HTML),
+ reply(From, R)
+ end.
+
%% do_analyse_to_file(Module,OutFile,ErlFile) -> {ok,OutFile} | {error,Error}
%% Module = atom()
%% OutFile = ErlFile = string()
@@ -2027,6 +2092,42 @@ fill2() -> ".| ".
fill3() -> "| ".
%%%--Export--------------------------------------------------------------
+do_export(Module, OutFile, From, State) ->
+ case file:open(OutFile,[write,binary,raw]) of
+ {ok,Fd} ->
+ Reply =
+ case Module of
+ '_' ->
+ export_info(State#main_state.imported),
+ collect(State#main_state.nodes),
+ do_export_table(State#main_state.compiled,
+ State#main_state.imported,
+ Fd);
+ _ ->
+ export_info(Module,State#main_state.imported),
+ try is_loaded(Module, State) of
+ {loaded, File} ->
+ [{Module,Clauses}] =
+ ets:lookup(?COVER_CLAUSE_TABLE,Module),
+ collect(Module, Clauses,
+ State#main_state.nodes),
+ do_export_table([{Module,File}],[],Fd);
+ {imported, File, ImportFiles} ->
+ %% don't know if I should allow this -
+ %% export a module which is only imported
+ Imported = [{Module,File,ImportFiles}],
+ do_export_table([],Imported,Fd)
+ catch throw:_ ->
+ {error,{not_cover_compiled,Module}}
+ end
+ end,
+ file:close(Fd),
+ reply(From, Reply);
+ {error,Reason} ->
+ reply(From, {error, {cant_open_file,OutFile,Reason}})
+
+ end.
+
do_export_table(Compiled, Imported, Fd) ->
ModList = merge(Imported,Compiled),
write_module_data(ModList,Fd).
@@ -2043,7 +2144,7 @@ merge([],ModuleList) ->
write_module_data([{Module,File}|ModList],Fd) ->
write({file,Module,File},Fd),
- [Clauses] = ets:lookup(?COLLECTION_TABLE,Module),
+ [Clauses] = ets:lookup(?COLLECTION_CLAUSE_TABLE,Module),
write(Clauses,Fd),
ModuleData = ets:match_object(?COLLECTION_TABLE,{#bump{module=Module},'_'}),
do_write_module_data(ModuleData,Fd),
@@ -2093,7 +2194,7 @@ do_import_to_table(Fd,ImportFile,Imported,DontImport) ->
{Module,Clauses} ->
case lists:member(Module,DontImport) of
false ->
- ets:insert(?COLLECTION_TABLE,{Module,Clauses});
+ ets:insert(?COLLECTION_CLAUSE_TABLE,{Module,Clauses});
true ->
ok
end,
@@ -2127,14 +2228,14 @@ do_reset_main_node(Module,Nodes) ->
remote_reset(Module,Nodes).
do_reset_collection_table(Module) ->
- ets:delete(?COLLECTION_TABLE,Module),
+ ets:delete(?COLLECTION_CLAUSE_TABLE,Module),
ets:match_delete(?COLLECTION_TABLE, {#bump{module=Module},'_'}).
%% do_reset(Module) -> ok
%% The reset is done on a per-clause basis to avoid building
%% long lists in the case of very large modules
do_reset(Module) ->
- [{Module,Clauses}] = ets:lookup(?COVER_TABLE, Module),
+ [{Module,Clauses}] = ets:lookup(?COVER_CLAUSE_TABLE, Module),
do_reset2(Clauses).
do_reset2([{M,F,A,C,_L}|Clauses]) ->
@@ -2149,10 +2250,19 @@ do_reset2([]) ->
ok.
do_clear(Module) ->
- ets:match_delete(?COVER_TABLE, {Module,'_'}),
+ ets:match_delete(?COVER_CLAUSE_TABLE, {Module,'_'}),
ets:match_delete(?COVER_TABLE, {#bump{module=Module},'_'}),
ets:match_delete(?COLLECTION_TABLE, {#bump{module=Module},'_'}).
+not_loaded(Module, unloaded, State) ->
+ do_clear(Module),
+ remote_unload(State#main_state.nodes,[Module]),
+ Compiled = update_compiled([Module],
+ State#main_state.compiled),
+ State#main_state{ compiled = Compiled };
+not_loaded(_Module,_Else, State) ->
+ State.
+
%%%--Div-----------------------------------------------------------------
@@ -2174,7 +2284,36 @@ escape_lt_and_gt1([$<|T],Acc) ->
escape_lt_and_gt1(T,[$;,$t,$l,$&|Acc]);
escape_lt_and_gt1([$>|T],Acc) ->
escape_lt_and_gt1(T,[$;,$t,$g,$&|Acc]);
+escape_lt_and_gt1([$&|T],Acc) ->
+ escape_lt_and_gt1(T,[$;,$p,$m,$a,$&|Acc]);
escape_lt_and_gt1([],Acc) ->
lists:reverse(Acc);
escape_lt_and_gt1([H|T],Acc) ->
escape_lt_and_gt1(T,[H|Acc]).
+
+pmap(Fun, List) ->
+ pmap(Fun, List, 20).
+pmap(Fun, List, Limit) ->
+ pmap(Fun, List, [], Limit, 0, []).
+pmap(Fun, [E | Rest], Pids, Limit, Cnt, Acc) when Cnt < Limit ->
+ Collector = self(),
+ Pid = spawn_link(fun() ->
+ ?SPAWN_DBG(pmap,E),
+ Collector ! {res,self(),Fun(E)}
+ end),
+ erlang:monitor(process, Pid),
+ pmap(Fun, Rest, Pids ++ [Pid], Limit, Cnt + 1, Acc);
+pmap(Fun, List, [Pid | Pids], Limit, Cnt, Acc) ->
+ receive
+ {'DOWN', _Ref, process, _, _} ->
+ pmap(Fun, List, [Pid | Pids], Limit, Cnt - 1, Acc);
+ {res, Pid, Res} ->
+ pmap(Fun, List, Pids, Limit, Cnt, [Res | Acc])
+ end;
+pmap(_Fun, [], [], _Limit, 0, Acc) ->
+ lists:reverse(Acc);
+pmap(Fun, [], [], Limit, Cnt, Acc) ->
+ receive
+ {'DOWN', _Ref, process, _, _} ->
+ pmap(Fun, [], [], Limit, Cnt - 1, Acc)
+ end.
diff --git a/lib/tools/src/eprof.erl b/lib/tools/src/eprof.erl
index b4313d6888..87fdc1fa34 100644
--- a/lib/tools/src/eprof.erl
+++ b/lib/tools/src/eprof.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
+%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
%% Purpose: Profile a system in order to figure out where the
@@ -23,456 +23,467 @@
-module(eprof).
-behaviour(gen_server).
--export([start/0, stop/0, dump/0, total_analyse/0,
- start_profiling/1, profile/2, profile/4, profile/1,
- stop_profiling/0, analyse/0, log/1]).
+-export([start/0,
+ stop/0,
+ dump/0,
+ start_profiling/1, start_profiling/2,
+ profile/1, profile/2, profile/3, profile/4, profile/5,
+ stop_profiling/0,
+ analyze/0, analyze/1, analyze/2,
+ log/1]).
%% Internal exports
-export([init/1,
- call/4,
handle_call/3,
handle_cast/2,
handle_info/2,
terminate/2,
code_change/3]).
+-record(bpd, {
+ n = 0, % number of total calls
+ us = 0, % sum of uS for all calls
+ p = gb_trees:empty(), % tree of {Pid, {Mfa, {Count, Us}}}
+ mfa = [] % list of {Mfa, {Count, Us}}
+ }).
+
+-record(state, {
+ profiling = false,
+ pattern = {'_','_','_'},
+ rootset = [],
+ fd = undefined,
+ start_ts = undefined,
+ reply = undefined,
+ bpd = #bpd{}
+ }).
+
+
+
+%% -------------------------------------------------------------------- %%
+%%
+%% API
+%%
+%% -------------------------------------------------------------------- %%
--include_lib("stdlib/include/qlc.hrl").
-
--import(lists, [flatten/1,reverse/1,keysort/2]).
-
-
--record(state, {table = notable,
- proc = noproc,
- profiling = false,
- pfunc = undefined,
- pop = running,
- ptime = 0,
- overhead = 0,
- rootset = []}).
-
-%%%%%%%%%%%%%%
-
-start() -> gen_server:start({local, eprof}, eprof, [], []).
-stop() -> gen_server:call(eprof, stop, infinity).
+start() -> gen_server:start({local, ?MODULE}, ?MODULE, [], []).
+stop() -> gen_server:call(?MODULE, stop, infinity).
+profile(Fun) when is_function(Fun) ->
+ profile([], Fun);
+profile(Rs) when is_list(Rs) ->
+ start_profiling(Rs).
profile(Pids, Fun) ->
- start(),
- gen_server:call(eprof, {profile,Pids,erlang,apply,[Fun,[]]},infinity).
+ profile(Pids, Fun, {'_','_','_'}).
+
+profile(Pids, Fun, Pattern) ->
+ profile(Pids, erlang, apply, [Fun,[]], Pattern).
profile(Pids, M, F, A) ->
+ profile(Pids, M, F, A, {'_','_','_'}).
+
+profile(Pids, M, F, A, Pattern) ->
start(),
- gen_server:call(eprof, {profile,Pids,M,F,A},infinity).
+ gen_server:call(?MODULE, {profile,Pids,Pattern,M,F,A},infinity).
dump() ->
- gen_server:call(eprof, dump, infinity).
+ gen_server:call(?MODULE, dump, infinity).
-analyse() ->
- gen_server:call(eprof, analyse, infinity).
+analyze() ->
+ analyze(procs).
-log(File) ->
- gen_server:call(eprof, {logfile, File}, infinity).
+analyze(Type) when is_atom(Type) ->
+ analyze(Type, []);
+analyze(Opts) when is_list(Opts) ->
+ analyze(procs, Opts).
+analyze(Type, Opts) when is_list(Opts) ->
+ gen_server:call(?MODULE, {analyze, Type, Opts}, infinity).
-total_analyse() ->
- gen_server:call(eprof, total_analyse, infinity).
+log(File) ->
+ gen_server:call(?MODULE, {logfile, File}, infinity).
start_profiling(Rootset) ->
+ start_profiling(Rootset, {'_','_','_'}).
+start_profiling(Rootset, Pattern) ->
start(),
- gen_server:call(eprof, {profile, Rootset}, infinity).
+ gen_server:call(?MODULE, {profile, Rootset, Pattern}, infinity).
stop_profiling() ->
- gen_server:call(eprof, stop_profiling, infinity).
+ gen_server:call(?MODULE, stop_profiling, infinity).
-profile(Rs) ->
- start_profiling(Rs).
-%%%%%%%%%%%%%%%%
+%% -------------------------------------------------------------------- %%
+%%
+%% init
+%%
+%% -------------------------------------------------------------------- %%
-init(_) ->
+init([]) ->
process_flag(trap_exit, true),
- process_flag(priority, max),
- put(three_one, {3,1}), %To avoid building garbage.
{ok, #state{}}.
-subtr({X1,Y1,Z1}, {X1,Y1,Z2}) ->
- Z1 - Z2;
-subtr({X1,Y1,Z1}, {X2,Y2,Z2}) ->
- (((X1-X2) * 1000000) + Y1 - Y2) * 1000000 + Z1 - Z2.
+%% -------------------------------------------------------------------- %%
+%%
+%% handle_call
+%%
+%% -------------------------------------------------------------------- %%
-update_call_statistics(Tab, Key, Time) ->
- try ets:update_counter(Tab, Key, Time) of
- NewTime when is_integer(NewTime) ->
- ets:update_counter(Tab, Key, get(three_one))
- catch
- error:badarg ->
- ets:insert(Tab, {Key,Time,1})
- end.
+%% analyze
-update_other_statistics(Tab, Key, Time) ->
- try
- ets:update_counter(Tab, Key, Time)
- catch
- error:badarg ->
- ets:insert(Tab, {Key,Time,0})
- end.
+handle_call({analyze, _, _}, _, #state{ bpd = #bpd{ p = {0,nil}, us = 0, n = 0} = Bpd } = S) when is_record(Bpd, bpd) ->
+ {reply, nothing_to_analyze, S};
-do_messages({trace_ts,From,Op,Mfa,Time}, Tab, undefined,_PrevOp0,_PrevTime0) ->
- PrevFunc = [From|Mfa],
- receive
- {trace_ts,_,_,_,_}=Ts -> do_messages(Ts, Tab, PrevFunc, Op, Time)
- after 0 ->
- {PrevFunc,Op,Time}
- end;
-do_messages({trace_ts,From,Op,Mfa,Time}, Tab, PrevFunc0, call, PrevTime0) ->
- update_call_statistics(Tab, PrevFunc0, subtr(Time, PrevTime0)),
- PrevFunc = case Op of
- exit -> undefined;
- out -> undefined;
- _ -> [From|Mfa]
- end,
- receive
- {trace_ts,_,_,_,_}=Ts -> do_messages(Ts, Tab, PrevFunc, Op, Time)
- after 0 ->
- {PrevFunc,Op,Time}
- end;
-do_messages({trace_ts,From,Op,Mfa,Time}, Tab, PrevFunc0, _PrevOp0, PrevTime0) ->
- update_other_statistics(Tab, PrevFunc0, subtr(Time, PrevTime0)),
- PrevFunc = case Op of
- exit -> undefined;
- out -> undefined;
- _ -> [From|Mfa]
- end,
- receive
- {trace_ts,_,_,_,_}=Ts -> do_messages(Ts, Tab, PrevFunc, Op, Time)
- after 0 ->
- {PrevFunc,Op,Time}
- end.
+handle_call({analyze, procs, Opts}, _, #state{ bpd = #bpd{ p = Ps, us = Tus} = Bpd, fd = Fd} = S) when is_record(Bpd, bpd) ->
+ lists:foreach(fun
+ ({Pid, Mfas}) ->
+ {Pn, Pus} = sum_bp_total_n_us(Mfas),
+ format(Fd, "~n****** Process ~w -- ~s % of profiled time *** ~n", [Pid, s("~.2f", [100.0*divide(Pus,Tus)])]),
+ print_bp_mfa(Mfas, {Pn,Pus}, Fd, Opts),
+ ok
+ end, gb_trees:to_list(Ps)),
+ {reply, ok, S};
-%%%%%%%%%%%%%%%%%%
+handle_call({analyze, total, Opts}, _, #state{ bpd = #bpd{ mfa = Mfas, n = Tn, us = Tus} = Bpd, fd = Fd} = S) when is_record(Bpd, bpd) ->
+ print_bp_mfa(Mfas, {Tn, Tus}, Fd, Opts),
+ {reply, ok, S};
-handle_cast(_Req, S) -> {noreply, S}.
+handle_call({analyze, Type, _Opts}, _, S) ->
+ {reply, {error, {undefined, Type}}, S};
-terminate(_Reason,_S) ->
- call_trace_for_all(false),
- normal.
+%% profile
-%%%%%%%%%%%%%%%%%%
+handle_call({profile, _Rootset, _Pattern, _M,_F,_A}, _From, #state{ profiling = true } = S) ->
+ {reply, {error, already_profiling}, S};
-handle_call({logfile, F}, _FromTag, Status) ->
- case file:open(F, [write]) of
- {ok, Fd} ->
- case get(fd) of
- undefined -> ok;
- FdOld -> file:close(FdOld)
- end,
- put(fd, Fd),
- {reply, ok, Status};
- {error, _} ->
- {reply, error, Status}
- end;
+handle_call({profile, Rootset, Pattern, M,F,A}, From, #state{fd = Fd } = S) ->
-handle_call({profile, Rootset}, {From, _Tag}, S) ->
- link(From),
- maybe_delete(S#state.table),
- io:format("eprof: Starting profiling ..... ~n",[]),
- ptrac(S#state.rootset, false, all()),
- flush_receive(),
- Tab = ets:new(eprof, [set, public]),
- case ptrac(Rootset, true, all()) of
- false ->
- {reply, error, #state{}};
+ set_pattern_trace(false, S#state.pattern),
+ set_process_trace(false, S#state.rootset),
+
+ Pid = setup_profiling(M,F,A),
+ case set_process_trace(true, [Pid|Rootset]) of
true ->
- uni_schedule(),
- call_trace_for_all(true),
- erase(replyto),
- {reply, profiling, #state{table = Tab,
- proc = From,
- profiling = true,
- rootset = Rootset}}
+ set_pattern_trace(true, Pattern),
+ T0 = now(),
+ execute_profiling(Pid),
+ {noreply, #state{
+ profiling = true,
+ rootset = [Pid|Rootset],
+ start_ts = T0,
+ reply = From,
+ fd = Fd,
+ pattern = Pattern
+ }};
+ false ->
+ exit(Pid, eprof_kill),
+ {reply, error, #state{ fd = Fd}}
end;
-handle_call(stop_profiling, _FromTag, S) when S#state.profiling ->
- ptrac(S#state.rootset, false, all()),
- call_trace_for_all(false),
- multi_schedule(),
- io:format("eprof: Stop profiling~n",[]),
- ets:delete(S#state.table, nofunc),
- {reply, profiling_stopped, S#state{profiling = false}};
+handle_call({profile, _Rootset, _Pattern}, _From, #state{ profiling = true } = S) ->
+ {reply, {error, already_profiling}, S};
-handle_call(stop_profiling, _FromTag, S) ->
- {reply, profiling_already_stopped, S};
+handle_call({profile, Rootset, Pattern}, From, #state{ fd = Fd } = S) ->
+
+ set_pattern_trace(false, S#state.pattern),
+ set_process_trace(false, S#state.rootset),
-handle_call({profile, Rootset, M, F, A}, FromTag, S) ->
- io:format("eprof: Starting profiling..... ~n", []),
- maybe_delete(S#state.table),
- ptrac(S#state.rootset, false, all()),
- flush_receive(),
- put(replyto, FromTag),
- Tab = ets:new(eprof, [set, public]),
- P = spawn_link(eprof, call, [self(), M, F, A]),
- case ptrac([P|Rootset], true, all()) of
+ case set_process_trace(true, Rootset) of
true ->
- uni_schedule(),
- call_trace_for_all(true),
- P ! {self(),go},
- {noreply, #state{table = Tab,
- profiling = true,
- rootset = [P|Rootset]}};
+ T0 = now(),
+ set_pattern_trace(true, Pattern),
+ {reply, profiling, #state{
+ profiling = true,
+ rootset = Rootset,
+ start_ts = T0,
+ reply = From,
+ fd = Fd,
+ pattern = Pattern
+ }};
false ->
- exit(P, kill),
- erase(replyto),
- {reply, error, #state{}}
+ {reply, error, #state{ fd = Fd }}
end;
-handle_call(dump, _FromTag, S) ->
- {reply, dump(S#state.table), S};
-
-handle_call(analyse, _FromTag, S) ->
- {reply, analyse(S), S};
+handle_call(stop_profiling, _From, #state{ profiling = false } = S) ->
+ {reply, profiling_already_stopped, S};
-handle_call(total_analyse, _FromTag, S) ->
- {reply, total_analyse(S), S};
+handle_call(stop_profiling, _From, #state{ profiling = true } = S) ->
-handle_call(stop, _FromTag, S) ->
- multi_schedule(),
- {stop, normal, stopped, S}.
+ set_pattern_trace(pause, S#state.pattern),
-%%%%%%%%%%%%%%%%%%%
+ Bpd = collect_bpd(),
-handle_info({trace_ts,_From,_Op,_Func,_Time}=M, S0) when S0#state.profiling ->
- Start = erlang:now(),
- #state{table=Tab,pop=PrevOp0,ptime=PrevTime0,pfunc=PrevFunc0,
- overhead=Overhead0} = S0,
- {PrevFunc,PrevOp,PrevTime} = do_messages(M, Tab, PrevFunc0, PrevOp0, PrevTime0),
- Overhead = Overhead0 + subtr(erlang:now(), Start),
- S = S0#state{overhead=Overhead,pfunc=PrevFunc,pop=PrevOp,ptime=PrevTime},
- {noreply,S};
+ set_process_trace(false, S#state.rootset),
+ set_pattern_trace(false, S#state.pattern),
-handle_info({trace_ts, From, _, _, _}, S) when not S#state.profiling ->
- ptrac([From], false, all()),
- {noreply, S};
+ {reply, profiling_stopped, S#state{
+ profiling = false,
+ rootset = [],
+ pattern = {'_','_','_'},
+ bpd = Bpd
+ }};
-handle_info({_P, {answer, A}}, S) ->
- ptrac(S#state.rootset, false, all()),
- io:format("eprof: Stop profiling~n",[]),
- {From,_Tag} = get(replyto),
- catch unlink(From),
- ets:delete(S#state.table, nofunc),
- gen_server:reply(erase(replyto), {ok, A}),
- multi_schedule(),
- {noreply, S#state{profiling = false,
- rootset = []}};
-
-handle_info({'EXIT', P, Reason},
- #state{profiling=true,proc=P,table=T,rootset=RootSet}) ->
- maybe_delete(T),
- ptrac(RootSet, false, all()),
- multi_schedule(),
- io:format("eprof: Profiling failed\n",[]),
- case erase(replyto) of
- undefined ->
- {noreply, #state{}};
- FromTag ->
- gen_server:reply(FromTag, {error, Reason}),
- {noreply, #state{}}
+%% logfile
+handle_call({logfile, File}, _From, #state{ fd = OldFd } = S) ->
+ case file:open(File, [write]) of
+ {ok, Fd} ->
+ case OldFd of
+ undefined -> ok;
+ OldFd -> file:close(OldFd)
+ end,
+ {reply, ok, S#state{ fd = Fd}};
+ Error ->
+ {reply, Error, S}
end;
-handle_info({'EXIT',_P,_Reason}, S) ->
- {noreply, S}.
+handle_call(dump, _From, #state{ bpd = Bpd } = S) when is_record(Bpd, bpd) ->
+ {reply, gb_trees:to_list(Bpd#bpd.p), S};
-uni_schedule() ->
- erlang:system_flag(multi_scheduling, block).
+handle_call(stop, _FromTag, S) ->
+ {stop, normal, stopped, S}.
-multi_schedule() ->
- erlang:system_flag(multi_scheduling, unblock).
+%% -------------------------------------------------------------------- %%
+%%
+%% handle_cast
+%%
+%% -------------------------------------------------------------------- %%
-%%%%%%%%%%%%%%%%%%
+handle_cast(_Msg, State) ->
+ {noreply, State}.
-call(Top, M, F, A) ->
- receive
- {Top,go} ->
- Top ! {self(), {answer, apply(M,F,A)}}
- end.
+%% -------------------------------------------------------------------- %%
+%%
+%% handle_info
+%%
+%% -------------------------------------------------------------------- %%
-call_trace_for_all(Flag) ->
- erlang:trace_pattern(on_load, Flag, [local]),
- erlang:trace_pattern({'_','_','_'}, Flag, [local]).
+handle_info({'EXIT', _, normal}, S) ->
+ {noreply, S};
+handle_info({'EXIT', _, eprof_kill}, S) ->
+ {noreply, S};
+handle_info({'EXIT', _, Reason}, #state{ reply = FromTag } = S) ->
-ptrac([P|T], How, Flags) when is_pid(P) ->
- case dotrace(P, How, Flags) of
- true ->
- ptrac(T, How, Flags);
- false when How ->
- false;
- false ->
- ptrac(T, How, Flags)
- end;
+ set_process_trace(false, S#state.rootset),
+ set_pattern_trace(false, S#state.pattern),
-ptrac([P|T], How, Flags) when is_atom(P) ->
- case whereis(P) of
- undefined when How ->
- false;
- undefined when not How ->
- ptrac(T, How, Flags);
- Pid ->
- ptrac([Pid|T], How, Flags)
- end;
+ gen_server:reply(FromTag, {error, Reason}),
+ {noreply, S#state{
+ profiling = false,
+ rootset = [],
+ pattern = {'_','_','_'}
+ }};
-ptrac([H|_],_How,_Flags) ->
- io:format("** eprof bad process ~w~n",[H]),
- false;
+% check if Pid is spawned process?
+handle_info({_Pid, {answer, Result}}, #state{ reply = {From,_} = FromTag} = S) ->
-ptrac([],_,_) -> true.
+ set_pattern_trace(pause, S#state.pattern),
-dotrace(P, How, What) ->
- case (catch erlang:trace(P, How, What)) of
- 1 ->
- true;
- _Other when not How ->
- true;
- _Other ->
- io:format("** eprof: bad process: ~p,~p,~p~n", [P,How,What]),
- false
- end.
+ Bpd = collect_bpd(),
-all() -> [call,arity,return_to,running,timestamp,set_on_spawn].
-
-total_analyse(#state{table=notable}) ->
- nothing_to_analyse;
-total_analyse(S) ->
- #state{table = T, overhead = Overhead} = S,
- QH = qlc:q([{{From,Mfa},Time,Count} ||
- {[From|Mfa],Time,Count} <- ets:table(T)]),
- Pcalls = reverse(keysort(2, replicas(qlc:eval(QH)))),
- Time = collect_times(Pcalls),
- format("FUNCTION~44s TIME ~n", ["CALLS"]),
- printit(Pcalls, Time),
- format("\nTotal time: ~.2f\n", [Time / 1000000]),
- format("Measurement overhead: ~.2f\n", [Overhead / 1000000]).
-
-analyse(#state{table=notable}) ->
- nothing_to_analyse;
-analyse(S) ->
- #state{table = T, overhead = Overhead} = S,
- Pids = ordsets:from_list(flatten(ets:match(T, {['$1'|'_'],'_', '_'}))),
- Times = sum(ets:match(T, {'_','$1', '_'})),
- format("FUNCTION~44s TIME ~n", ["CALLS"]),
- do_pids(Pids, T, 0, Times),
- format("\nTotal time: ~.2f\n", [Times / 1000000]),
- format("Measurement overhead: ~.2f\n", [Overhead / 1000000]).
-
-do_pids([Pid|Tail], T, AckTime, Total) ->
- Pcalls =
- reverse(keysort(2, to_tups(ets:match(T, {[Pid|'$1'], '$2','$3'})))),
- Time = collect_times(Pcalls),
- PercentTotal = 100 * (divide(Time, Total)),
- format("~n****** Process ~w -- ~s % of profiled time *** ~n",
- [Pid, fpf(PercentTotal)]),
- printit(Pcalls, Time),
- do_pids(Tail, T, AckTime + Time, Total);
-do_pids([], _, _, _) ->
- ok.
+ set_process_trace(false, S#state.rootset),
+ set_pattern_trace(false, S#state.pattern),
-printit([],_) -> ok;
-printit([{{Mod,Fun,Arity}, Time, Calls} |Tail], ProcTime) ->
- format("~s ~s ~s % ~n", [ff(Mod,Fun,Arity), fint(Calls),
- fpf(100*(divide(Time,ProcTime)))]),
- printit(Tail, ProcTime);
-printit([{{_,{Mod,Fun,Arity}}, Time, Calls} |Tail], ProcTime) ->
- format("~s ~s ~s % ~n", [ff(Mod,Fun,Arity), fint(Calls),
- fpf(100*(divide(Time,ProcTime)))]),
- printit(Tail, ProcTime);
-printit([_|T], Time) ->
- printit(T, Time).
-
-ff(Mod,Fun,Arity) ->
- pad(flatten(io_lib:format("~w:~w/~w", [Mod,Fun, Arity])),45).
-
-pad(Str, Len) ->
- Strlen = length(Str),
- if
- Strlen > Len -> strip_tail(Str, 45);
- true -> lists:append(Str, mklist(Len-Strlen))
- end.
+ catch unlink(From),
+ gen_server:reply(FromTag, {ok, Result}),
+ {noreply, S#state{
+ profiling = false,
+ rootset = [],
+ pattern = {'_','_','_'},
+ bpd = Bpd
+ }}.
+
+%% -------------------------------------------------------------------- %%
+%%
+%% termination
+%%
+%% -------------------------------------------------------------------- %%
+
+terminate(_Reason, #state{ fd = undefined }) ->
+ set_pattern_trace(false, {'_','_','_'}),
+ ok;
+terminate(_Reason, #state{ fd = Fd }) ->
+ file:close(Fd),
+ set_pattern_trace(false, {'_','_','_'}),
+ ok.
-strip_tail([_|_], 0) ->[];
-strip_tail([H|T], I) -> [H|strip_tail(T, I-1)];
-strip_tail([],_I) -> [].
+%% -------------------------------------------------------------------- %%
+%%
+%% code_change
+%%
+%% -------------------------------------------------------------------- %%
-fpf(F) -> strip_tail(flatten(io_lib:format("~w", [round(F)])), 5).
-fint(Int) -> pad(flatten(io_lib:format("~w",[Int])), 10).
+code_change(_OldVsn, State, _Extra) ->
+ {ok, State}.
-mklist(0) -> [];
-mklist(I) -> [$ |mklist(I-1)].
-to_tups(L) -> lists:map(fun(List) -> erlang:list_to_tuple(List) end, L).
+%% -------------------------------------------------------------------- %%
+%%
+%% AUX Functions
+%%
+%% -------------------------------------------------------------------- %%
-divide(X,Y) -> X / Y.
+setup_profiling(M,F,A) ->
+ spawn_link(fun() -> spin_profile(M,F,A) end).
-collect_times([]) -> 0;
-collect_times([Tup|Tail]) -> element(2, Tup) + collect_times(Tail).
+spin_profile(M, F, A) ->
+ receive
+ {Pid, execute} ->
+ Pid ! {self(), {answer, erlang:apply(M,F,A)}}
+ end.
-dump(T) ->
- L = ets:tab2list(T),
- format(L).
+execute_profiling(Pid) ->
+ Pid ! {self(), execute}.
-format([H|T]) ->
- format("~p~n", [H]), format(T);
-format([]) -> ok.
+set_pattern_trace(Flag, Pattern) ->
+ erlang:system_flag(multi_scheduling, block),
+ erlang:trace_pattern(on_load, Flag, [call_time]),
+ erlang:trace_pattern(Pattern, Flag, [call_time]),
+ erlang:system_flag(multi_scheduling, unblock),
+ ok.
-format(F, A) ->
- io:format(F,A),
- case get(fd) of
- undefined -> ok;
- Fd -> io:format(Fd, F,A)
+set_process_trace(Flag, Pids) ->
+ % do we need procs for meta info?
+ % could be useful
+ set_process_trace(Flag, Pids, [call, set_on_spawn]).
+set_process_trace(_, [], _) -> true;
+set_process_trace(Flag, [Pid|Pids], Options) when is_pid(Pid) ->
+ try
+ erlang:trace(Pid, Flag, Options),
+ set_process_trace(Flag, Pids, Options)
+ catch
+ _:_ ->
+ false
+ end;
+set_process_trace(Flag, [Name|Pids], Options) when is_atom(Name) ->
+ case whereis(Name) of
+ undefined ->
+ set_process_trace(Flag, Pids, Options);
+ Pid ->
+ set_process_trace(Flag, [Pid|Pids], Options)
end.
-maybe_delete(T) ->
- catch ets:delete(T).
+collect_bpd() ->
+ collect_bpd([M || M <- [element(1, Mi) || Mi <- code:all_loaded()], M =/= ?MODULE]).
+
+collect_bpd(Ms) when is_list(Ms) ->
+ collect_bpdf(collect_mfas(Ms) ++ erlang:system_info(snifs)).
+
+collect_mfas(Ms) ->
+ lists:foldl(fun
+ (M, Mfas) ->
+ Mfas ++ [{M, F, A} || {F, A} <- M:module_info(functions)]
+ end, [], Ms).
+
+collect_bpdf(Mfas) ->
+ collect_bpdf(Mfas, #bpd{}).
+collect_bpdf([], Bpd) ->
+ Bpd;
+collect_bpdf([Mfa|Mfas], #bpd{n = N, us = Us, p = Tree, mfa = Code } = Bpd) ->
+ case erlang:trace_info(Mfa, call_time) of
+ {call_time, []} ->
+ collect_bpdf(Mfas, Bpd);
+ {call_time, Data} when is_list(Data) ->
+ {CTn, CTus, CTree} = collect_bpdfp(Mfa, Tree, Data),
+ collect_bpdf(Mfas, Bpd#bpd{
+ n = CTn + N,
+ us = CTus + Us,
+ p = CTree,
+ mfa = [{Mfa, {CTn, CTus}}|Code]
+ });
+ {call_time, false} ->
+ collect_bpdf(Mfas, Bpd);
+ {call_time, _Other} ->
+ collect_bpdf(Mfas, Bpd)
+ end.
-sum([[H]|T]) -> H + sum(T);
-sum([]) -> 0.
+collect_bpdfp(Mfa, Tree, Data) ->
+ lists:foldl(fun
+ ({Pid, Ni, Si, Usi}, {PTno, PTuso, To}) ->
+ Time = Si * 1000000 + Usi,
+ Ti1 = case gb_trees:lookup(Pid, To) of
+ none ->
+ gb_trees:enter(Pid, [{Mfa, {Ni, Time}}], To);
+ {value, Pmfas} ->
+ gb_trees:enter(Pid, [{Mfa, {Ni, Time}}|Pmfas], To)
+ end,
+ {PTno + Ni, PTuso + Time, Ti1}
+ end, {0,0, Tree}, Data).
+
+%% manipulators
+sort_mfa(Bpfs, mfa) when is_list(Bpfs) ->
+ lists:sort(fun
+ ({A,_}, {B,_}) when A < B -> true;
+ (_, _) -> false
+ end, Bpfs);
+sort_mfa(Bpfs, time) when is_list(Bpfs) ->
+ lists:sort(fun
+ ({_,{_,A}}, {_,{_,B}}) when A < B -> true;
+ (_, _) -> false
+ end, Bpfs);
+sort_mfa(Bpfs, calls) when is_list(Bpfs) ->
+ lists:sort(fun
+ ({_,{A,_}}, {_,{B,_}}) when A < B -> true;
+ (_, _) -> false
+ end, Bpfs);
+sort_mfa(Bpfs, _) when is_list(Bpfs) -> sort_mfa(Bpfs, time).
+
+filter_mfa(Bpfs, Ts) when is_list(Ts) ->
+ filter_mfa(Bpfs, [], proplists:get_value(calls, Ts, 0), proplists:get_value(time, Ts, 0));
+filter_mfa(Bpfs, _) -> Bpfs.
+filter_mfa([], Out, _, _) -> lists:reverse(Out);
+filter_mfa([{_, {C, T}}=Bpf|Bpfs], Out, Ct, Tt) when C >= Ct, T >= Tt -> filter_mfa(Bpfs, [Bpf|Out], Ct, Tt);
+filter_mfa([_|Bpfs], Out, Ct, Tt) -> filter_mfa(Bpfs, Out, Ct, Tt).
+
+sum_bp_total_n_us(Mfas) ->
+ lists:foldl(fun ({_, {Ci,Usi}}, {Co, Uso}) -> {Co + Ci, Uso + Usi} end, {0,0}, Mfas).
+
+%% strings and format
+
+string_bp_mfa(Mfas, Tus) -> string_bp_mfa(Mfas, Tus, {0,0,0,0,0}, []).
+string_bp_mfa([], _, Ws, Strings) -> {Ws, lists:reverse(Strings)};
+string_bp_mfa([{Mfa, {Count, Time}}|Mfas], Tus, {MfaW, CountW, PercW, TimeW, TpCW}, Strings) ->
+ Smfa = s(Mfa),
+ Scount = s(Count),
+ Stime = s(Time),
+ Sperc = s("~.2f", [100*divide(Time,Tus)]),
+ Stpc = s("~.2f", [divide(Time,Count)]),
+
+ string_bp_mfa(Mfas, Tus, {
+ erlang:max(MfaW, length(Smfa)),
+ erlang:max(CountW,length(Scount)),
+ erlang:max(PercW, length(Sperc)),
+ erlang:max(TimeW, length(Stime)),
+ erlang:max(TpCW, length(Stpc))
+ }, [[Smfa, Scount, Sperc, Stime, Stpc] | Strings]).
+
+print_bp_mfa(Mfas, {_Tn, Tus}, Fd, Opts) ->
+ Fmfas = filter_mfa(sort_mfa(Mfas, proplists:get_value(sort, Opts)), proplists:get_value(filter, Opts)),
+ {{MfaW, CountW, PercW, TimeW, TpCW}, Strs} = string_bp_mfa(Fmfas, Tus),
+ Ws = {
+ erlang:max(length("FUNCTION"), MfaW),
+ erlang:max(length("CALLS"), CountW),
+ erlang:max(length(" %"), PercW),
+ erlang:max(length("TIME"), TimeW),
+ erlang:max(length("uS / CALLS"), TpCW)
+ },
+ format(Fd, Ws, ["FUNCTION", "CALLS", " %", "TIME", "uS / CALLS"]),
+ format(Fd, Ws, ["--------", "-----", "---", "----", "----------"]),
+
+ lists:foreach(fun (String) -> format(Fd, Ws, String) end, Strs),
+ ok.
-replicas(L) ->
- replicas(L, []).
+s({M,F,A}) -> s("~w:~w/~w",[M,F,A]);
+s(Term) -> s("~p", [Term]).
+s(Format, Terms) -> lists:flatten(io_lib:format(Format, Terms)).
-replicas([{{Pid, {Mod,Fun,Arity}}, Ack,Calls} |Tail], Result) ->
- case search({Mod,Fun,Arity},Result) of
- false ->
- replicas(Tail, [{{Pid, {Mod,Fun,Arity}}, Ack,Calls} |Result]);
- {Ack2, Calls2} ->
- Result2 = del({Mod,Fun,Arity}, Result),
- replicas(Tail, [{{Pid, {Mod,Fun,Arity}},
- Ack+Ack2,Calls+Calls2} |Result2])
- end;
-replicas([_|T], Ack) -> %% Whimpy
- replicas(T, Ack);
-
-replicas([], Res) -> Res.
-
-search(Key, [{{_,Key}, Ack, Calls}|_]) ->
- {Ack, Calls};
-search(Key, [_|T]) ->
- search(Key, T);
-search(_Key,[]) -> false.
-
-del(Key, [{{_,Key},_Ack,_Calls}|T]) ->
- T;
-del(Key, [H | Tail]) ->
- [H|del(Key, Tail)];
-del(_Key,[]) -> [].
-
-flush_receive() ->
- receive
- {trace_ts, From, _, _, _} when is_pid(From) ->
- ptrac([From], false, all()),
- flush_receive();
- _ ->
- flush_receive()
- after 0 ->
- ok
- end.
+format(Fd, {MfaW, CountW, PercW, TimeW, TpCW}, Strings) ->
+ format(Fd, s("~~.~ps ~~~ps ~~~ps ~~~ps [~~~ps]~~n", [MfaW, CountW, PercW, TimeW, TpCW]), Strings);
+format(undefined, Format, Strings) ->
+ io:format(Format, Strings),
+ ok;
+format(Fd, Format, Strings) ->
+ io:format(Fd, Format, Strings),
+ io:format(Format, Strings),
+ ok.
-code_change(_OldVsn, State, _Extra) ->
- {ok,State}.
+divide(_,0) -> 0.0;
+divide(T,N) -> T/N.
diff --git a/lib/tools/src/xref_base.erl b/lib/tools/src/xref_base.erl
index d0dbf4a2b4..93f0e9c0c8 100644
--- a/lib/tools/src/xref_base.erl
+++ b/lib/tools/src/xref_base.erl
@@ -1,24 +1,26 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2000-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 2000-2010. All Rights Reserved.
+%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
-module(xref_base).
+%% Avoid warning for local function error/1 clashing with autoimported BIF.
+-compile({no_auto_import,[error/1]}).
-export([new/0, new/1, delete/1,
add_directory/2, add_directory/3,
add_module/2, add_module/3,
@@ -29,7 +31,7 @@
add_release/2, add_release/3,
get_library_path/1, set_library_path/2, set_library_path/3,
set_up/1, set_up/2,
- q/2, q/3, info/1, info/2, info/3, update/1, update/2,
+ q/2, q/3, info/1, info/2, info/3, update/1, update/2,
forget/1, forget/2, variables/1, variables/2,
analyze/2, analyze/3, analysis/1,
get_default/2, set_default/3,
@@ -38,14 +40,14 @@
-export([format_error/1]).
%% The following functions are exported for testing purposes only:
--export([do_add_module/4, do_add_application/2, do_add_release/2,
+-export([do_add_module/4, do_add_application/2, do_add_release/2,
do_remove_module/2]).
--import(lists,
- [filter/2, flatten/1, foldl/3, keysearch/3, map/2, mapfoldl/3,
- member/2, reverse/1, sort/1, usort/1]).
+-import(lists,
+ [filter/2, flatten/1, foldl/3, foreach/2, keysearch/3, map/2,
+ mapfoldl/3, member/2, reverse/1, sort/1, usort/1]).
--import(sofs,
+-import(sofs,
[constant_function/2, converse/1, difference/2, domain/1,
empty_set/0, family/1, family_difference/2, intersection/2,
family_projection/2, family_to_relation/1, family_union/1,
@@ -103,12 +105,12 @@ delete(State) ->
ok
end
end,
- map(Fun, dict:to_list(State#xref.variables)),
+ foreach(Fun, dict:to_list(State#xref.variables)),
ok.
add_directory(State, Dir) ->
add_directory(State, Dir, []).
-
+
%% -> {ok, Modules, NewState} | Error
add_directory(State, Dir, Options) ->
ValOptions = option_values([builtins, recurse, verbose, warnings], State),
@@ -277,7 +279,7 @@ q(S, Q, Options) when is_atom(Q) ->
q(S, atom_to_list(Q), Options);
q(S, Q, Options) ->
case xref_utils:is_string(Q, 1) of
- true ->
+ true ->
case set_up(S, Options) of
{ok, S1} ->
case xref_compiler:compile(Q, S1#xref.variables) of
@@ -336,7 +338,7 @@ forget(State, Variable) when is_atom(Variable) ->
forget(State, Variables) ->
Vars = State#xref.variables,
do_forget(Variables, Vars, Variables, State).
-
+
variables(State) ->
variables(State, [user]).
@@ -350,9 +352,9 @@ variables(State, Options) ->
{ok, NewState} ->
{U, P} = do_variables(NewState),
R1 = if User -> [{user, U}]; true -> [] end,
- R = if
- Predef -> [{predefined,P} | R1];
- true -> R1
+ R = if
+ Predef -> [{predefined,P} | R1];
+ true -> R1
end,
{{ok, R}, NewState};
Error ->
@@ -368,7 +370,7 @@ analyze(State, Analysis) ->
%% -> {{ok, Answer}, NewState} | {Error, NewState}
analyze(State, Analysis, Options) ->
case analysis(Analysis, State#xref.mode) of
- P when is_list(P) ->
+ P when is_list(P) ->
q(State, P, Options);
error ->
R = case analysis(Analysis, functions) of
@@ -461,7 +463,7 @@ get_default(State, Option) ->
%% -> [{Option, Value}]
get_default(State) ->
- Fun = fun(O) -> V = current_default(State, O), {O, V} end,
+ Fun = fun(O) -> V = current_default(State, O), {O, V} end,
map(Fun, [builtins, recurse, verbose, warnings]).
%% -> {ok, NewState} -> Error
@@ -478,7 +480,7 @@ set_default(State, Options) ->
format_error({error, Module, Error}) ->
Module:format_error(Error);
format_error({invalid_options, Options}) ->
- io_lib:format("Unknown option(s) or invalid option value(s): ~p~n",
+ io_lib:format("Unknown option(s) or invalid option value(s): ~p~n",
[Options]);
format_error({invalid_filename, Term}) ->
io_lib:format("A file name (a string) was expected: ~p~n", [Term]);
@@ -540,7 +542,7 @@ updated_modules(State) ->
case xref_utils:file_info(File) of
{ok, {_, file, readable, MTime}} when MTime =/= RTime ->
[{M,File} | L];
- _Else ->
+ _Else ->
L
end
end,
@@ -591,7 +593,7 @@ do_add_release(Dir, RelName, OB, OV, OW, State) ->
case xref_utils:release_directory(Dir, true, "ebin") of
{ok, ReleaseDirName, ApplDir, Dirs} ->
ApplDirs = xref_utils:select_last_application_version(Dirs),
- Release = case RelName of
+ Release = case RelName of
[[]] -> ReleaseDirName;
[Name] -> Name
end,
@@ -615,7 +617,7 @@ do_add_release(S, XRel) ->
end.
add_rel_appls([ApplDir | ApplDirs], Release, OB, OV, OW, State) ->
- {ok, _AppName, NewState} =
+ {ok, _AppName, NewState} =
add_appldir(ApplDir, Release, [[]], OB, OV, OW, State),
add_rel_appls(ApplDirs, Release, OB, OV, OW, NewState);
add_rel_appls([], [Release], _OB, _OV, _OW, NewState) ->
@@ -637,10 +639,10 @@ add_appldir(ApplDir, Release, Name, OB, OV, OW, OldState) ->
[[]] -> AppName0;
[N] -> N
end,
- AppInfo = #xref_app{name = AppName, rel_name = Release,
+ AppInfo = #xref_app{name = AppName, rel_name = Release,
vsn = Vsn, dir = Dir},
State1 = do_add_application(OldState, AppInfo),
- {ok, _Modules, NewState} =
+ {ok, _Modules, NewState} =
do_add_directory(Dir, [AppName], OB, false, OV, OW, State1),
{ok, AppName, NewState}.
@@ -662,7 +664,7 @@ do_add_directory(Dir, AppName, Bui, Rec, Ver, War, State) ->
ok = is_filename(Dir),
{FileNames, Errors, Jams, Unreadable} =
xref_utils:scan_directory(Dir, Rec, [?Suffix], [".jam"]),
- warnings(War, jam, Jams),
+ warnings(War, jam, Jams),
warnings(War, unreadable, Unreadable),
case Errors of
[] ->
@@ -683,7 +685,7 @@ do_add_a_module(File, AppName, Builtins, Verbose, Warnings, State) ->
false ->
throw_error({invalid_filename, File});
Splitname ->
- do_add_module(Splitname, AppName, Builtins, Verbose,
+ do_add_module(Splitname, AppName, Builtins, Verbose,
Warnings, State)
end.
@@ -691,7 +693,7 @@ do_add_a_module(File, AppName, Builtins, Verbose, Warnings, State) ->
%% Options: verbose, warnings, builtins
do_add_module({Dir, Basename}, AppName, Builtins, Verbose, Warnings, State) ->
File = filename:join(Dir, Basename),
- {ok, M, Bad, NewState} =
+ {ok, M, Bad, NewState} =
do_add_module1(Dir, File, AppName, Builtins, Verbose, Warnings, State),
filter(fun({Tag,B}) -> warnings(Warnings, Tag, [[File,B]]) end, Bad),
{ok, M, NewState}.
@@ -723,7 +725,7 @@ do_add_module1(Dir, File, AppName, Builtins, Verbose, Warnings, State) ->
{ok, {_, _, _, Time}} -> Time;
Error -> throw(Error)
end,
- XMod = #xref_mod{name = M, app_name = AppName, dir = Dir,
+ XMod = #xref_mod{name = M, app_name = AppName, dir = Dir,
mtime = T, builtins = Builtins,
no_unresolved = NoUnresCalls},
do_add_module(State, XMod, UnresCalls, Data);
@@ -736,13 +738,13 @@ abst(File, Builtins, Mode) when Mode =:= functions ->
case beam_lib:chunks(File, [abstract_code, exports, attributes]) of
{ok, {M,[{abstract_code,NoA},_X,_A]}} when NoA =:= no_abstract_code ->
{ok, M, NoA};
- {ok, {M, [{abstract_code, {abstract_v1, Forms}},
+ {ok, {M, [{abstract_code, {abstract_v1, Forms}},
{exports,X0}, {attributes,A}]}} ->
%% R7.
X = xref_utils:fa_to_mfa(X0, M),
D = deprecated(A, X, M),
xref_reader:module(M, Forms, Builtins, X, D);
- {ok, {M, [{abstract_code, {abstract_v2, Forms}},
+ {ok, {M, [{abstract_code, {abstract_v2, Forms}},
{exports,X0}, {attributes,A}]}} ->
%% R8-R9B.
X = xref_utils:fa_to_mfa(X0, M),
@@ -769,8 +771,8 @@ abst(File, Builtins, Mode) when Mode =:= modules ->
true ->
I0;
false ->
- Fun = fun({M,F,A}) ->
- not xref_utils:is_builtin(M, F, A)
+ Fun = fun({M,F,A}) ->
+ not xref_utils:is_builtin(M, F, A)
end,
filter(Fun, I0)
end,
@@ -790,7 +792,7 @@ mfa_exports(X0, Attributes, M) ->
xref_utils:fa_to_mfa(X1, M).
adjust_arity(F, A) ->
- case xref_utils:is_static_function(F, A) of
+ case xref_utils:is_static_function(F, A) of
true -> A;
false -> A - 1
end.
@@ -885,7 +887,7 @@ do_add_module(S, M, XMod, Unres0, Data) when S#xref.mode =:= functions ->
Unres = domain(UnresCalls),
DefinedFuns = domain(DefAt),
- {AXC, ALC, Bad1, LPreCAt2, XPreCAt2} =
+ {AXC, ALC, Bad1, LPreCAt2, XPreCAt2} =
extra_edges(AXC1, ALC1, Bad0, DefinedFuns),
Bad = map(fun(B) -> {xref_attr, B} end, Bad1),
LPreCAt = union(LPreCAt1, LPreCAt2),
@@ -904,8 +906,8 @@ do_add_module(S, M, XMod, Unres0, Data) when S#xref.mode =:= functions ->
%% {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} =
+ 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,
@@ -977,13 +979,13 @@ extra_edges(CAX, CAL, Bad0, F) ->
ALC = restriction(2, restriction(ALC0, F), F),
LPreCAt2 = restriction(CAL, ALC),
XPreCAt2 = restriction(CAX, AXC),
- Bad = Bad0 ++ to_external(difference(AXC0, 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_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():
@@ -1011,10 +1013,10 @@ inter_graph(X, L, LC, XC, CallAt) ->
Es = union(LEs, XEs),
E1 = to_external(restriction(difference(LC, LEs), XL)),
- R0 = xref_utils:xset(reachable(E1, G, []),
+ 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.
@@ -1033,7 +1035,7 @@ inter_graph(X, L, LC, XC, CallAt) ->
?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,
+ [XL, XEs, LEs, E1, R0, RL, RX, R, EE,
ECallAt1, ECallAt2, ECallAt]),
{EE, ECallAt}.
@@ -1121,7 +1123,7 @@ remove_erase([], D) ->
do_add_libraries(Path, Verbose, State) ->
message(Verbose, lib_search, []),
- {C, E} = xref_utils:list_path(Path, [?Suffix]),
+ {C, E} = xref_utils:list_path(Path, [?Suffix]),
message(Verbose, done, []),
MDs = to_external(relation_to_family(relation(C))),
%% message(Verbose, lib_check, []),
@@ -1160,23 +1162,23 @@ do_set_up(S, VerboseOpt) ->
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
+%% 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
+%% 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,
+ [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),
@@ -1206,7 +1208,7 @@ do_set_up(S) when S#xref.mode =:= functions ->
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} =
+ {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),
@@ -1228,22 +1230,22 @@ do_set_up(S) when S#xref.mode =:= functions ->
%% 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 =
+ 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},
+ 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 =
+ IFun =
+ fun({Mod,EE_M}, XMods) ->
+ IMFun =
fun(XrefMod) ->
- [NoCalls, NoFunctionCalls,
+ [NoCalls, NoFunctionCalls,
NoFunctions, _NoInter] = XrefMod#xref_mod.info,
- NewInfo = [NoCalls, NoFunctionCalls, NoFunctions,
+ NewInfo = [NoCalls, NoFunctionCalls, NoFunctions,
{no_inter_function_calls,length(EE_M)}],
XrefMod#xref_mod{info = NewInfo}
end,
@@ -1274,11 +1276,11 @@ do_set_up(S) when S#xref.mode =:= functions ->
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] =
+ [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),
@@ -1288,8 +1290,8 @@ do_set_up(S) when S#xref.mode =:= modules ->
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},
+
+ ME = projection({external, fun({M1,{M2,_F2,_A2}}) -> {M1,M2} end},
family_to_relation(I0)),
ME2AE = multiple_relative_product({M2A, M2A}, ME),
@@ -1298,7 +1300,7 @@ do_set_up(S) when S#xref.mode =:= modules ->
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} =
+ {_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),
@@ -1312,7 +1314,7 @@ do_set_up(S) when S#xref.mode =:= modules ->
X = family_union(X1, Lib),
Empty = empty_set(),
- Vs = [{'X',X},{'U',U},{'B',B},{'XU',XU},{v,V},
+ 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},
@@ -1328,10 +1330,10 @@ finish_set_up(S, Vs) ->
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,
+ 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);
@@ -1362,15 +1364,15 @@ var_type('EE') -> {function, edge};
var_type('LC') -> {function, edge};
var_type('UC') -> {function, edge};
var_type('XC') -> {function, edge};
-var_type('AE') -> {application, edge};
-var_type('ME') -> {module, edge};
+var_type('AE') -> {application, edge};
+var_type('ME') -> {module, edge};
var_type('RE') -> {release, edge};
var_type(_) -> {foo, bar}.
make_families(ModDictList, N) ->
Fun1 = fun({_,XMod}) -> XMod#xref_mod.data end,
Ss = from_sets(map(Fun1, ModDictList)),
- %% io:format("~n~p <= module data <= ~p~n",
+ %% io:format("~n~p <= module data <= ~p~n",
%% [pack:lsize(Ss), pack:usize(Ss)]),
make_fams(N, Ss, []).
@@ -1389,7 +1391,7 @@ make_M2A(ModDictList) ->
make_A2R(ApplDict) ->
AppDict = dict:to_list(ApplDict),
Fun = fun({A,XApp}) -> {A, XApp#xref_app.rel_name} end,
- Appl0 = family(map(Fun, AppDict)),
+ Appl0 = family(map(Fun, AppDict)),
AllApps = domain(Appl0),
Appl = family_to_relation(Appl0),
{Appl, AllApps}.
@@ -1445,13 +1447,13 @@ make_libs(XU, F, AM, LibPath, LibDict) ->
false ->
Libraries = dict:to_list(LibDict),
Lb = restriction(a_function(Libraries), UM),
- MFun = fun({M,XLib}) ->
+ MFun = fun({M,XLib}) ->
#xref_lib{dir = Dir} = XLib,
xref_utils:module_filename(Dir, M)
end,
map(MFun, to_external(Lb))
end,
- Fun = fun(FileName, Deprs) ->
+ Fun = fun(FileName, Deprs) ->
case beam_lib:chunks(FileName, [exports, attributes]) of
{ok, {M, [{exports,X}, {attributes,A}]}} ->
Exports = mfa_exports(X, A, M),
@@ -1496,14 +1498,14 @@ user_family(R) ->
partition_family({external, fun({_MFA1, {M2,_,_}}) -> M2 end}, R).
do_variables(State) ->
- Fun = fun({Name, #xref_var{vtype = user}}, {P,U}) ->
+ Fun = fun({Name, #xref_var{vtype = user}}, {P,U}) ->
{P,[Name | U]};
- ({Name, #xref_var{vtype = predef}}, A={P,U}) ->
+ ({Name, #xref_var{vtype = predef}}, A={P,U}) ->
case atom_to_list(Name) of
[H|_] when H>= $a, H=<$z -> A;
_Else -> {[Name | P], U}
end;
- ({{tmp, V}, _}, A) ->
+ ({{tmp, V}, _}, A) ->
io:format("Bug in ~p: temporary ~p~n", [?MODULE, V]), A;
(_V, A) -> A
end,
@@ -1565,7 +1567,7 @@ do_info(S, libraries) ->
map(fun({_L,XLib}) -> lib_info(XLib) end, D);
do_info(_S, I) ->
error({no_such_info, I}).
-
+
do_info(S, Type, E) when is_atom(E) ->
do_info(S, Type, [E]);
do_info(S, modules, Modules0) when is_list(Modules0) ->
@@ -1598,7 +1600,7 @@ find_info([E | Es], Dict, Error) ->
{ok, X} ->
[X | find_info(Es, Dict, Error)]
end;
-find_info([], _Dict, _Error) ->
+find_info([], _Dict, _Error) ->
[].
%% -> {[{AppName, RelName}], [{RelName, XApp}]}
@@ -1618,7 +1620,7 @@ rel_apps(S) ->
rel_apps_sums(AR, RRA0, S) ->
AppMods = app_mods(S), % [{AppName, XMod}]
RRA1 = relation_to_family(relation(RRA0)),
- RRA = inverse(substitution(1, RRA1)),
+ RRA = inverse(substitution(1, RRA1)),
%% RRA is [{RelName,{RelName,[XApp]}}]
RelMods = relative_product1(relation(AR), relation(AppMods)),
RelAppsMods = relative_product1(RRA, RelMods),
@@ -1630,7 +1632,7 @@ rel_apps_sums(AR, RRA0, S) ->
%% -> [{AppName, XMod}]
app_mods(S) ->
D = sort(dict:to_list(S#xref.modules)),
- Fun = fun({_M,XMod}, Acc) ->
+ Fun = fun({_M,XMod}, Acc) ->
case XMod#xref_mod.app_name of
[] -> Acc;
[AppName] -> [{AppName, XMod} | Acc]
@@ -1639,7 +1641,7 @@ app_mods(S) ->
foldl(Fun, [], D).
mod_info(XMod) ->
- #xref_mod{name = M, app_name = AppName, builtins = BuiltIns,
+ #xref_mod{name = M, app_name = AppName, builtins = BuiltIns,
dir = Dir, info = Info} = XMod,
App = sup_info(AppName),
{M, [{application, App}, {builtins, BuiltIns}, {directory, Dir} | Info]}.
@@ -1649,7 +1651,7 @@ app_info({AppName, ModSums}, S) ->
#xref_app{rel_name = RelName, vsn = Vsn, dir = Dir} = XApp,
Release = sup_info(RelName),
{AppName, [{directory,Dir}, {release, Release}, {version,Vsn} | ModSums]}.
-
+
rel_info({{RelName, XApps}, ModSums}, S) ->
NoApps = length(XApps),
XRel = dict:fetch(RelName, S#xref.releases),
@@ -1678,16 +1680,16 @@ no_sum(S, L) when S#xref.mode =:= modules ->
[{no_analyzed_modules, length(L)}].
no_sum([XMod | D], C0, UC0, LC0, XC0, UFC0, L0, X0, EV0, NoM) ->
- [{no_calls, {C,UC}},
+ [{no_calls, {C,UC}},
{no_function_calls, {LC,XC,UFC}},
{no_functions, {L,X}},
{no_inter_function_calls, EV}] = XMod#xref_mod.info,
no_sum(D, C0+C, UC0+UC, LC0+LC, XC0+XC, UFC0+UFC, L0+L, X0+X, EV0+EV, NoM);
no_sum([], C, UC, LC, XC, UFC, L, X, EV, NoM) ->
[{no_analyzed_modules, NoM},
- {no_calls, {C,UC}},
+ {no_calls, {C,UC}},
{no_function_calls, {LC,XC,UFC}},
- {no_functions, {L,X}},
+ {no_functions, {L,X}},
{no_inter_function_calls, EV}].
%% -> ok | throw(Error)
@@ -1712,20 +1714,20 @@ warnings(Flag, Message, [F | Fs]) ->
%% pack(term()) -> term()
%%
%% The identify function. The returned term does not use more heap
-%% than the given term. Tuples that are equal (=:=/2) are made
+%% than the given term. Tuples that are equal (=:=/2) are made
%% "the same".
%%
%% The process dictionary is used because it seems to be faster than
%% anything else right now...
%%
%pack(T) -> T;
-pack(T) ->
+pack(T) ->
PD = erase(),
NT = pack1(T),
%% true = T =:= NT,
%% io:format("erasing ~p elements...~n", [length(erase())]),
erase(), % wasting heap (and time)...
- map(fun({K,V}) -> put(K, V) end, PD),
+ foreach(fun({K,V}) -> put(K, V) end, PD),
NT.
pack1(C) when not is_tuple(C), not is_list(C) ->
diff --git a/lib/tools/src/xref_compiler.erl b/lib/tools/src/xref_compiler.erl
index 67ac8c617d..1445e135be 100644
--- a/lib/tools/src/xref_compiler.erl
+++ b/lib/tools/src/xref_compiler.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2000-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 2000-2010. All Rights Reserved.
+%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
@@ -31,21 +31,23 @@
-define(CALL(F), ok).
-endif.
+%% Avoid warning for local function error/1 clashing with autoimported BIF.
+-compile({no_auto_import,[error/1]}).
-export([compile/2]).
-export([update_graph_counter/3]).
-export([format_error/1]).
--import(lists,
+-import(lists,
[concat/1, foldl/3, nthtail/2, reverse/1, sort/1, sublist/2]).
-import(sofs,
[composite/2, difference/2, empty_set/0, from_term/1,
intersection/2, is_empty_set/1, multiple_relative_product/2,
projection/2, relation/1, relation_to_family/1,
- restriction/2, substitution/2, to_external/1, union/2,
- union_of_family/1]).
+ restriction/2, specification/2, substitution/2,
+ to_external/1, union/2, union_of_family/1]).
%%
%% Exported functions
@@ -75,7 +77,7 @@ compile(Chars, Table) ->
{error, Info, Line} ->
error({parse_error, Line, Info})
end.
-
+
format_error({error, Module, Error}) ->
Module:format_error(Error);
format_error({parse_error, Line, Error}) ->
@@ -115,7 +117,7 @@ statements([Stmt={assign, VarType, Name, E} | Stmts0], Table, L, UV) ->
throw_error({variable_reassigned, xref_parser:t2s(Stmt)});
error ->
{Type, OType, NewE} = t_expr(E, Table),
- Val = #xref_var{name = Name, vtype = VarType,
+ Val = #xref_var{name = Name, vtype = VarType,
otype = OType, type = Type},
NewTable = dict:store(Name, Val, Table),
Stmts = if Stmts0 =:= [] -> [{variable, Name}]; true -> Stmts0 end,
@@ -128,9 +130,9 @@ statements([Expr], Table, L, UV) ->
E1 = un_familiarize(Type, OType, NewE),
NE = case {Type, OType} of
%% Edges with empty sets of line numbers are removed.
- {{line, _}, edge} ->
+ {{line, _}, edge} ->
{relation_to_family, E1};
- {_Type, edge_closure} ->
+ {_Type, edge_closure} ->
%% Fake a closure usage, just to make sure it is destroyed.
E2 = {fun graph_access/2, E1, E1},
{fun(_E) -> 'closure()' end, E2};
@@ -163,7 +165,7 @@ t_expr(E, Table) ->
%%% Constant = atom() | {atom(), atom()} | MFA | {MFA, MFA}
%%% Call = atom() % function in the sofs module
%%% | fun()
-%%% Type = {line, LineType} | function | module | application | release
+%%% Type = {line, LineType} | function | module | application | release
%%% | number
%%% LineType = line | local_call | external_call | export_call | all_line_call
%%% VarType = predef | user | tmp
@@ -182,7 +184,7 @@ check_expr({variable, Name}, Table) ->
case dict:find(Name, Table) of
{ok, #xref_var{vtype = VarType, otype = OType, type = Type}} ->
V0 = {variable, {VarType, Name}},
- V = case {VarType, Type, OType} of
+ V = case {VarType, Type, OType} of
{predef, release, _} -> V0;
{predef, application, _} -> V0;
{predef, module, _} -> V0;
@@ -212,7 +214,7 @@ check_expr(Expr={set, SOp, E}, Table) ->
{edge_set, domain} -> vertex_set;
{edge_set, weak} -> edge_set;
{edge_set, strict} -> edge_set;
- _ ->
+ _ ->
throw_error({type_error, xref_parser:t2s(Expr)})
end,
Op = set_op(SOp),
@@ -223,10 +225,10 @@ check_expr(Expr={graph, Op, E}, Table) ->
case Type of
{line, _LineType} ->
throw_error({type_error, xref_parser:t2s(Expr)});
- _Else ->
+ _Else ->
ok
end,
- OType =
+ OType =
case {NOType, Op} of
{edge, components} -> vertex_set;
{edge, condensation} -> edge_set;
@@ -237,7 +239,7 @@ check_expr(Expr={graph, Op, E}, Table) ->
%% Neither need nor want these ones:
%% {edge_set, closure} -> edge_set_closure;
%% {edge_set, components} -> vertex_set_set;
- _ ->
+ _ ->
throw_error({type_error, xref_parser:t2s(Expr)})
end,
E2 = {convert, NOType, edge_closure, E1},
@@ -271,10 +273,10 @@ check_expr(Expr={set, SOp, E1, E2}, Table) ->
number ->
{expr, number, number, {call, ari_op(SOp), NE1, NE2}};
_Else -> % set
- {Type, NewE1, NewE2} =
+ {Type, NewE1, NewE2} =
case {type_ord(Type1), type_ord(Type2)} of
{T1, T2} when T1 =:= T2 ->
- %% Example: if Type1 = {line, line} and
+ %% Example: if Type1 = {line, line} and
%% Type2 = {line, export_line}, then this is not
%% correct, but works:
{Type1, NE1, NE2};
@@ -296,7 +298,7 @@ check_expr(Expr={restr, ROp, E1, E2}, Table) ->
throw_error({type_error, xref_parser:t2s(Expr)});
{_Type1, {line, _LineType2}} ->
throw_error({type_error, xref_parser:t2s(Expr)});
- _ ->
+ _ ->
ok
end,
case {OType1, OType2} of
@@ -307,14 +309,14 @@ check_expr(Expr={restr, ROp, E1, E2}, Table) ->
{edge, vertex} ->
restriction(ROp, E1, Type1, NE1, Type2, NE2);
{edge_closure, vertex} when ROp =:= '|||' ->
- {expr, _, _, R1} =
+ {expr, _, _, R1} =
closure_restriction('|', Type1, Type2, OType2, NE1, NE2),
- {expr, _, _, R2} =
+ {expr, _, _, R2} =
closure_restriction('||', Type1, Type2, OType2, NE1, NE2),
{expr, Type1, edge, {call, intersection, R1, R2}};
- {edge_closure, vertex} ->
+ {edge_closure, vertex} ->
closure_restriction(ROp, Type1, Type2, OType2, NE1, NE2);
- _ ->
+ _ ->
throw_error({type_error, xref_parser:t2s(Expr)})
end;
check_expr(Expr={path, E1, E2}, Table) ->
@@ -330,7 +332,7 @@ check_expr(Expr={path, E1, E2}, Table) ->
end,
E2b = {convert, OType2, Type2, Type1, E2a},
{OType1, NE1} = path_arg(OType1a, E1a),
- NE2 = case {OType1, OType2} of
+ NE2 = case {OType1, OType2} of
{path, edge} -> {convert, OType2, edge_closure, E2b};
{path, edge_closure} when Type1 =:= Type2 -> E2b;
_ -> throw_error({type_error, xref_parser:t2s(Expr)})
@@ -347,7 +349,7 @@ check_expr({regexpr, RExpr, Type0}, _Table) ->
release -> 'R'
end,
Var = {variable, {predef, V}},
- Call = {call, fun(E, V2) -> xref_utils:regexpr(E, V2) end,
+ Call = {call, fun(E, V2) -> xref_utils:regexpr(E, V2) end,
{constants, RExpr}, Var},
{expr, Type, vertex, Call};
check_expr(C={constant, _Type, _OType, _C}, Table) ->
@@ -368,15 +370,15 @@ check_conversion(OType, Type1, Type2, Expr) ->
end.
%% Allowed conversions.
-conversions(_OType, {line, LineType}, {line, LineType}) -> ok;
+conversions(_OType, {line, LineType}, {line, LineType}) -> ok;
conversions(edge, {line, _}, {line, all_line_call}) -> ok;
-conversions(edge, From, {line, Line})
+conversions(edge, From, {line, Line})
when is_atom(From), Line =/= all_line_call -> ok;
conversions(vertex, From, {line, line}) when is_atom(From) -> ok;
conversions(vertex, From, To) when is_atom(From), is_atom(To) -> ok;
conversions(edge, From, To) when is_atom(From), is_atom(To) -> ok;
%% "Extra":
-conversions(edge, {line, Line}, To)
+conversions(edge, {line, Line}, To)
when is_atom(To), Line =/= all_line_call -> ok;
conversions(vertex, {line, line}, To) when is_atom(To) -> ok;
conversions(_OType, _From, _To) -> not_ok.
@@ -399,7 +401,7 @@ ari_op(difference) -> fun(X, Y) -> X - Y end.
restriction(ROp, E1, Type1, NE1, Type2, NE2) ->
{Column, _} = restr_op(ROp),
- case NE1 of
+ case NE1 of
{call, union_of_family, _E} when ROp =:= '|' ->
restriction(Column, Type1, E1, Type2, NE2);
{call, union_of_family, _E} when ROp =:= '||' ->
@@ -455,8 +457,8 @@ check_constants(Cs=[C={constant, Type0, OType, _Con} | Cs1], Table) ->
E = function_vertices_to_family(Type, OType, {constants, S}),
{expr, Type, OType, E};
[{Type1, [C1|_]}, {Type2, [C2|_]} | _] ->
- throw_error({type_mismatch,
- make_vertex(Type1, C1),
+ throw_error({type_mismatch,
+ make_vertex(Type1, C1),
make_vertex(Type2, C2)})
end.
@@ -467,7 +469,7 @@ check_mix([C={constant, Type, OType, _Con} | Cs], Type0, OType, _C0)
check_mix(Cs, Type, OType, C);
check_mix([C | _], _Type0, _OType0, C0) ->
throw_error({type_mismatch, xref_parser:t2s(C0), xref_parser:t2s(C)});
-check_mix([], _Type0, _OType0, _C0) ->
+check_mix([], _Type0, _OType0, _C0) ->
ok.
split(Types, Cs, Table) ->
@@ -478,11 +480,11 @@ split([Type | Types], Vs, AllSoFar, _Type, Table, L) ->
S0 = known_vertices(Type, Vs, Table),
S = difference(S0, AllSoFar),
case is_empty_set(S) of
- true ->
+ true ->
split(Types, Vs, AllSoFar, Type, Table, L);
- false ->
+ false ->
All = union(AllSoFar, S0),
- split(Types, Vs, All, Type, Table,
+ split(Types, Vs, All, Type, Table,
[{Type, to_external(S)} | L])
end;
split([], Vs, All, Type, _Table, L) ->
@@ -491,7 +493,7 @@ split([], Vs, All, Type, _Table, L) ->
[C|_] -> throw_error({unknown_constant, make_vertex(Type, C)})
end.
-make_vertex(Type, C) ->
+make_vertex(Type, C) ->
xref_parser:t2s({constant, Type, vertex, C}).
constant_vertices([{constant, _Type, edge, {A,B}} | Cs], L) ->
@@ -504,7 +506,7 @@ constant_vertices([], L) ->
known_vertices('Fun', Cs, T) ->
M = projection(1, Cs),
F = union_of_family(restriction(fetch_value(v, T), M)),
- intersection(Cs, F);
+ union(bifs(Cs), intersection(Cs, F));
known_vertices('Mod', Cs, T) ->
intersection(Cs, fetch_value('M', T));
known_vertices('App', Cs, T) ->
@@ -512,6 +514,11 @@ known_vertices('App', Cs, T) ->
known_vertices('Rel', Cs, T) ->
intersection(Cs, fetch_value('R', T)).
+bifs(Cs) ->
+ specification({external,
+ fun({M,F,A}) -> xref_utils:is_builtin(M, F, A) end},
+ Cs).
+
function_vertices_to_family(function, vertex, E) ->
{call, partition_family, 1, E};
function_vertices_to_family(_Type, _OType, E) ->
@@ -567,11 +574,11 @@ convert(E, OType, FromType, ToType) ->
general(_ObjectType, FromType, ToType, X) when FromType =:= ToType ->
X;
-general(edge, {line, _LineType}, ToType, LEs) ->
+general(edge, {line, _LineType}, ToType, LEs) ->
VEs = {projection, ?Q({external, fun({V1V2,_Ls}) -> V1V2 end}), LEs},
general(edge, function, ToType, VEs);
general(edge, function, ToType, VEs) ->
- MEs = {projection,
+ MEs = {projection,
?Q({external, fun({{M1,_,_},{M2,_,_}}) -> {M1,M2} end}),
VEs},
general(edge, module, ToType, MEs);
@@ -580,7 +587,7 @@ general(edge, module, ToType, MEs) ->
general(edge, application, ToType, AEs);
general(edge, application, release, AEs) ->
{image, {get, ae}, AEs};
-general(vertex, {line, _LineType}, ToType, L) ->
+general(vertex, {line, _LineType}, ToType, L) ->
V = {partition_family, ?Q(1), {domain, L}},
general(vertex, function, ToType, V);
general(vertex, function, ToType, V) ->
@@ -595,18 +602,18 @@ general(vertex, application, release, A) ->
special(_ObjectType, FromType, ToType, X) when FromType =:= ToType ->
X;
special(edge, {line, _LineType}, {line, all_line_call}, Calls) ->
- {put, ?T(mods),
- {projection,
- ?Q({external, fun({{{M1,_,_},{M2,_,_}},_}) -> {M1,M2} end}),
+ {put, ?T(mods),
+ {projection,
+ ?Q({external, fun({{{M1,_,_},{M2,_,_}},_}) -> {M1,M2} end}),
Calls},
- {put, ?T(def_at),
+ {put, ?T(def_at),
{union, {image, {get, def_at},
- {union, {domain, {get, ?T(mods)}},
+ {union, {domain, {get, ?T(mods)}},
{range, {get, ?T(mods)}}}}},
{fun funs_to_lines/2,
{get, ?T(def_at)}, Calls}}};
special(edge, function, {line, LineType}, VEs) ->
- Var = if
+ Var = if
LineType =:= line -> call_at;
LineType =:= export_call -> e_call_at;
LineType =:= local_call -> l_call_at;
@@ -615,9 +622,9 @@ special(edge, function, {line, LineType}, VEs) ->
line_edges(VEs, Var);
special(edge, module, ToType, MEs) ->
VEs = {image,
- {projection,
+ {projection,
?Q({external, fun(FE={{M1,_,_},{M2,_,_}}) -> {{M1,M2},FE} end}),
- {union,
+ {union,
{image, {get, e},
{projection, ?Q({external, fun({M1,_M2}) -> M1 end}), MEs}}}},
MEs},
@@ -629,7 +636,7 @@ special(edge, release, ToType, REs) ->
AEs = {inverse_image, {get, ae}, REs},
special(edge, application, ToType, AEs);
special(vertex, function, {line, _LineType}, V) ->
- {restriction,
+ {restriction,
{union_of_family, {restriction, {get, def_at}, {domain, V}}},
{union_of_family, V}};
special(vertex, module, ToType, M) ->
@@ -643,15 +650,15 @@ special(vertex, release, ToType, R) ->
special(vertex, application, ToType, A).
line_edges(VEs, CallAt) ->
- {put, ?T(ves), VEs,
- {put, ?T(m1),
- {projection, ?Q({external, fun({{M1,_,_},_}) -> M1 end}),
+ {put, ?T(ves), VEs,
+ {put, ?T(m1),
+ {projection, ?Q({external, fun({{M1,_,_},_}) -> M1 end}),
{get, ?T(ves)}},
{image, {projection, ?Q({external, fun(C={VV,_L}) -> {VV,C} end}),
{union, {image, {get, CallAt}, {get, ?T(m1)}}}},
{get, ?T(ves)}}}}.
-%% {(((v1,l1),(v2,l2)),l) :
+%% {(((v1,l1),(v2,l2)),l) :
%% (v1,l1) in DefAt and (v2,l2) in DefAt and ((v1,v2),L) in CallAt}
funs_to_lines(DefAt, CallAt) ->
T1 = multiple_relative_product({DefAt, DefAt}, projection(1, CallAt)),
@@ -765,7 +772,7 @@ save_vars([], _D, Vs, UVs, L) ->
%% Traverses the expression again, this time using more or less the
%% inverse of the table created by find_nodes. The first time a node
-%% is visited, its children are traversed, the following times a
+%% is visited, its children are traversed, the following times a
%% get instructions are inserted (using the saved value).
make_instructions(N, UserVars, D) ->
{D1, Is0} = make_instrs(N, D, []),
@@ -777,9 +784,9 @@ make_instructions(N, UserVars, D) ->
make_more_instrs([UV | UVs], D, Is) ->
case dict:find(UV, D) of
- error ->
+ error ->
make_more_instrs(UVs, D, Is);
- _Else ->
+ _Else ->
{ND, NIs} = make_instrs(UV, D, Is),
make_more_instrs(UVs, ND, [pop | NIs])
end;
@@ -844,17 +851,17 @@ evaluate([{quote, Val} | P], T, S) ->
evaluate(P, T, [Val | S]);
evaluate([{get, Var} | P], T, S) when is_atom(Var) -> % predefined
Value = fetch_value(Var, T),
- Val = case Value of
+ Val = case Value of
{R, _} -> R; % relation
_ -> Value % simple set
end,
- evaluate(P, T, [Val | S]);
+ evaluate(P, T, [Val | S]);
evaluate([{get, {inverse, Var}} | P], T, S) -> % predefined, inverse
{_, R} = fetch_value(Var, T),
- evaluate(P, T, [R | S]);
+ evaluate(P, T, [R | S]);
evaluate([{get, {user, Var}} | P], T, S) ->
Val = fetch_value(Var, T),
- evaluate(P, T, [Val | S]);
+ evaluate(P, T, [Val | S]);
evaluate([{get, Var} | P], T, S) -> % tmp
evaluate(P, T, [dict:fetch(Var, T) | S]);
evaluate([{save, Var={tmp, _}} | P], T, S=[Val | _]) ->
@@ -862,7 +869,7 @@ evaluate([{save, Var={tmp, _}} | P], T, S=[Val | _]) ->
evaluate(P, dict:store(Var, Val, T1), S);
evaluate([{save, {user, Name}} | P], T, S=[Val | _]) ->
#xref_var{vtype = user, otype = OType, type = Type} = dict:fetch(Name, T),
- NewVar = #xref_var{name = Name, value = Val,
+ NewVar = #xref_var{name = Name, value = Val,
vtype = user, otype = OType, type = Type},
T1 = update_graph_counter(Val, +1, T),
NT = dict:store(Name, NewVar, T1),
@@ -889,7 +896,7 @@ update_graph_counter(Value, Inc, T) ->
error when Inc =:= 1 ->
dict:store(Value, 1, T)
end;
- _EXIT ->
+ _EXIT ->
T
end.
diff --git a/lib/tools/src/xref_reader.erl b/lib/tools/src/xref_reader.erl
index db755c31d8..d22f0df164 100644
--- a/lib/tools/src/xref_reader.erl
+++ b/lib/tools/src/xref_reader.erl
@@ -1,19 +1,19 @@
%%
%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2000-2009. All Rights Reserved.
-%%
+%%
+%% Copyright Ericsson AB 2000-2010. All Rights Reserved.
+%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
-%%
+%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
-%%
+%%
%% %CopyrightEnd%
%%
-module(xref_reader).
@@ -22,7 +22,7 @@
-import(lists, [keysearch/3, member/2, reverse/1]).
--record(xrefr,
+-record(xrefr,
{module=[],
function=[],
def_at=[],
@@ -59,15 +59,15 @@
module(Module, Forms, CollectBuiltins, X, DF) ->
Attrs = [{Attr,V} || {attribute,_Line,Attr,V} <- Forms],
IsAbstract = xref_utils:is_abstract_module(Attrs),
- S = #xrefr{module = Module, builtins_too = CollectBuiltins,
+ S = #xrefr{module = Module, builtins_too = CollectBuiltins,
is_abstr = IsAbstract, x = X, df = DF},
forms(Forms, S).
forms([F | Fs], S) ->
S1 = form(F, S),
forms(Fs, S1);
-forms([], S) ->
- #xrefr{module = M, def_at = DefAt,
+forms([], S) ->
+ #xrefr{module = M, def_at = DefAt,
l_call_at = LCallAt, x_call_at = XCallAt,
el = LC, ex = XC, x = X, df = Depr,
lattrs = AL, xattrs = AX, battrs = B, unresolved = U} = S,
@@ -75,7 +75,7 @@ forms([], S) ->
{ok, M, {DefAt, LCallAt, XCallAt, LC, XC, X, Attrs, Depr}, U}.
form({attribute, Line, xref, Calls}, S) -> % experimental
- #xrefr{module = M, function = Fun,
+ #xrefr{module = M, function = Fun,
lattrs = L, xattrs = X, battrs = B} = S,
attr(Calls, Line, M, Fun, L, X, B, S);
form({attribute, _Line, _Attr, _Val}, S) ->
@@ -110,12 +110,12 @@ clauses([{clause, _Line, _H, G, B} | Cs], FunVars, Matches, S) ->
S2 = expr(B, S1),
S3 = S2#xrefr{funvars = FunVars, matches = Matches},
clauses(Cs, S3);
-clauses([], _FunVars, _Matches, S) ->
+clauses([], _FunVars, _Matches, S) ->
S.
attr([E={From, To} | As], Ln, M, Fun, AL, AX, B, S) ->
case mfa(From, M) of
- {_, _, MFA} when MFA =:= Fun; [] =:= Fun ->
+ {_, _, 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);
@@ -164,7 +164,7 @@ expr({call, Line,
%% Added in R10B-6. M:F/A.
expr({'fun', Line, {function, Mod, Fun, Arity}}, S);
expr({'fun', Line, {function, Mod, Name, Arity}}, S) ->
- %% Added in R10B-6. M:F/A.
+ %% Added in R10B-6. M:F/A.
As = lists:duplicate(Arity, {atom, Line, foo}),
external_call(Mod, Name, As, Line, false, S);
expr({'fun', Line, {function, Name, Arity}, _Extra}, S) ->
@@ -183,7 +183,7 @@ expr({call, Line, {remote, _Line, Mod, Name}, As}, S) ->
expr({call, Line, F, As}, S) ->
external_call(erlang, apply, [F, list2term(As)], Line, true, S);
expr({match, _Line, {var,_,Var}, {'fun', _, {clauses, Cs}, _Extra}}, S) ->
- %% This is what is needed in R7 to avoid warnings for the functions
+ %% This is what is needed in R7 to avoid warnings for the functions
%% that are passed around by the "expansion" of list comprehension.
S1 = S#xrefr{funvars = [Var | S#xrefr.funvars]},
clauses(Cs, S1);
@@ -192,6 +192,14 @@ expr({match, _Line, {var,_,Var}, E}, S) ->
%% Args = [A,B], apply(m, f, Args)
S1 = S#xrefr{matches = [{Var, E} | S#xrefr.matches]},
expr(E, S1);
+expr({op, _Line, 'orelse', Op1, Op2}, S) ->
+ expr([Op1, Op2], S);
+expr({op, _Line, 'andalso', Op1, Op2}, S) ->
+ expr([Op1, Op2], S);
+expr({op, Line, Op, Operand1, Operand2}, S) ->
+ external_call(erlang, Op, [Operand1, Operand2], Line, false, S);
+expr({op, Line, Op, Operand}, S) ->
+ external_call(erlang, Op, [Operand], Line, false, S);
expr(T, S) when is_tuple(T) ->
expr(tuple_to_list(T), S);
expr([E | Es], S) ->
@@ -241,13 +249,13 @@ external_call(Mod, Fun, ArgsList, Line, X, S) ->
_Else -> % apply2, 1 or 2
check_funarg(W, ArgsList, Line, S1)
end.
-
+
eval_args(Mod, Fun, ArgsTerm, Line, S, ArgsList, Extra) ->
{IsSimpleCall, M, F} = mod_fun(Mod, Fun),
case term2list(ArgsTerm, [], S) of
undefined ->
S1 = unresolved(M, F, -1, Line, S),
- expr(ArgsList, S1);
+ expr(ArgsList, S1);
ArgsList2 when not IsSimpleCall ->
S1 = unresolved(M, F, length(ArgsList2), Line, S),
expr(ArgsList, S1);
@@ -288,14 +296,14 @@ fun_args(apply2, [FunArg, Args]) -> {FunArg, Args};
fun_args(1, [FunArg | Args]) -> {FunArg, Args};
fun_args(2, [_Node, FunArg | Args]) -> {FunArg, Args}.
-list2term([A | As]) ->
+list2term([A | As]) ->
{cons, 0, A, list2term(As)};
-list2term([]) ->
+list2term([]) ->
{nil, 0}.
term2list({cons, _Line, H, T}, L, S) ->
term2list(T, [H | L], S);
-term2list({nil, _Line}, L, _S) ->
+term2list({nil, _Line}, L, _S) ->
reverse(L);
term2list({var, _, Var}, L, S) ->
case keysearch(Var, 1, S#xrefr.matches) of
@@ -332,11 +340,11 @@ handle_call(Locality, To0, Line, S, IsUnres) ->
true ->
S
end,
- case Locality of
- local ->
+ case Locality of
+ local ->
S1#xrefr{el = [Call | S1#xrefr.el],
l_call_at = [CallAt | S1#xrefr.l_call_at]};
- external ->
+ external ->
S1#xrefr{ex = [Call | S1#xrefr.ex],
x_call_at = [CallAt | S1#xrefr.x_call_at]}
end.
diff --git a/lib/tools/src/xref_utils.erl b/lib/tools/src/xref_utils.erl
index 0ef199cec7..9d4a175d88 100644
--- a/lib/tools/src/xref_utils.erl
+++ b/lib/tools/src/xref_utils.erl
@@ -18,6 +18,8 @@
%%
-module(xref_utils).
+%% Avoid warning for local function error/1 clashing with autoimported BIF.
+-compile({no_auto_import,[error/1]}).
-export([xset/2]).
-export([is_directory/1, file_info/1, fa_to_mfa/2]).