1qlc(3)                     Erlang Module Definition                     qlc(3)
2
3
4

NAME

6       qlc - Query interface to Mnesia, ETS, Dets, and so on.
7
8

DESCRIPTION

10       This  module provides a query interface to Mnesia, ETS, Dets, and other
11       data structures that provide an iterator style traversal of objects.
12

OVERVIEW

14       This module provides a query  interface  to  QLC  tables.  Typical  QLC
15       tables  are  Mnesia, ETS, and Dets tables. Support is also provided for
16       user-defined tables, see section  Implementing a QLC Table. A query  is
17       expressed  using  Query  List  Comprehensions  (QLCs). The answers to a
18       query are determined by data in QLC tables that fulfill the constraints
19       expressed  by  the QLCs of the query. QLCs are similar to ordinary list
20       comprehensions as described in  Erlang Reference Manual  and   Program‐
21       ming  Examples,  except that variables introduced in patterns cannot be
22       used in list expressions. In the absence of optimizations  and  options
23       such as cache and unique (see section Common Options, every QLC free of
24       QLC tables evaluates to the same list of answers as the identical ordi‐
25       nary list comprehension.
26
27       While  ordinary  list  comprehensions  evaluate to lists, calling q/1,2
28       returns a query handle. To obtain all the answers to a query,  eval/1,2
29       is  to be called with the query handle as first argument. Query handles
30       are essentially functional objects (funs) created in the module calling
31       q/1,2.  As  the  funs  refer to the module code, be careful not to keep
32       query handles too long if the module  code  is  to  be  replaced.  Code
33       replacement  is  described  in section  Compilation and Code Loading in
34       the Erlang Reference Manual. The list of answers can also be  traversed
35       in  chunks by use of a query cursor. Query cursors are created by call‐
36       ing cursor/1,2 with a query handle as first argument. Query cursors are
37       essentially  Erlang  processes.  One  answer at a time is sent from the
38       query cursor process to the process that created the cursor.
39

SYNTAX

41       Syntactically QLCs have the same parts as ordinary list comprehensions:
42
43       [Expression || Qualifier1, Qualifier2, ...]
44
45       Expression (the template) is  any  Erlang  expression.  Qualifiers  are
46       either  filters or generators. Filters are Erlang expressions returning
47       boolean(). Generators have the form Pattern  <-  ListExpression,  where
48       ListExpression is an expression evaluating to a query handle or a list.
49       Query  handles  are  returned  from  append/1,2,  keysort/2,3,   q/1,2,
50       sort/1,2, string_to_handle/1,2,3, and table/2.
51

EVALUATION

53       A query handle is evaluated in the following order:
54
55         * Inspection  of  options  and  the  collection  of information about
56           tables. As a result, qualifiers are modified during  the  optimiza‐
57           tion phase.
58
59         * All  list  expressions are evaluated. If a cursor has been created,
60           evaluation takes place in the cursor process. For list  expressions
61           that  are  QLCs, the list expressions of the generators of the QLCs
62           are evaluated as well. Be careful if  list  expressions  have  side
63           effects, as list expressions are evaluated in unspecified order.
64
65         * The  answers  are  found  by evaluating the qualifiers from left to
66           right, backtracking when some filter returns false,  or  collecting
67           the template when all filters return true.
68
69       Filters  that  do not return boolean() but fail are handled differently
70       depending on their syntax: if the filter is a guard, it returns  false,
71       otherwise  the  query evaluation fails. This behavior makes it possible
72       for the qlc module to do some optimizations without affecting the mean‐
73       ing  of a query. For example, when testing some position of a table and
74       one or more constants for equality, only the objects with equal  values
75       are candidates for further evaluation. The other objects are guaranteed
76       to make the filter return false, but never fail.  The  (small)  set  of
77       candidate  objects  can often be found by looking up some key values of
78       the table or by traversing the table using a match specification. It is
79       necessary to place the guard filters immediately after the table gener‐
80       ator, otherwise the candidate objects are not  restricted  to  a  small
81       set.  The  reason  is that objects that could make the query evaluation
82       fail must not be excluded by looking up a key or running a match speci‐
83       fication.
84

JOIN

86       The  qlc  module  supports fast join of two query handles. Fast join is
87       possible if some position P1 of one query handler and some position  P2
88       of another query handler are tested for equality. Two fast join methods
89       are provided:
90
91         * Lookup join traverses all objects of one  query  handle  and  finds
92           objects  of  the other handle (a QLC table) such that the values at
93           P1 and P2 match or compare equal. The qlc module  does  not  create
94           any  indexes  but  looks  up  values using the key position and the
95           indexed positions of the QLC table.
96
97         * Merge join sorts the objects of each query handle if necessary  and
98           filters  out  objects  where the values at P1 and P2 do not compare
99           equal. If many objects with the same value of P2 exist, a temporary
100           file is used for the equivalence classes.
101
102       The qlc module warns at compile time if a QLC combines query handles in
103       such a way that more than one join is possible. That is, no query plan‐
104       ner  is  provided  that  can  select a good order between possible join
105       operations. It is up to the user to  order  the  joins  by  introducing
106       query handles.
107
108       The  join  is  to  be  expressed  as a guard filter. The filter must be
109       placed immediately after the  two  joined  generators,  possibly  after
110       guard  filters  that use variables from no other generators but the two
111       joined generators. The qlc module inspects the operands of =:=/2, ==/2,
112       is_record/2,  element/2, and logical operators (and/2, or/2, andalso/2,
113       orelse/2, xor/2) when determining which joins to consider.
114

COMMON OPTIONS

116       The following options are accepted by  cursor/2,  eval/2,  fold/4,  and
117       info/2:
118
119         * {cache_all,  Cache},  where  Cache  is  equal to ets or list adds a
120           {cache, Cache} option to every list expression of the query  except
121           tables  and lists. Defaults to {cache_all, no}. Option cache_all is
122           equivalent to {cache_all, ets}.
123
124         * {max_list_size, MaxListSize}, where  MaxListSize  is  the  size  in
125           bytes  of  terms on the external format. If the accumulated size of
126           collected objects exceeds MaxListSize, the objects are written onto
127           a  temporary  file. This option is used by option {cache, list} and
128           by the merge join method. Defaults to 512*1024 bytes.
129
130         * {tmpdir_usage, TmpFileUsage} determines the action taken  when  qlc
131           is  about  to create temporary files on the directory set by option
132           tmpdir. If the value is not_allowed, an error  tuple  is  returned,
133           otherwise  temporary  files  are  created  as  needed.  Default  is
134           allowed, which means that no further action is  taken.  The  values
135           info_msg,  warning_msg,  and  error_msg mean that the function with
136           the corresponding name in module error_logger is called for  print‐
137           ing some information (currently the stacktrace).
138
139         * {tmpdir,  TempDirectory}  sets the directory used by merge join for
140           temporary files and by option {cache, list}. The option also  over‐
141           rides  option tmpdir of keysort/3 and sort/2. Defaults to "", which
142           means that the directory returned by file:get_cwd() is used.
143
144         * {unique_all, true} adds a  {unique,  true}  option  to  every  list
145           expression  of  the  query. Defaults to {unique_all, false}. Option
146           unique_all is equivalent to {unique_all, true}.
147

GETTING STARTED

149       As mentioned earlier, queries are expressed in the  list  comprehension
150       syntax  as described in section Expressions in Erlang Reference Manual.
151       In the following, some familiarity with list comprehensions is assumed.
152       The  examples  in  section  List Comprehensions in Programming Examples
153       can get you started. Notice that list comprehensions  do  not  add  any
154       computational  power  to  the  language; anything that can be done with
155       list comprehensions can also be done without them. But they add  syntax
156       for  expressing simple search problems, which is compact and clear once
157       you get used to it.
158
159       Many list comprehension expressions can be evaluated by the qlc module.
160       Exceptions  are expressions, such that variables introduced in patterns
161       (or filters) are used in some generator later in  the  list  comprehen‐
162       sion.  As an example, consider an implementation of lists:append(L): [X
163       ||Y <- L, X <- Y]. Y is introduced in the first generator and  used  in
164       the second. The ordinary list comprehension is normally to be preferred
165       when there is a choice as to which  to  use.  One  difference  is  that
166       eval/1,2  collects  answers  in  a list that is finally reversed, while
167       list comprehensions collect  answers  on  the  stack  that  is  finally
168       unwound.
169
170       What  the qlc module primarily adds to list comprehensions is that data
171       can be read from QLC tables in small chunks. A QLC table is created  by
172       calling  qlc:table/2.  Usually  qlc:table/2 is not called directly from
173       the query but through an interface function  of  some  data  structure.
174       Erlang/OTP includes a few examples of such functions: mnesia:table/1,2,
175       ets:table/1,2, and dets:table/1,2. For a  given  data  structure,  many
176       functions can create QLC tables, but common for these functions is that
177       they return a query handle created by qlc:table/2. Using the QLC tables
178       provided by Erlang/OTP is usually probably sufficient, but for the more
179       advanced user section Implementing a QLC Table describes the  implemen‐
180       tation of a function calling qlc:table/2.
181
182       Besides  qlc:table/2,  other  functions  return query handles. They are
183       used more seldom than tables, but are sometimes useful.  qlc:append/1,2
184       traverses  objects  from many tables or lists after each other. If, for
185       example, you want to traverse all answers to a query QH and then finish
186       off  by  a  term  {finished}, you can do that by calling qlc:append(QH,
187       [{finished}]). append/2 first returns all objects  of  QH,  then  {fin‐
188       ished}.  If  a  tuple  {finished} exists among the answers to QH, it is
189       returned twice from append/2.
190
191       As another example, consider concatenating the answers to  two  queries
192       QH1  and  QH2  while  removing  all duplicates. This is accomplished by
193       using option unique:
194
195       qlc:q([X || X <- qlc:append(QH1, QH2)], {unique, true})
196
197       The cost is substantial: every returned answer is stored in an ETS  ta‐
198       ble.  Before  returning  an answer, it is looked up in the ETS table to
199       check if it has already been returned. Without the unique  option,  all
200       answers  to  QH1  would be returned followed by all answers to QH2. The
201       unique option keeps the order between the remaining answers.
202
203       If the order of the answers is not important, there is  an  alternative
204       to the unique option, namely to sort the answers uniquely:
205
206       qlc:sort(qlc:q([X || X <- qlc:append(QH1, QH2)], {unique, true})).
207
208       This query also removes duplicates but the answers are sorted. If there
209       are many answers, temporary files are used.  Notice  that  to  get  the
210       first  unique answer, all answers must be found and sorted. Both alter‐
211       natives find duplicates by comparing answers, that is, if A1 and A2 are
212       answers found in that order, then A2 is a removed if A1 == A2.
213
214       To  return  only a few answers, cursors can be used. The following code
215       returns no more than five answers using an ETS table  for  storing  the
216       unique answers:
217
218       C = qlc:cursor(qlc:q([X || X <- qlc:append(QH1, QH2)],{unique,true})),
219       R = qlc:next_answers(C, 5),
220       ok = qlc:delete_cursor(C),
221       R.
222
223       QLCs  are  convenient  for stating constraints on data from two or more
224       tables. The following example does a natural join on two query  handles
225       on position 2:
226
227       qlc:q([{X1,X2,X3,Y1} ||
228                 {X1,X2,X3} <- QH1,
229                 {Y1,Y2} <- QH2,
230                 X2 =:= Y2])
231
232       The  qlc  module evaluates this differently depending on the query han‐
233       dles QH1 and QH2. If, for example, X2 is matched against the key  of  a
234       QLC  table,  the  lookup join method traverses the objects of QH2 while
235       looking up key values in the table. However, if not X2 or Y2 is matched
236       against  the  key or an indexed position of a QLC table, the merge join
237       method ensures that QH1 and QH2 are both sorted on position 2 and  next
238       do the join by traversing the objects one by one.
239
240       Option  join  can be used to force the qlc module to use a certain join
241       method. For the rest of this section it is assumed that the excessively
242       slow join method called "nested loop" has been chosen:
243
244       qlc:q([{X1,X2,X3,Y1} ||
245                 {X1,X2,X3} <- QH1,
246                 {Y1,Y2} <- QH2,
247                 X2 =:= Y2],
248             {join, nested_loop})
249
250       In this case the filter is applied to every possible pair of answers to
251       QH1 and QH2, one at a time. If there are M answers to QH1 and N answers
252       to QH2, the filter is run M*N times.
253
254       If  QH2  is  a call to the function for gb_trees, as defined in section
255       Implementing a QLC Table, then gb_table:table/1, the iterator  for  the
256       gb-tree is initiated for each answer to QH1. The objects of the gb-tree
257       are then returned one by one. This is probably the most  efficient  way
258       of traversing the table in that case, as it takes minimal computational
259       power to get the following object. But if QH2 is not a table but a more
260       complicated  QLC,  it  can be more efficient to use some RAM memory for
261       collecting the answers in a cache, particularly if there are only a few
262       answers.  It  must  then  be  assumed  that  evaluating QH2 has no side
263       effects so that the meaning of the query does  not  change  if  QH2  is
264       evaluated  only once. One way of caching the answers is to evaluate QH2
265       first of all and substitute the list of answers for QH2 in  the  query.
266       Another way is to use option cache. It is expressed like this:
267
268       QH2' = qlc:q([X || X <- QH2], {cache, ets})
269
270       or only
271
272       QH2' = qlc:q([X || X <- QH2], cache)
273
274       The effect of option cache is that when generator QH2' is run the first
275       time, every answer is stored in an ETS table. When the next  answer  of
276       QH1  is  tried, answers to QH2' are copied from the ETS table, which is
277       very fast. As for option unique the  cost  is  a  possibly  substantial
278       amount of RAM memory.
279
280       Option  {cache,  list} offers the possibility to store the answers in a
281       list on the process heap. This has the potential of being  faster  than
282       ETS  tables,  as  there is no need to copy answers from the table. How‐
283       ever, it can often result in slower evaluation because of more  garbage
284       collections  of  the  process heap and increased RAM memory consumption
285       because of larger heaps. Another drawback with cache lists is  that  if
286       the  list  size  exceeds a limit, a temporary file is used. Reading the
287       answers from a file is much slower than copying them from an ETS table.
288       But  if  the  available RAM memory is scarce, setting the limit to some
289       low value is an alternative.
290
291       Option cache_all can be set to ets or list when evaluating a query.  It
292       adds  a  cache  or {cache, list} option to every list expression except
293       QLC tables and lists on all levels of the query. This can be  used  for
294       testing  if  caching  would improve efficiency at all. If the answer is
295       yes, further testing is needed to pinpoint the generators that  are  to
296       be cached.
297

IMPLEMENTING A QLC TABLE

299       As  an  example of how to use function table/2, the implementation of a
300       QLC table for the gb_trees module is given:
301
302       -module(gb_table).
303
304       -export([table/1]).
305
306       table(T) ->
307           TF = fun() -> qlc_next(gb_trees:next(gb_trees:iterator(T))) end,
308           InfoFun = fun(num_of_objects) -> gb_trees:size(T);
309                        (keypos) -> 1;
310                        (is_sorted_key) -> true;
311                        (is_unique_objects) -> true;
312                        (_) -> undefined
313                     end,
314           LookupFun =
315               fun(1, Ks) ->
316                       lists:flatmap(fun(K) ->
317                                             case gb_trees:lookup(K, T) of
318                                                 {value, V} -> [{K,V}];
319                                                 none -> []
320                                             end
321                                     end, Ks)
322               end,
323           FormatFun =
324               fun({all, NElements, ElementFun}) ->
325                       ValsS = io_lib:format("gb_trees:from_orddict(~w)",
326                                             [gb_nodes(T, NElements, ElementFun)]),
327                       io_lib:format("gb_table:table(~s)", [ValsS]);
328                  ({lookup, 1, KeyValues, _NElements, ElementFun}) ->
329                       ValsS = io_lib:format("gb_trees:from_orddict(~w)",
330                                             [gb_nodes(T, infinity, ElementFun)]),
331                       io_lib:format("lists:flatmap(fun(K) -> "
332                                     "case gb_trees:lookup(K, ~s) of "
333                                     "{value, V} -> [{K,V}];none -> [] end "
334                                     "end, ~w)",
335                                     [ValsS, [ElementFun(KV) || KV <- KeyValues]])
336               end,
337           qlc:table(TF, [{info_fun, InfoFun}, {format_fun, FormatFun},
338                          {lookup_fun, LookupFun},{key_equality,'=='}]).
339
340       qlc_next({X, V, S}) ->
341           [{X,V} | fun() -> qlc_next(gb_trees:next(S)) end];
342       qlc_next(none) ->
343           [].
344
345       gb_nodes(T, infinity, ElementFun) ->
346           gb_nodes(T, -1, ElementFun);
347       gb_nodes(T, NElements, ElementFun) ->
348           gb_iter(gb_trees:iterator(T), NElements, ElementFun).
349
350       gb_iter(_I, 0, _EFun) ->
351           '...';
352       gb_iter(I0, N, EFun) ->
353           case gb_trees:next(I0) of
354               {X, V, I} ->
355                   [EFun({X,V}) | gb_iter(I, N-1, EFun)];
356               none ->
357                   []
358           end.
359
360       TF is the traversal function. The qlc module requires that there  is  a
361       way  of  traversing  all objects of the data structure. gb_trees has an
362       iterator function suitable for  that  purpose.  Notice  that  for  each
363       object  returned, a new fun is created. As long as the list is not ter‐
364       minated by [], it is assumed that the tail of the  list  is  a  nullary
365       function  and  that  calling  the function returns further objects (and
366       functions).
367
368       The lookup function is optional. It is assumed that the lookup function
369       always  finds values much faster than it would take to traverse the ta‐
370       ble. The first argument is the  position  of  the  key.  As  qlc_next/1
371       returns  the  objects  as {Key, Value} pairs, the position is 1. Notice
372       that the lookup function is to return {Key, Value} pairs, as  the  tra‐
373       versal function does.
374
375       The  format function is also optional. It is called by info/1,2 to give
376       feedback at runtime of how the query is to be evaluated. Try to give as
377       good  feedback  as  possible  without  showing too much details. In the
378       example, at most seven objects of the table are shown. The format func‐
379       tion  handles  two  cases:  all means that all objects of the table are
380       traversed; {lookup, 1, KeyValues} means that  the  lookup  function  is
381       used for looking up key values.
382
383       Whether  the  whole  table  is  traversed  or  only some keys looked up
384       depends on how the query is expressed. If the query has the form
385
386       qlc:q([T || P <- LE, F])
387
388       and P is a tuple, the qlc module analyzes P and F in  compile  time  to
389       find positions of tuple P that are tested for equality to constants. If
390       such a position at runtime turns out to be the key position, the lookup
391       function  can  be used, otherwise all objects of the table must be tra‐
392       versed. The info function InfoFun returns the key position.  There  can
393       be  indexed  positions  as well, also returned by the info function. An
394       index is an extra table that makes lookup on some position fast. Mnesia
395       maintains  indexes  upon  request,  and  introduces so called secondary
396       keys. The qlc module prefers to look up objects using  the  key  before
397       secondary keys regardless of the number of constants to look up.
398

KEY EQUALITY

400       Erlang/OTP has two operators for testing term equality: ==/2 and =:=/2.
401       The difference is all about the integers that  can  be  represented  by
402       floats.  For example, 2 == 2.0 evaluates to true while 2 =:= 2.0 evalu‐
403       ates to false. Normally this is a minor issue, but the qlc module  can‐
404       not ignore the difference, which affects the user's choice of operators
405       in QLCs.
406
407       If the qlc module at compile time can determine that some  constant  is
408       free  of  integers,  it  does  not matter which one of ==/2 or =:=/2 is
409       used:
410
411       1> E1 = ets:new(t, [set]), % uses =:=/2 for key equality
412       Q1 = qlc:q([K ||
413       {K} <- ets:table(E1),
414       K == 2.71 orelse K == a]),
415       io:format("~s~n", [qlc:info(Q1)]).
416       ets:match_spec_run(lists:flatmap(fun(V) ->
417                                               ets:lookup(20493, V)
418                                        end,
419                                        [a,2.71]),
420                          ets:match_spec_compile([{{'$1'},[],['$1']}]))
421
422       In the example, operator ==/2 has been handled exactly as  =:=/2  would
423       have  been handled. However, if it cannot be determined at compile time
424       that some constant is free of integers, and the table uses  =:=/2  when
425       comparing  keys  for  equality  (see option key_equality), then the qlc
426       module does not try to look up the constant. The reason is  that  there
427       is  in the general case no upper limit on the number of key values that
428       can compare equal to such a constant; every combination of integers and
429       floats must be looked up:
430
431       2> E2 = ets:new(t, [set]),
432       true = ets:insert(E2, [{{2,2},a},{{2,2.0},b},{{2.0,2},c}]),
433       F2 = fun(I) ->
434       qlc:q([V || {K,V} <- ets:table(E2), K == I])
435       end,
436       Q2 = F2({2,2}),
437       io:format("~s~n", [qlc:info(Q2)]).
438       ets:table(53264,
439                 [{traverse,
440                   {select,[{{'$1','$2'},[{'==','$1',{const,{2,2}}}],['$2']}]}}])
441       3> lists:sort(qlc:e(Q2)).
442       [a,b,c]
443
444       Looking up only {2,2} would not return b and c.
445
446       If the table uses ==/2 when comparing keys for equality, the qlc module
447       looks up the constant regardless of which operator is used in the  QLC.
448       However, ==/2 is to be preferred:
449
450       4> E3 = ets:new(t, [ordered_set]), % uses ==/2 for key equality
451       true = ets:insert(E3, [{{2,2.0},b}]),
452       F3 = fun(I) ->
453       qlc:q([V || {K,V} <- ets:table(E3), K == I])
454       end,
455       Q3 = F3({2,2}),
456       io:format("~s~n", [qlc:info(Q3)]).
457       ets:match_spec_run(ets:lookup(86033, {2,2}),
458                          ets:match_spec_compile([{{'$1','$2'},[],['$2']}]))
459       5> qlc:e(Q3).
460       [b]
461
462       Lookup  join  is handled analogously to lookup of constants in a table:
463       if the join operator is ==/2, and the table where constants are  to  be
464       looked  up uses =:=/2 when testing keys for equality, then the qlc mod‐
465       ule does not consider lookup join for that table.
466

DATA TYPES

468       abstract_expr() = erl_parse:abstract_expr()
469
470              Parse trees for Erlang expression, see section The Abstract For‐
471              mat in the ERTS User's Guide.
472
473       answer() = term()
474
475       answers() = [answer()]
476
477       cache() = ets | list | no
478
479       match_expression() = ets:match_spec()
480
481              Match  specification, see section Match Specifications in Erlang
482              in the ERTS User's Guide and ms_transform(3).
483
484       no_files() = integer() >= 1
485
486              An integer > 1.
487
488       key_pos() = integer() >= 1 | [integer() >= 1]
489
490       max_list_size() = integer() >= 0
491
492       order() = ascending | descending | order_fun()
493
494       order_fun() = fun((term(), term()) -> boolean())
495
496       query_cursor()
497
498              A query cursor.
499
500       query_handle()
501
502              A query handle.
503
504       query_handle_or_list() = query_handle() | list()
505
506       query_list_comprehension() = term()
507
508              A literal query list comprehension.
509
510       spawn_options() = default | [proc_lib:spawn_option()]
511
512       sort_options() = [sort_option()] | sort_option()
513
514       sort_option() =
515           {compressed, boolean()} |
516           {no_files, no_files()} |
517           {order, order()} |
518           {size, integer() >= 1} |
519           {tmpdir, tmp_directory()} |
520           {unique, boolean()}
521
522              See file_sorter(3).
523
524       tmp_directory() = [] | file:name()
525
526       tmp_file_usage() =
527           allowed | not_allowed | info_msg | warning_msg | error_msg
528

EXPORTS

530       append(QHL) -> QH
531
532              Types:
533
534                 QHL = [query_handle_or_list()]
535                 QH = query_handle()
536
537              Returns a query handle. When evaluating  query  handle  QH,  all
538              answers  to the first query handle in QHL are returned, followed
539              by all answers to the remaining query handles in QHL.
540
541       append(QH1, QH2) -> QH3
542
543              Types:
544
545                 QH1 = QH2 = query_handle_or_list()
546                 QH3 = query_handle()
547
548              Returns a query handle. When evaluating query  handle  QH3,  all
549              answers to QH1 are returned, followed by all answers to QH2.
550
551              append(QH1, QH2) is equivalent to append([QH1, QH2]).
552
553       cursor(QH) -> Cursor
554
555       cursor(QH, Options) -> Cursor
556
557              Types:
558
559                 QH = query_handle_or_list()
560                 Options = [Option] | Option
561                 Option =
562                     {cache_all, cache()} |
563                     cache_all |
564                     {max_list_size, max_list_size()} |
565                     {spawn_options, spawn_options()} |
566                     {tmpdir_usage, tmp_file_usage()} |
567                     {tmpdir, tmp_directory()} |
568                     {unique_all, boolean()} |
569                     unique_all
570                 Cursor = query_cursor()
571
572              Creates  a  query cursor and makes the calling process the owner
573              of the  cursor.  The  cursor  is  to  be  used  as  argument  to
574              next_answers/1,2   and   (eventually)   delete_cursor/1.   Calls
575              erlang:spawn_opt/2 to spawn and link to a process that evaluates
576              the  query  handle. The value of option spawn_options is used as
577              last argument when calling spawn_opt/2. Defaults to [link].
578
579              Example:
580
581              1> QH = qlc:q([{X,Y} || X <- [a,b], Y <- [1,2]]),
582              QC = qlc:cursor(QH),
583              qlc:next_answers(QC, 1).
584              [{a,1}]
585              2> qlc:next_answers(QC, 1).
586              [{a,2}]
587              3> qlc:next_answers(QC, all_remaining).
588              [{b,1},{b,2}]
589              4> qlc:delete_cursor(QC).
590              ok
591
592              cursor(QH) is equivalent to cursor(QH, []).
593
594       delete_cursor(QueryCursor) -> ok
595
596              Types:
597
598                 QueryCursor = query_cursor()
599
600              Deletes a query cursor. Only the owner of the cursor can  delete
601              the cursor.
602
603       e(QH) -> Answers | Error
604
605       e(QH, Options) -> Answers | Error
606
607       eval(QH) -> Answers | Error
608
609       eval(QH, Options) -> Answers | Error
610
611              Types:
612
613                 QH = query_handle_or_list()
614                 Answers = answers()
615                 Options = [Option] | Option
616                 Option =
617                     {cache_all, cache()} |
618                     cache_all |
619                     {max_list_size, max_list_size()} |
620                     {tmpdir_usage, tmp_file_usage()} |
621                     {tmpdir, tmp_directory()} |
622                     {unique_all, boolean()} |
623                     unique_all
624                 Error = {error, module(), Reason}
625                 Reason = file_sorter:reason()
626
627              Evaluates a query handle in the calling process and collects all
628              answers in a list.
629
630              Example:
631
632              1> QH = qlc:q([{X,Y} || X <- [a,b], Y <- [1,2]]),
633              qlc:eval(QH).
634              [{a,1},{a,2},{b,1},{b,2}]
635
636              eval(QH) is equivalent to eval(QH, []).
637
638       fold(Function, Acc0, QH) -> Acc1 | Error
639
640       fold(Function, Acc0, QH, Options) -> Acc1 | Error
641
642              Types:
643
644                 QH = query_handle_or_list()
645                 Function = fun((answer(), AccIn) -> AccOut)
646                 Acc0 = Acc1 = AccIn = AccOut = term()
647                 Options = [Option] | Option
648                 Option =
649                     {cache_all, cache()} |
650                     cache_all |
651                     {max_list_size, max_list_size()} |
652                     {tmpdir_usage, tmp_file_usage()} |
653                     {tmpdir, tmp_directory()} |
654                     {unique_all, boolean()} |
655                     unique_all
656                 Error = {error, module(), Reason}
657                 Reason = file_sorter:reason()
658
659              Calls  Function  on  successive  answers  to  the  query  handle
660              together  with an extra argument AccIn. The query handle and the
661              function are evaluated in the  calling  process.  Function  must
662              return a new accumulator, which is passed to the next call. Acc0
663              is returned if there are no answers to the query handle.
664
665              Example:
666
667              1> QH = [1,2,3,4,5,6],
668              qlc:fold(fun(X, Sum) -> X + Sum end, 0, QH).
669              21
670
671              fold(Function, Acc0, QH) is equivalent to  fold(Function,  Acc0,
672              QH, []).
673
674       format_error(Error) -> Chars
675
676              Types:
677
678                 Error = {error, module(), term()}
679                 Chars = io_lib:chars()
680
681              Returns  a  descriptive  string  in  English  of  an error tuple
682              returned by some of the functions of the qlc module or the parse
683              transform. This function is mainly used by the compiler invoking
684              the parse transform.
685
686       info(QH) -> Info
687
688       info(QH, Options) -> Info
689
690              Types:
691
692                 QH = query_handle_or_list()
693                 Options = [Option] | Option
694                 Option = EvalOption | ReturnOption
695                 EvalOption =
696                     {cache_all, cache()} |
697                     cache_all |
698                     {max_list_size, max_list_size()} |
699                     {tmpdir_usage, tmp_file_usage()} |
700                     {tmpdir, tmp_directory()} |
701                     {unique_all, boolean()} |
702                     unique_all
703                 ReturnOption =
704                     {depth, Depth} |
705                     {flat, boolean()} |
706                     {format, Format} |
707                     {n_elements, NElements}
708                 Depth = infinity | integer() >= 0
709                 Format = abstract_code | string
710                 NElements = infinity | integer() >= 1
711                 Info = abstract_expr() | string()
712
713              Returns  information  about  a  query  handle.  The  information
714              describes  the  simplifications  and  optimizations that are the
715              results of preparing the query for evaluation. This function  is
716              probably mainly useful during debugging.
717
718              The  information has the form of an Erlang expression where QLCs
719              most likely occur. Depending on the  format  functions  of  men‐
720              tioned  QLC  tables,  it  is not certain that the information is
721              absolutely accurate.
722
723              Options:
724
725                * The default is to return a sequence of QLCs in a block,  but
726                  if  option  {flat,  false}  is  specified, one single QLC is
727                  returned.
728
729                * The default is to return a string, but  if  option  {format,
730                  abstract_code}  is  specified,  abstract  code  is  returned
731                  instead. In the abstract code, port identifiers, references,
732                  and pids are represented by strings.
733
734                * The  default  is  to  return  all  elements in lists, but if
735                  option {n_elements, NElements} is specified, only a  limited
736                  number of elements are returned.
737
738                * The default is to show all parts of objects and match speci‐
739                  fications, but if option {depth, Depth} is specified,  parts
740                  of terms below a certain depth are replaced by '...'.
741
742              info(QH) is equivalent to info(QH, []).
743
744              Examples:
745
746              In  the  following  example two simple QLCs are inserted only to
747              hold option {unique, true}:
748
749              1> QH = qlc:q([{X,Y} || X <- [x,y], Y <- [a,b]]),
750              io:format("~s~n", [qlc:info(QH, unique_all)]).
751              begin
752                  V1 =
753                      qlc:q([
754                             SQV ||
755                                 SQV <- [x,y]
756                            ],
757                            [{unique,true}]),
758                  V2 =
759                      qlc:q([
760                             SQV ||
761                                 SQV <- [a,b]
762                            ],
763                            [{unique,true}]),
764                  qlc:q([
765                         {X,Y} ||
766                             X <- V1,
767                             Y <- V2
768                        ],
769                        [{unique,true}])
770              end
771
772              In the following example QLC V2 has been inserted  to  show  the
773              joined  generators  and  the join method chosen. A convention is
774              used for lookup join: the first generator (G2) is the  one  tra‐
775              versed,  the second (G1) is the table where constants are looked
776              up.
777
778              1> E1 = ets:new(e1, []),
779              E2 = ets:new(e2, []),
780              true = ets:insert(E1, [{1,a},{2,b}]),
781              true = ets:insert(E2, [{a,1},{b,2}]),
782              Q = qlc:q([{X,Z,W} ||
783              {X, Z} <- ets:table(E1),
784              {W, Y} <- ets:table(E2),
785              X =:= Y]),
786              io:format("~s~n", [qlc:info(Q)]).
787              begin
788                  V1 =
789                      qlc:q([
790                             P0 ||
791                                 P0 = {W,Y} <- ets:table(17)
792                            ]),
793                  V2 =
794                      qlc:q([
795                             [G1|G2] ||
796                                 G2 <- V1,
797                                 G1 <- ets:table(16),
798                                 element(2, G1) =:= element(1, G2)
799                            ],
800                            [{join,lookup}]),
801                  qlc:q([
802                         {X,Z,W} ||
803                             [{X,Z}|{W,Y}] <- V2
804                        ])
805              end
806
807       keysort(KeyPos, QH1) -> QH2
808
809       keysort(KeyPos, QH1, SortOptions) -> QH2
810
811              Types:
812
813                 KeyPos = key_pos()
814                 SortOptions = sort_options()
815                 QH1 = query_handle_or_list()
816                 QH2 = query_handle()
817
818              Returns a query handle. When evaluating query  handle  QH2,  the
819              answers  to query handle QH1 are sorted by file_sorter:keysort/4
820              according to the options.
821
822              The sorter uses temporary files only if QH1 does not evaluate to
823              a  list and the size of the binary representation of the answers
824              exceeds Size bytes, where Size is the value of option size.
825
826              keysort(KeyPos, QH1) is equivalent to keysort(KeyPos, QH1, []).
827
828       next_answers(QueryCursor) -> Answers | Error
829
830       next_answers(QueryCursor, NumberOfAnswers) -> Answers | Error
831
832              Types:
833
834                 QueryCursor = query_cursor()
835                 Answers = answers()
836                 NumberOfAnswers = all_remaining | integer() >= 1
837                 Error = {error, module(), Reason}
838                 Reason = file_sorter:reason()
839
840              Returns some or all of the remaining answers to a query  cursor.
841              Only the owner of QueryCursor can retrieve answers.
842
843              Optional  argument NumberOfAnswers determines the maximum number
844              of answers returned. Defaults to 10. If less than the  requested
845              number  of answers is returned, subsequent calls to next_answers
846              return [].
847
848       q(QLC) -> QH
849
850       q(QLC, Options) -> QH
851
852              Types:
853
854                 QH = query_handle()
855                 Options = [Option] | Option
856                 Option =
857                     {max_lookup, MaxLookup} |
858                     {cache, cache()} |
859                     cache |
860                     {join, Join} |
861                     {lookup, Lookup} |
862                     {unique, boolean()} |
863                     unique
864                 MaxLookup = integer() >= 0 | infinity
865                 Join = any | lookup | merge | nested_loop
866                 Lookup = boolean() | any
867                 QLC = query_list_comprehension()
868
869              Returns a query handle for a QLC. The  QLC  must  be  the  first
870              argument to this function, otherwise it is evaluated as an ordi‐
871              nary list comprehension. It is also necessary to add the follow‐
872              ing line to the source code:
873
874              -include_lib("stdlib/include/qlc.hrl").
875
876              This  causes  a parse transform to substitute a fun for the QLC.
877              The (compiled) fun is called when the query handle is evaluated.
878
879              When calling qlc:q/1,2 from the Erlang shell, the  parse  trans‐
880              form  is automatically called. When this occurs, the fun substi‐
881              tuted  for  the  QLC  is  not  compiled  but  is  evaluated   by
882              erl_eval(3). This is also true when expressions are evaluated by
883              file:eval/1,2 or in the debugger.
884
885              To be explicit, this does not work:
886
887              A = [X || {X} <- [{1},{2}]],
888              QH = qlc:q(A),
889
890              Variable A is bound to the evaluated value of the  list  compre‐
891              hension  ([1,2]).  The  compiler complains with an error message
892              ("argument is  not  a  query  list  comprehension");  the  shell
893              process stops with a badarg reason.
894
895              q(QLC) is equivalent to q(QLC, []).
896
897              Options:
898
899                * Option  {cache,  ets}  can be used to cache the answers to a
900                  QLC. The answers are stored in one ETS table for each cached
901                  QLC.  When  a  cached  QLC  is  evaluated again, answers are
902                  fetched from the table  without  any  further  computations.
903                  Therefore, when all answers to a cached QLC have been found,
904                  the ETS tables used for caching answers to the qualifiers of
905                  the  QLC  can  be  emptied.  Option  cache  is equivalent to
906                  {cache, ets}.
907
908                * Option {cache, list} can be used to cache the answers  to  a
909                  QLC  like  {cache,  ets}. The difference is that the answers
910                  are kept in a list (on the process  heap).  If  the  answers
911                  would  occupy  more  than  a certain amount of RAM memory, a
912                  temporary file is  used  for  storing  the  answers.  Option
913                  max_list_size sets the limit in bytes and the temporary file
914                  is put on the directory set by option tmpdir.
915
916                  Option cache has no effect if it is known that the QLC is to
917                  be  evaluated at most once. This is always true for the top-
918                  most QLC and also for the list expression of the first  gen‐
919                  erator  in a list of qualifiers. Notice that in the presence
920                  of side  effects  in  filters  or  callback  functions,  the
921                  answers to QLCs can be affected by option cache.
922
923                * Option  {unique,  true}  can  be  used  to  remove duplicate
924                  answers to a QLC. The unique answers are stored in  one  ETS
925                  table  for  each  QLC. The table is emptied every time it is
926                  known that there are no more  answers  to  the  QLC.  Option
927                  unique  is equivalent to {unique, true}. If option unique is
928                  combined with option {cache, ets}, two ETS tables are  used,
929                  but the full answers are stored in one table only. If option
930                  unique is combined with option {cache,  list},  the  answers
931                  are  sorted twice using keysort/3; once to remove duplicates
932                  and once to restore the order.
933
934              Options cache and unique apply not only to the  QLC  itself  but
935              also to the results of looking up constants, running match spec‐
936              ifications, and joining handles.
937
938              Example:
939
940              In the following example the cached results of  the  merge  join
941              are  traversed  for  each value of A. Notice that without option
942              cache the join would have been carried out three times, once for
943              each value of A.
944
945              1> Q = qlc:q([{A,X,Z,W} ||
946              A <- [a,b,c],
947              {X,Z} <- [{a,1},{b,4},{c,6}],
948              {W,Y} <- [{2,a},{3,b},{4,c}],
949              X =:= Y],
950              {cache, list}),
951              io:format("~s~n", [qlc:info(Q)]).
952              begin
953                  V1 =
954                      qlc:q([
955                             P0 ||
956                                 P0 = {X,Z} <-
957                                     qlc:keysort(1, [{a,1},{b,4},{c,6}], [])
958                            ]),
959                  V2 =
960                      qlc:q([
961                             P0 ||
962                                 P0 = {W,Y} <-
963                                     qlc:keysort(2, [{2,a},{3,b},{4,c}], [])
964                            ]),
965                  V3 =
966                      qlc:q([
967                             [G1|G2] ||
968                                 G1 <- V1,
969                                 G2 <- V2,
970                                 element(1, G1) == element(2, G2)
971                            ],
972                            [{join,merge},{cache,list}]),
973                  qlc:q([
974                         {A,X,Z,W} ||
975                             A <- [a,b,c],
976                             [{X,Z}|{W,Y}] <- V3,
977                             X =:= Y
978                        ])
979              end
980
981              sort/1,2  and  keysort/2,3  can also be used for caching answers
982              and for removing duplicates. When sorting answers are cached  in
983              a  list,  possibly stored on a temporary file, and no ETS tables
984              are used.
985
986              Sometimes (see table/2) traversal of tables can be done by look‐
987              ing  up  key  values, which is assumed to be fast. Under certain
988              (rare) circumstances there can be too many key  values  to  look
989              up. Option {max_lookup, MaxLookup} can then be used to limit the
990              number of lookups: if  more  than  MaxLookup  lookups  would  be
991              required,  no  lookups  are  done  but  the  table  is traversed
992              instead. Defaults to infinity, which  means  that  there  is  no
993              limit on the number of keys to look up.
994
995              Example:
996
997              In the following example, using the gb_table module from section
998              Implementing a QLC Table, there are six keys to look up:  {1,a},
999              {1,b},  {1,c},  {2,a},  {2,b}, and {2,c}. The reason is that the
1000              two elements of key {X, Y} are compared separately.
1001
1002              1> T = gb_trees:empty(),
1003              QH = qlc:q([X || {{X,Y},_} <- gb_table:table(T),
1004              ((X == 1) or (X == 2)) andalso
1005              ((Y == a) or (Y == b) or (Y == c))]),
1006              io:format("~s~n", [qlc:info(QH)]).
1007              ets:match_spec_run(
1008                     lists:flatmap(fun(K) ->
1009                                          case
1010                                              gb_trees:lookup(K,
1011                                                              gb_trees:from_orddict([]))
1012                                          of
1013                                              {value,V} ->
1014                                                  [{K,V}];
1015                                              none ->
1016                                                  []
1017                                          end
1018                                   end,
1019                                   [{1,a},{1,b},{1,c},{2,a},{2,b},{2,c}]),
1020                     ets:match_spec_compile([{{{'$1','$2'},'_'},[],['$1']}]))
1021
1022              Options:
1023
1024                * Option {lookup, true} can be used to  ensure  that  the  qlc
1025                  module  looks  up  constants in some QLC table. If there are
1026                  more than one QLC table among the list  expressions  of  the
1027                  generators,  constants  must be looked up in at least one of
1028                  the tables. The evaluation of the query fails if  there  are
1029                  no constants to look up. This option is useful when it would
1030                  be unacceptable to traverse all objects in some table.  Set‐
1031                  ting  option  lookup  to false ensures that no constants are
1032                  looked up ({max_lookup, 0} has the same effect). Defaults to
1033                  any,  which means that constants are looked up whenever pos‐
1034                  sible.
1035
1036                * Option {join, Join} can be used to  ensure  that  a  certain
1037                  join method is used:
1038
1039                  * {join, lookup} invokes the lookup join method.
1040
1041                  * {join, merge} invokes the merge join method.
1042
1043                  * {join,  nested_loop}  invokes the method of matching every
1044                    pair of objects from two handles. This  method  is  mostly
1045                    very slow.
1046
1047                  The  evaluation  of the query fails if the qlc module cannot
1048                  carry out the chosen join method.  Defaults  to  any,  which
1049                  means that some fast join method is used if possible.
1050
1051       sort(QH1) -> QH2
1052
1053       sort(QH1, SortOptions) -> QH2
1054
1055              Types:
1056
1057                 SortOptions = sort_options()
1058                 QH1 = query_handle_or_list()
1059                 QH2 = query_handle()
1060
1061              Returns  a  query  handle. When evaluating query handle QH2, the
1062              answers to query handle QH1  are  sorted  by  file_sorter:sort/3
1063              according to the options.
1064
1065              The sorter uses temporary files only if QH1 does not evaluate to
1066              a list and the size of the binary representation of the  answers
1067              exceeds Size bytes, where Size is the value of option size.
1068
1069              sort(QH1) is equivalent to sort(QH1, []).
1070
1071       string_to_handle(QueryString) -> QH | Error
1072
1073       string_to_handle(QueryString, Options) -> QH | Error
1074
1075       string_to_handle(QueryString, Options, Bindings) -> QH | Error
1076
1077              Types:
1078
1079                 QueryString = string()
1080                 Options = [Option] | Option
1081                 Option =
1082                     {max_lookup, MaxLookup} |
1083                     {cache, cache()} |
1084                     cache |
1085                     {join, Join} |
1086                     {lookup, Lookup} |
1087                     {unique, boolean()} |
1088                     unique
1089                 MaxLookup = integer() >= 0 | infinity
1090                 Join = any | lookup | merge | nested_loop
1091                 Lookup = boolean() | any
1092                 Bindings = erl_eval:binding_struct()
1093                 QH = query_handle()
1094                 Error = {error, module(), Reason}
1095                 Reason = erl_parse:error_info() | erl_scan:error_info()
1096
1097              A  string  version of q/1,2. When the query handle is evaluated,
1098              the fun  created  by  the  parse  transform  is  interpreted  by
1099              erl_eval(3). The query string is to be one single QLC terminated
1100              by a period.
1101
1102              Example:
1103
1104              1> L = [1,2,3],
1105              Bs = erl_eval:add_binding('L', L, erl_eval:new_bindings()),
1106              QH = qlc:string_to_handle("[X+1 || X <- L].", [], Bs),
1107              qlc:eval(QH).
1108              [2,3,4]
1109
1110              string_to_handle(QueryString) is  equivalent  to  string_to_han‐
1111              dle(QueryString, []).
1112
1113              string_to_handle(QueryString,    Options)   is   equivalent   to
1114              string_to_handle(QueryString, Options, erl_eval:new_bindings()).
1115
1116              This function is probably mainly useful when called from outside
1117              of Erlang, for example from a driver written in C.
1118
1119       table(TraverseFun, Options) -> QH
1120
1121              Types:
1122
1123                 TraverseFun = TraverseFun0 | TraverseFun1
1124                 TraverseFun0 = fun(() -> TraverseResult)
1125                 TraverseFun1 = fun((match_expression()) -> TraverseResult)
1126                 TraverseResult = Objects | term()
1127                 Objects = [] | [term() | ObjectList]
1128                 ObjectList = TraverseFun0 | Objects
1129                 Options = [Option] | Option
1130                 Option =
1131                     {format_fun, FormatFun} |
1132                     {info_fun, InfoFun} |
1133                     {lookup_fun, LookupFun} |
1134                     {parent_fun, ParentFun} |
1135                     {post_fun, PostFun} |
1136                     {pre_fun, PreFun} |
1137                     {key_equality, KeyComparison}
1138                 FormatFun  =  undefined  |  fun((SelectedObjects)  -> Format‐
1139                 edTable)
1140                 SelectedObjects =
1141                     all |
1142                     {all, NElements, DepthFun} |
1143                     {match_spec, match_expression()} |
1144                     {lookup, Position, Keys} |
1145                     {lookup, Position, Keys, NElements, DepthFun}
1146                 NElements = infinity | integer() >= 1
1147                 DepthFun = fun((term()) -> term())
1148                 FormatedTable = {Mod, Fun, Args} | abstract_expr() | string()
1149                 InfoFun = undefined | fun((InfoTag) -> InfoValue)
1150                 InfoTag  =   indices   |   is_unique_objects   |   keypos   |
1151                 num_of_objects
1152                 InfoValue = undefined | term()
1153                 LookupFun = undefined | fun((Position, Keys) -> LookupResult)
1154                 LookupResult = [term()] | term()
1155                 ParentFun = undefined | fun(() -> ParentFunValue)
1156                 PostFun = undefined | fun(() -> term())
1157                 PreFun = undefined | fun((PreArgs) -> term())
1158                 PreArgs = [PreArg]
1159                 PreArg = {parent_value, ParentFunValue} | {stop_fun, StopFun}
1160                 ParentFunValue = undefined | term()
1161                 StopFun = undefined | fun(() -> term())
1162                 KeyComparison = '=:=' | '=='
1163                 Position = integer() >= 1
1164                 Keys = [term()]
1165                 Mod = Fun = atom()
1166                 Args = [term()]
1167                 QH = query_handle()
1168
1169              Returns  a  query handle for a QLC table. In Erlang/OTP there is
1170              support for ETS, Dets, and Mnesia tables, but  many  other  data
1171              structures  can  be turned into QLC tables. This is accomplished
1172              by letting function(s)  in  the  module  implementing  the  data
1173              structure create a query handle by calling qlc:table/2. The dif‐
1174              ferent ways to traverse the table and properties  of  the  table
1175              are handled by callback functions provided as options to qlc:ta‐
1176              ble/2.
1177
1178                * Callback function TraverseFun is used for traversing the ta‐
1179                  ble.  It is to return a list of objects terminated by either
1180                  [] or a nullary fun to be used for traversing  the  not  yet
1181                  traversed  objects  of  the table. Any other return value is
1182                  immediately returned as value of the query evaluation. Unary
1183                  TraverseFuns  are  to  accept a match specification as argu‐
1184                  ment. The match specification is created by the parse trans‐
1185                  form  by  analyzing  the  pattern  of  the generator calling
1186                  qlc:table/2 and filters using variables  introduced  in  the
1187                  pattern. If the parse transform cannot find a match specifi‐
1188                  cation equivalent to the pattern and filters, TraverseFun is
1189                  called with a match specification returning every object.
1190
1191                  * Modules  that  can  use match specifications for optimized
1192                    traversal of tables are to call qlc:table/2 with an  unary
1193                    TraverseFun. An example is ets:table/2.
1194
1195                  * Other  modules can provide a nullary TraverseFun. An exam‐
1196                    ple is gb_table:table/1 in section Implementing a QLC  Ta‐
1197                    ble.
1198
1199                * Unary callback function PreFun is called once before the ta‐
1200                  ble is read for the first time. If the call fails, the query
1201                  evaluation fails.
1202
1203                  Argument  PreArgs  is a list of tagged values. There are two
1204                  tags, parent_value and stop_fun, used by Mnesia for managing
1205                  transactions.
1206
1207                  * The value of parent_value is the value returned by Parent‐
1208                    Fun, or undefined if there is no ParentFun.  ParentFun  is
1209                    called  once just before the call of PreFun in the context
1210                    of the process calling eval/1,2, fold/3,4, or cursor/1,2.
1211
1212                  * The value of stop_fun is a nullary fun  that  deletes  the
1213                    cursor if called from the parent, or undefined if there is
1214                    no cursor.
1215
1216                * Nullary callback function PostFun is called once  after  the
1217                  table  was  last read. The return value, which is caught, is
1218                  ignored. If PreFun has been called for a table,  PostFun  is
1219                  guaranteed  to be called for that table, even if the evalua‐
1220                  tion of the query fails for some reason.
1221
1222                  The pre (post) functions for different tables are  evaluated
1223                  in unspecified order.
1224
1225                  Other table access than reading, such as calling InfoFun, is
1226                  assumed to be OK at any time.
1227
1228                * Binary callback function LookupFun is used  for  looking  up
1229                  objects in the table. The first argument Position is the key
1230                  position or an indexed position and the second argument Keys
1231                  is a sorted list of unique values. The return value is to be
1232                  a list of all objects (tuples), such  that  the  element  at
1233                  Position  is  a  member  of  Keys. Any other return value is
1234                  immediately returned  as  value  of  the  query  evaluation.
1235                  LookupFun  is  called instead of traversing the table if the
1236                  parse transform at compile time can determine that the  fil‐
1237                  ters match and compare the element at Position in such a way
1238                  that only Keys need to be looked up to  find  all  potential
1239                  answers.
1240
1241                  The  key position is obtained by calling InfoFun(keypos) and
1242                  the indexed positions by calling  InfoFun(indices).  If  the
1243                  key  position  can  be used for lookup, it is always chosen,
1244                  otherwise the indexed position requiring the least number of
1245                  lookups  is  chosen.  If  there is a tie between two indexed
1246                  positions, the one occurring first in the list  returned  by
1247                  InfoFun  is chosen. Positions requiring more than max_lookup
1248                  lookups are ignored.
1249
1250                * Unary callback function InfoFun  is  to  return  information
1251                  about the table. undefined is to be returned if the value of
1252                  some tag is unknown:
1253
1254                  indices:
1255                    Returns a list of indexed positions, a  list  of  positive
1256                    integers.
1257
1258                  is_unique_objects:
1259                    Returns  true  if  the objects returned by TraverseFun are
1260                    unique.
1261
1262                  keypos:
1263                    Returns the position of the table key, a positive integer.
1264
1265                  is_sorted_key:
1266                    Returns true if the objects returned  by  TraverseFun  are
1267                    sorted on the key.
1268
1269                  num_of_objects:
1270                    Returns the number of objects in the table, a non-negative
1271                    integer.
1272
1273                * Unary callback function FormatFun is used  by  info/1,2  for
1274                  displaying the call that created the query handle of the ta‐
1275                  ble. Defaults to undefined, which means that  info/1,2  dis‐
1276                  plays  a  call  to '$MOD':'$FUN'/0. It is up to FormatFun to
1277                  present the selected objects of the table in a suitable way.
1278                  However,  if a character list is chosen for presentation, it
1279                  must be an Erlang expression that can be scanned and  parsed
1280                  (a trailing dot is added by info/1,2 though).
1281
1282                  FormatFun  is  called  with  an  argument that describes the
1283                  selected objects based on optimizations done as a result  of
1284                  analyzing  the  filters of the QLC where the call to qlc:ta‐
1285                  ble/2 occurs. The argument can have the following values:
1286
1287                  {lookup, Position, Keys, NElements, DepthFun}.:
1288                    LookupFun is used for looking up objects in the table.
1289
1290                  {match_spec, MatchExpression}:
1291                    No way of finding all possible answers by looking up  keys
1292                    was  found,  but  the  filters could be transformed into a
1293                    match specification. All answers are found by calling Tra‐
1294                    verseFun(MatchExpression).
1295
1296                  {all, NElements, DepthFun}:
1297                    No  optimization was found. A match specification matching
1298                    all objects is used if TraverseFun is unary.
1299
1300                    NElements is the value of the info/1,2 option n_elements.
1301
1302                    DepthFun is a function that can be used for  limiting  the
1303                    size  of  terms;  calling DepthFun(Term) substitutes '...'
1304                    for parts  of  Term  below  the  depth  specified  by  the
1305                    info/1,2 option depth.
1306
1307                    If  calling FormatFun with an argument including NElements
1308                    and DepthFun fails, FormatFun is called once again with an
1309                    argument  excluding NElements and DepthFun ({lookup, Posi‐
1310                    tion, Keys} or all).
1311
1312                * The value of option key_equality is to be '=:=' if the table
1313                  considers  two  keys  equal if they match, and to be '==' if
1314                  two keys are equal if they compare equal. Defaults to '=:='.
1315
1316              For the various options recognized by  table/1,2  in  respective
1317              module, see ets(3), dets(3), and mnesia(3).
1318

SEE ALSO

1320       dets(3),  erl_eval(3),  erlang(3),  error_logger(3),  ets(3),  file(3),
1321       file_sorter(3), mnesia(3), shell(3),  Erlang  Reference  Manual,   Pro‐
1322       gramming Examples
1323
1324
1325
1326Ericsson AB                     stdlib 3.8.2.1                          qlc(3)
Impressum