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

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/dets.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>dets</title>
 
27
    <prepared>Claes Wikstr&ouml;m</prepared>
 
28
    <responsible>Claes Wikstr&ouml;m</responsible>
 
29
    <docno></docno>
 
30
    <approved>nobody</approved>
 
31
    <checked>no</checked>
 
32
    <date>2001-06-06</date>
 
33
    <rev>B</rev>
 
34
    <file>dets.sgml</file>
 
35
  </header>
 
36
  <module>dets</module>
 
37
  <modulesummary>A Disk Based Term Storage</modulesummary>
 
38
  <description>
 
39
    <p>The module <c>dets</c> provides a term storage on file. The
 
40
      stored terms, in this module called <em>objects</em>, are tuples
 
41
      such that one element is defined to be the key. A Dets
 
42
      <em>table</em> is a collection of objects with the key at the same
 
43
      position stored on a file.</p>
 
44
    <p>Dets is used by the Mnesia application, and is provided as is
 
45
      for users who are interested in an efficient storage of Erlang
 
46
      terms on disk only. Many applications just need to store some
 
47
      terms in a file. Mnesia adds transactions, queries, and
 
48
      distribution. The size of Dets files cannot exceed 2 GB. If larger
 
49
      tables are needed, Mnesia's table fragmentation can be used.</p>
 
50
    <p>There are three types of Dets tables: set, bag and
 
51
      duplicate_bag. A table of type <em>set</em> has at most one object
 
52
      with a given key. If an object with a key already present in the
 
53
      table is inserted, the existing object is overwritten by the new
 
54
      object. A table of type <em>bag</em> has zero or more different
 
55
      objects with a given key. A table of type <em>duplicate_bag</em>
 
56
      has zero or more possibly matching objects with a given key.</p>
 
57
    <p>Dets tables must be opened before they can be updated or read,
 
58
      and when finished they must be properly closed. If a table has not
 
59
      been properly closed, Dets will automatically repair the table.
 
60
      This can take a substantial time if the table is large. A Dets
 
61
      table is closed when the process which opened the table
 
62
      terminates. If several Erlang processes (users) open the same Dets
 
63
      table, they will share the table. The table is properly closed
 
64
      when all users have either terminated or closed the table. Dets
 
65
      tables are not properly closed if the Erlang runtime system is
 
66
      terminated abnormally.</p>
 
67
    <note>
 
68
      <p>A ^C command abnormally terminates an Erlang runtime
 
69
        system in a Unix environment with a break-handler.</p>
 
70
    </note>
 
71
    <p>Since all operations performed by Dets are disk operations, it
 
72
      is important to realize that a single look-up operation involves a
 
73
      series of disk seek and read operations. For this reason, the Dets
 
74
      functions are much slower than the corresponding Ets functions,
 
75
      although Dets exports a similar interface.</p>
 
76
    <p>Dets organizes data as a linear hash list and the hash list
 
77
      grows gracefully as more data is inserted into the table. Space
 
78
      management on the file is performed by what is called a buddy
 
79
      system. The current implementation keeps the entire buddy system
 
80
      in RAM, which implies that if the table gets heavily fragmented,
 
81
      quite some memory can be used up. The only way to defragment a
 
82
      table is to close it and then open it again with the <c>repair</c>
 
83
      option set to <c>force</c>.</p>
 
84
    <p>It is worth noting that the ordered_set type present in Ets is
 
85
      not yet implemented by Dets, neither is the limited support for
 
86
      concurrent updates which makes a sequence of <c>first</c> and
 
87
      <c>next</c> calls safe to use on fixed Ets tables. Both these
 
88
      features will be implemented by Dets in a future release of
 
89
      Erlang/OTP. Until then, the Mnesia application (or some user
 
90
      implemented method for locking) has to be used to implement safe
 
91
      concurrency. Currently, no library of Erlang/OTP has support for
 
92
      ordered disk based term storage.</p>
 
93
    <p>Two versions of the format used for storing objects on file are
 
94
      supported by Dets. The first version, 8, is the format always used
 
95
      for tables created by OTP R7 and earlier. The second version, 9,
 
96
      is the default version of tables created by OTP R8 (and later OTP
 
97
      releases). OTP R8 can create version 8 tables, and convert version
 
98
      8 tables to version 9, and vice versa, upon request.
 
99
      </p>
 
100
    <p>All Dets functions return <c>{error, Reason}</c> if an error
 
101
      occurs (<c>first/1</c> and <c>next/2</c> are exceptions, they exit
 
102
      the process with the error tuple). If given badly formed
 
103
      arguments, all functions exit the process with a <c>badarg</c>
 
104
      message.</p>
 
105
    <p><em>Types</em></p>
 
106
    <pre>
 
107
access() = read | read_write
 
108
auto_save() = infinity | int()
 
109
bindings_cont() = tuple()
 
110
bool() = true | false
 
111
file() = string()
 
112
int() = integer() >= 0
 
113
keypos() = integer() >= 1
 
114
name() = atom() | ref()
 
115
no_slots() = integer() >= 0 | default
 
116
object() = tuple()
 
117
object_cont() = tuple()
 
118
select_cont() = tuple()
 
119
type() = bag | duplicate_bag | set
 
120
version() = 8 | 9 | default    </pre>
 
121
  </description>
 
122
  <funcs>
 
123
    <func>
 
124
      <name>all() -> [Name]</name>
 
125
      <fsummary>Return a list of the names of all open Dets tables on this node.</fsummary>
 
126
      <type>
 
127
        <v>Name = name()</v>
 
128
      </type>
 
129
      <desc>
 
130
        <p>Returns a list of the names of all open tables on this
 
131
          node.</p>
 
132
      </desc>
 
133
    </func>
 
134
    <func>
 
135
      <name>bchunk(Name, Continuation) -> {Continuation2, Data} | '$end_of_table' | {error, Reason}</name>
 
136
      <fsummary>Return a chunk of objects stored in a Dets table.</fsummary>
 
137
      <type>
 
138
        <v>Name = name()</v>
 
139
        <v>Continuation = start | cont()</v>
 
140
        <v>Continuation2 = cont()</v>
 
141
        <v>Data = binary() | tuple()</v>
 
142
      </type>
 
143
      <desc>
 
144
        <p>Returns a list of objects stored in a table. The exact
 
145
          representation of the returned objects is not public. The
 
146
          lists of data can be used for initializing a table by giving
 
147
          the value <c>bchunk</c> to the <c>format</c> option of the
 
148
          <c>init_table/3</c> function. The Mnesia application uses this
 
149
          function for copying open tables.</p>
 
150
        <p>Unless the table is protected using <c>safe_fixtable/2</c>,
 
151
          calls to <c>bchunk/2</c> may not work as expected if
 
152
          concurrent updates are made to the table.</p>
 
153
        <p>The first time <c>bchunk/2</c> is called, an initial
 
154
          continuation, the atom <c>start</c>, must be provided.</p>
 
155
        <p>The <c>bchunk/2</c> function returns a tuple
 
156
          <c>{Continuation2, Data}</c>, where <c>Data</c> is a list of
 
157
          objects. <c>Continuation2</c> is another continuation which is
 
158
          to be passed on to a subsequent call to <c>bchunk/2</c>. With
 
159
          a series of calls to <c>bchunk/2</c> it is possible to extract
 
160
          all objects of the table.
 
161
          </p>
 
162
        <p><c>bchunk/2</c> returns <c>'$end_of_table'</c> when all
 
163
          objects have been returned, or <c>{error, Reason}</c> if an
 
164
          error occurs.
 
165
          </p>
 
166
      </desc>
 
167
    </func>
 
168
    <func>
 
169
      <name>close(Name) -> ok | {error, Reason} </name>
 
170
      <fsummary>Close a Dets table.</fsummary>
 
171
      <type>
 
172
        <v>Name = name()</v>
 
173
      </type>
 
174
      <desc>
 
175
        <p>Closes a table. Only processes that have opened a table are
 
176
          allowed to close it.
 
177
          </p>
 
178
        <p>All open tables must be closed before the system is
 
179
          stopped. If an attempt is made to open a table which has not
 
180
          been properly closed, Dets automatically tries to repair the
 
181
          table.</p>
 
182
      </desc>
 
183
    </func>
 
184
    <func>
 
185
      <name>delete(Name, Key) -> ok | {error, Reason}</name>
 
186
      <fsummary>Delete all objects with a given key from a Dets table.</fsummary>
 
187
      <type>
 
188
        <v>Name = name()</v>
 
189
      </type>
 
190
      <desc>
 
191
        <p>Deletes all objects with the key <c>Key</c> from the table
 
192
          <c>Name</c>.</p>
 
193
      </desc>
 
194
    </func>
 
195
    <func>
 
196
      <name>delete_all_objects(Name) -> ok | {error, Reason}</name>
 
197
      <fsummary>Delete all objects from a Dets table.</fsummary>
 
198
      <type>
 
199
        <v>Name = name()</v>
 
200
      </type>
 
201
      <desc>
 
202
        <p>Deletes all objects from a table in almost constant time.
 
203
          However, if the table if fixed, <c>delete_all_objects(T)</c>
 
204
          is equivalent to <c>match_delete(T, '_')</c>.</p>
 
205
      </desc>
 
206
    </func>
 
207
    <func>
 
208
      <name>delete_object(Name, Object) -> ok | {error, Reason}</name>
 
209
      <fsummary>Delete a given object from a Dets table.</fsummary>
 
210
      <type>
 
211
        <v>Name = name()</v>
 
212
        <v>Object = object()</v>
 
213
      </type>
 
214
      <desc>
 
215
        <p>Deletes all instances of a given object from a table. If a
 
216
          table is of type <c>bag</c> or <c>duplicate_bag</c>, the
 
217
          <c>delete/2</c> function cannot be used to delete only some of
 
218
          the objects with a given key. This function makes this
 
219
          possible.</p>
 
220
      </desc>
 
221
    </func>
 
222
    <func>
 
223
      <name>first(Name) -> Key | '$end_of_table'</name>
 
224
      <fsummary>Return the first key stored in a Dets table.</fsummary>
 
225
      <type>
 
226
        <v>Key = term()</v>
 
227
        <v>Name = name()</v>
 
228
      </type>
 
229
      <desc>
 
230
        <p>Returns the first key stored in the table <c>Name</c>
 
231
          according to the table's internal order, or
 
232
          <c>'$end_of_table'</c> if the table is empty.</p>
 
233
        <p>Unless the table is protected using <c>safe_fixtable/2</c>,
 
234
          subsequent calls to <c>next/2</c> may not work as expected if
 
235
          concurrent updates are made to the table.</p>
 
236
        <p>Should an error occur, the process is exited with an error
 
237
          tuple <c>{error, Reason}</c>. The reason for not returning the
 
238
          error tuple is that it cannot be distinguished from a key.</p>
 
239
        <p>There are two reasons why <c>first/1</c> and <c>next/2</c>
 
240
          should not be used: they are not very efficient, and they
 
241
          prevent the use of the key <c>'$end_of_table'</c> since this
 
242
          atom is used to indicate the end of the table. If possible,
 
243
          the <c>match</c>, <c>match_object</c>, and <c>select</c>
 
244
          functions should be used for traversing tables.</p>
 
245
      </desc>
 
246
    </func>
 
247
    <func>
 
248
      <name>foldl(Function, Acc0, Name) -> Acc1 | {error, Reason}</name>
 
249
      <fsummary>Fold a function over a Dets table.</fsummary>
 
250
      <type>
 
251
        <v>Function = fun(Object, AccIn) -> AccOut</v>
 
252
        <v>Acc0 = Acc1 = AccIn = AccOut = term()</v>
 
253
        <v>Name = name()</v>
 
254
        <v>Object = object()</v>
 
255
      </type>
 
256
      <desc>
 
257
        <p>Calls <c>Function</c> on successive elements of the table
 
258
          <c>Name</c> together with an extra argument <c>AccIn</c>. The
 
259
          order in which the elements of the table are traversed is
 
260
          unspecified. <c>Function</c> must return a new accumulator
 
261
          which is passed to the next call. <c>Acc0</c> is returned if
 
262
          the table is empty.</p>
 
263
      </desc>
 
264
    </func>
 
265
    <func>
 
266
      <name>foldr(Function, Acc0, Name) -> Acc1 | {error, Reason}</name>
 
267
      <fsummary>Fold a function over a Dets table.</fsummary>
 
268
      <type>
 
269
        <v>Function = fun(Object, AccIn) -> AccOut</v>
 
270
        <v>Acc0 = Acc1 = AccIn = AccOut = term()</v>
 
271
        <v>Name = name()</v>
 
272
        <v>Object = object()</v>
 
273
      </type>
 
274
      <desc>
 
275
        <p>Calls <c>Function</c> on successive elements of the table
 
276
          <c>Name</c> together with an extra argument <c>AccIn</c>. The
 
277
          order in which the elements of the table are traversed is
 
278
          unspecified. <c>Function</c> must return a new accumulator
 
279
          which is passed to the next call. <c>Acc0</c> is returned if
 
280
          the table is empty.</p>
 
281
      </desc>
 
282
    </func>
 
283
    <func>
 
284
      <name>from_ets(Name, EtsTab) -> ok | {error, Reason}</name>
 
285
      <fsummary>Replace the objects of a Dets table with the objects of an Ets table.</fsummary>
 
286
      <type>
 
287
        <v>Name = name()</v>
 
288
        <v>EtsTab = -&nbsp;see ets(3)&nbsp;-</v>
 
289
      </type>
 
290
      <desc>
 
291
        <p>Deletes all objects of the table <c>Name</c> and then
 
292
          inserts all the objects of the Ets table <c>EtsTab</c>. The
 
293
          order in which the objects are inserted is not specified.
 
294
          Since <c>ets:safe_fixtable/2</c> is called the Ets table must
 
295
          be public or owned by the calling process.</p>
 
296
      </desc>
 
297
    </func>
 
298
    <func>
 
299
      <name>info(Name) -> InfoList | undefined</name>
 
300
      <fsummary>Return information about a Dets table.</fsummary>
 
301
      <type>
 
302
        <v>Name = name()</v>
 
303
        <v>InfoList = [{Item, Value}]</v>
 
304
      </type>
 
305
      <desc>
 
306
        <p>Returns information about the table <c>Name</c> as a list of
 
307
          <c>{Item, Value}</c> tuples:</p>
 
308
        <list type="bulleted">
 
309
          <item>
 
310
            <p><c>{file_size, int()}</c>, the size of the file in
 
311
              bytes.</p>
 
312
          </item>
 
313
          <item>
 
314
            <p><c>{filename, file()}</c>, the name of the file
 
315
              where objects are stored.</p>
 
316
          </item>
 
317
          <item>
 
318
            <p><c>{keypos, keypos()}</c>, the position of the
 
319
              key.</p>
 
320
          </item>
 
321
          <item>
 
322
            <p><c>{size, int()}</c>, the number of objects stored
 
323
              in the table.</p>
 
324
          </item>
 
325
          <item>
 
326
            <p><c>{type, type()}</c>, the type of the table.</p>
 
327
          </item>
 
328
        </list>
 
329
      </desc>
 
330
    </func>
 
331
    <func>
 
332
      <name>info(Name, Item) -> Value | undefined</name>
 
333
      <fsummary>Return the information associated with a given item for a Dets table.</fsummary>
 
334
      <type>
 
335
        <v>Name = name()</v>
 
336
      </type>
 
337
      <desc>
 
338
        <p>Returns the information associated with <c>Item</c> for the
 
339
          table <c>Name</c>. In addition to the <c>{Item, Value}</c>
 
340
          pairs defined for <c>info/1</c>, the following items are
 
341
          allowed:</p>
 
342
        <list type="bulleted">
 
343
          <item>
 
344
            <p><c>{access, access()}</c>, the access mode.</p>
 
345
          </item>
 
346
          <item>
 
347
            <p><c>{auto_save, auto_save()}</c>, the auto save
 
348
              interval.</p>
 
349
          </item>
 
350
          <item>
 
351
            <p><c>{bchunk_format, binary()}</c>, an opaque binary
 
352
              describing the format of the objects returned by
 
353
              <c>bchunk/2</c>. The binary can be used as argument to
 
354
              <c>is_compatible_chunk_format/2</c>. Only available for
 
355
              version 9 tables.</p>
 
356
          </item>
 
357
          <item>
 
358
            <p><c>{hash,</c> Hash<c>}</c>. Describes which BIF is
 
359
              used to calculate the hash values of the objects stored in
 
360
              the Dets table. Possible values of Hash are <c>hash</c>,
 
361
              which implies that the <c>erlang:hash/2</c> BIF is used,
 
362
              <c>phash</c>, which implies that the <c>erlang:phash/2</c>
 
363
              BIF is used, and <c>phash2</c>, which implies that the
 
364
              <c>erlang:phash2/1</c> BIF is used.</p>
 
365
          </item>
 
366
          <item>
 
367
            <p><c>{memory, int()}</c>, the size of the file in
 
368
              bytes. The same value is associated with the item
 
369
              <c>file_size</c>.</p>
 
370
          </item>
 
371
          <item>
 
372
            <p><c>{no_keys, int()}</c>, the number of different
 
373
              keys stored in the table. Only available for version 9
 
374
              tables.</p>
 
375
          </item>
 
376
          <item>
 
377
            <p><c>{no_objects, int()}</c>, the number of objects
 
378
              stored in the table.</p>
 
379
          </item>
 
380
          <item>
 
381
            <p><c>{no_slots, {Min, Used, Max}}</c>, the number of
 
382
              slots of the table. <c>Min</c> is the minimum number of
 
383
              slots, <c>Used</c> is the number of currently used slots,
 
384
              and <c>Max</c> is the maximum number of slots. Only
 
385
              available for version 9 tables.</p>
 
386
          </item>
 
387
          <item>
 
388
            <p><c>{owner, pid()}</c>, the pid of the process that
 
389
              handles requests to the Dets table.</p>
 
390
          </item>
 
391
          <item>
 
392
            <p><c>{ram_file, bool()}</c>, whether the table is
 
393
              kept in RAM.</p>
 
394
          </item>
 
395
          <item>
 
396
            <p><c>{safe_fixed,</c> SafeFixed<c>}</c>. If the table
 
397
              is fixed, SafeFixed is a tuple <c>{FixedAtTime, [{Pid,RefCount}]}</c>. <c>FixedAtTime</c> is the time when
 
398
              the table was first fixed, and <c>Pid</c> is the pid of
 
399
              the process that fixes the table <c>RefCount</c> times.
 
400
              There may be any number of processes in the list. If the
 
401
              table is not fixed, SafeFixed is the atom <c>false</c>.</p>
 
402
          </item>
 
403
          <item>
 
404
            <p><c>{version, int()}</c>, the version of the format
 
405
              of the table.</p>
 
406
          </item>
 
407
        </list>
 
408
      </desc>
 
409
    </func>
 
410
    <func>
 
411
      <name>init_table(Name, InitFun [, Options]) -> ok  | {error, Reason}</name>
 
412
      <fsummary>Replace all objects of a Dets table.</fsummary>
 
413
      <type>
 
414
        <v>Name = atom()</v>
 
415
        <v>InitFun = fun(Arg) -> Res</v>
 
416
        <v>Arg = read | close</v>
 
417
        <v>Res = end_of_input | {[object()], InitFun} | {Data, InitFun}  | term()</v>
 
418
        <v>Data = binary() | tuple()</v>
 
419
      </type>
 
420
      <desc>
 
421
        <p>Replaces the existing objects of the table <c>Name</c> with
 
422
          objects created by calling the input function <c>InitFun</c>,
 
423
          see below. The reason for using this function rather than
 
424
          calling <c>insert/2</c> is that of efficiency. It should be
 
425
          noted that the input functions are called by the process that
 
426
          handles requests to the Dets table, not by the calling
 
427
          process.</p>
 
428
        <p>When called with the argument <c>read</c> the function
 
429
          <c>InitFun</c> is assumed to return <c>end_of_input</c> when
 
430
          there is no more input, or <c>{Objects, Fun}</c>, where
 
431
          <c>Objects</c> is a list of objects and <c>Fun</c> is a new
 
432
          input function. Any other value Value is returned as an error
 
433
          <c>{error, {init_fun, Value}}</c>. Each input function will be
 
434
          called exactly once, and should an error occur, the last
 
435
          function is called with the argument <c>close</c>, the reply
 
436
          of which is ignored.</p>
 
437
        <p>If the type of the table is <c>set</c> and there is more
 
438
          than one object with a given key, one of the objects is
 
439
          chosen. This is not necessarily the last object with the given
 
440
          key in the sequence of objects returned by the input
 
441
          functions. Duplicate keys should be avoided, or the file 
 
442
          will be unnecessarily fragmented. This holds also for duplicated
 
443
          objects stored in tables of type <c>bag</c>.</p>
 
444
        <p>It is important that the table has a sufficient number of
 
445
          slots for the objects. If not, the hash list will start to
 
446
          grow when <c>init_table/2</c> returns which will significantly
 
447
          slow down access to the table for a period of time. The
 
448
          minimum number of slots is set by the <c>open_file/2</c>
 
449
          option <c>min_no_slots</c> and returned by the <c>info/2</c>
 
450
          item <c>no_slots</c>. See also the <c>min_no_slots</c> option
 
451
          below.
 
452
          </p>
 
453
        <p>The <c>Options</c> argument is a list of <c>{Key, Val}</c>
 
454
          tuples where the following values are allowed:</p>
 
455
        <list type="bulleted">
 
456
          <item>
 
457
            <p><c>{min_no_slots, no_slots()}</c>. Specifies the
 
458
              estimated number of different keys that will be stored
 
459
              in the table. The <c>open_file</c> option with the same
 
460
              name is ignored unless the table is created, and in that
 
461
              case performance can be enhanced by supplying an
 
462
              estimate when initializing the table.</p>
 
463
          </item>
 
464
          <item>
 
465
            <p><c>{format, Format}</c>. Specifies the format of the
 
466
              objects returned by the function <c>InitFun</c>. If
 
467
              <c>Format</c> is <c>term</c> (the default),
 
468
              <c>InitFun</c> is assumed to return a list of tuples. If
 
469
              <c>Format</c> is <c>bchunk</c>, <c>InitFun</c> is
 
470
              assumed to return <c>Data</c> as returned by
 
471
              <c>bchunk/2</c>. This option overrides the
 
472
              <c>min_no_slots</c> option.</p>
 
473
          </item>
 
474
        </list>
 
475
      </desc>
 
476
    </func>
 
477
    <func>
 
478
      <name>insert(Name, Objects) -> ok | {error, Reason}</name>
 
479
      <fsummary>Insert one or more objects into a Dets table.</fsummary>
 
480
      <type>
 
481
        <v>Name = name()</v>
 
482
        <v>Objects = object() | [object()]</v>
 
483
      </type>
 
484
      <desc>
 
485
        <p>Inserts one or more objects into the table <c>Name</c>. If
 
486
          there already exists an object with a key matching the key of
 
487
          some of the given objects and the table type is <c>set</c>,
 
488
          the old object will be replaced.</p>
 
489
      </desc>
 
490
    </func>
 
491
    <func>
 
492
      <name>insert_new(Name, Objects) -> Bool</name>
 
493
      <fsummary>Insert one or more objects into a Dets table.</fsummary>
 
494
      <type>
 
495
        <v>Name = name()</v>
 
496
        <v>Objects = object() | [object()]</v>
 
497
        <v>Bool = bool()</v>
 
498
      </type>
 
499
      <desc>
 
500
        <p>Inserts one or more objects into the table <c>Name</c>. If
 
501
          there already exists some object with a key matching the key
 
502
          of any of the given objects the table is not updated and
 
503
          <c>false</c> is returned, otherwise the objects are inserted
 
504
          and <c>true</c> returned.</p>
 
505
      </desc>
 
506
    </func>
 
507
    <func>
 
508
      <name>is_compatible_bchunk_format(Name, BchunkFormat) -> Bool</name>
 
509
      <fsummary>Test compatibility of a table's chunk data.</fsummary>
 
510
      <type>
 
511
        <v>Name = name()</v>
 
512
        <v>BchunkFormat = binary()</v>
 
513
        <v>Bool = bool()</v>
 
514
      </type>
 
515
      <desc>
 
516
        <p>Returns <c>true</c> if it would be possible to initialize
 
517
          the table <c>Name</c>, using <c>init_table/3</c> with the
 
518
          option <c>{format,&nbsp;bchunk}</c>, with objects read with
 
519
          <c>bchunk/2</c> from some table <c>T</c> such that calling
 
520
          <c>info(T,&nbsp;bchunk_format)</c> returns
 
521
          <c>BchunkFormat</c>.</p>
 
522
      </desc>
 
523
    </func>
 
524
    <func>
 
525
      <name>is_dets_file(FileName) -> Bool | {error, Reason}</name>
 
526
      <fsummary>Test for a Dets table.</fsummary>
 
527
      <type>
 
528
        <v>FileName = file()</v>
 
529
        <v>Bool = bool()</v>
 
530
      </type>
 
531
      <desc>
 
532
        <p>Returns <c>true</c> if the file <c>FileName</c> is a Dets
 
533
          table, <c>false</c> otherwise.</p>
 
534
      </desc>
 
535
    </func>
 
536
    <func>
 
537
      <name>lookup(Name, Key) -> [Object] | {error, Reason}</name>
 
538
      <fsummary>Return all objects with a given key stored in a Dets table.</fsummary>
 
539
      <type>
 
540
        <v>Key = term()</v>
 
541
        <v>Name = name()</v>
 
542
        <v>Object = object()</v>
 
543
      </type>
 
544
      <desc>
 
545
        <p>Returns a list of all objects with the key <c>Key</c>
 
546
          stored in the table <c>Name</c>. For example:</p>
 
547
        <pre>
 
548
2> <input>dets:open_file(abc, [{type, bag}]).</input>
 
549
{ok,abc}
 
550
3> <input>dets:insert(abc, {1,2,3}).</input>
 
551
ok
 
552
4> <input>dets:insert(abc, {1,3,4}).</input>
 
553
ok
 
554
5> <input>dets:lookup(abc, 1).</input>
 
555
[{1,2,3},{1,3,4}]        </pre>
 
556
        <p>If the table is of type <c>set</c>, the function returns
 
557
          either the empty list or a list with one object, as there
 
558
          cannot be more than one object with a given key. If the table
 
559
          is of type <c>bag</c> or <c>duplicate_bag</c>, the function
 
560
          returns a list of arbitrary length.</p>
 
561
        <p>Note that the order of objects returned is unspecified. In
 
562
          particular, the order in which objects were inserted is not
 
563
          reflected.</p>
 
564
      </desc>
 
565
    </func>
 
566
    <func>
 
567
      <name>match(Continuation) -> {[Match], Continuation2} | '$end_of_table' | {error, Reason}</name>
 
568
      <fsummary>Match a chunk of objects stored in a Dets table and return a list of variable bindings.</fsummary>
 
569
      <type>
 
570
        <v>Continuation = Continuation2 = bindings_cont()</v>
 
571
        <v>Match = [term()]</v>
 
572
      </type>
 
573
      <desc>
 
574
        <p>Matches some objects stored in a table and returns a
 
575
          non-empty list of the bindings that match a given pattern in
 
576
          some unspecified order. The table, the pattern, and the number
 
577
          of objects that are matched are all defined by
 
578
          <c>Continuation</c>, which has been returned by a prior call
 
579
          to <c>match/1</c> or <c>match/3</c>.</p>
 
580
        <p>When all objects of the table have been matched,
 
581
          <c>'$end_of_table'</c> is returned.</p>
 
582
      </desc>
 
583
    </func>
 
584
    <func>
 
585
      <name>match(Name, Pattern) -> [Match] | {error, Reason}</name>
 
586
      <fsummary>Match the objects stored in a Dets table and return a list of variable bindings.</fsummary>
 
587
      <type>
 
588
        <v>Name = name()</v>
 
589
        <v>Pattern = tuple()</v>
 
590
        <v>Match = [term()]</v>
 
591
      </type>
 
592
      <desc>
 
593
        <p>Returns for each object of the table <c>Name</c> that
 
594
          matches <c>Pattern</c> a list of bindings in some unspecified
 
595
          order. See <seealso marker="ets">ets(3)</seealso> for a
 
596
          description of patterns. If the keypos'th element of
 
597
          <c>Pattern</c> is unbound, all objects of the table are
 
598
          matched. If the keypos'th element is bound, only the
 
599
          objects with the right key are matched.</p>
 
600
      </desc>
 
601
    </func>
 
602
    <func>
 
603
      <name>match(Name, Pattern, N) -> {[Match], Continuation}  | '$end_of_table' | {error, Reason}</name>
 
604
      <fsummary>Match the first chunk of objects stored in a Dets table and return a list of variable bindings.</fsummary>
 
605
      <type>
 
606
        <v>Name = name()</v>
 
607
        <v>Pattern = tuple()</v>
 
608
        <v>N = default | int()</v>
 
609
        <v>Match = [term()]</v>
 
610
        <v>Continuation = bindings_cont()</v>
 
611
      </type>
 
612
      <desc>
 
613
        <p>Matches some or all objects of the table <c>Name</c> and
 
614
          returns a non-empty list of the bindings that match
 
615
          <c>Pattern</c> in some unspecified order. See <seealso marker="ets">ets(3)</seealso> for a description of
 
616
          patterns.</p>
 
617
        <p>A tuple of the bindings and a continuation is returned,
 
618
          unless the table is empty, in which case
 
619
          <c>'$end_of_table'</c> is returned. The continuation is to be
 
620
          used when matching further objects by calling
 
621
          <c>match/1</c>.</p>
 
622
        <p>If the keypos'th element of <c>Pattern</c> is bound, all
 
623
          objects of the table are matched. If the keypos'th element is
 
624
          unbound, all objects of the table are matched, <c>N</c>
 
625
          objects at a time, until at least one object matches or the
 
626
          end of the table has been reached. The default, indicated by
 
627
          giving <c>N</c> the value <c>default</c>, is to let the number
 
628
          of objects vary depending on the sizes of the objects. If
 
629
          <c>Name</c> is a version 9 table, all objects with the same
 
630
          key are always matched at the same time which implies that
 
631
          more than N objects may sometimes be matched.
 
632
          </p>
 
633
        <p>The table should always be protected using
 
634
          <c>safe_fixtable/2</c> before calling <c>match/3</c>, or
 
635
          errors may occur when calling <c>match/1</c>.</p>
 
636
      </desc>
 
637
    </func>
 
638
    <func>
 
639
      <name>match_delete(Name, Pattern) -> ok | {error, Reason}</name>
 
640
      <fsummary>Delete all objects that match a given pattern from a Dets table.</fsummary>
 
641
      <type>
 
642
        <v>Name = name()</v>
 
643
        <v>Pattern = tuple()</v>
 
644
      </type>
 
645
      <desc>
 
646
        <p>Deletes all objects that match <c>Pattern</c> from the
 
647
          table <c>Name</c>. 
 
648
          See <seealso marker="ets#match/2">ets:match/2</seealso> for a
 
649
          description of patterns.</p>
 
650
        <p>If the keypos'th element of <c>Pattern</c> is bound,
 
651
          only the objects with the right key are matched.</p>
 
652
      </desc>
 
653
    </func>
 
654
    <func>
 
655
      <name>match_object(Continuation) -> {[Object], Continuation2}  | '$end_of_table' | {error, Reason}</name>
 
656
      <fsummary>Match a chunk of objects stored in a Dets table and return a list of objects.</fsummary>
 
657
      <type>
 
658
        <v>Continuation = Continuation2 = object_cont()</v>
 
659
        <v>Object = object()</v>
 
660
      </type>
 
661
      <desc>
 
662
        <p>Returns a non-empty list of some objects stored in a table
 
663
          that match a given pattern in some unspecified order. The
 
664
          table, the pattern, and the number of objects that are matched
 
665
          are all defined by <c>Continuation</c>, which has been
 
666
          returned by a prior call to <c>match_object/1</c> or
 
667
          <c>match_object/3</c>.</p>
 
668
        <p>When all objects of the table have been matched,
 
669
          <c>'$end_of_table'</c> is returned.</p>
 
670
      </desc>
 
671
    </func>
 
672
    <func>
 
673
      <name>match_object(Name, Pattern) -> [Object] | {error, Reason}</name>
 
674
      <fsummary>Match the objects stored in a Dets table and return a list of objects.</fsummary>
 
675
      <type>
 
676
        <v>Name = name()</v>
 
677
        <v>Pattern = tuple()</v>
 
678
        <v>Object = object()</v>
 
679
      </type>
 
680
      <desc>
 
681
        <p>Returns a list of all objects of the table <c>Name</c> that
 
682
          match <c>Pattern</c> in some unspecified order. See <seealso marker="ets">ets(3)</seealso> for a description of patterns.
 
683
          </p>
 
684
        <p>If the keypos'th element of <c>Pattern</c> is
 
685
          unbound, all objects of the table are matched. If the
 
686
          keypos'th element of <c>Pattern</c> is bound, only the
 
687
          objects with the right key are matched.</p>
 
688
        <p>Using the <c>match_object</c> functions for traversing all
 
689
          objects of a table is more efficient than calling
 
690
          <c>first/1</c> and <c>next/2</c> or <c>slot/2</c>.</p>
 
691
      </desc>
 
692
    </func>
 
693
    <func>
 
694
      <name>match_object(Name, Pattern, N) -> {[Object], Continuation}  | '$end_of_table' | {error, Reason}</name>
 
695
      <fsummary>Match the first chunk of objects stored in a Dets table and return a list of objects.</fsummary>
 
696
      <type>
 
697
        <v>Name = name()</v>
 
698
        <v>Pattern = tuple()</v>
 
699
        <v>N = default | int()</v>
 
700
        <v>Object = object()</v>
 
701
        <v>Continuation = object_cont()</v>
 
702
      </type>
 
703
      <desc>
 
704
        <p>Matches some or all objects stored in the table <c>Name</c>
 
705
          and returns a non-empty list of the objects that match
 
706
          <c>Pattern</c> in some unspecified order. See <seealso marker="ets">ets(3)</seealso> for a description of
 
707
          patterns.</p>
 
708
        <p>A list of objects and a continuation is returned, unless
 
709
          the table is empty, in which case <c>'$end_of_table'</c>
 
710
          is returned. The continuation is to be used when matching
 
711
          further objects by calling <c>match_object/1</c>.</p>
 
712
        <p>If the keypos'th element of <c>Pattern</c> is bound, all
 
713
          objects of the table are matched. If the keypos'th element is
 
714
          unbound, all objects of the table are matched, <c>N</c>
 
715
          objects at a time, until at least one object matches or the
 
716
          end of the table has been reached. The default, indicated by
 
717
          giving <c>N</c> the value <c>default</c>, is to let the number
 
718
          of objects vary depending on the sizes of the objects. If
 
719
          <c>Name</c> is a version 9 table, all matching objects with
 
720
          the same key are always returned in the same reply which
 
721
          implies that more than N objects may sometimes be returned.
 
722
          </p>
 
723
        <p>The table should always be protected using
 
724
          <c>safe_fixtable/2</c> before calling <c>match_object/3</c>,
 
725
          or errors may occur when calling <c>match_object/1</c>.</p>
 
726
      </desc>
 
727
    </func>
 
728
    <func>
 
729
      <name>member(Name, Key) -> Bool | {error, Reason}</name>
 
730
      <fsummary>Test for occurrence of a key in a Dets table.</fsummary>
 
731
      <type>
 
732
        <v>Name = name()</v>
 
733
        <v>Key = term()</v>
 
734
        <v>Bool = bool()</v>
 
735
      </type>
 
736
      <desc>
 
737
        <p>Works like <c>lookup/2</c>, but does not return the
 
738
          objects. The function returns <c>true</c> if one or more
 
739
          elements of the table has the key <c>Key</c>, <c>false</c>
 
740
          otherwise.</p>
 
741
      </desc>
 
742
    </func>
 
743
    <func>
 
744
      <name>next(Name, Key1) -> Key2 | '$end_of_table'</name>
 
745
      <fsummary>Return the next key in a Dets table.</fsummary>
 
746
      <type>
 
747
        <v>Name = name()</v>
 
748
        <v>Key1 = Key2 = term()</v>
 
749
      </type>
 
750
      <desc>
 
751
        <p>Returns the key following <c>Key1</c> in the table
 
752
          <c>Name</c> according to the table's internal order, or
 
753
          <c>'$end_of_table'</c> if there is no next key.</p>
 
754
        <p>Should an error occur, the process is exited with an error
 
755
          tuple <c>{error, Reason}</c>.</p>
 
756
        <p>Use <c>first/1</c> to find the first key in the table.</p>
 
757
      </desc>
 
758
    </func>
 
759
    <func>
 
760
      <name>open_file(Filename) -> {ok, Reference} | {error, Reason}</name>
 
761
      <fsummary>Open an existing Dets table.</fsummary>
 
762
      <type>
 
763
        <v>FileName = file()</v>
 
764
        <v>Reference = ref()</v>
 
765
      </type>
 
766
      <desc>
 
767
        <p>Opens an existing table. If the table has not been properly
 
768
          closed, the error <c>{error, need_repair}</c> is returned. The
 
769
          returned reference is to be used as the name of the table.
 
770
          This function is most useful for debugging purposes.</p>
 
771
      </desc>
 
772
    </func>
 
773
    <func>
 
774
      <name>open_file(Name, Args) -> {ok, Name} | {error, Reason}</name>
 
775
      <fsummary>Open a Dets table.</fsummary>
 
776
      <type>
 
777
        <v>Name = atom()</v>
 
778
      </type>
 
779
      <desc>
 
780
        <p>Opens a table. An empty Dets table is created if no file
 
781
          exists.</p>
 
782
        <p>The atom <c>Name</c> is the name of the table. The table
 
783
          name must be provided in all subsequent operations on the
 
784
          table. The name can be used by other processes as well, and
 
785
          several process can share one table.
 
786
          </p>
 
787
        <p>If two processes open the same table by giving the same
 
788
          name and arguments, then the table will have two users. If one
 
789
          user closes the table, it still remains open until the second
 
790
          user closes the table.</p>
 
791
        <p>The <c>Args</c> argument is a list of <c>{Key, Val}</c>
 
792
          tuples where the following values are allowed:</p>
 
793
        <list type="bulleted">
 
794
          <item>
 
795
            <p><c>{access, access()}</c>. It is possible to open
 
796
              existing tables in read-only mode. A table which is opened
 
797
              in read-only mode is not subjected to the automatic file
 
798
              reparation algorithm if it is later opened after a crash.
 
799
              The default value is <c>read_write</c>.</p>
 
800
          </item>
 
801
          <item>
 
802
            <p><c>{auto_save, auto_save()}</c>, the auto save
 
803
              interval. If the interval is an integer <c>Time</c>, the
 
804
              table is flushed to disk whenever it is not accessed for
 
805
              <c>Time</c> milliseconds. A table that has been flushed
 
806
              will require no reparation when reopened after an
 
807
              uncontrolled emulator halt. If the interval is the atom
 
808
              <c>infinity</c>, auto save is disabled. The default value
 
809
              is 180000 (3 minutes).</p>
 
810
          </item>
 
811
          <item>
 
812
            <p><c>{estimated_no_objects, int()}</c>. Equivalent to the
 
813
              <c>min_no_slots</c> option.</p>
 
814
          </item>
 
815
          <item>
 
816
            <p><c>{file, file()}</c>, the name of the file to be
 
817
              opened. The default value is the name of the table.</p>
 
818
          </item>
 
819
          <item>
 
820
            <p><c>{max_no_slots, no_slots()}</c>, the maximum number
 
821
              of slots that will be used. The default value is 2 M, and
 
822
              the maximal value is 32 M. Note that a higher value may
 
823
              increase the fragmentation of the table, and conversely,
 
824
              that a smaller value may decrease the fragmentation, at
 
825
              the expense of execution time. Only available for version
 
826
              9 tables.</p>
 
827
          </item>
 
828
          <item>
 
829
            <p><c>{min_no_slots, no_slots()}</c>. Application
 
830
              performance can be enhanced with this flag by specifying,
 
831
              when the table is created, the estimated number of
 
832
              different keys that will be stored in the table. The
 
833
              default value as well as the minimum value is 256.</p>
 
834
          </item>
 
835
          <item>
 
836
            <p><c>{keypos, keypos()}</c>, the position of the
 
837
              element of each object to be used as key. The default
 
838
              value is 1. The ability to explicitly state the key
 
839
              position is most convenient when we want to store Erlang
 
840
              records in which the first position of the record is the
 
841
              name of the record type.</p>
 
842
          </item>
 
843
          <item>
 
844
            <p><c>{ram_file, bool()}</c>, whether the table is to
 
845
              be kept in RAM. Keeping the table in RAM may sound like an
 
846
              anomaly, but can enhance the performance of applications
 
847
              which open a table, insert a set of objects, and then
 
848
              close the table. When the table is closed, its contents
 
849
              are written to the disk file. The default value is
 
850
              <c>false</c>.</p>
 
851
          </item>
 
852
          <item>
 
853
            <p><c>{repair, Value}</c>. <c>Value</c> can be either
 
854
              a <c>bool()</c> or the atom <c>force</c>. The flag
 
855
              specifies whether the Dets server should invoke the
 
856
              automatic file reparation algorithm. The default is
 
857
              <c>true</c>. If <c>false</c> is specified, there is no
 
858
              attempt to repair the file and <c>{error, need_repair}</c>
 
859
              is returned if the table needs to be repaired.</p>
 
860
            <p>The value <c>force</c> means that a reparation will
 
861
              take place even if the table has been properly closed.
 
862
              This is how to convert tables created by older versions of
 
863
              STDLIB. An example is tables hashed with the deprecated
 
864
              <c>erlang:hash/2</c> BIF. Tables created with Dets from a
 
865
              STDLIB version of 1.8.2 and later use the
 
866
              <c>erlang:phash/2</c> function or the
 
867
              <c>erlang:phash2/1</c> function, which is preferred.</p>
 
868
            <p>The <c>repair</c> option is ignored if the table is
 
869
              already open.</p>
 
870
          </item>
 
871
          <item>
 
872
            <p><c>{type, type()}</c>, the type of the table. The
 
873
              default value is <c>set</c>.</p>
 
874
          </item>
 
875
          <item>
 
876
            <p><c>{version, version()}</c>, the version of the format
 
877
              used for the table. The default value is <c>9</c>. Tables
 
878
              on the format used before OTP R8 can be created by giving
 
879
              the value <c>8</c>. A version 8 table can be converted to
 
880
              a version 9 table by giving the options <c>{version,9}</c>
 
881
              and <c>{repair,force}</c>.</p>
 
882
          </item>
 
883
        </list>
 
884
      </desc>
 
885
    </func>
 
886
    <func>
 
887
      <name>pid2name(Pid) -> {ok, Name} | undefined</name>
 
888
      <fsummary>Return the name of the Dets table handled by a pid.</fsummary>
 
889
      <type>
 
890
        <v>Name = name()</v>
 
891
        <v>Pid = pid()</v>
 
892
      </type>
 
893
      <desc>
 
894
        <p>Returns the name of the table given the pid of a process
 
895
          that handles requests to a table, or <c>undefined</c> if
 
896
          there is no such table.</p>
 
897
        <p>This function is meant to be used for debugging only.</p>
 
898
      </desc>
 
899
    </func>
 
900
    <func>
 
901
      <name>repair_continuation(Continuation, MatchSpec) -> Continuation2</name>
 
902
      <fsummary>Repair a continuation from select/1 or select/3.</fsummary>
 
903
      <type>
 
904
        <v>Continuation = Continuation2 = select_cont()</v>
 
905
        <v>MatchSpec = match_spec()</v>
 
906
      </type>
 
907
      <desc>
 
908
        <p>This function can be used to restore an opaque continuation
 
909
          returned by <c>select/3</c> or <c>select/1</c> if the
 
910
          continuation has passed through external term format (been
 
911
          sent between nodes or stored on disk).</p>
 
912
        <p>The reason for this function is that continuation terms
 
913
          contain compiled match specifications and therefore will be
 
914
          invalidated if converted to external term format. Given that
 
915
          the original match specification is kept intact, the
 
916
          continuation can be restored, meaning it can once again be
 
917
          used in subsequent <c>select/1</c> calls even though it has
 
918
          been stored on disk or on another node.</p>
 
919
        <p>See also <c>ets(3)</c> for further explanations and
 
920
          examples.
 
921
          </p>
 
922
        <note>
 
923
          <p>This function is very rarely needed in application code. It
 
924
            is used by Mnesia to implement distributed <c>select/3</c>
 
925
            and <c>select/1</c> sequences. A normal application would
 
926
            either use Mnesia or keep the continuation from being
 
927
            converted to external format.</p>
 
928
          <p>The reason for not having an external representation of
 
929
            compiled match specifications is performance. It may be
 
930
            subject to change in future releases, while this interface
 
931
            will remain for backward compatibility.</p>
 
932
        </note>
 
933
      </desc>
 
934
    </func>
 
935
    <func>
 
936
      <name>safe_fixtable(Name, Fix)</name>
 
937
      <fsummary>Fix a Dets table for safe traversal.</fsummary>
 
938
      <type>
 
939
        <v>Name = name()</v>
 
940
        <v>Fix = bool()</v>
 
941
      </type>
 
942
      <desc>
 
943
        <p>If <c>Fix</c> is <c>true</c>, the table <c>Name</c> is
 
944
          fixed (once more) by the calling process, otherwise the table
 
945
          is released. The table is also released when a fixing process
 
946
          terminates.
 
947
          </p>
 
948
        <p>If several processes fix a table, the table will remain
 
949
          fixed until all processes have released it or terminated. A
 
950
          reference counter is kept on a per process basis, and N
 
951
          consecutive fixes require N releases to release the table.</p>
 
952
        <p>It is not guaranteed that calls to <c>first/1</c>,
 
953
          <c>next/2</c>, select and match functions work as expected
 
954
          even if the table has been fixed; the limited support for
 
955
          concurrency implemented in Ets has not yet been implemented
 
956
          in Dets. Fixing a table currently only disables resizing of
 
957
          the hash list of the table.</p>
 
958
        <p>If objects have been added while the table was fixed, the
 
959
          hash list will start to grow when the table is released which
 
960
          will significantly slow down access to the table for a period
 
961
          of time.</p>
 
962
      </desc>
 
963
    </func>
 
964
    <func>
 
965
      <name>select(Continuation) -> {Selection, Continuation2}  | '$end_of_table' | {error, Reason}</name>
 
966
      <fsummary>Apply a match specification to some objects stored in a Dets table.</fsummary>
 
967
      <type>
 
968
        <v>Continuation = Continuation2 = select_cont()</v>
 
969
        <v>Selection = [term()]</v>
 
970
      </type>
 
971
      <desc>
 
972
        <p>Applies a match specification to some objects stored in a
 
973
          table and returns a non-empty list of the results. The
 
974
          table, the match specification, and the number of objects
 
975
          that are matched are all defined by <c>Continuation</c>,
 
976
          which has been returned by a prior call to <c>select/1</c>
 
977
          or <c>select/3</c>.</p>
 
978
        <p>When all objects of the table have been matched,
 
979
          <c>'$end_of_table'</c> is returned.</p>
 
980
      </desc>
 
981
    </func>
 
982
    <func>
 
983
      <name>select(Name, MatchSpec) -> Selection | {error, Reason}</name>
 
984
      <fsummary>Apply a match specification to all objects stored in a Dets table.</fsummary>
 
985
      <type>
 
986
        <v>Name = name()</v>
 
987
        <v>MatchSpec = match_spec()</v>
 
988
        <v>Selection = [term()]</v>
 
989
      </type>
 
990
      <desc>
 
991
        <p>Returns the results of applying the match specification
 
992
          <c>MatchSpec</c> to all or some objects stored in the table
 
993
          <c>Name</c>. The order of the objects is not specified. See
 
994
          the ERTS User's Guide for a description of match
 
995
          specifications.</p>
 
996
        <p>If the keypos'th element of <c>MatchSpec</c> is
 
997
          unbound, the match specification is applied to all objects of
 
998
          the table. If the keypos'th element is bound, the match
 
999
          specification is applied to the objects with the right key(s)
 
1000
          only.</p>
 
1001
        <p>Using the <c>select</c> functions for traversing all
 
1002
          objects of a table is more efficient than calling
 
1003
          <c>first/1</c> and <c>next/2</c> or <c>slot/2</c>.
 
1004
          </p>
 
1005
      </desc>
 
1006
    </func>
 
1007
    <func>
 
1008
      <name>select(Name, MatchSpec, N) -> {Selection, Continuation}  | '$end_of_table' | {error, Reason}</name>
 
1009
      <fsummary>Apply a match specification to the first chunk of objects stored in a Dets table.</fsummary>
 
1010
      <type>
 
1011
        <v>Name = name()</v>
 
1012
        <v>MatchSpec = match_spec()</v>
 
1013
        <v>N = default | int()</v>
 
1014
        <v>Selection = [term()]</v>
 
1015
        <v>Continuation = select_cont()</v>
 
1016
      </type>
 
1017
      <desc>
 
1018
        <p>Returns the results of applying the match specification
 
1019
          <c>MatchSpec</c> to some or all objects stored in the table
 
1020
          <c>Name</c>. The order of the objects is not specified. See
 
1021
          the ERTS User's Guide for a description of match
 
1022
          specifications.</p>
 
1023
        <p>A tuple of the results of applying the match specification
 
1024
          and a continuation is returned, unless the table is empty,
 
1025
          in which case <c>'$end_of_table'</c> is returned. The
 
1026
          continuation is to be used when matching further objects by
 
1027
          calling <c>select/1</c>.</p>
 
1028
        <p>If the keypos'th element of <c>MatchSpec</c> is bound, the
 
1029
          match specification is applied to all objects of the table
 
1030
          with the right key(s). If the keypos'th element of
 
1031
          <c>MatchSpec</c> is unbound, the match specification is
 
1032
          applied to all objects of the table, <c>N</c> objects at a
 
1033
          time, until at least one object matches or the end of the
 
1034
          table has been reached. The default, indicated by giving
 
1035
          <c>N</c> the value <c>default</c>, is to let the number of
 
1036
          objects vary depending on the sizes of the objects. If
 
1037
          <c>Name</c> is a version 9 table, all objects with the same
 
1038
          key are always handled at the same time which implies that the
 
1039
          match specification may be applied to more than N objects.
 
1040
          </p>
 
1041
        <p>The table should always be protected using
 
1042
          <c>safe_fixtable/2</c> before calling <c>select/3</c>, or
 
1043
          errors may occur when calling <c>select/1</c>.</p>
 
1044
      </desc>
 
1045
    </func>
 
1046
    <func>
 
1047
      <name>select_delete(Name, MatchSpec) -> N | {error, Reason}</name>
 
1048
      <fsummary>Delete all objects that match a given pattern from a Dets table.</fsummary>
 
1049
      <type>
 
1050
        <v>Name = name()</v>
 
1051
        <v>MatchSpec = match_spec()</v>
 
1052
        <v>N = int()</v>
 
1053
      </type>
 
1054
      <desc>
 
1055
        <p>Deletes each object from the table <c>Name</c> such that
 
1056
          applying the match specification <c>MatchSpec</c> to the
 
1057
          object returns the value <c>true</c>. See the ERTS
 
1058
          User's Guide for a description of match
 
1059
          specifications. Returns the number of deleted objects.</p>
 
1060
        <p>If the keypos'th element of <c>MatchSpec</c> is
 
1061
          bound, the match specification is applied to the objects
 
1062
          with the right key(s) only.</p>
 
1063
      </desc>
 
1064
    </func>
 
1065
    <func>
 
1066
      <name>slot(Name, I) -> '$end_of_table' | [Object] | {error, Reason}</name>
 
1067
      <fsummary>Return the list of objects associated with a slot of a Dets table.</fsummary>
 
1068
      <type>
 
1069
        <v>Name = name()</v>
 
1070
        <v>I = int()</v>
 
1071
        <v>Object = object()</v>
 
1072
      </type>
 
1073
      <desc>
 
1074
        <p>The objects of a table are distributed among slots,
 
1075
          starting with slot <c>0</c> and ending with slot n. This
 
1076
          function returns the list of objects associated with slot
 
1077
          <c>I</c>. If <c>I</c> is greater than n <c>'$end_of_table'</c>
 
1078
          is returned.</p>
 
1079
      </desc>
 
1080
    </func>
 
1081
    <func>
 
1082
      <name>sync(Name) -> ok | {error, Reason}</name>
 
1083
      <fsummary>Ensure that all updates made to a Dets table are written to disk.</fsummary>
 
1084
      <type>
 
1085
        <v>Name = name()</v>
 
1086
      </type>
 
1087
      <desc>
 
1088
        <p>Ensures that all updates made to the table <c>Name</c> are
 
1089
          written to disk. This also applies to tables which have been
 
1090
          opened with the <c>ram_file</c> flag set to <c>true</c>. In
 
1091
          this case, the contents of the RAM file are flushed to
 
1092
          disk.</p>
 
1093
        <p>Note that the space management data structures kept in RAM,
 
1094
          the buddy system, is also written to the disk. This may take
 
1095
          some time if the table is fragmented.</p>
 
1096
      </desc>
 
1097
    </func>
 
1098
    <func>
 
1099
      <name>table(Name [, Options]) -> QueryHandle</name>
 
1100
      <fsummary>Return a QLC query handle.</fsummary>
 
1101
      <type>
 
1102
        <v>Name = name()</v>
 
1103
        <v>QueryHandle = -&nbsp;a query handle, see qlc(3)&nbsp;-</v>
 
1104
        <v>Options = [Option] | Option</v>
 
1105
        <v>Option = {n_objects, Limit} | {traverse, TraverseMethod}</v>
 
1106
        <v>Limit = default | integer() >= 1</v>
 
1107
        <v>TraverseMethod = first_next | select | {select, MatchSpec}</v>
 
1108
        <v>MatchSpec = match_spec()</v>
 
1109
      </type>
 
1110
      <desc>
 
1111
        <p>          <marker id="qlc_table"></marker>
 
1112
Returns a QLC (Query List
 
1113
          Comprehension) query handle. The module <c>qlc</c>
 
1114
          implements a query language aimed mainly at Mnesia but Ets
 
1115
          tables, Dets tables, and lists are also recognized by <c>qlc</c>
 
1116
          as sources of data. Calling <c>dets:table/1,2</c> is the
 
1117
          means to make the Dets table <c>Name</c> usable to <c>qlc</c>.</p>
 
1118
        <p>When there are only simple restrictions on the key position
 
1119
          <c>qlc</c> uses <c>dets:lookup/2</c> to look up the keys, but when
 
1120
          that is not possible the whole table is traversed. The
 
1121
          option <c>traverse</c> determines how this is done:</p>
 
1122
        <list type="bulleted">
 
1123
          <item>
 
1124
            <p><c>first_next</c>. The table is traversed one key at
 
1125
              a time by calling <c>dets:first/1</c> and
 
1126
              <c>dets:next/2</c>.</p>
 
1127
          </item>
 
1128
          <item>
 
1129
            <p><c>select</c>. The table is traversed by calling
 
1130
              <c>dets:select/3</c> and <c>dets:select/1</c>. The option
 
1131
              <c>n_objects</c> determines the number of objects
 
1132
              returned (the third argument of <c>select/3</c>). The
 
1133
              match specification (the second argument of
 
1134
              <c>select/3</c>) is assembled by <c>qlc</c>: simple filters are
 
1135
              translated into equivalent match specifications while
 
1136
              more complicated filters have to be applied to all
 
1137
              objects returned by <c>select/3</c> given a match
 
1138
              specification that matches all objects.</p>
 
1139
          </item>
 
1140
          <item>
 
1141
            <p><c>{select, MatchSpec}</c>. As for <c>select</c>
 
1142
              the table is traversed by calling <c>dets:select/3</c>
 
1143
              and <c>dets:select/1</c>. The difference is that the
 
1144
              match specification is explicitly given. This is how to
 
1145
              state match specifications that cannot easily be
 
1146
              expressed within the syntax provided by <c>qlc</c>.</p>
 
1147
          </item>
 
1148
        </list>
 
1149
        <p>The following example uses an explicit match specification
 
1150
          to traverse the table:</p>
 
1151
        <pre>
 
1152
1> <input>dets:open_file(t, []),</input>
 
1153
<input>dets:insert(t, [{1,a},{2,b},{3,c},{4,d}]),</input>
 
1154
<input>MS = ets:fun2ms(fun({X,Y}) when (X > 1) or (X &lt; 5) -> {Y} end),</input>
 
1155
<input>QH1 = dets:table(t, [{traverse, {select, MS}}]).</input>        </pre>
 
1156
        <p>An example with implicit match specification:</p>
 
1157
        <pre>
 
1158
2> <input>QH2 = qlc:q([{Y} || {X,Y} &lt;- dets:table(t), (X > 1) or (X &lt; 5)]).</input>        </pre>
 
1159
        <p>The latter example is in fact equivalent to the former which 
 
1160
          can be verified using the function <c>qlc:info/1</c>:</p>
 
1161
        <pre>
 
1162
3> <input>qlc:info(QH1) =:= qlc:info(QH2).</input>
 
1163
true        </pre>
 
1164
        <p><c>qlc:info/1</c> returns information about a query handle,
 
1165
          and in this case identical information is returned for the
 
1166
          two query handles.</p>
 
1167
      </desc>
 
1168
    </func>
 
1169
    <func>
 
1170
      <name>to_ets(Name, EtsTab) -> EtsTab | {error, Reason}</name>
 
1171
      <fsummary>Insert all objects of a Dets table into an Ets table.</fsummary>
 
1172
      <type>
 
1173
        <v>Name = name()</v>
 
1174
        <v>EtsTab = -&nbsp;see ets(3)&nbsp;-</v>
 
1175
      </type>
 
1176
      <desc>
 
1177
        <p>Inserts the objects of the Dets table <c>Name</c> into the
 
1178
          Ets table <c>EtsTab</c>. The order in which the objects are
 
1179
          inserted is not specified. The existing objects of the Ets
 
1180
          table are kept unless overwritten.</p>
 
1181
      </desc>
 
1182
    </func>
 
1183
    <func>
 
1184
      <name>traverse(Name, Fun) -> Return | {error, Reason}</name>
 
1185
      <fsummary>Apply a function to all or some objects stored in a Dets table.</fsummary>
 
1186
      <type>
 
1187
        <v>Fun = fun(Object) -> FunReturn</v>
 
1188
        <v>FunReturn = continue | {continue, Val} | {done, Value}</v>
 
1189
        <v>Val = Value = term()</v>
 
1190
        <v>Name = name()</v>
 
1191
        <v>Object = object()</v>
 
1192
        <v>Return = [term()]</v>
 
1193
      </type>
 
1194
      <desc>
 
1195
        <p>Applies <c>Fun</c> to each object stored in the table
 
1196
          <c>Name</c> in some unspecified order. Different actions are
 
1197
          taken depending on the return value of <c>Fun</c>. The
 
1198
          following <c>Fun</c> return values are allowed:</p>
 
1199
        <taglist>
 
1200
          <tag><c>continue</c></tag>
 
1201
          <item>
 
1202
            <p>Continue to perform the traversal. For example, the
 
1203
              following function can be used to print out the contents
 
1204
              of a table:</p>
 
1205
            <pre>
 
1206
fun(X) -> io:format("~p~n", [X]), continue end.            </pre>
 
1207
          </item>
 
1208
          <tag><c>{continue, Val}</c></tag>
 
1209
          <item>
 
1210
            <p>Continue the traversal and accumulate <c>Val</c>. The
 
1211
              following function is supplied in order to collect all
 
1212
              objects of a table in a list: </p>
 
1213
            <pre>
 
1214
fun(X) -> {continue, X} end.            </pre>
 
1215
          </item>
 
1216
          <tag><c>{done, Value}</c></tag>
 
1217
          <item>
 
1218
            <p>Terminate the traversal and return <c>[Value | Acc]</c>.</p>
 
1219
          </item>
 
1220
        </taglist>
 
1221
        <p>Any other value returned by <c>Fun</c> terminates the
 
1222
          traversal and is immediately returned.
 
1223
          </p>
 
1224
      </desc>
 
1225
    </func>
 
1226
    <func>
 
1227
      <name>update_counter(Name, Key, Increment) -> Result</name>
 
1228
      <fsummary>Update a counter object stored in a Dets table.</fsummary>
 
1229
      <type>
 
1230
        <v>Name = name()</v>
 
1231
        <v>Key = term()</v>
 
1232
        <v>Increment = {Pos, Incr} | Incr</v>
 
1233
        <v>Pos = Incr = Result = integer()</v>
 
1234
      </type>
 
1235
      <desc>
 
1236
        <p>Updates the object with key <c>Key</c> stored in the table
 
1237
          <c>Name</c> of type <c>set</c> by adding <c>Incr</c> to the
 
1238
          element at the <c>Pos</c>:th position. The new counter value
 
1239
          is returned. If no position is specified, the element directly
 
1240
          following the key is updated.</p>
 
1241
        <p>This functions provides a way of updating a counter,
 
1242
          without having to look up an object, update the object by
 
1243
          incrementing an element and insert the resulting object into
 
1244
          the table again.</p>
 
1245
      </desc>
 
1246
    </func>
 
1247
  </funcs>
 
1248
 
 
1249
  <section>
 
1250
    <title>See Also</title>
 
1251
    <p><seealso marker="ets">ets(3)</seealso>, 
 
1252
      mnesia(3), 
 
1253
      <seealso marker="qlc">qlc(3)</seealso></p>
 
1254
  </section>
 
1255
</erlref>
 
1256