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

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/supervisor.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>supervisor</title>
 
27
    <prepared></prepared>
 
28
    <docno></docno>
 
29
    <date></date>
 
30
    <rev></rev>
 
31
  </header>
 
32
  <module>supervisor</module>
 
33
  <modulesummary>Generic Supervisor Behaviour</modulesummary>
 
34
  <description>
 
35
    <p>A behaviour module for implementing a supervisor, a process which
 
36
      supervises other processes called child processes. A child
 
37
      process can either be another supervisor or a worker process.
 
38
      Worker processes are normally implemented using one of
 
39
      the <c>gen_event</c>, <c>gen_fsm</c>, or <c>gen_server</c>
 
40
      behaviours. A supervisor implemented using this module will have
 
41
      a standard set of interface functions and include functionality
 
42
      for tracing and error reporting. Supervisors are used to build an
 
43
      hierarchical process structure called a supervision tree, a
 
44
      nice way to structure a fault tolerant application. Refer to
 
45
      <em>OTP Design Principles</em> for more information.</p>
 
46
    <p>A supervisor assumes the definition of which child processes to
 
47
      supervise to be located in a callback module exporting a
 
48
      pre-defined set of functions.</p>
 
49
    <p>Unless otherwise stated, all functions in this module will fail
 
50
      if the specified supervisor does not exist or if bad arguments
 
51
      are given.</p>
 
52
  </description>
 
53
 
 
54
  <section>
 
55
    <title>Supervision Principles</title>
 
56
    <p>The supervisor is responsible for starting, stopping and
 
57
      monitoring its child processes. The basic idea of a supervisor is
 
58
      that it should keep its child processes alive by restarting them
 
59
      when necessary.</p>
 
60
    <p>The children of a supervisor is defined as a list of <em>child specifications</em>. When the supervisor is started, the child
 
61
      processes are started in order from left to right according to
 
62
      this list. When the supervisor terminates, it first terminates
 
63
      its child processes in reversed start order, from right to left.</p>
 
64
    <p></p>
 
65
    <p>A supervisor can have one of the following <em>restart strategies</em>:</p>
 
66
    <list type="bulleted">
 
67
      <item>
 
68
        <p><c>one_for_one</c> - if one child process terminates and
 
69
          should be restarted, only that child process is affected.</p>
 
70
      </item>
 
71
      <item>
 
72
        <p><c>one_for_all</c> - if one child process terminates and
 
73
          should be restarted, all other child processes are terminated
 
74
          and then all child processes are restarted.</p>
 
75
      </item>
 
76
      <item>
 
77
        <p><c>rest_for_one</c> - if one child process terminates and
 
78
          should be restarted, the 'rest' of the child processes --
 
79
          i.e. the child processes after the terminated child process
 
80
          in the start order -- are terminated. Then the terminated
 
81
          child process and all child processes after it are restarted.</p>
 
82
      </item>
 
83
      <item>
 
84
        <p><c>simple_one_for_one</c> - a simplified <c>one_for_one</c>
 
85
          supervisor, where all child processes are dynamically added
 
86
          instances of the same process type, i.e. running the same
 
87
          code.</p>
 
88
        <p>The functions <c>terminate_child/2</c>, <c>delete_child/2</c>
 
89
          and <c>restart_child/2</c> are invalid for
 
90
          <c>simple_one_for_one</c> supervisors and will return
 
91
          <c>{error,simple_one_for_one}</c> if the specified supervisor
 
92
          uses this restart strategy.</p>
 
93
      </item>
 
94
    </list>
 
95
    <p>To prevent a supervisor from getting into an infinite loop of
 
96
      child process terminations and restarts, a <em>maximum restart frequency</em> is defined using two integer values <c>MaxR</c>
 
97
      and <c>MaxT</c>. If more than <c>MaxR</c> restarts occur within
 
98
      <c>MaxT</c> seconds, the supervisor terminates all child
 
99
      processes and then itself.
 
100
    </p>
 
101
    <marker id="child_spec"/>
 
102
    <p>This is the type definition of a child specification:</p>
 
103
    <pre>
 
104
child_spec() = {Id,StartFunc,Restart,Shutdown,Type,Modules}
 
105
 Id = term()
 
106
 StartFunc = {M,F,A}
 
107
  M = F = atom()
 
108
  A = [term()]
 
109
 Restart = permanent | transient | temporary
 
110
 Shutdown = brutal_kill | int()>=0 | infinity
 
111
 Type = worker | supervisor
 
112
 Modules = [Module] | dynamic
 
113
  Module = atom()</pre>
 
114
    <list type="bulleted">
 
115
      <item>
 
116
        <p><c>Id</c> is a name that is used to identify the child
 
117
          specification internally by the supervisor.</p>
 
118
      </item>
 
119
      <item>
 
120
        <p><c>StartFunc</c> defines the function call used to start
 
121
          the child process. It should be a module-function-arguments
 
122
          tuple <c>{M,F,A}</c> used as <c>apply(M,F,A)</c>.</p>
 
123
        <p>          <br></br>
 
124
</p>
 
125
        <p>The start function <em>must create and link to</em> the child
 
126
          process, and should return <c>{ok,Child}</c> or
 
127
          <c>{ok,Child,Info}</c> where <c>Child</c> is the pid of
 
128
          the child process and <c>Info</c> an arbitrary term which is
 
129
          ignored by the supervisor.</p>
 
130
        <p>          <br></br>
 
131
</p>
 
132
        <p>The start function can also return <c>ignore</c> if the child
 
133
          process for some reason cannot be started, in which case
 
134
          the child specification will be kept by the supervisor but
 
135
          the non-existing child process will be ignored.</p>
 
136
        <p>          <br></br>
 
137
</p>
 
138
        <p>If something goes wrong, the function may also return an
 
139
          error tuple <c>{error,Error}</c>.</p>
 
140
        <p>          <br></br>
 
141
</p>
 
142
        <p>Note that the <c>start_link</c> functions of the different
 
143
          behaviour modules fulfill the above requirements.</p>
 
144
      </item>
 
145
      <item>
 
146
        <p><c>Restart</c> defines when a terminated child process
 
147
          should be restarted. A <c>permanent</c> child process should
 
148
          always be restarted, a <c>temporary</c> child process should
 
149
          never be restarted and a <c>transient</c> child process
 
150
          should be restarted only if it terminates abnormally, i.e.
 
151
          with another exit reason than <c>normal</c>.</p>
 
152
      </item>
 
153
      <item>
 
154
        <p><c>Shutdown</c> defines how a child process should be
 
155
          terminated. <c>brutal_kill</c> means the child process will
 
156
          be unconditionally terminated using <c>exit(Child,kill)</c>.
 
157
          An integer timeout value means that the supervisor will tell
 
158
          the child process to terminate by calling
 
159
          <c>exit(Child,shutdown)</c> and then wait for an exit signal
 
160
          with reason <c>shutdown</c> back from the child process. If
 
161
          no exit signal is received within the specified time,
 
162
          the child process is unconditionally terminated using
 
163
          <c>exit(Child,kill)</c>.</p>
 
164
        <p>If the child process is another supervisor, <c>Shutdown</c>
 
165
          should be set to <c>infinity</c> to give the subtree ample
 
166
          time to shutdown.</p>
 
167
        <p><em>Important note on simple-one-for-one supervisors:</em>
 
168
          The dynamically created child processes of a
 
169
          simple-one-for-one supervisor are not explicitly killed,
 
170
          regardless of shutdown strategy, but are expected to terminate
 
171
          when the supervisor does (that is, when an exit signal from
 
172
          the parent process is received).</p>
 
173
        <p>Note that all child processes implemented using the standard
 
174
          OTP behavior modules automatically adhere to the shutdown
 
175
          protocol.</p>
 
176
      </item>
 
177
      <item>
 
178
        <p><c>Type</c> specifies if the child process is a supervisor or
 
179
          a worker.</p>
 
180
      </item>
 
181
      <item>
 
182
        <p><c>Modules</c> is used by the release handler during code
 
183
          replacement to determine which processes are using a certain
 
184
          module. As a rule of thumb <c>Modules</c> should be a list
 
185
          with one element <c>[Module]</c>, where <c>Module</c> is
 
186
          the callback module, if the child process is a supervisor,
 
187
          gen_server or gen_fsm. If the child process is an event
 
188
          manager (gen_event) with a dynamic set of callback modules,
 
189
          <c>Modules</c> should be <c>dynamic</c>. See <em>OTP Design Principles</em> for more information about release handling.</p>
 
190
      </item>
 
191
      <item>
 
192
        <p>Internally, the supervisor also keeps track of the pid
 
193
          <c>Child</c> of the child process, or <c>undefined</c> if no
 
194
          pid exists.</p>
 
195
      </item>
 
196
    </list>
 
197
  </section>
 
198
  <funcs>
 
199
    <func>
 
200
      <name>start_link(Module, Args) -> Result</name>
 
201
      <name>start_link(SupName, Module, Args) -> Result</name>
 
202
      <fsummary>Create a supervisor process.</fsummary>
 
203
      <type>
 
204
        <v>SupName = {local,Name} | {global,Name}</v>
 
205
        <v>&nbsp;Name = atom()</v>
 
206
        <v>Module = atom()</v>
 
207
        <v>Args = term()</v>
 
208
        <v>Result = {ok,Pid} | ignore | {error,Error}</v>
 
209
        <v>&nbsp;Pid = pid()</v>
 
210
        <v>&nbsp;Error = {already_started,Pid}} | shutdown | term()</v>
 
211
      </type>
 
212
      <desc>
 
213
        <p>Creates a supervisor process as part of a supervision tree.
 
214
          The function will, among other things, ensure that
 
215
          the supervisor is linked to the calling process (its
 
216
          supervisor).</p>
 
217
        <p>The created supervisor process calls <c>Module:init/1</c> to
 
218
          find out about restart strategy, maximum restart frequency
 
219
          and child processes. To ensure a synchronized start-up
 
220
          procedure, <c>start_link/2,3</c> does not return until
 
221
          <c>Module:init/1</c> has returned and all child processes
 
222
          have been started.</p>
 
223
        <p>If <c>SupName={local,Name}</c> the supervisor is registered
 
224
          locally as <c>Name</c> using <c>register/2</c>. If
 
225
          <c>SupName={global,Name}</c> the supervisor is registered
 
226
          globally as <c>Name</c> using <c>global:register_name/2</c>.
 
227
          If no name is provided, the supervisor is not registered.</p>
 
228
        <p><c>Module</c> is the name of the callback module.</p>
 
229
        <p><c>Args</c> is an arbitrary term which is passed as
 
230
          the argument to <c>Module:init/1</c>.</p>
 
231
        <p>If the supervisor and its child processes are successfully
 
232
          created (i.e. if all child process start functions return
 
233
          <c>{ok,Child}</c>, <c>{ok,Child,Info}</c>, or <c>ignore</c>)
 
234
          the function returns <c>{ok,Pid}</c>, where <c>Pid</c> is
 
235
          the pid of the supervisor. If there already exists a process
 
236
          with the specified <c>SupName</c> the function returns
 
237
          <c>{error,{already_started,Pid}}</c>, where <c>Pid</c> is
 
238
          the pid of that process.</p>
 
239
        <p>If <c>Module:init/1</c> returns <c>ignore</c>, this function
 
240
          returns <c>ignore</c> as well and the supervisor terminates
 
241
          with reason <c>normal</c>.
 
242
          If <c>Module:init/1</c> fails or returns an incorrect value,
 
243
          this function returns <c>{error,Term}</c> where <c>Term</c>
 
244
          is a term with information about the error, and the supervisor
 
245
          terminates with reason <c>Term</c>.</p>
 
246
        <p>If any child process start function fails or returns an error
 
247
          tuple or an erroneous value, the function returns
 
248
          <c>{error,shutdown}</c> and the supervisor terminates all
 
249
          started child processes and then itself with reason
 
250
          <c>shutdown</c>.</p>
 
251
      </desc>
 
252
    </func>
 
253
    <func>
 
254
      <name>start_child(SupRef, ChildSpec) -> Result</name>
 
255
      <fsummary>Dynamically add a child process to a supervisor.</fsummary>
 
256
      <type>
 
257
        <v>SupRef = Name | {Name,Node} | {global,Name} | pid()</v>
 
258
        <v>&nbsp;Name = Node = atom()</v>
 
259
        <v>ChildSpec = child_spec() | [term()]</v>
 
260
        <v>Result = {ok,Child} | {ok,Child,Info} | {error,Error}</v>
 
261
        <v>&nbsp;Child = pid() | undefined</v>
 
262
        <v>&nbsp;Info = term()</v>
 
263
        <v>&nbsp;Error = already_present | {already_started,Child} | term()</v>
 
264
      </type>
 
265
      <desc>
 
266
        <p>Dynamically adds a child specification to the supervisor
 
267
          <c>SupRef</c> which starts the corresponding child process.</p>
 
268
        <p><c>SupRef</c> can be:</p>
 
269
        <list type="bulleted">
 
270
          <item>the pid,</item>
 
271
          <item><c>Name</c>, if the supervisor is locally registered,</item>
 
272
          <item><c>{Name,Node}</c>, if the supervisor is locally
 
273
           registered at another node, or</item>
 
274
          <item><c>{global,Name}</c>, if the supervisor is globally
 
275
           registered.</item>
 
276
        </list>
 
277
        <p><c>ChildSpec</c> should be a valid child specification
 
278
          (unless the supervisor is a <c>simple_one_for_one</c>
 
279
          supervisor, see below). The child process will be started by
 
280
          using the start function as defined in the child
 
281
          specification.</p>
 
282
        <p>If the case of a <c>simple_one_for_one</c> supervisor,
 
283
          the child specification defined in <c>Module:init/1</c> will
 
284
          be used and <c>ChildSpec</c> should instead be an arbitrary
 
285
          list of terms <c>List</c>. The child process will then be
 
286
          started by appending <c>List</c> to the existing start
 
287
          function arguments, i.e. by calling
 
288
          <c>apply(M, F, A++List)</c> where <c>{M,F,A}</c> is the start
 
289
          function defined in the child specification.</p>
 
290
        <p>If there already exists a child specification with
 
291
          the specified <c>Id</c>, <c>ChildSpec</c> is discarded and
 
292
          the function returns <c>{error,already_present}</c> or
 
293
          <c>{error,{already_started,Child}}</c>, depending on if
 
294
          the corresponding child process is running or not.</p>
 
295
        <p>If the child process start function returns <c>{ok,Child}</c>
 
296
          or <c>{ok,Child,Info}</c>, the child specification and pid is
 
297
          added to the supervisor and the function returns the same
 
298
          value.</p>
 
299
        <p>If the child process start function returns <c>ignore</c>,
 
300
          the child specification is added to the supervisor, the pid
 
301
          is set to <c>undefined</c> and the function returns
 
302
          <c>{ok,undefined}</c>.</p>
 
303
        <p>If the child process start function returns an error tuple or
 
304
          an erroneous value, or if it fails, the child specification is
 
305
          discarded and the function returns <c>{error,Error}</c> where
 
306
          <c>Error</c> is a term containing information about the error
 
307
          and child specification.</p>
 
308
      </desc>
 
309
    </func>
 
310
    <func>
 
311
      <name>terminate_child(SupRef, Id) -> Result</name>
 
312
      <fsummary>Terminate a child process belonging to a supervisor.</fsummary>
 
313
      <type>
 
314
        <v>SupRef = Name | {Name,Node} | {global,Name} | pid()</v>
 
315
        <v>&nbsp;Name = Node = atom()</v>
 
316
        <v>Id = term()</v>
 
317
        <v>Result = ok | {error,Error}</v>
 
318
        <v>&nbsp;Error = not_found | simple_one_for_one</v>
 
319
      </type>
 
320
      <desc>
 
321
        <p>Tells the supervisor <c>SupRef</c> to terminate the child
 
322
          process corresponding to the child specification identified
 
323
          by <c>Id</c>. The process, if there is one, is terminated but
 
324
          the child specification is kept by the supervisor. This means
 
325
          that the child process may be later be restarted by
 
326
          the supervisor. The child process can also be restarted
 
327
          explicitly by calling <c>restart_child/2</c>. Use
 
328
          <c>delete_child/2</c> to remove the child specification.</p>
 
329
        <p>See <c>start_child/2</c> for a description of
 
330
          <c>SupRef</c>.</p>
 
331
        <p>If successful, the function returns <c>ok</c>. If there is
 
332
          no child specification with the specified <c>Id</c>,
 
333
          the function returns <c>{error,not_found}</c>.</p>
 
334
      </desc>
 
335
    </func>
 
336
    <func>
 
337
      <name>delete_child(SupRef, Id) -> Result</name>
 
338
      <fsummary>Delete a child specification from a supervisor.</fsummary>
 
339
      <type>
 
340
        <v>SupRef = Name | {Name,Node} | {global,Name} | pid()</v>
 
341
        <v>&nbsp;Name = Node = atom()</v>
 
342
        <v>Id = term()</v>
 
343
        <v>Result = ok | {error,Error}</v>
 
344
        <v>&nbsp;Error = running | not_found | simple_one_for_one</v>
 
345
      </type>
 
346
      <desc>
 
347
        <p>Tells the supervisor <c>SupRef</c> to delete the child
 
348
          specification identified by <c>Id</c>. The corresponding child
 
349
          process must not be running, use <c>terminate_child/2</c> to
 
350
          terminate it.</p>
 
351
        <p>See <c>start_child/2</c> for a description of <c>SupRef</c>.</p>
 
352
        <p>If successful, the function returns <c>ok</c>. If the child
 
353
          specification identified by <c>Id</c> exists but
 
354
          the corresponding child process is running, the function
 
355
          returns <c>{error,running}</c>. If the child specification
 
356
          identified by <c>Id</c> does not exist, the function returns
 
357
          <c>{error,not_found}</c>.</p>
 
358
      </desc>
 
359
    </func>
 
360
    <func>
 
361
      <name>restart_child(SupRef, Id) -> Result</name>
 
362
      <fsummary>Restart a terminated child process belonging to a supervisor.</fsummary>
 
363
      <type>
 
364
        <v>SupRef = Name | {Name,Node} | {global,Name} | pid()</v>
 
365
        <v>&nbsp;Name = Node = atom()</v>
 
366
        <v>Id = term()</v>
 
367
        <v>Result = {ok,Child} | {ok,Child,Info} | {error,Error}</v>
 
368
        <v>&nbsp;Child = pid() | undefined</v>
 
369
        <v>&nbsp;Error = running | not_found | simple_one_for_one | term()</v>
 
370
      </type>
 
371
      <desc>
 
372
        <p>Tells the supervisor <c>SupRef</c> to restart a child process
 
373
          corresponding to the child specification identified by
 
374
          <c>Id</c>. The child specification must exist and
 
375
          the corresponding child process must not be running.</p>
 
376
        <p>See <c>start_child/2</c> for a description of <c>SupRef</c>.</p>
 
377
        <p>If the child specification identified by <c>Id</c> does not
 
378
          exist, the function returns <c>{error,not_found}</c>. If
 
379
          the child specification exists but the corresponding process
 
380
          is already running, the function returns
 
381
          <c>{error,running}</c>.</p>
 
382
        <p>If the child process start function returns <c>{ok,Child}</c>
 
383
          or <c>{ok,Child,Info}</c>, the pid is added to the supervisor
 
384
          and the function returns the same value.</p>
 
385
        <p>If the child process start function returns <c>ignore</c>,
 
386
          the pid remains set to <c>undefined</c> and the function
 
387
          returns <c>{ok,undefined}</c>.</p>
 
388
        <p>If the child process start function returns an error tuple or
 
389
          an erroneous value, or if it fails, the function returns
 
390
          <c>{error,Error}</c> where <c>Error</c> is a term containing
 
391
          information about the error.</p>
 
392
      </desc>
 
393
    </func>
 
394
    <func>
 
395
      <name>which_children(SupRef) -> [{Id,Child,Type,Modules}]</name>
 
396
      <fsummary>Return information about all children specifications and child processes belonging to a supervisor.</fsummary>
 
397
      <type>
 
398
        <v>SupRef = Name | {Name,Node} | {global,Name} | pid()</v>
 
399
        <v>&nbsp;Name = Node = atom()</v>
 
400
        <v>Id = term() | undefined</v>
 
401
        <v>Child = pid() | undefined</v>
 
402
        <v>Type = worker | supervisor</v>
 
403
        <v>Modules = [Module] | dynamic</v>
 
404
        <v>&nbsp;Module = atom()</v>
 
405
      </type>
 
406
      <desc>
 
407
        <p>Returns a list with information about all child
 
408
          specifications and child processes belonging to
 
409
          the supervisor <c>SupRef</c>.</p>
 
410
        <p>See <c>start_child/2</c> for a description of <c>SupRef</c>.</p>
 
411
        <p>The information given for each child specification/process
 
412
          is:</p>
 
413
        <list type="bulleted">
 
414
          <item>
 
415
            <p><c>Id</c> - as defined in the child specification or
 
416
              <c>undefined</c> in the case of a
 
417
              <c>simple_one_for_one</c> supervisor.</p>
 
418
          </item>
 
419
          <item>
 
420
            <p><c>Child</c> - the pid of the corresponding child
 
421
              process, or <c>undefined</c> if there is no such process.</p>
 
422
          </item>
 
423
          <item>
 
424
            <p><c>Type</c> - as defined in the child specification.</p>
 
425
          </item>
 
426
          <item>
 
427
            <p><c>Modules</c> - as defined in the child specification.</p>
 
428
          </item>
 
429
        </list>
 
430
      </desc>
 
431
    </func>
 
432
    <func>
 
433
      <name>check_childspecs([ChildSpec]) -> Result</name>
 
434
      <fsummary>Check if child specifications are syntactically correct.</fsummary>
 
435
      <type>
 
436
        <v>ChildSpec = child_spec()</v>
 
437
        <v>Result = ok | {error,Error}</v>
 
438
        <v>&nbsp;Error = term()</v>
 
439
      </type>
 
440
      <desc>
 
441
        <p>This function takes a list of child specification as argument
 
442
          and returns <c>ok</c> if all of them are syntactically
 
443
          correct, or <c>{error,Error}</c> otherwise.</p>
 
444
      </desc>
 
445
    </func>
 
446
  </funcs>
 
447
 
 
448
  <section>
 
449
    <title>CALLBACK FUNCTIONS</title>
 
450
    <p>The following functions should be exported from a
 
451
      <c>supervisor</c> callback module.</p>
 
452
  </section>
 
453
  <funcs>
 
454
    <func>
 
455
      <name>Module:init(Args) -> Result</name>
 
456
      <fsummary>Return a supervisor specification.</fsummary>
 
457
      <type>
 
458
        <v>Args = term()</v>
 
459
        <v>Result = {ok,{{RestartStrategy,MaxR,MaxT},[ChildSpec]}} | ignore</v>
 
460
        <v>&nbsp;RestartStrategy = one_for_all | one_for_one | rest_for_one | simple_one_for_one</v>
 
461
        <v>&nbsp;MaxR = MaxT = int()>=0</v>
 
462
        <v>&nbsp;ChildSpec = child_spec()</v>
 
463
      </type>
 
464
      <desc>
 
465
        <p>Whenever a supervisor is started using
 
466
          <c>supervisor:start_link/2,3</c>, this function is called by
 
467
          the new process to find out about restart strategy, maximum
 
468
          restart frequency and child specifications.</p>
 
469
        <p><c>Args</c> is the <c>Args</c> argument provided to the start
 
470
          function.</p>
 
471
        <p><c>RestartStrategy</c> is the restart strategy and
 
472
          <c>MaxR</c> and <c>MaxT</c> defines the maximum restart
 
473
          frequency of the supervisor. <c>[ChildSpec]</c> is a list of
 
474
          valid child specifications defining which child processes
 
475
          the supervisor should start and monitor. See the discussion
 
476
          about Supervision Principles above.</p>
 
477
        <p>Note that when the restart strategy is
 
478
          <c>simple_one_for_one</c>, the list of child specifications
 
479
          must be a list with one child specification only.
 
480
          (The <c>Id</c> is ignored). No child process is then started
 
481
          during the initialization phase, but all children are assumed
 
482
          to be started dynamically using
 
483
          <c>supervisor:start_child/2</c>.</p>
 
484
        <p>The function may also return <c>ignore</c>.</p>
 
485
      </desc>
 
486
    </func>
 
487
  </funcs>
 
488
 
 
489
  <section>
 
490
    <title>SEE ALSO</title>
 
491
    <p><seealso marker="gen_event">gen_event(3)</seealso>, 
 
492
      <seealso marker="gen_fsm">gen_fsm(3)</seealso>, 
 
493
      <seealso marker="gen_server">gen_server(3)</seealso>, 
 
494
      <seealso marker="sys">sys(3)</seealso></p>
 
495
  </section>
 
496
</erlref>
 
497