~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/runtime_tools/src/inviso_rt_meta.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
2
 
%% Version 1.1, (the "License"); you may not use this file except in
3
 
%% compliance with the License. You should have received a copy of the
4
 
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
6
 
%% 
7
 
%% Software distributed under the License is distributed on an "AS IS"
8
 
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
 
%% the License for the specific language governing rights and limitations
10
 
%% under the License.
11
 
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
17
 
%%
18
 
%% Author: Lennart �hman, lennart.ohman@st.se
19
 
%%
20
 
%% This module implements the meta tracer process belonging to the
21
 
%% runtime component. Its main purpose is to write the ti-file (traceinformation).
22
 
%% The ti-file contains translations between process id:s and what ever "you"
23
 
%% want to read in the merged and formatted logfile.
24
 
%% This process interacts with the runtime component process.
25
 
%%
26
 
%% Currently it handles the following types of ti-files:
27
 
%%   Plain raw, binary log.
28
 
%%   Relay to other inviso_rt_meta process on another node.
29
 
%%
30
 
%% The TI file will be on binary format and each entry is:
31
 
%%   <<LengthIndicator:32, {Pid,Alias,Op,NowStamp} >>
32
 
%%       Pid=pid(), or if OP==unalias pid()|any_other_than_pid()
33
 
%%       Op=alias|unalias
34
 
%% -----------------------------------------------------------------------------
35
 
-module(inviso_rt_meta).
36
 
 
37
 
%% -----------------------------------------------------------------------------
38
 
%% API exports.
39
 
%% -----------------------------------------------------------------------------
40
 
 
41
 
-export([start/2,start/5]).
42
 
-export([stop/1,suspend/1]).
43
 
-export([init_tpm/5,init_tpm/8]).
44
 
-export([tpm/5,tpm/6,tpm/9,tpm_tracer/5,tpm_tracer/6,tpm_tracer/9]).
45
 
-export([tpm_ms/6,tpm_ms_tracer/6,ctpm_ms/5,ctpm/4]).
46
 
-export([local_register/1,global_register/1]).
47
 
-export([remove_local_register/1,remove_global_register/1]).
48
 
 
49
 
-export([write_ti/1]).
50
 
 
51
 
-export([get_tracer/0,tpm_ms/5,tpm_ms_tracer/5,list_tpm_ms/3,ctpm_ms/4]).
52
 
 
53
 
-export([metacast_call/5,metacast_return_from/6]).
54
 
-export([get_state/1]).
55
 
%% -----------------------------------------------------------------------------
56
 
 
57
 
%% -----------------------------------------------------------------------------
58
 
%% Internal exports.
59
 
%% -----------------------------------------------------------------------------
60
 
 
61
 
-export([init/6]).
62
 
-export([init_std_publld/2,clean_std_publld/1]).
63
 
%% -----------------------------------------------------------------------------
64
 
 
65
 
%% -----------------------------------------------------------------------------
66
 
%% Constants.
67
 
%% -----------------------------------------------------------------------------
68
 
 
69
 
-define(NAMED_MS_TAB,inviso_rt_meta_named_ms).
70
 
 
71
 
%% -----------------------------------------------------------------------------
72
 
 
73
 
 
74
 
%% =============================================================================
75
 
%% Exported API (Meant to be used by a runtime component).
76
 
%% =============================================================================
77
 
 
78
 
%% start(TiData,Tracer)={ok,Pid} | {error,Reason}
79
 
%% start(TiData,Tracer,InitPublLDmfa,RemovePublLDmfa,CleanPublLDmf)=
80
 
%%     {ok,Pid} | {error,Reason}
81
 
%%   TiData={file,FileName}|{relay,Node}
82
 
%%   Tracer=pid()|port()
83
 
%%   FileName=string()
84
 
%%   InitPublLDmfa={Mod,Func,ArgList}
85
 
%%   RemovePublLDmf={Mod,Func} | void
86
 
%%     RemovePublLDmf(PublLD)->nothing significant.
87
 
%%     These functions are called to create and destroy the public loopdata
88
 
%%     structure available to the meta-trace CallFunc and ReturnFunc.
89
 
%%   CleanPublLDmf={Mod,Func}
90
 
%%     This function will periodically be called to clean the public LD from
91
 
%%     pending meta-trace messages waiting for a corresponding return_from
92
 
%%     message.
93
 
%%
94
 
%% Starts a meta-tracer process, opening the ti-file specified in TiData. PublLD
95
 
%% is used to communicate data, typically between a call and return_from.
96
 
%% If no special initialization function is specified a standard one is used.
97
 
%% Note that the meta tracer function must know "who" is the regular tracer
98
 
%% (process or port). This because it must be possible to append {tracer,Tracer}
99
 
%% in meta match specs.
100
 
start(TiData,Tracer) ->
101
 
    Pid=spawn_link(?MODULE,
102
 
                   init,
103
 
                   [self(),
104
 
                    TiData,
105
 
                    Tracer,
106
 
                    {?MODULE,init_std_publld,[2,[]]},
107
 
                    void,
108
 
                    {?MODULE,clean_std_publld}]),
109
 
    wait_for_reply(Pid).
110
 
start(TiData,Tracer,InitPublLDmfa,RemovePublLDmf,CleanPublLDmf) ->
111
 
    Pid=spawn_link(?MODULE,
112
 
                   init,
113
 
                   [self(),TiData,Tracer,InitPublLDmfa,RemovePublLDmf,CleanPublLDmf]),
114
 
    wait_for_reply(Pid).
115
 
 
116
 
wait_for_reply(Pid) ->
117
 
    receive
118
 
        {Pid,ok} ->
119
 
            {ok,Pid};
120
 
        {Pid,{error,Reason}} ->
121
 
            {error,Reason}
122
 
    after
123
 
        10000 ->                             % After very long time.
124
 
            exit(Pid,kill),                  % It must be hanging.
125
 
            {error,time_out}
126
 
    end.
127
 
%% -----------------------------------------------------------------------------
128
 
 
129
 
%% stop(Pid)=ok
130
 
%%   Pid=Adders to the meta tracer, pid().
131
 
%% Shutsdown the metatracer.
132
 
stop(Pid) ->
133
 
    Pid ! {stop,self()},
134
 
    ok.
135
 
%% -----------------------------------------------------------------------------
136
 
 
137
 
%% suspend(Pid)=ok
138
 
%%   Pid=Adders to the meta tracer, pid().
139
 
%% Suspends the meta tracer by removing all meta trace patterns.
140
 
suspend(Pid) ->
141
 
    Pid ! {suspend,self()},
142
 
    ok.
143
 
%% -----------------------------------------------------------------------------
144
 
 
145
 
%% init_tpm(Pid,Mod,Func,Arity,CallFunc)=
146
 
%% init_tpm(Pid,Mod,Func,Arity,InitFunc,CallFunc,ReturnFunc,RemoveFunc)=ok|{error,Reason}.
147
 
%%   Pid=Address to meta tracer process, pid().
148
 
%%   Mod,Func=Pointing out the function which shall be meta traced, atom().
149
 
%%   Arity=As above, integer().
150
 
%%   InitFunc,RemoveFunc={Module,Function}|fun(), functions being called when
151
 
%%     to initialize the public loopdata structure, and to reset it.
152
 
%%       InitFunc(Mod,Func,Arity,PublLD)->{ok,NewPublLD,Output}
153
 
%%         Supposed to initialize whatever needs to be done before
154
 
%%         handling any incoming meta-trace message for the Mod:Func/Arity.
155
 
%%       RemoveFunc(Mod,Func,Arity,PublLD)->{ok,NewPublLD}
156
 
%%         Called when meta tracing of Mod:Func/Arity is stopped. It is supposed
157
 
%%         to clear datastructures away from the PublLD.
158
 
%% Initializes the public loopdata for this function. Note that we can not use wildcards
159
 
%% here (even if it is perfectly legal in Erlang). It also sets the CallFunc and
160
 
%% ReturnFunc for the meta traced function. The function is hence ready to be
161
 
%% meta traced with either tpm/5 or tpm_ms/5.
162
 
%% This function is synchronous, waiting for a reply from the meta server.
163
 
init_tpm(Pid,Mod,Func,Arity,CallFunc) ->
164
 
    init_tpm(Pid,Mod,Func,Arity,void,CallFunc,void,void).
165
 
init_tpm(Pid,Mod,Func,Arity,InitFunc,CallFunc,ReturnFunc,RemoveFunc) ->
166
 
    send_wait(Pid,
167
 
              {init_tpm,{Mod,Func,Arity},InitFunc,CallFunc,ReturnFunc,RemoveFunc}).
168
 
%% -----------------------------------------------------------------------------
169
 
 
170
 
%% tpm(Pid,Mod,Func,Arity,MatchSpec)={ok,N}|{error,Reason}
171
 
%% tpm(Pid,Mod,Func,Arity,MatchSpec,CallFunc)={ok,N}|{error,Reason}
172
 
%% tpm(Pid,Mod,Func,Arity,MatchSpec,InitFunc,CallFunc,ReturnFunc,RemoveFunc)=
173
 
%%   Pid=Address to meta tracer process, pid().
174
 
%%   Mod,Func=Pointing out the function which shall be meta traced, atom().
175
 
%%   Arity=As above, integer().
176
 
%%   MatchSpec=List of match specification, possibly empty. Remember {return_trace}
177
 
%%     if expecting return_from messages.
178
 
%%   InitFunc,CallFunc,ReturnFunc,RemoveFunc={Module,Function}|fun(),
179
 
%%     functions being called when these functions are called by the meta trace
180
 
%%     server at certain events.
181
 
%%       CallFunc(CallingPid,ActualArgList,PublLD)->{ok,NewPrivLD,Output}
182
 
%%       ReturnFunc(CallingPid,ReturnValue,PublLD)->{ok,NewPrivLD,Output}
183
 
%%         When a call respectively return_from trace message arrives for the meta
184
 
%%         traced function, the corresponding function is called.
185
 
%%         The ReturnFunc must handle the fact that a return_from message arrives
186
 
%%         for a call which was never noticed. This because the message queue of the
187
 
%%         meta tracer may have been emptied.
188
 
%%   Reason=badarg | 
189
 
%%   Output=Characters to be written to the ti-file, bin() | 'void'
190
 
%% The tpm/5 function simply starts meta tracing for the function. It must
191
 
%% previously have been initialized.
192
 
%% tpm/6 & /9 initializes the function and starts meta tracing.
193
 
tpm(Pid,Mod,Func,Arity,MatchSpec)
194
 
  when atom(Mod),atom(Func),integer(Arity),list(MatchSpec),Mod/='_',Func/='_'->
195
 
    send_wait(Pid,{tpm,{Mod,Func,Arity,MatchSpec}});
196
 
tpm(_,_,_,_,_) ->
197
 
    {error,badarg}.
198
 
 
199
 
tpm(Pid,Mod,Func,Arity,MatchSpec,CallFunc) ->
200
 
    tpm(Pid,Mod,Func,Arity,MatchSpec,void,CallFunc,void,void).
201
 
 
202
 
tpm(Pid,Mod,Func,Arity,MatchSpec,InitFunc,CallFunc,ReturnFunc,RemoveFunc)
203
 
  when atom(Mod),atom(Func),integer(Arity),list(MatchSpec),Mod/='_',Func/='_' ->
204
 
    send_wait(Pid,{tpm,{Mod,Func,Arity,MatchSpec},InitFunc,CallFunc,ReturnFunc,RemoveFunc});
205
 
tpm(_,_,_,_,_,_,_,_,_) ->
206
 
    {error,badarg}.
207
 
%% -----------------------------------------------------------------------------
208
 
 
209
 
%% Same as tpm/X but the meta tracer will automatically append {tracer,Tracer}
210
 
%% to the enable list in a {trace,Disable,Enable} match spec action term.
211
 
tpm_tracer(Pid,Mod,Func,Arity,MatchSpec)
212
 
  when atom(Mod),atom(Func),integer(Arity),list(MatchSpec),Mod/='_',Func/='_'->
213
 
    send_wait(Pid,{tpm_tracer,{Mod,Func,Arity,MatchSpec}});
214
 
tpm_tracer(_,_,_,_,_) ->
215
 
    {error,badarg}.
216
 
 
217
 
tpm_tracer(Pid,Mod,Func,Arity,MatchSpec,CallFunc) ->
218
 
    tpm_tracer(Pid,Mod,Func,Arity,MatchSpec,void,CallFunc,void,void).
219
 
 
220
 
tpm_tracer(Pid,Mod,Func,Arity,MatchSpec,InitFunc,CallFunc,ReturnFunc,RemoveFunc)
221
 
  when atom(Mod),atom(Func),integer(Arity),list(MatchSpec),Mod/='_',Func/='_' ->
222
 
    send_wait(Pid,{tpm_tracer,
223
 
                   {Mod,Func,Arity,MatchSpec},
224
 
                   InitFunc,CallFunc,ReturnFunc,RemoveFunc});
225
 
tpm_tracer(_,_,_,_,_,_,_,_,_) ->
226
 
    {error,badarg}.
227
 
%% -----------------------------------------------------------------------------
228
 
 
229
 
%% tpm_ms(Pid,Mod,Func,Arity,MSname,MS)={ok,N}|{error,Reason}
230
 
%%   Pid=Address to meta tracer process, pid().
231
 
%%   Mod,Func=Pointing out the function to which we shall add a match-spec., atom().
232
 
%%   Arity=As above, integer().
233
 
%%   MSname=A name to be used if this MS shall be removed later. term().
234
 
%%   MatchSpec=List of match specification, Remember {return_trace}
235
 
%%     if expecting return_from messages.
236
 
%% This function adds a list of match-specs to the already existing ones. It
237
 
%% uses an internal database to keep track of existing match-specs. If the
238
 
%% match-spec does not result in any meta traced functions (for whatever reason),
239
 
%% the MS is not saved in the database. The previously known match-specs are
240
 
%% not removed.
241
 
tpm_ms(Pid,Mod,Func,Arity,MSname,MS) ->
242
 
    send_wait(Pid,{tpm_ms,{Mod,Func,Arity},MSname,MS}).
243
 
%% -----------------------------------------------------------------------------
244
 
 
245
 
%% Same as tpm_ms/6 but the meta tracer will automatically append {tracer,Tracer}
246
 
%% to the enable list in a {trace,Disable,Enable} match spec action term.
247
 
tpm_ms_tracer(Pid,Mod,Func,Arity,MSname,MS) ->
248
 
    send_wait(Pid,{tpm_ms_tracer,{Mod,Func,Arity},MSname,MS}).
249
 
%% -----------------------------------------------------------------------------
250
 
 
251
 
%% ctpm_ms(Pid,Mod,Func,Arity)=ok
252
 
%%
253
 
%% Removes a names match-spec from the meta traced function. Note that is never
254
 
%% a fault to remove an MS. Not even from a function which is non existant.
255
 
ctpm_ms(Pid,Mod,Func,Arity,MSname) ->
256
 
    send_wait(Pid,{ctpm_ms,{Mod,Func,Arity},MSname}).
257
 
%% -----------------------------------------------------------------------------
258
 
 
259
 
%% Quick versions for erlang:register/2 which also uses a default CallFunc
260
 
%% and a default ReturnFunc.
261
 
local_register(Pid) ->
262
 
    Res1=tpm(Pid,
263
 
             erlang,register,2,[{'_',[],[{exception_trace}]}],
264
 
             fun metafunc_init/4,fun local_register_call/3,
265
 
             fun local_register_return/3,void),
266
 
    Res2=tpm(Pid,
267
 
             erlang,unregister,1,[],
268
 
             void,fun local_unregister_call/3,void,void),
269
 
    {Res1,Res2}.
270
 
%% -----------------------------------------------------------------------------
271
 
 
272
 
%% Quick version for global:register_name/2, /3.
273
 
global_register(Pid) ->
274
 
    Res1=tpm(Pid,global,handle_call,3,[{[{register,'_','_','_'},'_','_'],[],[]}],
275
 
        void,fun global_register_call/3,void,void),
276
 
    Res2=tpm(Pid,global,delete_global_name,2,[],
277
 
             void,fun global_unregister_call/3,void,void),
278
 
    {Res1,Res2}.
279
 
%% -----------------------------------------------------------------------------
280
 
 
281
 
%% ctpm(Pid,Mod,Func,Arity)=ok|{error,bad_mfa}
282
 
%%
283
 
%% Removes the meta trace pattern for the function, means stops generating output
284
 
%% for this function. The public LD may be cleared by the previously entered
285
 
%% RemoveFunc.
286
 
ctpm(Pid,Mod,Func,Arity) ->
287
 
    send_wait(Pid,{ctpm,{Mod,Func,Arity}}).
288
 
%% -----------------------------------------------------------------------------
289
 
 
290
 
%% remove_local_register(Pid)={Res1,Res2}
291
 
%%   Res1,Res2=ok|{error,Reason}
292
 
remove_local_register(Pid) ->
293
 
    Res1=ctpm(Pid,erlang,register,2),
294
 
    Res2=ctpm(Pid,erlang,unregister,1),
295
 
    {Res1,Res2}.
296
 
%% -----------------------------------------------------------------------------
297
 
 
298
 
%% remove_global_register(Pid)={Res1,Res2}
299
 
%%   Res1,Res2=ok|{error,Reason}
300
 
remove_global_register(Pid) ->
301
 
    Res1=ctpm(Pid,global,handle_call,3),
302
 
    Res2=ctpm(Pid,global,delete_global_name,2),
303
 
    {Res1,Res2}.
304
 
%% -----------------------------------------------------------------------------
305
 
 
306
 
%% Exported help functions which may be used in programming CallFunc and/or
307
 
%% ReturnFunc. Useful if the call is done on one node but must trigger the
308
 
%% start of something at other nodes.
309
 
metacast_call(Nodes,OrigPid,M,F,Args) ->
310
 
    multicast(Nodes,{trace_ts,OrigPid,call,{M,F,Args},void}),
311
 
    ok.
312
 
 
313
 
metacast_return_from(Nodes,OrigPid,M,F,Arity,Value) ->
314
 
    multicast(Nodes,{trace_ts,OrigPid,return_from,{M,F,Arity},Value,void}),
315
 
    ok.
316
 
 
317
 
multicast([Node|Rest],Msg) ->
318
 
    {?MODULE,Node} ! Msg,
319
 
    multicast(Rest,Msg);
320
 
multicast([],_) ->
321
 
    true.
322
 
%% -----------------------------------------------------------------------------
323
 
 
324
 
%% get_states(Pid)={ok,LD,PubLD}.
325
 
get_state(Pid) ->
326
 
    send_wait(Pid,get_state).
327
 
%% -----------------------------------------------------------------------------
328
 
 
329
 
 
330
 
send_wait(To,Msg) ->
331
 
    Ref=make_ref(),
332
 
    MRef=erlang:monitor(process,To),
333
 
    To ! {Msg,Ref,self()},
334
 
    receive
335
 
        {inviso_rt_meta_reply,Ref,Reply} ->
336
 
            erlang:demonitor(MRef),
337
 
            Reply;
338
 
        {'DOWN',MRef,_,_To,_Reason} ->
339
 
            {error,no_metatracer}
340
 
    end.
341
 
 
342
 
reply(To,Ref,Reply) ->
343
 
    To ! {inviso_rt_meta_reply,Ref,Reply}.
344
 
%% -----------------------------------------------------------------------------
345
 
 
346
 
%% =============================================================================
347
 
%% Special API.
348
 
%% =============================================================================
349
 
 
350
 
%% write_ti(OutPut)=
351
 
%%   OutPut=binary()
352
 
%% Makes an extra entry into the trace information file (ti-file). This is useful
353
 
%% if a pid-alias association is learned in another way than through a meta traced
354
 
%% function call. Note that this API can only be used locally at the node in
355
 
%% question.
356
 
write_ti(OutPut) ->
357
 
    catch ?MODULE ! {write_ti,OutPut}.
358
 
%% -----------------------------------------------------------------------------
359
 
 
360
 
 
361
 
%% =============================================================================
362
 
%% API intended to be used on CallFuncs and RemoveFuncs.
363
 
%% =============================================================================
364
 
 
365
 
%% The reason there must be a special API for CallFuncs and RemoveFuncs are is
366
 
%% that those functions are executed inside *this* process context. Hence they
367
 
%% can not make function calls requiering this process to receive messages.
368
 
 
369
 
%% Returns the tracer used for regular tracing. The reason this is implemented
370
 
%% in this way is that this function is intended to be used in meta trace call-
371
 
%% back functions. And there we can not have message passing API:s to the meta
372
 
%% trace(!).
373
 
get_tracer() ->
374
 
    get(tracer).
375
 
%% -----------------------------------------------------------------------------
376
 
 
377
 
%% Function equivalent to inviso_rt:tpm_ms/6. This function can *only* be used
378
 
%% inside a CallFunc or a RemoveFunc.
379
 
tpm_ms(Mod,Func,Arity,MSname,MS) ->
380
 
    case check_mfarity_exists(Mod,Func,Arity) of
381
 
        yes ->                               % Ok, and args must be ok then also.
382
 
            {ok,h_tpm_ms(Mod,Func,Arity,MSname,MS)};
383
 
        no ->
384
 
            {error,not_initiated}
385
 
    end.
386
 
%% -----------------------------------------------------------------------------
387
 
 
388
 
tpm_ms_tracer(Mod,Func,Arity,MSname,MS) ->
389
 
    case check_mfarity_exists(Mod,Func,Arity) of
390
 
        yes ->                               % Ok, and args must be ok then also.
391
 
            NewMS=add_tracer(MS,get_tracer()),
392
 
            {ok,h_tpm_ms(Mod,Func,Arity,MSname,NewMS)};
393
 
        no ->
394
 
            {error,not_initiated}
395
 
    end.
396
 
%% -----------------------------------------------------------------------------
397
 
 
398
 
%% Function that returns all MSname in use for Mod:Func/Arity
399
 
list_tpm_ms(Mod,Func,Arity) ->
400
 
    {ok,h_list_tpm_ms(Mod,Func,Arity)}.
401
 
%% -----------------------------------------------------------------------------
402
 
 
403
 
%% Function equivalent to inviso_rt:ctpm_ms/5. This function can *only* be used
404
 
%% inside a CallFunc or a RemoveFunc.
405
 
ctpm_ms(Mod,Func,Arity,MSname) ->
406
 
    h_ctpm_ms(Mod,Func,Arity,MSname),
407
 
    ok.
408
 
%% -----------------------------------------------------------------------------
409
 
 
410
 
 
411
 
%% =============================================================================
412
 
%% The server implemenation.
413
 
%% =============================================================================
414
 
 
415
 
init(Parent,TiData,Tracer,InitPublLDmfa,RemovePublLDmf,CleanPublLDmf) ->
416
 
    process_flag(priority,high),            % Since we may receive from many procs.
417
 
    register(?MODULE,self()),               % So we can act as relay receiver.
418
 
    case open_traceinfo_file(TiData) of
419
 
        {ok,TI} ->                          % The ti.-file.
420
 
            TId=ets:new(?NAMED_MS_TAB,[named_table,set,protected]),
421
 
            PublLD=do_init_publ_ld(InitPublLDmfa),
422
 
            Parent ! {self(),ok},
423
 
            put(tracer,Tracer),             % Uggly quick fix!
424
 
            loop(Parent,
425
 
                 Tracer,
426
 
                 TI,
427
 
                 mk_new_ld(InitPublLDmfa,RemovePublLDmf,CleanPublLDmf,TId),
428
 
                 PublLD,
429
 
                 now());
430
 
        {error,Reason} ->
431
 
            Parent ! {self(),{error,Reason}}
432
 
    end.
433
 
%% -----------------------------------------------------------------------------
434
 
 
435
 
loop(Parent,Tracer,TI,LD,PrevPublLD,PrevCleanTime) ->
436
 
    {PublLD,CleanTime}=throw_old_failed(get_cleanpublldmf_ld(LD),PrevPublLD,PrevCleanTime),
437
 
    receive
438
 
        {{init_tpm,{Mod,Func,Arity},InitFunc,CallFunc,ReturnFunc,RemoveFunc},Ref,Parent} ->
439
 
            case check_mfarity_exists(Mod,Func,Arity) of
440
 
                no ->                       % Good then we can add it!
441
 
                    case check_tpm_args(Mod,Func,Arity) of
442
 
                        true ->             % Args are ok.
443
 
                            {NewLD,NewPublLD}=
444
 
                                h_init_tpm(Mod,Func,Arity,
445
 
                                           InitFunc,CallFunc,ReturnFunc,RemoveFunc,
446
 
                                           TI,LD,PublLD),
447
 
                            reply(Parent,Ref,ok),
448
 
                            loop(Parent,Tracer,TI,NewLD,NewPublLD,CleanTime);
449
 
                        false ->            % Faulty arguments,
450
 
                            reply(Parent,Ref,{error,bad_mfa}),
451
 
                            loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
452
 
                    end;
453
 
                yes ->                      % If it already exists, cant init again.
454
 
                    reply(Parent,Ref,{error,already_initiated}),
455
 
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
456
 
            end;
457
 
        {{tpm,{Mod,Func,Arity,MS},InitFunc,CallFunc,ReturnFunc,RemoveFunc},Ref,Parent} ->
458
 
            case check_mfarity_exists(Mod,Func,Arity) of
459
 
                no ->                       % Good then we can add it!
460
 
                    case check_tpm_args(Mod,Func,Arity) of
461
 
                        true ->             % Args are ok.
462
 
                            {NewLD,NewPublLD,N}=
463
 
                                h_tpm(Mod,Func,Arity,MS,
464
 
                                      InitFunc,CallFunc,ReturnFunc,RemoveFunc,
465
 
                                      TI,LD,PublLD),
466
 
                            reply(Parent,Ref,{ok,N}),
467
 
                            loop(Parent,Tracer,TI,NewLD,NewPublLD,CleanTime);
468
 
                        false ->
469
 
                            reply(Parent,Ref,{error,bad_mfa}),
470
 
                            loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
471
 
                    end;
472
 
                yes ->
473
 
                    reply(Parent,Ref,{error,already_initiated}),
474
 
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
475
 
            end;
476
 
        {{tpm,{Mod,Func,Arity,MS}},Ref,Parent} ->
477
 
            case check_mfarity_exists(Mod,Func,Arity) of
478
 
                yes ->                      % Ok, and args must be ok then also.
479
 
                    {NewLD,N}=h_tpm(Mod,Func,Arity,MS,LD),
480
 
                    reply(Parent,Ref,{ok,N}),
481
 
                    loop(Parent,Tracer,TI,NewLD,PublLD,CleanTime);
482
 
                no ->                       % Must be initiated before.
483
 
                    reply(Parent,Ref,{error,not_initiated}),
484
 
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
485
 
            end;
486
 
        {{tpm_tracer,{Mod,Func,Arity,MS},InitFunc,CallFunc,ReturnFunc,RemoveFunc},Ref,Parent} ->
487
 
            case check_mfarity_exists(Mod,Func,Arity) of
488
 
                no ->                       % Good then we can add it!
489
 
                    case check_tpm_args(Mod,Func,Arity) of
490
 
                        true ->             % Args are ok.
491
 
                            NewMS=add_tracer(MS,Tracer),
492
 
                            {NewLD,NewPublLD,N}=
493
 
                                h_tpm(Mod,Func,Arity,NewMS,
494
 
                                      InitFunc,CallFunc,ReturnFunc,RemoveFunc,
495
 
                                      TI,LD,PublLD),
496
 
                            reply(Parent,Ref,{ok,N}),
497
 
                            loop(Parent,Tracer,TI,NewLD,NewPublLD,CleanTime);
498
 
                        false ->
499
 
                            reply(Parent,Ref,{error,bad_mfa}),
500
 
                            loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
501
 
                    end;
502
 
                yes ->
503
 
                    reply(Parent,Ref,{error,already_initiated}),
504
 
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
505
 
            end;
506
 
        {{tpm_tracer,{Mod,Func,Arity,MS}},Ref,Parent} ->
507
 
            case check_mfarity_exists(Mod,Func,Arity) of
508
 
                yes ->                      % Ok, and args must be ok then also.
509
 
                    NewMS=add_tracer(MS,Tracer),
510
 
                    {NewLD,N}=h_tpm(Mod,Func,Arity,NewMS,LD),
511
 
                    reply(Parent,Ref,{ok,N}),
512
 
                    loop(Parent,Tracer,TI,NewLD,PublLD,CleanTime);
513
 
                no ->                       % Must be initiated before.
514
 
                    reply(Parent,Ref,{error,not_initiated}),
515
 
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
516
 
            end;
517
 
        {{tpm_ms,{Mod,Func,Arity},MSname,MS},Ref,Parent} ->
518
 
            case check_mfarity_exists(Mod,Func,Arity) of
519
 
                yes ->                      % Ok, and args must be ok then also.
520
 
                    reply(Parent,Ref,{ok,h_tpm_ms(Mod,Func,Arity,MSname,MS)}),
521
 
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime);
522
 
                no ->
523
 
                    reply(Parent,Ref,{error,not_initiated}),
524
 
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
525
 
            end;
526
 
        {{tpm_ms_tracer,{Mod,Func,Arity},MSname,MS},Ref,Parent} ->
527
 
            case check_mfarity_exists(Mod,Func,Arity) of
528
 
                yes ->                      % Ok, and args must be ok then also.
529
 
                    NewMS=add_tracer(MS,Tracer),
530
 
                    reply(Parent,Ref,{ok,h_tpm_ms(Mod,Func,Arity,MSname,NewMS)}),
531
 
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime);
532
 
                no ->
533
 
                    reply(Parent,Ref,{error,not_initiated}),
534
 
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
535
 
            end;
536
 
        {{ctpm_ms,{Mod,Func,Arity},MSname},Ref,Parent} ->
537
 
            reply(Parent,Ref,ok),
538
 
            h_ctpm_ms(Mod,Func,Arity,MSname),
539
 
            loop(Parent,Tracer,TI,LD,PublLD,CleanTime);
540
 
        {{ctpm,{Mod,Func,Arity}},Ref,Parent} ->
541
 
            case get_remove_func_ld(Mod,Func,Arity,LD) of
542
 
                false ->                    % Incorrect Mod:Func/Arity!
543
 
                    reply(Parent,Ref,{error,bad_mfa}),
544
 
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime); % Do nothing!
545
 
                MF ->                       % {M,F}, Func or 'void'.
546
 
                    catch erlang:trace_pattern({Mod,Func,Arity},false,[meta]),
547
 
                    NewPublLD=do_removefunc(MF,Mod,Func,Arity,PublLD),
548
 
                    NewLD=ctpm_ld(Mod,Func,Arity,LD),
549
 
                    reply(Parent,Ref,ok),
550
 
                    loop(Parent,Tracer,TI,NewLD,NewPublLD,CleanTime)
551
 
            end;
552
 
        {suspend,Parent} ->                 % Removes all meta trace patterns.
553
 
            stop_all_meta_tracing(get_all_meta_funcs_ld(LD),PublLD,LD),
554
 
            do_remove_publ_ld(get_removepublldmf_ld(LD),PublLD),
555
 
            NewPublLD=do_init_publ_ld(get_initpublldmfa_ld(LD)),
556
 
            loop(Parent,Tracer,TI,reset_ld(LD),NewPublLD,CleanTime);
557
 
        {stop,Parent} ->                    % Make a controlled shutdown.
558
 
            stop_all_meta_tracing(get_all_meta_funcs_ld(LD),PublLD,LD),
559
 
            do_remove_publ_ld(get_removepublldmf_ld(LD),PublLD),
560
 
            close_traceinfo_file(TI);       % And then simply terminate.
561
 
        {trace_ts,Pid,call,{M,F,Args},TS} ->
562
 
            case handle_meta(get_call_func_ld(M,F,length(Args),LD),Pid,{call,Args,TS},PublLD) of
563
 
                {ok,NewPublLD,Output} when is_binary(Output);is_list(Output) ->
564
 
                    write_output(TI,Output),
565
 
                    loop(Parent,Tracer,TI,LD,NewPublLD,CleanTime);
566
 
                {ok,NewPublLD,_} ->         % No output to the ti-file this time.
567
 
                    loop(Parent,Tracer,TI,LD,NewPublLD,CleanTime);
568
 
                _ ->                        % Not handled correct, not much to do.
569
 
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
570
 
            end;
571
 
        {trace_ts,Pid,TypeTag,{M,F,Arity},Value,TS}
572
 
          when TypeTag==return_from;TypeTag==exception_from ->
573
 
            case handle_meta(get_return_func_ld(M,F,Arity,LD),Pid,{TypeTag,Value,TS},PublLD) of
574
 
                {ok,NewPublLD,Output} when is_binary(Output);is_list(Output) ->
575
 
                    write_output(TI,Output),
576
 
                    loop(Parent,Tracer,TI,LD,NewPublLD,CleanTime);
577
 
                {ok,NewPublLD,_} ->         % No output to the ti-file this time.
578
 
                    loop(Parent,Tracer,TI,LD,NewPublLD,CleanTime);
579
 
                _ ->                        % Not handled correct, not much to do.
580
 
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
581
 
            end;
582
 
        {relayed_meta,Bin} ->
583
 
            write_output(TI,Bin),
584
 
            loop(Parent,Tracer,TI,LD,PublLD,CleanTime);
585
 
        {write_ti,OutPut} ->
586
 
            write_output(TI,OutPut),
587
 
            loop(Parent,Tracer,TI,LD,PublLD,CleanTime);
588
 
        {get_state,Ref,From} ->             % Debug function.
589
 
            reply(From,Ref,{ok,LD,PublLD}),
590
 
            loop(Parent,Tracer,TI,LD,PublLD,CleanTime);
591
 
        _Other ->
592
 
            loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
593
 
    end.
594
 
 
595
 
 
596
 
%% =============================================================================
597
 
%% First level help functions.
598
 
%% =============================================================================
599
 
 
600
 
%% Function which opens the trace-information file(s). It must understand
601
 
%% the tidata specification which is part of the tracerdata given to the
602
 
%% runtime component during init_tracing.
603
 
%% It must return an internal notation of the time of file open and a
604
 
%% useful descriptor the write_output function can use.
605
 
%% Returns {ok,TiDescriptor} or {error,Reason}.
606
 
open_traceinfo_file({file,FileName}) ->     % A plain raw binary file.
607
 
    case file:open(FileName,[write,raw,binary]) of
608
 
        {ok,FD} ->
609
 
            {ok,{file,FD}};
610
 
        {error,Reason} ->
611
 
            {error,{open,[FileName,Reason]}}
612
 
    end;
613
 
open_traceinfo_file({relay,ToNode}) ->      % Use distributed Erlang.
614
 
    {ok,{relay,ToNode}};
615
 
open_traceinfo_file(IncorrectTI) ->
616
 
    {error,{badarg,IncorrectTI}}.
617
 
%% -----------------------------------------------------------------------------
618
 
 
619
 
close_traceinfo_file({file,FD}) ->
620
 
    file:close(FD);
621
 
close_traceinfo_file(_) ->
622
 
    ok.
623
 
%% -----------------------------------------------------------------------------
624
 
 
625
 
%% Help function handling initializing meta tracing of a function.
626
 
%% Returns {NewLD,NewPublLD}.
627
 
h_init_tpm(Mod,Func,Arity,InitFunc,CallFunc,ReturnFunc,RemoveFunc,TI,LD,PublLD) ->
628
 
    case do_initfunc(InitFunc,Mod,Func,Arity,PublLD) of
629
 
        {NewPublLD,Output} ->
630
 
            write_output(TI,Output),
631
 
            NewLD=init_tpm_ld(Mod,Func,Arity,CallFunc,ReturnFunc,RemoveFunc,LD),
632
 
            {NewLD,NewPublLD};
633
 
        false ->                            % The initfunc did not do anything.
634
 
            NewLD=init_tpm_ld(Mod,Func,Arity,CallFunc,ReturnFunc,RemoveFunc,LD),
635
 
            {NewLD,PublLD}
636
 
    end.
637
 
%% -----------------------------------------------------------------------------
638
 
 
639
 
%% Help function handling initializing meta tracing of a function and also
640
 
%% set the meta trace pattern as specified.
641
 
%% Returns {NewLD,NewPublLD,N}.
642
 
h_tpm(Mod,Func,Arity,MS,InitFunc,CallFunc,ReturnFunc,RemoveFunc,TI,LD,PublLD) ->
643
 
    {NewLD,NewPublLD}=
644
 
        h_init_tpm(Mod,Func,Arity,InitFunc,CallFunc,ReturnFunc,RemoveFunc,TI,LD,PublLD),
645
 
    case set_meta_tracing(Mod,Func,Arity,MS) of
646
 
        true ->                              % Ok, set one pattern.
647
 
            {NewLD,NewPublLD,1};
648
 
        false ->
649
 
            {NewLD,NewPublLD,0}
650
 
    end.
651
 
%% -----------------------------------------------------------------------------
652
 
 
653
 
%% Help function handling setting meta trace patter for a function which has
654
 
%% already been intialized. Note that we must remove all potentially stored
655
 
%% match-specs, if this function has been given match-specs before with
656
 
%% tpm_ms.
657
 
%% Returns a {NewLD,N}.
658
 
h_tpm(Mod,Func,Arity,MS,LD) ->
659
 
    case set_meta_tracing(Mod,Func,Arity,MS) of
660
 
        true ->
661
 
            {remove_ms_ld(Mod,Func,Arity,LD),1};
662
 
        false ->
663
 
            {LD,0}
664
 
    end.
665
 
%% -----------------------------------------------------------------------------
666
 
 
667
 
%% Help function that adds a match-spec to Mod:Func/Arity. It is not defined
668
 
%% in which order the match-specs will be given to the BIF.
669
 
%% Note that if an MS with the same name as an exiting is inserted, the previous
670
 
%% match-spec will be removed.
671
 
%% Very important to realise is that the empty meta match spec [] imposes no
672
 
%% restrictions what so ever on the generating of meta trace call messages.
673
 
%% Uncontrolled sending of such messages may quickly drain power from the system.
674
 
%% Since an empty match-spec will "disappear" when added to other match specs,
675
 
%% the empty match is transformed to what it actually is: [{'_',[],[]}].
676
 
%% Returns 0 or 1 indicating failure or success.
677
 
h_tpm_ms(Mod,Func,Arity,MSname,MS) ->
678
 
    MSsNames=get_ms_ld(Mod,Func,Arity),     % Fetch all previous match-specs.
679
 
    TransformedMS=h_tpm_ms_convert_null_ms(MS),
680
 
    MSsNames1=lists:keydelete(MSname,1,MSsNames), % If it already existed, it is gone!
681
 
    NewMSs=lists:flatten([TransformedMS,lists:map(fun({_Name,MSx})->MSx end,MSsNames1)]),
682
 
    case set_meta_tracing(Mod,Func,Arity,NewMSs) of
683
 
        true ->                             % We only save the MS if it was good.
684
 
            put_ms_ld(Mod,Func,Arity,MSname,TransformedMS,MSsNames1),
685
 
            1;
686
 
        false ->
687
 
            0
688
 
    end.
689
 
 
690
 
%% Help function converting the null match spec into, still a null match spec,
691
 
%% on a proper match spec format. This because it will otherwise be difficult
692
 
%% to see the difference between no active tpm_ms and all a set of null ms.
693
 
h_tpm_ms_convert_null_ms([]) ->
694
 
    [{'_',[],[]}];
695
 
h_tpm_ms_convert_null_ms(MS) ->
696
 
    MS.
697
 
%% -----------------------------------------------------------------------------
698
 
 
699
 
%% Help function returning a list of all names used for match-functions for
700
 
%% the Mod:Func/Arity in question.
701
 
h_list_tpm_ms(Mod,Func,Arity) ->
702
 
    MSsNames=get_ms_ld(Mod,Func,Arity),     % A list of {MSname,MS}.
703
 
    lists:map(fun({MSname,_})->MSname end,MSsNames).
704
 
%% -----------------------------------------------------------------------------
705
 
 
706
 
%% Function that removes a named match-spec. Returns nothing significant.
707
 
%% Note that if we end up with no match-specs, we must remove the meta trace
708
 
%% patten all together. That is bringing the function back to just initiated.
709
 
h_ctpm_ms(Mod,Func,Arity,MSname) ->
710
 
    case get_ms_ld(Mod,Func,Arity) of
711
 
        [] ->                               % The name does certainly not exist!
712
 
            true;                           % We don't have to do anything.
713
 
        MSsNames ->
714
 
            case lists:keysearch(MSname,1,MSsNames) of
715
 
                {value,{_,_MS}} ->          % Ok, we must do something!
716
 
                    NewMSsNames=lists:keydelete(MSname,1,MSsNames),
717
 
                    case lists:flatten(lists:map(fun({_Name,MS})->MS end,NewMSsNames)) of
718
 
                        [] ->               % This means stop meta tracing.
719
 
                            set_meta_tracing(Mod,Func,Arity,false);
720
 
                        NewMSs ->
721
 
                            set_meta_tracing(Mod,Func,Arity,NewMSs)
722
 
                    end,
723
 
                    set_ms_ld(Mod,Func,Arity,NewMSsNames);
724
 
                false ->                    % But this name does not exist.
725
 
                    true                    % So we do not have to do anything.
726
 
            end
727
 
    end.
728
 
%% -----------------------------------------------------------------------------
729
 
 
730
 
%% Function that checks the arguments to the meta trace pattern. The reason we
731
 
%% must do this is that we can only allow meta tracing on specific functions and
732
 
%% not using wildpatterns. Otherwise the meta trace server will not understand
733
 
%% which callfunc for instance to call when a meta-trace message is generated
734
 
%% for a function.
735
 
%% Returns 'true' or 'false'.
736
 
check_tpm_args(Mod,Func,Arity)
737
 
  when atom(Mod),atom(Func),integer(Arity),Mod/='_',Func/='_' ->
738
 
    true;
739
 
check_tpm_args(_,_,_) ->
740
 
    false.
741
 
%% -----------------------------------------------------------------------------
742
 
 
743
 
%% Help function which calls the actual BIF setting meta-trace-patterns.
744
 
%% Returns 'true' or 'false'.
745
 
set_meta_tracing(Mod,Func,Arity,MS) when atom(Mod) ->
746
 
    case erlang:module_loaded(Mod) of
747
 
        true ->
748
 
            set_meta_tracing_2(Mod,Func,Arity,MS);
749
 
        false ->                            % The module is not loaded.
750
 
            case code:ensure_loaded(Mod) of
751
 
                {module,_Mod} ->
752
 
                    set_meta_tracing_2(Mod,Func,Arity,MS);
753
 
                {error,_Reason} ->          % Could not load the module.
754
 
                    false                   % No use try to trace.
755
 
            end
756
 
    end;
757
 
set_meta_tracing(_,_,_,_) ->
758
 
    false.
759
 
 
760
 
set_meta_tracing_2(Mod,Func,Arity,MS) ->
761
 
    case catch erlang:trace_pattern({Mod,Func,Arity},MS,[meta]) of
762
 
        0 ->                                % Hmm, nothing happend :-)
763
 
            false;
764
 
        N when integer(N) ->                % The normal case, some functions were hit.
765
 
            true;
766
 
        {'EXIT',_Reason} ->
767
 
            false
768
 
    end.
769
 
%% -----------------------------------------------------------------------------
770
 
 
771
 
%% Help function which removes all meta trace pattern for the functions mentioned
772
 
%% in the list being first argument. It also executes the remove funcs for each
773
 
%% and every no longer meta traced function. This done since some of the remove
774
 
%% functions may do side-effects (like deleteing ETS tables).
775
 
%% Returns nothing significant.
776
 
stop_all_meta_tracing([{M,F,Arity}|Rest],PublLD,LD) ->
777
 
    catch erlang:trace_pattern({M,F,Arity},false,[meta]),
778
 
    NewPublLD=do_removefunc(get_remove_func_ld(M,F,Arity,LD),M,F,Arity,PublLD),
779
 
    stop_all_meta_tracing(Rest,NewPublLD,LD);
780
 
stop_all_meta_tracing([],_,_) ->
781
 
    true.
782
 
%% -----------------------------------------------------------------------------
783
 
 
784
 
%% This function calls the function registered to be handler for a certain
785
 
%% meta-traced function. Such a function or fun must take three arguments
786
 
%% and return {ok,NewPrivLD,OutPutBinary} or 'false'. OutPutBinary may be
787
 
%% something else, and is then ignored.
788
 
handle_meta({M,F},Pid,Arg1,PrivLD) ->
789
 
    (catch M:F(Pid,Arg1,PrivLD));
790
 
handle_meta(Fun,Pid,Arg1,PrivLD) when function(Fun) ->
791
 
    (catch Fun(Pid,Arg1,PrivLD));
792
 
handle_meta(_,_,_,_) ->                     % Don't know how to do this.
793
 
    false.
794
 
%% -----------------------------------------------------------------------------
795
 
 
796
 
%% Help function writing output from a callback function to the ti-file.
797
 
%% Output can be a binary or a list of binaries.
798
 
write_output(TI,[OutPut|Rest]) ->
799
 
    write_output(TI,OutPut),
800
 
    write_output(TI,Rest);
801
 
write_output({file,FD},Bin) when is_binary(Bin) -> % Plain direct-binary file
802
 
    Size=byte_size(Bin),
803
 
    file:write(FD,list_to_binary([<<0,Size:32>>,Bin]));
804
 
write_output({relay,ToNode},Bin) when atom(ToNode),binary(Bin) ->
805
 
    {inviso_rt_meta,ToNode} ! {relayed_meta,Bin};
806
 
write_output(_,_) ->                        % Don't understand, just skip.
807
 
    true.
808
 
%% -----------------------------------------------------------------------------
809
 
 
810
 
 
811
 
%% =============================================================================
812
 
%% Various help functions.
813
 
%% =============================================================================
814
 
 
815
 
%% Help function initializing the public loopdata structure. Note that if the
816
 
%% supplied InitPublLDmfa is faulty we let the structure become the error.
817
 
%% The error will most likely turn up in an error report somewhere, eventually.
818
 
do_init_publ_ld({M,F,Args}) when atom(M),atom(F),list(Args) ->
819
 
    case catch apply(M,F,Args) of
820
 
        {'EXIT',_Reason} ->
821
 
            {error,init_publ_ld_func};      % Let the struct be this error!
822
 
        InitialPublLD ->
823
 
            InitialPublLD
824
 
    end;
825
 
do_init_publ_ld(_) ->
826
 
    {error,init_publ_ld_func}.
827
 
%% -----------------------------------------------------------------------------
828
 
 
829
 
%% Help function which removes the public loopdata structure. The function does
830
 
%% not necessarily have to exist. Returns nothing significant.
831
 
do_remove_publ_ld({M,F},PublLD) when atom(M),atom(F) ->
832
 
    catch M:F(PublLD);
833
 
do_remove_publ_ld(_,_) ->
834
 
    true.
835
 
%% -----------------------------------------------------------------------------        
836
 
 
837
 
%% Hlp function initializing a particular meta traced function into the public
838
 
%% loopdata. Note that the function is not mandatory.
839
 
%% Returns {NewPublLD,Output} or 'false'.
840
 
do_initfunc({M,F},Mod,Func,Arity,PublLD) when atom(M),atom(F) ->
841
 
    case catch M:F(Mod,Func,Arity,PublLD) of
842
 
        {ok,NewPublLD,Output} ->
843
 
            {NewPublLD,Output};
844
 
        _ ->                                % Everything else is an error.
845
 
            false                           % Act as no initialization function.
846
 
    end;
847
 
do_initfunc(Fun,Mod,Func,Arity,PublLD) when function(Fun) ->
848
 
    case catch Fun(Mod,Func,Arity,PublLD) of
849
 
        {ok,NewPublLD,Output} ->
850
 
            {NewPublLD,Output};
851
 
        _ ->                                % Everything else is an error.
852
 
            false                           % Act as no initialization function.
853
 
    end;
854
 
do_initfunc(_,_,_,_,_) ->                   % Perhaps too generous, should be 'void' only.
855
 
    false.
856
 
%% -----------------------------------------------------------------------------
857
 
 
858
 
%% Help function removing a particular meta traced function from the public
859
 
%% loopdata. Note that we do not make much noice should the call back function
860
 
%% be faulty.
861
 
do_removefunc({M,F},Mod,Func,Arity,PublLD) when atom(M),atom(F) ->
862
 
    case catch M:F(Mod,Func,Arity,PublLD) of
863
 
        {ok,NewPublLD} ->
864
 
            NewPublLD;
865
 
        _ ->                                % Everything else is an error.
866
 
            PublLD                          % Act as no initialization function.
867
 
    end;
868
 
do_removefunc(Fun,Mod,Func,Arity,PublLD) when function(Fun) ->
869
 
    case catch Fun(Mod,Func,Arity,PublLD) of
870
 
        {ok,NewPublLD} ->
871
 
            NewPublLD;
872
 
        _ ->                                % Everything else is an error.
873
 
            PublLD                          % Act as no initialization function.
874
 
    end;
875
 
do_removefunc(_,_,_,_,PublLD) ->
876
 
    PublLD.
877
 
%% -----------------------------------------------------------------------------
878
 
 
879
 
%% Function that, if the time has come, goes through the priv-ld structure and
880
 
%% cleans away entryn left behind. The usual cause is that the function call
881
 
%% caused an exception and there were therefore no matching return_from.
882
 
%% Returns {NewPrivLD,now()}.
883
 
throw_old_failed({M,F},PrivLD,PrevClean) ->
884
 
    case difference_in_now(PrevClean,now(),60) of % We clean once every minute.
885
 
        true ->
886
 
            case catch apply(M,F,[PrivLD]) of
887
 
                {'EXIT',_Reason} ->         % Something went wrong, ignore it.
888
 
                    {PrivLD,now()};         % Just keep the old priv-ld.
889
 
                NewPrivLD ->                % The function must return a priv-ld.
890
 
                    {NewPrivLD,now()}
891
 
            end;
892
 
        false ->                            % Not time yet!
893
 
            {PrivLD,PrevClean}
894
 
    end.
895
 
%% -----------------------------------------------------------------------------
896
 
 
897
 
%% Help function comparing two now timestamps. Returns true or false depending
898
 
%% on if S2 is more than DiffS seconds after S1. Only works for differences
899
 
%% less than 1 million seconds.
900
 
difference_in_now({MegaS1,S1,_},{MegaS2,S2,_},DiffS) ->
901
 
    if
902
 
        MegaS1+1<MegaS2 ->                  % More than 1 Mega sec. difference.
903
 
            true;
904
 
        MegaS1==MegaS2,S1+DiffS<S2 ->
905
 
            true;
906
 
        MegaS1+1==MegaS2,S1+DiffS<S2+1000000 ->
907
 
            true;
908
 
        true ->
909
 
            false
910
 
    end.
911
 
%% -----------------------------------------------------------------------------
912
 
 
913
 
%% This help function adds a {tracer,Tracer} to the enable-list in a 'trace'
914
 
%% match spec action. The reason for this is that the author of the a meta
915
 
%% match spec meant to turn tracing on for the process executing the match spec
916
 
%% can not know the tracer. This since the match spec is most likely authored
917
 
%% at the control component's node, and not here.
918
 
%% Note the double tuple necessary to make it just precise a tuple!
919
 
%% Returns a new match spec.
920
 
add_tracer([MS1|Rest],Tracer) ->
921
 
    [add_tracer_2(MS1,Tracer)|add_tracer(Rest,Tracer)];
922
 
add_tracer([],_) ->
923
 
    [];
924
 
add_tracer(NotList,_Tracer) ->              % Can be 'false', but also an error.
925
 
    NotList.
926
 
 
927
 
add_tracer_2({Head,Cond,Body},Tracer) ->
928
 
    {Head,Cond,add_tracer_3(Body,Tracer)};
929
 
add_tracer_2(Faulty,_Tracer) ->
930
 
    Faulty.
931
 
 
932
 
add_tracer_3([{trace,Disable,Enable}|Rest],Tracer) when list(Enable) ->
933
 
    [{trace,Disable,Enable++[{{tracer,Tracer}}]}|Rest];
934
 
add_tracer_3([ActionTerm|Rest],Tracer) ->
935
 
    [ActionTerm|add_tracer_3(Rest,Tracer)];
936
 
add_tracer_3([],_Tracer) ->
937
 
    [];
938
 
add_tracer_3(FaultyBody,_Tracer) ->
939
 
    FaultyBody.
940
 
%% -----------------------------------------------------------------------------
941
 
 
942
 
%% -----------------------------------------------------------------------------
943
 
%% Help functions handling internal loopdata.
944
 
%% -----------------------------------------------------------------------------
945
 
 
946
 
-record(ld,{init_publ_ld_mfa,               % {M,F,Args}
947
 
            remove_publ_ld_mf,              % {M,F} | void
948
 
            clean_publ_ld_mf,               % {Mod,Func}
949
 
            ms_mfarities=notable,           % ETS holding names match functions.
950
 
            call_mfarities=[],              % [{{M,F,Arity},2-TupleOrFun},...]
951
 
            return_mfarities=[],            % [{{M,F,Arity},2-TupleOrFun},...]
952
 
            remove_mfarities=[]
953
 
           }).
954
 
 
955
 
mk_new_ld(InitPublLDmfa,RemovePublLDmf,CleanPublLDmf,TId) ->
956
 
    #ld{
957
 
           init_publ_ld_mfa=InitPublLDmfa,
958
 
           remove_publ_ld_mf=RemovePublLDmf,
959
 
           clean_publ_ld_mf=CleanPublLDmf,
960
 
           ms_mfarities=TId
961
 
       }.
962
 
%% -----------------------------------------------------------------------------
963
 
 
964
 
%% Function which restores the internal loop data to somekind of initial state.
965
 
%% This is useful when tracing has been suspended.
966
 
reset_ld(#ld{init_publ_ld_mfa=InitPublLDmfa,
967
 
             remove_publ_ld_mf=RemovePublLDmf,
968
 
             clean_publ_ld_mf=CleanPublLDmf,
969
 
             ms_mfarities=TId}) ->
970
 
    ets:match_delete(TId,{'_','_'}),        % Empty the table.
971
 
    #ld{init_publ_ld_mfa=InitPublLDmfa,
972
 
        remove_publ_ld_mf=RemovePublLDmf,
973
 
        clean_publ_ld_mf=CleanPublLDmf,
974
 
        ms_mfarities=TId}.
975
 
%% -----------------------------------------------------------------------------
976
 
 
977
 
get_initpublldmfa_ld(#ld{init_publ_ld_mfa=InitPublLDmfa}) ->
978
 
    InitPublLDmfa.
979
 
%% -----------------------------------------------------------------------------
980
 
 
981
 
get_removepublldmf_ld(#ld{remove_publ_ld_mf=RemovePublLDmf}) ->
982
 
    RemovePublLDmf.
983
 
%% -----------------------------------------------------------------------------
984
 
 
985
 
get_cleanpublldmf_ld(#ld{clean_publ_ld_mf=CleanPublLDmf}) ->
986
 
    CleanPublLDmf.
987
 
%% -----------------------------------------------------------------------------
988
 
 
989
 
%% Help function adding data associated with a meta traced function to the
990
 
%% internal loopdata. Called when meta tracing is activated for M:F/Arity.
991
 
init_tpm_ld(M,F,Arity,CallFunc,ReturnFunc,RemoveFunc,LD) ->
992
 
    ets:insert(LD#ld.ms_mfarities,{{M,F,Arity},[]}),
993
 
    CallFuncs=LD#ld.call_mfarities,
994
 
    ReturnFuncs=LD#ld.return_mfarities,
995
 
    RemoveFuncs=LD#ld.remove_mfarities,
996
 
    LD#ld{call_mfarities=[{{M,F,Arity},CallFunc}|CallFuncs],
997
 
          return_mfarities=[{{M,F,Arity},ReturnFunc}|ReturnFuncs],
998
 
          remove_mfarities=[{{M,F,Arity},RemoveFunc}|RemoveFuncs]}.
999
 
%% -----------------------------------------------------------------------------
1000
 
 
1001
 
%% Help function which answers the question if we have already initiated the
1002
 
%% function. It is done by looking in the ETS-table with named match-functions.
1003
 
%% If there is an entry in the set-type table for M:F/Arity, the function is
1004
 
%% initiated.
1005
 
%% Returns 'yes' or 'no'.
1006
 
check_mfarity_exists(M,F,Arity) ->
1007
 
    case ets:lookup(?NAMED_MS_TAB,{M,F,Arity}) of
1008
 
        [] ->
1009
 
            no;
1010
 
        [_] ->
1011
 
            yes
1012
 
    end.
1013
 
%% -----------------------------------------------------------------------------
1014
 
 
1015
 
%% Help function adding an entry with [{MSname,MSlist}|MSsNames] for M:F/Arity.
1016
 
%% Note that any already existing entry is removed.
1017
 
%% Returns nothing significant.
1018
 
put_ms_ld(M,F,Arity,MSname,MS,MSsNames) ->
1019
 
    ets:insert(?NAMED_MS_TAB,{{M,F,Arity},[{MSname,MS}|MSsNames]}).
1020
 
%% -----------------------------------------------------------------------------
1021
 
 
1022
 
%% Help function taking a list of {MSname,MSs} and storing them in the
1023
 
%% internal loop data structure. The storage is actually implemented as an ETS
1024
 
%% table. Any previous list of {MSname,MSs} associated with this {M,F,Arity} will
1025
 
%% be lost. Returns nothing significant.
1026
 
set_ms_ld(M,F,Arity,MSsNames) ->
1027
 
    ets:insert(?NAMED_MS_TAB,{{M,F,Arity},MSsNames}).
1028
 
%% -----------------------------------------------------------------------------
1029
 
 
1030
 
%% Help function fetching a list of {MSname,MatchSpecs} for a M:F/Arity. The
1031
 
%% match-functions are stored in an ETS table searchable on {M,F,Arity}.
1032
 
get_ms_ld(M,F,Arity) ->
1033
 
    case ets:lookup(?NAMED_MS_TAB,{M,F,Arity}) of
1034
 
        [{_MFArity,MSsNames}] ->
1035
 
            MSsNames;
1036
 
        [] ->
1037
 
            []
1038
 
    end.
1039
 
%% -----------------------------------------------------------------------------
1040
 
 
1041
 
%% Help function removing all saved match-specs for a certain M:F/Arity.
1042
 
%% Returns a new loopdata structure.
1043
 
remove_ms_ld(M,F,Arity,LD) ->
1044
 
    ets:delete(LD#ld.ms_mfarities,{M,F,Arity}),
1045
 
    LD.
1046
 
%% -----------------------------------------------------------------------------
1047
 
 
1048
 
%% Help function which removes all information about a meta traced function from
1049
 
%% the internal loopdata. Returns a new loopdata structure.
1050
 
ctpm_ld(M,F,Arity,LD) ->
1051
 
    ets:delete(LD#ld.ms_mfarities,{M,F,Arity}),
1052
 
    NewCallFuncs=lists:keydelete({M,F,Arity},1,LD#ld.call_mfarities),
1053
 
    NewReturnFuncs=lists:keydelete({M,F,Arity},1,LD#ld.return_mfarities),
1054
 
    NewRemoveFuncs=lists:keydelete({M,F,Arity},1,LD#ld.remove_mfarities),
1055
 
    LD#ld{call_mfarities=NewCallFuncs,
1056
 
          return_mfarities=NewReturnFuncs,
1057
 
          remove_mfarities=NewRemoveFuncs}.
1058
 
%% -----------------------------------------------------------------------------
1059
 
 
1060
 
get_call_func_ld(M,F,Arity,#ld{call_mfarities=CallFuncs}) ->
1061
 
    case lists:keysearch({M,F,Arity},1,CallFuncs) of
1062
 
        {value,{_,MF}} ->
1063
 
            MF;
1064
 
        false ->
1065
 
            false
1066
 
    end.
1067
 
%% -----------------------------------------------------------------------------
1068
 
 
1069
 
get_return_func_ld(M,F,Arity,#ld{return_mfarities=CallFuncs}) ->
1070
 
    case lists:keysearch({M,F,Arity},1,CallFuncs) of
1071
 
        {value,{_,MF}} ->
1072
 
            MF;
1073
 
        false ->
1074
 
            false
1075
 
    end.
1076
 
%% -----------------------------------------------------------------------------
1077
 
 
1078
 
get_remove_func_ld(M,F,Arity,#ld{remove_mfarities=RemoveFuncs}) ->
1079
 
    case lists:keysearch({M,F,Arity},1,RemoveFuncs) of
1080
 
        {value,{_,MF}} ->
1081
 
            MF;
1082
 
        false ->
1083
 
            false
1084
 
    end.
1085
 
%% -----------------------------------------------------------------------------
1086
 
 
1087
 
%% Function returning a list of all {Mod,Func,Arity} which are currently meta
1088
 
%% traced. It does do by listifying the call_mfarities field in the internal
1089
 
%% loopdata.
1090
 
get_all_meta_funcs_ld(#ld{call_mfarities=CallFuncs}) ->
1091
 
    lists:map(fun({MFArity,_})->MFArity end,CallFuncs).
1092
 
%% -----------------------------------------------------------------------------
1093
 
 
1094
 
 
1095
 
%% =============================================================================
1096
 
%% Functions for the standard PublLD structure.
1097
 
%%
1098
 
%% It is tuple {Part1,GlobalData} where Part1 is of length at least 2.
1099
 
%% Where each field is a list of tuples. The last item in each tuple shall be
1100
 
%% a now tuple, making it possible to clean it away should it be too old to be
1101
 
%% relevant (there was no return_from message due to a failure).
1102
 
%% Other fields can be used for other functions.
1103
 
%% The GlobalData is not cleaned but instead meant to store data must be passed
1104
 
%% to each CallFunc when a meta trace message arrives.
1105
 
%% =============================================================================
1106
 
                      
1107
 
%% Function returning our standard priv-loopdata structure.
1108
 
init_std_publld(Size,GlobalData) ->
1109
 
    {list_to_tuple(lists:duplicate(Size,[])),GlobalData}.
1110
 
%% -----------------------------------------------------------------------------
1111
 
 
1112
 
%% Function capable of cleaning out a standard publ-ld. The last element of each
1113
 
%% tuple must be the now item.
1114
 
%% Returns a new publ-ld structure.
1115
 
clean_std_publld({Part1,GlobalData}) ->
1116
 
    {clean_std_publld_2(Part1,now(),tuple_size(Part1),[]),GlobalData}.
1117
 
 
1118
 
clean_std_publld_2(_,_,0,Accum) ->
1119
 
    list_to_tuple(Accum);
1120
 
clean_std_publld_2(PublLD,Now,Index,Accum) ->
1121
 
    NewTupleList=clean_std_publld_3(element(Index,PublLD),Now),
1122
 
    clean_std_publld_2(PublLD,Now,Index-1,[NewTupleList|Accum]).
1123
 
 
1124
 
clean_std_publld_3([Tuple|Rest],Now) ->
1125
 
    PrevNow=element(tuple_size(Tuple),Tuple), % Last item shall be the now item.
1126
 
    case difference_in_now(PrevNow,Now,30) of
1127
 
        true ->                             % Remove it then!
1128
 
            clean_std_publld_3(Rest,Now);
1129
 
        false ->                            % Keep it!
1130
 
            [Tuple|clean_std_publld_3(Rest,Now)]
1131
 
    end;
1132
 
clean_std_publld_3([],_) ->
1133
 
    [].
1134
 
%% -----------------------------------------------------------------------------
1135
 
 
1136
 
%% =============================================================================
1137
 
%% Functions used as handling functions (as funs) for registered process names.
1138
 
%% (Given that we use the standard priv-ld, otherwise you must do your own!).
1139
 
%% =============================================================================
1140
 
 
1141
 
%% Call-back for initializing the meta traced functions there are quick functions
1142
 
%% for. Returns a new public loop data structure.
1143
 
metafunc_init(erlang,register,2,{Part1,GlobalData}) ->
1144
 
    {setelement(1,Part1,[]),GlobalData}.
1145
 
%% -----------------------------------------------------------------------------
1146
 
 
1147
 
%% Call-function for erlang:register/2.
1148
 
%% This function adds the call to register/2 to a standard priv-ld structure.
1149
 
%% Note that we *must* search for previous entries from the same process. If such
1150
 
%% still in structure it means a failed register/2 call. It must first be removed
1151
 
%% so it can not be mixed up with this one. Since meta-trace message will arrive
1152
 
%% in order, there was no return_from message for that call if we are here now.
1153
 
local_register_call(CallingPid,{call,[Alias,Pid],TS},{Part1,GlobalData}) ->
1154
 
    TupleList=element(1,Part1),             % The register/2 entry in a std. priv-ld.
1155
 
    NewTupleList=lists:keydelete(CallingPid,1,TupleList), % If present, remove previous call.
1156
 
    {ok,
1157
 
     {setelement(1,Part1,[{CallingPid,{Alias,Pid},TS}|NewTupleList]),GlobalData},
1158
 
     void}.
1159
 
 
1160
 
%% Return-function for the erlang:register/2 BIF.
1161
 
%% This function formulates the output and removes the corresponding call entry
1162
 
%% from the standard priv-ld structure.
1163
 
local_register_return(CallingPid,{return_from,_Val,_TS},PublLD={Part1,GlobalData}) ->
1164
 
    TupleList=element(1,Part1),             % The register/2 entry in a std. priv-ld.
1165
 
    case lists:keysearch(CallingPid,1,TupleList) of
1166
 
        {value,{_,{Alias,Pid},NowTS}} ->
1167
 
            NewTupleList=lists:keydelete(CallingPid,1,TupleList),
1168
 
            {ok,
1169
 
             {setelement(1,Part1,NewTupleList),GlobalData},
1170
 
             term_to_binary({Pid,Alias,alias,NowTS})};
1171
 
        false ->                            % Strange, then don't know what to do.
1172
 
            {ok,PublLD,void}                % Do nothing seems safe.
1173
 
    end;
1174
 
local_register_return(CallingPid,{exception_from,_Val,_TS},{Part1,GlobalData}) ->
1175
 
    TupleList=element(1,Part1),             % The register/2 entry in a std. priv-ld.
1176
 
    NewTupleList=lists:keydelete(CallingPid,1,TupleList),
1177
 
    {ok,{setelement(1,Part1,NewTupleList),GlobalData},void}; % No association then.
1178
 
local_register_return(_,_,PublLD) ->        % Don't understand this.
1179
 
    {ok,PublLD,void}.
1180
 
 
1181
 
%% When unregister/1 us called we simply want a unalias entry in the ti-file.
1182
 
%% We can unfortunately not connect it with a certain pid.
1183
 
local_unregister_call(_CallingPid,{_TypeTag,[Alias],TS},PublLD) ->
1184
 
    {ok,PublLD,term_to_binary({undefined,Alias,unalias,TS})}.
1185
 
%% -----------------------------------------------------------------------------
1186
 
 
1187
 
%% Call-function for global:register_name/2,/3.
1188
 
%% This function is actually the call function for the handle_call/3 in the
1189
 
%% global server. Note that we must check that we only do this on the node
1190
 
%% where Pid actually resides.
1191
 
global_register_call(_CallingPid,{call,[{register,Alias,P,_},_,_],TS},PublLD)
1192
 
  when node(P)==node()->
1193
 
    {ok,PublLD,term_to_binary({P,{global,Alias},alias,TS})};
1194
 
global_register_call(_CallingPid,_,PublLD) ->
1195
 
    {ok,PublLD,void}.
1196
 
 
1197
 
%% Call-function for global:unregister_name. It acutally checks on the use of
1198
 
%% global:delete_global_name/2 which is called when ever a global name is removed.
1199
 
global_unregister_call(_CallingPid,{call,[Alias,P],TS},PublLD) when node(P)==node()->
1200
 
    {ok,PublLD,term_to_binary({P,{global,Alias},unalias,TS})};
1201
 
global_unregister_call(_CallingPid,_,PublLD) ->
1202
 
    {ok,PublLD,void}.
1203
 
%% -----------------------------------------------------------------------------
1204
 
 
1205
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2006-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%% Author: Lennart �hman, lennart.ohman@st.se
 
20
%%
 
21
%% This module implements the meta tracer process belonging to the
 
22
%% runtime component. Its main purpose is to write the ti-file (traceinformation).
 
23
%% The ti-file contains translations between process id:s and what ever "you"
 
24
%% want to read in the merged and formatted logfile.
 
25
%% This process interacts with the runtime component process.
 
26
%%
 
27
%% Currently it handles the following types of ti-files:
 
28
%%   Plain raw, binary log.
 
29
%%   Relay to other inviso_rt_meta process on another node.
 
30
%%
 
31
%% The TI file will be on binary format and each entry is:
 
32
%%   <<LengthIndicator:32, {Pid,Alias,Op,NowStamp} >>
 
33
%%       Pid=pid(), or if OP==unalias pid()|any_other_than_pid()
 
34
%%       Op=alias|unalias
 
35
%% -----------------------------------------------------------------------------
 
36
-module(inviso_rt_meta).
 
37
 
 
38
%% -----------------------------------------------------------------------------
 
39
%% API exports.
 
40
%% -----------------------------------------------------------------------------
 
41
 
 
42
-export([start/2,start/5]).
 
43
-export([stop/1,suspend/1]).
 
44
-export([init_tpm/5,init_tpm/8]).
 
45
-export([tpm/5,tpm/6,tpm/9,tpm_tracer/5,tpm_tracer/6,tpm_tracer/9]).
 
46
-export([tpm_ms/6,tpm_ms_tracer/6,ctpm_ms/5,ctpm/4]).
 
47
-export([local_register/1,global_register/1]).
 
48
-export([remove_local_register/1,remove_global_register/1]).
 
49
 
 
50
-export([write_ti/1]).
 
51
 
 
52
-export([get_tracer/0,tpm_ms/5,tpm_ms_tracer/5,list_tpm_ms/3,ctpm_ms/4]).
 
53
 
 
54
-export([metacast_call/5,metacast_return_from/6]).
 
55
-export([get_state/1]).
 
56
%% -----------------------------------------------------------------------------
 
57
 
 
58
%% -----------------------------------------------------------------------------
 
59
%% Internal exports.
 
60
%% -----------------------------------------------------------------------------
 
61
 
 
62
-export([init/6]).
 
63
-export([init_std_publld/2,clean_std_publld/1]).
 
64
%% -----------------------------------------------------------------------------
 
65
 
 
66
%% -----------------------------------------------------------------------------
 
67
%% Constants.
 
68
%% -----------------------------------------------------------------------------
 
69
 
 
70
-define(NAMED_MS_TAB,inviso_rt_meta_named_ms).
 
71
 
 
72
%% -----------------------------------------------------------------------------
 
73
 
 
74
 
 
75
%% =============================================================================
 
76
%% Exported API (Meant to be used by a runtime component).
 
77
%% =============================================================================
 
78
 
 
79
%% start(TiData,Tracer)={ok,Pid} | {error,Reason}
 
80
%% start(TiData,Tracer,InitPublLDmfa,RemovePublLDmfa,CleanPublLDmf)=
 
81
%%     {ok,Pid} | {error,Reason}
 
82
%%   TiData={file,FileName}|{relay,Node}
 
83
%%   Tracer=pid()|port()
 
84
%%   FileName=string()
 
85
%%   InitPublLDmfa={Mod,Func,ArgList}
 
86
%%   RemovePublLDmf={Mod,Func} | void
 
87
%%     RemovePublLDmf(PublLD)->nothing significant.
 
88
%%     These functions are called to create and destroy the public loopdata
 
89
%%     structure available to the meta-trace CallFunc and ReturnFunc.
 
90
%%   CleanPublLDmf={Mod,Func}
 
91
%%     This function will periodically be called to clean the public LD from
 
92
%%     pending meta-trace messages waiting for a corresponding return_from
 
93
%%     message.
 
94
%%
 
95
%% Starts a meta-tracer process, opening the ti-file specified in TiData. PublLD
 
96
%% is used to communicate data, typically between a call and return_from.
 
97
%% If no special initialization function is specified a standard one is used.
 
98
%% Note that the meta tracer function must know "who" is the regular tracer
 
99
%% (process or port). This because it must be possible to append {tracer,Tracer}
 
100
%% in meta match specs.
 
101
start(TiData,Tracer) ->
 
102
    Pid=spawn_link(?MODULE,
 
103
                   init,
 
104
                   [self(),
 
105
                    TiData,
 
106
                    Tracer,
 
107
                    {?MODULE,init_std_publld,[2,[]]},
 
108
                    void,
 
109
                    {?MODULE,clean_std_publld}]),
 
110
    wait_for_reply(Pid).
 
111
start(TiData,Tracer,InitPublLDmfa,RemovePublLDmf,CleanPublLDmf) ->
 
112
    Pid=spawn_link(?MODULE,
 
113
                   init,
 
114
                   [self(),TiData,Tracer,InitPublLDmfa,RemovePublLDmf,CleanPublLDmf]),
 
115
    wait_for_reply(Pid).
 
116
 
 
117
wait_for_reply(Pid) ->
 
118
    receive
 
119
        {Pid,ok} ->
 
120
            {ok,Pid};
 
121
        {Pid,{error,Reason}} ->
 
122
            {error,Reason}
 
123
    after
 
124
        10000 ->                             % After very long time.
 
125
            exit(Pid,kill),                  % It must be hanging.
 
126
            {error,time_out}
 
127
    end.
 
128
%% -----------------------------------------------------------------------------
 
129
 
 
130
%% stop(Pid)=ok
 
131
%%   Pid=Adders to the meta tracer, pid().
 
132
%% Shutsdown the metatracer.
 
133
stop(Pid) ->
 
134
    Pid ! {stop,self()},
 
135
    ok.
 
136
%% -----------------------------------------------------------------------------
 
137
 
 
138
%% suspend(Pid)=ok
 
139
%%   Pid=Adders to the meta tracer, pid().
 
140
%% Suspends the meta tracer by removing all meta trace patterns.
 
141
suspend(Pid) ->
 
142
    Pid ! {suspend,self()},
 
143
    ok.
 
144
%% -----------------------------------------------------------------------------
 
145
 
 
146
%% init_tpm(Pid,Mod,Func,Arity,CallFunc)=
 
147
%% init_tpm(Pid,Mod,Func,Arity,InitFunc,CallFunc,ReturnFunc,RemoveFunc)=ok|{error,Reason}.
 
148
%%   Pid=Address to meta tracer process, pid().
 
149
%%   Mod,Func=Pointing out the function which shall be meta traced, atom().
 
150
%%   Arity=As above, integer().
 
151
%%   InitFunc,RemoveFunc={Module,Function}|fun(), functions being called when
 
152
%%     to initialize the public loopdata structure, and to reset it.
 
153
%%       InitFunc(Mod,Func,Arity,PublLD)->{ok,NewPublLD,Output}
 
154
%%         Supposed to initialize whatever needs to be done before
 
155
%%         handling any incoming meta-trace message for the Mod:Func/Arity.
 
156
%%       RemoveFunc(Mod,Func,Arity,PublLD)->{ok,NewPublLD}
 
157
%%         Called when meta tracing of Mod:Func/Arity is stopped. It is supposed
 
158
%%         to clear datastructures away from the PublLD.
 
159
%% Initializes the public loopdata for this function. Note that we can not use wildcards
 
160
%% here (even if it is perfectly legal in Erlang). It also sets the CallFunc and
 
161
%% ReturnFunc for the meta traced function. The function is hence ready to be
 
162
%% meta traced with either tpm/5 or tpm_ms/5.
 
163
%% This function is synchronous, waiting for a reply from the meta server.
 
164
init_tpm(Pid,Mod,Func,Arity,CallFunc) ->
 
165
    init_tpm(Pid,Mod,Func,Arity,void,CallFunc,void,void).
 
166
init_tpm(Pid,Mod,Func,Arity,InitFunc,CallFunc,ReturnFunc,RemoveFunc) ->
 
167
    send_wait(Pid,
 
168
              {init_tpm,{Mod,Func,Arity},InitFunc,CallFunc,ReturnFunc,RemoveFunc}).
 
169
%% -----------------------------------------------------------------------------
 
170
 
 
171
%% tpm(Pid,Mod,Func,Arity,MatchSpec)={ok,N}|{error,Reason}
 
172
%% tpm(Pid,Mod,Func,Arity,MatchSpec,CallFunc)={ok,N}|{error,Reason}
 
173
%% tpm(Pid,Mod,Func,Arity,MatchSpec,InitFunc,CallFunc,ReturnFunc,RemoveFunc)=
 
174
%%   Pid=Address to meta tracer process, pid().
 
175
%%   Mod,Func=Pointing out the function which shall be meta traced, atom().
 
176
%%   Arity=As above, integer().
 
177
%%   MatchSpec=List of match specification, possibly empty. Remember {return_trace}
 
178
%%     if expecting return_from messages.
 
179
%%   InitFunc,CallFunc,ReturnFunc,RemoveFunc={Module,Function}|fun(),
 
180
%%     functions being called when these functions are called by the meta trace
 
181
%%     server at certain events.
 
182
%%       CallFunc(CallingPid,ActualArgList,PublLD)->{ok,NewPrivLD,Output}
 
183
%%       ReturnFunc(CallingPid,ReturnValue,PublLD)->{ok,NewPrivLD,Output}
 
184
%%         When a call respectively return_from trace message arrives for the meta
 
185
%%         traced function, the corresponding function is called.
 
186
%%         The ReturnFunc must handle the fact that a return_from message arrives
 
187
%%         for a call which was never noticed. This because the message queue of the
 
188
%%         meta tracer may have been emptied.
 
189
%%   Reason=badarg | 
 
190
%%   Output=Characters to be written to the ti-file, bin() | 'void'
 
191
%% The tpm/5 function simply starts meta tracing for the function. It must
 
192
%% previously have been initialized.
 
193
%% tpm/6 & /9 initializes the function and starts meta tracing.
 
194
tpm(Pid,Mod,Func,Arity,MatchSpec)
 
195
  when is_atom(Mod),is_atom(Func),is_integer(Arity),is_list(MatchSpec),Mod/='_',Func/='_'->
 
196
    send_wait(Pid,{tpm,{Mod,Func,Arity,MatchSpec}});
 
197
tpm(_,_,_,_,_) ->
 
198
    {error,badarg}.
 
199
 
 
200
tpm(Pid,Mod,Func,Arity,MatchSpec,CallFunc) ->
 
201
    tpm(Pid,Mod,Func,Arity,MatchSpec,void,CallFunc,void,void).
 
202
 
 
203
tpm(Pid,Mod,Func,Arity,MatchSpec,InitFunc,CallFunc,ReturnFunc,RemoveFunc)
 
204
  when is_atom(Mod),is_atom(Func),is_integer(Arity),is_list(MatchSpec),Mod/='_',Func/='_' ->
 
205
    send_wait(Pid,{tpm,{Mod,Func,Arity,MatchSpec},InitFunc,CallFunc,ReturnFunc,RemoveFunc});
 
206
tpm(_,_,_,_,_,_,_,_,_) ->
 
207
    {error,badarg}.
 
208
%% -----------------------------------------------------------------------------
 
209
 
 
210
%% Same as tpm/X but the meta tracer will automatically append {tracer,Tracer}
 
211
%% to the enable list in a {trace,Disable,Enable} match spec action term.
 
212
tpm_tracer(Pid,Mod,Func,Arity,MatchSpec)
 
213
  when is_atom(Mod),is_atom(Func),is_integer(Arity),is_list(MatchSpec),Mod/='_',Func/='_'->
 
214
    send_wait(Pid,{tpm_tracer,{Mod,Func,Arity,MatchSpec}});
 
215
tpm_tracer(_,_,_,_,_) ->
 
216
    {error,badarg}.
 
217
 
 
218
tpm_tracer(Pid,Mod,Func,Arity,MatchSpec,CallFunc) ->
 
219
    tpm_tracer(Pid,Mod,Func,Arity,MatchSpec,void,CallFunc,void,void).
 
220
 
 
221
tpm_tracer(Pid,Mod,Func,Arity,MatchSpec,InitFunc,CallFunc,ReturnFunc,RemoveFunc)
 
222
  when is_atom(Mod),is_atom(Func),is_integer(Arity),is_list(MatchSpec),Mod/='_',Func/='_' ->
 
223
    send_wait(Pid,{tpm_tracer,
 
224
                   {Mod,Func,Arity,MatchSpec},
 
225
                   InitFunc,CallFunc,ReturnFunc,RemoveFunc});
 
226
tpm_tracer(_,_,_,_,_,_,_,_,_) ->
 
227
    {error,badarg}.
 
228
%% -----------------------------------------------------------------------------
 
229
 
 
230
%% tpm_ms(Pid,Mod,Func,Arity,MSname,MS)={ok,N}|{error,Reason}
 
231
%%   Pid=Address to meta tracer process, pid().
 
232
%%   Mod,Func=Pointing out the function to which we shall add a match-spec., atom().
 
233
%%   Arity=As above, integer().
 
234
%%   MSname=A name to be used if this MS shall be removed later. term().
 
235
%%   MatchSpec=List of match specification, Remember {return_trace}
 
236
%%     if expecting return_from messages.
 
237
%% This function adds a list of match-specs to the already existing ones. It
 
238
%% uses an internal database to keep track of existing match-specs. If the
 
239
%% match-spec does not result in any meta traced functions (for whatever reason),
 
240
%% the MS is not saved in the database. The previously known match-specs are
 
241
%% not removed.
 
242
tpm_ms(Pid,Mod,Func,Arity,MSname,MS) ->
 
243
    send_wait(Pid,{tpm_ms,{Mod,Func,Arity},MSname,MS}).
 
244
%% -----------------------------------------------------------------------------
 
245
 
 
246
%% Same as tpm_ms/6 but the meta tracer will automatically append {tracer,Tracer}
 
247
%% to the enable list in a {trace,Disable,Enable} match spec action term.
 
248
tpm_ms_tracer(Pid,Mod,Func,Arity,MSname,MS) ->
 
249
    send_wait(Pid,{tpm_ms_tracer,{Mod,Func,Arity},MSname,MS}).
 
250
%% -----------------------------------------------------------------------------
 
251
 
 
252
%% ctpm_ms(Pid,Mod,Func,Arity)=ok
 
253
%%
 
254
%% Removes a names match-spec from the meta traced function. Note that is never
 
255
%% a fault to remove an MS. Not even from a function which is non existant.
 
256
ctpm_ms(Pid,Mod,Func,Arity,MSname) ->
 
257
    send_wait(Pid,{ctpm_ms,{Mod,Func,Arity},MSname}).
 
258
%% -----------------------------------------------------------------------------
 
259
 
 
260
%% Quick versions for erlang:register/2 which also uses a default CallFunc
 
261
%% and a default ReturnFunc.
 
262
local_register(Pid) ->
 
263
    Res1=tpm(Pid,
 
264
             erlang,register,2,[{'_',[],[{exception_trace}]}],
 
265
             fun metafunc_init/4,fun local_register_call/3,
 
266
             fun local_register_return/3,void),
 
267
    Res2=tpm(Pid,
 
268
             erlang,unregister,1,[],
 
269
             void,fun local_unregister_call/3,void,void),
 
270
    {Res1,Res2}.
 
271
%% -----------------------------------------------------------------------------
 
272
 
 
273
%% Quick version for global:register_name/2, /3.
 
274
global_register(Pid) ->
 
275
    Res1=tpm(Pid,global,handle_call,3,[{[{register,'_','_','_'},'_','_'],[],[]}],
 
276
        void,fun global_register_call/3,void,void),
 
277
    Res2=tpm(Pid,global,delete_global_name,2,[],
 
278
             void,fun global_unregister_call/3,void,void),
 
279
    {Res1,Res2}.
 
280
%% -----------------------------------------------------------------------------
 
281
 
 
282
%% ctpm(Pid,Mod,Func,Arity)=ok|{error,bad_mfa}
 
283
%%
 
284
%% Removes the meta trace pattern for the function, means stops generating output
 
285
%% for this function. The public LD may be cleared by the previously entered
 
286
%% RemoveFunc.
 
287
ctpm(Pid,Mod,Func,Arity) ->
 
288
    send_wait(Pid,{ctpm,{Mod,Func,Arity}}).
 
289
%% -----------------------------------------------------------------------------
 
290
 
 
291
%% remove_local_register(Pid)={Res1,Res2}
 
292
%%   Res1,Res2=ok|{error,Reason}
 
293
remove_local_register(Pid) ->
 
294
    Res1=ctpm(Pid,erlang,register,2),
 
295
    Res2=ctpm(Pid,erlang,unregister,1),
 
296
    {Res1,Res2}.
 
297
%% -----------------------------------------------------------------------------
 
298
 
 
299
%% remove_global_register(Pid)={Res1,Res2}
 
300
%%   Res1,Res2=ok|{error,Reason}
 
301
remove_global_register(Pid) ->
 
302
    Res1=ctpm(Pid,global,handle_call,3),
 
303
    Res2=ctpm(Pid,global,delete_global_name,2),
 
304
    {Res1,Res2}.
 
305
%% -----------------------------------------------------------------------------
 
306
 
 
307
%% Exported help functions which may be used in programming CallFunc and/or
 
308
%% ReturnFunc. Useful if the call is done on one node but must trigger the
 
309
%% start of something at other nodes.
 
310
metacast_call(Nodes,OrigPid,M,F,Args) ->
 
311
    multicast(Nodes,{trace_ts,OrigPid,call,{M,F,Args},void}),
 
312
    ok.
 
313
 
 
314
metacast_return_from(Nodes,OrigPid,M,F,Arity,Value) ->
 
315
    multicast(Nodes,{trace_ts,OrigPid,return_from,{M,F,Arity},Value,void}),
 
316
    ok.
 
317
 
 
318
multicast([Node|Rest],Msg) ->
 
319
    {?MODULE,Node} ! Msg,
 
320
    multicast(Rest,Msg);
 
321
multicast([],_) ->
 
322
    true.
 
323
%% -----------------------------------------------------------------------------
 
324
 
 
325
%% get_states(Pid)={ok,LD,PubLD}.
 
326
get_state(Pid) ->
 
327
    send_wait(Pid,get_state).
 
328
%% -----------------------------------------------------------------------------
 
329
 
 
330
 
 
331
send_wait(To,Msg) ->
 
332
    Ref=make_ref(),
 
333
    MRef=erlang:monitor(process,To),
 
334
    To ! {Msg,Ref,self()},
 
335
    receive
 
336
        {inviso_rt_meta_reply,Ref,Reply} ->
 
337
            erlang:demonitor(MRef),
 
338
            Reply;
 
339
        {'DOWN',MRef,_,_To,_Reason} ->
 
340
            {error,no_metatracer}
 
341
    end.
 
342
 
 
343
reply(To,Ref,Reply) ->
 
344
    To ! {inviso_rt_meta_reply,Ref,Reply}.
 
345
%% -----------------------------------------------------------------------------
 
346
 
 
347
%% =============================================================================
 
348
%% Special API.
 
349
%% =============================================================================
 
350
 
 
351
%% write_ti(OutPut)=
 
352
%%   OutPut=binary()
 
353
%% Makes an extra entry into the trace information file (ti-file). This is useful
 
354
%% if a pid-alias association is learned in another way than through a meta traced
 
355
%% function call. Note that this API can only be used locally at the node in
 
356
%% question.
 
357
write_ti(OutPut) ->
 
358
    catch ?MODULE ! {write_ti,OutPut}.
 
359
%% -----------------------------------------------------------------------------
 
360
 
 
361
 
 
362
%% =============================================================================
 
363
%% API intended to be used on CallFuncs and RemoveFuncs.
 
364
%% =============================================================================
 
365
 
 
366
%% The reason there must be a special API for CallFuncs and RemoveFuncs are is
 
367
%% that those functions are executed inside *this* process context. Hence they
 
368
%% can not make function calls requiering this process to receive messages.
 
369
 
 
370
%% Returns the tracer used for regular tracing. The reason this is implemented
 
371
%% in this way is that this function is intended to be used in meta trace call-
 
372
%% back functions. And there we can not have message passing API:s to the meta
 
373
%% trace(!).
 
374
get_tracer() ->
 
375
    get(tracer).
 
376
%% -----------------------------------------------------------------------------
 
377
 
 
378
%% Function equivalent to inviso_rt:tpm_ms/6. This function can *only* be used
 
379
%% inside a CallFunc or a RemoveFunc.
 
380
tpm_ms(Mod,Func,Arity,MSname,MS) ->
 
381
    case check_mfarity_exists(Mod,Func,Arity) of
 
382
        yes ->                               % Ok, and args must be ok then also.
 
383
            {ok,h_tpm_ms(Mod,Func,Arity,MSname,MS)};
 
384
        no ->
 
385
            {error,not_initiated}
 
386
    end.
 
387
%% -----------------------------------------------------------------------------
 
388
 
 
389
tpm_ms_tracer(Mod,Func,Arity,MSname,MS) ->
 
390
    case check_mfarity_exists(Mod,Func,Arity) of
 
391
        yes ->                               % Ok, and args must be ok then also.
 
392
            NewMS=add_tracer(MS,get_tracer()),
 
393
            {ok,h_tpm_ms(Mod,Func,Arity,MSname,NewMS)};
 
394
        no ->
 
395
            {error,not_initiated}
 
396
    end.
 
397
%% -----------------------------------------------------------------------------
 
398
 
 
399
%% Function that returns all MSname in use for Mod:Func/Arity
 
400
list_tpm_ms(Mod,Func,Arity) ->
 
401
    {ok,h_list_tpm_ms(Mod,Func,Arity)}.
 
402
%% -----------------------------------------------------------------------------
 
403
 
 
404
%% Function equivalent to inviso_rt:ctpm_ms/5. This function can *only* be used
 
405
%% inside a CallFunc or a RemoveFunc.
 
406
ctpm_ms(Mod,Func,Arity,MSname) ->
 
407
    h_ctpm_ms(Mod,Func,Arity,MSname),
 
408
    ok.
 
409
%% -----------------------------------------------------------------------------
 
410
 
 
411
 
 
412
%% =============================================================================
 
413
%% The server implemenation.
 
414
%% =============================================================================
 
415
 
 
416
init(Parent,TiData,Tracer,InitPublLDmfa,RemovePublLDmf,CleanPublLDmf) ->
 
417
    process_flag(priority,high),            % Since we may receive from many procs.
 
418
    register(?MODULE,self()),               % So we can act as relay receiver.
 
419
    case open_traceinfo_file(TiData) of
 
420
        {ok,TI} ->                          % The ti.-file.
 
421
            TId=ets:new(?NAMED_MS_TAB,[named_table,set,protected]),
 
422
            PublLD=do_init_publ_ld(InitPublLDmfa),
 
423
            Parent ! {self(),ok},
 
424
            put(tracer,Tracer),             % Uggly quick fix!
 
425
            loop(Parent,
 
426
                 Tracer,
 
427
                 TI,
 
428
                 mk_new_ld(InitPublLDmfa,RemovePublLDmf,CleanPublLDmf,TId),
 
429
                 PublLD,
 
430
                 now());
 
431
        {error,Reason} ->
 
432
            Parent ! {self(),{error,Reason}}
 
433
    end.
 
434
%% -----------------------------------------------------------------------------
 
435
 
 
436
loop(Parent,Tracer,TI,LD,PrevPublLD,PrevCleanTime) ->
 
437
    {PublLD,CleanTime}=throw_old_failed(get_cleanpublldmf_ld(LD),PrevPublLD,PrevCleanTime),
 
438
    receive
 
439
        {{init_tpm,{Mod,Func,Arity},InitFunc,CallFunc,ReturnFunc,RemoveFunc},Ref,Parent} ->
 
440
            case check_mfarity_exists(Mod,Func,Arity) of
 
441
                no ->                       % Good then we can add it!
 
442
                    case check_tpm_args(Mod,Func,Arity) of
 
443
                        true ->             % Args are ok.
 
444
                            {NewLD,NewPublLD}=
 
445
                                h_init_tpm(Mod,Func,Arity,
 
446
                                           InitFunc,CallFunc,ReturnFunc,RemoveFunc,
 
447
                                           TI,LD,PublLD),
 
448
                            reply(Parent,Ref,ok),
 
449
                            loop(Parent,Tracer,TI,NewLD,NewPublLD,CleanTime);
 
450
                        false ->            % Faulty arguments,
 
451
                            reply(Parent,Ref,{error,bad_mfa}),
 
452
                            loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
 
453
                    end;
 
454
                yes ->                      % If it already exists, cant init again.
 
455
                    reply(Parent,Ref,{error,already_initiated}),
 
456
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
 
457
            end;
 
458
        {{tpm,{Mod,Func,Arity,MS},InitFunc,CallFunc,ReturnFunc,RemoveFunc},Ref,Parent} ->
 
459
            case check_mfarity_exists(Mod,Func,Arity) of
 
460
                no ->                       % Good then we can add it!
 
461
                    case check_tpm_args(Mod,Func,Arity) of
 
462
                        true ->             % Args are ok.
 
463
                            {NewLD,NewPublLD,N}=
 
464
                                h_tpm(Mod,Func,Arity,MS,
 
465
                                      InitFunc,CallFunc,ReturnFunc,RemoveFunc,
 
466
                                      TI,LD,PublLD),
 
467
                            reply(Parent,Ref,{ok,N}),
 
468
                            loop(Parent,Tracer,TI,NewLD,NewPublLD,CleanTime);
 
469
                        false ->
 
470
                            reply(Parent,Ref,{error,bad_mfa}),
 
471
                            loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
 
472
                    end;
 
473
                yes ->
 
474
                    reply(Parent,Ref,{error,already_initiated}),
 
475
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
 
476
            end;
 
477
        {{tpm,{Mod,Func,Arity,MS}},Ref,Parent} ->
 
478
            case check_mfarity_exists(Mod,Func,Arity) of
 
479
                yes ->                      % Ok, and args must be ok then also.
 
480
                    {NewLD,N}=h_tpm(Mod,Func,Arity,MS,LD),
 
481
                    reply(Parent,Ref,{ok,N}),
 
482
                    loop(Parent,Tracer,TI,NewLD,PublLD,CleanTime);
 
483
                no ->                       % Must be initiated before.
 
484
                    reply(Parent,Ref,{error,not_initiated}),
 
485
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
 
486
            end;
 
487
        {{tpm_tracer,{Mod,Func,Arity,MS},InitFunc,CallFunc,ReturnFunc,RemoveFunc},Ref,Parent} ->
 
488
            case check_mfarity_exists(Mod,Func,Arity) of
 
489
                no ->                       % Good then we can add it!
 
490
                    case check_tpm_args(Mod,Func,Arity) of
 
491
                        true ->             % Args are ok.
 
492
                            NewMS=add_tracer(MS,Tracer),
 
493
                            {NewLD,NewPublLD,N}=
 
494
                                h_tpm(Mod,Func,Arity,NewMS,
 
495
                                      InitFunc,CallFunc,ReturnFunc,RemoveFunc,
 
496
                                      TI,LD,PublLD),
 
497
                            reply(Parent,Ref,{ok,N}),
 
498
                            loop(Parent,Tracer,TI,NewLD,NewPublLD,CleanTime);
 
499
                        false ->
 
500
                            reply(Parent,Ref,{error,bad_mfa}),
 
501
                            loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
 
502
                    end;
 
503
                yes ->
 
504
                    reply(Parent,Ref,{error,already_initiated}),
 
505
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
 
506
            end;
 
507
        {{tpm_tracer,{Mod,Func,Arity,MS}},Ref,Parent} ->
 
508
            case check_mfarity_exists(Mod,Func,Arity) of
 
509
                yes ->                      % Ok, and args must be ok then also.
 
510
                    NewMS=add_tracer(MS,Tracer),
 
511
                    {NewLD,N}=h_tpm(Mod,Func,Arity,NewMS,LD),
 
512
                    reply(Parent,Ref,{ok,N}),
 
513
                    loop(Parent,Tracer,TI,NewLD,PublLD,CleanTime);
 
514
                no ->                       % Must be initiated before.
 
515
                    reply(Parent,Ref,{error,not_initiated}),
 
516
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
 
517
            end;
 
518
        {{tpm_ms,{Mod,Func,Arity},MSname,MS},Ref,Parent} ->
 
519
            case check_mfarity_exists(Mod,Func,Arity) of
 
520
                yes ->                      % Ok, and args must be ok then also.
 
521
                    reply(Parent,Ref,{ok,h_tpm_ms(Mod,Func,Arity,MSname,MS)}),
 
522
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime);
 
523
                no ->
 
524
                    reply(Parent,Ref,{error,not_initiated}),
 
525
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
 
526
            end;
 
527
        {{tpm_ms_tracer,{Mod,Func,Arity},MSname,MS},Ref,Parent} ->
 
528
            case check_mfarity_exists(Mod,Func,Arity) of
 
529
                yes ->                      % Ok, and args must be ok then also.
 
530
                    NewMS=add_tracer(MS,Tracer),
 
531
                    reply(Parent,Ref,{ok,h_tpm_ms(Mod,Func,Arity,MSname,NewMS)}),
 
532
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime);
 
533
                no ->
 
534
                    reply(Parent,Ref,{error,not_initiated}),
 
535
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
 
536
            end;
 
537
        {{ctpm_ms,{Mod,Func,Arity},MSname},Ref,Parent} ->
 
538
            reply(Parent,Ref,ok),
 
539
            h_ctpm_ms(Mod,Func,Arity,MSname),
 
540
            loop(Parent,Tracer,TI,LD,PublLD,CleanTime);
 
541
        {{ctpm,{Mod,Func,Arity}},Ref,Parent} ->
 
542
            case get_remove_func_ld(Mod,Func,Arity,LD) of
 
543
                false ->                    % Incorrect Mod:Func/Arity!
 
544
                    reply(Parent,Ref,{error,bad_mfa}),
 
545
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime); % Do nothing!
 
546
                MF ->                       % {M,F}, Func or 'void'.
 
547
                    catch erlang:trace_pattern({Mod,Func,Arity},false,[meta]),
 
548
                    NewPublLD=do_removefunc(MF,Mod,Func,Arity,PublLD),
 
549
                    NewLD=ctpm_ld(Mod,Func,Arity,LD),
 
550
                    reply(Parent,Ref,ok),
 
551
                    loop(Parent,Tracer,TI,NewLD,NewPublLD,CleanTime)
 
552
            end;
 
553
        {suspend,Parent} ->                 % Removes all meta trace patterns.
 
554
            stop_all_meta_tracing(get_all_meta_funcs_ld(LD),PublLD,LD),
 
555
            do_remove_publ_ld(get_removepublldmf_ld(LD),PublLD),
 
556
            NewPublLD=do_init_publ_ld(get_initpublldmfa_ld(LD)),
 
557
            loop(Parent,Tracer,TI,reset_ld(LD),NewPublLD,CleanTime);
 
558
        {stop,Parent} ->                    % Make a controlled shutdown.
 
559
            stop_all_meta_tracing(get_all_meta_funcs_ld(LD),PublLD,LD),
 
560
            do_remove_publ_ld(get_removepublldmf_ld(LD),PublLD),
 
561
            close_traceinfo_file(TI);       % And then simply terminate.
 
562
        {trace_ts,Pid,call,{M,F,Args},TS} ->
 
563
            case handle_meta(get_call_func_ld(M,F,length(Args),LD),Pid,{call,Args,TS},PublLD) of
 
564
                {ok,NewPublLD,Output} when is_binary(Output);is_list(Output) ->
 
565
                    write_output(TI,Output),
 
566
                    loop(Parent,Tracer,TI,LD,NewPublLD,CleanTime);
 
567
                {ok,NewPublLD,_} ->         % No output to the ti-file this time.
 
568
                    loop(Parent,Tracer,TI,LD,NewPublLD,CleanTime);
 
569
                _ ->                        % Not handled correct, not much to do.
 
570
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
 
571
            end;
 
572
        {trace_ts,Pid,TypeTag,{M,F,Arity},Value,TS}
 
573
          when TypeTag==return_from;TypeTag==exception_from ->
 
574
            case handle_meta(get_return_func_ld(M,F,Arity,LD),Pid,{TypeTag,Value,TS},PublLD) of
 
575
                {ok,NewPublLD,Output} when is_binary(Output);is_list(Output) ->
 
576
                    write_output(TI,Output),
 
577
                    loop(Parent,Tracer,TI,LD,NewPublLD,CleanTime);
 
578
                {ok,NewPublLD,_} ->         % No output to the ti-file this time.
 
579
                    loop(Parent,Tracer,TI,LD,NewPublLD,CleanTime);
 
580
                _ ->                        % Not handled correct, not much to do.
 
581
                    loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
 
582
            end;
 
583
        {relayed_meta,Bin} ->
 
584
            write_output(TI,Bin),
 
585
            loop(Parent,Tracer,TI,LD,PublLD,CleanTime);
 
586
        {write_ti,OutPut} ->
 
587
            write_output(TI,OutPut),
 
588
            loop(Parent,Tracer,TI,LD,PublLD,CleanTime);
 
589
        {get_state,Ref,From} ->             % Debug function.
 
590
            reply(From,Ref,{ok,LD,PublLD}),
 
591
            loop(Parent,Tracer,TI,LD,PublLD,CleanTime);
 
592
        _Other ->
 
593
            loop(Parent,Tracer,TI,LD,PublLD,CleanTime)
 
594
    end.
 
595
 
 
596
 
 
597
%% =============================================================================
 
598
%% First level help functions.
 
599
%% =============================================================================
 
600
 
 
601
%% Function which opens the trace-information file(s). It must understand
 
602
%% the tidata specification which is part of the tracerdata given to the
 
603
%% runtime component during init_tracing.
 
604
%% It must return an internal notation of the time of file open and a
 
605
%% useful descriptor the write_output function can use.
 
606
%% Returns {ok,TiDescriptor} or {error,Reason}.
 
607
open_traceinfo_file({file,FileName}) ->     % A plain raw binary file.
 
608
    case file:open(FileName,[write,raw,binary]) of
 
609
        {ok,FD} ->
 
610
            {ok,{file,FD}};
 
611
        {error,Reason} ->
 
612
            {error,{open,[FileName,Reason]}}
 
613
    end;
 
614
open_traceinfo_file({relay,ToNode}) ->      % Use distributed Erlang.
 
615
    {ok,{relay,ToNode}};
 
616
open_traceinfo_file(IncorrectTI) ->
 
617
    {error,{badarg,IncorrectTI}}.
 
618
%% -----------------------------------------------------------------------------
 
619
 
 
620
close_traceinfo_file({file,FD}) ->
 
621
    file:close(FD);
 
622
close_traceinfo_file(_) ->
 
623
    ok.
 
624
%% -----------------------------------------------------------------------------
 
625
 
 
626
%% Help function handling initializing meta tracing of a function.
 
627
%% Returns {NewLD,NewPublLD}.
 
628
h_init_tpm(Mod,Func,Arity,InitFunc,CallFunc,ReturnFunc,RemoveFunc,TI,LD,PublLD) ->
 
629
    case do_initfunc(InitFunc,Mod,Func,Arity,PublLD) of
 
630
        {NewPublLD,Output} ->
 
631
            write_output(TI,Output),
 
632
            NewLD=init_tpm_ld(Mod,Func,Arity,CallFunc,ReturnFunc,RemoveFunc,LD),
 
633
            {NewLD,NewPublLD};
 
634
        false ->                            % The initfunc did not do anything.
 
635
            NewLD=init_tpm_ld(Mod,Func,Arity,CallFunc,ReturnFunc,RemoveFunc,LD),
 
636
            {NewLD,PublLD}
 
637
    end.
 
638
%% -----------------------------------------------------------------------------
 
639
 
 
640
%% Help function handling initializing meta tracing of a function and also
 
641
%% set the meta trace pattern as specified.
 
642
%% Returns {NewLD,NewPublLD,N}.
 
643
h_tpm(Mod,Func,Arity,MS,InitFunc,CallFunc,ReturnFunc,RemoveFunc,TI,LD,PublLD) ->
 
644
    {NewLD,NewPublLD}=
 
645
        h_init_tpm(Mod,Func,Arity,InitFunc,CallFunc,ReturnFunc,RemoveFunc,TI,LD,PublLD),
 
646
    case set_meta_tracing(Mod,Func,Arity,MS) of
 
647
        true ->                              % Ok, set one pattern.
 
648
            {NewLD,NewPublLD,1};
 
649
        false ->
 
650
            {NewLD,NewPublLD,0}
 
651
    end.
 
652
%% -----------------------------------------------------------------------------
 
653
 
 
654
%% Help function handling setting meta trace patter for a function which has
 
655
%% already been intialized. Note that we must remove all potentially stored
 
656
%% match-specs, if this function has been given match-specs before with
 
657
%% tpm_ms.
 
658
%% Returns a {NewLD,N}.
 
659
h_tpm(Mod,Func,Arity,MS,LD) ->
 
660
    case set_meta_tracing(Mod,Func,Arity,MS) of
 
661
        true ->
 
662
            {remove_ms_ld(Mod,Func,Arity,LD),1};
 
663
        false ->
 
664
            {LD,0}
 
665
    end.
 
666
%% -----------------------------------------------------------------------------
 
667
 
 
668
%% Help function that adds a match-spec to Mod:Func/Arity. It is not defined
 
669
%% in which order the match-specs will be given to the BIF.
 
670
%% Note that if an MS with the same name as an exiting is inserted, the previous
 
671
%% match-spec will be removed.
 
672
%% Very important to realise is that the empty meta match spec [] imposes no
 
673
%% restrictions what so ever on the generating of meta trace call messages.
 
674
%% Uncontrolled sending of such messages may quickly drain power from the system.
 
675
%% Since an empty match-spec will "disappear" when added to other match specs,
 
676
%% the empty match is transformed to what it actually is: [{'_',[],[]}].
 
677
%% Returns 0 or 1 indicating failure or success.
 
678
h_tpm_ms(Mod,Func,Arity,MSname,MS) ->
 
679
    MSsNames=get_ms_ld(Mod,Func,Arity),     % Fetch all previous match-specs.
 
680
    TransformedMS=h_tpm_ms_convert_null_ms(MS),
 
681
    MSsNames1=lists:keydelete(MSname,1,MSsNames), % If it already existed, it is gone!
 
682
    NewMSs=lists:flatten([TransformedMS,lists:map(fun({_Name,MSx})->MSx end,MSsNames1)]),
 
683
    case set_meta_tracing(Mod,Func,Arity,NewMSs) of
 
684
        true ->                             % We only save the MS if it was good.
 
685
            put_ms_ld(Mod,Func,Arity,MSname,TransformedMS,MSsNames1),
 
686
            1;
 
687
        false ->
 
688
            0
 
689
    end.
 
690
 
 
691
%% Help function converting the null match spec into, still a null match spec,
 
692
%% on a proper match spec format. This because it will otherwise be difficult
 
693
%% to see the difference between no active tpm_ms and all a set of null ms.
 
694
h_tpm_ms_convert_null_ms([]) ->
 
695
    [{'_',[],[]}];
 
696
h_tpm_ms_convert_null_ms(MS) ->
 
697
    MS.
 
698
%% -----------------------------------------------------------------------------
 
699
 
 
700
%% Help function returning a list of all names used for match-functions for
 
701
%% the Mod:Func/Arity in question.
 
702
h_list_tpm_ms(Mod,Func,Arity) ->
 
703
    MSsNames=get_ms_ld(Mod,Func,Arity),     % A list of {MSname,MS}.
 
704
    lists:map(fun({MSname,_})->MSname end,MSsNames).
 
705
%% -----------------------------------------------------------------------------
 
706
 
 
707
%% Function that removes a named match-spec. Returns nothing significant.
 
708
%% Note that if we end up with no match-specs, we must remove the meta trace
 
709
%% patten all together. That is bringing the function back to just initiated.
 
710
h_ctpm_ms(Mod,Func,Arity,MSname) ->
 
711
    case get_ms_ld(Mod,Func,Arity) of
 
712
        [] ->                               % The name does certainly not exist!
 
713
            true;                           % We don't have to do anything.
 
714
        MSsNames ->
 
715
            case lists:keysearch(MSname,1,MSsNames) of
 
716
                {value,{_,_MS}} ->          % Ok, we must do something!
 
717
                    NewMSsNames=lists:keydelete(MSname,1,MSsNames),
 
718
                    case lists:flatten(lists:map(fun({_Name,MS})->MS end,NewMSsNames)) of
 
719
                        [] ->               % This means stop meta tracing.
 
720
                            set_meta_tracing(Mod,Func,Arity,false);
 
721
                        NewMSs ->
 
722
                            set_meta_tracing(Mod,Func,Arity,NewMSs)
 
723
                    end,
 
724
                    set_ms_ld(Mod,Func,Arity,NewMSsNames);
 
725
                false ->                    % But this name does not exist.
 
726
                    true                    % So we do not have to do anything.
 
727
            end
 
728
    end.
 
729
%% -----------------------------------------------------------------------------
 
730
 
 
731
%% Function that checks the arguments to the meta trace pattern. The reason we
 
732
%% must do this is that we can only allow meta tracing on specific functions and
 
733
%% not using wildpatterns. Otherwise the meta trace server will not understand
 
734
%% which callfunc for instance to call when a meta-trace message is generated
 
735
%% for a function.
 
736
%% Returns 'true' or 'false'.
 
737
check_tpm_args(Mod,Func,Arity)
 
738
  when is_atom(Mod),is_atom(Func),is_integer(Arity),Mod/='_',Func/='_' ->
 
739
    true;
 
740
check_tpm_args(_,_,_) ->
 
741
    false.
 
742
%% -----------------------------------------------------------------------------
 
743
 
 
744
%% Help function which calls the actual BIF setting meta-trace-patterns.
 
745
%% Returns 'true' or 'false'.
 
746
set_meta_tracing(Mod,Func,Arity,MS) when is_atom(Mod) ->
 
747
    case erlang:module_loaded(Mod) of
 
748
        true ->
 
749
            set_meta_tracing_2(Mod,Func,Arity,MS);
 
750
        false ->                            % The module is not loaded.
 
751
            case code:ensure_loaded(Mod) of
 
752
                {module,_Mod} ->
 
753
                    set_meta_tracing_2(Mod,Func,Arity,MS);
 
754
                {error,_Reason} ->          % Could not load the module.
 
755
                    false                   % No use try to trace.
 
756
            end
 
757
    end;
 
758
set_meta_tracing(_,_,_,_) ->
 
759
    false.
 
760
 
 
761
set_meta_tracing_2(Mod,Func,Arity,MS) ->
 
762
    case catch erlang:trace_pattern({Mod,Func,Arity},MS,[meta]) of
 
763
        0 ->                                % Hmm, nothing happend :-)
 
764
            false;
 
765
        N when is_integer(N) ->                % The normal case, some functions were hit.
 
766
            true;
 
767
        {'EXIT',_Reason} ->
 
768
            false
 
769
    end.
 
770
%% -----------------------------------------------------------------------------
 
771
 
 
772
%% Help function which removes all meta trace pattern for the functions mentioned
 
773
%% in the list being first argument. It also executes the remove funcs for each
 
774
%% and every no longer meta traced function. This done since some of the remove
 
775
%% functions may do side-effects (like deleteing ETS tables).
 
776
%% Returns nothing significant.
 
777
stop_all_meta_tracing([{M,F,Arity}|Rest],PublLD,LD) ->
 
778
    catch erlang:trace_pattern({M,F,Arity},false,[meta]),
 
779
    NewPublLD=do_removefunc(get_remove_func_ld(M,F,Arity,LD),M,F,Arity,PublLD),
 
780
    stop_all_meta_tracing(Rest,NewPublLD,LD);
 
781
stop_all_meta_tracing([],_,_) ->
 
782
    true.
 
783
%% -----------------------------------------------------------------------------
 
784
 
 
785
%% This function calls the function registered to be handler for a certain
 
786
%% meta-traced function. Such a function or fun must take three arguments
 
787
%% and return {ok,NewPrivLD,OutPutBinary} or 'false'. OutPutBinary may be
 
788
%% something else, and is then ignored.
 
789
handle_meta({M,F},Pid,Arg1,PrivLD) ->
 
790
    (catch M:F(Pid,Arg1,PrivLD));
 
791
handle_meta(Fun,Pid,Arg1,PrivLD) when is_function(Fun) ->
 
792
    (catch Fun(Pid,Arg1,PrivLD));
 
793
handle_meta(_,_,_,_) ->                     % Don't know how to do this.
 
794
    false.
 
795
%% -----------------------------------------------------------------------------
 
796
 
 
797
%% Help function writing output from a callback function to the ti-file.
 
798
%% Output can be a binary or a list of binaries.
 
799
write_output(TI,[OutPut|Rest]) ->
 
800
    write_output(TI,OutPut),
 
801
    write_output(TI,Rest);
 
802
write_output({file,FD},Bin) when is_binary(Bin) -> % Plain direct-binary file
 
803
    Size=byte_size(Bin),
 
804
    file:write(FD,list_to_binary([<<0,Size:32>>,Bin]));
 
805
write_output({relay,ToNode},Bin) when is_atom(ToNode),is_binary(Bin) ->
 
806
    {inviso_rt_meta,ToNode} ! {relayed_meta,Bin};
 
807
write_output(_,_) ->                        % Don't understand, just skip.
 
808
    true.
 
809
%% -----------------------------------------------------------------------------
 
810
 
 
811
 
 
812
%% =============================================================================
 
813
%% Various help functions.
 
814
%% =============================================================================
 
815
 
 
816
%% Help function initializing the public loopdata structure. Note that if the
 
817
%% supplied InitPublLDmfa is faulty we let the structure become the error.
 
818
%% The error will most likely turn up in an error report somewhere, eventually.
 
819
do_init_publ_ld({M,F,Args}) when is_atom(M),is_atom(F),is_list(Args) ->
 
820
    case catch apply(M,F,Args) of
 
821
        {'EXIT',_Reason} ->
 
822
            {error,init_publ_ld_func};      % Let the struct be this error!
 
823
        InitialPublLD ->
 
824
            InitialPublLD
 
825
    end;
 
826
do_init_publ_ld(_) ->
 
827
    {error,init_publ_ld_func}.
 
828
%% -----------------------------------------------------------------------------
 
829
 
 
830
%% Help function which removes the public loopdata structure. The function does
 
831
%% not necessarily have to exist. Returns nothing significant.
 
832
do_remove_publ_ld({M,F},PublLD) when is_atom(M),is_atom(F) ->
 
833
    catch M:F(PublLD);
 
834
do_remove_publ_ld(_,_) ->
 
835
    true.
 
836
%% -----------------------------------------------------------------------------        
 
837
 
 
838
%% Hlp function initializing a particular meta traced function into the public
 
839
%% loopdata. Note that the function is not mandatory.
 
840
%% Returns {NewPublLD,Output} or 'false'.
 
841
do_initfunc({M,F},Mod,Func,Arity,PublLD) when is_atom(M),is_atom(F) ->
 
842
    case catch M:F(Mod,Func,Arity,PublLD) of
 
843
        {ok,NewPublLD,Output} ->
 
844
            {NewPublLD,Output};
 
845
        _ ->                                % Everything else is an error.
 
846
            false                           % Act as no initialization function.
 
847
    end;
 
848
do_initfunc(Fun,Mod,Func,Arity,PublLD) when is_function(Fun) ->
 
849
    case catch Fun(Mod,Func,Arity,PublLD) of
 
850
        {ok,NewPublLD,Output} ->
 
851
            {NewPublLD,Output};
 
852
        _ ->                                % Everything else is an error.
 
853
            false                           % Act as no initialization function.
 
854
    end;
 
855
do_initfunc(_,_,_,_,_) ->                   % Perhaps too generous, should be 'void' only.
 
856
    false.
 
857
%% -----------------------------------------------------------------------------
 
858
 
 
859
%% Help function removing a particular meta traced function from the public
 
860
%% loopdata. Note that we do not make much noice should the call back function
 
861
%% be faulty.
 
862
do_removefunc({M,F},Mod,Func,Arity,PublLD) when is_atom(M),is_atom(F) ->
 
863
    case catch M:F(Mod,Func,Arity,PublLD) of
 
864
        {ok,NewPublLD} ->
 
865
            NewPublLD;
 
866
        _ ->                                % Everything else is an error.
 
867
            PublLD                          % Act as no initialization function.
 
868
    end;
 
869
do_removefunc(Fun,Mod,Func,Arity,PublLD) when is_function(Fun) ->
 
870
    case catch Fun(Mod,Func,Arity,PublLD) of
 
871
        {ok,NewPublLD} ->
 
872
            NewPublLD;
 
873
        _ ->                                % Everything else is an error.
 
874
            PublLD                          % Act as no initialization function.
 
875
    end;
 
876
do_removefunc(_,_,_,_,PublLD) ->
 
877
    PublLD.
 
878
%% -----------------------------------------------------------------------------
 
879
 
 
880
%% Function that, if the time has come, goes through the priv-ld structure and
 
881
%% cleans away entryn left behind. The usual cause is that the function call
 
882
%% caused an exception and there were therefore no matching return_from.
 
883
%% Returns {NewPrivLD,now()}.
 
884
throw_old_failed({M,F},PrivLD,PrevClean) ->
 
885
    case difference_in_now(PrevClean,now(),60) of % We clean once every minute.
 
886
        true ->
 
887
            case catch apply(M,F,[PrivLD]) of
 
888
                {'EXIT',_Reason} ->         % Something went wrong, ignore it.
 
889
                    {PrivLD,now()};         % Just keep the old priv-ld.
 
890
                NewPrivLD ->                % The function must return a priv-ld.
 
891
                    {NewPrivLD,now()}
 
892
            end;
 
893
        false ->                            % Not time yet!
 
894
            {PrivLD,PrevClean}
 
895
    end.
 
896
%% -----------------------------------------------------------------------------
 
897
 
 
898
%% Help function comparing two now timestamps. Returns true or false depending
 
899
%% on if S2 is more than DiffS seconds after S1. Only works for differences
 
900
%% less than 1 million seconds.
 
901
difference_in_now({MegaS1,S1,_},{MegaS2,S2,_},DiffS) ->
 
902
    if
 
903
        MegaS1+1<MegaS2 ->                  % More than 1 Mega sec. difference.
 
904
            true;
 
905
        MegaS1==MegaS2,S1+DiffS<S2 ->
 
906
            true;
 
907
        MegaS1+1==MegaS2,S1+DiffS<S2+1000000 ->
 
908
            true;
 
909
        true ->
 
910
            false
 
911
    end.
 
912
%% -----------------------------------------------------------------------------
 
913
 
 
914
%% This help function adds a {tracer,Tracer} to the enable-list in a 'trace'
 
915
%% match spec action. The reason for this is that the author of the a meta
 
916
%% match spec meant to turn tracing on for the process executing the match spec
 
917
%% can not know the tracer. This since the match spec is most likely authored
 
918
%% at the control component's node, and not here.
 
919
%% Note the double tuple necessary to make it just precise a tuple!
 
920
%% Returns a new match spec.
 
921
add_tracer([MS1|Rest],Tracer) ->
 
922
    [add_tracer_2(MS1,Tracer)|add_tracer(Rest,Tracer)];
 
923
add_tracer([],_) ->
 
924
    [];
 
925
add_tracer(NotList,_Tracer) ->              % Can be 'false', but also an error.
 
926
    NotList.
 
927
 
 
928
add_tracer_2({Head,Cond,Body},Tracer) ->
 
929
    {Head,Cond,add_tracer_3(Body,Tracer)};
 
930
add_tracer_2(Faulty,_Tracer) ->
 
931
    Faulty.
 
932
 
 
933
add_tracer_3([{trace,Disable,Enable}|Rest],Tracer) when is_list(Enable) ->
 
934
    [{trace,Disable,Enable++[{{tracer,Tracer}}]}|Rest];
 
935
add_tracer_3([ActionTerm|Rest],Tracer) ->
 
936
    [ActionTerm|add_tracer_3(Rest,Tracer)];
 
937
add_tracer_3([],_Tracer) ->
 
938
    [];
 
939
add_tracer_3(FaultyBody,_Tracer) ->
 
940
    FaultyBody.
 
941
%% -----------------------------------------------------------------------------
 
942
 
 
943
%% -----------------------------------------------------------------------------
 
944
%% Help functions handling internal loopdata.
 
945
%% -----------------------------------------------------------------------------
 
946
 
 
947
-record(ld,{init_publ_ld_mfa,               % {M,F,Args}
 
948
            remove_publ_ld_mf,              % {M,F} | void
 
949
            clean_publ_ld_mf,               % {Mod,Func}
 
950
            ms_mfarities=notable,           % ETS holding names match functions.
 
951
            call_mfarities=[],              % [{{M,F,Arity},2-TupleOrFun},...]
 
952
            return_mfarities=[],            % [{{M,F,Arity},2-TupleOrFun},...]
 
953
            remove_mfarities=[]
 
954
           }).
 
955
 
 
956
mk_new_ld(InitPublLDmfa,RemovePublLDmf,CleanPublLDmf,TId) ->
 
957
    #ld{
 
958
           init_publ_ld_mfa=InitPublLDmfa,
 
959
           remove_publ_ld_mf=RemovePublLDmf,
 
960
           clean_publ_ld_mf=CleanPublLDmf,
 
961
           ms_mfarities=TId
 
962
       }.
 
963
%% -----------------------------------------------------------------------------
 
964
 
 
965
%% Function which restores the internal loop data to somekind of initial state.
 
966
%% This is useful when tracing has been suspended.
 
967
reset_ld(#ld{init_publ_ld_mfa=InitPublLDmfa,
 
968
             remove_publ_ld_mf=RemovePublLDmf,
 
969
             clean_publ_ld_mf=CleanPublLDmf,
 
970
             ms_mfarities=TId}) ->
 
971
    ets:match_delete(TId,{'_','_'}),        % Empty the table.
 
972
    #ld{init_publ_ld_mfa=InitPublLDmfa,
 
973
        remove_publ_ld_mf=RemovePublLDmf,
 
974
        clean_publ_ld_mf=CleanPublLDmf,
 
975
        ms_mfarities=TId}.
 
976
%% -----------------------------------------------------------------------------
 
977
 
 
978
get_initpublldmfa_ld(#ld{init_publ_ld_mfa=InitPublLDmfa}) ->
 
979
    InitPublLDmfa.
 
980
%% -----------------------------------------------------------------------------
 
981
 
 
982
get_removepublldmf_ld(#ld{remove_publ_ld_mf=RemovePublLDmf}) ->
 
983
    RemovePublLDmf.
 
984
%% -----------------------------------------------------------------------------
 
985
 
 
986
get_cleanpublldmf_ld(#ld{clean_publ_ld_mf=CleanPublLDmf}) ->
 
987
    CleanPublLDmf.
 
988
%% -----------------------------------------------------------------------------
 
989
 
 
990
%% Help function adding data associated with a meta traced function to the
 
991
%% internal loopdata. Called when meta tracing is activated for M:F/Arity.
 
992
init_tpm_ld(M,F,Arity,CallFunc,ReturnFunc,RemoveFunc,LD) ->
 
993
    ets:insert(LD#ld.ms_mfarities,{{M,F,Arity},[]}),
 
994
    CallFuncs=LD#ld.call_mfarities,
 
995
    ReturnFuncs=LD#ld.return_mfarities,
 
996
    RemoveFuncs=LD#ld.remove_mfarities,
 
997
    LD#ld{call_mfarities=[{{M,F,Arity},CallFunc}|CallFuncs],
 
998
          return_mfarities=[{{M,F,Arity},ReturnFunc}|ReturnFuncs],
 
999
          remove_mfarities=[{{M,F,Arity},RemoveFunc}|RemoveFuncs]}.
 
1000
%% -----------------------------------------------------------------------------
 
1001
 
 
1002
%% Help function which answers the question if we have already initiated the
 
1003
%% function. It is done by looking in the ETS-table with named match-functions.
 
1004
%% If there is an entry in the set-type table for M:F/Arity, the function is
 
1005
%% initiated.
 
1006
%% Returns 'yes' or 'no'.
 
1007
check_mfarity_exists(M,F,Arity) ->
 
1008
    case ets:lookup(?NAMED_MS_TAB,{M,F,Arity}) of
 
1009
        [] ->
 
1010
            no;
 
1011
        [_] ->
 
1012
            yes
 
1013
    end.
 
1014
%% -----------------------------------------------------------------------------
 
1015
 
 
1016
%% Help function adding an entry with [{MSname,MSlist}|MSsNames] for M:F/Arity.
 
1017
%% Note that any already existing entry is removed.
 
1018
%% Returns nothing significant.
 
1019
put_ms_ld(M,F,Arity,MSname,MS,MSsNames) ->
 
1020
    ets:insert(?NAMED_MS_TAB,{{M,F,Arity},[{MSname,MS}|MSsNames]}).
 
1021
%% -----------------------------------------------------------------------------
 
1022
 
 
1023
%% Help function taking a list of {MSname,MSs} and storing them in the
 
1024
%% internal loop data structure. The storage is actually implemented as an ETS
 
1025
%% table. Any previous list of {MSname,MSs} associated with this {M,F,Arity} will
 
1026
%% be lost. Returns nothing significant.
 
1027
set_ms_ld(M,F,Arity,MSsNames) ->
 
1028
    ets:insert(?NAMED_MS_TAB,{{M,F,Arity},MSsNames}).
 
1029
%% -----------------------------------------------------------------------------
 
1030
 
 
1031
%% Help function fetching a list of {MSname,MatchSpecs} for a M:F/Arity. The
 
1032
%% match-functions are stored in an ETS table searchable on {M,F,Arity}.
 
1033
get_ms_ld(M,F,Arity) ->
 
1034
    case ets:lookup(?NAMED_MS_TAB,{M,F,Arity}) of
 
1035
        [{_MFArity,MSsNames}] ->
 
1036
            MSsNames;
 
1037
        [] ->
 
1038
            []
 
1039
    end.
 
1040
%% -----------------------------------------------------------------------------
 
1041
 
 
1042
%% Help function removing all saved match-specs for a certain M:F/Arity.
 
1043
%% Returns a new loopdata structure.
 
1044
remove_ms_ld(M,F,Arity,LD) ->
 
1045
    ets:delete(LD#ld.ms_mfarities,{M,F,Arity}),
 
1046
    LD.
 
1047
%% -----------------------------------------------------------------------------
 
1048
 
 
1049
%% Help function which removes all information about a meta traced function from
 
1050
%% the internal loopdata. Returns a new loopdata structure.
 
1051
ctpm_ld(M,F,Arity,LD) ->
 
1052
    ets:delete(LD#ld.ms_mfarities,{M,F,Arity}),
 
1053
    NewCallFuncs=lists:keydelete({M,F,Arity},1,LD#ld.call_mfarities),
 
1054
    NewReturnFuncs=lists:keydelete({M,F,Arity},1,LD#ld.return_mfarities),
 
1055
    NewRemoveFuncs=lists:keydelete({M,F,Arity},1,LD#ld.remove_mfarities),
 
1056
    LD#ld{call_mfarities=NewCallFuncs,
 
1057
          return_mfarities=NewReturnFuncs,
 
1058
          remove_mfarities=NewRemoveFuncs}.
 
1059
%% -----------------------------------------------------------------------------
 
1060
 
 
1061
get_call_func_ld(M,F,Arity,#ld{call_mfarities=CallFuncs}) ->
 
1062
    case lists:keysearch({M,F,Arity},1,CallFuncs) of
 
1063
        {value,{_,MF}} ->
 
1064
            MF;
 
1065
        false ->
 
1066
            false
 
1067
    end.
 
1068
%% -----------------------------------------------------------------------------
 
1069
 
 
1070
get_return_func_ld(M,F,Arity,#ld{return_mfarities=CallFuncs}) ->
 
1071
    case lists:keysearch({M,F,Arity},1,CallFuncs) of
 
1072
        {value,{_,MF}} ->
 
1073
            MF;
 
1074
        false ->
 
1075
            false
 
1076
    end.
 
1077
%% -----------------------------------------------------------------------------
 
1078
 
 
1079
get_remove_func_ld(M,F,Arity,#ld{remove_mfarities=RemoveFuncs}) ->
 
1080
    case lists:keysearch({M,F,Arity},1,RemoveFuncs) of
 
1081
        {value,{_,MF}} ->
 
1082
            MF;
 
1083
        false ->
 
1084
            false
 
1085
    end.
 
1086
%% -----------------------------------------------------------------------------
 
1087
 
 
1088
%% Function returning a list of all {Mod,Func,Arity} which are currently meta
 
1089
%% traced. It does do by listifying the call_mfarities field in the internal
 
1090
%% loopdata.
 
1091
get_all_meta_funcs_ld(#ld{call_mfarities=CallFuncs}) ->
 
1092
    lists:map(fun({MFArity,_})->MFArity end,CallFuncs).
 
1093
%% -----------------------------------------------------------------------------
 
1094
 
 
1095
 
 
1096
%% =============================================================================
 
1097
%% Functions for the standard PublLD structure.
 
1098
%%
 
1099
%% It is tuple {Part1,GlobalData} where Part1 is of length at least 2.
 
1100
%% Where each field is a list of tuples. The last item in each tuple shall be
 
1101
%% a now tuple, making it possible to clean it away should it be too old to be
 
1102
%% relevant (there was no return_from message due to a failure).
 
1103
%% Other fields can be used for other functions.
 
1104
%% The GlobalData is not cleaned but instead meant to store data must be passed
 
1105
%% to each CallFunc when a meta trace message arrives.
 
1106
%% =============================================================================
 
1107
                      
 
1108
%% Function returning our standard priv-loopdata structure.
 
1109
init_std_publld(Size,GlobalData) ->
 
1110
    {list_to_tuple(lists:duplicate(Size,[])),GlobalData}.
 
1111
%% -----------------------------------------------------------------------------
 
1112
 
 
1113
%% Function capable of cleaning out a standard publ-ld. The last element of each
 
1114
%% tuple must be the now item.
 
1115
%% Returns a new publ-ld structure.
 
1116
clean_std_publld({Part1,GlobalData}) ->
 
1117
    {clean_std_publld_2(Part1,now(),tuple_size(Part1),[]),GlobalData}.
 
1118
 
 
1119
clean_std_publld_2(_,_,0,Accum) ->
 
1120
    list_to_tuple(Accum);
 
1121
clean_std_publld_2(PublLD,Now,Index,Accum) ->
 
1122
    NewTupleList=clean_std_publld_3(element(Index,PublLD),Now),
 
1123
    clean_std_publld_2(PublLD,Now,Index-1,[NewTupleList|Accum]).
 
1124
 
 
1125
clean_std_publld_3([Tuple|Rest],Now) ->
 
1126
    PrevNow=element(tuple_size(Tuple),Tuple), % Last item shall be the now item.
 
1127
    case difference_in_now(PrevNow,Now,30) of
 
1128
        true ->                             % Remove it then!
 
1129
            clean_std_publld_3(Rest,Now);
 
1130
        false ->                            % Keep it!
 
1131
            [Tuple|clean_std_publld_3(Rest,Now)]
 
1132
    end;
 
1133
clean_std_publld_3([],_) ->
 
1134
    [].
 
1135
%% -----------------------------------------------------------------------------
 
1136
 
 
1137
%% =============================================================================
 
1138
%% Functions used as handling functions (as funs) for registered process names.
 
1139
%% (Given that we use the standard priv-ld, otherwise you must do your own!).
 
1140
%% =============================================================================
 
1141
 
 
1142
%% Call-back for initializing the meta traced functions there are quick functions
 
1143
%% for. Returns a new public loop data structure.
 
1144
metafunc_init(erlang,register,2,{Part1,GlobalData}) ->
 
1145
    {setelement(1,Part1,[]),GlobalData}.
 
1146
%% -----------------------------------------------------------------------------
 
1147
 
 
1148
%% Call-function for erlang:register/2.
 
1149
%% This function adds the call to register/2 to a standard priv-ld structure.
 
1150
%% Note that we *must* search for previous entries from the same process. If such
 
1151
%% still in structure it means a failed register/2 call. It must first be removed
 
1152
%% so it can not be mixed up with this one. Since meta-trace message will arrive
 
1153
%% in order, there was no return_from message for that call if we are here now.
 
1154
local_register_call(CallingPid,{call,[Alias,Pid],TS},{Part1,GlobalData}) ->
 
1155
    TupleList=element(1,Part1),             % The register/2 entry in a std. priv-ld.
 
1156
    NewTupleList=lists:keydelete(CallingPid,1,TupleList), % If present, remove previous call.
 
1157
    {ok,
 
1158
     {setelement(1,Part1,[{CallingPid,{Alias,Pid},TS}|NewTupleList]),GlobalData},
 
1159
     void}.
 
1160
 
 
1161
%% Return-function for the erlang:register/2 BIF.
 
1162
%% This function formulates the output and removes the corresponding call entry
 
1163
%% from the standard priv-ld structure.
 
1164
local_register_return(CallingPid,{return_from,_Val,_TS},PublLD={Part1,GlobalData}) ->
 
1165
    TupleList=element(1,Part1),             % The register/2 entry in a std. priv-ld.
 
1166
    case lists:keysearch(CallingPid,1,TupleList) of
 
1167
        {value,{_,{Alias,Pid},NowTS}} ->
 
1168
            NewTupleList=lists:keydelete(CallingPid,1,TupleList),
 
1169
            {ok,
 
1170
             {setelement(1,Part1,NewTupleList),GlobalData},
 
1171
             term_to_binary({Pid,Alias,alias,NowTS})};
 
1172
        false ->                            % Strange, then don't know what to do.
 
1173
            {ok,PublLD,void}                % Do nothing seems safe.
 
1174
    end;
 
1175
local_register_return(CallingPid,{exception_from,_Val,_TS},{Part1,GlobalData}) ->
 
1176
    TupleList=element(1,Part1),             % The register/2 entry in a std. priv-ld.
 
1177
    NewTupleList=lists:keydelete(CallingPid,1,TupleList),
 
1178
    {ok,{setelement(1,Part1,NewTupleList),GlobalData},void}; % No association then.
 
1179
local_register_return(_,_,PublLD) ->        % Don't understand this.
 
1180
    {ok,PublLD,void}.
 
1181
 
 
1182
%% When unregister/1 us called we simply want a unalias entry in the ti-file.
 
1183
%% We can unfortunately not connect it with a certain pid.
 
1184
local_unregister_call(_CallingPid,{_TypeTag,[Alias],TS},PublLD) ->
 
1185
    {ok,PublLD,term_to_binary({undefined,Alias,unalias,TS})}.
 
1186
%% -----------------------------------------------------------------------------
 
1187
 
 
1188
%% Call-function for global:register_name/2,/3.
 
1189
%% This function is actually the call function for the handle_call/3 in the
 
1190
%% global server. Note that we must check that we only do this on the node
 
1191
%% where Pid actually resides.
 
1192
global_register_call(_CallingPid,{call,[{register,Alias,P,_},_,_],TS},PublLD)
 
1193
  when node(P)==node()->
 
1194
    {ok,PublLD,term_to_binary({P,{global,Alias},alias,TS})};
 
1195
global_register_call(_CallingPid,_,PublLD) ->
 
1196
    {ok,PublLD,void}.
 
1197
 
 
1198
%% Call-function for global:unregister_name. It acutally checks on the use of
 
1199
%% global:delete_global_name/2 which is called when ever a global name is removed.
 
1200
global_unregister_call(_CallingPid,{call,[Alias,P],TS},PublLD) when node(P)==node()->
 
1201
    {ok,PublLD,term_to_binary({P,{global,Alias},unalias,TS})};
 
1202
global_unregister_call(_CallingPid,_,PublLD) ->
 
1203
    {ok,PublLD,void}.
 
1204
%% -----------------------------------------------------------------------------
 
1205
 
 
1206
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1207