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

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/beam_lib.xml

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
<?xml version="1.0" encoding="latin1" ?>
 
2
<!DOCTYPE erlref SYSTEM "erlref.dtd">
 
3
 
 
4
<erlref>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>2000</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>beam_lib</title>
 
27
    <prepared>Hans Bolinder</prepared>
 
28
    <docno></docno>
 
29
    <date>1999-10-30</date>
 
30
    <rev>PA1</rev>
 
31
  </header>
 
32
  <module>beam_lib</module>
 
33
  <modulesummary>An Interface To the BEAM File Format</modulesummary>
 
34
  <description>
 
35
    <p><c>beam_lib</c> provides an interface to files created by
 
36
      the BEAM compiler ("BEAM files"). The format used, a variant of
 
37
      "EA IFF 1985" Standard for Interchange Format Files, divides data
 
38
      into chunks.</p>
 
39
    <p>Chunk data can be returned as binaries or as compound terms.
 
40
      Compound terms are returned when chunks are referenced by names
 
41
      (atoms) rather than identifiers (strings).  The names recognized
 
42
      and the corresponding identifiers are:</p>
 
43
    <list type="bulleted">
 
44
      <item><c>abstract_code ("Abst")</c></item>
 
45
      <item><c>attributes ("Attr")</c></item>
 
46
      <item><c>compile_info ("CInf")</c></item>
 
47
      <item><c>exports ("ExpT")</c></item>
 
48
      <item><c>labeled_exports ("ExpT")</c></item>
 
49
      <item><c>imports ("ImpT")</c></item>
 
50
      <item><c>indexed_imports ("ImpT")</c></item>
 
51
      <item><c>locals ("LocT")</c></item>
 
52
      <item><c>labeled_locals ("LocT")</c></item>
 
53
      <item><c>atoms ("Atom")</c></item>
 
54
    </list>
 
55
  </description>
 
56
 
 
57
  <section>
 
58
    <marker id="debug_info"></marker>
 
59
    <title>Debug Information/Abstract Code</title>
 
60
    <p>The option <c>debug_info</c> can be given to the compiler (see
 
61
      <seealso marker="compiler:compile#debug_info">compile(3)</seealso>)
 
62
      in order to have debug information in the form of abstract code
 
63
      (see <seealso marker="erts:absform">The Abstract Format</seealso>
 
64
      in ERTS User's Guide) stored in the <c>abstract_code</c> chunk.
 
65
      Tools such as Debugger and Xref require the debug information to
 
66
      be included.</p>
 
67
    <warning>
 
68
      <p>Source code can be reconstructed from the debug information.
 
69
        Use encrypted debug information (see below) to prevent this.</p>
 
70
    </warning>
 
71
    <p>The debug information can also be removed from BEAM files
 
72
      using <seealso marker="#strip/1">strip/1</seealso>,
 
73
      <seealso marker="#strip_files/1">strip_files/1</seealso> and/or
 
74
      <seealso marker="#strip_release/1">strip_release/1</seealso>.</p>
 
75
    <p><em>Reconstructing source code</em></p>
 
76
    <p>Here is an example of how to reconstruct source code from
 
77
      the debug information in a BEAM file <c>Beam</c>:</p>
 
78
    <code type="none">
 
79
      {ok,{_,[{abstract_code,{_,AC}}]}} = beam_lib:chunks(Beam,[abstract_code]).
 
80
      io:fwrite("~s~n", [erl_prettypr:format(erl_syntax:form_list(AC))]).</code>
 
81
    <p><em>Encrypted debug information</em></p>
 
82
    <p>The debug information can be encrypted in order to keep
 
83
      the source code secret, but still being able to use tools such as
 
84
      Xref or Debugger. </p>
 
85
    <p>To use encrypted debug information, a key must be provided to
 
86
      the compiler and <c>beam_lib</c>. The key is given as a string and
 
87
      it is recommended that it contains at least 32 characters and
 
88
      that both upper and lower case letters as well as digits and
 
89
      special characters are used.</p>
 
90
    <p></p>
 
91
    <p>The default type -- and currently the only type -- of crypto
 
92
      algorithm is <c>des3_cbc</c>, three rounds of DES. The key string
 
93
      will be scrambled using <c>erlang:md5/1</c> to generate
 
94
      the actual keys used for <c>des3_cbc</c>.</p>
 
95
    <note>
 
96
      <p>As far as we know when by the time of writing, it is
 
97
        infeasible to break <c>des3_cbc</c> encryption without any
 
98
        knowledge of the key. Therefore, as long as the key is kept
 
99
        safe and is unguessable, the encrypted debug information
 
100
        <em>should</em> be safe from intruders.</p>
 
101
    </note>
 
102
    <p>There are two ways to provide the key:</p>
 
103
    <list type="ordered">
 
104
      <item>
 
105
        <p>Use the compiler option <c>{debug_info,Key}</c>, see
 
106
          <seealso marker="compiler:compile#debug_info_key">compile(3)</seealso>,
 
107
          and the function
 
108
          <seealso marker="#crypto_key_fun/1">crypto_key_fun/1</seealso>
 
109
          to register a fun which returns the key whenever
 
110
          <c>beam_lib</c> needs to decrypt the debug information.</p>
 
111
        <p>If no such fun is registered, <c>beam_lib</c> will instead
 
112
          search for a <c>.erlang.crypt</c> file, see below.</p>
 
113
      </item>
 
114
      <item>
 
115
        <p>Store the key in a text file named <c>.erlang.crypt</c>.</p>
 
116
        <p>In this case, the compiler option <c>encrypt_debug_info</c>
 
117
          can be used, see
 
118
          <seealso marker="compiler:compile#encrypt_debug_info">compile(3)</seealso>.</p>
 
119
      </item>
 
120
    </list>
 
121
    <p><em>.erlang.crypt</em></p>
 
122
    <p><c>beam_lib</c> searches for <c>.erlang.crypt</c> in the current
 
123
      directory and then the home directory for the current user. If
 
124
      the file is found and contains a key, <c>beam_lib</c> will
 
125
      implicitly create a crypto key fun and register it.</p>
 
126
    <p>The <c>.erlang.crypt</c> file should contain a single list of
 
127
      tuples:</p>
 
128
    <code type="none">
 
129
      {debug_info, Mode, Module, Key}</code>
 
130
    <p><c>Mode</c> is the type of crypto algorithm; currently, the only
 
131
      allowed value thus is <c>des3_cbc</c>. <c>Module</c> is either an
 
132
      atom, in which case <c>Key</c> will only be used for the module
 
133
      <c>Module</c>, or <c>[]</c>, in which case <c>Key</c> will be
 
134
      used for all modules. <c>Key</c> is the non-empty key string.</p>
 
135
    <p>The <c>Key</c> in the first tuple where both <c>Mode</c> and
 
136
      <c>Module</c> matches will be used.</p>
 
137
    <p>Here is an example of an <c>.erlang.crypt</c> file that returns
 
138
      the same key for all modules:</p>
 
139
    <code type="none"><![CDATA[
 
140
[{debug_info, des3_cbc, [], "%>7}|pc/DM6Cga*68$Mw]L#&_Gejr]G^"}].]]></code>
 
141
    <p>And here is a slightly more complicated example of an
 
142
      <c>.erlang.crypt</c> which provides one key for the module
 
143
      <c>t</c>, and another key for all other modules:</p>
 
144
    <code type="none"><![CDATA[
 
145
[{debug_info, des3_cbc, t, "My KEY"},
 
146
 {debug_info, des3_cbc, [], "%>7}|pc/DM6Cga*68$Mw]L#&_Gejr]G^"}].]]></code>
 
147
    <note>
 
148
      <p>Do not use any of the keys in these examples. Use your own
 
149
        keys.</p>
 
150
    </note>
 
151
  </section>
 
152
 
 
153
  <section>
 
154
    <title>DATA TYPES</title>
 
155
    <code type="none">
 
156
beam() -> Module | Filename | binary()
 
157
  Module = atom()
 
158
  Filename = string() | atom()</code>
 
159
    <p>Each of the functions described below accept either the module
 
160
      name, the filename, or a binary containing the beam module.</p>
 
161
    <code type="none">
 
162
chunkdata() = {ChunkId, DataB} | {ChunkName, DataT}
 
163
  ChunkId = chunkid()
 
164
  DataB = binary()
 
165
  {ChunkName, DataT} =
 
166
        {abstract_code, AbstractCode}
 
167
      | {attributes, [{Attribute, [AttributeValue]}]}
 
168
      | {compile_info, [{InfoKey, [InfoValue]}]}
 
169
      | {exports, [{Function, Arity}]}
 
170
      | {labeled_exports, [{Function, Arity, Label}]}
 
171
      | {imports, [{Module, Function, Arity}]}
 
172
      | {indexed_imports, [{Index, Module, Function, Arity}]}
 
173
      | {locals, [{Function, Arity}]}]}
 
174
      | {labeled_locals, [{Function, Arity, Label}]}]}
 
175
      | {atoms, [{integer(), atom()}]}
 
176
  AbstractCode = {AbstVersion, Forms} | no_abstract_code
 
177
    AbstVersion = atom()
 
178
  Attribute = atom()
 
179
  AttributeValue = term()
 
180
  Module = Function = atom()
 
181
  Arity = int()
 
182
  Label = int()</code>
 
183
    <p>It is not checked that the forms conform to the abstract format
 
184
      indicated by <c>AbstVersion</c>. <c>no_abstract_code</c> means
 
185
      that the <c>"Abst"</c> chunk is present, but empty.</p>
 
186
    <p>The list of attributes is sorted on <c>Attribute</c>, and each
 
187
      attribute name occurs once in the list. The attribute values
 
188
      occur in the same order as in the file. The lists of functions
 
189
      are also sorted.</p>
 
190
    <code type="none">
 
191
chunkid() = "Abst" | "Attr" | "CInf"
 
192
            | "ExpT" | "ImpT" | "LocT"
 
193
            | "Atom"
 
194
 
 
195
chunkname() = abstract_code | attributes | compile_info
 
196
            | exports | labeled_exports
 
197
            | imports | indexed_imports
 
198
            | locals | labeled_locals
 
199
            | atoms
 
200
      
 
201
chunkref() = chunkname() | chunkid()</code>
 
202
  </section>
 
203
  <funcs>
 
204
    <func>
 
205
      <name>chunks(Beam, [ChunkRef]) ->  {ok, {Module, [ChunkData]}} | {error, beam_lib, Reason}</name>
 
206
      <fsummary>Read selected chunks from a BEAM file or binary</fsummary>
 
207
      <type>
 
208
        <v>Beam = beam()</v>
 
209
        <v>ChunkRef = chunkref()</v>
 
210
        <v>Module = atom()</v>
 
211
        <v>ChunkData = chunkdata()</v>
 
212
        <v>Reason = {unknown_chunk, Filename, atom()}</v>
 
213
        <v>&nbsp;&nbsp;| {key_missing_or_invalid, Filename, abstract_code}</v>
 
214
        <v>&nbsp;&nbsp;| Reason1 -- see info/1</v>
 
215
        <v>&nbsp;Filename = string()</v>
 
216
      </type>
 
217
      <desc>
 
218
        <p>Reads chunk data for selected chunks refs. The order of
 
219
          the returned list of chunk data is determined by the order
 
220
          of the list of chunks references.</p>
 
221
      </desc>
 
222
    </func>
 
223
    <func>
 
224
      <name>chunks(Beam, [ChunkRef], [Option]) ->  {ok, {Module, [ChunkResult]}} | {error, beam_lib, Reason}</name>
 
225
      <fsummary>Read selected chunks from a BEAM file or binary</fsummary>
 
226
      <type>
 
227
        <v>Beam = beam()</v>
 
228
        <v>ChunkRef = chunkref()</v>
 
229
        <v>Module = atom()</v>
 
230
        <v>Option = allow_missing_chunks</v>
 
231
        <v>ChunkResult = {chunkref(), ChunkContents} | {chunkref(), missing_chunk}</v>
 
232
        <v>Reason = {missing_chunk, Filename, atom()}</v>
 
233
        <v>&nbsp;&nbsp;| {key_missing_or_invalid, Filename, abstract_code}</v>
 
234
        <v>&nbsp;&nbsp;| Reason1 -- see info/1</v>
 
235
        <v>&nbsp;Filename = string()</v>
 
236
      </type>
 
237
      <desc>
 
238
        <p>Reads chunk data for selected chunks refs. The order of
 
239
          the returned list of chunk data is determined by the order
 
240
          of the list of chunks references.</p>
 
241
        <p>By default, if any requested chunk is missing in <c>Beam</c>,
 
242
          an <c>error</c> tuple is returned.
 
243
          However, if the option <c>allow_missing_chunks</c> has been given,
 
244
          a result will be returned even if chunks are missing.
 
245
          In the result list, any missing chunks will be represented as
 
246
          <c>{ChunkRef,missing_chunk}</c>.
 
247
          Note, however, that if the <c>"Atom"</c> chunk if missing, that is
 
248
          considered a fatal error and the return value will be an <c>error</c>
 
249
          tuple.</p>
 
250
      </desc>
 
251
    </func>
 
252
    <func>
 
253
      <name>version(Beam) -> {ok, {Module, [Version]}} | {error, beam_lib, Reason}</name>
 
254
      <fsummary>Read the BEAM file's module version</fsummary>
 
255
      <type>
 
256
        <v>Beam = beam()</v>
 
257
        <v>Module = atom()</v>
 
258
        <v>Version = term()</v>
 
259
        <v>Reason -- see chunks/2</v>
 
260
      </type>
 
261
      <desc>
 
262
        <p>Returns the module version(s). A version is defined by
 
263
          the module attribute <c>-vsn(Vsn)</c>. If this attribute is
 
264
          not specified, the version defaults to the checksum of
 
265
          the module. Note that if the version <c>Vsn</c> is not a list,
 
266
          it is made into one, that is <c>{ok,{Module,[Vsn]}}</c> is
 
267
          returned. If there are several <c>-vsn</c> module attributes,
 
268
          the result is the concatenated list of versions. Examples:</p>
 
269
        <pre>
 
270
1> <input>beam_lib:version(a).</input> % -vsn(1).
 
271
{ok,{a,[1]}}
 
272
2> <input>beam_lib:version(b).</input> % -vsn([1]).
 
273
{ok,{b,[1]}}
 
274
3> <input>beam_lib:version(c).</input> % -vsn([1]). -vsn(2).
 
275
{ok,{c,[1,2]}}
 
276
4> <input>beam_lib:version(d).</input> % no -vsn attribute
 
277
{ok,{d,[275613208176997377698094100858909383631]}}</pre>
 
278
      </desc>
 
279
    </func>
 
280
    <func>
 
281
      <name>md5(Beam) -> {ok, {Module, MD5}} | {error, beam_lib, Reason}</name>
 
282
      <fsummary>Read the BEAM file's module version</fsummary>
 
283
      <type>
 
284
        <v>Beam = beam()</v>
 
285
        <v>Module = atom()</v>
 
286
        <v>MD5 = binary()</v>
 
287
        <v>Reason -- see chunks/2</v>
 
288
      </type>
 
289
      <desc>
 
290
        <p>Calculates an MD5 redundancy check for the code of the module
 
291
          (compilation date and other attributes are not included).</p>
 
292
      </desc>
 
293
    </func>
 
294
    <func>
 
295
      <name>info(Beam) -> [{Item, Info}] | {error, beam_lib, Reason1}</name>
 
296
      <fsummary>Information about a BEAM file</fsummary>
 
297
      <type>
 
298
        <v>Beam = beam()</v>
 
299
        <v>Item, Info -- see below</v>
 
300
        <v>Reason1 = {chunk_too_big, Filename, ChunkId, ChunkSize, FileSize}</v>
 
301
        <v>&nbsp;&nbsp;| {invalid_beam_file, Filename, Pos}</v>
 
302
        <v>&nbsp;&nbsp;| {invalid_chunk, Filename, ChunkId}</v>
 
303
        <v>&nbsp;&nbsp;| {missing_chunk, Filename, ChunkId}</v>
 
304
        <v>&nbsp;&nbsp;| {not_a_beam_file, Filename}</v>
 
305
        <v>&nbsp;&nbsp;| {file_error, Filename, Posix}</v>
 
306
        <v>&nbsp;Filename = string()</v>
 
307
        <v>&nbsp;ChunkId = chunkid()</v>
 
308
        <v>&nbsp;ChunkSize = FileSize = int()</v>
 
309
        <v>&nbsp;Pos = int()</v>
 
310
        <v>&nbsp;Posix = posix() -- see file(3)</v>
 
311
      </type>
 
312
      <desc>
 
313
        <p>Returns a list containing some information about a BEAM file
 
314
          as tuples <c>{Item, Info}</c>:</p>
 
315
        <taglist>
 
316
          <tag><c>{file, Filename} | {binary, Binary}</c></tag>
 
317
          <item>
 
318
            <p>The name (string) of the BEAM file, or the binary from
 
319
              which the information was extracted.</p>
 
320
          </item>
 
321
          <tag><c>{module, Module}</c></tag>
 
322
          <item>
 
323
            <p>The name (atom) of the module.</p>
 
324
          </item>
 
325
          <tag><c>{chunks, [{ChunkId, Pos, Size}]}</c></tag>
 
326
          <item>
 
327
            <p>For each chunk, the identifier (string) and the position
 
328
              and size of the chunk data, in bytes.</p>
 
329
          </item>
 
330
        </taglist>
 
331
      </desc>
 
332
    </func>
 
333
    <func>
 
334
      <name>cmp(Beam1, Beam2) -> ok | {error, beam_lib, Reason}</name>
 
335
      <fsummary>Compare two BEAM files</fsummary>
 
336
      <type>
 
337
        <v>Beam1 = Beam2 = beam()</v>
 
338
        <v>Reason = {modules_different, Module1, Module2}</v>
 
339
        <v>&nbsp;&nbsp;| {chunks_different, ChunkId}</v>
 
340
        <v>&nbsp;&nbsp;| Reason1 -- see info/1</v>
 
341
        <v>&nbsp;Module1 = Module2 = atom()</v>
 
342
        <v>&nbsp;ChunkId = chunkid()</v>
 
343
      </type>
 
344
      <desc>
 
345
        <p>Compares the contents of two BEAM files. If the module names
 
346
          are the same, and the chunks with the identifiers
 
347
          <c>"Code"</c>, <c>"ExpT"</c>, <c>"ImpT"</c>, <c>"StrT"</c>,
 
348
          and <c>"Atom"</c> have the same contents in both files,
 
349
          <c>ok</c> is returned. Otherwise an error message is returned.</p>
 
350
      </desc>
 
351
    </func>
 
352
    <func>
 
353
      <name>cmp_dirs(Dir1, Dir2) ->  {Only1, Only2, Different} | {error, beam_lib, Reason1}</name>
 
354
      <fsummary>Compare the BEAM files in two directories</fsummary>
 
355
      <type>
 
356
        <v>Dir1 = Dir2 = string() | atom()</v>
 
357
        <v>Different = [{Filename1, Filename2}]</v>
 
358
        <v>Only1 = Only2 = [Filename]</v>
 
359
        <v>Filename = Filename1 = Filename2 = string()</v>
 
360
        <v>Reason1 = {not_a_directory, term()} | -- see info/1</v>
 
361
      </type>
 
362
      <desc>
 
363
        <p>The <c>cmp_dirs/2</c> function compares the BEAM files in
 
364
          two directories. Only files with extension <c>".beam"</c> are
 
365
          compared. BEAM files that exist in directory <c>Dir1</c>
 
366
          (<c>Dir2</c>) only are returned in <c>Only1</c>
 
367
          (<c>Only2</c>). BEAM files that exist on both directories but
 
368
          are considered different by <c>cmp/2</c> are returned as
 
369
          pairs {<c>Filename1</c>, <c>Filename2</c>} where
 
370
          <c>Filename1</c> (<c>Filename2</c>) exists in directory
 
371
          <c>Dir1</c> (<c>Dir2</c>).</p>
 
372
      </desc>
 
373
    </func>
 
374
    <func>
 
375
      <name>diff_dirs(Dir1, Dir2) -> ok | {error, beam_lib, Reason1}</name>
 
376
      <fsummary>Compare the BEAM files in two directories</fsummary>
 
377
      <type>
 
378
        <v>Dir1 = Dir2 = string() | atom()</v>
 
379
        <v>Reason1 = {not_a_directory, term()} | -- see info/1</v>
 
380
      </type>
 
381
      <desc>
 
382
        <p>The <c>diff_dirs/2</c> function compares the BEAM files in
 
383
          two directories the way <c>cmp_dirs/2</c> does, but names of
 
384
          files that exist in only one directory or are different are
 
385
          presented on standard output.</p>
 
386
      </desc>
 
387
    </func>
 
388
    <func>
 
389
      <name>strip(Beam1) -> {ok, {Module, Beam2}} | {error, beam_lib, Reason1}</name>
 
390
      <fsummary>Removes chunks not needed by the loader from a BEAM file</fsummary>
 
391
      <type>
 
392
        <v>Beam1 = Beam2 = beam()</v>
 
393
        <v>Module = atom()</v>
 
394
        <v>Reason1 -- see info/1</v>
 
395
      </type>
 
396
      <desc>
 
397
        <p>The <c>strip/1</c> function removes all chunks from a BEAM
 
398
          file except those needed by the loader. In particular,
 
399
          the debug information (<c>abstract_code</c> chunk) is removed.</p>
 
400
      </desc>
 
401
    </func>
 
402
    <func>
 
403
      <name>strip_files(Files) ->  {ok, [{Module, Beam2}]} | {error, beam_lib, Reason1}</name>
 
404
      <fsummary>Removes chunks not needed by the loader from BEAM files</fsummary>
 
405
      <type>
 
406
        <v>Files = [Beam1]</v>
 
407
        <v>&nbsp;Beam1 = beam()</v>
 
408
        <v>Module = atom()</v>
 
409
        <v>Beam2 = beam()</v>
 
410
        <v>Reason1 -- see info/1</v>
 
411
      </type>
 
412
      <desc>
 
413
        <p>The <c>strip_files/1</c> function removes all chunks except
 
414
          those needed by the loader from BEAM files. In particular,
 
415
          the debug information (<c>abstract_code</c> chunk) is removed.
 
416
          The returned list contains one element for each given file
 
417
          name, in the same order as in <c>Files</c>.</p>
 
418
      </desc>
 
419
    </func>
 
420
    <func>
 
421
      <name>strip_release(Dir) ->  {ok, [{Module, Filename]}} | {error, beam_lib, Reason1}</name>
 
422
      <fsummary>Removes chunks not needed by the loader from all BEAM files of a release</fsummary>
 
423
      <type>
 
424
        <v>Dir = string() | atom()</v>
 
425
        <v>Module = atom()</v>
 
426
        <v>Filename = string()</v>
 
427
        <v>Reason1 = {not_a_directory, term()} | -- see info/1</v>
 
428
      </type>
 
429
      <desc>
 
430
        <p>The <c>strip_release/1</c> function removes all chunks
 
431
          except those needed by the loader from the BEAM files of a
 
432
          release. <c>Dir</c> should be the installation root
 
433
          directory. For example, the current OTP release can be
 
434
          stripped with the call
 
435
          <c>beam_lib:strip_release(code:root_dir())</c>.</p>
 
436
      </desc>
 
437
    </func>
 
438
    <func>
 
439
      <name>format_error(Reason) -> Chars</name>
 
440
      <fsummary>Return an English description of a BEAM read error reply</fsummary>
 
441
      <type>
 
442
        <v>Reason -- see other functions</v>
 
443
        <v>Chars = [char() | Chars]</v>
 
444
      </type>
 
445
      <desc>
 
446
        <p>Given the error returned by any function in this module, 
 
447
          the function <c>format_error</c> returns a descriptive string
 
448
          of the error in English. For file errors, the function 
 
449
          <c>file:format_error(Posix)</c> should be called.</p>
 
450
      </desc>
 
451
    </func>
 
452
    <func>
 
453
      <name>crypto_key_fun(CryptoKeyFun) -> ok | {error, Reason}</name>
 
454
      <fsummary>Register a fun that provides a crypto key</fsummary>
 
455
      <type>
 
456
        <v>CryptoKeyFun = fun() -- see below</v>
 
457
        <v>Reason = badfun | exists | term()</v>
 
458
      </type>
 
459
      <desc>
 
460
        <p>The <c>crypto_key_fun/1</c> function registers a unary fun
 
461
          that will be called if <c>beam_lib</c> needs to read an
 
462
          <c>abstract_code</c> chunk that has been encrypted. The fun
 
463
          is held in a process that is started by the function.</p>
 
464
        <p>If there already is a fun registered when attempting to
 
465
          register a fun, <c>{error, exists}</c> is returned.</p>
 
466
        <p>The fun must handle the following arguments:</p>
 
467
        <code type="none">
 
468
\011  CryptoKeyFun(init) -> ok | {ok, NewCryptoKeyFun} | {error, Term}</code>
 
469
        <p>Called when the fun is registered, in the process that holds
 
470
          the fun. Here the crypto key fun can do any necessary
 
471
          initializations. If <c>{ok, NewCryptoKeyFun}</c> is returned
 
472
          then <c>NewCryptoKeyFun</c> will be registered instead of
 
473
          <c>CryptoKeyFun</c>. If <c>{error, Term}</c> is returned,
 
474
          the registration is aborted and <c>crypto_key_fun/1</c>
 
475
          returns <c>{error, Term}</c> as well.</p>
 
476
        <code type="none">
 
477
\011  CryptoKeyFun({debug_info, Mode, Module, Filename}) -> Key</code>
 
478
        <p>Called when the key is needed for the module <c>Module</c>
 
479
          in the file named <c>Filename</c>. <c>Mode</c> is the type of
 
480
          crypto algorithm; currently, the only possible value thus is
 
481
          <c>des3_cbc</c>. The call should fail (raise an exception) if
 
482
          there is no key available.</p>
 
483
        <code type="none">
 
484
\011  CryptoKeyFun(clear) -> term()</code>
 
485
        <p>Called before the fun is unregistered. Here any cleaning up
 
486
          can be done. The return value is not important, but is passed
 
487
          back to the caller of <c>clear_crypto_key_fun/0</c> as part
 
488
          of its return value.</p>
 
489
      </desc>
 
490
    </func>
 
491
    <func>
 
492
      <name>clear_crypto_key_fun() -> {ok, Result}</name>
 
493
      <fsummary>Unregister the current crypto key fun</fsummary>
 
494
      <type>
 
495
        <v>Result = undefined | term()</v>
 
496
      </type>
 
497
      <desc>
 
498
        <p>Unregisters the crypto key fun and terminates the process
 
499
          holding it, started by <c>crypto_key_fun/1</c>.</p>
 
500
        <p>The <c>clear_crypto_key_fun/1</c> either returns
 
501
          <c>{ok, undefined}</c> if there was no crypto key fun
 
502
          registered, or <c>{ok, Term}</c>, where <c>Term</c> is
 
503
          the return value from <c>CryptoKeyFun(clear)</c>, see
 
504
          <c>crypto_key_fun/1</c>.</p>
 
505
      </desc>
 
506
    </func>
 
507
  </funcs>
 
508
</erlref>
 
509