This module provides the parse transformation that makes calls to
The translation from funs to match specifications
is accessed through the two "pseudo functions"
As everyone trying to use
Read the whole manual page if it is the first time you are using the transformations.
Match specifications are used more or less as filters. They resemble
usual Erlang matching in a list comprehension or in a fun used with
As the execution and structure of the match specifications are like that of a fun, it is more straightforward to write it using the familiar fun syntax and to have that translated into a match specification automatically. A real fun is clearly more powerful than the match specifications allow, but bearing the match specifications in mind, and what they can do, it is still more convenient to write it all as a fun. This module contains the code that translates the fun syntax into match specification terms.
Using
Consider a simple table of employees:
-record(emp, {empno, %Employee number as a string, the key
surname, %Surname of the employee
givenname, %Given name of employee
dept, %Department, one of {dev,sales,prod,adm}
empyear}). %Year the employee was employed
We create the table using:
ets:new(emp_tab, [{keypos,#emp.empno},named_table,ordered_set]).
We fill the table with randomly chosen data:
[{emp,"011103","Black","Alfred",sales,2000},
{emp,"041231","Doe","John",prod,2001},
{emp,"052341","Smith","John",dev,1997},
{emp,"076324","Smith","Ella",sales,1995},
{emp,"122334","Weston","Anna",prod,2002},
{emp,"535216","Chalker","Samuel",adm,1998},
{emp,"789789","Harrysson","Joe",adm,1996},
{emp,"963721","Scott","Juliana",dev,2003},
{emp,"989891","Brown","Gabriel",prod,1999}]
Assuming that we want the employee numbers of everyone in the sales department, there are several ways.
1> ets:match(emp_tab, {'_', '$1', '_', '_', sales, '_'}). [["011103"],["076324"]]
ets:foldr(fun(#emp{empno = E, dept = sales},Acc) -> [E | Acc];
(_,Acc) -> Acc
end,
[],
emp_tab).
The result is
Consider a "pure"
ets:select(emp_tab, [{#emp{empno = '$1', dept = sales, _='_'},[],['$1']}]).
Although the record syntax is used, it is still hard to
read and even harder to write. The first element of the tuple,
Using
-include_lib("stdlib/include/ms_transform.hrl").
ets:select(emp_tab, ets:fun2ms(
fun(#emp{empno = E, dept = sales}) ->
E
end)).
This example requires no special knowledge of match
specifications to understand. The head of the fun matches what
you want to filter out and the body returns what you want
returned. As long as the fun can be kept within the limits of the
match specifications, there is no need to transfer all table data
to the process for filtering as in the
In the
Assume that we want to get all the employee numbers of employees
hired before year 2000. Using
[E | Acc];
(_,Acc) -> Acc
end,
[],
emp_tab). ]]>
The result is
This gives the same result.
We write it using
E
end)). ]]>
Assume that we want the whole object matching instead of only one element. One alternative is to assign a variable to every part of the record and build it up once again in the body of the fun, but the following is easier:
Obj
end)).]]>
As in ordinary Erlang matching, you can bind a variable to the
whole matched object using a "match inside the match", that is, a
This example concerns the body of the fun. Assume that all employee
numbers beginning with zero (
ets:select(emp_tab, ets:fun2ms(
fun(#emp{empno = [$0 | Rest] }) ->
{[$0|Rest],[$1|Rest]}
end)).
This query hits the feature of partially bound
keys in table type
The fun can have many clauses. Assume that we want to do the following:
If an employee started before 1997, return the tuple
If an employee started 1997 or later, but before 2001, return
For all other employees, return
This is accomplished as follows:
{guru,E};
(#emp{empno = E, empyear = Y}) when Y < 1997 ->
{inventory, E};
(#emp{empno = E, empyear = Y}) when Y > 2001 ->
{newbie, E};
(#emp{empno = E, empyear = Y}) -> % 1997 -- 2001
{rookie, E}
end)). ]]>
The result is as follows:
[{rookie,"011103"},
{rookie,"041231"},
{guru,"052341"},
{guru,"076324"},
{newbie,"122334"},
{rookie,"535216"},
{inventory,"789789"},
{newbie,"963721"},
{rookie,"989891"}]
What more can you do? A simple answer is: see the documentation of
The head of the fun is a head matching (or mismatching)
one parameter, one object of the table we select
from. The object is always a single variable (can be
The guard section can contain any guard expression of Erlang. The following is a list of BIFs and expressions:
Type tests:
Boolean operators:
Relational operators: >, >=, <, =<, =:=, ==, =/=, /=
Arithmetics:
Bitwise operators:
The guard BIFs:
Contrary to the fact with "handwritten" match specifications, the
Semicolons (
The body of the fun is used to construct the
resulting value. When selecting from tables, one usually construct
a suiting term here, using ordinary Erlang term construction, like
tuple parentheses, list brackets, and variables matched out in the
head, possibly with the occasional constant. Whatever
expressions are allowed in guards are also allowed here, but no special
functions exist except
The
This section describes the slightly different match specifications
translated by
The same reasons for using the parse transformation apply to
The following is an example module to trace on:
-module(toy).
-export([start/1, store/2, retrieve/1]).
start(Args) ->
toy_table = ets:new(toy_table, Args).
store(Key, Value) ->
ets:insert(toy_table, {Key,Value}).
retrieve(Key) ->
[{Key, Value}] = ets:lookup(toy_table, Key),
Value.
During model testing, the first test results in
We suspect the
1> dbg:tracer(). {ok,<0.88.0>}
We turn on call tracing for all processes, we want to make a pretty restrictive trace pattern, so there is no need to call trace only a few processes (usually it is not):
2> dbg:p(all,call). {ok,[{matched,nonode@nohost,25}]}
We specify the filter, we want to view calls that resemble
3> dbg:tp(ets,new,dbg:fun2ms(fun([toy_table,_]) -> true end)). {ok,[{matched,nonode@nohost,1},{saved,1}]}
As can be seen, the fun used with
The following trace output is received during test:
) call ets:new(toy_table, [ordered_set]) ]]>
Assume that we have not found the problem yet, and want to see what
4> dbg:tp(ets,new,dbg:fun2ms(fun([toy_table,_]) -> return_trace() end)).
The following trace output is received during test:
) call ets:new(toy_table,[ordered_set])
(<0.86.0>) returned from ets:new/2 -> 24 ]]>
The call to
The test now fails with
start(Args) ->
toy_table = ets:new(toy_table, [named_table|Args]).
With the same tracing turned on, the following trace output is received:
) call ets:new(toy_table,[named_table,ordered_set])
(<0.86.0>) returned from ets:new/2 -> toy_table ]]>
Assume that the module now passes all testing and goes into
the system. After a while, it is found that table
1> dbg:tracer(). {ok,<0.88.0>} 2> dbg:p(all,call). {ok,[{matched,nonode@nohost,25}]} 3> dbg:tpl(toy,store,dbg:fun2ms(fun([A,_]) when is_atom(A) -> true end)). {ok,[{matched,nonode@nohost,1},{saved,1}]}
We use
Assume that nothing happens when tracing in this way. The function
is never called with these parameters. We conclude that
someone else (some other module) is doing it and realize that we
must trace on
4> dbg:tpl(ets,insert,dbg:fun2ms(fun([toy_table,{A,_}]) when is_atom(A) -> message(caller()) end)). {ok,[{matched,nonode@nohost,1},{saved,2}]}
The caller is now displayed in the "additional message" part of the trace output, and the following is displayed after a while:
) call ets:insert(toy_table,{garbage,can}) ({evil_mod,evil_fun,2}) ]]>
You have realized that function
This example illustrates the most used calls in match specifications for
The following warnings and restrictions apply to the funs used in
with
To use the pseudo functions triggering the translation,
ensure to include the header file
The fun must be literally constructed inside the
parameter list to the pseudo functions. The fun cannot
be bound to a variable first and then passed to
Many restrictions apply to the fun that is translated into a match specification. To put it simple: you cannot use anything in the fun that you cannot use in a match specification. This means that, among others, the following restrictions apply to the fun itself:
Functions written in Erlang cannot be called, neither can local functions, global functions, or real funs.
Everything that is written as a function call is translated
into a match specification call to a built-in function, so that
the call
Variables occurring in the head of the fun are replaced by
match specification variables in the order of occurrence, so
that fragment
Variables that are not included in the head are imported
from the environment and made into match specification
1> X = 25. 25 2> ets:fun2ms(fun({A,B}) when A > X -> B end). [{{'$1','$2'},[{'>','$1',{const,25}}],['$2']}]
Matching with
1> ets:fun2ms(fun({A,[B|C]} = D) when A > B -> D end). [{{'$1',['$2'|'$3']},[{'>','$1','$2'}],['$_']}] 2> ets:fun2ms(fun({A,[B|C]=D}) when A > B -> D end). Error: fun with head matching ('=' in head) cannot be translated into match_spec {error,transform_error} 3> ets:fun2ms(fun({A,[B|C]}) when A > B -> D = [B|C], D end). Error: fun with body matching ('=' in body) is illegal as match_spec {error,transform_error}
All variables are bound in the head of a match specification, so
the translator cannot allow multiple bindings. The special case
when matching is done on the top-level makes the variable bind
to
The following expressions are translated equally:
ets:fun2ms(fun({a,_} = A) -> A end).
ets:fun2ms(fun({a,_}) -> object() end).
The special match specification variables
ets:match_object(Table, {'$1',test,'$2'}).
This is the same as:
ets:select(Table, ets:fun2ms(fun({A,test,B}) -> object() end)).
In this simple case, the former expression is probably preferable in terms of readability.
The
ets:select(Table, [{{'$1',test,'$2'},[],['$_']}]).
Matching on the top-level of the fun head can be a
more natural way to access
Term constructions/literals are translated as much as is needed to
get them into valid match specification. This way tuples are made
into match specification tuple constructions (a one element tuple
containing the tuple) and constant expressions are used when
importing variables from the environment. Records are also
translated into plain tuple constructions, calls to element,
and so on. The guard test
Language constructions such as
If header file
Ensure that the header is included when using
If pseudo function triggering the translation is
The translation from funs to match specifications is done at compile time, so runtime performance is not affected by using these pseudo functions.
For more information about match specifications, see the
Takes an error code returned by one of the other functions in the module and creates a textual description of the error.
Implements the transformation at compile time. This
function is called by the compiler to do the source code
transformation if and when header file
For information about how to use this parse transformation, see
For a description of match specifications, see section
Implements the transformation when the