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
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,
The number of tables stored at one Erlang node is limited.
The current default limit is approximately 1400 tables. The upper
limit can be increased by setting the environment variable
Note that there is no automatic garbage collection for tables.
Even if there are no references to a table from any process, it
will not automatically be destroyed unless the owner process
terminates. It can be destroyed explicitly by using
Some implementation details:
Also worth noting is the subtle difference between
matching and comparing equal, which is
demonstrated by the different table types
In general, the functions below will exit with reason
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 towards a single object will either succeed or fail completely without any effect at all (atomicy). Nor can any intermediate results of the update be seen by other processes (isolation). Some functions that update several objects state that they even guarantee atomicy and isolation for the entire operation. In database terms the isolation level can be seen as "serializable", as if all isolated operations were carried out serially, one after the other in a strict order.
No other support is available within ETS that would guarantee
consistency between objects. However, the
Some of the functions uses a match specification,
match_spec. A brief explanation is given in
Opaque continuation used by
A match specification, see above.
A compiled match specification.
A table identifier, as returned by new/2.
Returns a list of all tables at the node. Named tables are given by their names, unnamed tables are given 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 may or may not be included in the list. Only tables created/deleted before ets:all() is called are guaranteed to be included/excluded.
Deletes the entire table
Deletes all objects with the key
Delete all objects in the ETS table
Delete the exact object
Reads a file produced by
Equivalent to
Reads a file produced by
The currently only supported option is
If no
If verification is turned on and the file was written with
the option
Returns the first key
Use
If
If
Fills an already created ETS table with the objects in the
already opened Dets table named
Throws a badarg error if any of the tables does not exist or the dets table is not open.
Pseudo function that by means of a
The parse transform is implemented in the module
The fun is very restricted, it can take only a single
parameter (the object to match): a sole variable or a
tuple. It needs to use the
The return value is the resulting match_spec.
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 this 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 will be replaced by match_spec
4> ets:fun2ms(fun({M,N}) when N > X, is_atomm(M) -> M end). Error: fun containing local Erlang function calls ('is_atomm' 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 can be seen by the example, the function can be called from the shell too. The fun needs to be literally in the call when used from the shell as well. Other means than the parse_transform are used in the shell case, but more or less the same restrictions apply (the exception being records, as they are not handled by the shell).
If the parse_transform is not applied to a module which
calls this pseudo function, the call will fail in runtime
(with a
For more information, see
Make process
The process
Note that
Displays information about all ETS tables on tty.
Browses the table
Returns information about the table
Returns the information associated with
In R11B and earlier, this function would not fail but return
In addition to the
If the table has been fixed using
If the table never has been fixed, the call returns
Returns internal statistics about set, bag and duplicate_bag tables on an internal format used by OTP test suites.
Not for production use.
Replaces the existing objects of the table
When called with the argument
If the type of the table is
Inserts the object or all of the objects in the list
The entire operation is guaranteed to be
This function works exactly like
This function is used to check if a term is a valid
compiled
ets:is_compiled_ms(ets:match_spec_compile([{'_',[],[true]}])).
will yield
MS = ets:match_spec_compile([{'_',[],[true]}]),
Broken = binary_to_term(term_to_binary(MS)),
ets:is_compiled_ms(Broken).
will yield false, as the variable
The fact that compiled match_specs has no external representation is for performance reasons. It may be subject to change in future releases, while this interface will still remain for backward compatibility reasons.
Returns the last key
Use
Returns a list of all objects with the key
In the case of
If the table is of type
Note that the time order of object insertions is preserved; the first object inserted with the given key will be first in the resulting list, and so on.
Insert and look-up times in tables of type
If the table
If the table is of type
If no object with the key
The difference between
Matches the objects in the table
A pattern is a term that may contain:
The function returns a list with one element for each matching object, where each element is an ordered list of pattern variable bindings. An example:
6> ets:match(T, '$1'). % Matches every object in the 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, i.e. 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.
On tables of the
Works like
Continues a match started with
Deletes all objects which match the pattern
Matches the objects in the table
If the key is specified in the pattern, the match is very efficient. If the key is not specified, i.e. 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.
On tables of the
Works like
Continues a match started with
This function transforms a
If the term
This function has limited use in normal code, it is used by
Dets to perform the
This function executes the matching specified in a
compiled
The matching will be executed on each element in
Table = ets:new...
MatchSpec = ....
% The following call...
ets:match_spec_run(ets:tab2list(Table),
ets:match_spec_compile(MatchSpec)),
% ...will give the same result as the more common (and more efficient)
ets:select(Table,MatchSpec),
This function has limited use in normal code, it is used by
Dets to perform the
Works like
Creates a new table and returns a table identifier which 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.
The parameter
Note that any tuple stored in the table must have at
least
Set a process as heir. The heir will inherit the table if
the owner terminates. The message
In current implementation, table type
Returns the next key
Use
Unless a table of type
Returns the previous key
Use
Renames the named table
This function can be used to restore an opaque continuation
returned by
The reason for this function is that continuation terms
contain compiled match_specs and therefore will be
invalidated if converted to external term format. Given that
the original match_spec is kept intact, the continuation can
be restored, meaning it can once again be used in subsequent
As an example, the following sequence of calls will fail:
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).
...while the following sequence will work:
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)).
...as the call to
This function is very rarely needed in application code. It
is used by Mnesia to implement distributed
The reason for not having an external representation of a compiled match_spec is performance. It may be subject to change in future releases, while this interface will remain for backward compatibility.
Fixes a table of the
A process fixes a table by calling
If several processes fix a table, the table will remain 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 actually release the table.
When a table is fixed, a sequence of
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)).
Note that no deleted objects are actually removed 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 will never be freed. The performance of operations on the table will also degrade significantly.
Use
Note that for tables of the
Matches the objects in the table
This means that the match_spec is always a list of one or
more tuples (of arity 3). The tuples first element should be
a pattern as described in the documentation of
The return value is constructed using the "match variables"
bound in the MatchHead or using the special match variables
ets:match(Tab,{'$1','$2','$3'})
is exactly equivalent to:
ets:select(Tab,[{{'$1','$2','$3'},[],['$$']}])
- and the following
ets:match_object(Tab,{'$1','$2','$1'})
is exactly equivalent to
ets:select(Tab,[{{'$1','$2','$1'},[],['$_']}])
Composite terms can be constructed in the
ets:select(Tab,[{{'$1','$2','$3'},[],['$$']}])
gives the same output as:
ets:select(Tab,[{{'$1','$2','$3'},[],[['$1','$2','$3']]}])
i.e. 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 with the single element in the tuple being the tuple
one wants to construct (as an ordinary tuple could be mistaken
for a
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
The
is expressed like this (X replaced with '$1' and Y with '$2'):
On tables of the
Works like
Continues a match started with
Matches the objects in the table
The function could be described as a
The function returns the number of objects matched.
Matches the objects in the table
The function returns the number of objects actually deleted from the table.
The
Works like
Works like
Note that this is not equivalent to
reversing the result list of a
Continues a match started with
For all other table types, the behaviour is exactly that of
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).
...
Set table options. The only option that currently is allowed to be
set after the table has been created is
This function is mostly for debugging purposes, Normally
one should use
Returns all objects in the
Unless a table of type
Dumps the table
Equivalent to
Dumps the table
When dumping the table, certain 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's 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 actual 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.
The
The number of objects actually written to the file is noted in the file footer, why verification of file truncation is possible even if the file was updated during dump.
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 will detect the slightest bitflip in the file data. Using this costs a fair amount of CPU time.
Whenever the
Returns a list of all objects in the table
Returns information about the table dumped to file by
The following items are returned:
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
An error is returned if the file is inaccessible,
badly damaged or not an file produced with
When there are only simple restrictions on the key position
QLC uses
The following example uses an explicit match_spec 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 implicit match_spec:
10> QH2 = qlc:q([{Y} || {X,Y} <- ets:table(Tab), (X > 1) or (X < 5)]).
The latter example is in fact equivalent to the former which
can be verified using the function
11> qlc:info(QH1) =:= qlc:info(QH2). true
This function is a utility to test a
This is a useful debugging and test tool, especially when
writing complicated
Fills an already created/opened Dets table with the objects
in the already opened ETS table named
This function provides an efficient way to update one or more counters, without the hassle of having to look up an object, update the object by incrementing an element and insert the resulting object into the table again. (The update is done atomically; i.e. no process can access the ets table in the middle of the operation.)
It will destructively update the object with key
If a
A list of
The given
The function will fail with reason
This function provides an efficient way to update one or more elements within an object, without the hassle of having to look up, update and write back the entire object.
It will destructively update the object with key
A list of
The function returns
The given
The function will fail with reason