1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2004-2018. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20-module(qlc).
21
22%%% Purpose: Main API module qlc. Functions for evaluation.
23%%% Other files:
24%%% qlc_pt. Implements the parse transform.
25
26%% External exports
27
28%% Avoid warning for local function error/1 clashing with autoimported BIF.
29-compile({no_auto_import,[error/1]}).
30-export([parse_transform/2,
31         parse_transform_info/0,
32         transform_from_evaluator/2]).
33
34-export([q/1, q/2]).
35
36-export([eval/1, e/1, eval/2, e/2, fold/3, fold/4]).
37-export([cursor/1, cursor/2,
38         next_answers/1, next_answers/2,
39         delete_cursor/1]).
40-export([append/1, append/2]).
41
42-export([sort/1, sort/2, keysort/2, keysort/3]).
43
44-export([table/2]).
45
46-export([info/1, info/2]).
47
48-export([string_to_handle/1, string_to_handle/2, string_to_handle/3]).
49
50-export([format_error/1]).
51
52%% Exported to qlc_pt.erl only:
53-export([template_state/0, aux_name/3, name_suffix/2, vars/1,
54         var_ufold/2, var_fold/3, all_selections/1]).
55
56-dialyzer(no_improper_lists).
57
58%% When cache=list lists bigger than ?MAX_LIST_SIZE bytes are put on
59%% file. Also used when merge join finds big equivalence classes.
60-define(MAX_LIST_SIZE, 512*1024).
61
62-record(qlc_append, % qlc:append/1,2
63        {hl
64        }).
65
66-record(qlc_table,   % qlc:table/2
67        {trav_fun,   % traverse fun
68         trav_MS,    % boolean(); true iff traverse fun takes a match spec
69         pre_fun,
70         post_fun,
71         info_fun,
72         format_fun,
73         lookup_fun,
74         parent_fun,
75         key_equality, % '==' | '=:=' | undefined (--R12B-5)
76         lu_vals,    % undefined | {Position,Values}; values to be looked up
77         ms = no_match_spec
78                     % match specification; [T || P <- Tab, Fs]
79        }).
80
81-record(qlc_sort,    % qlc:sort/1,2 and qlc:keysort/2,3
82        {h,
83         keypos,     % sort | {keysort, KeyPos}
84         unique,
85         compressed, % [] | [compressed]
86         order,
87         fs_opts,    % file_sorter options
88         tmpdir_usage = allowed, % allowed | not_allowed
89                                 %  | warning_msg | error_msg | info_msg
90         tmpdir
91        }).
92
93%% Also in qlc_pt.erl.
94-record(qlc_lc,     % qlc:q/1,2
95        {lc,
96         opt        % #qlc_opt
97        }).
98
99-record(qlc_list,   % a prepared list
100        {l,
101         ms = no_match_spec
102        }).
103
104-record(qlc_join,        % a prepared join
105        {kind,           % {merge, KeyEquality} |
106                         % {lookup, KeyEquality, LookupFun}
107         opt,            % #qlc_opt from q/2.
108         h1, q1, c1,     % to be traversed by "lookup join"
109         h2, q2, c2      % to be looked up by "lookup join"
110        }).
111
112%%% A query cursor is a tuple {qlc_cursor, Cursor} where Cursor is a pair
113%%% {CursorPid, OwnerPid}.
114
115-record(qlc_cursor, {c}).
116
117-record(qlc_opt,
118        {unique = false,      % boolean()
119         cache = false,       % boolean() | list (true~ets, false~no)
120         max_lookup = -1,     % int() >= 0 | -1 (represents infinity)
121         join = any,          % any | nested_loop | merge | lookup
122         tmpdir = "",         % global tmpdir
123         lookup = any,        % any | boolean()
124         max_list = ?MAX_LIST_SIZE,  % int() >= 0
125         tmpdir_usage = allowed    % allowed | not_allowed
126                                   %  | warning_msg | error_msg | info_msg
127        }).
128
129-record(setup, {parent}).
130
131-define(THROWN_ERROR, {?MODULE, throw_error, _, _}).
132
133-export_type([query_cursor/0, query_handle/0]).
134
135%%% A query handle is a tuple {qlc_handle, Handle} where Handle is one
136%%% of #qlc_append, #qlc_table, #qlc_sort, and #qlc_lc.
137
138-record(qlc_handle, {h}).
139
140get_handle(#qlc_handle{h = #qlc_lc{opt = {qlc_opt, U, C, M}}=H}) ->
141    %% R11B-0.
142    H#qlc_lc{opt = #qlc_opt{unique = U, cache = C, max_lookup = M}};
143get_handle(#qlc_handle{h = H}) ->
144    H;
145get_handle(L) when is_list(L) ->
146    L;
147get_handle(_) ->
148    badarg.
149
150%%%
151%%% Exported functions
152%%%
153
154-type(query_list_comprehension() :: term()).
155-opaque(query_cursor() :: {qlc_cursor, term()}).
156-opaque(query_handle() :: {qlc_handle, term()}).
157-type(query_handle_or_list() :: query_handle() | list()).
158-type(answers() :: [answer()]).
159-type(answer() :: term()).
160-type(abstract_expr() :: erl_parse:abstract_expr()).
161-type(match_expression() :: ets:match_spec()).
162-type(spawn_options() :: default | [proc_lib:spawn_option()]).
163-type(sort_options() :: [sort_option()] | sort_option()).
164-type(sort_option() :: {compressed, boolean()}
165                     | {no_files, no_files()}
166                     | {order, order()}
167                     | {size, pos_integer()}
168                     | {tmpdir, tmp_directory()}
169                     | {unique, boolean()}).
170-type(order() :: ascending | descending | order_fun()).
171-type(order_fun() :: fun((term(), term()) -> boolean())).
172-type(tmp_directory() :: [] | file:name()).
173-type(no_files() :: pos_integer()). % > 1
174-type(key_pos() :: pos_integer() | [pos_integer()]).
175-type(max_list_size() :: non_neg_integer()).
176-type(cache() :: ets | list | no).
177-type(tmp_file_usage() :: allowed | not_allowed | info_msg
178                        | warning_msg  | error_msg).
179
180-spec(append(QHL) -> QH when
181      QHL :: [query_handle_or_list()],
182      QH :: query_handle()).
183append(QHs) ->
184    Hs = [case get_handle(QH) of
185              badarg -> erlang:error(badarg, [QHs]);
186              H -> H
187          end || QH <- QHs],
188    #qlc_handle{h = #qlc_append{hl = Hs}}.
189
190-spec(append(QH1, QH2) -> QH3 when
191      QH1 :: query_handle_or_list(),
192      QH2 :: query_handle_or_list(),
193      QH3 :: query_handle()).
194append(QH1, QH2) ->
195    Hs = [case get_handle(QH) of
196              badarg -> erlang:error(badarg, [QH1, QH2]);
197              H -> H
198          end || QH <- [QH1, QH2]],
199    #qlc_handle{h = #qlc_append{hl = Hs}}.
200
201-spec(cursor(QH) -> Cursor when
202      QH :: query_handle_or_list(),
203      Cursor :: query_cursor()).
204cursor(QH) ->
205    cursor(QH, []).
206
207-spec(cursor(QH, Options) -> Cursor when
208      QH :: query_handle_or_list(),
209      Options :: [Option] | Option,
210      Option :: {cache_all, cache()} | cache_all
211              | {max_list_size, max_list_size()}
212              | {spawn_options, spawn_options()}
213              | {tmpdir_usage, tmp_file_usage()}
214              | {tmpdir, tmp_directory()}
215              | {unique_all, boolean()} | unique_all,
216      Cursor :: query_cursor()).
217cursor(QH, Options) ->
218    case {options(Options, [unique_all, cache_all, tmpdir,
219                            spawn_options, max_list_size,
220                            tmpdir_usage]),
221          get_handle(QH)} of
222        {B1, B2} when B1 =:= badarg; B2 =:= badarg ->
223            erlang:error(badarg, [QH, Options]);
224        {[GUnique, GCache, TmpDir, SpawnOptions0, MaxList, TmpUsage], H} ->
225            SpawnOptions = spawn_options(SpawnOptions0),
226            case cursor_process(H, GUnique, GCache, TmpDir,
227                                SpawnOptions, MaxList, TmpUsage) of
228                Pid when is_pid(Pid) ->
229                    #qlc_cursor{c = {Pid, self()}};
230                Error ->
231                    Error
232            end
233    end.
234
235-spec(delete_cursor(QueryCursor) -> ok when
236      QueryCursor :: query_cursor()).
237delete_cursor(#qlc_cursor{c = {_, Owner}}=C) when Owner =/= self() ->
238    erlang:error(not_cursor_owner, [C]);
239delete_cursor(#qlc_cursor{c = {Pid, _}}) ->
240    stop_cursor(Pid);
241delete_cursor(T) ->
242    erlang:error(badarg, [T]).
243
244-spec(e(QH) -> Answers | Error when
245      QH :: query_handle_or_list(),
246      Answers :: answers(),
247      Error :: {error, module(), Reason},
248      Reason :: file_sorter:reason()).
249e(QH) ->
250    eval(QH, []).
251
252-spec(e(QH, Options) -> Answers | Error when
253      QH :: query_handle_or_list(),
254      Options :: [Option] | Option,
255      Option :: {cache_all, cache()} | cache_all
256              | {max_list_size, max_list_size()}
257              | {tmpdir_usage, tmp_file_usage()}
258              | {tmpdir, tmp_directory()}
259              | {unique_all, boolean()} | unique_all,
260      Answers :: answers(),
261      Error :: {error, module(), Reason},
262      Reason :: file_sorter:reason()).
263e(QH, Options) ->
264    eval(QH, Options).
265
266-spec(eval(QH) -> Answers | Error when
267      QH :: query_handle_or_list(),
268      Answers :: answers(),
269      Error :: {error, module(), Reason},
270      Reason :: file_sorter:reason()).
271eval(QH) ->
272    eval(QH, []).
273
274-spec(eval(QH, Options) -> Answers | Error when
275      QH :: query_handle_or_list(),
276      Answers :: answers(),
277      Options :: [Option] | Option,
278      Option :: {cache_all, cache()} | cache_all
279              | {max_list_size, max_list_size()}
280              | {tmpdir_usage, tmp_file_usage()}
281              | {tmpdir, tmp_directory()}
282              | {unique_all, boolean()} | unique_all,
283      Error :: {error, module(), Reason},
284      Reason :: file_sorter:reason()).
285eval(QH, Options) ->
286    case {options(Options, [unique_all, cache_all, tmpdir, max_list_size,
287                            tmpdir_usage]),
288          get_handle(QH)} of
289        {B1, B2} when B1 =:= badarg; B2 =:= badarg ->
290            erlang:error(badarg, [QH, Options]);
291        {[GUnique, GCache, TmpDir, MaxList, TmpUsage], Handle} ->
292            try
293                Prep = prepare_qlc(Handle, [], GUnique, GCache,
294                                   TmpDir, MaxList, TmpUsage),
295                case setup_qlc(Prep, #setup{parent = self()}) of
296                    {L, Post, _LocalPost} when is_list(L) ->
297                        post_funs(Post),
298                        L;
299                    {Objs, Post, _LocalPost} when is_function(Objs) ->
300                        try
301                            collect(Objs)
302                        after
303                            post_funs(Post)
304                        end
305                end
306            catch throw:Term:Stacktrace ->
307                case Stacktrace of
308                    [?THROWN_ERROR | _] ->
309                        Term;
310                    _ ->
311                        erlang:raise(throw, Term, Stacktrace)
312                end
313            end
314    end.
315
316-spec(fold(Function, Acc0, QH) ->
317               Acc1 | Error when
318      QH :: query_handle_or_list(),
319      Function :: fun((answer(), AccIn) -> AccOut),
320      Acc0 :: term(),
321      Acc1 :: term(),
322      AccIn :: term(),
323      AccOut :: term(),
324      Error :: {error, module(), Reason},
325      Reason :: file_sorter:reason()).
326fold(Fun, Acc0, QH) ->
327    fold(Fun, Acc0, QH, []).
328
329-spec(fold(Function, Acc0, QH, Options) ->
330               Acc1 | Error when
331      QH :: query_handle_or_list(),
332      Function :: fun((answer(), AccIn) -> AccOut),
333      Acc0 :: term(),
334      Acc1 :: term(),
335      AccIn :: term(),
336      AccOut :: term(),
337      Options :: [Option] | Option,
338      Option :: {cache_all, cache()} | cache_all
339              | {max_list_size, max_list_size()}
340              | {tmpdir_usage, tmp_file_usage()}
341              | {tmpdir, tmp_directory()}
342              | {unique_all, boolean()} | unique_all,
343      Error :: {error, module(), Reason},
344      Reason :: file_sorter:reason()).
345fold(Fun, Acc0, QH, Options) ->
346    case {options(Options, [unique_all, cache_all, tmpdir, max_list_size,
347                            tmpdir_usage]),
348          get_handle(QH)} of
349        {B1, B2} when B1 =:= badarg; B2 =:= badarg ->
350            erlang:error(badarg, [Fun, Acc0, QH, Options]);
351        {[GUnique, GCache, TmpDir, MaxList, TmpUsage], Handle} ->
352            try
353                Prep = prepare_qlc(Handle, not_a_list, GUnique, GCache,
354                                   TmpDir, MaxList, TmpUsage),
355                case setup_qlc(Prep, #setup{parent = self()}) of
356                    {Objs, Post, _LocalPost} when is_function(Objs);
357                                                  is_list(Objs) ->
358                        try
359                            fold_loop(Fun, Objs, Acc0)
360                        after
361                            post_funs(Post)
362                        end
363                end
364            catch throw:Term:Stacktrace ->
365                case Stacktrace of
366                    [?THROWN_ERROR | _] ->
367                        Term;
368                    _ ->
369                        erlang:raise(throw, Term, Stacktrace)
370                end
371            end
372    end.
373
374-spec(format_error(Error) -> Chars when
375      Error :: {error, module(), term()},
376      Chars :: io_lib:chars()).
377format_error(not_a_query_list_comprehension) ->
378    io_lib:format("argument is not a query list comprehension", []);
379format_error({used_generator_variable, V}) ->
380    io_lib:format("generated variable ~w must not be used in list expression",
381                  [V]);
382format_error(binary_generator) ->
383    io_lib:format("cannot handle binary generators", []);
384format_error(too_complex_join) ->
385    io_lib:format("cannot handle join of three or more generators efficiently",
386                  []);
387format_error(too_many_joins) ->
388    io_lib:format("cannot handle more than one join efficiently", []);
389format_error(nomatch_pattern) ->
390    io_lib:format("pattern cannot possibly match", []);
391format_error(nomatch_filter) ->
392    io_lib:format("filter evaluates to 'false'", []);
393format_error({Location, Mod, Reason}) when is_integer(Location);
394                                           tuple_size(Location) =:= 2 ->
395    io_lib:format("~s: ~ts~n",
396                  [pos(Location), lists:flatten(Mod:format_error(Reason))]);
397%% file_sorter errors
398format_error({bad_object, FileName}) ->
399    io_lib:format("the temporary file \"~ts\" holding answers is corrupt",
400                 [FileName]);
401format_error(bad_object) ->
402    io_lib:format("the keys could not be extracted from some term", []);
403format_error({file_error, FileName, Reason}) ->
404    io_lib:format("\"~ts\": ~tp~n",[FileName, file:format_error(Reason)]);
405format_error({premature_eof, FileName}) ->
406    io_lib:format("\"~ts\": end-of-file was encountered inside some binary term",
407                  [FileName]);
408format_error({tmpdir_usage, Why}) ->
409    io_lib:format("temporary file was needed for ~w~n", [Why]);
410format_error({error, Module, Reason}) ->
411    Module:format_error(Reason);
412format_error(E) ->
413    io_lib:format("~tp~n", [E]).
414
415pos({Line,Col}) ->
416    io_lib:format("~w:~w", [Line,Col]);
417pos(Line) ->
418    io_lib:format("~w", [Line]).
419
420-spec(info(QH) -> Info when
421      QH :: query_handle_or_list(),
422      Info :: abstract_expr() | string()).
423info(QH) ->
424    info(QH, []).
425
426-spec(info(QH, Options) -> Info when
427      QH :: query_handle_or_list(),
428      Options :: [Option] | Option,
429      Option :: EvalOption | ReturnOption,
430      EvalOption :: {cache_all, cache()} | cache_all
431                  | {max_list_size, max_list_size()}
432                  | {tmpdir_usage, tmp_file_usage()}
433                  | {tmpdir, tmp_directory()}
434                  | {unique_all, boolean()} | unique_all,
435      ReturnOption :: {depth, Depth}
436                    | {flat, boolean()}
437                    | {format, Format}
438                    | {n_elements, NElements},
439      Depth :: infinity | non_neg_integer(),
440      Format :: abstract_code | string,
441      NElements :: infinity | pos_integer(),
442      Info :: abstract_expr() | string()).
443info(QH, Options) ->
444    case {options(Options, [unique_all, cache_all, flat, format, n_elements,
445                            depth, tmpdir, max_list_size, tmpdir_usage]),
446          get_handle(QH)} of
447        {B1, B2} when B1 =:= badarg; B2 =:= badarg ->
448            erlang:error(badarg, [QH, Options]);
449        {[GUnique, GCache, Flat, Format, NElements,
450          Depth, TmpDir, MaxList, TmpUsage],
451         H} ->
452            try
453                Prep = prepare_qlc(H, [], GUnique, GCache,
454                                   TmpDir, MaxList, TmpUsage),
455                Info = le_info(Prep, {NElements,Depth}),
456                AbstractCode = abstract(Info, Flat, NElements, Depth),
457                case Format of
458                    abstract_code ->
459                        abstract_code(AbstractCode);
460                    string ->
461                        Hook = fun({special, _Anno, String}, _I, _P, _F) ->
462                                       String
463                               end,
464                        lists:flatten(erl_pp:expr(AbstractCode, 0, Hook));
465                    debug -> % Not documented. Intended for testing only.
466                        Info
467                end
468            catch throw:Term:Stacktrace ->
469                case Stacktrace of
470                    [?THROWN_ERROR | _] ->
471                        Term;
472                    _ ->
473                        erlang:raise(throw, Term, Stacktrace)
474                end
475            end
476    end.
477
478-spec(keysort(KeyPos, QH1) -> QH2 when
479      KeyPos :: key_pos(),
480      QH1 :: query_handle_or_list(),
481      QH2 :: query_handle()).
482keysort(KeyPos, QH) ->
483    keysort(KeyPos, QH, []).
484
485-spec(keysort(KeyPos, QH1, SortOptions) -> QH2 when
486      KeyPos :: key_pos(),
487      SortOptions :: sort_options(),
488      QH1 :: query_handle_or_list(),
489      QH2 :: query_handle()).
490keysort(KeyPos, QH, Options) ->
491    case {is_keypos(KeyPos),
492          options(Options, [tmpdir, order, unique, compressed,
493                            size, no_files]),
494          get_handle(QH)} of
495        {true, [TmpDir, Order, Unique,Compressed | _], H} when H =/= badarg ->
496            #qlc_handle{h = #qlc_sort{h = H, keypos = {keysort,KeyPos},
497                                      unique = Unique,
498                                      compressed = Compressed,
499                                      order = Order,
500                                      fs_opts = listify(Options),
501                                      tmpdir = TmpDir}};
502        _ ->
503            erlang:error(badarg, [KeyPos, QH, Options])
504    end.
505
506-define(DEFAULT_NUM_OF_ANSWERS, 10).
507
508-spec(next_answers(QueryCursor) ->
509            Answers | Error when
510      QueryCursor :: query_cursor(),
511      Answers :: answers(),
512      Error :: {error, module(), Reason},
513      Reason :: file_sorter:reason()).
514next_answers(C) ->
515    next_answers(C, ?DEFAULT_NUM_OF_ANSWERS).
516
517-spec(next_answers(QueryCursor, NumberOfAnswers) ->
518            Answers | Error when
519      QueryCursor :: query_cursor(),
520      Answers :: answers(),
521      NumberOfAnswers :: all_remaining | pos_integer(),
522      Error :: {error, module(), Reason},
523      Reason :: file_sorter:reason()).
524next_answers(#qlc_cursor{c = {_, Owner}}=C,
525             NumOfAnswers) when Owner =/= self() ->
526    erlang:error(not_cursor_owner, [C, NumOfAnswers]);
527next_answers(#qlc_cursor{c = {Pid, _}}=C, NumOfAnswers) ->
528    N = case NumOfAnswers of
529            all_remaining -> -1;
530            _ when is_integer(NumOfAnswers), NumOfAnswers > 0 -> NumOfAnswers;
531            _ -> erlang:error(badarg, [C, NumOfAnswers])
532        end,
533    next_loop(Pid, [], N);
534next_answers(T1, T2) ->
535    erlang:error(badarg, [T1, T2]).
536
537-spec(parse_transform(Forms, Options) -> Forms2 when
538      Forms :: [erl_parse:abstract_form()],
539      Forms2 :: [erl_parse:abstract_form()],
540      Options :: [Option],
541      Option :: type_checker | compile:option()).
542
543parse_transform(Forms, Options) ->
544    qlc_pt:parse_transform(Forms, Options).
545
546-spec parse_transform_info() -> #{'error_location' => 'column'}.
547
548parse_transform_info() ->
549    #{error_location => column}.
550
551%% The funcspecs qlc:q/1 and qlc:q/2 are known by erl_eval.erl and
552%% erl_lint.erl.
553-spec(q(QLC) -> QH when
554      QLC :: query_list_comprehension(),
555      QH :: query_handle()).
556q(QLC_lc) ->
557    q(QLC_lc, []).
558
559-spec(q(QLC, Options) -> QH when
560      QH :: query_handle(),
561      Options :: [Option] | Option,
562      Option :: {max_lookup, MaxLookup}
563              | {cache, cache()} | cache
564              | {join, Join}
565              | {lookup, Lookup}
566              | {unique, boolean()} | unique,
567      MaxLookup :: non_neg_integer() | infinity,
568      Join :: any | lookup | merge | nested_loop,
569      Lookup :: boolean() | any,
570      QLC :: query_list_comprehension()).
571q(#qlc_lc{}=QLC_lc, Options) ->
572    case options(Options, [unique, cache, max_lookup, join, lookup]) of
573        [Unique, Cache, Max, Join, Lookup] ->
574            Opt = #qlc_opt{unique = Unique, cache = Cache,
575                           max_lookup = Max, join = Join, lookup = Lookup},
576            #qlc_handle{h = QLC_lc#qlc_lc{opt = Opt}};
577        _ ->
578            erlang:error(badarg, [QLC_lc, Options])
579    end;
580q(T1, T2) ->
581    erlang:error(badarg, [T1, T2]).
582
583-spec(sort(QH1) -> QH2 when
584      QH1 :: query_handle_or_list(),
585      QH2 :: query_handle()).
586sort(QH) ->
587    sort(QH, []).
588
589-spec(sort(QH1, SortOptions) -> QH2 when
590      SortOptions :: sort_options(),
591      QH1 :: query_handle_or_list(),
592      QH2 :: query_handle()).
593sort(QH, Options) ->
594    case {options(Options, [tmpdir, order, unique, compressed,
595                            size, no_files]), get_handle(QH)} of
596        {B1, B2} when B1 =:= badarg; B2 =:= badarg ->
597            erlang:error(badarg, [QH, Options]);
598        {[TD, Order, Unique, Compressed | _], H} ->
599            #qlc_handle{h = #qlc_sort{h = H, keypos = sort, unique = Unique,
600                                      compressed = Compressed, order = Order,
601                                      fs_opts = listify(Options),
602                                      tmpdir = TD}}
603    end.
604
605%% Note that the generated code is evaluated by (the slow) erl_eval.
606-spec(string_to_handle(QueryString) -> QH | Error when
607      QueryString :: string(),
608      QH :: query_handle(),
609      Error :: {error, module(), Reason},
610      Reason :: erl_parse:error_info() | erl_scan:error_info()).
611string_to_handle(Str) ->
612    string_to_handle(Str, []).
613
614-spec(string_to_handle(QueryString, Options) -> QH | Error when
615      QueryString :: string(),
616      Options :: [Option] | Option,
617      Option :: {max_lookup, MaxLookup}
618              | {cache, cache()} | cache
619              | {join, Join}
620              | {lookup, Lookup}
621              | {unique, boolean()} | unique,
622      MaxLookup :: non_neg_integer() | infinity,
623      Join :: any | lookup | merge | nested_loop,
624      Lookup :: boolean() | any,
625      QH :: query_handle(),
626      Error :: {error, module(), Reason},
627      Reason :: erl_parse:error_info() | erl_scan:error_info()).
628string_to_handle(Str, Options) ->
629    string_to_handle(Str, Options, erl_eval:new_bindings()).
630
631-spec(string_to_handle(QueryString, Options, Bindings) -> QH | Error when
632      QueryString :: string(),
633      Options :: [Option] | Option,
634      Option :: {max_lookup, MaxLookup}
635              | {cache, cache()} | cache
636              | {join, Join}
637              | {lookup, Lookup}
638              | {unique, boolean()} | unique,
639      MaxLookup :: non_neg_integer() | infinity,
640      Join :: any | lookup | merge | nested_loop,
641      Lookup :: boolean() | any,
642      Bindings :: erl_eval:binding_struct(),
643      QH :: query_handle(),
644      Error :: {error, module(), Reason},
645      Reason :: erl_parse:error_info() | erl_scan:error_info()).
646string_to_handle(Str, Options, Bindings) when is_list(Str) ->
647    case options(Options, [unique, cache, max_lookup, join, lookup]) of
648        badarg ->
649            erlang:error(badarg, [Str, Options, Bindings]);
650        [Unique, Cache, MaxLookup, Join, Lookup] ->
651            case erl_scan:string(Str, 1, [text]) of
652                {ok, Tokens, _} ->
653                    ScanRes =
654                        case erl_eval:extended_parse_exprs(Tokens) of
655                            {ok, [Expr0], SBs} ->
656                                {ok, Expr0, SBs};
657                            {ok, _ExprList, _SBs} ->
658                                erlang:error(badarg,
659                                             [Str, Options, Bindings]);
660                            E ->
661                                E
662                        end,
663                    case ScanRes of
664                        {ok, Expr, XBs} ->
665                            Bs1 = merge_binding_structs(Bindings, XBs),
666                            case qlc_pt:transform_expression(Expr, Bs1) of
667                                {ok, {call, _, _QlcQ,  Handle}} ->
668                                    {value, QLC_lc, _} =
669                                        erl_eval:exprs(Handle, Bs1),
670                                    O = #qlc_opt{unique = Unique,
671                                                 cache = Cache,
672                                                 max_lookup = MaxLookup,
673                                                 join = Join,
674                                                 lookup = Lookup},
675                                    #qlc_handle{h = QLC_lc#qlc_lc{opt = O}};
676                                {not_ok, [{error, Error} | _]} ->
677                                    error(Error)
678                            end;
679                        {error, ErrorInfo} ->
680                            error(ErrorInfo)
681                    end;
682                {error, ErrorInfo, _EndLocation} ->
683                    error(ErrorInfo)
684            end
685    end;
686string_to_handle(T1, T2, T3) ->
687    erlang:error(badarg, [T1, T2, T3]).
688
689-spec(table(TraverseFun, Options) -> QH when
690      TraverseFun :: TraverseFun0 | TraverseFun1,
691      TraverseFun0 :: fun(() -> TraverseResult),
692      TraverseFun1 :: fun((match_expression()) -> TraverseResult),
693      TraverseResult :: Objects | term(),
694      Objects :: [] | [term() | ObjectList],
695      ObjectList :: TraverseFun0 | Objects,
696      Options :: [Option] | Option,
697      Option :: {format_fun, FormatFun}
698              | {info_fun, InfoFun}
699              | {lookup_fun, LookupFun}
700              | {parent_fun, ParentFun}
701              | {post_fun, PostFun}
702              | {pre_fun, PreFun}
703              | {key_equality, KeyComparison},
704      FormatFun :: undefined  | fun((SelectedObjects) -> FormatedTable),
705      SelectedObjects :: all
706                       | {all, NElements, DepthFun}
707                       | {match_spec, match_expression()}
708                       | {lookup, Position, Keys}
709                       | {lookup, Position, Keys, NElements, DepthFun},
710      NElements :: infinity | pos_integer(),
711      DepthFun :: fun((term()) -> term()),
712      FormatedTable :: {Mod, Fun, Args}
713                     | abstract_expr()
714                     | string(),
715      InfoFun :: undefined  | fun((InfoTag) -> InfoValue),
716      InfoTag :: indices | is_unique_objects | keypos | num_of_objects,
717      InfoValue :: undefined  | term(),
718      LookupFun :: undefined  | fun((Position, Keys) -> LookupResult),
719      LookupResult :: [term()] | term(),
720      ParentFun :: undefined  | fun(() -> ParentFunValue),
721      PostFun :: undefined  | fun(() -> term()),
722      PreFun :: undefined  | fun((PreArgs) -> term()),
723      PreArgs :: [PreArg],
724      PreArg :: {parent_value, ParentFunValue}  | {stop_fun, StopFun},
725      ParentFunValue :: undefined  | term(),
726      StopFun :: undefined  | fun(() -> term()),
727      KeyComparison :: '=:=' | '==',
728      Position :: pos_integer(),
729      Keys :: [term()],
730      Mod :: atom(),
731      Fun :: atom(),
732      Args :: [term()],
733      QH :: query_handle()).
734table(TraverseFun, Options) when is_function(TraverseFun) ->
735    case {is_function(TraverseFun, 0),
736          IsFun1 = is_function(TraverseFun, 1)} of
737        {false, false} ->
738            erlang:error(badarg, [TraverseFun, Options]);
739        _ ->
740            case options(Options, [pre_fun, post_fun, info_fun, format_fun,
741                                   lookup_fun, parent_fun, key_equality]) of
742                [PreFun, PostFun, InfoFun, FormatFun, LookupFun, ParentFun,
743                 KeyEquality] ->
744                    T = #qlc_table{trav_fun = TraverseFun, pre_fun = PreFun,
745                                   post_fun = PostFun, info_fun = InfoFun,
746                                   parent_fun = ParentFun,
747                                   trav_MS = IsFun1,
748                                   format_fun = FormatFun,
749                                   lookup_fun = LookupFun,
750                                   key_equality = KeyEquality},
751                    #qlc_handle{h = T};
752                badarg ->
753                    erlang:error(badarg, [TraverseFun, Options])
754            end
755    end;
756table(T1, T2) ->
757    erlang:error(badarg, [T1, T2]).
758
759-spec(transform_from_evaluator(LC, Bs) -> Return when
760      LC :: abstract_expr(),
761      Bs :: erl_eval:binding_struct(),
762      Return :: {ok, abstract_expr()}
763              | {not_ok, {error, module(), Reason :: term()}}).
764
765transform_from_evaluator(LC, Bs0) ->
766    qlc_pt:transform_from_evaluator(LC, Bs0).
767
768-define(TEMPLATE_STATE, 1).
769
770template_state() ->
771    ?TEMPLATE_STATE.
772
773aux_name(Name, N, AllNames) ->
774    {VN, _} = aux_name1(Name, N, AllNames),
775    VN.
776
777name_suffix(A, Suff) ->
778    list_to_atom(lists:concat([A, Suff])).
779
780vars(E) ->
781    var_ufold(fun({var,_A,V}) -> V end, E).
782
783var_ufold(F, E) ->
784    ordsets:from_list(var_fold(F, [], E)).
785
786all_selections([]) ->
787    [[]];
788all_selections([{I,Cs} | ICs]) ->
789    [[{I,C} | L] || C <- Cs, L <- all_selections(ICs)].
790
791%%%
792%%% Local functions
793%%%
794
795merge_binding_structs(Bs1, Bs2) ->
796    lists:foldl(fun({N, V}, Bs) -> erl_eval:add_binding(N, V, Bs)
797                end, Bs1, erl_eval:bindings(Bs2)).
798
799aux_name1(Name, N, AllNames) ->
800    SN = name_suffix(Name, N),
801    case gb_sets:is_member(SN, AllNames) of
802        true -> aux_name1(Name, N + 1, AllNames);
803        false -> {SN, N}
804    end.
805
806var_fold(F, A, {var,_,V}=Var) when V =/= '_' ->
807    [F(Var) | A];
808var_fold(F, A, T) when is_tuple(T) ->
809    var_fold(F, A, tuple_to_list(T));
810var_fold(F, A, [E | Es]) ->
811    var_fold(F, var_fold(F, A, E), Es);
812var_fold(_F, A, _T) ->
813    A.
814
815options(Options, Keys) when is_list(Options) ->
816    options(Options, Keys, []);
817options(Option, Keys) ->
818    options([Option], Keys, []).
819
820options(Options0, [Key | Keys], L) when is_list(Options0) ->
821    Options = case lists:member(Key, Options0) of
822                  true ->
823                      [atom_option(Key) | lists:delete(Key, Options0)];
824                  false ->
825                      Options0
826              end,
827    V = case lists:keyfind(Key, 1, Options) of
828            {format_fun, U=undefined} ->
829                {ok, U};
830            {info_fun, U=undefined} ->
831                {ok, U};
832            {lookup_fun, U=undefined} ->
833                {ok, U};
834            {parent_fun, U=undefined} ->
835                {ok, U};
836            {post_fun, U=undefined} ->
837                {ok, U};
838            {pre_fun, U=undefined} ->
839                {ok, U};
840            {info_fun, Fun} when is_function(Fun, 1) ->
841                {ok, Fun};
842            {pre_fun, Fun} when is_function(Fun, 1) ->
843                {ok, Fun};
844            {post_fun, Fun} when is_function(Fun, 0) ->
845                {ok, Fun};
846            {lookup_fun, Fun} when is_function(Fun, 2) ->
847                {ok, Fun};
848            {max_lookup, Max} when is_integer(Max), Max >= 0 ->
849                {ok, Max};
850            {max_lookup, infinity} ->
851                {ok, -1};
852            {format_fun, Fun} when is_function(Fun, 1) ->
853                {ok, Fun};
854            {parent_fun, Fun} when is_function(Fun, 0) ->
855                {ok, Fun};
856            {key_equality, KE='=='} ->
857                {ok, KE};
858            {key_equality, KE='=:='} ->
859                {ok, KE};
860            {join, J=any} ->
861                {ok, J};
862            {join, J=nested_loop} ->
863                {ok, J};
864            {join, J=merge} ->
865                {ok, J};
866            {join, J=lookup} ->
867                {ok, J};
868            {lookup, LookUp} when is_boolean(LookUp); LookUp =:= any ->
869                {ok, LookUp};
870            {max_list_size, Max} when is_integer(Max), Max >= 0 ->
871                {ok, Max};
872            {tmpdir_usage, TmpUsage} when TmpUsage =:= allowed;
873                                          TmpUsage =:= not_allowed;
874                                          TmpUsage =:= info_msg;
875                                          TmpUsage =:= warning_msg;
876                                          TmpUsage =:= error_msg ->
877                {ok, TmpUsage};
878            {unique, Unique} when is_boolean(Unique) ->
879                {ok, Unique};
880            {cache, Cache} when is_boolean(Cache); Cache =:= list ->
881                {ok, Cache};
882            {cache, ets} ->
883                {ok, true};
884            {cache, no} ->
885                {ok, false};
886            {unique_all, UniqueAll} when is_boolean(UniqueAll) ->
887                {ok, UniqueAll};
888            {cache_all, CacheAll} when is_boolean(CacheAll);
889                                       CacheAll =:= list ->
890                {ok, CacheAll};
891            {cache_all, ets} ->
892                {ok, true};
893            {cache_all, no} ->
894                {ok, false};
895            {spawn_options, default} ->
896                {ok, default};
897            {spawn_options, SpawnOptions} ->
898                case is_proper_list(SpawnOptions) of
899                    true ->
900                        {ok, SpawnOptions};
901                    false ->
902                        badarg
903                end;
904            {flat, Flat} when is_boolean(Flat) ->
905                {ok, Flat};
906            {format, Format} when Format =:= string;
907                                  Format =:= abstract_code;
908                                  Format =:= debug ->
909                {ok, Format};
910            {n_elements, NElements} when NElements =:= infinity;
911                                         is_integer(NElements),
912                                         NElements > 0 ->
913                {ok, NElements};
914            {depth, Depth} when Depth =:= infinity;
915                                is_integer(Depth), Depth >= 0 ->
916                {ok, Depth};
917            {order, Order} when is_function(Order, 2);
918                                (Order =:= ascending);
919                                (Order =:= descending) ->
920                {ok, Order};
921            {compressed, Comp} when Comp ->
922                {ok, [compressed]};
923            {compressed, Comp} when not Comp ->
924                {ok, []};
925            {tmpdir, T} ->
926                {ok, T};
927            {size, Size} when is_integer(Size), Size > 0 ->
928                {ok, Size};
929            {no_files, NoFiles} when is_integer(NoFiles), NoFiles > 1 ->
930                {ok, NoFiles};
931            {Key, _} ->
932                badarg;
933            false ->
934                Default = default_option(Key),
935                {ok, Default}
936        end,
937    case V of
938        badarg ->
939            badarg;
940        {ok, Value} ->
941            NewOptions = lists:keydelete(Key, 1, Options),
942            options(NewOptions, Keys, [Value | L])
943    end;
944options([], [], L) ->
945    lists:reverse(L);
946options(_Options, _, _L) ->
947    badarg.
948
949default_option(pre_fun) -> undefined;
950default_option(post_fun) -> undefined;
951default_option(info_fun) -> undefined;
952default_option(format_fun) -> undefined;
953default_option(lookup_fun) -> undefined;
954default_option(max_lookup) -> -1;
955default_option(join) -> any;
956default_option(lookup) -> any;
957default_option(parent_fun) -> undefined;
958default_option(key_equality) -> '=:=';
959default_option(spawn_options) -> default;
960default_option(flat) -> true;
961default_option(format) -> string;
962default_option(n_elements) -> infinity;
963default_option(depth) -> infinity;
964default_option(max_list_size) -> ?MAX_LIST_SIZE;
965default_option(tmpdir_usage) -> allowed;
966default_option(cache) -> false;
967default_option(cache_all) -> false;
968default_option(unique) -> false;
969default_option(unique_all) -> false;
970default_option(order) -> ascending; % default values from file_sorter.erl
971default_option(compressed) -> [];
972default_option(tmpdir) -> "";
973default_option(size) -> 524288;
974default_option(no_files) -> 16.
975
976atom_option(cache) -> {cache, true};
977atom_option(unique) -> {unique, true};
978atom_option(cache_all) -> {cache_all, true};
979atom_option(unique_all) -> {unique_all, true};
980atom_option(lookup) -> {lookup, true};
981atom_option(flat) -> {flat, true};
982atom_option(Key) -> Key.
983
984is_proper_list([_ | L]) ->
985    is_proper_list(L);
986is_proper_list(L) ->
987    L =:= [].
988
989spawn_options(default) ->
990    [link];
991spawn_options(SpawnOptions) ->
992    lists:delete(monitor,
993                 case lists:member(link, SpawnOptions) of
994                     true ->
995                         SpawnOptions;
996                     false ->
997                         [link | SpawnOptions]
998                 end).
999
1000is_keypos(Keypos) when is_integer(Keypos), Keypos > 0 ->
1001    true;
1002is_keypos([]) ->
1003    false;
1004is_keypos(L) ->
1005    is_keyposs(L).
1006
1007is_keyposs([Kp | Kps]) when is_integer(Kp), Kp > 0 ->
1008    is_keyposs(Kps);
1009is_keyposs(Kps) ->
1010    Kps =:= [].
1011
1012listify(L) when is_list(L) ->
1013    L;
1014listify(T) ->
1015    [T].
1016
1017%% Optimizations to be carried out.
1018-record(optz,
1019        {unique = false,    % boolean()
1020         cache = false,     % boolean() | list
1021         join_option = any, % constraint set by the 'join' option
1022         fast_join = no,    % no | #qlc_join. 'no' means nested loop.
1023         opt                % #qlc_opt
1024        }).
1025
1026%% Prepared #qlc_lc.
1027-record(qlc,
1028        {lcf,       % fun() -> Val
1029         codef,
1030         qdata,     % with evaluated list expressions
1031         init_value,
1032         optz       % #optz
1033        }).
1034
1035%% Prepared simple #qlc_lc.
1036-record(simple_qlc,
1037        {p,         % atom(), pattern variable
1038         le,
1039         anno :: erl_anno:anno(),
1040         init_value,
1041         optz       % #optz
1042         }).
1043
1044-record(prepared,
1045        {qh,     % #qlc_append | #qlc_table | #qlc | #simple_qlc |
1046                 % #qlc_sort | list()
1047         sorted = no,  % yes | no | ascending | descending
1048         sort_info = [], %
1049         sort_info2 = [], % 'sort_info' updated with pattern info; qh is LE
1050         lu_skip_quals = [], % qualifiers to skip due to lookup
1051         join = {[],[]},  % {Lookup, Merge}
1052         n_objs = undefined,   % for join (not used yet)
1053         is_unique_objects = false, % boolean()
1054         is_cached = false          % boolean() (true means 'ets' or 'list')
1055        }).
1056
1057%%% Cursor process functions.
1058
1059cursor_process(H, GUnique, GCache, TmpDir, SpawnOptions, MaxList, TmpUsage) ->
1060    Parent = self(),
1061    Setup = #setup{parent = Parent},
1062    CF = fun() ->
1063                 %% Unless exit/2 is trapped no cleanup can be done.
1064                 %% The user is assumed not to set the flag to false.
1065                 process_flag(trap_exit, true),
1066                 MonRef = erlang:monitor(process, Parent),
1067                 {Objs, Post, _LocalPost} =
1068                     try
1069                         Prep = prepare_qlc(H, not_a_list, GUnique, GCache,
1070                                            TmpDir, MaxList, TmpUsage),
1071                         setup_qlc(Prep, Setup)
1072                     catch Class:Reason:Stacktrace ->
1073                           Parent ! {self(),
1074                                     {caught, Class, Reason, Stacktrace}},
1075                           exit(normal)
1076                     end,
1077                 Parent ! {self(), ok},
1078                 wait_for_request(Parent, MonRef, Post),
1079                 reply(Parent, MonRef, Post, Objs)
1080         end,
1081    Pid = spawn_opt(CF, SpawnOptions),
1082    parent_fun(Pid, Parent).
1083
1084%% Expect calls from tables calling the parent_fun and finally an 'ok'.
1085parent_fun(Pid, Parent) ->
1086    receive
1087        {Pid, ok} -> Pid;
1088        {TPid, {parent_fun, Fun}} ->
1089            V = try
1090                    {value, Fun()}
1091                catch Class:Reason:Stacktrace ->
1092                    {parent_fun_caught, Class, Reason, Stacktrace}
1093            end,
1094            TPid ! {Parent, V},
1095            parent_fun(Pid, Parent);
1096        {Pid, {caught, throw, Error, [?THROWN_ERROR | _]}} ->
1097            Error;
1098        {Pid, {caught, Class, Reason, Stacktrace}} ->
1099            erlang:raise(Class, Reason, Stacktrace)
1100    end.
1101
1102reply(Parent, MonRef, Post, []) ->
1103    no_more(Parent, MonRef, Post);
1104reply(Parent, MonRef, Post, [Answer | Cont]) ->
1105    Parent ! {self(), {answer, Answer}},
1106    wait_for_request(Parent, MonRef, Post),
1107    reply(Parent, MonRef, Post, Cont);
1108reply(Parent, MonRef, Post, Cont) ->
1109    Reply = try
1110                if
1111                    is_function(Cont) ->
1112                        Cont();
1113                    true ->
1114                        throw_error(Cont)
1115                end
1116            catch
1117                Class:Reason:Stacktrace ->
1118                   post_funs(Post),
1119                   Message = {caught, Class, Reason, Stacktrace},
1120                   Parent ! {self(), Message},
1121                   exit(normal)
1122            end,
1123    reply(Parent, MonRef, Post, Reply).
1124
1125no_more(Parent, MonRef, Post) ->
1126    Parent ! {self(), no_more},
1127    wait_for_request(Parent, MonRef, Post),
1128    no_more(Parent, MonRef, Post).
1129
1130wait_for_request(Parent, MonRef, Post) ->
1131    receive
1132        {Parent, stop} ->
1133            post_funs(Post),
1134            exit(normal);
1135        {Parent, more} ->
1136            ok;
1137        {'EXIT', Parent, _Reason} ->
1138            post_funs(Post),
1139            exit(normal);
1140        {'DOWN', MonRef, process, Parent, _Info} ->
1141            post_funs(Post),
1142            exit(normal);
1143        {'EXIT', Pid, _Reason} when Pid =:= self() ->
1144            %% Trapped signal. The cursor ignores it...
1145            wait_for_request(Parent, MonRef, Post);
1146        Other ->
1147            error_logger:error_msg(
1148              "The qlc cursor ~w received an unexpected message:\n~tp\n",
1149              [self(), Other]),
1150            wait_for_request(Parent, MonRef, Post)
1151    end.
1152
1153%%% End of cursor process functions.
1154
1155abstract_code({special, Anno, String}) ->
1156    {string, Anno, String};
1157abstract_code(Tuple) when is_tuple(Tuple) ->
1158    list_to_tuple(abstract_code(tuple_to_list(Tuple)));
1159abstract_code([H | T]) ->
1160    [abstract_code(H) | abstract_code(T)];
1161abstract_code(Term) ->
1162    Term.
1163
1164%% Also in qlc_pt.erl.
1165-define(Q, q).
1166-define(QLC_Q(A1, A2, A3, A4, LC, Os),
1167        {call,A1,{remote,A2,{atom,A3,?MODULE},{atom,A4,?Q}},[LC | Os]}).
1168
1169abstract(Info, false=_Flat, NElements, Depth) ->
1170    abstract(Info, NElements, Depth);
1171abstract(Info, true=_Flat, NElements, Depth) ->
1172    Abstract = abstract(Info, NElements, Depth),
1173    Vars = abstract_vars(Abstract),
1174    {_, Body0, Expr} = flatten_abstr(Abstract, 1, Vars, []),
1175    case Body0 of
1176        [] ->
1177            Expr;
1178        [{match,_,Expr,Q}] ->
1179            Q;
1180        [{match,_,Expr,Q} | Body] ->
1181            {block, anno0(), lists:reverse(Body, [Q])};
1182        _ ->
1183            {block, anno0(), lists:reverse(Body0, [Expr])}
1184    end.
1185
1186abstract(Info, NElements, Depth) ->
1187    abstract1(Info, NElements, Depth, anno1()).
1188
1189abstract1({qlc, E0, Qs0, Opt}, NElements, Depth, A) ->
1190    Qs = lists:map(fun({generate, P, LE}) ->
1191                           {generate, A, binary_to_term(P),
1192                            abstract1(LE, NElements, Depth, A)};
1193                      (F) ->
1194                           binary_to_term(F)
1195                   end, Qs0),
1196    E = binary_to_term(E0),
1197    Os = case Opt of
1198             [] -> [];
1199             _ -> [abstract_term(Opt, 1)]
1200         end,
1201    ?QLC_Q(A, A, A, A, {lc,A,E,Qs}, Os);
1202abstract1({table, {M, F, As0}}, _NElements, _Depth, Anno)
1203                          when is_atom(M), is_atom(F), is_list(As0) ->
1204    As = [abstract_term(A, 1) || A <- As0],
1205    {call, Anno, {remote, Anno, {atom, Anno, M}, {atom, Anno, F}}, As};
1206abstract1({table, TableDesc}, _NElements, _Depth, _A) ->
1207    case io_lib:deep_char_list(TableDesc) of
1208        true ->
1209            {ok, Tokens, _} =
1210                erl_scan:string(lists:flatten(TableDesc++"."), 1, [text]),
1211            {ok, Es, Bs} =
1212                erl_eval:extended_parse_exprs(Tokens),
1213            [Expr] = erl_eval:subst_values_for_vars(Es, Bs),
1214            special(Expr);
1215        false -> % abstract expression
1216            TableDesc
1217    end;
1218abstract1({append, Infos}, NElements, Depth, A) ->
1219    As = lists:foldr(fun(Info, As0) ->
1220                             {cons,A,abstract1(Info, NElements, Depth, A),
1221                              As0}
1222                     end, {nil, A}, Infos),
1223    {call, A, {remote, A, {atom, A, ?MODULE}, {atom, A, append}}, [As]};
1224abstract1({sort, Info, SortOptions}, NElements, Depth, A) ->
1225    {call, A, {remote, A, {atom, A, ?MODULE}, {atom, A, sort}},
1226     [abstract1(Info, NElements, Depth, A), abstract_term(SortOptions, 1)]};
1227abstract1({keysort, Info, Kp, SortOptions}, NElements, Depth, A) ->
1228    {call, A, {remote, A, {atom, A, ?MODULE}, {atom, A, keysort}},
1229     [abstract_term(Kp, 1), abstract1(Info, NElements, Depth, A),
1230      abstract_term(SortOptions, 1)]};
1231abstract1({list,L,MS}, NElements, Depth, A) ->
1232    {call, A, {remote, A, {atom, A, ets}, {atom, A, match_spec_run}},
1233     [abstract1(L, NElements, Depth, A),
1234      {call, A, {remote, A, {atom, A, ets}, {atom, A, match_spec_compile}},
1235       [abstract_term(depth(MS, Depth), 1)]}]};
1236abstract1({list, L}, NElements, Depth, _A) when NElements =:= infinity;
1237                                                NElements >= length(L) ->
1238    abstract_term(depth(L, Depth), 1);
1239abstract1({list, L}, NElements, Depth, _A) ->
1240    abstract_term(depth(lists:sublist(L, NElements), Depth) ++ '...', 1).
1241
1242special({value, _, Thing}) ->
1243    abstract_term(Thing);
1244special(Tuple) when is_tuple(Tuple) ->
1245    list_to_tuple(special(tuple_to_list(Tuple)));
1246special([E|Es]) ->
1247    [special(E)|special(Es)];
1248special(Expr) ->
1249    Expr.
1250
1251depth(List, infinity) ->
1252    List;
1253depth(List, Depth) ->
1254    [depth1(E, Depth) || E <- List].
1255
1256depth_fun(infinity = _Depth) ->
1257    fun(E) -> E end;
1258depth_fun(Depth) ->
1259    fun(E) -> depth1(E, Depth) end.
1260
1261depth1([]=L, _D) ->
1262    L;
1263depth1(_Term, 0) ->
1264    '...';
1265depth1(Tuple, D) when is_tuple(Tuple) ->
1266    depth_tuple(Tuple, tuple_size(Tuple), 1, D - 1, []);
1267depth1(List, D) when is_list(List) ->
1268    if
1269        D =:= 1 ->
1270            ['...'];
1271        true ->
1272            depth_list(List, D - 1)
1273    end;
1274depth1(Binary, D) when byte_size(Binary) > D - 1 ->
1275    D1 = D - 1,
1276    <<Bin:D1/bytes,_/bytes>> = Binary,
1277    <<Bin/bytes,"...">>;
1278depth1(T, _Depth) ->
1279    T.
1280
1281depth_list([]=L, _D) ->
1282    L;
1283depth_list(_L, 0) ->
1284    '...';
1285depth_list([E | Es], D) ->
1286    [depth1(E, D) | depth_list(Es, D - 1)].
1287
1288depth_tuple(_Tuple, Sz, I, _D, L) when I > Sz ->
1289    list_to_tuple(lists:reverse(L));
1290depth_tuple(_L, _Sz, _I, 0, L) ->
1291    list_to_tuple(lists:reverse(L, ['...']));
1292depth_tuple(Tuple, Sz, I, D, L) ->
1293    E = depth1(element(I, Tuple), D),
1294    depth_tuple(Tuple, Sz, I + 1, D - 1, [E | L]).
1295
1296abstract_term(Term) ->
1297    abstract_term(Term, 0).
1298
1299abstract_term(Term, Line) ->
1300    abstr_term(Term, anno(Line)).
1301
1302abstr_term(Tuple, Anno) when is_tuple(Tuple) ->
1303    {tuple,Anno,[abstr_term(E, Anno) || E <- tuple_to_list(Tuple)]};
1304abstr_term([_ | _]=L, Anno) ->
1305    case io_lib:char_list(L) of
1306        true ->
1307            erl_parse:abstract(L, erl_anno:line(Anno));
1308        false ->
1309            abstr_list(L, Anno)
1310    end;
1311abstr_term(Fun, Anno) when is_function(Fun) ->
1312    case erl_eval:fun_data(Fun) of
1313        {fun_data, _Bs, Cs} ->
1314            {'fun', Anno, {clauses, Cs}};
1315        {named_fun_data, _Bs, Name, Cs} ->
1316            {named_fun, Anno, Name, Cs};
1317        false ->
1318            {name, Name} = erlang:fun_info(Fun, name),
1319            {arity, Arity} = erlang:fun_info(Fun, arity),
1320            case erlang:fun_info(Fun, type) of
1321                {type, external} ->
1322                    {module, Module} = erlang:fun_info(Fun, module),
1323                    {'fun', Anno, {function,
1324				   {atom,Anno,Module},
1325				   {atom,Anno,Name},
1326				   {integer,Anno,Arity}}};
1327                {type, local} ->
1328                    {'fun', Anno, {function,Name,Arity}}
1329            end
1330    end;
1331abstr_term(PPR, Anno) when is_pid(PPR); is_port(PPR); is_reference(PPR) ->
1332    {special, Anno, lists:flatten(io_lib:write(PPR))};
1333abstr_term(Map, Anno) when is_map(Map) ->
1334    {map,Anno,
1335     [{map_field_assoc,Anno,abstr_term(K, Anno),abstr_term(V, Anno)} ||
1336         {K,V} <- maps:to_list(Map)]};
1337abstr_term(Simple, Anno) ->
1338    erl_parse:abstract(Simple, erl_anno:line(Anno)).
1339
1340abstr_list([H | T], Anno) ->
1341    {cons, Anno, abstr_term(H, Anno), abstr_list(T, Anno)};
1342abstr_list(T, Anno) ->
1343    abstr_term(T, Anno).
1344
1345%% Since generator pattern variables cannot be used in list
1346%% expressions, it is OK to flatten out QLCs using temporary
1347%% variables.
1348flatten_abstr(?QLC_Q(A1, A2, A3, A4, LC0, Os), VN0, Vars, Body0) ->
1349    {lc,Anno,E,Qs0} = LC0,
1350    F = fun({generate,AnnoG,P,LE0}, {VN1,Body1}) ->
1351                {VN2,Body2,LE} = flatten_abstr(LE0, VN1, Vars, Body1),
1352                {{generate,AnnoG,P,LE}, {VN2,Body2}};
1353           (Fil, VN_Body) ->
1354                {Fil, VN_Body}
1355        end,
1356    {Qs, {VN3,Body}} = lists:mapfoldl(F, {VN0,Body0}, Qs0),
1357    LC = {lc,Anno,E,Qs},
1358    {V, VN} = aux_name1('V', VN3, Vars),
1359    Var = {var, A1, V},
1360    QLC = ?QLC_Q(A1, A2, A3, A4, LC, Os),
1361    {VN + 1, [{match, A1, Var, QLC} | Body], Var};
1362flatten_abstr(T0, VN0, Vars, Body0) when is_tuple(T0) ->
1363    {VN, Body, L} = flatten_abstr(tuple_to_list(T0), VN0, Vars, Body0),
1364    {VN, Body, list_to_tuple(L)};
1365flatten_abstr([E0 | Es0], VN0, Vars, Body0) ->
1366    {VN1, Body1, E} = flatten_abstr(E0, VN0, Vars, Body0),
1367    {VN, Body, Es} = flatten_abstr(Es0, VN1, Vars, Body1),
1368    {VN, Body, [E | Es]};
1369flatten_abstr(E, VN, _Vars, Body) ->
1370    {VN, Body, E}.
1371
1372abstract_vars(Abstract) ->
1373    gb_sets:from_list(ordsets:to_list(vars(Abstract))).
1374
1375collect([]=L) ->
1376    L;
1377collect([Answer | Cont]) ->
1378    [Answer | collect(Cont)];
1379collect(Cont) ->
1380    case Cont() of
1381        Answers when is_list(Answers) ->
1382            collect(Answers);
1383        Term ->
1384            throw_error(Term)
1385    end.
1386
1387fold_loop(Fun, [Obj | Cont], Acc) ->
1388    fold_loop(Fun, Cont, Fun(Obj, Acc));
1389fold_loop(_Fun, [], Acc) ->
1390    Acc;
1391fold_loop(Fun, Cont, Acc) ->
1392    case Cont() of
1393        Objects when is_list(Objects) ->
1394            fold_loop(Fun, Objects, Acc);
1395        Term ->
1396            Term
1397    end.
1398
1399next_loop(Pid, L, N) when N =/= 0 ->
1400    case monitor_request(Pid, more) of
1401        no_more ->
1402            lists:reverse(L);
1403        {answer, Answer} ->
1404            next_loop(Pid, [Answer | L], N - 1);
1405        {caught, throw, Error, [?THROWN_ERROR | _]} ->
1406            Error;
1407        {caught, Class, Reason, Stacktrace} ->
1408            {current_stacktrace, CurrentStacktrace} =
1409                erlang:process_info(self(), current_stacktrace),
1410            erlang:raise(Class, Reason, Stacktrace ++ CurrentStacktrace);
1411        error ->
1412            erlang:error({qlc_cursor_pid_no_longer_exists, Pid})
1413    end;
1414next_loop(_Pid, L, _N) ->
1415    lists:reverse(L).
1416
1417stop_cursor(Pid) ->
1418    erlang:monitor(process, Pid),
1419    unlink(Pid),
1420    receive
1421        {'EXIT',Pid,_Reason} -> % Simply ignore the error.
1422            receive
1423                {'DOWN',_,process,Pid,_} -> ok
1424            end
1425    after 0 ->
1426            Pid ! {self(),stop},
1427            receive
1428                {'DOWN',_,process,Pid,_} -> ok
1429            end
1430    end.
1431
1432monitor_request(Pid, Req) ->
1433    Ref = erlang:monitor(process, Pid),
1434    Pid ! {self(), Req},
1435    receive
1436        {'DOWN', Ref, process, Pid, _Info} ->
1437            receive
1438                {'EXIT', Pid, _Reason} -> ok
1439            after 1 -> ok end,
1440            error;
1441        {'EXIT', Pid, _Reason} ->
1442            receive
1443                {'DOWN', _, process, Pid, _} -> error
1444            end;
1445        {Pid, Reply} ->
1446            erlang:demonitor(Ref, [flush]),
1447            Reply
1448    end.
1449
1450%% Marker for skipped filter or unused generator.
1451-define(SKIP, (-1)).
1452
1453%% Qual = {gen, LE} | fil
1454-define(qual_data(QNum, GoToIndex, State, Qual),
1455        {QNum, GoToIndex, State, Qual}).
1456
1457-record(join, % generated by qlc_pt
1458        {op, q1, q2, wh1, wh2, cs_fun}). % op is unused
1459
1460%% le_info/1 returns an intermediate information format only used for
1461%% testing purposes. Changes will happen without notice.
1462%%
1463%% QueryDesc = {qlc, TemplateDesc, [QualDesc], [QueryOpt]}
1464%%           | {table, TableDesc}
1465%%           | {append, [QueryDesc]}
1466%%           | {sort, QueryDesc, [sort_option()]}
1467%%           | {keysort, key_pos(), QueryDesc, [sort_option()]}
1468%%           | {list, list()}
1469%%           | {list, QueryDesc, match_expression()}
1470%% TableDesc = {Mod, Fun, Args}
1471%%           | erl_parse:abstract_expr()
1472%%           | string()
1473%% Mod = module()
1474%% Fun = atom()
1475%% Args = [term()]
1476%% QualDesc = FilterDesc
1477%%          | {generate, PatternDesc, QueryDesc}
1478%% QueryOpt = {cache, boolean()} | cache
1479%%          | {unique, boolean()} | unique
1480%% FilterDesc = PatternDesc = TemplateDesc = binary()
1481
1482le_info(#prepared{qh = #simple_qlc{le = LE, p = P, anno = Anno, optz = Optz}},
1483        InfOpt) ->
1484    QVar = term_to_binary({var, Anno, P}),
1485    {qlc, QVar, [{generate, QVar, le_info(LE, InfOpt)}], opt_info(Optz)};
1486le_info(#prepared{qh = #qlc{codef = CodeF, qdata = Qdata, optz = Optz}},
1487        InfOpt) ->
1488    Code = CodeF(),
1489    TemplateState = template_state(),
1490    E = element(TemplateState, Code),
1491    QualInfo0 = qual_info(Qdata, Code, InfOpt),
1492    QualInfo1 = case Optz#optz.fast_join of
1493                    #qlc_join{} = Join ->
1494                        join_info(Join, QualInfo0, Qdata, Code);
1495                    no ->
1496                        QualInfo0
1497                end,
1498    QualInfo = [I || I <- QualInfo1, I =/= skip],
1499    {qlc, E, QualInfo, opt_info(Optz)};
1500le_info(#prepared{qh = #qlc_table{format_fun = FormatFun, trav_MS = TravMS,
1501                                  ms = MS, lu_vals = LuVals}}, InfOpt) ->
1502    {NElements, Depth} = InfOpt,
1503    %% The 'depth' option applies to match specifications as well.
1504    %% This is for limiting imported variables (parameters).
1505    DepthFun = depth_fun(Depth),
1506    case LuVals of
1507        _ when FormatFun =:= undefined ->
1508            {table, {'$MOD', '$FUN', []}};
1509        {Pos, Vals} ->
1510            Formated = try FormatFun({lookup, Pos, Vals, NElements, DepthFun})
1511                       catch _:_ -> FormatFun({lookup, Pos, Vals})
1512                       end,
1513            if
1514                MS =:= no_match_spec ->
1515                    {table, Formated};
1516                true ->
1517                    {list, {table, Formated}, depth(MS, Depth)}
1518            end;
1519        _ when TravMS, is_list(MS) ->
1520            {table, FormatFun({match_spec, depth(MS, Depth)})};
1521        _ when MS =:= no_match_spec ->
1522            try {table, FormatFun({all, NElements, DepthFun})}
1523            catch _:_ -> {table, FormatFun(all)}
1524            end
1525    end;
1526le_info(#prepared{qh = #qlc_append{hl = HL}}, InfOpt) ->
1527    {append, [le_info(H, InfOpt) || H <- HL]};
1528le_info(#prepared{qh = #qlc_sort{h = H, keypos = sort,
1529                                 fs_opts = SortOptions0, tmpdir = TmpDir}},
1530        InfOpt) ->
1531    SortOptions = sort_options_global_tmp(SortOptions0, TmpDir),
1532    {sort, le_info(H, InfOpt), SortOptions};
1533le_info(#prepared{qh = #qlc_sort{h = H, keypos = {keysort, Kp},
1534                                 fs_opts = SortOptions0, tmpdir = TmpDir}},
1535        InfOpt) ->
1536    SortOptions = sort_options_global_tmp(SortOptions0, TmpDir),
1537    {keysort, le_info(H, InfOpt), Kp, SortOptions};
1538le_info(#prepared{qh = #qlc_list{l = L, ms = no_match_spec}}, _InfOpt) ->
1539    {list, L};
1540le_info(#prepared{qh = #qlc_list{l = L, ms = MS}},_InfOpt) when is_list(L) ->
1541    {list, {list, L}, MS};
1542le_info(#prepared{qh = #qlc_list{l = L, ms = MS}}, InfOpt) ->
1543    {list, le_info(L, InfOpt), MS}.
1544
1545qual_info([?qual_data(_QNum, _GoI, ?SKIP, fil) | Qdata], Code, InfOpt) ->
1546    %% see skip_lookup_filters()
1547    [skip | qual_info(Qdata, Code, InfOpt)];
1548qual_info([?qual_data(QNum, _GoI, _SI, fil) | Qdata], Code, InfOpt) ->
1549    [element(QNum + 1, Code) | qual_info(Qdata, Code, InfOpt)];
1550qual_info([?qual_data(_QNum, _GoI, _SI, {gen,#join{}}) | Qdata],
1551          Code, InfOpt) ->
1552    [skip | qual_info(Qdata, Code, InfOpt)];
1553qual_info([?qual_data(QNum, _GoI, _SI, {gen,LE}) | Qdata], Code, InfOpt) ->
1554    [{generate,element(QNum + 1, Code),le_info(LE, InfOpt)} |
1555     qual_info(Qdata, Code, InfOpt)];
1556qual_info([], _Code, _InfOpt) ->
1557    [].
1558
1559join_info(Join, QInfo, Qdata, Code) ->
1560    #qlc_join{kind = Kind, q1 = QNum1a, c1 = C1, q2 = QNum2a, c2 = C2,
1561              opt = Opt} = Join,
1562    {?qual_data(JQNum,_,_,_), Rev, QNum1, QNum2, _WH1, _WH2, CsFun} =
1563        find_join_data(Qdata, QNum1a, QNum2a),
1564    {Cs1_0, Cs2_0, Compat} = CsFun(),
1565    [Cs1, Cs2] = case Compat of
1566                     [] -> % --R12B-5
1567                         [[{C,[{V,'=:='} || V <- Vs]} || {C,Vs} <- CVs] ||
1568                             CVs <- [Cs1_0, Cs2_0]];
1569                     _ -> % 'v1', R13A --
1570                         %% Only compared constants (==).
1571                         [Cs1_0, Cs2_0]
1572                 end,
1573    Anno = anno0(),
1574    G1_0 = {var,Anno,'G1'}, G2_0 = {var,Anno,'G2'},
1575    JP = element(JQNum + 1, Code),
1576    %% Create code for wh1 and wh2 in #join{}:
1577    {{I1,G1}, {I2,G2}, QInfoL} =
1578        case Kind of
1579            {merge, _} ->
1580                {JG1,QInfo1} = join_merge_info(QNum1, QInfo, Code, G1_0, Cs1),
1581                {JG2,QInfo2} = join_merge_info(QNum2, QInfo, Code, G2_0, Cs2),
1582                {JG1, JG2, QInfo1 ++ QInfo2};
1583            _ when Rev ->
1584                {JG2,QInfo2} = join_merge_info(QNum2, QInfo, Code, G2_0, Cs2),
1585                {J1, QInfo1} = join_lookup_info(QNum1, QInfo, G1_0),
1586                {{J1,G1_0}, JG2, QInfo2 ++ [QInfo1]};
1587            _ ->
1588                {JG1,QInfo1} = join_merge_info(QNum1, QInfo, Code, G1_0, Cs1),
1589                {J2, QInfo2} = join_lookup_info(QNum2, QInfo, G2_0),
1590                {JG1, {J2,G2_0}, QInfo1 ++ [QInfo2]}
1591        end,
1592    {JOptVal, JOp} = kind2op(Kind),
1593    JOpt = [{join, JOptVal}] ++ opt_info(join_unique_cache(Opt)),
1594    JFil = term_to_binary({op,Anno,JOp,
1595                           {call,Anno,{atom,Anno,element},
1596                            [{integer,Anno,C1},G1]},
1597                           {call,Anno,{atom,Anno,element},
1598                            [{integer,Anno,C2},G2]}}),
1599    P = term_to_binary({cons, Anno, G1, G2}),
1600    JInfo = {generate, JP, {qlc, P, QInfoL ++ [JFil], JOpt}},
1601    {Before, [I1 | After]} = lists:split(QNum1 - 1, QInfo),
1602    Before ++ [JInfo] ++ lists:delete(I2, After).
1603
1604kind2op({merge, _KE}) -> {merge, '=='};
1605kind2op({lookup, KE, _LU_fun}) -> {lookup, KE}.
1606
1607%% qlc:q(P0 || P0 = Pattern <- H1, ConstFilters),
1608%% where "P0" is a fresh variable and ConstFilters are filters that
1609%% test constant values of pattern columns.
1610join_merge_info(QNum, QInfo, Code, G, ExtraConstants) ->
1611    {generate, _, LEInfo}=I = lists:nth(QNum, QInfo),
1612    P = binary_to_term(element(QNum + 1, Code)),
1613    case {P, ExtraConstants} of
1614        {{var, _, _}, []} ->
1615            %% No need to introduce a QLC.
1616            TP = term_to_binary(G),
1617            I2 = {generate, TP, LEInfo},
1618            {{I,G}, [I2]};
1619        _ ->
1620            {EPV, M} =
1621                case P of
1622                    {var, _, _} ->
1623                        %% No need to introduce a pattern variable.
1624                        {P, P};
1625                    _ ->
1626                        {PV, _} = aux_name1('P', 0, abstract_vars(P)),
1627                        Anno = anno0(),
1628                        V = {var, Anno, PV},
1629                        {V, {match, Anno, V, P}}
1630                 end,
1631            DQP = term_to_binary(EPV),
1632            LEI = {generate, term_to_binary(M), LEInfo},
1633            TP = term_to_binary(G),
1634            CFs = [begin
1635                       A = anno0(),
1636                       Call = {call,A,{atom,A,element},[{integer,A,Col},EPV]},
1637                       F = list2op([{op,A,Op,abstract_term(Con),Call}
1638                                      || {Con,Op} <- ConstOps], 'or', A),
1639                       term_to_binary(F)
1640                   end ||
1641                      {Col,ConstOps} <- ExtraConstants],
1642            {{I,G}, [{generate, TP, {qlc, DQP, [LEI | CFs], []}}]}
1643    end.
1644
1645list2op([E], _Op, _Anno) ->
1646    E;
1647list2op([E | Es], Op, Anno) ->
1648    {op,Anno,Op,E,list2op(Es, Op, Anno)}.
1649
1650join_lookup_info(QNum, QInfo, G) ->
1651    {generate, _, LEInfo}=I = lists:nth(QNum, QInfo),
1652    TP = term_to_binary(G),
1653    {I, {generate, TP, LEInfo}}.
1654
1655opt_info(#optz{unique = Unique, cache = Cache0, join_option = JoinOption}) ->
1656    %% No 'nested_loop' options are added here, even if there are
1657    %% nested loops to carry out, unless a 'nested_loop' was given as
1658    %% option. The reason is that the qlc module does not know about
1659    %% all instances of nested loops.
1660    Cache = if
1661                Cache0 -> ets;
1662                true -> Cache0
1663            end,
1664    [{T,V} || {T,V} <- [{cache,Cache},{unique,Unique}],
1665              V =/= default_option(T)] ++
1666    [{T,V} || {T,V} <- [{join,JoinOption}], V =:= nested_loop].
1667
1668prepare_qlc(H, InitialValue, GUnique, GCache, TmpDir, MaxList, TmpUsage) ->
1669    GOpt = #qlc_opt{unique = GUnique, cache = GCache,
1670                    tmpdir = TmpDir, max_list = MaxList,
1671                    tmpdir_usage = TmpUsage},
1672    case opt_le(prep_le(H, GOpt), 1) of
1673        #prepared{qh = #qlc{} = QLC}=Prep ->
1674            Prep#prepared{qh = QLC#qlc{init_value = InitialValue}};
1675        #prepared{qh = #simple_qlc{}=SimpleQLC}=Prep ->
1676            Prep#prepared{qh = SimpleQLC#simple_qlc{init_value = InitialValue}};
1677        Prep ->
1678            Prep
1679    end.
1680
1681%%% The options given to append, q and table (unique and cache) as well
1682%%% as the type of expression (list, table, append, qlc...) are
1683%%% analyzed by prep_le. The results are is_unique_objects and
1684%%% is_cached. It is checked that the evaluation (in the Erlang sense)
1685%%% of list expressions yields qlc handles.
1686
1687prep_le(#qlc_lc{lc = LC_fun, opt = #qlc_opt{} = Opt0}=H, GOpt) ->
1688    #qlc_opt{unique = GUnique, cache = GCache,
1689             tmpdir = TmpDir, max_list = MaxList,
1690             tmpdir_usage = TmpUsage} = GOpt,
1691    Unique = Opt0#qlc_opt.unique or GUnique,
1692    Cache = if
1693                not GCache -> Opt0#qlc_opt.cache;
1694                true -> GCache
1695            end,
1696    Opt = Opt0#qlc_opt{unique = Unique, cache = Cache,
1697                       tmpdir = TmpDir, max_list = MaxList,
1698                       tmpdir_usage = TmpUsage},
1699    prep_qlc_lc(LC_fun(), Opt, GOpt, H);
1700prep_le(#qlc_table{info_fun = IF}=T, GOpt) ->
1701    {SortInfo, Sorted} = table_sort_info(T),
1702    IsUnique = grd(IF, is_unique_objects),
1703    Prep = #prepared{qh = T, sort_info = SortInfo, sorted = Sorted,
1704                     is_unique_objects = IsUnique},
1705    Opt = if
1706              IsUnique or not GOpt#qlc_opt.unique,
1707              T#qlc_table.ms =:= no_match_spec ->
1708                  GOpt#qlc_opt{cache = false};
1709              true ->
1710                  GOpt
1711          end,
1712    may_create_simple(Opt, Prep);
1713prep_le(#qlc_append{hl = HL}, GOpt) ->
1714    case lists:flatmap(fun(#prepared{qh = #qlc_list{l = []}}) -> [];
1715                          (#prepared{qh = #qlc_append{hl = HL1}}) -> HL1;
1716                          (H) -> [H] end,
1717                       [prep_le(H, GOpt) || H <- HL]) of
1718        []=Nil ->
1719            short_list(Nil);
1720        [Prep] ->
1721            Prep;
1722        PrepL ->
1723            Cache = lists:all(fun(#prepared{is_cached = IsC}) -> IsC =/= false
1724                              end, PrepL),
1725            %% The handles in hl are replaced by prepared handles:
1726            Prep = #prepared{qh = #qlc_append{hl = PrepL}, is_cached = Cache},
1727            may_create_simple(GOpt, Prep)
1728    end;
1729prep_le(#qlc_sort{h = H0}=Q0, GOpt) ->
1730    %% The handle h is replaced by a prepared handle:
1731    Q = Q0#qlc_sort{h = prep_le(H0, GOpt)},
1732    prep_sort(Q, GOpt);
1733prep_le([_, _ | _]=L, GOpt) ->
1734    Prep = #prepared{qh = #qlc_list{l = L}, is_cached = true},
1735    Opt = if
1736              not GOpt#qlc_opt.unique ->
1737                  GOpt#qlc_opt{cache = false};
1738             true -> GOpt
1739          end,
1740    may_create_simple(Opt, Prep);
1741prep_le(L, _GOpt) when is_list(L) ->
1742    short_list(L);
1743prep_le(T, _GOpt) ->
1744    erlang:error({unsupported_qlc_handle, #qlc_handle{h = T}}).
1745
1746eval_le(LE_fun, GOpt) ->
1747    case LE_fun() of
1748        {error, ?MODULE, _} = Error ->
1749            throw_error(Error);
1750        R ->
1751            case get_handle(R) of
1752                badarg ->
1753                    erlang:error(badarg, [R]);
1754                H ->
1755                    prep_le(H, GOpt)
1756            end
1757    end.
1758
1759prep_qlc_lc({simple_v1, PVar, LE_fun, L}, Opt, GOpt, _H) ->
1760    check_lookup_option(Opt, false),
1761    prep_simple_qlc(PVar, anno(L), eval_le(LE_fun, GOpt), Opt);
1762prep_qlc_lc({qlc_v1, QFun, CodeF, Qdata0, QOpt}, Opt, GOpt, _H) ->
1763    F = fun(?qual_data(_QNum, _GoI, _SI, fil)=QualData, ModGens) ->
1764                {QualData, ModGens};
1765           (?qual_data(_QNum, _GoI, _SI, {gen, #join{}})=QualData, ModGens) ->
1766                {QualData, ModGens};
1767           (?qual_data(QNum, GoI, SI, {gen, LE_fun}), ModGens0) ->
1768                Prep1 = eval_le(LE_fun, GOpt),
1769                {Prep, ModGens} =
1770                    prep_generator(QNum, Prep1, QOpt, Opt, ModGens0),
1771                {?qual_data(QNum, GoI, SI, {gen, Prep}), ModGens}
1772        end,
1773    {Qdata, ModGens} = lists:mapfoldl(F, [], Qdata0),
1774    SomeLookUp = lists:keymember(true, 2, ModGens),
1775    check_lookup_option(Opt, SomeLookUp),
1776    case ModGens of
1777        [{_QNum, _LookUp, all, OnePrep}] ->
1778            check_join_option(Opt),
1779            OnePrep;
1780        _ ->
1781            Prep0 = prep_qlc(QFun, CodeF, Qdata, QOpt, Opt),
1782            LU_SkipQuals =
1783                lists:flatmap(fun({QNum,_LookUp,Fs,_Prep}) -> [{QNum,Fs}]
1784                              end, ModGens),
1785            Prep1 = Prep0#prepared{lu_skip_quals = LU_SkipQuals},
1786            prep_join(Prep1, QOpt, Opt)
1787    end;
1788prep_qlc_lc(_, _Opt, _GOpt, H) ->
1789    erlang:error({unsupported_qlc_handle, #qlc_handle{h = H}}).
1790
1791prep_generator(QNum, Prep0, QOpt, Opt, ModGens) ->
1792    PosFun = fun(KeyEquality) -> pos_fun(KeyEquality, QOpt, QNum) end,
1793    MSFs = case match_specs(QOpt, QNum) of
1794               undefined ->
1795                   {no_match_spec, []};
1796               {_, _}=MSFs0 ->
1797                   MSFs0
1798         end,
1799    #prepared{qh = LE} = Prep0,
1800    case prep_gen(LE, Prep0, PosFun, MSFs, Opt) of
1801        {replace, Fs, LookUp, Prep} ->
1802            {Prep, [{QNum,LookUp,Fs,Prep} | ModGens]};
1803        {skip, SkipFils, LookUp, Prep} ->
1804            {Prep, [{QNum,LookUp,SkipFils,Prep} | ModGens]};
1805        {no, _Fs, _LookUp, Prep} ->
1806            {Prep, ModGens}
1807    end.
1808
1809pos_fun(undefined, QOpt, QNum) ->
1810    {'=:=', constants(QOpt, QNum)}; %% --R12B-5
1811pos_fun('=:=', QOpt, QNum) ->
1812    {'=:=', constants(QOpt, QNum)};
1813pos_fun('==', QOpt, QNum) ->
1814    try {'==', equal_constants(QOpt, QNum)} % R13A--
1815    catch _:_ -> {'=:=', constants(QOpt, QNum)}
1816    end.
1817
1818prep_gen(#qlc_table{lu_vals = LuV0, ms = MS0, trav_MS = TravMS,
1819                    info_fun = IF, lookup_fun = LU_fun,
1820                    key_equality = KeyEquality}=LE0,
1821         Prep0, PosFun0, {MS, Fs}, Opt) ->
1822    PosFun = PosFun0(KeyEquality),
1823    {LuV, {STag,SkipFils}} = find_const_positions(IF, LU_fun, PosFun, Opt),
1824    LU = LuV =/= false,
1825    if
1826        LuV0 =/= undefined; MS0 =/= no_match_spec ->
1827            {no, [], false, Prep0};
1828        MS =/= no_match_spec, LU ->
1829            MS1 = if
1830                      Fs =:= SkipFils; STag =:= Fs ->
1831                          %% The guard of the match specification
1832                          %% is covered by the lookup.
1833                          case MS of
1834                              [{'$1',_Guard,['$1']}] -> % no transformation
1835                                  no_match_spec;
1836                              [{Head,_Guard,Body}] ->
1837                                  [{Head,[],Body}] % true guard
1838                          end;
1839                      true ->
1840                          MS
1841                  end,
1842            Prep = Prep0#prepared{qh = LE0#qlc_table{lu_vals = LuV,ms = MS1}},
1843            {replace, Fs, LU, Prep};
1844        LU ->
1845            Prep = Prep0#prepared{qh = LE0#qlc_table{lu_vals = LuV}},
1846            {skip, SkipFils, LU, Prep};
1847        TravMS, MS =/= no_match_spec ->
1848            Prep = Prep0#prepared{qh = LE0#qlc_table{ms = MS},
1849                                  is_unique_objects = false},
1850            {replace, Fs, false, may_create_simple(Opt, Prep)};
1851        true ->
1852            {no, [], false, Prep0}
1853    end;
1854prep_gen(#qlc_list{l = []}, Prep0, _PosFun, {_MS, Fs}, _Opt) ->
1855    %% unique and cached
1856    {replace, Fs, false, Prep0};
1857prep_gen(#qlc_list{ms = no_match_spec}=LE0, Prep0, _PosFun, {MS, Fs}, Opt)
1858                                  when MS =/= no_match_spec ->
1859    Prep = Prep0#prepared{qh = LE0#qlc_list{ms = MS},
1860                          is_cached = false},
1861    {replace, Fs, false, may_create_simple(Opt, Prep)};
1862prep_gen(#qlc_list{}, Prep0, _PosFun, {MS, Fs}, Opt)
1863                                  when MS =/= no_match_spec ->
1864    ListMS = #qlc_list{l = Prep0, ms = MS},
1865    LE = #prepared{qh = ListMS, is_cached = false},
1866    {replace, Fs, false, may_create_simple(Opt, LE)};
1867prep_gen(_LE0, Prep0, _PosFun, _MSFs, _Opt) ->
1868    {no, [], false, Prep0}.
1869
1870-define(SIMPLE_QVAR, 'SQV').
1871
1872may_create_simple(#qlc_opt{unique = Unique, cache = Cache} = Opt,
1873                  #prepared{is_cached = IsCached,
1874                            is_unique_objects = IsUnique} = Prep) ->
1875    if
1876        Unique and not IsUnique;
1877        (Cache =/= false) and not IsCached ->
1878            prep_simple_qlc(?SIMPLE_QVAR, anno(1), Prep, Opt);
1879        true ->
1880            Prep
1881    end.
1882
1883prep_simple_qlc(PVar, Anno, LE, Opt) ->
1884    check_join_option(Opt),
1885    #prepared{is_cached = IsCached,
1886              sort_info = SortInfo, sorted = Sorted,
1887              is_unique_objects = IsUnique} = LE,
1888    #qlc_opt{unique = Unique, cache = Cache} = Opt,
1889    Cachez = if
1890                 Unique -> Cache;
1891                 not IsCached -> Cache;
1892                 true -> false
1893             end,
1894    Optz = #optz{unique = Unique and not IsUnique,
1895                 cache = Cachez, opt = Opt},
1896    QLC = #simple_qlc{p = PVar, le = LE, anno = Anno,
1897                      init_value = not_a_list, optz = Optz},
1898    %% LE#prepared.join is not copied
1899    #prepared{qh = QLC, is_unique_objects = IsUnique or Unique,
1900              sort_info = SortInfo, sorted = Sorted,
1901              is_cached = IsCached or (Cachez =/= false)}.
1902
1903prep_sort(#qlc_sort{h = #prepared{sorted = yes}=Prep}, _GOpt) ->
1904    Prep;
1905prep_sort(#qlc_sort{h = #prepared{is_unique_objects = IsUniqueObjs}}=Q,
1906          GOpt) ->
1907    S1 = sort_unique(IsUniqueObjs, Q),
1908    S2 = sort_tmpdir(S1, GOpt),
1909    S = S2#qlc_sort{tmpdir_usage = GOpt#qlc_opt.tmpdir_usage},
1910    {SortInfo, Sorted} = sort_sort_info(S),
1911    #prepared{qh = S, is_cached = true, sort_info = SortInfo,
1912              sorted = Sorted,
1913              is_unique_objects = S#qlc_sort.unique or IsUniqueObjs}.
1914
1915prep_qlc(QFun, CodeF, Qdata0, QOpt, Opt) ->
1916    #qlc_opt{unique = Unique, cache = Cache, join = Join} = Opt,
1917    Optz = #optz{unique = Unique, cache = Cache,
1918                 join_option = Join, opt = Opt},
1919    {Qdata, SortInfo} = qlc_sort_info(Qdata0, QOpt),
1920    QLC = #qlc{lcf = QFun, codef = CodeF, qdata = Qdata,
1921               init_value = not_a_list, optz = Optz},
1922    #prepared{qh = QLC, sort_info = SortInfo,
1923              is_unique_objects = Unique,
1924              is_cached = Cache =/= false}.
1925
1926%% 'sorted', 'sorted_info', and 'sorted_info2' are used to avoid
1927%% sorting on a key when there is no need to sort on the key. 'sorted'
1928%% is set by qlc:sort() only; its purpose is to assure that if columns
1929%% 1 to i are constant, then column i+1 is key-sorted (always true if
1930%% the tuples are sorted). Note: the implementation is (too?) simple.
1931%% For instance, each column is annotated with 'ascending' or
1932%% 'descending' (not yet). More exact would be, as examples, 'always
1933%% ascending' and 'ascending if all preceding columns are constant'.
1934%%
1935%% The 'size' of the template is not used (size_of_qualifier(QOpt, 0)).
1936
1937qlc_sort_info(Qdata0, QOpt) ->
1938    F = fun(?qual_data(_QNum, _GoI, _SI, fil)=Qd, Info) ->
1939                {Qd, Info};
1940           (?qual_data(_QNum, _GoI, _SI, {gen, #join{}})=Qd, Info) ->
1941                {Qd, Info};
1942           (?qual_data(QNum, GoI, SI, {gen, PrepLE0}), Info) ->
1943                PrepLE = sort_info(PrepLE0, QNum, QOpt),
1944                Qd = ?qual_data(QNum, GoI, SI, {gen, PrepLE}),
1945                I = [{{Column,Order}, [{traverse,QNum,C}]} ||
1946                        {{C,Order},What} <- PrepLE#prepared.sort_info2,
1947                        What =:= [], % Something else later...
1948                        Column <- equal_template_columns(QOpt, {QNum,C})],
1949                {Qd, [I | Info]}
1950        end,
1951    {Qdata, SortInfoL} = lists:mapfoldl(F, [], Qdata0),
1952    SortInfo0 = [{{Pos,Ord}, [template]} ||
1953                    Pos <- constant_columns(QOpt, 0),
1954                    Ord <- orders(yes)]
1955           ++ lists:append(SortInfoL),
1956    SortInfo = family_union(SortInfo0),
1957    {Qdata, SortInfo}.
1958
1959sort_info(#prepared{sort_info = SI, sorted = S} = Prep, QNum, QOpt) ->
1960    SI1 = [{{C,Ord},[]} ||
1961              S =/= no,
1962              is_integer(Sz = size_of_qualifier(QOpt, QNum)),
1963              Sz > 0, % the size of the pattern
1964              (NConstCols = size_of_constant_prefix(QOpt, QNum)) < Sz,
1965              C <- [NConstCols+1],
1966              Ord <- orders(S)]
1967       ++ [{{Pos,Ord},[]} || Pos <- constant_columns(QOpt, QNum),
1968                             Ord <- orders(yes)]
1969       ++ [{PosOrd,[]} || {PosOrd,_} <- SI],
1970    SI2 = lists:usort(SI1),
1971    Prep#prepared{sort_info2 = SI2}.
1972
1973%orders(descending=O) ->
1974%    [O];
1975orders(ascending=O) ->
1976    [O];
1977orders(yes) ->
1978    [ascending
1979%   ,descending
1980    ].
1981
1982sort_unique(true, #qlc_sort{fs_opts = SortOptions, keypos = sort}=Sort) ->
1983    Sort#qlc_sort{unique = false,
1984                  fs_opts =
1985                      lists:keydelete(unique, 1,
1986                                      lists:delete(unique, SortOptions))};
1987sort_unique(_, Sort) ->
1988    Sort.
1989
1990sort_tmpdir(S, #qlc_opt{tmpdir = ""}) ->
1991    S;
1992sort_tmpdir(S, Opt) ->
1993    S#qlc_sort{tmpdir = Opt#qlc_opt.tmpdir}.
1994
1995short_list(L) ->
1996    %% length(L) < 2: all elements are known be equal
1997    #prepared{qh = #qlc_list{l = L}, sorted = yes, is_unique_objects = true,
1998              is_cached = true}.
1999
2000find_const_positions(IF, LU_fun, {KeyEquality, PosFun},
2001                     #qlc_opt{max_lookup = Max, lookup = Lookup})
2002           when is_function(LU_fun), is_function(PosFun), is_function(IF),
2003                Lookup =/= false ->
2004    case call(IF, keypos, undefined, [])  of
2005        undefined ->
2006            Indices = call(IF, indices, undefined, []),
2007            find_const_position_idx(Indices, KeyEquality, PosFun, Max, []);
2008        KeyPos ->
2009            case pos_vals(KeyPos, KeyEquality, PosFun(KeyPos), Max) of
2010                false ->
2011                    find_const_position_idx(IF(indices), KeyEquality,
2012                                            PosFun, Max, []);
2013                PosValuesSkip ->
2014                    PosValuesSkip
2015            end
2016    end;
2017find_const_positions(_IF, _LU_fun, _KE_PosFun, _Opt0) ->
2018    {false, {some,[]}}.
2019
2020find_const_position_idx([I | Is], KeyEquality, PosFun, Max, L0) ->
2021    case pos_vals(I, KeyEquality, PosFun(I), Max) of
2022        false ->
2023            find_const_position_idx(Is, KeyEquality, PosFun, Max, L0);
2024        {{_Pos, Values}, _SkipFils}=PosValuesFils ->
2025            L = [{length(Values), PosValuesFils} | L0],
2026            find_const_position_idx(Is, KeyEquality, PosFun, Max, L)
2027    end;
2028find_const_position_idx(_, _KeyEquality, _PosFun, _Max, []) ->
2029    {false, {some,[]}};
2030find_const_position_idx(_, _KeyEquality, _PosFun, _Max, L) ->
2031    [{_,PVF} | _] = lists:sort(L),
2032    PVF.
2033
2034pos_vals(Pos, '==', {usort_needed, Values, SkipFils}, Max) ->
2035    pos_vals_max(Pos, lists:usort(Values), SkipFils, Max);
2036pos_vals(Pos, '=:=', {usort_needed, Values, SkipFils}, Max) ->
2037    pos_vals_max(Pos, lists:sort(nub(Values)), SkipFils, Max);
2038pos_vals(Pos, _KeyEquality, {values, Values, SkipFils}, Max) ->
2039    pos_vals_max(Pos, Values, SkipFils, Max);
2040pos_vals(_Pos, _KeyEquality, _T, _Max) ->
2041    false.
2042
2043nub([]) ->
2044    [];
2045nub([E | L]) ->
2046    case lists:member(E, Es=nub(L)) of
2047        true ->
2048            Es;
2049        false ->
2050            [E | Es]
2051    end.
2052
2053%% length(Values) >= 1
2054pos_vals_max(Pos, Values, Skip, Max) when Max =:= -1; Max >= length(Values) ->
2055    {{Pos, Values}, Skip};
2056pos_vals_max(_Pos, _Value, _Skip, _Max) ->
2057    false.
2058
2059prep_join(Prep, QOpt, Opt) ->
2060    case join_opt(QOpt) of
2061        undefined ->
2062            check_join_option(Opt),
2063            Prep;
2064        EqualMatch ->
2065            {Ix, M} = case EqualMatch of
2066                          {NEqual, NMatch} ->
2067                              pref_join(NEqual, NMatch, Prep, QOpt, Opt);
2068                          EM ->
2069                              pref_join(EM, EM, Prep, QOpt, Opt)
2070                      end,
2071            SI = family_union(Prep#prepared.sort_info ++ M),
2072            Prep#prepared{join = {Ix, M}, sort_info = SI}
2073    end.
2074
2075%% The parse transform ensures that only two tables are involved.
2076pref_join(Equal, Match, Prep, QOpt, #qlc_opt{join = JoinOpt}) ->
2077    JQs = [{KeyEquality, QCs} ||
2078              {KeyEquality, QCsL} <- [{'==',Equal}, {'=:=',Match}],
2079              QCs <- QCsL],
2080    IxL = [pref_lookup_join(KE, QCs, Prep, QOpt) ||
2081              JoinOpt =:= any orelse JoinOpt =:= lookup,
2082              {KE, QCs} <- JQs],
2083    ML = [pref_merge_join(KE, QCs, Prep, QOpt) ||
2084             JoinOpt =:= any orelse JoinOpt =:= merge,
2085             {KE, QCs} <- JQs],
2086    {lists:usort(lists:append(IxL)), lists:usort(lists:append(ML))}.
2087
2088pref_lookup_join(KeyEquality, {[{Q1,C1},{Q2,C2}],Skip}, Prep, QOpt)
2089                                       when is_integer(C1), is_integer(C2) ->
2090    #prepared{qh = #qlc{qdata = QData}} = Prep,
2091    Is1 = lookup_qual_data(QData, Q1, KeyEquality),
2092    Lu2 = [pref_lookup_join2(Q2, C2, Q1, C1, Skip, QOpt, KeyEquality) ||
2093              IC1 <- Is1, IC1 =:= C1],
2094    Is2 = lookup_qual_data(QData, Q2, KeyEquality),
2095    Lu1 = [pref_lookup_join2(Q1, C1, Q2, C2, Skip, QOpt, KeyEquality) ||
2096              IC2 <- Is2, IC2 =:= C2],
2097    family(Lu1 ++ Lu2);
2098pref_lookup_join(KE, [{_,Cs1},{_,Cs2}]=L, Prep, QOpt) when is_list(Cs1),
2099                                                           is_list(Cs2) ->
2100    %% --R12B-5
2101    lists:append([pref_lookup_join(KE, QC,Prep,QOpt) ||
2102                     QC <- selections_no_skip(L)]).
2103
2104lookup_qual_data(QData, QNum, KeyEquality) ->
2105    case lists:keysearch(QNum, 1, QData) of
2106        {value, ?qual_data(QNum, _, _, {gen, PrepLE})} ->
2107            join_indices(PrepLE, KeyEquality)
2108    end.
2109
2110%% If the table has a match specification (ms =/= no_match_spec) that
2111%% has _not_ been derived from a filter but from a query handle then
2112%% the lookup join cannot be done. This particular case has not been
2113%% excluded here but is taken care of in opt_join().
2114join_indices(#prepared{qh = #qlc_table{info_fun = IF,
2115                                       lookup_fun = LU_fun,
2116                                       key_equality = KeyEquality,
2117                                       lu_vals = undefined}},
2118             KE) when is_function(LU_fun),
2119                      KE =:= KeyEquality orelse
2120                      KE =:= '=:=' andalso
2121                            KeyEquality =:= undefined -> % --R12B-5
2122    KpL = case call(IF, keypos, undefined, []) of
2123              undefined -> [];
2124              Kp -> [Kp]
2125          end,
2126    case call(IF, indices, undefined, []) of
2127        undefined -> KpL;
2128        Is0 -> lists:usort(KpL ++ Is0)
2129    end;
2130join_indices(_Prep, _KeyEquality) ->
2131    [].
2132
2133pref_lookup_join2(Q1, C1, Q2, C2, Skip, QOpt, KeyEquality) ->
2134    TemplCols = compared_template_columns(QOpt, {Q1,C1}, KeyEquality),
2135    {{Q1,C1,Q2,C2},{lookup_join,TemplCols,KeyEquality,Skip}}.
2136
2137pref_merge_join(KE, {[{Q1,C1},{Q2,C2}],Skip}, Prep, QOpt)
2138                                       when is_integer(C1), is_integer(C2) ->
2139    #prepared{qh = #qlc{qdata = QData}} = Prep,
2140    Sort1 = merge_qual_data(QData, Q1),
2141    Sort2 = merge_qual_data(QData, Q2),
2142    Merge = pref_merge(KE, Q1, C1, Q2, C2, Skip, Sort1, Sort2, QOpt),
2143    family_union(Merge);
2144pref_merge_join(KE, [{_,Cs1},{_,Cs2}]=L, Prep, QOpt) when is_list(Cs1),
2145                                                      is_list(Cs2) ->
2146    %% --R12B-5
2147    lists:append([pref_merge_join(KE, QC, Prep, QOpt) ||
2148                     QC <- selections_no_skip(L)]).
2149
2150selections_no_skip(L) ->
2151    [{C,{some,[]}} || C <- all_selections(L)].
2152
2153merge_qual_data(QData, QNum) ->
2154    case lists:keysearch(QNum, 1, QData) of
2155        {value, ?qual_data(QNum, _, _, {gen, PrepLE})} ->
2156            #prepared{sort_info2 = SortInfo} = PrepLE,
2157            SortInfo
2158    end.
2159
2160pref_merge(KE, Q1, C1, Q2, C2, Skip, Sort1, Sort2, QOpt) ->
2161    Col1 = {Q1,C1},
2162    Col2 = {Q2,C2},
2163    DoSort = [QC || {{_QNum,Col}=QC,SortL} <- [{Col1,Sort1}, {Col2,Sort2}],
2164                    lists:keymember({Col, ascending}, 1, SortL) =:= false],
2165    J = [{{Q1,C1,Q2,C2}, {merge_join,DoSort,KE,Skip}}],
2166    %% true = (QOpt(template))(Col1, '==') =:= (QOpt(template))(Col2, '==')
2167    [{{Column, ascending}, J} ||
2168        Column <- equal_template_columns(QOpt, Col1)] ++ [{other, J}].
2169
2170table_sort_info(#qlc_table{info_fun = IF}) ->
2171    case call(IF, is_sorted_key, undefined, []) of
2172        undefined ->
2173            {[], no};
2174        false ->
2175            {[], no};
2176        true ->
2177            case call(IF, keypos, undefined, []) of
2178                undefined -> % strange
2179                    {[], no};
2180                KeyPos ->
2181                    {[{{KeyPos,ascending},[]}], no}
2182            end
2183    end.
2184
2185sort_sort_info(#qlc_sort{keypos = sort, order = Ord0}) ->
2186    {[], sort_order(Ord0)};
2187sort_sort_info(#qlc_sort{keypos = {keysort,Kp0}, order = Ord0}) ->
2188    Kp = case Kp0 of
2189             [Pos | _] -> Pos;
2190             _ -> Kp0
2191         end,
2192    {[{{Kp,sort_order(Ord0)},[]}], no}.
2193
2194sort_order(F) when is_function(F) ->
2195    no;
2196sort_order(Order) ->
2197    Order.
2198
2199check_join_option(#qlc_opt{join = any}) ->
2200    ok;
2201check_join_option(#qlc_opt{join = Join}) ->
2202    erlang:error(no_join_to_carry_out, [{join,Join}]).
2203
2204check_lookup_option(#qlc_opt{lookup = true}, false) ->
2205    erlang:error(no_lookup_to_carry_out, [{lookup,true}]);
2206check_lookup_option(_QOpt, _LuV) ->
2207    ok.
2208
2209compared_template_columns(QOpt, QNumColumn, KeyEquality) ->
2210    (QOpt(template))(QNumColumn, KeyEquality).
2211
2212equal_template_columns(QOpt, QNumColumn) ->
2213    (QOpt(template))(QNumColumn, '==').
2214
2215%eq_template_columns(QOpt, QNumColumn) ->
2216%    (QOpt(template))(QNumColumn, '=:=').
2217
2218size_of_constant_prefix(QOpt, QNum) ->
2219    (QOpt(n_leading_constant_columns))(QNum).
2220
2221constants(QOpt, QNum) ->
2222    (QOpt(constants))(QNum).
2223
2224equal_constants(QOpt, QNum) ->
2225    (QOpt(equal_constants))(QNum).
2226
2227join_opt(QOpt) ->
2228    QOpt(join).
2229
2230match_specs(QOpt, QNum) ->
2231    (QOpt(match_specs))(QNum).
2232
2233constant_columns(QOpt, QNum) ->
2234    (QOpt(constant_columns))(QNum).
2235
2236size_of_qualifier(QOpt, QNum) ->
2237    (QOpt(size))(QNum).
2238
2239%% Two optimizations are carried out:
2240%% 1. The first generator is never cached if the QLC itself is cached.
2241%% Since the answers do not need to be cached, the top-most QLC is
2242%% never cached either. Simple QLCs not holding any options are
2243%% removed. Simple QLCs are coalesced when possible.
2244%% 2. Merge join and lookup join is done if possible.
2245
2246opt_le(#prepared{qh = #simple_qlc{le = LE0, optz = Optz0}=QLC}=Prep0,
2247       GenNum) ->
2248    case LE0 of
2249        #prepared{qh = #simple_qlc{p = LE_Pvar, le = LE2, optz = Optz2}} ->
2250            %% Coalesce two simple QLCs.
2251            Cachez = case Optz2#optz.cache of
2252                         false -> Optz0#optz.cache;
2253                         Cache2 -> Cache2
2254                     end,
2255            Optz = Optz0#optz{cache = Cachez,
2256                              unique = Optz0#optz.unique or Optz2#optz.unique},
2257            PVar = if
2258                       LE_Pvar =:= ?SIMPLE_QVAR -> QLC#simple_qlc.p;
2259                       true -> LE_Pvar
2260                   end,
2261            Prep = Prep0#prepared{qh = QLC#simple_qlc{p = PVar, le = LE2,
2262                                                      optz = Optz}},
2263            opt_le(Prep, GenNum);
2264        _ ->
2265            Optz1 = no_cache_of_first_generator(Optz0, GenNum),
2266            case {opt_le(LE0, 1), Optz1} of
2267                {LE, #optz{unique = false, cache = false}} ->
2268                    LE;
2269                {LE, _} ->
2270                    Prep0#prepared{qh = QLC#simple_qlc{le = LE, optz = Optz1}}
2271            end
2272    end;
2273opt_le(#prepared{qh = #qlc{}, lu_skip_quals = LU_SkipQuals0}=Prep0, GenNum) ->
2274    #prepared{qh = #qlc{qdata = Qdata0, optz = Optz0}=QLC} = Prep0,
2275    #optz{join_option = JoinOption, opt = Opt} = Optz0,
2276    JoinOption = Optz0#optz.join_option,
2277    {LU_QNum, Join, JoinSkipFs, DoSort} =
2278        opt_join(Prep0#prepared.join, JoinOption, Qdata0, Opt, LU_SkipQuals0),
2279    {LU_Skip, LU_SkipQuals} =
2280        lists:partition(fun({QNum,_Fs}) -> QNum =:= LU_QNum end,
2281                        LU_SkipQuals0),
2282    LU_SkipFs = lists:flatmap(fun({_QNum,Fs}) -> Fs end, LU_SkipQuals),
2283    %% If LU_QNum has a match spec it must be applied _after_ the
2284    %% lookup join (the filter must not be skipped!).
2285    Qdata1 = if
2286                 LU_Skip =:= [] -> Qdata0;
2287                 true -> activate_join_lookup_filter(LU_QNum, Qdata0)
2288             end,
2289    Qdata2 = skip_lookup_filters(Qdata1, LU_SkipFs ++ JoinSkipFs),
2290    F = fun(?qual_data(QNum, GoI, SI, {gen, #prepared{}=PrepLE}), GenNum1) ->
2291                NewPrepLE = maybe_sort(PrepLE, QNum, DoSort, Opt),
2292                {?qual_data(QNum, GoI, SI, {gen, opt_le(NewPrepLE, GenNum1)}),
2293                 GenNum1 + 1};
2294           (Qd, GenNum1) ->
2295                {Qd, GenNum1}
2296        end,
2297    {Qdata, _} = lists:mapfoldl(F, 1, Qdata2),
2298    Optz1 = no_cache_of_first_generator(Optz0, GenNum),
2299    Optz = Optz1#optz{fast_join = Join},
2300    Prep0#prepared{qh = QLC#qlc{qdata = Qdata, optz = Optz}};
2301opt_le(#prepared{qh = #qlc_append{hl = HL}}=Prep, GenNum) ->
2302    Hs = [opt_le(H, GenNum) || H <- HL],
2303    Prep#prepared{qh = #qlc_append{hl = Hs}};
2304opt_le(#prepared{qh = #qlc_sort{h = H}=Sort}=Prep, GenNum) ->
2305    Prep#prepared{qh = Sort#qlc_sort{h = opt_le(H, GenNum)}};
2306opt_le(Prep, _GenNum) ->
2307    Prep.
2308
2309no_cache_of_first_generator(Optz, GenNum) when GenNum > 1 ->
2310    Optz;
2311no_cache_of_first_generator(Optz, 1) ->
2312    Optz#optz{cache = false}.
2313
2314maybe_sort(LE, QNum, DoSort, Opt) ->
2315    case lists:keyfind(QNum, 1, DoSort) of
2316        {QNum, Col} ->
2317            #qlc_opt{tmpdir = TmpDir, tmpdir_usage = TmpUsage} = Opt,
2318            SortOpts = [{tmpdir,Dir} || Dir <- [TmpDir], Dir =/= ""],
2319            Sort = #qlc_sort{h = LE, keypos = {keysort, Col}, unique = false,
2320                             compressed = [], order = ascending,
2321                             fs_opts = SortOpts, tmpdir_usage = TmpUsage,
2322                             tmpdir = TmpDir},
2323            #prepared{qh = Sort, sorted = no, join = no};
2324        false ->
2325            LE
2326    end.
2327
2328skip_lookup_filters(Qdata, []) ->
2329    Qdata;
2330skip_lookup_filters(Qdata0, LU_SkipFs) ->
2331    [case lists:member(QNum, LU_SkipFs) of
2332         true ->
2333             ?qual_data(QNum, GoI, ?SKIP, fil);
2334         false ->
2335             Qd
2336     end || ?qual_data(QNum, GoI, _, _)=Qd <- Qdata0].
2337
2338%% If the qualifier used for lookup by the join (QNum) has a match
2339%% specification it must be applied _after_ the lookup join (the
2340%% filter must not be skipped!).
2341activate_join_lookup_filter(QNum, Qdata) ->
2342    {_,GoI2,SI2,{gen,Prep2}} = lists:keyfind(QNum, 1, Qdata),
2343    Table2 = Prep2#prepared.qh,
2344    NPrep2 = Prep2#prepared{qh = Table2#qlc_table{ms = no_match_spec}},
2345    %% Table2#qlc_table.ms has been reset; the filter will be run.
2346    lists:keyreplace(QNum, 1, Qdata, ?qual_data(QNum,GoI2,SI2,{gen,NPrep2})).
2347
2348opt_join(Join, JoinOption, Qdata, Opt, LU_SkipQuals) ->
2349    %% prep_qlc_lc() assures that no unwanted join is carried out
2350    {Ix0, M0} = Join,
2351    Ix1 = opt_join_lu(Ix0, Qdata, LU_SkipQuals),
2352    Ix = lists:reverse(lists:keysort(2, Ix1)), % prefer to skip
2353    case Ix of
2354        [{{Q1,C1,Q2,C2},Skip,KE,LU_fun} | _] ->
2355            J = #qlc_join{kind = {lookup, KE, LU_fun}, q1 = Q1,
2356                          c1 = C1, q2 = Q2, c2 = C2, opt = Opt},
2357            {Q2, J, Skip, []};
2358        [] ->
2359            M = opt_join_merge(M0),
2360            case M of
2361                [{{Q1,C1,Q2,C2},{merge_join,DoSort,KE,Skip}}|_] ->
2362                    J = #qlc_join{kind = {merge, KE}, opt = Opt,
2363                                  q1 = Q1, c1 = C1, q2 = Q2, c2 = C2},
2364                    {not_a_qnum, J, Skip, DoSort};
2365                [] when JoinOption =:= nested_loop ->
2366                    {not_a_qnum, no, [], []};
2367                _ when JoinOption =/= any ->
2368                    erlang:error(cannot_carry_out_join, [JoinOption]);
2369                _ ->
2370                    {not_a_qnum, no, [], []}
2371            end
2372    end.
2373
2374opt_join_lu([{{_Q1,_C1,Q2,_C2}=J,[{lookup_join,_KEols,JKE,Skip0} | _]} | LJ],
2375            Qdata, LU_SkipQuals) ->
2376    {Q2,_,_,{gen,Prep2}} = lists:keyfind(Q2, 1, Qdata),
2377    #qlc_table{ms = MS, key_equality = KE,
2378               lookup_fun = LU_fun} = Prep2#prepared.qh,
2379    %% If there is no filter to skip (the match spec was derived
2380    %% from a query handle) then the lookup join cannot be done.
2381    case
2382        MS =/= no_match_spec andalso
2383        lists:keymember(Q2, 1, LU_SkipQuals) =:= false
2384    of
2385        true ->
2386            opt_join_lu(LJ, Qdata, LU_SkipQuals);
2387        false ->
2388            %% The join is preferred before evaluating the match spec
2389            %% (if there is one).
2390            Skip = skip_if_possible(JKE, KE, Skip0),
2391            [{J,Skip,KE,LU_fun} | opt_join_lu(LJ, Qdata, LU_SkipQuals)]
2392    end;
2393opt_join_lu([], _Qdata, _LU_SkipQuals) ->
2394    [].
2395
2396opt_join_merge(M) ->
2397    %% Prefer not to sort arguments. Prefer to skip join filter.
2398    L = [{-length(DoSort),length(Skip),
2399         {QCs,{merge_join,DoSort,KE,Skip}}} ||
2400            {_KpOrder_or_other,MJ} <- M,
2401            {QCs,{merge_join,DoSort,KE,Skip0}} <- MJ,
2402            Skip <- [skip_if_possible(KE, '==', Skip0)]],
2403    lists:reverse([J || {_,_,J} <- lists:sort(L)]).
2404
2405%% Cannot skip the join filter the join operator is '=:=' and the join
2406%% is performed using '=='. Note: the tag 'some'/'all' is not used.
2407skip_if_possible('=:=', '==', _) ->
2408    [];
2409skip_if_possible(_, _, {_SkipTag, Skip}) ->
2410    Skip.
2411
2412%% -> {Objects, Post, LocalPost} | throw()
2413%% Post is a list of funs (closures) to run afterwards.
2414%% LocalPost should be run when all objects have been found (optimization).
2415%% LocalPost will always be a subset of Post.
2416%% List expressions are evaluated, resulting in lists of objects kept in
2417%% RAM or on disk.
2418%% An error term is thrown as soon as cleanup according Post has been
2419%% done. (This is opposed to errors during evaluation; such errors are
2420%% returned as terms.)
2421setup_qlc(Prep, Setup) ->
2422    Post0 = [],
2423    setup_le(Prep, Post0, Setup).
2424
2425setup_le(#prepared{qh = #simple_qlc{le = LE, optz = Optz}}, Post0, Setup) ->
2426    {Objs, Post, LocalPost} = setup_le(LE, Post0, Setup),
2427    unique_cache(Objs, Post, LocalPost, Optz);
2428setup_le(#prepared{qh = #qlc{lcf = QFun, qdata = Qdata, init_value = V,
2429                             optz = Optz}}, Post0, Setup) ->
2430    {GoTo, FirstState, Post, LocalPost} =
2431        setup_quals(Qdata, Post0, Setup, Optz),
2432    Objs = fun() -> QFun(FirstState, V, GoTo) end,
2433    unique_cache(Objs, Post, LocalPost, Optz);
2434setup_le(#prepared{qh = #qlc_table{post_fun = PostFun}=Table}, Post, Setup) ->
2435    H = table_handle(Table, Post, Setup),
2436    %% The pre fun has been called from table_handle():
2437    {H, [PostFun | Post], []};
2438setup_le(#prepared{qh = #qlc_append{hl = PrepL}}, Post0, Setup) ->
2439    F = fun(Prep, {Post1, LPost1}) ->
2440                {Objs, Post2, LPost2} = setup_le(Prep, Post1, Setup),
2441                {Objs, {Post2, LPost1++LPost2}}
2442        end,
2443    {ObjsL, {Post, LocalPost}} = lists:mapfoldl(F, {Post0,[]}, PrepL),
2444    {fun() -> append_loop(ObjsL, 0) end, Post, LocalPost};
2445setup_le(#prepared{qh = #qlc_sort{h = Prep, keypos = Kp,
2446                                  unique = Unique, compressed = Compressed,
2447                                  order = Order, fs_opts = SortOptions0,
2448                                  tmpdir_usage = TmpUsage,tmpdir = TmpDir}},
2449         Post0, Setup) ->
2450    SortOptions = sort_options_global_tmp(SortOptions0, TmpDir),
2451    LF = fun(Objs) ->
2452                 sort_list(Objs, Order, Unique, Kp, SortOptions, Post0)
2453         end,
2454    case setup_le(Prep, Post0, Setup) of
2455        {L, Post, LocalPost} when is_list(L) ->
2456            {LF(L), Post, LocalPost};
2457        {Objs, Post, LocalPost} ->
2458            FF = fun(Objs1) ->
2459                         file_sort_handle(Objs1, Kp, SortOptions, TmpDir,
2460                                          Compressed, Post, LocalPost)
2461                 end,
2462            sort_handle(Objs, LF, FF, SortOptions, Post, LocalPost,
2463                        {TmpUsage, sorting})
2464    end;
2465setup_le(#prepared{qh = #qlc_list{l = L, ms = MS}}, Post, _Setup)
2466              when (no_match_spec =:= MS); L =:= [] ->
2467    {L, Post, []};
2468setup_le(#prepared{qh = #qlc_list{l = L, ms = MS}}, Post, _Setup)
2469                                   when is_list(L) ->
2470    {ets:match_spec_run(L, ets:match_spec_compile(MS)), Post, []};
2471setup_le(#prepared{qh = #qlc_list{l = H0, ms = MS}}, Post0, Setup) ->
2472    {Objs0, Post, LocalPost} = setup_le(H0, Post0, Setup),
2473    Objs = ets:match_spec_run(Objs0, ets:match_spec_compile(MS)),
2474    {Objs, Post, LocalPost}.
2475
2476%% The goto table (a tuple) is created at runtime. It is accessed by
2477%% the generated code in order to find next clause to execute. For
2478%% generators there is also a fun; calling the fun runs the list
2479%% expression of the generator. There are two elements for a filter:
2480%% the first one is the state to go when the filter is false; the
2481%% other the state when the filter is true. There are three elements
2482%% for a generator G: the first one is the state of the generator
2483%% before G (or the stop state if there is no generator); the second
2484%% one is the state of the qualifier following the generator (or the
2485%% template if there is no next generator); the third one is the list
2486%% expression fun.
2487%% There are also join generators which are "activated" when it is
2488%% possbible to do a join.
2489
2490setup_quals(Qdata, Post0, Setup, Optz) ->
2491    {GoTo0, Post1, LocalPost0} =
2492        setup_quals(0, Qdata, [], Post0, [], Setup),
2493    GoTo1 = lists:keysort(1, GoTo0),
2494    FirstState0 = next_state(Qdata),
2495    {GoTo2, FirstState, Post, LocalPost1} =
2496        case Optz#optz.fast_join of
2497            #qlc_join{kind = {merge,_KE}, c1 = C1, c2 = C2, opt = Opt} = MJ ->
2498                MF = fun(_Rev, {H1, WH1}, {H2, WH2}) ->
2499                             fun() ->
2500                                  merge_join(WH1(H1), C1, WH2(H2), C2, Opt)
2501                             end
2502                     end,
2503                setup_join(MJ, Qdata, GoTo1, FirstState0, MF, Post1);
2504            #qlc_join{kind = {lookup,_KE,LuF}, c1 = C1, c2 = C2} = LJ ->
2505                LF = fun(Rev, {H1, WH1}, {H2, WH2}) ->
2506                             {H, W} = if
2507                                          Rev -> {H2, WH2};
2508                                          true -> {H1, WH1}
2509                                      end,
2510                             fun() ->
2511                                     lookup_join(W(H), C1, LuF, C2, Rev)
2512                             end
2513                     end,
2514                setup_join(LJ, Qdata, GoTo1, FirstState0, LF, Post1);
2515            no ->
2516                {flat_goto(GoTo1), FirstState0, Post1, []}
2517        end,
2518    GoTo = list_to_tuple(GoTo2),
2519    {GoTo, FirstState, Post, LocalPost0 ++ LocalPost1}.
2520
2521setup_quals(GenLoopS, [?qual_data(_QNum,GoI,?SKIP,fil) | Qdata],
2522            Gs, P, LP, Setup) ->
2523    %% ?SKIP causes runtime error. See also skip_lookup_filters().
2524    setup_quals(GenLoopS, Qdata, [{GoI,[?SKIP,?SKIP]} | Gs], P, LP, Setup);
2525setup_quals(GenLoopS, [?qual_data(_QNum,GoI,_SI,fil) | Qdata],
2526            Gs, P, LP, Setup) ->
2527    setup_quals(GenLoopS, Qdata, [{GoI,[GenLoopS,next_state(Qdata)]} | Gs],
2528                P, LP, Setup);
2529setup_quals(GenLoopS, [?qual_data(_QNum,GoI,_SI, {gen,#join{}}) | Qdata],
2530            Gs, P, LP, Setup) ->
2531    setup_quals(GenLoopS, Qdata, [{GoI,[?SKIP,?SKIP,?SKIP]} | Gs],P,LP,Setup);
2532setup_quals(GenLoopS, [?qual_data(_QNum,GoI,SI,{gen,LE}) | Qdata],
2533            Gs, P, LP, Setup) ->
2534    {V, NP, LP1} = setup_le(LE, P, Setup),
2535    setup_quals(SI + 1, Qdata, [{GoI, [GenLoopS,next_state(Qdata),V]} | Gs],
2536                NP, LP ++ LP1, Setup);
2537setup_quals(GenLoopS, [], Gs, P, LP, _Setup) ->
2538    {[{1,[GenLoopS]} | Gs], P, LP}.
2539
2540%% Finds the qualifier in Qdata that performs the join between Q1 and
2541%% Q2, and sets it up using the handles already set up for Q1 and Q2.
2542%% Removes Q1 and Q2 from GoTo0 and updates the join qualifier in GoTo0.
2543%% Note: the parse transform has given each generator three slots
2544%% in the GoTo table. The position of these slots within the GoTo table
2545%% is fixed (at runtime).
2546%% (Assumes there is only one join-generator in Qdata.)
2547setup_join(J, Qdata, GoTo0, FirstState0, JoinFun, Post0) ->
2548    #qlc_join{q1 = QNum1a, q2 = QNum2a, opt = Opt} = J,
2549    {?qual_data(_QN,JGoI,JSI,_), Rev, QNum1, QNum2, WH1, WH2, _CsFun} =
2550        find_join_data(Qdata, QNum1a, QNum2a),
2551    [{GoI1,SI1}] = [{GoI,SI} ||
2552                       ?qual_data(QNum,GoI,SI,_) <- Qdata, QNum =:= QNum1],
2553    [{GoI2,SI2}] = [{GoI,SI} ||
2554                       ?qual_data(QNum,GoI,SI,_) <- Qdata, QNum =:= QNum2],
2555
2556    [H1] = [H || {GoI,[_Back,_Forth,H]} <- GoTo0, GoI =:= GoI1],
2557    [{BackH2,H2}] =
2558           [{Back,H} || {GoI,[Back,_Forth,H]} <- GoTo0, GoI =:= GoI2],
2559    H0 = JoinFun(Rev, {H1,WH1}, {H2,WH2}),
2560    %% The qlc expression options apply to the introduced qlc expr as well.
2561    {H, Post, LocalPost} =
2562         unique_cache(H0, Post0, [], join_unique_cache(Opt)),
2563    [JBack] = [Back || {GoI,[Back,_,_]} <- GoTo0, GoI =:= GoI1],
2564    JForth = next_after(Qdata, SI1, QNum2),
2565    GoTo1 = lists:map(fun({GoI,_}) when GoI =:= JGoI ->
2566                              {JGoI, [JBack, JForth, H]};
2567                         ({GoI,_}) when GoI =:= GoI1; GoI =:= GoI2 ->
2568                              {GoI, [?SKIP,?SKIP,?SKIP]}; % not necessary
2569                         (Go) ->
2570                              Go
2571                      end, GoTo0),
2572    GoTo = lists:map(fun(S) when S =:= SI1 ->
2573                             JSI;
2574                        (S) when S =:= SI2 ->
2575                             next_after(Qdata, S, QNum2);
2576                        (S) when S =:= SI1+1 ->
2577                             JSI+1;
2578                        (S) when S =:= SI2+1, SI1 + 1 =:= BackH2  ->
2579                             JSI+1;
2580                        (S) when S =:= SI2+1 ->
2581                             BackH2;
2582                        (S) -> S
2583                     end, flat_goto(GoTo1)),
2584    FirstState = if
2585                     SI1 =:= FirstState0 -> JSI;
2586                     true -> FirstState0
2587                 end,
2588    {GoTo, FirstState, Post, LocalPost}.
2589
2590join_unique_cache(#qlc_opt{cache = Cache, unique = Unique}=Opt) ->
2591    #optz{cache = Cache, unique = Unique, opt = Opt}.
2592
2593flat_goto(GoTo) ->
2594    lists:flatmap(fun({_,L}) -> L end, GoTo).
2595
2596next_after([?qual_data(_, _, S, _) | Qdata], S, QNum2) ->
2597    case Qdata of
2598        [?qual_data(QNum2, _, _, _) | Qdata1] ->
2599            next_state(Qdata1);
2600        _ ->
2601            next_state(Qdata)
2602    end;
2603next_after([_ | Qdata], S, QNum2) ->
2604    next_after(Qdata, S, QNum2).
2605
2606next_state([?qual_data(_,_,_,{gen,#join{}}) | Qdata]) ->
2607    next_state(Qdata);
2608next_state([?qual_data(_,_,?SKIP,fil) | Qdata]) ->
2609    %% see skip_lookup_filters()
2610    next_state(Qdata);
2611next_state([?qual_data(_,_,S,_) | _]) ->
2612    S;
2613next_state([]) ->
2614    template_state().
2615
2616find_join_data(Qdata, QNum1, QNum2) ->
2617    [QRev] = [{Q,Rev,QN1,QN2,H1,H2,CsF} ||
2618                 ?qual_data(_QN,_GoI,_SI,
2619                            {gen,#join{q1 = QN1,q2 = QN2,
2620                                       wh1 = H1, wh2 = H2,
2621                                       cs_fun = CsF}})= Q <- Qdata,
2622                 if
2623                     QN1 =:= QNum1, QN2 =:= QNum2 ->
2624                         not (Rev = false);
2625                     QN1 =:= QNum2, QN2 =:= QNum1 ->
2626                         Rev = true;
2627                     true ->
2628                         Rev = false
2629                 end],
2630    QRev.
2631
2632table_handle(#qlc_table{trav_fun = TraverseFun, trav_MS = TravMS,
2633                        pre_fun = PreFun, lookup_fun = LuF,
2634                        parent_fun = ParentFun, lu_vals = LuVals, ms = MS},
2635             Post, Setup) ->
2636    #setup{parent = Parent} = Setup,
2637    ParentValue =
2638        if
2639            ParentFun =:= undefined ->
2640                undefined;
2641            Parent =:= self() ->
2642                try
2643                    ParentFun()
2644                catch Class:Reason:Stacktrace ->
2645                    post_funs(Post),
2646                    erlang:raise(Class, Reason, Stacktrace)
2647                end;
2648            true ->
2649                case monitor_request(Parent, {parent_fun, ParentFun}) of
2650                    error -> % parent has died
2651                        post_funs(Post),
2652                        exit(normal);
2653                    {value, Value} ->
2654                        Value;
2655                    {parent_fun_caught, Class, Reason, Stacktrace} ->
2656                        %% No use augmenting Stacktrace here.
2657                        post_funs(Post),
2658                        erlang:raise(Class, Reason, Stacktrace)
2659                end
2660        end,
2661    StopFun =
2662        if
2663            Parent =:= self() ->
2664                undefined;
2665            true ->
2666                Cursor = #qlc_cursor{c = {self(), Parent}},
2667                fun() -> delete_cursor(Cursor) end
2668        end,
2669    PreFunArgs = [{parent_value, ParentValue}, {stop_fun, StopFun}],
2670    _ = call(PreFun, PreFunArgs, ok, Post),
2671    case LuVals of
2672        {Pos, Vals} when MS =:= no_match_spec ->
2673            LuF(Pos, Vals);
2674        {Pos, Vals} ->
2675            case LuF(Pos, Vals) of
2676                [] ->
2677                    [];
2678                Objs when is_list(Objs) ->
2679                    ets:match_spec_run(Objs,
2680                                       ets:match_spec_compile(MS));
2681                Error ->
2682                    post_funs(Post),
2683                    throw_error(Error)
2684            end;
2685        _ when not TravMS ->
2686            MS = no_match_spec, % assertion
2687            TraverseFun;
2688        _ when MS =:= no_match_spec ->
2689            fun() -> TraverseFun([{'$1',[],['$1']}]) end;
2690        _ ->
2691            fun() -> TraverseFun(MS) end
2692    end.
2693
2694-define(CHUNK_SIZE, 64*1024).
2695
2696open_file(FileName, Extra, Post) ->
2697    case file:open(FileName, [read, raw, binary | Extra]) of
2698        {ok, Fd} ->
2699            {fun() ->
2700                 case file:position(Fd, bof) of
2701                     {ok, 0} ->
2702                         TF = fun([], _) ->
2703                                      [];
2704                                 (Ts, C) when is_list(Ts) ->
2705                                      lists:reverse(Ts, C)
2706                              end,
2707                         file_loop_read(<<>>, ?CHUNK_SIZE, {Fd,FileName}, TF);
2708                     Error ->
2709                         file_error(FileName, Error)
2710                 end
2711             end, Fd};
2712        Error ->
2713            post_funs(Post),
2714            throw_file_error(FileName, Error)
2715    end.
2716
2717file_loop(Bin0, Fd_FName, Ts0, TF) ->
2718    case
2719        try file_loop2(Bin0, Ts0)
2720        catch _:_ ->
2721            {_Fd, FileName} = Fd_FName,
2722            error({bad_object, FileName})
2723        end
2724    of
2725        {terms, <<Size:4/unit:8, B/bytes>>=Bin, []} ->
2726            file_loop_read(Bin, Size - byte_size(B) + 4, Fd_FName, TF);
2727        {terms, <<Size:4/unit:8, _/bytes>>=Bin, Ts} ->
2728            C = fun() -> file_loop_read(Bin, Size+4, Fd_FName, TF) end,
2729            TF(Ts, C);
2730        {terms, B, Ts} ->
2731            C = fun() -> file_loop_read(B, ?CHUNK_SIZE, Fd_FName, TF) end,
2732            TF(Ts, C);
2733        Error ->
2734            Error
2735    end.
2736
2737file_loop2(<<Size:4/unit:8, B:Size/bytes, Bin/bytes>>, Ts) ->
2738    file_loop2(Bin, [binary_to_term(B) | Ts]);
2739file_loop2(Bin, Ts) ->
2740    {terms, Bin, Ts}.
2741
2742%% After power failures (and only then) files with corrupted Size
2743%% fields have been observed in a disk_log file. If file:read/2 is
2744%% asked to read a huge amount of data the emulator may crash. Nothing
2745%% has been done here to prevent such crashes (by inspecting
2746%% BytesToRead in some way) since temporary files will never be read
2747%% after a power failure.
2748file_loop_read(B, MinBytesToRead, {Fd, FileName}=Fd_FName, TF) ->
2749    BytesToRead = erlang:max(?CHUNK_SIZE, MinBytesToRead),
2750    case file:read(Fd, BytesToRead) of
2751        {ok, Bin} when byte_size(B) =:= 0 ->
2752            file_loop(Bin, Fd_FName, [], TF);
2753        {ok, Bin} ->
2754            case B of
2755                <<Size:4/unit:8, Tl/bytes>>
2756                                when byte_size(Bin) + byte_size(Tl) >= Size ->
2757                    {B1, B2} = split_binary(Bin, Size - byte_size(Tl)),
2758                    Foo = fun([T], Fun) -> [T | Fun] end,
2759                    %% TF should be applied exactly once.
2760                    case
2761                        file_loop(list_to_binary([B, B1]), Fd_FName, [], Foo)
2762                    of
2763                        [T | Fun] ->
2764                            true = is_function(Fun),
2765                            file_loop(B2, Fd_FName, [T], TF);
2766                        Error ->
2767                            Error
2768                    end;
2769                _ ->
2770                    file_loop(list_to_binary([B, Bin]), Fd_FName, [], TF)
2771            end;
2772        eof when byte_size(B) =:= 0 ->
2773            TF([], foo);
2774        eof ->
2775            error({bad_object, FileName});
2776        Error ->
2777            file_error(FileName, Error)
2778    end.
2779
2780sort_cursor_input(H, NoObjects) ->
2781    fun(close) ->
2782            ok;
2783       (read) ->
2784            sort_cursor_input_read(H, NoObjects)
2785    end.
2786
2787sort_cursor_list_output(TmpDir, Z, Unique) ->
2788    fun(close) ->
2789            {terms, []};
2790       ({value, NoObjects}) ->
2791            fun(BTerms) when Unique; length(BTerms) =:= NoObjects ->
2792                    fun(close) ->
2793                            {terms, BTerms};
2794                       (BTerms1) ->
2795                            sort_cursor_file(BTerms ++ BTerms1, TmpDir, Z)
2796                    end;
2797               (BTerms) ->
2798                    sort_cursor_file(BTerms, TmpDir, Z)
2799            end
2800    end.
2801
2802sort_cursor_file(BTerms, TmpDir, Z) ->
2803    FName = tmp_filename(TmpDir),
2804    case file:open(FName, [write, raw, binary | Z]) of
2805        {ok, Fd} ->
2806            WFun = write_terms(FName, Fd),
2807            WFun(BTerms);
2808        Error ->
2809            throw_file_error(FName, Error)
2810    end.
2811
2812sort_options_global_tmp(S, "") ->
2813    S;
2814sort_options_global_tmp(S, TmpDir) ->
2815    [{tmpdir,TmpDir} | lists:keydelete(tmpdir, 1, S)].
2816
2817tmp_filename(TmpDirOpt) ->
2818    U = "_",
2819    Node = node(),
2820    Pid = os:getpid(),
2821    Unique = erlang:unique_integer(),
2822    F = lists:concat([?MODULE,U,Node,U,Pid,U,Unique]),
2823    TmpDir = case TmpDirOpt of
2824                 "" ->
2825                     {ok, CurDir} = file:get_cwd(),
2826                     CurDir;
2827                 TDir ->
2828                     TDir
2829             end,
2830    filename:join(filename:absname(TmpDir), F).
2831
2832write_terms(FileName, Fd) ->
2833    fun(close) ->
2834            _ = file:close(Fd),
2835            {file, FileName};
2836       (BTerms) ->
2837            case file:write(Fd, size_bin(BTerms, [])) of
2838                ok ->
2839                    write_terms(FileName, Fd);
2840                Error ->
2841                    _ = file:close(Fd),
2842                    throw_file_error(FileName, Error)
2843            end
2844    end.
2845
2846size_bin([], L) ->
2847    L;
2848size_bin([BinTerm | BinTerms], L) ->
2849    size_bin(BinTerms, [L, <<(byte_size(BinTerm)):4/unit:8>> | BinTerm]).
2850
2851sort_cursor_input_read([], NoObjects) ->
2852    {end_of_input, NoObjects};
2853sort_cursor_input_read([Object | Cont], NoObjects) ->
2854    {[term_to_binary(Object)], sort_cursor_input(Cont, NoObjects + 1)};
2855sort_cursor_input_read(F, NoObjects) ->
2856    case F() of
2857        Objects when is_list(Objects) ->
2858            sort_cursor_input_read(Objects, NoObjects);
2859        Term ->
2860            throw_error(Term)
2861    end.
2862
2863unique_cache(L, Post, LocalPost, Optz) when is_list(L) ->
2864    case Optz#optz.unique of
2865        true ->
2866            {unique_sort_list(L), Post, LocalPost};
2867        false ->
2868            %% If Optz#optz.cache then an ETS table could be used.
2869            {L, Post, LocalPost}
2870    end;
2871unique_cache(H, Post, LocalPost, #optz{unique = false, cache = false}) ->
2872    {H, Post, LocalPost};
2873unique_cache(H, Post, LocalPost, #optz{unique = true, cache = false}) ->
2874    E = ets:new(qlc, [set, private]),
2875    {fun() -> no_dups(H, E) end, [del_table(E) | Post], LocalPost};
2876unique_cache(H, Post, LocalPost, #optz{unique = false, cache = true}) ->
2877    E = ets:new(qlc, [set, private]),
2878    {L, P} = unique_cache_post(E),
2879    {fun() -> cache(H, E, LocalPost) end, [P | Post], [L]};
2880unique_cache(H, Post, LocalPost, #optz{unique = true, cache = true}) ->
2881    UT = ets:new(qlc, [bag, private]),
2882    MT = ets:new(qlc, [set, private]),
2883    {L1, P1} = unique_cache_post(UT),
2884    {L2, P2} = unique_cache_post(MT),
2885    {fun() -> ucache(H, UT, MT, LocalPost) end, [P1, P2 | Post], [L1, L2]};
2886unique_cache(H, Post, LocalPost, #optz{unique = false, cache = list}=Optz) ->
2887    Ref = make_ref(),
2888    F = del_lcache(Ref),
2889    #qlc_opt{tmpdir = TmpDir, max_list = MaxList, tmpdir_usage = TmpUsage} =
2890        Optz#optz.opt,
2891    {fun() -> lcache(H, Ref, LocalPost, TmpDir, MaxList, TmpUsage) end,
2892     [F | Post], [F]};
2893unique_cache(H, Post0, LocalPost0, #optz{unique = true, cache = list}=Optz) ->
2894    #qlc_opt{tmpdir = TmpDir, max_list = MaxList, tmpdir_usage = TmpUsage} =
2895        Optz#optz.opt,
2896    Size = if
2897               MaxList >= 1 bsl 31 -> (1 bsl 31) - 1;
2898               MaxList =:= 0 -> 1;
2899               true ->  MaxList
2900           end,
2901    SortOptions = [{size, Size}, {tmpdir, TmpDir}],
2902    USortOptions = [{unique, true} | SortOptions],
2903    TmpUsageM = {TmpUsage, caching},
2904    LF1 = fun(Objs) -> lists:ukeysort(1, Objs) end,
2905    FF1 = fun(Objs) ->
2906                  file_sort_handle(Objs, {keysort, 1}, USortOptions,
2907                                   TmpDir, [], Post0, LocalPost0)
2908          end,
2909    {UH, Post1, LocalPost1} = sort_handle(tag_objects(H, 1), LF1, FF1,
2910                                          USortOptions, Post0, LocalPost0,
2911                                          TmpUsageM),
2912    LF2 = fun(Objs) -> lists:keysort(2, Objs) end,
2913    FF2 = fun(Objs) ->
2914                  file_sort_handle(Objs, {keysort, 2}, SortOptions, TmpDir,
2915                                   [], Post1, LocalPost1)
2916          end,
2917    {SH, Post, LocalPost} =
2918        sort_handle(UH, LF2, FF2, SortOptions, Post1, LocalPost1, TmpUsageM),
2919    if
2920        is_list(SH) ->
2921            %% Remove the tag once and for all.
2922            {untag_objects2(SH), Post, LocalPost};
2923        true ->
2924            %% Every traversal untags the objects...
2925            {fun() -> untag_objects(SH) end, Post, LocalPost}
2926    end.
2927
2928unique_cache_post(E) ->
2929    {empty_table(E), del_table(E)}.
2930
2931unique_sort_list(L) ->
2932    E = ets:new(qlc, [set, private]),
2933    unique_list(L, E).
2934
2935unique_list([], E) ->
2936    true = ets:delete(E),
2937    [];
2938unique_list([Object | Objects], E) ->
2939    case ets:member(E, Object) of
2940        false ->
2941            true = ets:insert(E, {Object}),
2942            [Object | unique_list(Objects, E)];
2943        true ->
2944            unique_list(Objects, E)
2945    end.
2946
2947sort_list(L, CFun, true, sort, _SortOptions, _Post) when is_function(CFun) ->
2948    lists:usort(CFun, L);
2949sort_list(L, CFun, false, sort, _SortOptions, _Post) when is_function(CFun) ->
2950    lists:sort(CFun, L);
2951sort_list(L, ascending, true, sort, _SortOptions, _Post) ->
2952    lists:usort(L);
2953sort_list(L, descending, true, sort, _SortOptions, _Post) ->
2954    lists:reverse(lists:usort(L));
2955sort_list(L, ascending, false, sort, _SortOptions, _Post) ->
2956    lists:sort(L);
2957sort_list(L, descending, false, sort, _SortOptions, _Post) ->
2958    lists:reverse(lists:sort(L));
2959sort_list(L, Order, Unique, {keysort, Kp}, _SortOptions, _Post)
2960           when is_integer(Kp), is_atom(Order) ->
2961    case {Order, Unique} of
2962        {ascending, true} ->
2963            lists:ukeysort(Kp, L);
2964        {ascending, false} ->
2965            lists:keysort(Kp, L);
2966        {descending, true} ->
2967            lists:reverse(lists:ukeysort(Kp, L));
2968        {descending, false} ->
2969            lists:reverse(lists:keysort(Kp, L))
2970    end;
2971sort_list(L, _Order, _Unique, Sort, SortOptions, Post) ->
2972    In = fun(_) -> {L, fun(_) -> end_of_input end} end,
2973    Out = sort_list_output([]),
2974    TSortOptions = [{format,term} | SortOptions],
2975    do_sort(In, Out, Sort, TSortOptions, Post).
2976
2977sort_list_output(L) ->
2978    fun(close) ->
2979            lists:append(lists:reverse(L));
2980       (Terms) when is_list(Terms) ->
2981            sort_list_output([Terms | L])
2982    end.
2983
2984%% Don't use the file_sorter unless it is known that objects will be
2985%% put on a temporary file (optimization).
2986sort_handle(H, ListFun, FileFun, SortOptions, Post, LocalPost, TmpUsageM) ->
2987    Size = case lists:keyfind(size, 1, SortOptions) of
2988               {size, Size0} -> Size0;
2989               false -> default_option(size)
2990           end,
2991    sort_cache(H, [], Size, {ListFun, FileFun, Post, LocalPost, TmpUsageM}).
2992
2993sort_cache([], CL, _Sz, {LF, _FF, Post, LocalPost, _TmpUsageM}) ->
2994    {LF(lists:reverse(CL)), Post, LocalPost};
2995sort_cache(Objs, CL, Sz, C) when Sz < 0 ->
2996    sort_cache2(Objs, CL, false, C);
2997sort_cache([Object | Cont], CL, Sz0, C) ->
2998    Sz = decr_list_size(Sz0, Object),
2999    sort_cache(Cont, [Object | CL], Sz, C);
3000sort_cache(F, CL, Sz, C) ->
3001    case F() of
3002        Objects when is_list(Objects) ->
3003            sort_cache(Objects, CL, Sz, C);
3004        Term ->
3005            {_LF, _FF, Post, _LocalPost, _TmpUsageM} = C,
3006            post_funs(Post),
3007            throw_error(Term)
3008    end.
3009
3010sort_cache2([], CL, _X, {LF, _FF, Post, LocalPost, _TmpUsageM}) ->
3011    {LF(lists:reverse(CL)), Post, LocalPost};
3012sort_cache2([Object | Cont], CL, _, C) ->
3013    sort_cache2(Cont, [Object | CL], true, C);
3014sort_cache2(F, CL, false, C) ->
3015    %% Find one extra object to be sure that temporary file(s) will be
3016    %% used when calling the file_sorter. This works even if
3017    %% duplicates are removed.
3018    case F() of
3019        Objects when is_list(Objects) ->
3020            sort_cache2(Objects, CL, true, C);
3021        Term ->
3022            {_LF, _FF, Post, _LocalPost, _TmpUsageM} = C,
3023            post_funs(Post),
3024            throw_error(Term)
3025    end;
3026sort_cache2(_Cont, _CL, true, {_LF,_FF,Post,_LocalPost, {not_allowed,M}}) ->
3027    post_funs(Post),
3028    throw_reason({tmpdir_usage, M});
3029sort_cache2(Cont, CL, true, {_LF, FF, _Post, _LocalPost, {TmpUsage, M}}) ->
3030    maybe_error_logger(TmpUsage, M),
3031    FF(lists:reverse(CL, Cont)).
3032
3033file_sort_handle(H, Kp, SortOptions, TmpDir, Compressed, Post, LocalPost) ->
3034    In = sort_cursor_input(H, 0),
3035    Unique = lists:member(unique, SortOptions)
3036             orelse
3037             lists:keymember(unique, 1, SortOptions),
3038    Out = sort_cursor_list_output(TmpDir, Compressed, Unique),
3039    Reply = do_sort(In, Out, Kp, SortOptions, Post),
3040    case Reply of
3041        {file, FileName} ->
3042            {F, Fd} = open_file(FileName, Compressed, Post),
3043            P = fun() -> _ = file:close(Fd),
3044                         _ = file:delete(FileName)
3045                end,
3046            {F, [P | Post], LocalPost};
3047        {terms, BTerms} ->
3048            try
3049                {[binary_to_term(B) || B <- BTerms], Post, LocalPost}
3050            catch Class:Reason:Stacktrace ->
3051                post_funs(Post),
3052                erlang:raise(Class, Reason, Stacktrace)
3053            end
3054    end.
3055
3056do_sort(In, Out, Sort, SortOptions, Post) ->
3057    try
3058        case do_sort(In, Out, Sort, SortOptions) of
3059            {error, Reason} -> throw_reason(Reason);
3060            Reply -> Reply
3061        end
3062    catch Class:Term:Stacktrace ->
3063        post_funs(Post),
3064        erlang:raise(Class, Term, Stacktrace)
3065    end.
3066
3067do_sort(In, Out, sort, SortOptions) ->
3068    file_sorter:sort(In, Out, SortOptions);
3069do_sort(In, Out, {keysort, KeyPos}, SortOptions) ->
3070    file_sorter:keysort(KeyPos, In, Out, SortOptions).
3071
3072del_table(Ets) ->
3073    fun() -> true = ets:delete(Ets) end.
3074
3075empty_table(Ets) ->
3076    fun() -> true = ets:delete_all_objects(Ets) end.
3077
3078append_loop([[_ | _]=L], _N) ->
3079    L;
3080append_loop([F], _N) ->
3081    F();
3082append_loop([L | Hs], N) ->
3083    append_loop(L, N, Hs).
3084
3085append_loop([], N, Hs) ->
3086    append_loop(Hs, N);
3087append_loop([Object | Cont], N, Hs) ->
3088    [Object | append_loop(Cont, N + 1, Hs)];
3089append_loop(F, 0, Hs) ->
3090    case F() of
3091        [] ->
3092            append_loop(Hs, 0);
3093        [Object | Cont] ->
3094            [Object | append_loop(Cont, 1, Hs)];
3095        Term ->
3096            Term
3097    end;
3098append_loop(F, _N, Hs) -> % when _N > 0
3099    fun() -> append_loop(F, 0, Hs) end.
3100
3101no_dups([]=Cont, UTab) ->
3102    true = ets:delete_all_objects(UTab),
3103    Cont;
3104no_dups([Object | Cont], UTab) ->
3105    case ets:member(UTab, Object)  of
3106        false ->
3107            true = ets:insert(UTab, {Object}),
3108            %% A fun is created here, even if Cont is a list; objects
3109            %% will not be copied to the ETS table unless requested.
3110            [Object | fun() -> no_dups(Cont, UTab) end];
3111        true ->
3112            no_dups(Cont, UTab)
3113    end;
3114no_dups(F, UTab) ->
3115    case F() of
3116        Objects when is_list(Objects) ->
3117            no_dups(Objects, UTab);
3118        Term ->
3119            Term
3120    end.
3121
3122%% When all objects have been returned from a cached QLC, the
3123%% generators of the expression will never be called again, and so the
3124%% tables used by the generators (LocalPost) can be emptied.
3125
3126cache(H, MTab, LocalPost) ->
3127    case ets:member(MTab, 0) of
3128        false ->
3129            true = ets:insert(MTab, {0}),
3130            cache(H, MTab, 1, LocalPost);
3131        true ->
3132            cache_recall(MTab, 1)
3133    end.
3134
3135cache([]=Cont, _MTab, _SeqNo, LocalPost) ->
3136    local_post(LocalPost),
3137    Cont;
3138cache([Object | Cont], MTab, SeqNo, LocalPost) ->
3139    true = ets:insert(MTab, {SeqNo, Object}),
3140    %% A fun is created here, even if Cont is a list; objects
3141    %% will not be copied to the ETS table unless requested.
3142    [Object | fun() -> cache(Cont, MTab, SeqNo + 1, LocalPost) end];
3143cache(F, MTab, SeqNo, LocalPost) ->
3144    case F() of
3145        Objects when is_list(Objects) ->
3146            cache(Objects, MTab, SeqNo, LocalPost);
3147        Term ->
3148            Term
3149    end.
3150
3151cache_recall(MTab, SeqNo) ->
3152    case ets:lookup(MTab, SeqNo) of
3153        []=Cont ->
3154            Cont;
3155        [{SeqNo, Object}] ->
3156            [Object | fun() -> cache_recall(MTab, SeqNo + 1) end]
3157    end.
3158
3159ucache(H, UTab, MTab, LocalPost) ->
3160    case ets:member(MTab, 0) of
3161        false ->
3162            true = ets:insert(MTab, {0}),
3163            ucache(H, UTab, MTab, 1, LocalPost);
3164        true ->
3165            ucache_recall(UTab, MTab, 1)
3166    end.
3167
3168ucache([]=Cont, _UTab, _MTab, _SeqNo, LocalPost) ->
3169    local_post(LocalPost),
3170    Cont;
3171ucache([Object | Cont], UTab, MTab, SeqNo, LocalPost) ->
3172    %% Always using 28 bits hash value...
3173    Hash = erlang:phash2(Object),
3174    case ets:lookup(UTab, Hash) of
3175        [] ->
3176            ucache3(Object, Cont, Hash, UTab, MTab, SeqNo, LocalPost);
3177        HashSeqObjects ->
3178            case lists:keymember(Object, 3, HashSeqObjects) of
3179                true ->
3180                    ucache(Cont, UTab, MTab, SeqNo, LocalPost);
3181                false ->
3182                    ucache3(Object, Cont, Hash, UTab, MTab, SeqNo, LocalPost)
3183            end
3184    end;
3185ucache(F, UTab, MTab, SeqNo, LocalPost) ->
3186    case F() of
3187        Objects when is_list(Objects) ->
3188            ucache(Objects, UTab, MTab, SeqNo, LocalPost);
3189        Term ->
3190            Term
3191    end.
3192
3193ucache3(Object, Cont, Hash, UTab, MTab, SeqNo, LocalPost) ->
3194    true = ets:insert(UTab, {Hash, SeqNo, Object}),
3195    true = ets:insert(MTab, {SeqNo, Hash}),
3196    %% A fun is created here, even if Cont is a list; objects
3197    %% will not be copied to the ETS table unless requested.
3198    [Object | fun() -> ucache(Cont, UTab, MTab, SeqNo+1, LocalPost) end].
3199
3200ucache_recall(UTab, MTab, SeqNo) ->
3201    case ets:lookup(MTab, SeqNo) of
3202        []=Cont ->
3203            Cont;
3204        [{SeqNo, Hash}] ->
3205            Object = case ets:lookup(UTab, Hash) of
3206                         [{Hash, SeqNo, Object0}] -> Object0;
3207                         HashSeqObjects ->
3208                             {Hash, SeqNo, Object0} =
3209                                 lists:keyfind(SeqNo, 2, HashSeqObjects),
3210                             Object0
3211                     end,
3212            [Object | fun() -> ucache_recall(UTab, MTab, SeqNo + 1) end]
3213    end.
3214
3215-define(LCACHE_FILE(Ref), {Ref, '$_qlc_cache_tmpfiles_'}).
3216
3217lcache(H, Ref, LocalPost, TmpDir, MaxList, TmpUsage) ->
3218    Key = ?LCACHE_FILE(Ref),
3219    case get(Key) of
3220        undefined ->
3221            lcache1(H, {Key, LocalPost, TmpDir, MaxList, TmpUsage},
3222                    MaxList, []);
3223        {file, _Fd, _TmpFile, F} ->
3224            F();
3225        L when is_list(L) ->
3226            L
3227    end.
3228
3229lcache1([]=Cont, {Key, LocalPost, _TmpDir, _MaxList, _TmpUsage}, _Sz, Acc) ->
3230    local_post(LocalPost),
3231    case get(Key) of
3232        undefined ->
3233            put(Key, lists:reverse(Acc)),
3234            Cont;
3235        {file, Fd, TmpFile, _F} ->
3236            case lcache_write(Fd, TmpFile, Acc) of
3237                ok ->
3238                    Cont;
3239                Error ->
3240                    Error
3241            end
3242    end;
3243lcache1(H, State, Sz, Acc) when Sz < 0 ->
3244    {Key, LocalPost, TmpDir, MaxList, TmpUsage} = State,
3245    GetFile =
3246        case get(Key) of
3247            {file, Fd0, TmpFile, _F} ->
3248                {TmpFile, Fd0};
3249            undefined when TmpUsage =:= not_allowed ->
3250                error({tmpdir_usage, caching});
3251            undefined ->
3252                maybe_error_logger(TmpUsage, caching),
3253                FName = tmp_filename(TmpDir),
3254                {F, Fd0} = open_file(FName, [write], LocalPost),
3255                put(Key, {file, Fd0, FName, F}),
3256                {FName, Fd0}
3257        end,
3258    case GetFile of
3259        {FileName, Fd} ->
3260            case lcache_write(Fd, FileName, Acc) of
3261                ok ->
3262                    lcache1(H, State, MaxList, []);
3263                Error ->
3264                    Error
3265            end;
3266        Error ->
3267            Error
3268    end;
3269lcache1([Object | Cont], State, Sz0, Acc) ->
3270    Sz = decr_list_size(Sz0, Object),
3271    [Object | lcache2(Cont, State, Sz, [Object | Acc])];
3272lcache1(F, State, Sz, Acc) ->
3273    case F() of
3274        Objects when is_list(Objects) ->
3275            lcache1(Objects, State, Sz, Acc);
3276        Term ->
3277            Term
3278    end.
3279
3280lcache2([Object | Cont], State, Sz0, Acc) when Sz0 >= 0 ->
3281    Sz = decr_list_size(Sz0, Object),
3282    [Object | lcache2(Cont, State, Sz, [Object | Acc])];
3283lcache2(Cont, State, Sz, Acc) ->
3284    fun() -> lcache1(Cont, State, Sz, Acc) end.
3285
3286lcache_write(Fd, FileName, L) ->
3287    write_binary_terms(t2b(L, []), Fd, FileName).
3288
3289t2b([], Bs) ->
3290    Bs;
3291t2b([T | Ts], Bs) ->
3292    t2b(Ts, [term_to_binary(T) | Bs]).
3293
3294del_lcache(Ref) ->
3295    fun() ->
3296            Key = ?LCACHE_FILE(Ref),
3297            case get(Key) of
3298                undefined ->
3299                    ok;
3300                {file, Fd, TmpFile, _F} ->
3301                    _ = file:close(Fd),
3302                    _ = file:delete(TmpFile),
3303                    erase(Key);
3304                _L ->
3305                    erase(Key)
3306            end
3307    end.
3308
3309tag_objects([Object | Cont], T) ->
3310    [{Object, T} | tag_objects2(Cont, T + 1)];
3311tag_objects([]=Cont, _T) ->
3312    Cont;
3313tag_objects(F, T) ->
3314    case F() of
3315        Objects when is_list(Objects) ->
3316            tag_objects(Objects, T);
3317        Term ->
3318            Term
3319    end.
3320
3321tag_objects2([Object | Cont], T) ->
3322    [{Object, T} | tag_objects2(Cont, T + 1)];
3323tag_objects2(Objects, T) ->
3324    fun() -> tag_objects(Objects, T) end.
3325
3326untag_objects([]=Objs) ->
3327    Objs;
3328untag_objects([{Object, _N} | Cont]) ->
3329    [Object | untag_objects2(Cont)];
3330untag_objects(F) ->
3331    case F() of
3332        Objects when is_list(Objects) ->
3333            untag_objects(Objects);
3334        Term -> % Cannot happen
3335            Term
3336    end.
3337
3338untag_objects2([{Object, _N} | Cont]) ->
3339    [Object | untag_objects2(Cont)];
3340untag_objects2([]=Cont) ->
3341    Cont;
3342untag_objects2(Objects) ->
3343    fun() -> untag_objects(Objects) end.
3344
3345%%% Merge join.
3346%%% Temporary files are used when many objects have the same key.
3347
3348-define(JWRAP(E1, E2), [E1 | E2]).
3349
3350-record(m, {id, tmpdir, max_list, tmp_usage}).
3351
3352merge_join([]=Cont, _C1, _T2, _C2, _Opt) ->
3353    Cont;
3354merge_join([E1 | L1], C1, L2, C2, Opt) ->
3355    #qlc_opt{tmpdir = TmpDir, max_list = MaxList,
3356             tmpdir_usage = TmpUsage} = Opt,
3357    M = #m{id = merge_join_id(), tmpdir = TmpDir, max_list = MaxList,
3358           tmp_usage = TmpUsage},
3359    merge_join2(E1, element(C1, E1), L1, C1, L2, C2, M);
3360merge_join(F1, C1, L2, C2, Opt) ->
3361    case F1() of
3362        L1 when is_list(L1) ->
3363            merge_join(L1, C1, L2, C2, Opt);
3364        T1 ->
3365            T1
3366    end.
3367
3368merge_join1(_E2, _K2, []=Cont, _C1, _L2, _C2, M) ->
3369    end_merge_join(Cont, M);
3370merge_join1(E2, K2, [E1 | L1], C1, L2, C2, M) ->
3371    K1 = element(C1, E1),
3372    if
3373        K1 == K2 ->
3374            same_keys2(E1, K1, L1, C1, L2, C2, E2, M);
3375        K1 > K2 ->
3376            merge_join2(E1, K1, L1, C1, L2, C2, M);
3377        true -> % K1 < K2
3378            merge_join1(E2, K2, L1, C1, L2, C2, M)
3379    end;
3380merge_join1(E2, K2, F1, C1, L2, C2, M) ->
3381    case F1() of
3382        L1 when is_list(L1) ->
3383            merge_join1(E2, K2, L1, C1, L2, C2, M);
3384        T1 ->
3385            T1
3386    end.
3387
3388merge_join2(_E1, _K1, _L1, _C1, []=Cont, _C2, M) ->
3389    end_merge_join(Cont, M);
3390merge_join2(E1, K1, L1, C1, [E2 | L2], C2, M) ->
3391    K2 = element(C2, E2),
3392    if
3393        K1 == K2 ->
3394            same_keys2(E1, K1, L1, C1, L2, C2, E2, M);
3395        K1 > K2 ->
3396            merge_join2(E1, K1, L1, C1, L2, C2, M);
3397        true -> % K1 < K2
3398            merge_join1(E2, K2, L1, C1, L2, C2, M)
3399    end;
3400merge_join2(E1, K1, L1, C1, F2, C2, M) ->
3401    case F2() of
3402        L2 when is_list(L2) ->
3403            merge_join2(E1, K1, L1, C1, L2, C2, M);
3404        T2 ->
3405            T2
3406    end.
3407
3408%% element(C2, E2_0) == K1
3409same_keys2(E1, K1, L1, C1, [], _C2, E2_0, M) ->
3410    Cont = fun(_L1b) -> end_merge_join([], M) end,
3411    loop_same_keys(E1, K1, L1, C1, [E2_0], Cont, M);
3412same_keys2(E1, K1, L1, C1, [E2 | L2]=L2_0, C2, E2_0, M) ->
3413    K2 = element(C2, E2),
3414    if
3415        K1 == K2 ->
3416            same_keys1(E1, K1, L1, C1, E2, C2, E2_0, L2, M);
3417        K1 < K2 ->
3418            [?JWRAP(E1, E2_0) |
3419             fun() -> same_loop1(L1, K1, C1, E2_0, L2_0, C2, M) end]
3420    end;
3421same_keys2(E1, K1, L1, C1, F2, C2, E2_0, M) ->
3422    case F2() of
3423        L2 when is_list(L2) ->
3424            same_keys2(E1, K1, L1, C1, L2, C2, E2_0, M);
3425        T2 ->
3426            Cont = fun(_L1b) -> T2 end,
3427            loop_same_keys(E1, K1, L1, C1, [E2_0], Cont, M)
3428    end.
3429
3430same_loop1([], _K1_0, _C1, _E2_0, _L2, _C2, M) ->
3431    end_merge_join([], M);
3432same_loop1([E1 | L1], K1_0, C1, E2_0, L2, C2, M) ->
3433    K1 = element(C1, E1),
3434    if
3435        K1 == K1_0 ->
3436            [?JWRAP(E1, E2_0) |
3437             fun() -> same_loop1(L1, K1_0, C1, E2_0, L2, C2, M) end];
3438        K1_0 < K1 ->
3439            merge_join2(E1, K1, L1, C1, L2, C2, M)
3440    end;
3441same_loop1(F1, K1_0, C1, E2_0, L2, C2, M) ->
3442    case F1() of
3443        L1 when is_list(L1) ->
3444            same_loop1(L1, K1_0, C1, E2_0, L2, C2, M);
3445        T1 ->
3446            T1
3447    end.
3448
3449%% element(C2, E2_0) == K1, element(C2, E2) == K1_0
3450same_keys1(E1_0, K1_0, []=L1, C1, E2, C2, E2_0, L2, M) ->
3451    [?JWRAP(E1_0, E2_0), ?JWRAP(E1_0, E2) |
3452     fun() -> same_keys(K1_0, E1_0, L1, C1, L2, C2, M) end];
3453same_keys1(E1_0, K1_0, [E1 | _]=L1, C1, E2, C2, E2_0, L2, M) ->
3454    K1 = element(C1, E1),
3455    if
3456        K1_0 == K1 ->
3457            E2s = [E2, E2_0],
3458            Sz0 = decr_list_size(M#m.max_list, E2s),
3459            same_keys_cache(E1_0, K1_0, L1, C1, L2, C2, E2s, Sz0, M);
3460        K1_0 < K1  ->
3461            [?JWRAP(E1_0, E2_0), ?JWRAP(E1_0, E2) |
3462             fun() -> same_keys(K1_0, E1_0, L1, C1, L2, C2, M) end]
3463    end;
3464same_keys1(E1_0, K1_0, F1, C1, E2, C2, E2_0, L2, M) ->
3465    case F1() of
3466        L1 when is_list(L1) ->
3467            same_keys1(E1_0, K1_0, L1, C1, E2, C2, E2_0, L2, M);
3468        T1 ->
3469            Cont = fun() -> T1 end,
3470            loop_same(E1_0, [E2, E2_0], Cont)
3471    end.
3472
3473%% There is no such element E in L1 such that element(C1, E) == K1.
3474same_keys(_K1, _E1, _L1, _C1, []=Cont, _C2, M) ->
3475    end_merge_join(Cont, M);
3476same_keys(K1, E1, L1, C1, [E2 | L2], C2, M) ->
3477    K2 = element(C2, E2),
3478    if
3479        K1 == K2 ->
3480            [?JWRAP(E1, E2) |
3481             fun() -> same_keys(K1, E1, L1, C1, L2, C2, M) end];
3482        K1 < K2 ->
3483            merge_join1(E2, K2, L1, C1, L2, C2, M)
3484    end;
3485same_keys(K1, E1, L1, C1, F2, C2, M) ->
3486    case F2() of
3487        L2 when is_list(L2) ->
3488            same_keys(K1, E1, L1, C1, L2, C2, M);
3489        T2 ->
3490            T2
3491    end.
3492
3493%% There are at least two elements in [E1 | L1] that are to be combined
3494%% with the elements in E2s (length(E2s) > 1). This loop covers the case
3495%% when all elements in E2 with key K1 can be kept in RAM.
3496same_keys_cache(E1, K1, L1, C1, [], _C2, E2s, _Sz, M) ->
3497    Cont = fun(_L1b) -> end_merge_join([], M) end,
3498    loop_same_keys(E1, K1, L1, C1, E2s, Cont, M);
3499same_keys_cache(E1, K1, L1, C1, L2, C2, E2s, Sz0, M) when Sz0 < 0 ->
3500    case init_merge_join(M) of
3501        ok ->
3502            Sz = M#m.max_list,
3503            C = fun() ->
3504                        same_keys_file(E1, K1, L1, C1, L2, C2, [], Sz, M)
3505                end,
3506            write_same_keys(E1, E2s, M, C);
3507        Error ->
3508            Error
3509    end;
3510same_keys_cache(E1, K1, L1, C1, [E2 | L2], C2, E2s, Sz0, M) ->
3511    K2 = element(C2, E2),
3512    if
3513        K1 == K2 ->
3514            Sz = decr_list_size(Sz0, E2),
3515            same_keys_cache(E1, K1, L1, C1, L2, C2, [E2 | E2s], Sz, M);
3516        K1 < K2 ->
3517            Cont = fun(L1b) -> merge_join1(E2, K2, L1b, C1, L2, C2, M) end,
3518            loop_same_keys(E1, K1, L1, C1, E2s, Cont, M)
3519    end;
3520same_keys_cache(E1, K1, L1, C1, F2, C2, E2s, Sz, M) ->
3521    case F2() of
3522        L2 when is_list(L2) ->
3523            same_keys_cache(E1, K1, L1, C1, L2, C2, E2s, Sz, M);
3524        T2 ->
3525            Cont = fun(_L1b) -> T2 end,
3526            loop_same_keys(E1, K1, L1, C1, E2s, Cont, M)
3527    end.
3528
3529%% E2s holds all elements E2 in L2 such that element(E2, C2) == K1.
3530loop_same_keys(E1, _K1, [], _C1, E2s, _Cont, M) ->
3531    end_merge_join(loop_same(E1, E2s, []), M);
3532loop_same_keys(E1, K1, L1, C1, E2s, Cont, M) ->
3533    loop_same(E1, E2s, fun() -> loop_keys(K1, L1, C1, E2s, Cont, M) end).
3534
3535loop_same(_E1, [], L) ->
3536    L;
3537loop_same(E1, [E2 | E2s], L) ->
3538    loop_same(E1, E2s, [?JWRAP(E1, E2) | L]).
3539
3540loop_keys(K, [E1 | L1]=L1_0, C1, E2s, Cont, M) ->
3541    K1 = element(C1, E1),
3542    if
3543        K1 == K ->
3544            loop_same_keys(E1, K1, L1, C1, E2s, Cont, M);
3545        K1 > K ->
3546            Cont(L1_0)
3547    end;
3548loop_keys(_K, []=L1, _C1, _Es2, Cont, _M) ->
3549    Cont(L1);
3550loop_keys(K, F1, C1, E2s, Cont, M) ->
3551    case F1() of
3552        L1 when is_list(L1) ->
3553            loop_keys(K, L1, C1, E2s, Cont, M);
3554        T1 ->
3555            T1
3556    end.
3557
3558%% This is for the case when a temporary file has to be used.
3559same_keys_file(E1, K1, L1, C1, [], _C2, E2s, _Sz, M) ->
3560    Cont = fun(_L1b) -> end_merge_join([], M) end,
3561    same_keys_file_write(E1, K1, L1, C1, E2s, M, Cont);
3562same_keys_file(E1, K1, L1, C1, L2, C2, E2s, Sz0, M) when Sz0 < 0 ->
3563    Sz = M#m.max_list,
3564    C = fun() -> same_keys_file(E1, K1, L1, C1, L2, C2, [], Sz, M) end,
3565    write_same_keys(E1, E2s, M, C);
3566same_keys_file(E1, K1, L1, C1, [E2 | L2], C2, E2s, Sz0, M) ->
3567    K2 = element(C2, E2),
3568    if
3569        K1 == K2 ->
3570            Sz = decr_list_size(Sz0, E2),
3571            same_keys_file(E1, K1, L1, C1, L2, C2, [E2 | E2s], Sz, M);
3572        K1 < K2 ->
3573            Cont = fun(L1b) ->
3574                           %% The temporary file could be truncated here.
3575                           merge_join1(E2, K2, L1b, C1, L2, C2, M)
3576                   end,
3577            same_keys_file_write(E1, K1, L1, C1, E2s, M, Cont)
3578    end;
3579same_keys_file(E1, K1, L1, C1, F2, C2, E2s, Sz, M) ->
3580    case F2() of
3581        L2 when is_list(L2) ->
3582            same_keys_file(E1, K1, L1, C1, L2, C2, E2s, Sz, M);
3583        T2 ->
3584            Cont = fun(_L1b) -> T2 end,
3585            same_keys_file_write(E1, K1, L1, C1, E2s, M, Cont)
3586    end.
3587
3588same_keys_file_write(E1, K1, L1, C1, E2s, M, Cont) ->
3589    C = fun() -> loop_keys_file(K1, L1, C1, Cont, M) end,
3590    write_same_keys(E1, E2s, M, C).
3591
3592write_same_keys(_E1, [], _M, Cont) ->
3593    Cont();
3594write_same_keys(E1, Es2, M, Cont) ->
3595    write_same_keys(E1, Es2, M, [], Cont).
3596
3597%% Avoids one (the first) traversal of the temporary file.
3598write_same_keys(_E1, [], M, E2s, Objs) ->
3599    case write_merge_join(M, E2s) of
3600        ok -> Objs;
3601        Error -> Error
3602    end;
3603write_same_keys(E1, [E2 | E2s0], M, E2s, Objs) ->
3604    BE2 = term_to_binary(E2),
3605    write_same_keys(E1, E2s0, M, [BE2 | E2s], [?JWRAP(E1, E2) | Objs]).
3606
3607loop_keys_file(K, [E1 | L1]=L1_0, C1, Cont, M) ->
3608    K1 = element(C1, E1),
3609    if
3610        K1 == K ->
3611            C = fun() -> loop_keys_file(K1, L1, C1, Cont, M) end,
3612            read_merge_join(M, E1, C);
3613        K1 > K ->
3614            Cont(L1_0)
3615    end;
3616loop_keys_file(_K, []=L1, _C1, Cont, _M) ->
3617    Cont(L1);
3618loop_keys_file(K, F1, C1, Cont, M) ->
3619    case F1() of
3620        L1 when is_list(L1) ->
3621            loop_keys_file(K, L1, C1, Cont, M);
3622        T1 ->
3623            T1
3624    end.
3625
3626end_merge_join(Reply, M) ->
3627    end_merge_join(M),
3628    Reply.
3629
3630%% Normally post_funs() cleans up temporary files by calling funs in
3631%% Post. It seems impossible to do that with the temporary file(s)
3632%% used when many objects have the same key--such a file is created
3633%% after the setup when Post is prepared. There seems to be no real
3634%% alternative to using the process dictionary, at least as things
3635%% have been implemented so far. Probably all of Post could have been
3636%% put in the process dictionary...
3637
3638-define(MERGE_JOIN_FILE, '$_qlc_merge_join_tmpfiles_').
3639
3640init_merge_join(#m{id = MergeId, tmpdir = TmpDir, tmp_usage = TmpUsage}) ->
3641    case tmp_merge_file(MergeId) of
3642        {Fd, FileName} ->
3643            case file:position(Fd, bof) of
3644                {ok, 0} ->
3645                    case file:truncate(Fd) of
3646                        ok ->
3647                            ok;
3648                        Error ->
3649                            file_error(FileName, Error)
3650                    end;
3651                Error ->
3652                    file_error(FileName, Error)
3653            end;
3654        none when TmpUsage =:= not_allowed ->
3655            error({tmpdir_usage, joining});
3656        none ->
3657            maybe_error_logger(TmpUsage, joining),
3658            FName = tmp_filename(TmpDir),
3659            case file:open(FName, [raw, binary, read, write]) of
3660                {ok, Fd} ->
3661                    TmpFiles = get(?MERGE_JOIN_FILE),
3662                    put(?MERGE_JOIN_FILE, [{MergeId, Fd, FName} | TmpFiles]),
3663                    ok;
3664                Error ->
3665                    file_error(FName, Error)
3666            end
3667    end.
3668
3669write_merge_join(#m{id = MergeId}, BTerms) ->
3670    {Fd, FileName} = tmp_merge_file(MergeId),
3671    write_binary_terms(BTerms, Fd, FileName).
3672
3673read_merge_join(#m{id = MergeId}, E1, Cont) ->
3674    {Fd, FileName} = tmp_merge_file(MergeId),
3675    case file:position(Fd, bof) of
3676        {ok, 0} ->
3677            Fun = fun([], _) ->
3678                          Cont();
3679                     (Ts, C) when is_list(Ts) ->
3680                          join_read_terms(E1, Ts, C)
3681                  end,
3682            file_loop_read(<<>>, ?CHUNK_SIZE, {Fd, FileName}, Fun);
3683        Error ->
3684            file_error(FileName, Error)
3685    end.
3686
3687join_read_terms(_E1, [], Objs) ->
3688    Objs;
3689join_read_terms(E1, [E2 | E2s], Objs) ->
3690    join_read_terms(E1, E2s, [?JWRAP(E1, E2) | Objs]).
3691
3692end_merge_join(#m{id = MergeId}) ->
3693    case tmp_merge_file(MergeId) of
3694        none ->
3695            ok;
3696        {Fd, FileName}  ->
3697            _ = file:close(Fd),
3698            _ = file:delete(FileName),
3699            put(?MERGE_JOIN_FILE,
3700                lists:keydelete(MergeId, 1, get(?MERGE_JOIN_FILE)))
3701    end.
3702
3703end_all_merge_joins() ->
3704    lists:foreach(
3705      fun(Id) -> end_merge_join(#m{id = Id}) end,
3706      [Id || {Id, _Fd, _FileName} <- lists:flatten([get(?MERGE_JOIN_FILE)])]),
3707    erase(?MERGE_JOIN_FILE).
3708
3709merge_join_id() ->
3710    case get(?MERGE_JOIN_FILE) of
3711        undefined ->
3712            put(?MERGE_JOIN_FILE, []);
3713        _ ->
3714            ok
3715    end,
3716    make_ref().
3717
3718tmp_merge_file(MergeId) ->
3719    TmpFiles = get(?MERGE_JOIN_FILE),
3720    case lists:keyfind(MergeId, 1, TmpFiles) of
3721        {MergeId, Fd, FileName} ->
3722            {Fd, FileName};
3723        false ->
3724            none
3725    end.
3726
3727decr_list_size(Sz0, E) when is_integer(Sz0) ->
3728    Sz0 - erlang:external_size(E).
3729
3730%%% End of merge join.
3731
3732lookup_join([E1 | L1], C1, LuF, C2, Rev) ->
3733    K1 = element(C1, E1),
3734    case LuF(C2, [K1]) of
3735        [] ->
3736            lookup_join(L1, C1, LuF, C2, Rev);
3737        [E2] when Rev ->
3738            [?JWRAP(E2, E1) | fun() -> lookup_join(L1, C1, LuF, C2, Rev) end];
3739        [E2] ->
3740            [?JWRAP(E1, E2) | fun() -> lookup_join(L1, C1, LuF, C2, Rev) end];
3741        E2s when is_list(E2s), Rev ->
3742            [?JWRAP(E2, E1) || E2 <- E2s] ++
3743                fun() -> lookup_join(L1, C1, LuF, C2, Rev) end;
3744        E2s when is_list(E2s) ->
3745            [?JWRAP(E1, E2) || E2 <- E2s] ++
3746                fun() -> lookup_join(L1, C1, LuF, C2, Rev) end;
3747        Term ->
3748            Term
3749    end;
3750lookup_join([]=Cont, _C1, _LuF, _C2, _Rev) ->
3751    Cont;
3752lookup_join(F1, C1, LuF, C2, Rev) ->
3753    case F1() of
3754        L1 when is_list(L1) ->
3755            lookup_join(L1, C1, LuF, C2, Rev);
3756        T1 ->
3757            T1
3758    end.
3759
3760maybe_error_logger(allowed, _) ->
3761    ok;
3762maybe_error_logger(Name, Why) ->
3763    [_, _, {?MODULE,maybe_error_logger,_,_} | Stacktrace] =
3764	expand_stacktrace(),
3765    Trimmer = fun(M, _F, _A) -> M =:= erl_eval end,
3766    Formater = fun(Term, I) -> io_lib:print(Term, I, 80, -1) end,
3767    X = erl_error:format_stacktrace(1, Stacktrace, Trimmer, Formater),
3768    error_logger:Name("qlc: temporary file was needed for ~w\n~ts\n",
3769                      [Why, lists:flatten(X)]).
3770
3771expand_stacktrace() ->
3772    D = erlang:system_flag(backtrace_depth, 8),
3773    try
3774        %% Compensate for a bug in erlang:system_flag/2:
3775        expand_stacktrace(erlang:max(1, D))
3776    after
3777        erlang:system_flag(backtrace_depth, D)
3778    end.
3779
3780expand_stacktrace(D) ->
3781    _ = erlang:system_flag(backtrace_depth, D),
3782    {'EXIT', {foo, Stacktrace}} = (catch erlang:error(foo)),
3783    L = lists:takewhile(fun({M,_,_,_}) -> M =/= ?MODULE
3784                        end, lists:reverse(Stacktrace)),
3785    if
3786        length(L) < 3 andalso length(Stacktrace) =:= D ->
3787            expand_stacktrace(D + 5);
3788        true ->
3789            Stacktrace
3790    end.
3791
3792write_binary_terms(BTerms, Fd, FileName) ->
3793    case file:write(Fd, size_bin(BTerms, [])) of
3794        ok ->
3795            ok;
3796        Error ->
3797            file_error(FileName, Error)
3798    end.
3799
3800post_funs(L) ->
3801    end_all_merge_joins(),
3802    local_post(L).
3803
3804local_post(L) ->
3805    lists:foreach(fun(undefined) -> ok;
3806                     (F) -> catch (F)()
3807                  end, L).
3808
3809call(undefined, _Arg, Default, _Post) ->
3810    Default;
3811call(Fun, Arg, _Default, Post) ->
3812    try
3813        Fun(Arg)
3814    catch Class:Reason:Stacktrace ->
3815        post_funs(Post),
3816        erlang:raise(Class, Reason, Stacktrace)
3817    end.
3818
3819grd(undefined, _Arg) ->
3820    false;
3821grd(Fun, Arg) ->
3822    case Fun(Arg) of
3823        true ->
3824            true;
3825        _ ->
3826            false
3827    end.
3828
3829anno0() ->
3830    anno(0).
3831
3832anno1() ->
3833    anno(1).
3834
3835anno(L) ->
3836    erl_anno:new(L).
3837
3838family(L) ->
3839    sofs:to_external(sofs:relation_to_family(sofs:relation(L))).
3840
3841family_union(L) ->
3842    R = sofs:relation(L,[{atom,[atom]}]),
3843    sofs:to_external(sofs:family_union(sofs:relation_to_family(R))).
3844
3845file_error(File, {error, Reason}) ->
3846    error({file_error, File, Reason}).
3847
3848-spec throw_file_error(string(), {'error',atom()}) -> no_return().
3849
3850throw_file_error(File, {error, Reason}) ->
3851    throw_reason({file_error, File, Reason}).
3852
3853-spec throw_reason(term()) -> no_return().
3854
3855throw_reason(Reason) ->
3856    throw_error(error(Reason)).
3857
3858-spec throw_error(term()) -> no_return().
3859
3860throw_error(Error) ->
3861    throw(Error).
3862
3863error(Reason) ->
3864    {error, ?MODULE, Reason}.
3865