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  ta‐
15       bles  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 re‐
28       turns a query handle. To obtain all the answers to a query, eval/1,2 is
29       to be called with the query handle as first argument. Query handles are
30       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  re‐
33       placement  is described in section  Compilation and Code Loading in the
34       Erlang Reference Manual. The list of answers can also be  traversed  in
35       chunks  by  use of a query cursor. Query cursors are created by calling
36       cursor/1,2 with a query handle as first argument. Query cursors are es‐
37       sentially Erlang processes. One answer at a time is sent from the query
38       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  ei‐
46       ther  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 ta‐
56           bles. As a result, qualifiers are modified during the  optimization
57           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 ef‐
63           fects, 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 ob‐
92           jects  of the other handle (a QLC table) such that the values at P1
93           and P2 match or compare equal. The qlc module does not  create  any
94           indexes  but looks up values using the key position and the indexed
95           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 op‐
105       erations. It is up to the user to order the joins by introducing  query
106       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 al‐
134           lowed, 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  ex‐
145           pression  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  un‐
168       wound.
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. Er‐
174       lang/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 re‐
189       turned 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 us‐
193       ing 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 ef‐
263       fects so that the meaning of the query does not change if QH2 is evalu‐
264       ated only once. One way of caching the answers is to evaluate QH2 first
265       of all and substitute the list of answers for QH2 in the query. Another
266       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  ob‐
363       ject  returned, a new fun is created. As long as the list is not termi‐
364       nated by [], it is assumed that the tail of the list is a nullary func‐
365       tion  and  that calling the function returns further objects (and func‐
366       tions).
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  re‐
371       turns the objects as {Key, Value} pairs, the position is 1. Notice that
372       the lookup function is to return {Key, Value} pairs, as  the  traversal
373       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 ex‐
378       ample, 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 de‐
384       pends 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(
417              lists:flatmap(fun(V) ->
418                          ets:lookup(#Ref<0.3098908599.2283929601.256025>,
419                                  V)
420                      end,
421                      [a, 2.71]),
422              ets:match_spec_compile([{{'$1'}, [], ['$1']}]))
423
424       In the example, operator ==/2 has been handled exactly as  =:=/2  would
425       have  been handled. However, if it cannot be determined at compile time
426       that some constant is free of integers, and the table uses  =:=/2  when
427       comparing  keys  for  equality  (see option key_equality), then the qlc
428       module does not try to look up the constant. The reason is  that  there
429       is  in the general case no upper limit on the number of key values that
430       can compare equal to such a constant; every combination of integers and
431       floats must be looked up:
432
433       2> E2 = ets:new(t, [set]),
434       true = ets:insert(E2, [{{2,2},a},{{2,2.0},b},{{2.0,2},c}]),
435       F2 = fun(I) ->
436       qlc:q([V || {K,V} <- ets:table(E2), K == I])
437       end,
438       Q2 = F2({2,2}),
439       io:format("~s~n", [qlc:info(Q2)]).
440       ets:table(#Ref<0.3098908599.2283929601.256125>,
441                 [{traverse,
442                   {select,
443                    [{{'$1', '$2'}, [{'==', '$1', {const, {2, 2}}}], ['$2']}]}}])
444       3> lists:sort(qlc:e(Q2)).
445       [a,b,c]
446
447       Looking up only {2,2} would not return b and c.
448
449       If the table uses ==/2 when comparing keys for equality, the qlc module
450       looks up the constant regardless of which operator is used in the  QLC.
451       However, ==/2 is to be preferred:
452
453       4> E3 = ets:new(t, [ordered_set]), % uses ==/2 for key equality
454       true = ets:insert(E3, [{{2,2.0},b}]),
455       F3 = fun(I) ->
456       qlc:q([V || {K,V} <- ets:table(E3), K == I])
457       end,
458       Q3 = F3({2,2}),
459       io:format("~s~n", [qlc:info(Q3)]).
460       ets:match_spec_run(ets:lookup(#Ref<0.3098908599.2283929601.256211>,
461                                     {2, 2}),
462                          ets:match_spec_compile([{{'$1', '$2'}, [], ['$2']}]))
463       5> qlc:e(Q3).
464       [b]
465
466       Lookup  join  is handled analogously to lookup of constants in a table:
467       if the join operator is ==/2, and the table where constants are  to  be
468       looked  up uses =:=/2 when testing keys for equality, then the qlc mod‐
469       ule does not consider lookup join for that table.
470

DATA TYPES

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

EXPORTS

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

SEE ALSO

1333       dets(3),  erl_eval(3),  erlang(3),  error_logger(3),  ets(3),  file(3),
1334       file_sorter(3), mnesia(3), shell(3),  Erlang  Reference  Manual,   Pro‐
1335       gramming Examples
1336
1337
1338
1339Ericsson AB                      stdlib 3.17.2                          qlc(3)
Impressum