~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

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

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
4
4
<erlref>
5
5
  <header>
6
6
    <copyright>
7
 
      <year>2004</year><year>2009</year>
 
7
      <year>2004</year><year>2011</year>
8
8
      <holder>Ericsson AB. All Rights Reserved.</holder>
9
9
    </copyright>
10
10
    <legalnotice>
45
45
      tables</em>. Typical QLC tables are ETS, Dets, and Mnesia
46
46
      tables. There is also support for user defined tables, see the
47
47
      <seealso marker="#implementing_a_qlc_table">Implementing a QLC
48
 
      table</seealso> section. A <em>query</em> is stated using
 
48
      table</seealso> section. <marker
 
49
      id="query_list_comprehension"></marker>
 
50
      A <em>query</em> is stated using
49
51
      <em>Query List Comprehensions</em> (QLCs). The answers to a
50
52
      query are determined by data in QLC tables that fulfill the
51
53
      constraints expressed by the QLCs of the query. QLCs are similar
55
57
      fact, in the absence of optimizations and options such as
56
58
      <c>cache</c> and <c>unique</c> (see below), every QLC free of
57
59
      QLC tables evaluates to the same list of answers as the
58
 
      identical ordinary list comprehension. </p>
 
60
      identical ordinary list comprehension.</p>
59
61
 
60
62
    <p>While ordinary list comprehensions evaluate to lists, calling
61
 
      <seealso marker="#q">qlc:q/1,2</seealso> returns a <em>Query
 
63
      <seealso marker="#q">qlc:q/1,2</seealso> returns a <marker
 
64
      id="query_handle"></marker><em> Query
62
65
      Handle</em>. To obtain all the answers to a query, <seealso
63
66
      marker="#eval">qlc:eval/1,2</seealso> should be called with the
64
67
      query handle as first argument. Query handles are essentially
69
72
      Code replacement is described in the <seealso
70
73
      marker="doc/reference_manual:code_loading">Erlang Reference
71
74
      Manual</seealso>. The list of answers can also be traversed in
72
 
      chunks by use of a <em>Query Cursor</em>. Query cursors are
 
75
      chunks by use of a <marker
 
76
      id="query_cursor"></marker><em>Query Cursor</em>. Query cursors are
73
77
      created by calling <seealso
74
78
      marker="#cursor">qlc:cursor/1,2</seealso> with a query handle as
75
79
      first argument. Query cursors are essentially Erlang processes.
226
230
 
227
231
  </section>
228
232
 
229
 
  <section><title>Common data types</title>
230
 
 
231
 
    <list type="bulleted">
232
 
      <item><p><c>QueryCursor = {qlc_cursor, term()}</c></p>
233
 
      </item>
234
 
      <item><p><c>QueryHandle = {qlc_handle, term()}</c></p>
235
 
      </item>
236
 
      <item><p><c>QueryHandleOrList = QueryHandle | list()</c></p>
237
 
      </item>
238
 
      <item><p><c>Answers = [Answer]</c></p>
239
 
      </item>
240
 
      <item><p><c>Answer = term()</c></p>
241
 
      </item>
242
 
      <item><p><c>AbstractExpression =&nbsp;</c> -&nbsp;parse trees
243
 
          for Erlang expressions, see the <seealso
244
 
          marker="erts:absform">abstract format</seealso>
245
 
          documentation in the ERTS User's Guide&nbsp;-</p>
246
 
      </item>
247
 
      <item><p><c>MatchExpression =&nbsp;</c>
248
 
          -&nbsp;match&nbsp;specifications, see the <seealso
249
 
          marker="erts:match_spec">match specification</seealso>
250
 
          documentation in the ERTS User's Guide and <seealso
251
 
          marker="ms_transform">ms_transform(3)</seealso>&nbsp;-</p>
252
 
      </item>
253
 
      <item><p><c>SpawnOptions = default | spawn_options()</c></p>
254
 
      </item>
255
 
      <item><p><c>SortOptions = [SortOption] | SortOption</c></p>
256
 
      </item>
257
 
      <item><p><c>SortOption = {compressed, bool()}
258
 
            | {no_files, NoFiles} 
259
 
            | {order, Order} 
260
 
            | {size, Size} 
261
 
            | {tmpdir, TempDirectory} 
262
 
            | {unique, bool()}&nbsp;</c>
263
 
            -&nbsp;see <seealso
264
 
            marker="file_sorter">file_sorter(3)</seealso>&nbsp;-</p>
265
 
      </item>
266
 
      <item><p><c>Order = ascending | descending | OrderFun</c></p>
267
 
      </item>
268
 
      <item><p><c>OrderFun = fun(term(), term()) -> bool()</c></p>
269
 
      </item>
270
 
      <item><p><c>TempDirectory = "" | filename()</c></p>
271
 
      </item>
272
 
      <item><p><c>Size = int() > 0</c></p>
273
 
      </item>
274
 
      <item><p><c>NoFiles = int() > 1</c></p>
275
 
      </item>
276
 
      <item><p><c>KeyPos = int() > 0 | [int() > 0]</c></p>
277
 
      </item>
278
 
      <item><p><c>MaxListSize = int() >= 0</c></p>
279
 
      </item>
280
 
      <item><p><c>bool() = true | false</c></p>
281
 
      </item>
282
 
      <item><p><c>Cache = ets | list | no</c></p>
283
 
      </item>
284
 
      <item><p><c>TmpFileUsage = allowed | not_allowed | info_msg 
285
 
            | warning_msg | error_msg</c></p>
286
 
      </item>
287
 
      <item><p><c>filename() =&nbsp;</c> -&nbsp;see <seealso
288
 
            marker="filename">filename(3)</seealso>&nbsp;-</p>
289
 
      </item>
290
 
      <item><p><c>spawn_options() =&nbsp;</c> -&nbsp;see <seealso
291
 
          marker="erts:erlang">erlang(3)</seealso>&nbsp;-</p>
292
 
      </item>
293
 
 
294
 
    </list>
295
 
 
296
 
  </section>
297
 
 
298
233
  <section><title>Getting started</title>
299
234
 
300
235
    <p><marker id="getting_started"></marker> As already mentioned
679
614
 
680
615
  </section>
681
616
 
 
617
  <datatypes>
 
618
    <datatype>
 
619
      <name name="abstract_expr"></name>
 
620
      <desc><p>Parse trees for Erlang expression, see the <seealso
 
621
        marker="erts:absform">abstract format</seealso>
 
622
        documentation in the ERTS User's Guide.</p></desc>
 
623
    </datatype>
 
624
    <datatype>
 
625
      <name name="answer"></name>
 
626
    </datatype>
 
627
    <datatype>
 
628
      <name name="answers"></name>
 
629
    </datatype>
 
630
    <datatype>
 
631
      <name name="cache"></name>
 
632
    </datatype>
 
633
    <datatype>
 
634
      <name name="match_expression"></name>
 
635
      <desc><p>Match&nbsp;specification, see the <seealso
 
636
          marker="erts:match_spec">match specification</seealso>
 
637
          documentation in the ERTS User's Guide and <seealso
 
638
          marker="ms_transform">ms_transform(3).</seealso></p></desc>
 
639
    </datatype>
 
640
    <datatype>
 
641
      <name name="no_files"></name>
 
642
      <desc><p>Actually an integer > 1.</p></desc>
 
643
    </datatype>
 
644
    <datatype>
 
645
      <name name="key_pos"></name>
 
646
    </datatype>
 
647
    <datatype>
 
648
      <name name="max_list_size"></name>
 
649
    </datatype>
 
650
    <datatype>
 
651
      <name name="order"></name>
 
652
    </datatype>
 
653
    <datatype>
 
654
      <name name="order_fun"></name>
 
655
    </datatype>
 
656
    <datatype>
 
657
      <name name="query_cursor"></name>
 
658
      <desc><p>A <seealso marker="#query_cursor">query cursor</seealso>.</p>
 
659
      </desc>
 
660
    </datatype>
 
661
    <datatype>
 
662
      <name name="query_handle"></name>
 
663
      <desc><p>A <seealso marker="#query_handle">query handle</seealso>.</p>
 
664
      </desc>
 
665
    </datatype>
 
666
    <datatype>
 
667
      <name name="query_handle_or_list"></name>
 
668
    </datatype>
 
669
    <datatype>
 
670
      <name name="query_list_comprehension"></name>
 
671
      <desc><p>A literal
 
672
        <seealso marker="#query_list_comprehension">query
 
673
         list comprehension</seealso>.</p></desc>
 
674
    </datatype>
 
675
    <datatype>
 
676
      <name name="spawn_options"></name>
 
677
    </datatype>
 
678
    <datatype>
 
679
      <name name="sort_options"></name>
 
680
    </datatype>
 
681
    <datatype>
 
682
      <name name="sort_option"></name>
 
683
      <desc><p>See <seealso
 
684
        marker="file_sorter">file_sorter(3)</seealso>.</p></desc>
 
685
    </datatype>
 
686
    <datatype>
 
687
      <name name="tmp_directory"></name>
 
688
    </datatype>
 
689
    <datatype>
 
690
      <name name="tmp_file_usage"></name>
 
691
    </datatype>
 
692
  </datatypes>
 
693
 
682
694
  <funcs>
683
695
 
684
696
    <func>
685
 
      <name>append(QHL) -> QH</name>
 
697
      <name name="append" arity="1"/>
686
698
      <fsummary>Return a query handle.</fsummary>
687
 
      <type>
688
 
        <v>QHL = [QueryHandleOrList]</v>
689
 
        <v>QH = QueryHandle</v>
690
 
      </type>
691
699
      <desc>
692
700
        <p>Returns a query handle. When evaluating the query handle
693
 
          <c>QH</c> all answers to the first query handle in
694
 
          <c>QHL</c> is returned followed by all answers to the rest
695
 
          of the query handles in <c>QHL</c>.</p>
 
701
          <c><anno>QH</anno></c> all answers to the first query handle in
 
702
          <c><anno>QHL</anno></c> are returned followed by all answers
 
703
          to the rest of the query handles in <c><anno>QHL</anno></c>.</p>
696
704
      </desc>
697
705
    </func>
698
706
 
699
707
    <func>
700
 
      <name>append(QH1, QH2) -> QH3</name>
 
708
      <name name="append" arity="2"/>
701
709
      <fsummary>Return a query handle.</fsummary>
702
 
      <type>
703
 
        <v>QH1 = QH2 = QueryHandleOrList</v>
704
 
        <v>QH3 = QueryHandle</v>
705
 
      </type>
706
710
      <desc>
707
711
        <p>Returns a query handle. When evaluating the query handle
708
 
          <c>QH3</c> all answers to <c>QH1</c> are returned followed
709
 
          by all answers to <c>QH2</c>.</p>
 
712
          <c><anno>QH3</anno></c> all answers to
 
713
          <c><anno>QH1</anno></c> are returned followed by all answers
 
714
          to <c><anno>QH2</anno></c>.</p>
710
715
 
711
716
        <p><c>append(QH1,&nbsp;QH2)</c> is equivalent to
712
717
          <c>append([QH1,&nbsp;QH2])</c>.</p>
714
719
    </func>
715
720
 
716
721
    <func>
717
 
      <name>cursor(QueryHandleOrList [, Options]) -> QueryCursor</name>
 
722
      <name name="cursor" arity="1"/>
 
723
      <name name="cursor" arity="2"/>
718
724
      <fsummary>Create a query cursor.</fsummary>
719
 
      <type>
720
 
        <v>Options = [Option] | Option</v>
721
 
        <v>Option = {cache_all, Cache} | cache_all
722
 
                  | {max_list_size, MaxListSize}
723
 
                  | {spawn_options, SpawnOptions}
724
 
                  | {tmpdir_usage, TmpFileUsage}
725
 
                  | {tmpdir, TempDirectory}
726
 
                  | {unique_all, bool()} | unique_all</v>
727
 
      </type>
728
725
      <desc>
729
726
        <p><marker id="cursor"></marker>Creates a query cursor and
730
727
          makes the calling process the owner of the cursor. The
746
743
[{b,1},{b,2}]
747
744
4> <input>qlc:delete_cursor(QC).</input>
748
745
ok</pre>
 
746
        <p><c>cursor(<anno>QH</anno>)</c> is equivalent to
 
747
          <c>cursor(<anno>QH</anno>, [])</c>.</p>
749
748
      </desc>
750
749
    </func>
751
750
 
752
751
    <func>
753
 
      <name>delete_cursor(QueryCursor) -> ok</name>
 
752
      <name name="delete_cursor" arity="1"/>
754
753
      <fsummary>Delete a query cursor.</fsummary>
755
754
      <desc>
756
755
        <p>Deletes a query cursor. Only the owner of the cursor can
759
758
    </func>
760
759
 
761
760
    <func>
762
 
      <name>eval(QueryHandleOrList [, Options]) -> Answers | Error</name>
763
 
      <name>e(QueryHandleOrList [, Options]) -> Answers</name>
 
761
      <name name="eval" arity="1"/>
 
762
      <name name="eval" arity="2"/>
 
763
      <name name="e" arity="1"/>
 
764
      <name name="e" arity="2"/>
764
765
      <fsummary>Return all answers to a query.</fsummary>
765
 
      <type>
766
 
        <v>Options = [Option] | Option</v>
767
 
        <v>Option = {cache_all, Cache} | cache_all
768
 
                  | {max_list_size, MaxListSize}
769
 
                  | {tmpdir_usage, TmpFileUsage}
770
 
                  | {tmpdir, TempDirectory}
771
 
                  | {unique_all, bool()} | unique_all</v>
772
 
        <v>Error = {error, module(), Reason}</v>
773
 
        <v>Reason =&nbsp;-&nbsp;as returned by file_sorter(3)&nbsp;-</v>
774
 
      </type>
775
766
      <desc>
776
767
        <p><marker id="eval"></marker>Evaluates a query handle in the
777
768
          calling process and collects all answers in a list.</p>
780
771
1> <input>QH = qlc:q([{X,Y} || X &lt;- [a,b], Y &lt;- [1,2]]),</input>
781
772
<input>qlc:eval(QH).</input>
782
773
[{a,1},{a,2},{b,1},{b,2}]</pre>
 
774
        <p><c>eval(<anno>QH</anno>)</c> is equivalent to
 
775
          <c>eval(<anno>QH</anno>, [])</c>.</p>
783
776
      </desc>
784
777
    </func>
785
778
 
786
779
    <func>
787
 
      <name>fold(Function, Acc0, QueryHandleOrList [, Options]) -> 
788
 
               Acc1 | Error</name>
 
780
      <name name="fold" arity="3"/>
 
781
      <name name="fold" arity="4"/>
789
782
      <fsummary>Fold a function over the answers to a query.</fsummary>
790
 
      <type>
791
 
        <v>Function = fun(Answer, AccIn) -> AccOut</v>
792
 
        <v>Acc0 = Acc1 = AccIn = AccOut = term()</v>
793
 
        <v>Options = [Option] | Option</v>
794
 
        <v>Option = {cache_all, Cache} | cache_all
795
 
                  | {max_list_size, MaxListSize}
796
 
                  | {tmpdir_usage, TmpFileUsage}
797
 
                  | {tmpdir, TempDirectory}
798
 
                  | {unique_all, bool()} | unique_all</v>
799
 
        <v>Error = {error, module(), Reason}</v>
800
 
        <v>Reason =&nbsp;-&nbsp;as returned by file_sorter(3)&nbsp;-</v>
801
 
      </type>
802
783
      <desc>
803
 
        <p>Calls <c>Function</c> on successive answers to the query
804
 
          handle together with an extra argument <c>AccIn</c>. The
805
 
          query handle and the function are evaluated in the calling
806
 
          process. <c>Function</c> must return a new accumulator which
807
 
          is passed to the next call. <c>Acc0</c> is returned if there
808
 
          are no answers to the query handle.</p>
 
784
        <p>Calls <c><anno>Function</anno></c> on successive answers to
 
785
          the query handle together with an extra argument
 
786
          <c><anno>AccIn</anno></c>. The query handle and the function
 
787
          are evaluated in the calling process.
 
788
          <c><anno>Function</anno></c> must return a new accumulator
 
789
          which is passed to the next call.
 
790
          <c><anno>Acc0</anno></c> is returned if there are no answers
 
791
          to the query handle.</p>
809
792
 
810
793
        <pre>
811
794
1> <input>QH = [1,2,3,4,5,6],</input>
812
795
<input>qlc:fold(fun(X, Sum) -> X + Sum end, 0, QH).</input>
813
796
21</pre>
 
797
        <p><c>fold(<anno>Function</anno>, <anno>Acc0</anno>,
 
798
          <anno>QH</anno>)</c> is equivalent to
 
799
          <c>fold(<anno>Function</anno>, <anno>Acc0</anno>,
 
800
          <anno>QH</anno>, [])</c>.</p>
814
801
      </desc>
815
802
    </func>
816
803
 
817
804
    <func>
818
 
      <name>format_error(Error) -> Chars</name>
 
805
      <name name="format_error" arity="1"/>
819
806
      <fsummary>Return an English description of a an error tuple.</fsummary>
820
 
      <type>
821
 
        <v>Error = {error, module(), term()}</v>
822
 
        <v>Chars = [char() | Chars]</v>
823
 
      </type>
824
807
      <desc>
825
808
        <p>Returns a descriptive string in English of an error tuple
826
809
          returned by some of the functions of the <c>qlc</c> module
830
813
    </func>
831
814
 
832
815
    <func>
833
 
      <name>info(QueryHandleOrList [, Options]) -> Info</name>
 
816
      <name name="info" arity="1"/>
 
817
      <name name="info" arity="2"/>
834
818
      <fsummary>Return code describing a query handle.</fsummary>
835
 
      <type>
836
 
        <v>Options = [Option] | Option</v>
837
 
        <v>Option = EvalOption | ReturnOption</v>
838
 
        <v>EvalOption = {cache_all, Cache} | cache_all
839
 
                      | {max_list_size, MaxListSize}
840
 
                      | {tmpdir_usage, TmpFileUsage}
841
 
                      | {tmpdir, TempDirectory}
842
 
                      | {unique_all, bool()} | unique_all</v>
843
 
        <v>ReturnOption = {depth, Depth}
844
 
                        | {flat, bool()}
845
 
                        | {format, Format}
846
 
                        | {n_elements, NElements}</v>
847
 
        <v>Depth = infinity | int() >= 0</v>
848
 
        <v>Format = abstract_code | string</v>
849
 
        <v>NElements = infinity | int() > 0</v>
850
 
        <v>Info = AbstractExpression | string()</v>
851
 
      </type>
852
819
      <desc>
853
820
        <p><marker id="info"></marker>Returns information about a
854
821
          query handle. The information describes the simplifications
879
846
<input>io:format("~s~n", [qlc:info(QH, unique_all)]).</input>
880
847
begin
881
848
    V1 =
882
 
        qlc:q([ 
 
849
        qlc:q([
883
850
               SQV ||
884
851
                   SQV &lt;- [x,y]
885
852
              ],
886
853
              [{unique,true}]),
887
854
    V2 =
888
 
        qlc:q([ 
 
855
        qlc:q([
889
856
               SQV ||
890
857
                   SQV &lt;- [a,b]
891
858
              ],
892
859
              [{unique,true}]),
893
 
    qlc:q([ 
 
860
    qlc:q([
894
861
           {X,Y} ||
895
862
               X &lt;- V1,
896
863
               Y &lt;- V2
913
880
<input>io:format("~s~n", [qlc:info(Q)]).</input>
914
881
begin
915
882
    V1 =
916
 
        qlc:q([ 
 
883
        qlc:q([
917
884
               P0 ||
918
885
                   P0 = {W,Y} &lt;- ets:table(17)
919
886
              ]),
920
887
    V2 =
921
 
        qlc:q([ 
 
888
        qlc:q([
922
889
               [G1|G2] ||
923
890
                   G2 &lt;- V1,
924
891
                   G1 &lt;- ets:table(16),
925
892
                   element(2, G1) =:= element(1, G2)
926
893
              ],
927
894
              [{join,lookup}]),
928
 
    qlc:q([ 
 
895
    qlc:q([
929
896
           {X,Z,W} ||
930
897
               [{X,Z}|{W,Y}] &lt;- V2
931
898
          ])
936
903
          method chosen. A convention is used for lookup join: the
937
904
          first generator (<c>G2</c>) is the one traversed, the second
938
905
          one (<c>G1</c>) is the table where constants are looked up.</p>
 
906
 
 
907
        <p><c>info(<anno>QH</anno>)</c> is equivalent to
 
908
          <c>info(<anno>QH</anno>, [])</c>.</p>
939
909
      </desc>
940
910
    </func>
941
911
 
942
912
    <func>
943
 
      <name>keysort(KeyPos, QH1 [, SortOptions]) -> QH2</name>
 
913
      <name name="keysort" arity="2"/>
 
914
      <name name="keysort" arity="3"/>
944
915
      <fsummary>Return a query handle.</fsummary>
945
 
      <type>
946
 
        <v>QH1 = QueryHandleOrList</v>
947
 
        <v>QH2 = QueryHandle</v>
948
 
      </type>
949
916
      <desc>
950
917
        <p>Returns a query handle. When evaluating the query handle
951
 
          <c>QH2</c> the answers to the query handle <c>QH1</c> are
952
 
          sorted by <seealso
 
918
          <c><anno>QH2</anno></c> the answers to the query handle
 
919
          <c><anno>QH1</anno></c> are sorted by <seealso
953
920
          marker="file_sorter">file_sorter:keysort/4</seealso>
954
921
          according to the options.</p>
955
922
 
956
 
        <p>The sorter will use temporary files only if <c>QH1</c> does
957
 
          not evaluate to a list and the size of the binary
958
 
          representation of the answers exceeds <c>Size</c> bytes,
959
 
          where <c>Size</c> is the value of the <c>size</c> option.</p>
 
923
        <p>The sorter will use temporary files only if
 
924
          <c><anno>QH1</anno></c> does not evaluate to a list and the
 
925
          size of the binary representation of the answers exceeds
 
926
          <c>Size</c> bytes, where <c>Size</c> is the value of the
 
927
          <c>size</c> option.</p>
 
928
 
 
929
        <p><c>keysort(<anno>KeyPos</anno>, <anno>QH1</anno>)</c>
 
930
          is equivalent to
 
931
          <c>keysort(<anno>KeyPos</anno>, <anno>QH1</anno>, [])</c>.</p>
960
932
      </desc>
961
933
    </func>
962
934
 
963
935
    <func>
964
 
      <name>next_answers(QueryCursor [, NumberOfAnswers]) ->  
965
 
            Answers | Error</name>
 
936
      <name name="next_answers" arity="1"/>
 
937
      <name name="next_answers" arity="2"/>
966
938
      <fsummary>Return some or all answers to a query.</fsummary>
967
 
      <type>
968
 
        <v>NumberOfAnswers = all_remaining | int() > 0</v>
969
 
        <v>Error = {error, module(), Reason}</v>
970
 
        <v>Reason =&nbsp;-&nbsp;as returned by file_sorter(3)&nbsp;-</v>
971
 
      </type>
972
939
      <desc>
973
940
        <p>Returns some or all of the remaining answers to a query
974
 
          cursor. Only the owner of <c>Cursor</c> can retrieve
975
 
          answers.</p>
976
 
 
 
941
          cursor. Only the owner of <c><anno>QueryCursor</anno></c> can
 
942
          retrieve answers.</p>
977
943
        <p>The optional argument <c>NumberOfAnswers</c>determines the
978
944
          maximum number of answers returned. The default value is
979
945
          <c>10</c>. If less than the requested number of answers is
983
949
    </func>
984
950
 
985
951
    <func>
986
 
      <name>q(QueryListComprehension [, Options]) -> QueryHandle</name>
 
952
      <name name="q" arity="1"/>
 
953
      <name name="q" arity="2"/>
987
954
      <fsummary>Return a handle for a query list comprehension.</fsummary>
988
 
      <type>
989
 
        <v>QueryListComprehension =&nbsp;
990
 
               -&nbsp;literal query listcomprehension&nbsp;-</v>
991
 
        <v>Options = [Option] | Option</v>
992
 
        <v>Option = {max_lookup, MaxLookup}
993
 
                  | {cache, Cache} | cache
994
 
                  | {join, Join}
995
 
                  | {lookup, Lookup}
996
 
                  | {unique, bool()} | unique</v>
997
 
        <v>MaxLookup = int() >= 0 | infinity</v>
998
 
        <v>Join = any | lookup | merge | nested_loop</v>
999
 
        <v>Lookup = bool() | any</v>
1000
 
      </type>
1001
955
      <desc>
1002
956
        <p><marker id="q"></marker>Returns a query handle for a query
1003
957
          list comprehension. The query list comprehension must be the
1024
978
 
1025
979
        <pre>
1026
980
...
1027
 
A = [X || {X} &lt;- [{1},{2}]], 
 
981
A = [X || {X} &lt;- [{1},{2}]],
1028
982
QH = qlc:q(A),
1029
983
...</pre>
1030
984
 
1034
988
          list comprehension"); the shell process stops with a
1035
989
          <c>badarg</c> reason.</p>
1036
990
 
 
991
        <p><c>q(<anno>QLC</anno>)</c> is equivalent to
 
992
          <c>q(<anno>QLC</anno>, [])</c>.</p>
 
993
 
1037
994
        <p>The <c>{cache,&nbsp;ets}</c> option can be used to cache
1038
995
          the answers to a query list comprehension. The answers are
1039
996
          stored in one ETS table for each cached query list
1092
1049
<input>io:format("~s~n", [qlc:info(Q)]).</input>
1093
1050
begin
1094
1051
    V1 =
1095
 
        qlc:q([ 
 
1052
        qlc:q([
1096
1053
               P0 ||
1097
1054
                   P0 = {X,Z} &lt;-
1098
1055
                       qlc:keysort(1, [{a,1},{b,4},{c,6}], [])
1099
1056
              ]),
1100
1057
    V2 =
1101
 
        qlc:q([ 
 
1058
        qlc:q([
1102
1059
               P0 ||
1103
1060
                   P0 = {W,Y} &lt;-
1104
1061
                       qlc:keysort(2, [{2,a},{3,b},{4,c}], [])
1105
1062
              ]),
1106
1063
    V3 =
1107
 
        qlc:q([ 
 
1064
        qlc:q([
1108
1065
               [G1|G2] ||
1109
1066
                   G1 &lt;- V1,
1110
1067
                   G2 &lt;- V2,
1111
1068
                   element(1, G1) == element(2, G2)
1112
1069
              ],
1113
1070
              [{join,merge},{cache,list}]),
1114
 
    qlc:q([ 
 
1071
    qlc:q([
1115
1072
           {A,X,Z,W} ||
1116
1073
               A &lt;- [a,b,c],
1117
1074
               [{X,Z}|{W,Y}] &lt;- V3,
1170
1127
          elements of the key {X,&nbsp;Y} are compared separately.</p>
1171
1128
 
1172
1129
        <p>The <c>{lookup,&nbsp;true}</c> option can be used to ensure
1173
 
          that the <c>qlc</c> module will look up constants in some 
 
1130
          that the <c>qlc</c> module will look up constants in some
1174
1131
          QLC table. If there
1175
1132
          are more than one QLC table among the generators' list
1176
1133
          expressions, constants have to be looked up in at least one
1190
1147
          <c>{join,&nbsp;nested_loop}</c> invokes the method of
1191
1148
          matching every pair of objects from two handles. The last
1192
1149
          method is mostly very slow. The evaluation of the query
1193
 
          fails if the <c>qlc</c> module cannot carry out the chosen 
 
1150
          fails if the <c>qlc</c> module cannot carry out the chosen
1194
1151
          join method. The
1195
1152
          default value is <c>any</c> which means that some fast join
1196
1153
          method will be used if possible.</p>
1198
1155
    </func>
1199
1156
 
1200
1157
    <func>
1201
 
      <name>sort(QH1 [, SortOptions]) -> QH2</name>
 
1158
      <name name="sort" arity="1"/>
 
1159
      <name name="sort" arity="2"/>
1202
1160
      <fsummary>Return a query handle.</fsummary>
1203
 
      <type>
1204
 
        <v>QH1 = QueryHandleOrList</v>
1205
 
        <v>QH2 = QueryHandle</v>
1206
 
      </type>
1207
1161
      <desc>
1208
1162
        <p>Returns a query handle. When evaluating the query handle
1209
 
          <c>QH2</c> the answers to the query handle <c>QH1</c> are
1210
 
          sorted by <seealso
 
1163
          <c><anno>QH2</anno></c> the answers to the query handle
 
1164
          <c><anno>QH1</anno></c> are sorted by <seealso
1211
1165
          marker="file_sorter">file_sorter:sort/3</seealso> according
1212
1166
          to the options.</p>
1213
1167
 
1214
 
        <p>The sorter will use temporary files only if <c>QH1</c> does
1215
 
          not evaluate to a list and the size of the binary
1216
 
          representation of the answers exceeds <c>Size</c> bytes,
1217
 
          where <c>Size</c> is the value of the <c>size</c> option.</p>
 
1168
        <p>The sorter will use temporary files only if
 
1169
          <c><anno>QH1</anno></c> does not evaluate to a list and the
 
1170
          size of the binary representation of the answers exceeds
 
1171
          <c>Size</c> bytes, where <c>Size</c> is the value of the
 
1172
          <c>size</c> option.</p>
 
1173
 
 
1174
        <p><c>sort(<anno>QH1</anno>)</c> is equivalent to
 
1175
          <c>sort(<anno>QH1</anno>, [])</c>.</p>
 
1176
 
1218
1177
      </desc>
1219
1178
    </func>
1220
1179
 
1221
1180
    <func>
1222
 
      <name>string_to_handle(QueryString [, Options [, Bindings]]) ->
1223
 
            QueryHandle | Error</name>
 
1181
      <name name="string_to_handle" arity="1"/>
 
1182
      <name name="string_to_handle" arity="2"/>
 
1183
      <name name="string_to_handle" arity="3"/>
1224
1184
      <fsummary>Return a handle for a query list comprehension.</fsummary>
1225
 
      <type>
1226
 
        <v>QueryString = string()</v>
1227
 
        <v>Options = [Option] | Option</v>
1228
 
        <v>Option = {max_lookup, MaxLookup}
1229
 
                  | {cache, Cache} | cache
1230
 
                  | {join, Join}
1231
 
                  | {lookup, Lookup}
1232
 
                  | {unique, bool()} | unique</v>
1233
 
        <v>MaxLookup = int() >= 0 | infinity</v>
1234
 
        <v>Join = any | lookup | merge | nested_loop</v>
1235
 
        <v>Lookup = bool() | any</v>
1236
 
        <v>Bindings =&nbsp;-&nbsp;as returned by
1237
 
        erl_eval:bindings/1&nbsp;-</v>
1238
 
        <v>Error = {error, module(), Reason}</v>
1239
 
        <v>Reason = &nbsp;-&nbsp;ErrorInfo as returned by
1240
 
        erl_scan:string/1 or erl_parse:parse_exprs/1&nbsp;-</v>
1241
 
      </type>
1242
1185
      <desc>
1243
1186
        <p>A string version of <c>qlc:q/1,2</c>. When the query handle
1244
1187
          is evaluated the fun created by the parse transform is
1253
1196
<input>qlc:eval(QH).</input>
1254
1197
[2,3,4]</pre>
1255
1198
 
 
1199
        <p><c>string_to_handle(<anno>QueryString</anno>)</c>
 
1200
          is equivalent to
 
1201
          <c>string_to_handle(<anno>QueryString</anno>, [])</c>.</p>
 
1202
 
 
1203
        <p><c>string_to_handle(<anno>QueryString</anno>,
 
1204
          <anno>Options</anno>)</c>
 
1205
          is equivalent to
 
1206
          <c>string_to_handle(<anno>QueryString</anno>,
 
1207
          <anno>Options</anno>, erl_eval:new_bindings())</c>.</p>
 
1208
 
1256
1209
        <p>This function is probably useful mostly when called from
1257
1210
          outside of Erlang, for instance from a driver written in C.</p>
1258
1211
      </desc>
1259
1212
    </func>
1260
1213
 
1261
1214
    <func>
1262
 
      <name>table(TraverseFun, Options) -> QueryHandle</name>
 
1215
      <name name="table" arity="2"/>
1263
1216
      <fsummary>Return a query handle for a table.</fsummary>
1264
 
      <type>
1265
 
        <v>TraverseFun = TraverseFun0 | TraverseFun1</v>
1266
 
        <v>TraverseFun0 = fun() -> TraverseResult</v>
1267
 
        <v>TraverseFun1 = fun(MatchExpression) -> TraverseResult</v>
1268
 
        <v>TraverseResult = Objects | term()</v>
1269
 
        <v>Objects = [] | [term() | ObjectList]</v>
1270
 
        <v>ObjectList = TraverseFun0 | Objects</v>
1271
 
        <v>Options = [Option] | Option</v>
1272
 
        <v>Option = {format_fun, FormatFun}
1273
 
                  | {info_fun, InfoFun}
1274
 
                  | {lookup_fun, LookupFun}
1275
 
                  | {parent_fun, ParentFun}
1276
 
                  | {post_fun, PostFun}
1277
 
                  | {pre_fun, PreFun}
1278
 
                  | {key_equality, KeyComparison}</v>
1279
 
        <v>FormatFun = undefined  | fun(SelectedObjects) -> FormatedTable</v>
1280
 
        <v>SelectedObjects = all
1281
 
                           | {all, NElements, DepthFun}
1282
 
                           | {match_spec, MatchExpression}
1283
 
                           | {lookup, Position, Keys}
1284
 
                           | {lookup, Position, Keys, NElements, DepthFun}</v>
1285
 
        <v>NElements = infinity | int() > 0</v>
1286
 
        <v>DepthFun = fun(term()) -> term()</v>
1287
 
        <v>FormatedTable = {Mod, Fun, Args}
1288
 
                         | AbstractExpression
1289
 
                         | character_list()</v>
1290
 
        <v>InfoFun = undefined  | fun(InfoTag) -> InfoValue</v>
1291
 
        <v>InfoTag = indices | is_unique_objects | keypos | num_of_objects</v>
1292
 
        <v>InfoValue = undefined  | term()</v>
1293
 
        <v>LookupFun = undefined  | fun(Position, Keys) -> LookupResult</v>
1294
 
        <v>LookupResult = [term()] | term()</v>
1295
 
        <v>ParentFun = undefined  | fun() -> ParentFunValue</v>
1296
 
        <v>PostFun = undefined  | fun() -> void()</v>
1297
 
        <v>PreFun = undefined  | fun([PreArg]) -> void()</v>
1298
 
        <v>PreArg = {parent_value, ParentFunValue}  | {stop_fun, StopFun}</v>
1299
 
        <v>ParentFunValue = undefined  | term()</v>
1300
 
        <v>StopFun = undefined  | fun() -> void()</v>
1301
 
        <v>KeyComparison = '=:=' | '=='</v>
1302
 
        <v>Position = int() > 0</v>
1303
 
        <v>Keys = [term()]</v>
1304
 
        <v>Mod = Fun = atom()</v>
1305
 
        <v>Args = [term()]</v>
1306
 
      </type>
1307
1217
      <desc>
1308
1218
        <p><marker id="table"></marker>Returns a query handle for a
1309
1219
          QLC table. In Erlang/OTP there is support for ETS, Dets and
1315
1225
          as well as properties of the table are handled by callback
1316
1226
          functions provided as options to <c>qlc:table/2</c>.</p>
1317
1227
 
1318
 
        <p>The callback function <c>TraverseFun</c> is used for
1319
 
          traversing the table. It is to return a list of objects
1320
 
          terminated by either <c>[]</c> or a nullary fun to be used
1321
 
          for traversing the not yet traversed objects of the table.
1322
 
          Any other return value is immediately returned as value of
1323
 
          the query evaluation. Unary <c>TraverseFun</c>s are to
1324
 
          accept a match specification as argument. The match
1325
 
          specification is created by the parse transform by analyzing
1326
 
          the pattern of the generator calling <c>qlc:table/2</c> and
1327
 
          filters using variables introduced in the pattern. If the
1328
 
          parse transform cannot find a match specification equivalent
1329
 
          to the pattern and filters, <c>TraverseFun</c> will be
1330
 
          called with a match specification returning every object.
1331
 
          Modules that can utilize match specifications for optimized
 
1228
        <p>The callback function <c><anno>TraverseFun</anno></c> is
 
1229
          used for traversing the table. It is to return a list of
 
1230
          objects terminated by either <c>[]</c> or a nullary fun to
 
1231
          be used for traversing the not yet traversed objects of the
 
1232
          table. Any other return value is immediately returned as
 
1233
          value of the query evaluation. Unary
 
1234
          <c><anno>TraverseFun</anno></c>s are to accept a match
 
1235
          specification as argument. The match specification is
 
1236
          created by the parse transform by analyzing the pattern of
 
1237
          the generator calling <c>qlc:table/2</c> and filters using
 
1238
          variables introduced in the pattern. If the parse transform
 
1239
          cannot find a match specification equivalent to the pattern
 
1240
          and filters, <c><anno>TraverseFun</anno></c> will be called
 
1241
          with a match specification returning every object. Modules
 
1242
          that can utilize match specifications for optimized
1332
1243
          traversal of tables should call <c>qlc:table/2</c> with a
1333
 
          unary <c>TraverseFun</c> while other modules can provide a
1334
 
          nullary <c>TraverseFun</c>. <c>ets:table/2</c> is an example
1335
 
          of the former; <c>gb_table:table/1</c> in the <seealso
1336
 
          marker="#implementing_a_qlc_table">Implementing a QLC
1337
 
          table</seealso> section is an example of the latter.</p>
 
1244
          unary
 
1245
          <c><anno>TraverseFun</anno></c> while other modules can
 
1246
          provide a nullary
 
1247
          <c><anno>TraverseFun</anno></c>. <c>ets:table/2</c> is an
 
1248
          example of the former; <c>gb_table:table/1</c> in the
 
1249
          <seealso marker="#implementing_a_qlc_table">Implementing a
 
1250
          QLC table</seealso> section is an example of the latter.</p>
1338
1251
 
1339
 
        <p><c>PreFun</c> is a unary callback function that is called
1340
 
          once before the table is read for the first time. If the
1341
 
          call fails, the query evaluation fails. Similarly, the
1342
 
          nullary callback function <c>PostFun</c> is called once
1343
 
          after the table was last read. The return value, which is
1344
 
          caught, is ignored. If <c>PreFun</c> has been called for a
1345
 
          table, <c>PostFun</c> is guaranteed to be called for that
1346
 
          table, even if the evaluation of the query fails for some
1347
 
          reason. The order in which pre (post) functions for
 
1252
        <p><c><anno>PreFun</anno></c> is a unary callback function
 
1253
          that is called once before the table is read for the first
 
1254
          time. If the call fails, the query evaluation fails.
 
1255
          Similarly, the nullary callback function
 
1256
          <c><anno>PostFun</anno></c> is called once after the table
 
1257
          was last read. The return value, which is caught, is
 
1258
          ignored. If <c><anno>PreFun</anno></c> has been called for a
 
1259
          table,
 
1260
          <c><anno>PostFun</anno></c> is guaranteed to be called for
 
1261
          that table, even if the evaluation of the query fails for
 
1262
          some reason. The order in which pre (post) functions for
1348
1263
          different tables are evaluated is not specified. Other table
1349
 
          access than reading, such as calling <c>InfoFun</c>, is
1350
 
          assumed to be OK at any time. The argument <c>PreArgs</c> is
1351
 
          a list of tagged values. Currently there are two tags,
 
1264
          access than reading, such as calling
 
1265
          <c><anno>InfoFun</anno></c>, is assumed to be OK at any
 
1266
          time. The argument <c><anno>PreArgs</anno></c> is a list of
 
1267
          tagged values. Currently there are two tags,
1352
1268
          <c>parent_value</c> and <c>stop_fun</c>, used by Mnesia for
1353
1269
          managing transactions. The value of <c>parent_value</c> is
1354
 
          the value returned by <c>ParentFun</c>, or <c>undefined</c>
1355
 
          if there is no <c>ParentFun</c>. <c>ParentFun</c> is called
1356
 
          once just before the call of <c>PreFun</c> in the context of
1357
 
          the process calling <c>eval</c>, <c>fold</c>, or
 
1270
          the value returned by <c><anno>ParentFun</anno></c>, or
 
1271
          <c>undefined</c> if there is no <c>ParentFun</c>.
 
1272
          <c><anno>ParentFun</anno></c> is called once just before the
 
1273
          call of
 
1274
          <c><anno>PreFun</anno></c> in the context of the process
 
1275
          calling
 
1276
          <c>eval</c>, <c>fold</c>, or
1358
1277
          <c>cursor</c>. The value of <c>stop_fun</c> is a nullary fun
1359
1278
          that deletes the cursor if called from the parent, or
1360
1279
          <c>undefined</c> if there is no cursor.</p>
1361
1280
 
1362
1281
        <p><marker id="lookup_fun"></marker>The binary callback
1363
 
          function <c>LookupFun</c> is used for looking up objects in
1364
 
          the table. The first argument <c>Position</c> is the key
1365
 
          position or an indexed position and the second argument
1366
 
          <c>Keys</c> is a sorted list of unique values. The return
1367
 
          value is to be a list of all objects (tuples) such that the
1368
 
          element at <c>Position</c> is a member of <c>Keys</c>. Any
1369
 
          other return value is immediately returned as value of the
1370
 
          query evaluation. <c>LookupFun</c> is called instead of
 
1282
          function <c><anno>LookupFun</anno></c> is used for looking
 
1283
          up objects in the table. The first argument
 
1284
          <c><anno>Position</anno></c> is the key position or an
 
1285
          indexed position and the second argument
 
1286
          <c><anno>Keys</anno></c> is a sorted list of unique values.
 
1287
          The return value is to be a list of all objects (tuples)
 
1288
          such that the element at <c>Position</c> is a member of
 
1289
          <c><anno>Keys</anno></c>. Any other return value is
 
1290
          immediately returned as value of the query evaluation.
 
1291
          <c><anno>LookupFun</anno></c> is called instead of
1371
1292
          traversing the table if the parse transform at compile time
1372
1293
          can find out that the filters match and compare the element
1373
 
          at <c>Position</c> in such a way that only <c>Keys</c> need
1374
 
          to be looked up in order to find all potential answers. The
1375
 
          key position is obtained by calling <c>InfoFun(keypos)</c>
1376
 
          and the indexed positions by calling
1377
 
          <c>InfoFun(indices)</c>. If the key position can be used for
1378
 
          lookup it is always chosen, otherwise the indexed position
1379
 
          requiring the least number of lookups is chosen. If there is
1380
 
          a tie between two indexed positions the one occurring first
1381
 
          in the list returned by <c>InfoFun</c> is chosen. Positions
1382
 
          requiring more than <seealso
1383
 
          marker="#max_lookup">max_lookup</seealso> lookups are
1384
 
          ignored.</p>
 
1294
          at <c><anno>Position</anno></c> in such a way that only
 
1295
          <c><anno>Keys</anno></c> need to be looked up in order to
 
1296
          find all potential answers. The key position is obtained by
 
1297
          calling
 
1298
          <c><anno>InfoFun</anno>(keypos)</c> and the indexed
 
1299
          positions by calling
 
1300
          <c><anno>InfoFun</anno>(indices)</c>. If the key position
 
1301
          can be used for lookup it is always chosen, otherwise the
 
1302
          indexed position requiring the least number of lookups is
 
1303
          chosen. If there is a tie between two indexed positions the
 
1304
          one occurring first in the list returned by
 
1305
          <c><anno>InfoFun</anno></c> is chosen. Positions requiring
 
1306
          more than <seealso marker="#max_lookup">max_lookup</seealso>
 
1307
          lookups are ignored.</p>
1385
1308
 
1386
 
        <p>The unary callback function <c>InfoFun</c> is to return
1387
 
          information about the table. <c>undefined</c> should be
1388
 
          returned if the value of some tag is unknown:</p>
 
1309
        <p>The unary callback function <c><anno>InfoFun</anno></c> is
 
1310
          to return information about the table. <c>undefined</c>
 
1311
          should be returned if the value of some tag is unknown:</p>
1389
1312
 
1390
1313
        <list type="bulleted">
1391
1314
          <item><c>indices</c>. Returns a list of indexed
1406
1329
          </item>
1407
1330
        </list>
1408
1331
 
1409
 
        <p>The unary callback function <c>FormatFun</c> is used by
1410
 
          <seealso marker="#info">qlc:info/1,2</seealso> for
1411
 
          displaying the call that created the table's query handle.
1412
 
          The default value, <c>undefined</c>, means that
 
1332
        <p>The unary callback function <c><anno>FormatFun</anno></c>
 
1333
          is used by <seealso marker="#info">qlc:info/1,2</seealso>
 
1334
          for displaying the call that created the table's query
 
1335
          handle. The default value, <c>undefined</c>, means that
1413
1336
          <c>info/1,2</c> displays a call to <c>'$MOD':'$FUN'/0</c>.
1414
 
          It is up to <c>FormatFun</c> to present the selected objects
1415
 
          of the table in a suitable way. However, if a character list
1416
 
          is chosen for presentation it must be an Erlang expression
1417
 
          that can be scanned and parsed (a trailing dot will be added
1418
 
          by <c>qlc:info</c> though). <c>FormatFun</c> is called with
1419
 
          an argument that describes the selected objects based on
1420
 
          optimizations done as a result of analyzing the filters of
1421
 
          the QLC where the call to <c>qlc:table/2</c> occurs. The
1422
 
          possible values of the argument are:</p>
 
1337
          It is up to <c><anno>FormatFun</anno></c> to present the
 
1338
          selected objects of the table in a suitable way. However, if
 
1339
          a character list is chosen for presentation it must be an
 
1340
          Erlang expression that can be scanned and parsed (a trailing
 
1341
          dot will be added by <c>qlc:info</c> though).
 
1342
          <c><anno>FormatFun</anno></c> is called with an argument
 
1343
          that describes the selected objects based on optimizations
 
1344
          done as a result of analyzing the filters of the QLC where
 
1345
          the call to
 
1346
          <c>qlc:table/2</c> occurs. The possible values of the
 
1347
          argument are:</p>
1423
1348
 
1424
1349
        <list type="bulleted">
1425
1350
          <item><c>{lookup, Position, Keys, NElements, DepthFun}</c>.
1443
1368
          can be used for limiting the size of terms; calling
1444
1369
          <c>DepthFun(Term)</c> substitutes <c>'...'</c> for parts of
1445
1370
          <c>Term</c> below the depth specified by the <c>info/1,2</c>
1446
 
          option <c>depth</c>. If calling <c>FormatFun</c> with an
1447
 
          argument including <c>NElements</c> and <c>DepthFun</c>
1448
 
          fails, <c>FormatFun</c> is called once again with an
1449
 
          argument excluding <c>NElements</c> and <c>DepthFun</c>
 
1371
          option <c>depth</c>. If calling
 
1372
          <c><anno>FormatFun</anno></c> with an argument including
 
1373
          <c>NElements</c> and <c>DepthFun</c> fails,
 
1374
          <c><anno>FormatFun</anno></c> is called once again with an
 
1375
          argument excluding
 
1376
          <c>NElements</c> and <c>DepthFun</c>
1450
1377
          (<c>{lookup,&nbsp;Position,&nbsp;Keys}</c> or
1451
1378
          <c>all</c>).</p>
1452
1379
 
1458
1385
 
1459
1386
        <p>See <seealso marker="ets#qlc_table">ets(3)</seealso>,
1460
1387
          <seealso marker="dets#qlc_table">dets(3)</seealso> and
1461
 
          <seealso marker="mnesia:mnesia#qlc_table">mnesia(3)</seealso> 
 
1388
          <seealso marker="mnesia:mnesia#qlc_table">mnesia(3)</seealso>
1462
1389
          for the various options recognized by <c>table/1,2</c> in
1463
1390
          respective module.</p>
1464
1391
      </desc>
1472
1399
      <seealso marker="doc/reference_manual:users_guide">
1473
1400
           Erlang Reference Manual</seealso>,
1474
1401
      <seealso marker="erl_eval">erl_eval(3)</seealso>,
1475
 
      <seealso marker="erts:erlang">erlang(3)</seealso>, 
 
1402
      <seealso marker="erts:erlang">erlang(3)</seealso>,
1476
1403
      <seealso marker="ets">ets(3)</seealso>,
1477
 
      <seealso marker="kernel:file">file(3)</seealso>, 
1478
 
      <seealso marker="error_logger:file">error_logger(3)</seealso>, 
 
1404
      <seealso marker="kernel:file">file(3)</seealso>,
 
1405
      <seealso marker="error_logger:file">error_logger(3)</seealso>,
1479
1406
      <seealso marker="file_sorter">file_sorter(3)</seealso>,
1480
 
      <seealso marker="mnesia:mnesia">mnesia(3)</seealso>, 
 
1407
      <seealso marker="mnesia:mnesia">mnesia(3)</seealso>,
1481
1408
      <seealso marker="doc/programming_examples:users_guide">
1482
1409
           Programming Examples</seealso>,
1483
1410
      <seealso marker="shell">shell(3)</seealso></p>