View Source ets (stdlib v6.1.2)
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.
Insert and lookup times in tables of type set
are constant, regardless of the
table size. For table types bag
and duplicate_bag
time is proportional to
the number of objects with the same key. Even seemingly unrelated keys may
inflict linear search to be skipped past while looking for the key of interest
(due to hash collision).
Warning
For tables of type
bag
andduplicate_bag
, avoid inserting an extensive amount of objects with the same key. It will hurt insert and lookup performance as well as real time characteristics of the runtime environment (hash bucket linear search do not yield).
The ordered_set
table type uses a binary search tree. Insert and lookup times
are proportional to the logarithm of the number of objects in the table.
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 theERL_MAX_ETS_TABLES
anyway. It should be set to an approximate of the maximum amount of tables used since an internal table for named tables is sized using this value. If large amounts of named tables are used andERL_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/0
and not aninteger/0
). - 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/0
and afloat/0
that extends to the same value. Hence the key1
and the key1.0
are regarded as equal in anordered_set
table.
Failures
Functions in this module fail by raising an error exception with error reason:
badarg
- If any argument has the wrong format.badarg
- If the table identifier is invalid.badarg
- If the operation is denied because of table access rights (protected or private).system_limit
- Modification of a value causes it to not be representable internally in the VM. For example, incrementation of a counter past the largest integer representable.system_limit
- If a match specification passed as argument has excessive nesting which causes scheduler stack exhaustion for the scheduler that the calling process is executing on. Scheduler stack size can be configured when starting the runtime system.
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
. - Single-step traversal one key at at time, but using
first_lookup/1
,next_lookup/2
,last_lookup/1
andprev_lookup/2
. This is more efficient when you also need to lookup the objects for the keys. - 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
.
No table traversal will guarantee a consistent snapshot of the entire table if the table is also updated by concurrent processes during the traversal. The result of each concurrently updated object may be seen (or not) depending on if it has happened when the traversal visits that part of the table. The only way to guarantee a full consistent table snapshot (if you really need that) is to disallow concurrent updates during the entire 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 return2
even though2
has never existed in the table ordered as the first key. In the same way, a concurrent call toets:next(t, 1)
may return3
even though3
never existed in the table ordered directly after1
.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 forordered_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.
A match specifications with excessive nesting will cause a
system_limit
error exception to be raised.
Summary
Types
A compiled match specification.
Opaque continuation used by select/1,3
,
select_reverse/1,3
, match/1,3
, and
match_object/1,3
.
A match specification, see Match Specifications.
Functions
Returns a list of all tables at the node. Named tables are specified by their names, unnamed tables are specified by their table identifiers.
Deletes the entire table Table
.
Deletes all objects with key Key
from table Table
. This function succeeds
even if no objects with key Key
exist.
Delete all objects in the ETS table Table
. The operation is guaranteed to be
atomic and isolated.
Delete the exact object 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.
Reads a file produced by tab2file/2
or tab2file/3
and creates the
corresponding table Table
.
Reads a file produced by tab2file/2
or tab2file/3
and creates the
corresponding table Table
.
Returns the first key Key
in table 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.
Acc0
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.
Acc0
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.
Fills an already created ETS table with the objects in the already opened Dets
table DetsTab
. Existing objects in the ETS table are kept unless overwritten.
Pseudo function that by a parse_transform
translates LiteralFun
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.
Make process Pid
the new owner of table Table
. If successful, message
{'ETS-TRANSFER',Table,FromPid,GiftData}
is sent to the new owner.
Displays information about all ETS tables on a terminal.
Browses table Table
on a terminal.
Returns information about table Table
as a list of tuples. If Table
has the
correct type for a table identifier, but does not refer to an existing ETS
table, undefined
is returned. If Table
is not of the correct type, a
badarg
exception is raised.
Returns the information associated with Item
for table Table
, or returns
undefined
if Table
does not refer an existing ETS table. If Table
is not
of the correct type, or if Item
is not one of the allowed values, a badarg
exception is raised.
Replaces the existing objects of table Table
with objects created by calling
the input function InitFun
, 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
.
Inserts the object or all of the objects in list ObjectOrObjects
into table
Table
.
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.
Checks if a term represent a valid compiled
match specification. A compiled match specification is
only valid on the Erlang node where it was compiled by calling
match_spec_compile/1
.
Returns the last key Key
according to Erlang term order in table Table
of
type ordered_set
. For other table types, the function is synonymous to
first/1
. If the table is empty, '$end_of_table'
is returned.
Returns a list of all objects with key Key
in table Table
.
For a table Table
of type set
or ordered_set
, the function returns the
Pos
:th element of the object with key Key
.
For a table Table
of type set
or ordered_set
, the function returns the
Pos
:th element of the object with key Key
.
Matches the objects in table Table
against pattern Pattern
.
Works like match/2
, but returns only a limited (Limit
) number of matching
objects. Term Continuation
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
.
Deletes all objects that match pattern Pattern
from table Table
. For a
description of patterns, see match/2
.
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 Continuation
, which can be used in subsequent calls to
this function.
Matches the objects in table Table
against pattern Pattern
. For a
description of patterns, see match/2
. The function returns a list of all
objects that match the pattern.
Works like match_object/2
, but only returns a limited (Limit
) number of
matching objects. Term Continuation
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
.
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. To check the validity of a compiled match
specification, use is_compiled_ms/1
.
Executes the matching specified in a compiled
match specification on a list of terms. Term
CompiledMatchSpec
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.
Works like lookup/2
, but does not return the objects. Returns true
if one or
more elements in the table has key Key
, otherwise false
.
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.
Returns the next key Key2
, following key Key1
in table 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.
Returns the previous key Key2
, preceding key Key1
according to Erlang term
order in table Table
of type ordered_set
. For other table types, the
function is synonymous to next/2
. If no previous key exists, '$end_of_table'
is returned.
Renames the named table Table
to the new name Name
. Afterwards, the old name
cannot be used to access the table. Renaming an unnamed table has no effect.
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
.
Matches the objects in table 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
Works like select/2
, but only returns a limited (Limit
) number of matching
objects. Term Continuation
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
.
Matches the objects in table 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.
Matches the objects in table 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.
Matches the objects in the table Table
using a
match specification. For each matched object, the existing
object is replaced with the match specification result.
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
.
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.
This function is mostly for debugging purposes, normally first
/next
or
last
/prev
are to be used instead.
Dumps table Table
to file Filename
.
Dumps table Table
to file Filename
.
Returns a list of all objects in table Table
.
Returns information about the table dumped to file by tab2file/2
or
tab2file/3
.
Equivalent to table/2
.
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 Table
usable to QLC.
Returns and removes a list of all objects with key Key
in table Table
.
This function is a utility to test a match specification
used in calls to select/2
. The function both tests MatchSpec
for "syntactic"
correctness and runs the match specification against object Tuple
.
Fills an already created/opened Dets table with the objects in the already
opened ETS table named Table
. The Dets table is emptied before the objects are
inserted.
Equivalent to update_counter/4
.
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.
Equivalent to update_element/4
.
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.
Types
-type comp_match_spec() :: compiled_match_spec().
-opaque compiled_match_spec()
A compiled match specification.
-type continuation() :: '$end_of_table' | {table(), integer(), integer(), compiled_match_spec(), list(), integer()} | {table(), _, _, integer(), compiled_match_spec(), list(), integer(), integer()}.
Opaque continuation used by select/1,3
,
select_reverse/1,3
, match/1,3
, and
match_object/1,3
.
-type match_spec() :: [{match_pattern(), [_], [_]}].
A match specification, see Match Specifications.
-type tab() :: table().
-type table_access() :: public | protected | private.
-type table_type() :: set | ordered_set | bag | duplicate_bag.
-opaque tid()
A table identifier, as returned by new/2
.
Functions
-spec all() -> [Table] when Table :: table().
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.
-spec delete(Table) -> true when Table :: table().
Deletes the entire table Table
.
Deletes all objects with key Key
from table Table
. This function succeeds
even if no objects with key Key
exist.
-spec delete_all_objects(Table) -> true when Table :: table().
Delete all objects in the ETS table Table
. The operation is guaranteed to be
atomic and isolated.
Delete the exact object 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.
-spec file2tab(Filename) -> {ok, Table} | {error, Reason} when Filename :: file:name(), Table :: table(), Reason :: term().
Reads a file produced by tab2file/2
or tab2file/3
and creates the
corresponding table Table
.
Equivalent to file2tab(Filename, [])
.
-spec file2tab(Filename, Options) -> {ok, Table} | {error, Reason} when Filename :: file:name(), Table :: table(), Options :: [Option], Option :: {verify, boolean()}, Reason :: term().
Reads a file produced by tab2file/2
or tab2file/3
and creates the
corresponding table 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.
Returns the first key Key
in table 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
.
-spec first_lookup(Table) -> {Key, [Object]} | '$end_of_table' when Table :: table(), Key :: term(), Object :: tuple().
Similar to first/1
except that it returns the object(s) along with the key
stored in the table. This is equivalent to doing first/1
followed by a
lookup/2
. If the table is empty, '$end_of_table'
is returned.
To find subsequent objects in the table, use next_lookup/2
.
-spec foldl(Function, Acc0, Table) -> Acc1 when Function :: fun((Element :: term(), AccIn) -> AccOut), Table :: table(), Acc0 :: term(), Acc1 :: term(), AccIn :: term(), AccOut :: term().
Acc0
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 Function
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.
-spec foldr(Function, Acc0, Table) -> Acc1 when Function :: fun((Element :: term(), AccIn) -> AccOut), Table :: table(), Acc0 :: term(), Acc1 :: term(), AccIn :: term(), AccOut :: term().
Acc0
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 Function
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.
-spec from_dets(Table, DetsTab) -> true when Table :: table(), DetsTab :: dets:tab_name().
Fills an already created ETS table with the objects in the already opened Dets
table DetsTab
. 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.
-spec fun2ms(LiteralFun) -> MatchSpec when LiteralFun :: function(), MatchSpec :: match_spec().
Pseudo function that by a parse_transform
translates LiteralFun
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 abadarg
). Theets
module exports a function with this name, but it is never to be called except when using the function in the shell. If theparse_transform
is properly applied by including header filems_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
.
-spec give_away(Table, Pid, GiftData) -> true when Table :: table(), Pid :: pid(), GiftData :: term().
Make process Pid
the new owner of table Table
. If successful, message
{'ETS-TRANSFER',Table,FromPid,GiftData}
is sent to the new owner.
The process Pid
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.
-spec i() -> ok.
Displays information about all ETS tables on a terminal.
-spec i(Table) -> ok when Table :: table().
Browses table Table
on a terminal.
-spec info(Table) -> InfoList | undefined when Table :: table(), InfoList :: [InfoTuple], InfoTuple :: {compressed, boolean()} | {decentralized_counters, boolean()} | {heir, pid() | none} | {id, tid()} | {keypos, pos_integer()} | {memory, non_neg_integer()} | {name, atom()} | {named_table, boolean()} | {node, node()} | {owner, pid()} | {protection, table_access()} | {size, non_neg_integer()} | {type, table_type()} | {write_concurrency, boolean()} | {read_concurrency, boolean()}.
Returns information about table Table
as a list of tuples. If Table
has the
correct type for a table identifier, but does not refer to an existing ETS
table, undefined
is returned. If Table
is not of the correct type, a
badarg
exception is raised.
{compressed, boolean()}
- Indicates if the table is compressed.{decentralized_counters, boolean()}
- Indicates whether the table usesdecentralized_counters
.{heir, pid() | none}
- The pid of the heir of the table, ornone
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 usesread_concurrency
or not.{write_concurrency, WriteConcurrencyAlternative}
- Indicates whichwrite_concurrency
option the table uses.
Note
The execution time of this function is affected by the
decentralized_counters
table option. The execution time is much longer when thedecentralized_counters
option is set totrue
than when thedecentralized_counters
option is set tofalse
.
-spec info(Table, Item) -> Value | undefined when Table :: table(), Item :: binary | compressed | decentralized_counters | fixed | heir | id | keypos | memory | name | named_table | node | owner | protection | safe_fixed | safe_fixed_monotonic_time | size | stats | type | write_concurrency | read_concurrency, Value :: term().
Returns the information associated with Item
for table Table
, or returns
undefined
if Table
does not refer an existing ETS table. If Table
is not
of the correct type, or if Item
is not one of the allowed values, a badarg
exception is raised.
In addition to the {Item,Value}
pairs defined for info/1
, the following
items are allowed:
Item=binary, Value=BinInfo
BinInfo
is a list containing miscellaneous information about binaries kept by the table. ThisItem
can be changed or removed without prior notice. In the current implementationBinInfo
is a list of tuples{BinaryId,BinarySize,BinaryRefcCount}
.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.
Note
The execution time of this function is affected by the
decentralized_counters
table option when the second argument of the function issize
ormemory
. The execution time is much longer when thedecentralized_counters
option is set totrue
than when thedecentralized_counters
option is set tofalse
.
-spec init_table(Table, InitFun) -> true when Table :: table(), InitFun :: fun((Arg) -> Res), Arg :: read | close, Res :: end_of_input | {Objects :: [term()], InitFun} | term().
Replaces the existing objects of table Table
with objects created by calling
the input function InitFun
, 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 InitFun
is assumed to return
end_of_input
when there is no more input, or {Objects, Fun}
, where Objects
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
.
-spec insert(Table, ObjectOrObjects) -> true when Table :: table(), ObjectOrObjects :: tuple() | [tuple()].
Inserts the object or all of the objects in list ObjectOrObjects
into table
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 table type is
bag
and the object matches any whole object in the table, the object is not inserted. - 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.
For bag
and duplicate_bag
, objects in the list with identical keys will be
inserted in list order (from head to tail). That is, a subsequent call to
lookup(T,Key)
will return them in that inserted order.
Note
For
bag
the insertion order of indentical keys described above was accidentally reverted in OTP 23.0 and later fixed in OTP 25.3. That is, from OTP 23.0 up until OTP 25.3 the objects in a list are inserted in reverse order (from tail to head).For
duplicate_bag
the same faulty reverse insertion exist from OTP 23.0 until OTP 25.3. However, it is unpredictable and may or may not happen. A longer list will increase the probabiliy of the insertion being done in reverse.
-spec insert_new(Table, ObjectOrObjects) -> boolean() when Table :: table(), 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 ObjectOrObjects
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.
Checks if a term represent a valid compiled
match specification. A compiled match specification is
only valid on the Erlang node where it was compiled by calling
match_spec_compile/1
.
Note
Before STDLIB 3.4 (OTP 20.0) compiled match specifications did not have an external representation. If passed through
binary_to_term(term_to_binary(CMS))
or sent to another node and back, the result was always an empty binary<<>>
.After STDLIB 3.4 (OTP 20.0) compiled match specifications have an external representation as a node specific reference to the original compiled match specification. If passed through
binary_to_term(term_to_binary(CMS))
or sent to another node and back, the result may or may not be a valid compiled match specification depending on if the original compiled match specification was still alive.
Returns the last key Key
according to Erlang term order in table Table
of
type ordered_set
. For other table types, the function is synonymous to
first/1
. If the table is empty, '$end_of_table'
is returned.
To find preceding keys in the table, use prev/2
.
-spec last_lookup(Table) -> {Key, [Object]} | '$end_of_table' when Table :: table(), Key :: term(), Object :: tuple().
Similar to last/1
except that it returns the object(s) along with the key
stored in the table. This is equivalent to doing last/1
followed by a
lookup/2
. If the table is empty, '$end_of_table'
is returned.
To find preceding objects in the table, use prev_lookup/2
.
Returns a list of all objects with key Key
in table 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/0
1
as a key in an
ordered_set
and get the object returned as a result of doing a
lookup/2
with float/0
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 sequential order of object insertions is preserved; the first object inserted with the specified key is the first in the resulting list, and so on. See also the note about list insertion order.
-spec lookup_element(Table, Key, Pos) -> Elem when Table :: table(), Key :: term(), Pos :: pos_integer(), Elem :: term() | [term()].
For a table Table
of type set
or ordered_set
, the function returns the
Pos
:th element of the object with key Key
.
For tables of type bag
or duplicate_bag
, the functions returns a list with
the Pos
:th element of every object with key Key
.
If no object with key Key
exists, the function exits with reason badarg
.
If Pos
is larger than the size of the tuple, 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
.
-spec lookup_element(Table, Key, Pos, Default) -> Elem when Table :: table(), Key :: term(), Pos :: pos_integer(), Default :: term(), Elem :: term() | [term()].
For a table Table
of type set
or ordered_set
, the function returns the
Pos
:th element of the object with key Key
.
For tables of type bag
or duplicate_bag
, the functions returns a list with
the Pos
:th element of every object with key Key
.
If no object with key Key
exists, the function returns Default
.
If Pos
is larger than the size of any tuple with a matching key, 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/4
.
-spec match(Continuation) -> {[Match], Continuation} | '$end_of_table' when 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
Continuation
, which can be used in subsequent calls to this function.
When there are no more objects in the table, '$end_of_table'
is returned.
-spec match(Table, Pattern) -> [Match] when Table :: table(), Pattern :: match_pattern(), Match :: [term()].
Matches the objects in table Table
against pattern 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.
-spec match(Table, Pattern, Limit) -> {[Match], Continuation} | '$end_of_table' when Table :: table(), Pattern :: match_pattern(), Limit :: pos_integer(), Match :: [term()], Continuation :: continuation().
Works like match/2
, but returns only a limited (Limit
) number of matching
objects. Term Continuation
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
.
-spec match_delete(Table, Pattern) -> true when Table :: table(), Pattern :: match_pattern().
Deletes all objects that match pattern Pattern
from table Table
. For a
description of patterns, see match/2
.
-spec match_object(Continuation) -> {[Object], Continuation} | '$end_of_table' when 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 Continuation
, which can be used in subsequent calls to
this function.
When there are no more objects in the table, '$end_of_table'
is returned.
-spec match_object(Table, Pattern) -> [Object] when Table :: table(), Pattern :: match_pattern(), Object :: tuple().
Matches the objects in table Table
against pattern 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.
-spec match_object(Table, Pattern, Limit) -> {[Object], Continuation} | '$end_of_table' when Table :: table(), Pattern :: match_pattern(), Limit :: pos_integer(), Object :: tuple(), Continuation :: continuation().
Works like match_object/2
, but only returns a limited (Limit
) number of
matching objects. Term Continuation
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
.
-spec match_spec_compile(MatchSpec) -> CompiledMatchSpec when MatchSpec :: match_spec(), CompiledMatchSpec :: compiled_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. To check the validity of a compiled match
specification, use is_compiled_ms/1
.
If term MatchSpec
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 thedets:select/1
operations.
-spec match_spec_run(List, CompiledMatchSpec) -> list() when List :: [term()], CompiledMatchSpec :: compiled_match_spec().
Executes the matching specified in a compiled
match specification on a list of terms. Term
CompiledMatchSpec
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 List
and the function returns a
list containing all results. If an element in List
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 List
.
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 thedets:select/1
operations and by Mnesia during transactions.
Works like lookup/2
, but does not return the objects. Returns true
if one or
more elements in the table has key Key
, otherwise false
.
-spec new(Name, Options) -> table() when Name :: atom(), Options :: [Option], Option :: Type | Access | named_table | {keypos, Pos} | {heir, Pid :: pid(), HeirData} | {heir, none} | Tweaks, Type :: table_type(), Access :: table_access(), WriteConcurrencyAlternative :: boolean() | auto, Tweaks :: {write_concurrency, WriteConcurrencyAlternative} | {read_concurrency, boolean()} | {decentralized_counters, boolean()} | compressed, Pos :: pos_integer(), 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 Options
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}, {decentralized_counters,false}]
.
set
- The table is aset
table: one key, one object, no order among objects. This is the default table type.ordered_set
- The table is aordered_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, theordered_set
tables regard keys as equal when they compare equal, not only when they match. This means that to anordered_set
table,integer/0
1
andfloat/0
1.0
are regarded as equal. This also means that the key used to lookup an element does not necessarily match the key in the returned elements, iffloat/0
's andinteger/0
's are mixed in keys of a table.bag
- The table is abag
table, which can have many objects, but only one instance of each object, per key.duplicate_bag
- The table is aduplicate_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 itsName
which can then be used instead of the table identifier in subsequent operations.The function will also return the
Name
instead of the table identifier. To get the table identifier of a named table, usewhereis/1
.{keypos,Pos}
- Specifies which element in the stored tuples to use as key. By default, it is the first element, that is,Pos=1
. 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
Pos
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,HeirData}
is sent to the heir when that occurs. The heir must be a local process. Default heir isnone
, which destroys the table when the owner terminates.{write_concurrency,WriteConcurrencyAlternative}
- Performance tuning. Defaults tofalse
, 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 totrue
, the table is optimized for 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.The
auto
alternative for thewrite_concurrency
option is similar to thetrue
option but automatically adjusts the synchronization granularity during runtime depending on how the table is used. This is the recommendedwrite_concurrency
option when using Erlang/OTP 25 and above as it performs well in most scenarios.The
write_concurrency
option can be combined with the optionsread_concurrency
anddecentralized_counters
. You typically want to combinewrite_concurrency
withread_concurrency
when large concurrent read bursts and large concurrent write bursts are common; for more information, see optionread_concurrency
. It is almost always a good idea to combine thewrite_concurrency
option with thedecentralized_counters
option.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
andread_concurrency
is a constant overhead per table forset
,bag
andduplicate_bag
when thetrue
alternative for thewrite_concurrency
option is not used. For all tables with theauto
alternative andordered_set
tables withtrue
alternative the memory overhead depends on the amount of actual detected concurrency during runtime. The memory overhead can be especially large when bothwrite_concurrency
andread_concurrency
are combined.Note
Prior to stdlib-3.7 (OTP-22.0)
write_concurrency
had no effect onordered_set
.Note
The
auto
alternative for thewrite_concurrency
option is only available in OTP-25.0 and above.{read_concurrency,boolean()}
(Since OTP R14B)
Performance tuning. Defaults tofalse
. When set totrue
, the table is optimized for concurrent read operations. When this option is enabled 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 optionwrite_concurrency
. You typically want to combine these when large concurrent read bursts and large concurrent write bursts are common.{decentralized_counters,boolean()}
(Since OTP 23.0)
Performance tuning. Defaults totrue
for all tables with thewrite_concurrency
option set toauto
. For tables of typeordered_set
the option also defaults to true when thewrite_concurrency
option is set totrue
. The option defaults tofalse
for all other configurations. This option has no effect if thewrite_concurrency
option is set tofalse
.When this option is set to
true
, the table is optimized for frequent concurrent calls to operations that modify the tables size and/or its memory consumption (e.g.,insert/2
anddelete/2
). The drawback is that calls toinfo/1
andinfo/2
withsize
ormemory
as the second argument can get much slower when thedecentralized_counters
option is turned on.When this option is enabled the counters for the table size and memory consumption are distributed over several cache lines and the scheduling threads are mapped to one of those cache lines. The
erl
option+dcg
can be used to control the number of cache lines that the counters are distributed over.compressed
(Since OTP R14B01)
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 asmatch
andselect
, get much slower. The key element is not compressed.
-spec next(Table, Key1) -> Key2 | '$end_of_table' when Table :: table(), Key1 :: term(), Key2 :: term().
Returns the next key Key2
, following key Key1
in table 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 Key1
no longer
exists in the table. For table type ordered_set
, the function always returns
the next key after Key1
in term order, regardless whether Key1
ever existed
in the table.
-spec next_lookup(Table, Key1) -> {Key2, [Object]} | '$end_of_table' when Table :: table(), Key1 :: term(), Key2 :: term(), Object :: tuple().
Similar to next/2
except that it returns the object(s) along with the key
stored in the table. This is equivalent to doing next/2
followed by a
lookup/2
. If no next key exists, '$end_of_table'
is returned.
It can be interleaved with next/2
during traversal.
-spec prev(Table, Key1) -> Key2 | '$end_of_table' when Table :: table(), Key1 :: term(), Key2 :: term().
Returns the previous key Key2
, preceding key Key1
according to Erlang term
order in table Table
of type ordered_set
. For other table types, the
function is synonymous to next/2
. If no previous key exists, '$end_of_table'
is returned.
To find the last key in an ordered_set
table, use last/1
.
-spec prev_lookup(Table, Key1) -> {Key2, [Object]} | '$end_of_table' when Table :: table(), Key1 :: term(), Key2 :: term(), Object :: tuple().
Similar to prev/2
except that it returns the object(s) along with the key
stored in the table. This is equivalent to doing prev/2
followed by a
lookup/2
. If no previous key exists, '$end_of_table'
is returned.
It can be interleaved with prev/2
during traversal.
Renames the named table Table
to the new name Name
. Afterwards, the old name
cannot be used to access the table. Renaming an unnamed table has no effect.
-spec repair_continuation(Continuation, MatchSpec) -> Continuation when 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 may therefore be 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 may fail:
T=ets:new(x,[]),
...
MS = ets:fun2ms(fun({N,_}=A) when (N rem 10) =:= 0 -> A end),
{_,C} = ets:select(T, MS, 10),
MaybeBroken = binary_to_term(term_to_binary(C)),
ets:select(MaybeBroken).
The following sequence works, as the call to
repair_continuation/2
reestablishes the
MaybeBroken
continuation.
T=ets:new(x,[]),
...
MS = ets:fun2ms(fun({N,_}=A) when (N rem 10) =:= 0 -> A end),
{_,C} = ets:select(T,MS,10),
MaybeBroken = binary_to_term(term_to_binary(C)),
ets:select(ets:repair_continuation(MaybeBroken,MS)).
Note
This function is rarely needed in application code. It is used by Mnesia to provide distributed
select/3
andselect/1
sequences. A normal application would either use Mnesia or keep the continuation from being converted to external format.The actual behavior of compiled match specifications when recreated from external format has changed and may change in future releases, but this interface remains for backward compatibility. See
is_compiled_ms/1
.
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(Table, true)
. The table remains fixed until
the process releases it by calling
safe_fixtable(Table, false)
, 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(Table,X) ->
safe_fixtable(Table,true),
clean_all_with_value(Table,X,ets:first(Table)),
safe_fixtable(Table,false).
clean_all_with_value(Table,X,'$end_of_table') ->
true;
clean_all_with_value(Table,X,Key) ->
case ets:lookup(Table,Key) of
[{Key,X}] ->
ets:delete(Table,Key);
_ ->
true
end,
clean_all_with_value(Table,X,ets:next(Table,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(Table, 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
.
-spec select(Continuation) -> {[Match], Continuation} | '$end_of_table' when 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
Continuation
, which can be used in subsequent calls to this function.
When there are no more objects in the table, '$end_of_table'
is returned.
-spec select(Table, MatchSpec) -> [Match] when Table :: table(), MatchSpec :: match_spec(), Match :: term().
Matches the objects in table 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(Table,{'$1','$2','$3'})
is exactly equivalent to:
ets:select(Table,[{{'$1','$2','$3'},[],['$$']}])
And that the following match_object/2
call:
ets:match_object(Table,{'$1','$2','$1'})
is exactly equivalent to
ets:select(Table,[{{'$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(Table,[{{'$1','$2','$3'},[],['$$']}])
gives the same output as:
ets:select(Table,[{{'$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(Table,[{{'$1','$2','$1'},[],['$_']}])
gives the same output as:
ets:select(Table,[{{'$1','$2','$1'},[],[{{'$1','$2','$3'}}]}])
This syntax is equivalent to the syntax used in the trace patterns (see the
dbg
) 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.
-spec select(Table, MatchSpec, Limit) -> {[Match], Continuation} | '$end_of_table' when Table :: table(), MatchSpec :: match_spec(), Limit :: pos_integer(), Match :: term(), Continuation :: continuation().
Works like select/2
, but only returns a limited (Limit
) number of matching
objects. Term Continuation
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
.
-spec select_count(Table, MatchSpec) -> NumMatched when Table :: table(), MatchSpec :: match_spec(), NumMatched :: non_neg_integer().
Matches the objects in table 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 select_delete/2
function that does not
delete any elements, but only counts them.
The function returns the number of objects matched.
-spec select_delete(Table, MatchSpec) -> NumDeleted when Table :: table(), MatchSpec :: match_spec(), NumDeleted :: non_neg_integer().
Matches the objects in table 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.
-spec select_replace(Table, MatchSpec) -> NumReplaced when Table :: table(), MatchSpec :: match_spec(), NumReplaced :: non_neg_integer().
Matches the objects in the table 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 specification 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}]}])),
-spec select_reverse(Continuation) -> {[Match], Continuation} | '$end_of_table' when 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).
...
-spec select_reverse(Table, MatchSpec) -> [Match] when Table :: table(), 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
.
-spec select_reverse(Table, MatchSpec, Limit) -> {[Match], Continuation} | '$end_of_table' when Table :: table(), MatchSpec :: match_spec(), Limit :: pos_integer(), 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 Limit
matching objects in the table, not the first.
-spec setopts(Table, Opts) -> true when Table :: table(), 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.
-spec slot(Table, I) -> [Object] | '$end_of_table' when Table :: table(), I :: non_neg_integer(), 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 I
of table Table
. A table can be traversed by
repeatedly calling the function, starting with the first slot I=0
and ending
when '$end_of_table'
is returned. If argument I
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 I
in Erlang term order.
-spec tab2file(Table, Filename) -> ok | {error, Reason} when Table :: table(), Filename :: file:name(), Reason :: term().
Dumps table Table
to file Filename
.
Equivalent to tab2file(Table, Filename,[])
-spec tab2file(Table, Filename, Options) -> ok | {error, Reason} when Table :: table(), Filename :: file:name(), Options :: [Option], Option :: {extended_info, [ExtInfo]} | {sync, boolean()}, ExtInfo :: md5sum | object_count, Reason :: term().
Dumps table Table
to file Filename
.
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}
.
Returns a list of all objects in table Table
.
-spec tabfile_info(Filename) -> {ok, TableInfo} | {error, Reason} when Filename :: file:name(), TableInfo :: [InfoItem], InfoItem :: {name, atom()} | {type, Type} | {protection, Protection} | {named_table, boolean()} | {keypos, non_neg_integer()} | {size, non_neg_integer()} | {extended_info, [ExtInfo]} | {version, {Major :: non_neg_integer(), Minor :: non_neg_integer()}}, 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 withfile2tab/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
, orordered_set
). This type is used when loading the table again.protection
- The protection of the dumped table (that is,private
,protected
, orpublic
). A table loaded from the file gets the same protection.named_table
-true
if the table was a named table when dumped to file, otherwisefalse
. Notice that when a named table is loaded from a file, there cannot exist a table in the system with the same name.keypos
- Thekeypos
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 apublic
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 totab2file/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 atomsobject_count
andmd5sum
.version
- A tuple{Major,Minor}
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
.
-spec table(Table) -> QueryHandle when Table :: table(), QueryHandle :: qlc:query_handle().
Equivalent to table/2
.
-spec table(Table, Options) -> QueryHandle when Table :: table(), QueryHandle :: qlc:query_handle(), Options :: [Option] | Option, Option :: {n_objects, NObjects} | {traverse, TraverseMethod}, NObjects :: default | pos_integer(), 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 Table
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 callingfirst/1
andnext/2
.last_prev
- The table is traversed one key at a time by callinglast/1
andprev/2
.select
- The table is traversed by callingselect/3
andselect/1
. Optionn_objects
determines the number of objects returned (the third argument ofselect/3
); the default is to return100
objects at a time. The match specification (the second argument ofselect/3
) is assembled by QLC: simple filters are translated into equivalent match specifications while more complicated filters must be applied to all objects returned byselect/3
given a match specification that matches all objects.{select, MatchSpec}
- As forselect
, the table is traversed by callingselect/3
andselect/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(Table = 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(Table, [{traverse, {select, MS}}]).
An example with an implicit match specification:
10> QH2 = qlc:q([{Y} || {X,Y} <- ets:table(Table), (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.
Returns and removes a list of all objects with key Key
in table Table
.
The specified Key
is used to identify the object by either comparing equal
the key of an object in an ordered_set
table, or matching in other types of
tables (for details on the difference, see lookup/2
and new/2
).
-spec test_ms(Tuple, MatchSpec) -> {ok, Result} | {error, Errors} when 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 MatchSpec
for "syntactic"
correctness and runs the match specification against object Tuple
.
If the match specification is syntactically correct, the function either returns
{ok,Result}
, where Result
is what would have been the result in a real
select/2
call, or false
if the match specification does not
match object Tuple
.
If the match specification contains errors, tuple {error, Errors}
is returned,
where Errors
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
.
-spec to_dets(Table, DetsTab) -> DetsTab when Table :: table(), DetsTab :: dets:tab_name().
Fills an already created/opened Dets table with the objects in the already
opened ETS table named Table
. The Dets table is emptied before the objects are
inserted.
-spec update_counter(Table, Key, UpdateOp | [UpdateOp] | Incr) -> Result | [Result] when Table :: table(), Key :: term(), UpdateOp :: {Pos, Incr} | {Pos, Incr, Threshold, SetValue}, Pos :: integer(), Incr :: integer(), Threshold :: integer(), SetValue :: integer(), Result :: integer().
Equivalent to update_counter/4
.
-spec update_counter(Table, Key, UpdateOp | Incr | [UpdateOp], Default) -> Result | [Result] when Table :: table(), Key :: term(), UpdateOp :: {Pos, Incr} | {Pos, Incr, Threshold, SetValue}, Pos :: integer(), Incr :: integer(), Threshold :: integer(), SetValue :: integer(), Result :: integer(), Default :: tuple().
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 updates the object with key Key
in table Table
by adding Incr
to the element at position Pos
. The new counter value is
returned. If no position is specified, the element directly following key
(<keypos>+1
) is updated.
If a Threshold
is specified, the counter is reset to value SetValue
if the
following conditions occur:
Incr
is not negative (>= 0
) and the result would be greater than (>
)Threshold
.Incr
is negative (< 0
) and the result would be less than (<
)Threshold
.
A list of UpdateOp
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 Key
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 Default
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
,Threshold
, orSetValue
is not an integer.
-spec update_element(Table, Key, ElementSpec) -> boolean() when Table :: table(), Key :: term(), ElementSpec :: {Pos, Value} | [{Pos, Value}], Pos :: pos_integer(), Value :: term().
Equivalent to update_element/4
.
-spec update_element(Table, Key, ElementSpec, Default) -> true when Table :: table(), Key :: term(), ElementSpec :: {Pos, Value} | [{Pos, Value}], Pos :: pos_integer(), Value :: term(), Default :: tuple().
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 Key
in table Table
.
The element at position Pos
is given the value Value
.
A list of {Pos,Value}
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 Key
is found, otherwise false
.
The specified Key
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 Default
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 function fails with reason badarg
in the following situations:
- The table type is not
set
orordered_set
. Pos
< 1.Pos
> object arity.- The default object arity is smaller than
<keypos>
. - The element to update is also the key.
This function returns the tid/0
of the named table identified by
TableName
, or undefined
if no such table exists. The tid/0
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/0
will be invalid even if another named
table is created with the same name.