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

« back to all changes in this revision

Viewing changes to lib/kernel/doc/src/seq_trace.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 erlref SYSTEM "erlref.dtd">
 
3
 
 
4
<erlref>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>1998</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>seq_trace</title>
 
27
    <prepared>kenneth@erix.ericsson.se</prepared>
 
28
    <docno></docno>
 
29
    <date>1998-04-16</date>
 
30
    <rev>A</rev>
 
31
  </header>
 
32
  <module>seq_trace</module>
 
33
  <modulesummary>Sequential Tracing of Messages</modulesummary>
 
34
  <description>
 
35
    <p>Sequential tracing makes it possible to trace all messages
 
36
      resulting from one initial message. Sequential tracing is
 
37
      completely independent of the ordinary tracing in Erlang, which
 
38
      is controlled by the <c>erlang:trace/3</c> BIF. See the chapter
 
39
      <seealso marker="#whatis">What is Sequential Tracing</seealso>
 
40
      below for more information about what sequential tracing is and
 
41
      how it can be used.</p>
 
42
    <p><c>seq_trace</c> provides functions which control all aspects of 
 
43
      sequential tracing. There are functions for activation,
 
44
      deactivation, inspection and for collection of the trace output.</p>
 
45
    <note>
 
46
      <p>The implementation of sequential tracing is in beta status.
 
47
        This means that the programming interface still might undergo
 
48
        minor adjustments (possibly incompatible) based on feedback
 
49
        from users.</p>
 
50
    </note>
 
51
  </description>
 
52
  <funcs>
 
53
    <func>
 
54
      <name>set_token(Token) -> PreviousToken</name>
 
55
      <fsummary>Set the trace token</fsummary>
 
56
      <type>
 
57
        <v>Token = PreviousToken = term() | []</v>
 
58
      </type>
 
59
      <desc>
 
60
        <p>Sets the trace token for the calling process to <c>Token</c>.
 
61
          If <c>Token == []</c> then tracing is disabled, otherwise
 
62
          <c>Token</c> should be an Erlang term returned from
 
63
          <c>get_token/0</c> or <c>set_token/1</c>. <c>set_token/1</c>
 
64
          can be used to temporarily exclude message passing from
 
65
          the trace by setting the trace token to empty like this:</p>
 
66
        <code type="none">
 
67
OldToken = seq_trace:set_token([]), % set to empty and save 
 
68
                                    % old value
 
69
% do something that should not be part of the trace
 
70
io:format("Exclude the signalling caused by this~n"),
 
71
seq_trace:set_token(OldToken), % activate the trace token again
 
72
...  </code>
 
73
        <p>Returns the previous value of the trace token.</p>
 
74
      </desc>
 
75
    </func>
 
76
    <func>
 
77
      <name>set_token(Component, Val) -> {Component, OldVal}</name>
 
78
      <fsummary>Set a component of the trace token</fsummary>
 
79
      <type>
 
80
        <v>Component = label | serial | Flag</v>
 
81
        <v>&nbsp;Flag = send | 'receive' | print | timestamp </v>
 
82
        <v>Val = OldVal -- see below</v>
 
83
      </type>
 
84
      <desc>
 
85
        <p>Sets the individual <c>Component</c> of the trace token to
 
86
          <c>Val</c>. Returns the previous value of the component.</p>
 
87
        <taglist>
 
88
          <tag><c>set_token(label, Int)</c></tag>
 
89
          <item>
 
90
            <p>The <c>label</c> component is an integer which
 
91
              identifies all events belonging to the same sequential
 
92
              trace. If several sequential traces can be active
 
93
              simultaneously, <c>label</c> is used to identify
 
94
              the separate traces. Default is 0.</p>
 
95
          </item>
 
96
          <tag><c>set_token(serial, SerialValue)</c></tag>
 
97
          <item>
 
98
            <p><c>SerialValue = {Previous, Current}</c>.
 
99
              The <c>serial</c> component contains counters which
 
100
              enables the traced messages to be sorted, should never be
 
101
              set explicitly by the user as these counters are updated
 
102
              automatically. Default is <c>{0, 0}</c>.</p>
 
103
          </item>
 
104
          <tag><c>set_token(send, Bool)</c></tag>
 
105
          <item>
 
106
            <p>A trace token flag (<c>true | false</c>) which
 
107
              enables/disables tracing on message sending. Default is
 
108
              <c>false</c>.</p>
 
109
          </item>
 
110
          <tag><c>set_token('receive', Bool)</c></tag>
 
111
          <item>
 
112
            <p>A trace token flag (<c>true | false</c>) which
 
113
              enables/disables tracing on message reception. Default is
 
114
              <c>false</c>.</p>
 
115
          </item>
 
116
          <tag><c>set_token(print, Bool)</c></tag>
 
117
          <item>
 
118
            <p>A trace token flag (<c>true | false</c>) which
 
119
              enables/disables tracing on explicit calls to
 
120
              <c>seq_trace:print/1</c>. Default is <c>false</c>.</p>
 
121
          </item>
 
122
          <tag><c>set_token(timestamp, Bool)</c></tag>
 
123
          <item>
 
124
            <p>A trace token flag (<c>true | false</c>) which
 
125
              enables/disables a timestamp to be generated for each
 
126
              traced event. Default is <c>false</c>.</p>
 
127
          </item>
 
128
        </taglist>
 
129
      </desc>
 
130
    </func>
 
131
    <func>
 
132
      <name>get_token() -> TraceToken</name>
 
133
      <fsummary>Return the value of the trace token</fsummary>
 
134
      <type>
 
135
        <v>TraceToken = term() | []</v>
 
136
      </type>
 
137
      <desc>
 
138
        <p>Returns the value of the trace token for the calling process.
 
139
          If <c>[]</c> is returned, it means that tracing is not active.
 
140
          Any other value returned is the value of an active trace
 
141
          token. The value returned can be used as input to
 
142
          the <c>set_token/1</c> function.</p>
 
143
      </desc>
 
144
    </func>
 
145
    <func>
 
146
      <name>get_token(Component) -> {Component, Val}</name>
 
147
      <fsummary>Return the value of a trace token component</fsummary>
 
148
      <type>
 
149
        <v>Component = label | serial | Flag</v>
 
150
        <v>&nbsp;Flag = send | 'receive' | print | timestamp </v>
 
151
        <v>Val -- see set_token/2</v>
 
152
      </type>
 
153
      <desc>
 
154
        <p>Returns the value of the trace token component
 
155
          <c>Component</c>. See
 
156
          <seealso marker="#set_token/2">set_token/2</seealso> for
 
157
          possible values of <c>Component</c> and <c>Val</c>.</p>
 
158
      </desc>
 
159
    </func>
 
160
    <func>
 
161
      <name>print(TraceInfo) -> void()</name>
 
162
      <fsummary>Put the Erlang term <c>TraceInfo</c>into the sequential trace output</fsummary>
 
163
      <type>
 
164
        <v>TraceInfo = term()</v>
 
165
      </type>
 
166
      <desc>
 
167
        <p>Puts the Erlang term <c>TraceInfo</c> into the sequential
 
168
          trace output if the calling process currently is executing
 
169
          within a sequential trace and the <c>print</c> flag of
 
170
          the trace token is set.</p>
 
171
      </desc>
 
172
    </func>
 
173
    <func>
 
174
      <name>print(Label, TraceInfo) -> void()</name>
 
175
      <fsummary>Put the Erlang term <c>TraceInfo</c>into the sequential trace output</fsummary>
 
176
      <type>
 
177
        <v>Label = int()</v>
 
178
        <v>TraceInfo = term()</v>
 
179
      </type>
 
180
      <desc>
 
181
        <p>Same as <c>print/1</c> with the additional condition that
 
182
          <c>TraceInfo</c> is output only if <c>Label</c> is equal to
 
183
          the label component of the trace token.</p>
 
184
      </desc>
 
185
    </func>
 
186
    <func>
 
187
      <name>reset_trace() -> void()</name>
 
188
      <fsummary>Stop all sequential tracing on the local node</fsummary>
 
189
      <desc>
 
190
        <p>Sets the trace token to empty for all processes on the
 
191
          local node. The process internal counters used to create
 
192
          the serial of the trace token is set to 0. The trace token is
 
193
          set to empty for all messages in message queues. Together
 
194
          this will effectively stop all ongoing sequential tracing in
 
195
          the local node.</p>
 
196
      </desc>
 
197
    </func>
 
198
    <func>
 
199
      <name>set_system_tracer(Tracer) -> OldTracer</name>
 
200
      <fsummary>Set the system tracer</fsummary>
 
201
      <type>
 
202
        <v>Tracer = OldTracer = pid() | port() | false</v>
 
203
      </type>
 
204
      <desc>
 
205
        <p>Sets the system tracer. The system tracer can be either a
 
206
          process or port denoted by <c>Tracer</c>. Returns the previous
 
207
          value (which can be <c>false</c> if no system tracer is
 
208
          active).</p>
 
209
        <p>Failure: <c>{badarg, Info}}</c> if <c>Pid</c> is not an
 
210
          existing local pid.</p>
 
211
      </desc>
 
212
    </func>
 
213
    <func>
 
214
      <name>get_system_tracer() -> Tracer</name>
 
215
      <fsummary>Return the pid() or port() of the current system tracer.</fsummary>
 
216
      <type>
 
217
        <v>Tracer = pid() | port() | false</v>
 
218
      </type>
 
219
      <desc>
 
220
        <p>Returns the pid or port identifier of the current system
 
221
          tracer or <c>false</c> if no system tracer is activated.</p>
 
222
      </desc>
 
223
    </func>
 
224
  </funcs>
 
225
 
 
226
  <section>
 
227
    <title>Trace Messages Sent To the System Tracer</title>
 
228
    <p>The format of the messages are:</p>
 
229
    <code type="none">
 
230
{seq_trace, Label, SeqTraceInfo, TimeStamp}</code>
 
231
    <p>or</p>
 
232
    <code type="none">
 
233
{seq_trace, Label, SeqTraceInfo}</code>
 
234
    <p>depending on whether the <c>timestamp</c> flag of the trace
 
235
      token is set to <c>true</c> or <c>false</c>. Where:</p>
 
236
    <code type="none">
 
237
Label = int()
 
238
TimeStamp = {Seconds, Milliseconds, Microseconds}  
 
239
  Seconds = Milliseconds = Microseconds = int()</code>
 
240
    <p>The <c>SeqTraceInfo</c> can have the following formats:</p>
 
241
    <taglist>
 
242
      <tag><c>{send, Serial, From, To, Message}</c></tag>
 
243
      <item>
 
244
        <p>Used when a process <c>From</c> with its trace token flag
 
245
          <c>print</c> set to <c>true</c> has sent a message.</p>
 
246
      </item>
 
247
      <tag><c>{'receive', Serial, From, To, Message}</c></tag>
 
248
      <item>
 
249
        <p>Used when a process <c>To</c> receives a message with a
 
250
          trace token that has the <c>'receive'</c> flag set to
 
251
          <c>true</c>.</p>
 
252
      </item>
 
253
      <tag><c>{print, Serial, From, _, Info}</c></tag>
 
254
      <item>
 
255
        <p>Used when a process <c>From</c> has called 
 
256
          <c>seq_trace:print(Label, TraceInfo)</c> and has a trace
 
257
          token with the <c>print</c> flag set to <c>true</c> and
 
258
          <c>label</c> set to <c>Label</c>.</p>
 
259
      </item>
 
260
    </taglist>
 
261
    <p><c>Serial</c> is a tuple <c>{PreviousSerial, ThisSerial}</c>,
 
262
      where the first integer <c>PreviousSerial</c> denotes the serial
 
263
      counter passed in the last received message which carried a trace 
 
264
      token. If the process is the first one in a new sequential trace,
 
265
      <c>PreviousSerial</c> is set to the value of the process internal 
 
266
      "trace clock". The second integer <c>ThisSerial</c> is the serial
 
267
      counter that a process sets on outgoing messages and it is based
 
268
      on the process internal "trace clock" which is incremented by one
 
269
      before it is attached to the trace token in the message.</p>
 
270
  </section>
 
271
 
 
272
  <section>
 
273
    <marker id="whatis"></marker>
 
274
    <title>What is Sequential Tracing</title>
 
275
    <p>Sequential tracing is a way to trace a sequence of messages sent
 
276
      between different local or remote processes, where the sequence
 
277
      is initiated by one single message. In short it works like this:</p>
 
278
    <p>Each process has a <em>trace token</em>, which can be empty or
 
279
      not empty. When not empty the trace token can be seen as
 
280
      the tuple <c>{Label, Flags, Serial, From}</c>. The trace token is
 
281
      passed invisibly with each message.</p>
 
282
    <p>In order to start a sequential trace the user must explicitly set
 
283
      the trace token in the process that will send the first message
 
284
      in a sequence.</p>
 
285
    <p>The trace token of a process is set each time the process
 
286
      matches a message in a receive statement, according to the trace
 
287
      token carried by the received message, empty or not.</p>
 
288
    <p>On each Erlang node a process can be set as the <em>system tracer</em>. This process will receive trace messages each time
 
289
      a message with a trace token is sent or received (if the trace
 
290
      token flag <c>send</c> or <c>'receive'</c> is set). The system
 
291
      tracer can then print each trace event, write it to a file or
 
292
      whatever suitable.</p>
 
293
    <note>
 
294
      <p>The system tracer will only receive those trace events that
 
295
        occur locally within the Erlang node. To get the whole picture
 
296
        of a sequential trace that involves processes on several Erlang
 
297
        nodes, the output from the system tracer on each involved node
 
298
        must be merged (off line).</p>
 
299
    </note>
 
300
    <p>In the following sections Sequential Tracing and its most
 
301
      fundamental concepts are described.</p>
 
302
  </section>
 
303
 
 
304
  <section>
 
305
    <title>Trace Token</title>
 
306
    <p>Each process has a current trace token. Initially the token is
 
307
      empty. When the process sends a message to another process, a
 
308
      copy of the current token will be sent "invisibly" along with
 
309
      the message.</p>
 
310
    <p>The current token of a process is set in two ways, either</p>
 
311
    <list type="ordered">
 
312
      <item>
 
313
        <p>explicitly by the process itself, through a call to
 
314
          <c>seq_trace:set_token</c>, or</p>
 
315
      </item>
 
316
      <item>
 
317
        <p>when a message is received.</p>
 
318
      </item>
 
319
    </list>
 
320
    <p>In both cases the current token will be set. In particular, if
 
321
      the token of a message received is empty, the current token of
 
322
      the process is set to empty.</p>
 
323
    <p>A trace token contains a label, and a set of flags. Both
 
324
      the label and the flags are set in 1 and 2 above.</p>
 
325
  </section>
 
326
 
 
327
  <section>
 
328
    <title>Serial</title>
 
329
    <p>The trace token contains a component which is called
 
330
      <c>serial</c>. It consists of two integers <c>Previous</c> and
 
331
      <c>Current</c>. The purpose is to uniquely identify each traced
 
332
      event within a trace sequence and to order the messages
 
333
      chronologically and in the different branches if any.</p>
 
334
    <p>The algorithm for updating <c>Serial</c> can be described as
 
335
      follows:</p>
 
336
    <p>Let each process have two counters <c>prev_cnt</c> and
 
337
      <c>curr_cnt</c> which both are set to 0 when a process is created.
 
338
      The counters are updated at the following occasions:</p>
 
339
    <list type="bulleted">
 
340
      <item>
 
341
        <p><em>When the process is about to send a message and the trace token is not empty.</em></p>
 
342
        <p>Let the serial of the trace token be <c>tprev</c> and
 
343
          <c>tcurr</c>.          <br></br>
 
344
<c>curr_cnt := curr_cnt + 1</c>          <br></br>
 
345
<c>tprev := prev_cnt</c>          <br></br>
 
346
<c>tcurr := curr_cnt</c></p>
 
347
        <p>The trace token with <c>tprev</c> and <c>tcurr</c> is then
 
348
          passed along with the message.</p>
 
349
      </item>
 
350
      <item>
 
351
        <p><em>When the process calls</em><c>seq_trace:print(Label, Info)</c>, <em>Label matches the label part of the trace token and the trace token print flag is true.</em></p>
 
352
        <p>The same algorithm as for send above.</p>
 
353
      </item>
 
354
      <item>
 
355
        <p><em>When a message is received and contains a nonempty trace token.</em></p>
 
356
        <p>The process trace token is set to the trace token from
 
357
          the message.</p>
 
358
        <p>Let the serial of the trace token be <c>tprev</c> and
 
359
          <c>tcurr</c>.          <br></br>
 
360
<c><![CDATA[if (curr_cnt < tcurr )]]></c>          <br></br>
 
361
 
 
362
          &nbsp; &nbsp; &nbsp; &nbsp;<c>curr_cnt := tcurr</c>          <br></br>
 
363
<c>prev_cnt := tcurr</c></p>
 
364
      </item>
 
365
    </list>
 
366
    <p>The <c>curr_cnt</c> of a process is incremented each time
 
367
      the process is involved in a sequential trace. The counter can
 
368
      reach its limit (27 bits) if a process is very long-lived and is
 
369
      involved in much sequential tracing. If the counter overflows it
 
370
      will not be possible to use the serial for ordering of the trace
 
371
      events. To prevent the counter from overflowing in the middle of
 
372
      a sequential trace the function <c>seq_trace:reset_trace/0</c>
 
373
      can be called to reset the <c>prev_cnt</c> and <c>curr_cnt</c> of
 
374
      all processes in the Erlang node. This function will also set all
 
375
      trace tokens in processes and their message queues to empty and
 
376
      will thus stop all ongoing sequential tracing.</p>
 
377
  </section>
 
378
 
 
379
  <section>
 
380
    <title>Performance considerations</title>
 
381
    <p>The performance degradation for a system which is enabled for
 
382
      Sequential Tracing is negligible as long as no tracing is
 
383
      activated. When tracing is activated there will of course be an
 
384
      extra cost for each traced message but all other messages will be
 
385
      unaffected.</p>
 
386
  </section>
 
387
 
 
388
  <section>
 
389
    <title>Ports</title>
 
390
    <p>Sequential tracing is not performed across ports.</p>
 
391
    <p>If the user for some reason wants to pass the trace token to a
 
392
      port this has to be done manually in the code of the port
 
393
      controlling process. The port controlling processes have to check
 
394
      the appropriate sequential trace settings (as obtained from
 
395
      <c>seq_trace:get_token/1</c> and include trace information in
 
396
      the message data sent to their respective ports.</p>
 
397
    <p>Similarly, for messages received from a port, a port controller
 
398
      has to retrieve trace specific information, and set appropriate
 
399
      sequential trace flags through calls to
 
400
      <c>seq_trace:set_token/2</c>.</p>
 
401
  </section>
 
402
 
 
403
  <section>
 
404
    <title>Distribution</title>
 
405
    <p>Sequential tracing between nodes is performed transparently.
 
406
      This applies to C-nodes built with Erl_Interface too. A C-node
 
407
      built with Erl_Interface only maintains one trace token, which
 
408
      means that the C-node will appear as one process from
 
409
      the sequential tracing point of view.</p>
 
410
    <p>In order to be able to perform sequential tracing between
 
411
      distributed Erlang nodes, the distribution protocol has been
 
412
      extended (in a backward compatible way). An Erlang node which
 
413
      supports sequential tracing can communicate with an older
 
414
      (OTP R3B) node but messages passed within that node can of course
 
415
      not be traced.</p>
 
416
  </section>
 
417
 
 
418
  <section>
 
419
    <title>Example of Usage</title>
 
420
    <p>The example shown here will give rough idea of how the new
 
421
      primitives can be used and what kind of output it will produce.</p>
 
422
    <p>Assume that we have an initiating process with
 
423
      <c><![CDATA[Pid == <0.30.0>]]></c> like this:</p>
 
424
    <code type="none">
 
425
-module(seqex).
 
426
-compile(export_all).
 
427
 
 
428
loop(Port) ->
 
429
    receive 
 
430
        {Port,Message} ->
 
431
            seq_trace:set_token(label,17),
 
432
            seq_trace:set_token('receive',true),
 
433
            seq_trace:set_token(print,true),
 
434
            seq_trace:print(17,"**** Trace Started ****"),
 
435
\011    call_server ! {self(),the_message};
 
436
\011{ack,Ack} ->
 
437
\011    ok
 
438
    end,
 
439
    loop(Port).</code>
 
440
    <p>And a registered process <c>call_server</c> with
 
441
      <c><![CDATA[Pid == <0.31.0>]]></c> like this:</p>
 
442
    <code type="none">
 
443
loop() ->
 
444
    receive
 
445
        {PortController,Message} ->
 
446
\011    Ack = {received, Message},
 
447
\011    seq_trace:print(17,"We are here now"),
 
448
\011    PortController ! {ack,Ack}
 
449
    end,
 
450
    loop().</code>
 
451
    <p>A possible output from the system's sequential_tracer (inspired
 
452
      by AXE-10 and MD-110) could look like:</p>
 
453
    <pre>
 
454
17:&lt;0.30.0> Info {0,1} WITH
 
455
"**** Trace Started ****"
 
456
17:&lt;0.31.0> Received {0,2} FROM &lt;0.30.0> WITH
 
457
{&lt;0.30.0>,the_message}
 
458
17:&lt;0.31.0> Info {2,3} WITH
 
459
"We are here now"
 
460
17:&lt;0.30.0> Received {2,4} FROM &lt;0.31.0> WITH
 
461
{ack,{received,the_message}}</pre>
 
462
    <p>The implementation of a system tracer process that produces
 
463
      the printout above could look like this:</p>
 
464
    <code type="none">
 
465
tracer() ->
 
466
    receive
 
467
        {seq_trace,Label,TraceInfo} ->
 
468
           print_trace(Label,TraceInfo,false);
 
469
        {seq_trace,Label,TraceInfo,Ts} ->
 
470
           print_trace(Label,TraceInfo,Ts);
 
471
        Other -> ignore
 
472
    end,
 
473
    tracer().        
 
474
 
 
475
print_trace(Label,TraceInfo,false) ->
 
476
    io:format("~p:",[Label]),
 
477
    print_trace(TraceInfo);
 
478
print_trace(Label,TraceInfo,Ts) ->
 
479
    io:format("~p ~p:",[Label,Ts]),
 
480
    print_trace(TraceInfo).
 
481
 
 
482
print_trace({print,Serial,From,_,Info}) ->
 
483
    io:format("~p Info ~p WITH~n~p~n", [From,Serial,Info]);
 
484
print_trace({'receive',Serial,From,To,Message}) ->
 
485
    io:format("~p Received ~p FROM ~p WITH~n~p~n", 
 
486
              [To,Serial,From,Message]);
 
487
print_trace({send,Serial,From,To,Message}) ->
 
488
    io:format("~p Sent ~p TO ~p WITH~n~p~n", 
 
489
              [From,Serial,To,Message]).</code>
 
490
    <p>The code that creates a process that runs the tracer function
 
491
      above and sets that process as the system tracer could look like
 
492
      this:</p>
 
493
    <code type="none">
 
494
start() ->
 
495
    Pid = spawn(?MODULE,tracer,[]),
 
496
    seq_trace:set_system_tracer(Pid), % set Pid as the system tracer 
 
497
    ok.</code>
 
498
    <p>With a function like <c>test/0</c> below the whole example can be
 
499
      started.</p>
 
500
    <code type="none">
 
501
test() ->
 
502
    P = spawn(?MODULE, loop, [port]),
 
503
    register(call_server, spawn(?MODULE, loop, [])),
 
504
    start(),
 
505
    P ! {port,message}.</code>
 
506
  </section>
 
507
</erlref>
 
508