~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/tools/src/eprof.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
%% Purpose: Profile a system in order to figure out where the 
23
23
-module(eprof).
24
24
-behaviour(gen_server).
25
25
 
26
 
-export([start/0, stop/0, dump/0, total_analyse/0,
27
 
         start_profiling/1, profile/2, profile/4, profile/1,
28
 
         stop_profiling/0, analyse/0, log/1]).
 
26
-export([start/0,
 
27
         stop/0,
 
28
         dump/0,
 
29
         start_profiling/1, start_profiling/2,
 
30
         profile/1, profile/2, profile/3, profile/4, profile/5,
 
31
         stop_profiling/0,
 
32
         analyze/0, analyze/1, analyze/2,
 
33
         log/1]).
29
34
 
30
35
%% Internal exports 
31
36
-export([init/1,
32
 
         call/4,
33
37
         handle_call/3,
34
38
         handle_cast/2,
35
39
         handle_info/2,
36
40
         terminate/2,
37
41
         code_change/3]).
38
 
 
39
 
-include_lib("stdlib/include/qlc.hrl").
40
 
 
41
 
-import(lists, [flatten/1,reverse/1,keysort/2]).
42
 
 
43
 
 
44
 
-record(state, {table = notable,
45
 
                proc = noproc,
46
 
                profiling = false, 
47
 
                pfunc = undefined,
48
 
                pop = running,
49
 
                ptime = 0,
50
 
                overhead = 0,
51
 
                rootset = []}).
52
 
 
53
 
%%%%%%%%%%%%%%
54
 
 
55
 
start() -> gen_server:start({local, eprof}, eprof, [], []).
56
 
stop()  -> gen_server:call(eprof, stop, infinity).
57
 
 
 
42
-record(bpd, {
 
43
        n   = 0,                 % number of total calls
 
44
        us  = 0,                 % sum of uS for all calls
 
45
        p   = gb_trees:empty(),  % tree of {Pid, {Mfa, {Count, Us}}}
 
46
        mfa = []                 % list of {Mfa, {Count, Us}}
 
47
    }).
 
48
 
 
49
-record(state, {
 
50
        profiling = false,
 
51
        pattern   = {'_','_','_'},
 
52
        rootset   = [],
 
53
        fd    = undefined,
 
54
        start_ts  = undefined,
 
55
        reply     = undefined,
 
56
        bpd       = #bpd{}
 
57
    }).
 
58
 
 
59
 
 
60
 
 
61
%% -------------------------------------------------------------------- %%
 
62
%%
 
63
%% API
 
64
%%
 
65
%% -------------------------------------------------------------------- %%
 
66
 
 
67
start() -> gen_server:start({local, ?MODULE}, ?MODULE, [], []).
 
68
stop()  -> gen_server:call(?MODULE, stop, infinity).
 
69
 
 
70
profile(Fun) when is_function(Fun) ->
 
71
    profile([], Fun);
 
72
profile(Rs) when is_list(Rs) ->
 
73
    start_profiling(Rs).
58
74
 
59
75
profile(Pids, Fun) ->
60
 
    start(),
61
 
    gen_server:call(eprof, {profile,Pids,erlang,apply,[Fun,[]]},infinity).
 
76
    profile(Pids, Fun, {'_','_','_'}).
 
77
 
 
78
profile(Pids, Fun, Pattern) ->
 
79
    profile(Pids, erlang, apply, [Fun,[]], Pattern).
62
80
 
63
81
profile(Pids, M, F, A) ->
 
82
    profile(Pids, M, F, A, {'_','_','_'}).
 
83
 
 
84
profile(Pids, M, F, A, Pattern) ->
64
85
    start(),
65
 
    gen_server:call(eprof, {profile,Pids,M,F,A},infinity).
 
86
    gen_server:call(?MODULE, {profile,Pids,Pattern,M,F,A},infinity).
66
87
 
67
88
dump() -> 
68
 
    gen_server:call(eprof, dump, infinity).
69
 
 
70
 
analyse() ->
71
 
    gen_server:call(eprof, analyse, infinity).
 
89
    gen_server:call(?MODULE, dump, infinity).
 
90
 
 
91
analyze() ->
 
92
    analyze(procs).
 
93
 
 
94
analyze(Type) when is_atom(Type) ->
 
95
    analyze(Type, []);
 
96
analyze(Opts) when is_list(Opts) ->
 
97
    analyze(procs, Opts).
 
98
analyze(Type, Opts) when is_list(Opts) ->
 
99
    gen_server:call(?MODULE, {analyze, Type, Opts}, infinity).
72
100
 
73
101
log(File) ->
74
 
    gen_server:call(eprof, {logfile, File}, infinity).
75
 
 
76
 
total_analyse() ->
77
 
    gen_server:call(eprof, total_analyse, infinity).
 
102
    gen_server:call(?MODULE, {logfile, File}, infinity).
78
103
 
79
104
start_profiling(Rootset) ->
 
105
    start_profiling(Rootset, {'_','_','_'}).
 
106
start_profiling(Rootset, Pattern) ->
80
107
    start(),
81
 
    gen_server:call(eprof, {profile, Rootset}, infinity).
 
108
    gen_server:call(?MODULE, {profile, Rootset, Pattern}, infinity).
82
109
 
83
110
stop_profiling() ->
84
 
    gen_server:call(eprof, stop_profiling, infinity).
85
 
 
86
 
profile(Rs) ->
87
 
    start_profiling(Rs).
88
 
 
89
 
%%%%%%%%%%%%%%%%
90
 
 
91
 
init(_) ->
 
111
    gen_server:call(?MODULE, stop_profiling, infinity).
 
112
 
 
113
 
 
114
%% -------------------------------------------------------------------- %%
 
115
%%
 
116
%% init
 
117
%%
 
118
%% -------------------------------------------------------------------- %%
 
119
 
 
120
init([]) ->
92
121
    process_flag(trap_exit, true),
93
 
    process_flag(priority, max),
94
 
    put(three_one, {3,1}),                      %To avoid building garbage.
95
122
    {ok, #state{}}.
96
123
 
97
 
subtr({X1,Y1,Z1}, {X1,Y1,Z2}) ->
98
 
    Z1 - Z2;
99
 
subtr({X1,Y1,Z1}, {X2,Y2,Z2}) ->
100
 
    (((X1-X2) * 1000000) + Y1 - Y2) * 1000000 + Z1 - Z2.
101
 
 
102
 
update_call_statistics(Tab, Key, Time) ->
103
 
    try ets:update_counter(Tab, Key, Time) of
104
 
        NewTime when is_integer(NewTime) ->
105
 
            ets:update_counter(Tab, Key, get(three_one))
106
 
    catch
107
 
        error:badarg ->
108
 
            ets:insert(Tab, {Key,Time,1})
109
 
    end.
110
 
 
111
 
update_other_statistics(Tab, Key, Time) ->
112
 
    try
113
 
        ets:update_counter(Tab, Key, Time)
114
 
    catch
115
 
        error:badarg ->
116
 
            ets:insert(Tab, {Key,Time,0})
117
 
    end.
118
 
 
119
 
do_messages({trace_ts,From,Op,Mfa,Time}, Tab, undefined,_PrevOp0,_PrevTime0) ->
120
 
    PrevFunc = [From|Mfa],
121
 
    receive
122
 
        {trace_ts,_,_,_,_}=Ts -> do_messages(Ts, Tab, PrevFunc, Op, Time)
123
 
    after 0 ->
124
 
            {PrevFunc,Op,Time}
125
 
    end;
126
 
do_messages({trace_ts,From,Op,Mfa,Time}, Tab, PrevFunc0, call, PrevTime0) ->
127
 
    update_call_statistics(Tab, PrevFunc0, subtr(Time, PrevTime0)),
128
 
    PrevFunc = case Op of
129
 
                   exit -> undefined;
130
 
                   out -> undefined;
131
 
                   _ -> [From|Mfa]
132
 
               end,
133
 
    receive
134
 
        {trace_ts,_,_,_,_}=Ts -> do_messages(Ts, Tab, PrevFunc, Op, Time)
135
 
    after 0 ->
136
 
            {PrevFunc,Op,Time}
137
 
    end;
138
 
do_messages({trace_ts,From,Op,Mfa,Time}, Tab, PrevFunc0, _PrevOp0, PrevTime0) ->
139
 
    update_other_statistics(Tab, PrevFunc0, subtr(Time, PrevTime0)),
140
 
    PrevFunc = case Op of
141
 
                   exit -> undefined;
142
 
                   out -> undefined;
143
 
                   _ -> [From|Mfa]
144
 
               end,
145
 
    receive
146
 
        {trace_ts,_,_,_,_}=Ts -> do_messages(Ts, Tab, PrevFunc, Op, Time)
147
 
    after 0 ->
148
 
            {PrevFunc,Op,Time}
149
 
    end.
150
 
 
151
 
%%%%%%%%%%%%%%%%%%
152
 
 
153
 
handle_cast(_Req, S) -> {noreply, S}.
154
 
 
155
 
terminate(_Reason,_S) ->
156
 
    call_trace_for_all(false),
157
 
    normal.
158
 
 
159
 
%%%%%%%%%%%%%%%%%%
160
 
 
161
 
handle_call({logfile, F}, _FromTag, Status) ->
162
 
    case file:open(F, [write]) of
 
124
%% -------------------------------------------------------------------- %%
 
125
%%
 
126
%% handle_call
 
127
%%
 
128
%% -------------------------------------------------------------------- %%
 
129
 
 
130
%% analyze
 
131
 
 
132
handle_call({analyze, _, _}, _, #state{ bpd = #bpd{ p = {0,nil}, us = 0, n = 0} = Bpd } = S) when is_record(Bpd, bpd) ->
 
133
    {reply, nothing_to_analyze, S};
 
134
 
 
135
handle_call({analyze, procs, Opts}, _, #state{ bpd = #bpd{ p = Ps, us = Tus} = Bpd, fd = Fd} = S) when is_record(Bpd, bpd) ->
 
136
    lists:foreach(fun
 
137
            ({Pid, Mfas}) ->
 
138
                {Pn, Pus} =  sum_bp_total_n_us(Mfas),
 
139
                format(Fd, "~n****** Process ~w    -- ~s % of profiled time *** ~n", [Pid, s("~.2f", [100.0*divide(Pus,Tus)])]),
 
140
                print_bp_mfa(Mfas, {Pn,Pus}, Fd, Opts),
 
141
                ok
 
142
        end, gb_trees:to_list(Ps)),
 
143
    {reply, ok, S};
 
144
 
 
145
handle_call({analyze, total, Opts}, _, #state{ bpd = #bpd{ mfa = Mfas, n = Tn, us = Tus} = Bpd, fd = Fd} = S) when is_record(Bpd, bpd) ->
 
146
    print_bp_mfa(Mfas, {Tn, Tus}, Fd, Opts),
 
147
    {reply, ok, S};
 
148
 
 
149
handle_call({analyze, Type, _Opts}, _, S) ->
 
150
    {reply, {error, {undefined, Type}}, S};
 
151
 
 
152
%% profile
 
153
 
 
154
handle_call({profile, _Rootset, _Pattern, _M,_F,_A}, _From, #state{ profiling = true } = S) ->
 
155
    {reply, {error, already_profiling}, S};
 
156
 
 
157
handle_call({profile, Rootset, Pattern, M,F,A}, From, #state{fd = Fd } = S) ->
 
158
 
 
159
    set_pattern_trace(false, S#state.pattern),
 
160
    set_process_trace(false, S#state.rootset),
 
161
 
 
162
    Pid = setup_profiling(M,F,A),
 
163
    case set_process_trace(true, [Pid|Rootset]) of
 
164
        true ->
 
165
            set_pattern_trace(true, Pattern),
 
166
            T0 = now(),
 
167
            execute_profiling(Pid),
 
168
            {noreply, #state{
 
169
                    profiling = true,
 
170
                    rootset   = [Pid|Rootset],
 
171
                    start_ts  = T0,
 
172
                    reply     = From,
 
173
                    fd        = Fd,
 
174
                    pattern   = Pattern
 
175
                }};
 
176
        false ->
 
177
            exit(Pid, eprof_kill),
 
178
            {reply, error, #state{ fd = Fd}}
 
179
    end;
 
180
 
 
181
handle_call({profile, _Rootset, _Pattern}, _From, #state{ profiling = true } = S) ->
 
182
    {reply, {error, already_profiling}, S};
 
183
 
 
184
handle_call({profile, Rootset, Pattern}, From, #state{ fd = Fd } = S) ->
 
185
 
 
186
    set_pattern_trace(false, S#state.pattern),
 
187
    set_process_trace(false, S#state.rootset),
 
188
 
 
189
    case set_process_trace(true, Rootset) of
 
190
        true ->
 
191
            T0 = now(),
 
192
            set_pattern_trace(true, Pattern),
 
193
            {reply, profiling, #state{
 
194
                    profiling = true,
 
195
                    rootset   = Rootset,
 
196
                    start_ts  = T0,
 
197
                    reply     = From,
 
198
                    fd        = Fd,
 
199
                    pattern   = Pattern
 
200
                }};
 
201
        false ->
 
202
            {reply, error, #state{ fd = Fd }}
 
203
    end;
 
204
 
 
205
handle_call(stop_profiling, _From, #state{ profiling = false } = S) ->
 
206
    {reply, profiling_already_stopped, S};
 
207
 
 
208
handle_call(stop_profiling, _From, #state{ profiling = true } = S) ->
 
209
 
 
210
    set_pattern_trace(pause, S#state.pattern),
 
211
 
 
212
    Bpd = collect_bpd(),
 
213
 
 
214
    set_process_trace(false, S#state.rootset),
 
215
    set_pattern_trace(false, S#state.pattern),
 
216
 
 
217
    {reply, profiling_stopped, S#state{
 
218
        profiling = false,
 
219
        rootset   = [],
 
220
        pattern   = {'_','_','_'},
 
221
        bpd       = Bpd
 
222
    }};
 
223
 
 
224
%% logfile
 
225
handle_call({logfile, File}, _From, #state{ fd = OldFd } = S) ->
 
226
    case file:open(File, [write]) of
163
227
        {ok, Fd} ->
164
 
            case get(fd) of
 
228
            case OldFd of
165
229
                undefined -> ok;
166
 
                FdOld -> file:close(FdOld)
 
230
                OldFd -> file:close(OldFd)
167
231
            end,
168
 
            put(fd, Fd),
169
 
            {reply, ok, Status};
170
 
        {error, _} ->
171
 
            {reply, error, Status}
172
 
    end;
173
 
 
174
 
handle_call({profile, Rootset}, {From, _Tag}, S) ->
175
 
    link(From),
176
 
    maybe_delete(S#state.table),
177
 
    io:format("eprof: Starting profiling ..... ~n",[]),
178
 
    ptrac(S#state.rootset, false, all()),
179
 
    flush_receive(),
180
 
    Tab = ets:new(eprof, [set, public]),
181
 
    case ptrac(Rootset, true, all()) of
182
 
        false ->
183
 
            {reply, error,  #state{}};
184
 
        true ->
185
 
            uni_schedule(),
186
 
            call_trace_for_all(true),
187
 
            erase(replyto),
188
 
            {reply, profiling, #state{table = Tab,
189
 
                                      proc = From,
190
 
                                      profiling = true,
191
 
                                      rootset = Rootset}}
192
 
    end;
193
 
 
194
 
handle_call(stop_profiling, _FromTag, S) when S#state.profiling ->
195
 
    ptrac(S#state.rootset, false, all()),
196
 
    call_trace_for_all(false),
197
 
    multi_schedule(),
198
 
    io:format("eprof: Stop profiling~n",[]),
199
 
    ets:delete(S#state.table, nofunc),
200
 
    {reply, profiling_stopped, S#state{profiling = false}};
201
 
 
202
 
handle_call(stop_profiling, _FromTag, S) ->
203
 
    {reply, profiling_already_stopped, S};
204
 
 
205
 
handle_call({profile, Rootset, M, F, A}, FromTag, S) ->
206
 
    io:format("eprof: Starting profiling..... ~n", []),
207
 
    maybe_delete(S#state.table),
208
 
    ptrac(S#state.rootset, false, all()),
209
 
    flush_receive(),
210
 
    put(replyto, FromTag),
211
 
    Tab = ets:new(eprof, [set, public]),
212
 
    P = spawn_link(eprof, call, [self(), M, F, A]),
213
 
    case ptrac([P|Rootset], true, all()) of
214
 
        true ->
215
 
            uni_schedule(),
216
 
            call_trace_for_all(true),
217
 
            P ! {self(),go},
218
 
            {noreply, #state{table     = Tab, 
219
 
                             profiling = true,
220
 
                             rootset   = [P|Rootset]}};
221
 
        false ->
222
 
            exit(P, kill),
223
 
            erase(replyto),
224
 
            {reply, error, #state{}}
225
 
    end;
226
 
 
227
 
handle_call(dump, _FromTag, S) ->
228
 
    {reply, dump(S#state.table), S};
229
 
 
230
 
handle_call(analyse, _FromTag, S) ->
231
 
    {reply, analyse(S), S};
232
 
 
233
 
handle_call(total_analyse, _FromTag, S) ->
234
 
    {reply, total_analyse(S), S};
 
232
            {reply, ok, S#state{ fd = Fd}};
 
233
        Error ->
 
234
            {reply, Error, S}
 
235
    end;
 
236
 
 
237
handle_call(dump, _From, #state{ bpd = Bpd } = S) when is_record(Bpd, bpd) ->
 
238
    {reply, gb_trees:to_list(Bpd#bpd.p), S};
235
239
 
236
240
handle_call(stop, _FromTag, S) ->
237
 
    multi_schedule(),
238
241
    {stop, normal, stopped, S}.
239
242
 
240
 
%%%%%%%%%%%%%%%%%%%
241
 
 
242
 
handle_info({trace_ts,_From,_Op,_Func,_Time}=M, S0) when S0#state.profiling ->
243
 
    Start = erlang:now(),
244
 
    #state{table=Tab,pop=PrevOp0,ptime=PrevTime0,pfunc=PrevFunc0,
245
 
           overhead=Overhead0} = S0,
246
 
    {PrevFunc,PrevOp,PrevTime} = do_messages(M, Tab, PrevFunc0, PrevOp0, PrevTime0),
247
 
    Overhead = Overhead0 + subtr(erlang:now(), Start),
248
 
    S = S0#state{overhead=Overhead,pfunc=PrevFunc,pop=PrevOp,ptime=PrevTime},
249
 
    {noreply,S};
250
 
 
251
 
handle_info({trace_ts, From, _, _, _}, S) when not S#state.profiling ->
252
 
    ptrac([From], false, all()),
253
 
    {noreply, S};
254
 
 
255
 
handle_info({_P, {answer, A}}, S) ->
256
 
    ptrac(S#state.rootset, false, all()),
257
 
    io:format("eprof: Stop profiling~n",[]),
258
 
    {From,_Tag} = get(replyto),
 
243
%% -------------------------------------------------------------------- %%
 
244
%%
 
245
%% handle_cast
 
246
%%
 
247
%% -------------------------------------------------------------------- %%
 
248
 
 
249
handle_cast(_Msg, State) ->
 
250
    {noreply, State}.
 
251
 
 
252
%% -------------------------------------------------------------------- %%
 
253
%%
 
254
%% handle_info
 
255
%%
 
256
%% -------------------------------------------------------------------- %%
 
257
 
 
258
handle_info({'EXIT', _, normal}, S) ->
 
259
    {noreply, S};
 
260
handle_info({'EXIT', _, eprof_kill}, S) ->
 
261
    {noreply, S};
 
262
handle_info({'EXIT', _, Reason}, #state{ reply = FromTag } = S) ->
 
263
 
 
264
    set_process_trace(false, S#state.rootset),
 
265
    set_pattern_trace(false, S#state.pattern),
 
266
 
 
267
    gen_server:reply(FromTag, {error, Reason}),
 
268
    {noreply, S#state{
 
269
        profiling = false,
 
270
        rootset   = [],
 
271
        pattern   = {'_','_','_'}
 
272
    }};
 
273
 
 
274
% check if Pid is spawned process?
 
275
handle_info({_Pid, {answer, Result}}, #state{ reply = {From,_} = FromTag} = S) ->
 
276
 
 
277
    set_pattern_trace(pause, S#state.pattern),
 
278
 
 
279
    Bpd = collect_bpd(),
 
280
 
 
281
    set_process_trace(false, S#state.rootset),
 
282
    set_pattern_trace(false, S#state.pattern),
 
283
 
259
284
    catch unlink(From),
260
 
    ets:delete(S#state.table, nofunc),
261
 
    gen_server:reply(erase(replyto), {ok, A}),
262
 
    multi_schedule(),
263
 
    {noreply, S#state{profiling = false,
264
 
                      rootset = []}};
265
 
 
266
 
handle_info({'EXIT', P, Reason},
267
 
            #state{profiling=true,proc=P,table=T,rootset=RootSet}) ->
268
 
    maybe_delete(T),
269
 
    ptrac(RootSet, false, all()),
270
 
    multi_schedule(),
271
 
    io:format("eprof: Profiling failed\n",[]),
272
 
    case erase(replyto) of
 
285
    gen_server:reply(FromTag, {ok, Result}),
 
286
    {noreply, S#state{
 
287
        profiling = false,
 
288
        rootset   = [],
 
289
        pattern   = {'_','_','_'},
 
290
        bpd       = Bpd
 
291
    }}.
 
292
 
 
293
%% -------------------------------------------------------------------- %%
 
294
%%
 
295
%% termination
 
296
%%
 
297
%% -------------------------------------------------------------------- %%
 
298
 
 
299
terminate(_Reason, #state{ fd = undefined }) ->
 
300
    set_pattern_trace(false, {'_','_','_'}),
 
301
    ok;
 
302
terminate(_Reason, #state{ fd = Fd }) ->
 
303
    file:close(Fd),
 
304
    set_pattern_trace(false, {'_','_','_'}),
 
305
    ok.
 
306
 
 
307
%% -------------------------------------------------------------------- %%
 
308
%%
 
309
%% code_change
 
310
%%
 
311
%% -------------------------------------------------------------------- %%
 
312
 
 
313
code_change(_OldVsn, State, _Extra) ->
 
314
    {ok, State}.
 
315
 
 
316
 
 
317
%% -------------------------------------------------------------------- %%
 
318
%%
 
319
%% AUX Functions
 
320
%%
 
321
%% -------------------------------------------------------------------- %%
 
322
 
 
323
setup_profiling(M,F,A) ->
 
324
    spawn_link(fun() -> spin_profile(M,F,A) end).
 
325
 
 
326
spin_profile(M, F, A) ->
 
327
    receive
 
328
        {Pid, execute} ->
 
329
            Pid ! {self(), {answer, erlang:apply(M,F,A)}}
 
330
    end.
 
331
 
 
332
execute_profiling(Pid) ->
 
333
    Pid ! {self(), execute}.
 
334
 
 
335
set_pattern_trace(Flag, Pattern) ->
 
336
    erlang:system_flag(multi_scheduling, block),
 
337
    erlang:trace_pattern(on_load, Flag, [call_time]),
 
338
    erlang:trace_pattern(Pattern, Flag, [call_time]),
 
339
    erlang:system_flag(multi_scheduling, unblock),
 
340
    ok.
 
341
 
 
342
set_process_trace(Flag, Pids) ->
 
343
    % do we need procs for meta info?
 
344
    % could be useful
 
345
    set_process_trace(Flag, Pids, [call, set_on_spawn]).
 
346
set_process_trace(_, [], _) -> true;
 
347
set_process_trace(Flag, [Pid|Pids], Options) when is_pid(Pid) ->
 
348
    try
 
349
        erlang:trace(Pid, Flag, Options),
 
350
        set_process_trace(Flag, Pids, Options)
 
351
    catch
 
352
        _:_ ->
 
353
            false
 
354
    end;
 
355
set_process_trace(Flag, [Name|Pids], Options) when is_atom(Name) ->
 
356
    case whereis(Name) of
273
357
        undefined ->
274
 
            {noreply, #state{}};
275
 
        FromTag ->
276
 
            gen_server:reply(FromTag, {error, Reason}),
277
 
            {noreply, #state{}}
278
 
    end;
279
 
 
280
 
handle_info({'EXIT',_P,_Reason}, S) ->
281
 
    {noreply, S}.
282
 
 
283
 
uni_schedule() ->
284
 
    erlang:system_flag(multi_scheduling, block).
285
 
 
286
 
multi_schedule() ->
287
 
    erlang:system_flag(multi_scheduling, unblock).
288
 
 
289
 
%%%%%%%%%%%%%%%%%%
290
 
 
291
 
call(Top, M, F, A) ->
292
 
    receive
293
 
        {Top,go} ->
294
 
            Top ! {self(), {answer, apply(M,F,A)}}
295
 
    end.
296
 
 
297
 
call_trace_for_all(Flag) ->
298
 
    erlang:trace_pattern(on_load, Flag, [local]),
299
 
    erlang:trace_pattern({'_','_','_'}, Flag, [local]).
300
 
 
301
 
ptrac([P|T], How, Flags) when is_pid(P) ->
302
 
    case dotrace(P, How, Flags) of
303
 
        true ->
304
 
            ptrac(T, How, Flags);
305
 
        false when How ->
306
 
            false;
307
 
        false ->
308
 
            ptrac(T, How, Flags)
309
 
    end;
310
 
 
311
 
ptrac([P|T], How, Flags) when is_atom(P) ->
312
 
    case whereis(P) of
313
 
        undefined when How ->
314
 
            false;
315
 
        undefined when not How ->
316
 
            ptrac(T, How, Flags);
 
358
            set_process_trace(Flag, Pids, Options);
317
359
        Pid ->
318
 
            ptrac([Pid|T], How, Flags)
319
 
    end;
320
 
 
321
 
ptrac([H|_],_How,_Flags) ->
322
 
    io:format("** eprof bad process ~w~n",[H]),
323
 
    false;
324
 
 
325
 
ptrac([],_,_) -> true.
326
 
 
327
 
dotrace(P, How, What) ->
328
 
    case (catch erlang:trace(P, How, What)) of
329
 
        1 ->
330
 
            true;
331
 
        _Other when not How ->
332
 
            true;
333
 
        _Other ->
334
 
            io:format("** eprof: bad process: ~p,~p,~p~n", [P,How,What]),
335
 
            false
336
 
    end.
337
 
 
338
 
all() -> [call,arity,return_to,running,timestamp,set_on_spawn].
339
 
 
340
 
total_analyse(#state{table=notable}) ->
341
 
    nothing_to_analyse;
342
 
total_analyse(S) ->
343
 
    #state{table = T, overhead = Overhead} = S,
344
 
    QH = qlc:q([{{From,Mfa},Time,Count} ||
345
 
                   {[From|Mfa],Time,Count} <- ets:table(T)]),
346
 
    Pcalls = reverse(keysort(2, replicas(qlc:eval(QH)))),
347
 
    Time = collect_times(Pcalls),
348
 
    format("FUNCTION~44s      TIME ~n", ["CALLS"]),   
349
 
    printit(Pcalls, Time),
350
 
    format("\nTotal time: ~.2f\n", [Time / 1000000]),
351
 
    format("Measurement overhead: ~.2f\n", [Overhead / 1000000]).
352
 
 
353
 
analyse(#state{table=notable}) ->
354
 
    nothing_to_analyse;
355
 
analyse(S) ->
356
 
    #state{table = T, overhead = Overhead} = S,
357
 
    Pids = ordsets:from_list(flatten(ets:match(T, {['$1'|'_'],'_', '_'}))),
358
 
    Times = sum(ets:match(T, {'_','$1', '_'})),
359
 
    format("FUNCTION~44s      TIME ~n", ["CALLS"]),     
360
 
    do_pids(Pids, T, 0, Times),
361
 
    format("\nTotal time: ~.2f\n", [Times / 1000000]),
362
 
    format("Measurement overhead: ~.2f\n", [Overhead / 1000000]).
363
 
 
364
 
do_pids([Pid|Tail], T, AckTime, Total) ->
365
 
    Pcalls = 
366
 
     reverse(keysort(2, to_tups(ets:match(T, {[Pid|'$1'], '$2','$3'})))),
367
 
    Time = collect_times(Pcalls),
368
 
    PercentTotal = 100 * (divide(Time, Total)),
369
 
    format("~n****** Process ~w    -- ~s % of profiled time *** ~n", 
370
 
           [Pid, fpf(PercentTotal)]),
371
 
    printit(Pcalls, Time),
372
 
    do_pids(Tail, T, AckTime + Time, Total);
373
 
do_pids([], _, _, _) -> 
374
 
    ok.
375
 
 
376
 
printit([],_) -> ok;
377
 
printit([{{Mod,Fun,Arity}, Time, Calls} |Tail], ProcTime)  ->
378
 
    format("~s  ~s ~s % ~n", [ff(Mod,Fun,Arity), fint(Calls),
379
 
                              fpf(100*(divide(Time,ProcTime)))]),
380
 
    printit(Tail, ProcTime);
381
 
printit([{{_,{Mod,Fun,Arity}}, Time, Calls} |Tail], ProcTime)  ->
382
 
    format("~s  ~s ~s % ~n", [ff(Mod,Fun,Arity), fint(Calls),
383
 
                              fpf(100*(divide(Time,ProcTime)))]),
384
 
    printit(Tail, ProcTime); 
385
 
printit([_|T], Time) ->
386
 
    printit(T, Time).
387
 
 
388
 
ff(Mod,Fun,Arity) ->
389
 
    pad(flatten(io_lib:format("~w:~w/~w", [Mod,Fun, Arity])),45).
390
 
 
391
 
pad(Str, Len) -> 
392
 
    Strlen = length(Str),
393
 
    if
394
 
        Strlen > Len -> strip_tail(Str, 45);
395
 
        true -> lists:append(Str, mklist(Len-Strlen))
396
 
    end.
397
 
 
398
 
strip_tail([_|_], 0) ->[];
399
 
strip_tail([H|T], I) -> [H|strip_tail(T, I-1)];
400
 
strip_tail([],_I) -> [].
401
 
 
402
 
fpf(F) -> strip_tail(flatten(io_lib:format("~w", [round(F)])), 5).
403
 
fint(Int) -> pad(flatten(io_lib:format("~w",[Int])), 10).
404
 
 
405
 
mklist(0) -> [];
406
 
mklist(I) -> [$ |mklist(I-1)].
407
 
 
408
 
to_tups(L) -> lists:map(fun(List) -> erlang:list_to_tuple(List) end, L).
409
 
 
410
 
divide(X,Y) -> X / Y.
411
 
 
412
 
collect_times([]) -> 0;
413
 
collect_times([Tup|Tail]) -> element(2, Tup) + collect_times(Tail).
414
 
 
415
 
dump(T) ->
416
 
    L = ets:tab2list(T),
417
 
    format(L).
418
 
 
419
 
format([H|T]) -> 
420
 
    format("~p~n", [H]), format(T);
421
 
format([]) -> ok.
422
 
 
423
 
format(F, A) ->
424
 
    io:format(F,A),
425
 
    case get(fd) of
426
 
        undefined -> ok;
427
 
        Fd -> io:format(Fd, F,A)
428
 
    end.
429
 
 
430
 
maybe_delete(T) ->
431
 
    catch ets:delete(T).
432
 
 
433
 
sum([[H]|T]) -> H + sum(T);
434
 
sum([]) -> 0.
435
 
 
436
 
replicas(L) ->
437
 
    replicas(L, []).
438
 
 
439
 
replicas([{{Pid, {Mod,Fun,Arity}}, Ack,Calls} |Tail], Result) ->
440
 
    case search({Mod,Fun,Arity},Result) of
441
 
        false ->
442
 
            replicas(Tail, [{{Pid, {Mod,Fun,Arity}}, Ack,Calls} |Result]);
443
 
        {Ack2, Calls2} ->
444
 
            Result2 = del({Mod,Fun,Arity}, Result),
445
 
            replicas(Tail, [{{Pid, {Mod,Fun,Arity}}, 
446
 
                             Ack+Ack2,Calls+Calls2} |Result2])
447
 
    end;
448
 
 
449
 
replicas([_|T], Ack) ->  %% Whimpy
450
 
    replicas(T, Ack);
451
 
 
452
 
replicas([], Res) -> Res.
453
 
 
454
 
search(Key, [{{_,Key}, Ack, Calls}|_]) -> 
455
 
    {Ack, Calls};
456
 
search(Key, [_|T]) -> 
457
 
    search(Key, T);
458
 
search(_Key,[]) -> false.
459
 
 
460
 
del(Key, [{{_,Key},_Ack,_Calls}|T]) ->
461
 
    T;
462
 
del(Key, [H | Tail]) ->
463
 
    [H|del(Key, Tail)];
464
 
del(_Key,[]) -> [].
465
 
 
466
 
flush_receive() ->
467
 
    receive 
468
 
        {trace_ts, From, _, _, _} when is_pid(From) ->
469
 
            ptrac([From], false, all()),
470
 
            flush_receive();
471
 
        _ ->
472
 
            flush_receive()
473
 
    after 0 ->
474
 
            ok
475
 
    end.
476
 
 
477
 
code_change(_OldVsn, State, _Extra) ->
478
 
    {ok,State}.
 
360
            set_process_trace(Flag, [Pid|Pids], Options)
 
361
    end.
 
362
 
 
363
collect_bpd() ->
 
364
    collect_bpd([M || M <- [element(1, Mi) || Mi <- code:all_loaded()], M =/= ?MODULE]).
 
365
 
 
366
collect_bpd(Ms) when is_list(Ms) ->
 
367
    collect_bpdf(collect_mfas(Ms) ++ erlang:system_info(snifs)).
 
368
 
 
369
collect_mfas(Ms) ->
 
370
    lists:foldl(fun
 
371
            (M, Mfas) ->
 
372
                Mfas ++ [{M, F, A} || {F, A} <- M:module_info(functions)]
 
373
        end, [], Ms).
 
374
 
 
375
collect_bpdf(Mfas) ->
 
376
    collect_bpdf(Mfas, #bpd{}).
 
377
collect_bpdf([], Bpd) ->
 
378
    Bpd;
 
379
collect_bpdf([Mfa|Mfas], #bpd{n = N, us = Us, p = Tree, mfa = Code } = Bpd) ->
 
380
    case erlang:trace_info(Mfa, call_time) of
 
381
        {call_time, []} ->
 
382
            collect_bpdf(Mfas, Bpd);
 
383
        {call_time, Data} when is_list(Data) ->
 
384
            {CTn, CTus, CTree} = collect_bpdfp(Mfa, Tree, Data),
 
385
            collect_bpdf(Mfas, Bpd#bpd{
 
386
                    n   = CTn  + N,
 
387
                    us  = CTus + Us,
 
388
                    p   = CTree,
 
389
                    mfa = [{Mfa, {CTn, CTus}}|Code]
 
390
                });
 
391
        {call_time, false} ->
 
392
            collect_bpdf(Mfas, Bpd);
 
393
        {call_time, _Other} ->
 
394
            collect_bpdf(Mfas, Bpd)
 
395
    end.
 
396
 
 
397
collect_bpdfp(Mfa, Tree, Data) ->
 
398
     lists:foldl(fun
 
399
        ({Pid, Ni, Si, Usi}, {PTno, PTuso, To}) ->
 
400
            Time = Si * 1000000 + Usi,
 
401
            Ti1  = case gb_trees:lookup(Pid, To) of
 
402
                none ->
 
403
                    gb_trees:enter(Pid, [{Mfa, {Ni, Time}}], To);
 
404
                {value, Pmfas} ->
 
405
                    gb_trees:enter(Pid, [{Mfa, {Ni, Time}}|Pmfas], To)
 
406
            end,
 
407
            {PTno + Ni, PTuso + Time, Ti1}
 
408
    end, {0,0, Tree}, Data).
 
409
 
 
410
%% manipulators
 
411
sort_mfa(Bpfs, mfa) when is_list(Bpfs) ->
 
412
    lists:sort(fun
 
413
            ({A,_}, {B,_}) when A < B -> true;
 
414
            (_, _) -> false
 
415
        end, Bpfs);
 
416
sort_mfa(Bpfs, time) when is_list(Bpfs) ->
 
417
    lists:sort(fun
 
418
            ({_,{_,A}}, {_,{_,B}}) when A < B -> true;
 
419
            (_, _) -> false
 
420
        end, Bpfs);
 
421
sort_mfa(Bpfs, calls) when is_list(Bpfs) ->
 
422
    lists:sort(fun
 
423
            ({_,{A,_}}, {_,{B,_}}) when A < B -> true;
 
424
            (_, _) -> false
 
425
        end, Bpfs);
 
426
sort_mfa(Bpfs, _) when is_list(Bpfs) -> sort_mfa(Bpfs, time).
 
427
 
 
428
filter_mfa(Bpfs, Ts) when is_list(Ts) ->
 
429
    filter_mfa(Bpfs, [], proplists:get_value(calls, Ts, 0), proplists:get_value(time, Ts, 0));
 
430
filter_mfa(Bpfs, _) -> Bpfs.
 
431
filter_mfa([], Out, _, _) -> lists:reverse(Out);
 
432
filter_mfa([{_, {C, T}}=Bpf|Bpfs], Out, Ct, Tt) when C >= Ct, T >= Tt -> filter_mfa(Bpfs, [Bpf|Out], Ct, Tt);
 
433
filter_mfa([_|Bpfs], Out, Ct, Tt) -> filter_mfa(Bpfs, Out, Ct, Tt).
 
434
 
 
435
sum_bp_total_n_us(Mfas) ->
 
436
    lists:foldl(fun ({_, {Ci,Usi}}, {Co, Uso}) -> {Co + Ci, Uso + Usi} end, {0,0}, Mfas).
 
437
 
 
438
%% strings and format
 
439
 
 
440
string_bp_mfa(Mfas, Tus) -> string_bp_mfa(Mfas, Tus, {0,0,0,0,0}, []).
 
441
string_bp_mfa([], _, Ws, Strings) -> {Ws, lists:reverse(Strings)};
 
442
string_bp_mfa([{Mfa, {Count, Time}}|Mfas], Tus, {MfaW, CountW, PercW, TimeW, TpCW}, Strings) ->
 
443
        Smfa   = s(Mfa),
 
444
        Scount = s(Count),
 
445
        Stime  = s(Time),
 
446
        Sperc  = s("~.2f", [100*divide(Time,Tus)]),
 
447
        Stpc   = s("~.2f", [divide(Time,Count)]),
 
448
 
 
449
        string_bp_mfa(Mfas, Tus, {
 
450
                erlang:max(MfaW,  length(Smfa)),
 
451
                erlang:max(CountW,length(Scount)),
 
452
                erlang:max(PercW, length(Sperc)),
 
453
                erlang:max(TimeW, length(Stime)),
 
454
                erlang:max(TpCW,  length(Stpc))
 
455
            }, [[Smfa, Scount, Sperc, Stime, Stpc] | Strings]).
 
456
 
 
457
print_bp_mfa(Mfas, {_Tn, Tus}, Fd, Opts) ->
 
458
    Fmfas = filter_mfa(sort_mfa(Mfas, proplists:get_value(sort, Opts)), proplists:get_value(filter, Opts)),
 
459
    {{MfaW, CountW, PercW, TimeW, TpCW}, Strs} = string_bp_mfa(Fmfas, Tus),
 
460
    Ws = {
 
461
        erlang:max(length("FUNCTION"), MfaW),
 
462
        erlang:max(length("CALLS"), CountW),
 
463
        erlang:max(length("  %"), PercW),
 
464
        erlang:max(length("TIME"), TimeW),
 
465
        erlang:max(length("uS / CALLS"), TpCW)
 
466
    },
 
467
    format(Fd, Ws, ["FUNCTION", "CALLS", "  %", "TIME", "uS / CALLS"]),
 
468
    format(Fd, Ws, ["--------", "-----", "---", "----", "----------"]),
 
469
 
 
470
    lists:foreach(fun (String) -> format(Fd, Ws, String) end, Strs),
 
471
    ok.
 
472
 
 
473
s({M,F,A}) -> s("~w:~w/~w",[M,F,A]);
 
474
s(Term) -> s("~p", [Term]).
 
475
s(Format, Terms) -> lists:flatten(io_lib:format(Format, Terms)).
 
476
 
 
477
 
 
478
format(Fd, {MfaW, CountW, PercW, TimeW, TpCW}, Strings) ->
 
479
    format(Fd, s("~~.~ps  ~~~ps  ~~~ps  ~~~ps  [~~~ps]~~n", [MfaW, CountW, PercW, TimeW, TpCW]), Strings);
 
480
format(undefined, Format, Strings) ->
 
481
    io:format(Format, Strings),
 
482
    ok;
 
483
format(Fd, Format, Strings) ->
 
484
    io:format(Fd, Format, Strings),
 
485
    io:format(Format, Strings),
 
486
    ok.
 
487
 
 
488
divide(_,0) -> 0.0;
 
489
divide(T,N) -> T/N.