~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/observer/doc/src/ttb_ug.xml

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
<?xml version="1.0" encoding="latin1" ?>
 
2
<!DOCTYPE chapter SYSTEM "chapter.dtd">
 
3
 
 
4
<chapter>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>2002</year>
 
8
      <year>2007</year>
 
9
      <holder>Ericsson AB, All Rights Reserved</holder>
 
10
    </copyright>
 
11
    <legalnotice>
 
12
  The contents of this file are subject to the Erlang Public License,
 
13
  Version 1.1, (the "License"); you may not use this file except in
 
14
  compliance with the License. You should have received a copy of the
 
15
  Erlang Public License along with this software. If not, it can be
 
16
  retrieved online at http://www.erlang.org/.
 
17
 
 
18
  Software distributed under the License is distributed on an "AS IS"
 
19
  basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
20
  the License for the specific language governing rights and limitations
 
21
  under the License.
 
22
 
 
23
  The Initial Developer of the Original Code is Ericsson AB.
 
24
    </legalnotice>
 
25
 
 
26
    <title>Trace Tool Builder</title>
 
27
    <prepared></prepared>
 
28
    <docno></docno>
 
29
    <date></date>
 
30
    <rev></rev>
 
31
  </header>
 
32
 
 
33
  <section>
 
34
    <title>Introduction</title>
 
35
    <p>The Trace Tool Builder is a base for building trace tools for
 
36
      single node or distributed erlang systems. It requires the
 
37
      <c>runtime_tools</c> application to be available on the traced
 
38
      node.
 
39
      </p>
 
40
    <p>The main features of the Trace Tool Builder are:</p>
 
41
    <list type="bulleted">
 
42
      <item>Start tracing to file ports on several nodes with one
 
43
       function call.</item>
 
44
      <item>Write additional information to a trace information file,
 
45
       which is read during formatting.</item>
 
46
      <item>Restoring of previous configuration by maintaining a
 
47
       history buffer and handling configuration files.</item>
 
48
      <item>Some simple support for sequential tracing.</item>
 
49
      <item>Formatting of binary trace logs and merging of logs from
 
50
       multiple nodes.</item>
 
51
    </list>
 
52
    <p>Even though the intention of the Trace Tool Builder is to serve
 
53
      as a base for tailor made trace tools, it is of course possible
 
54
      to use it directly from the erlang shell. The application only
 
55
      allows the use of file port tracer, so if you would like would
 
56
      like to use other types of trace clients you will be better off
 
57
      using <c>dbg</c> directly instead.</p>
 
58
  </section>
 
59
 
 
60
  <section>
 
61
    <title>Getting Started</title>
 
62
    <p>The <c>ttb</c> module is the interface to all functions in the
 
63
      Trace Tool Builder. To get started the least you need to do is to
 
64
      start a tracer with <c>ttb:tracer/0/1/2</c>, and set the required
 
65
      trace flags on the processes you want to trace with
 
66
      <c>ttb:p/2</c>. Then, when the tracing is completed, you must stop
 
67
      the tracer with <c>ttb:stop/0/1</c> and format the trace log with
 
68
      <c>ttb:format/1/2</c>.
 
69
      </p>
 
70
    <p><c>ttb:tracer/0/1/2</c> opens a file trace port on each node
 
71
      that shall be traced. All trace messages will be written to this
 
72
      port and end up in a binary file (the binary trace log).
 
73
      </p>
 
74
    <p><c>ttb:p/2</c> specifies which processes that shall be
 
75
      traced. Trace flags given in this call specifies what to trace on
 
76
      each process. You can call this function several times if you like
 
77
      different trace flags to be set on different processes.
 
78
      </p>
 
79
    <p>If you want to trace function calls (i.e. if you have the
 
80
      <c>call</c> trace flag set on any of your processes), you must
 
81
      also set trace patterns on the required function(s) with
 
82
      <c>ttb:tp</c> or <c>ttb:tpl</c>. A function is only traced if it
 
83
      has a trace pattern. The trace pattern specifies how to trace the
 
84
      function by using match specifications. Match specifications are
 
85
      described in the User's Guide for the erlang runtime system
 
86
      <c>erts</c>.
 
87
      </p>
 
88
    <p><c>ttb:stop/0/1</c> stops tracing on all nodes, deletes all
 
89
      trace patterns and flushes the trace port buffer.
 
90
      </p>
 
91
    <p><c>ttb:format/1/2</c> translates the binary trace logs into
 
92
      something readable. By default <c>ttb</c> presents each trace
 
93
      message as a line of text, but you can also write your own handler
 
94
      to make more complex interpretations of the trace information. A
 
95
      trace log can even be presented graphically via the Event Tracer
 
96
      application. Note that if you give the <c>format</c> option to
 
97
      <c>ttb:stop/1</c> the formatting is automatically done when
 
98
      stopping <c>ttb</c>.
 
99
      </p>
 
100
 
 
101
    <section>
 
102
      <title>Example: Tracing the local node from the erlang shell</title>
 
103
      <p>This small module is used in the example:</p>
 
104
      <code type="none">
 
105
-module(m).
 
106
-export([f/0]).
 
107
f() ->
 
108
   receive 
 
109
      From when pid(From) -> 
 
110
\011 Now = erlang:now(),
 
111
         From ! {self(),Now}
 
112
   end.      </code>
 
113
      <p>The following example shows the basic use of <c>ttb</c> from
 
114
        the erlang shell. Default options are used both for starting the
 
115
        tracer and for formatting. This gives a trace log named
 
116
        <c>Node-ttb</c>, where <c>Node</c> is the name of the node.  The
 
117
        default handler prints the formatted trace messages in the
 
118
        shell.</p>
 
119
      <code type="none"><![CDATA[
 
120
(tiger@durin)47> %% First I spawn a process running my test function
 
121
(tiger@durin)47> Pid = spawn(m,f,[]).
 
122
<0.125.0>
 
123
(tiger@durin)48> 
 
124
(tiger@durin)48> %% Then I start a tracer...
 
125
(tiger@durin)48> ttb:tracer().
 
126
{ok,[tiger@durin]}
 
127
(tiger@durin)49> 
 
128
(tiger@durin)49> %% and activate the new process for tracing
 
129
(tiger@durin)49> %% function calls and sent messages.
 
130
(tiger@durin)49> ttb:p(Pid,[call,send]).
 
131
{ok,[{<0.125.0>,[{matched,tiger@durin,1}]}]}
 
132
(tiger@durin)50> 
 
133
(tiger@durin)50> %% Here I set a trace pattern on erlang:now/0
 
134
(tiger@durin)50> %% The trace pattern is a simple match spec
 
135
(tiger@durin)50> %% generated by dbg:fun2ms/1. It indicates that 
 
136
(tiger@durin)50> %% the return value shall be traced.
 
137
(tiger@durin)50> MS = dbg:fun2ms(fun(_) -> return_trace() end).
 
138
[{'_',[],[{return_trace}]}]
 
139
(tiger@durin)51> ttb:tp(erlang,now,MS).
 
140
{ok,[{matched,tiger@durin,1},{saved,1}]}
 
141
(tiger@durin)52> 
 
142
(tiger@durin)52> %% I run my test (i.e. send a message to
 
143
(tiger@durin)52> %% my new process)
 
144
(tiger@durin)52> Pid ! self().
 
145
<0.72.0>
 
146
(tiger@durin)53> 
 
147
(tiger@durin)53> %% And then I have to stop ttb in order to flush
 
148
(tiger@durin)53> %% the trace port buffer
 
149
(tiger@durin)53> ttb:stop().
 
150
stopped
 
151
(tiger@durin)54> 
 
152
(tiger@durin)54> %% Finally I format my trace log
 
153
(tiger@durin)54> ttb:format("tiger@durin-ttb").
 
154
({<0.125.0>,{m,f,0},tiger@durin}) call erlang:now()
 
155
({<0.125.0>,{m,f,0},tiger@durin}) returned from erlang:now/0 ->
 
156
{1031,133451,667611}
 
157
({<0.125.0>,{m,f,0},tiger@durin}) <0.72.0> ! 
 
158
{<0.125.0>,{1031,133451,667611}}
 
159
ok      ]]></code>
 
160
    </section>
 
161
 
 
162
    <section>
 
163
      <title>Example: Build your own tool</title>
 
164
      <p>This small example shows a simple tool for "debug tracing",
 
165
        i.e. tracing of function calls with return values.</p>
 
166
      <code type="none"><![CDATA[
 
167
-module(mydebug).
 
168
-export([start/0,trc/1,stop/0,format/1]).
 
169
-export([print/4]).
 
170
 
 
171
%% Include ms_transform.hrl so that I can use dbg:fun2ms/2 to
 
172
%% generate match specifications.
 
173
-include_lib("stdlib/include/ms_transform.hrl").
 
174
 
 
175
%%% -------------Tool API-------------
 
176
%%% ----------------------------------
 
177
%%% Star the "mydebug" tool
 
178
start() ->
 
179
    %% The options specify that the binary log shall be named
 
180
    %% <Node>-debug_log and that the print/4 function in this
 
181
    %% module shall be used as format handler
 
182
    ttb:tracer(all,[{file,"debug_log"},{handler,{{?MODULE,print},0}}]),
 
183
    %% All processes (existing and new) shall trace function calls
 
184
    %% and include a timestamp in each trace message
 
185
    ttb:p(all,[call,timestamp]).
 
186
 
 
187
%%% Set trace pattern on function(s)
 
188
trc(M) when atom(M) ->
 
189
    trc({M,'_','_'});
 
190
trc({M,F}) when atom(M), atom(F) ->
 
191
    trc({M,F,'_'});
 
192
trc({M,F,_A}=MFA) when atom(M), atom(F) ->
 
193
    %% This match spec specifies that return values shall 
 
194
    %% be traced. NOTE that ms_transform.hrl must be included
 
195
    %% if dbg:fun2ms/1 shall be used!
 
196
    MatchSpec = dbg:fun2ms(fun(_) -> return_trace() end),
 
197
    ttb:tpl(MFA,MatchSpec).
 
198
 
 
199
%%% Format a binary trace log
 
200
format(File) ->
 
201
    ttb:format(File).
 
202
 
 
203
%%% Stop the "mydebug" tool
 
204
stop() ->
 
205
    ttb:stop().
 
206
 
 
207
%%% --------Internal functions--------
 
208
%%% ----------------------------------
 
209
%%% Format handler
 
210
print(_Out,end_of_trace,_TI,N) ->
 
211
    N;
 
212
print(Out,Trace,_TI,N) ->
 
213
    do_print(Out,Trace,N),
 
214
    N+1.
 
215
 
 
216
do_print(Out,{trace_ts,P,call,{M,F,A},Ts},N) ->
 
217
    io:format(Out,
 
218
\011      "~w: ~w, ~w:~n"
 
219
\011      "Call      : ~w:~w/~w~n"
 
220
\011      "Arguments :~p~n~n",
 
221
\011      [N,Ts,P,M,F,length(A),A]);
 
222
do_print(Out,{trace_ts,P,return_from,{M,F,A},R,Ts},N) ->
 
223
    io:format(Out,
 
224
\011      "~w: ~w, ~w:~n"
 
225
\011      "Return from  : ~w:~w/~w~n"
 
226
\011      "Return value :~p~n~n",
 
227
\011      [N,Ts,P,M,F,A,R]).      ]]></code>
 
228
      <p>To distinguish trace logs produced with this tool from other
 
229
        logs, the <c>file</c> option is used in <c>tracer/2</c>. The
 
230
        logs will therefore be named <c>Node-debug_log</c>, where
 
231
        <c>Node</c> is the name of the node where the log is produced.
 
232
        </p>
 
233
      <p>By using the <c>handler</c> option when starting the tracer,
 
234
        the information about how to format the file is stored in the
 
235
        trace information file (<c>.ti</c>). This is not necessary, as
 
236
        it might be given at the time of formatting instead. It can
 
237
        however be useful if you e.g. want to automatically format your
 
238
        trace logs by using the <c>format</c> option in
 
239
        <c>ttb:stop/1</c>. It also means that you don't need any
 
240
        knowledge of the content of a binary log to be able to format it
 
241
        the way it was intended. If the <c>handler</c> option is given
 
242
        both when starting the tracer and when formatting, the one given
 
243
        when formatting is used.
 
244
        </p>
 
245
      <p>The <c>call</c> trace flag is set on all processes. This
 
246
        means that any function activated with the <c>trc/1</c> command
 
247
        will be traced on all existing and new processes.
 
248
        </p>
 
249
    </section>
 
250
  </section>
 
251
 
 
252
  <section>
 
253
    <title>Running the Trace Tool Builder against a remote node</title>
 
254
    <p>The Observer application might not always be available on the
 
255
      node that shall be traced (in the following called the "traced
 
256
      node"). It is still possible to run the Trace Tool Builder from
 
257
      another node (in the following called the "trace control node") as
 
258
      long as
 
259
      </p>
 
260
    <list type="bulleted">
 
261
      <item>The Observer application is available on the trace control node.</item>
 
262
      <item>The Runtime Tools application is available on both the
 
263
       trace control node and the traced node.</item>
 
264
    </list>
 
265
    <p>If the Trace Tool Builder shall be used against a remote node,
 
266
      it is highly recommended to start the trace control node as
 
267
      <em>hidden</em>. This way it can connect to the traced node
 
268
      without the traced node "seeing" it, i.e. if the <c>nodes()</c>
 
269
      BIF is called on the traced node, the trace control node will not
 
270
      show. To start a hidden node, add the <c>-hidden</c> option to the
 
271
      <c>erl</c> command, e.g.</p>
 
272
    <code type="none">
 
273
% erl -sname trace_control -hidden    </code>
 
274
 
 
275
    <section>
 
276
      <title>Diskless node</title>
 
277
      <p>If the traced node is diskless, <c>ttb</c> must be started from
 
278
        a trace control node with disk access, and the <c>file</c> option
 
279
        must be given to the <c>tracer/2</c> function with the value
 
280
        <c>{local, File}</c>, e.g.</p>
 
281
      <code type="none">
 
282
(trace_control@durin)1> ttb:tracer(mynode@diskless,[{file,{local,
 
283
{wrap,"mytrace"}}}]).
 
284
{ok,[mynode@diskless]}      </code>
 
285
    </section>
 
286
  </section>
 
287
 
 
288
  <section>
 
289
    <marker id="trace_info"></marker>
 
290
    <title>Trace Information and the .ti File</title>
 
291
    <p>In addition to the trace log file(s), a file with the extension
 
292
      <c>.ti</c> is created when the Trace Tool Builder is started. This
 
293
      is the trace information file. It is a binary file, and it
 
294
      contains the process information, trace flags used, the name of
 
295
      the node to which it belongs and all information written with the
 
296
      <c>write_trace_info/2</c> function.
 
297
      </p>
 
298
    <p>To be able to use all this information during formatting, it is
 
299
      important that the trace information file exists in the same
 
300
      directory as the trace log, and that it has the same name as the
 
301
      trace log with the additional extension <c>.ti</c>.
 
302
      </p>
 
303
    <p>Except for the process information, everything in the trace
 
304
      information file is passed on to the handler function when
 
305
      formatting. The <c>TI</c> parameter is a list of
 
306
      <c>{Key,ValueList}</c> tuples. The keys <c>flags</c>,
 
307
      <c>handler</c>, <c>file</c> and <c>node</c> are used for
 
308
      information written directly by <c>ttb</c>.
 
309
      </p>
 
310
    <p>You can add information to the trace information file by
 
311
      calling <c>write_trace_info/2</c>. Note that <c>ValueList</c>
 
312
      always will be a list, and if you call <c>write_trace_info/2</c>
 
313
      several times with the same <c>Key</c>, the <c>ValueList</c> will
 
314
      be extended with a new value each time. Example:
 
315
      </p>
 
316
    <p><c>ttb:write_trace_info(mykey,1)</c> gives the entry
 
317
      <c>{mykey,[1]}</c> in <c>TI</c>. Another call,
 
318
      <c>ttb:write_trace_info(mykey,2)</c>, changes this entry to
 
319
      <c>{mykey,[1,2]}</c>.
 
320
      </p>
 
321
  </section>
 
322
 
 
323
  <section>
 
324
    <title>Wrap Logs</title>
 
325
    <p>If you want to limit the size of the trace logs, you can use
 
326
      wrap logs. This works almost like a ciclular buffer. You can
 
327
      specify the maximum number of binary logs and the maximum size of
 
328
      each log. <c>ttb</c> will create a new binary log each time a log
 
329
      reaches the maximum size. When the the maximum number of logs are
 
330
      reached, the oldest log is deleted before a new one is created.
 
331
      </p>
 
332
    <p>Wrap logs can be formatted one by one or all at once. See
 
333
      <seealso marker="#format">Formatting</seealso>.
 
334
      </p>
 
335
  </section>
 
336
 
 
337
  <section>
 
338
    <marker id="format"></marker>
 
339
    <title>Formatting</title>
 
340
    <p>Formatting can be done automatically when stopping <c>ttb</c>
 
341
      (see <seealso marker="#fetch_format">Automatically collect and format logs from all nodes</seealso>), or explicitly by calling
 
342
      the <c>ttb:format/1/2</c> function.
 
343
      </p>
 
344
    <p>Formatting means to read a binary log and present it in a
 
345
      readable format. You can use the default format handler in
 
346
      <c>ttb</c> to present each trace message as a line of text, or
 
347
      write your own handler to make more complex interpretations of the
 
348
      trace information. You can even use the Event Tracer <c>et</c> to
 
349
      present the trace log graphically (see <seealso marker="#et_viewer">Presenting trace logs with Event Tracer</seealso>).
 
350
      </p>
 
351
    <p>The first argument to <c>ttb:format/1/2</c> specifies which
 
352
      binary log(s) to format. This can be the name of one binary log, a
 
353
      list of such logs or the name of a directory containing one or
 
354
      more binary logs. If this argument indicates more than one log,
 
355
      and the <c>timestamp</c> flag was set when tracing, the trace
 
356
      messages from the different logs will be merged according to the
 
357
      timestamps in each message.
 
358
      </p>
 
359
    <p>The second argument to <c>ttb:format/2</c> is a list of
 
360
      options. The <c>out</c> option specifies the destination where the
 
361
      formatted text shall be written. Default destination is
 
362
      <c>standard_io</c>, but a filename can also be given. The
 
363
      <c>handler</c> option specifies the format handler to use. If this
 
364
      option is not given, the <c>handler</c> option given when starting
 
365
      the tracer is used. If the <c>handler</c> option was not given
 
366
      when starting the tracer either, a default handler is used, which
 
367
      prints each trace message as a line of text.
 
368
      </p>
 
369
    <p>A format handler is a fun taking four arguments. This fun will
 
370
      be called for each trace message in the binary log(s). A simple
 
371
      example which only prints each trace message could be like this:</p>
 
372
    <code type="none">
 
373
fun(Fd, Trace, _TraceInfo, State) ->
 
374
   io:format(Fd, "Trace: ~p~n", [Trace]),
 
375
   State
 
376
end.    </code>
 
377
    <p><c>Fd</c> is the file descriptor for the destination file, or
 
378
      the atom <c>standard_io</c>. <c>_TraceInfo</c> contains information
 
379
      from the trace information file (see <seealso marker="#trace_info">Trace Information and the .ti File</seealso>). <c>State</c> is a state variable for the format
 
380
      handler fun. The initial value of the <c>State</c> variable is
 
381
      given with the handler option, e.g.</p>
 
382
    <code type="none">
 
383
ttb:format("tiger@durin-ttb", [{handler, {{Mod,Fun}, initial_state}}])
 
384
                                                     ^^^^^^^^^^^^^    </code>
 
385
    <p>Another format handler could be used to calculate time spent by
 
386
      the garbage collector:</p>
 
387
    <code type="none">
 
388
fun(_Fd,{trace_ts,P,gc_start,_Info,StartTs},_TraceInfo,State) ->
 
389
      [{P,StartTs}|State];
 
390
   (Fd,{trace_ts,P,gc_end,_Info,EndTs},_TraceInfo,State) ->
 
391
      {value,{P,StartTs}} = lists:keysearch(P,1,State),
 
392
      Time = diff(StartTs,EndTs),
 
393
      io:format("GC in process ~w: ~w milliseconds~n", [P,Time]),
 
394
      State -- [{P,StartTs}]
 
395
end    </code>
 
396
    <p>A more refined version of this format handler is the function
 
397
      <c>handle_gc/4</c> in the module <c>multitrace.erl</c> which can
 
398
      be found in the <c>src</c> directory of the Observer application.
 
399
      </p>
 
400
    <p>By giving the format handler <c>et</c>, you can have the trace
 
401
      log presented graphically with <c>et_viewer</c> in the Event
 
402
      Tracer application (see <seealso marker="#et_viewer">Presenting trace logs with Event Tracer</seealso>).
 
403
      </p>
 
404
    <p>Wrap logs can be formatted one by one or all in one go. To
 
405
      format one of the wrap logs in a set, give the exact name of the
 
406
      file. To format the whole set of wrap logs, give the name with '*'
 
407
      instead of the wrap count. An example:
 
408
      </p>
 
409
    <p>Start tracing:</p>
 
410
    <code type="none">
 
411
(tiger@durin)1> ttb:tracer(node(),[{file,{wrap,"trace"}}]).
 
412
{ok,[tiger@durin]}
 
413
(tiger@durin)2> ttb:p(...)
 
414
...    </code>
 
415
    <p>This will give a set of binary logs, like:</p>
 
416
    <code type="none">
 
417
tiger@durin-trace.0.wrp
 
418
tiger@durin-trace.1.wrp
 
419
tiger@durin-trace.2.wrp
 
420
...    </code>
 
421
    <p>Format the whole set of logs:</p>
 
422
    <code type="none">
 
423
1> ttb:format("tiger@durin-trace.*.wrp").
 
424
....
 
425
ok
 
426
2>    </code>
 
427
    <p>Format only the first log:</p>
 
428
    <code type="none">
 
429
1> ttb:format("tiger@durin-trace.0.wrp").
 
430
....
 
431
ok
 
432
2>    </code>
 
433
    <p>To merge all wrap logs from two nodes:</p>
 
434
    <code type="none">
 
435
1> ttb:format(["tiger@durin-trace.*.wrp","lion@durin-trace.*.wrp"]).
 
436
....
 
437
ok
 
438
2>    </code>
 
439
 
 
440
    <section>
 
441
      <marker id="et_viewer"></marker>
 
442
      <title>Presenting trace logs with Event Tracer</title>
 
443
      <p>For detailed information about the Event Tracer, please turn
 
444
        to the User's Guide and Reference Manuals for the <c>et</c>
 
445
        application.
 
446
        </p>
 
447
      <p>By giving the format handler <c>et</c>, you can have the
 
448
        trace log presented graphically with <c>et_viewer</c> in the
 
449
        Event Tracer application. <c>ttb</c> provides a few different
 
450
        filters which can be selected from the Filter menu in the
 
451
        <c>et_viewer</c> window. The filters are names according to the
 
452
        type of actors they present (i.e. what each vertical line in the
 
453
        sequence diagram represent). Interaction between actors is shown
 
454
        as red arrows between two vertical lines, and activities within
 
455
        an actor are shown as blue text to the right of the actors line.
 
456
        </p>
 
457
      <p>The <c>processes</c> filter is the only filter which will
 
458
        show all trace messages from a trace log. Each vertical line in
 
459
        the sequence diagram represents a process. Erlang messages,
 
460
        spawn and link/unlink are typical interactions between
 
461
        processes. Function calls, scheduling and garbage collection are
 
462
        typical activities within a process. <c>processes</c> is the
 
463
        default filter.
 
464
        </p>
 
465
      <p>The rest of the filters will only show function calls and
 
466
        function returns. All other trace message are discarded. To get
 
467
        the most out of these filters, <c>et_viewer</c> needs to known
 
468
        the caller of each function and the time of return. This can be
 
469
        obtained by using both the <c>call</c> and <c>return_to</c>
 
470
        flags when tracing. Note that the <c>return_to</c> flag only
 
471
        works with local call trace, i.e. when trace patterns are set
 
472
        with <c>ttb:tpl</c>.
 
473
        </p>
 
474
      <p>The same result can be obtaind by using the <c>call</c> flag
 
475
        only and setting a match specification like this on local or
 
476
        global function calls:</p>
 
477
      <code type="none">
 
478
1> dbg:fun2ms(fun(_) -> return_trace(),message(caller()) end).
 
479
[{'_',[],[{return_trace},{message,{caller}}]}]      </code>
 
480
      <p>This should however be done with care, since the
 
481
        <c>{return_trace}</c> function in the match specification will
 
482
        destroy tail recursiveness.
 
483
        </p>
 
484
      <p>The <c>modules</c> filter shows each module as a vertical
 
485
        line in the sequence diagram. External function calls/returns
 
486
        are shown as interactions between modules and internal function
 
487
        calls/returns are shown as activities within a module.
 
488
        </p>
 
489
      <p>The <c>functions</c> filter shows each function as a vertical
 
490
        line in the sequence diagram. A function calling itself is shown
 
491
        as an activity within a function, and all other function calls
 
492
        are shown as interactions between functions.
 
493
        </p>
 
494
      <p>The <c>mods_and_procs</c> and <c>funcs_and_procs</c> filters
 
495
        are equivalent to the <c>modules</c> and <c>functions</c>
 
496
        filters respectively, except that each module or function can
 
497
        have several vertical lines, one for each process it resides on.
 
498
        </p>
 
499
      <p>As an example this module is used, and the function
 
500
        <c>bar:f1()</c> is called from another module <c>foo</c>.</p>
 
501
      <code type="none">
 
502
-module(bar).
 
503
-export([f1/0,f3/0]).
 
504
f1() ->
 
505
    f2(),
 
506
    ok.
 
507
f2() ->
 
508
    spawn(?MODULE,f3,[]).
 
509
f3() ->
 
510
    ok.      </code>
 
511
      <p>The <c>call</c> and <c>return_to</c> flags are used, and
 
512
        trace pattern is set on local calls in module <c>bar</c>.
 
513
        </p>
 
514
      <p><c>ttb:format("tiger@durin-ttb", [{handler, et}])</c> gives the
 
515
        following result:
 
516
        </p>
 
517
      <p></p>
 
518
      <image file="et_processes">
 
519
        <icaption>Filter: "processes"</icaption>
 
520
      </image>
 
521
      <image file="et_modsprocs">
 
522
        <icaption>Filter: "mods_and_procs"</icaption>
 
523
      </image>
 
524
    </section>
 
525
  </section>
 
526
 
 
527
  <section>
 
528
    <marker id="fetch_format"></marker>
 
529
    <title>Automatically collect and format logs from all nodes</title>
 
530
    <p>If the option <c>fetch</c> is given to the <c>ttb:stop/1</c>
 
531
      function, trace logs and trace information files are fetched
 
532
      from all nodes after tracing is stopped. The logs are stored in a
 
533
      new directory named <c>ttb_upload-Timestamp</c> under the working
 
534
      directory of the trace control node.
 
535
      </p>
 
536
    <p>If the option <c>format</c> is given to <c>ttb:stop/1</c>, the
 
537
      trace logs are automatically formatted after tracing is
 
538
      stopped. Note that <c>format</c> also implies <c>fetch</c>,
 
539
      i.e. the trace logs will be collected from all nodes as for the
 
540
      <c>fetch</c> option before they are formatted. All logs in the
 
541
      upload directory are merged during formatting.
 
542
      </p>
 
543
  </section>
 
544
 
 
545
  <section>
 
546
    <title>History and Configuration Files</title>
 
547
    <p>For the tracing functionality, <c>dbg</c> could be used instead
 
548
      of the <c>ttb</c> for setting trace flags on processes and trace
 
549
      patterns for call trace, i.e. the functions <c>p</c>, <c>tp</c>,
 
550
      <c>tpl</c>, <c>ctp</c>, <c>ctpl</c> and <c>ctpg</c>. The only
 
551
      thing added by <c>ttb</c> for these functions is that all calls
 
552
      are stored in the history buffer and can be recalled and stored in
 
553
      a configuration file. This makes it easy to setup the same trace
 
554
      environment e.g. if you want to compare two test runs. It also
 
555
      reduces the amount of typing when using <c>ttb</c> from the erlang
 
556
      shell.
 
557
      </p>
 
558
    <p>Use <c>list_history/0</c> to see the content of the history
 
559
      buffer, and <c>run_history/1</c> to re-execute one of the entries.
 
560
      </p>
 
561
    <p>The main purpose of the history buffer is the possibility to
 
562
      create configuration files. Any function stored in the history
 
563
      buffer can be written to a configuration file and used for
 
564
      creating a specific configuration at any time with one single
 
565
      function call.
 
566
      </p>
 
567
    <p>A configuration file is created or extended with
 
568
      <c>write_config/2/3</c>. Configuration files are binary files
 
569
      and can therefore only be read and written with functions provided
 
570
      by <c>ttb</c>.
 
571
      </p>
 
572
    <p>You can write the complete content of the history buffer to a
 
573
      config file by calling
 
574
      <c>ttb:write_config(ConfigFile,all)</c>. And you can write
 
575
      selected entries from the history by calling
 
576
      <c>ttb:write_config(ConfigFile,NumList)</c>, where
 
577
      <c>NumList</c> is a list of integers pointing out the history
 
578
      entries to write.
 
579
      </p>
 
580
    <p>User defined entries can also be written to a config file by
 
581
      calling the function
 
582
      <c>ttb:write_config(ConfigFile,ConfigList)</c> where
 
583
      <c>ConfigList</c> is a list of <c>{Module,Function,Args}</c>.
 
584
      </p>
 
585
    <p>Any existing file <c>ConfigFile</c> is deleted and a new file
 
586
      is created when <c>write_config/2</c> is called. The option
 
587
      <c>append</c> can be used if you wish to add something at the end
 
588
      of an existing config file, e.g.
 
589
      <c>ttb:write_config(ConfigFile,What,[append])</c>.
 
590
      </p>
 
591
 
 
592
    <section>
 
593
      <title>Example: History and configuration files</title>
 
594
      <p>See the content of the history buffer</p>
 
595
      <code type="none"><![CDATA[
 
596
(tiger@durin)191> ttb:tracer().                                    
 
597
{ok,[tiger@durin]}
 
598
(tiger@durin)192> ttb:p(self(),[garbage_collection,call]).               
 
599
{ok,{[<0.1244.0>],[garbage_collection,call]}}
 
600
(tiger@durin)193> ttb:tp(ets,new,2,[]).                                  
 
601
{ok,[{matched,1}]}
 
602
(tiger@durin)194> ttb:list_history().
 
603
[{1,{ttb,tracer,[tiger@durin,[]]}},
 
604
 {2,{ttb,p,[<0.1244.0>,[garbage_collection,call]]}},
 
605
 {3,{ttb,tp,[ets,new,2,[]]}}]      ]]></code>
 
606
      <p>Execute an entry from the history buffer:</p>
 
607
      <code type="none"><![CDATA[
 
608
(tiger@durin)195> ttb:ctp(ets,new,2).
 
609
{ok,[{matched,1}]}
 
610
(tiger@durin)196> ttb:list_history().
 
611
[{1,{ttb,tracer,[tiger@durin,[]]}},
 
612
 {2,{ttb,p,[<0.1244.0>,[garbage_collection,call]]}},
 
613
 {3,{ttb,tp,[ets,new,2,[]]}},
 
614
 {4,{ttb,ctp,[ets,new,2]}}]
 
615
(tiger@durin)197> ttb:run_history(3).
 
616
ttb:tp(ets,new,2,[]) ->
 
617
{ok,[{matched,1}]}      ]]></code>
 
618
      <p>Write the content of the history buffer to a configuration
 
619
        file:</p>
 
620
      <code type="none"><![CDATA[
 
621
(tiger@durin)198> ttb:write_config("myconfig",all).
 
622
ok
 
623
(tiger@durin)199> ttb:list_config("myconfig").
 
624
[{1,{ttb,tracer,[tiger@durin,[]]}},
 
625
 {2,{ttb,p,[<0.1244.0>,[garbage_collection,call]]}},
 
626
 {3,{ttb,tp,[ets,new,2,[]]}},
 
627
 {4,{ttb,ctp,[ets,new,2]}},
 
628
 {5,{ttb,tp,[ets,new,2,[]]}}]      ]]></code>
 
629
      <p>Extend an existing configuration:</p>
 
630
      <code type="none"><![CDATA[
 
631
(tiger@durin)200> ttb:write_config("myconfig",[{ttb,tp,[ets,delete,1,[]]}],
 
632
[append]).
 
633
ok
 
634
(tiger@durin)201> ttb:list_config("myconfig").
 
635
[{1,{ttb,tracer,[tiger@durin,[]]}},
 
636
 {2,{ttb,p,[<0.1244.0>,[garbage_collection,call]]}},
 
637
 {3,{ttb,tp,[ets,new,2,[]]}},
 
638
 {4,{ttb,ctp,[ets,new,2]}},
 
639
 {5,{ttb,tp,[ets,new,2,[]]}},
 
640
 {6,{ttb,tp,[ets,delete,1,[]]}}]      ]]></code>
 
641
      <p>Go back to a previous configuration after stopping Trace Tool
 
642
        Builder:</p>
 
643
      <code type="none"><![CDATA[
 
644
(tiger@durin)202> ttb:stop().
 
645
ok
 
646
(tiger@durin)203> ttb:run_config("myconfig").
 
647
ttb:tracer(tiger@durin,[]) ->
 
648
{ok,[tiger@durin]}
 
649
 
 
650
ttb:p(<0.1244.0>,[garbage_collection,call]) ->
 
651
{ok,{[<0.1244.0>],[garbage_collection,call]}}
 
652
 
 
653
ttb:tp(ets,new,2,[]) ->
 
654
{ok,[{matched,1}]}
 
655
 
 
656
ttb:ctp(ets,new,2) ->
 
657
{ok,[{matched,1}]}
 
658
 
 
659
ttb:tp(ets,new,2,[]) ->
 
660
{ok,[{matched,1}]}
 
661
 
 
662
ttb:tp(ets,delete,1,[]) ->
 
663
{ok,[{matched,1}]}
 
664
 
 
665
ok      ]]></code>
 
666
      <p>Write selected entries from the history buffer to a
 
667
        configuration file:</p>
 
668
      <code type="none"><![CDATA[
 
669
(tiger@durin)204> ttb:list_history().          
 
670
[{1,{ttb,tracer,[tiger@durin,[]]}},
 
671
 {2,{ttb,p,[<0.1244.0>,[garbage_collection,call]]}},
 
672
 {3,{ttb,tp,[ets,new,2,[]]}},
 
673
 {4,{ttb,ctp,[ets,new,2]}},
 
674
 {5,{ttb,tp,[ets,new,2,[]]}},
 
675
 {6,{ttb,tp,[ets,delete,1,[]]}}]
 
676
(tiger@durin)205> ttb:write_config("myconfig",[1,2,3,6]).
 
677
ok
 
678
(tiger@durin)206> ttb:list_config("myconfig").
 
679
[{1,{ttb,tracer,[tiger@durin,[]]}},
 
680
 {2,{ttb,p,[<0.1244.0>,[garbage_collection,call]]}},
 
681
 {3,{ttb,tp,[ets,new,2,[]]}},
 
682
 {4,{ttb,tp,[ets,delete,1,[]]}}]
 
683
(tiger@durin)207>       ]]></code>
 
684
    </section>
 
685
  </section>
 
686
 
 
687
  <section>
 
688
    <title>Sequential Tracing</title>
 
689
    <p>To learn what sequential tracing is and how it can be used,
 
690
      please turn to the reference manual for the
 
691
      <em><c>seq_trace</c></em> module in the <em><c>kernel</c></em>
 
692
      application.
 
693
      </p>
 
694
    <p>The support for sequencial tracing provided by the Trace Tool
 
695
      Builder includes </p>
 
696
    <list type="bulleted">
 
697
      <item>Initiation of the system tracer. This is automatically
 
698
       done when a trace port is started with <c>ttb:tracer/0/1/2</c></item>
 
699
      <item>Creation of match specifications which activates
 
700
       sequential tracing</item>
 
701
    </list>
 
702
    <p>Starting sequential tracing requires that a tracer has been
 
703
      started with the <c>ttb:tracer/0/1/2</c> function. Sequential
 
704
      tracing can then either be started via a trigger function with a
 
705
      match specification created with <c>ttb:seq_trigger_ms/0/1</c>,
 
706
      or directly by using the <c>seq_trace</c> module in the
 
707
      <c>kernel</c> application.
 
708
      </p>
 
709
 
 
710
    <section>
 
711
      <title>Example: Sequential tracing</title>
 
712
      <p>In the following example, the function
 
713
        <c>dbg:get_tracer/0</c> is used as trigger for sequential
 
714
        tracing:</p>
 
715
      <code type="none"><![CDATA[
 
716
(tiger@durin)110> ttb:tracer().                               
 
717
{ok,[tiger@durin]}
 
718
(tiger@durin)111> ttb:p(self(),call).                               
 
719
{ok,{[<0.158.0>],[call]}}
 
720
(tiger@durin)112> ttb:tp(dbg,get_tracer,0,ttb:seq_trigger_ms(send)).
 
721
{ok,[{matched,1},{saved,1}]}
 
722
(tiger@durin)113> dbg:get_tracer(), seq_trace:reset_trace().         
 
723
true
 
724
(tiger@durin)114> ttb:stop().                                       
 
725
ok
 
726
(tiger@durin)115> ttb:format("tiger@durin-ttb").                    
 
727
({<0.158.0>,{shell,evaluator,3},tiger@durin}) call dbg:get_tracer()
 
728
SeqTrace [0]: ({<0.158.0>,{shell,evaluator,3},tiger@durin}) 
 
729
{<0.237.0>,dbg,tiger@durin} ! {<0.158.0>,{get_tracer,tiger@durin}} 
 
730
[Serial: {0,1}]
 
731
SeqTrace [0]: ({<0.237.0>,dbg,tiger@durin}) 
 
732
{<0.158.0>,{shell,evaluator,3},tiger@durin} ! {dbg,{ok,#Port<0.222>}} 
 
733
[Serial: {1,2}]
 
734
ok
 
735
(tiger@durin)116>       ]]></code>
 
736
      <p>Starting sequential tracing with a trigger is actually more
 
737
        useful if the trigger function is not called directly from the
 
738
        shell, but rather implicitly within a larger system. When
 
739
        calling a function from the shell, it is simpler to start
 
740
        sequential tracing directly, e.g.</p>
 
741
      <code type="none"><![CDATA[
 
742
(tiger@durin)116> ttb:tracer().                               
 
743
{ok,[tiger@durin]}
 
744
(tiger@durin)117> seq_trace:set_token(send,true), dbg:get_tracer(), 
 
745
seq_trace:reset_trace().
 
746
true
 
747
(tiger@durin)118> ttb:stop().
 
748
ok
 
749
(tiger@durin)119> ttb:format("tiger@durin-ttb").
 
750
SeqTrace [0]: ({<0.158.0>,{shell,evaluator,3},tiger@durin}) 
 
751
{<0.246.0>,dbg,tiger@durin} ! {<0.158.0>,{get_tracer,tiger@durin}} 
 
752
[Serial: {0,1}]
 
753
SeqTrace [0]: ({<0.246.0>,dbg,tiger@durin}) 
 
754
{<0.158.0>,{shell,evaluator,3},tiger@durin} ! {dbg,{ok,#Port<0.229>}} 
 
755
[Serial: {1,2}]
 
756
ok
 
757
(tiger@durin)120>       ]]></code>
 
758
      <p>In both examples above, the <c>seq_trace:reset_trace/0</c>
 
759
        resets the trace token immediately after the traced function in
 
760
        order to avoid lots of trace messages due to the printouts in
 
761
        the erlang shell.
 
762
        </p>
 
763
      <p>All functions in the <c>seq_trace</c> module, except
 
764
        <c>set_system_tracer/1</c>, can be used after the trace port has
 
765
        been started with <c>ttb:tracer/0/1/2</c>.
 
766
        </p>
 
767
    </section>
 
768
  </section>
 
769
 
 
770
  <section>
 
771
    <title>Example: Multipurpose trace tool</title>
 
772
    <p>The module <c>multitrace.erl</c> which can be found in the
 
773
      <c>src</c> directory of the Observer application implements a
 
774
      small tool with three possible trace settings. The trace messages
 
775
      are written to binary files which can be formatted with the
 
776
      function <em><c>multitrace:format/1/2</c></em>.
 
777
      </p>
 
778
    <taglist>
 
779
      <tag><em><c>multitrace:debug(What)</c></em></tag>
 
780
      <item>Start calltrace on all processes and trace the given
 
781
       function(s). The format handler used is
 
782
      <c>multitrace:handle_debug/4</c> which prints each call and
 
783
       return. <c>What</c> must be an item or a list of items to trace,
 
784
       given on the format <c>{Module,Function,Arity}</c>,
 
785
      <c>{Module,Function}</c> or just <c>Module</c>.</item>
 
786
      <tag><em><c>multitrace:gc(Procs)</c></em></tag>
 
787
      <item>Trace garbage collection on the given process(es). The
 
788
       format handler used is <c>multitrace:handle_gc/4</c> which
 
789
       prints start and stop and the time spent for each GC.</item>
 
790
      <tag><em><c>multitrace:schedule(Procs)</c></em></tag>
 
791
      <item>Trace in- and out-scheduling on the given process(es). The
 
792
       format handler used is <c>multitrace:handle_schedule/4</c> which
 
793
       prints each in and out scheduling with process, timestamp and
 
794
       current function. It also prints the total time each traced
 
795
       process was scheduled in.</item>
 
796
    </taglist>
 
797
  </section>
 
798
</chapter>
 
799