diff options
Diffstat (limited to 'lib/tools/src')
-rw-r--r-- | lib/tools/src/cover.erl | 585 | ||||
-rw-r--r-- | lib/tools/src/eprof.erl | 757 | ||||
-rw-r--r-- | lib/tools/src/xref_base.erl | 2 | ||||
-rw-r--r-- | lib/tools/src/xref_compiler.erl | 2 | ||||
-rw-r--r-- | lib/tools/src/xref_utils.erl | 2 |
5 files changed, 752 insertions, 596 deletions
diff --git a/lib/tools/src/cover.erl b/lib/tools/src/cover.erl index 6501e05a6e..ada2db45be 100644 --- a/lib/tools/src/cover.erl +++ b/lib/tools/src/cover.erl @@ -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 1656899e8f..93f0e9c0c8 100644 --- a/lib/tools/src/xref_base.erl +++ b/lib/tools/src/xref_base.erl @@ -19,6 +19,8 @@ -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, diff --git a/lib/tools/src/xref_compiler.erl b/lib/tools/src/xref_compiler.erl index c80eb0e669..1445e135be 100644 --- a/lib/tools/src/xref_compiler.erl +++ b/lib/tools/src/xref_compiler.erl @@ -31,6 +31,8 @@ -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]). 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]). |