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

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/proc_lib.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>proc_lib</title>
 
27
    <prepared></prepared>
 
28
    <docno></docno>
 
29
    <date></date>
 
30
    <rev></rev>
 
31
  </header>
 
32
  <module>proc_lib</module>
 
33
  <modulesummary>Functions for asynchronous and synchronous start of processes adhering to the OTP design principles.</modulesummary>
 
34
  <description>
 
35
    <p>This module is used to start processes adhering to
 
36
      the <seealso marker="doc/design_principles:des_princ">OTP Design Principles</seealso>. Specifically, the functions in this
 
37
      module are used by the OTP standard behaviors (<c>gen_server</c>,
 
38
      <c>gen_fsm</c>, ...) when starting new processes. The functions
 
39
      can also be used to start <em>special processes</em>, user
 
40
      defined processes which comply to the OTP design principles. See
 
41
      <seealso marker="doc/design_principles:spec_proc">Sys and Proc_Lib</seealso> in OTP Design Principles for an example.</p>
 
42
    <p>Some useful information is initialized when a process starts.
 
43
      The registered names, or the process identifiers, of the parent
 
44
      process, and the parent ancestors, are stored together with
 
45
      information about the function initially called in the process.</p>
 
46
    <p>While in "plain Erlang" a process is said to terminate normally
 
47
      only for the exit reason <c>normal</c>, a process started
 
48
      using <c>proc_lib</c> is also said to terminate normally if it
 
49
      exits with reason <c>shutdown</c>. This is the reason used when
 
50
      an application (supervision tree) is stopped.</p>
 
51
    <p>When a process started using <c>proc_lib</c> terminates
 
52
      abnormally -- that is, with another exit reason than <c>normal</c>
 
53
      or <c>shutdown</c> -- a <em>crash report</em> is generated, which
 
54
      is written to terminal by the default SASL event handler. That is,
 
55
      the crash report is normally only visible if the SASL application
 
56
      is started. See
 
57
      <seealso marker="sasl:sasl_app">sasl(6)</seealso> and
 
58
      <seealso marker="sasl:error_logging">SASL User's Guide</seealso>.</p>
 
59
    <p>The crash report contains the previously stored information such
 
60
      as ancestors and initial function, the termination reason, and
 
61
      information regarding other processes which terminate as a result
 
62
      of this process terminating.</p>
 
63
  </description>
 
64
  <funcs>
 
65
    <func>
 
66
      <name>spawn(Fun) -> pid()</name>
 
67
      <name>spawn(Node, Fun) -> pid()</name>
 
68
      <name>spawn(Module, Function, Args) -> pid()</name>
 
69
      <name>spawn(Node, Module, Function, Args) -> pid()</name>
 
70
      <fsummary>Spawn a new process.</fsummary>
 
71
      <type>
 
72
        <v>Node = node()</v>
 
73
        <v>Fun = fun() -> void()</v>
 
74
        <v>Module = Function = atom()</v>
 
75
        <v>Args = [term()]</v>
 
76
      </type>
 
77
      <desc>
 
78
        <p>Spawns a new process and initializes it as described above.
 
79
          The process is spawned using the
 
80
          <seealso marker="kernel:erlang#spawn/1">spawn</seealso> BIFs.</p>
 
81
      </desc>
 
82
    </func>
 
83
    <func>
 
84
      <name>spawn_link(Fun) -> pid()</name>
 
85
      <name>spawn_link(Node, Fun) -> pid()</name>
 
86
      <name>spawn_link(Module, Function, Args) -> pid()</name>
 
87
      <name>spawn_link(Node, Module, Function, Args) -> pid()</name>
 
88
      <fsummary>Spawn and link to a new process.</fsummary>
 
89
      <type>
 
90
        <v>Node = node()</v>
 
91
        <v>Fun = fun() -> void()</v>
 
92
        <v>Module = Function = atom()</v>
 
93
        <v>Args = [term()]</v>
 
94
      </type>
 
95
      <desc>
 
96
        <p>Spawns a new process and initializes it as described above.
 
97
          The process is spawned using the
 
98
          <seealso marker="kernel:erlang#spawn_link/1">spawn_link</seealso>
 
99
          BIFs.</p>
 
100
      </desc>
 
101
    </func>
 
102
    <func>
 
103
      <name>spawn_opt(Fun, SpawnOpts) -> pid()</name>
 
104
      <name>spawn_opt(Node, Fun, SpawnOpts) -> pid()</name>
 
105
      <name>spawn_opt(Module, Function, Args, SpawnOpts) -> pid()</name>
 
106
      <name>spawn_opt(Node, Module, Func, Args, SpawnOpts) -> pid()</name>
 
107
      <fsummary>Spawn a new process with given options.</fsummary>
 
108
      <type>
 
109
        <v>Node = node()</v>
 
110
        <v>Fun = fun() -> void()</v>
 
111
        <v>Module = Function = atom()</v>
 
112
        <v>Args = [term()]</v>
 
113
        <v>SpawnOpts -- see erlang:spawn_opt/2,3,4,5</v>
 
114
      </type>
 
115
      <desc>
 
116
        <p>Spawns a new process and initializes it as described above.
 
117
          The process is spawned using the
 
118
          <seealso marker="kernel:erlang#spawn_opt/2">spawn_opt</seealso>
 
119
          BIFs.</p>
 
120
        <note>
 
121
          <p>Using the spawn option <c>monitor</c> is currently not
 
122
            allowed, but will cause the function to fail with reason
 
123
            <c>badarg</c>.</p>
 
124
        </note>
 
125
      </desc>
 
126
    </func>
 
127
    <func>
 
128
      <name>start(Module, Function, Args) -> Ret</name>
 
129
      <name>start(Module, Function, Args, Time) -> Ret</name>
 
130
      <name>start(Module, Function, Args, Time, SpawnOpts) -> Ret</name>
 
131
      <name>start_link(Module, Function, Args) -> Ret</name>
 
132
      <name>start_link(Module, Function, Args, Time) -> Ret</name>
 
133
      <name>start_link(Module, Function, Args, Time, SpawnOpts) -> Ret</name>
 
134
      <fsummary>Start a new process synchronously.</fsummary>
 
135
      <type>
 
136
        <v>Module = Function = atom()</v>
 
137
        <v>Args = [term()]</v>
 
138
        <v>Time = int() >= 0 | infinity</v>
 
139
        <v>SpawnOpts -- see erlang:spawn_opt/2,3,4,5</v>
 
140
        <v>Ret = term() | {error, Reason}</v>
 
141
      </type>
 
142
      <desc>
 
143
        <p>Starts a new process synchronously. Spawns the process and
 
144
          waits for it to start.  When the process has started, it
 
145
          <em>must</em> call
 
146
          <seealso marker="#init_ack/2">init_ack(Parent,Ret)</seealso>
 
147
          or <seealso marker="#init_ack/1">init_ack(Ret)</seealso>,
 
148
          where <c>Parent</c> is the process that evaluates this
 
149
          function.  At this time, <c>Ret</c> is returned.</p>
 
150
        <p>If the <c>start_link/3,4,5</c> function is used and
 
151
          the process crashes before it has called <c>init_ack/1,2</c>,
 
152
          <c>{error, Reason}</c> is returned if the calling process
 
153
          traps exits.</p>
 
154
        <p>If <c>Time</c> is specified as an integer, this function
 
155
          waits for <c>Time</c> milliseconds for the new process to call
 
156
          <c>init_ack</c>, or <c>{error, timeout}</c> is returned, and
 
157
          the process is killed.</p>
 
158
        <p>The <c>SpawnOpts</c> argument, if given, will be passed
 
159
          as the last argument to the <c>spawn_opt/2,3,4,5</c> BIF.</p>
 
160
        <note>
 
161
          <p>Using the spawn option <c>monitor</c> is currently not
 
162
            allowed, but will cause the function to fail with reason
 
163
            <c>badarg</c>.</p>
 
164
        </note>
 
165
      </desc>
 
166
    </func>
 
167
    <func>
 
168
      <name>init_ack(Parent, Ret) -> void()</name>
 
169
      <name>init_ack(Ret) -> void()</name>
 
170
      <fsummary>Used by a process when it has started.</fsummary>
 
171
      <type>
 
172
        <v>Parent = pid()</v>
 
173
        <v>Ret = term()</v>
 
174
      </type>
 
175
      <desc>
 
176
        <p>This function must used by a process that has been started by
 
177
          a <seealso marker="#start/3">start[_link]/3,4,5</seealso>
 
178
          function. It tells <c>Parent</c> that the process has
 
179
          initialized itself, has started, or has failed to initialize
 
180
          itself.</p>
 
181
        <p>The <c>init_ack/1</c> function uses the parent value
 
182
          previously stored by the start function used.</p>
 
183
        <p>If this function is not called, the start function will
 
184
          return an error tuple (if a link and/or a timeout is used) or
 
185
          hang otherwise.</p>
 
186
        <p>The following example illustrates how this function and
 
187
          <c>proc_lib:start_link/3</c> are used.</p>
 
188
        <code type="none">
 
189
-module(my_proc).
 
190
-export([start_link/0]).
 
191
-export([init/1]).
 
192
 
 
193
start_link() ->
 
194
    proc_lib:start_link(my_proc, init, [self()]).
 
195
 
 
196
init(Parent) ->
 
197
    case do_initialization() of
 
198
        ok ->
 
199
            proc_lib:init_ack(Parent, {ok, self()});
 
200
        {error, Reason} ->
 
201
            exit(Reason)
 
202
    end,
 
203
    loop().
 
204
 
 
205
...</code>
 
206
      </desc>
 
207
    </func>
 
208
    <func>
 
209
      <name>format(CrashReport) -> string()</name>
 
210
      <fsummary>Format a crash report.</fsummary>
 
211
      <type>
 
212
        <v>CrashReport = term()</v>
 
213
      </type>
 
214
      <desc>
 
215
        <p>This function can be used by a user defined event handler to
 
216
          format a crash report. The crash report is sent using
 
217
          <c>error_logger:error_report(crash_report, CrashReport)</c>.
 
218
          That is, the event to be handled is of the format
 
219
          <c>{error_report, GL, {Pid, crash_report, CrashReport}}</c>
 
220
          where <c>GL</c> is the group leader pid of the process
 
221
          <c>Pid</c> which sent the crash report.</p>
 
222
      </desc>
 
223
    </func>
 
224
    <func>
 
225
      <name>initial_call(Process) -> {Module,Function,Args} | false</name>
 
226
      <fsummary>Extract the initial call of a <c>proc_lib</c>spawned process.</fsummary>
 
227
      <type>
 
228
        <v>Process = pid() | {X,Y,Z} | ProcInfo</v>
 
229
        <v>&nbsp;X = Y = Z = int()</v>
 
230
        <v>&nbsp;ProcInfo = term()</v>
 
231
        <v>Module = Function = atom()</v>
 
232
        <v>Args = [atom()]</v>
 
233
      </type>
 
234
      <desc>
 
235
        <p>Extracts the initial call of a process that was started
 
236
          using one of the spawn or start functions described above.
 
237
          <c>Process</c> can either be a pid, an integer tuple (from
 
238
          which a pid can be created), or the process information of a
 
239
          process <c>Pid</c> fetched through an
 
240
          <c>erlang:process_info(Pid)</c> function call.</p>
 
241
 
 
242
        <note><p>The list <c>Args</c> no longer contains the actual arguments,
 
243
        but the same number of atoms as the number of arguments; the first atom
 
244
        is always <c>'Argument__1'</c>, the second <c>'Argument__2'</c>, and
 
245
        so on. The reason is that the argument list could waste a significant
 
246
        amount of memory, and if the argument list contained funs, it could
 
247
        be impossible to upgrade the code for the module.</p>
 
248
 
 
249
        <p>If the process was spawned using a fun, <c>initial_call/1</c> no
 
250
        longer returns the actual fun, but the module, function for the local
 
251
        function implementing the fun, and the arity, for instance
 
252
        <c>{some_module,-work/3-fun-0-,0}</c> (meaning that the fun was
 
253
        created in the function <c>some_module:work/3</c>).
 
254
        The reason is that keeping the fun would prevent code upgrade for the
 
255
        module, and that a significant amount of memory could be wasted.</p>
 
256
        </note>
 
257
      </desc>
 
258
    </func>
 
259
    <func>
 
260
      <name>translate_initial_call(Process) -> {Module,Function,Arity} | Fun</name>
 
261
      <fsummary>Extract and translate the initial call of a <c>proc_lib</c>spawned process.</fsummary>
 
262
      <type>
 
263
        <v>Process = pid() | {X,Y,Z} | ProcInfo</v>
 
264
        <v>&nbsp;X = Y = Z = int()</v>
 
265
        <v>&nbsp;ProcInfo = term()</v>
 
266
        <v>Module = Function = atom()</v>
 
267
        <v>Arity = int()</v>
 
268
        <v>Fun = fun() -> void()</v>
 
269
      </type>
 
270
      <desc>
 
271
        <p>This function is used by the <c>c:i/0</c> and
 
272
          <c>c:regs/0</c> functions in order to present process
 
273
          information.</p>
 
274
        <p>Extracts the initial call of a process that was started
 
275
          using one of the spawn or start functions described above,
 
276
          and translates it to more useful information. <c>Process</c>
 
277
          can either be a pid, an integer tuple (from which a pid can
 
278
          be created), or the process information of a process
 
279
          <c>Pid</c> fetched through an <c>erlang:process_info(Pid)</c>
 
280
          function call.</p>
 
281
        <p>If the initial call is to one of the system defined behaviors
 
282
          such as <c>gen_server</c> or <c>gen_event</c>, it is
 
283
          translated to more useful information. If a <c>gen_server</c>
 
284
          is spawned, the returned <c>Module</c> is the name of
 
285
          the callback module and <c>Function</c> is <c>init</c>
 
286
          (the function that initiates the new server).</p>
 
287
        <p>A <c>supervisor</c> and a <c>supervisor_bridge</c> are also
 
288
          <c>gen_server</c> processes. In order to return information
 
289
          that this process is a supervisor and the name of the
 
290
          call-back module, <c>Module</c> is <c>supervisor</c> and
 
291
          <c>Function</c> is the name of the supervisor callback
 
292
          module. <c>Arity</c> is <c>1</c> since the <c>init/1</c>
 
293
          function is called initially in the callback module.</p>
 
294
        <p>By default, <c>{proc_lib,init_p,5}</c> is returned if no
 
295
          information about the initial call can be found. It is
 
296
          assumed that the caller knows that the process has been
 
297
          spawned with the <c>proc_lib</c> module.</p>
 
298
      </desc>
 
299
    </func>
 
300
    <func>
 
301
      <name>hibernate(Module, Function, Args)</name>
 
302
      <fsummary>Hibernate a process until a message is sent to it</fsummary>
 
303
      <type>
 
304
        <v>Module = Function = atom()</v>
 
305
        <v>Args = [term()]</v>
 
306
      </type>
 
307
      <desc>
 
308
        <p>This function does the same as (and does call) the BIF
 
309
          <seealso marker="kernel:erlang#erlang:hibernate/3">hibernate/3</seealso>,
 
310
          but ensures that exception handling and logging continues to
 
311
          work as expected when the process wakes up. Always use this
 
312
          function instead of the BIF for processes started using
 
313
          <c>proc_lib</c> functions.</p>
 
314
      </desc>
 
315
    </func>
 
316
  </funcs>
 
317
 
 
318
  <section>
 
319
    <title>SEE ALSO</title>
 
320
    <p><seealso marker="kernel:error_logger">error_logger(3)</seealso></p>
 
321
  </section>
 
322
</erlref>
 
323