Built-in term storage.
This module is an interface to the Erlang built-in term storage
BIFs. These provide the ability to store very large quantities of
data in an Erlang runtime system, and to have constant access
time to the data. (In the case of ordered_set
, see below,
access time is proportional to the logarithm of the number of
stored objects.)
Data is organized as a set of dynamic tables, which can store tuples. Each table is created by a process. When the process terminates, the table is automatically destroyed. Every table has access rights set at creation.
Tables are divided into four different types, set
,
ordered_set
, bag
, and duplicate_bag
.
A set
or ordered_set
table can only have one object
associated with each key. A bag
or duplicate_bag
table can
have many objects associated with each key.
Note!
The number of tables stored at one Erlang node used to
be limited. This is no longer the case (except by memory usage).
The previous default limit was about 1400 tables and
could be increased by setting the environment variable
ERL_MAX_ETS_TABLES
or the command line option
+e
before starting the
Erlang runtime system. This hard limit has been removed, but it is currently
useful to set the ERL_MAX_ETS_TABLES
anyway. It should be
set to an approximate of the maximum amount of tables used. This since
an internal table for named tables is sized using this value. If
large amounts of named tables are used and ERL_MAX_ETS_TABLES
hasn't been increased, the performance of named table lookup will
degrade.
Notice that there is no automatic garbage collection for tables.
Even if there are no references to a table from any process, it
is not automatically destroyed unless the owner process
terminates. To destroy a table explicitly, use function
delete/1
.
The default owner is the process that created the
table. To transfer table ownership at process termination, use
option heir
or call
give_away/3
.
Some implementation details:
In the current implementation, every object insert and look-up operation results in a copy of the object.
'$end_of_table'
is not to be used as a key, as this atom is used to mark the end of the table when using functionsfirst/1
andnext/2
.
Notice the subtle difference between
matching and comparing equal, which is
demonstrated by table types set
and ordered_set
:
-
Two Erlang terms
match
if they are of the same type and have the same value, so that1
matches1
, but not1.0
(as1.0
is afloat()
and not aninteger()
). -
Two Erlang terms compare equal if they either are of the same type and value, or if both are numeric types and extend to the same value, so that
1
compares equal to both1
and1.0
. -
The
ordered_set
works on the Erlang term order and no defined order exists between aninteger()
and afloat()
that extends to the same value. Hence the key1
and the key1.0
are regarded as equal in anordered_set
table.
Failure
The functions in this module exits with reason
badarg
if any argument has the wrong format, if the
table identifier is invalid, or if the operation is denied because of
table access rights (protected
or private).
Concurrency
This module provides some limited support for concurrent access. All updates to single objects are guaranteed to be both atomic and isolated. This means that an updating operation to a single object either succeeds or fails completely without any effect (atomicity) and that no intermediate results of the update can be seen by other processes (isolation). Some functions that update many objects state that they even guarantee atomicity and isolation for the entire operation. In database terms the isolation level can be seen as "serializable", as if all isolated operations are carried out serially, one after the other in a strict order.
Table traversal
There are different ways to traverse through the objects of a table.
Single-step traversal one key at at time, using
first/1
,next/2
,last/1
andprev/2
.Search with simple match patterns, using
match/1/2/3
,match_delete/2
andmatch_object/1/2/3
.Search with more powerful match specifications, using
select/1/2/3
,select_count/2
,select_delete/2
,select_replace/2
andselect_reverse/1/2/3
.Table conversions, using
tab2file/2/3
andtab2list/1
.
None of these ways of table traversal will guarantee a consistent table snapshot if the table is also updated during the traversal. Moreover, traversals not done in a safe way, on tables where keys are inserted or deleted during the traversal, may yield the following undesired effects:
Any key may be missed.
Any key may be found more than once.
The traversal may fail with
badarg
exception if keys are deleted.
A table traversal is safe if either
the table is of type
ordered_set
.the entire table traversal is done within one ETS function call.
function
safe_fixtable/2
is used to keep the table fixated during the entire traversal.
Note!
Even though the access of a single object is always guaranteed to be atomic and isolated, each traversal through a table to find the next key is not done with such guarantees. This is often not a problem, but may cause rare subtle "unexpected" effects if a concurrent process inserts objects during a traversal. For example, consider one process doing
ets:new(t, [ordered_set, named_table]), ets:insert(t, {1}), ets:insert(t, {2}), ets:insert(t, {3}),
A concurrent call to ets:first(t)
, done by another
process, may then in rare cases return 2
even though
2
has never existed in the table ordered as the first key. In
the same way, a concurrent call to ets:next(t, 1)
may return
3
even though 3
never existed in the table
ordered directly after 1
.
Effects like this are improbable but possible. The probability will
further be reduced (if not vanish) if table option
write_concurrency
is not enabled. This can also only be a potential concern for
ordered_set
where the traversal order is defined.
Traversals using match
and select
functions may not need to
scan the entire table depending on how the key is specified. A match
pattern with a fully bound key (without any match variables) will
optimize the operation to a single key lookup without any table traversal
at all. For ordered_set
a partially bound key will limit the
traversal to only scan a subset of the table based on term order. A
partially bound key is either a list or a tuple with a prefix that is fully
bound. Example:
1>T = ets:new(t,[ordered_set]), ets:insert(T, {"555-1234", "John Smith"}).
true 2>%% Efficient search of all with area code 555
2>ets:match(T,{[$5,$5,$5,$- |'$1'],'$2'}).
[["1234","John Smith"]]
Match Specifications
Some of the functions use a match specification,
match_spec
. For a brief explanation, see
select/2
. For a detailed
description, see section
Match Specifications in Erlang in ERTS User's Guide.
Types
access() = public | protected | private
continuation()
Opaque continuation used by
select/1,3
,
select_reverse/1,3
,
match/1,3
, and
match_object/1,3
.
match_spec() = [{match_pattern(), [term()], [term()]}]
A match specification, see above.
comp_match_spec()
A compiled match specification.
match_pattern() = atom() | tuple()
tab() = atom() | tid()
tid()
A table identifier, as returned by
new/2
.
type() = set | ordered_set | bag | duplicate_bag
Functions
all() -> [Tab]
Tab = tab()
Returns a list of all tables at the node. Named tables are specified by their names, unnamed tables are specified by their table identifiers.
There is no guarantee of consistency in the returned list. Tables
created or deleted by other processes "during" the ets:all()
call either are or are not included in the list. Only tables
created/deleted before ets:all()
is called are
guaranteed to be included/excluded.
delete_all_objects(Tab) -> true
Tab = tab()
Delete all objects in the ETS table
.
The operation is guaranteed to be
atomic and isolated.
delete_object(Tab, Object) -> true
Tab = tab()
Object = tuple()
Delete the exact object
from the
ETS table,
leaving objects with the same key but other differences
(useful for type bag
). In a duplicate_bag
table, all
instances of the object are deleted.
file2tab(Filename) -> {ok, Tab} | {error, Reason}
Filename = file:name()
Tab = tab()
Reason = term()
Reads a file produced by
tab2file/2
or
tab2file/3
and
creates the corresponding table
.
Equivalent to file2tab(
.
file2tab(Filename, Options) -> {ok, Tab} | {error, Reason}
Filename = file:name()
Tab = tab()
Options = [Option]
Option = {verify, boolean()}
Reason = term()
Reads a file produced by
tab2file/2
or
tab2file/3
and creates the
corresponding table
.
The only supported option is {verify,boolean()}
.
If verification is turned on (by specifying {verify,true}
),
the function uses whatever information is present in the file to
assert that the information is not damaged. How this is done depends
on which extended_info
was written using
tab2file/3
.
If no extended_info
is present in the file and
{verify,true}
is specified, the number of objects
written is compared to the size of the original table when the
dump was started. This can make verification fail if the table was
public
and objects were added or removed while the
table was dumped to file. To avoid this problem,
either do not verify files dumped while updated simultaneously
or use option {extended_info, [object_count]}
to
tab2file/3
, which
extends the information in the file with the number of objects
written.
If verification is turned on and the file was written with
option {extended_info, [md5sum]}
, reading the file
is slower and consumes radically more CPU time than otherwise.
{verify,false}
is the default.
first(Tab) -> Key | '$end_of_table'
Tab = tab()
Key = term()
Returns the first key
in table
. For an ordered_set
table, the first
key in Erlang term order is returned. For other
table types, the first key according to the internal
order of the table is returned. If the table is empty,
'$end_of_table'
is returned.
To find subsequent keys in the table, use
next/2
.
foldl(Function, Acc0, Tab) -> Acc1
Function = fun((Element :: term(), AccIn) -> AccOut)
Tab = tab()
Acc0 = Acc1 = AccIn = AccOut = term()
is returned if the table is empty.
This function is similar to
lists:foldl/3
.
The table elements are traversed in an unspecified order, except for
ordered_set
tables, where they are traversed first to last.
If
inserts objects into the table,
or another
process inserts objects into the table, those objects can
(depending on key ordering) be included in the traversal.
foldr(Function, Acc0, Tab) -> Acc1
Function = fun((Element :: term(), AccIn) -> AccOut)
Tab = tab()
Acc0 = Acc1 = AccIn = AccOut = term()
is returned if the table is empty.
This function is similar to
lists:foldr/3
.
The table elements are traversed in an unspecified order, except for
ordered_set
tables, where they are traversed last to first.
If
inserts objects into the table,
or another
process inserts objects into the table, those objects can
(depending on key ordering) be included in the traversal.
from_dets(Tab, DetsTab) -> true
Tab = tab()
DetsTab = dets:tab_name()
Fills an already created ETS table with the objects in the
already opened Dets table
.
Existing objects in the ETS table are kept unless
overwritten.
If any of the tables does not exist or the Dets table is
not open, a badarg
exception is raised.
fun2ms(LiteralFun) -> MatchSpec
LiteralFun = function()
MatchSpec = match_spec()
Pseudo function that by a parse_transform
translates
typed as parameter in the function
call to a
match specification.
With "literal" is meant that the fun must textually be written
as the parameter of the function, it cannot be held in a
variable that in turn is passed to the function.
The parse transform is provided in the ms_transform
module and the source must include
file ms_transform.hrl
in STDLIB for this
pseudo function to work. Failing to include the hrl file in
the source results in a runtime error, not a compile
time error. The include file is easiest included by adding line
-include_lib("stdlib/include/ms_transform.hrl").
to
the source file.
The fun is very restricted, it can take only a single
parameter (the object to match): a sole variable or a
tuple. It must use the is_
guard tests.
Language constructs that have no representation in a match
specification (if
, case
, receive
,
and so on) are not allowed.
The return value is the resulting match specification.
Example:
1> ets:fun2ms(fun({M,N}) when N > 3 -> M end).
[{{'$1','$2'},[{'>','$2',3}],['$1']}]
Variables from the environment can be imported, so that the following works:
2>X=3.
3 3>ets:fun2ms(fun({M,N}) when N > X -> M end).
[{{'$1','$2'},[{'>','$2',{const,3}}],['$1']}]
The imported variables are replaced by match specification
const
expressions, which is consistent with the
static scoping for Erlang funs. However, local or global function
calls cannot be in the guard or body of the fun. Calls to built-in
match specification functions is of course allowed:
4>ets:fun2ms(fun({M,N}) when N > X, my_fun(M) -> M end).
Error: fun containing local Erlang function calls ('my_fun' called in guard) cannot be translated into match_spec {error,transform_error} 5>ets:fun2ms(fun({M,N}) when N > X, is_atom(M) -> M end).
[{{'$1','$2'},[{'>','$2',{const,3}},{is_atom,'$1'}],['$1']}]
As shown by the example, the function can be called from the shell also. The fun must be literally in the call when used from the shell as well.
Warning!
If the parse_transform
is not applied to a module that
calls this pseudo function, the call fails in runtime
(with a badarg
). The ets
module
exports a function with this name, but it is never to
be called except when using the function in the
shell. If the parse_transform
is properly applied by
including header file ms_transform.hrl
, compiled
code never calls the function, but the function call is
replaced by a literal match specification.
For more information, see
ms_transform(3)
.
give_away(Tab, Pid, GiftData) -> true
Tab = tab()
Pid = pid()
GiftData = term()
Make process
the new owner of table
. If successful, message
{'ETS-TRANSFER',
is sent to the new owner.
The process
must be alive, local, and not
already the owner of the table.
The calling process must be the table owner.
Notice that this function does not affect option
heir
of the table. A table
owner can, for example, set heir
to itself, give the table
away, and then get it back if the receiver terminates.
i() -> ok
Displays information about all ETS tables on a terminal.
info(Tab) -> InfoList | undefined
Tab = tab()
InfoList = [InfoTuple]
InfoTuple =
{compressed, boolean()} |
{heir, pid() | none} |
{id, tid()} |
{keypos, integer() >= 1} |
{memory, integer() >= 0} |
{name, atom()} |
{named_table, boolean()} |
{node, node()} |
{owner, pid()} |
{protection, access()} |
{size, integer() >= 0} |
{type, type()} |
{write_concurrency, boolean()} |
{read_concurrency, boolean()}
Returns information about table
as a list of
tuples. If
has the correct type
for a table identifier, but does not refer to an existing ETS
table, undefined
is returned. If
is
not of the correct type, a badarg
exception is raised.
{compressed, boolean()}
Indicates if the table is compressed.
{heir, pid() | none}
The pid of the heir of the table, or none
if no heir
is set.
{id,
tid()
}
The table identifier.
{keypos, integer() >= 1}
The key position.
{memory, integer() >= 0
The number of words allocated to the table.
{name, atom()}
The table name.
{named_table, boolean()}
Indicates if the table is named.
{node, node()}
The node where the table is stored. This field is no longer meaningful, as tables cannot be accessed from other nodes.
{owner, pid()}
The pid of the owner of the table.
{protection,
access()
}
The table access rights.
{size, integer() >= 0
The number of objects inserted in the table.
{type,
type()
}
The table type.
{read_concurrency, boolean()}
Indicates whether the table uses read_concurrency
or
not.
{write_concurrency, boolean()}
Indicates whether the table uses write_concurrency
.
info(Tab, Item) -> Value | undefined
Tab = tab()
Item =
compressed | fixed | heir | id | keypos | memory | name |
named_table | node | owner | protection | safe_fixed |
safe_fixed_monotonic_time | size | stats | type |
write_concurrency | read_concurrencyValue = term()
Returns the information associated with Item
for table
, or returns undefined
if Tab
does not refer an existing ETS table. If
is
not of the correct type, or if
is not
one of the allowed values, a badarg
exception is raised.
In addition to the {
pairs defined for info/1
,
the following items are allowed:
-
Item=fixed, Value=boolean()
Indicates if the table is fixed by any process.
-
Item=safe_fixed|safe_fixed_monotonic_time, Value={FixationTime,Info}|false
If the table is fixed using
safe_fixtable/2
, the call returns a tuple whereFixationTime
is the last time when the table changed from unfixed to fixed.The format and value of
FixationTime
depends onItem
:safe_fixed
FixationTime
corresponds to the result returned byerlang:timestamp/0
at the time of fixation. Notice that when the system uses single or multi time warp modes this can produce strange results, as the use ofsafe_fixed
is not time warp safe. Time warp safe code must usesafe_fixed_monotonic_time
instead.safe_fixed_monotonic_time
FixationTime
corresponds to the result returned byerlang:monotonic_time/0
at the time of fixation. The use ofsafe_fixed_monotonic_time
is time warp safe.Info
is a possibly empty lists of tuples{Pid,RefCount}
, one tuple for every process the table is fixed by now.RefCount
is the value of the reference counter and it keeps track of how many times the table has been fixed by the process.Table fixations are not limited to
safe_fixtable/2
. Temporary fixations may also be done by for example traversing functions likeselect
andmatch
. Such table fixations are automatically released before the corresponding functions returns, but they may be seen by a concurrent call toets:info(T,safe_fixed|safe_fixed_monotonic_time)
.If the table is not fixed at all, the call returns
false
. -
Item=stats, Value=tuple()
Returns internal statistics about tables on an internal format used by OTP test suites. Not for production use.
init_table(Tab, InitFun) -> true
Tab = tab()
InitFun = fun((Arg) -> Res)
Arg = read | close
Res = end_of_input | {Objects :: [term()], InitFun} | term()
Replaces the existing objects of table
with
objects created by calling the input function
,
see below. This function is provided for compatibility with
the dets
module, it is not more efficient than filling
a table by using
insert/2
.
When called with argument read
, the function
is assumed to return
end_of_input
when
there is no more input, or {
, where
is a list of objects and Fun
is a
new input function. Any other value Value
is returned as an
error {error, {init_fun, Value}}
. Each input function is
called exactly once, and if an error occur, the last
function is called with argument close
, the reply
of which is ignored.
If the table type is set
and more than one object
exists with a given key, one of the objects is
chosen. This is not necessarily the last object with the given
key in the sequence of objects returned by the input
functions. This holds also for duplicated
objects stored in tables of type bag
.
insert(Tab, ObjectOrObjects) -> true
Tab = tab()
ObjectOrObjects = tuple() | [tuple()]
Inserts the object or all of the objects in list
into table
.
-
If the table type is
set
and the key of the inserted objects matches the key of any object in the table, the old object is replaced. -
If the table type is
ordered_set
and the key of the inserted object compares equal to the key of any object in the table, the old object is replaced. -
If the list contains more than one object with matching keys and the table type is
set
, one is inserted, which one is not defined. The same holds for table typeordered_set
if the keys compare equal.
The entire operation is guaranteed to be atomic and isolated, even when a list of objects is inserted.
insert_new(Tab, ObjectOrObjects) -> boolean()
Tab = tab()
ObjectOrObjects = tuple() | [tuple()]
Same as insert/2
except that instead of overwriting objects with the same key
(for set
or ordered_set
) or adding more objects with
keys already existing in the table (for bag
and
duplicate_bag
), false
is returned.
If
is a
list, the function checks every key before
inserting anything. Nothing is inserted unless
all keys present in the list are absent from the
table. Like insert/2
, the entire operation is guaranteed to be
atomic and isolated.
is_compiled_ms(Term) -> boolean()
Term = term()
Checks if a term is a valid
compiled match specification.
The compiled match specification is an opaque datatype that
cannot be sent between Erlang nodes or be stored on
disk. Any attempt to create an external representation of a
compiled match specification results in an empty binary
(<<>>
).
Examples:
The following expression yields true
::
ets:is_compiled_ms(ets:match_spec_compile([{'_',[],[true]}])).
The following expressions yield false
, as variable
Broken
contains a compiled match specification that has
passed through external representation:
MS = ets:match_spec_compile([{'_',[],[true]}]), Broken = binary_to_term(term_to_binary(MS)), ets:is_compiled_ms(Broken).
Note!
The reason for not having an external representation of compiled match specifications is performance. It can be subject to change in future releases, while this interface remains for backward compatibility.
last(Tab) -> Key | '$end_of_table'
Tab = tab()
Key = term()
lookup(Tab, Key) -> [Object]
Tab = tab()
Key = term()
Object = tuple()
Returns a list of all objects with key
in
table
.
-
For tables of type
set
,bag
, orduplicate_bag
, an object is returned only if the specified key matches the key of the object in the table. -
For tables of type
ordered_set
, an object is returned if the specified key compares equal to the key of an object in the table.
The difference is the same as between =:=
and ==
.
As an example, one can insert an object with
integer()
1
as a key in an ordered_set
and get the object returned as a result of doing a lookup/2
with float()
1.0
as the key to search for.
For tables of type set
or ordered_set
,
the function returns either the empty list or a list with one
element, as there cannot be more than one object with the same
key. For tables of type bag
or duplicate_bag
, the
function returns a list of arbitrary length.
Notice that the time order of object insertions is preserved; the first object inserted with the specified key is the first in the resulting list, and so on.
Insert and lookup times in tables of type set
,
bag
, and duplicate_bag
are constant, regardless
of the table size. For the ordered_set
datatype, time is proportional to the (binary) logarithm of
the number of objects.
lookup_element(Tab, Key, Pos) -> Elem
Tab = tab()
Key = term()
Pos = integer() >= 1
Elem = term() | [term()]
For a table
of type set
or
ordered_set
, the function returns the
:th
element of the object with key
.
For tables of type bag
or duplicate_bag
,
the functions returns a list with the
:th
element of every object with key
.
If no object with key
exists, the
function exits with reason badarg
.
The difference between set
, bag
, and
duplicate_bag
on one hand, and ordered_set
on
the other, regarding the fact that ordered_set
view keys as equal when they compare equal
whereas the other table types regard them equal only when
they match, holds for lookup_element/3
.
match(Continuation) -> {[Match], Continuation} | '$end_of_table'
Match = [term()]
Continuation = continuation()
Continues a match started with
match/3
. The next
chunk of the size specified in the initial match/3
call is returned together with a new
,
which can be used in subsequent calls to this function.
When there are no more objects in the table, '$end_of_table'
is returned.
match(Tab, Pattern) -> [Match]
Tab = tab()
Pattern = match_pattern()
Match = [term()]
Matches the objects in table
against
pattern
.
A pattern is a term that can contain:
- Bound parts (Erlang terms)
'_'
that matches any Erlang term- Pattern variables
'$N'
, whereN
=0,1,...
The function returns a list with one element for each matching object, where each element is an ordered list of pattern variable bindings, for example:
6>ets:match(T, '$1').
% Matches every object in table [[{rufsen,dog,7}],[{brunte,horse,5}],[{ludde,dog,5}]] 7>ets:match(T, {'_',dog,'$1'}).
[[7],[5]] 8>ets:match(T, {'_',cow,'$1'}).
[]
If the key is specified in the pattern, the match is very efficient. If the key is not specified, that is, if it is a variable or an underscore, the entire table must be searched. The search time can be substantial if the table is very large.
For tables of type ordered_set
, the result is in
the same order as in a first
/next
traversal.
match(Tab, Pattern, Limit) ->
{[Match], Continuation} | '$end_of_table'
Tab = tab()
Pattern = match_pattern()
Limit = integer() >= 1
Match = [term()]
Continuation = continuation()
Works like match/2
,
but returns only a limited (
) number of
matching objects. Term
can then
be used in subsequent calls to
match/1
to get the next chunk of matching
objects. This is a space-efficient way to work on objects in a
table, which is faster than traversing the table object
by object using
first/1
and
next/2
.
If the table is empty, '$end_of_table'
is returned.
Use safe_fixtable/2
to guarantee safe traversal
for subsequent calls to match/1
.
match_delete(Tab, Pattern) -> true
Tab = tab()
Pattern = match_pattern()
Deletes all objects that match pattern
from table
. For a description of patterns,
see match/2
.
match_object(Continuation) ->
{[Object], Continuation} | '$end_of_table'
Object = tuple()
Continuation = continuation()
Continues a match started with
match_object/3
.
The next chunk of the size specified in the initial
match_object/3
call is returned together with a new
, which can be used in subsequent
calls to this function.
When there are no more objects in the table, '$end_of_table'
is returned.
match_object(Tab, Pattern) -> [Object]
Tab = tab()
Pattern = match_pattern()
Object = tuple()
Matches the objects in table
against
pattern
. For a description of patterns,
see match/2
.
The function returns a list of all objects that
match the pattern.
If the key is specified in the pattern, the match is very efficient. If the key is not specified, that is, if it is a variable or an underscore, the entire table must be searched. The search time can be substantial if the table is very large.
For tables of type ordered_set
, the result is in
the same order as in a first
/next
traversal.
match_object(Tab, Pattern, Limit) ->
{[Object], Continuation} | '$end_of_table'
Tab = tab()
Pattern = match_pattern()
Limit = integer() >= 1
Object = tuple()
Continuation = continuation()
Works like
match_object/2
, but only returns a
limited (
) number of matching objects. Term
can then be used in subsequent
calls to
match_object/1
to get the next chunk of matching
objects. This is a space-efficient way to work on objects in a
table, which is faster than traversing the table object
by object using
first/1
and
next/2
.
If the table is empty, '$end_of_table'
is returned.
Use safe_fixtable/2
to guarantee safe traversal
for subsequent calls to
match_object/1
.
match_spec_compile(MatchSpec) -> CompiledMatchSpec
MatchSpec = match_spec()
CompiledMatchSpec = comp_match_spec()
Transforms a
match specification into an
internal representation that can be used in subsequent calls to
match_spec_run/2
.
The internal representation is
opaque and cannot be converted to external term format and
then back again without losing its properties (that is, it cannot
be sent to a process on another node and still remain a
valid compiled match specification, nor can it be stored on disk).
To check the validity of a compiled match specification, use
is_compiled_ms/1
.
If term
cannot be compiled (does not
represent a valid match specification), a badarg
exception is
raised.
Note!
This function has limited use in normal code. It is used by the
dets
module
to perform the dets:select()
operations.
match_spec_run(List, CompiledMatchSpec) -> list()
List = [term()]
CompiledMatchSpec = comp_match_spec()
Executes the matching specified in a compiled
match specification on a list
of terms. Term
is to be
the result of a call to
match_spec_compile/1
and is hence the internal
representation of the match specification one wants to use.
The matching is executed on each element in
and the function returns a list containing all results. If an element
in
does not match, nothing is returned
for that element. The length of the result list is therefore
equal or less than the length of parameter
.
Example:
The following two calls give the same result (but certainly not the same execution time):
Table = ets:new... MatchSpec = ... % The following call... ets:match_spec_run(ets:tab2list(Table), ets:match_spec_compile(MatchSpec)), % ...gives the same result as the more common (and more efficient) ets:select(Table, MatchSpec),
Note!
This function has limited use in normal code. It is used by the
dets
module
to perform the dets:select()
operations and by
Mnesia during transactions.
member(Tab, Key) -> boolean()
Tab = tab()
Key = term()
Works like lookup/2
,
but does not return the objects. Returns true
if one or more
elements in the table has key
, otherwise
false
.
new(Name, Options) -> tid() | atom()
Name = atom()
Options = [Option]
Option =
Type | Access | named_table |
{keypos, Pos} |
{heir, Pid :: pid(), HeirData} |
{heir, none} |
TweaksType = type()
Access = access()
Tweaks =
{write_concurrency, boolean()} |
{read_concurrency, boolean()} |
compressedPos = integer() >= 1
HeirData = term()
Creates a new table and returns a table identifier that can be used in subsequent operations. The table identifier can be sent to other processes so that a table can be shared between different processes within a node.
Parameter
is a list of options that
specifies table type, access rights, key position, and whether the
table is named. Default values are used for omitted options.
This means that not specifying any options ([]
) is the same
as specifying [set, protected, {keypos,1}, {heir,none},
{write_concurrency,false}, {read_concurrency,false}]
.
set
The table is a set
table: one key, one object,
no order among objects. This is the default table type.
ordered_set
The table is a ordered_set
table: one key, one
object, ordered in Erlang term order, which is the order
implied by the < and > operators. Tables of this type
have a somewhat different behavior in some situations
than tables of other types. Most notably, the
ordered_set
tables regard keys as equal when they
compare equal, not only when they match. This
means that to an ordered_set
table, integer()
1
and float()
1.0
are regarded as equal.
This also means that the
key used to lookup an element not necessarily
matches the key in the returned elements, if
float()
's and integer()
's are mixed in
keys of a table.
bag
The table is a bag
table, which can have many
objects, but only one instance of each object, per key.
duplicate_bag
The table is a duplicate_bag
table, which can have
many objects, including multiple copies of the same
object, per key.
public
Any process can read or write to the table.
protected
The owner process can read and write to the table. Other processes can only read the table. This is the default setting for the access rights.
private
Only the owner process can read or write to the table.
named_table
If this option is present, the table is registered under its
which can then be used instead of the
table identifier in subsequent operations.
The function will also return the
instead of the table identifier. To get the table identifier of a
named table, use
whereis/1
.
{keypos,Pos }
Specifies which element in the stored tuples to use
as key. By default, it is the first element, that is,
. However, this is not always
appropriate. In
particular, we do not want the first element to be the
key if we want to store Erlang records in a table.
Notice that any tuple stored in the table must have at
least
number of elements.
{heir,Pid ,HeirData } |
{heir,none}
Set a process as heir. The heir inherits the table if
the owner terminates. Message
{'ETS-TRANSFER',tid(),FromPid,
is
sent to the heir when that occurs. The heir must be a local
process. Default heir is none
, which destroys the table
when the owner terminates.
{write_concurrency,boolean()}
Performance tuning. Defaults to false
, in which case an
operation that
mutates (writes to) the table obtains exclusive access,
blocking any concurrent access of the same table until finished.
If set to true
, the table is optimized to concurrent
write access. Different objects of the same table can be mutated
(and read) by concurrent processes. This is achieved to some
degree at the expense of memory consumption and the performance
of sequential access and concurrent reading.
Option write_concurrency
can be combined with option
read_concurrency
. You typically want to combine
these when large concurrent read bursts and large concurrent
write bursts are common; for more information, see option
read_concurrency
.
Notice that this option does not change any guarantees about
atomicity and isolation.
Functions that makes such promises over many objects (like
insert/2
)
gain less (or nothing) from this option.
The memory consumption inflicted by both write_concurrency
and read_concurrency
is a constant overhead per table for
set
, bag
and duplicate_bag
. For
ordered_set
the memory overhead depends on the number
of inserted objects and the amount of actual detected
concurrency in runtime. The memory overhead can be especially
large when both options are combined.
Note!
Prior to stdlib-3.7 (OTP-22.0) write_concurrency
had no
effect on ordered_set
.
{read_concurrency,boolean()}
Performance tuning. Defaults to false
. When set to
true
, the table is optimized for concurrent read
operations. When this option is enabled on a runtime system with
SMP support, read operations become much cheaper; especially on
systems with multiple physical processors. However, switching
between read and write operations becomes more expensive.
You typically want to enable this option when concurrent read operations are much more frequent than write operations, or when concurrent reads and writes comes in large read and write bursts (that is, many reads not interrupted by writes, and many writes not interrupted by reads).
You typically do not want to enable this option when the common access pattern is a few read operations interleaved with a few write operations repeatedly. In this case, you would get a performance degradation by enabling this option.
Option read_concurrency
can be combined with option
write_concurrency
.
You typically want to combine these when large concurrent
read bursts and large concurrent write bursts are common.
compressed
If this option is present, the table data is stored in a more
compact format to consume less memory. However, it will make
table operations slower. Especially operations that need to
inspect entire objects, such as match
and select
,
get much slower. The key element is not compressed.
next(Tab, Key1) -> Key2 | '$end_of_table'
Tab = tab()
Key1 = Key2 = term()
Returns the next key
, following key
in table
. For table
type ordered_set
, the next key in Erlang term order is
returned. For other table types, the next key
according to the internal order of the table is returned. If no
next key exists, '$end_of_table'
is returned.
To find the first key in the table, use
first/1
.
Unless a table of type set
, bag
, or
duplicate_bag
is fixated using
safe_fixtable/2
,
a call to next/2
will fail if
no longer
exists in the table. For table type ordered_set
, the function
always returns the next key after
in term
order, regardless whether
ever existed in the
table.
prev(Tab, Key1) -> Key2 | '$end_of_table'
Tab = tab()
Key1 = Key2 = term()
rename(Tab, Name) -> Name
Tab = tab()
Name = atom()
Renames the named table
to the new name
. Afterwards, the old name cannot be used to
access the table. Renaming an unnamed table has no effect.
repair_continuation(Continuation, MatchSpec) -> Continuation
Continuation = continuation()
MatchSpec = match_spec()
Restores an opaque continuation returned by
select/3
or
select/1
if the
continuation has passed through external term format (been
sent between nodes or stored on disk).
The reason for this function is that continuation terms
contain compiled match specifications and therefore are
invalidated if converted to external term format. Given that the
original match specification is kept intact, the continuation can
be restored, meaning it can once again be used in subsequent
select/1
calls even though it has been stored on
disk or on another node.
Examples:
The following sequence of calls fails:
T=ets:new(x,[]), ... {_,C} = ets:select(T,ets:fun2ms(fun({N,_}=A) when (N rem 10) =:= 0 -> A end),10), Broken = binary_to_term(term_to_binary(C)), ets:select(Broken).
The following sequence works, as the call to
repair_continuation/2
reestablishes the (deliberately)
invalidated continuation Broken
.
T=ets:new(x,[]), ... MS = ets:fun2ms(fun({N,_}=A) when (N rem 10) =:= 0 -> A end), {_,C} = ets:select(T,MS,10), Broken = binary_to_term(term_to_binary(C)), ets:select(ets:repair_continuation(Broken,MS)).
Note!
This function is rarely needed in application code. It is used
by Mnesia to provide distributed select/3
and select/1
sequences. A normal application would
either use Mnesia or keep the continuation from being
converted to external format.
The reason for not having an external representation of a compiled match specification is performance. It can be subject to change in future releases, while this interface remains for backward compatibility.
safe_fixtable(Tab, Fix) -> true
Tab = tab()
Fix = boolean()
Fixes a table of type set
, bag
, or
duplicate_bag
for
safe traversal using
first/1
&
next/2
,
match/3
&
match/1
,
match_object/3
&
match_object/1
, or
select/3
&
select/1
.
A process fixes a table by calling
safe_fixtable(
. The table remains
fixed until the process releases it by calling
safe_fixtable(
, or until the process
terminates.
If many processes fix a table, the table remains fixed until all processes have released it (or terminated). A reference counter is kept on a per process basis, and N consecutive fixes requires N releases to release the table.
When a table is fixed, a sequence of
first/1
and
next/2
calls are
guaranteed to succeed even if keys are removed during the
traversal. The keys for objects inserted or deleted during a
traversal may or may not be returned by next/2
depending on
the ordering of keys within the table and if the key exists at the time
next/2
is called.
Example:
clean_all_with_value(Tab,X) -> safe_fixtable(Tab,true), clean_all_with_value(Tab,X,ets:first(Tab)), safe_fixtable(Tab,false). clean_all_with_value(Tab,X,'$end_of_table') -> true; clean_all_with_value(Tab,X,Key) -> case ets:lookup(Tab,Key) of [{Key,X}] -> ets:delete(Tab,Key); _ -> true end, clean_all_with_value(Tab,X,ets:next(Tab,Key)).
Notice that deleted objects are not freed from a fixed table until it has been released. If a process fixes a table but never releases it, the memory used by the deleted objects is never freed. The performance of operations on the table also degrades significantly.
To retrieve information about which processes have fixed which
tables, use
info(Tab, safe_fixed_monotonic_time)
. A system with
many processes fixing tables can need a monitor that sends alarms
when tables have been fixed for too long.
Notice that safe_fixtable/2
is not necessary for table type
ordered_set
and for traversals done by a single ETS function call,
like select/2
.
select(Continuation) -> {[Match], Continuation} | '$end_of_table'
Match = term()
Continuation = continuation()
Continues a match started with
select/3
. The next
chunk of the size specified in the initial select/3
call is returned together with a new
,
which can be used in subsequent calls to this function.
When there are no more objects in the table, '$end_of_table'
is returned.
select(Tab, MatchSpec) -> [Match]
Tab = tab()
MatchSpec = match_spec()
Match = term()
Matches the objects in table
using a
match specification.
This is a more general call than
match/2
and
match_object/2
calls. In its simplest form, the match specification is as
follows:
MatchSpec = [MatchFunction] MatchFunction = {MatchHead, [Guard], [Result]} MatchHead = "Pattern as in ets:match" Guard = {"Guardtest name", ...} Result = "Term construct"
This means that the match specification is always a list of one or
more tuples (of arity 3). The first element of the tuple is to be
a pattern as described in
match/2
.
The second element of the tuple is to
be a list of 0 or more guard tests (described below). The
third element of the tuple is to be a list containing a
description of the value to return. In almost all
normal cases, the list contains exactly one term that fully
describes the value to return for each object.
The return value is constructed using the "match variables"
bound in MatchHead
or using the special match variables
'$_'
(the whole matching object) and '$$'
(all
match variables in a list), so that the following
match/2
expression:
ets:match(Tab,{'$1','$2','$3'})
is exactly equivalent to:
ets:select(Tab,[{{'$1','$2','$3'},[],['$$']}])
And that the following match_object/2
call:
ets:match_object(Tab,{'$1','$2','$1'})
is exactly equivalent to
ets:select(Tab,[{{'$1','$2','$1'},[],['$_']}])
Composite terms can be constructed in the Result
part
either by simply writing a list, so that the following code:
ets:select(Tab,[{{'$1','$2','$3'},[],['$$']}])
gives the same output as:
ets:select(Tab,[{{'$1','$2','$3'},[],[['$1','$2','$3']]}])
That is, all the bound variables in the match head as a list. If
tuples are to be constructed, one has to write a tuple of
arity 1 where the single element in the tuple is the tuple
one wants to construct (as an ordinary tuple can be mistaken
for a Guard
).
Therefore the following call:
ets:select(Tab,[{{'$1','$2','$1'},[],['$_']}])
gives the same output as:
ets:select(Tab,[{{'$1','$2','$1'},[],[{{'$1','$2','$3'}}]}])
This syntax is equivalent to the syntax used in the trace
patterns (see the
dbg(3)
) module in Runtime_Tools.
The Guard
s are constructed as tuples, where the first
element is the test name and the remaining elements
are the test parameters. To check for a specific type
(say a list) of the element bound to the match variable
'$1'
, one would write the test as
{is_list, '$1'}
. If the test fails, the object in the
table does not match and the next MatchFunction
(if
any) is tried. Most guard tests present in Erlang can be
used, but only the new versions prefixed is_
are
allowed (is_float
, is_atom
, and so on).
The Guard
section can also contain logic and
arithmetic operations, which are written with the same syntax
as the guard tests (prefix notation), so that the following
guard test written in Erlang:
is_integer(X), is_integer(Y), X + Y < 4711
is expressed as follows (X
replaced with '$1'
and
Y
with '$2'
):
[{is_integer, '$1'}, {is_integer, '$2'}, {'<', {'+', '$1', '$2'}, 4711}]
For tables of type ordered_set
, objects are visited
in the same order as in a first
/next
traversal. This means that the match specification is
executed against objects with keys in the first
/next
order and the corresponding result list is in the order of that
execution.
select(Tab, MatchSpec, Limit) ->
{[Match], Continuation} | '$end_of_table'
Tab = tab()
MatchSpec = match_spec()
Limit = integer() >= 1
Match = term()
Continuation = continuation()
Works like select/2
,
but only returns a limited
(
) number of matching objects. Term
can then be used in subsequent
calls to select/1
to get the next chunk of matching
objects. This is a space-efficient way to work on objects in a
table, which is still faster than traversing the table object by
object using first/1
and next/2
.
If the table is empty, '$end_of_table'
is returned.
Use safe_fixtable/2
to guarantee safe traversal
for subsequent calls to select/1
.
select_count(Tab, MatchSpec) -> NumMatched
Tab = tab()
MatchSpec = match_spec()
NumMatched = integer() >= 0
Matches the objects in table
using a
match specification. If the
match specification returns true
for an object, that object
considered a match and is counted. For any other result from
the match specification the object is not considered a match and is
therefore not counted.
This function can be described as a
match_delete/2
function that does not delete any elements, but only counts them.
The function returns the number of objects matched.
select_delete(Tab, MatchSpec) -> NumDeleted
Tab = tab()
MatchSpec = match_spec()
NumDeleted = integer() >= 0
Matches the objects in table
using a
match specification. If the
match specification returns true
for an object, that object is
removed from the table. For any other result from the match
specification the object is retained. This is a more general
call than the
match_delete/2
call.
The function returns the number of objects deleted from the table.
Note!
The match specification has to return the atom true
if
the object is to be deleted. No other return value gets the
object deleted. So one cannot use the same match specification for
looking up elements as for deleting them.
select_replace(Tab, MatchSpec) -> NumReplaced
Tab = tab()
MatchSpec = match_spec()
NumReplaced = integer() >= 0
Matches the objects in the table
using a
match specification. For each
matched object, the existing object is replaced with
the match specification result.
The match-and-replace operation for each individual object is guaranteed to be
atomic and isolated. The
select_replace
table traversal as a whole, like all other select functions,
does not give such guarantees.
The match specifiction must be guaranteed to retain the key
of any matched object. If not, select_replace
will fail with badarg
without updating any objects.
For the moment, due to performance and semantic constraints,
tables of type bag
are not yet supported.
The function returns the total number of replaced objects.
Example
For all 2-tuples with a list in second position, add atom 'marker'
first in the list:
1>T = ets:new(x,[]), ets:insert(T, {key, [1, 2, 3]}).
true 2>MS = ets:fun2ms(fun({K, L}) when is_list(L) -> {K, [marker | L]} end).
[{{'$1','$2'},[{is_list,'$2'}],[{{'$1',[marker|'$2']}}]}] 3>ets:select_replace(T, MS).
1 4>ets:tab2list(T).
[{key,[marker,1,2,3]}]
A generic single object compare-and-swap operation:
[Old] = ets:lookup(T, Key), New = update_object(Old), Success = (1 =:= ets:select_replace(T, [{Old, [], [{const, New}]}])),
select_reverse(Continuation) ->
{[Match], Continuation} | '$end_of_table'
Continuation = continuation()
Match = term()
Continues a match started with
select_reverse/3
. For tables of type
ordered_set
, the traversal of the table continues
to objects with keys earlier in the Erlang term order. The
returned list also contains objects with keys in reverse order.
For all other table types, the behavior is exactly that of
select/1
.
Example:
1> T = ets:new(x,[ordered_set]).
2> [ ets:insert(T,{N}) || N <- lists:seq(1,10) ].
...
3> {R0,C0} = ets:select_reverse(T,[{'_',[],['$_']}],4).
...
4> R0.
[{10},{9},{8},{7}]
5> {R1,C1} = ets:select_reverse(C0).
...
6> R1.
[{6},{5},{4},{3}]
7> {R2,C2} = ets:select_reverse(C1).
...
8> R2.
[{2},{1}]
9> '$end_of_table' = ets:select_reverse(C2).
...
select_reverse(Tab, MatchSpec) -> [Match]
Tab = tab()
MatchSpec = match_spec()
Match = term()
Works like select/2
,
but returns the list in reverse order for table type ordered_set
.
For all other table types, the return value is identical to that of
select/2
.
select_reverse(Tab, MatchSpec, Limit) ->
{[Match], Continuation} | '$end_of_table'
Tab = tab()
MatchSpec = match_spec()
Limit = integer() >= 1
Match = term()
Continuation = continuation()
Works like select/3
,
but for table type ordered_set
traversing is done starting at the last object in
Erlang term order and moves to the first. For all other table
types, the return value is identical to that of select/3
.
Notice that this is not equivalent to
reversing the result list of a select/3
call, as the result list
is not only reversed, but also contains the last
matching objects in the table, not the first.
setopts(Tab, Opts) -> true
Tab = tab()
Opts = Opt | [Opt]
Opt = {heir, pid(), HeirData} | {heir, none}
HeirData = term()
Sets table options. The only allowed option to be set after the
table has been created is
heir
.
The calling process must be the table owner.
slot(Tab, I) -> [Object] | '$end_of_table'
Tab = tab()
I = integer() >= 0
Object = tuple()
This function is mostly for debugging purposes, Normally
first
/next
or last
/prev
are to be used
instead.
Returns all objects in slot
of table
. A table can be traversed by repeatedly
calling the function,
starting with the first slot
and
ending when '$end_of_table'
is returned.
If argument
is out of range,
the function fails with reason badarg
.
Unless a table of type set
, bag
, or
duplicate_bag
is protected using
safe_fixtable/2
,
a traversal can fail if
concurrent updates are made to the table. For table type
ordered_set
, the function returns a list containing
object
in Erlang term order.
tab2file(Tab, Filename) -> ok | {error, Reason}
Tab = tab()
Filename = file:name()
Reason = term()
Dumps table
to file
.
Equivalent to
tab2file(
tab2file(Tab, Filename, Options) -> ok | {error, Reason}
Tab = tab()
Filename = file:name()
Options = [Option]
Option = {extended_info, [ExtInfo]} | {sync, boolean()}
ExtInfo = md5sum | object_count
Reason = term()
Dumps table
to file
.
When dumping the table, some information about the table is dumped to a header at the beginning of the dump. This information contains data about the table type, name, protection, size, version, and if it is a named table. It also contains notes about what extended information is added to the file, which can be a count of the objects in the file or a MD5 sum of the header and records in the file.
The size field in the header might not correspond to the number of records in the file if the table is public and records are added or removed from the table during dumping. Public tables updated during dump, and that one wants to verify when reading, needs at least one field of extended information for the read verification process to be reliable later.
Option extended_info
specifies what extra
information is written to the table dump:
object_count
The number of objects written to the file is noted in the file footer, so file truncation can be verified even if the file was updated during dump.
md5sum
The header and objects in the file are checksummed using the built-in MD5 functions. The MD5 sum of all objects is written in the file footer, so that verification while reading detects the slightest bitflip in the file data. Using this costs a fair amount of CPU time.
Whenever option extended_info
is used, it
results in a file not readable by versions of ETS before
that in STDLIB 1.15.1
If option sync
is set to true
, it ensures that
the content of the file is written to the disk before
tab2file
returns. Defaults to {sync, false}
.
tabfile_info(Filename) -> {ok, TableInfo} | {error, Reason}
Filename = file:name()
TableInfo = [InfoItem]
InfoItem =
{name, atom()} |
{type, Type} |
{protection, Protection} |
{named_table, boolean()} |
{keypos, integer() >= 0} |
{size, integer() >= 0} |
{extended_info, [ExtInfo]} |
{version,
{Major :: integer() >= 0, Minor :: integer() >= 0}}ExtInfo = md5sum | object_count
Type = bag | duplicate_bag | ordered_set | set
Protection = private | protected | public
Reason = term()
Returns information about the table dumped to file by
tab2file/2
or
tab2file/3
.
The following items are returned:
name
The name of the dumped table. If the table was a
named table, a table with the same name cannot exist when the
table is loaded from file with
file2tab/2
.
If the table is
not saved as a named table, this field has no significance
when loading the table from file.
type
The ETS type of the dumped table (that is, set
,
bag
, duplicate_bag
, or ordered_set
). This
type is used when loading the table again.
protection
The protection of the dumped table (that is, private
,
protected
, or public
). A table loaded from the
file gets the same protection.
named_table
true
if the table was a named table when dumped
to file, otherwise false
. Notice that when a named table
is loaded from a file, there cannot exist a table in the
system with the same name.
keypos
The keypos
of the table dumped to file, which
is used when loading the table again.
size
The number of objects in the table when the table dump
to file started. For a public
table, this number
does not need to correspond to the number of objects saved to
the file, as objects can have been added or deleted by another
process during table dump.
extended_info
The extended information written in the file footer to
allow stronger verification during table loading from file, as
specified to
tab2file/3
. Notice that this
function only tells which information is present, not
the values in the file footer. The value is a list containing one
or more of the atoms object_count
and md5sum
.
version
A tuple {
containing the major and
minor version of the file format for ETS table dumps. This
version field was added beginning with STDLIB 1.5.1.
Files dumped with older versions return {0,0}
in this
field.
An error is returned if the file is inaccessible,
badly damaged, or not produced with
tab2file/2
or
tab2file/3
.
table(Tab) -> QueryHandle
Tab = tab()
QueryHandle = qlc:query_handle()
table(Tab, Options) -> QueryHandle
Tab = tab()
QueryHandle = qlc:query_handle()
Options = [Option] | Option
Option = {n_objects, NObjects} | {traverse, TraverseMethod}
NObjects = default | integer() >= 1
TraverseMethod =
first_next | last_prev | select |
{select, MatchSpec :: match_spec()}
Returns a Query List
Comprehension (QLC) query handle. The
qlc
module provides
a query language aimed mainly at Mnesia, but ETS
tables, Dets tables,
and lists are also recognized by QLC as sources of
data. Calling table/1,2
is the means to make the
ETS table Tab
usable to QLC.
When there are only simple restrictions on the key position,
QLC uses lookup/2
to look up the keys. When
that is not possible, the whole table is traversed.
Option traverse
determines how this is done:
first_next
The table is traversed one key at a time by calling
first/1
and
next/2
.
last_prev
The table is traversed one key at a time by calling
last/1
and
prev/2
.
select
The table is traversed by calling
select/3
and
select/1
.
Option n_objects
determines the number of objects
returned (the third argument of select/3
); the
default is to return 100
objects at a time. The
match specification (the
second argument of select/3
) is assembled by QLC: simple
filters are translated into equivalent match specifications
while more complicated filters must be applied to all
objects returned by select/3
given a match specification
that matches all objects.
{select, MatchSpec }
As for select
, the table is traversed by calling
select/3
and
select/1
.
The difference is that the match specification is explicitly
specified. This is how to state match specifications that cannot
easily be expressed within the syntax provided by QLC.
Examples:
An explicit match specification is here used to traverse the table:
9>true = ets:insert(Tab = ets:new(t, []), [{1,a},{2,b},{3,c},{4,d}]),
MS = ets:fun2ms(fun({X,Y}) when (X > 1) or (X < 5) -> {Y} end),
QH1 = ets:table(Tab, [{traverse, {select, MS}}]).
An example with an implicit match specification:
10> QH2 = qlc:q([{Y} || {X,Y} <- ets:table(Tab), (X > 1) or (X < 5)]).
The latter example is equivalent to the former, which
can be verified using function qlc:info/1
:
11> qlc:info(QH1) =:= qlc:info(QH2).
true
qlc:info/1
returns information about a query handle,
and in this case identical information is returned for the
two query handles.
take(Tab, Key) -> [Object]
Tab = tab()
Key = term()
Object = tuple()
test_ms(Tuple, MatchSpec) -> {ok, Result} | {error, Errors}
Tuple = tuple()
MatchSpec = match_spec()
Result = term()
Errors = [{warning | error, string()}]
This function is a utility to test a
match specification used in
calls to select/2
.
The function both tests
for "syntactic"
correctness and runs the match specification against object
.
If the match specification is syntactically correct, the function
either returns {ok,
, where
is what would have been the result in a
real select/2
call, or false
if the match specification
does not match object
.
If the match specification contains errors, tuple
{error,
is returned,
where
is a list of natural language
descriptions of what was wrong with the match specification.
This is a useful debugging and test tool, especially when
writing complicated select/2
calls.
See also: erlang:match_spec_test/3.
to_dets(Tab, DetsTab) -> DetsTab
Tab = tab()
DetsTab = dets:tab_name()
Fills an already created/opened Dets table with the objects
in the already opened ETS table named
.
The Dets table is emptied before the objects are inserted.
This function provides an efficient way to update one or more counters, without the trouble of having to look up an object, update the object by incrementing an element, and insert the resulting object into the table again. The operation is guaranteed to be atomic and isolated.
This function destructively update the object with key
in table
by adding
to the element at position
. The new counter value is
returned. If no position is specified, the element directly
following key (<keypos>+1
) is updated.
If a
is specified, the counter is
reset to value
if the following
conditions occur:
is not negative (Incr >= 0
) and the result would be greater than (>
)
.Threshold
is negative (Incr < 0
) and the result would be less than (<
)
.Threshold
A list of
can be supplied to do many
update operations within the object.
The operations are carried out in the
order specified in the list. If the same counter position occurs
more than once in the list, the corresponding counter is thus
updated many times, each time based on the previous result.
The return value is a list of the new counter values from each
update operation in the same order as in the operation list. If an
empty list is specified, nothing is updated and an empty list is
returned. If the function fails, no updates are done.
The specified
is used to identify the object
by either matching the key of an object in a set
table, or compare equal to the key of an object in an
ordered_set
table (for details on the difference, see
lookup/2
and
new/2
).
If a default object
is specified,
it is used
as the object to be updated if the key is missing from the table. The
value in place of the key is ignored and replaced by the proper key
value. The return value is as if the default object had not been used,
that is, a single updated element or a list of them.
The function fails with reason badarg
in the following
situations:
- The table type is not
set
orordered_set
. - No object with the correct key exists and no default object was supplied.
- The object has the wrong arity.
- The default object arity is smaller than
<keypos>
. - Any field from the default object that is updated is not an integer.
- The element to update is not an integer.
- The element to update is also the key.
- Any of
,Pos
,Incr
, orThreshold
is not an integer.SetValue
This function provides an efficient way to update one or more elements within an object, without the trouble of having to look up, update, and write back the entire object.
This function destructively updates the object with key
in table
.
The element at position
is given
the value
.
A list of {
can be
supplied to update many
elements within the same object. If the same position occurs more
than once in the list, the last value in the list is written. If
the list is empty or the function fails, no updates are done.
The function is also atomic in the sense that other processes
can never see any intermediate results.
Returns true
if an object with key
is found, otherwise false
.
The specified
is used to identify the object
by either matching the key of an object in a set
table, or compare equal to the key of an object in an
ordered_set
table (for details on the difference, see
lookup/2
and
new/2
).
The function fails with reason badarg
in the following
situations:
- The table type is not
set
orordered_set
.
< 1.Pos
> object arity.Pos - The element to update is also the key.
whereis(TableName) -> tid() | undefined
TableName = atom()
This function returns the
tid()
of the named table
identified by
, or undefined
if
no such table exists. The tid()
can be used in place of the
table name in all operations, which is slightly faster since the name
does not have to be resolved on each call.
If the table is deleted, the tid()
will be invalid even if
another named table is created with the same name.