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

« back to all changes in this revision

Viewing changes to lib/kernel/doc/src/erlang.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>erlang</title>
 
27
    <prepared></prepared>
 
28
    <docno></docno>
 
29
    <date></date>
 
30
    <rev></rev>
 
31
  </header>
 
32
  <module>erlang</module>
 
33
  <modulesummary>The Erlang BIFs</modulesummary>
 
34
  <description>
 
35
    <p>By convention, most built-in functions (BIFs) are seen as being
 
36
      in the module <c>erlang</c>. A number of the BIFs are viewed more
 
37
      or less as part of the Erlang programming language and are
 
38
      <em>auto-imported</em>. Thus, it is not necessary to specify
 
39
      the module name and both the calls <c>atom_to_list(Erlang)</c> and
 
40
      <c>erlang:atom_to_list(Erlang)</c> are identical.</p>
 
41
    <p>In the text, auto-imported BIFs are listed without module prefix.
 
42
      BIFs listed with module prefix are not auto-imported.</p>
 
43
    <p>BIFs may fail for a variety of reasons. All BIFs fail with
 
44
      reason <c>badarg</c> if they are called with arguments of an
 
45
      incorrect type. The other reasons that may make BIFs fail are
 
46
      described in connection with the description of each individual
 
47
      BIF.</p>
 
48
    <p>Some BIFs may be used in guard tests, these are marked with
 
49
      "Allowed in guard tests".</p>
 
50
  </description>
 
51
 
 
52
  <section>
 
53
    <title>DATA TYPES</title>
 
54
    <marker id="iolist_definition"></marker>
 
55
    <code type="none">
 
56
ext_binary()
 
57
  a binary data object,
 
58
  structured according to the Erlang external term format
 
59
 
 
60
iodata() = iolist() | binary()
 
61
 
 
62
iolist() = [char() | binary() | iolist()]
 
63
  a binary is allowed as the tail of the list</code>
 
64
  </section>
 
65
  <funcs>
 
66
    <func>
 
67
      <name>abs(Number) ->  int() | float()</name>
 
68
      <fsummary>Arithmetical absolute value</fsummary>
 
69
      <type>
 
70
        <v>Number = number()</v>
 
71
      </type>
 
72
      <desc>
 
73
        <p>Returns an integer or float which is the arithmetical
 
74
          absolute value of <c>Number</c>.</p>
 
75
        <pre>
 
76
> <input>abs(-3.33).</input>
 
77
3.33
 
78
> <input>abs(-3).</input>
 
79
3</pre>
 
80
        <p>Allowed in guard tests.</p>
 
81
      </desc>
 
82
    </func>
 
83
    <func>
 
84
      <name>adler32(Data) -> int()</name>
 
85
      <fsummary>Compute adler32 checksum</fsummary>
 
86
      <type>
 
87
        <v>Data = iodata()</v>
 
88
      </type>
 
89
      <desc>
 
90
        <p>Computes and returns the adler32 checksum for <c>Data</c>.</p>
 
91
      </desc>
 
92
    </func>
 
93
    <func>
 
94
      <name>adler32(OldAdler, Data) -> int()</name>
 
95
      <fsummary>Compute adler32 checksum</fsummary>
 
96
      <type>
 
97
        <v>OldAdler = int()</v>
 
98
        <v>Data = iodata()</v>
 
99
      </type>
 
100
      <desc>
 
101
        <p>Continue computing the adler32 checksum by combining 
 
102
        the previous checksum, <c>OldAdler</c>, with the checksum of 
 
103
        <c>Data</c>.</p>
 
104
        <p>The following code:</p>
 
105
        <code>
 
106
        X = adler32(Data1),
 
107
        Y = adler32(X,Data2).
 
108
        </code>
 
109
        <p>- would assign the same value to <c>Y</c> as this would:</p>
 
110
        <code>
 
111
        Y = adler32([Data1,Data2]).
 
112
        </code>
 
113
      </desc>
 
114
    </func>
 
115
    <func>
 
116
      <name>adler32_combine(FirstAdler, SecondAdler, SecondSize) -> int()</name>
 
117
      <fsummary>Combine two adler32 checksums</fsummary>
 
118
      <type>
 
119
        <v>FirstAdler = SecondAdler = int()</v>
 
120
        <v>SecondSize = int()</v>
 
121
      </type>
 
122
      <desc>
 
123
        <p>Combines two previously computed adler32 checksums. 
 
124
        This computation requires the size of the data object for 
 
125
        the second checksum to be known.</p>
 
126
        <p>The following code:</p>
 
127
        <code>
 
128
        Y = adler32(Data1),
 
129
        Z = adler32(Y,Data2).
 
130
        </code>
 
131
        <p>- would assign the same value to <c>Z</c> as this would:</p>
 
132
        <code>
 
133
        X = adler32(Data1),
 
134
        Y = adler32(Data2),
 
135
        Z = adler32_combine(X,Y,iolist_size(Data2)).
 
136
        </code>
 
137
      </desc>
 
138
    </func>
 
139
    <func>
 
140
      <name>erlang:append_element(Tuple1, Term) -> Tuple2</name>
 
141
      <fsummary>Append an extra element to a tuple</fsummary>
 
142
      <type>
 
143
        <v>Tuple1 = Tuple2 = tuple()</v>
 
144
        <v>Term = term()</v>
 
145
      </type>
 
146
      <desc>
 
147
        <p>Returns a new tuple which has one element more than
 
148
          <c>Tuple1</c>, and contains the elements in <c>Tuple1</c>
 
149
          followed by <c>Term</c> as the last element. Semantically
 
150
          equivalent to
 
151
          <c>list_to_tuple(tuple_to_list(Tuple ++ [Term])</c>, but much
 
152
          faster.</p>
 
153
        <pre>
 
154
> <input>erlang:append_element({one, two}, three).</input>
 
155
{one,two,three}</pre>
 
156
      </desc>
 
157
    </func>
 
158
    <func>
 
159
      <name>apply(Fun, Args) -> term() | empty()</name>
 
160
      <fsummary>Apply a function to an argument list</fsummary>
 
161
      <type>
 
162
        <v>Fun = fun()</v>
 
163
        <v>Args = [term()]</v>
 
164
      </type>
 
165
      <desc>
 
166
        <p>Call a fun, passing the elements in <c>Args</c> as
 
167
          arguments.</p>
 
168
        <p>Note: If the number of elements in the arguments are known at
 
169
          compile-time, the call is better written as
 
170
          <c>Fun(Arg1, Arg2, ... ArgN)</c>.</p>
 
171
        <warning>
 
172
          <p>Earlier, <c>Fun</c> could also be given as
 
173
            <c>{Module, Function}</c>, equivalent to
 
174
            <c>apply(Module, Function, Args)</c>. This usage is
 
175
            deprecated and will stop working in a future release of
 
176
            Erlang/OTP.</p>
 
177
        </warning>
 
178
      </desc>
 
179
    </func>
 
180
    <func>
 
181
      <name>apply(Module, Function, Args) -> term() | empty()</name>
 
182
      <fsummary>Apply a function to an argument list</fsummary>
 
183
      <type>
 
184
        <v>Module = Function = atom()</v>
 
185
        <v>Args = [term()]</v>
 
186
      </type>
 
187
      <desc>
 
188
        <p>Returns the result of applying <c>Function</c> in
 
189
          <c>Module</c> to <c>Args</c>. The applied function must
 
190
          be exported from <c>Module</c>. The arity of the function is
 
191
          the length of <c>Args</c>.</p>
 
192
        <pre>
 
193
> <input>apply(lists, reverse, [[a, b, c]]).</input>
 
194
[c,b,a]</pre>
 
195
        <p><c>apply</c> can be used to evaluate BIFs by using
 
196
          the module name <c>erlang</c>.</p>
 
197
        <pre>
 
198
> <input>apply(erlang, atom_to_list, ['Erlang']).</input>
 
199
"Erlang"</pre>
 
200
        <p>Note: If the number of arguments are known at compile-time,
 
201
          the call is better written as
 
202
          <c>Module:Function(Arg1, Arg2, ..., ArgN)</c>.</p>
 
203
        <p>Failure: <c>error_handler:undefined_function/3</c> is called
 
204
          if the applied function is not exported. The error handler
 
205
          can be redefined (see
 
206
          <seealso marker="#process_flag/2">process_flag/2</seealso>).
 
207
          If the <c>error_handler</c> is undefined, or if the user has
 
208
          redefined the default <c>error_handler</c> so the replacement
 
209
          module is undefined, an error with the reason <c>undef</c>
 
210
          is generated.</p>
 
211
      </desc>
 
212
    </func>
 
213
    <func>
 
214
      <name>atom_to_list(Atom) -> string()</name>
 
215
      <fsummary>Text representation of an atom</fsummary>
 
216
      <type>
 
217
        <v>Atom = atom()</v>
 
218
      </type>
 
219
      <desc>
 
220
        <p>Returns a string which corresponds to the text
 
221
          representation of <c>Atom</c>.</p>
 
222
        <pre>
 
223
> <input>atom_to_list('Erlang').</input>
 
224
"Erlang"</pre>
 
225
      </desc>
 
226
    </func>
 
227
    <func>
 
228
      <name>binary_to_list(Binary) -> [char()]</name>
 
229
      <fsummary>Convert a binary to a list</fsummary>
 
230
      <type>
 
231
        <v>Binary = binary()</v>
 
232
      </type>
 
233
      <desc>
 
234
        <p>Returns a list of integers which correspond to the bytes of
 
235
          <c>Binary</c>.</p>
 
236
      </desc>
 
237
    </func>
 
238
    <func>
 
239
      <name>binary_to_list(Binary, Start, Stop) -> [char()]</name>
 
240
      <fsummary>Convert part of a binary to a list</fsummary>
 
241
      <type>
 
242
        <v>Binary = binary()</v>
 
243
        <v>Start = Stop = 1..byte_size(Binary)</v>
 
244
      </type>
 
245
      <desc>
 
246
        <p>As <c>binary_to_list/1</c>, but returns a list of integers
 
247
          corresponding to the bytes from position <c>Start</c> to
 
248
          position <c>Stop</c> in <c>Binary</c>. Positions in the
 
249
          binary are numbered starting from 1.</p>
 
250
      </desc>
 
251
    </func>
 
252
    <func>
 
253
      <name>bitstring_to_list(Bitstring) -> [char()|bitstring()]</name>
 
254
      <fsummary>Convert a bitstring to a list</fsummary>
 
255
      <type>
 
256
        <v>Bitstring = bitstring()</v>
 
257
      </type>
 
258
      <desc>
 
259
        <p>Returns a list of integers which correspond to the bytes of
 
260
          <c>Bitstring</c>. If the number of bits in the binary is not
 
261
          divisible by 8, the last element of the list will be a bitstring
 
262
          containing the remaining bits (1 up to 7 bits).</p>
 
263
      </desc>
 
264
    </func>
 
265
    <func>
 
266
      <name>binary_to_term(Binary) -> term()</name>
 
267
      <fsummary>Decode an Erlang external term format binary</fsummary>
 
268
      <type>
 
269
        <v>Binary = ext_binary()</v>
 
270
      </type>
 
271
      <desc>
 
272
        <p>Returns an Erlang term which is the result of decoding
 
273
          the binary object <c>Binary</c>, which must be encoded
 
274
          according to the Erlang external term format. See also
 
275
          <seealso marker="#term_to_binary/1">term_to_binary/1</seealso>.</p>
 
276
      </desc>
 
277
    </func>
 
278
    <func>
 
279
      <name>bit_size(Bitstring) -> int()</name>
 
280
      <fsummary>Return the size of a bitstring</fsummary>
 
281
      <type>
 
282
        <v>Bitstring = bitstring()</v>
 
283
      </type>
 
284
      <desc>
 
285
        <p>Returns an integer which is the size in bits of <c>Bitstring</c>.</p>
 
286
        <pre>
 
287
> <input>bit_size(&lt;&lt;433:16,3:3&gt;&gt;).</input>
 
288
19
 
289
> <input>bit_size(&lt;&lt;1,2,3&gt;&gt;).</input>
 
290
24</pre>
 
291
        <p>Allowed in guard tests.</p>
 
292
      </desc>
 
293
    </func>
 
294
    <func>
 
295
      <name>erlang:bump_reductions(Reductions) -> void()</name>
 
296
      <fsummary>Increment the reduction counter</fsummary>
 
297
      <type>
 
298
        <v>Reductions = int()</v>
 
299
      </type>
 
300
      <desc>
 
301
        <p>This implementation-dependent function increments
 
302
          the reduction counter for the calling process. In the Beam
 
303
          emulator, the reduction counter is normally incremented by
 
304
          one for each function and BIF call, and a context switch is
 
305
          forced when the counter reaches 1000.</p>
 
306
        <warning>
 
307
          <p>This BIF might be removed in a future version of the Beam
 
308
            machine without prior warning. It is unlikely to be
 
309
            implemented in other Erlang implementations.</p>
 
310
        </warning>
 
311
      </desc>
 
312
    </func>
 
313
    <func>
 
314
      <name>byte_size(Bitstring) -> int()</name>
 
315
      <fsummary>Return the size of a bitstring (or binary)</fsummary>
 
316
      <type>
 
317
        <v>Bitstring = bitstring()</v>
 
318
      </type>
 
319
      <desc>
 
320
        <p>Returns an integer which is the number of bytes needed to contain
 
321
        <c>Bitstring</c>. (That is, if the number of bits in <c>Bitstring</c> is not
 
322
        divisible by 8, the resulting number of bytes will be rounded <em>up</em>.)</p>
 
323
        <pre>
 
324
> <input>byte_size(&lt;&lt;433:16,3:3&gt;&gt;).</input>
 
325
3
 
326
> <input>byte_size(&lt;&lt;1,2,3&gt;&gt;).</input>
 
327
3</pre>
 
328
        <p>Allowed in guard tests.</p>
 
329
      </desc>
 
330
    </func>
 
331
    <func>
 
332
      <name>erlang:cancel_timer(TimerRef) -> Time | false</name>
 
333
      <fsummary>Cancel a timer</fsummary>
 
334
      <type>
 
335
        <v>TimerRef = ref()</v>
 
336
        <v>Time = int()</v>
 
337
      </type>
 
338
      <desc>
 
339
        <p>Cancels a timer, where <c>TimerRef</c> was returned by
 
340
          either
 
341
          <seealso marker="#erlang:send_after/3">erlang:send_after/3</seealso>
 
342
          or
 
343
          <seealso marker="#erlang:start_timer/3">erlang:start_timer/3</seealso>.
 
344
          If the timer is there to be removed, the function returns
 
345
          the time in milliseconds left until the timer would have expired,
 
346
          otherwise <c>false</c> (which means that <c>TimerRef</c> was
 
347
          never a timer, that it has already been cancelled, or that it
 
348
          has already delivered its message).</p>
 
349
        <p>See also 
 
350
          <seealso marker="#erlang:send_after/3">erlang:send_after/3</seealso>,
 
351
          <seealso marker="#erlang:start_timer/3">erlang:start_timer/3</seealso>,
 
352
          and
 
353
          <seealso marker="#erlang:read_timer/1">erlang:read_timer/1</seealso>.</p>
 
354
        <p>Note: Cancelling a timer does not guarantee that the message
 
355
          has not already been delivered to the message queue.</p>
 
356
      </desc>
 
357
    </func>
 
358
 
 
359
    <func>
 
360
      <name>check_process_code(Pid, Module) -> bool()</name>
 
361
      <fsummary>Check if a process is executing old code for a module</fsummary>
 
362
      <type>
 
363
        <v>Pid = pid()</v>
 
364
        <v>Module = atom()</v>
 
365
      </type>
 
366
      <desc>
 
367
        <p>Returns <c>true</c> if the process <c>Pid</c> is executing
 
368
          old code for <c>Module</c>. That is, if the current call of
 
369
          the process executes old code for this module, or if the
 
370
          process has references to old code for this module, or if the
 
371
          process contains funs that references old code for this
 
372
          module. Otherwise, it returns <c>false</c>.</p>
 
373
        <pre>
 
374
> <input>check_process_code(Pid, lists).</input>
 
375
false</pre>
 
376
        <p>See also <seealso marker="code">code(3)</seealso>.</p>
 
377
      </desc>
 
378
    </func>
 
379
    <func>
 
380
      <name>concat_binary(ListOfBinaries)</name>
 
381
      <fsummary>Concatenate a list of binaries (deprecated)</fsummary>
 
382
      <desc>
 
383
        <p>Do not use; use
 
384
          <seealso marker="#list_to_binary/1">list_to_binary/1</seealso>
 
385
          instead.</p>
 
386
      </desc>
 
387
    </func>
 
388
    <func>
 
389
      <name>crc32(Data) -> int()</name>
 
390
      <fsummary>Compute crc32 (IEEE 802.3) checksum</fsummary>
 
391
      <type>
 
392
        <v>Data = iodata()</v>
 
393
      </type>
 
394
      <desc>
 
395
        <p>Computes and returns the crc32 (IEEE 802.3 style) checksum for <c>Data</c>.</p>
 
396
      </desc>
 
397
    </func>
 
398
    <func>
 
399
      <name>crc32(OldCrc, Data) -> int()</name>
 
400
      <fsummary>Compute crc32 (IEEE 802.3) checksum</fsummary>
 
401
      <type>
 
402
        <v>OldCrc = int()</v>
 
403
        <v>Data = iodata()</v>
 
404
      </type>
 
405
      <desc>
 
406
        <p>Continue computing the crc32 checksum by combining 
 
407
        the previous checksum, <c>OldCrc</c>, with the checksum of 
 
408
        <c>Data</c>.</p>
 
409
        <p>The following code:</p>
 
410
        <code>
 
411
        X = crc32(Data1),
 
412
        Y = crc32(X,Data2).
 
413
        </code>
 
414
        <p>- would assign the same value to <c>Y</c> as this would:</p>
 
415
        <code>
 
416
        Y = crc32([Data1,Data2]).
 
417
        </code>
 
418
      </desc>
 
419
    </func>
 
420
    <func>
 
421
      <name>crc32_combine(FirstCrc, SecondCrc, SecondSize) -> int()</name>
 
422
      <fsummary>Combine two crc32 (IEEE 802.3) checksums</fsummary>
 
423
      <type>
 
424
        <v>FirstCrc = SecondCrc = int()</v>
 
425
        <v>SecondSize = int()</v>
 
426
      </type>
 
427
      <desc>
 
428
        <p>Combines two previously computed crc32 checksums. 
 
429
        This computation requires the size of the data object for 
 
430
        the second checksum to be known.</p>
 
431
        <p>The following code:</p>
 
432
        <code>
 
433
        Y = crc32(Data1),
 
434
        Z = crc32(Y,Data2).
 
435
        </code>
 
436
        <p>- would assign the same value to <c>Z</c> as this would:</p>
 
437
        <code>
 
438
        X = crc32(Data1),
 
439
        Y = crc32(Data2),
 
440
        Z = crc32_combine(X,Y,iolist_size(Data2)).
 
441
        </code>
 
442
      </desc>
 
443
    </func>
 
444
    <func>
 
445
      <name>date() -> {Year, Month, Day}</name>
 
446
      <fsummary>Current date</fsummary>
 
447
      <type>
 
448
        <v>Year = Month = Day = int()</v>
 
449
      </type>
 
450
      <desc>
 
451
        <p>Returns the current date as <c>{Year, Month, Day}</c>.</p>
 
452
        <p>The time zone and daylight saving time correction depend on
 
453
          the underlying OS.</p>
 
454
        <pre>
 
455
> <input>date().</input>
 
456
{1995,2,19}</pre>
 
457
      </desc>
 
458
    </func>
 
459
    <func>
 
460
      <name>decode_packet(Type,Bin,Options) -> {ok,Packet,Rest} | {more,Length} | {error,Reason}</name>
 
461
      <fsummary>Extracts a protocol packet from a binary</fsummary>
 
462
      <type>
 
463
        <v>Bin = binary()</v>
 
464
        <v>Options = [Opt]</v>
 
465
        <v>Packet = binary() | HttpPacket</v>
 
466
        <v>Rest = binary()</v>
 
467
        <v>Length = int() | undefined</v>
 
468
        <v>Reason = term()</v>
 
469
        <v>&nbsp;Type, Opt -- see below</v>
 
470
        <v></v>
 
471
        <v>HttpPacket = HttpRequest | HttpResponse | HttpHeader | http_eoh | HttpError</v>
 
472
        <v>HttpRequest = {http_request, HttpMethod, HttpUri, HttpVersion}</v>
 
473
        <v>HttpResponse = {http_response, HttpVersion, integer(), string()}</v>
 
474
        <v>HttpHeader = {http_header, int(), HttpField, Reserved=term(), Value=string()}</v>
 
475
        <v>HttpError = {http_error, string()}</v>
 
476
        <v>HttpMethod = HttpMethodAtom | string()</v>
 
477
        <v>HttpMethodAtom = 'OPTIONS' | 'GET' | 'HEAD' | 'POST' | 'PUT' | 'DELETE' | 'TRACE'</v>
 
478
        <v>HttpUri = '*' | {absoluteURI, http|https, Host=string(), Port=int()|undefined, Path=string()} | 
 
479
                     {scheme, Scheme=string(), string()} | {abs_path, string} | string()</v>
 
480
        <v>HttpVersion = {Major=int(), Minor=int()}</v>
 
481
        <v>HttpField = HttpFieldAtom | string()</v>
 
482
        <v>HttpFieldAtom = 'Cache-Control' | 'Connection' | 'Date' | 'Pragma' | 'Transfer-Encoding' | 'Upgrade' | 'Via' | 'Accept' | 'Accept-Charset' | 'Accept-Encoding' | 'Accept-Language' | 'Authorization' | 'From' | 'Host' | 'If-Modified-Since' | 'If-Match' | 'If-None-Match' | 'If-Range' | 'If-Unmodified-Since' | 'Max-Forwards' | 'Proxy-Authorization' | 'Range' | 'Referer' | 'User-Agent' | 'Age' | 'Location' | 'Proxy-Authenticate' | 'Public' | 'Retry-After' | 'Server' | 'Vary' | 'Warning' | 'Www-Authenticate' | 'Allow' | 'Content-Base' | 'Content-Encoding' | 'Content-Language' | 'Content-Length' | 'Content-Location' | 'Content-Md5' | 'Content-Range' | 'Content-Type' | 'Etag' | 'Expires' | 'Last-Modified' | 'Accept-Ranges' | 'Set-Cookie' | 'Set-Cookie2' | 'X-Forwarded-For' | 'Cookie' | 'Keep-Alive' | 'Proxy-Connection'</v>
 
483
        <v></v>
 
484
      </type>
 
485
      <desc>
 
486
        <p>Decodes the binary <c>Bin</c> according to the packet
 
487
        protocol specified by <c>Type</c>. Very simular to the packet
 
488
        handling done by sockets with the option {packet,Type}.</p>
 
489
        <p>If an entire packet is contained in <c>Bin</c> it is
 
490
        returned together with the remainder of the binary as
 
491
        <c>{ok,Packet,Rest}</c>.</p>
 
492
        <p>If <c>Bin</c> does not contain the entire packet,
 
493
        <c>{more,Length}</c> is returned. <c>Length</c> is either the
 
494
        expected <em>total size</em> of the packet or <c>undefined</c>
 
495
        if the expected packet size is not known. <c>decode_packet</c>
 
496
        can then be called again with more data added.</p>
 
497
        <p>If the packet does not conform to the protocol format
 
498
        <c>{error,Reason}</c> is returned.</p>
 
499
        <p>The following values of <c>Type</c> are valid:</p>
 
500
        <taglist>
 
501
          <tag><c>raw | 0</c></tag>
 
502
          <item>
 
503
            <p>No packet handling is done. Entire binary is
 
504
            returned unless it is empty.</p>
 
505
          </item>
 
506
          <tag><c>1 | 2 | 4</c></tag>
 
507
          <item>
 
508
            <p>Packets consist of a header specifying the number of
 
509
              bytes in the packet, followed by that number of bytes.
 
510
              The length of header can be one, two, or four bytes;
 
511
              the order of the bytes is big-endian. The header
 
512
              will be stripped off when the packet is returned.</p>
 
513
          </item>
 
514
          <tag><c>line</c></tag>
 
515
          <item>
 
516
            <p>A packet is a line terminated with newline. The
 
517
              newline character is included in the returned packet
 
518
              unless the line was truncated according to the option
 
519
              <c>line_length</c>.</p> 
 
520
          </item>
 
521
          <tag><c>asn1 | cdr | sunrm | fcgi | tpkt</c></tag>
 
522
          <item>
 
523
            <p>The header is <em>not</em> stripped off.</p>
 
524
            <p>The meanings of the packet types are as follows:</p>
 
525
            <taglist>     
 
526
              <tag><c>asn1</c> - ASN.1 BER</tag><item></item>
 
527
              <tag><c>sunrm</c> - Sun's RPC encoding</tag><item></item>
 
528
              <tag><c>cdr</c> - CORBA (GIOP 1.1)</tag><item></item>
 
529
              <tag><c>fcgi</c> - Fast CGI</tag><item></item>
 
530
              <tag><c>tpkt</c> - TPKT format [RFC1006]</tag><item></item>
 
531
            </taglist>
 
532
          </item>
 
533
          <tag><c>http | httph</c></tag>
 
534
          <item>
 
535
            <p>The Hypertext Transfer Protocol. The packets
 
536
               are returned with the format according to
 
537
               <c>HttpPacket</c> described above. A packet is either a
 
538
               request, a response, a header or an end of header
 
539
               mark. Invalid lines are returned as <c>HttpError</c>.</p> 
 
540
            <p>Recognized request methods and header fields are returned as atoms.
 
541
               Others are returned as strings.</p>
 
542
            <p>The protocol type <c>http</c> should only be used for
 
543
               the first line when a <c>HttpRequest</c> or a
 
544
               <c>HttpResponse</c> is expected. The following calls
 
545
               should use <c>httph</c> to get <c>HttpHeader</c>'s until
 
546
               <c>http_eoh</c> is returned that marks the end of the
 
547
               headers and the beginning of any following message body.</p> 
 
548
          </item>
 
549
        </taglist>
 
550
        <p>The following options are available:</p>
 
551
            <taglist>
 
552
              <tag><c>{packet_size, int()}</c></tag>
 
553
              <item><p>Sets the max allowed size of the packet body. If
 
554
                the packet header indicates that the length of the
 
555
                packet is longer than the max allowed length, the packet
 
556
                is considered invalid. Default is 0 which means no
 
557
                size limit.</p>
 
558
              </item>
 
559
              <tag><c>{line_length, int()}</c></tag>
 
560
              <item><p>Applies only to line oriented protocols
 
561
                (<c>line</c>, <c>http</c>). Lines longer than this
 
562
                will be truncated.</p>
 
563
              </item>
 
564
            </taglist>
 
565
        <pre>
 
566
> <input>erlang:decode_packet(1,&lt;&lt;3,"abcd"&gt;&gt;,[]).</input>
 
567
{ok,&lt;&lt;"abc"&gt;&gt;,&lt;&lt;"d"&gt;&gt;}
 
568
> <input>erlang:decode_packet(1,&lt;&lt;5,"abcd"&gt;&gt;,[]).</input>
 
569
{more,6}</pre>
 
570
      </desc>
 
571
    </func>
 
572
    <func>
 
573
      <name>delete_module(Module) -> true | undefined</name>
 
574
      <fsummary>Make the current code for a module old</fsummary>
 
575
      <type>
 
576
        <v>Module = atom()</v>
 
577
      </type>
 
578
      <desc>
 
579
        <p>Makes the current code for <c>Module</c> become old code, and
 
580
          deletes all references for this module from the export table.
 
581
          Returns <c>undefined</c> if the module does not exist,
 
582
          otherwise <c>true</c>.</p>
 
583
        <warning>
 
584
          <p>This BIF is intended for the code server (see
 
585
            <seealso marker="code">code(3)</seealso>) and should not be
 
586
            used elsewhere.</p>
 
587
        </warning>
 
588
        <p>Failure: <c>badarg</c> if there is already an old version of
 
589
          <c>Module</c>.</p>
 
590
      </desc>
 
591
    </func>
 
592
    <func>
 
593
      <name>erlang:demonitor(MonitorRef) -> true</name>
 
594
      <fsummary>Stop monitoring</fsummary>
 
595
      <type>
 
596
        <v>MonitorRef = ref()</v>
 
597
      </type>
 
598
      <desc>
 
599
        <p>If <c>MonitorRef</c> is a reference which the calling process
 
600
          obtained by calling
 
601
          <seealso marker="#erlang:monitor/2">erlang:monitor/2</seealso>,
 
602
          this monitoring is turned off. If the monitoring is already
 
603
          turned off, nothing happens.</p>
 
604
        <p>Once <c>erlang:demonitor(MonitorRef)</c> has returned it is
 
605
          guaranteed that no <c>{'DOWN', MonitorRef, _, _, _}</c> message
 
606
          due to the monitor will be placed in the callers message queue
 
607
          in the future. A <c>{'DOWN', MonitorRef, _, _, _}</c> message
 
608
          might have been placed in the callers message queue prior to
 
609
          the call, though. Therefore, in most cases, it is advisable
 
610
          to remove such a <c>'DOWN'</c> message from the message queue
 
611
          after monitoring has been stopped. 
 
612
          <seealso marker="#erlang:demonitor/2">erlang:demonitor(MonitorRef, [flush])</seealso> can be used instead of
 
613
          <c>erlang:demonitor(MonitorRef)</c> if this cleanup is wanted.</p>
 
614
        <note>
 
615
          <p>Prior to OTP release R11B (erts version 5.5) <c>erlang:demonitor/1</c>
 
616
            behaved completely asynchronous, i.e., the monitor was active
 
617
            until the "demonitor signal" reached the monitored entity. This
 
618
            had one undesirable effect, though. You could never know when
 
619
            you were guaranteed <em>not</em> to receive a <c>DOWN</c> message
 
620
            due to the monitor.</p>
 
621
          <p>Current behavior can be viewed as two combined operations:
 
622
            asynchronously send a "demonitor signal" to the monitored entity
 
623
            and ignore any future results of the monitor. </p>
 
624
        </note>
 
625
        <p>Failure: It is an error if <c>MonitorRef</c> refers to a
 
626
          monitoring started by another process. Not all such cases are
 
627
          cheap to check; if checking is cheap, the call fails with
 
628
          <c>badarg</c> (for example if <c>MonitorRef</c> is a remote
 
629
          reference).</p>
 
630
      </desc>
 
631
    </func>
 
632
    <func>
 
633
      <name>erlang:demonitor(MonitorRef, OptionList) -> true</name>
 
634
      <fsummary>Stop monitoring</fsummary>
 
635
      <type>
 
636
        <v>MonitorRef = ref()</v>
 
637
        <v>OptionList = [Option]</v>
 
638
        <v>Option = flush</v>
 
639
      </type>
 
640
      <desc>
 
641
        <p><c>erlang:demonitor(MonitorRef, [])</c> is equivalent to
 
642
          <seealso marker="#erlang:demonitor/1">erlang:demonitor(MonitorRef)</seealso>.</p>
 
643
        <p>Currently the following <c>Option</c>s are valid:</p>
 
644
        <taglist>
 
645
          <tag><c>flush</c></tag>
 
646
          <item>
 
647
            <p>Remove (one) <c>{_, MonitorRef, _, _, _}</c> message,
 
648
              if there is one, from the callers message queue after
 
649
              monitoring has been stopped.</p>
 
650
            <p>Calling <c>erlang:demonitor(MonitorRef, [flush])</c>
 
651
              is equivalent to:</p>
 
652
            <code type="none">
 
653
 
 
654
    erlang:demonitor(MonitorRef),
 
655
    receive
 
656
\011{_, MonitorRef, _, _, _} ->
 
657
\011    true
 
658
    after 0 ->
 
659
\011    true
 
660
    end</code>
 
661
          </item>
 
662
        </taglist>
 
663
        <note>
 
664
          <p>More options may be added in the future.</p>
 
665
        </note>
 
666
        <p>Failure: <c>badarg</c> if <c>OptionList</c> is not a list, or
 
667
          if <c>Option</c> is not a valid option, or the same failure as for
 
668
          <seealso marker="#erlang:demonitor/1">erlang:demonitor/1</seealso></p>
 
669
      </desc>
 
670
    </func>
 
671
    <func>
 
672
      <name>disconnect_node(Node) -> bool() | ignored</name>
 
673
      <fsummary>Force the disconnection of a node</fsummary>
 
674
      <type>
 
675
        <v>Node = atom()</v>
 
676
      </type>
 
677
      <desc>
 
678
        <p>Forces the disconnection of a node. This will appear to
 
679
          the node <c>Node</c> as if the local node has crashed. This
 
680
          BIF is mainly used in the Erlang network authentication
 
681
          protocols. Returns <c>true</c> if disconnection succeeds,
 
682
          otherwise <c>false</c>. If the local node is not alive,
 
683
          the function returns <c>ignored</c>.</p>
 
684
      </desc>
 
685
    </func>
 
686
    <func>
 
687
      <name>erlang:display(Term) -> true</name>
 
688
      <fsummary>Print a term on standard output</fsummary>
 
689
      <type>
 
690
        <v>Term = term()</v>
 
691
      </type>
 
692
      <desc>
 
693
        <p>Prints a text representation of <c>Term</c> on the standard
 
694
          output.</p>
 
695
        <warning>
 
696
          <p>This BIF is intended for debugging only.</p>
 
697
        </warning>
 
698
      </desc>
 
699
    </func>
 
700
    <func>
 
701
      <name>element(N, Tuple) -> term()</name>
 
702
      <fsummary>Get Nth element of a tuple</fsummary>
 
703
      <type>
 
704
        <v>N = 1..tuple_size(Tuple)</v>
 
705
        <v>Tuple = tuple()</v>
 
706
      </type>
 
707
      <desc>
 
708
        <p>Returns the <c>N</c>th element (numbering from 1) of
 
709
          <c>Tuple</c>.</p>
 
710
        <pre>
 
711
> <input>element(2, {a, b, c}).</input>
 
712
b</pre>
 
713
        <p>Allowed in guard tests.</p>
 
714
      </desc>
 
715
    </func>
 
716
    <func>
 
717
      <name>erase() -> [{Key, Val}]</name>
 
718
      <fsummary>Return and delete the process dictionary</fsummary>
 
719
      <type>
 
720
        <v>Key = Val = term()</v>
 
721
      </type>
 
722
      <desc>
 
723
        <p>Returns the process dictionary and deletes it.</p>
 
724
        <pre>
 
725
> <input>put(key1, {1, 2, 3}),</input>
 
726
<input>put(key2, [a, b, c]),</input>
 
727
<input>erase().</input>
 
728
[{key1,{1,2,3}},{key2,[a,b,c]}]</pre>
 
729
      </desc>
 
730
    </func>
 
731
    <func>
 
732
      <name>erase(Key) -> Val | undefined</name>
 
733
      <fsummary>Return and delete a value from the process dictionary</fsummary>
 
734
      <type>
 
735
        <v>Key = Val = term()</v>
 
736
      </type>
 
737
      <desc>
 
738
        <p>Returns the value <c>Val</c> associated with <c>Key</c> and
 
739
          deletes it from the process dictionary. Returns
 
740
          <c>undefined</c> if no value is associated with <c>Key</c>.</p>
 
741
        <pre>
 
742
> <input>put(key1, {merry, lambs, are, playing}),</input>
 
743
<input>X = erase(key1),</input>
 
744
<input>{X, erase(key1)}.</input>
 
745
{{merry,lambs,are,playing},undefined}</pre>
 
746
      </desc>
 
747
    </func>
 
748
    <func>
 
749
      <name>erlang:error(Reason)</name>
 
750
      <fsummary>Stop execution with a given reason</fsummary>
 
751
      <type>
 
752
        <v>Reason = term()</v>
 
753
      </type>
 
754
      <desc>
 
755
        <p>Stops the execution of the calling process with the reason
 
756
          <c>Reason</c>, where <c>Reason</c> is any term. The actual
 
757
          exit reason will be <c>{Reason, Where}</c>, where <c>Where</c>
 
758
          is a list of the functions most recently called (the current
 
759
          function first). Since evaluating this function causes
 
760
          the process to terminate, it has no return value.</p>
 
761
        <pre>
 
762
> <input>catch erlang:error(foobar).</input>
 
763
{'EXIT',{foobar,[{erl_eval,do_apply,5},
 
764
                 {erl_eval,expr,5},
 
765
                 {shell,exprs,6},
 
766
                 {shell,eval_exprs,6},
 
767
                 {shell,eval_loop,3}]}}</pre>
 
768
      </desc>
 
769
    </func>
 
770
    <func>
 
771
      <name>erlang:error(Reason, Args)</name>
 
772
      <fsummary>Stop execution with a given reason</fsummary>
 
773
      <type>
 
774
        <v>Reason = term()</v>
 
775
        <v>Args = [term()]</v>
 
776
      </type>
 
777
      <desc>
 
778
        <p>Stops the execution of the calling process with the reason
 
779
          <c>Reason</c>, where <c>Reason</c> is any term. The actual
 
780
          exit reason will be <c>{Reason, Where}</c>, where <c>Where</c>
 
781
          is a list of the functions most recently called (the current
 
782
          function first). <c>Args</c> is expected to be the list of
 
783
          arguments for the current function; in Beam it will be used
 
784
          to provide the actual arguments for the current function in
 
785
          the <c>Where</c> term. Since evaluating this function causes
 
786
          the process to terminate, it has no return value.</p>
 
787
      </desc>
 
788
    </func>
 
789
    <func>
 
790
      <name>exit(Reason)</name>
 
791
      <fsummary>Stop execution with a given reason</fsummary>
 
792
      <type>
 
793
        <v>Reason = term()</v>
 
794
      </type>
 
795
      <desc>
 
796
        <p>Stops the execution of the calling process with the exit
 
797
          reason <c>Reason</c>, where <c>Reason</c> is any term. Since
 
798
          evaluating this function causes the process to terminate, it
 
799
          has no return value.</p>
 
800
        <pre>
 
801
> <input>exit(foobar).</input>
 
802
** exception exit: foobar
 
803
> <input>catch exit(foobar).</input>
 
804
{'EXIT',foobar}</pre>
 
805
      </desc>
 
806
    </func>
 
807
    <func>
 
808
      <name>exit(Pid, Reason) -> true</name>
 
809
      <fsummary>Send an exit signal to a process</fsummary>
 
810
      <type>
 
811
        <v>Pid = pid()</v>
 
812
        <v>Reason = term()</v>
 
813
      </type>
 
814
      <desc>
 
815
        <p>Sends an exit signal with exit reason <c>Reason</c> to
 
816
          the process <c>Pid</c>.</p>
 
817
        <p>The following behavior apply if <c>Reason</c> is any term
 
818
          except <c>normal</c> or <c>kill</c>:</p>
 
819
        <p>If <c>Pid</c> is not trapping exits, <c>Pid</c> itself will
 
820
          exit with exit reason <c>Reason</c>. If <c>Pid</c> is trapping
 
821
          exits, the exit signal is transformed into a message
 
822
          <c>{'EXIT', From, Reason}</c> and delivered to the message
 
823
          queue of <c>Pid</c>. <c>From</c> is the pid of the process
 
824
          which sent the exit signal. See also
 
825
          <seealso marker="#process_flag/2">process_flag/2</seealso>.</p>
 
826
        <p>If <c>Reason</c> is the atom <c>normal</c>, <c>Pid</c> will
 
827
          not exit. If it is trapping exits, the exit signal is
 
828
          transformed into a message <c>{'EXIT', From, normal}</c>
 
829
          and delivered to its message queue.</p>
 
830
        <p>If <c>Reason</c> is the atom <c>kill</c>, that is if
 
831
          <c>exit(Pid, kill)</c> is called, an untrappable exit signal
 
832
          is sent to <c>Pid</c> which will unconditionally exit with
 
833
          exit reason <c>killed</c>.</p>
 
834
      </desc>
 
835
    </func>
 
836
    <func>
 
837
      <name>erlang:fault(Reason)</name>
 
838
      <fsummary>Stop execution with a given reason</fsummary>
 
839
      <type>
 
840
        <v>Reason = term()</v>
 
841
      </type>
 
842
      <desc>
 
843
        <p>This function is deprecated and will be removed in the next release.
 
844
        Used <seealso marker="#erlang:error/1">erlang:error(Reason)</seealso>
 
845
        instead.</p>
 
846
      </desc>
 
847
    </func>
 
848
    <func>
 
849
      <name>erlang:fault(Reason, Args)</name>
 
850
      <fsummary>Stop execution with a given reason</fsummary>
 
851
      <type>
 
852
        <v>Reason = term()</v>
 
853
        <v>Args = [term()]</v>
 
854
      </type>
 
855
      <desc>
 
856
        <p>This function is deprecated and will be removed in the next release.
 
857
        Use <seealso marker="#erlang:error/2">erlang:error(Reason, Args)</seealso>
 
858
        instead.</p>
 
859
      </desc>
 
860
    </func>
 
861
    <func>
 
862
      <name>float(Number) -> float()</name>
 
863
      <fsummary>Convert a number to a float</fsummary>
 
864
      <type>
 
865
        <v>Number = number()</v>
 
866
      </type>
 
867
      <desc>
 
868
        <p>Returns a float by converting <c>Number</c> to a float.</p>
 
869
        <pre>
 
870
> <input>float(55).</input>
 
871
55.0</pre>
 
872
        <p>Allowed in guard tests.</p>
 
873
        <note>
 
874
          <p>Note that if used on the top-level in a guard, it will
 
875
            test whether the argument is a floating point number; for
 
876
            clarity, use
 
877
            <seealso marker="#is_float/1">is_float/1</seealso> instead.</p>
 
878
          <p>When <c>float/1</c> is used in an expression in a guard,
 
879
            such as '<c>float(A) == 4.0</c>', it converts a number as
 
880
            described above.</p>
 
881
        </note>
 
882
      </desc>
 
883
    </func>
 
884
    <func>
 
885
      <name>float_to_list(Float) -> string()</name>
 
886
      <fsummary>Text representation of a float</fsummary>
 
887
      <type>
 
888
        <v>Float = float()</v>
 
889
      </type>
 
890
      <desc>
 
891
        <p>Returns a string which corresponds to the text
 
892
          representation of <c>Float</c>.</p>
 
893
        <pre>
 
894
> <input>float_to_list(7.0).</input>
 
895
"7.00000000000000000000e+00"</pre>
 
896
      </desc>
 
897
    </func>
 
898
    <func>
 
899
      <name>erlang:fun_info(Fun) -> [{Item, Info}]</name>
 
900
      <fsummary>Information about a fun</fsummary>
 
901
      <type>
 
902
        <v>Fun = fun()</v>
 
903
        <v>Item, Info -- see below</v>
 
904
      </type>
 
905
      <desc>
 
906
        <p>Returns a list containing information about the fun
 
907
          <c>Fun</c>. Each element of the list is a tuple. The order of
 
908
          the tuples is not defined, and more tuples may be added in a
 
909
          future release.</p>
 
910
        <warning>
 
911
          <p>This BIF is mainly intended for debugging, but it can
 
912
            occasionally be useful in library functions that might need
 
913
            to verify, for instance, the arity of a fun.</p>
 
914
        </warning>
 
915
        <p>There are two types of funs with slightly different
 
916
          semantics:</p>
 
917
        <p>A fun created by <c>fun M:F/A</c> is called an
 
918
          <em>external</em> fun. Calling it will always call the
 
919
          function <c>F</c> with arity <c>A</c> in the latest code for
 
920
          module <c>M</c>. Note that module <c>M</c> does not even need
 
921
          to be loaded when the fun <c>fun M:F/A</c> is created.</p>
 
922
        <p>All other funs are called <em>local</em>. When a local fun
 
923
          is called, the same version of the code that created the fun
 
924
          will be called (even if newer version of the module has been
 
925
          loaded).</p>
 
926
        <p>The following elements will always be present in the list
 
927
          for both local and external funs:</p>
 
928
        <taglist>
 
929
          <tag><c>{type, Type}</c></tag>
 
930
          <item>
 
931
            <p><c>Type</c> is either <c>local</c> or <c>external</c>.</p>
 
932
          </item>
 
933
          <tag><c>{module, Module}</c></tag>
 
934
          <item>
 
935
            <p><c>Module</c> (an atom) is the module name.</p>
 
936
            <p>If <c>Fun</c> is a local fun, <c>Module</c> is the module
 
937
              in which the fun is defined.</p>
 
938
            <p>If <c>Fun</c> is an external fun, <c>Module</c> is the
 
939
              module that the fun refers to.</p>
 
940
          </item>
 
941
          <tag><c>{name, Name}</c></tag>
 
942
          <item>
 
943
            <p><c>Name</c> (an atom) is a function name.</p>
 
944
            <p>If <c>Fun</c> is a local fun, <c>Name</c> is the name
 
945
              of the local function that implements the fun.
 
946
              (This name was generated by the compiler, and is generally
 
947
              only of informational use. As it is a local function, it
 
948
              is not possible to call it directly.)
 
949
              If no code is currently loaded for the fun, <c>[]</c>
 
950
              will be returned instead of an atom.</p>
 
951
            <p>If <c>Fun</c> is an external fun, <c>Name</c> is the name
 
952
              of the exported function that the fun refers to.</p>
 
953
          </item>
 
954
          <tag><c>{arity, Arity}</c></tag>
 
955
          <item>
 
956
            <p><c>Arity</c> is the number of arguments that the fun
 
957
              should be called with.</p>
 
958
          </item>
 
959
          <tag><c>{env, Env}</c></tag>
 
960
          <item>
 
961
            <p><c>Env</c> (a list) is the environment or free variables
 
962
              for the fun. (For external funs, the returned list is
 
963
              always empty.)</p>
 
964
          </item>
 
965
        </taglist>
 
966
        <p>The following elements will only be present in the list if
 
967
          <c>Fun</c> is local:</p>
 
968
        <taglist>
 
969
          <tag><c>{pid, Pid}</c></tag>
 
970
          <item>
 
971
            <p><c>Pid</c> is the pid of the process that originally
 
972
              created the fun.</p>
 
973
          </item>
 
974
          <tag><c>{index, Index}</c></tag>
 
975
          <item>
 
976
            <p><c>Index</c> (an integer) is an index into the module's
 
977
              fun table.</p>
 
978
          </item>
 
979
          <tag><c>{new_index, Index}</c></tag>
 
980
          <item>
 
981
            <p><c>Index</c> (an integer) is an index into the module's
 
982
              fun table.</p>
 
983
          </item>
 
984
          <tag><c>{new_uniq, Uniq}</c></tag>
 
985
          <item>
 
986
            <p><c>Uniq</c> (a binary) is a unique value for this fun.</p>
 
987
          </item>
 
988
          <tag><c>{uniq, Uniq}</c></tag>
 
989
          <item>
 
990
            <p><c>Uniq</c> (an integer) is a unique value for this fun.</p>
 
991
          </item>
 
992
        </taglist>
 
993
      </desc>
 
994
    </func>
 
995
    <func>
 
996
      <name>erlang:fun_info(Fun, Item) -> {Item, Info}</name>
 
997
      <fsummary>Information about a fun</fsummary>
 
998
      <type>
 
999
        <v>Fun = fun()</v>
 
1000
        <v>Item, Info -- see below</v>
 
1001
      </type>
 
1002
      <desc>
 
1003
        <p>Returns information about <c>Fun</c> as specified by
 
1004
          <c>Item</c>, in the form <c>{Item,Info}</c>.</p>
 
1005
        <p>For any fun, <c>Item</c> can be any of the atoms
 
1006
          <c>module</c>, <c>name</c>, <c>arity</c>, or <c>env</c>.</p>
 
1007
        <p>For a local fun, <c>Item</c> can also be any of the atoms
 
1008
          <c>index</c>, <c>new_index</c>, <c>new_uniq</c>,
 
1009
          <c>uniq</c>, and <c>pid</c>. For an external fun, the value
 
1010
          of any of these items is always the atom <c>undefined</c>.</p>
 
1011
        <p>See
 
1012
          <seealso marker="#erlang:fun_info/1">erlang:fun_info/1</seealso>.</p>
 
1013
      </desc>
 
1014
    </func>
 
1015
    <func>
 
1016
      <name>erlang:fun_to_list(Fun) -> string()</name>
 
1017
      <fsummary>Text representation of a fun</fsummary>
 
1018
      <type>
 
1019
        <v>Fun = fun()</v>
 
1020
      </type>
 
1021
      <desc>
 
1022
        <p>Returns a string which corresponds to the text
 
1023
          representation of <c>Fun</c>.</p>
 
1024
      </desc>
 
1025
    </func>
 
1026
    <func>
 
1027
      <name>erlang:function_exported(Module, Function, Arity) -> bool()</name>
 
1028
      <fsummary>Check if a function is exported and loaded</fsummary>
 
1029
      <type>
 
1030
        <v>Module = Function = atom()</v>
 
1031
        <v>Arity = int()</v>
 
1032
      </type>
 
1033
      <desc>
 
1034
        <p>Returns <c>true</c> if the module <c>Module</c> is loaded
 
1035
          and contains an exported function <c>Function/Arity</c>;
 
1036
          otherwise <c>false</c>.</p>
 
1037
        <p>Returns <c>false</c> for any BIF (functions implemented in C
 
1038
          rather than in Erlang).</p>
 
1039
      </desc>
 
1040
    </func>
 
1041
    <func>
 
1042
      <name>garbage_collect() -> true</name>
 
1043
      <fsummary>Force an immediate garbage collection of the calling process</fsummary>
 
1044
      <desc>
 
1045
        <p>Forces an immediate garbage collection of the currently
 
1046
          executing process. The function should not be used, unless
 
1047
          it has been noticed -- or there are good reasons to suspect --
 
1048
          that the spontaneous garbage collection will occur too late
 
1049
          or not at all. Improper use may seriously degrade system
 
1050
          performance.</p>
 
1051
        <p>Compatibility note: In versions of OTP prior to R7,
 
1052
          the garbage collection took place at the next context switch,
 
1053
          not immediately. To force a context switch after a call to
 
1054
          <c>erlang:garbage_collect()</c>, it was sufficient to make
 
1055
          any function call.</p>
 
1056
      </desc>
 
1057
    </func>
 
1058
    <func>
 
1059
      <name>garbage_collect(Pid) -> bool()</name>
 
1060
      <fsummary>Force an immediate garbage collection of a process</fsummary>
 
1061
      <type>
 
1062
        <v>Pid = pid()</v>
 
1063
      </type>
 
1064
      <desc>
 
1065
        <p>Works like <c>erlang:garbage_collect()</c> but on any
 
1066
          process. The same caveats apply. Returns <c>false</c> if
 
1067
          <c>Pid</c> refers to a dead process; <c>true</c> otherwise.</p>
 
1068
      </desc>
 
1069
    </func>
 
1070
    <func>
 
1071
      <name>get() -> [{Key, Val}]</name>
 
1072
      <fsummary>Return the process dictionary</fsummary>
 
1073
      <type>
 
1074
        <v>Key = Val = term()</v>
 
1075
      </type>
 
1076
      <desc>
 
1077
        <p>Returns the process dictionary as a list of
 
1078
          <c>{Key, Val}</c> tuples.</p>
 
1079
        <pre>
 
1080
> <input>put(key1, merry),</input>
 
1081
<input>put(key2, lambs),</input>
 
1082
<input>put(key3, {are, playing}),</input>
 
1083
<input>get().</input>
 
1084
[{key1,merry},{key2,lambs},{key3,{are,playing}}]</pre>
 
1085
      </desc>
 
1086
    </func>
 
1087
    <func>
 
1088
      <name>get(Key) -> Val | undefined</name>
 
1089
      <fsummary>Return a value from the process dictionary</fsummary>
 
1090
      <type>
 
1091
        <v>Key = Val = term()</v>
 
1092
      </type>
 
1093
      <desc>
 
1094
        <p>Returns the value <c>Val</c>associated with <c>Key</c> in
 
1095
          the process dictionary, or <c>undefined</c> if <c>Key</c>
 
1096
          does not exist.</p>
 
1097
        <pre>
 
1098
> <input>put(key1, merry),</input>
 
1099
<input>put(key2, lambs),</input>
 
1100
<input>put({any, [valid, term]}, {are, playing}),</input>
 
1101
<input>get({any, [valid, term]}).</input>
 
1102
{are,playing}</pre>
 
1103
      </desc>
 
1104
    </func>
 
1105
    <func>
 
1106
      <name>erlang:get_cookie() -> Cookie | nocookie</name>
 
1107
      <fsummary>Get the magic cookie of the local node</fsummary>
 
1108
      <type>
 
1109
        <v>Cookie = atom()</v>
 
1110
      </type>
 
1111
      <desc>
 
1112
        <p>Returns the magic cookie of the local node, if the node is
 
1113
          alive; otherwise the atom <c>nocookie</c>.</p>
 
1114
      </desc>
 
1115
    </func>
 
1116
    <func>
 
1117
      <name>get_keys(Val) -> [Key]</name>
 
1118
      <fsummary>Return a list of keys from the process dictionary</fsummary>
 
1119
      <type>
 
1120
        <v>Val = Key = term()</v>
 
1121
      </type>
 
1122
      <desc>
 
1123
        <p>Returns a list of keys which are associated with the value
 
1124
          <c>Val</c> in the process dictionary.</p>
 
1125
        <pre>
 
1126
> <input>put(mary, {1, 2}),</input>
 
1127
<input>put(had, {1, 2}),</input>
 
1128
<input>put(a, {1, 2}),</input>
 
1129
<input>put(little, {1, 2}),</input>
 
1130
<input>put(dog, {1, 3}),</input>
 
1131
<input>put(lamb, {1, 2}),</input>
 
1132
<input>get_keys({1, 2}).</input>
 
1133
[mary,had,a,little,lamb]</pre>
 
1134
      </desc>
 
1135
    </func>
 
1136
    <func>
 
1137
      <name>erlang:get_stacktrace() -> [{Module, Function, Arity | Args}]</name>
 
1138
      <fsummary>Get the call stack back-trace of the last exception</fsummary>
 
1139
      <type>
 
1140
        <v>Module = Function = atom()</v>
 
1141
        <v>Arity = int()</v>
 
1142
        <v>Args = [term()]</v>
 
1143
      </type>
 
1144
      <desc>
 
1145
        <p>Get the call stack back-trace (<em>stacktrace</em>) of the last
 
1146
          exception in the calling process as a list of 
 
1147
          <c>{Module,Function,Arity}</c> tuples.
 
1148
          The <c>Arity</c> field in the first tuple may be the argument
 
1149
          list of that function call instead of an arity integer,
 
1150
          depending on the exception.</p>
 
1151
        <p>If there has not been any exceptions in a process, the
 
1152
          stacktrace is []. After a code change for the process,
 
1153
          the stacktrace may also be reset to [].</p>
 
1154
        <p>The stacktrace is the same data as the <c>catch</c> operator
 
1155
          returns, for example:</p>
 
1156
        <p><c>{'EXIT',{badarg,Stacktrace}} = catch abs(x)</c></p>
 
1157
        <p>See also
 
1158
          <seealso marker="#erlang:error/1">erlang:error/1</seealso> and
 
1159
          <seealso marker="#erlang:error/2">erlang:error/2</seealso>.</p>
 
1160
      </desc>
 
1161
    </func>
 
1162
    <func>
 
1163
      <name>group_leader() -> GroupLeader</name>
 
1164
      <fsummary>Get the group leader for the calling process</fsummary>
 
1165
      <type>
 
1166
        <v>GroupLeader = pid()</v>
 
1167
      </type>
 
1168
      <desc>
 
1169
        <p>Returns the pid of the group leader for the process which
 
1170
          evaluates the function.</p>
 
1171
        <p>Every process is a member of some process group and all
 
1172
          groups have a <em>group leader</em>. All IO from the group
 
1173
          is channeled to the group leader. When a new process is
 
1174
          spawned, it gets the same group leader as the spawning
 
1175
          process. Initially, at system start-up, <c>init</c> is both
 
1176
          its own group leader and the group leader of all processes.</p>
 
1177
      </desc>
 
1178
    </func>
 
1179
    <func>
 
1180
      <name>group_leader(GroupLeader, Pid) -> true</name>
 
1181
      <fsummary>Set the group leader for a process</fsummary>
 
1182
      <type>
 
1183
        <v>GroupLeader = Pid = pid()</v>
 
1184
      </type>
 
1185
      <desc>
 
1186
        <p>Sets the group leader of <c>Pid</c> to <c>GroupLeader</c>.
 
1187
          Typically, this is used when a processes started from a
 
1188
          certain shell should have another group leader than
 
1189
          <c>init</c>.</p>
 
1190
        <p>See also
 
1191
          <seealso marker="#group_leader/0">group_leader/0</seealso>.</p>
 
1192
      </desc>
 
1193
    </func>
 
1194
    <func>
 
1195
      <name>halt()</name>
 
1196
      <fsummary>Halt the Erlang runtime system and indicate normal exit to the calling environment</fsummary>
 
1197
      <desc>
 
1198
        <p>Halts the Erlang runtime system and indicates normal exit to
 
1199
          the calling environment. Has no return value.</p>
 
1200
        <pre>
 
1201
> <input>halt().</input>
 
1202
os_prompt%</pre>
 
1203
      </desc>
 
1204
    </func>
 
1205
    <func>
 
1206
      <name>halt(Status)</name>
 
1207
      <fsummary>Halt the Erlang runtime system</fsummary>
 
1208
      <type>
 
1209
        <v>Status = int()>=0 | string()</v>
 
1210
      </type>
 
1211
      <desc>
 
1212
        <p><c>Status</c> must be a non-negative integer, or a string.
 
1213
          Halts the Erlang runtime system. Has no return value.
 
1214
          If <c>Status</c> is an integer, it is returned as an exit
 
1215
          status of Erlang to the calling environment.
 
1216
          If <c>Status</c> is a string, produces an Erlang crash dump
 
1217
          with <c>String</c> as slogan, and then exits with a non-zero
 
1218
          status code.</p>
 
1219
        <p>Note that on many platforms, only the status codes 0-255 are
 
1220
          supported by the operating system.</p>
 
1221
      </desc>
 
1222
    </func>
 
1223
    <func>
 
1224
      <name>erlang:hash(Term, Range) -> Hash</name>
 
1225
      <fsummary>Hash function (deprecated)</fsummary>
 
1226
      <desc>
 
1227
        <p>Returns a hash value for <c>Term</c> within the range
 
1228
          <c>1..Range</c>. The allowed range is 1..2^27-1.</p>
 
1229
        <warning>
 
1230
          <p>This BIF is deprecated as the hash value may differ on
 
1231
            different architectures. Also the hash values for integer
 
1232
            terms larger than 2^27 as well as large binaries are very
 
1233
            poor. The BIF is retained for backward compatibility
 
1234
            reasons (it may have been used to hash records into a file),
 
1235
            but all new code should use one of the BIFs
 
1236
            <c>erlang:phash/2</c> or <c>erlang:phash2/1,2</c> instead.</p>
 
1237
        </warning>
 
1238
      </desc>
 
1239
    </func>
 
1240
    <func>
 
1241
      <name>hd(List) -> term()</name>
 
1242
      <fsummary>Head of a list</fsummary>
 
1243
      <type>
 
1244
        <v>List = [term()]</v>
 
1245
      </type>
 
1246
      <desc>
 
1247
        <p>Returns the head of <c>List</c>, that is, the first element.</p>
 
1248
        <pre>
 
1249
> <input>hd([1,2,3,4,5]).</input>
 
1250
1</pre>
 
1251
        <p>Allowed in guard tests.</p>
 
1252
        <p>Failure: <c>badarg</c> if <c>List</c> is the empty list [].</p>
 
1253
      </desc>
 
1254
    </func>
 
1255
    <func>
 
1256
      <name>erlang:hibernate(Module, Function, Args)</name>
 
1257
      <fsummary>Hibernate a process until a message is sent to it</fsummary>
 
1258
      <type>
 
1259
        <v>Module = Function = atom()</v>
 
1260
        <v>Args = [term()]</v>
 
1261
      </type>
 
1262
      <desc>
 
1263
        <p>Puts the calling process into a wait state where its memory
 
1264
          allocation has been reduced as much as possible, which is
 
1265
          useful if the process does not expect to receive any messages
 
1266
          in the near future.</p>
 
1267
        <p>The process will be awaken when a message is sent to it, and
 
1268
          control will resume in <c>Module:Function</c> with
 
1269
          the arguments given by <c>Args</c> with the call stack
 
1270
          emptied, meaning that the process will terminate when that
 
1271
          function returns. Thus <c>erlang:hibernate/3</c> will never
 
1272
          return to its caller.</p>
 
1273
        <p>If the process has any message in its message queue,
 
1274
          the process will be awaken immediately in the same way as
 
1275
          described above.</p>
 
1276
        <p>In more technical terms, what <c>erlang:hibernate/3</c> does
 
1277
          is the following. It discards the call stack for the process.
 
1278
          Then it garbage collects the process. After the garbage
 
1279
          collection, all live data is in one continuous heap. The heap
 
1280
          is then shrunken to the exact same size as the live data
 
1281
          which it holds (even if that size is less than the minimum
 
1282
          heap size for the process).</p>
 
1283
        <p>If the size of the live data in the process is less than
 
1284
          the minimum heap size, the first garbage collection occurring
 
1285
          after the process has been awaken will ensure that the heap
 
1286
          size is changed to a size not smaller than the minimum heap
 
1287
          size.</p>
 
1288
        <p>Note that emptying the call stack means that any surrounding
 
1289
          <c>catch</c> is removed and has to be re-inserted after
 
1290
          hibernation. One effect of this is that processes started
 
1291
          using <c>proc_lib</c> (also indirectly, such as
 
1292
          <c>gen_server</c> processes), should use
 
1293
          <seealso marker="stdlib:proc_lib#hibernate/3">proc_lib:hibernate/3</seealso>
 
1294
          instead to ensure that the exception handler continues to work
 
1295
          when the process wakes up.</p>
 
1296
      </desc>
 
1297
    </func>
 
1298
    <func>
 
1299
      <name>integer_to_list(Integer) -> string()</name>
 
1300
      <fsummary>Text representation of an integer</fsummary>
 
1301
      <type>
 
1302
        <v>Integer = int()</v>
 
1303
      </type>
 
1304
      <desc>
 
1305
        <p>Returns a string which corresponds to the text
 
1306
          representation of <c>Integer</c>.</p>
 
1307
        <pre>
 
1308
> <input>integer_to_list(77).</input>
 
1309
"77"</pre>
 
1310
      </desc>
 
1311
    </func>
 
1312
    <func>
 
1313
      <name>erlang:integer_to_list(Integer, Base) -> string()</name>
 
1314
      <fsummary>Text representation of an integer</fsummary>
 
1315
      <type>
 
1316
        <v>Integer = int()</v>
 
1317
        <v>Base = 2..36</v>
 
1318
      </type>
 
1319
      <desc>
 
1320
        <p>Returns a string which corresponds to the text
 
1321
          representation of <c>Integer</c> in base <c>Base</c>.</p>
 
1322
        <pre>
 
1323
> <input>erlang:integer_to_list(1023, 16).</input>
 
1324
"3FF"</pre>
 
1325
      </desc>
 
1326
    </func>
 
1327
    <func>
 
1328
      <name>iolist_to_binary(IoListOrBinary) -> binary()</name>
 
1329
      <fsummary>Convert an iolist to a binary</fsummary>
 
1330
      <type>
 
1331
        <v>IoListOrBinary = iolist() | binary()</v>
 
1332
      </type>
 
1333
      <desc>
 
1334
        <p>Returns a binary which is made from the integers and
 
1335
          binaries in <c>IoListOrBinary</c>.</p>
 
1336
        <pre>
 
1337
> <input>Bin1 = &lt;&lt;1,2,3&gt;&gt;.</input>
 
1338
&lt;&lt;1,2,3&gt;&gt;
 
1339
> <input>Bin2 = &lt;&lt;4,5&gt;&gt;.</input>
 
1340
&lt;&lt;4,5&gt;&gt;
 
1341
> <input>Bin3 = &lt;&lt;6&gt;&gt;.</input>
 
1342
&lt;&lt;6&gt;&gt;
 
1343
> <input>iolist_to_binary([Bin1,1,[2,3,Bin2],4|Bin3]).</input>
 
1344
&lt;&lt;1,2,3,1,2,3,4,5,4,6&gt;&gt;</pre>
 
1345
      </desc>
 
1346
    </func>
 
1347
    <func>
 
1348
      <name>iolist_size(Item) -> int()</name>
 
1349
      <fsummary>Size of an iolist</fsummary>
 
1350
      <type>
 
1351
        <v>Item = iolist() | binary()</v>
 
1352
      </type>
 
1353
      <desc>
 
1354
        <p>Returns an integer which is the size in bytes
 
1355
          of the binary that would be the result of 
 
1356
          <c>iolist_to_binary(Item)</c>.</p>
 
1357
        <pre>
 
1358
> <input>iolist_size([1,2|&lt;&lt;3,4>>]).</input>
 
1359
4</pre>
 
1360
      </desc>
 
1361
    </func>
 
1362
    <func>
 
1363
      <name>is_alive() -> bool()</name>
 
1364
      <fsummary>Check whether the local node is alive</fsummary>
 
1365
      <desc>
 
1366
        <p>Returns <c>true</c> if the local node is alive; that is, if
 
1367
          the node can be part of a distributed system. Otherwise, it
 
1368
          returns <c>false</c>.</p>
 
1369
      </desc>
 
1370
    </func>
 
1371
    <func>
 
1372
      <name>is_atom(Term) -> bool()</name>
 
1373
      <fsummary>Check whether a term is an atom</fsummary>
 
1374
      <type>
 
1375
        <v>Term = term()</v>
 
1376
      </type>
 
1377
      <desc>
 
1378
        <p>Returns <c>true</c> if <c>Term</c> is an atom;
 
1379
          otherwise returns <c>false</c>.</p>
 
1380
        <p>Allowed in guard tests.</p>
 
1381
      </desc>
 
1382
    </func>
 
1383
    <func>
 
1384
      <name>is_binary(Term) -> bool()</name>
 
1385
      <fsummary>Check whether a term is a binary</fsummary>
 
1386
      <type>
 
1387
        <v>Term = term()</v>
 
1388
      </type>
 
1389
      <desc>
 
1390
        <p>Returns <c>true</c> if <c>Term</c> is a binary;
 
1391
          otherwise returns <c>false</c>.</p>
 
1392
 
 
1393
        <p>A binary always contains a complete number of bytes.</p>
 
1394
 
 
1395
        <p>Allowed in guard tests.</p>
 
1396
      </desc>
 
1397
    </func>
 
1398
    <func>
 
1399
      <name>is_bitstring(Term) -> bool()</name>
 
1400
      <fsummary>Check whether a term is a bitstring</fsummary>
 
1401
      <type>
 
1402
        <v>Term = term()</v>
 
1403
      </type>
 
1404
      <desc>
 
1405
        <p>Returns <c>true</c> if <c>Term</c> is a bitstring (including a binary);
 
1406
          otherwise returns <c>false</c>.</p>
 
1407
 
 
1408
        <p>Allowed in guard tests.</p>
 
1409
      </desc>
 
1410
    </func>
 
1411
    <func>
 
1412
      <name>is_boolean(Term) -> bool()</name>
 
1413
      <fsummary>Check whether a term is a boolean</fsummary>
 
1414
      <type>
 
1415
        <v>Term = term()</v>
 
1416
      </type>
 
1417
      <desc>
 
1418
        <p>Returns <c>true</c> if <c>Term</c> is
 
1419
          either the atom <c>true</c> or the atom <c>false</c>
 
1420
          (i.e. a boolean); otherwise returns <c>false</c>.</p>
 
1421
        <p>Allowed in guard tests.</p>
 
1422
      </desc>
 
1423
    </func>
 
1424
    <func>
 
1425
      <name>erlang:is_builtin(Module, Function, Arity) -> bool()</name>
 
1426
      <fsummary>Check if a function is a BIF implemented in C</fsummary>
 
1427
      <type>
 
1428
        <v>Module = Function = atom()</v>
 
1429
        <v>Arity = int()</v>
 
1430
      </type>
 
1431
      <desc>
 
1432
        <p>Returns <c>true</c> if <c>Module:Function/Arity</c> is
 
1433
          a BIF implemented in C; otherwise returns <c>false</c>.
 
1434
          This BIF is useful for builders of cross reference tools.</p>
 
1435
      </desc>
 
1436
    </func>
 
1437
    <func>
 
1438
      <name>is_float(Term) -> bool()</name>
 
1439
      <fsummary>Check whether a term is a float</fsummary>
 
1440
      <type>
 
1441
        <v>Term = term()</v>
 
1442
      </type>
 
1443
      <desc>
 
1444
        <p>Returns <c>true</c> if <c>Term</c> is a floating point
 
1445
          number; otherwise returns <c>false</c>.</p>
 
1446
        <p>Allowed in guard tests.</p>
 
1447
      </desc>
 
1448
    </func>
 
1449
    <func>
 
1450
      <name>is_function(Term) -> bool()</name>
 
1451
      <fsummary>Check whether a term is a fun</fsummary>
 
1452
      <type>
 
1453
        <v>Term = term()</v>
 
1454
      </type>
 
1455
      <desc>
 
1456
        <p>Returns <c>true</c> if <c>Term</c> is a fun; otherwise
 
1457
          returns <c>false</c>.</p>
 
1458
        <p>Allowed in guard tests.</p>
 
1459
      </desc>
 
1460
    </func>
 
1461
    <func>
 
1462
      <name>is_function(Term, Arity) -> bool()</name>
 
1463
      <fsummary>Check whether a term is a fun with a given arity</fsummary>
 
1464
      <type>
 
1465
        <v>Term = term()</v>
 
1466
        <v>Arity = int()</v>
 
1467
      </type>
 
1468
      <desc>
 
1469
        <p>Returns <c>true</c> if <c>Term</c> is a fun that can be
 
1470
          applied with <c>Arity</c> number of arguments; otherwise
 
1471
          returns <c>false</c>.</p>
 
1472
        <p>Allowed in guard tests.</p>
 
1473
        <warning>
 
1474
          <p>Currently, <c>is_function/2</c> will also return
 
1475
            <c>true</c> if the first argument is a tuple fun (a tuple
 
1476
            containing two atoms). In a future release, tuple funs will
 
1477
            no longer be supported and <c>is_function/2</c> will return
 
1478
            <c>false</c> if given a tuple fun.</p>
 
1479
        </warning>
 
1480
      </desc>
 
1481
    </func>
 
1482
    <func>
 
1483
      <name>is_integer(Term) -> bool()</name>
 
1484
      <fsummary>Check whether a term is an integer</fsummary>
 
1485
      <type>
 
1486
        <v>Term = term()</v>
 
1487
      </type>
 
1488
      <desc>
 
1489
        <p>Returns <c>true</c> if <c>Term</c> is an integer;
 
1490
          otherwise returns <c>false</c>.</p>
 
1491
        <p>Allowed in guard tests.</p>
 
1492
      </desc>
 
1493
    </func>
 
1494
    <func>
 
1495
      <name>is_list(Term) -> bool()</name>
 
1496
      <fsummary>Check whether a term is a list</fsummary>
 
1497
      <type>
 
1498
        <v>Term = term()</v>
 
1499
      </type>
 
1500
      <desc>
 
1501
        <p>Returns <c>true</c> if <c>Term</c> is a list with
 
1502
          zero or more elements; otherwise returns <c>false</c>.</p>
 
1503
        <p>Allowed in guard tests.</p>
 
1504
      </desc>
 
1505
    </func>
 
1506
    <func>
 
1507
      <name>is_number(Term) -> bool()</name>
 
1508
      <fsummary>Check whether a term is a number</fsummary>
 
1509
      <type>
 
1510
        <v>Term = term()</v>
 
1511
      </type>
 
1512
      <desc>
 
1513
        <p>Returns <c>true</c> if <c>Term</c> is either an integer or a
 
1514
          floating point number; otherwise returns <c>false</c>.</p>
 
1515
        <p>Allowed in guard tests.</p>
 
1516
      </desc>
 
1517
    </func>
 
1518
    <func>
 
1519
      <name>is_pid(Term) -> bool()</name>
 
1520
      <fsummary>Check whether a term is a pid</fsummary>
 
1521
      <type>
 
1522
        <v>Term = term()</v>
 
1523
      </type>
 
1524
      <desc>
 
1525
        <p>Returns <c>true</c> if <c>Term</c> is a pid (process
 
1526
          identifier); otherwise returns <c>false</c>.</p>
 
1527
        <p>Allowed in guard tests.</p>
 
1528
      </desc>
 
1529
    </func>
 
1530
    <func>
 
1531
      <name>is_port(Term) -> bool()</name>
 
1532
      <fsummary>Check whether a term is a port</fsummary>
 
1533
      <type>
 
1534
        <v>Term = term()</v>
 
1535
      </type>
 
1536
      <desc>
 
1537
        <p>Returns <c>true</c> if <c>Term</c> is a port identifier;
 
1538
          otherwise returns <c>false</c>.</p>
 
1539
        <p>Allowed in guard tests.</p>
 
1540
      </desc>
 
1541
    </func>
 
1542
    <func>
 
1543
      <name>is_process_alive(Pid) -> bool()</name>
 
1544
      <fsummary>Check whether a process is alive</fsummary>
 
1545
      <type>
 
1546
        <v>Pid = pid()</v>
 
1547
      </type>
 
1548
      <desc>
 
1549
        <p>
 
1550
          <c>Pid</c> must refer to a process at the local node.
 
1551
          Returns <c>true</c> if the process exists and is alive, that
 
1552
          is, is not exiting and has not exited. Otherwise, returns
 
1553
          <c>false</c>.
 
1554
        </p>
 
1555
      </desc>
 
1556
    </func>
 
1557
    <func>
 
1558
      <name>is_record(Term, RecordTag) -> bool()</name>
 
1559
      <fsummary>Check whether a term appears to be a record</fsummary>
 
1560
      <type>
 
1561
        <v>Term = term()</v>
 
1562
        <v>RecordTag = atom()</v>
 
1563
      </type>
 
1564
      <desc>
 
1565
        <p>Returns <c>true</c> if <c>Term</c> is a tuple and its first
 
1566
          element is <c>RecordTag</c>. Otherwise, returns <c>false</c>.</p>
 
1567
        <note>
 
1568
          <p>Normally the compiler treats calls to <c>is_record/2</c>
 
1569
            specially. It emits code to verify that <c>Term</c> is a
 
1570
            tuple, that its first element is <c>RecordTag</c>, and that
 
1571
            the size is correct. However, if the <c>RecordTag</c> is
 
1572
            not a literal atom, the <c>is_record/2</c> BIF will be
 
1573
            called instead and the size of the tuple will not be
 
1574
            verified.</p>
 
1575
        </note>
 
1576
        <p>Allowed in guard tests, if <c>RecordTag</c> is a literal
 
1577
          atom.</p>
 
1578
      </desc>
 
1579
    </func>
 
1580
    <func>
 
1581
      <name>is_record(Term, RecordTag, Size) -> bool()</name>
 
1582
      <fsummary>Check whether a term appears to be a record</fsummary>
 
1583
      <type>
 
1584
        <v>Term = term()</v>
 
1585
        <v>RecordTag = atom()</v>
 
1586
        <v>Size = int()</v>
 
1587
      </type>
 
1588
      <desc>
 
1589
        <p><c>RecordTag</c> must be an atom. Returns <c>true</c> if
 
1590
          <c>Term</c> is a tuple, its first element is <c>RecordTag</c>,
 
1591
          and its size is <c>Size</c>. Otherwise, returns <c>false</c>.</p>
 
1592
        <p>Allowed in guard tests, provided that <c>RecordTag</c> is
 
1593
          a literal atom and <c>Size</c> is a literal integer.</p>
 
1594
        <note>
 
1595
          <p>This BIF is documented for completeness. In most cases
 
1596
            <c>is_record/2</c> should be used.</p>
 
1597
        </note>
 
1598
      </desc>
 
1599
    </func>
 
1600
    <func>
 
1601
      <name>is_reference(Term) -> bool()</name>
 
1602
      <fsummary>Check whether a term is a reference</fsummary>
 
1603
      <type>
 
1604
        <v>Term = term()</v>
 
1605
      </type>
 
1606
      <desc>
 
1607
        <p>Returns <c>true</c> if <c>Term</c> is a reference;
 
1608
          otherwise returns <c>false</c>.</p>
 
1609
        <p>Allowed in guard tests.</p>
 
1610
      </desc>
 
1611
    </func>
 
1612
    <func>
 
1613
      <name>is_tuple(Term) -> bool()</name>
 
1614
      <fsummary>Check whether a term is a tuple</fsummary>
 
1615
      <type>
 
1616
        <v>Term = term()</v>
 
1617
      </type>
 
1618
      <desc>
 
1619
        <p>Returns <c>true</c> if <c>Term</c> is a tuple;
 
1620
          otherwise returns <c>false</c>.</p>
 
1621
        <p>Allowed in guard tests.</p>
 
1622
      </desc>
 
1623
    </func>
 
1624
    <func>
 
1625
      <name>length(List) -> int()</name>
 
1626
      <fsummary>Length of a list</fsummary>
 
1627
      <type>
 
1628
        <v>List = [term()]</v>
 
1629
      </type>
 
1630
      <desc>
 
1631
        <p>Returns the length of <c>List</c>.</p>
 
1632
        <pre>
 
1633
> <input>length([1,2,3,4,5,6,7,8,9]).</input>
 
1634
9</pre>
 
1635
        <p>Allowed in guard tests.</p>
 
1636
      </desc>
 
1637
    </func>
 
1638
    <func>
 
1639
      <name>link(Pid) -> true</name>
 
1640
      <fsummary>Create a link to another process (or port)</fsummary>
 
1641
      <type>
 
1642
        <v>Pid = pid() | port()</v>
 
1643
      </type>
 
1644
      <desc>
 
1645
        <p>Creates a link between the calling process and another
 
1646
          process (or port) <c>Pid</c>, if there is not such a link
 
1647
          already. If a process attempts to create a link to itself,
 
1648
          nothing is done. Returns <c>true</c>.</p>
 
1649
        <p>If <c>Pid</c> does not exist, the behavior of the BIF depends
 
1650
          on if the calling process is trapping exits or not (see
 
1651
          <seealso marker="#process_flag/2">process_flag/2</seealso>):</p>
 
1652
        <list type="bulleted">
 
1653
          <item>If the calling process is not trapping exits, and
 
1654
           checking <c>Pid</c> is cheap -- that is, if <c>Pid</c> is
 
1655
           local -- <c>link/1</c> fails with reason <c>noproc</c>.</item>
 
1656
          <item>Otherwise, if the calling process is trapping exits,
 
1657
           and/or <c>Pid</c> is remote, <c>link/1</c> returns
 
1658
          <c>true</c>, but an exit signal with reason <c>noproc</c>
 
1659
           is sent to the calling process.</item>
 
1660
        </list>
 
1661
      </desc>
 
1662
    </func>
 
1663
    <func>
 
1664
      <name>list_to_atom(String) -> atom()</name>
 
1665
      <fsummary>Convert from text representation to an atom</fsummary>
 
1666
      <type>
 
1667
        <v>String = string()</v>
 
1668
      </type>
 
1669
      <desc>
 
1670
        <p>Returns the atom whose text representation is <c>String</c>.</p>
 
1671
        <pre>
 
1672
> <input>list_to_atom("Erlang").</input>
 
1673
'Erlang'</pre>
 
1674
      </desc>
 
1675
    </func>
 
1676
    <func>
 
1677
      <name>list_to_binary(IoList) -> binary()</name>
 
1678
      <fsummary>Convert a list to a binary</fsummary>
 
1679
      <type>
 
1680
        <v>IoList = iolist()</v>
 
1681
      </type>
 
1682
      <desc>
 
1683
        <p>Returns a binary which is made from the integers and
 
1684
          binaries in <c>IoList</c>.</p>
 
1685
        <pre>
 
1686
> <input>Bin1 = &lt;&lt;1,2,3&gt;&gt;.</input>
 
1687
&lt;&lt;1,2,3&gt;&gt;
 
1688
> <input>Bin2 = &lt;&lt;4,5&gt;&gt;.</input>
 
1689
&lt;&lt;4,5&gt;&gt;
 
1690
> <input>Bin3 = &lt;&lt;6&gt;&gt;.</input>
 
1691
&lt;&lt;6&gt;&gt;
 
1692
> <input>list_to_binary([Bin1,1,[2,3,Bin2],4|Bin3]).</input>
 
1693
&lt;&lt;1,2,3,1,2,3,4,5,4,6&gt;&gt;</pre>
 
1694
      </desc>
 
1695
    </func>
 
1696
    <func>
 
1697
      <name>list_to_bitstring(BitstringList) -> bitstring()</name>
 
1698
      <fsummary>Convert a list to a bitstring</fsummary>
 
1699
      <type>
 
1700
        <v>BitstringList = [BitstringList | bitstring() | char()]</v>
 
1701
      </type>
 
1702
      <desc>
 
1703
        <p>Returns a bitstring which is made from the integers and
 
1704
          bitstrings in <c>BitstringList</c>. (The last tail in <c>BitstringList</c>
 
1705
          is allowed to be a bitstring.)</p>
 
1706
        <pre>
 
1707
> <input>Bin1 = &lt;&lt;1,2,3&gt;&gt;.</input>
 
1708
&lt;&lt;1,2,3&gt;&gt;
 
1709
> <input>Bin2 = &lt;&lt;4,5&gt;&gt;.</input>
 
1710
&lt;&lt;4,5&gt;&gt;
 
1711
> <input>Bin3 = &lt;&lt;6,7:4,&gt;&gt;.</input>
 
1712
&lt;&lt;6&gt;&gt;
 
1713
> <input>list_to_binary([Bin1,1,[2,3,Bin2],4|Bin3]).</input>
 
1714
&lt;&lt;1,2,3,1,2,3,4,5,4,6,7:46&gt;&gt;</pre>
 
1715
      </desc>
 
1716
    </func>
 
1717
    <func>
 
1718
      <name>list_to_existing_atom(String) -> atom()</name>
 
1719
      <fsummary>Convert from text representation to an atom</fsummary>
 
1720
      <type>
 
1721
        <v>String = string()</v>
 
1722
      </type>
 
1723
      <desc>
 
1724
        <p>Returns the atom whose text representation is <c>String</c>,
 
1725
          but only if there already exists such atom.</p>
 
1726
        <p>Failure: <c>badarg</c> if there does not already exist an atom
 
1727
          whose text representation is <c>String</c>.</p>
 
1728
      </desc>
 
1729
    </func>
 
1730
    <func>
 
1731
      <name>list_to_float(String) -> float()</name>
 
1732
      <fsummary>Convert from text representation to a float</fsummary>
 
1733
      <type>
 
1734
        <v>String = string()</v>
 
1735
      </type>
 
1736
      <desc>
 
1737
        <p>Returns the float whose text representation is <c>String</c>.</p>
 
1738
        <pre>
 
1739
> <input>list_to_float("2.2017764e+0").</input>
 
1740
2.2017764</pre>
 
1741
        <p>Failure: <c>badarg</c> if <c>String</c> contains a bad
 
1742
          representation of a float.</p>
 
1743
      </desc>
 
1744
    </func>
 
1745
    <func>
 
1746
      <name>list_to_integer(String) -> int()</name>
 
1747
      <fsummary>Convert from text representation to an integer</fsummary>
 
1748
      <type>
 
1749
        <v>String = string()</v>
 
1750
      </type>
 
1751
      <desc>
 
1752
        <p>Returns an integer whose text representation is
 
1753
          <c>String</c>.</p>
 
1754
        <pre>
 
1755
> <input>list_to_integer("123").</input>
 
1756
123</pre>
 
1757
        <p>Failure: <c>badarg</c> if <c>String</c> contains a bad
 
1758
          representation of an integer.</p>
 
1759
      </desc>
 
1760
    </func>
 
1761
    <func>
 
1762
      <name>erlang:list_to_integer(String, Base) -> int()</name>
 
1763
      <fsummary>Convert from text representation to an integer</fsummary>
 
1764
      <type>
 
1765
        <v>String = string()</v>
 
1766
        <v>Base = 2..36</v>
 
1767
      </type>
 
1768
      <desc>
 
1769
        <p>Returns an integer whose text representation in base
 
1770
          <c>Base</c> is <c>String</c>.</p>
 
1771
        <pre>
 
1772
> <input>erlang:list_to_integer("3FF", 16).</input>
 
1773
1023</pre>
 
1774
        <p>Failure: <c>badarg</c> if <c>String</c> contains a bad
 
1775
          representation of an integer.</p>
 
1776
      </desc>
 
1777
    </func>
 
1778
    <func>
 
1779
      <name>list_to_pid(String) -> pid()</name>
 
1780
      <fsummary>Convert from text representation to a pid</fsummary>
 
1781
      <type>
 
1782
        <v>String = string()</v>
 
1783
      </type>
 
1784
      <desc>
 
1785
        <p>Returns a pid whose text representation is <c>String</c>.</p>
 
1786
        <warning>
 
1787
          <p>This BIF is intended for debugging and for use in
 
1788
            the Erlang operating system. It should not be used in
 
1789
            application programs.</p>
 
1790
        </warning>
 
1791
        <pre>
 
1792
> <input>list_to_pid("&lt;0.4.1>").</input>
 
1793
&lt;0.4.1></pre>
 
1794
        <p>Failure: <c>badarg</c> if <c>String</c> contains a bad
 
1795
          representation of a pid.</p>
 
1796
      </desc>
 
1797
    </func>
 
1798
    <func>
 
1799
      <name>list_to_tuple(List) -> tuple()</name>
 
1800
      <fsummary>Convert a list to a tuple</fsummary>
 
1801
      <type>
 
1802
        <v>List = [term()]</v>
 
1803
      </type>
 
1804
      <desc>
 
1805
        <p>Returns a tuple which corresponds to <c>List</c>. <c>List</c>
 
1806
          can contain any Erlang terms.</p>
 
1807
        <pre>
 
1808
> <input>list_to_tuple([share, ['Ericsson_B', 163]]).</input>
 
1809
{share, ['Ericsson_B', 163]}</pre>
 
1810
      </desc>
 
1811
    </func>
 
1812
    <func>
 
1813
      <name>load_module(Module, Binary) -> {module, Module} | {error, Reason}</name>
 
1814
      <fsummary>Load object code for a module</fsummary>
 
1815
      <type>
 
1816
        <v>Module = atom()</v>
 
1817
        <v>Binary = binary()</v>
 
1818
        <v>Reason = badfile | not_purged | badfile</v>
 
1819
      </type>
 
1820
      <desc>
 
1821
        <p>If <c>Binary</c> contains the object code for the module
 
1822
          <c>Module</c>, this BIF loads that object code. Also, if
 
1823
          the code for the module <c>Module</c> already exists, all
 
1824
          export references are replaced so they point to the newly
 
1825
          loaded code. The previously loaded code is kept in the system
 
1826
          as old code, as there may still be processes which are
 
1827
          executing that code. It returns either
 
1828
          <c>{module, Module}</c>, or <c>{error, Reason}</c> if loading
 
1829
          fails. <c>Reason</c> is one of the following:</p>
 
1830
        <taglist>
 
1831
          <tag><c>badfile</c></tag>
 
1832
          <item>
 
1833
            <p>The object code in <c>Binary</c> has an incorrect format.</p>
 
1834
          </item>
 
1835
          <tag><c>not_purged</c></tag>
 
1836
          <item>
 
1837
            <p><c>Binary</c> contains a module which cannot be loaded
 
1838
              because old code for this module already exists.</p>
 
1839
          </item>
 
1840
          <tag><c>badfile</c></tag>
 
1841
          <item>
 
1842
            <p>The object code contains code for another module than
 
1843
              <c>Module</c></p>
 
1844
          </item>
 
1845
        </taglist>
 
1846
        <warning>
 
1847
          <p>This BIF is intended for the code server (see
 
1848
            <seealso marker="code">code(3)</seealso>) and should not be
 
1849
            used elsewhere.</p>
 
1850
        </warning>
 
1851
      </desc>
 
1852
    </func>
 
1853
    <func>
 
1854
      <name>erlang:loaded() -> [Module]</name>
 
1855
      <fsummary>List of all loaded modules</fsummary>
 
1856
      <type>
 
1857
        <v>Module = atom()</v>
 
1858
      </type>
 
1859
      <desc>
 
1860
        <p>Returns a list of all loaded Erlang modules (current and/or
 
1861
          old code), including preloaded modules.</p>
 
1862
        <p>See also <seealso marker="code">code(3)</seealso>.</p>
 
1863
      </desc>
 
1864
    </func>
 
1865
    <func>
 
1866
      <name>erlang:localtime() -> {Date, Time}</name>
 
1867
      <fsummary>Current local date and time</fsummary>
 
1868
      <type>
 
1869
        <v>Date = {Year, Month, Day}</v>
 
1870
        <v>Time = {Hour, Minute, Second}</v>
 
1871
        <v>&nbsp;Year = Month = Day = Hour = Minute = Second = int()</v>
 
1872
      </type>
 
1873
      <desc>
 
1874
        <p>Returns the current local date and time
 
1875
          <c>{{Year, Month, Day}, {Hour, Minute, Second}}</c>.</p>
 
1876
        <p>The time zone and daylight saving time correction depend
 
1877
          on the underlying OS.</p>
 
1878
        <pre>
 
1879
> <input>erlang:localtime().</input>
 
1880
{{1996,11,6},{14,45,17}}</pre>
 
1881
      </desc>
 
1882
    </func>
 
1883
    <func>
 
1884
      <name>erlang:localtime_to_universaltime({Date1, Time1}) -> {Date2, Time2}</name>
 
1885
      <fsummary>Convert from local to Universal Time Coordinated (UTC) date and time</fsummary>
 
1886
      <type>
 
1887
        <v>Date1 = Date2 = {Year, Month, Day}</v>
 
1888
        <v>Time1 = Time2 = {Hour, Minute, Second}</v>
 
1889
        <v>&nbsp;Year = Month = Day = Hour = Minute = Second = int()</v>
 
1890
      </type>
 
1891
      <desc>
 
1892
        <p>Converts local date and time to Universal Time Coordinated
 
1893
          (UTC), if this is supported by the underlying OS. Otherwise,
 
1894
          no conversion is done and <c>{Date1, Time1}</c> is returned.</p>
 
1895
        <pre>
 
1896
> <input>erlang:localtime_to_universaltime({{1996,11,6},{14,45,17}}).</input>
 
1897
{{1996,11,6},{13,45,17}}</pre>
 
1898
        <p>Failure: <c>badarg</c> if <c>Date1</c> or <c>Time1</c> do
 
1899
          not denote a valid date or time.</p>
 
1900
      </desc>
 
1901
    </func>
 
1902
    <func>
 
1903
      <name>erlang:localtime_to_universaltime({Date1, Time1}, IsDst) -> {Date2, Time2}</name>
 
1904
      <fsummary>Convert from local to Universal Time Coordinated (UTC) date and time</fsummary>
 
1905
      <type>
 
1906
        <v>Date1 = Date2 = {Year, Month, Day}</v>
 
1907
        <v>Time1 = Time2 = {Hour, Minute, Second}</v>
 
1908
        <v>&nbsp;Year = Month = Day = Hour = Minute = Second = int()</v>
 
1909
        <v>IsDst = true | false | undefined</v>
 
1910
      </type>
 
1911
      <desc>
 
1912
        <p>Converts local date and time to Universal Time Coordinated
 
1913
          (UTC) just like <c>erlang:localtime_to_universaltime/1</c>,
 
1914
          but the caller decides if daylight saving time is active or
 
1915
          not.</p>
 
1916
        <p>If <c>IsDst == true</c> the <c>{Date1, Time1}</c> is during
 
1917
          daylight saving time, if <c>IsDst == false</c> it is not,
 
1918
          and if <c>IsDst == undefined</c> the underlying OS may
 
1919
          guess, which is the same as calling
 
1920
          <c>erlang:localtime_to_universaltime({Date1, Time1})</c>.</p>
 
1921
        <pre>
 
1922
> <input>erlang:localtime_to_universaltime({{1996,11,6},{14,45,17}}, true).</input>
 
1923
{{1996,11,6},{12,45,17}}
 
1924
> <input>erlang:localtime_to_universaltime({{1996,11,6},{14,45,17}}, false).</input>
 
1925
{{1996,11,6},{13,45,17}}
 
1926
> <input>erlang:localtime_to_universaltime({{1996,11,6},{14,45,17}}, undefined).</input>
 
1927
{{1996,11,6},{13,45,17}}</pre>
 
1928
        <p>Failure: <c>badarg</c> if <c>Date1</c> or <c>Time1</c> do
 
1929
          not denote a valid date or time.</p>
 
1930
      </desc>
 
1931
    </func>
 
1932
    <func>
 
1933
      <name>make_ref() -> ref()</name>
 
1934
      <fsummary>Return an almost unique reference</fsummary>
 
1935
      <desc>
 
1936
        <p>Returns an almost unique reference.</p>
 
1937
        <p>The returned reference will re-occur after approximately 2^82
 
1938
          calls; therefore it is unique enough for practical purposes.</p>
 
1939
        <pre>
 
1940
> <input>make_ref().</input>
 
1941
#Ref&lt;0.0.0.135></pre>
 
1942
      </desc>
 
1943
    </func>
 
1944
    <func>
 
1945
      <name>erlang:make_tuple(Arity, InitialValue) -> tuple()</name>
 
1946
      <fsummary>Create a new tuple of a given arity</fsummary>
 
1947
      <type>
 
1948
        <v>Arity = int()</v>
 
1949
        <v>InitialValue = term()</v>
 
1950
      </type>
 
1951
      <desc>
 
1952
        <p>Returns a new tuple of the given <c>Arity</c>, where all
 
1953
          elements are <c>InitialValue</c>.</p>
 
1954
        <pre>
 
1955
> <input>erlang:make_tuple(4, []).</input>
 
1956
{[],[],[],[]}</pre>
 
1957
      </desc>
 
1958
    </func>
 
1959
    <func>
 
1960
      <name>erlang:md5(Data) -> Digest</name>
 
1961
      <fsummary>Compute an MD5 message digest</fsummary>
 
1962
      <type>
 
1963
        <v>Data = iodata()</v>
 
1964
        <v>Digest = binary()</v>
 
1965
      </type>
 
1966
      <desc>
 
1967
        <p>Computes an <c>MD5</c> message digest from <c>Data</c>, where
 
1968
          the length of the digest is 128 bits (16 bytes). <c>Data</c>
 
1969
          is a binary or a list of small integers and binaries.</p>
 
1970
        <p>See The MD5 Message Digest Algorithm (RFC 1321) for more
 
1971
          information about MD5.</p>
 
1972
        <warning><p>The MD5 Message Digest Algorithm is <em>not</em> considered
 
1973
        safe for code-signing or software integrity purposes.</p></warning>
 
1974
      </desc>
 
1975
    </func>
 
1976
    <func>
 
1977
      <name>erlang:md5_final(Context) -> Digest</name>
 
1978
      <fsummary>Finish the update of an MD5 context and return the computed MD5 message digest</fsummary>
 
1979
      <type>
 
1980
        <v>Context = Digest = binary()</v>
 
1981
      </type>
 
1982
      <desc>
 
1983
        <p>Finishes the update of an MD5 <c>Context</c> and returns
 
1984
          the computed <c>MD5</c> message digest.</p>
 
1985
      </desc>
 
1986
    </func>
 
1987
    <func>
 
1988
      <name>erlang:md5_init() -> Context</name>
 
1989
      <fsummary>Create an MD5 context</fsummary>
 
1990
      <type>
 
1991
        <v>Context = binary()</v>
 
1992
      </type>
 
1993
      <desc>
 
1994
        <p>Creates an MD5 context, to be used in subsequent calls to
 
1995
          <c>md5_update/2</c>.</p>
 
1996
      </desc>
 
1997
    </func>
 
1998
    <func>
 
1999
      <name>erlang:md5_update(Context, Data) -> NewContext</name>
 
2000
      <fsummary>Update an MD5 context with data, and return a new context</fsummary>
 
2001
      <type>
 
2002
        <v>Data = iodata()</v>
 
2003
        <v>Context = NewContext = binary()</v>
 
2004
      </type>
 
2005
      <desc>
 
2006
        <p>Updates an MD5 <c>Context</c> with <c>Data</c>, and returns
 
2007
          a <c>NewContext</c>.</p>
 
2008
      </desc>
 
2009
    </func>
 
2010
    <func>
 
2011
      <name>erlang:memory() -> [{Type, Size}]</name>
 
2012
      <fsummary>Information about dynamically allocated memory</fsummary>
 
2013
      <type>
 
2014
        <v>Type, Size -- see below</v>
 
2015
      </type>
 
2016
      <desc>
 
2017
        <p>Returns a list containing information about memory
 
2018
          dynamically allocated by the Erlang emulator. Each element of
 
2019
          the list is a tuple <c>{Type, Size}</c>. The first element
 
2020
          <c>Type</c>is an atom describing memory type. The second
 
2021
          element <c>Size</c>is memory size in bytes. A description of
 
2022
          each memory type follows:</p>
 
2023
        <taglist>
 
2024
          <tag><c>total</c></tag>
 
2025
          <item>
 
2026
            <p>The total amount of memory currently allocated, which is
 
2027
              the same as the sum of memory size for <c>processes</c>
 
2028
              and <c>system</c>.</p>
 
2029
          </item>
 
2030
          <tag><c>processes</c></tag>
 
2031
          <item>
 
2032
            <p>The total amount of memory currently allocated by
 
2033
              the Erlang processes.</p>
 
2034
          </item>
 
2035
          <tag><c>processes_used</c></tag>
 
2036
          <item>
 
2037
            <p>The total amount of memory currently used by the Erlang
 
2038
              processes.</p>
 
2039
            <p>This memory is part of the memory presented as
 
2040
              <c>processes</c> memory.</p>
 
2041
          </item>
 
2042
          <tag><c>system</c></tag>
 
2043
          <item>
 
2044
            <p>The total amount of memory currently allocated by
 
2045
              the emulator that is not directly related to any Erlang
 
2046
              process.</p>
 
2047
            <p>Memory presented as <c>processes</c> is not included in
 
2048
              this memory.</p>
 
2049
          </item>
 
2050
          <tag><c>atom</c></tag>
 
2051
          <item>
 
2052
            <p>The total amount of memory currently allocated for atoms.</p>
 
2053
            <p>This memory is part of the memory presented as
 
2054
              <c>system</c> memory.</p>
 
2055
          </item>
 
2056
          <tag><c>atom_used</c></tag>
 
2057
          <item>
 
2058
            <p>The total amount of memory currently used for atoms.</p>
 
2059
            <p>This memory is part of the memory presented as
 
2060
              <c>atom</c> memory.</p>
 
2061
          </item>
 
2062
          <tag><c>binary</c></tag>
 
2063
          <item>
 
2064
            <p>The total amount of memory currently allocated for
 
2065
              binaries.</p>
 
2066
            <p>This memory is part of the memory presented as
 
2067
              <c>system</c> memory.</p>
 
2068
          </item>
 
2069
          <tag><c>code</c></tag>
 
2070
          <item>
 
2071
            <p>The total amount of memory currently allocated for
 
2072
              Erlang code.</p>
 
2073
            <p>This memory is part of the memory presented as
 
2074
              <c>system</c> memory.</p>
 
2075
          </item>
 
2076
          <tag><c>ets</c></tag>
 
2077
          <item>
 
2078
            <p>The total amount of memory currently allocated for ets
 
2079
              tables.</p>
 
2080
            <p>This memory is part of the memory presented as
 
2081
              <c>system</c> memory.</p>
 
2082
          </item>
 
2083
          <tag><c>maximum</c></tag>
 
2084
          <item>
 
2085
            <p>The maximum total amount of memory allocated since
 
2086
              the emulator was started.</p>
 
2087
            <p>This tuple is only present when the emulator is run with
 
2088
              instrumentation.</p>
 
2089
            <p>For information on how to run the emulator with
 
2090
              instrumentation see
 
2091
              <seealso marker="tools:instrument">instrument(3)</seealso>
 
2092
              and/or <seealso marker="erts:erl">erl(1)</seealso>.</p>
 
2093
          </item>
 
2094
        </taglist>
 
2095
        <note>
 
2096
          <p>The <c>system</c> value is not complete. Some allocated
 
2097
            memory that should be part of the <c>system</c> value are
 
2098
            not.</p>
 
2099
          <p>When the emulator is run with instrumentation,
 
2100
            the <c>system</c> value is more accurate, but memory
 
2101
            directly allocated by <c>malloc</c> (and friends) are still
 
2102
            not part of the <c>system</c> value. Direct calls to
 
2103
            <c>malloc</c> are only done from OS specific runtime
 
2104
            libraries and perhaps from user implemented Erlang drivers
 
2105
            that do not use the memory allocation functions in
 
2106
            the driver interface.</p>
 
2107
          <p>Since the <c>total</c> value is the sum of <c>processes</c>
 
2108
            and <c>system</c> the error in <c>system</c> will propagate
 
2109
            to the <c>total</c> value.</p>
 
2110
          <p>The different amounts of memory that are summed are
 
2111
            <em>not</em> gathered atomically which also introduce
 
2112
            an error in the result.</p>
 
2113
        </note>
 
2114
        <p>The different values has the following relation to each
 
2115
          other. Values beginning with an uppercase letter is not part
 
2116
          of the result.</p>
 
2117
        <code type="none">
 
2118
\011total = processes + system
 
2119
\011processes = processes_used + ProcessesNotUsed
 
2120
\011system = atom + binary + code + ets + OtherSystem
 
2121
\011atom = atom_used + AtomNotUsed
 
2122
 
 
2123
\011RealTotal = processes + RealSystem
 
2124
\011RealSystem = system + MissedSystem</code>
 
2125
        <p>More tuples in the returned list may be added in the future.</p>
 
2126
        <note>
 
2127
          <p>The <c>total</c> value is supposed to be the total amount
 
2128
            of memory dynamically allocated by the emulator. Shared
 
2129
            libraries, the code of the emulator itself, and
 
2130
            the emulator stack(s) are not supposed to be included. That
 
2131
            is, the <c>total</c> value is <em>not</em> supposed to be
 
2132
            equal to the total size of all pages mapped to the emulator.
 
2133
            Furthermore, due to fragmentation and pre-reservation of
 
2134
            memory areas, the size of the memory segments which contain
 
2135
            the dynamically allocated memory blocks can be substantially
 
2136
            larger than the total size of the dynamically allocated
 
2137
            memory blocks.</p>
 
2138
        </note>
 
2139
        <note>
 
2140
          <p>
 
2141
            Since erts version 5.6.4 <c>erlang:memory/0</c> requires that
 
2142
            all <seealso marker="erts:erts_alloc">erts_alloc(3)</seealso>
 
2143
            allocators are enabled (default behaviour).
 
2144
          </p>
 
2145
        </note>
 
2146
        <p>Failure:</p>
 
2147
        <taglist>
 
2148
          <tag><c>notsup</c></tag>
 
2149
          <item>
 
2150
            If an <seealso marker="erts:erts_alloc">erts_alloc(3)</seealso>
 
2151
            allocator has been disabled.
 
2152
          </item>
 
2153
        </taglist>
 
2154
      </desc>
 
2155
    </func>
 
2156
    <func>
 
2157
      <name>erlang:memory(Type | [Type]) -> Size | [{Type, Size}]</name>
 
2158
      <fsummary>Information about dynamically allocated memory</fsummary>
 
2159
      <type>
 
2160
        <v>Type, Size -- see below</v>
 
2161
      </type>
 
2162
      <desc>
 
2163
        <p>Returns the memory size in bytes allocated for memory of
 
2164
          type <c>Type</c>. The argument can also be given as a list
 
2165
          of <c>Type</c> atoms, in which case a corresponding list of
 
2166
          <c>{Type, Size}</c> tuples is returned.</p>
 
2167
        <note>
 
2168
          <p>
 
2169
            Since erts version 5.6.4 <c>erlang:memory/1</c> requires that
 
2170
            all <seealso marker="erts:erts_alloc">erts_alloc(3)</seealso>
 
2171
            allocators are enabled (default behaviour).
 
2172
          </p>
 
2173
        </note>
 
2174
        <p>Failures:</p>
 
2175
        <taglist>
 
2176
          <tag><c>badarg</c></tag>
 
2177
          <item>
 
2178
            If <c>Type</c> is not one of the memory types listed in the
 
2179
            documentation of
 
2180
            <seealso marker="#erlang:memory/0">erlang:memory/0</seealso>.
 
2181
          </item>
 
2182
          <tag><c>badarg</c></tag>
 
2183
          <item>
 
2184
            If <c>maximum</c> is passed as <c>Type</c> and the emulator
 
2185
            is not run in instrumented mode.
 
2186
          </item>
 
2187
          <tag><c>notsup</c></tag>
 
2188
          <item>
 
2189
            If an <seealso marker="erts:erts_alloc">erts_alloc(3)</seealso>
 
2190
            allocator has been disabled.
 
2191
          </item>
 
2192
        </taglist>
 
2193
        <p>See also
 
2194
          <seealso marker="#erlang:memory/0">erlang:memory/0</seealso>.</p>
 
2195
      </desc>
 
2196
    </func>
 
2197
    <func>
 
2198
      <name>module_loaded(Module) -> bool()</name>
 
2199
      <fsummary>Check if a module is loaded</fsummary>
 
2200
      <type>
 
2201
        <v>Module = atom()</v>
 
2202
      </type>
 
2203
      <desc>
 
2204
        <p>Returns <c>true</c> if the module <c>Module</c> is loaded,
 
2205
          otherwise returns <c>false</c>. It does not attempt to load
 
2206
          the module.</p>
 
2207
        <warning>
 
2208
          <p>This BIF is intended for the code server (see
 
2209
            <seealso marker="code">code(3)</seealso>) and should not be
 
2210
            used elsewhere.</p>
 
2211
        </warning>
 
2212
      </desc>
 
2213
    </func>
 
2214
    <func>
 
2215
      <name>erlang:monitor(Type, Item) -> MonitorRef</name>
 
2216
      <fsummary>Start monitoring</fsummary>
 
2217
      <type>
 
2218
        <v>Type = process</v>
 
2219
        <v>Item = pid() | {RegName, Node} | RegName</v>
 
2220
        <v>&nbsp;RegName = atom()</v>
 
2221
        <v>&nbsp;Node = node()</v>
 
2222
        <v>MonitorRef = reference()</v>
 
2223
      </type>
 
2224
      <desc>
 
2225
        <p>The calling process starts monitoring <c>Item</c> which is
 
2226
          an object of type <c>Type</c>.</p>
 
2227
        <p>Currently only processes can be monitored, i.e. the only
 
2228
          allowed <c>Type</c> is <c>process</c>, but other types may be
 
2229
          allowed in the future.</p>
 
2230
        <p><c>Item</c> can be:</p>
 
2231
        <taglist>
 
2232
          <tag><c>pid()</c></tag>
 
2233
          <item>
 
2234
            <p>The pid of the process to monitor.</p>
 
2235
          </item>
 
2236
          <tag><c>{RegName, Node}</c></tag>
 
2237
          <item>
 
2238
            <p>A tuple consisting of a registered name of a process and
 
2239
              a node name. The process residing on the node <c>Node</c>
 
2240
              with the registered name <c>RegName</c> will be monitored.</p>
 
2241
          </item>
 
2242
          <tag><c>RegName</c></tag>
 
2243
          <item>
 
2244
            <p>The process locally registered as <c>RegName</c> will be
 
2245
              monitored.</p>
 
2246
          </item>
 
2247
        </taglist>
 
2248
        <note>
 
2249
          <p>When a process is monitored by registered name, the process
 
2250
            that has the registered name at the time when
 
2251
            <c>erlang:monitor/2</c> is called will be monitored.
 
2252
            The monitor will not be effected, if the registered name is
 
2253
            unregistered.</p>
 
2254
        </note>
 
2255
        <p>A <c>'DOWN'</c> message will be sent to the monitoring
 
2256
          process if <c>Item</c> dies, if <c>Item</c> does not exist,
 
2257
          or if the connection is lost to the node which <c>Item</c>
 
2258
          resides on. A <c>'DOWN'</c> message has the following pattern:</p>
 
2259
        <code type="none">
 
2260
{'DOWN', MonitorRef, Type, Object, Info}</code>
 
2261
        <p>where <c>MonitorRef</c> and <c>Type</c> are the same as
 
2262
          described above, and:</p>
 
2263
        <taglist>
 
2264
          <tag><c>Object</c></tag>
 
2265
          <item>
 
2266
            <p>A reference to the monitored object:</p>
 
2267
            <list type="bulleted">
 
2268
              <item>the pid of the monitored process, if <c>Item</c> was
 
2269
               specified as a pid.</item>
 
2270
              <item><c>{RegName, Node}</c>, if <c>Item</c> was specified as
 
2271
              <c>{RegName, Node}</c>.</item>
 
2272
              <item><c>{RegName, Node}</c>, if <c>Item</c> was specified as
 
2273
              <c>RegName</c>. <c>Node</c> will in this case be the
 
2274
               name of the local node (<c>node()</c>).</item>
 
2275
            </list>
 
2276
          </item>
 
2277
          <tag><c>Info</c></tag>
 
2278
          <item>
 
2279
            <p>Either the exit reason of the process, <c>noproc</c>
 
2280
              (non-existing process), or <c>noconnection</c> (no
 
2281
              connection to <c>Node</c>).</p>
 
2282
          </item>
 
2283
        </taglist>
 
2284
        <note>
 
2285
          <p>If/when <c>erlang:monitor/2</c> is extended (e.g. to
 
2286
            handle other item types than <c>process</c>), other
 
2287
            possible values for <c>Object</c>, and <c>Info</c> in the
 
2288
            <c>'DOWN'</c> message will be introduced.</p>
 
2289
        </note>
 
2290
        <p>The monitoring is turned off either when the <c>'DOWN'</c>
 
2291
          message is sent, or when
 
2292
          <seealso marker="#erlang:demonitor/1">erlang:demonitor/1</seealso>
 
2293
          is called.</p>
 
2294
        <p>If an attempt is made to monitor a process on an older node
 
2295
          (where remote process monitoring is not implemented or one
 
2296
          where remote process monitoring by registered name is not
 
2297
          implemented), the call fails with <c>badarg</c>.</p>
 
2298
        <p>Making several calls to <c>erlang:monitor/2</c> for the same
 
2299
          <c>Item</c> is not an error; it results in as many, completely
 
2300
          independent, monitorings.</p>
 
2301
        <note>
 
2302
          <p>The format of the <c>'DOWN'</c> message changed in the 5.2
 
2303
            version of the emulator (OTP release R9B) for monitor <em>by registered name</em>. The <c>Object</c> element of
 
2304
            the <c>'DOWN'</c> message could in earlier versions
 
2305
            sometimes be the pid of the monitored process and sometimes
 
2306
            be the registered name. Now the <c>Object</c> element is
 
2307
            always a tuple consisting of the registered name and
 
2308
            the node name. Processes on new nodes (emulator version 5.2
 
2309
            or greater) will always get <c>'DOWN'</c> messages on
 
2310
            the new format even if they are monitoring processes on old
 
2311
            nodes. Processes on old nodes will always get <c>'DOWN'</c>
 
2312
            messages on the old format.</p>
 
2313
        </note>
 
2314
      </desc>
 
2315
    </func>
 
2316
    <func>
 
2317
      <name>monitor_node(Node, Flag) -> true</name>
 
2318
      <fsummary>Monitor the status of a node</fsummary>
 
2319
      <type>
 
2320
        <v>Node = node()</v>
 
2321
        <v>Flag = bool()</v>
 
2322
      </type>
 
2323
      <desc>
 
2324
        <p>Monitors the status of the node <c>Node</c>. If <c>Flag</c>
 
2325
          is <c>true</c>, monitoring is turned on; if <c>Flag</c> is
 
2326
          <c>false</c>, monitoring is turned off.</p>
 
2327
        <p>Making several calls to <c>monitor_node(Node, true)</c> for
 
2328
          the same <c>Node</c> is not an error; it results in as many,
 
2329
          completely independent, monitorings.</p>
 
2330
        <p>If <c>Node</c> fails or does not exist, the message
 
2331
          <c>{nodedown, Node}</c> is delivered to the process. If a
 
2332
          process has made two calls to <c>monitor_node(Node, true)</c>
 
2333
          and <c>Node</c> terminates, two <c>nodedown</c> messages are
 
2334
          delivered to the process. If there is no connection to
 
2335
          <c>Node</c>, there will be an attempt to create one. If this
 
2336
          fails, a <c>nodedown</c> message is delivered.</p>
 
2337
        <p>Nodes connected through hidden connections can be monitored
 
2338
          as any other node.</p>
 
2339
        <p>Failure: <c>badarg</c>if the local node is not alive.</p>
 
2340
      </desc>
 
2341
    </func>
 
2342
    <func>
 
2343
      <name>erlang:monitor_node(Node, Flag, Options) -> true</name>
 
2344
      <fsummary>Monitor the status of a node</fsummary>
 
2345
      <type>
 
2346
        <v>Node = node()</v>
 
2347
        <v>Flag = bool()</v>
 
2348
        <v>Options = [Option]</v>
 
2349
        <v>Option = allow_passive_connect</v>
 
2350
      </type>
 
2351
      <desc>
 
2352
        <p>Behaves as <c>monitor_node/2</c> except that it allows an
 
2353
          extra option to be given, namely <c>allow_passive_connect</c>.
 
2354
          The option allows the BIF to wait the normal net connection
 
2355
          timeout for the <em>monitored node</em> to connect itself,
 
2356
          even if it cannot be actively connected from this node
 
2357
          (i.e. it is blocked). The state where this might be useful can
 
2358
          only be achieved by using the kernel option
 
2359
          <c>dist_auto_connect once</c>. If that kernel option is not
 
2360
          used, the <c>allow_passive_connect</c> option has no
 
2361
          effect.</p>
 
2362
        <note>
 
2363
          <p>The <c>allow_passive_connect</c> option is used
 
2364
            internally and is seldom needed in applications where the
 
2365
            network topology and the kernel options in effect is known in
 
2366
            advance.</p>
 
2367
        </note>
 
2368
        <p>Failure: <c>badarg</c> if the local node is not alive or the
 
2369
          option list is malformed.</p>
 
2370
      </desc>
 
2371
    </func>
 
2372
    <func>
 
2373
      <name>node() -> Node</name>
 
2374
      <fsummary>Name of the local node</fsummary>
 
2375
      <type>
 
2376
        <v>Node = node()</v>
 
2377
      </type>
 
2378
      <desc>
 
2379
        <p>Returns the name of the local node. If the node is not alive,
 
2380
          <c>nonode@nohost</c> is returned instead.</p>
 
2381
        <p>Allowed in guard tests.</p>
 
2382
      </desc>
 
2383
    </func>
 
2384
    <func>
 
2385
      <name>node(Arg) -> Node</name>
 
2386
      <fsummary>At which node is a pid, port or reference located</fsummary>
 
2387
      <type>
 
2388
        <v>Arg = pid() | port() | ref()</v>
 
2389
        <v>Node = node()</v>
 
2390
      </type>
 
2391
      <desc>
 
2392
        <p>Returns the node where <c>Arg</c> is located. <c>Arg</c> can
 
2393
          be a pid, a reference, or a port. If the local node is not
 
2394
          alive, <c>nonode@nohost</c> is returned.</p>
 
2395
        <p>Allowed in guard tests.</p>
 
2396
      </desc>
 
2397
    </func>
 
2398
    <func>
 
2399
      <name>nodes() -> Nodes</name>
 
2400
      <fsummary>All visible nodes in the system</fsummary>
 
2401
      <type>
 
2402
        <v>Nodes = [node()]</v>
 
2403
      </type>
 
2404
      <desc>
 
2405
        <p>Returns a list of all visible nodes in the system, excluding
 
2406
          the local node. Same as <c>nodes(visible)</c>.</p>
 
2407
      </desc>
 
2408
    </func>
 
2409
    <func>
 
2410
      <name>nodes(Arg | [Arg]) -> Nodes</name>
 
2411
      <fsummary>All nodes of a certain type in the system</fsummary>
 
2412
      <type>
 
2413
        <v>Arg = visible | hidden | connected | this | known</v>
 
2414
        <v>Nodes = [node()]</v>
 
2415
      </type>
 
2416
      <desc>
 
2417
        <p>Returns a list of nodes according to argument given.
 
2418
          The result returned when the argument is a list, is the list
 
2419
          of nodes satisfying the disjunction(s) of the list elements.</p>
 
2420
        <p><c>Arg</c> can be any of the following:</p>
 
2421
        <taglist>
 
2422
          <tag><c>visible</c></tag>
 
2423
          <item>
 
2424
            <p>Nodes connected to this node through normal connections.</p>
 
2425
          </item>
 
2426
          <tag><c>hidden</c></tag>
 
2427
          <item>
 
2428
            <p>Nodes connected to this node through hidden connections.</p>
 
2429
          </item>
 
2430
          <tag><c>connected</c></tag>
 
2431
          <item>
 
2432
            <p>All nodes connected to this node.</p>
 
2433
          </item>
 
2434
          <tag><c>this</c></tag>
 
2435
          <item>
 
2436
            <p>This node.</p>
 
2437
          </item>
 
2438
          <tag><c>known</c></tag>
 
2439
          <item>
 
2440
            <p>Nodes which are known to this node, i.e., connected,
 
2441
              previously connected, etc.</p>
 
2442
          </item>
 
2443
        </taglist>
 
2444
        <p>Some equalities: <c>[node()] = nodes(this)</c>,
 
2445
          <c>nodes(connected) = nodes([visible, hidden])</c>, and
 
2446
          <c>nodes() = nodes(visible)</c>.</p>
 
2447
        <p>If the local node is not alive,
 
2448
          <c>nodes(this) == nodes(known) == [nonode@nohost]</c>, for
 
2449
          any other <c>Arg</c> the empty list [] is returned.</p>
 
2450
      </desc>
 
2451
    </func>
 
2452
    <func>
 
2453
      <name>now() -> {MegaSecs, Secs, MicroSecs}</name>
 
2454
      <fsummary>Elapsed time since 00:00 GMT</fsummary>
 
2455
      <type>
 
2456
        <v>MegaSecs = Secs = MicroSecs = int()</v>
 
2457
      </type>
 
2458
      <desc>
 
2459
        <p>Returns the tuple <c>{MegaSecs, Secs, MicroSecs}</c> which is
 
2460
          the elapsed time since 00:00 GMT, January 1, 1970 (zero hour)
 
2461
          on the assumption that the underlying OS supports this.
 
2462
          Otherwise, some other point in time is chosen. It is also
 
2463
          guaranteed that subsequent calls to this BIF returns
 
2464
          continuously increasing values. Hence, the return value from
 
2465
          <c>now()</c> can be used to generate unique time-stamps. It
 
2466
          can only be used to check the local time of day if
 
2467
          the time-zone info of the underlying operating system is
 
2468
          properly configured.</p>
 
2469
      </desc>
 
2470
    </func>
 
2471
    <func>
 
2472
      <name>open_port(PortName, PortSettings) -> port()</name>
 
2473
      <fsummary>Open a port</fsummary>
 
2474
      <type>
 
2475
        <v>PortName = {spawn, Command} | {fd, In, Out}</v>
 
2476
        <v>&nbsp;Command = string()</v>
 
2477
        <v>&nbsp;In = Out = int()</v>
 
2478
        <v>PortSettings = [Opt]</v>
 
2479
        <v>&nbsp;Opt = {packet, N} | stream | {line, L} | {cd, Dir} | {env, Env} | exit_status | use_stdio | nouse_stdio | stderr_to_stdout | in | out | binary | eof</v>
 
2480
        <v>&nbsp;&nbsp;N = 1 | 2 | 4</v>
 
2481
        <v>&nbsp;&nbsp;L = int()</v>
 
2482
        <v>&nbsp;&nbsp;Dir = string()</v>
 
2483
        <v>&nbsp;&nbsp;Env = [{Name, Val}]</v>
 
2484
        <v>&nbsp;&nbsp;&nbsp;Name = string()</v>
 
2485
        <v>&nbsp;&nbsp;&nbsp;Val = string() | false</v>
 
2486
      </type>
 
2487
      <desc>
 
2488
        <p>Returns a port identifier as the result of opening a
 
2489
          new Erlang port. A port can be seen as an external Erlang
 
2490
          process. <c>PortName</c> is one of the following:</p>
 
2491
        <taglist>
 
2492
          <tag><c>{spawn, Command}</c></tag>
 
2493
          <item>
 
2494
            <p>Starts an external program. <c>Command</c> is the name
 
2495
              of the external program which will be run. <c>Command</c>
 
2496
              runs outside the Erlang work space unless an Erlang
 
2497
              driver with the name <c>Command</c> is found. If found,
 
2498
              that driver will be started. A driver runs in the Erlang
 
2499
              workspace, which means that it is linked with the Erlang
 
2500
              runtime system.</p>
 
2501
            <p>When starting external programs on Solaris, the system
 
2502
              call <c>vfork</c> is used in preference to <c>fork</c>
 
2503
              for performance reasons, although it has a history of
 
2504
              being less robust. If there are problems with using
 
2505
              <c>vfork</c>, setting the environment variable
 
2506
              <c>ERL_NO_VFORK</c> to any value will cause <c>fork</c>
 
2507
              to be used instead.</p>
 
2508
          </item>
 
2509
          <tag><c>{fd, In, Out}</c></tag>
 
2510
          <item>
 
2511
            <p>Allows an Erlang process to access any currently opened
 
2512
              file descriptors used by Erlang. The file descriptor
 
2513
              <c>In</c> can be used for standard input, and the file
 
2514
              descriptor <c>Out</c> for standard output. It is only
 
2515
              used for various servers in the Erlang operating system
 
2516
              (<c>shell</c> and <c>user</c>). Hence, its use is very
 
2517
              limited.</p>
 
2518
          </item>
 
2519
        </taglist>
 
2520
        <p><c>PortSettings</c> is a list of settings for the port.
 
2521
          Valid settings are:</p>
 
2522
        <taglist>
 
2523
          <tag><c>{packet, N}</c></tag>
 
2524
          <item>
 
2525
            <p>Messages are preceded by their length, sent in <c>N</c>
 
2526
              bytes, with the most significant byte first. Valid values
 
2527
              for <c>N</c> are 1, 2, or 4.</p>
 
2528
          </item>
 
2529
          <tag><c>stream</c></tag>
 
2530
          <item>
 
2531
            <p>Output messages are sent without packet lengths. A
 
2532
              user-defined protocol must be used between the Erlang
 
2533
              process and the external object.</p>
 
2534
          </item>
 
2535
          <tag><c>{line, L}</c></tag>
 
2536
          <item>
 
2537
            <p>Messages are delivered on a per line basis. Each line
 
2538
              (delimited by the OS-dependent newline sequence) is
 
2539
              delivered in one single message. The message data format
 
2540
              is <c>{Flag, Line}</c>, where <c>Flag</c> is either
 
2541
              <c>eol</c> or <c>noeol</c> and <c>Line</c> is the actual
 
2542
              data delivered (without the newline sequence).</p>
 
2543
            <p><c>L</c> specifies the maximum line length in bytes.
 
2544
              Lines longer than this will be delivered in more than one
 
2545
              message, with the <c>Flag</c> set to <c>noeol</c> for all
 
2546
              but the last message. If end of file is encountered
 
2547
              anywhere else than immediately following a newline
 
2548
              sequence, the last line will also be delivered with
 
2549
              the <c>Flag</c> set to <c>noeol</c>. In all other cases,
 
2550
              lines are delivered with <c>Flag</c> set to <c>eol</c>.</p>
 
2551
            <p>The <c>{packet, N}</c> and <c>{line, L}</c> settings are
 
2552
              mutually exclusive.</p>
 
2553
          </item>
 
2554
          <tag><c>{cd, Dir}</c></tag>
 
2555
          <item>
 
2556
            <p>This is only valid for <c>{spawn, Command}</c>.
 
2557
              The external program starts using <c>Dir</c> as its
 
2558
              working directory. <c>Dir</c> must be a string. Not
 
2559
              available on VxWorks.</p>
 
2560
          </item>
 
2561
          <tag><c>{env, Env}</c></tag>
 
2562
          <item>
 
2563
            <p>This is only valid for <c>{spawn, Command}</c>.
 
2564
              The environment of the started process is extended using
 
2565
              the environment specifications in <c>Env</c>.</p>
 
2566
            <p><c>Env</c> should be a list of tuples <c>{Name, Val}</c>,
 
2567
              where <c>Name</c> is the name of an environment variable,
 
2568
              and <c>Val</c> is the value it is to have in the spawned
 
2569
              port process. Both <c>Name</c> and <c>Val</c> must be
 
2570
              strings. The one exception is <c>Val</c> being the atom
 
2571
              <c>false</c> (in analogy with <c>os:getenv/1</c>), which
 
2572
              removes the environment variable. Not available on
 
2573
              VxWorks.</p>
 
2574
          </item>
 
2575
          <tag><c>exit_status</c></tag>
 
2576
          <item>
 
2577
            <p>This is only valid for <c>{spawn, Command}</c> where
 
2578
              <c>Command</c> refers to an external program.</p>
 
2579
            <p>When the external process connected to the port exits, a
 
2580
              message of the form <c>{Port,{exit_status,Status}}</c> is
 
2581
              sent to the connected process, where <c>Status</c> is the
 
2582
              exit status of the external process. If the program
 
2583
              aborts, on Unix the same convention is used as the shells
 
2584
              do (i.e., 128+signal).</p>
 
2585
            <p>If the <c>eof</c> option has been given as well,
 
2586
              the <c>eof</c> message and the <c>exit_status</c> message
 
2587
              appear in an unspecified order.</p>
 
2588
            <p>If the port program closes its stdout without exiting,
 
2589
              the <c>exit_status</c> option will not work.</p>
 
2590
          </item>
 
2591
          <tag><c>use_stdio</c></tag>
 
2592
          <item>
 
2593
            <p>This is only valid for <c>{spawn, Command}</c>. It
 
2594
              allows the standard input and output (file descriptors 0
 
2595
              and 1) of the spawned (UNIX) process for communication
 
2596
              with Erlang.</p>
 
2597
          </item>
 
2598
          <tag><c>nouse_stdio</c></tag>
 
2599
          <item>
 
2600
            <p>The opposite of <c>use_stdio</c>. Uses file descriptors
 
2601
              3 and 4 for communication with Erlang.</p>
 
2602
          </item>
 
2603
          <tag><c>stderr_to_stdout</c></tag>
 
2604
          <item>
 
2605
            <p>Affects ports to external programs. The executed program
 
2606
              gets its standard error file redirected to its standard
 
2607
              output file. <c>stderr_to_stdout</c> and
 
2608
              <c>nouse_stdio</c> are mutually exclusive.</p>
 
2609
          </item>
 
2610
          <tag><c>in</c></tag>
 
2611
          <item>
 
2612
            <p>The port can only be used for input.</p>
 
2613
          </item>
 
2614
          <tag><c>out</c></tag>
 
2615
          <item>
 
2616
            <p>The port can only be used for output.</p>
 
2617
          </item>
 
2618
          <tag><c>binary</c></tag>
 
2619
          <item>
 
2620
            <p>All IO from the port are binary data objects as opposed
 
2621
              to lists of bytes.</p>
 
2622
          </item>
 
2623
          <tag><c>eof</c></tag>
 
2624
          <item>
 
2625
            <p>The port will not be closed at the end of the file and
 
2626
              produce an exit signal. Instead, it will remain open and
 
2627
              a <c>{Port, eof}</c> message will be sent to the process
 
2628
              holding the port.</p>
 
2629
          </item>
 
2630
          <tag><c>hide</c></tag>
 
2631
          <item>
 
2632
            <p>When running on Windows, suppress creation of a new
 
2633
              console window when spawning the port program.
 
2634
              (This option has no effect on other platforms.)</p>
 
2635
          </item>
 
2636
        </taglist>
 
2637
        <p>The default is <c>stream</c> for all types of port and
 
2638
          <c>use_stdio</c> for spawned ports.</p>
 
2639
        <p>Failure: If the port cannot be opened, the exit reason is
 
2640
          <c>badarg</c>, <c>system_limit</c>, or the Posix error code which
 
2641
          most closely describes the error, or <c>einval</c> if no Posix code
 
2642
          is appropriate:</p>
 
2643
        <taglist>
 
2644
          <tag><c>badarg</c></tag>
 
2645
          <item>
 
2646
            <p>Bad input arguments to <c>open_port</c>.</p>
 
2647
          </item>
 
2648
          <tag><c>system_limit</c></tag>
 
2649
          <item>
 
2650
            <p>All available ports in the Erlang emulator are in use.</p>
 
2651
          </item>
 
2652
          <tag><c>enomem</c></tag>
 
2653
          <item>
 
2654
            <p>There was not enough memory to create the port.</p>
 
2655
          </item>
 
2656
          <tag><c>eagain</c></tag>
 
2657
          <item>
 
2658
            <p>There are no more available operating system processes.</p>
 
2659
          </item>
 
2660
          <tag><c>enametoolong</c></tag>
 
2661
          <item>
 
2662
            <p>The external command given was too long.</p>
 
2663
          </item>
 
2664
          <tag><c>emfile</c></tag>
 
2665
          <item>
 
2666
            <p>There are no more available file descriptors (for the operating system process
 
2667
            that the Erlang emulator runs in).</p>
 
2668
          </item>
 
2669
          <tag><c>enfile</c></tag>
 
2670
          <item>
 
2671
            <p>The file table is full (for the entire operating system).</p>
 
2672
          </item>
 
2673
        </taglist>
 
2674
        <p>During use of a port opened using <c>{spawn, Name}</c>,
 
2675
          errors arising when sending messages to it are reported to
 
2676
          the owning process using signals of the form
 
2677
          <c>{'EXIT', Port, PosixCode}</c>. See <c>file(3)</c> for
 
2678
          possible values of <c>PosixCode</c>.</p>
 
2679
        <p><marker id="ERL_MAX_PORTS"></marker>
 
2680
          The maximum number of ports that can be open at the same
 
2681
          time is 1024 by default, but can be configured by
 
2682
          the environment variable <c>ERL_MAX_PORTS</c>.</p>
 
2683
      </desc>
 
2684
    </func>
 
2685
    <func>
 
2686
      <name>erlang:phash(Term, Range) -> Hash</name>
 
2687
      <fsummary>Portable hash function</fsummary>
 
2688
      <type>
 
2689
        <v>Term = term()</v>
 
2690
        <v>Range = 1..2^32</v>
 
2691
        <v>Hash = 1..Range</v>
 
2692
      </type>
 
2693
      <desc>
 
2694
        <p>Portable hash function that will give the same hash for
 
2695
          the same Erlang term regardless of machine architecture and
 
2696
          ERTS version (the BIF was introduced in ERTS 4.9.1.1). Range
 
2697
          can be between 1 and 2^32, the function returns a hash value
 
2698
          for <c>Term</c> within the range <c>1..Range</c>.</p>
 
2699
        <p>This BIF could be used instead of the old deprecated
 
2700
          <c>erlang:hash/2</c> BIF, as it calculates better hashes for
 
2701
          all data-types, but consider using <c>phash2/1,2</c> instead.</p>
 
2702
      </desc>
 
2703
    </func>
 
2704
    <func>
 
2705
      <name>erlang:phash2(Term [, Range]) -> Hash</name>
 
2706
      <fsummary>Portable hash function</fsummary>
 
2707
      <type>
 
2708
        <v>Term = term()</v>
 
2709
        <v>Range = 1..2^32</v>
 
2710
        <v>Hash = 0..Range-1</v>
 
2711
      </type>
 
2712
      <desc>
 
2713
        <p>Portable hash function that will give the same hash for
 
2714
          the same Erlang term regardless of machine architecture and
 
2715
          ERTS version (the BIF was introduced in ERTS 5.2). Range can
 
2716
          be between 1 and 2^32, the function returns a hash value for
 
2717
          <c>Term</c> within the range <c>0..Range-1</c>. When called
 
2718
          without the <c>Range</c> argument, a value in the range
 
2719
          <c>0..2^27-1</c> is returned.</p>
 
2720
        <p>This BIF should always be used for hashing terms. It
 
2721
          distributes small integers better than <c>phash/2</c>, and
 
2722
          it is faster for bignums and binaries.</p>
 
2723
        <p>Note that the range <c>0..Range-1</c> is different from
 
2724
          the range of <c>phash/2</c> (<c>1..Range</c>).</p>
 
2725
      </desc>
 
2726
    </func>
 
2727
    <func>
 
2728
      <name>pid_to_list(Pid) -> string()</name>
 
2729
      <fsummary>Text representation of a pid</fsummary>
 
2730
      <type>
 
2731
        <v>Pid = pid()</v>
 
2732
      </type>
 
2733
      <desc>
 
2734
        <p>Returns a string which corresponds to the text
 
2735
          representation of <c>Pid</c>.</p>
 
2736
        <warning>
 
2737
          <p>This BIF is intended for debugging and for use in
 
2738
            the Erlang operating system. It should not be used in
 
2739
            application programs.</p>
 
2740
        </warning>
 
2741
      </desc>
 
2742
    </func>
 
2743
    <func>
 
2744
      <name>port_close(Port) -> true</name>
 
2745
      <fsummary>Close an open port</fsummary>
 
2746
      <type>
 
2747
        <v>Port = port() | atom()</v>
 
2748
      </type>
 
2749
      <desc>
 
2750
        <p>Closes an open port. Roughly the same as
 
2751
          <c>Port ! {self(), close}</c> except for the error behaviour
 
2752
          (see below), and that the port does <em>not</em> reply with
 
2753
          <c>{Port, closed}</c>. Any process may close a port with
 
2754
          <c>port_close/1</c>, not only the port owner (the connected
 
2755
          process).</p>
 
2756
        <p>For comparison: <c>Port ! {self(), close}</c> fails with
 
2757
          <c>badarg</c> if <c>Port</c> cannot be sent to (i.e.,
 
2758
          <c>Port</c> refers neither to a port nor to a process). If
 
2759
          <c>Port</c> is a closed port nothing happens. If <c>Port</c>
 
2760
          is an open port and the calling process is the port owner,
 
2761
          the port replies with <c>{Port, closed}</c> when all buffers
 
2762
          have been flushed and the port really closes, but if
 
2763
          the calling process is not the port owner the <em>port owner</em> fails with <c>badsig</c>.</p>
 
2764
        <p>Note that any process can close a port using
 
2765
          <c>Port ! {PortOwner, close}</c> just as if it itself was
 
2766
          the port owner, but the reply always goes to the port owner.</p>
 
2767
        <p>In short: <c>port_close(Port)</c> has a cleaner and more
 
2768
          logical behaviour than <c>Port ! {self(), close}</c>.</p>
 
2769
        <p>Failure: <c>badarg</c> if <c>Port</c> is not an open port or
 
2770
          the registered name of an open port.</p>
 
2771
      </desc>
 
2772
    </func>
 
2773
    <func>
 
2774
      <name>port_command(Port, Data) -> true</name>
 
2775
      <fsummary>Send data to a port</fsummary>
 
2776
      <type>
 
2777
        <v>Port = port() | atom()</v>
 
2778
        <v>Data = iodata()</v>
 
2779
      </type>
 
2780
      <desc>
 
2781
        <p>Sends data to a port. Same as
 
2782
          <c>Port ! {self(), {command, Data}}</c> except for the error
 
2783
          behaviour (see below). Any process may send data to a port
 
2784
          with <c>port_command/2</c>, not only the port owner
 
2785
          (the connected process).</p>
 
2786
        <p>For comparison: <c>Port ! {self(), {command, Data}}</c>
 
2787
          fails with <c>badarg</c> if <c>Port</c> cannot be sent to
 
2788
          (i.e., <c>Port</c> refers neither to a port nor to a process).
 
2789
          If <c>Port</c> is a closed port the data message disappears
 
2790
          without a sound. If <c>Port</c> is open and the calling
 
2791
          process is not the port owner, the <em>port owner</em> fails
 
2792
          with <c>badsig</c>. The port owner fails with <c>badsig</c>
 
2793
          also if <c>Data</c> is not a valid IO list.</p>
 
2794
        <p>Note that any process can send to a port using
 
2795
          <c>Port ! {PortOwner, {command, Data}}</c> just as if it
 
2796
          itself was the port owner.</p>
 
2797
        <p>In short: <c>port_command(Port, Data)</c> has a cleaner and
 
2798
          more logical behaviour than
 
2799
          <c>Port ! {self(), {command, Data}}</c>.</p>
 
2800
        <p>Failure: <c>badarg</c> if <c>Port</c> is not an open port
 
2801
          or the registered name of an open port.</p>
 
2802
      </desc>
 
2803
    </func>
 
2804
    <func>
 
2805
      <name>port_connect(Port, Pid) -> true</name>
 
2806
      <fsummary>Set the owner of a port</fsummary>
 
2807
      <type>
 
2808
        <v>Port = port() | atom()</v>
 
2809
        <v>Pid = pid()</v>
 
2810
      </type>
 
2811
      <desc>
 
2812
        <p>Sets the port owner (the connected port) to <c>Pid</c>.
 
2813
          Roughly the same as <c>Port ! {self(), {connect, Pid}}</c>
 
2814
          except for the following:</p>
 
2815
        <list type="bulleted">
 
2816
          <item>
 
2817
            <p>The error behavior differs, see below.</p>
 
2818
          </item>
 
2819
          <item>
 
2820
            <p>The port does <em>not</em> reply with
 
2821
              <c>{Port,connected}</c>.</p>
 
2822
          </item>
 
2823
          <item>
 
2824
            <p>The new port owner gets linked to the port.</p>
 
2825
          </item>
 
2826
        </list>
 
2827
        <p>The old port owner stays linked to the port and have to call
 
2828
          <c>unlink(Port)</c> if this is not desired. Any process may
 
2829
          set the port owner to be any process with
 
2830
          <c>port_connect/2</c>.</p>
 
2831
        <p>For comparison: <c>Port ! {self(), {connect, Pid}}</c> fails
 
2832
          with <c>badarg</c> if <c>Port</c> cannot be sent to (i.e.,
 
2833
          <c>Port</c> refers neither to a port nor to a process). If
 
2834
          <c>Port</c> is a closed port nothing happens. If <c>Port</c>
 
2835
          is an open port and the calling process is the port owner,
 
2836
          the port replies with <c>{Port, connected}</c> to the old
 
2837
          port owner. Note that the old port owner is still linked to
 
2838
          the port, and that the new is not. If <c>Port</c> is an open
 
2839
          port and the calling process is not the port owner,
 
2840
          the <em>port owner</em> fails with <c>badsig</c>. The port
 
2841
          owner fails with <c>badsig</c> also if <c>Pid</c> is not an
 
2842
          existing local pid.</p>
 
2843
        <p>Note that any process can set the port owner using
 
2844
          <c>Port ! {PortOwner, {connect, Pid}}</c> just as if it
 
2845
          itself was the port owner, but the reply always goes to
 
2846
          the port owner.</p>
 
2847
        <p>In short: <c>port_connect(Port, Pid)</c> has a cleaner and
 
2848
          more logical behaviour than
 
2849
          <c>Port ! {self(),{connect,Pid}}</c>.</p>
 
2850
        <p>Failure: <c>badarg</c> if <c>Port</c> is not an open port
 
2851
          or the registered name of an open port, or if <c>Pid</c> is
 
2852
          not an existing local pid.</p>
 
2853
      </desc>
 
2854
    </func>
 
2855
    <func>
 
2856
      <name>port_control(Port, Operation, Data) -> Res</name>
 
2857
      <fsummary>Perform a synchronous control operation on a port</fsummary>
 
2858
      <type>
 
2859
        <v>Port = port() | atom()</v>
 
2860
        <v>Operation = int()</v>
 
2861
        <v>Data = Res = iodata()</v>
 
2862
      </type>
 
2863
      <desc>
 
2864
        <p>Performs a synchronous control operation on a port.
 
2865
          The meaning of <c>Operation</c> and <c>Data</c> depends on
 
2866
          the port, i.e., on the port driver. Not all port drivers
 
2867
          support this control feature.</p>
 
2868
        <p>Returns: a list of integers in the range 0 through 255, or a
 
2869
          binary, depending on the port driver. The meaning of
 
2870
          the returned data also depends on the port driver.</p>
 
2871
        <p>Failure: <c>badarg</c> if <c>Port</c> is not an open port or
 
2872
          the registered name of an open port, if <c>Operation</c>
 
2873
          cannot fit in a 32-bit integer, if the port driver does not
 
2874
          support synchronous control operations, or if the port driver
 
2875
          so decides for any reason (probably something wrong with
 
2876
          <c>Operation</c> or <c>Data</c>).</p>
 
2877
      </desc>
 
2878
    </func>
 
2879
    <func>
 
2880
      <name>erlang:port_call(Port, Operation, Data) -> term()</name>
 
2881
      <fsummary>Synchronous call to a port with term data</fsummary>
 
2882
      <type>
 
2883
        <v>Port = port() | atom()</v>
 
2884
        <v>Operation = int()</v>
 
2885
        <v>Data = term()</v>
 
2886
      </type>
 
2887
      <desc>
 
2888
        <p>Performs a synchronous call to a port. The meaning of
 
2889
          <c>Operation</c> and <c>Data</c> depends on the port, i.e.,
 
2890
          on the port driver. Not all port drivers support this feature.</p>
 
2891
        <p><c>Port</c> is a port identifier, referring to a driver.</p>
 
2892
        <p><c>Operation</c> is an integer, which is passed on to
 
2893
          the driver.</p>
 
2894
        <p><c>Data</c> is any Erlang term. This data is converted to
 
2895
          binary term format and sent to the port.</p>
 
2896
        <p>Returns: a term from the driver. The meaning of the returned
 
2897
          data also depends on the port driver.</p>
 
2898
        <p>Failure: <c>badarg</c> if <c>Port</c> is not an open port or
 
2899
          the registered name of an open port, if <c>Operation</c>
 
2900
          cannot fit in a 32-bit integer, if the port driver does not
 
2901
          support synchronous control operations, or if the port driver
 
2902
          so decides for any reason (probably something wrong with
 
2903
          <c>Operation</c> or <c>Data</c>).</p>
 
2904
      </desc>
 
2905
    </func>
 
2906
    <func>
 
2907
      <name>erlang:port_info(Port) -> [{Item, Info}] | undefined</name>
 
2908
      <fsummary>Information about a port</fsummary>
 
2909
      <type>
 
2910
        <v>Port = port() | atom()</v>
 
2911
        <v>Item, Info -- see below</v>
 
2912
      </type>
 
2913
      <desc>
 
2914
        <p>Returns a list containing tuples with information about
 
2915
          the <c>Port</c>, or <c>undefined</c> if the port is not open.
 
2916
          The order of the tuples is not defined, nor are all the
 
2917
          tuples mandatory.</p>
 
2918
        <taglist>
 
2919
          <tag><c>{registered_name, RegName}</c></tag>
 
2920
          <item>
 
2921
            <p><c>RegName</c> (an atom) is the registered name of
 
2922
              the port. If the port has no registered name, this tuple
 
2923
              is not present in the list.</p>
 
2924
          </item>
 
2925
          <tag><c>{id, Index}</c></tag>
 
2926
          <item>
 
2927
            <p><c>Index</c> (an integer) is the internal index of the
 
2928
              port. This index may be used to separate ports.</p>
 
2929
          </item>
 
2930
          <tag><c>{connected, Pid}</c></tag>
 
2931
          <item>
 
2932
            <p><c>Pid</c> is the process connected to the port.</p>
 
2933
          </item>
 
2934
          <tag><c>{links, Pids}</c></tag>
 
2935
          <item>
 
2936
            <p><c>Pids</c> is a list of pids to which processes the
 
2937
              port is linked.</p>
 
2938
          </item>
 
2939
          <tag><c>{name, String}</c></tag>
 
2940
          <item>
 
2941
            <p><c>String</c> is the command name set by
 
2942
              <c>open_port</c>.</p>
 
2943
          </item>
 
2944
          <tag><c>{input, Bytes}</c></tag>
 
2945
          <item>
 
2946
            <p><c>Bytes</c> is the total number of bytes read from
 
2947
              the port.</p>
 
2948
          </item>
 
2949
          <tag><c>{output, Bytes}</c></tag>
 
2950
          <item>
 
2951
            <p><c>Bytes</c> is the total number of bytes written to
 
2952
              the port.</p>
 
2953
          </item>
 
2954
        </taglist>
 
2955
        <p>Failure: <c>badarg</c> if <c>Port</c> is not a local port.</p>
 
2956
      </desc>
 
2957
    </func>
 
2958
    <func>
 
2959
      <name>erlang:port_info(Port, Item) -> {Item, Info} | undefined | []</name>
 
2960
      <fsummary>Information about a port</fsummary>
 
2961
      <type>
 
2962
        <v>Port = port() | atom()</v>
 
2963
        <v>Item, Info -- see below</v>
 
2964
      </type>
 
2965
      <desc>
 
2966
        <p>Returns information about <c>Port</c> as specified
 
2967
          by <c>Item</c>, or <c>undefined</c> if the port is not open.
 
2968
          Also, if <c>Item == registered_name</c> and the port has no
 
2969
          registered name, [] is returned.</p>
 
2970
        <p>For valid values of <c>Item</c>, and corresponding
 
2971
          values of <c>Info</c>, see
 
2972
          <seealso marker="#erlang:port_info/1">erlang:port_info/1</seealso>.</p>
 
2973
        <p>Failure: <c>badarg</c> if <c>Port</c> is not a local port.</p>
 
2974
      </desc>
 
2975
    </func>
 
2976
    <func>
 
2977
      <name>erlang:port_to_list(Port) -> string()</name>
 
2978
      <fsummary>Text representation of a port identifier</fsummary>
 
2979
      <type>
 
2980
        <v>Port = port()</v>
 
2981
      </type>
 
2982
      <desc>
 
2983
        <p>Returns a string which corresponds to the text
 
2984
          representation of the port identifier <c>Port</c>.</p>
 
2985
        <warning>
 
2986
          <p>This BIF is intended for debugging and for use in
 
2987
            the Erlang operating system. It should not be used in
 
2988
            application programs.</p>
 
2989
        </warning>
 
2990
      </desc>
 
2991
    </func>
 
2992
    <func>
 
2993
      <name>erlang:ports() -> [port()]</name>
 
2994
      <fsummary>All open ports</fsummary>
 
2995
      <desc>
 
2996
        <p>Returns a list of all ports on the local node.</p>
 
2997
      </desc>
 
2998
    </func>
 
2999
    <func>
 
3000
      <name>pre_loaded() -> [Module]</name>
 
3001
      <fsummary>List of all pre-loaded modules</fsummary>
 
3002
      <type>
 
3003
        <v>Module = atom()</v>
 
3004
      </type>
 
3005
      <desc>
 
3006
        <p>Returns a list of Erlang modules which are pre-loaded in
 
3007
          the system. As all loading of code is done through the file
 
3008
          system, the file system must have been loaded previously.
 
3009
          Hence, at least the module <c>init</c> must be pre-loaded.</p>
 
3010
      </desc>
 
3011
    </func>
 
3012
    <func>
 
3013
      <name>erlang:process_display(Pid, Type) -> void()</name>
 
3014
      <fsummary>Write information about a local process on standard error</fsummary>
 
3015
      <type>
 
3016
        <v>Pid = pid()</v>
 
3017
        <v>Type = backtrace</v>
 
3018
      </type>
 
3019
      <desc>
 
3020
        <p>Writes information about the local process <c>Pid</c> on
 
3021
          standard error. The currently allowed value for the atom
 
3022
          <c>Type</c> is <c>backtrace</c>, which shows the contents of
 
3023
          the call stack, including information about the call chain, with
 
3024
          the current function printed first. The format of the output
 
3025
          is not further defined.</p>
 
3026
      </desc>
 
3027
    </func>
 
3028
    <func>
 
3029
      <name>process_flag(Flag, Value) -> OldValue</name>
 
3030
      <fsummary>Set process flags for the calling process</fsummary>
 
3031
      <type>
 
3032
        <v>Flag, Value, OldValue -- see below</v>
 
3033
      </type>
 
3034
      <desc>
 
3035
        <p>Sets certain flags for the process which calls this
 
3036
          function. Returns the old value of the flag.</p>
 
3037
        <taglist>
 
3038
          <tag><c>process_flag(trap_exit, Boolean)</c></tag>
 
3039
          <item>
 
3040
            <p>When <c>trap_exit</c> is set to <c>true</c>, exit signals
 
3041
              arriving to a process are converted to <c>{'EXIT', From, Reason}</c> messages, which can be received as ordinary
 
3042
              messages. If <c>trap_exit</c> is set to <c>false</c>, the
 
3043
              process exits if it receives an exit signal other than
 
3044
              <c>normal</c> and the exit signal is propagated to its
 
3045
              linked processes. Application processes should normally
 
3046
              not trap exits.</p>
 
3047
            <p>See also <seealso marker="#exit/2">exit/2</seealso>.</p>
 
3048
          </item>
 
3049
          <tag><c>process_flag(error_handler, Module)</c></tag>
 
3050
          <item>
 
3051
            <p>This is used by a process to redefine the error handler
 
3052
              for undefined function calls and undefined registered
 
3053
              processes.  Inexperienced users should not use this flag
 
3054
              since code auto-loading is dependent on the correct
 
3055
              operation of the error handling module.</p>
 
3056
          </item>
 
3057
          <tag><c>process_flag(min_heap_size, MinHeapSize)</c></tag>
 
3058
          <item>
 
3059
            <p>This changes the minimum heap size for the calling
 
3060
              process.</p>
 
3061
          </item>
 
3062
          <tag><c>process_flag(priority, Level)</c></tag>
 
3063
          <item>
 
3064
            <marker id="process_flag_priority"></marker>
 
3065
            <p>This sets the process priority. <c>Level</c> is an atom.
 
3066
              There are currently four priority levels: <c>low</c>,
 
3067
              <c>normal</c>, <c>high</c>, and <c>max</c>. The default
 
3068
              priority level is <c>normal</c>. <em>NOTE</em>: The
 
3069
              <c>max</c> priority level is reserved for internal use in
 
3070
              the Erlang runtime system, and should <em>not</em> be used
 
3071
              by others.
 
3072
            </p>
 
3073
            <p>Internally in each priority level processes are scheduled
 
3074
              in a round robin fashion.
 
3075
            </p>
 
3076
            <p>Execution of processes on priority <c>normal</c> and
 
3077
              priority <c>low</c> will be interleaved. Processes on
 
3078
              priority <c>low</c> will be selected for execution less
 
3079
              frequently than processes on priority <c>normal</c>.
 
3080
            </p>
 
3081
            <p>When there are runnable processes on priority <c>high</c>
 
3082
              no processes on priority <c>low</c>, or <c>normal</c> will
 
3083
              be selected for execution. Note, however, that this does
 
3084
              <em>not</em> mean that no processes on priority <c>low</c>,
 
3085
              or <c>normal</c> will be able to run when there are
 
3086
              processes on priority <c>high</c> running. On the runtime
 
3087
              system with SMP support there might be more processes running
 
3088
              in parallel than processes on priority <c>high</c>, i.e.,
 
3089
              a <c>low</c>, and a <c>high</c> priority process might
 
3090
              execute at the same time.
 
3091
            </p>
 
3092
            <p>When there are runnable processes on priority <c>max</c>
 
3093
              no processes on priority <c>low</c>, <c>normal</c>, or
 
3094
              <c>high</c> will be selected for execution. As with the
 
3095
              <c>high</c> priority, processes on lower priorities might
 
3096
              execute in parallel with processes on priority <c>max</c>.
 
3097
            </p>
 
3098
            <p>Scheduling is preemptive. Regardless of priority, a process
 
3099
              is preempted when it has consumed more than a certain amount
 
3100
              of reductions since the last time it was selected for
 
3101
              execution.
 
3102
            </p>
 
3103
            <p><em>NOTE</em>: You should not depend on the scheduling
 
3104
              to remain exactly as it is today. Scheduling, at least on
 
3105
              the runtime system with SMP support, is very likely to be
 
3106
              modified in the future in order to better utilize available
 
3107
              processor cores.
 
3108
            </p>
 
3109
            <p>There is currently <em>no</em> automatic mechanism for
 
3110
              avoiding priority inversion, such as priority inheritance,
 
3111
              or priority ceilings. When using priorities you have
 
3112
              to take this into account and handle such scenarios by
 
3113
              yourself.
 
3114
            </p>
 
3115
            <p>Making calls from a <c>high</c> priority process into code
 
3116
              that you don't have control over may cause the <c>high</c>
 
3117
              priority process to wait for a processes with lower
 
3118
              priority, i.e., effectively decreasing the priority of the
 
3119
              <c>high</c> priority process during the call. Even if this
 
3120
              isn't the case with one version of the code that you don't
 
3121
              have under your control, it might be the case in a future
 
3122
              version of it. This might, for example, happen if a
 
3123
              <c>high</c> priority process triggers code loading, since
 
3124
              the code server runs on priority <c>normal</c>.
 
3125
            </p>
 
3126
            <p>Other priorities than <c>normal</c> are normally not needed.
 
3127
              When other priorities are used, they need to be used
 
3128
              with care, especially the <c>high</c> priority <em>must</em>
 
3129
              be used with care. A process on <c>high</c> priority should
 
3130
              only perform work for short periods of time. Busy looping for
 
3131
              long periods of time in a <c>high</c> priority process will
 
3132
              most likely cause problems, since there are important servers
 
3133
              in OTP running on priority <c>normal</c>.
 
3134
            </p>
 
3135
          </item>
 
3136
 
 
3137
          <tag><c>process_flag(save_calls, N)</c></tag>
 
3138
          <item>
 
3139
            <p>When there are runnable processes on priority <c>max</c>
 
3140
              no processes on priority <c>low</c>, <c>normal</c>, or
 
3141
              <c>high</c> will be selected for execution. As with the
 
3142
              <c>high</c> priority, processes on lower priorities might
 
3143
              execute in parallel with processes on priority <c>max</c>.
 
3144
            </p>
 
3145
            <p><c>N</c> must be an integer in the interval 0..10000.
 
3146
              If <c>N</c> &gt; 0, call saving is made active for the
 
3147
              process, which means that information about the <c>N</c>
 
3148
              most recent global function calls, BIF calls, sends and
 
3149
              receives made by the process are saved in a list, which
 
3150
              can be retrieved with
 
3151
              <c>process_info(Pid, last_calls)</c>. A global function
 
3152
              call is one in which the module of the function is
 
3153
              explicitly mentioned. Only a fixed amount of information
 
3154
              is saved: a tuple <c>{Module, Function, Arity}</c> for
 
3155
              function calls, and the mere atoms <c>send</c>,
 
3156
              <c>'receive'</c> and <c>timeout</c> for sends and receives
 
3157
              (<c>'receive'</c> when a message is received and
 
3158
              <c>timeout</c> when a receive times out). If <c>N</c> = 0,
 
3159
              call saving is disabled for the process, which is the
 
3160
              default. Whenever the size of the call saving list is set,
 
3161
              its contents are reset.</p>
 
3162
          </item>
 
3163
          <tag><c>process_flag(sensitive, Boolean)</c></tag>
 
3164
          <item>
 
3165
            <p>Set or clear the <c>sensitive</c> flag for the current process.
 
3166
              When a process has been marked as sensitive by calling
 
3167
              <c>process_flag(sensitive, true)</c>, features in the run-time
 
3168
              system that can be used for examining the data and/or inner working
 
3169
              of the process are silently disabled.</p>
 
3170
            <p>Features that are disabled include (but are not limited to)
 
3171
              the following:</p>
 
3172
            <p>Tracing: Trace flags can still be set for the process, but no
 
3173
              trace messages of any kind will be generated.
 
3174
              (If the <c>sensitive</c> flag is turned off, trace messages will
 
3175
              again be generated if there are any trace flags set.)</p>
 
3176
            <p>Sequential tracing: The sequential trace token will be propagated
 
3177
              as usual, but no sequential trace messages will be generated.</p>
 
3178
            <p><c>process_info/1,2</c> cannot be used to read out the message
 
3179
              queue or the process dictionary (both will be returned as empty lists).</p>
 
3180
            <p>Stack back-traces cannot be displayed for the process.</p>
 
3181
            <p>In crash dumps, the stack, messages, and the process dictionary
 
3182
              will be omitted.</p>
 
3183
            <p>If <c>{save_calls,N}</c> has been set for the process, no
 
3184
              function calls will be saved to the call saving list.
 
3185
              (The call saving list will not be cleared; furthermore, send, receive,
 
3186
              and timeout events will still be added to the list.)</p>
 
3187
          </item>
 
3188
        </taglist>
 
3189
      </desc>
 
3190
    </func>
 
3191
    <func>
 
3192
      <name>process_flag(Pid, Flag, Value) -> OldValue</name>
 
3193
      <fsummary>Set process flags for a process</fsummary>
 
3194
      <type>
 
3195
        <v>Pid = pid()</v>
 
3196
        <v>Flag, Value, OldValue -- see below</v>
 
3197
      </type>
 
3198
      <desc>
 
3199
        <p>Sets certain flags for the process <c>Pid</c>, in the same
 
3200
          manner as
 
3201
          <seealso marker="#process_flag/2">process_flag/2</seealso>.
 
3202
          Returns the old value of the flag. The allowed values for
 
3203
          <c>Flag</c> are only a subset of those allowed in
 
3204
          <c>process_flag/2</c>, namely: <c>save_calls</c>.</p>
 
3205
        <p>Failure: <c>badarg</c> if <c>Pid</c> is not a local process.</p>
 
3206
      </desc>
 
3207
    </func>
 
3208
    <func>
 
3209
      <name>process_info(Pid) -> InfoResult</name>
 
3210
      <fsummary>Information about a process</fsummary>
 
3211
      <type>
 
3212
        <v>Pid = pid()</v>
 
3213
        <v>Item = atom()</v>
 
3214
        <v>Info = term()</v>
 
3215
        <v>InfoTuple = {Item, Info}</v>
 
3216
        <v>InfoTupleList = [InfoTuple]</v>
 
3217
        <v>InfoResult = InfoTupleList | undefined</v>
 
3218
      </type>
 
3219
      <desc>
 
3220
        <p>Returns a list containing <c>InfoTuple</c>s with
 
3221
          miscellaneous information about the process identified by
 
3222
          <c>Pid</c>, or <c>undefined</c> if the process is not alive.
 
3223
        </p>
 
3224
        <p>
 
3225
          The order of the <c>InfoTuple</c>s is not defined, nor
 
3226
          are all the <c>InfoTuple</c>s mandatory. The <c>InfoTuple</c>s
 
3227
          part of the result may be changed without prior notice.
 
3228
          Currently <c>InfoTuple</c>s with the following <c>Item</c>s
 
3229
          are part of the result:
 
3230
          <c>current_function</c>, <c>initial_call</c>, <c>status</c>,
 
3231
          <c>message_queue_len</c>, <c>messages</c>, <c>links</c>,
 
3232
          <c>dictionary</c>, <c>trap_exit</c>, <c>error_handler</c>,
 
3233
          <c>priority</c>, <c>group_leader</c>, <c>total_heap_size</c>,
 
3234
          <c>heap_size</c>, <c>stack_size</c>, <c>reductions</c>, and
 
3235
          <c>garbage_collection</c>.
 
3236
          If the process identified by <c>Pid</c> has a registered name
 
3237
          also an <c>InfoTuple</c> with <c>Item == registered_name</c>
 
3238
          will appear.
 
3239
        </p>
 
3240
        <p>See <seealso marker="#process_info/2">process_info/2</seealso>
 
3241
           for information about specific <c>InfoTuple</c>s.</p>
 
3242
        <warning>
 
3243
          <p>This BIF is intended for <em>debugging only</em>, use
 
3244
          <seealso marker="#process_info/2">process_info/2</seealso>
 
3245
          for all other purposes.
 
3246
          </p>
 
3247
        </warning>
 
3248
        <p>Failure: <c>badarg</c> if <c>Pid</c> is not a local process.</p>
 
3249
      </desc>
 
3250
    </func>
 
3251
    <func>
 
3252
      <name>process_info(Pid, ItemSpec) -> InfoResult</name>
 
3253
      <fsummary>Information about a process</fsummary>
 
3254
      <type>
 
3255
        <v>Pid = pid()</v>
 
3256
        <v>Item = atom()</v>
 
3257
        <v>Info = term()</v>
 
3258
        <v>ItemList = [Item]</v>
 
3259
        <v>ItemSpec = Item | ItemList</v>
 
3260
        <v>InfoTuple = {Item, Info}</v>
 
3261
        <v>InfoTupleList = [InfoTuple]</v>
 
3262
        <v>InfoResult = InfoTuple | InfoTupleList | undefined | []</v>
 
3263
      </type>
 
3264
      <desc>
 
3265
        <p>Returns information about the process identified by <c>Pid</c>
 
3266
           as specified by the <c>ItemSpec</c>, or <c>undefined</c> if the
 
3267
           process is not alive.
 
3268
        </p>
 
3269
        <p>If the process is alive and <c>ItemSpec</c> is a single
 
3270
           <c>Item</c>, the returned value is the corresponding
 
3271
           <c>InfoTuple</c> unless <c>ItemSpec == registered_name</c>
 
3272
           and the process has no registered name. In this case
 
3273
           <c>[]</c> is returned. This strange behavior is due to
 
3274
           historical reasons, and is kept for backward compatibility.
 
3275
        </p>
 
3276
        <p>If <c>ItemSpec</c> is an <c>ItemList</c>, the result is an
 
3277
           <c>InfoTupleList</c>. The <c>InfoTuple</c>s in the 
 
3278
           <c>InfoTupleList</c> will appear with the corresponding
 
3279
           <c>Item</c>s in the same order as the <c>Item</c>s appeared
 
3280
           in the <c>ItemList</c>. Valid <c>Item</c>s may appear multiple
 
3281
           times in the <c>ItemList</c>.
 
3282
        </p>
 
3283
         <note><p>If <c>registered_name</c> is part of an <c>ItemList</c>
 
3284
                  and the process has no name registered a
 
3285
                  <c>{registered_name, []}</c> <c>InfoTuple</c> <em>will</em>
 
3286
                  appear in the resulting <c>InfoTupleList</c>. This
 
3287
                  behavior is different than when
 
3288
                  <c>ItemSpec == registered_name</c>, and than when
 
3289
                  <c>process_info/1</c> is used.
 
3290
        </p></note>
 
3291
        <p>Currently the following <c>InfoTuple</c>s with corresponding
 
3292
           <c>Item</c>s are valid:</p>
 
3293
        <taglist>
 
3294
          <tag><c>{backtrace, Bin}</c></tag>
 
3295
          <item>
 
3296
            <p>The binary <c>Bin</c> contains the same information as
 
3297
              the output from
 
3298
              <c>erlang:process_display(Pid, backtrace)</c>. Use
 
3299
              <c>binary_to_list/1</c> to obtain the string of characters
 
3300
              from the binary.</p>
 
3301
          </item>
 
3302
          <tag><c>{binary, BinInfo}</c></tag>
 
3303
          <item>
 
3304
            <p><c>BinInfo</c> is a list containing miscellaneous information
 
3305
              about binaries currently being referred to by this process.
 
3306
              This <c>InfoTuple</c> may be changed or removed without prior
 
3307
              notice.</p>
 
3308
          </item>
 
3309
          <tag><c>{catchlevel, CatchLevel}</c></tag>
 
3310
          <item>
 
3311
            <p><c>CatchLevel</c> is the number of currently active
 
3312
            catches in this process. This <c>InfoTuple</c> may be
 
3313
            changed or removed without prior notice.</p>
 
3314
          </item>
 
3315
          <tag><c>{current_function, {Module, Function, Args}}</c></tag>
 
3316
          <item>
 
3317
            <p><c>Module</c>, <c>Function</c>, <c>Args</c> is
 
3318
              the current function call of the process.</p>
 
3319
          </item>
 
3320
          <tag><c>{dictionary, Dictionary}</c></tag>
 
3321
          <item>
 
3322
            <p><c>Dictionary</c> is the dictionary of the process.</p>
 
3323
          </item>
 
3324
          <tag><c>{error_handler, Module}</c></tag>
 
3325
          <item>
 
3326
            <p><c>Module</c> is the error handler module used by
 
3327
              the process (for undefined function calls, for example).</p>
 
3328
          </item>
 
3329
          <tag><c>{garbage_collection, GCInfo}</c></tag>
 
3330
          <item>
 
3331
            <p><c>GCInfo</c> is a list which contains miscellaneous
 
3332
               information about garbage collection for this process.
 
3333
               The content of <c>GCInfo</c> may be changed without
 
3334
               prior notice.</p>
 
3335
          </item>
 
3336
          <tag><c>{group_leader, GroupLeader}</c></tag>
 
3337
          <item>
 
3338
            <p><c>GroupLeader</c> is group leader for the IO of
 
3339
              the process.</p>
 
3340
          </item>
 
3341
          <tag><c>{heap_size, Size}</c></tag>
 
3342
          <item>
 
3343
            <p><c>Size</c> is the size in words of youngest heap generation
 
3344
            of the process. This generation currently include the stack
 
3345
            of the process. This information is highly implementation
 
3346
            dependent, and may change if the implementation change.
 
3347
            </p>
 
3348
          </item>
 
3349
          <tag><c>{initial_call, {Module, Function, Arity}}</c></tag>
 
3350
          <item>
 
3351
            <p><c>Module</c>, <c>Function</c>, <c>Arity</c> is
 
3352
              the initial function call with which the process was
 
3353
              spawned.</p>
 
3354
          </item>
 
3355
          <tag><c>{links, Pids}</c></tag>
 
3356
          <item>
 
3357
            <p><c>Pids</c> is a list of pids, with processes to
 
3358
              which the process has a link.</p>
 
3359
          </item>
 
3360
          <tag><c>{last_calls, false|Calls}</c></tag>
 
3361
          <item>
 
3362
            <p>The value is <c>false</c> if call saving is not active
 
3363
              for the process (see
 
3364
              <seealso marker="#process_flag/3">process_flag/3</seealso>).
 
3365
              If call saving is active, a list is returned, in which
 
3366
              the last element is the most recent called.</p>
 
3367
          </item>
 
3368
          <tag><c>{memory, Size}</c></tag>
 
3369
          <item>
 
3370
            <p><c>Size</c> is the size in bytes of the process. This
 
3371
              includes call stack, heap and internal structures.</p>
 
3372
          </item>
 
3373
          <tag><c>{message_binary, BinInfo}</c></tag>
 
3374
          <item>
 
3375
            <p><c>BinInfo</c> is a list containing miscellaneous information
 
3376
              about binaries currently being referred to by the message
 
3377
              area. This <c>InfoTuple</c> is only valid on an emulator
 
3378
              using the hybrid heap type. This <c>InfoTuple</c> may be
 
3379
              changed or removed without prior notice.</p>
 
3380
          </item>
 
3381
          <tag><c>{message_queue_len, MessageQueueLen}</c></tag>
 
3382
          <item>
 
3383
            <p><c>MessageQueueLen</c> is the number of messages
 
3384
              currently in the message queue of the process. This is
 
3385
              the length of the list <c>MessageQueue</c> returned as
 
3386
              the info item <c>messages</c> (see below).</p>
 
3387
          </item>
 
3388
          <tag><c>{messages, MessageQueue}</c></tag>
 
3389
          <item>
 
3390
            <p><c>MessageQueue</c> is a list of the messages to
 
3391
              the process, which have not yet been processed.</p>
 
3392
          </item>
 
3393
          <tag><c>{monitored_by, Pids}</c></tag>
 
3394
          <item>
 
3395
            <p>A list of pids that are monitoring the process (with
 
3396
              <c>erlang:monitor/2</c>).</p>
 
3397
          </item>
 
3398
          <tag><c>{monitors, Monitors}</c></tag>
 
3399
          <item>
 
3400
            <p>A list of monitors (started by <c>erlang:monitor/2</c>)
 
3401
              that are active for the process. For a local process
 
3402
              monitor or a remote process monitor by pid, the list item
 
3403
              is <c>{process, Pid}</c>, and for a remote process
 
3404
              monitor by name, the list item is
 
3405
              <c>{process, {RegName, Node}}</c>.</p>
 
3406
          </item>
 
3407
          <tag><c>{priority, Level}</c></tag>
 
3408
          <item>
 
3409
            <p><c>Level</c> is the current priority level for
 
3410
              the process. For more information on priorities see
 
3411
              <seealso marker="#process_flag_priority">process_flag(priority, Level)</seealso>.</p>
 
3412
          </item>
 
3413
          <tag><c>{reductions, Number}</c></tag>
 
3414
          <item>
 
3415
            <p><c>Number</c> is the number of reductions executed by
 
3416
              the process.</p>
 
3417
          </item>
 
3418
          <tag><c>{registered_name, Atom}</c></tag>
 
3419
          <item>
 
3420
            <p><c>Atom</c> is the registered name of the process. If
 
3421
              the process has no registered name, this tuple is not
 
3422
              present in the list.</p>
 
3423
          </item>
 
3424
          <tag><c>{sequential_trace_token, [] | SequentialTraceToken}</c></tag>
 
3425
          <item>
 
3426
            <p><c>SequentialTraceToken</c> the sequential trace token for
 
3427
            the process. This <c>InfoTuple</c> may be changed or removed
 
3428
            without prior notice.</p>
 
3429
          </item>
 
3430
          <tag><c>{stack_size, Size}</c></tag>
 
3431
          <item>
 
3432
            <p><c>Size</c> is the stack size of the process in words.</p>
 
3433
          </item>
 
3434
          <tag><c>{status, Status}</c></tag>
 
3435
          <item>
 
3436
            <p><c>Status</c> is the status of the process. <c>Status</c>
 
3437
              is <c>waiting</c> (waiting for a message), <c>running</c>,
 
3438
              <c>runnable</c> (ready to run, but another process is
 
3439
              running), or <c>suspended</c> (suspended on a "busy" port
 
3440
              or by the <c>erlang:suspend_process/[1,2]</c> BIF).</p>
 
3441
          </item>
 
3442
          <tag><c>{suspending, SuspendeeList}</c></tag>
 
3443
          <item>
 
3444
            <p><c>SuspendeeList</c> is a list of <c>{Suspendee,
 
3445
            ActiveSuspendCount, OutstandingSuspendCount}</c> tuples.
 
3446
            <c>Suspendee</c> is the pid of a process that have been or is to
 
3447
            be suspended by the process identified by <c>Pid</c> via the
 
3448
            <seealso marker="#erlang:suspend_process/2">erlang:suspend_process/2</seealso>
 
3449
            BIF, or the
 
3450
            <seealso marker="#erlang:suspend_process/1">erlang:suspend_process/1</seealso>
 
3451
            BIF. <c>ActiveSuspendCount</c> is the number of times the
 
3452
            <c>Suspendee</c> has been suspended by <c>Pid</c>.
 
3453
            <c>OutstandingSuspendCount</c> is the number of not yet
 
3454
            completed suspend requests sent by <c>Pid</c>. That is,
 
3455
            if <c>ActiveSuspendCount /= 0</c>, <c>Suspendee</c> is
 
3456
            currently in the suspended state, and if
 
3457
            <c>OutstandingSuspendCount /= 0</c> the <c>asynchronous</c>
 
3458
            option of <c>erlang:suspend_process/2</c> has been used and
 
3459
            the suspendee has not yet been suspended by <c>Pid</c>.
 
3460
            Note that the <c>ActiveSuspendCount</c> and
 
3461
            <c>OutstandingSuspendCount</c> are not the total suspend count
 
3462
            on <c>Suspendee</c>, only the parts contributed by <c>Pid</c>.
 
3463
            </p>
 
3464
          </item>
 
3465
          <tag><c>{total_heap_size, Size}</c></tag>
 
3466
          <item>
 
3467
            <p><c>Size</c> is the total size in words of all heap
 
3468
            fragments of the process. This currently include the stack
 
3469
            of the process.
 
3470
            </p>
 
3471
          </item>
 
3472
          <tag><c>{trace, InternalTraceFlags}</c></tag>
 
3473
          <item>
 
3474
            <p><c>InternalTraceFlags</c> is an integer representing
 
3475
            internal trace flag for this process. This <c>InfoTuple</c>
 
3476
            may be changed or removed without prior notice.</p>
 
3477
          </item>
 
3478
          <tag><c>{trap_exit, Boolean}</c></tag>
 
3479
          <item>
 
3480
            <p><c>Boolean</c> is <c>true</c> if the process is trapping
 
3481
              exits, otherwise it is <c>false</c>.</p>
 
3482
          </item>
 
3483
        </taglist>
 
3484
        <p>Note however, that not all implementations support every one
 
3485
          of the above <c>Items</c>.</p>
 
3486
        <p>Failure: <c>badarg</c> if <c>Pid</c> is not a local process,
 
3487
        or if <c>Item</c> is not a valid <c>Item</c>.</p>
 
3488
      </desc>
 
3489
    </func>
 
3490
    <func>
 
3491
      <name>processes() -> [pid()]</name>
 
3492
      <fsummary>All processes</fsummary>
 
3493
      <desc>
 
3494
        <p>Returns a list of process identifiers corresponding to
 
3495
           all the processes currently existing on the local node.
 
3496
        </p>
 
3497
        <p>Note that a process that is exiting, exists but is not alive, i.e.,
 
3498
           <c>is_process_alive/1</c> will return <c>false</c> for a process
 
3499
           that is exiting, but its process identifier will be part
 
3500
           of the result returned from <c>processes/0</c>.
 
3501
        </p>
 
3502
        <pre>
 
3503
> <input>processes().</input>
 
3504
[&lt;0.0.0&gt;,&lt;0.2.0&gt;,&lt;0.4.0&gt;,&lt;0.5.0&gt;,&lt;0.7.0&gt;,&lt;0.8.0&gt;]</pre>
 
3505
      </desc>
 
3506
    </func>
 
3507
    <func>
 
3508
      <name>purge_module(Module) -> void()</name>
 
3509
      <fsummary>Remove old code for a module</fsummary>
 
3510
      <type>
 
3511
        <v>Module = atom()</v>
 
3512
      </type>
 
3513
      <desc>
 
3514
        <p>Removes old code for <c>Module</c>. Before this BIF is used,
 
3515
          <c>erlang:check_process_code/2</c> should be called to check
 
3516
          that no processes are executing old code in the module.</p>
 
3517
        <warning>
 
3518
          <p>This BIF is intended for the code server (see
 
3519
            <seealso marker="code">code(3)</seealso>) and should not be
 
3520
            used elsewhere.</p>
 
3521
        </warning>
 
3522
        <p>Failure: <c>badarg</c> if there is no old code for
 
3523
          <c>Module</c>.</p>
 
3524
      </desc>
 
3525
    </func>
 
3526
    <func>
 
3527
      <name>put(Key, Val) -> OldVal | undefined</name>
 
3528
      <fsummary>Add a new value to the process dictionary</fsummary>
 
3529
      <type>
 
3530
        <v>Key = Val = OldVal = term()</v>
 
3531
      </type>
 
3532
      <desc>
 
3533
        <p>Adds a new <c>Key</c> to the process dictionary, associated
 
3534
          with the value <c>Val</c>, and returns <c>undefined</c>. If
 
3535
          <c>Key</c> already exists, the old value is deleted and
 
3536
          replaced by <c>Val</c> and the function returns the old value.</p>
 
3537
        <note>
 
3538
          <p>The values stored when <c>put</c> is evaluated within
 
3539
            the scope of a <c>catch</c> will not be retracted if a
 
3540
            <c>throw</c> is evaluated, or if an error occurs.</p>
 
3541
        </note>
 
3542
        <pre>
 
3543
> <input>X = put(name, walrus), Y = put(name, carpenter),</input>
 
3544
<input>Z = get(name),</input>
 
3545
<input>{X, Y, Z}.</input>
 
3546
{undefined,walrus,carpenter}</pre>
 
3547
      </desc>
 
3548
    </func>
 
3549
    <func>
 
3550
      <name>erlang:raise(Class, Reason, Stacktrace)</name>
 
3551
      <fsummary>Stop execution with an exception of given class, reason and call stack backtrace</fsummary>
 
3552
      <type>
 
3553
        <v>Class = error | exit | throw</v>
 
3554
        <v>Reason = term()</v>
 
3555
        <v>Stacktrace = [{Module, Function, Arity | Args} | {Fun, Args}]</v>
 
3556
        <v>&nbsp;Module = Function = atom()</v>
 
3557
        <v>&nbsp;Arity = int()</v>
 
3558
        <v>&nbsp;Args = [term()]</v>
 
3559
        <v>&nbsp;Fun = [fun()]</v>
 
3560
      </type>
 
3561
      <desc>
 
3562
        <p>Stops the execution of the calling process with an
 
3563
          exception of given class, reason and call stack backtrace
 
3564
          (<em>stacktrace</em>).</p>
 
3565
        <warning>
 
3566
          <p>This BIF is intended for debugging and for use in
 
3567
            the Erlang operating system. In general, it should
 
3568
            be avoided in applications, unless you know
 
3569
            very well what you are doing.</p>
 
3570
        </warning>
 
3571
        <p><c>Class</c> is one of <c>error</c>, <c>exit</c> or
 
3572
          <c>throw</c>, so if it were not for the stacktrace
 
3573
          <c>erlang:raise(Class, Reason, Stacktrace)</c> is
 
3574
          equivalent to <c>erlang:Class(Reason)</c>.
 
3575
          <c>Reason</c> is any term and <c>Stacktrace</c> is a list as
 
3576
          returned from <c>get_stacktrace()</c>, that is a list of
 
3577
          3-tuples <c>{Module, Function, Arity | Args}</c> where
 
3578
          <c>Module</c> and <c>Function</c> are atoms and the third
 
3579
          element is an integer arity or an argument list. The
 
3580
          stacktrace may also contain <c>{Fun, Args}</c> tuples where
 
3581
          <c>Fun</c> is a local fun and <c>Args</c> is an argument list.</p>
 
3582
        <p>The stacktrace is used as the exception stacktrace for the
 
3583
          calling process; it will be truncated to the current
 
3584
          maximum stacktrace depth.</p>
 
3585
        <p>Because evaluating this function causes the process to
 
3586
          terminate, it has no return value - unless the arguments are
 
3587
          invalid, in which case the function <em>returns the error reason</em>, that is <c>badarg</c>. If you want to be
 
3588
          really sure not to return you can call
 
3589
          <c>erlang:error(erlang:raise(Class, Reason, Stacktrace))</c>
 
3590
          and hope to distinguish exceptions later.</p>
 
3591
      </desc>
 
3592
    </func>
 
3593
    <func>
 
3594
      <name>erlang:read_timer(TimerRef) -> int() | false</name>
 
3595
      <fsummary>Number of milliseconds remaining for a timer</fsummary>
 
3596
      <type>
 
3597
        <v>TimerRef = ref()</v>
 
3598
      </type>
 
3599
      <desc>
 
3600
        <p><c>TimerRef</c> is a timer reference returned by
 
3601
          <seealso marker="#erlang:send_after/3">erlang:send_after/3</seealso>
 
3602
          or
 
3603
          <seealso marker="#erlang:start_timer/3">erlang:start_timer/3</seealso>.
 
3604
          If the timer is active, the function returns the time in
 
3605
          milliseconds left until the timer will expire, otherwise
 
3606
          <c>false</c> (which means that <c>TimerRef</c> was never a
 
3607
          timer, that it has been cancelled, or that it has already
 
3608
          delivered its message).</p>
 
3609
        <p>See also 
 
3610
          <seealso marker="#erlang:send_after/3">erlang:send_after/3</seealso>,
 
3611
          <seealso marker="#erlang:start_timer/3">erlang:start_timer/3</seealso>,
 
3612
          and
 
3613
          <seealso marker="#erlang:cancel_timer/1">erlang:cancel_timer/1</seealso>.</p>
 
3614
      </desc>
 
3615
    </func>
 
3616
    <func>
 
3617
      <name>erlang:ref_to_list(Ref) -> string()</name>
 
3618
      <fsummary>Text representation of a reference</fsummary>
 
3619
      <type>
 
3620
        <v>Ref = ref()</v>
 
3621
      </type>
 
3622
      <desc>
 
3623
        <p>Returns a string which corresponds to the text
 
3624
          representation of <c>Ref</c>.</p>
 
3625
        <warning>
 
3626
          <p>This BIF is intended for debugging and for use in
 
3627
            the Erlang operating system. It should not be used in
 
3628
            application programs.</p>
 
3629
        </warning>
 
3630
      </desc>
 
3631
    </func>
 
3632
    <func>
 
3633
      <name>register(RegName, Pid | Port) -> true</name>
 
3634
      <fsummary>Register a name for a pid (or port)</fsummary>
 
3635
      <type>
 
3636
        <v>RegName = atom()</v>
 
3637
        <v>Pid = pid()</v>
 
3638
        <v>Port = port()</v>
 
3639
      </type>
 
3640
      <desc>
 
3641
        <p>Associates the name <c>RegName</c> with a pid or a port
 
3642
          identifier. <c>RegName</c>, which must be an atom, can be used
 
3643
          instead of the pid / port identifier in the send operator
 
3644
          (<c>RegName ! Message</c>).</p>
 
3645
        <pre>
 
3646
> <input>register(db, Pid).</input>
 
3647
true</pre>
 
3648
        <p>Failure: <c>badarg</c> if <c>Pid</c> is not an existing,
 
3649
          local process or port, if <c>RegName</c> is already in use,
 
3650
          if the process or port is already registered (already has a
 
3651
          name), or if <c>RegName</c> is the atom <c>undefined</c>.</p>
 
3652
      </desc>
 
3653
    </func>
 
3654
    <func>
 
3655
      <name>registered() -> [RegName]</name>
 
3656
      <fsummary>All registered names</fsummary>
 
3657
      <type>
 
3658
        <v>RegName = atom()</v>
 
3659
      </type>
 
3660
      <desc>
 
3661
        <p>Returns a list of names which have been registered using
 
3662
          <seealso marker="#register/2">register/2</seealso>.</p>
 
3663
        <pre>
 
3664
> <input>registered().</input>
 
3665
[code_server, file_server, init, user, my_db]</pre>
 
3666
      </desc>
 
3667
    </func>
 
3668
    <func>
 
3669
      <name>erlang:resume_process(Suspendee) -> true</name>
 
3670
      <fsummary>Resume a suspended process</fsummary>
 
3671
      <type>
 
3672
        <v>Suspendee = pid()</v>
 
3673
      </type>
 
3674
      <desc>
 
3675
        <p>Decreases the suspend count on the process identified by
 
3676
        <c>Suspendee</c>. <c>Suspendee</c> should previously have been
 
3677
        suspended via
 
3678
        <seealso marker="#erlang:suspend_process/2">erlang:suspend_process/2</seealso>,
 
3679
        or
 
3680
        <seealso marker="#erlang:suspend_process/1">erlang:suspend_process/1</seealso>
 
3681
        by the process calling <c>erlang:resume_process(Suspendee)</c>. When
 
3682
        the suspend count on <c>Suspendee</c> reach zero, <c>Suspendee</c>
 
3683
        will be resumed, i.e., the state of the <c>Suspendee</c> is changed
 
3684
        from suspended into the state <c>Suspendee</c> was in before it was
 
3685
        suspended.
 
3686
        </p>
 
3687
        <warning>
 
3688
          <p>This BIF is intended for debugging only.</p>
 
3689
        </warning>
 
3690
        <p>Failures:</p>
 
3691
        <taglist>
 
3692
          <tag><c>badarg</c></tag>
 
3693
          <item>
 
3694
          If <c>Suspendee</c> isn't a process identifier.
 
3695
          </item>
 
3696
          <tag><c>badarg</c></tag>
 
3697
          <item>
 
3698
          If the process calling <c>erlang:resume_process/1</c> had
 
3699
          not previously increased the suspend count on the process
 
3700
          identified by <c>Suspendee</c>.
 
3701
          </item>
 
3702
          <tag><c>badarg</c></tag>
 
3703
          <item>
 
3704
          If the process identified by <c>Suspendee</c> is not alive.
 
3705
          </item>
 
3706
        </taglist>
 
3707
      </desc>
 
3708
    </func>
 
3709
    <func>
 
3710
      <name>round(Number) -> int()</name>
 
3711
      <fsummary>Return an integer by rounding a number</fsummary>
 
3712
      <type>
 
3713
        <v>Number = number()</v>
 
3714
      </type>
 
3715
      <desc>
 
3716
        <p>Returns an integer by rounding <c>Number</c>.</p>
 
3717
        <pre>
 
3718
> <input>round(5.5).</input>
 
3719
6</pre>
 
3720
        <p>Allowed in guard tests.</p>
 
3721
      </desc>
 
3722
    </func>
 
3723
    <func>
 
3724
      <name>self() -> pid()</name>
 
3725
      <fsummary>Pid of the calling process</fsummary>
 
3726
      <desc>
 
3727
        <p>Returns the pid (process identifier) of the calling process.</p>
 
3728
        <pre>
 
3729
> <input>self().</input>
 
3730
&lt;0.26.0></pre>
 
3731
        <p>Allowed in guard tests.</p>
 
3732
      </desc>
 
3733
    </func>
 
3734
    <func>
 
3735
      <name>erlang:send(Dest, Msg) -> Msg</name>
 
3736
      <fsummary>Send a message</fsummary>
 
3737
      <type>
 
3738
        <v>Dest = pid() | port() | RegName | {RegName, Node}</v>
 
3739
        <v>Msg = term()</v>
 
3740
        <v>&nbsp;RegName = atom()</v>
 
3741
        <v>&nbsp;Node = node()</v>
 
3742
      </type>
 
3743
      <desc>
 
3744
        <p>Sends a message and returns <c>Msg</c>. This is the same as
 
3745
          <c>Dest ! Msg</c>.</p>
 
3746
        <p><c>Dest</c> may be a remote or local pid, a (local) port, a
 
3747
          locally registered name, or a tuple <c>{RegName, Node}</c>
 
3748
          for a registered name at another node.</p>
 
3749
      </desc>
 
3750
    </func>
 
3751
    <func>
 
3752
      <name>erlang:send(Dest, Msg, [Option]) -> Res</name>
 
3753
      <fsummary>Send a message conditionally</fsummary>
 
3754
      <type>
 
3755
        <v>Dest = pid() | port() | RegName | {RegName, Node}</v>
 
3756
        <v>&nbsp;RegName = atom()</v>
 
3757
        <v>&nbsp;Node = node()</v>
 
3758
        <v>Msg = term()</v>
 
3759
        <v>Option = nosuspend | noconnect</v>
 
3760
        <v>Res = ok | nosuspend | noconnect</v>
 
3761
      </type>
 
3762
      <desc>
 
3763
        <p>Sends a message and returns <c>ok</c>, or does not send
 
3764
          the message but returns something else (see below). Otherwise
 
3765
          the same as
 
3766
          <seealso marker="#erlang:send/2">erlang:send/2</seealso>. See
 
3767
          also
 
3768
          <seealso marker="#erlang:send_nosuspend/2">erlang:send_nosuspend/2,3</seealso>.
 
3769
          for more detailed explanation and warnings.</p>
 
3770
        <p>The possible options are:</p>
 
3771
        <taglist>
 
3772
          <tag><c>nosuspend</c></tag>
 
3773
          <item>
 
3774
            <p>If the sender would have to be suspended to do the send,
 
3775
              <c>nosuspend</c> is returned instead.</p>
 
3776
          </item>
 
3777
          <tag><c>noconnect</c></tag>
 
3778
          <item>
 
3779
            <p>If the destination node would have to be auto-connected
 
3780
              before doing the send, <c>noconnect</c> is returned
 
3781
              instead.</p>
 
3782
          </item>
 
3783
        </taglist>
 
3784
        <warning>
 
3785
          <p>As with <c>erlang:send_nosuspend/2,3</c>: Use with extreme
 
3786
            care!</p>
 
3787
        </warning>
 
3788
      </desc>
 
3789
    </func>
 
3790
    <func>
 
3791
      <name>erlang:send_after(Time, Dest, Msg) -> TimerRef</name>
 
3792
      <fsummary>Start a timer</fsummary>
 
3793
      <type>
 
3794
        <v>Time = int()</v>
 
3795
        <v>&nbsp;0 &lt;= Time &lt;= 4294967295</v>
 
3796
        <v>Dest = pid() | RegName </v>
 
3797
        <v>&nbsp;LocalPid = pid() (of a process, alive or dead, on the local node)</v>
 
3798
        <v>Msg = term()</v>
 
3799
        <v>TimerRef = ref()</v>
 
3800
      </type>
 
3801
      <desc>
 
3802
        <p>Starts a timer which will send the message <c>Msg</c>
 
3803
          to <c>Dest</c> after <c>Time</c> milliseconds.</p>
 
3804
        <p>If <c>Dest</c> is an atom, it is supposed to be the name of
 
3805
          a registered process. The process referred to by the name is
 
3806
          looked up at the time of delivery. No error is given if
 
3807
          the name does not refer to a process.</p>
 
3808
        <p>If <c>Dest</c> is a pid, the timer will be automatically
 
3809
          canceled if the process referred to by the pid is not alive,
 
3810
          or when the process exits. This feature was introduced in
 
3811
          erts version 5.4.11. Note that timers will not be
 
3812
          automatically canceled when <c>Dest</c> is an atom.</p>
 
3813
        <p>See also
 
3814
          <seealso marker="#erlang:start_timer/3">erlang:start_timer/3</seealso>,
 
3815
          <seealso marker="#erlang:cancel_timer/1">erlang:cancel_timer/1</seealso>,
 
3816
          and
 
3817
          <seealso marker="#erlang:read_timer/1">erlang:read_timer/1</seealso>.</p>
 
3818
        <p>Failure: <c>badarg</c> if the arguments does not satisfy
 
3819
          the requirements specified above.</p>
 
3820
      </desc>
 
3821
    </func>
 
3822
    <func>
 
3823
      <name>erlang:send_nosuspend(Dest, Msg) -> bool()</name>
 
3824
      <fsummary>Try to send a message without ever blocking</fsummary>
 
3825
      <type>
 
3826
        <v>Dest = pid() | port() | RegName | {RegName, Node}</v>
 
3827
        <v>&nbsp;RegName = atom()</v>
 
3828
        <v>&nbsp;Node = node()</v>
 
3829
        <v>Msg = term()</v>
 
3830
      </type>
 
3831
      <desc>
 
3832
        <p>The same as
 
3833
          <seealso marker="#erlang:send/3">erlang:send(Dest, Msg, [nosuspend])</seealso>, but returns <c>true</c> if
 
3834
          the message was sent and <c>false</c> if the message was not
 
3835
          sent because the sender would have had to be suspended.</p>
 
3836
        <p>This function is intended for send operations towards an
 
3837
          unreliable remote node without ever blocking the sending
 
3838
          (Erlang) process. If the connection to the remote node
 
3839
          (usually not a real Erlang node, but a node written in C or
 
3840
          Java) is overloaded, this function <em>will not send the message</em> but return <c>false</c> instead.</p>
 
3841
        <p>The same happens, if <c>Dest</c> refers to a local port that
 
3842
          is busy. For all other destinations (allowed for the ordinary
 
3843
          send operator <c>'!'</c>) this function sends the message and
 
3844
          returns <c>true</c>.</p>
 
3845
        <p>This function is only to be used in very rare circumstances
 
3846
          where a process communicates with Erlang nodes that can
 
3847
          disappear without any trace causing the TCP buffers and
 
3848
          the drivers queue to be over-full before the node will actually
 
3849
          be shut down (due to tick timeouts) by <c>net_kernel</c>. The
 
3850
          normal reaction to take when this happens is some kind of
 
3851
          premature shutdown of the other node.</p>
 
3852
        <p>Note that ignoring the return value from this function would
 
3853
          result in <em>unreliable</em> message passing, which is
 
3854
          contradictory to the Erlang programming model. The message is
 
3855
          <em>not</em> sent if this function returns <c>false</c>.</p>
 
3856
        <p>Note also that in many systems, transient states of
 
3857
          overloaded queues are normal. The fact that this function
 
3858
          returns <c>false</c> does not in any way mean that the other
 
3859
          node is guaranteed to be non-responsive, it could be a
 
3860
          temporary overload. Also a return value of <c>true</c> does
 
3861
          only mean that the message could be sent on the (TCP) channel
 
3862
          without blocking, the message is not guaranteed to have
 
3863
          arrived at the remote node. Also in the case of a disconnected
 
3864
          non-responsive node, the return value is <c>true</c> (mimics
 
3865
          the behaviour of the <c>!</c> operator). The expected
 
3866
          behaviour as well as the actions to take when the function
 
3867
          returns <c>false</c> are application and hardware specific.</p>
 
3868
        <warning>
 
3869
          <p>Use with extreme care!</p>
 
3870
        </warning>
 
3871
      </desc>
 
3872
    </func>
 
3873
    <func>
 
3874
      <name>erlang:send_nosuspend(Dest, Msg, Options) -> bool()</name>
 
3875
      <fsummary>Try to send a message without ever blocking</fsummary>
 
3876
      <type>
 
3877
        <v>Dest = pid() | port() | RegName | {RegName, Node}</v>
 
3878
        <v>&nbsp;RegName = atom()</v>
 
3879
        <v>&nbsp;Node = node()</v>
 
3880
        <v>Msg = term()</v>
 
3881
        <v>Option = noconnect</v>
 
3882
      </type>
 
3883
      <desc>
 
3884
        <p>The same as
 
3885
          <seealso marker="#erlang:send/3">erlang:send(Dest, Msg, [nosuspend | Options])</seealso>,
 
3886
          but with boolean return value.</p>
 
3887
        <p>This function behaves like
 
3888
          <seealso marker="#erlang:send_nosuspend/2">erlang:send_nosuspend/2)</seealso>,
 
3889
          but takes a third parameter, a list of options. The only
 
3890
          currently implemented option is <c>noconnect</c>. The option
 
3891
          <c>noconnect</c> makes the function return <c>false</c> if
 
3892
          the remote node is not currently reachable by the local
 
3893
          node. The normal behaviour is to try to connect to the node,
 
3894
          which may stall the process for a shorter period. The use of
 
3895
          the <c>noconnect</c> option makes it possible to be
 
3896
          absolutely sure not to get even the slightest delay when
 
3897
          sending to a remote process. This is especially useful when
 
3898
          communicating with nodes who expect to always be
 
3899
          the connecting part (i.e. nodes written in C or Java).</p>
 
3900
        <p>Whenever the function returns <c>false</c> (either when a
 
3901
          suspend would occur or when <c>noconnect</c> was specified and
 
3902
          the node was not already connected), the message is guaranteed
 
3903
          <em>not</em> to have been sent.</p>
 
3904
        <warning>
 
3905
          <p>Use with extreme care!</p>
 
3906
        </warning>
 
3907
      </desc>
 
3908
    </func>
 
3909
    <func>
 
3910
      <name>erlang:set_cookie(Node, Cookie) -> true</name>
 
3911
      <fsummary>Set the magic cookie of a node</fsummary>
 
3912
      <type>
 
3913
        <v>Node = node()</v>
 
3914
        <v>Cookie = atom()</v>
 
3915
      </type>
 
3916
      <desc>
 
3917
        <p>Sets the magic cookie of <c>Node</c> to the atom
 
3918
          <c>Cookie</c>. If <c>Node</c> is the local node, the function
 
3919
          also sets the cookie of all other unknown nodes to
 
3920
          <c>Cookie</c> (see
 
3921
          <seealso marker="doc/reference_manual:distributed">Distributed Erlang</seealso> in the Erlang Reference Manual).</p>
 
3922
        <p>Failure: <c>function_clause</c> if the local node is not
 
3923
          alive.</p>
 
3924
      </desc>
 
3925
    </func>
 
3926
    <func>
 
3927
      <name>setelement(Index, Tuple1, Value) -> Tuple2</name>
 
3928
      <fsummary>Set Nth element of a tuple</fsummary>
 
3929
      <type>
 
3930
        <v>Index = 1..tuple_size(Tuple1)</v>
 
3931
        <v>Tuple1 = Tuple2 = tuple()</v>
 
3932
        <v>Value = term()</v>
 
3933
      </type>
 
3934
      <desc>
 
3935
        <p>Returns a tuple which is a copy of the argument <c>Tuple1</c>
 
3936
          with the element given by the integer argument <c>Index</c>
 
3937
          (the first element is the element with index 1) replaced by
 
3938
          the argument <c>Value</c>.</p>
 
3939
        <pre>
 
3940
> <input>setelement(2, {10, green, bottles}, red).</input>
 
3941
{10,red,bottles}</pre>
 
3942
      </desc>
 
3943
    </func>
 
3944
    <func>
 
3945
      <name>size(Item) -> int()</name>
 
3946
      <fsummary>Size of a tuple or binary</fsummary>
 
3947
      <type>
 
3948
        <v>Item = tuple() | binary()</v>
 
3949
      </type>
 
3950
      <desc>
 
3951
        <p>Returns an integer which is the size of the argument
 
3952
          <c>Item</c>,  which must be either a tuple or a binary.</p>
 
3953
        <pre>
 
3954
> <input>size({morni, mulle, bwange}).</input>
 
3955
3</pre>
 
3956
        <p>Allowed in guard tests.</p>
 
3957
      </desc>
 
3958
    </func>
 
3959
    <func>
 
3960
      <name>spawn(Fun) -> pid()</name>
 
3961
      <fsummary>Create a new process with a fun as entry point</fsummary>
 
3962
      <type>
 
3963
        <v>Fun = fun()</v>
 
3964
      </type>
 
3965
      <desc>
 
3966
        <p>Returns the pid of a new process started by the application
 
3967
          of <c>Fun</c> to the empty list <c>[]</c>. Otherwise works
 
3968
          like <seealso marker="#spawn/3">spawn/3</seealso>.</p>
 
3969
      </desc>
 
3970
    </func>
 
3971
    <func>
 
3972
      <name>spawn(Node, Fun) -> pid()</name>
 
3973
      <fsummary>Create a new process with a fun as entry point on a given node</fsummary>
 
3974
      <type>
 
3975
        <v>Node = node()</v>
 
3976
        <v>Fun = fun()</v>
 
3977
      </type>
 
3978
      <desc>
 
3979
        <p>Returns the pid of a new process started by the application
 
3980
          of <c>Fun</c> to the empty list <c>[]</c> on <c>Node</c>. If
 
3981
          <c>Node</c> does not exist, a useless pid is returned.
 
3982
          Otherwise works like
 
3983
          <seealso marker="#spawn/3">spawn/3</seealso>.</p>
 
3984
      </desc>
 
3985
    </func>
 
3986
    <func>
 
3987
      <name>spawn(Module, Function, Args) -> pid()</name>
 
3988
      <fsummary>Create a new process with a function as entry point</fsummary>
 
3989
      <type>
 
3990
        <v>Module = Function = atom()</v>
 
3991
        <v>Args = [term()]</v>
 
3992
      </type>
 
3993
      <desc>
 
3994
        <p>Returns the pid of a new process started by the application
 
3995
          of <c>Module:Function</c> to <c>Args</c>. The new process
 
3996
          created will be placed in the system scheduler queue and be
 
3997
          run some time later.</p>
 
3998
        <p><c>error_handler:undefined_function(Module, Function, Args)</c> is evaluated by the new process if
 
3999
          <c>Module:Function/Arity</c> does not exist (where
 
4000
          <c>Arity</c> is the length of <c>Args</c>). The error handler
 
4001
          can be redefined (see
 
4002
          <seealso marker="#process_flag/2">process_flag/2</seealso>).
 
4003
          If <c>error_handler</c> is undefined, or the user has
 
4004
          redefined the default <c>error_handler</c> its replacement is
 
4005
          undefined, a failure with the reason <c>undef</c> will occur.</p>
 
4006
        <pre>
 
4007
> <input>spawn(speed, regulator, [high_speed, thin_cut]).</input>
 
4008
&lt;0.13.1></pre>
 
4009
      </desc>
 
4010
    </func>
 
4011
    <func>
 
4012
      <name>spawn(Node, Module, Function, ArgumentList) -> pid()</name>
 
4013
      <fsummary>Create a new process with a function as entry point on a given node</fsummary>
 
4014
      <type>
 
4015
        <v>Node = node()</v>
 
4016
        <v>Module = Function = atom()</v>
 
4017
        <v>Args = [term()]</v>
 
4018
      </type>
 
4019
      <desc>
 
4020
        <p>Returns the pid of a new process started by the application
 
4021
          of <c>Module:Function</c> to <c>Args</c> on <c>Node</c>. If
 
4022
          <c>Node</c> does not exists, a useless pid is returned.
 
4023
          Otherwise works like
 
4024
          <seealso marker="#spawn/3">spawn/3</seealso>.</p>
 
4025
      </desc>
 
4026
    </func>
 
4027
    <func>
 
4028
      <name>spawn_link(Fun) -> pid()</name>
 
4029
      <fsummary>Create and link to a new process with a fun as entry point</fsummary>
 
4030
      <type>
 
4031
        <v>Fun = fun()</v>
 
4032
      </type>
 
4033
      <desc>
 
4034
        <p>Returns the pid of a new process started by the application
 
4035
          of <c>Fun</c> to the empty list []. A link is created between
 
4036
          the calling process and and the new process, atomically.
 
4037
          Otherwise works like
 
4038
          <seealso marker="#spawn/3">spawn/3</seealso>.</p>
 
4039
      </desc>
 
4040
    </func>
 
4041
    <func>
 
4042
      <name>spawn_link(Node, Fun) -></name>
 
4043
      <fsummary>Create and link to a new process with a fun as entry point on a specified node</fsummary>
 
4044
      <type>
 
4045
        <v>Node = node()</v>
 
4046
        <v>Fun = fun()</v>
 
4047
      </type>
 
4048
      <desc>
 
4049
        <p>Returns the pid of a new process started by the application
 
4050
          of <c>Fun</c> to the empty list [] on <c>Node</c>. A link is
 
4051
          created between the calling process and and the new process,
 
4052
          atomically. If <c>Node</c> does not exist, a useless pid is
 
4053
          returned (and due to the link, an exit signal with exit
 
4054
          reason <c>noconnection</c> will be received). Otherwise works
 
4055
          like <seealso marker="#spawn/3">spawn/3</seealso>.</p>
 
4056
      </desc>
 
4057
    </func>
 
4058
    <func>
 
4059
      <name>spawn_link(Module, Function, Args) -> pid()</name>
 
4060
      <fsummary>Create and link to a new process with a function as entry point</fsummary>
 
4061
      <type>
 
4062
        <v>Module = Function = atom()</v>
 
4063
        <v>Args = [term()]</v>
 
4064
      </type>
 
4065
      <desc>
 
4066
        <p>Returns the pid of a new process started by the application
 
4067
          of <c>Module:Function</c> to <c>Args</c>. A link is created
 
4068
          between the calling process and the new process, atomically.
 
4069
          Otherwise works like
 
4070
          <seealso marker="#spawn/3">spawn/3</seealso>.</p>
 
4071
      </desc>
 
4072
    </func>
 
4073
    <func>
 
4074
      <name>spawn_link(Node, Module, Function, Args) -> pid()</name>
 
4075
      <fsummary>Create and link to a new process with a function as entry point on a given node</fsummary>
 
4076
      <type>
 
4077
        <v>Node = node()</v>
 
4078
        <v>Module = Function = atom()</v>
 
4079
        <v>Args = [term()]</v>
 
4080
      </type>
 
4081
      <desc>
 
4082
        <p>Returns the pid of a new process started by the application
 
4083
          of <c>Module:Function</c> to <c>Args</c> on <c>Node</c>. A
 
4084
          link is created between the calling process and the new
 
4085
          process, atomically. If <c>Node</c> does not exist, a useless
 
4086
          pid is returned (and due to the link, an exit signal with exit
 
4087
          reason <c>noconnection</c> will be received). Otherwise works
 
4088
          like <seealso marker="#spawn/3">spawn/3</seealso>.</p>
 
4089
      </desc>
 
4090
    </func>
 
4091
    <func>
 
4092
      <name>spawn_monitor(Fun) -> {pid(),reference()}</name>
 
4093
      <fsummary>Create and monitor a new process with a fun as entry point</fsummary>
 
4094
      <type>
 
4095
        <v>Fun = fun()</v>
 
4096
      </type>
 
4097
      <desc>
 
4098
        <p>Returns the pid of a new process started by the application
 
4099
          of <c>Fun</c> to the empty list [] and reference for a monitor
 
4100
          created to the new process.
 
4101
          Otherwise works like
 
4102
          <seealso marker="#spawn/3">spawn/3</seealso>.</p>
 
4103
      </desc>
 
4104
    </func>
 
4105
    <func>
 
4106
      <name>spawn_monitor(Module, Function, Args) -> {pid(),reference()}</name>
 
4107
      <fsummary>Create and monitor a new process with a function as entry point</fsummary>
 
4108
      <type>
 
4109
        <v>Module = Function = atom()</v>
 
4110
        <v>Args = [term()]</v>
 
4111
      </type>
 
4112
      <desc>
 
4113
        <p>A new process is started by the application
 
4114
          of <c>Module:Function</c> to <c>Args</c>, and the process is
 
4115
          monitored at the same time. Returns the pid and a reference
 
4116
          for the monitor.
 
4117
          Otherwise works like
 
4118
          <seealso marker="#spawn/3">spawn/3</seealso>.</p>
 
4119
      </desc>
 
4120
    </func>
 
4121
    <func>
 
4122
      <name>spawn_opt(Fun, [Option]) -> pid() | {pid(),reference()}</name>
 
4123
      <fsummary>Create a new process with a fun as entry point</fsummary>
 
4124
      <type>
 
4125
        <v>Fun = fun()</v>
 
4126
        <v>Option = link | monitor | {priority, Level} | {fullsweep_after, Number} | {min_heap_size, Size}</v>
 
4127
        <v>&nbsp;Level = low | normal | high</v>
 
4128
        <v>&nbsp;Number = int()</v>
 
4129
        <v>&nbsp;Size = int()</v>
 
4130
      </type>
 
4131
      <desc>
 
4132
        <p>Returns the pid of a new process started by the application
 
4133
          of <c>Fun</c> to the empty list <c>[]</c>. Otherwise
 
4134
          works like
 
4135
          <seealso marker="#spawn_opt/4">spawn_opt/4</seealso>.</p>
 
4136
        <p>If the option <c>monitor</c> is given, the newly created
 
4137
          process will be monitored and both the pid and reference for
 
4138
          the monitor will be returned.</p>
 
4139
      </desc>
 
4140
    </func>
 
4141
    <func>
 
4142
      <name>spawn_opt(Node, Fun, [Option]) -> pid()</name>
 
4143
      <fsummary>Create a new process with a fun as entry point on a given node</fsummary>
 
4144
      <type>
 
4145
        <v>Node = node()</v>
 
4146
        <v>Fun = fun()</v>
 
4147
        <v>Option = link | {priority, Level} | {fullsweep_after, Number} | {min_heap_size, Size}</v>
 
4148
        <v>&nbsp;Level = low | normal | high</v>
 
4149
        <v>&nbsp;Number = int()</v>
 
4150
        <v>&nbsp;Size = int()</v>
 
4151
      </type>
 
4152
      <desc>
 
4153
        <p>Returns the pid of a new process started by the application
 
4154
          of <c>Fun</c> to the empty list <c>[]</c> on <c>Node</c>. If
 
4155
          <c>Node</c> does not exist, a useless pid is returned.
 
4156
          Otherwise works like
 
4157
          <seealso marker="#spawn_opt/4">spawn_opt/4</seealso>.</p>
 
4158
      </desc>
 
4159
    </func>
 
4160
    <func>
 
4161
      <name>spawn_opt(Module, Function, Args, [Option]) -> pid() | {pid(),reference()}</name>
 
4162
      <fsummary>Create a new process with a function as entry point</fsummary>
 
4163
      <type>
 
4164
        <v>Module = Function = atom()</v>
 
4165
        <v>Args = [term()]</v>
 
4166
        <v>Option = link | monitor | {priority, Level}  | {fullsweep_after, Number} | {min_heap_size, Size}</v>
 
4167
        <v>&nbsp;Level = low | normal | high</v>
 
4168
        <v>&nbsp;Number = int()</v>
 
4169
        <v>&nbsp;Size = int()</v>
 
4170
      </type>
 
4171
      <desc>
 
4172
        <p>Works exactly like
 
4173
          <seealso marker="#spawn/3">spawn/3</seealso>, except that an
 
4174
          extra option list is given when creating the process.</p>
 
4175
        <p>If the option <c>monitor</c> is given, the newly created
 
4176
          process will be monitored and both the pid and reference for
 
4177
          the monitor will be returned.</p>
 
4178
        <taglist>
 
4179
          <tag><c>link</c></tag>
 
4180
          <item>
 
4181
            <p>Sets a link to the parent process (like
 
4182
              <c>spawn_link/3</c> does).</p>
 
4183
          </item>
 
4184
          <tag><c>monitor</c></tag>
 
4185
          <item>
 
4186
            <p>Monitor the new process (just like
 
4187
              <seealso marker="#erlang:monitor/2">erlang:monitor/2</seealso> does).</p>
 
4188
          </item>
 
4189
          <tag><c>{priority, Level}</c></tag>
 
4190
          <item>
 
4191
            <p>Sets the priority of the new process. Equivalent to
 
4192
              executing
 
4193
              <seealso marker="#process_flag_priority">process_flag(priority, Level)</seealso> in the start function of the new process,
 
4194
              except that the priority will be set before the process is
 
4195
              selected for execution for the first time. For more information
 
4196
              on priorities see
 
4197
              <seealso marker="#process_flag_priority">process_flag(priority, Level)</seealso>.</p>
 
4198
          </item>
 
4199
          <tag><c>{fullsweep_after, Number}</c></tag>
 
4200
          <item>
 
4201
            <p>This option is only useful for performance tuning.
 
4202
              In general, you should not use this option unless you
 
4203
              know that there is problem with execution times and/or
 
4204
              memory consumption, and you should measure to make sure
 
4205
              that the option improved matters.
 
4206
              </p>
 
4207
            <p>The Erlang runtime system uses a generational garbage
 
4208
              collection scheme, using an "old heap" for data that has
 
4209
              survived at least one garbage collection. When there is
 
4210
              no more room on the old heap, a fullsweep garbage
 
4211
              collection will be done.</p>
 
4212
            <p>The <c>fullsweep_after</c> option makes it possible to
 
4213
              specify the maximum number of generational collections
 
4214
              before forcing a fullsweep even if there is still room on
 
4215
              the old heap. Setting the number to zero effectively
 
4216
              disables the general collection algorithm, meaning that
 
4217
              all live data is copied at every garbage collection.</p>
 
4218
            <p>Here are a few cases when it could be useful to change
 
4219
              <c>fullsweep_after</c>. Firstly, if binaries that are no
 
4220
              longer used should be thrown away as soon as possible.
 
4221
              (Set <c>Number</c> to zero.) Secondly, a process that
 
4222
              mostly have short-lived data will be fullsweeped seldom
 
4223
              or never, meaning that the old heap will contain mostly
 
4224
              garbage. To ensure a fullsweep once in a while, set
 
4225
              <c>Number</c> to a suitable value such as 10 or 20.
 
4226
              Thirdly, in embedded systems with limited amount of RAM
 
4227
              and no virtual memory, one might want to preserve memory
 
4228
              by setting <c>Number</c> to zero. (The value may be set
 
4229
              globally, see
 
4230
              <seealso marker="#erlang:system_flag/2">erlang:system_flag/2</seealso>.)</p>
 
4231
          </item>
 
4232
          <tag><c>{min_heap_size, Size}</c></tag>
 
4233
          <item>
 
4234
            <p>This option is only useful for performance tuning.
 
4235
              In general, you should not use this option unless you
 
4236
              know that there is problem with execution times and/or
 
4237
              memory consumption, and you should measure to make sure
 
4238
              that the option improved matters.
 
4239
              </p>
 
4240
            <p>Gives a minimum heap size in words. Setting this value
 
4241
              higher than the system default might speed up some
 
4242
              processes because less garbage collection is done.
 
4243
              Setting too high value, however, might waste memory and
 
4244
              slow down the system due to worse data locality.
 
4245
              Therefore, it is recommended to use this option only for
 
4246
              fine-tuning an application and to measure the execution
 
4247
              time with various <c>Size</c> values.</p>
 
4248
          </item>
 
4249
        </taglist>
 
4250
      </desc>
 
4251
    </func>
 
4252
    <func>
 
4253
      <name>spawn_opt(Node, Module, Function, Args, [Option]) -> pid()</name>
 
4254
      <fsummary>Create a new process with a function as entry point on a given node</fsummary>
 
4255
      <type>
 
4256
        <v>Node = node()</v>
 
4257
        <v>Module = Function = atom()</v>
 
4258
        <v>Args = [term()]</v>
 
4259
        <v>Option = link | {priority, Level} | {fullsweep_after, Number} | {min_heap_size, Size}</v>
 
4260
        <v>&nbsp;Level = low | normal | high</v>
 
4261
        <v>&nbsp;Number = int()</v>
 
4262
        <v>&nbsp;Size = int()</v>
 
4263
      </type>
 
4264
      <desc>
 
4265
        <p>Returns the pid of a new process started by the application
 
4266
          of <c>Module:Function</c> to <c>Args</c> on <c>Node</c>. If
 
4267
          <c>Node</c> does not exist, a useless pid is returned.
 
4268
          Otherwise works like
 
4269
          <seealso marker="#spawn_opt/4">spawn_opt/4</seealso>.</p>
 
4270
      </desc>
 
4271
    </func>
 
4272
    <func>
 
4273
      <name>split_binary(Bin, Pos) -> {Bin1, Bin2}</name>
 
4274
      <fsummary>Split a binary into two</fsummary>
 
4275
      <type>
 
4276
        <v>Bin = Bin1 = Bin2 = binary()</v>
 
4277
        <v>Pos = 1..byte_size(Bin)</v>
 
4278
      </type>
 
4279
      <desc>
 
4280
        <p>Returns a tuple containing the binaries which are the result
 
4281
          of splitting <c>Bin</c> into two parts at position <c>Pos</c>.
 
4282
          This is not a destructive operation. After the operation,
 
4283
          there will be three binaries altogether.</p>
 
4284
        <pre>
 
4285
> <input>B = list_to_binary("0123456789").</input>
 
4286
&lt;&lt;"0123456789">>
 
4287
> <input>byte_size(B).</input>
 
4288
10
 
4289
> <input>{B1, B2} = split_binary(B,3).</input>
 
4290
{&lt;&lt;"012">>,&lt;&lt;"3456789">>}
 
4291
> <input>byte_size(B1).</input>
 
4292
3
 
4293
> <input>byte_size(B2).</input>
 
4294
7</pre>
 
4295
      </desc>
 
4296
    </func>
 
4297
    <func>
 
4298
      <name>erlang:start_timer(Time, Dest, Msg) -> TimerRef</name>
 
4299
      <fsummary>Start a timer</fsummary>
 
4300
      <type>
 
4301
        <v>Time = int()</v>
 
4302
        <v>&nbsp;0 &lt;= Time &lt;= 4294967295</v>
 
4303
        <v>Dest = LocalPid | RegName </v>
 
4304
        <v>&nbsp;LocalPid = pid() (of a process, alive or dead, on the local node)</v>
 
4305
        <v>&nbsp;RegName = atom()</v>
 
4306
        <v>Msg = term()</v>
 
4307
        <v>TimerRef = ref()</v>
 
4308
      </type>
 
4309
      <desc>
 
4310
        <p>Starts a timer which will send the message
 
4311
          <c>{timeout, TimerRef, Msg}</c> to <c>Dest</c>
 
4312
          after <c>Time</c> milliseconds.</p>
 
4313
        <p>If <c>Dest</c> is an atom, it is supposed to be the name of
 
4314
          a registered process. The process referred to by the name is
 
4315
          looked up at the time of delivery. No error is given if
 
4316
          the name does not refer to a process.</p>
 
4317
        <p>If <c>Dest</c> is a pid, the timer will be automatically
 
4318
          canceled if the process referred to by the pid is not alive,
 
4319
          or when the process exits. This feature was introduced in
 
4320
          erts version 5.4.11. Note that timers will not be
 
4321
          automatically canceled when <c>Dest</c> is an atom.</p>
 
4322
        <p>See also
 
4323
          <seealso marker="#erlang:send_after/3">erlang:send_after/3</seealso>,
 
4324
          <seealso marker="#erlang:cancel_timer/1">erlang:cancel_timer/1</seealso>,
 
4325
          and
 
4326
          <seealso marker="#erlang:read_timer/1">erlang:read_timer/1</seealso>.</p>
 
4327
        <p>Failure: <c>badarg</c> if the arguments does not satisfy
 
4328
          the requirements specified above.</p>
 
4329
      </desc>
 
4330
    </func>
 
4331
    <func>
 
4332
      <name>statistics(Type) -> Res</name>
 
4333
      <fsummary>Information about the system</fsummary>
 
4334
      <type>
 
4335
        <v>Type, Res -- see below</v>
 
4336
      </type>
 
4337
      <desc>
 
4338
        <p>Returns information about the system as specified by
 
4339
          <c>Type</c>:</p>
 
4340
        <taglist>
 
4341
          <tag><c>context_switches</c></tag>
 
4342
          <item>
 
4343
            <p>Returns <c>{ContextSwitches, 0}</c>, where
 
4344
              <c>ContextSwitches</c> is the total number of context
 
4345
              switches since the system started.</p>
 
4346
          </item>
 
4347
          <tag><c>exact_reductions</c></tag>
 
4348
          <item>
 
4349
            <marker id="statistics_exact_reductions"></marker>
 
4350
            <p>Returns
 
4351
              <c>{Total_Exact_Reductions, Exact_Reductions_Since_Last_Call}</c>.</p>
 
4352
            <p><em>NOTE:</em><c>statistics(exact_reductions)</c> is
 
4353
              a more expensive operation than
 
4354
              <seealso marker="#statistics_reductions">statistics(reductions)</seealso>
 
4355
              especially on an Erlang machine with SMP support.</p>
 
4356
          </item>
 
4357
          <tag><c>garbage_collection</c></tag>
 
4358
          <item>
 
4359
            <p>Returns <c>{Number_of_GCs, Words_Reclaimed, 0}</c>. This
 
4360
              information may not be valid for all implementations.</p>
 
4361
          </item>
 
4362
          <tag><c>io</c></tag>
 
4363
          <item>
 
4364
            <p>Returns <c>{{input, Input}, {output, Output}}</c>,
 
4365
              where <c>Input</c> is the total number of bytes received
 
4366
              through ports, and <c>Output</c> is the total number of
 
4367
              bytes output to ports.</p>
 
4368
          </item>
 
4369
          <tag><c>reductions</c></tag>
 
4370
          <item>
 
4371
            <marker id="statistics_reductions"></marker>
 
4372
            <p>Returns
 
4373
              <c>{Total_Reductions, Reductions_Since_Last_Call}</c>.</p>
 
4374
            <p><em>NOTE:</em> From erts version 5.5 (OTP release R11B)
 
4375
              this value does not include reductions performed in current
 
4376
              time slices of currently scheduled processes. If an
 
4377
              exact value is wanted, use
 
4378
              <seealso marker="#statistics_exact_reductions">statistics(exact_reductions)</seealso>.</p>
 
4379
          </item>
 
4380
          <tag><c>run_queue</c></tag>
 
4381
          <item>
 
4382
            <p>Returns the length of the run queue, that is, the number
 
4383
              of processes that are ready to run.</p>
 
4384
          </item>
 
4385
          <tag><c>runtime</c></tag>
 
4386
          <item>
 
4387
            <p>Returns <c>{Total_Run_Time, Time_Since_Last_Call}</c>.</p>
 
4388
          </item>
 
4389
          <tag><c>wall_clock</c></tag>
 
4390
          <item>
 
4391
            <p>Returns
 
4392
              <c>{Total_Wallclock_Time, Wallclock_Time_Since_Last_Call}</c>.
 
4393
              <c>wall_clock</c> can be used in the same manner as
 
4394
              <c>runtime</c>, except that real time is measured as
 
4395
              opposed to runtime or CPU time.</p>
 
4396
          </item>
 
4397
        </taglist>
 
4398
        <p>All times are in milliseconds.</p>
 
4399
        <pre>
 
4400
> <input>statistics(runtime).</input>
 
4401
{1690,1620}
 
4402
> <input>statistics(reductions).</input>
 
4403
{2046,11}
 
4404
> <input>statistics(garbage_collection).</input>
 
4405
{85,23961,0}</pre>
 
4406
      </desc>
 
4407
    </func>
 
4408
    <func>
 
4409
      <name>erlang:suspend_process(Suspendee, OptList) -> true | false</name>
 
4410
      <fsummary>Suspend a process</fsummary>
 
4411
      <type>
 
4412
        <v>Suspendee = pid()</v>
 
4413
        <v>OptList = [Opt]</v>
 
4414
        <v>Opt = atom()</v>
 
4415
      </type>
 
4416
      <desc>
 
4417
        <p>Increases the suspend count on the process identified by
 
4418
        <c>Suspendee</c> and puts it in the suspended state if it isn't
 
4419
        already in the suspended state. A suspended process will not be
 
4420
        scheduled for execution until the process has been resumed.
 
4421
        </p>
 
4422
 
 
4423
        <p>A process can be suspended by multiple processes and can
 
4424
        be suspended multiple times by a single process. A suspended
 
4425
        process will not leave the suspended state until its suspend 
 
4426
        count reach zero. The suspend count of <c>Suspendee</c> is
 
4427
        decreased when
 
4428
        <seealso marker="#erlang:resume_process/1">erlang:resume_process(Suspendee)</seealso>
 
4429
        is called by the same process that called
 
4430
        <c>erlang:suspend_process(Suspendee)</c>. All increased suspend
 
4431
        counts on other processes acquired by a process will automatically be
 
4432
        decreased when the process terminates.</p>
 
4433
 
 
4434
        <p>Currently the following options (<c>Opt</c>s) are available:</p>
 
4435
        <taglist>
 
4436
          <tag><c>asynchronous</c></tag>
 
4437
          <item>
 
4438
          A suspend request is sent to the process identified by
 
4439
          <c>Suspendee</c>. <c>Suspendee</c> will eventually suspend
 
4440
          unless it is resumed before it was able to suspend. The caller
 
4441
          of <c>erlang:suspend_process/2</c> will return immediately,
 
4442
          regardless of whether the <c>Suspendee</c> has suspended yet
 
4443
          or not. Note that the point in time when the <c>Suspendee</c>
 
4444
          will actually suspend cannot be deduced from other events
 
4445
          in the system. The only guarantee given is that the
 
4446
          <c>Suspendee</c> will <em>eventually</em> suspend (unless it
 
4447
          is resumed). If the <c>asynchronous</c> option has <em>not</em>
 
4448
          been passed, the caller of <c>erlang:suspend_process/2</c> will
 
4449
          be blocked until the <c>Suspendee</c> has actually suspended.
 
4450
          </item>
 
4451
          <tag><c>unless_suspending</c></tag>
 
4452
          <item>
 
4453
          The process identified by <c>Suspendee</c> will be suspended
 
4454
          unless the calling process already is suspending the
 
4455
          <c>Suspendee</c>. If <c>unless_suspending</c> is combined
 
4456
          with the <c>asynchronous</c> option, a suspend request will be
 
4457
          sent unless the calling process already is suspending the
 
4458
          <c>Suspendee</c> or if a suspend request already has been sent
 
4459
          and is in transit. If the calling process already is suspending
 
4460
          the <c>Suspendee</c>, or if combined with the <c>asynchronous</c>
 
4461
          option and a send request already is in transit,
 
4462
          <c>false</c> is returned and the suspend count on <c>Suspendee</c>
 
4463
          will remain unchanged.
 
4464
          </item>
 
4465
        </taglist>
 
4466
 
 
4467
        <p>If the suspend count on the process identified by
 
4468
        <c>Suspendee</c> was increased, <c>true</c> is returned; otherwise,
 
4469
        <c>false</c> is returned.</p>
 
4470
 
 
4471
        <warning>
 
4472
          <p>This BIF is intended for debugging only.</p>
 
4473
        </warning>
 
4474
        <p>Failures:</p>
 
4475
        <taglist>
 
4476
          <tag><c>badarg</c></tag>
 
4477
          <item>
 
4478
          If <c>Suspendee</c> isn't a process identifier.
 
4479
          </item>
 
4480
          <tag><c>badarg</c></tag>
 
4481
          <item>
 
4482
          If the process identified by <c>Suspendee</c> is same the process as
 
4483
          the process calling <c>erlang:suspend_process/2</c>.
 
4484
          </item>
 
4485
          <tag><c>badarg</c></tag>
 
4486
          <item>
 
4487
          If the process identified by <c>Suspendee</c> is not alive.
 
4488
          </item>
 
4489
          <tag><c>badarg</c></tag>
 
4490
          <item>
 
4491
          If the process identified by <c>Suspendee</c> resides on another node.
 
4492
          </item>
 
4493
          <tag><c>badarg</c></tag>
 
4494
          <item>
 
4495
          If <c>OptList</c> isn't a proper list of valid <c>Opt</c>s.
 
4496
          </item>
 
4497
          <tag><c>system_limit</c></tag>
 
4498
          <item>
 
4499
          If the process identified by <c>Suspendee</c> has been suspended more
 
4500
          times by the calling process than can be represented by the
 
4501
          currently used internal data structures. The current system limit
 
4502
          is larger than 2 000 000 000 suspends, and it will never be less
 
4503
          than that.
 
4504
          </item>
 
4505
        </taglist>
 
4506
      </desc>
 
4507
    </func>
 
4508
    <func>
 
4509
      <name>erlang:suspend_process(Suspendee) -> true</name>
 
4510
      <fsummary>Suspend a process</fsummary>
 
4511
      <type>
 
4512
        <v>Suspendee = pid()</v>
 
4513
      </type>
 
4514
      <desc>
 
4515
        <p>Suspends the process identified by <c>Suspendee</c>. The
 
4516
        same as calling
 
4517
        <seealso marker="#erlang:suspend_process/2">erlang:suspend_process(Suspendee, [])</seealso>. For more information see the documentation of <seealso marker="#erlang:suspend_process/2">erlang:suspend_process/2</seealso>.
 
4518
        </p>
 
4519
        <warning>
 
4520
          <p>This BIF is intended for debugging only.</p>
 
4521
        </warning>
 
4522
      </desc>
 
4523
    </func>
 
4524
    <func>
 
4525
      <name>erlang:system_flag(Flag, Value) -> OldValue</name>
 
4526
      <fsummary>Set system flags</fsummary>
 
4527
      <type>
 
4528
        <v>Flag, Value, OldValue -- see below</v>
 
4529
      </type>
 
4530
      <desc>
 
4531
        <p>Sets various system properties of the Erlang node. Returns
 
4532
          the old value of the flag.</p>
 
4533
        <taglist>
 
4534
          <tag><c>erlang:system_flag(backtrace_depth, Depth)</c></tag>
 
4535
          <item>
 
4536
            <p>Sets the maximum depth of call stack back-traces in the
 
4537
              exit reason element of <c>'EXIT'</c> tuples.</p>
 
4538
          </item>
 
4539
          <tag><c>erlang:system_flag(fullsweep_after, Number)</c></tag>
 
4540
          <item>
 
4541
            <p><c>Number</c> is a non-negative integer which indicates
 
4542
              how many times generational garbages collections can be
 
4543
              done without forcing a fullsweep collection. The value
 
4544
              applies to new processes; processes already running are
 
4545
              not affected.</p>
 
4546
            <p>In low-memory systems (especially without virtual
 
4547
              memory), setting the value to 0 can help to conserve
 
4548
              memory.</p>
 
4549
            <p>An alternative way to set this value is through the
 
4550
              (operating system) environment variable
 
4551
              <c>ERL_FULLSWEEP_AFTER</c>.</p>
 
4552
          </item>
 
4553
          <tag><c>erlang:system_flag(min_heap_size, MinHeapSize)</c></tag>
 
4554
          <item>
 
4555
            <p>Sets the default minimum heap size for processes. The
 
4556
              size is given in words. The new <c>min_heap_size</c> only
 
4557
              effects processes spawned after the change of
 
4558
              <c>min_heap_size</c> has been made.
 
4559
              The <c>min_heap_size</c> can be set for individual
 
4560
              processes by use of
 
4561
              <seealso marker="#spawn_opt/4">spawn_opt/N</seealso> or
 
4562
              <seealso marker="#process_flag/2">process_flag/2</seealso>. </p>
 
4563
          </item>
 
4564
          <tag><c>erlang:system_flag(multi_scheduling, BlockState)</c></tag>
 
4565
          <item>
 
4566
            <marker id="system_flag_multi_scheduling"></marker>
 
4567
            <p><c>BlockState = block | unblock</c></p>
 
4568
            <p>If multi-scheduling is enabled, more than one scheduler
 
4569
              thread is used by the emulator. Multi-scheduling can be
 
4570
              blocked. When multi-scheduling has been blocked, only
 
4571
              one scheduler thread will schedule Erlang processes.</p>
 
4572
            <p>If <c>BlockState =:= block</c>, multi-scheduling will
 
4573
              be blocked. If <c>BlockState =:= unblock</c> and no-one
 
4574
              else is blocking multi-scheduling and this process has
 
4575
              only blocked one time, multi-scheduling will be unblocked.
 
4576
              One process can block multi-scheduling multiple times.
 
4577
              If a process has blocked multiple times, it has to
 
4578
              unblock exactly as many times as it has blocked before it
 
4579
              has released its multi-scheduling block. If a process that
 
4580
              has blocked multi-scheduling exits, it will release its
 
4581
              blocking of multi-scheduling.</p>
 
4582
            <p>The return values are <c>disabled</c>, <c>blocked</c>,
 
4583
              or <c>enabled</c>. The returned value describes the
 
4584
              state just after the call to
 
4585
              <c>erlang:system_flag(multi_scheduling, BlockState)</c>
 
4586
              has been made. The return values are described in the
 
4587
              documentation of <seealso marker="#system_info_multi_scheduling">erlang:system_info(multi_scheduling)</seealso>.</p>
 
4588
            <p><em>NOTE</em>: Blocking of multi-scheduling should normally
 
4589
              not be needed. If you feel that you need to
 
4590
              block multi-scheduling, think through the
 
4591
              problem at least a couple of times again.
 
4592
              Blocking multi-scheduling should only be used
 
4593
              as a last resort since it will most likely be
 
4594
              a <em>very inefficient</em> way to solve the
 
4595
              problem.</p>
 
4596
            <p>See also <seealso marker="#system_info_multi_scheduling">erlang:system_info(multi_scheduling)</seealso>,
 
4597
              <seealso marker="#system_info_multi_scheduling_blockers">erlang:system_info(multi_scheduling_blockers)</seealso>, and
 
4598
              <seealso marker="#system_info_schedulers">erlang:system_info(schedulers)</seealso>.</p>
 
4599
          </item>
 
4600
          <tag><c>erlang:system_flag(trace_control_word, TCW)</c></tag>
 
4601
          <item>
 
4602
            <p>Sets the value of the node's trace control word to
 
4603
              <c>TCW</c>. <c>TCW</c> should be an unsigned integer. For
 
4604
              more information see documentation of the
 
4605
              <seealso marker="erts:match_spec#set_tcw">set_tcw</seealso>
 
4606
              function in the match specification documentation in the
 
4607
              ERTS User's Guide.</p>
 
4608
          </item>
 
4609
        </taglist>
 
4610
        <note>
 
4611
          <p>The <c>schedulers</c> option has been removed as
 
4612
            of erts version 5.5.3. The number of scheduler
 
4613
            threads is determined at emulator boot time, and
 
4614
            cannot be changed after that.</p>
 
4615
        </note>
 
4616
      </desc>
 
4617
    </func>
 
4618
    <func>
 
4619
      <name>erlang:system_info(Type) -> Res</name>
 
4620
      <fsummary>Information about the system</fsummary>
 
4621
      <type>
 
4622
        <v>Type, Res -- see below</v>
 
4623
      </type>
 
4624
      <desc>
 
4625
        <p>Returns various information about the current system
 
4626
          (emulator) as specified by <c>Type</c>:</p>
 
4627
        <taglist>
 
4628
          <tag><c>allocated_areas</c></tag>
 
4629
          <item>
 
4630
            <marker id="system_info_allocated_areas"></marker>
 
4631
            <p>Returns a list of tuples with information about
 
4632
              miscellaneous allocated memory areas.</p>
 
4633
            <p>Each tuple contains an atom describing type of memory as
 
4634
              first element and amount of allocated memory in bytes as
 
4635
              second element. In those cases when there is information
 
4636
              present about allocated and used memory, a third element
 
4637
              is present. This third element contains the amount of
 
4638
              used memory in bytes.</p>
 
4639
            <p><c>erlang:system_info(allocated_areas)</c> is intended
 
4640
              for debugging, and the content is highly implementation
 
4641
              dependent. The content of the results will therefore
 
4642
              change when needed without prior notice.</p>
 
4643
            <p><em>Note:</em> The sum of these values is <em>not</em>
 
4644
              the total amount of memory allocated by the emulator.
 
4645
              Some values are part of other values, and some memory
 
4646
              areas are not part of the result. If you are interested
 
4647
              in the total amount of memory allocated by the emulator
 
4648
              see <seealso marker="#erlang:memory/0">erlang:memory/0,1</seealso>.</p>
 
4649
          </item>
 
4650
          <tag><c>allocator</c></tag>
 
4651
          <item>
 
4652
            <marker id="system_info_allocator"></marker>
 
4653
            <p>Returns <c>{Allocator, Version, Features, Settings}.</c></p>
 
4654
            <p>Types:</p>
 
4655
            <list type="bulleted">
 
4656
              <item><c>Allocator = undefined | elib_malloc | glibc</c></item>
 
4657
              <item><c>Version = [int()]</c></item>
 
4658
              <item><c>Features = [atom()]</c></item>
 
4659
              <item><c>Settings = [{Subsystem, [{Parameter, Value}]}]</c></item>
 
4660
              <item><c>Subsystem = atom()</c></item>
 
4661
              <item><c>Parameter = atom()</c></item>
 
4662
              <item><c>Value = term()</c></item>
 
4663
            </list>
 
4664
            <p>Explanation:</p>
 
4665
            <list type="bulleted">
 
4666
              <item>
 
4667
                <p><c>Allocator</c> corresponds to the <c>malloc()</c>
 
4668
                  implementation used. If <c>Allocator</c> equals
 
4669
                  <c>undefined</c>, the <c>malloc()</c> implementation
 
4670
                  used could not be identified. Currently
 
4671
                  <c>elib_malloc</c> and <c>glibc</c> can be identified.</p>
 
4672
              </item>
 
4673
              <item>
 
4674
                <p><c>Version</c> is a list of integers (but not a
 
4675
                  string) representing the version of
 
4676
                  the <c>malloc()</c> implementation used.</p>
 
4677
              </item>
 
4678
              <item>
 
4679
                <p><c>Features</c> is a list of atoms representing
 
4680
                  allocation features used.</p>
 
4681
              </item>
 
4682
              <item>
 
4683
                <p><c>Settings</c> is a list of subsystems, their
 
4684
                  configurable parameters, and used values. Settings
 
4685
                  may differ between different combinations of
 
4686
                  platforms, allocators, and allocation features.
 
4687
                  Memory sizes are given in bytes.</p>
 
4688
              </item>
 
4689
            </list>
 
4690
            <p>See also "System Flags Effecting erts_alloc" in
 
4691
              <seealso marker="erts:erts_alloc#flags">erts_alloc(3)</seealso>.</p>
 
4692
          </item>
 
4693
          <tag><c>alloc_util_allocators</c></tag>
 
4694
          <item>
 
4695
            <marker id="system_info_alloc_util_allocators"></marker>
 
4696
             <p>Returns a list of the names of all allocators
 
4697
                using the ERTS internal <c>alloc_util</c> framework
 
4698
                as atoms. For more information see the
 
4699
                <seealso marker="erts:erts_alloc#alloc_util">"the
 
4700
                alloc_util framework" section in the
 
4701
                erts_alloc(3)</seealso> documentation.
 
4702
             </p>
 
4703
          </item>
 
4704
          <tag><c>{allocator, Alloc}</c></tag>
 
4705
          <item>
 
4706
            <marker id="system_info_allocator_tuple"></marker>
 
4707
            <p>Returns information about the specified allocator.
 
4708
               As of erts version 5.6.1 the return value is a list
 
4709
               of <c>{instance, InstanceNo, InstanceInfo}</c> tuples
 
4710
               where <c>InstanceInfo</c> contains information about
 
4711
               a specific instance of the allocator.
 
4712
               If <c>Alloc</c> is not a recognized allocator,
 
4713
              <c>undefined</c> is returned. If <c>Alloc</c> is disabled,
 
4714
              <c>false</c> is returned.</p>
 
4715
            <p><em>Note:</em> The information returned is highly
 
4716
              implementation dependent and may be changed, or removed
 
4717
              at any time without prior notice. It was initially
 
4718
              intended as a tool when developing new allocators, but
 
4719
              since it might be of interest for others it has been
 
4720
              briefly documented.</p>
 
4721
            <p>The recognized allocators are listed in
 
4722
              <seealso marker="erts:erts_alloc">erts_alloc(3)</seealso>.
 
4723
              After reading the <c>erts_alloc(3)</c> documentation,
 
4724
              the returned information
 
4725
              should more or less speak for itself. But it can be worth
 
4726
              explaining some things. Call counts are presented by two
 
4727
              values. The first value is giga calls, and the second
 
4728
              value is calls. <c>mbcs</c>, and <c>sbcs</c> are
 
4729
              abbreviations for, respectively, multi-block carriers, and
 
4730
              single-block carriers. Sizes are presented in bytes. When
 
4731
              it is not a size that is presented, it is the amount of
 
4732
              something. Sizes and amounts are often presented by three
 
4733
              values, the first is current value, the second is maximum
 
4734
              value since the last call to
 
4735
              <c>erlang:system_info({allocator, Alloc})</c>, and
 
4736
              the third is maximum value since the emulator was started.
 
4737
              If only one value is present, it is the current value.
 
4738
              <c>fix_alloc</c> memory block types are presented by two
 
4739
              values. The first value is memory pool size and
 
4740
              the second value used memory size.</p>
 
4741
          </item>
 
4742
          <tag><c>{allocator_sizes, Alloc}</c></tag>
 
4743
          <item>
 
4744
            <marker id="system_info_allocator_sizes"></marker>
 
4745
            <p>Returns various size information for the specified
 
4746
            allocator. The information returned is a subset of the
 
4747
            information returned by
 
4748
            <seealso marker="#system_info_allocator_tuple">erlang:system_info({allocator, Alloc})</seealso>.
 
4749
            </p>
 
4750
          </item>
 
4751
          <tag><c>c_compiler_used</c></tag>
 
4752
          <item>
 
4753
            <p>Returns a two-tuple describing the C compiler used when
 
4754
               compiling the runtime system. The first element is an
 
4755
               atom describing the name of the compiler, or <c>undefined</c>
 
4756
               if unknown. The second element is a term describing the
 
4757
               version of the compiler, or <c>undefined</c> if unknown.
 
4758
             </p>
 
4759
          </item>
 
4760
          <tag><c>check_io</c></tag>
 
4761
          <item>
 
4762
            <p>Returns a list containing miscellaneous information
 
4763
              regarding the emulators internal I/O checking. Note,
 
4764
              the content of the returned list may vary between
 
4765
              platforms and over time. The only thing guaranteed is
 
4766
              that a list is returned.</p>
 
4767
          </item>
 
4768
          <tag><c>compat_rel</c></tag>
 
4769
          <item>
 
4770
            <p>Returns the compatibility mode of the local node as
 
4771
              an integer. The integer returned represents the
 
4772
              Erlang/OTP release which the current emulator has been
 
4773
              set to be backward compatible with. The compatibility
 
4774
              mode can be configured at startup by using the command
 
4775
              line flag <c>+R</c>, see
 
4776
              <seealso marker="erts:erl#compat_rel">erl(1)</seealso>.</p>
 
4777
          </item>
 
4778
          <tag><c>creation</c></tag>
 
4779
          <item>
 
4780
            <p>Returns the creation of the local node as an integer.
 
4781
              The creation is changed when a node is restarted. The
 
4782
              creation of a node is stored in process identifiers, port
 
4783
              identifiers, and references. This makes it (to some
 
4784
              extent) possible to distinguish between identifiers from
 
4785
              different incarnations of a node. Currently valid
 
4786
              creations are integers in the range 1..3, but this may
 
4787
              (probably will) change in the future. If the node is not
 
4788
              alive, 0 is returned.</p>
 
4789
          </item>
 
4790
          <tag><c>debug_compiled</c></tag>
 
4791
          <item>
 
4792
            <p>Returns <c>true</c> if the emulator has been debug
 
4793
               compiled; otherwise, <c>false</c>.
 
4794
            </p>
 
4795
          </item>
 
4796
          <tag><c>dist</c></tag>
 
4797
          <item>
 
4798
            <p>Returns a binary containing a string of distribution
 
4799
              information formatted as in Erlang crash dumps. For more
 
4800
              information see the <seealso marker="erts:crash_dump">"How to interpret the Erlang crash dumps"</seealso>
 
4801
              chapter in the ERTS User's Guide.</p>
 
4802
          </item>
 
4803
          <tag><c>dist_ctrl</c></tag>
 
4804
          <item>
 
4805
            <p>Returns a list of tuples
 
4806
              <c>{Node, ControllingEntity}</c>, one entry for each
 
4807
              connected remote node. The <c>Node</c> is the name of the
 
4808
              node and the <c>ControllingEntity</c> is the port or pid
 
4809
              responsible for the communication to that node. More
 
4810
              specifically, the <c>ControllingEntity</c> for nodes
 
4811
              connected via TCP/IP (the normal case) is the socket
 
4812
              actually used in communication with the specific node.</p>
 
4813
          </item>
 
4814
          <tag><c>driver_version</c></tag>
 
4815
          <item>
 
4816
            <p>Returns a string containing the erlang driver version
 
4817
              used by the runtime system. It will be on the form
 
4818
              <seealso marker="erts:erl_driver#version_management">"&lt;major ver&gt;.&lt;minor ver&gt;"</seealso>.</p>
 
4819
          </item>
 
4820
          <tag><c>elib_malloc</c></tag>
 
4821
          <item>
 
4822
            <p>If the emulator uses the <c>elib_malloc</c> memory
 
4823
              allocator, a list of two-element tuples containing status
 
4824
              information is returned; otherwise, <c>false</c> is
 
4825
              returned. The list currently contains the following
 
4826
              two-element tuples (all sizes are presented in bytes):</p>
 
4827
            <taglist>
 
4828
              <tag><c>{heap_size, Size}</c></tag>
 
4829
              <item>
 
4830
                <p>Where <c>Size</c> is the current heap size.</p>
 
4831
              </item>
 
4832
              <tag><c>{max_alloced_size, Size}</c></tag>
 
4833
              <item>
 
4834
                <p>Where <c>Size</c> is the maximum amount of memory
 
4835
                  allocated on the heap since the emulator started.</p>
 
4836
              </item>
 
4837
              <tag><c>{alloced_size, Size}</c></tag>
 
4838
              <item>
 
4839
                <p>Where <c>Size</c> is the current amount of memory
 
4840
                  allocated on the heap.</p>
 
4841
              </item>
 
4842
              <tag><c>{free_size, Size}</c></tag>
 
4843
              <item>
 
4844
                <p>Where <c>Size</c> is the current amount of free
 
4845
                  memory on the heap.</p>
 
4846
              </item>
 
4847
              <tag><c>{no_alloced_blocks, No}</c></tag>
 
4848
              <item>
 
4849
                <p>Where <c>No</c> is the current number of allocated
 
4850
                  blocks on the heap.</p>
 
4851
              </item>
 
4852
              <tag><c>{no_free_blocks, No}</c></tag>
 
4853
              <item>
 
4854
                <p>Where <c>No</c> is the current number of free blocks
 
4855
                  on the heap.</p>
 
4856
              </item>
 
4857
              <tag><c>{smallest_alloced_block, Size}</c></tag>
 
4858
              <item>
 
4859
                <p>Where <c>Size</c> is the size of the smallest
 
4860
                  allocated block on the heap.</p>
 
4861
              </item>
 
4862
              <tag><c>{largest_free_block, Size}</c></tag>
 
4863
              <item>
 
4864
                <p>Where <c>Size</c> is the size of the largest free
 
4865
                  block on the heap.</p>
 
4866
              </item>
 
4867
            </taglist>
 
4868
          </item>
 
4869
          <tag><c>fullsweep_after</c></tag>
 
4870
          <item>
 
4871
            <p>Returns <c>{fullsweep_after, int()}</c> which is the
 
4872
              <c>fullsweep_after</c> garbage collection setting used
 
4873
              by default. For more information see
 
4874
              <c>garbage_collection</c> described below.</p>
 
4875
          </item>
 
4876
          <tag><c>garbage_collection</c></tag>
 
4877
          <item>
 
4878
            <p>Returns a list describing the default garbage collection
 
4879
              settings. A process spawned on the local node by a
 
4880
              <c>spawn</c> or <c>spawn_link</c> will use these
 
4881
              garbage collection settings. The default settings can be
 
4882
              changed by use of
 
4883
              <seealso marker="#erlang:system_flag/2">system_flag/2</seealso>.
 
4884
              <seealso marker="#spawn_opt/4">spawn_opt/4</seealso>
 
4885
              can spawn a process that does not use the default
 
4886
              settings.</p>
 
4887
          </item>
 
4888
          <tag><c>global_heaps_size</c></tag>
 
4889
          <item>
 
4890
            <p>Returns the current size of the shared (global) heap.</p>
 
4891
          </item>
 
4892
          <tag><c>heap_sizes</c></tag>
 
4893
          <item>
 
4894
            <p>Returns a list of integers representing valid heap sizes 
 
4895
              in words. All Erlang heaps are sized from sizes in this
 
4896
              list.</p>
 
4897
          </item>
 
4898
          <tag><c>heap_type</c></tag>
 
4899
          <item>
 
4900
            <p>Returns the heap type used by the current emulator.
 
4901
              Currently the following heap types exist:</p>
 
4902
            <taglist>
 
4903
              <tag><c>private</c></tag>
 
4904
              <item>
 
4905
                <p>Each process has a heap reserved for its use and no
 
4906
                  references between heaps of different processes are
 
4907
                  allowed. Messages passed between processes are copied
 
4908
                  between heaps.</p>
 
4909
              </item>
 
4910
              <tag><c>shared</c></tag>
 
4911
              <item>
 
4912
                <p>One heap for use by all processes. Messages passed
 
4913
                  between processes are passed by reference.</p>
 
4914
              </item>
 
4915
              <tag><c>hybrid</c></tag>
 
4916
              <item>
 
4917
                <p>A hybrid of the <c>private</c> and <c>shared</c> heap
 
4918
                  types. A shared heap as well as private heaps are
 
4919
                  used.</p>
 
4920
              </item>
 
4921
            </taglist>
 
4922
          </item>
 
4923
          <tag><c>info</c></tag>
 
4924
          <item>
 
4925
            <p>Returns a binary containing a string of miscellaneous
 
4926
              system information formatted as in Erlang crash dumps.
 
4927
              For more information see the
 
4928
              <seealso marker="erts:crash_dump">"How to interpret the Erlang crash dumps"</seealso> chapter in the ERTS
 
4929
              User's Guide.</p>
 
4930
          </item>
 
4931
          <tag><c>kernel_poll</c></tag>
 
4932
          <item>
 
4933
            <p>Returns <c>true</c> if the emulator uses some kind of
 
4934
              kernel-poll implementation; otherwise, <c>false</c>.</p>
 
4935
          </item>
 
4936
          <tag><c>loaded</c></tag>
 
4937
          <item>
 
4938
            <p>Returns a binary containing a string of loaded module
 
4939
              information formatted as in Erlang crash dumps. For more
 
4940
              information see the <seealso marker="erts:crash_dump">"How to interpret the Erlang crash dumps"</seealso> chapter
 
4941
              in the ERTS User's Guide.</p>
 
4942
          </item>
 
4943
          <tag><c>logical_processors</c></tag>
 
4944
          <item>
 
4945
            <p>Returns the number of logical processors detected on the
 
4946
               system as an integer or the atom <c>unknown</c> if the
 
4947
               emulator wasn't able to detect any.
 
4948
            </p>
 
4949
          </item>
 
4950
          <tag><c>machine</c></tag>
 
4951
          <item>
 
4952
            <p>Returns a string containing the Erlang machine name.</p>
 
4953
          </item>
 
4954
          <tag><c>modified_timing_level</c></tag>
 
4955
          <item>
 
4956
            <p>Returns the modified timing level (an integer) if
 
4957
              modified timing has been enabled; otherwise,
 
4958
              <c>undefined</c>. See the <c>+T</c> command line flag
 
4959
              in the documentation of the
 
4960
              <seealso marker="erts:erl#+T">erl(1)</seealso>
 
4961
              command for more information on modified timing.</p>
 
4962
          </item>
 
4963
          <tag><c>multi_scheduling</c></tag>
 
4964
          <item>
 
4965
            <marker id="system_info_multi_scheduling"></marker>
 
4966
            <p>Returns <c>disabled</c>, <c>blocked</c>, or <c>enabled</c>.
 
4967
              A description of the return values:</p>
 
4968
            <taglist>
 
4969
              <tag><c>disabled</c></tag>
 
4970
              <item>
 
4971
                <p>The emulator has only one scheduler thread. The
 
4972
                  emulator does not have SMP support, or have been
 
4973
                  started with only one scheduler thread.</p>
 
4974
              </item>
 
4975
              <tag><c>blocked</c></tag>
 
4976
              <item>
 
4977
                <p>The emulator has more than one scheduler thread,
 
4978
                  but all scheduler threads but one have been blocked,
 
4979
                  i.e., only one scheduler thread will schedule
 
4980
                  Erlang processes and execute Erlang code.</p>
 
4981
              </item>
 
4982
              <tag><c>enabled</c></tag>
 
4983
              <item>
 
4984
                <p>The emulator has more than one scheduler thread,
 
4985
                  and no scheduler threads have been blocked, i.e.,
 
4986
                  all available scheduler threads will schedule
 
4987
                  Erlang processes and execute Erlang code.</p>
 
4988
              </item>
 
4989
            </taglist>
 
4990
            <p>See also <seealso marker="#system_flag_multi_scheduling">erlang:system_flag(multi_scheduling, BlockState)</seealso>,
 
4991
              <seealso marker="#system_info_multi_scheduling_blockers">erlang:system_info(multi_scheduling_blockers)</seealso>, and
 
4992
              <seealso marker="#system_info_schedulers">erlang:system_info(schedulers)</seealso>.</p>
 
4993
          </item>
 
4994
          <tag><c>multi_scheduling_blockers</c></tag>
 
4995
          <item>
 
4996
            <marker id="system_info_multi_scheduling_blockers"></marker>
 
4997
            <p>Returns a list of <c>PID</c>s when multi-scheduling
 
4998
              is blocked; otherwise, the empty list. The <c>PID</c>s
 
4999
              in the list is <c>PID</c>s of the processes currently
 
5000
              blocking multi-scheduling. A <c>PID</c> will only be
 
5001
              present once in the list, even if the corresponding
 
5002
              process has blocked multiple times.</p>
 
5003
            <p>See also <seealso marker="#system_flag_multi_scheduling">erlang:system_flag(multi_scheduling, BlockState)</seealso>,
 
5004
              <seealso marker="#system_info_multi_scheduling">erlang:system_info(multi_scheduling)</seealso>, and
 
5005
              <seealso marker="#system_info_schedulers">erlang:system_info(schedulers)</seealso>.</p>
 
5006
          </item>
 
5007
          <tag><c>otp_release</c></tag>
 
5008
          <item>
 
5009
            <marker id="system_info_otp_release"></marker>
 
5010
            <p>Returns a string containing the OTP release number.</p>
 
5011
          </item>
 
5012
          <tag><c>process_count</c></tag>
 
5013
          <item>
 
5014
            <p>Returns the number of processes currently existing at
 
5015
              the local node as an integer. The same value as
 
5016
              <c>length(processes())</c> returns.</p>
 
5017
          </item>
 
5018
          <tag><c>process_limit</c></tag>
 
5019
          <item>
 
5020
            <p>Returns the maximum number of concurrently existing
 
5021
              processes at the local node as an integer. This limit
 
5022
              can be configured at startup by using the command line
 
5023
              flag <c>+P</c>, see
 
5024
              <seealso marker="erts:erl#max_processes">erl(1)</seealso>.</p>
 
5025
          </item>
 
5026
          <tag><c>procs</c></tag>
 
5027
          <item>
 
5028
            <p>Returns a binary containing a string of process and port
 
5029
              information formatted as in Erlang crash dumps. For more
 
5030
              information see the <seealso marker="erts:crash_dump">"How to interpret the Erlang crash dumps"</seealso> chapter
 
5031
              in the ERTS User's Guide.</p>
 
5032
          </item>
 
5033
          <tag><c>scheduler_id</c></tag>
 
5034
          <item>
 
5035
            <marker id="system_info_scheduler_id"></marker>
 
5036
            <p>Returns the scheduler id (<c>SchedulerId</c>) of the
 
5037
              scheduler thread that the calling process is executing
 
5038
              on. <c>SchedulerId</c> is a positive integer; where
 
5039
              <c><![CDATA[1 <= SchedulerId <= erlang:system_info(schedulers)]]></c>. See also
 
5040
              <seealso marker="#system_info_schedulers">erlang:system_info(schedulers)</seealso>.</p>
 
5041
          </item>
 
5042
          <tag><c>schedulers</c></tag>
 
5043
          <item>
 
5044
            <marker id="system_info_schedulers"></marker>
 
5045
            <p>Returns the number of scheduler threads used by
 
5046
              the emulator. A scheduler thread schedules Erlang
 
5047
              processes and Erlang ports, and execute Erlang code
 
5048
              and Erlang linked in driver code.</p>
 
5049
            <p>The number of scheduler threads is determined at
 
5050
              emulator boot time and cannot be changed after
 
5051
              that.</p>
 
5052
            <p>See also <seealso marker="#system_info_scheduler_id">erlang:system_info(scheduler_id)</seealso>,
 
5053
              <seealso marker="#system_flag_multi_scheduling">erlang:system_flag(multi_scheduling, BlockState)</seealso>,
 
5054
              <seealso marker="#system_info_multi_scheduling">erlang:system_info(multi_scheduling)</seealso>, and
 
5055
              and <seealso marker="#system_info_multi_scheduling_blockers">erlang:system_info(multi_scheduling_blockers)</seealso>.</p>
 
5056
          </item>
 
5057
          <tag><c>smp_support</c></tag>
 
5058
          <item>
 
5059
            <p>Returns <c>true</c> if the emulator has been compiled
 
5060
              with smp support; otherwise, <c>false</c>.</p>
 
5061
          </item>
 
5062
          <tag><c>system_version</c></tag>
 
5063
          <item>
 
5064
            <p>Returns a string containing the emulator type and
 
5065
              version as well as some important properties such as
 
5066
              the size of the thread pool, etc.</p>
 
5067
          </item>
 
5068
          <tag><c>system_architecture</c></tag>
 
5069
          <item>
 
5070
            <p>Returns a string containing the processor and OS
 
5071
              architecture the emulator is built for.</p>
 
5072
          </item>
 
5073
          <tag><c>threads</c></tag>
 
5074
          <item>
 
5075
            <p>Returns <c>true</c> if the emulator has been compiled
 
5076
              with thread support; otherwise, <c>false</c> is
 
5077
              returned.</p>
 
5078
          </item>
 
5079
          <tag><c>thread_pool_size</c></tag>
 
5080
          <item>
 
5081
            <marker id="system_info_thread_pool_size"></marker>
 
5082
            <p>Returns the number of async threads in the async thread
 
5083
              pool used for asynchronous driver calls
 
5084
              (<seealso marker="erts:erl_driver#driver_async">driver_async()</seealso>)
 
5085
              as an integer.</p>
 
5086
          </item>
 
5087
          <tag><c>trace_control_word</c></tag>
 
5088
          <item>
 
5089
            <p>Returns the value of the node's trace control word.
 
5090
              For more information see documentation of the function
 
5091
              <c>get_tcw</c> in "Match Specifications in Erlang",
 
5092
              <seealso marker="erts:match_spec#get_tcw">ERTS User's Guide</seealso>.</p>
 
5093
          </item>
 
5094
          <tag><c>version</c></tag>
 
5095
          <item>
 
5096
            <marker id="system_info_version"></marker>
 
5097
            <p>Returns a string containing the version number of the
 
5098
              emulator.</p>
 
5099
          </item>
 
5100
          <tag><c>wordsize</c></tag>
 
5101
          <item>
 
5102
            <p>Returns the word size in bytes as an integer, i.e. on a
 
5103
              32-bit architecture 4 is returned, and on a 64-bit
 
5104
              architecture 8 is returned.</p>
 
5105
          </item>
 
5106
        </taglist>
 
5107
        <note>
 
5108
          <p>The <c>scheduler</c> argument has changed name to
 
5109
            <c>scheduler_id</c>. This in order to avoid mixup with
 
5110
            the <c>schedulers</c> argument. The <c>scheduler</c>
 
5111
            argument was introduced in ERTS version 5.5 and renamed
 
5112
            in ERTS version 5.5.1.</p>
 
5113
        </note>
 
5114
      </desc>
 
5115
    </func>
 
5116
 
 
5117
    <func>
 
5118
      <name>erlang:system_monitor() -> MonSettings</name>
 
5119
      <fsummary>Current system performance monitoring settings</fsummary>
 
5120
      <type>
 
5121
        <v>MonSettings -> {MonitorPid, Options} | undefined</v>
 
5122
        <v>&nbsp;MonitorPid = pid()</v>
 
5123
        <v>&nbsp;Options = [Option]</v>
 
5124
        <v>&nbsp;&nbsp;Option = {long_gc, Time} | {large_heap, Size} | busy_port | busy_dist_port</v>
 
5125
        <v>&nbsp;&nbsp;&nbsp;Time = Size = int()</v>
 
5126
      </type>
 
5127
      <desc>
 
5128
        <p>Returns the current system monitoring settings set by
 
5129
          <seealso marker="#erlang:system_monitor/2">erlang:system_monitor/2</seealso>
 
5130
          as <c>{MonitorPid, Options}</c>, or <c>undefined</c> if there
 
5131
          are no settings. The order of the options may be different
 
5132
          from the one that was set.</p>
 
5133
      </desc>
 
5134
    </func>
 
5135
 
 
5136
    <func>
 
5137
      <name>erlang:system_monitor(undefined | {MonitorPid, Options}) -> MonSettings</name>
 
5138
      <fsummary>Set or clear system performance monitoring options</fsummary>
 
5139
      <type>
 
5140
        <v>MonitorPid, Options, MonSettings -- see below</v>
 
5141
      </type>
 
5142
      <desc>
 
5143
        <p>When called with the argument <c>undefined</c>, all
 
5144
          system performance monitoring settings are cleared.</p>
 
5145
        <p>Calling the function with <c>{MonitorPid, Options}</c> as
 
5146
          argument, is the same as calling
 
5147
          <seealso marker="#erlang:system_monitor/2">erlang:system_monitor(MonitorPid, Options)</seealso>.</p>
 
5148
        <p>Returns the previous system monitor settings just like
 
5149
          <seealso marker="#erlang:system_monitor/0">erlang:system_monitor/0</seealso>.</p>
 
5150
      </desc>
 
5151
    </func>
 
5152
 
 
5153
    <func>
 
5154
      <name>erlang:system_monitor(MonitorPid, [Option]) -> MonSettings</name>
 
5155
      <fsummary>Set system performance monitoring options</fsummary>
 
5156
      <type>
 
5157
        <v>MonitorPid = pid()</v>
 
5158
        <v>Option = {long_gc, Time} | {large_heap, Size} | busy_port | busy_dist_port</v>
 
5159
        <v>&nbsp;Time = Size = int()</v>
 
5160
        <v>MonSettings = {OldMonitorPid, [Option]}</v>
 
5161
        <v>&nbsp;OldMonitorPid = pid()</v>
 
5162
      </type>
 
5163
      <desc>
 
5164
        <p>Sets system performance monitoring options. <c>MonitorPid</c>
 
5165
          is a local pid that will receive system monitor messages, and
 
5166
          the second argument is a list of monitoring options:</p>
 
5167
        <taglist>
 
5168
          <tag><c>{long_gc, Time}</c></tag>
 
5169
          <item>
 
5170
            <p>If a garbage collection in the system takes at least
 
5171
              <c>Time</c> wallclock milliseconds, a message
 
5172
              <c>{monitor, GcPid, long_gc, Info}</c> is sent to
 
5173
              <c>MonitorPid</c>. <c>GcPid</c> is the pid that was
 
5174
              garbage collected and <c>Info</c> is a list of two-element
 
5175
              tuples describing the result of the garbage collection.
 
5176
              One of the tuples is <c>{timeout, GcTime}</c> where
 
5177
              <c>GcTime</c> is the actual time for the garbage
 
5178
              collection in milliseconds. The other tuples are
 
5179
              tagged with <c>heap_size</c>, <c>heap_block_size</c>,
 
5180
              <c>stack_size</c>, <c>mbuf_size</c>, <c>old_heap_size</c>,
 
5181
              and <c>old_heap_block_size</c>. These tuples are
 
5182
              explained in the documentation of the
 
5183
              <seealso marker="#gc_start">gc_start</seealso>
 
5184
              trace message (see
 
5185
              <seealso marker="#erlang:trace/3">erlang:trace/3</seealso>).
 
5186
              New tuples may be added, and the order of the tuples in
 
5187
              the <c>Info</c> list may be changed at any time without prior
 
5188
              notice.
 
5189
              </p>
 
5190
          </item>
 
5191
          <tag><c>{large_heap, Size}</c></tag>
 
5192
          <item>
 
5193
            <p>If a garbage collection in the system results in
 
5194
              the allocated size of a heap being at least <c>Size</c>
 
5195
              words, a message <c>{monitor, GcPid, large_heap, Info}</c>
 
5196
              is sent to <c>MonitorPid</c>. <c>GcPid</c> and <c>Info</c>
 
5197
              are the same as for <c>long_gc</c> above, except that
 
5198
              the tuple tagged with <c>timeout</c> is not present.
 
5199
              <em>Note</em>: As of erts version 5.6 the monitor message
 
5200
              is sent if the sum of the sizes of all memory blocks allocated
 
5201
              for all heap generations is equal to or larger than <c>Size</c>.
 
5202
              Previously the monitor message was sent if the memory block
 
5203
              allocated for the youngest generation was equal to or larger
 
5204
              than <c>Size</c>.
 
5205
            </p>
 
5206
          </item>
 
5207
          <tag><c>busy_port</c></tag>
 
5208
          <item>
 
5209
            <p>If a process in the system gets suspended because it
 
5210
              sends to a busy port, a message
 
5211
              <c>{monitor, SusPid, busy_port, Port}</c> is sent to
 
5212
              <c>MonitorPid</c>. <c>SusPid</c> is the pid that got
 
5213
              suspended when sending to <c>Port</c>.</p>
 
5214
          </item>
 
5215
          <tag><c>busy_dist_port</c></tag>
 
5216
          <item>
 
5217
            <p>If a process in the system gets suspended because it
 
5218
              sends to a process on a remote node whose inter-node
 
5219
              communication was handled by a busy port, a message
 
5220
              <c>{monitor, SusPid, busy_dist_port, Port}</c> is sent to
 
5221
              <c>MonitorPid</c>. <c>SusPid</c> is the pid that got
 
5222
              suspended when sending through the inter-node
 
5223
              communication port <c>Port</c>.</p>
 
5224
          </item>
 
5225
        </taglist>
 
5226
        <p>Returns the previous system monitor settings just like
 
5227
          <seealso marker="#erlang:system_monitor/0">erlang:system_monitor/0</seealso>.</p>
 
5228
        <note>
 
5229
          <p>If a monitoring process gets so large that it itself
 
5230
            starts to cause system monitor messages when garbage
 
5231
            collecting, the messages will enlarge the process's
 
5232
            message queue and probably make the problem worse.</p>
 
5233
          <p>Keep the monitoring process neat and do not set the system
 
5234
            monitor limits too tight.</p>
 
5235
        </note>
 
5236
        <p>Failure: <c>badarg</c> if <c>MonitorPid</c> does not exist.</p>
 
5237
      </desc>
 
5238
    </func>
 
5239
 
 
5240
    <func>
 
5241
      <name>erlang:system_profile() -> ProfilerSettings</name>
 
5242
      <fsummary>Current system profiling settings</fsummary>
 
5243
      <type>
 
5244
        <v>ProfilerSettings -> {ProfilerPid, Options} | undefined</v>
 
5245
        <v>&nbsp;ProfilerPid = pid() | port()</v>
 
5246
        <v>&nbsp;Options = [Option]</v>
 
5247
        <v>&nbsp;&nbsp;Option = runnable_procs | runnable_ports | scheduler | exclusive</v>
 
5248
      </type>
 
5249
      <desc>
 
5250
        <p>Returns the current system profiling settings set by
 
5251
          <seealso marker="#erlang:system_profile/2">erlang:system_profile/2</seealso>
 
5252
          as <c>{ProfilerPid, Options}</c>, or <c>undefined</c> if there
 
5253
          are no settings. The order of the options may be different
 
5254
          from the one that was set.</p>
 
5255
      </desc>
 
5256
    </func>
 
5257
 
 
5258
    <func>
 
5259
      <name>erlang:system_profile(ProfilerPid, Options) -> ProfilerSettings</name>
 
5260
      <fsummary>Current system profiling settings</fsummary>
 
5261
      <type>
 
5262
        <v>ProfilerSettings -> {ProfilerPid, Options} | undefined</v>
 
5263
        <v>&nbsp;ProfilerPid = pid() | port()</v>
 
5264
        <v>&nbsp;Options = [Option]</v>
 
5265
        <v>&nbsp;&nbsp;Option = runnable_procs | runnable_ports | scheduler | exclusive</v>
 
5266
      </type>
 
5267
      <desc>
 
5268
        <p>Sets system profiler options. <c>ProfilerPid</c>
 
5269
          is a local pid or port that will receive profiling messages. The
 
5270
          receiver is excluded from all profiling.
 
5271
          The second argument is a list of profiling options:</p>
 
5272
        <taglist>
 
5273
          <tag><c>runnable_procs</c></tag>
 
5274
          <item>
 
5275
          <p>If a process is put into or removed from the runqueue a message, 
 
5276
             <c>{profile, Pid, State, Mfa, Ts}</c>, is sent to
 
5277
             <c>ProfilerPid</c>. Running processes that is reinsertet into the
 
5278
             runqueue after completing its reductions does not trigger this
 
5279
             message.
 
5280
          </p>
 
5281
          </item>
 
5282
          <tag><c>runnable_ports</c></tag>
 
5283
          <item>
 
5284
          <p>If a port is put into or removed from the runqueue a message, 
 
5285
             <c>{profile, Port, State, 0, Ts}</c>, is sent to
 
5286
             <c>ProfilerPid</c>.
 
5287
          </p>
 
5288
          </item>
 
5289
          <tag><c>scheduler</c></tag>
 
5290
          <item>
 
5291
          <p>If a scheduler is put to sleep or awoken a message,
 
5292
             <c>{profile, scheduler, Id, State, NoScheds, Ts}</c>, is sent
 
5293
             to <c>ProfilerPid</c>.
 
5294
          </p>
 
5295
          </item>
 
5296
          <tag><c>exclusive</c></tag>
 
5297
          <item>
 
5298
          <p>
 
5299
             If a synchronous call to a port from a process is done, the
 
5300
             calling process is considered not runnable during the call
 
5301
             runtime to the port. The calling process is notified as
 
5302
             <c>inactive</c> and subsequently <c>active</c> when the port
 
5303
             callback returns.
 
5304
          </p>
 
5305
          </item>
 
5306
        </taglist>
 
5307
        <note><p><c>erlang:system_profile</c> is considered experimental and
 
5308
        its behaviour may change in the future.</p>
 
5309
        </note>
 
5310
      </desc>
 
5311
    </func>
 
5312
 
 
5313
    <func>
 
5314
      <name>term_to_binary(Term) -> ext_binary()</name>
 
5315
      <fsummary>Encode a term to an Erlang external term format binary</fsummary>
 
5316
      <type>
 
5317
        <v>Term = term()</v>
 
5318
      </type>
 
5319
      <desc>
 
5320
        <p>Returns a binary data object which is the result of encoding
 
5321
          <c>Term</c> according to the Erlang external term format.</p>
 
5322
        <p>This can be used for a variety of purposes, for example
 
5323
          writing a term to a file in an efficient way, or sending an
 
5324
          Erlang term to some type of communications channel not
 
5325
          supported by distributed Erlang.</p>
 
5326
        <p>See also
 
5327
          <seealso marker="#binary_to_term/1">binary_to_term/1</seealso>.</p>
 
5328
      </desc>
 
5329
    </func>
 
5330
    <func>
 
5331
      <name>term_to_binary(Term, [Option]) -> ext_binary()</name>
 
5332
      <fsummary>Encode a term to en Erlang external term format binary</fsummary>
 
5333
      <type>
 
5334
        <v>Term = term()</v>
 
5335
        <v>Option = compressed | {compressed,Level} | {minor_version,Version}</v>
 
5336
      </type>
 
5337
      <desc>
 
5338
        <p>Returns a binary data object which is the result of encoding
 
5339
          <c>Term</c> according to the Erlang external term format.</p>
 
5340
        <p>If the option <c>compressed</c> is provided, the external
 
5341
          term format will be compressed. The compressed format is
 
5342
          automatically recognized by <c>binary_to_term/1</c> in R7B and later.</p>
 
5343
        <p>It is also possible to specify a compression level by giving
 
5344
          the option <c>{compressed,Level}</c>, where <c>Level</c> is an
 
5345
          integer from 0 through 9. <c>0</c> means that no compression
 
5346
          will be done (it is the same as not giving any <c>compressed</c> option);
 
5347
          <c>1</c> will take the least time but may not compress as well as
 
5348
          the higher levels; <c>9</c> will take the most time and may produce
 
5349
          a smaller result. Note the "mays" in the preceding sentence; depending
 
5350
          on the input term, level 9 compression may or may not produce a smaller
 
5351
          result than level 1 compression.</p>
 
5352
        <p>Currently, <c>compressed</c> gives the same result as
 
5353
          <c>{compressed,6}</c>.</p>
 
5354
        <p>The option <c>{minor_version,Version}</c> can be use to control
 
5355
          some details of the encoding. This option was
 
5356
          introduced in R11B-4. Currently, the allowed values for <c>Version</c>
 
5357
          are <c>0</c> and <c>1</c>.</p>
 
5358
        <p><c>{minor_version,1}</c> forces any floats in the term to be encoded
 
5359
          in a more space-efficient and exact way (namely in the 64-bit IEEE format,
 
5360
          rather than converted to a textual representation). <c>binary_to_term/1</c>
 
5361
          in R11B-4 and later is able decode the new representation.</p>
 
5362
        <p><c>{minor_version,0}</c> is currently the default, meaning that floats
 
5363
          will be encoded using a textual representation; this option is useful if
 
5364
          you want to ensure that releases prior to R11B-4 can decode resulting
 
5365
          binary.</p>
 
5366
        <p>See also
 
5367
          <seealso marker="#binary_to_term/1">binary_to_term/1</seealso>.</p>
 
5368
      </desc>
 
5369
    </func>
 
5370
    <func>
 
5371
      <name>throw(Any)</name>
 
5372
      <fsummary>Throw an exception</fsummary>
 
5373
      <type>
 
5374
        <v>Any = term()</v>
 
5375
      </type>
 
5376
      <desc>
 
5377
        <p>A non-local return from a function. If evaluated within a
 
5378
          <c>catch</c>, <c>catch</c> will return the value <c>Any</c>.</p>
 
5379
        <pre>
 
5380
> <input>catch throw({hello, there}).</input>
 
5381
{hello,there}</pre>
 
5382
        <p>Failure: <c>nocatch</c> if not evaluated within a catch.</p>
 
5383
      </desc>
 
5384
    </func>
 
5385
    <func>
 
5386
      <name>time() -> {Hour, Minute, Second}</name>
 
5387
      <fsummary>Current time</fsummary>
 
5388
      <type>
 
5389
        <v>Hour = Minute = Second = int()</v>
 
5390
      </type>
 
5391
      <desc>
 
5392
        <p>Returns the current time as <c>{Hour, Minute, Second}</c>.</p>
 
5393
        <p>The time zone and daylight saving time correction depend on
 
5394
          the underlying OS.</p>
 
5395
        <pre>
 
5396
> <input>time().</input>
 
5397
{9,42,44}</pre>
 
5398
      </desc>
 
5399
    </func>
 
5400
    <func>
 
5401
      <name>tl(List1) -> List2</name>
 
5402
      <fsummary>Tail of a list</fsummary>
 
5403
      <type>
 
5404
        <v>List1 = List2 = [term()]</v>
 
5405
      </type>
 
5406
      <desc>
 
5407
        <p>Returns the tail of <c>List1</c>, that is, the list minus
 
5408
          the first element.</p>
 
5409
        <pre>
 
5410
> <input>tl([geesties, guilies, beasties]).</input>
 
5411
[guilies, beasties]</pre>
 
5412
        <p>Allowed in guard tests.</p>
 
5413
        <p>Failure: <c>badarg</c> if <c>List</c> is the empty list [].</p>
 
5414
      </desc>
 
5415
    </func>
 
5416
    <func>
 
5417
      <name>erlang:trace(PidSpec, How, FlagList) -> int()</name>
 
5418
      <fsummary>Set trace flags for a process or processes</fsummary>
 
5419
      <type>
 
5420
        <v>PidSpec = pid() | existing | new | all</v>
 
5421
        <v>How = bool()</v>
 
5422
        <v>FlagList = [Flag]</v>
 
5423
        <v>&nbsp;Flag -- see below</v>
 
5424
      </type>
 
5425
      <desc>
 
5426
        <p>Turns on (if <c>How == true</c>) or off (if
 
5427
          <c>How == false</c>) the trace flags in <c>FlagList</c> for
 
5428
          the process or processes represented by <c>PidSpec</c>.</p>
 
5429
        <p><c>PidSpec</c> is either a pid for a local process, or one of
 
5430
          the following atoms:</p>
 
5431
        <taglist>
 
5432
          <tag><c>existing</c></tag>
 
5433
          <item>
 
5434
            <p>All processes currently existing.</p>
 
5435
          </item>
 
5436
          <tag><c>new</c></tag>
 
5437
          <item>
 
5438
            <p>All processes that will be created in the future.</p>
 
5439
          </item>
 
5440
          <tag><c>all</c></tag>
 
5441
          <item>
 
5442
            <p>All currently existing processes and all processes that
 
5443
              will be created in the future.</p>
 
5444
          </item>
 
5445
        </taglist>
 
5446
        <p><c>FlagList</c> can contain any number of the following
 
5447
          flags (the "message tags" refers to the list of messages
 
5448
          following below):</p>
 
5449
        <taglist>
 
5450
          <tag><c>all</c></tag>
 
5451
          <item>
 
5452
            <p>Set all trace flags except <c>{tracer, Tracer}</c> and
 
5453
              <c>cpu_timestamp</c> that are in their nature different
 
5454
              than the others.</p>
 
5455
          </item>
 
5456
          <tag><c>send</c></tag>
 
5457
          <item>
 
5458
            <p>Trace sending of messages.</p>
 
5459
            <p>Message tags: <c>send</c>,
 
5460
              <c>send_to_non_existing_process</c>.</p>
 
5461
          </item>
 
5462
          <tag><c>'receive'</c></tag>
 
5463
          <item>
 
5464
            <p>Trace receiving of messages.</p>
 
5465
            <p>Message tags: <c>'receive'</c>.</p>
 
5466
          </item>
 
5467
          <tag><c>procs</c></tag>
 
5468
          <item>
 
5469
            <p>Trace process related events.</p>
 
5470
            <p>Message tags: <c>spawn</c>, <c>exit</c>,
 
5471
              <c>register</c>, <c>unregister</c>, <c>link</c>,
 
5472
              <c>unlink</c>, <c>getting_linked</c>,
 
5473
              <c>getting_unlinked</c>.</p>
 
5474
          </item>
 
5475
          <tag><c>call</c></tag>
 
5476
          <item>
 
5477
            <p>Trace certain function calls. Specify which function
 
5478
              calls to trace by calling
 
5479
              <seealso marker="#erlang:trace_pattern/3">erlang:trace_pattern/3</seealso>.</p>
 
5480
            <p>Message tags: <c>call</c>, <c>return_from</c>.</p>
 
5481
          </item>
 
5482
          <tag><c>silent</c></tag>
 
5483
          <item>
 
5484
            <p>Used in conjunction with the <c>call</c> trace flag.
 
5485
              The <c>call</c>, <c>return_from</c> and <c>return_to</c>
 
5486
              trace messages are inhibited if this flag is set,
 
5487
              but if there are match specs they are executed as normal.</p>
 
5488
            <p>Silent mode is inhibited by executing
 
5489
              <c>erlang:trace(_, false, [silent|_])</c>,
 
5490
              or by a match spec executing the <c>{silent, false}</c>
 
5491
              function.</p>
 
5492
            <p>The <c>silent</c> trace flag facilitates setting up
 
5493
              a trace on many or even all processes in the system.
 
5494
              Then the interesting trace can be activated and
 
5495
              deactivated using the <c>{silent,Bool}</c>
 
5496
              match spec function, giving a high degree
 
5497
              of control of which functions with which 
 
5498
              arguments that triggers the trace.</p>
 
5499
            <p>Message tags: <c>call</c>, <c>return_from</c>, 
 
5500
              <c>return_to</c>. Or rather, the absence of.</p>
 
5501
          </item>
 
5502
          <tag><c>return_to</c></tag>
 
5503
          <item>
 
5504
            <p>Used in conjunction with the <c>call</c> trace flag.
 
5505
              Trace the actual return from a traced function back to
 
5506
              its caller. Only works for functions traced with
 
5507
              the <c>local</c> option to
 
5508
              <seealso marker="#erlang:trace_pattern/3">erlang:trace_pattern/3</seealso>.</p>
 
5509
            <p>The semantics is that a trace message is sent when a
 
5510
              call traced function actually returns, that is, when a
 
5511
              chain of tail recursive calls is ended. There will be
 
5512
              only one trace message sent per chain of tail recursive
 
5513
              calls, why the properties of tail recursiveness for
 
5514
              function calls are kept while tracing with this flag.
 
5515
              Using <c>call</c> and <c>return_to</c> trace together
 
5516
              makes it possible to know exactly in which function a
 
5517
              process executes at any time.</p>
 
5518
            <p>To get trace messages containing return values from
 
5519
              functions, use the <c>{return_trace}</c> match_spec
 
5520
              action instead.</p>
 
5521
            <p>Message tags: <c>return_to</c>.</p>
 
5522
          </item>
 
5523
          <tag><c>running</c></tag>
 
5524
          <item>
 
5525
            <p>Trace scheduling of processes.</p>
 
5526
            <p>Message tags: <c>in</c>, and <c>out</c>.</p>
 
5527
          </item>
 
5528
          <tag><c>exiting</c></tag>
 
5529
          <item>
 
5530
            <p>Trace scheduling of an exiting processes.</p>
 
5531
            <p>Message tags: <c>in_exiting</c>, <c>out_exiting</c>, and
 
5532
            <c>out_exited</c>.</p>
 
5533
          </item>
 
5534
          <tag><c>garbage_collection</c></tag>
 
5535
          <item>
 
5536
            <p>Trace garbage collections of processes.</p>
 
5537
            <p>Message tags: <c>gc_start</c>, <c>gc_end</c>.</p>
 
5538
          </item>
 
5539
          <tag><c>timestamp</c></tag>
 
5540
          <item>
 
5541
            <p>Include a time stamp in all trace messages. The time
 
5542
              stamp (Ts) is of the same form as returned by
 
5543
              <c>erlang:now()</c>.</p>
 
5544
          </item>
 
5545
          <tag><c>cpu_timestamp</c></tag>
 
5546
          <item>
 
5547
            <p>A global trace flag for the Erlang node that makes all
 
5548
              trace timestamps be in CPU time, not wallclock. It is
 
5549
              only allowed with <c>PidSpec==all</c>. If the host
 
5550
              machine operating system does not support high resolution
 
5551
              CPU time measurements, <c>trace/3</c> exits with
 
5552
              <c>badarg</c>.</p>
 
5553
          </item>
 
5554
          <tag><c>arity</c></tag>
 
5555
          <item>
 
5556
            <p>Used in conjunction with the <c>call</c> trace flag.
 
5557
              <c>{M, F, Arity}</c> will be specified instead of
 
5558
              <c>{M, F, Args}</c> in call trace messages.</p>
 
5559
          </item>
 
5560
          <tag><c>set_on_spawn</c></tag>
 
5561
          <item>
 
5562
            <p>Makes any process created by a traced process inherit
 
5563
              its trace flags, including the <c>set_on_spawn</c> flag.</p>
 
5564
          </item>
 
5565
          <tag><c>set_on_first_spawn</c></tag>
 
5566
          <item>
 
5567
            <p>Makes the first process created by a traced process
 
5568
              inherit its trace flags, excluding
 
5569
              the <c>set_on_first_spawn</c> flag.</p>
 
5570
          </item>
 
5571
          <tag><c>set_on_link</c></tag>
 
5572
          <item>
 
5573
            <p>Makes any process linked by a traced process inherit its
 
5574
              trace flags, including the <c>set_on_link</c> flag.</p>
 
5575
          </item>
 
5576
          <tag><c>set_on_first_link</c></tag>
 
5577
          <item>
 
5578
            <p>Makes the first process linked to by a traced process
 
5579
              inherit its trace flags, excluding
 
5580
              the <c>set_on_first_link</c> flag.</p>
 
5581
          </item>
 
5582
          <tag><c>{tracer, Tracer}</c></tag>
 
5583
          <item>
 
5584
            <p>Specify where to send the trace messages. <c>Tracer</c>
 
5585
              must be the pid of a local process or the port identifier
 
5586
              of a local port. If this flag is not given, trace
 
5587
              messages will be sent to the process that called
 
5588
              <c>erlang:trace/3</c>.</p>
 
5589
          </item>
 
5590
        </taglist>
 
5591
        <p>The effect of combining <c>set_on_first_link</c> with
 
5592
          <c>set_on_link</c> is the same as having
 
5593
          <c>set_on_first_link</c> alone. Likewise for
 
5594
          <c>set_on_spawn</c> and <c>set_on_first_spawn</c>.</p>
 
5595
        <p>If the <c>timestamp</c> flag is not given, the tracing
 
5596
          process will receive the trace messages described below.
 
5597
          <c>Pid</c> is the pid of the traced process in which
 
5598
          the traced event has occurred. The third element of the tuple
 
5599
          is the message tag.</p>
 
5600
        <p>If the <c>timestamp</c> flag is given, the first element of
 
5601
          the tuple will be <c>trace_ts</c> instead and the timestamp
 
5602
          is added last in the tuple.</p>
 
5603
        <taglist>
 
5604
          <tag><c>{trace, Pid, 'receive', Msg}</c></tag>
 
5605
          <item>
 
5606
            <p>When <c>Pid</c> receives the message <c>Msg</c>.</p>
 
5607
          </item>
 
5608
          <tag><c>{trace, Pid, send, Msg, To}</c></tag>
 
5609
          <item>
 
5610
            <p>When <c>Pid</c> sends the message <c>Msg</c> to
 
5611
              the process <c>To</c>.</p>
 
5612
          </item>
 
5613
          <tag><c>{trace, Pid, send_to_non_existing_process, Msg, To}</c></tag>
 
5614
          <item>
 
5615
            <p>When <c>Pid</c> sends the message <c>Msg</c> to
 
5616
              the non-existing process <c>To</c>.</p>
 
5617
          </item>
 
5618
          <tag><c>{trace, Pid, call, {M, F, Args}}</c></tag>
 
5619
          <item>
 
5620
            <p>When <c>Pid</c> calls a traced function. The return
 
5621
              values of calls are never supplied, only the call and its
 
5622
              arguments.</p>
 
5623
            <p>Note that the trace flag <c>arity</c> can be used to
 
5624
              change the contents of this message, so that <c>Arity</c>
 
5625
              is specified instead of <c>Args</c>.</p>
 
5626
          </item>
 
5627
          <tag><c>{trace, Pid, return_to, {M, F, Arity}}</c></tag>
 
5628
          <item>
 
5629
            <p>When <c>Pid</c> returns <em>to</em> the specified
 
5630
              function. This trace message is sent if both
 
5631
              the <c>call</c> and the <c>return_to</c> flags are set,
 
5632
              and the function is set to be traced on <em>local</em>
 
5633
              function calls. The message is only sent when returning
 
5634
              from a chain of tail recursive function calls where at
 
5635
              least one call generated a <c>call</c> trace message
 
5636
              (that is, the functions match specification matched and
 
5637
              <c>{message, false}</c> was not an action).</p>
 
5638
          </item>
 
5639
          <tag><c>{trace, Pid, return_from, {M, F, Arity}, ReturnValue}</c></tag>
 
5640
          <item>
 
5641
            <p>When <c>Pid</c> returns <em>from</em> the specified
 
5642
              function. This trace message is sent if the <c>call</c>
 
5643
              flag is set, and the function has a match specification
 
5644
              with a <c>return_trace</c> or <c>exception_trace</c> action.</p>
 
5645
          </item>
 
5646
          <tag><c>{trace, Pid, exception_from, {M, F, Arity}, {Class, Value}}</c></tag>
 
5647
          <item>
 
5648
            <p>When <c>Pid</c> exits <em>from</em> the specified
 
5649
              function due to an exception. This trace message is sent
 
5650
              if the <c>call</c> flag is set, and the function has 
 
5651
              a match specification with an <c>exception_trace</c> action.</p>
 
5652
          </item>
 
5653
          <tag><c>{trace, Pid, spawn, Pid2, {M, F, Args}}</c></tag>
 
5654
          <item>
 
5655
            <p>When <c>Pid</c> spawns a new process <c>Pid2</c> with
 
5656
              the specified function call as entry point.</p>
 
5657
            <p>Note that <c>Args</c> is supposed to be the argument
 
5658
              list, but may be any term in the case of an erroneous
 
5659
              spawn.</p>
 
5660
          </item>
 
5661
          <tag><c>{trace, Pid, exit, Reason}</c></tag>
 
5662
          <item>
 
5663
            <p>When <c>Pid</c> exits with reason <c>Reason</c>.</p>
 
5664
          </item>
 
5665
          <tag><c>{trace, Pid, link, Pid2}</c></tag>
 
5666
          <item>
 
5667
            <p>When <c>Pid</c> links to a process <c>Pid2</c>.</p>
 
5668
          </item>
 
5669
          <tag><c>{trace, Pid, unlink, Pid2}</c></tag>
 
5670
          <item>
 
5671
            <p>When <c>Pid</c> removes the link from a process
 
5672
              <c>Pid2</c>.</p>
 
5673
          </item>
 
5674
          <tag><c>{trace, Pid, getting_linked, Pid2}</c></tag>
 
5675
          <item>
 
5676
            <p>When <c>Pid</c> gets linked to a process <c>Pid2</c>.</p>
 
5677
          </item>
 
5678
          <tag><c>{trace, Pid, getting_unlinked, Pid2}</c></tag>
 
5679
          <item>
 
5680
            <p>When <c>Pid</c> gets unlinked from a process <c>Pid2</c>.</p>
 
5681
          </item>
 
5682
          <tag><c>{trace, Pid, register, RegName}</c></tag>
 
5683
          <item>
 
5684
            <p>When <c>Pid</c> gets the name <c>RegName</c> registered.</p>
 
5685
          </item>
 
5686
          <tag><c>{trace, Pid, unregister, RegName}</c></tag>
 
5687
          <item>
 
5688
            <p>When <c>Pid</c> gets the name <c>RegName</c> unregistered.
 
5689
              Note that this is done automatically when a registered
 
5690
              process exits.</p>
 
5691
          </item>
 
5692
          <tag><c>{trace, Pid, in, {M, F, Arity} | 0}</c></tag>
 
5693
          <item>
 
5694
            <p>When <c>Pid</c> is scheduled to run. The process will
 
5695
              run in function <c>{M, F, Arity}</c>. On some rare
 
5696
              occasions the current function cannot be determined, then
 
5697
              the last element <c>Arity</c> is 0.</p>
 
5698
          </item>
 
5699
          <tag><c>{trace, Pid, out, {M, F, Arity} | 0}</c></tag>
 
5700
          <item>
 
5701
            <p>When <c>Pid</c> is scheduled out. The process was
 
5702
              running in function {M, F, Arity}. On some rare occasions
 
5703
              the current function cannot be determined, then the last
 
5704
              element <c>Arity</c> is 0.</p>
 
5705
          </item>
 
5706
          <tag><c>{trace, Pid, gc_start, Info}</c></tag>
 
5707
          <item>
 
5708
            <marker id="gc_start"></marker>
 
5709
            <p>Sent when garbage collection is about to be started.
 
5710
              <c>Info</c> is a list of two-element tuples, where
 
5711
              the first element is a key, and the second is the value.
 
5712
              You should not depend on the tuples have any defined
 
5713
              order. Currently, the following keys are defined:</p>
 
5714
            <taglist>
 
5715
              <tag><c>heap_size</c></tag>
 
5716
              <item>The size of the used part of the heap.</item>
 
5717
              <tag><c>heap_block_size</c></tag>
 
5718
              <item>The size of the memory block used for storing
 
5719
                    the heap and the stack.</item>
 
5720
              <tag><c>old_heap_size</c></tag>
 
5721
              <item>The size of the used part of the old heap.</item>
 
5722
              <tag><c>old_heap_block_size</c></tag>
 
5723
              <item>The size of the memory block used for storing
 
5724
                    the old heap.</item>
 
5725
              <tag><c>stack_size</c></tag>
 
5726
              <item>The actual size of the stack.</item>
 
5727
              <tag><c>recent_size</c></tag>
 
5728
              <item>The size of the data that survived the previous garbage
 
5729
               collection.</item>
 
5730
              <tag><c>mbuf_size</c></tag>
 
5731
              <item>The combined size of message buffers associated with
 
5732
               the process.</item>
 
5733
            </taglist>
 
5734
            <p>All sizes are in words.</p>
 
5735
          </item>
 
5736
          <tag><c>{trace, Pid, gc_end, Info}</c></tag>
 
5737
          <item>
 
5738
            <p>Sent when garbage collection is finished. <c>Info</c>
 
5739
              contains the same kind of list as in the <c>gc_start</c>
 
5740
              message, but the sizes reflect the new sizes after
 
5741
              garbage collection.</p>
 
5742
          </item>
 
5743
        </taglist>
 
5744
        <p>If the tracing process dies, the flags will be silently
 
5745
          removed.</p>
 
5746
        <p>Only one process can trace a particular process. For this
 
5747
          reason, attempts to trace an already traced process will fail.</p>
 
5748
        <p>Returns: A number indicating the number of processes that
 
5749
          matched <c>PidSpec</c>. If <c>PidSpec</c> is a pid,
 
5750
          the return value will be <c>1</c>. If <c>PidSpec</c> is
 
5751
          <c>all</c> or <c>existing</c> the return value will be
 
5752
          the number of processes running, excluding tracer processes.
 
5753
          If <c>PidSpec</c> is <c>new</c>, the return value will be
 
5754
          <c>0</c>.</p>
 
5755
        <p>Failure: If specified arguments are not supported. For
 
5756
          example <c>cpu_timestamp</c> is not supported on all
 
5757
          platforms.</p>
 
5758
      </desc>
 
5759
    </func>
 
5760
    <func>
 
5761
      <name>erlang:trace_delivered(Tracee) -> Ref</name>
 
5762
      <fsummary>Notification when trace has been delivered</fsummary>
 
5763
      <type>
 
5764
        <v>Tracee = pid() | all</v>
 
5765
        <v>Ref = reference()</v>
 
5766
      </type>
 
5767
      <desc>
 
5768
        <p>The delivery of trace messages is dislocated on the time-line
 
5769
          compared to other events in the system. If you know that the
 
5770
          <c>Tracee</c> has passed some specific point in its execution,
 
5771
          and you want to know when at least all trace messages
 
5772
          corresponding to events up to this point have reached the tracer
 
5773
          you can use <c>erlang:trace_delivered(Tracee)</c>. A
 
5774
          <c>{trace_delivered, Tracee, Ref}</c> message is sent to
 
5775
          the caller of <c>erlang:trace_delivered(Tracee)</c> when it
 
5776
          is guaranteed that all trace messages have been delivered to
 
5777
          the tracer up to the point that the <c>Tracee</c> had reached
 
5778
          at the time of the call to
 
5779
          <c>erlang:trace_delivered(Tracee)</c>.</p>
 
5780
        <p>Note that the <c>trace_delivered</c> message does <em>not</em>
 
5781
          imply that trace messages have been delivered; instead, it implies
 
5782
          that all trace messages that <em>should</em> be delivered have
 
5783
          been delivered. It is not an error if <c>Tracee</c> isn't, and
 
5784
          hasn't been traced by someone, but if this is the case,
 
5785
          <em>no</em> trace messages will have been delivered when the
 
5786
          <c>trace_delivered</c> message arrives.</p>
 
5787
        <p>Note that <c>Tracee</c> has to refer to a process currently,
 
5788
          or previously existing on the same node as the caller of
 
5789
          <c>erlang:trace_delivered(Tracee)</c> resides on.
 
5790
          The special <c>Tracee</c> atom <c>all</c> denotes all processes
 
5791
          that currently are traced in the node.</p>
 
5792
        <p>An example: Process <c>A</c> is tracee, port <c>B</c> is
 
5793
          tracer, and process <c>C</c> is the port owner of <c>B</c>.
 
5794
          <c>C</c> wants to close <c>B</c> when <c>A</c> exits. <c>C</c>
 
5795
          can ensure that the trace isn't truncated by calling
 
5796
          <c>erlang:trace_delivered(A)</c> when <c>A</c> exits and wait
 
5797
          for the <c>{trace_delivered, A, Ref}</c> message before closing
 
5798
          <c>B</c>.</p>
 
5799
        <p>Failure: <c>badarg</c> if <c>Tracee</c> does not refer to a
 
5800
          process (dead or alive) on the same node as the caller of
 
5801
          <c>erlang:trace_delivered(Tracee)</c> resides on.</p>
 
5802
      </desc>
 
5803
    </func>
 
5804
    <func>
 
5805
      <name>erlang:trace_info(PidOrFunc, Item) -> Res</name>
 
5806
      <fsummary>Trace information about a process or function</fsummary>
 
5807
      <type>
 
5808
        <v>PidOrFunc = pid() | new | {Module, Function, Arity} | on_load</v>
 
5809
        <v>&nbsp;Module = Function = atom()</v>
 
5810
        <v>&nbsp;Arity = int()</v>
 
5811
        <v>Item, Res -- see below</v>
 
5812
      </type>
 
5813
      <desc>
 
5814
        <p>Returns trace information about a process or function.</p>
 
5815
        <p>To get information about a process, <c>PidOrFunc</c> should
 
5816
          be a pid or the atom <c>new</c>. The atom <c>new</c> means
 
5817
          that the default trace state for processes to be created will
 
5818
          be returned. <c>Item</c> must have one of the following
 
5819
          values:</p>
 
5820
        <taglist>
 
5821
          <tag><c>flags</c></tag>
 
5822
          <item>
 
5823
            <p>Return a list of atoms indicating what kind of traces is
 
5824
              enabled for the process. The list will be empty if no
 
5825
              traces are enabled, and one or more of the followings
 
5826
              atoms if traces are enabled: <c>send</c>,
 
5827
              <c>'receive'</c>, <c>set_on_spawn</c>, <c>call</c>,
 
5828
              <c>return_to</c>, <c>procs</c>, <c>set_on_first_spawn</c>,
 
5829
              <c>set_on_link</c>, <c>running</c>,
 
5830
              <c>garbage_collection</c>, <c>timestamp</c>, and
 
5831
              <c>arity</c>. The order is arbitrary.</p>
 
5832
          </item>
 
5833
          <tag><c>tracer</c></tag>
 
5834
          <item>
 
5835
            <p>Return the identifier for process or port tracing this
 
5836
              process. If this process is not being traced, the return
 
5837
              value will be <c>[]</c>.</p>
 
5838
          </item>
 
5839
        </taglist>
 
5840
        <p>To get information about a function, <c>PidOrFunc</c> should
 
5841
          be a three-element tuple: <c>{Module, Function, Arity}</c> or
 
5842
          the atom <c>on_load</c>. No wildcards are allowed. Returns
 
5843
          <c>undefined</c> if the function does not exist or
 
5844
          <c>false</c> if the function is not traced at all. <c>Item</c>
 
5845
          must have one of the following values:</p>
 
5846
        <taglist>
 
5847
          <tag><c>traced</c></tag>
 
5848
          <item>
 
5849
            <p>Return <c>global</c> if this function is traced on
 
5850
              global function calls, <c>local</c> if this function is
 
5851
              traced on local function calls (i.e local and global
 
5852
              function calls), and <c>false</c> if neither local nor
 
5853
              global function calls are traced.</p>
 
5854
          </item>
 
5855
          <tag><c>match_spec</c></tag>
 
5856
          <item>
 
5857
            <p>Return the match specification for this function, if it
 
5858
              has one. If the function is locally or globally traced but
 
5859
              has no match specification defined, the returned value
 
5860
              is <c>[]</c>.</p>
 
5861
          </item>
 
5862
          <tag><c>meta</c></tag>
 
5863
          <item>
 
5864
            <p>Return the meta trace tracer process or port for this
 
5865
              function, if it has one. If the function is not meta
 
5866
              traced the returned value is <c>false</c>, and if
 
5867
              the function is meta traced but has once detected that
 
5868
              the tracer proc is invalid, the returned value is [].</p>
 
5869
          </item>
 
5870
          <tag><c>meta_match_spec</c></tag>
 
5871
          <item>
 
5872
            <p>Return the meta trace match specification for this
 
5873
              function, if it has one. If the function is meta traced
 
5874
              but has no match specification defined, the returned
 
5875
              value is <c>[]</c>.</p>
 
5876
          </item>
 
5877
          <tag><c>call_count</c></tag>
 
5878
          <item>
 
5879
            <p>Return the call count value for this function or
 
5880
              <c>true</c> for the pseudo function <c>on_load</c> if call
 
5881
              count tracing is active. Return <c>false</c> otherwise.
 
5882
              See also
 
5883
              <seealso marker="#erlang:trace_pattern/3">erlang:trace_pattern/3</seealso>.</p>
 
5884
          </item>
 
5885
          <tag><c>all</c></tag>
 
5886
          <item>
 
5887
            <p>Return a list containing the <c>{Item, Value}</c> tuples
 
5888
              for all other items, or return <c>false</c> if no tracing
 
5889
              is active for this function.</p>
 
5890
          </item>
 
5891
        </taglist>
 
5892
        <p>The actual return value will be <c>{Item, Value}</c>, where
 
5893
          <c>Value</c> is the requested information as described above.
 
5894
          If a pid for a dead process was given, or the name of a
 
5895
          non-existing function, <c>Value</c> will be <c>undefined</c>.</p>
 
5896
        <p>If <c>PidOrFunc</c> is the <c>on_load</c>, the information
 
5897
          returned refers to the default value for code that will be
 
5898
          loaded.</p>
 
5899
      </desc>
 
5900
    </func>
 
5901
    <func>
 
5902
      <name>erlang:trace_pattern(MFA, MatchSpec) -> int()</name>
 
5903
      <fsummary>Set trace patterns for global call tracing</fsummary>
 
5904
      <desc>
 
5905
        <p>The same as
 
5906
          <seealso marker="#erlang:trace_pattern/3">erlang:trace_pattern(MFA, MatchSpec, [])</seealso>,
 
5907
          retained for backward compatibility.</p>
 
5908
      </desc>
 
5909
    </func>
 
5910
    <func>
 
5911
      <name>erlang:trace_pattern(MFA, MatchSpec, FlagList) -> int()</name>
 
5912
      <fsummary>Set trace patterns for tracing of function calls</fsummary>
 
5913
      <type>
 
5914
        <v>MFA, MatchSpec, FlagList -- see below</v>
 
5915
      </type>
 
5916
      <desc>
 
5917
        <p>This BIF is used to enable or disable call tracing for
 
5918
          exported functions. It must be combined with
 
5919
          <seealso marker="#erlang:trace/3">erlang:trace/3</seealso>
 
5920
          to set the <c>call</c> trace flag for one or more processes.</p>
 
5921
        <p>Conceptually, call tracing works like this: Inside
 
5922
          the Erlang virtual machine there is a set of processes to be
 
5923
          traced and a set of functions to be traced. Tracing will be
 
5924
          enabled on the intersection of the set. That is, if a process
 
5925
          included in the traced process set calls a function included
 
5926
          in the traced function set, the trace action will be taken.
 
5927
          Otherwise, nothing will happen.</p>
 
5928
        <p>Use
 
5929
          <seealso marker="#erlang:trace/3">erlang:trace/3</seealso> to
 
5930
          add or remove one or more processes to the set of traced
 
5931
          processes. Use <c>erlang:trace_pattern/2</c> to add or remove
 
5932
          exported functions to the set of traced functions.</p>
 
5933
        <p>The <c>erlang:trace_pattern/3</c> BIF can also add match
 
5934
          specifications to an exported function. A match specification
 
5935
          comprises a pattern that the arguments to the function must
 
5936
          match, a guard expression which must evaluate to <c>true</c>
 
5937
          and an action to be performed. The default action is to send a
 
5938
          trace message. If the pattern does not match or the guard
 
5939
          fails, the action will not be executed.</p>
 
5940
        <p>The <c>MFA</c> argument should be a tuple like
 
5941
          <c>{Module, Function, Arity}</c> or the atom <c>on_load</c>
 
5942
          (described below). It can be the module, function, and arity
 
5943
          for an exported function (or a BIF in any module).
 
5944
          The <c>'_'</c> atom can be used to mean any of that kind.
 
5945
          Wildcards can be used in any of the following ways:</p>
 
5946
        <taglist>
 
5947
          <tag><c>{Module,Function,'_'}</c></tag>
 
5948
          <item>
 
5949
            <p>All exported functions of any arity named <c>Function</c>
 
5950
              in module <c>Module</c>.</p>
 
5951
          </item>
 
5952
          <tag><c>{Module,'_','_'}</c></tag>
 
5953
          <item>
 
5954
            <p>All exported functions in module <c>Module</c>.</p>
 
5955
          </item>
 
5956
          <tag><c>{'_','_','_'}</c></tag>
 
5957
          <item>
 
5958
            <p>All exported functions in all loaded modules.</p>
 
5959
          </item>
 
5960
        </taglist>
 
5961
        <p>Other combinations, such as <c>{Module,'_',Arity}</c>, are
 
5962
          not allowed. Local functions will match wildcards only if
 
5963
          the <c>local</c> option is in the <c>FlagList</c>.</p>
 
5964
        <p>If the <c>MFA</c> argument is the atom <c>on_load</c>,
 
5965
          the match specification and flag list will be used on all
 
5966
          modules that are newly loaded.</p>
 
5967
        <p>The <c>MatchSpec</c> argument can take any of the following
 
5968
          forms:</p>
 
5969
        <taglist>
 
5970
          <tag><c>false</c></tag>
 
5971
          <item>
 
5972
            <p>Disable tracing for the matching function(s). Any match
 
5973
              specification will be removed.</p>
 
5974
          </item>
 
5975
          <tag><c>true</c></tag>
 
5976
          <item>
 
5977
            <p>Enable tracing for the matching function(s).</p>
 
5978
          </item>
 
5979
          <tag><c>MatchSpecList</c></tag>
 
5980
          <item>
 
5981
            <p>A list of match specifications. An empty list is
 
5982
              equivalent to <c>true</c>. See the ERTS User's Guide
 
5983
              for a description of match specifications.</p>
 
5984
          </item>
 
5985
          <tag><c>restart</c></tag>
 
5986
          <item>
 
5987
            <p>For the <c>FlagList</c> option <c>call_count</c>:
 
5988
              restart the existing counters. The behaviour is undefined
 
5989
              for other <c>FlagList</c> options.</p>
 
5990
          </item>
 
5991
          <tag><c>pause</c></tag>
 
5992
          <item>
 
5993
            <p>For the <c>FlagList</c> option <c>call_count</c>: pause
 
5994
              the existing counters. The behaviour is undefined for
 
5995
              other <c>FlagList</c> options.</p>
 
5996
          </item>
 
5997
        </taglist>
 
5998
        <p>The <c>FlagList</c> parameter is a list of options.
 
5999
          The following options are allowed:</p>
 
6000
        <taglist>
 
6001
          <tag><c>global</c></tag>
 
6002
          <item>
 
6003
            <p>Turn on or off call tracing for global function calls
 
6004
              (that is, calls specifying the module explicitly). Only
 
6005
              exported functions will match and only global calls will
 
6006
              generate trace messages. This is the default.</p>
 
6007
          </item>
 
6008
          <tag><c>local</c></tag>
 
6009
          <item>
 
6010
            <p>Turn on or off call tracing for all types of function
 
6011
              calls. Trace messages will be sent whenever any of
 
6012
              the specified functions are called, regardless of how they
 
6013
              are called. If the <c>return_to</c> flag is set for
 
6014
              the process, a <c>return_to</c> message will also be sent
 
6015
              when this function returns to its caller.</p>
 
6016
          </item>
 
6017
          <tag><c>meta | {meta, Pid}</c></tag>
 
6018
          <item>
 
6019
            <p>Turn on or off meta tracing for all types of function
 
6020
              calls. Trace messages will be sent to the tracer process
 
6021
              or port <c>Pid</c> whenever any of the specified
 
6022
              functions are called, regardless of how they are called.
 
6023
              If no <c>Pid</c> is specified, <c>self()</c> is used as a
 
6024
              default tracer process.</p>
 
6025
            <p>Meta tracing traces all processes and does not care
 
6026
              about the process trace flags set by <c>trace/3</c>,
 
6027
              the trace flags are instead fixed to
 
6028
              <c>[call, timestamp]</c>.</p>
 
6029
            <p>The match spec function <c>{return_trace}</c> works with
 
6030
              meta trace and send its trace message to the same tracer
 
6031
              process.</p>
 
6032
          </item>
 
6033
          <tag><c>call_count</c></tag>
 
6034
          <item>
 
6035
            <p>Starts (<c>MatchSpec == true</c>) or stops
 
6036
              (<c>MatchSpec == false</c>) call count tracing for all
 
6037
              types of function calls. For every function a counter is
 
6038
              incremented when the function is called, in any process.
 
6039
              No process trace flags need to be activated.</p>
 
6040
            <p>If call count tracing is started while already running,
 
6041
              the count is restarted from zero. Running counters can be
 
6042
              paused with <c>MatchSpec == pause</c>. Paused and running
 
6043
              counters can be restarted from zero with
 
6044
              <c>MatchSpec == restart</c>.</p>
 
6045
            <p>The counter value can be read with
 
6046
              <seealso marker="#erlang:trace_info/2">erlang:trace_info/2</seealso>.</p>
 
6047
          </item>
 
6048
        </taglist>
 
6049
        <p>The <c>global</c> and <c>local</c> options are mutually
 
6050
          exclusive and <c>global</c> is the default (if no options are
 
6051
          specified). The <c>call_count</c> and <c>meta</c> options
 
6052
          perform a kind of local tracing, and can also not be combined
 
6053
          with <c>global</c>. A function can be either globally or
 
6054
          locally traced. If global tracing is specified for a
 
6055
          specified set of functions; local, meta and call count
 
6056
          tracing for the matching set of local functions will be
 
6057
          disabled, and vice versa.</p>
 
6058
        <p>When disabling trace, the option must match the type of trace
 
6059
          that is set on the function, so that local tracing must be
 
6060
          disabled with the <c>local</c> option and global tracing with
 
6061
          the <c>global</c> option (or no option at all), and so forth.</p>
 
6062
        <p>There is no way to directly change part of a match
 
6063
          specification list. If a function has a match specification,
 
6064
          you can replace it with a completely new one. If you need to
 
6065
          change an existing match specification, use the
 
6066
          <seealso marker="#erlang:trace_info/2">erlang:trace_info/2</seealso>
 
6067
          BIF to retrieve the existing match specification.</p>
 
6068
        <p>Returns the number of exported functions that matched
 
6069
          the <c>MFA</c> argument. This will be zero if none matched at
 
6070
          all.</p>
 
6071
      </desc>
 
6072
    </func>
 
6073
    <func>
 
6074
      <name>trunc(Number) -> int()</name>
 
6075
      <fsummary>Return an integer by the truncating a number</fsummary>
 
6076
      <type>
 
6077
        <v>Number = number()</v>
 
6078
      </type>
 
6079
      <desc>
 
6080
        <p>Returns an integer by the truncating <c>Number</c>.</p>
 
6081
        <pre>
 
6082
> <input>trunc(5.5).</input>
 
6083
5</pre>
 
6084
        <p>Allowed in guard tests.</p>
 
6085
      </desc>
 
6086
    </func>
 
6087
    <func>
 
6088
      <name>tuple_size(Tuple) -> int()</name>
 
6089
      <fsummary>Return the size of a tuple</fsummary>
 
6090
      <type>
 
6091
        <v>Tuple = tuple()</v>
 
6092
      </type>
 
6093
      <desc>
 
6094
        <p>Returns an integer which is the number of elements in <c>Tuple</c>.</p>
 
6095
        <pre>
 
6096
> <input>tuple_size({morni, mulle, bwange}).</input>
 
6097
3</pre>
 
6098
        <p>Allowed in guard tests.</p>
 
6099
      </desc>
 
6100
    </func>
 
6101
    <func>
 
6102
      <name>tuple_to_list(Tuple) -> [term()]</name>
 
6103
      <fsummary>Convert a tuple to a list</fsummary>
 
6104
      <type>
 
6105
        <v>Tuple = tuple()</v>
 
6106
      </type>
 
6107
      <desc>
 
6108
        <p>Returns a list which corresponds to <c>Tuple</c>.
 
6109
          <c>Tuple</c> may contain any Erlang terms.</p>
 
6110
        <pre>
 
6111
> <input>tuple_to_list({share, {'Ericsson_B', 163}}).</input>
 
6112
[share,{'Ericsson_B',163}]</pre>
 
6113
      </desc>
 
6114
    </func>
 
6115
    <func>
 
6116
      <name>erlang:universaltime() -> {Date, Time}</name>
 
6117
      <fsummary>Current date and time according to Universal Time Coordinated (UTC)</fsummary>
 
6118
      <type>
 
6119
        <v>Date = {Year, Month, Day}</v>
 
6120
        <v>Time = {Hour, Minute, Second}</v>
 
6121
        <v>&nbsp;Year = Month = Day = Hour = Minute = Second = int()</v>
 
6122
      </type>
 
6123
      <desc>
 
6124
        <p>Returns the current date and time according to Universal
 
6125
          Time Coordinated (UTC), also called GMT, in the form
 
6126
          <c>{{Year, Month, Day}, {Hour, Minute, Second}}</c> if
 
6127
          supported by the underlying operating system. If not,
 
6128
          <c>erlang:universaltime()</c> is equivalent to
 
6129
          <c>erlang:localtime()</c>.</p>
 
6130
        <pre>
 
6131
> <input>erlang:universaltime().</input>
 
6132
{{1996,11,6},{14,18,43}}</pre>
 
6133
      </desc>
 
6134
    </func>
 
6135
    <func>
 
6136
      <name>erlang:universaltime_to_localtime({Date1, Time1}) -> {Date2, Time2}</name>
 
6137
      <fsummary>Convert from Universal Time Coordinated (UTC) to local date and time</fsummary>
 
6138
      <type>
 
6139
        <v>Date1 = Date2 = {Year, Month, Day}</v>
 
6140
        <v>Time1 = Time2 = {Hour, Minute, Second}</v>
 
6141
        <v>&nbsp;Year = Month = Day = Hour = Minute = Second = int()</v>
 
6142
      </type>
 
6143
      <desc>
 
6144
        <p>Converts Universal Time Coordinated (UTC) date and time to
 
6145
          local date and time, if this is supported by the underlying
 
6146
          OS. Otherwise, no conversion is done, and
 
6147
          <c>{Date1, Time1}</c> is returned.</p>
 
6148
        <pre>
 
6149
> <input>erlang:universaltime_to_localtime({{1996,11,6},{14,18,43}}).</input>
 
6150
{{1996,11,7},{15,18,43}}</pre>
 
6151
        <p>Failure: <c>badarg</c> if <c>Date1</c> or <c>Time1</c> do
 
6152
          not denote a valid date or time.</p>
 
6153
      </desc>
 
6154
    </func>
 
6155
    <func>
 
6156
      <name>unlink(Id) -> true</name>
 
6157
      <fsummary>Remove a link, if there is one, to another process or port</fsummary>
 
6158
      <type>
 
6159
        <v>Id = pid() | port()</v>
 
6160
      </type>
 
6161
      <desc>
 
6162
        <p>Removes the link, if there is one, between the calling
 
6163
          process and the process or port referred to by <c>Id</c>.</p>
 
6164
        <p>Returns <c>true</c> and does not fail, even if there is no
 
6165
          link to <c>Id</c>, or if <c>Id</c> does not exist.</p>
 
6166
        <p>Once <c>unlink(Id)</c> has returned it is guaranteed that
 
6167
          the link between the caller and the entity referred to by
 
6168
          <c>Id</c> has no effect on the caller in the future (unless
 
6169
          the link is setup again). If caller is trapping exits, an
 
6170
          <c>{'EXIT', Id, _}</c> message due to the link might have
 
6171
          been placed in the callers message queue prior to the call,
 
6172
          though. Note, the <c>{'EXIT', Id, _}</c> message can be the
 
6173
          result of the link, but can also be the result of <c>Id</c>
 
6174
          calling <c>exit/2</c>. Therefore, it <em>may</em> be
 
6175
          appropriate to cleanup the message queue when trapping exits
 
6176
          after the call to <c>unlink(Id)</c>, as follow:</p>
 
6177
        <code type="none">
 
6178
 
 
6179
    unlink(Id),
 
6180
    receive
 
6181
\011{'EXIT', Id, _} ->
 
6182
\011    true
 
6183
    after 0 ->
 
6184
\011    true
 
6185
    end</code>
 
6186
        <note>
 
6187
          <p>Prior to OTP release R11B (erts version 5.5) <c>unlink/1</c>
 
6188
            behaved completely asynchronous, i.e., the link was active
 
6189
            until the "unlink signal" reached the linked entity. This
 
6190
            had one undesirable effect, though. You could never know when
 
6191
            you were guaranteed <em>not</em> to be effected by the link.</p>
 
6192
          <p>Current behavior can be viewed as two combined operations:
 
6193
            asynchronously send an "unlink signal" to the linked entity
 
6194
            and ignore any future results of the link.</p>
 
6195
        </note>
 
6196
      </desc>
 
6197
    </func>
 
6198
    <func>
 
6199
      <name>unregister(RegName) -> true</name>
 
6200
      <fsummary>Remove the registered name for a process (or port)</fsummary>
 
6201
      <type>
 
6202
        <v>RegName = atom()</v>
 
6203
      </type>
 
6204
      <desc>
 
6205
        <p>Removes the registered name <c>RegName</c>, associated with a
 
6206
          pid or a port identifier.</p>
 
6207
        <pre>
 
6208
> <input>unregister(db).</input>
 
6209
true</pre>
 
6210
        <p>Users are advised not to unregister system processes.</p>
 
6211
        <p>Failure: <c>badarg</c> if <c>RegName</c> is not a registered
 
6212
          name.</p>
 
6213
      </desc>
 
6214
    </func>
 
6215
    <func>
 
6216
      <name>whereis(RegName) -> pid() | port() | undefined</name>
 
6217
      <fsummary>Get the pid (or port) with a given registered name</fsummary>
 
6218
      <desc>
 
6219
        <p>Returns the pid or port identifier with the registered name
 
6220
          <c>RegName</c>. Returns <c>undefined</c> if the name is not
 
6221
          registered.</p>
 
6222
        <pre>
 
6223
> <input>whereis(db).</input>
 
6224
&lt;0.43.0></pre>
 
6225
      </desc>
 
6226
    </func>
 
6227
    <func>
 
6228
      <name>erlang:yield() -> true</name>
 
6229
      <fsummary>Let other processes get a chance to execute</fsummary>
 
6230
      <desc>
 
6231
        <p>Voluntarily let other processes (if any) get a chance to
 
6232
          execute. Using <c>erlang:yield()</c> is similar to
 
6233
          <c>receive after 1 -> ok end</c>, except that <c>yield()</c>
 
6234
          is faster.</p>
 
6235
      </desc>
 
6236
    </func>
 
6237
  </funcs>
 
6238
</erlref>
 
6239