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

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/gen_event.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>1996</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>gen_event</title>
 
27
    <prepared></prepared>
 
28
    <docno></docno>
 
29
    <date></date>
 
30
    <rev></rev>
 
31
  </header>
 
32
  <module>gen_event</module>
 
33
  <modulesummary>Generic Event Handling Behaviour</modulesummary>
 
34
  <description>
 
35
    <p>A behaviour module for implementing event handling functionality.
 
36
      The OTP event handling model consists of a generic event manager
 
37
      process with an arbitrary number of event handlers which are added and
 
38
      deleted dynamically.</p>
 
39
    <p>An event manager implemented using this module will have a standard
 
40
      set of interface functions and include functionality for tracing and
 
41
      error reporting. It will also fit into an OTP supervision tree.
 
42
      Refer to <em>OTP Design Principles</em> for more information.</p>
 
43
    <p>Each event handler is implemented as a callback module exporting
 
44
      a pre-defined set of functions. The relationship between the behaviour
 
45
      functions and the callback functions can be illustrated as follows:</p>
 
46
    <pre>
 
47
gen_event module                   Callback module
 
48
---------------\011                   -------------
 
49
gen_event:start_link       ----->  -
 
50
 
 
51
gen_event:add_handler
 
52
gen_event:add_suphandler   ----->  Module:init/1
 
53
 
 
54
gen_event:notify
 
55
gen_event:sync_notify      ----->  Module:handle_event/2
 
56
 
 
57
gen_event:call             ----->  Module:handle_call/2
 
58
 
 
59
-                          ----->  Module:handle_info/2
 
60
 
 
61
gen_event:delete_handler   ----->  Module:terminate/2
 
62
 
 
63
gen_event:swap_handler
 
64
gen_event:swap_sup_handler ----->  Module1:terminate/2
 
65
                                   Module2:init/1
 
66
 
 
67
gen_event:which_handlers   ----->  -
 
68
 
 
69
gen_event:stop             ----->  Module:terminate/2
 
70
 
 
71
-                          ----->  Module:code_change/3</pre>
 
72
    <p>Since each event handler is one callback module, an event manager
 
73
      will have several callback modules which are added and deleted
 
74
      dynamically. Therefore <c>gen_event</c> is more tolerant of callback
 
75
      module errors than the other behaviours. If a callback function for
 
76
      an installed event handler fails with <c>Reason</c>, or returns a
 
77
      bad value <c>Term</c>, the event manager will not fail. It will delete
 
78
      the event handler by calling the callback function
 
79
      <c>Module:terminate/2</c> (see below), giving as argument
 
80
      <c>{error,{'EXIT',Reason}}</c> or <c>{error,Term}</c>, respectively.
 
81
      No other event handler will be affected.</p>
 
82
    <p>The <c>sys</c> module can be used for debugging an event manager.</p>
 
83
    <p>Note that an event manager <em>does</em> trap exit signals
 
84
      automatically.</p>
 
85
    <p>The gen_event process can go into hibernation 
 
86
    (see <seealso marker="kernel:erlang#erlang:hibernate/3">erlang(3)</seealso>) if a callback
 
87
    function in a handler module specifies <c>'hibernate'</c> in its return value. 
 
88
    This might be useful if the server is expected to be idle for a long
 
89
    time. However this feature should be used with care as hibernation
 
90
    implies at least two garbage collections (when hibernating and
 
91
    shortly after waking up) and is not something you'd want to do
 
92
    between each event handled by a busy event manager.</p>
 
93
 
 
94
    <p>It's also worth noting that when multiple event handlers are
 
95
    invoked, it's sufficient that one single event handler returns a
 
96
    <c>'hibernate'</c> request for the whole event manager to go into
 
97
    hibernation.</p>
 
98
 
 
99
    <p>Unless otherwise stated, all functions in this module fail if
 
100
      the specified event manager does not exist or if bad arguments are
 
101
      given.</p>
 
102
  </description>
 
103
  <funcs>
 
104
    <func>
 
105
      <name>start_link() -> Result</name>
 
106
      <name>start_link(EventMgrName) -> Result</name>
 
107
      <fsummary>Create a generic event manager process in a supervision tree.</fsummary>
 
108
      <type>
 
109
        <v>EventMgrName = {local,Name} | {global,Name}</v>
 
110
        <v>&nbsp;Name = atom()</v>
 
111
        <v>Result = {ok,Pid} | {error,{already_started,Pid}}</v>
 
112
        <v>&nbsp;Pid = pid()</v>
 
113
      </type>
 
114
      <desc>
 
115
        <p>Creates an event manager process as part of a supervision
 
116
          tree. The function should be called, directly or indirectly,
 
117
          by the supervisor. It will, among other things, ensure that
 
118
          the event manager is linked to the supervisor.</p>
 
119
        <p>If <c>EventMgrName={local,Name}</c>, the event manager is
 
120
          registered locally as <c>Name</c> using <c>register/2</c>.
 
121
          If <c>EventMgrName={global,Name}</c>, the event manager is
 
122
          registered globally as <c>Name</c> using
 
123
          <c>global:register_name/2</c>. If no name is provided,
 
124
          the event manager is not registered.</p>
 
125
        <p>If the event manager is successfully created the function
 
126
          returns <c>{ok,Pid}</c>, where <c>Pid</c> is the pid of
 
127
          the event manager. If there already exists a process with
 
128
          the specified <c>EventMgrName</c> the function returns
 
129
          <c>{error,{already_started,Pid}}</c>, where <c>Pid</c> is
 
130
          the pid of that process.</p>
 
131
      </desc>
 
132
    </func>
 
133
    <func>
 
134
      <name>start() -> Result</name>
 
135
      <name>start(EventMgrName) -> Result</name>
 
136
      <fsummary>Create a stand-alone event manager process.</fsummary>
 
137
      <type>
 
138
        <v>EventMgrName = {local,Name} | {global,Name}</v>
 
139
        <v>&nbsp;Name = atom()</v>
 
140
        <v>Result = {ok,Pid} | {error,{already_started,Pid}}</v>
 
141
        <v>&nbsp;Pid = pid()</v>
 
142
      </type>
 
143
      <desc>
 
144
        <p>Creates a stand-alone event manager process, i.e. an event
 
145
          manager which is not part of a supervision tree and thus has
 
146
          no supervisor.</p>
 
147
        <p>See <c>start_link/0,1</c> for a description of arguments and
 
148
          return values.</p>
 
149
      </desc>
 
150
    </func>
 
151
    <func>
 
152
      <name>add_handler(EventMgrRef, Handler, Args) -> Result</name>
 
153
      <fsummary>Add an event handler to a generic event manager.</fsummary>
 
154
      <type>
 
155
        <v>EventMgr = Name | {Name,Node} | {global,Name} | pid()</v>
 
156
        <v>&nbsp;Name = Node = atom()</v>
 
157
        <v>Handler = Module | {Module,Id}</v>
 
158
        <v>&nbsp;Module = atom()</v>
 
159
        <v>&nbsp;Id = term()</v>
 
160
        <v>Args = term()</v>
 
161
        <v>Result = ok | {'EXIT',Reason} | term()</v>
 
162
        <v>&nbsp;Reason = term()</v>
 
163
      </type>
 
164
      <desc>
 
165
        <p>Adds a new event handler to the event manager <c>EventMgrRef</c>.
 
166
          The event manager will call <c>Module:init/1</c> to initiate
 
167
          the event handler and its internal state.</p>
 
168
        <p><c>EventMgrRef</c> can be:</p>
 
169
        <list type="bulleted">
 
170
          <item>the pid,</item>
 
171
          <item><c>Name</c>, if the event manager is locally registered,</item>
 
172
          <item><c>{Name,Node}</c>, if the event manager is locally
 
173
           registered at another node, or</item>
 
174
          <item><c>{global,Name}</c>, if the event manager is globally
 
175
           registered.</item>
 
176
        </list>
 
177
        <p><c>Handler</c> is the name of the callback module <c>Module</c> or
 
178
          a tuple <c>{Module,Id}</c>, where <c>Id</c> is any term.
 
179
          The <c>{Module,Id}</c> representation makes it possible to
 
180
          identify a specific event handler when there are several event
 
181
          handlers using the same callback module.</p>
 
182
        <p><c>Args</c> is an arbitrary term which is passed as the argument
 
183
          to <c>Module:init/1</c>.</p>
 
184
        <p>If <c>Module:init/1</c> returns a correct value, the event
 
185
          manager adds the event handler and this function returns
 
186
          <c>ok</c>. If <c>Module:init/1</c> fails with <c>Reason</c> or
 
187
          returns an unexpected value <c>Term</c>, the event handler is
 
188
          ignored and this function returns <c>{'EXIT',Reason}</c> or
 
189
          <c>Term</c>, respectively.</p>
 
190
      </desc>
 
191
    </func>
 
192
    <func>
 
193
      <name>add_sup_handler(EventMgrRef, Handler, Args) -> Result</name>
 
194
      <fsummary>Add a supervised event handler to a generic event manager.</fsummary>
 
195
      <type>
 
196
        <v>EventMgr = Name | {Name,Node} | {global,Name} | pid()</v>
 
197
        <v>&nbsp;Name = Node = atom()</v>
 
198
        <v>Handler = Module | {Module,Id}</v>
 
199
        <v>&nbsp;Module = atom()</v>
 
200
        <v>&nbsp;Id = term()</v>
 
201
        <v>Args = term()</v>
 
202
        <v>Result = ok | {'EXIT',Reason} | term()</v>
 
203
        <v>&nbsp;Reason = term()</v>
 
204
      </type>
 
205
      <desc>
 
206
        <p>Adds a new event handler in the same way as <c>add_handler/3</c>
 
207
          but will also supervise the connection between the event handler
 
208
          and the calling process.</p>
 
209
        <list type="bulleted">
 
210
          <item>If the calling process later terminates with <c>Reason</c>,
 
211
           the event manager will delete the event handler by calling
 
212
          <c>Module:terminate/2</c> with <c>{stop,Reason}</c> as argument.</item>
 
213
          <item>
 
214
            <p>If the event handler later is deleted, the event manager
 
215
              sends a message<c>{gen_event_EXIT,Handler,Reason}</c> to
 
216
              the calling process. <c>Reason</c> is one of the following:</p>
 
217
            <list type="bulleted">
 
218
              <item><c>normal</c>, if the event handler has been removed due to a
 
219
               call to <c>delete_handler/3</c>, or <c>remove_handler</c>
 
220
               has been returned by a callback function (see below).</item>
 
221
              <item><c>shutdown</c>, if the event handler has been removed
 
222
               because the event manager is terminating.</item>
 
223
              <item><c>{swapped,NewHandler,Pid}</c>, if the process <c>Pid</c>
 
224
               has replaced the event handler with another event handler
 
225
              <c>NewHandler</c> using a call to <c>swap_handler/3</c> or
 
226
              <c>swap_sup_handler/3</c>.</item>
 
227
              <item>a term, if the event handler is removed due to an error.
 
228
               Which term depends on the error.</item>
 
229
            </list>
 
230
          </item>
 
231
        </list>
 
232
        <p>See <c>add_handler/3</c> for a description of the arguments
 
233
          and return values.</p>
 
234
      </desc>
 
235
    </func>
 
236
    <func>
 
237
      <name>notify(EventMgrRef, Event) -> ok</name>
 
238
      <name>sync_notify(EventMgrRef, Event) -> ok</name>
 
239
      <fsummary>Notify an event manager about an event.</fsummary>
 
240
      <type>
 
241
        <v>EventMgrRef = Name | {Name,Node} | {global,Name} | pid()</v>
 
242
        <v>&nbsp;Name = Node = atom()</v>
 
243
        <v>Event = term()</v>
 
244
      </type>
 
245
      <desc>
 
246
        <p>Sends an event notification to the event manager
 
247
          <c>EventMgrRef</c>. The event manager will call
 
248
          <c>Module:handle_event/2</c> for each installed event handler to
 
249
          handle the event.</p>
 
250
        <p><c>notify</c> is asynchronous and will return immediately after
 
251
          the event notification has been sent. <c>sync_notify</c> is
 
252
          synchronous in the sense that it will return <c>ok</c> after
 
253
          the event has been handled by all event handlers.</p>
 
254
        <p>See <c>add_handler/3</c> for a description of <c>EventMgrRef</c>.</p>
 
255
        <p><c>Event</c> is an arbitrary term which is passed as one of
 
256
          the arguments to <c>Module:handle_event/2</c>.</p>
 
257
        <p><c>notify</c> will not fail even if the specified event manager
 
258
          does not exist, unless it is specified as <c>Name</c>.</p>
 
259
      </desc>
 
260
    </func>
 
261
    <func>
 
262
      <name>call(EventMgrRef, Handler, Request) -> Result</name>
 
263
      <name>call(EventMgrRef, Handler, Request, Timeout) -> Result</name>
 
264
      <fsummary>Make a synchronous call to a generic event manager.</fsummary>
 
265
      <type>
 
266
        <v>EventMgrRef = Name | {Name,Node} | {global,Name} | pid()</v>
 
267
        <v>&nbsp;Name = Node = atom()</v>
 
268
        <v>Handler = Module | {Module,Id}</v>
 
269
        <v>&nbsp;Module = atom()</v>
 
270
        <v>&nbsp;Id = term()</v>
 
271
        <v>Request = term()</v>
 
272
        <v>Timeout = int()>0 | infinity</v>
 
273
        <v>Result = Reply | {error,Error}</v>
 
274
        <v>&nbsp;Reply = term()</v>
 
275
        <v>&nbsp;Error = bad_module | {'EXIT',Reason} | term()</v>
 
276
        <v>&nbsp;&nbsp;Reason = term()</v>
 
277
      </type>
 
278
      <desc>
 
279
        <p>Makes a synchronous call to the event handler <c>Handler</c>
 
280
          installed in the event manager <c>EventMgrRef</c> by sending a
 
281
          request and waiting until a reply arrives or a timeout occurs.
 
282
          The event manager will call <c>Module:handle_call/2</c> to handle
 
283
          the request.</p>
 
284
        <p>See <c>add_handler/3</c> for a description of <c>EventMgrRef</c>
 
285
          and <c>Handler</c>.</p>
 
286
        <p><c>Request</c> is an arbitrary term which is passed as one of
 
287
          the arguments to <c>Module:handle_call/2</c>.</p>
 
288
        <p><c>Timeout</c> is an integer greater than zero which specifies
 
289
          how many milliseconds to wait for a reply, or the atom
 
290
          <c>infinity</c> to wait indefinitely. Default value is 5000.
 
291
          If no reply is received within the specified time, the function
 
292
          call fails.</p>
 
293
        <p>The return value <c>Reply</c> is defined in the return value of
 
294
          <c>Module:handle_call/2</c>. If the specified event handler is not
 
295
          installed, the function returns <c>{error,bad_module}</c>. If
 
296
          the callback function fails with <c>Reason</c> or returns an
 
297
          unexpected value <c>Term</c>, this function returns
 
298
          <c>{error,{'EXIT',Reason}}</c> or <c>{error,Term}</c>,
 
299
          respectively.</p>
 
300
      </desc>
 
301
    </func>
 
302
    <func>
 
303
      <name>delete_handler(EventMgrRef, Handler, Args) -> Result</name>
 
304
      <fsummary>Delete an event handler from a generic event manager.</fsummary>
 
305
      <type>
 
306
        <v>EventMgrRef = Name | {Name,Node} | {global,Name} | pid()</v>
 
307
        <v>&nbsp;Name = Node = atom()</v>
 
308
        <v>Handler = Module | {Module,Id}</v>
 
309
        <v>&nbsp;Module = atom()</v>
 
310
        <v>&nbsp;Id = term()</v>
 
311
        <v>Args = term()</v>
 
312
        <v>Result = term() | {error,module_not_found} | {'EXIT',Reason}</v>
 
313
        <v>&nbsp;Reason = term()</v>
 
314
      </type>
 
315
      <desc>
 
316
        <p>Deletes an event handler from the event manager
 
317
          <c>EventMgrRef</c>. The event manager will call
 
318
          <c>Module:terminate/2</c> to terminate the event handler.</p>
 
319
        <p>See <c>add_handler/3</c> for a description of <c>EventMgrRef</c>
 
320
          and <c>Handler</c>.</p>
 
321
        <p><c>Args</c> is an arbitrary term which is passed as one of
 
322
          the arguments to <c>Module:terminate/2</c>.</p>
 
323
        <p>The return value is the return value of <c>Module:terminate/2</c>.
 
324
          If the specified event handler is not installed, the function
 
325
          returns <c>{error,module_not_found}</c>. If the callback function
 
326
          fails with <c>Reason</c>, the function returns
 
327
          <c>{'EXIT',Reason}</c>.</p>
 
328
      </desc>
 
329
    </func>
 
330
    <func>
 
331
      <name>swap_handler(EventMgrRef, {Handler1,Args1}, {Handler2,Args2}) -> Result</name>
 
332
      <fsummary>Replace an event handler in a generic event manager.</fsummary>
 
333
      <type>
 
334
        <v>EventMgrRef = Name | {Name,Node} | {global,Name} | pid()</v>
 
335
        <v>&nbsp;Name = Node = atom()</v>
 
336
        <v>Handler1 = Handler2 = Module | {Module,Id}</v>
 
337
        <v>&nbsp;Module = atom()</v>
 
338
        <v>&nbsp;Id = term()</v>
 
339
        <v>Args1 = Args2 = term()</v>
 
340
        <v>Result = ok | {error,Error}</v>
 
341
        <v>&nbsp;Error = {'EXIT',Reason} | term()</v>
 
342
        <v>&nbsp;&nbsp;Reason = term()</v>
 
343
      </type>
 
344
      <desc>
 
345
        <p>Replaces an old event handler with a new event handler in
 
346
          the event manager <c>EventMgrRef</c>.</p>
 
347
        <p>See <c>add_handler/3</c> for a description of the arguments.</p>
 
348
        <p>First the old event handler <c>Handler1</c> is deleted.
 
349
          The event manager calls <c>Module1:terminate(Args1, ...)</c>,
 
350
          where <c>Module1</c> is the callback module of <c>Handler1</c>,
 
351
          and collects the return value.</p>
 
352
        <p>Then the new event handler <c>Handler2</c> is added and initiated
 
353
          by calling <c>Module2:init({Args2,Term})</c>, where <c>Module2</c>
 
354
          is the callback module of <c>Handler2</c> and <c>Term</c>
 
355
          the return value of <c>Module1:terminate/2</c>. This makes it
 
356
          possible to transfer information from <c>Handler1</c> to
 
357
          <c>Handler2</c>.</p>
 
358
        <p>The new handler will be added even if the the specified old event
 
359
          handler is not installed in which case <c>Term=error</c>, or if
 
360
          <c>Module1:terminate/2</c> fails with <c>Reason</c> in which case
 
361
          <c>Term={'EXIT',Reason}</c>.
 
362
          The old handler will be deleted even if <c>Module2:init/1</c>
 
363
          fails.</p>
 
364
        <p>If there was a supervised connection between <c>Handler1</c> and
 
365
          a process <c>Pid</c>, there will be a supervised connection
 
366
          between <c>Handler2</c> and <c>Pid</c> instead.</p>
 
367
        <p>If <c>Module2:init/1</c> returns a correct value, this function
 
368
          returns <c>ok</c>. If <c>Module2:init/1</c> fails with
 
369
          <c>Reason</c> or returns an unexpected value <c>Term</c>, this
 
370
          this function returns <c>{error,{'EXIT',Reason}}</c> or
 
371
          <c>{error,Term}</c>, respectively.</p>
 
372
      </desc>
 
373
    </func>
 
374
    <func>
 
375
      <name>swap_sup_handler(EventMgrRef, {Handler1,Args1}, {Handler2,Args2}) -> Result</name>
 
376
      <fsummary>Replace an event handler in a generic event manager.</fsummary>
 
377
      <type>
 
378
        <v>EventMgrRef = Name | {Name,Node} | {global,Name} | pid()</v>
 
379
        <v>&nbsp;Name = Node = atom()</v>
 
380
        <v>Handler1 = Handler 2 = Module | {Module,Id}</v>
 
381
        <v>&nbsp;Module = atom()</v>
 
382
        <v>&nbsp;Id = term()</v>
 
383
        <v>Args1 = Args2 = term()</v>
 
384
        <v>Result = ok | {error,Error}</v>
 
385
        <v>&nbsp;Error = {'EXIT',Reason} | term()</v>
 
386
        <v>&nbsp;&nbsp;Reason = term()</v>
 
387
      </type>
 
388
      <desc>
 
389
        <p>Replaces an event handler in the event manager <c>EventMgrRef</c>
 
390
          in the same way as <c>swap_handler/3</c> but will also supervise
 
391
          the connection between <c>Handler2</c> and the calling process.</p>
 
392
        <p>See <c>swap_handler/3</c> for a description of the arguments
 
393
          and return values.</p>
 
394
      </desc>
 
395
    </func>
 
396
    <func>
 
397
      <name>which_handlers(EventMgrRef) -> [Handler]</name>
 
398
      <fsummary>Return all event handlers installed in a generic event manager.</fsummary>
 
399
      <type>
 
400
        <v>EventMgrRef = Name | {Name,Node} | {global,Name} | pid()</v>
 
401
        <v>&nbsp;Name = Node = atom()</v>
 
402
        <v>Handler = Module | {Module,Id}</v>
 
403
        <v>&nbsp;Module = atom()</v>
 
404
        <v>&nbsp;Id = term()</v>
 
405
      </type>
 
406
      <desc>
 
407
        <p>Returns a list of all event handlers installed in the event
 
408
          manager <c>EventMgrRef</c>.</p>
 
409
        <p>See <c>add_handler/3</c> for a description of <c>EventMgrRef</c>
 
410
          and <c>Handler</c>.</p>
 
411
      </desc>
 
412
    </func>
 
413
    <func>
 
414
      <name>stop(EventMgrRef) -> ok</name>
 
415
      <fsummary>Terminate a generic event manager.</fsummary>
 
416
      <type>
 
417
        <v>EventMgrRef = Name | {Name,Node} | {global,Name} | pid()</v>
 
418
        <v>Name = Node = atom()</v>
 
419
      </type>
 
420
      <desc>
 
421
        <p>Terminates the event manager <c>EventMgrRef</c>. Before
 
422
          terminating, the event manager will call
 
423
          <c>Module:terminate(stop,...)</c> for each installed event
 
424
          handler.</p>
 
425
        <p>See <c>add_handler/3</c> for a description of the argument.</p>
 
426
      </desc>
 
427
    </func>
 
428
  </funcs>
 
429
 
 
430
  <section>
 
431
    <title>CALLBACK FUNCTIONS</title>
 
432
    <p>The following functions should be exported from a <c>gen_event</c>
 
433
      callback module.</p>
 
434
  </section>
 
435
  <funcs>
 
436
    <func>
 
437
      <name>Module:init(InitArgs) -> {ok,State} | {ok,State,hibernate}</name>
 
438
      <fsummary>Initialize an event handler.</fsummary>
 
439
      <type>
 
440
        <v>InitArgs = Args | {Args,Term}</v>
 
441
        <v>&nbsp;Args = Term = term()</v>
 
442
        <v>State = term()</v>
 
443
      </type>
 
444
      <desc>
 
445
        <p>Whenever a new event handler is added to an event manager,
 
446
          this function is called to initialize the event handler.</p>
 
447
        <p>If the event handler is added due to a call to
 
448
          <c>gen_event:add_handler/3</c> or
 
449
          <c>gen_event:add_sup_handler/3</c>, <c>InitArgs</c> is
 
450
          the <c>Args</c> argument of these functions.</p>
 
451
        <p>If the event handler is replacing another event handler due to
 
452
          a call to <c>gen_event:swap_handler/3</c> or
 
453
          <c>gen_event:swap_sup_handler/3</c>, or due to a <c>swap</c>
 
454
          return tuple from one of the other callback functions,
 
455
          <c>InitArgs</c> is a tuple <c>{Args,Term}</c> where <c>Args</c> is
 
456
          the argument provided in the function call/return tuple and
 
457
          <c>Term</c> is the result of terminating the old event handler,
 
458
          see <c>gen_event:swap_handler/3</c>.</p>
 
459
        <p>The function should return <c>{ok,State}</c> or <c>{ok,State, hibernate}</c>
 
460
          where <c>State</c> is the initial internal state of the event handler.</p>
 
461
        <p>If <c>{ok,State,hibernate}</c> is returned, the event
 
462
          manager will go into hibernation (by calling <seealso
 
463
          marker="proc_lib#hibernate/3">proc_lib:hibernate/3</seealso>),
 
464
          waiting for the next event to occur.</p>
 
465
      </desc>
 
466
    </func>
 
467
    <func>
 
468
      <name>Module:handle_event(Event, State) -> Result</name>
 
469
      <fsummary>Handle an event.</fsummary>
 
470
      <type>
 
471
        <v>Event = term()</v>
 
472
        <v>State = term()</v>
 
473
        <v>Result = {ok,NewState} | {ok,NewState,hibernate} </v>
 
474
        <v>&nbsp;&nbsp;| {swap_handler,Args1,NewState,Handler2,Args2} | remove_handler</v>
 
475
        <v>&nbsp;NewState = term()</v>
 
476
        <v>&nbsp;Args1 = Args2 = term()</v>
 
477
        <v>&nbsp;Handler2 = Module2 | {Module2,Id}</v>
 
478
        <v>&nbsp;&nbsp;Module2 = atom()</v>
 
479
        <v>&nbsp;&nbsp;Id = term()</v>
 
480
      </type>
 
481
      <desc>
 
482
        <p>Whenever an event manager receives an event sent using
 
483
          <c>gen_event:notify/2</c> or <c>gen_event:sync_notify/2</c>, this
 
484
          function is called for each installed event handler to handle
 
485
          the event.</p>
 
486
        <p><c>Event</c> is the <c>Event</c> argument of
 
487
          <c>notify</c>/<c>sync_notify</c>.</p>
 
488
        <p><c>State</c> is the internal state of the event handler.</p>
 
489
        <p>If the function returns <c>{ok,NewState}</c> or <c>{ok,NewState,hibernate}</c> 
 
490
          the event handler
 
491
          will remain in the event manager with the possible updated
 
492
          internal state <c>NewState</c>.</p>
 
493
        <p>If <c>{ok,NewState,hibernate}</c> is returned, the event
 
494
          manager will also go into hibernation (by calling <seealso
 
495
          marker="proc_lib#hibernate/3">proc_lib:hibernate/3</seealso>),
 
496
          waiting for the next event to occur. It is sufficient that one of the event 
 
497
          handlers return <c>{ok,NewState,hibernate}</c> for the whole event manager 
 
498
          process to hibernate.</p>
 
499
        <p>If the function returns
 
500
          <c>{swap_handler,Args1,NewState,Handler2,Args2}</c> the event
 
501
          handler will be replaced by <c>Handler2</c> by first calling
 
502
          <c>Module:terminate(Args1,NewState)</c> and then
 
503
          <c>Module2:init({Args2,Term})</c> where <c>Term</c> is the return
 
504
          value of <c>Module:terminate/2</c>.
 
505
          See <c>gen_event:swap_handler/3</c> for more information.</p>
 
506
        <p>If the function returns <c>remove_handler</c> the event handler
 
507
          will be deleted by calling
 
508
          <c>Module:terminate(remove_handler,State)</c>.</p>
 
509
      </desc>
 
510
    </func>
 
511
    <func>
 
512
      <name>Module:handle_call(Request, State) -> Result</name>
 
513
      <fsummary>Handle a synchronous request.</fsummary>
 
514
      <type>
 
515
        <v>Request = term()</v>
 
516
        <v>State = term()</v>
 
517
        <v>Result = {ok,Reply,NewState} | {ok,Reply,NewState,hibernate}</v>
 
518
        <v>&nbsp;| {swap_handler,Reply,Args1,NewState,Handler2,Args2}</v>
 
519
        <v>&nbsp;| {remove_handler, Reply}</v>
 
520
        <v>&nbsp;Reply = term()</v>
 
521
        <v>&nbsp;NewState = term()</v>
 
522
        <v>&nbsp;Args1 = Args2 = term()</v>
 
523
        <v>&nbsp;Handler2 = Module2 | {Module2,Id}</v>
 
524
        <v>&nbsp;&nbsp;Module2 = atom()</v>
 
525
        <v>&nbsp;&nbsp;Id = term()</v>
 
526
      </type>
 
527
      <desc>
 
528
        <p>Whenever an event manager receives a request sent using
 
529
          <c>gen_event:call/3,4</c>, this function is called for
 
530
          the specified event handler to handle the request.</p>
 
531
        <p><c>Request</c> is the <c>Request</c> argument of <c>call</c>.</p>
 
532
        <p><c>State</c> is the internal state of the event handler.</p>
 
533
        <p>The return values are the same as for <c>handle_event/2</c>
 
534
          except they also contain a term <c>Reply</c> which is the reply
 
535
          given back to the client as the return value of <c>call</c>.</p>
 
536
      </desc>
 
537
    </func>
 
538
    <func>
 
539
      <name>Module:handle_info(Info, State) -> Result</name>
 
540
      <fsummary>Handle an incoming message.</fsummary>
 
541
      <type>
 
542
        <v>Info = term()</v>
 
543
        <v>State = term()</v>
 
544
        <v>Result = {ok,NewState} | {ok,NewState,hibernate}</v>
 
545
        <v>&nbsp;| {swap_handler,Args1,NewState,Handler2,Args2} | remove_handler</v>
 
546
        <v>&nbsp;NewState = term()</v>
 
547
        <v>&nbsp;Args1 = Args2 = term()</v>
 
548
        <v>&nbsp;Handler2 = Module2 | {Module2,Id}</v>
 
549
        <v>&nbsp;&nbsp;Module2 = atom()</v>
 
550
        <v>&nbsp;&nbsp;Id = term()</v>
 
551
      </type>
 
552
      <desc>
 
553
        <p>This function is called for each installed event handler when
 
554
          an event manager receives any other message than an event or
 
555
          a synchronous request (or a system message).</p>
 
556
        <p><c>Info</c> is the received message.</p>
 
557
        <p>See <c>Module:handle_event/2</c> for a description of State
 
558
          and possible return values.</p>
 
559
      </desc>
 
560
    </func>
 
561
    <func>
 
562
      <name>Module:terminate(Arg, State) -> term()</name>
 
563
      <fsummary>Clean up before deletion.</fsummary>
 
564
      <type>
 
565
        <v>Arg = Args | {stop,Reason} | stop | remove_handler</v>
 
566
        <v>&nbsp;| {error,{'EXIT',Reason}} | {error,Term}</v>
 
567
        <v>&nbsp;Args = Reason = Term = term()</v>
 
568
      </type>
 
569
      <desc>
 
570
        <p>Whenever an event handler is deleted from an event manager,
 
571
          this function is called. It should be the opposite of
 
572
          <c>Module:init/1</c> and do any necessary cleaning up.</p>
 
573
        <p>If the event handler is deleted due to a call to
 
574
          <c>gen_event:delete_handler</c>, <c>gen_event:swap_handler/3</c>
 
575
          or <c>gen_event:swap_sup_handler/3</c>, <c>Arg</c> is
 
576
          the <c>Args</c> argument of this function call.</p>
 
577
        <p><c>Arg={stop,Reason}</c> if the event handler has a supervised
 
578
          connection to a process which has terminated with reason
 
579
          <c>Reason</c>.</p>
 
580
        <p><c>Arg=stop</c> if the event handler is deleted because
 
581
          the event manager is terminating.</p>
 
582
        <p><c>Arg=remove_handler</c> if the event handler is deleted because
 
583
          another callback function has returned <c>remove_handler</c> or
 
584
          <c>{remove_handler,Reply}</c>.</p>
 
585
        <p><c>Arg={error,Term}</c> if the event handler is deleted because
 
586
          a callback function returned an unexpected value <c>Term</c>,
 
587
          or <c>Arg={error,{'EXIT',Reason}}</c> if a callback function
 
588
          failed.</p>
 
589
        <p><c>State</c> is the internal state of the event handler.</p>
 
590
        <p>The function may return any term. If the event handler is
 
591
          deleted due to a call to <c>gen_event:delete_handler</c>,
 
592
          the return value of that function will be the return value of this
 
593
          function. If the event handler is to be replaced with another event
 
594
          handler due to a swap, the return value will be passed to
 
595
          the <c>init</c> function of the new event handler. Otherwise
 
596
          the return value is ignored.</p>
 
597
      </desc>
 
598
    </func>
 
599
    <func>
 
600
      <name>Module:code_change(OldVsn, State, Extra) -> {ok, NewState}</name>
 
601
      <fsummary>Update the internal state during upgrade/downgrade.</fsummary>
 
602
      <type>
 
603
        <v>OldVsn = Vsn | {down, Vsn}</v>
 
604
        <v>&nbsp;&nbsp;Vsn = term()</v>
 
605
        <v>State = NewState = term()</v>
 
606
        <v>Extra = term()</v>
 
607
      </type>
 
608
      <desc>
 
609
        <p>This function is called for an installed event handler which
 
610
          should update its internal state during a release
 
611
          upgrade/downgrade, i.e. when the instruction
 
612
          <c>{update,Module,Change,...}</c> where
 
613
          <c>Change={advanced,Extra}</c> is given in the <c>.appup</c>
 
614
          file. See <em>OTP Design Principles</em> for more
 
615
          information.</p>
 
616
        <p>In the case of an upgrade, <c>OldVsn</c> is <c>Vsn</c>, and
 
617
          in the case of a downgrade, <c>OldVsn</c> is
 
618
          <c>{down,Vsn}</c>. <c>Vsn</c> is defined by the <c>vsn</c>
 
619
          attribute(s) of the old version of the callback module
 
620
          <c>Module</c>. If no such attribute is defined, the version
 
621
          is the checksum of the BEAM file.</p>
 
622
        <p><c>State</c> is the internal state of the event handler.</p>
 
623
        <p><c>Extra</c> is passed as-is from the <c>{advanced,Extra}</c>
 
624
          part of the update instruction.</p>
 
625
        <p>The function should return the updated internal state.</p>
 
626
      </desc>
 
627
    </func>
 
628
  </funcs>
 
629
 
 
630
  <section>
 
631
    <title>SEE ALSO</title>
 
632
    <p><seealso marker="supervisor">supervisor(3)</seealso>, 
 
633
      <seealso marker="sys">sys(3)</seealso></p>
 
634
  </section>
 
635
</erlref>
 
636