~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/qlc.xml

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
<?xml version="1.0" encoding="latin1" ?>
 
2
<!DOCTYPE erlref SYSTEM "erlref.dtd">
 
3
 
 
4
<erlref>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>2004</year>
 
8
      <year>2007</year>
 
9
      <holder>Ericsson AB, All Rights Reserved</holder>
 
10
    </copyright>
 
11
    <legalnotice>
 
12
  The contents of this file are subject to the Erlang Public License,
 
13
  Version 1.1, (the "License"); you may not use this file except in
 
14
  compliance with the License. You should have received a copy of the
 
15
  Erlang Public License along with this software. If not, it can be
 
16
  retrieved online at http://www.erlang.org/.
 
17
 
 
18
  Software distributed under the License is distributed on an "AS IS"
 
19
  basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
20
  the License for the specific language governing rights and limitations
 
21
  under the License.
 
22
 
 
23
  The Initial Developer of the Original Code is Ericsson AB.
 
24
    </legalnotice>
 
25
 
 
26
    <title>qlc</title>
 
27
    <prepared>Hans Bolinder</prepared>
 
28
    <responsible>nobody</responsible>
 
29
    <docno></docno>
 
30
    <approved>nobody</approved>
 
31
    <checked>no</checked>
 
32
    <date>2004-08-25</date>
 
33
    <rev>PA1</rev>
 
34
    <file>qlc.sgml</file>
 
35
  </header>
 
36
  <module>qlc</module>
 
37
  <modulesummary>Query Interface to Mnesia, ETS, Dets, etc</modulesummary>
 
38
  <description>
 
39
    <p>The <c>qlc</c> module provides a query interface to Mnesia, ETS,
 
40
      Dets and other data structures that implement an iterator style
 
41
      traversal of objects. </p>
 
42
  </description>
 
43
 
 
44
  <section><title>Overview</title>
 
45
 
 
46
    <p>The <c>qlc</c> module implements a query interface to <em>QLC
 
47
      tables</em>. Typical QLC tables are ETS, Dets, and Mnesia
 
48
      tables. There is also support for user defined tables, see the
 
49
      <seealso marker="#implementing_a_qlc_table">Implementing a QLC
 
50
      table</seealso> section. A <em>query</em> is stated using
 
51
      <em>Query List Comprehensions</em> (QLCs). The answers to a
 
52
      query are determined by data in QLC tables that fulfill the
 
53
      constraints expressed by the QLCs of the query. QLCs are similar
 
54
      to ordinary list comprehensions as described in the Erlang
 
55
      Reference Manual and Programming Examples except that variables
 
56
      introduced in patterns cannot be used in list expressions. In
 
57
      fact, in the absence of optimizations and options such as
 
58
      <c>cache</c> and <c>unique</c> (see below), every QLC free of
 
59
      QLC tables evaluates to the same list of answers as the
 
60
      identical ordinary list comprehension. </p>
 
61
 
 
62
    <p>While ordinary list comprehensions evaluate to lists, calling
 
63
      <seealso marker="#q">qlc:q/1,2</seealso> returns a <em>Query
 
64
      Handle</em>. To obtain all the answers to a query, <seealso
 
65
      marker="#eval">qlc:eval/1,2</seealso> should be called with the
 
66
      query handle as first argument. Query handles are essentially
 
67
      functional objects ("funs") created in the module calling <c>q/1,2</c>.
 
68
      As the funs refer to the module's code, one should
 
69
      be careful not to keep query handles too long if the module's
 
70
      code is to be replaced.
 
71
      Code replacement is described in the <seealso
 
72
      marker="doc/reference_manual:code_loading">Erlang Reference
 
73
      Manual</seealso>. The list of answers can also be traversed in
 
74
      chunks by use of a <em>Query Cursor</em>. Query cursors are
 
75
      created by calling <seealso
 
76
      marker="#cursor">qlc:cursor/1,2</seealso> with a query handle as
 
77
      first argument. Query cursors are essentially Erlang processes.
 
78
      One answer at a time is sent from the query cursor process to
 
79
      the process that created the cursor.</p>
 
80
 
 
81
  </section>
 
82
 
 
83
  <section><title>Syntax</title>
 
84
 
 
85
    <p>Syntactically QLCs have the same parts as ordinary list
 
86
      comprehensions:</p>
 
87
 
 
88
    <code type="none">[Expression || Qualifier1, Qualifier2, ...]</code>
 
89
 
 
90
    <p><c>Expression</c> (the <em>template</em>) is an arbitrary
 
91
      Erlang expression. Qualifiers are either <em>filters</em> or
 
92
      <em>generators</em>. Filters are Erlang expressions returning
 
93
      <c>bool()</c>. Generators have the form
 
94
      <c><![CDATA[Pattern <- ListExpression]]></c>, where
 
95
      <c>ListExpression</c> is an expression evaluating to a query
 
96
      handle or a list. Query handles are returned from
 
97
      <c>qlc:table/2</c>, <c>qlc:append/1,2</c>, <c>qlc:sort/1,2</c>,
 
98
      <c>qlc:keysort/2,3</c>, <c>qlc:q/1,2</c>, and
 
99
      <c>qlc:string_to_handle/1,2,3</c>.</p>
 
100
 
 
101
  </section>
 
102
 
 
103
  <section><title>Evaluation</title>
 
104
 
 
105
    <p>The evaluation of a query handle begins by the inspection of
 
106
      options and the collection of information about tables. As a
 
107
      result qualifiers are modified during the optimization phase.
 
108
      Next all list expressions are evaluated. If a cursor has been
 
109
      created evaluation takes place in the cursor process. For those
 
110
      list expressions that are QLCs, the list expressions of the
 
111
      QLCs' generators are evaluated as well. One has to be careful if
 
112
      list expressions have side effects since the order in which list
 
113
      expressions are evaluated is unspecified. Finally the answers
 
114
      are found by evaluating the qualifiers from left to right,
 
115
      backtracking when some filter returns <c>false</c>, or
 
116
      collecting the template when all filters return <c>true</c>.</p>
 
117
 
 
118
    <p>Filters that do not return <c>bool()</c> but fail are handled
 
119
      differently depending on their syntax: if the filter is a guard
 
120
      it returns <c>false</c>, otherwise the query evaluation fails.
 
121
      This behavior makes it possible for the <c>qlc</c> module  
 
122
      to do some optimizations
 
123
      without affecting the meaning of a query. For example, when some
 
124
      position of a table is compared to one or more constants, only
 
125
      the objects with matching values are candidates for further
 
126
      evaluation. The other objects are guaranteed to make the filter
 
127
      return <c>false</c>, but never fail. The (small) set of
 
128
      candidate objects can often be found by looking up some key
 
129
      values of the table or by traversing the table using a match
 
130
      specification. It is necessary to place the guard filters
 
131
      immediately after the table's generator, otherwise the candidate
 
132
      objects will not be restricted to a small set. The reason is
 
133
      that objects that could make the query evaluation fail must not
 
134
      be excluded by looking up a key or running a match
 
135
      specification.</p>
 
136
 
 
137
  </section>
 
138
 
 
139
  <section><title>Join</title>
 
140
 
 
141
    <p>The <c>qlc</c> module supports fast join of two query handles. 
 
142
      Fast join is
 
143
      possible if some position (<c>P1</c>) of one query handler is
 
144
      compared to or matched against some position (<c>P2</c>) of
 
145
      another query handle. Two fast join methods have been
 
146
      implemented:</p>
 
147
 
 
148
    <list type="bulleted">
 
149
      <item>Lookup join traverses all objects of one query handle and
 
150
         finds objects of the other handle (a QLC table) such that the
 
151
         values at <c>P1</c> and <c>P2</c> match. The <c>qlc</c> module 
 
152
         does not create
 
153
         any indices but looks up values using the key position and
 
154
         the indexed positions of the QLC table.
 
155
      </item>
 
156
      <item>Merge join sorts the objects of each query handle if
 
157
         necessary and filters out objects where the values at
 
158
         <c>P1</c> and <c>P2</c> do not compare equal. If there are
 
159
         many objects with the same value of <c>P2</c> a temporary
 
160
         file will be used for the equivalence classes.
 
161
      </item>
 
162
    </list>
 
163
 
 
164
    <p>The <c>qlc</c> module warns at compile time if a QLC
 
165
      combines query handles in such a way that more than one join is
 
166
      possible. In other words, there is no query planner that can
 
167
      choose a good order between possible join operations. It is up
 
168
      to the user to order the joins by introducing query handles.</p>
 
169
 
 
170
    <p>The join is to be expressed as a guard filter. The filter must
 
171
      be placed immediately after the two joined generators, possibly
 
172
      after guard filters that use variables from no other generators
 
173
      but the two joined generators. The <c>qlc</c> module inspects 
 
174
      the operands of
 
175
      <c>=:=/2</c>, <c>==/2</c>, <c>is_record/2</c>, <c>element/2</c>,
 
176
      and logical operators (<c>and/2</c>, <c>or/2</c>,
 
177
      <c>andalso/2</c>, <c>orelse/2</c>, <c>xor/2</c>) when
 
178
      determining which joins to consider.</p>
 
179
 
 
180
  </section>
 
181
 
 
182
  <section><title>Common options</title>
 
183
 
 
184
    <p>The following options are accepted by <c>cursor/2</c>,
 
185
      <c>eval/2</c>, <c>fold/4</c>, and <c>info/2</c>:</p>
 
186
 
 
187
    <list type="bulleted">
 
188
      <item><c>{cache_all, Cache}</c> where <c>Cache</c> is
 
189
        equal to <c>ets</c> or <c>list</c> adds a
 
190
        <c>{cache,&nbsp;Cache}</c> option to every list expression
 
191
        of the query except tables and lists. Default is
 
192
        <c>{cache_all,&nbsp;no}</c>. The option <c>cache_all</c> is
 
193
        equivalent to <c>{cache_all,&nbsp;ets}</c>.
 
194
      </item>
 
195
      <item><c>{max_list_size, MaxListSize}</c> <marker
 
196
        id="max_list_size"></marker> where <c>MaxListSize</c> is the
 
197
        size in bytes of terms on the external format. If the
 
198
        accumulated size of collected objects exceeds
 
199
        <c>MaxListSize</c> the objects are written onto a temporary
 
200
        file. This option is used by the <c>{cache,&nbsp;list}</c>
 
201
        option as well as by the merge join method. Default is
 
202
        512*1024 bytes.
 
203
      </item>
 
204
      <item><c>{tmpdir_usage, TmpFileUsage}</c> determines the
 
205
        action taken when <c>qlc</c> is about to create temporary
 
206
        files on the directory set by the <c>tmpdir</c> option. If the
 
207
        value is <c>not_allowed</c> an error tuple is returned,
 
208
        otherwise temporary files are created as needed. Default is
 
209
        <c>allowed</c> which means that no further action is taken.
 
210
        The values <c>info_msg</c>, <c>warning_msg</c>, and
 
211
        <c>error_msg</c> mean that the function with the corresponding
 
212
        name in the module <c>error_logger</c> is called for printing
 
213
        some information (currently the stacktrace).
 
214
      </item>
 
215
      <item><c>{tmpdir, TempDirectory}</c> sets the directory used by
 
216
        merge join for temporary files and by the
 
217
        <c>{cache,&nbsp;list}</c> option. The option also overrides
 
218
        the <c>tmpdir</c> option of <c>keysort/3</c> and
 
219
        <c>sort/2</c>. The default value is <c>""</c> which means that
 
220
        the directory returned by <c>file:get_cwd()</c> is used.
 
221
      </item>
 
222
      <item><c>{unique_all, true}</c> adds a
 
223
        <c>{unique,&nbsp;true}</c> option to every list expression of
 
224
        the query. Default is <c>{unique_all,&nbsp;false}</c>. The
 
225
        option <c>unique_all</c> is equivalent to
 
226
        <c>{unique_all,&nbsp;true}</c>.
 
227
      </item>
 
228
    </list>
 
229
 
 
230
  </section>
 
231
 
 
232
  <section><title>Common data types</title>
 
233
 
 
234
    <list type="bulleted">
 
235
      <item><p><c>QueryCursor = {qlc_cursor, term()}</c></p>
 
236
      </item>
 
237
      <item><p><c>QueryHandle = {qlc_handle, term()}</c></p>
 
238
      </item>
 
239
      <item><p><c>QueryHandleOrList = QueryHandle | list()</c></p>
 
240
      </item>
 
241
      <item><p><c>Answers = [Answer]</c></p>
 
242
      </item>
 
243
      <item><p><c>Answer = term()</c></p>
 
244
      </item>
 
245
      <item><p><c>AbstractExpression =&nbsp;</c> -&nbsp;parse trees
 
246
          for Erlang expressions, see the <seealso
 
247
          marker="erts:absform">abstract format</seealso>
 
248
          documentation in the ERTS User's Guide&nbsp;-</p>
 
249
      </item>
 
250
      <item><p><c>MatchExpression =&nbsp;</c>
 
251
          -&nbsp;match&nbsp;specifications, see the <seealso
 
252
          marker="erts:match_spec">match specification</seealso>
 
253
          documentation in the ERTS User's Guide and <seealso
 
254
          marker="ms_transform">ms_transform(3)</seealso>&nbsp;-</p>
 
255
      </item>
 
256
      <item><p><c>SpawnOptions = default | spawn_options()</c></p>
 
257
      </item>
 
258
      <item><p><c>SortOptions = [SortOption] | SortOption</c></p>
 
259
      </item>
 
260
      <item><p><c>SortOption = {compressed, bool()}
 
261
            | {no_files, NoFiles} 
 
262
            | {order, Order} 
 
263
            | {size, Size} 
 
264
            | {tmpdir, TempDirectory} 
 
265
            | {unique, bool()}&nbsp;</c>
 
266
            -&nbsp;see <seealso
 
267
            marker="file_sorter">file_sorter(3)</seealso>&nbsp;-</p>
 
268
      </item>
 
269
      <item><p><c>Order = ascending | descending | OrderFun</c></p>
 
270
      </item>
 
271
      <item><p><c>OrderFun = fun(term(), term()) -> bool()</c></p>
 
272
      </item>
 
273
      <item><p><c>TempDirectory = "" | filename()</c></p>
 
274
      </item>
 
275
      <item><p><c>Size = int() > 0</c></p>
 
276
      </item>
 
277
      <item><p><c>NoFiles = int() > 1</c></p>
 
278
      </item>
 
279
      <item><p><c>KeyPos = int() > 0 | [int() > 0]</c></p>
 
280
      </item>
 
281
      <item><p><c>MaxListSize = int() >= 0</c></p>
 
282
      </item>
 
283
      <item><p><c>bool() = true | false</c></p>
 
284
      </item>
 
285
      <item><p><c>Cache = ets | list | no</c></p>
 
286
      </item>
 
287
      <item><p><c>TmpFileUsage = allowed | not_allowed | info_msg 
 
288
            | warning_msg | error_msg</c></p>
 
289
      </item>
 
290
      <item><p><c>filename() =&nbsp;</c> -&nbsp;see <seealso
 
291
            marker="filename">filename(3)</seealso>&nbsp;-</p>
 
292
      </item>
 
293
      <item><p><c>spawn_options() =&nbsp;</c> -&nbsp;see <seealso
 
294
          marker="kernel:erlang">erlang(3)</seealso>&nbsp;-</p>
 
295
      </item>
 
296
 
 
297
    </list>
 
298
 
 
299
  </section>
 
300
 
 
301
  <section><title>Getting started</title>
 
302
 
 
303
    <p><marker id="getting_started"></marker> As already mentioned
 
304
      queries are stated in the list comprehension syntax as described
 
305
      in the <seealso marker="doc/reference_manual:expressions">Erlang
 
306
      Reference Manual</seealso>. In the following some familiarity
 
307
      with list comprehensions is assumed. There are examples in
 
308
      <seealso
 
309
      marker="doc/programming_examples:list_comprehensions">Programming
 
310
      Examples</seealso> that can get you started. It should be
 
311
      stressed that list comprehensions do not add any computational
 
312
      power to the language; anything that can be done with list
 
313
      comprehensions can also be done without them. But they add a
 
314
      syntax for expressing simple search problems which is compact
 
315
      and clear once you get used to it.</p>
 
316
 
 
317
    <p>Many list comprehension expressions can be evaluated by the
 
318
      <c>qlc</c> module. Exceptions are expressions such that
 
319
      variables introduced in patterns (or filters) are used in some
 
320
      generator later in the list comprehension. As an example
 
321
      consider an implementation of lists:append(L): 
 
322
      <c><![CDATA[[X ||Y <- L, X <- Y]]]></c>. 
 
323
      Y is introduced in the first generator and used in the second.
 
324
      The ordinary list comprehension is normally to be preferred when
 
325
      there is a choice as to which to use. One difference is that
 
326
      <c>qlc:eval/1,2</c> collects answers in a list which is finally
 
327
      reversed, while list comprehensions collect answers on the stack
 
328
      which is finally unwound.</p>
 
329
 
 
330
    <p>What the <c>qlc</c> module primarily adds to list
 
331
      comprehensions is that data can be read from QLC tables in small
 
332
      chunks. A QLC table is created by calling <c>qlc:table/2</c>.
 
333
      Usually <c>qlc:table/2</c> is not called directly from the query
 
334
      but via an interface function of some data structure. There are
 
335
      a few examples of such functions in Erlang/OTP:
 
336
      <c>mnesia:table/1,2</c>, <c>ets:table/1,2</c>, and
 
337
      <c>dets:table/1,2</c>. For a given data structure there can be
 
338
      several functions that create QLC tables, but common for all
 
339
      these functions is that they return a query handle created by
 
340
      <c>qlc:table/2</c>. Using the QLC tables provided by OTP is
 
341
      probably sufficient in most cases, but for the more advanced
 
342
      user the section <seealso
 
343
      marker="#implementing_a_qlc_table">Implementing a QLC
 
344
      table</seealso> describes the implementation of a function
 
345
      calling <c>qlc:table/2</c>.</p>
 
346
 
 
347
    <p>Besides <c>qlc:table/2</c> there are other functions that
 
348
      return query handles. They might not be used as often as tables,
 
349
      but are useful from time to time. <c>qlc:append</c> traverses
 
350
      objects from several tables or lists after each other. If, for
 
351
      instance, you want to traverse all answers to a query QH and
 
352
      then finish off by a term <c>{finished}</c>, you can do that by
 
353
      calling <c>qlc:append(QH, [{finished}])</c>. <c>append</c> first
 
354
      returns all objects of QH, then <c>{finished}</c>. If there is
 
355
      one tuple <c>{finished}</c> among the answers to QH it will be
 
356
      returned twice from <c>append</c>.</p>
 
357
 
 
358
    <p>As another example, consider concatenating the answers to two
 
359
      queries QH1 and QH2 while removing all duplicates. The means to
 
360
      accomplish this is to use the <c>unique</c> option:</p> 
 
361
 
 
362
    <code type="none"><![CDATA[
 
363
qlc:q([X || X <- qlc:append(QH1, QH2)], {unique, true})]]></code>
 
364
 
 
365
    <p>The cost is substantial: every returned answer will be stored
 
366
      in an ETS table. Before returning an answer it is looked up in
 
367
      the ETS table to check if it has already been returned. Without
 
368
      the <c>unique</c> options all answers to QH1 would be returned
 
369
      followed by all answers to QH2. The <c>unique</c> options keeps
 
370
      the order between the remaining answers.</p>
 
371
 
 
372
    <p>If the order of the answers is not important there is the
 
373
      alternative to sort the answers uniquely:</p>
 
374
 
 
375
    <code type="none"><![CDATA[
 
376
qlc:sort(qlc:q([X || X <- qlc:append(QH1, QH2)], {unique, true})).]]></code>
 
377
 
 
378
    <p>This query also removes duplicates but the answers will be
 
379
      sorted. If there are many answers temporary files will be used.
 
380
      Note that in order to get the first unique answer all answers
 
381
      have to be found and sorted.</p>
 
382
 
 
383
    <p>To return just a few answers cursors can be used. The following
 
384
      code returns no more than five answers using an ETS table for
 
385
      storing the unique answers:</p>
 
386
 
 
387
    <code type="none"><![CDATA[
 
388
C = qlc:cursor(qlc:q([X || X <- qlc:append(QH1, QH2)],{unique,true})),
 
389
R = qlc:next_answers(C, 5),
 
390
ok = qlc:delete_cursor(C),
 
391
R.]]></code>
 
392
 
 
393
    <p>Query list comprehensions are convenient for stating
 
394
      constraints on data from two or more tables. An example that
 
395
      does a natural join on two query handles on position 2:</p>
 
396
 
 
397
    <code type="none"><![CDATA[
 
398
qlc:q([{X1,X2,X3,Y1} || 
 
399
          {X1,X2,X3} <- QH1, 
 
400
          {Y1,Y2} <- QH2, 
 
401
          X2 =:= Y2])]]></code>
 
402
 
 
403
    <p>The <c>qlc</c> module will evaluate this differently depending on 
 
404
      the query
 
405
      handles <c>QH1</c> and <c>QH2</c>. If, for example, <c>X2</c> is
 
406
      matched against the key of a QLC table the lookup join method
 
407
      will traverse the objects of <c>QH2</c> while looking up key
 
408
      values in the table. On the other hand, if neither <c>X2</c> nor
 
409
      <c>Y2</c> is matched against the key or an indexed position of a
 
410
      QLC table, the merge join method will make sure that <c>QH1</c>
 
411
      and <c>QH2</c> are both sorted on position 2 and next do the
 
412
      join by traversing the objects one by one.</p>
 
413
 
 
414
    <p>The <c>join</c> option can be used to force the <c>qlc</c> module 
 
415
      to use a
 
416
      certain join method. For the rest of this section it is assumed
 
417
      that the excessively slow join method called "nested loop" has
 
418
      been chosen:</p>
 
419
 
 
420
    <code type="none"><![CDATA[
 
421
qlc:q([{X1,X2,X3,Y1} || 
 
422
          {X1,X2,X3} <- QH1, 
 
423
          {Y1,Y2} <- QH2, 
 
424
          X2 =:= Y2],
 
425
      {join, nested_loop})]]></code>
 
426
 
 
427
    <p>In this case the filter will be applied to every possible pair
 
428
      of answers to QH1 and QH2, one at a time. If there are M answers
 
429
      to QH1 and N answers to QH2 the filter will be run M*N
 
430
      times.</p>
 
431
 
 
432
    <p>If QH2 is a call to the function for <c>gb_trees</c> as defined
 
433
      in the <seealso marker="#implementing_a_qlc_table">Implementing
 
434
      a QLC table</seealso> section, <c>gb_table:table/1</c>, the
 
435
      iterator for the gb-tree will be initiated for each answer to
 
436
      QH1 after which the objects of the gb-tree will be returned one
 
437
      by one. This is probably the most efficient way of traversing
 
438
      the table in that case since it takes minimal computational
 
439
      power to get the following object. But if QH2 is not a table but
 
440
      a more complicated QLC, it can be more efficient use some RAM
 
441
      memory for collecting the answers in a cache, particularly if
 
442
      there are only a few answers. It must then be assumed that
 
443
      evaluating QH2 has no side effects so that the meaning of the
 
444
      query does not change if QH2 is evaluated only once. One way of
 
445
      caching the answers is to evaluate QH2 first of all and
 
446
      substitute the list of answers for QH2 in the query. Another way
 
447
      is to use the <c>cache</c> option. It is stated like this:</p>
 
448
 
 
449
    <code type="none"><![CDATA[
 
450
QH2' = qlc:q([X || X <- QH2], {cache, ets})]]></code>
 
451
 
 
452
    <p>or just</p> 
 
453
 
 
454
    <code type="none"><![CDATA[
 
455
QH2' = qlc:q([X || X <- QH2], cache)]]></code>
 
456
 
 
457
    <p>The effect of the <c>cache</c> option is that when the
 
458
      generator QH2' is run the first time every answer is stored in
 
459
      an ETS table. When next answer of QH1 is tried, answers to QH2'
 
460
      are copied from the ETS table which is very fast. As for the
 
461
      <c>unique</c> option the cost is a possibly substantial amount
 
462
      of RAM memory. The <c>{cache,&nbsp;list}</c> option offers the
 
463
      possibility to store the answers in a list on the process heap.
 
464
      While this has the potential of being faster than ETS tables
 
465
      since there is no need to copy answers from the table it can
 
466
      often result in slower evaluation due to more garbage
 
467
      collections of the process' heap as well as increased RAM memory
 
468
      consumption due to larger heaps. Another drawback with cache
 
469
      lists is that if the size of the list exceeds a limit a
 
470
      temporary file will be used. Reading the answers from a file is
 
471
      very much slower than copying them from an ETS table. But if the
 
472
      available RAM memory is scarce setting the <seealso
 
473
      marker="#max_list_size">limit</seealso> to some low value is an
 
474
      alternative.</p>
 
475
 
 
476
    <p>There is an option <c>cache_all</c> that can be set to
 
477
      <c>ets</c> or <c>list</c> when evaluating a query. It adds a
 
478
      <c>cache</c> or <c>{cache,&nbsp;list}</c> option to every list
 
479
      expression except QLC tables and lists on all levels of the
 
480
      query. This can be used for testing if caching would improve
 
481
      efficiency at all. If the answer is yes further testing is
 
482
      needed to pinpoint the generators that should be cached.</p>
 
483
 
 
484
  </section>
 
485
 
 
486
  <section><title>Implementing a QLC table</title>
 
487
 
 
488
    <p><marker id="implementing_a_qlc_table"></marker>As an example of
 
489
      how to use the <seealso marker="#q">qlc:table/2</seealso>
 
490
      function the implementation of a QLC table for the <seealso
 
491
      marker="gb_trees">gb_trees</seealso> module is given:</p>
 
492
 
 
493
    <code type="none"><![CDATA[
 
494
-module(gb_table).
 
495
 
 
496
-export([table/1]).
 
497
 
 
498
table(T) ->
 
499
    TF = fun() -> qlc_next(gb_trees:next(gb_trees:iterator(T))) end,
 
500
    InfoFun = fun(num_of_objects) -> gb_trees:size(T);
 
501
                 (keypos) -> 1;
 
502
                 (_) -> undefined
 
503
              end,
 
504
    LookupFun =
 
505
        fun(1, Ks) ->
 
506
                lists:flatmap(fun(K) ->
 
507
                                      case gb_trees:lookup(K, T) of
 
508
                                          {value, V} -> [{K,V}];
 
509
                                          none -> []
 
510
                                      end
 
511
                              end, Ks)
 
512
        end,
 
513
    FormatFun =
 
514
        fun({all, NElements, ElementFun}) ->
 
515
                Vals = gb_nodes(T, NElements, ElementFun),
 
516
                {gb_trees, from_orddict, [Vals]};
 
517
           ({lookup, 1, KeyValues, _NElements, ElementFun}) ->
 
518
                ValsS = io_lib:format("gb_trees:from_orddict(~w)",
 
519
                                      [gb_nodes(T, infinity, ElementFun)]),
 
520
                io_lib:format("lists:flatmap(fun(K) -> "
 
521
                              "case gb_trees:lookup(K, ~s) of "
 
522
                              "{value, V} -> [{K,V}];none -> [] end "
 
523
                              "end, ~w)",
 
524
                              [ValsS, [ElementFun(KV) || KV <- KeyValues]])
 
525
        end,
 
526
    qlc:table(TF, [{info_fun, InfoFun}, {format_fun, FormatFun},
 
527
                   {lookup_fun, LookupFun}]).
 
528
 
 
529
qlc_next({X, V, S}) ->
 
530
    [{X,V} | fun() -> qlc_next(gb_trees:next(S)) end];
 
531
qlc_next(none) ->
 
532
    [].
 
533
 
 
534
gb_nodes(T, infinity, ElementFun) ->
 
535
    gb_nodes(T, -1, ElementFun);
 
536
gb_nodes(T, NElements, ElementFun) ->
 
537
    gb_iter(gb_trees:iterator(T), NElements, ElementFun).
 
538
 
 
539
gb_iter(_I, 0, _EFun) ->
 
540
    '...';
 
541
gb_iter(I0, N, EFun) ->
 
542
    case gb_trees:next(I0) of
 
543
        {X, V, I} ->
 
544
            [EFun({X,V}) | gb_iter(I, N-1, EFun)];
 
545
        none ->
 
546
            []
 
547
    end.]]></code>
 
548
 
 
549
    <p><c>TF</c> is the traversal function. The <c>qlc</c> module
 
550
      requires that there is a way of traversing all objects of the
 
551
      data structure; in <c>gb_trees</c> there is an iterator function
 
552
      suitable for that purpose. Note that for each object returned a
 
553
      new fun is created. As long as the list is not terminated by
 
554
      <c>[]</c> it is assumed that the tail of the list is a nullary
 
555
      function and that calling the function returns further objects
 
556
      (and functions).</p>
 
557
 
 
558
    <p>The lookup function is optional. It is assumed that the lookup
 
559
      function always finds values much faster than it would take to
 
560
      traverse the table. The first argument is the position of the
 
561
      key. Since <c>qlc_next</c> returns the objects as
 
562
      {Key,&nbsp;Value} pairs the position is 1. Note that the lookup
 
563
      function should return {Key,&nbsp;Value} pairs, just as the
 
564
      traversal function does.</p>
 
565
 
 
566
    <p>The format function is also optional. It is called by
 
567
      <c>qlc:info</c> to give feedback at runtime of how the query
 
568
      will be evaluated. One should try to give as good feedback as
 
569
      possible without showing too much details. In the example at
 
570
      most 7 objects of the table are shown. The format function
 
571
      handles two cases: <c>all</c> means that all objects of the
 
572
      table will be traversed; <c>{lookup,&nbsp;1,&nbsp;KeyValues}</c>
 
573
      means that the lookup function will be used for looking up key
 
574
      values.</p>
 
575
 
 
576
    <p>Whether the whole table will be traversed or just some keys
 
577
      looked up depends on how the query is stated. If the query has
 
578
      the form</p>
 
579
 
 
580
    <code type="none"><![CDATA[
 
581
qlc:q([T || P <- LE, F])]]></code>
 
582
 
 
583
    <p>and P is a tuple, the <c>qlc</c> module analyzes P and F in
 
584
      compile time to find positions of the tuple P that are matched
 
585
      or compared to constants. If such a position at runtime turns
 
586
      out to be the key position, the lookup function can be used,
 
587
      otherwise all objects of the table have to be traversed. It is
 
588
      the info function <c>InfoFun</c> that returns the key position.
 
589
      There can be indexed positions as well, also returned by the
 
590
      info function. An index is an extra table that makes lookup on
 
591
      some position fast. Mnesia maintains indices upon request,
 
592
      thereby introducing so called secondary keys. The <c>qlc</c>
 
593
      module prefers to look up objects using the key before secondary
 
594
      keys regardless of the number of constants to look up.</p>
 
595
 
 
596
  </section>
 
597
 
 
598
  <funcs>
 
599
 
 
600
    <func>
 
601
      <name>append(QHL) -> QH</name>
 
602
      <fsummary>Return a query handle.</fsummary>
 
603
      <type>
 
604
        <v>QHL = [QueryHandleOrList]</v>
 
605
        <v>QH = QueryHandle</v>
 
606
      </type>
 
607
      <desc>
 
608
        <p>Returns a query handle. When evaluating the query handle
 
609
          <c>QH</c> all answers to the first query handle in
 
610
          <c>QHL</c> is returned followed by all answers to the rest
 
611
          of the query handles in <c>QHL</c>.</p>
 
612
      </desc>
 
613
    </func>
 
614
 
 
615
    <func>
 
616
      <name>append(QH1, QH2) -> QH3</name>
 
617
      <fsummary>Return a query handle.</fsummary>
 
618
      <type>
 
619
        <v>QH1 = QH2 = QueryHandleOrList</v>
 
620
        <v>QH3 = QueryHandle</v>
 
621
      </type>
 
622
      <desc>
 
623
        <p>Returns a query handle. When evaluating the query handle
 
624
          <c>QH3</c> all answers to <c>QH1</c> are returned followed
 
625
          by all answers to <c>QH2</c>.</p>
 
626
 
 
627
        <p><c>append(QH1,&nbsp;QH2)</c> is equivalent to
 
628
          <c>append([QH1,&nbsp;QH2])</c>.</p>
 
629
      </desc>
 
630
    </func>
 
631
 
 
632
    <func>
 
633
      <name>cursor(QueryHandleOrList [, Options]) -> QueryCursor</name>
 
634
      <fsummary>Create a query cursor.</fsummary>
 
635
      <type>
 
636
        <v>Options = [Option] | Option</v>
 
637
        <v>Option = {cache_all, Cache} | cache_all
 
638
                  | {max_list_size, MaxListSize}
 
639
                  | {spawn_options, SpawnOptions}
 
640
                  | {tmpdir_usage, TmpFileUsage}
 
641
                  | {tmpdir, TempDirectory}
 
642
                  | {unique_all, bool()} | unique_all</v>
 
643
      </type>
 
644
      <desc>
 
645
        <p><marker id="cursor"></marker>Creates a query cursor and
 
646
          makes the calling process the owner of the cursor. The
 
647
          cursor is to be used as argument to <c>next_answers/1,2</c>
 
648
          and (eventually) <c>delete_cursor/1</c>. Calls
 
649
          <c>erlang:spawn_opt</c> to spawn and link a process which
 
650
          will evaluate the query handle. The value of the option
 
651
          <c>spawn_options</c> is used as last argument when calling
 
652
          <c>spawn_opt</c>. The default value is <c>[link]</c>.</p>
 
653
 
 
654
        <pre>
 
655
1> <input>QH = qlc:q([{X,Y} || X &lt;- [a,b], Y &lt;- [1,2]]),</input>
 
656
<input>QC = qlc:cursor(QH),</input>
 
657
<input>qlc:next_answers(QC, 1).</input>
 
658
[{a,1}]
 
659
2> <input>qlc:next_answers(QC, 1).</input>
 
660
[{a,2}]
 
661
3> <input>qlc:next_answers(QC, all_remaining).</input>
 
662
[{b,1},{b,2}]
 
663
4> <input>qlc:delete_cursor(QC).</input>
 
664
ok</pre>
 
665
      </desc>
 
666
    </func>
 
667
 
 
668
    <func>
 
669
      <name>delete_cursor(QueryCursor) -> ok</name>
 
670
      <fsummary>Delete a query cursor.</fsummary>
 
671
      <desc>
 
672
        <p>Deletes a query cursor. Only the owner of the cursor can
 
673
          delete the cursor.</p>
 
674
      </desc>
 
675
    </func>
 
676
 
 
677
    <func>
 
678
      <name>eval(QueryHandleOrList [, Options]) -> Answers | Error</name>
 
679
      <name>e(QueryHandleOrList [, Options]) -> Answers</name>
 
680
      <fsummary>Return all answers to a query.</fsummary>
 
681
      <type>
 
682
        <v>Options = [Option] | Option</v>
 
683
        <v>Option = {cache_all, Cache} | cache_all
 
684
                  | {max_list_size, MaxListSize}
 
685
                  | {tmpdir_usage, TmpFileUsage}
 
686
                  | {tmpdir, TempDirectory}
 
687
                  | {unique_all, bool()} | unique_all</v>
 
688
        <v>Error = {error, module(), Reason}</v>
 
689
        <v>Reason =&nbsp;-&nbsp;as returned by file_sorter(3)&nbsp;-</v>
 
690
      </type>
 
691
      <desc>
 
692
        <p><marker id="eval"></marker>Evaluates a query handle in the
 
693
          calling process and collects all answers in a list.</p>
 
694
 
 
695
        <pre>
 
696
1> <input>QH = qlc:q([{X,Y} || X &lt;- [a,b], Y &lt;- [1,2]]),</input>
 
697
<input>qlc:eval(QH).</input>
 
698
[{a,1},{a,2},{b,1},{b,2}]</pre>
 
699
      </desc>
 
700
    </func>
 
701
 
 
702
    <func>
 
703
      <name>fold(Function, Acc0, QueryHandleOrList [, Options]) -> 
 
704
               Acc1 | Error</name>
 
705
      <fsummary>Fold a function over the answers to a query.</fsummary>
 
706
      <type>
 
707
        <v>Function = fun(Answer, AccIn) -> AccOut</v>
 
708
        <v>Acc0 = Acc1 = AccIn = AccOut = term()</v>
 
709
        <v>Options = [Option] | Option</v>
 
710
        <v>Option = {cache_all, Cache} | cache_all
 
711
                  | {max_list_size, MaxListSize}
 
712
                  | {tmpdir_usage, TmpFileUsage}
 
713
                  | {tmpdir, TempDirectory}
 
714
                  | {unique_all, bool()} | unique_all</v>
 
715
        <v>Error = {error, module(), Reason}</v>
 
716
        <v>Reason =&nbsp;-&nbsp;as returned by file_sorter(3)&nbsp;-</v>
 
717
      </type>
 
718
      <desc>
 
719
        <p>Calls <c>Function</c> on successive answers to the query
 
720
          handle together with an extra argument <c>AccIn</c>. The
 
721
          query handle and the function are evaluated in the calling
 
722
          process. <c>Function</c> must return a new accumulator which
 
723
          is passed to the next call. <c>Acc0</c> is returned if there
 
724
          are no answers to the query handle.</p>
 
725
 
 
726
        <pre>
 
727
1> <input>QH = [1,2,3,4,5,6],</input>
 
728
<input>qlc:fold(fun(X, Sum) -> X + Sum end, 0, QH).</input>
 
729
21</pre>
 
730
      </desc>
 
731
    </func>
 
732
 
 
733
    <func>
 
734
      <name>format_error(Error) -> Chars</name>
 
735
      <fsummary>Return an English description of a an error tuple.</fsummary>
 
736
      <type>
 
737
        <v>Error = {error, module(), term()}</v>
 
738
        <v>Chars = [char() | Chars]</v>
 
739
      </type>
 
740
      <desc>
 
741
        <p>Returns a descriptive string in English of an error tuple
 
742
          returned by some of the functions of the <c>qlc</c> module
 
743
          or the parse transform. This function is mainly used by the
 
744
          compiler invoking the parse transform.</p>
 
745
      </desc>
 
746
    </func>
 
747
 
 
748
    <func>
 
749
      <name>info(QueryHandleOrList [, Options]) -> Info</name>
 
750
      <fsummary>Return code describing a query handle.</fsummary>
 
751
      <type>
 
752
        <v>Options = [Option] | Option</v>
 
753
        <v>Option = EvalOption | ReturnOption</v>
 
754
        <v>EvalOption = {cache_all, Cache} | cache_all
 
755
                      | {max_list_size, MaxListSize}
 
756
                      | {tmpdir_usage, TmpFileUsage}
 
757
                      | {tmpdir, TempDirectory}
 
758
                      | {unique_all, bool()} | unique_all</v>
 
759
        <v>ReturnOption = {depth, Depth}
 
760
                        | {flat, bool()}
 
761
                        | {format, Format}
 
762
                        | {n_elements, NElements}</v>
 
763
        <v>Depth = infinity | int() >= 0</v>
 
764
        <v>Format = abstract_code | string</v>
 
765
        <v>NElements = infinity | int() > 0</v>
 
766
        <v>Info = AbstractExpression | string()</v>
 
767
      </type>
 
768
      <desc>
 
769
        <p><marker id="info"></marker>Returns information about a
 
770
          query handle. The information describes the simplifications
 
771
          and optimizations that are the results of preparing the
 
772
          query for evaluation. This function is probably useful
 
773
          mostly during debugging.</p>
 
774
 
 
775
        <p>The information has the form of an Erlang expression where
 
776
          QLCs most likely occur. Depending on the format functions of
 
777
          mentioned QLC tables it may not be absolutely accurate.</p>
 
778
 
 
779
        <p>The default is to return a sequence of QLCs in a block, but
 
780
          if the option <c>{flat,&nbsp;false}</c> is given, one single
 
781
          QLC is returned. The default is to return a string, but if
 
782
          the option <c>{format,&nbsp;abstract_code}</c> is given,
 
783
          abstract code is returned instead. In the abstract code
 
784
          port identifiers, references, and pids are represented by
 
785
          strings. The default is to return
 
786
          all elements in lists, but if the
 
787
          <c>{n_elements,&nbsp;NElements}</c> option is given, only a
 
788
          limited number of elements are returned. The default is to
 
789
          show all of objects and match specifications, but if the
 
790
          <c>{depth,&nbsp;Depth}</c> option is given, parts of terms
 
791
          below a certain depth are replaced by <c>'...'</c>.</p>
 
792
 
 
793
        <pre>
 
794
1> <input>QH = qlc:q([{X,Y} || X &lt;- [x,y], Y &lt;- [a,b]]),</input>
 
795
<input>io:format("~s~n", [qlc:info(QH, unique_all)]).</input>
 
796
begin
 
797
    V1 =
 
798
        qlc:q([SQV ||
 
799
                   SQV &lt;- [x,y]],
 
800
              [{unique,true}]),
 
801
    V2 =
 
802
        qlc:q([SQV ||
 
803
                   SQV &lt;- [a,b]],
 
804
              [{unique,true}]),
 
805
    qlc:q([{X,Y} ||
 
806
               X &lt;- V1,
 
807
               Y &lt;- V2],
 
808
          [{unique,true}])
 
809
end</pre>
 
810
 
 
811
        <p>In this example two simple QLCs have been inserted just to
 
812
          hold the <c>{unique,&nbsp;true}</c> option.</p>
 
813
 
 
814
        <pre>
 
815
1> <input>E1 = ets:new(e1, []),</input>
 
816
<input>E2 = ets:new(e2, []),</input>
 
817
<input>true = ets:insert(E1, [{1,a},{2,b}]),</input>
 
818
<input>true = ets:insert(E2, [{a,1},{b,2}]),</input>
 
819
<input>Q = qlc:q([{X,Z,W} ||</input>
 
820
<input>{X, Z} &lt;- ets:table(E1),</input>
 
821
<input>{W, Y} &lt;- ets:table(E2),</input>
 
822
<input>X =:= Y]),</input>
 
823
<input>io:format("~s~n", [qlc:info(Q)]).</input>
 
824
begin
 
825
    V1 =
 
826
        qlc:q([P0 ||
 
827
                   P0 = {W,Y} &lt;- ets:table(17)]),
 
828
    V2 =
 
829
        qlc:q([[G1|G2] ||
 
830
                   G2 &lt;- V1,
 
831
                   G1 &lt;- ets:table(16),
 
832
                   element(2, G1) =:= element(1, G2)],
 
833
              [{join,lookup}]),
 
834
    qlc:q([{X,Z,W} ||
 
835
               [{X,Z}|{W,Y}] &lt;- V2,
 
836
               X =:= Y])
 
837
end</pre>
 
838
 
 
839
        <p>In this example the query list comprehension <c>V2</c> has
 
840
          been inserted to show the joined generators and the join
 
841
          method chosen. A convention is used for lookup join: the
 
842
          first generator (<c>G2</c>) is the one traversed, the second
 
843
          one (<c>G1</c>) is the table where constants are looked up.</p>
 
844
      </desc>
 
845
    </func>
 
846
 
 
847
    <func>
 
848
      <name>keysort(KeyPos, QH1 [, SortOptions]) -> QH2</name>
 
849
      <fsummary>Return a query handle.</fsummary>
 
850
      <type>
 
851
        <v>QH1 = QueryHandleOrList</v>
 
852
        <v>QH2 = QueryHandle</v>
 
853
      </type>
 
854
      <desc>
 
855
        <p>Returns a query handle. When evaluating the query handle
 
856
          <c>QH2</c> the answers to the query handle <c>QH1</c> are
 
857
          sorted by <seealso
 
858
          marker="file_sorter">file_sorter:keysort/4</seealso>
 
859
          according to the options.</p>
 
860
 
 
861
        <p>The sorter will use temporary files only if <c>QH1</c> does
 
862
          not evaluate to a list and the size of the binary
 
863
          representation of the answers exceeds <c>Size</c> bytes,
 
864
          where <c>Size</c> is the value of the <c>size</c> option.</p>
 
865
      </desc>
 
866
    </func>
 
867
 
 
868
    <func>
 
869
      <name>next_answers(QueryCursor [, NumberOfAnswers]) ->  
 
870
            Answers | Error</name>
 
871
      <fsummary>Return some or all answers to a query.</fsummary>
 
872
      <type>
 
873
        <v>NumberOfAnswers = all_remaining | int() > 0</v>
 
874
        <v>Error = {error, module(), Reason}</v>
 
875
        <v>Reason =&nbsp;-&nbsp;as returned by file_sorter(3)&nbsp;-</v>
 
876
      </type>
 
877
      <desc>
 
878
        <p>Returns some or all of the remaining answers to a query
 
879
          cursor. Only the owner of <c>Cursor</c> can retrieve
 
880
          answers.</p>
 
881
 
 
882
        <p>The optional argument <c>NumberOfAnswers</c>determines the
 
883
          maximum number of answers returned. The default value is
 
884
          <c>10</c>. If less than the requested number of answers is
 
885
          returned, subsequent calls to <c>next_answers</c> will
 
886
          return <c>[]</c>.</p>
 
887
      </desc>
 
888
    </func>
 
889
 
 
890
    <func>
 
891
      <name>q(QueryListComprehension [, Options]) -> QueryHandle</name>
 
892
      <fsummary>Return a handle for a query list comprehension.</fsummary>
 
893
      <type>
 
894
        <v>QueryListComprehension =&nbsp;
 
895
               -&nbsp;literal query listcomprehension&nbsp;-</v>
 
896
        <v>Options = [Option] | Option</v>
 
897
        <v>Option = {max_lookup, MaxLookup}
 
898
                  | {cache, Cache} | cache
 
899
                  | {join, Join}
 
900
                  | {lookup, Lookup}
 
901
                  | {unique, bool()} | unique</v>
 
902
        <v>MaxLookup = int() >= 0 | infinity</v>
 
903
        <v>Join = any | lookup | merge | nested_loop</v>
 
904
        <v>Lookup = bool() | any</v>
 
905
      </type>
 
906
      <desc>
 
907
        <p><marker id="q"></marker>Returns a query handle for a query
 
908
          list comprehension. The query list comprehension must be the
 
909
          first argument to <c>qlc:q/1,2</c> or it will be evaluated
 
910
          as an ordinary list comprehension. It is also necessary to
 
911
          add the line</p>
 
912
 
 
913
        <code type="none">
 
914
-include_lib("stdlib/include/qlc.hrl").</code>
 
915
 
 
916
        <p>to the source file. This causes a parse transform to
 
917
          substitute a fun for the query list comprehension. The
 
918
          (compiled) fun will be called when the query handle is
 
919
          evaluated.</p>
 
920
 
 
921
        <p>When calling <c>qlc:q/1,2</c> from the Erlang shell the
 
922
          parse transform is automatically called. When this happens
 
923
          the fun substituted for the query list comprehension is not
 
924
          compiled but will be evaluated by <c>erl_eval(3)</c>. This
 
925
          is also true when expressions are evaluated by means of
 
926
          <c>file:eval/1,2</c> or in the debugger.</p>
 
927
 
 
928
        <p>To be very explicit, this will not work:</p>
 
929
 
 
930
        <pre>
 
931
...
 
932
A = [X || {X} &lt;- [{1},{2}]], 
 
933
QH = qlc:q(A),
 
934
...</pre>
 
935
 
 
936
        <p>The variable <c>A</c> will be bound to the evaluated value
 
937
          of the list comprehension (<c>[1,2]</c>). The compiler
 
938
          complains with an error message ("argument is not a query
 
939
          list comprehension"); the shell process stops with a
 
940
          <c>badarg</c> reason.</p>
 
941
 
 
942
        <p>The <c>{cache,&nbsp;ets}</c> option can be used to cache
 
943
          the answers to a query list comprehension. The answers are
 
944
          stored in one ETS table for each cached query list
 
945
          comprehension. When a cached query list comprehension is
 
946
          evaluated again, answers are fetched from the table without
 
947
          any further computations. As a consequence, when all answers
 
948
          to a cached query list comprehension have been found, the
 
949
          ETS tables used for caching answers to the query list
 
950
          comprehension's qualifiers can be emptied. The option
 
951
          <c>cache</c> is equivalent to <c>{cache,&nbsp;ets}</c>.</p>
 
952
 
 
953
        <p>The <c>{cache,&nbsp;list}</c> option can be used to cache
 
954
          the answers to a query list comprehension just like
 
955
          <c>{cache,&nbsp;ets}</c>. The difference is that the answers
 
956
          are kept in a list (on the process heap). If the answers
 
957
          would occupy more than a certain amount of RAM memory a
 
958
          temporary file is used for storing the answers. The option
 
959
          <c>max_list_size</c> sets the limit in bytes and the temporary
 
960
          file is put on the directory set by the <c>tmpdir</c> option.</p>
 
961
 
 
962
        <p>The <c>cache</c> option has no effect if it is known that
 
963
          the query list comprehension will be evaluated at most once.
 
964
          This is always true for the top-most query list
 
965
          comprehension and also for the list expression of the first
 
966
          generator in a list of qualifiers. Note that in the presence
 
967
          of side effects in filters or callback functions the answers
 
968
          to query list comprehensions can be affected by the
 
969
          <c>cache</c> option.</p>
 
970
 
 
971
        <p>The <c>{unique,&nbsp;true}</c> option can be used to remove
 
972
          duplicate answers to a query list comprehension. The unique
 
973
          answers are stored in one ETS table for each query list
 
974
          comprehension. The table is emptied every time it is known
 
975
          that there are no more answers to the query list
 
976
          comprehension. The option <c>unique</c> is equivalent to
 
977
          <c>{unique,&nbsp;true}</c>. If the <c>unique</c> option is
 
978
          combined with the <c>{cache,&nbsp;ets}</c> option, two ETS
 
979
          tables are used, but the full answers are stored in one
 
980
          table only. If the <c>unique</c> option is combined with the
 
981
          <c>{cache,&nbsp;list}</c> option the answers are sorted
 
982
          twice using <c>keysort/3</c>; once to remove duplicates, and
 
983
          once to restore the order.</p>
 
984
 
 
985
        <p>The <c>cache</c> and <c>unique</c> options apply not only
 
986
          to the query list comprehension itself but also to the
 
987
          results of looking up constants, running match
 
988
          specifications, and joining handles. </p>
 
989
 
 
990
        <pre>
 
991
1> <input>Q = qlc:q([{A,X,Z,W} ||</input>
 
992
<input>A &lt;- [a,b,c],</input>
 
993
<input>{X,Z} &lt;- [{a,1},{b,4},{c,6}],</input>
 
994
<input>{W,Y} &lt;- [{2,a},{3,b},{4,c}],</input>
 
995
<input>X =:= Y],</input>
 
996
<input>{cache, list}),</input>
 
997
<input>io:format("~s~n", [qlc:info(Q)]).</input>
 
998
begin
 
999
    V1 =
 
1000
        qlc:q([P0 ||
 
1001
                   P0 = {X,Z} &lt;- qlc:keysort(1, [{a,1},{b,4},{c,6}], [])]),
 
1002
    V2 =
 
1003
        qlc:q([P0 ||
 
1004
                   P0 = {W,Y} &lt;- qlc:keysort(2, [{2,a},{3,b},{4,c}], [])]),
 
1005
    V3 =
 
1006
        qlc:q([[G1|G2] ||
 
1007
                   G1 &lt;- V1,
 
1008
                   G2 &lt;- V2,
 
1009
                   element(1, G1) == element(2, G2)],
 
1010
              [{join,merge},{cache,list}]),
 
1011
    qlc:q([{A,X,Z,W} ||
 
1012
               A &lt;- [a,b,c],
 
1013
               [{X,Z}|{W,Y}] &lt;- V3,
 
1014
               X =:= Y])
 
1015
end</pre>
 
1016
 
 
1017
        <p>In this example the cached results of the merge join are
 
1018
          traversed for each value of <c>A</c>. Note that without the
 
1019
          <c>cache</c> option the join would have been carried out
 
1020
          three times, once for each value of <c>A</c></p>
 
1021
 
 
1022
        <p><c>sort/1,2</c> and <c>keysort/2,3</c> can also be used for
 
1023
          caching answers and for removing duplicates. When sorting
 
1024
          answers are cached in a list, possibly stored on a temporary
 
1025
          file, and no ETS tables are used.</p>
 
1026
 
 
1027
        <p>Sometimes (see <seealso
 
1028
          marker="#lookup_fun">qlc:table/2</seealso> below) traversal
 
1029
          of tables can be done by looking up key values, which is
 
1030
          assumed to be fast. Under certain (rare) circumstances it
 
1031
          could happen that there are too many key values to look up.
 
1032
          <marker id="max_lookup"></marker> The
 
1033
          <c>{max_lookup,&nbsp;MaxLookup}</c> option can then be used
 
1034
          to limit the number of lookups: if more than
 
1035
          <c>MaxLookup</c> lookups would be required no lookups are
 
1036
          done but the table traversed instead. The default value is
 
1037
          <c>infinity</c> which means that there is no limit on the
 
1038
          number of keys to look up.</p>
 
1039
        <pre>
 
1040
1> <input>T = gb_trees:empty(),</input>
 
1041
<input>QH = qlc:q([X || {{X,Y},_} &lt;- gb_table:table(T),</input>
 
1042
<input>((X =:= 1) or (X =:= 2)),</input>
 
1043
<input>((Y =:= a) or (Y =:= b) or (Y =:= c))]),</input>
 
1044
<input>io:format("~s~n", [qlc:info(QH)]).</input>
 
1045
ets:match_spec_run(
 
1046
       lists:flatmap(fun(K) ->
 
1047
                            case
 
1048
                                gb_trees:lookup(K,
 
1049
                                                gb_trees:from_orddict([]))
 
1050
                            of
 
1051
                                {value,V} ->
 
1052
                                    [{K,V}];
 
1053
                                none ->
 
1054
                                    []
 
1055
                            end
 
1056
                     end,
 
1057
                     [{1,a},{1,b},{1,c},{2,a},{2,b},{2,c}]),
 
1058
       ets:match_spec_compile([{{{'$1','$2'},'_'},
 
1059
                                [{'andalso',
 
1060
                                  {'or',
 
1061
                                   {'=:=','$1',1},
 
1062
                                   {'=:=','$1',2}},
 
1063
                                  {'or',
 
1064
                                   {'or',
 
1065
                                    {'=:=','$2',a},
 
1066
                                    {'=:=','$2',b}},
 
1067
                                   {'=:=','$2',c}}}],
 
1068
                                ['$1']}]))</pre>
 
1069
 
 
1070
        <p>In this example using the <c>gb_table</c> module from the
 
1071
          <seealso marker="#implementing_a_qlc_table">Implementing a
 
1072
          QLC table</seealso> section there are six keys to look up:
 
1073
          <c>{1,a}</c>, <c>{1,b}</c>, <c>{1,c}</c>, <c>{2,a}</c>,
 
1074
          <c>{2,b}</c>, and <c>{2,c}</c>. The reason is that the two
 
1075
          elements of the key {X,&nbsp;Y} are matched separately.</p>
 
1076
 
 
1077
        <p>The <c>{lookup,&nbsp;true}</c> option can be used to ensure
 
1078
          that the <c>qlc</c> module will look up constants in some 
 
1079
          QLC table. If there
 
1080
          are more than one QLC table among the generators' list
 
1081
          expressions, constants have to be looked up in at least one
 
1082
          of the tables. The evaluation of the query fails if there
 
1083
          are no constants to look up. This option is useful in
 
1084
          situations when it would be unacceptable to traverse all
 
1085
          objects in some table. Setting the <c>lookup</c> option to
 
1086
          <c>false</c> ensures that no constants will be looked up
 
1087
          (<c>{max_lookup,&nbsp;0}</c> has the same effect). The
 
1088
          default value is <c>any</c> which means that constants will
 
1089
          be looked up whenever possible.</p>
 
1090
 
 
1091
        <p>The <c>{join,&nbsp;Join}</c> option can be used to ensure
 
1092
          that a certain join method will be used:
 
1093
          <c>{join,&nbsp;lookup}</c> invokes the lookup join method;
 
1094
          <c>{join,&nbsp;merge}</c> invokes the merge join method; and
 
1095
          <c>{join,&nbsp;nested_loop}</c> invokes the method of
 
1096
          matching every pair of objects from two handles. The last
 
1097
          method is mostly very slow. The evaluation of the query
 
1098
          fails if the <c>qlc</c> module cannot carry out the chosen 
 
1099
          join method. The
 
1100
          default value is <c>any</c> which means that some fast join
 
1101
          method will be used if possible.</p>
 
1102
      </desc>
 
1103
    </func>
 
1104
 
 
1105
    <func>
 
1106
      <name>sort(QH1 [, SortOptions]) -> QH2</name>
 
1107
      <fsummary>Return a query handle.</fsummary>
 
1108
      <type>
 
1109
        <v>QH1 = QueryHandleOrList</v>
 
1110
        <v>QH2 = QueryHandle</v>
 
1111
      </type>
 
1112
      <desc>
 
1113
        <p>Returns a query handle. When evaluating the query handle
 
1114
          <c>QH2</c> the answers to the query handle <c>QH1</c> are
 
1115
          sorted by <seealso
 
1116
          marker="file_sorter">file_sorter:sort/3</seealso> according
 
1117
          to the options.</p>
 
1118
 
 
1119
        <p>The sorter will use temporary files only if <c>QH1</c> does
 
1120
          not evaluate to a list and the size of the binary
 
1121
          representation of the answers exceeds <c>Size</c> bytes,
 
1122
          where <c>Size</c> is the value of the <c>size</c> option.</p>
 
1123
      </desc>
 
1124
    </func>
 
1125
 
 
1126
    <func>
 
1127
      <name>string_to_handle(QueryString [, Options [, Bindings]]) ->
 
1128
            QueryHandle | Error</name>
 
1129
      <fsummary>Return a handle for a query list comprehension.</fsummary>
 
1130
      <type>
 
1131
        <v>QueryString = string()</v>
 
1132
        <v>Options = [Option] | Option</v>
 
1133
        <v>Option = {max_lookup, MaxLookup}
 
1134
                  | {cache, Cache} | cache
 
1135
                  | {join, Join}
 
1136
                  | {lookup, Lookup}
 
1137
                  | {unique, bool()} | unique</v>
 
1138
        <v>MaxLookup = int() >= 0 | infinity</v>
 
1139
        <v>Join = any | lookup | merge | nested_loop</v>
 
1140
        <v>Lookup = bool() | any</v>
 
1141
        <v>Bindings =&nbsp;-&nbsp;as returned by
 
1142
        erl_eval:bindings/1&nbsp;-</v>
 
1143
        <v>Error = {error, module(), Reason}</v>
 
1144
        <v>Reason = &nbsp;-&nbsp;ErrorInfo as returned by
 
1145
        erl_scan:string/1 or erl_parse:parse_exprs/1&nbsp;-</v>
 
1146
      </type>
 
1147
      <desc>
 
1148
        <p>A string version of <c>qlc:q/1,2</c>. When the query handle
 
1149
          is evaluated the fun created by the parse transform is
 
1150
          interpreted by <c>erl_eval(3)</c>. The query string is to be
 
1151
          one single query list comprehension terminated by a
 
1152
          period.</p>
 
1153
 
 
1154
        <pre>
 
1155
1> <input>L = [1,2,3],</input>
 
1156
<input>Bs = erl_eval:add_binding('L', L, erl_eval:new_bindings()),</input>
 
1157
<input>QH = qlc:string_to_handle("[X+1 || X &lt;- L].", [], Bs),</input>
 
1158
<input>qlc:eval(QH).</input>
 
1159
[2,3,4]</pre>
 
1160
 
 
1161
        <p>This function is probably useful mostly when called from
 
1162
          outside of Erlang, for instance from a driver written in C.</p>
 
1163
      </desc>
 
1164
    </func>
 
1165
 
 
1166
    <func>
 
1167
      <name>table(TraverseFun, Options) -> QueryHandle</name>
 
1168
      <fsummary>Return a query handle for a table.</fsummary>
 
1169
      <type>
 
1170
        <v>TraverseFun = TraverseFun0 | TraverseFun1</v>
 
1171
        <v>TraverseFun0 = fun() -> TraverseResult</v>
 
1172
        <v>TraverseFun1 = fun(MatchExpression) -> TraverseResult</v>
 
1173
        <v>TraverseResult = Objects | term()</v>
 
1174
        <v>Objects = [] | [term() | ObjectList]</v>
 
1175
        <v>ObjectList = TraverseFun0 | Objects</v>
 
1176
        <v>Options = [Option] | Option</v>
 
1177
        <v>Option = {format_fun, FormatFun}
 
1178
                  | {info_fun, InfoFun}
 
1179
                  | {lookup_fun, LookupFun}
 
1180
                  | {parent_fun, ParentFun}
 
1181
                  | {post_fun, PostFun}
 
1182
                  | {pre_fun, PreFun}</v>
 
1183
        <v>FormatFun = undefined  | fun(SelectedObjects) -> FormatedTable</v>
 
1184
        <v>SelectedObjects = all
 
1185
                           | {all, NElements, DepthFun}
 
1186
                           | {match_spec, MatchExpression}
 
1187
                           | {lookup, Position, Keys}
 
1188
                           | {lookup, Position, Keys, NElements, DepthFun}</v>
 
1189
        <v>NElements = infinity | int() > 0</v>
 
1190
        <v>DepthFun = fun(term()) -> term()</v>
 
1191
        <v>FormatedTable = {Mod, Fun, Args}
 
1192
                         | AbstractExpression
 
1193
                         | character_list()</v>
 
1194
        <v>InfoFun = undefined  | fun(InfoTag) -> InfoValue</v>
 
1195
        <v>InfoTag = indices | is_unique_objects | keypos | num_of_objects</v>
 
1196
        <v>InfoValue = undefined  | term()</v>
 
1197
        <v>LookupFun = undefined  | fun(Position, Keys) -> LookupResult</v>
 
1198
        <v>LookupResult = [term()] | term()</v>
 
1199
        <v>ParentFun = undefined  | fun() -> ParentFunValue</v>
 
1200
        <v>PostFun = undefined  | fun() -> void()</v>
 
1201
        <v>PreFun = undefined  | fun([PreArg]) -> void()</v>
 
1202
        <v>PreArg = {parent_value, ParentFunValue}  | {stop_fun, StopFun}</v>
 
1203
        <v>ParentFunValue = undefined  | term()</v>
 
1204
        <v>StopFun = undefined  | fun() -> void()</v>
 
1205
        <v>Position = int() > 0</v>
 
1206
        <v>Keys = [term()]</v>
 
1207
        <v>Mod = Fun = atom()</v>
 
1208
        <v>Args = [term()]</v>
 
1209
      </type>
 
1210
      <desc>
 
1211
        <p><marker id="table"></marker>Returns a query handle for a
 
1212
          QLC table. In Erlang/OTP there is support for ETS, Dets and
 
1213
          Mnesia tables, but it is also possible to turn many other
 
1214
          data structures into QLC tables. The way to accomplish this
 
1215
          is to let function(s) in the module implementing the data
 
1216
          structure create a query handle by calling
 
1217
          <c>qlc:table/2</c>. The different ways to traverse the table
 
1218
          as well as properties of the table are handled by callback
 
1219
          functions provided as options to <c>qlc:table/2</c>.</p>
 
1220
 
 
1221
        <p>The callback function <c>TraverseFun</c> is used for
 
1222
          traversing the table. It is to return a list of objects
 
1223
          terminated by either <c>[]</c> or a nullary fun to be used
 
1224
          for traversing the not yet traversed objects of the table.
 
1225
          Any other return value is immediately returned as value of
 
1226
          the query evaluation. Unary <c>TraverseFun</c>s are to
 
1227
          accept a match specification as argument. The match
 
1228
          specification is created by the parse transform by analyzing
 
1229
          the pattern of the generator calling <c>qlc:table/2</c> and
 
1230
          filters using variables introduced in the pattern. If the
 
1231
          parse transform cannot find a match specification equivalent
 
1232
          to the pattern and filters, <c>TraverseFun</c> will be
 
1233
          called with a match specification returning every object.
 
1234
          Modules that can utilize match specifications for optimized
 
1235
          traversal of tables should call <c>qlc:table/2</c> with a
 
1236
          unary <c>TraverseFun</c> while other modules can provide a
 
1237
          nullary <c>TraverseFun</c>. <c>ets:table/2</c> is an example
 
1238
          of the former; <c>gb_table:table/1</c> in the <seealso
 
1239
          marker="#implementing_a_qlc_table">Implementing a QLC
 
1240
          table</seealso> section is an example of the latter.</p>
 
1241
 
 
1242
        <p><c>PreFun</c> is a unary callback function that is called
 
1243
          once before the table is read for the first time. If the
 
1244
          call fails, the query evaluation fails. Similarly, the
 
1245
          nullary callback function <c>PostFun</c> is called once
 
1246
          after the table was last read. The return value, which is
 
1247
          caught, is ignored. If <c>PreFun</c> has been called for a
 
1248
          table, <c>PostFun</c> is guaranteed to be called for that
 
1249
          table, even if the evaluation of the query fails for some
 
1250
          reason. The order in which pre (post) functions for
 
1251
          different tables are evaluated is not specified. Other table
 
1252
          access than reading, such as calling <c>InfoFun</c>, is
 
1253
          assumed to be OK at any time. The argument <c>PreArgs</c> is
 
1254
          a list of tagged values. Currently there are two tags,
 
1255
          <c>parent_value</c> and <c>stop_fun</c>, used by Mnesia for
 
1256
          managing transactions. The value of <c>parent_value</c> is
 
1257
          the value returned by <c>ParentFun</c>, or <c>undefined</c>
 
1258
          if there is no <c>ParentFun</c>. <c>ParentFun</c> is called
 
1259
          once just before the call of <c>PreFun</c> in the context of
 
1260
          the process calling <c>eval</c>, <c>fold</c>, or
 
1261
          <c>cursor</c>. The value of <c>stop_fun</c> is a nullary fun
 
1262
          that deletes the cursor if called from the parent, or
 
1263
          <c>undefined</c> if there is no cursor.</p>
 
1264
 
 
1265
        <p><marker id="lookup_fun"></marker>The binary callback
 
1266
          function <c>LookupFun</c> is used for looking up objects in
 
1267
          the table. The first argument <c>Position</c> is the key
 
1268
          position or an indexed position and the second argument
 
1269
          <c>Keys</c> is a sorted list of unique values. The return
 
1270
          value is to be a list of all objects (tuples) such that the
 
1271
          element at <c>Position</c> is a member of <c>Keys</c>. Any
 
1272
          other return value is immediately returned as value of the
 
1273
          query evaluation. <c>LookupFun</c> is called instead of
 
1274
          traversing the table if the parse transform at compile time
 
1275
          can find out that the filters match and compare the element
 
1276
          at <c>Position</c> in such a way that only <c>Keys</c> need
 
1277
          to be looked up in order to find all potential answers. The
 
1278
          key position is obtained by calling <c>InfoFun(keypos)</c>
 
1279
          and the indexed positions by calling
 
1280
          <c>InfoFun(indices)</c>. If the key position can be used for
 
1281
          lookup it is always chosen, otherwise the indexed position
 
1282
          requiring the least number of lookups is chosen. If there is
 
1283
          a tie between two indexed positions the one occurring first
 
1284
          in the list returned by <c>InfoFun</c> is chosen. Positions
 
1285
          requiring more than <seealso
 
1286
          marker="#max_lookup">max_lookup</seealso> lookups are
 
1287
          ignored.</p>
 
1288
 
 
1289
        <p>The unary callback function <c>InfoFun</c> is to return
 
1290
          information about the table. <c>undefined</c> should be
 
1291
          returned if the value of some tag is unknown:</p>
 
1292
 
 
1293
        <list type="bulleted">
 
1294
          <item><c>indices</c>. Returns a list of indexed
 
1295
           positions, a list of positive integers.
 
1296
          </item>
 
1297
          <item><c>is_unique_objects</c>. Returns <c>true</c> if
 
1298
           the objects returned by <c>TraverseFun</c> are unique.
 
1299
          </item>
 
1300
          <item><c>keypos</c>. Returns the position of the table's
 
1301
           key, a positive integer.
 
1302
          </item>
 
1303
          <item><c>is_sorted_key</c>. Returns <c>true</c> if
 
1304
           the objects returned by <c>TraverseFun</c> are sorted
 
1305
           on the key.
 
1306
          </item>
 
1307
          <item><c>num_of_objects</c>. Returns the number of
 
1308
           objects in the table, a non-negative integer.
 
1309
          </item>
 
1310
        </list>
 
1311
 
 
1312
        <p>The unary callback function <c>FormatFun</c> is used by
 
1313
          <seealso marker="#info">qlc:info/1,2</seealso> for
 
1314
          displaying the call that created the table's query handle.
 
1315
          The default value, <c>undefined</c>, means that
 
1316
          <c>info/1,2</c> displays a call to <c>'$MOD':'$FUN'/0</c>.
 
1317
          It is up to <c>FormatFun</c> to present the selected objects
 
1318
          of the table in a suitable way. However, if a character list
 
1319
          is chosen for presentation it must be an Erlang expression
 
1320
          that can be scanned and parsed (a trailing dot will be added
 
1321
          by <c>qlc:info</c> though). <c>FormatFun</c> is called with
 
1322
          an argument that describes the selected objects based on
 
1323
          optimizations done as a result of analyzing the filters of
 
1324
          the QLC where the call to <c>qlc:table/2</c> occurs. The
 
1325
          possible values of the argument are:</p>
 
1326
 
 
1327
        <list type="bulleted">
 
1328
          <item><c>{lookup, Position, Keys, NElements, DepthFun}</c>.
 
1329
          <c>LookupFun</c> is used for looking up objects in the
 
1330
           table.
 
1331
          </item>
 
1332
          <item><c>{match_spec, MatchExpression}</c>. No way of
 
1333
           finding all possible answers by looking up keys was
 
1334
           found, but the filters could be transformed into a
 
1335
           match specification. All answers are found by calling
 
1336
          <c>TraverseFun(MatchExpression)</c>.
 
1337
          </item>
 
1338
          <item><c>{all, NElements, DepthFun}</c>. No optimization was
 
1339
           found. A match specification matching all objects will be
 
1340
           used if <c>TraverseFun</c> is unary.
 
1341
          </item>
 
1342
        </list>
 
1343
 
 
1344
        <p><c>NElements</c> is the value of the <c>info/1,2</c> option
 
1345
          <c>n_elements</c>, and <c>DepthFun</c> is a function that
 
1346
          can be used for limiting the size of terms; calling
 
1347
          <c>DepthFun(Term)</c> substitutes <c>'...'</c> for parts of
 
1348
          <c>Term</c> below the depth specified by the <c>info/1,2</c>
 
1349
          option <c>depth</c>. If calling <c>FormatFun</c> with an
 
1350
          argument including <c>NElements</c> and <c>DepthFun</c>
 
1351
          fails, <c>FormatFun</c> is called once again with an
 
1352
          argument excluding <c>NElements</c> and <c>DepthFun</c>
 
1353
          (<c>{lookup,&nbsp;Position,&nbsp;Keys}</c> or
 
1354
          <c>all</c>).</p>
 
1355
 
 
1356
        <p>See <seealso marker="ets#qlc_table">ets(3)</seealso>,
 
1357
          <seealso marker="dets#qlc_table">dets(3)</seealso> and
 
1358
          <seealso marker="mnesia:mnesia#qlc_table">mnesia(3)</seealso> 
 
1359
          for the various options recognized by <c>table/1,2</c> in
 
1360
          respective module.</p>
 
1361
      </desc>
 
1362
    </func>
 
1363
 
 
1364
  </funcs>
 
1365
 
 
1366
  <section>
 
1367
    <title>See Also</title>
 
1368
    <p><seealso marker="dets">dets(3)</seealso>,
 
1369
      <seealso marker="doc/reference_manual:part_frame">
 
1370
           Erlang Reference Manual</seealso>,
 
1371
      <seealso marker="erl_eval">erl_eval(3)</seealso>,
 
1372
      <seealso marker="kernel:erlang">erlang(3)</seealso>, 
 
1373
      <seealso marker="ets">ets(3)</seealso>,
 
1374
      <seealso marker="kernel:file">file(3)</seealso>, 
 
1375
      <seealso marker="error_logger:file">error_logger(3)</seealso>, 
 
1376
      <seealso marker="file_sorter">file_sorter(3)</seealso>,
 
1377
      <seealso marker="mnesia:mnesia">mnesia(3)</seealso>, 
 
1378
      <seealso marker="doc/programming_examples:part_frame">
 
1379
           Programming Examples</seealso>,
 
1380
      <seealso marker="shell">shell(3)</seealso></p>
 
1381
  </section>
 
1382
</erlref>
 
1383