1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2004-2019. 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%%%----------------------------------------------------------------
21%%% Purpose:Test Suite for the 'qlc' module.
22%%%-----------------------------------------------------------------
23-module(qlc_SUITE).
24
25-define(QLC, qlc).
26-define(QLCs, "qlc").
27
28%%-define(debug, true).
29
30%% There are often many tests per testcase. Most tests are copied to a
31%% module, a file. The file is compiled and the test run. Should the
32%% test fail, the module file is not removed from ?privdir, but is
33%% kept for inspection. The name of the file is
34%% ?privdir/qlc_test_CASE.erl.
35-define(TESTMODULE, qlc_test).
36-define(TESTCASE, testcase_name).
37
38-ifdef(debug).
39-define(line, put(line, ?LINE), ).
40-define(config(X,Y), foo).
41-define(datadir, ?QLCs ++  "_SUITE_data").
42-define(privdir, ?QLCs ++ "_SUITE_priv").
43-define(testcase, current_testcase). % don't know
44-define(t, test_server).
45-else.
46-include_lib("common_test/include/ct.hrl").
47-define(datadir, proplists:get_value(data_dir, Config)).
48-define(privdir, proplists:get_value(priv_dir, Config)).
49-define(testcase, proplists:get_value(?TESTCASE, Config)).
50-endif.
51
52-include_lib("stdlib/include/ms_transform.hrl").
53
54-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
55	 init_per_group/2,end_per_group/2,
56	 init_per_testcase/2, end_per_testcase/2]).
57
58-export([
59	  badarg/1, nested_qlc/1, unused_var/1, lc/1, fun_clauses/1,
60	  filter_var/1, single/1, exported_var/1, generator_vars/1,
61	  nomatch/1, errors/1, pattern/1, overridden_bif/1,
62
63	  eval/1, cursor/1, fold/1, eval_unique/1, eval_cache/1, append/1,
64	  evaluator/1, string_to_handle/1, table/1, process_dies/1,
65	  sort/1, keysort/1, filesort/1, cache/1, cache_list/1, filter/1,
66	  info/1, nested_info/1, lookup1/1, lookup2/1, lookup_rec/1,
67	  indices/1, pre_fun/1, skip_filters/1,
68
69	  ets/1, dets/1,
70
71	  join_option/1, join_filter/1, join_lookup/1, join_merge/1,
72	  join_sort/1, join_complex/1,
73
74	  otp_5644/1, otp_5195/1, otp_6038_bug/1, otp_6359/1, otp_6562/1,
75	  otp_6590/1, otp_6673/1, otp_6964/1, otp_7114/1, otp_7238/1,
76	  otp_7232/1, otp_7552/1, otp_6674/1, otp_7714/1, otp_11758/1,
77          otp_12946/1,
78
79	  manpage/1,
80
81	  backward/1, forward/1,
82
83	  eep37/1]).
84
85%% Internal exports.
86-export([bad_table_throw/1, bad_table_exit/1, default_table/1, bad_table/1,
87         bad_table_format/1, bad_table_format_arity/1, bad_table_traverse/1,
88         bad_table_post/1, bad_table_lookup/1, bad_table_max_lookup/1,
89         bad_table_info_arity/1, bad_table_info_fun_n_objects/1,
90         bad_table_info_fun_indices/1, bad_table_info_fun_keypos/1,
91         bad_table_key_equality/1]).
92-export([evaluator_2/2]).
93-export([prep_scratchdir/1, truncate_tmpfile/2, crash/2, crash_tmpfile/2]).
94-export([etsc/2, etsc/3, create_ets/2, lookup_keys/1]).
95-export([strip_qlc_call/1, join_info/1, join_info_count/1]).
96-export([i/1, i/2, format_info/2]).
97
98-export([table_kill_parent/2, table_parent_throws/2,
99         table_parent_exits/2, table_bad_parent_fun/2]).
100-export([table/2, table/3, stop_list/2, table_error/2, table_error/3,
101         table_lookup_error/1]).
102
103%% error_logger
104-export([install_error_logger/0, uninstall_error_logger/0,
105         read_error_logger/0]).
106-export([init/1,
107	 handle_event/2, handle_call/2, handle_info/2,
108	 terminate/2]).
109
110init_per_testcase(Case, Config) ->
111    [{?TESTCASE, Case} | Config].
112
113end_per_testcase(_Case, _Config) ->
114    ok.
115
116suite() ->
117    [{ct_hooks,[ts_install_cth]},
118     {timetrap,{minutes,5}}].
119
120all() ->
121    [{group, parse_transform}, {group, evaluation},
122     {group, table_impls}, {group, join}, {group, tickets},
123     manpage, {group, compat}].
124
125groups() ->
126    [{parse_transform, [],
127      [badarg, nested_qlc, unused_var, lc, fun_clauses,
128       filter_var, single, exported_var, generator_vars,
129       nomatch, errors, pattern, overridden_bif]},
130     {evaluation, [],
131      [eval, cursor, fold, eval_unique, eval_cache, append,
132       evaluator, string_to_handle, table, process_dies, sort,
133       keysort, filesort, cache, cache_list, filter, info,
134       nested_info, lookup1, lookup2, lookup_rec, indices,
135       pre_fun, skip_filters, eep37]},
136     {table_impls, [], [ets, dets]},
137     {join, [],
138      [join_option, join_filter, join_lookup, join_merge,
139       join_sort, join_complex]},
140     {tickets, [],
141      [otp_5644, otp_5195, otp_6038_bug, otp_6359, otp_6562,
142       otp_6590, otp_6673, otp_6964, otp_7114, otp_7232,
143       otp_7238, otp_7552, otp_6674, otp_7714, otp_11758, otp_12946]},
144     {compat, [], [backward, forward]}].
145
146init_per_suite(Config) ->
147    Config.
148
149end_per_suite(_Config) ->
150    ok.
151
152init_per_group(_GroupName, Config) ->
153    Config.
154
155end_per_group(_GroupName, Config) ->
156    Config.
157
158badarg(Config) when is_list(Config) ->
159    Ts =
160	[{badarg,
161	  <<"-import(qlc, [q/1, q/2]).
162          q(_, _, _) -> ok.
163
164badarg() ->
165    qlc:q(foo),
166    qlc:q(foo, cache_all),
167    qlc:q(foo, cache_all, extra),
168    q(bar),
169    q(bar, cache_all),
170    q(bar, cache_all, extra).
171">>,
172       [],
173{errors,[{5,?QLC,not_a_query_list_comprehension},
174	 {6,?QLC,not_a_query_list_comprehension},
175	 {8,?QLC,not_a_query_list_comprehension},
176	 {9,?QLC,not_a_query_list_comprehension}],
177 []}}],
178    [] = compile(Config, Ts),
179    ok.
180
181%% Nested qlc expressions.
182nested_qlc(Config) when is_list(Config) ->
183    %% Nested QLC expressions. X is bound before the first one; Z and X
184    %% before the second one.
185    Ts =
186     [{nested_qlc1,
187       <<"nested_qlc() ->
188              X = 3, % X unused
189              Q = qlc:q([Y ||
190                            X <- % X shadowed
191                                begin Z = 3,
192                                      qlc:q([Y ||
193                                                Y <- [Z],
194                                                X <- [1,2,3], % X shadowed
195                                                X < Y])
196                                end,
197                            Y <-
198                                [y],
199                            Y > X]),
200              [y, y] = qlc:e(Q),
201              ok.
202       ">>,
203       [warn_unused_vars],
204       {warnings,[{{2,15},erl_lint,{unused_var,'X'}},
205                  {{4,29},erl_lint,{shadowed_var,'X',generate}},
206                  {{8,49},erl_lint,{shadowed_var,'X',generate}}]}},
207
208      {nested_qlc2,
209      <<"nested_qlc() ->
210             H0 = qlc:append([a,b], [c,d]),
211             qlc:q([{X,Y} ||
212                       X <- H0,
213                       Y <- qlc:q([{X,Y} ||
214                                      X <- H0, % X shadowed
215                                      Y <- H0])]),
216             ok.
217       ">>,
218       [warn_unused_vars],
219       {warnings,[{{6,39},erl_lint,{shadowed_var,'X',generate}}]}}
220    ],
221    [] = compile(Config, Ts),
222    ok.
223
224%% Unused variable with a name that should not be introduced.
225unused_var(Config) when is_list(Config) ->
226    Ts =
227     [{unused_var,
228       <<"unused_var() ->
229              qlc:q([X || begin Y1 = 3, true end, % Y1 unused
230                          Y <- [1,2,3],
231                          X <- [a,b,c],
232                          X < Y]).
233       ">>,
234       [warn_unused_vars],
235       {warnings,[{{2,33},erl_lint,{unused_var,'Y1'}}]}}],
236    [] = compile(Config, Ts),
237    ok.
238
239%% Ordinary LC expression.
240lc(Config) when is_list(Config) ->
241    Ts =
242     [{lc,
243       <<"lc() ->
244              [X || X <- [], X <- X]. % X shadowed
245        ">>,
246       [],
247       {warnings,[{{2,30},erl_lint,{shadowed_var,'X',generate}}]}}],
248    [] = compile(Config, Ts),
249    ok.
250
251%% Fun with several clauses.
252fun_clauses(Config) when is_list(Config) ->
253    Ts =
254     [{fun_clauses,
255       <<"fun_clauses() ->
256            {X,X1,X2} = {1,2,3},
257            F = fun({X}) -> qlc:q([X || X <- X]); % X shadowed (fun, generate)
258                   ([X]) -> qlc:q([X || X <- X])  % X shadowed (fun, generate)
259                end,
260            {F,X,X1,X2}.
261        ">>,
262       [],
263       {warnings,[{{3,22},erl_lint,{shadowed_var,'X','fun'}},
264                  {{3,41},erl_lint,{shadowed_var,'X',generate}},
265                  {{4,22},erl_lint,{shadowed_var,'X','fun'}},
266                  {{4,41},erl_lint,{shadowed_var,'X',generate}}]}}],
267    [] = compile(Config, Ts),
268    ok.
269
270%% Variable introduced in filter.
271filter_var(Config) when is_list(Config) ->
272    Ts =
273     [{filter_var,
274       <<"filter_var() ->
275              qlc:q([X ||
276                  Y <- [X ||
277                           X <- [1,2,3]],
278                  begin X = Y, true end]).
279        ">>,
280       [],
281       []},
282
283      {unsafe_filter_var,
284       <<"unsafe_filter_var() ->
285              qlc:q([{X,V} || X <- [1,2],
286                  case {a} of
287                      {_} ->
288                          true;
289                      V ->
290                          V
291                  end]).
292        ">>,
293       [],
294       {errors,[{{2,25},erl_lint,{unsafe_var,'V',{'case',{3,19}}}}],[]}}],
295    [] = compile(Config, Ts),
296    ok.
297
298
299%% Unused pattern variable.
300single(Config) when is_list(Config) ->
301    Ts =
302     [{single,
303       <<"single() ->
304              qlc:q([X || {X,Y} <- [{1,2}]]), % Y unused
305              qlc:q([[] || [] <- [[]]]).
306        ">>,
307       [warn_unused_vars],
308       {warnings,[{{2,30},erl_lint,{unused_var,'Y'}}]}}],
309    [] = compile(Config, Ts),
310    ok.
311
312%% Exported variable in list expression (rhs of generator).
313exported_var(Config) when is_list(Config) ->
314    Ts =
315     [{exported_var,
316       <<"exported() ->
317              qlc:q([X || X <- begin
318                                   case foo:bar() of
319                                       1 -> Z = a;
320                                       2 -> Z = b
321                                   end,
322                                   [Z = 3, Z = 3] % Z exported (twice...)
323                               end
324                         ]).
325       ">>,
326       [warn_export_vars],
327       {warnings,[{{7,37},erl_lint,{exported_var,'Z',{'case',{3,36}}}},
328                  {{7,44},erl_lint,{exported_var,'Z',{'case',{3,36}}}}]}}],
329    [] = compile(Config, Ts),
330    ok.
331
332%% Errors for generator variable used in list expression.
333generator_vars(Config) when is_list(Config) ->
334    Ts =
335      [{generator_vars,
336        <<"generator_vars() ->
337               qlc:q([X ||
338                      Z <- [1,2],
339                      X <- begin
340                               case 1 of
341                                   1 -> Z = a; % used_generator_variable
342                                   2 -> Z = b % used_generator_variable
343                               end,
344                               [Z = 3, Z = 3] % used_generator_variable (2)
345                           end
346                     ]).
347        ">>,
348        [],
349        {errors,[{{6,41},?QLC,{used_generator_variable,'Z'}},
350                 {{7,41},?QLC,{used_generator_variable,'Z'}},
351                 {{9,33},?QLC,{used_generator_variable,'Z'}},
352                 {{9,40},?QLC,{used_generator_variable,'Z'}}],
353         []}}],
354    [] = compile(Config, Ts),
355    ok.
356
357%% Unreachable clauses also found when compiling.
358nomatch(Config) when is_list(Config) ->
359    Ts =
360      [{unreachable1,
361        <<"unreachable1() ->
362               qlc:q([X || X <- [1,2],
363                   case X of
364                       true -> false;
365                       true -> true   % clause cannot match
366                    end]).
367        ">>,
368        [],
369        {warnings,[{5,v3_kernel,{nomatch_shadow,4}}]}},
370
371       {nomatch1,
372        <<"generator1() ->
373              qlc:q([3 || {3=4} <- []]).
374        ">>,
375        [],
376        %% {warnings,[{{2,27},qlc,nomatch_pattern}]}},
377        {warnings,[{2,v3_core,nomatch}]}},
378
379       {nomatch2,
380        <<"nomatch() ->
381                etsc(fun(E) ->
382                Q = qlc:q([3 || {3=4} <- ets:table(E)]),
383                [] = qlc:eval(Q),
384                false = lookup_keys(Q)
385          end, [{1},{2}]).
386        ">>,
387        [],
388        %% {warnings,[{{3,33},qlc,nomatch_pattern}]}},
389        {warnings,[{3,v3_core,nomatch}]}},
390
391       {nomatch3,
392        <<"nomatch() ->
393              etsc(fun(E) ->
394                          Q = qlc:q([{A,B,C,D} || A=B={C=D}={_,_} <-
395                                                    ets:table(E)]),
396                          [] = qlc:eval(Q),
397                          false = lookup_keys(Q)
398                    end, [{1,2},{2,3}]).
399        ">>,
400        [],
401        %% {warnings,[{{3,52},qlc,nomatch_pattern}]}},
402        {warnings,[{3,v3_core,nomatch}]}},
403
404       {nomatch4,
405        <<"nomatch() ->
406              etsc(fun(E) ->
407                          Q = qlc:q([{X,Y} || {<<X>>} = {<<Y>>} <-
408                                                    ets:table(E)]),
409                          [] = qlc:eval(Q),
410                          false = lookup_keys(Q)
411                    end, [{<<34>>},{<<40>>}]).
412        ">>,
413        [],
414        {errors,[{{3,48},erl_lint,illegal_bin_pattern}],[]}},
415
416       {nomatch5,
417        <<"nomatch() ->
418               etsc(fun(E) ->
419                           Q = qlc:q([t || {\"a\"++\"b\"} = {\"ac\"} <-
420                                                    ets:table(E)]),
421                           [t] = qlc:eval(Q),
422                           [\"ab\"] = lookup_keys(Q)
423                     end, [{\"ab\"}]).
424        ">>,
425        [],
426        {warnings,[{3,v3_core,nomatch}]}}
427
428      ],
429    [] = compile(Config, Ts),
430    ok.
431
432
433%% Errors within qlc expressions also found when compiling.
434errors(Config) when is_list(Config) ->
435    Ts =
436      [{errors1,
437        <<"errors1() ->
438               qlc:q([X || X <- A]). % A unbound
439        ">>,
440        [],
441        {errors,[{{2,33},erl_lint,{unbound_var,'A'}}],[]}}],
442    [] = compile(Config, Ts),
443    ok.
444
445%% Patterns.
446pattern(Config) when is_list(Config) ->
447    Ts = [
448      <<"%% Records in patterns. No lookup.
449         L = [#a{k=#k{v=91}}],
450         H = qlc:q([Q || Q = #a{k=#k{v=91}} <- qlc_SUITE:table(L, 2, [])]),
451         {qlc,_,[{generate,_,{table,{call,_,_,_}}}], []} = i(H),
452         L = qlc:e(H),
453         {call, _, _q, [{lc,_,{var,_,'Q'},
454                         [{generate,_,
455                           {match,_,_,_},
456                           {call,_,_,_}}]}]}
457              = i(H, {format,abstract_code})">>,
458
459      <<"%% No matchspec since there is a binary in the pattern.
460         etsc(fun(E) ->
461             Q = qlc:q([A || {<<A:3/unit:8>>} <- ets:table(E)]),
462             [_] = qlc:eval(Q),
463             {qlc,_,[{generate,_,{table,_}}], []} = i(Q)
464         end, [{<<\"hej\">>}])">>
465
466       ],
467    run(Config, <<"-record(a, {k,v}).
468                         -record(k, {t,v}).\n">>, Ts),
469    ok.
470
471%% Override a guard BIF with an imported or local function.
472overridden_bif(Config) ->
473    Ts = [
474	  <<"[2] = qlc:e(qlc:q([P || P <- [1,2,3], port(P)])),
475             [10] = qlc:e(qlc:q([P || P <- [0,9,10,11,12],
476                                      (is_reference(P) andalso P > 5)])),
477             Empty = gb_sets:empty(), Single = gb_sets:singleton(42),
478             GbSets = [Empty,Single],
479             [Single] = qlc:e(qlc:q([S || S <- GbSets, size(S) =/= 0]))
480            ">>
481	 ],
482    run(Config, "-import(gb_sets, [size/1]).
483                 -compile({no_auto_import, [size/1, is_reference/1]}).
484                 port(N) -> N rem 2 =:= 0.
485                 is_reference(N) -> N rem 10 =:= 0.\n", Ts),
486    ok.
487
488
489%% eval/2
490eval(Config) when is_list(Config) ->
491    ScratchDir = filename:join([?privdir, "scratch","."]),
492
493    Ts = [<<"{'EXIT',{badarg,_}} = (catch qlc:eval(not_a_qlc)),
494             H = qlc:q([X || X <- [1,2]]),
495             {'EXIT',{{unsupported_qlc_handle,{qlc_handle,foo}},_}}=
496                       (catch qlc:e({qlc_handle,foo})),
497             {'EXIT',{badarg,_}} = (catch qlc:eval(H, [{unique_all,badarg}])),
498             {'EXIT',{badarg,_}} =
499                      (catch qlc:eval(H, [{spawn_options,badarg}])),
500             {'EXIT',{badarg,_}} =
501                      (catch qlc:eval(H, [{unique_all,true},{bad,arg}])),
502             {throw,t} =
503                (catch {any_term,qlc:e(qlc:q([X || X <- throw({throw,t})]))}),
504             M = qlc,
505             {'EXIT',{badarg,_}} = (catch M:q(bad))">>,
506
507          [<<"Dir = \"">>,ScratchDir,<<"\",
508              qlc_SUITE:prep_scratchdir(Dir),
509
510              E = ets:new(foo, []),
511              [true || I <- lists:seq(1, 50000), not ets:insert(E, {I, I})],
512              H = qlc:q([{X,Y} || Y <- [1,2],
513                                  X <- qlc:sort(ets:table(E),{tmpdir,Dir}),
514                                  qlc_SUITE:truncate_tmpfile(Dir, 0)]),
515              R = qlc:eval(H),
516              ets:delete(E),
517              {error,_,{bad_object,_}} = R,
518              \"the tempo\" ++ _ = lists:flatten(qlc:format_error(R))">>],
519
520          [<<"Dir = \"">>,ScratchDir,<<"\",
521              qlc_SUITE:prep_scratchdir(Dir),
522
523              E = ets:new(foo, []),
524              Bin = term_to_binary(lists:seq(1,20000)),
525              [true || I <- lists:seq(1, 10), not ets:insert(E, {I, I, Bin})],
526              H = qlc:q([{X,Y} || Y <- [1,2],
527                                  X <- qlc:sort(ets:table(E),{tmpdir,Dir}),
528                                  qlc_SUITE:crash_tmpfile(Dir, 5)]),
529              R = qlc:eval(H),
530              ets:delete(E),
531              {error,_,{bad_object,_}} = R">>],
532
533          <<"E = ets:new(test, []),
534             H = qlc:q([{X,Y} || X <- qlc_SUITE:bad_table_throw(E),
535                                 Y <- ets:table(E)]),
536             R1 = (catch {any_term,qlc:eval(H, {unique_all,false})}),
537             R2 = (catch {any_term,qlc:eval(H, {unique_all,true})}),
538             ets:delete(E),
539             true = {throw,bad_pre_fun} == R1,
540             true = {throw,bad_pre_fun} == R2">>,
541
542          <<"E = ets:new(test, []),
543             H = qlc:q([{X,Y} || X <- qlc_SUITE:bad_table_exit(E),
544                                 Y <- ets:table(E)]),
545             R1 = (catch qlc:eval(H, {unique_all,false})),
546             R2 = (catch qlc:eval(H, {unique_all,true})),
547             ets:delete(E),
548             {'EXIT',{bad_pre_fun,_}} = R1,
549             {'EXIT',{bad_pre_fun,_}} = R2">>,
550
551          <<"Q = qlc:q([X || X <- [4,3,2,1,0,-1], begin 3/X > 0 end]),
552             {'EXIT',{badarith,_}} = (catch qlc:eval(Q, {unique_all,false})),
553             {'EXIT',{badarith,_}} = (catch qlc:eval(Q, {unique_all,true}))
554            ">>,
555
556          <<"[1,2] = qlc:eval(qlc:q([X || X <- [1,2]])),
557             [1,2,3,4] = qlc:eval(qlc:append([1,2],[3,4])),
558             [1,2] = qlc:eval(qlc:sort([2,1])),
559             E = ets:new(foo, []),
560             ets:insert(E, [{1},{2}]),
561             [{1},{2}] = lists:sort(qlc:eval(ets:table(E))),
562             true = ets:delete(E)">>,
563
564          <<"H = qlc:q([X || X <- [1,2],
565                             begin F = fun() ->
566                                qlc:e(qlc:q([Y || Y <- [1,2]])) end,
567                                F() == (fun f/0)() end]),
568             [1,2] = qlc:e(H),
569             ok.
570
571             f() -> [1,2].
572             foo() -> bar">>,
573
574          <<"C1_0_1 = [1,2],
575             %% The PT cannot rename C to C1_0_1; another name is chosen.
576             [1,2] = qlc:eval(qlc:q([C || C <- C1_0_1]))">>,
577
578          <<"H = qlc:q([X || {X,X} <- [{1,a},{2,2},{b,b},{3,4}]]),
579             [2,b] = qlc:e(H),
580             H1 = qlc:q([3 || {X,X} <- [{1,a},{2,2},{b,b},{3,4}]]),
581             [3,3] = qlc:e(H1)">>,
582
583          %% Just to cover a certain line in qlc.erl (avoids returning [])
584          <<"E = ets:new(foo, []),
585             Bin = term_to_binary(lists:seq(1,20000)),
586             [true || I <- lists:seq(1, 10), not ets:insert(E, {I, I, Bin})],
587             H = qlc:q([{X,Y} || Y <- [1,2], X <- qlc:sort(ets:table(E))]),
588             R = qlc:eval(H),
589             ets:delete(E),
590             20 = length(R)">>,
591
592          <<"H = qlc:q([{A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W} ||
593                 {A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W} <-
594                  [{a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w}]]),
595             [_] = qlc:e(H)">>,
596
597          <<"H = qlc:q([Y || Y <- [1,2]],
598                       {unique, begin [T] = qlc:e(qlc:q([X || X <- [true]],
599                                                        cache)),
600                                      T end}),
601             [1,2] = qlc:e(H)">>
602
603          ],
604
605    run(Config, Ts),
606    ok.
607
608%% cursor/2
609cursor(Config) when is_list(Config) ->
610    ScratchDir = filename:join([?privdir, "scratch","."]),
611    Ts = [<<"{'EXIT',{badarg,_}} =
612                   (catch qlc:cursor(fun() -> not_a_cursor end)),
613             H0 = qlc:q([X || X <- throw({throw,t})]),
614             {throw,t} = (catch {any_term,qlc:cursor(H0)}),
615             H = qlc:q([X || X <- [1,2]]),
616             {'EXIT',{badarg,_}} =
617                       (catch qlc:cursor(H,{spawn_options, [a|b]})),
618             {'EXIT',{badarg,_}} =
619                       (catch qlc:cursor(H,{bad_option,true}))">>,
620
621          <<"{'EXIT',{badarg,_}} = (catch qlc:delete_cursor(not_a_cursor))">>,
622
623          [<<"Dir = \"">>,ScratchDir,<<"\",
624              qlc_SUITE:prep_scratchdir(Dir), % kludge
625              E = ets:new(foo, []),
626              [true || I <- lists:seq(1, 50000), not ets:insert(E, {I, I})],
627              H = qlc:q([{X,Y} || begin put('$qlc_tmpdir', true), true end,
628                                  Y <- [1,2],
629                                  X <- qlc:sort(ets:table(E),{tmpdir,Dir}),
630                                  qlc_SUITE:truncate_tmpfile(Dir, 0)]),
631              C = qlc:cursor(H),
632              R = qlc:next_answers(C, all_remaining),
633              qlc:delete_cursor(C),
634              erase('$qlc_tmpdir'),
635              ets:delete(E),
636              {error,_,{bad_object,_}} = R">>],
637
638          <<"H1 = qlc:q([X || X <- [1,2]]),
639             C1 = qlc:cursor(H1),
640             [1,2] = qlc:next_answers(C1, all_remaining),
641             [] = qlc:next_answers(C1),
642             [] = qlc:next_answers(C1),
643             ok = qlc:delete_cursor(C1),
644
645             H2 = qlc:append([1,2],[3,4]),
646             C2 = qlc:cursor(H2),
647             [1,2,3,4] = qlc:next_answers(C2, all_remaining),
648             ok = qlc:delete_cursor(C2),
649
650             H3 = qlc:sort([2,1]),
651             C3 = qlc:cursor(H3),
652             [1,2] = qlc:next_answers(C3, all_remaining),
653             ok = qlc:delete_cursor(C3),
654
655             E = ets:new(foo, []),
656             ets:insert(E, [{1},{2}]),
657             H4 = ets:table(E),
658             C4 = qlc:cursor(H4),
659             [{1},{2}] = lists:sort(qlc:next_answers(C4, all_remaining)),
660             ok = qlc:delete_cursor(C4),
661             true = ets:delete(E)">>,
662
663          <<"H = qlc:q([{X,Y} || X <- [1,2], Y <- [a,b]]),
664             C = qlc:cursor(H, []),
665             [{1,a},{1,b}] = qlc:next_answers(C, 2),
666             [{2,a}] = qlc:next_answers(C, 1),
667             [{2,b}] = qlc:next_answers(C, all_remaining),
668             {'EXIT',{badarg,_}} = (catch qlc:next_answers(C, -1)),
669             P = self(),
670             Pid1 = spawn_link(fun() ->
671                          {'EXIT',{not_cursor_owner,_}} =
672                                (catch qlc:delete_cursor(C)),
673                          P ! {self(), done} end),
674             Pid2 = spawn_link(fun() ->
675                          {'EXIT',{not_cursor_owner,_}} =
676                                (catch qlc:next_answers(C)),
677                          P ! {self(), done} end),
678             receive {Pid1, done} -> ok end,
679             receive {Pid2, done} -> ok end,
680             ok = qlc:delete_cursor(C),
681             {'EXIT',{badarg,_}} = (catch qlc:next_answers(not_a_cursor)),
682             ok = qlc:delete_cursor(C)">>,
683
684          <<"Q = qlc:q([X || X <- [1,2,1,2,1]]),
685             C1 = qlc:cursor(Q, [{unique_all,true}]),
686             [1,2] = qlc:next_answers(C1, all_remaining),
687             ok = qlc:delete_cursor(C1),
688             C2 = qlc:cursor(Q, [{unique_all,true}]),
689             [1,2] = qlc:next_answers(C2, all_remaining),
690             ok = qlc:delete_cursor(C2)">>,
691
692          <<"Q = qlc:q([X || X <- [1,2,1,2,1]]),
693             C1 = qlc:cursor(Q, [{unique_all,true},{spawn_options, []}]),
694             [1,2] = qlc:next_answers(C1, all_remaining),
695             ok = qlc:delete_cursor(C1),
696             C2 = qlc:cursor(Q, [{unique_all,true},{spawn_options, default}]),
697             [1,2] = qlc:next_answers(C2, all_remaining),
698             ok = qlc:delete_cursor(C2)">>,
699
700          <<"Q = qlc:q([X || X <- [1,2,1,2,1]]),
701             C1 = qlc:cursor(Q, [{unique_all,false},{spawn_options, []}]),
702             [1,2,1,2,1] = qlc:next_answers(C1, all_remaining),
703             ok = qlc:delete_cursor(C1),
704             C2 = qlc:cursor(Q, [{unique_all,false},{spawn_options, []}]),
705             [1,2,1,2,1] = qlc:next_answers(C2, all_remaining),
706             ok = qlc:delete_cursor(C2)">>,
707
708          <<"Q = qlc:q([X || X <- [1,2,1,2,1]]),
709             C1 = qlc:cursor(Q, [{unique_all,false}]),
710             [1,2,1,2,1] = qlc:next_answers(C1, all_remaining),
711             ok = qlc:delete_cursor(C1),
712             C2 = qlc:cursor(Q, [{unique_all,false}]),
713             [1,2,1,2,1] = qlc:next_answers(C2, all_remaining),
714             ok = qlc:delete_cursor(C2)">>
715
716         ],
717    run(Config, Ts),
718    ok.
719
720%% fold/4
721fold(Config) when is_list(Config) ->
722    ScratchDir = filename:join([?privdir, "scratch","."]),
723    Ts = [<<"Q = qlc:q([X || X <- [1,2,1,2,1]]),
724             F = fun(Obj, A) -> A++[Obj] end,
725             {'EXIT',{badarg,_}} = (catch qlc:fold(F, [], Q, {bad,arg})),
726             {'EXIT',{badarg,_}} = (catch qlc:fold(F, [], badarg)),
727             {'EXIT',{badarg,_}} =
728               (catch qlc:fold(F, [], {spawn_options, [a|b]})),
729             H = qlc:q([X || X <- throw({throw,t})]),
730             {throw,t} = (catch {any_term,qlc:fold(F, [], H)}),
731             [1,2] = qlc:fold(F, [], Q, {unique_all,true}),
732             {'EXIT',{badarg,_}} =
733               (catch qlc:fold(F, [], Q, [{unique_all,bad}])),
734             [1,2,1,2,1] =
735                  qlc:fold(F, [], Q, [{unique_all,false}])">>,
736
737          [<<"Dir = \"">>,ScratchDir,<<"\",
738              qlc_SUITE:prep_scratchdir(Dir),
739
740              E = ets:new(foo, []),
741              [true || I <- lists:seq(1, 50000), not ets:insert(E, {I, I})],
742              H = qlc:q([{X,Y} || Y <- [1,2],
743                                  X <- qlc:sort(ets:table(E),{tmpdir,Dir}),
744                                  qlc_SUITE:truncate_tmpfile(Dir, 0)]),
745              F = fun(Obj, A) -> A++[Obj] end,
746              R = qlc:fold(F, [], H),
747              ets:delete(E),
748              {error,_,{bad_object,_}} = R">>],
749
750          <<"E = ets:new(test, []),
751             H = qlc:q([{X,Y} || X <- qlc_SUITE:bad_table_throw(E),
752                                 Y <- ets:table(E)]),
753             F = fun(Obj, A) -> A++[Obj] end,
754             R1 = (catch {any_term,qlc:fold(F, [], H, {unique_all,false})}),
755             R2 = (catch {any_term,qlc:fold(F, [], H, {unique_all,true})}),
756             ets:delete(E),
757             true = {throw,bad_pre_fun} == R1,
758             true = {throw,bad_pre_fun} == R2">>,
759
760          <<"E = ets:new(test, []),
761             H = qlc:q([{X,Y} || X <- qlc_SUITE:bad_table_exit(E),
762                                 Y <- ets:table(E)]),
763             F = fun(Obj, A) -> A++[Obj] end,
764             R1 = (catch qlc:fold(F, [], H, {unique_all,false})),
765             R2 = (catch qlc:fold(F, [], H, {unique_all,true})),
766             ets:delete(E),
767             {'EXIT',{bad_pre_fun,_}} = R1,
768             {'EXIT',{bad_pre_fun,_}} = R2">>,
769
770          <<"F = fun(Obj, A) -> A++[Obj] end,
771             Q = qlc:q([X || X <- [1,2,1,2,1], throw({throw,wrong})]),
772             {throw,wrong} =
773                 (catch {any_term,qlc:fold(F, [], Q, {unique_all,true})}),
774             {throw,wrong} =
775                 (catch {any_term,qlc:fold(F, [], Q)})">>,
776
777          <<"F = fun(Obj, A) -> A++[Obj] end,
778             Q = qlc:q([X || X <- [4,3,2,1,0,-1], begin 3/X > 0 end]),
779             {'EXIT',{badarith,_}} =
780                       (catch qlc:fold(F, [], Q, {unique_all,true})),
781             {'EXIT',{badarith,_}} =
782                 (catch qlc:fold(F, [], Q, [{unique_all,false}]))
783            ">>,
784
785          <<"F = fun(Obj, A) -> A++[Obj] end,
786             [1,2] = qlc:fold(F, [], qlc:q([X || X <- [1,2]])),
787             [1,2,3,4] = qlc:fold(F, [], qlc:append([1,2],[3,4])),
788             [1,2] = qlc:fold(F, [], qlc:sort([2,1])),
789             E = ets:new(foo, []),
790             ets:insert(E, [{1},{2}]),
791             [{1},{2}] = lists:sort(qlc:fold(F, [], ets:table(E))),
792             true = ets:delete(E)">>,
793
794          <<"F = fun(_Obj, _A) -> throw({throw,fatal}) end,
795             Q = qlc:q([X || X <- [4,3,2]]),
796             {throw,fatal} =
797              (catch {any_term,qlc:fold(F, [], Q, {unique_all,true})}),
798             {throw,fatal} =
799               (catch {any_term,qlc:fold(F, [], Q, [{unique_all,false}])})">>,
800
801          <<"G = fun(_Obj, _A, D) -> 17/D  end,
802             F = fun(Obj, A) -> G(Obj, A, 0) end,
803             Q = qlc:q([X || X <- [4,3,2]]),
804             {'EXIT',{badarith,_}} =
805                    (catch qlc:fold(F, [], Q, {unique_all,true})),
806             {'EXIT',{badarith,_}} =
807               (catch qlc:fold(F, [], Q, [{unique_all,false}]))
808            ">>
809         ],
810    run(Config, Ts),
811    ok.
812
813%% Test the unique_all option of eval.
814eval_unique(Config) when is_list(Config) ->
815    Ts = [<<"QLC1 = qlc:q([X || X <- qlc:append([[1,1,2], [1,2,3,2,3]])]),
816             [1,2,3] = qlc:eval(QLC1, {unique_all,true}),
817             QLC2 = qlc:q([X || X <- [1,2,1,2,1,2,1]]),
818             [1,2] = qlc:e(QLC2, {unique_all,true})">>,
819
820          <<"E = ets:new(test, []),
821             true = ets:insert(E, [{1,a},{2,b},{3,c}]),
822             H = qlc:q([X || X <- qlc:append([ets:table(E), ets:table(E)])]),
823             R1 = qlc:e(H, {unique_all,false}),
824             R2 = qlc:e(H, {unique_all,true}),
825             ets:delete(E),
826             true = lists:sort(R1) == [{1,a},{1,a},{2,b},{2,b},{3,c},{3,c}],
827             true = lists:sort(R2) == [{1,a},{2,b},{3,c}]
828            ">>,
829
830          <<"Q1 = qlc:q([{X,make_ref()} || X <- [1,2,1,2]]),
831             [_,_] = qlc:e(Q1, {unique_all,true}),
832             [_,_,_,_] = qlc:e(Q1, {unique_all,false}),
833             [_,_] = qlc:e(Q1, [{unique_all,true}]),
834             Q2 = qlc:q([{X,make_ref()} || X <- qlc:append([[1,2,1,2]])]),
835             [_,_] = qlc:e(Q2, {unique_all,true}),
836             [_,_,_,_] = qlc:e(Q2, {unique_all,false}),
837             [_,_] = qlc:e(Q2, [{unique_all,true}])
838            ">>,
839
840          <<"Q = qlc:q([{X,make_ref()} || X <- qlc:sort([1,2,1,2])]),
841             [_, _] = qlc:e(Q, {unique_all,true}),
842             Q1 = qlc:q([X || X <- [1,2,1,2]]),
843             Q2 = qlc:q([{X,make_ref()} || X <- qlc:sort(Q1)]),
844             [_, _] = qlc:e(Q2, {unique_all,true})
845            ">>,
846
847          <<"E = ets:new(test, []),
848             true = ets:insert(E, [{1,a},{2,b},{3,c}]),
849             H = qlc:q([X || X <- qlc:append([[1,2,1,2]])]),
850             [1,2,1,2] = qlc:e(H, {unique_all,false}),
851             [1,2] = qlc:e(H, {unique_all,true}),
852             ets:delete(E)">>,
853
854          <<"E = ets:new(foo, [duplicate_bag]),
855             true = ets:insert(E, [{1,a},{1,a},{2,b},{3,c},{4,c},{4,d}]),
856             Q1 = qlc:q([{X,make_ref()} || {_, X} <- ets:table(E)]),
857             true = length(qlc:eval(Q1, {unique_all, true})) =:= 5,
858             Q2 = qlc:q([X || {_, X} <- ets:table(E)]),
859             true = length(qlc:eval(Q2, {unique_all, true})) =:= 4,
860             Q3 = qlc:q([element(2, X) || X <- ets:table(E)]),
861             true = length(qlc:eval(Q3, {unique_all, true})) =:= 4,
862             Q4 = qlc:q([1 || _X <- ets:table(E)]),
863             true = length(qlc:eval(Q4, {unique_all, true})) =:= 1,
864             true = ets:delete(E)
865            ">>,
866
867          <<"Q1 = qlc:q([X || X <- qlc:append([[1], [2,1]])]),
868             Q2 = qlc:q([X || X <- qlc:append([[2,1], [2]])]),
869             Q3 = qlc:q([{X,Y} || X <- Q1, Y <- Q2]),
870             [{1,2},{1,1},{2,2},{2,1}] = qlc:e(Q3, {unique_all,true}),
871             Q4 = qlc:q([{X,Y,make_ref()} || X <- Q1, Y <- Q2]),
872             [{1,2,_},{1,1,_},{2,2,_},{2,1,_}] = qlc:e(Q4, {unique_all,true})
873            ">>,
874
875          <<"Q1 = qlc:q([X || X <- [1,2,1]]),
876             Q2 = qlc:q([X || X <- [2,1,2]]),
877             Q3 = qlc:q([{X,Y} || X <- Q1, Y <- Q2]),
878             [{1,2},{1,1},{2,2},{2,1}] = qlc:e(Q3,{unique_all,true}),
879             Q4 = qlc:q([{X,Y,make_ref()} || X <- Q1, Y <- Q2]),
880             [{1,2,_},{1,1,_},{2,2,_},{2,1,_}] = qlc:e(Q4, {unique_all,true})
881            ">>,
882
883          <<"Q1 = qlc:q([X || {X,_} <- [{1,a},{1,b}]]),
884             [1] = qlc:e(Q1, {unique_all, true}),
885             Q2 = qlc:q([a || _ <- [{1,a},{1,b}]]),
886             [a] = qlc:e(Q2, {unique_all, true})
887            ">>,
888
889          <<"Q = qlc:q([SQV || SQV <- qlc:q([X || X <- [1,2,1,#{a => 1}]],
890                                             unique)],
891                       unique),
892             {call,_,_,[{lc,_,{var,_,'X'},[{generate,_,{var,_,'X'},_}]},_]} =
893                 qlc:info(Q, [{format,abstract_code},unique_all]),
894             [1,2,#{a := 1}] = qlc:e(Q)">>,
895
896          <<"Q = qlc:q([X || X <- [1,2,1]]),
897             {call,_,_,[{lc,_,{var,_,'X'},[{generate,_,{var,_,'X'},_}]},_]} =
898                 qlc:info(Q, [{format,abstract_code},unique_all]),
899             [1,2] = qlc:e(Q, unique_all)">>,
900
901          <<"Q1 = qlc:sort([{1},{2},{3},{1}], [{unique,true}]),
902             Q = qlc:sort(Q1,[{unique,true}]),
903             {sort,{sort,{list,_},[{unique,true}]},[]} = i(Q)">>
904
905         ],
906    run(Config, Ts),
907    ok.
908
909%% Test the cache_all and unique_all options of eval.
910eval_cache(Config) when is_list(Config) ->
911    Ts = [
912       <<"E = ets:new(apa, [ordered_set]),
913          ets:insert(E, [{1},{2}]),
914          H = qlc:q([X || Y <- [3,4],
915                          ets:insert(E, {Y}),
916                          X <- ets:table(E)]), % already unique, no cache...
917          {qlc, _,
918           [{generate, _, {qlc, _,
919                           [{generate, _, {list, [3,4]}}],
920                           [{unique,true}]}},
921            _,
922            {generate, _, {table,_}}],
923           [{unique,true}]} = i(H, [cache_all, unique_all]),
924          [{1},{2},{3},{4}] = qlc:e(H,  [cache_all, unique_all]),
925          ets:delete(E)">>,
926
927       <<"E = ets:new(apa, [ordered_set]),
928          ets:insert(E, [{1},{2}]),
929          H = qlc:q([X || Y <- [3,4],
930                          ets:insert(E, {Y}),
931                          X <- ets:table(E)]), % no cache...
932          {qlc, _,
933           [{generate, _,{list, [3,4]}},
934            _,
935            {generate, _, {table,_}}],
936           []} = i(H, cache_all),
937          [{1},{2},{3},{1},{2},{3},{4}] = qlc:e(H,  [cache_all]),
938          ets:delete(E)">>,
939
940       <<"E = ets:new(apa, [ordered_set]),
941          ets:insert(E, [{1},{2}]),
942          H = qlc:q([X || Y <- [3,4],
943                          ets:insert(E, {Y}),
944                          X <- qlc:q([X || X <- ets:table(E)], cache)]),
945          {qlc, _,
946           [{generate, _, {list, [3,4]}},
947            _,
948            {generate, _, {qlc, _,
949                           [{generate, _, {table,_}}],
950                           [{cache,ets}]}}],
951           []} = i(H, cache_all),
952          [{1},{2},{3},{1},{2},{3}] = qlc:e(H,  [cache_all]),
953          ets:delete(E)">>,
954
955       <<"%% {cache_all,no} does not override {cache,true}.
956          E = ets:new(apa, [ordered_set]),
957          ets:insert(E, [{1},{2}]),
958          H = qlc:q([X || Y <- [3,4],
959                          ets:insert(E, {Y}),
960                          X <- qlc:q([X || X <- ets:table(E)], cache)]),
961          {qlc, _,
962           [{generate, _, {list, [3,4]}},
963            _,
964            {generate, _, {qlc, _,
965                           [{generate, _, {table,_}}],
966                           [{cache,ets}]}}],
967           []} = i(H, {cache_all,no}),
968          [{1},{2},{3},{1},{2},{3}] = qlc:e(H,  [cache_all]),
969          ets:delete(E)">>,
970
971       <<"E = ets:new(apa, [ordered_set]),
972          ets:insert(E, [{1},{2}]),
973          H = qlc:q([X || Y <- [3,4],
974                          ets:insert(E, {Y}),
975                          X <- ets:table(E)]),
976          {qlc, _,
977           [{generate, _, {qlc, _, [{generate, _,{list, [3,4]}}],
978                           [{unique,true}]}},
979            _,
980            {generate, _,{table,_}}],
981           [{unique,true}]} = i(H, unique_all),
982          [{1},{2},{3},{4}] = qlc:e(H, [unique_all]),
983          ets:delete(E)">>,
984
985          %% cache_all is ignored
986       <<"E = ets:new(apa, [ordered_set]),
987          ets:insert(E, [{1},{2},{0}]),
988          H = qlc:q([X || X <- qlc:sort(ets:table(E))]),
989          {sort,_Table,[]} = i(H, cache_all),
990          [{0},{1},{2}] = qlc:e(H, cache_all),
991          ets:delete(E)">>,
992
993       <<"F = fun(Obj, A) -> A++[Obj] end,
994          E = ets:new(apa, [duplicate_bag]),
995          true = ets:insert(E, [{1,a},{2,b},{1,a}]),
996          Q = qlc:q([X || X <- ets:table(E)], cache),
997          {table, _} = i(Q, []),
998          R = qlc:fold(F, [], Q, []),
999          ets:delete(E),
1000          true = [{1,a},{1,a},{2,b}] == lists:sort(R)">>,
1001
1002       <<"E = ets:new(apa, [ordered_set]),
1003          ets:insert(E, [{1},{2},{0}]),
1004          H = qlc:q([X || X <- ets:table(E)], cache),
1005          {table, _} = i(H, cache_all),
1006          [{0},{1},{2}]= qlc:e(H, cache_all),
1007          ets:delete(E)">>,
1008
1009       <<"E = ets:new(foo, []),
1010          true = ets:insert(E, [{1}, {2}]),
1011          Q1 = qlc:q([{X} || X <- ets:table(E)]),
1012          Q2 = qlc:q([{X,Y} || {X} <- Q1, {Y} <- Q1]),
1013          {qlc, _, [{generate, _, {table, _}},
1014                    {generate, _, {qlc, _, [{generate, _, {table, _}}],
1015                                   [{cache,ets}]}}],
1016           []} = i(Q2, cache_all),
1017          [{{1},{1}},{{1},{2}},{{2},{1}},{{2},{2}}] =
1018              lists:sort(qlc:e(Q2, cache_all)),
1019          ets:delete(E)">>,
1020
1021       <<"L1 = [1,2,3],
1022          L2 = [4,5,6],
1023          Q1 = qlc:append(L1, L2),
1024          Q2 = qlc:q([{X} || X <- Q1]),
1025          {qlc, _,[{generate, _,{append, [{list, L1}, {list, L2}]}}], []} =
1026              i(Q2, [cache_all]),
1027          [{1},{2},{3},{4},{5},{6}] = qlc:e(Q2, [cache_all])">>,
1028
1029       <<"H = qlc:sort(qlc:q([1 || _ <- [a,b]])),
1030          {sort, {qlc, _, [{generate, _, {qlc, _, [{generate, _,
1031                                                    {list, [a,b]}}],
1032                                          [{unique,true}]}}],
1033                  [{unique,true}]},
1034                 []} = i(H, unique_all),
1035          [1] = qlc:e(H, unique_all)">>
1036
1037         ],
1038    run(Config, Ts),
1039    ok.
1040
1041%% Test the append function.
1042append(Config) when is_list(Config) ->
1043    Ts = [<<"C = qlc:cursor(qlc:q([X || X <- [0,1,2,3], begin 10/X > 0.0 end])),
1044             R = (catch qlc:next_answers(C)),
1045             {'EXIT',{badarith,_}} = R">>,
1046
1047          <<"C = qlc:cursor(qlc:q([X || X <- [0 | fun() -> exit(bad) end]])),
1048             R = (catch qlc:next_answers(C)),
1049             {'EXIT',bad} = R">>,
1050
1051          <<"{'EXIT',{badarg,_}} = (catch qlc:append([a], a)),
1052             {'EXIT',{badarg,_}} = (catch qlc:append([[a],a]))">>,
1053
1054          <<"C = qlc:cursor(qlc:q([X || X <- [0,1,2,3],
1055                                     begin throw({throw,wrong}), true end])),
1056             {throw,wrong} = (catch {any_term,qlc:next_answers(C)})">>,
1057
1058          <<"QLC = qlc:q([X || X <- [0,1,2,3],
1059                               begin throw({throw,wrong}), true end]),
1060             {throw,wrong} = (catch {any_term,qlc:eval(QLC)}),
1061             {throw,wrong} =
1062                 (catch {any_term,qlc:e(QLC, {unique_all,true})})">>,
1063
1064          <<"H1 = qlc:q([X || X <- [1,2,3]]),
1065             H2 = qlc:q([X || X <- [4,5,6]]),
1066             R = qlc:e(qlc:q([X || X <- qlc:append([H1, H2])])),
1067             true = R == [1,2,3,4,5,6]">>,
1068
1069          <<"H1 = [1,2,3],
1070             H2 = qlc:q([X || X <- [4,5,6]]),
1071             R = qlc:e(qlc:q([X || X <- qlc:append(H1, H2)])),
1072             true = R == [1,2,3,4,5,6]">>,
1073
1074          <<"H1 = qlc:q([X || X <- [1,2,3]]),
1075             H2 = qlc:q([X || X <- [4,5,6]]),
1076             R = qlc:e(qlc:q([X || X <- qlc:append(qlc:e(H1), H2)])),
1077             true = R == [1,2,3,4,5,6]">>,
1078
1079          <<"H1 = qlc:q([X || X <- [1,2,3]]),
1080             H2 = [4,5,6],
1081             R = qlc:e(qlc:q([X || X <- qlc:append(H1, H2)])),
1082             true = R == [1,2,3,4,5,6]">>,
1083
1084          <<"H1 = qlc:q([X || X <- [1,2,3]]),
1085             H2 = qlc:q([X || X <- [4,5,6]]),
1086             R = qlc:e(qlc:q([X || X <- qlc:append([H1, H2, H1]), X < 5])),
1087             true = R == [1,2,3,4,1,2,3]">>,
1088
1089          <<"R = qlc:e(qlc:q([X || X <- qlc:append([lista(), anrop()])])),
1090             true = R == [a,b,1,2],
1091             ok.
1092
1093             lista() ->
1094                 [a,b].
1095
1096             anrop() ->
1097                  qlc:q([X || X <- [1,2]]).
1098             foo() -> bar">>,
1099
1100          %% Used to work up to R11B.
1101          %% <<"apa = qlc:e(qlc:q([X || X <- qlc:append([[1,2,3], ugly()])])),
1102          %%   ok.
1103          %%
1104          %%   ugly() ->
1105          %%       [a | apa].
1106          %%   foo() -> bar">>,
1107
1108
1109          %% Maybe this one should fail.
1110          <<"[a|b] = qlc:e(qlc:q([X || X <- qlc:append([[a|b]])])),
1111             ok">>,
1112
1113          <<"17 = qlc:e(qlc:q([X || X <- qlc:append([[1,2,3],ugly2()])])),
1114             ok.
1115
1116             ugly2() ->
1117                 [a | fun() -> 17 end].
1118             foo() -> bar">>,
1119
1120          <<"E = ets:new(test, []),
1121             true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1122             H = qlc:q([X || X <- qlc:append([ets:table(E), apa])]),
1123             {'EXIT',{badarg,_}} = (catch qlc:e(H)),
1124             false = ets:info(E, safe_fixed),
1125             {'EXIT',{badarg,_}} = (catch qlc:e(H)),
1126             false = ets:info(E, safe_fixed),
1127             {'EXIT',{badarg,_}} = (catch qlc:cursor(H)),
1128             false = ets:info(E, safe_fixed),
1129             F = fun(Obj, A) -> A++[Obj] end,
1130             {'EXIT',{badarg,_}} = (catch qlc:fold(F, [], H)),
1131             false = ets:info(E, safe_fixed),
1132             ets:delete(E)">>,
1133
1134          <<"H1 = qlc:q([X || X <- [1,2,3]]),
1135             H2 = qlc:q([X || X <- [a,b,c]]),
1136             R = qlc:e(qlc:q([X || X <- qlc:append(H1,qlc:append(H1,H2))])),
1137             true = R == [1,2,3,1,2,3,a,b,c]">>,
1138
1139          <<"H = qlc:q([X || X <- qlc:append([],qlc:append([[], []]))]),
1140             [] = qlc:e(H)">>,
1141
1142          <<"Q1 = qlc:q([X || X <- [3,4,4]]),
1143             Q2 = qlc:q([X || X <- qlc:sort(qlc:append([[1,2], Q1]))]),
1144             [1,2,3,4,4] = qlc:e(Q2),
1145             [1,2,3,4] = qlc:e(Q2, {unique_all,true})">>,
1146
1147          <<"[] = qlc:e(qlc:q([X || X <- qlc:append([])]))">>,
1148
1149          <<"Q1 = qlc:q([X || X <- [a,b]]),
1150             Q2 = qlc:q([X || X <- [1,2]]),
1151             Q3 = qlc:append([Q1, Q2, qlc:sort([2,1])]),
1152             Q = qlc:q([X || X <- Q3]),
1153             {append, [{list, [a,b]},
1154                       {list, [1,2]},
1155                       {sort,{list, [2,1]},[]}]} = i(Q),
1156             [a,b,1,2,1,2] = qlc:e(Q)">>
1157
1158          ],
1159    run(Config, Ts),
1160    ok.
1161
1162%% Simple call from evaluator.
1163evaluator(Config) when is_list(Config) ->
1164    true = is_alive(),
1165    evaluator_2(Config, []),
1166    {ok, Node} = start_node(qlc_SUITE_evaluator),
1167    ok = rpc:call(Node, ?MODULE, evaluator_2, [Config, [compiler]]),
1168    test_server:stop_node(Node),
1169    ok.
1170
1171evaluator_2(Config, Apps) ->
1172    lists:foreach(fun(App) -> true = code:del_path(App) end, Apps),
1173    FileName = filename:join(?privdir, "eval"),
1174    ok = file:write_file(FileName,
1175                         <<"H = qlc:q([X || X <- L]),
1176                            [1,2,3] = qlc:e(H).">>),
1177    Bs = erl_eval:add_binding('L', [1,2,3], erl_eval:new_bindings()),
1178    ok = file:eval(FileName, Bs),
1179
1180    %% The error message is "handled" a bit too much...
1181    %% (no trace of erl_lint left)
1182    ok = file:write_file(FileName,
1183             <<"H = qlc:q([X || X <- L]), qlc:e(H).">>),
1184    {error,_} = file:eval(FileName),
1185
1186    %% Ugly error message; badarg is caught by file.erl.
1187    ok = file:write_file(FileName,
1188             <<"H = qlc:q([Z || {X,Y} <- [{a,2}], Z <- [Y]]), qlc:e(H).">>),
1189    {error,_} = file:eval(FileName),
1190
1191    _ = file:delete(FileName),
1192    ok.
1193
1194start_node(Name) ->
1195    PA = filename:dirname(code:which(?MODULE)),
1196    test_server:start_node(Name, slave, [{args, "-pa " ++ PA}]).
1197
1198%% string_to_handle/1,2.
1199string_to_handle(Config) when is_list(Config) ->
1200    {'EXIT',{badarg,_}} = (catch qlc:string_to_handle(14)),
1201    {'EXIT',{badarg,_}} =
1202        (catch qlc:string_to_handle("[X || X <- [a].", unique_all)),
1203    R1 = {error, _, {_,erl_scan,_}} = qlc:string_to_handle("'"),
1204    "1: unterminated " ++ _ = lists:flatten(qlc:format_error(R1)),
1205    {error, _, {_,erl_parse,_}} = qlc:string_to_handle("foo"),
1206    {'EXIT',{badarg,_}} = (catch qlc:string_to_handle("foo, bar.")),
1207    R3 = {error, _, {_,?QLC,not_a_query_list_comprehension}} =
1208        qlc:string_to_handle("bad."),
1209    "1: argument is not" ++ _ = lists:flatten(qlc:format_error(R3)),
1210    R4 = {error, _, {_,?QLC,{used_generator_variable,'Y'}}} =
1211        qlc:string_to_handle("[X || begin Y = [1,2], true end, X <- Y]."),
1212    "1: generated variable 'Y'" ++ _ =
1213        lists:flatten(qlc:format_error(R4)),
1214    {error, _, {_,erl_lint,_}} = qlc:string_to_handle("[X || X <- A]."),
1215    H1 = qlc:string_to_handle("[X || X <- [1,2]]."),
1216    [1,2] = qlc:e(H1),
1217    H2 = qlc:string_to_handle("[X || X <- qlc:append([a,b],"
1218                                    "qlc:e(qlc:q([X || X <- [c,d,e]])))]."),
1219    [a,b,c,d,e] = qlc:e(H2),
1220    %% The generated fun has many arguments (erl_eval has a maximum of 20).
1221    H3 = qlc:string_to_handle(
1222           "[{A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W} ||"
1223           " {A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,Q,R,S,T,U,V,W} <- []]."),
1224    [] = qlc:e(H3),
1225    Bs1 = erl_eval:add_binding('L', [1,2,3], erl_eval:new_bindings()),
1226    H4 = qlc:string_to_handle("[X || X <- L].", [], Bs1),
1227    [1,2,3] = qlc:e(H4),
1228    H5 = qlc:string_to_handle("[X || X <- [1,2,1,2]].", [unique, cache]),
1229    [1,2] = qlc:e(H5),
1230
1231    Ets = ets:new(test, []),
1232    true = ets:insert(Ets, [{1}]),
1233    Bs2 = erl_eval:add_binding('E', Ets, erl_eval:new_bindings()),
1234    Q = "[X || {X} <- ets:table(E)].",
1235    [1] = qlc:e(qlc:string_to_handle(Q, [], Bs2)),
1236    [1] = qlc:e(qlc:string_to_handle(Q, {max_lookup,1000}, Bs2)),
1237    [1] = qlc:e(qlc:string_to_handle(Q, {max_lookup,infinity}, Bs2)),
1238    {'EXIT',{badarg,_}} =
1239        (catch qlc:string_to_handle(Q, {max_lookup,-1}, Bs2)),
1240    {'EXIT', {no_lookup_to_carry_out, _}} =
1241        (catch qlc:e(qlc:string_to_handle(Q, {lookup,true}, Bs2))),
1242    ets:delete(Ets),
1243
1244    %% References can be scanned and parsed.
1245    E2 = ets:new(test, [bag]),
1246    Ref = make_ref(),
1247    true = ets:insert(E2, [{Ref,Ref}]),
1248    S2 = "[{Val1} || {Ref1, Val1} <- ets:table("++io_lib:write(E2)++"),"
1249         "Ref1 =:= Ref].",
1250    Bs = erl_eval:add_binding('Ref', Ref, erl_eval:new_bindings()),
1251    [{Ref}] = qlc:e(qlc:string_to_handle(S2, [], Bs)),
1252    ets:delete(E2),
1253
1254    ok.
1255
1256%% table
1257table(Config) when is_list(Config) ->
1258    dets:start(),
1259    Ts = [
1260       <<"E = ets:new(test, []),
1261          {'EXIT',{badarg,_}} =
1262               (catch qlc:e(qlc:q([X || X <- ets:table(E, [badarg])]))),
1263          [] = qlc:e(qlc:q([X || X <- ets:table(E)])),
1264          ets:delete(E)">>,
1265
1266       <<"{'EXIT',{badarg,_}} = (catch qlc:table(not_a_fun, []))">>,
1267
1268       <<"E = ets:new(test, []),
1269          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1270          H = qlc:q([{X,Y} || X <- ets:table(E), Y <- ets:table(E)]),
1271          R = qlc:e(H),
1272          ets:delete(E),
1273          [{{1,a},{1,a}},{{1,a},{2,b}},{{1,a},{3,c}},
1274           {{2,b},{1,a}},{{2,b},{2,b}},{{2,b},{3,c}},
1275
1276           {{3,c},{1,a}},{{3,c},{2,b}},{{3,c},{3,c}}] = lists:sort(R)">>,
1277
1278       <<"E = ets:new(test, []),
1279          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1280          H = qlc:q([X || X <- qlc:append([ets:table(E), [a,b,c],
1281                                           ets:table(E)])]),
1282          R = qlc:e(H),
1283          ets:delete(E),
1284          [a,b,c,{1,a},{1,a},{2,b},{2,b},{3,c},{3,c}] = lists:sort(R)">>,
1285
1286       <<"E = ets:new(test, []),
1287          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1288          false = ets:info(E, safe_fixed),
1289          H = qlc:q([{X,Y} || X <- ets:table(E, {n_objects, default}),
1290                              Y <- ets:table(E, {n_objects, 2}),
1291                              false =/= ets:info(E, safe_fixed),
1292                              throw({throw,apa})]),
1293          {throw,apa} = (catch {any_term,qlc:e(H)}),
1294          false = ets:info(E, safe_fixed),
1295          ets:delete(E)">>,
1296
1297       <<"E = ets:new(test, []),
1298          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1299          false = ets:info(E, safe_fixed),
1300          H = qlc:q([{X,Y} || X <- ets:table(E), Y <- ets:table(E),
1301                              false =/= ets:info(E, safe_fixed), exit(apa)]),
1302          {'EXIT',apa} = (catch {any_term,qlc:e(H)}),
1303          false = ets:info(E, safe_fixed),
1304          ets:delete(E)">>,
1305
1306       <<"E = ets:new(test, []),
1307          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1308          H = qlc:q([{X,Y} || X <- qlc_SUITE:bad_table_throw(E),
1309                              Y <- ets:table(E)]),
1310          R = (catch {any_term,qlc:cursor(H)}),
1311          false = ets:info(E, safe_fixed),
1312          ets:delete(E),
1313          {throw,bad_pre_fun} = R">>,
1314
1315       <<"E = ets:new(test, []),
1316          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1317          H = qlc:q([{X,Y} || X <- qlc_SUITE:bad_table_exit(E),
1318                              Y <- ets:table(E)]),
1319          R = (catch {any_term,qlc:cursor(H)}),
1320          false = ets:info(E, safe_fixed),
1321          ets:delete(E),
1322          {'EXIT',{bad_pre_fun,_}} = R">>,
1323
1324       <<"E = ets:new(test, [ordered_set]),
1325          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1326          H = qlc:q([X || X <- qlc_SUITE:default_table(E)]),
1327          R = qlc:e(H),
1328          ets:delete(E),
1329          [{1,a},{2,b},{3,c}] = R">>,
1330
1331       <<"E = ets:new(test, [ordered_set]),
1332          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1333          H = qlc:q([X || X <- qlc_SUITE:bad_table(E)]),
1334          {'EXIT', {badarg, _}} = (catch qlc:e(H)),
1335          ets:delete(E)">>,
1336
1337       %% The info tag num_of_objects is currently not used.
1338%%        <<"E = ets:new(test, [ordered_set]),
1339%%           true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1340%%           H = qlc:q([X || X <- qlc_SUITE:bad_table_info_fun_n_objects(E)]),
1341%%           {'EXIT', finito} = (catch {any_term,qlc:e(H)}),
1342%%           ets:delete(E)">>,
1343
1344       <<"E = ets:new(test, [ordered_set]),
1345          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1346          H = qlc:q([Y || {X,Y} <- qlc_SUITE:bad_table_info_fun_indices(E),
1347                          X =:= a]),
1348          %% This is due to lookup. If the table were traversed there
1349          %% would be no failure.
1350          {throw, apa} = (catch {any_term,qlc:e(H)}),
1351          ets:delete(E)">>,
1352
1353       <<"E = ets:new(test, [ordered_set]),
1354          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1355          H = qlc:q([Y || {X,Y} <- qlc_SUITE:bad_table_info_fun_keypos(E),
1356                          X =:= a]),
1357          {'EXIT',{keypos,_}} = (catch {any_term,qlc:info(H)}),
1358          {'EXIT',{keypos,_}} = (catch {any_term,qlc:e(H)}),
1359          ets:delete(E)">>,
1360
1361       begin
1362       MS = ets:fun2ms(fun(X) when element(1, X) > 1 -> X end),
1363       [<<"E = ets:new(test, []),
1364           true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1365           MS = ">>, io_lib:format("~w", [MS]), <<",
1366           H = qlc:q([{X,Y} || X <- ets:table(E,{traverse,{select, MS}}),
1367                               Y <- ets:table(E)]),
1368           R = qlc:e(H),
1369           ets:delete(E),
1370           [{{2,b},{1,a}},{{2,b},{2,b}},{{2,b},{3,c}},
1371            {{3,c},{1,a}},{{3,c},{2,b}},{{3,c},{3,c}}] = lists:sort(R)">>]
1372       end,
1373
1374       begin % a short table
1375       MS = ets:fun2ms(fun(X) when element(1, X) > 1 -> X end),
1376       [<<"E = ets:new(test, []),
1377           true = ets:insert(E, [{0,b}]),
1378           MS =  ">>, io_lib:format("~w", [MS]), <<",
1379           H1 = qlc:q([X || X <- ets:table(E)]),
1380           R1 = qlc:e(H1),
1381           H2 = qlc:q([X || X <- ets:table(E, {traverse, {select, MS}})]),
1382           R2 = qlc:e(H2),
1383           ets:delete(E),
1384           [_] = R1,
1385           [] = R2">>]
1386       end,
1387
1388       begin
1389       File = filename:join(?privdir, "detsfile"),
1390       _ = file:delete(File),
1391       [<<"{ok, Tab} = dets:open_file(apa, [{file,\"">>, File, <<"\"},
1392                                           {type,bag}]),
1393           ok = dets:insert(Tab, [{1,a},{1,b}]),
1394           R = qlc:e(qlc:q([X || X <- dets:table(Tab)])),
1395           dets:close(Tab),
1396           file:delete(\"">>, File, <<"\"),
1397           R">>]
1398       end,
1399
1400       %% [T || P <- Table, F] turned into a match spec.
1401       <<"E = ets:new(apa, [duplicate_bag]),
1402          true = ets:insert(E, [{1,a},{2,b},{3,c},{4,d}]),
1403          QH = qlc:q([X || {X,_} <- ets:table(E), X > 2], unique),
1404          {qlc, _, [{generate, _, {table, _}}], [{unique,true}]} = i(QH),
1405          [3,4] = lists:sort(qlc:e(QH)),
1406          ets:delete(E)">>,
1407
1408       <<"E = ets:new(apa, []),
1409          true = ets:insert(E, [{1,a},{2,b}]),
1410          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_format(E)),
1411          ets:delete(E)">>,
1412
1413       <<"E = ets:new(apa, []),
1414          true = ets:insert(E, [{1,a},{2,b}]),
1415          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_format_arity(E)),
1416          ets:delete(E)">>,
1417
1418       <<"E = ets:new(apa, []),
1419          true = ets:insert(E, [{1,a},{2,b}]),
1420          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_info_arity(E)),
1421          ets:delete(E)">>,
1422
1423       <<"E = ets:new(apa, []),
1424          true = ets:insert(E, [{1,a},{2,b}]),
1425          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_traverse(E)),
1426          ets:delete(E)">>,
1427
1428       <<"E = ets:new(apa, []),
1429          true = ets:insert(E, [{1,a},{2,b}]),
1430          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_post(E)),
1431          ets:delete(E)">>,
1432
1433       <<"E = ets:new(apa, []),
1434          true = ets:insert(E, [{1,a},{2,b}]),
1435          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_max_lookup(E)),
1436          ets:delete(E)">>,
1437
1438       <<"E = ets:new(apa, []),
1439          true = ets:insert(E, [{1,a},{2,b}]),
1440          {'EXIT', {badarg, _}} = (catch qlc_SUITE:bad_table_lookup(E)),
1441          ets:delete(E)">>,
1442
1443       <<"L = [{1,a},{2,b},{3,c}],
1444          QH = qlc:q([element(2, X) || X <- qlc_SUITE:table(L, [2]),
1445                                       (element(1, X) =:= 1)
1446                                        or (2 =:= element(1, X))]),
1447          [a,b] = lists:sort(qlc:e(QH))">>,
1448
1449       <<"etsc(fun(E) ->
1450              Q = qlc:q([{A,B} || {A,B} <-
1451                                qlc:q([{B,A} || {A,B} <- ets:table(E),
1452                                                (A =:= 1) or (A =:= 2),
1453                                                math:sqrt(B) < A])]),
1454              [{2,2}] = qlc:eval(Q),
1455              [1,2] = lookup_keys(Q)
1456           end, [{1,1},{2,2}])">>
1457       ],
1458    run(Config, Ts),
1459
1460    Ts2 = [
1461       %% [T || P <- Table, F] turned into a match spec. Records needed.
1462       <<"E = ets:new(foo, [bag]),
1463          ets:insert(E, [{a,1,2},#a{b=3,c=4},{a,3}]),
1464          QH = qlc:q([X || X <- ets:table(E), is_record(X, a)]),
1465          {list,{table,_}, _} = i(QH),
1466          [{a,1,2},{a,3,4}] = lists:sort(qlc:eval(QH)),
1467          ets:delete(E)">>
1468       ],
1469    run(Config, <<"-record(a, {b,c}).\n">>, Ts2),
1470
1471    ok.
1472
1473%% Caller or cursor process dies.
1474process_dies(Config) when is_list(Config) ->
1475    Ts = [
1476       <<"E = ets:new(test, []),
1477          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1478          false = ets:info(E, safe_fixed),
1479          Parent = self(),
1480          F = fun() ->
1481                      H = qlc:q([X || X <- ets:table(E)]),
1482                      qlc:cursor(H),
1483                      Parent ! {self(),ok}
1484              end,
1485          Pid = spawn_link(F),
1486          receive {Pid,ok} -> ok end,
1487          timer:sleep(10),
1488          false = ets:info(E, safe_fixed),
1489          ets:delete(E)">>,
1490
1491       <<"%% This is not nice. The cursor's monitor kicks in.
1492          E = ets:new(test, []),
1493          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
1494          false = ets:info(E, safe_fixed),
1495          Parent = self(),
1496          F = fun() ->
1497                      H = qlc:q([X || begin
1498                                          process_flag(trap_exit, false),
1499                                          {links, [Pid]} =
1500                                              process_info(self(), links),
1501                                          unlink(Pid),
1502                                          timer:sleep(1),
1503                                          {links, []} =
1504                                              process_info(self(), links),
1505                                          true
1506                                      end,
1507                                      X <- ets:table(E)]),
1508                      C = qlc:cursor(H),
1509                      qlc:next_answers(C),
1510                      Parent ! {self(),ok}
1511              end,
1512          Pid = spawn_link(F),
1513          receive {Pid,ok} -> ok end,
1514          timer:sleep(10),
1515          false = ets:info(E, safe_fixed),
1516          ets:delete(E)">>,
1517
1518       <<"H = qlc:q([X || X <- [1,2]]),
1519          {qlc_cursor, Term} = C = qlc:cursor(H),
1520          PF = process_flag(trap_exit, true),
1521          F = fun(T) -> not is_pid(T) end,
1522          [Pid|_] = lists:dropwhile(F, tuple_to_list(Term)),
1523          exit(Pid, kill),
1524          timer:sleep(1),
1525          {'EXIT', {{qlc_cursor_pid_no_longer_exists, Pid}, _}} =
1526                (catch qlc:next_answers(C)),
1527          process_flag(trap_exit, PF)">>,
1528       <<"H = qlc:q([X || begin process_flag(trap_exit, true), true end,
1529                          X <- [1,2]]),
1530          {qlc_cursor, Term} = C = qlc:cursor(H),
1531          PF = process_flag(trap_exit, true),
1532          F = fun(T) -> not is_pid(T) end,
1533          [Pid|_] = lists:dropwhile(F, tuple_to_list(Term)),
1534          [1] = qlc:next_answers(C, 1),
1535          exit(Pid, stop),
1536          timer:sleep(1),
1537          {'EXIT', {{qlc_cursor_pid_no_longer_exists, Pid}, _}} =
1538              (catch qlc:next_answers(C)),
1539          process_flag(trap_exit, PF)">>,
1540       <<"%% This is not nice. No cleanup is done...
1541          H = qlc:q([X || begin process_flag(trap_exit, false), true end,
1542                     X <- [1,2]]),
1543          {qlc_cursor, Term} = C = qlc:cursor(H),
1544          PF = process_flag(trap_exit, true),
1545          F = fun(T) -> not is_pid(T) end,
1546          [Pid|_] = lists:dropwhile(F, tuple_to_list(Term)),
1547          [1] = qlc:next_answers(C, 1),
1548          exit(Pid, stop),
1549          timer:sleep(1),
1550          {'EXIT', {{qlc_cursor_pid_no_longer_exists, Pid}, _}} =
1551              (catch qlc:next_answers(C)),
1552          process_flag(trap_exit, PF)">>,
1553
1554       <<"PF = process_flag(trap_exit, true),
1555          E = ets:new(test, []),
1556          %% Hard kill. No cleanup will be done.
1557          H = qlc:q([X || begin exit(self(), kill), true end,
1558                          X <- ets:table(E)]),
1559          C = qlc:cursor(H),
1560          {'EXIT', {{qlc_cursor_pid_no_longer_exists, _}, _}} =
1561               (catch qlc:next_answers(C)),
1562          false = ets:info(E, safe_fixed), % - but Ets cleans up anyway.
1563          true = ets:delete(E),
1564          process_flag(trap_exit, PF)">>,
1565
1566       <<"E = ets:new(test, []),
1567          true = ets:insert(E, [{1,a}]),
1568          %% The signal is caught by trap_exit. No process dies...
1569          H = qlc:q([X || begin exit(self(), normal), true end,
1570                          X <- ets:table(E)]),
1571          C = qlc:cursor(H, {spawn_options, []}),
1572          [{1,a}] = qlc:next_answers(C),
1573          qlc:delete_cursor(C),
1574          false = ets:info(E, safe_fixed),
1575          true = ets:delete(E)">>,
1576       <<"E = ets:new(test, []),
1577          true = ets:insert(E, [{1,a}]),
1578          %% The same as last example.
1579          H = qlc:q([X || begin
1580                              process_flag(trap_exit, true),
1581                              exit(self(), normal), true
1582                          end,
1583                          X <- ets:table(E)]),
1584          C = qlc:cursor(H, {spawn_options, []}),
1585          [{1,a}] = qlc:next_answers(C),
1586          qlc:delete_cursor(C),
1587          false = ets:info(E, safe_fixed),
1588          true = ets:delete(E), ok">>,
1589       <<"E = ets:new(test, []),
1590          true = ets:insert(E, [{1,a}]),
1591          H = qlc:q([X || X <- ets:table(E)]),
1592          SpawnOpts = [link, monitor], % monitor is ignored
1593          {qlc_cursor, Term} = C = qlc:cursor(H, {spawn_options, SpawnOpts}),
1594          F = fun(T) -> not is_pid(T) end,
1595          [Pid|_] = lists:dropwhile(F, tuple_to_list(Term)),
1596          Me = self(),
1597          qlc_SUITE:install_error_logger(),
1598          Tuple = {this, tuple, is, writton, onto, the, error_logger},
1599          SP = spawn(fun() ->
1600                  Pid ! Tuple,
1601                  Me ! {self(), done}
1602                end),
1603          receive {SP, done} -> ok end,
1604          [{1,a}] = qlc:next_answers(C),
1605          qlc:delete_cursor(C),
1606          {error, _Pid, Tuple} = qlc_SUITE:read_error_logger(),
1607          qlc_SUITE:uninstall_error_logger(),
1608          false = ets:info(E, safe_fixed),
1609          true = ets:delete(E), ok">>
1610
1611        ],
1612    run(Config, Ts),
1613    ok.
1614
1615%% The sort option.
1616sort(Config) when is_list(Config) ->
1617    Ts = [
1618       <<"H = qlc:q([X || X <- qlc:sort([1,2,3,2], {unique,true})]),
1619          [1,2,3] = qlc:e(H),
1620          C1 = qlc:cursor(H),
1621          [1,2,3] = qlc:next_answers(C1, all_remaining),
1622          qlc:delete_cursor(C1)">>,
1623
1624       <<"H = qlc:q([{X,Y} || X <- qlc:sort(qlc:q([X || X <- [1,2,3,2]]),
1625                                            {unique,true}),
1626                              Y <- [a,b]]),
1627          [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] = qlc:e(H),
1628          C = qlc:cursor(H),
1629          [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] =
1630              qlc:next_answers(C, all_remaining),
1631          qlc:delete_cursor(C)">>,
1632
1633       <<"H = qlc:q([X || X <- qlc:sort(qlc:q([X || X <- apa]))]),
1634          {'EXIT',{badarg,_}} = (catch qlc:e(H))">>,
1635
1636          %% An example with a side effect. The result may vary...
1637       <<"E = ets:new(test, [duplicate_bag]),
1638          true = ets:insert(E, [{1,17},{1,a}]),
1639          H_1 = qlc:q([X || X <- ets:table(E)]),
1640          H = qlc:q([X || X <- [1,2,3], ets:insert(E, {1,-X}),
1641                          {_,Y} <- H_1,
1642                          X > Y]),
1643          true = lists:sort(qlc:e(H)) == [1,2,2,3,3,3],
1644          true = ets:delete(E)">>,
1645
1646       <<"E = ets:new(test, [duplicate_bag]),
1647          true = ets:insert(E, [{1,17}]),
1648          H_1 = qlc:q([X || X <- qlc:sort(ets:tab2list(E))]),
1649          %% Note: side effect in filter!
1650          H = qlc:q([X || X <- [1,2,3], ets:insert(E, {1,-X}),
1651                          {_,Y} <- H_1, X > Y]),
1652          [] = qlc:e(H),
1653          true = ets:delete(E)">>,
1654
1655       <<"H = qlc:q([X || X <- qlc:sort([1,2,3], {fopp,la})]),
1656          {'EXIT',{badarg,_}} = (catch qlc:e(H)),
1657          {'EXIT',{badarg,_}} = (catch qlc:cursor(H)),
1658          F = fun(Obj, A) -> A++[Obj] end,
1659          {'EXIT',{badarg,_}} = (catch qlc:fold(F, [], H))">>,
1660
1661       <<"Q1 = qlc:q([X || X <- [1,2]]),
1662          AL = [Q1, [1,2,3]],
1663          Q2 = qlc:q([X || X <- qlc:sort(qlc:append(AL))]),
1664          [1,1,2,2,3] = qlc:e(Q2)">>,
1665
1666       <<"H = qlc:q([{X,Y} || X <- qlc:sort(qlc:q([X || X <- [1,2,3,2]]),
1667                                            {unique,true}),
1668                              Y <- [a,b]]),
1669          {qlc, _,
1670           [{generate, _, {sort, {qlc, _, [{generate, _, {list, [1,2,3,2]}}],
1671                                  [{unique,true}]},
1672                           []}},
1673            {generate, _, {qlc, _, [{generate, _, {list, [a,b]}}],
1674                           [{unique,true}]}}],
1675           [{unique,true}]} = i(H, unique_all),
1676          [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] = qlc:e(H, unique_all)">>,
1677
1678       <<"L = [1,2,1,3,4,3,1],
1679          true = lists:sort(L) == qlc:e(qlc:q([X || X <- qlc:sort(L)])),
1680          true = lists:usort(L) ==
1681                 qlc:e(qlc:q([X || X <- qlc:sort(L, {unique,true})])),
1682          true = lists:reverse(lists:sort(L)) ==
1683                 qlc:e(qlc:q([X || X <- qlc:sort(L, {order, descending})])),
1684          true = lists:reverse(lists:usort(L)) ==
1685                 qlc:e(qlc:q([X || X <- qlc:sort(L, [{order, descending},
1686                                                     {unique, true}])])),
1687          CF = fun(X, Y) -> X =< Y end,
1688          true = lists:sort(L) ==
1689                 qlc:e(qlc:q([X || X <- qlc:sort(L, {order, CF})])),
1690          true = lists:usort(L) ==
1691                 qlc:e(qlc:q([X || X <- qlc:sort(L, [{order, CF},
1692                                                    {unique, true}])]))">>,
1693
1694       <<"E = ets:new(foo, []),
1695          [true || I <- lists:seq(1, 50000), not ets:insert(E, {I, I})],
1696          H = qlc:q([{X,Y} || X <- [a,b], Y <- qlc:sort(ets:table(E))]),
1697          100000 = length(qlc:e(H)),
1698          ets:delete(E)">>
1699
1700        ],
1701    run(Config, Ts),
1702    ok.
1703
1704%% The sort option.
1705keysort(Config) when is_list(Config) ->
1706
1707    Ts = [
1708       <<"OF = fun(X, Y) -> X =< Y end,
1709          F = fun(Obj, A) -> A++[Obj] end,
1710          H = qlc:q([X || X <- qlc:keysort(1, [{2,a},{1,b}], {order,OF})]),
1711          {'EXIT',{{badarg,order},_}} = (catch qlc:e(H)),
1712          {'EXIT',{{badarg,order},_}} = (catch qlc:fold(F, [], H)),
1713          {'EXIT',{{badarg,order},_}} = (catch qlc:cursor(H))">>,
1714
1715       <<"E = create_ets(1, 2),
1716          H = qlc:q([X || X <- qlc:keysort([1], ets:table(E),
1717                                           [{size,1},{tmpdir,\"/a/b/c\"}])]),
1718          H1 = qlc:q([X || {X,_} <- qlc:e(H), X < 4]),
1719          {error,_,{file_error,_,_}} = qlc:info(H1),
1720          {error,_,{file_error,_,_}} = qlc:e(H1),
1721          ets:delete(E)">>,
1722
1723       <<"L = [{1,a},{2,b},{3,c},{2,b}],
1724          H = qlc:q([{X,Y} || {X,_} <- qlc:keysort(1, qlc:q([X || X <- L]),
1725                                                   {unique,true}),
1726                              Y <- [a,b]]),
1727          [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] = qlc:e(H),
1728          C = qlc:cursor(H),
1729          [{1,a},{1,b},{2,a},{2,b},{3,a},{3,b}] =
1730              qlc:next_answers(C, all_remaining),
1731          qlc:delete_cursor(C)">>,
1732
1733       <<"H1 = qlc:q([X || X <- qlc:keysort(0, [])]),
1734          {'EXIT',{badarg,_}} = (catch qlc:e(H1)),
1735          H2 = qlc:q([X || X <- qlc:keysort(1, [], {bad,arg})]),
1736          {'EXIT',{badarg,_}} = (catch qlc:e(H2)),
1737          H3 = qlc:q([X || X <- qlc:keysort([], [])]),
1738          {'EXIT',{badarg,_}} = (catch qlc:e(H3))">>,
1739
1740       <<"H = qlc:q([X || X <- qlc:keysort(1, [{1,a},{2,b}],
1741                                           [{order,descending},
1742                                           {compressed,true}])]),
1743          [{2,b},{1,a}] = qlc:e(H),
1744          H2 = qlc:q([X || X <- qlc:keysort(1, [{1},{2}], compressed)]),
1745          {'EXIT', {badarg, _}} = (catch qlc:e(H2))">>,
1746
1747       <<"H = qlc:q([X || X <- qlc:keysort(1, [{1,a},{2,b}], {compressed,false})]),
1748          [{1,a},{2,b}] = qlc:e(H)">>,
1749
1750       <<"E = create_ets(1, 2),
1751          H = qlc:q([X || X <- qlc:keysort([1], ets:table(E),
1752                                           [{size,1},{tmpdir,\"/a/b/c\"}])]),
1753          F = fun(Obj, A) -> A++[Obj] end,
1754          {error,_,{file_error,_,_}} = qlc:e(H),
1755          \" \\\"no such\" ++ _ = lists:dropwhile(fun(A) -> A =/= $\s end,
1756                                 lists:flatten(qlc:format_error(qlc:e(H)))),
1757          {error,_,{file_error,_,_}} = qlc:e(H, {unique_all,true}),
1758          {error,_,{file_error,_,_}} = qlc:cursor(H),
1759          {error,_,{file_error,_,_}} = qlc:cursor(H, {unique_all,true}),
1760          {error,_,{file_error,_,_}} = qlc:cursor(H, {spawn_options, []}),
1761          {error,_,{file_error,_,_}} = qlc:cursor(H, {spawn_options,default}),
1762          {error,_,{file_error,_,_}} =
1763               qlc:cursor(H, [{unique_all,true},{spawn_options, []}]),
1764          {error,_,{file_error,_,_}} = qlc:fold(F, [], H),
1765          {error,_,{file_error,_,_}} = qlc:fold(F, [],H, {unique_all,true}),
1766          ets:delete(E)">>,
1767
1768       <<"L = [{1,b,a},{1,b,b},{1,a,a}],
1769          H = qlc:q([X || X <- qlc:keysort([4,1], L)]),
1770          {error,_,bad_object} = qlc:e(H),
1771          \"the keys\" ++ _ = qlc:format_error(qlc:e(H))">>,
1772
1773       begin
1774       File = filename:join(?privdir, "afile"),
1775       ok = file:write_file(File, <<>>),
1776       [<<"H = qlc:q([X || X <- qlc:keysort([1], [{1},{2},{1}],
1777                                            [{tmpdir,\"">>, File, <<"\"},
1778                                             {size,1}])]),
1779           {error,_,{file_error,_,_}} = qlc:e(H),
1780           file:delete(\"">>, File, <<"\")">>]
1781       end,
1782
1783       <<"H0 = qlc:q([X || X <- [1,2,3]]),
1784          H = qlc:q([X || X <- qlc:sort(H0,{tmpdir,\".\"})]),
1785          [1,2,3] = qlc:e(H)">>,
1786
1787       %% The global option 'tmpdir' takes precedence.
1788       begin
1789       PrivDir = ?privdir,
1790       [<<"L = [{1,a},{2,b}],
1791           H = qlc:q([X || X <- qlc:keysort([1], L, {tmpdir,\"/a/b/c\"})]),
1792           H1 = qlc:q([X || X <- H, X > 3]),
1793           Dir = \"">>, PrivDir, <<"\",
1794           Options = [{tmpdir, Dir}],
1795           {qlc,_,[{generate,_,{keysort,{list,L},[1],[{tmpdir,Dir}]}},_],[]} =
1796                i(H1, Options),
1797           [{1,a},{2,b}] = qlc:e(H1, Options)">>] % no check of "/a/b/c"
1798       end,
1799
1800       <<"L = [{2,c},{1,b},{1,a},{3,a},{1,c},{2,b}],
1801          true = lists:sort(L) ==
1802                 qlc:e(qlc:q([X || X <- qlc:keysort([1,2], L)]))">>,
1803
1804       <<"L = [{1,b},{2,c},{1,a},{3,e},{4,f},{3,d}],
1805          true = lists:keysort(1, L) ==
1806                 qlc:e(qlc:q([X || X <- qlc:keysort(1,L)])),
1807          true = lists:ukeysort(1, L) ==
1808                 qlc:e(qlc:q([X || X <- qlc:keysort(1, L, {unique,true})])),
1809          true = lists:reverse(lists:keysort(1, L)) ==
1810                 qlc:e(qlc:q([X || X <- qlc:keysort(1,L,
1811                                                    {order, descending})])),
1812          true = lists:reverse(lists:ukeysort(1, L)) ==
1813                 qlc:e(qlc:q([X || X <- qlc:keysort(1, L, [{unique,true},
1814                                                {order, descending}])]))">>,
1815
1816       <<"L = [{X} || X <- lists:seq(1,100000)],
1817          H1 = qlc:append([L,[{1,2},{2,3},{3,4}]]),
1818          H = qlc:keysort([1], qlc:keysort([1], H1, [{compressed,true}])),
1819          R = qlc:e(H),
1820          100003 = length(R)">>
1821
1822        ],
1823    run(Config, Ts),
1824
1825    ok.
1826
1827%% keysort/1,2, using a file.
1828filesort(Config) when is_list(Config) ->
1829    Ts = [
1830       <<"Q = qlc:q([X || X <- [{3},{1},{2}]]),
1831          Opts = [{size,10},{no_files,3}],
1832          Q2 = qlc:q([{X,Y} || Y <- [1,2], X <- qlc:keysort([1],Q,Opts)]),
1833          [{{1},1},{{2},1},{{3},1},{{1},2},{{2},2},{{3},2}] = qlc:e(Q2)">>
1834        ],
1835    run(Config, Ts),
1836    ok.
1837
1838
1839%% The cache option.
1840cache(Config) when is_list(Config) ->
1841    Ts = [
1842       <<"{'EXIT', {badarg, _}} = (catch qlc:q([X || X <- [1,2]], badarg))">>,
1843
1844       <<"Q1 = qlc:q([X || X <- [1,2,1,2,1]], {unique,true}),
1845          [1,2] = qlc:e(Q1),
1846          [1,2] = qlc:e(Q1, {unique_all,true}),
1847          Q2 = qlc:q([X || X <- qlc:q([X || X <- [1,2,1,2,1]],
1848                                      {unique,true})]),
1849          [1,2] = qlc:e(Q2),
1850          [1,2] = qlc:e(Q2, {unique_all,true}),
1851          Q3 = qlc:q([X || X <- qlc:append([[1,2,3], [4,5,6]])]),
1852          [1,2,3,4,5,6] = qlc:e(Q3)">>,
1853
1854       <<"Q1 = qlc:q([X || {X,_} <- [{1,a},{2,a},{1,b},{2,b}]]),
1855          Q2 = qlc:q([{X,make_ref()} || X <- Q1]),
1856          [{1,_},{2,_},{1,_},{2,_}] = qlc:e(Q2, {unique_all,false}),
1857          [{1,_},{2,_}] = qlc:e(Q2, {unique_all,true})">>,
1858
1859       <<"E = ets:new(test, [duplicate_bag]),
1860          true = ets:insert(E, [{1,a},{2,a},{1,b},{2,b}]),
1861          Q1 = qlc:q([X || {X,_} <- ets:table(E)]),
1862          Q2 = qlc:q([{X,make_ref()} || X <- Q1]),
1863          [{1,_},{1,_},{2,_},{2,_}] = lists:sort(qlc:e(Q2, {unique_all,false})),
1864          [{1,_},{2,_}] = lists:sort(qlc:e(Q2, {unique_all,true})),
1865          ets:delete(E)">>,
1866
1867       <<"Q1 = qlc:q([X || {X,_} <- [{1,a},{2,a},{1,b},{2,b}]]),
1868          Q2 = qlc:q([{X,make_ref()} || X <- qlc:append([Q1, Q1])]),
1869          [{1,_},{2,_},{1,_},{2,_},{1,_},{2,_},{1,_},{2,_}] =
1870                qlc:e(Q2, {unique_all,false}),
1871          [{1,_},{2,_}] = qlc:e(Q2, {unique_all,true})">>,
1872
1873       <<"[] = qlc:e(qlc:q([X || X <- []], {unique, true})),
1874          [] = qlc:e(qlc:q([X || X <- qlc:q([X || X <- qlc:append([])],
1875                                             {unique,true})]))">>,
1876
1877       <<"Q1 = qlc:q([{X,make_ref()} || {X,_} <- [{1,a},{1,b}]]),
1878          [{1,_},{1,_}] = qlc:e(Q1, {unique_all, true}),
1879          Q2 = qlc:q([Y || {X,_} <- [{1,a},{1,b}],
1880                           begin Y = {X,make_ref()}, true end]),
1881          [{1,_},{1,_}] = qlc:e(Q2, {unique_all,true}),
1882          Q3 = qlc:q([Y || X <- [{1,a},{2,a}],
1883                           begin {_,Z} = X, Y = {Z,make_ref()}, true end]),
1884          [{a,_},{a,_}] = qlc:e(Q3, {unique_all, true})">>,
1885
1886       <<"E = ets:new(apa, [duplicate_bag]),
1887          ets:insert(E, [{1,a},{2,a},{1,a}]),
1888          H1 = qlc:q([X || X <- qlc:append(ets:table(E),[7,3,5])],
1889                          {cache, true}),
1890          [{_,a},{_,a},{_,a},7,3,5] = qlc:e(H1),
1891          ets:delete(E)">>,
1892
1893       <<"F = fun(Obj, A) -> A++[Obj] end,
1894          H = qlc:q([X || X <- [1,3,2,4]], cache),
1895          Q = qlc:q([X || X <- H]),
1896          [1,3,2,4] = qlc:fold(F, [], Q, [])">>,
1897
1898       <<"F = fun(Obj, A) -> A++[Obj] end,
1899          E = ets:new(apa, [duplicate_bag]),
1900          true = ets:insert(E, [{1,a},{2,b},{1,a}]),
1901          Q1 = qlc:q([X || X <- ets:table(E)], [cache, unique]),
1902          Q = qlc:q([X || X <- Q1], [cache, unique]),
1903          {qlc, _, [{generate, _,{table,_}}], [{unique,true}]} = i(Q),
1904          R = qlc:fold(F, [], Q, []),
1905          ets:delete(E),
1906          true = [{1,a},{2,b}] == lists:sort(R)">>,
1907
1908       <<"E = ets:new(apa, [duplicate_bag]),
1909          ets:insert(E, [{1,a},{2,b},{1,a}]),
1910          H1 = qlc:q([X || X <- qlc:append(ets:table(E),[7,3])], cache),
1911          H2 = qlc:q([{Y,X} || Y <- [2,1,3], X <- H1]),
1912          [{2,_},{2,_},{2,_},{2,7},{2,3},
1913           {1,_},{1,_},{1,_},{1,7},{1,3},
1914           {3,_},{3,_},{3,_},{3,7},{3,3}] = qlc:e(H2),
1915          ets:delete(E)">>,
1916
1917          %% This case is not 100 percent determined. An Ets table
1918          %% is updated in a filter and later used in a generator.
1919       <<"E = ets:new(apa, [bag]),
1920          true = ets:insert(E, [{1,a},{2,b}]),
1921          H1 = qlc:q([Y || Y <- ets:table(E)],
1922                     [{cache, no}, {unique, true}]),
1923          H = qlc:q([{X,Y} || X <- [{1,a},{2,d},{3,e}],
1924                              ets:insert(E, X),
1925                              Y <- H1]),
1926          [{{1,a},_}, {{1,a},_}, {{2,d},_}, {{2,d},_}, {{2,d},_},
1927           {{3,e},_}, {{3,e},_}, {{3,e},_}, {{3,e},_}] = qlc:e(H),
1928          ets:delete(E)">>,
1929
1930          %% This case is not 100 percent determined. An Ets table
1931          %% is updated in a filter and later used in a generator.
1932       <<"E = ets:new(apa, [bag]),
1933          true = ets:insert(E, [{1,a},{2,b}]),
1934          H1 = qlc:q([Y || Y <- ets:table(E)],
1935                     [{cache, true}, {unique, true}]),
1936          H = qlc:q([{X,Y} || X <- [{1,a},{2,d},{3,e}],
1937                              ets:insert(E, X),
1938                              Y <- H1]),
1939          [{{1,a},_}, {{1,a},_}, {{2,d},_}, {{2,d},_}, {{3,e},_}, {{3,e},_}] =
1940              qlc:e(H),
1941          ets:delete(E)">>,
1942
1943       <<"%% {5979} and {5549} are both hashed to 28244 by phash2/1
1944          E = ets:new(apa, [duplicate_bag]),
1945          true = ets:insert(E, [{5979},{5549},{5979},{5549},{0}]),
1946          H1 = qlc:q([X || X <- ets:table(E)],
1947                     [{cache, true}, {unique, true}]),
1948          H = qlc:q([Y || _ <- [1,2], Y <- H1]),
1949          {qlc, _, [{generate, _, {list, [1,2]}},
1950                    {generate, _, {qlc, _, [{generate, _, {table,_}}],
1951                                   [{cache,ets},{unique,true}]}}],
1952           []} = i(H),
1953          [{0},{0},{5549},{5549},{5979},{5979}] = lists:sort(qlc:e(H)),
1954          ets:delete(E)">>,
1955
1956       <<"E = ets:new(apa, [ordered_set]),
1957          ets:insert(E, [{1},{2}]),
1958          H1 = qlc:q([X || X <- ets:table(E)], [cache, unique]),
1959          H2 = qlc:q([X || Y <- [3,4], ets:insert(E, {Y}), X <- H1]),
1960          {qlc, _, [{generate, _, {list, [3,4]}}, _,
1961                    {generate, _, {qlc, _, [{generate, _,
1962                                             {table, _}}],
1963                                   [{cache, ets}]}}],
1964           []} = i(H2),
1965          [{1},{2},{3},{1},{2},{3}] = qlc:e(H2),
1966          ets:delete(E)">>,
1967
1968       <<"E = ets:new(apa, [ordered_set]),
1969          ets:insert(E, [{1},{2}]),
1970          H1 = qlc:q([X || X <- ets:table(E)], [unique]),
1971          H2 = qlc:q([X || Y <- [3,4], ets:insert(E, {Y}), X <- H1]),
1972          [{1},{2},{3},{1},{2},{3},{4}] = qlc:e(H2),
1973          ets:delete(E)">>,
1974
1975       <<"H0 = qlc:append([a,b], [c,d]),
1976          H = qlc:q([{X,Y} ||
1977                        X <- H0,
1978                        Y <- qlc:q([{X1,Y} ||
1979                                       X1 <- H0,
1980                                       Y <- qlc:q([{X2,Y} ||
1981                                                      X2 <- H0,
1982                                                      Y <- H0])])]),
1983          {qlc, _,
1984           [{generate, _,{append, [{list, [a,b]}, {list, [c,d]}]}},
1985            {generate, _,
1986             {qlc, _,
1987              [{generate, _, {append,[{list, [a,b]},{list, [c,d]}]}},
1988               {generate, _,
1989                {qlc, _,
1990                 [{generate, _,{append,[{list, [a,b]}, {list, [c,d]}]}},
1991                  {generate, _,{append,[{list, [a,b]}, {list, [c,d]}]}}],
1992                 [{cache,ets}]}}],
1993              [{cache,ets}]}}],
1994           []} = i(H, cache_all)">>
1995
1996       ],
1997    run(Config, Ts),
1998    ok.
1999
2000%% OTP-6038. The {cache,list} option.
2001cache_list(Config) when is_list(Config) ->
2002    Ts = [
2003       begin
2004       PrivDir = ?privdir,
2005       [<<"%% unique, cache list. A simple qlc.
2006          Options = [{cache,list}, unique],
2007          L0 = [1,2,3,4,1,2,3,4],
2008          L = qlc_SUITE:table(L0, []),
2009          Q1 = qlc:q([X || X <- L], Options),
2010          Q = qlc:q([{X,Y} || X <- [a,b], Y <- Q1]),
2011          GOptions = [{tmpdir,\"">>, PrivDir, <<"\"}],
2012          {qlc,_,[{generate,_,{list,[a,b]}},
2013                  {generate,_,{qlc,_,
2014                               [{generate,_,{table,_}}],
2015                               [{cache,list},{unique,true}]}}],
2016           []} = i(Q, GOptions),
2017          true = [{X,Y} || X <- [a,b], Y <- [1,2,3,4]] =:=
2018                 qlc:e(Q, GOptions)">>]
2019       end,
2020
2021       begin
2022       MS = ets:fun2ms(fun({X,_}) when X > 1 -> X end),
2023       [<<"%% No cache, even if explicit match specification.
2024          etsc(fun(E) ->
2025                   MS =  ">>, io_lib:format("~w", [MS]), <<",
2026                   Options = [{cache,list}, unique],
2027                   Q = qlc:q([{X,Y} ||
2028                                 X <- ets:table(E, {traverse, {select, MS}}),
2029                                 Y <- [1,2,3]],
2030                             Options),
2031                   {qlc,_,[{generate,_,{table,{ets,table,_}}},
2032                           {generate,_,{list,[1,2,3]}}],
2033                    [{unique,true}]} = i(Q),
2034                   true = [{X,Y} || X <- lists:seq(2,10), Y <- [1,2,3]] =:=
2035                       lists:sort(qlc:e(Q))
2036               end, [{keypos,1}], [{I,a} || I <- lists:seq(1, 10)])">>]
2037       end,
2038
2039       <<"%% Temporary files.
2040          %% Remove list expression caches when possible. (no visible effect)
2041          T = lists:seq(1, 100000), % Huge terms on file
2042          F = fun(C) ->
2043                      Q0 = qlc:q([{X} || X <- [T,T,T], begin X > 0 end],
2044                                 {cache,C}),
2045                      Q1 = qlc:q([{X,Y,Z} ||
2046                                     X <- Q0,
2047                                     Y <- Q0,
2048                                     Z <- Q0],
2049                                 {cache,C}),
2050                      qlc:q([{X, Y} || Y <- [1], X <- Q1])
2051              end,
2052          Ql = F(list),
2053          Rl = qlc:e(Ql, {max_list_size, 64*1024}),
2054          Qe = F(ets),
2055          Re = qlc:e(Qe),
2056          Qf = F(no),
2057          Rf = qlc:e(Qf),
2058          Ri = qlc:e(Ql, {max_list_size, 1 bsl 35}), % heavy
2059          {27,27,27,27,true,true,true} =
2060              {length(Rl), length(Re), length(Rf), length(Ri),
2061               Rl =:= Re, Re =:= Rf, Rf =:= Ri}">>,
2062
2063       <<"%% File sorter.
2064          T = lists:seq(1, 10000),
2065          F = fun(C) ->
2066                      Q0 = qlc:q([{X} || X <- [T,T,T], begin X > 0 end],
2067                                 [{cache,C},unique]),
2068                      Q1 = qlc:q([{X,Y,Z} ||
2069                                     X <- Q0,
2070                                     Y <- Q0,
2071                                     Z <- Q0],
2072                                 [{cache,C},unique]),
2073                      qlc:q([{X, Y} || Y <- [1], X <- Q1])
2074              end,
2075          GOpt = [{max_list_size, 10000}],
2076          Ql = F(list),
2077          Rl = qlc:e(Ql, GOpt),
2078          Qe = F(ets),
2079          Re = qlc:e(Qe, GOpt),
2080          Qf = F(no),
2081          Rf = qlc:e(Qf, GOpt),
2082          {1,1,1,true,true} =
2083              {length(Rl), length(Re), length(Rf), Rl =:= Re, Re =:= Rf}">>,
2084
2085       <<"%% Remove list expression caches when possible. (no visible effect)
2086          Q0 = qlc:q([{X} || X <- [1,2,3], begin X > 0 end], {cache,list}),
2087          Q1 = qlc:q([{X,Y,Z} ||
2088                         X <- Q0,
2089                         Y <- Q0,
2090                         Z <- Q0],
2091                     {cache,list}),
2092          Q = qlc:q([{X, Y} || Y <- [1], X <- Q1]),
2093          R = qlc:e(Q),
2094          L0 = [{X} || X <- [1,2,3], begin X > 0 end],
2095          L1 = [{X,Y,Z} ||
2096                   X <- L0,
2097                   Y <- L0,
2098                   Z <- L0],
2099          L = [{X, Y} || Y <- [1], X <- L1],
2100          true = R =:= L">>,
2101
2102       <<"%% No temporary file.
2103          L = [{I,a} || I <- lists:seq(1, 10)],
2104          Q0 = qlc:q([X || X <- qlc_SUITE:table_error(L, 1, err),
2105                           begin element(1, X) > 5 end],
2106                     {cache,list}),
2107          Q = qlc:q([{X, element(1,Y)} ||
2108                        X <- lists:seq(1, 5),
2109                        Y <- Q0]),
2110          err = qlc:e(Q)">>,
2111
2112       <<"%% Sort internally.
2113          L = [{I,a} || I <- lists:seq(1, 10)],
2114          Q0 = qlc:q([X || X <- qlc_SUITE:table_error(L, 1, err),
2115                           begin element(1, X) > 5 end],
2116                     [unique,{cache,list}]),
2117          Q = qlc:q([{X, element(1,Y)} ||
2118                        X <- lists:seq(1, 5),
2119                        Y <- Q0]),
2120          err = qlc:e(Q, {max_list_size,0})">>,
2121
2122       <<"%% No temporary file.
2123          etsc(fun(E) ->
2124                       Q0 = qlc:q([X || X <- ets:table(E),
2125                                        begin element(1, X) > 5 end],
2126                                  {cache,list}),
2127                       Q = qlc:q([{X, element(1,Y)} || X <- lists:seq(1, 5),
2128                                                       Y <- Q0]),
2129                       R = [{X,Y} || X <- lists:seq(1, 5),
2130                                     Y <- lists:seq(6, 10)],
2131                       R = lists:sort(qlc:e(Q))
2132               end, [{keypos,1}], [{I,a} || I <- lists:seq(1, 10)])">>,
2133
2134       <<"%% Sort internally
2135          etsc(fun(E) ->
2136                       Q0 = qlc:q([X || X <- ets:table(E),
2137                                        begin element(1, X) > 5 end],
2138                                  [{cache,list},unique]),
2139                       Q = qlc:q([{X, element(1,Y)} || X <- lists:seq(1, 5),
2140                                                       Y <- Q0]),
2141                       R = [{X,Y} || X <- lists:seq(1, 5),
2142                                     Y <- lists:seq(6, 10)],
2143                       R = lists:sort(qlc:e(Q))
2144               end, [{keypos,1}], [{I,a} || I <- lists:seq(1, 10)])">>,
2145
2146       <<"%% A few more tests of unique and {cache,list}.
2147          F = fun(CU) ->
2148                      H1 = qlc:q([{X,Y} ||
2149                                     Y <- [a,b],
2150                                     X <- [1,2]],
2151                                 CU),
2152                      qlc:q([{X,Y,Z} || X <- [3,4], {Y,Z} <- H1])
2153              end,
2154          Q1 = F([]),
2155          Q2 = F([{cache,list}, unique]),
2156          R1 = qlc:e(Q1),
2157          R2 = qlc:e(Q2),
2158          R3 = qlc:e(Q2, {max_list_size, 0}), % still in RAM
2159          true = R1 =:= R2,
2160          true = R2 =:= R3">>,
2161
2162       <<"E = ets:new(t, [duplicate_bag]),
2163          true = ets:insert(E, [{2},{1},{2}]),
2164          H1 = qlc:q([{X,Y} ||
2165                         Y <- [a,b],
2166                         {X} <- ets:table(E)],
2167                     [{cache,list}, unique]),
2168          H2 = qlc:q([{X,Y,Z} || X <- [3,4], {Y,Z} <- H1]),
2169          {qlc,_,[{generate,_,{list,[3,4]}},
2170                  {generate,_,{qlc,_,
2171                               [{generate,_,{list,[a,b]}},
2172                                {generate,_,
2173                                 {qlc,_,[{generate,_,{table,{ets,table,_}}}],
2174                                  [{cache,list},{unique,true}]}}],
2175                               [{cache,list},{unique,true}]}}], []} = i(H2),
2176          L1s = [[{X,Y} || Y <- [a,b], X <- Xs] || Xs <- [[1,2], [2,1]]],
2177          L2s = [[{X,Y,Z} || X <- [3,4], {Y,Z} <- L1] || L1 <- L1s],
2178          R1 = qlc:e(H2),
2179          R2 = qlc:e(H2, {max_list_size, 0}), % on temporary file
2180          ets:delete(E),
2181          true = lists:member(R1, L2s),
2182          true = R1 =:= R2">>,
2183
2184       <<"E = ets:new(t, [duplicate_bag]),
2185          true = ets:insert(E, [{2},{1},{2}]),
2186          H1 = qlc:q([{X,Y} ||
2187                         Y <- [a,b],
2188                         {X} <- ets:table(E)],
2189                     [{cache,list}]),
2190          H2 = qlc:q([{X,Y,Z} || X <- [3,4], {Y,Z} <- H1]),
2191          L1s = [[{X,Y} || Y <- [a,b], X <- Xs] || Xs <- [[1,2,2], [2,2,1]]],
2192          L2s = [[{X,Y,Z} || X <- [3,4], {Y,Z} <- L1] || L1 <- L1s],
2193          R1 = qlc:e(H2),
2194          R2 = qlc:e(H2, {max_list_size, 0}), % on temporary file
2195          ets:delete(E),
2196          true = lists:member(R1, L2s),
2197          true = R1 =:= R2">>,
2198
2199       <<"Q1 = qlc:q([{X,Y} ||
2200                         Y <- [a,b],
2201                         {X,_} <- qlc_SUITE:table_error([{a,1}], 2, err)],
2202                     [{cache,list}, unique]),
2203          Q = qlc:q([{X,Y,Z} || X <- [3,4], {Y,Z} <- Q1]),
2204          {qlc,_,[{generate,_,{list,[3,4]}},
2205                  {generate,_,{qlc,_,
2206                               [{generate,_,{list,[a,b]}},
2207                                {generate,_,{table,_}}],
2208                               [{cache,list},{unique,true}]}}],
2209           []} = i(Q),
2210          err = qlc:e(Q,{max_list_size,0})">>,
2211
2212       begin
2213       Privdir = ?privdir,
2214       [<<"
2215          E = ets:new(t, [duplicate_bag]),
2216          N = 17000,
2217          true = ets:insert(E, [{X,X} || X <- lists:seq(1, N)]),
2218          N = ets:info(E, size),
2219          RF = fun(GOpts) ->
2220                       F = fun(CU) ->
2221                                   H1 = qlc:q([{X,Y} ||
2222                                                  Y <- [a,b],
2223                                                  {X,_} <- ets:table(E)],
2224                                              CU),
2225                                   qlc:q([{X,Y,Z} || X <- [3,4], {Y,Z} <- H1])
2226                           end,
2227                       Q1 = F([{cache,list}, unique]),
2228                       _ = qlc:info(Q1, GOpts),
2229                       R1 = qlc:e(Q1, GOpts),
2230                       Q2 = F([unique]),
2231                       R2 = qlc:e(Q2, GOpts),
2232                       true = lists:sort(R1) =:= lists:sort(R2)
2233               end,
2234          GOpts = [{tmpdir,\"">>,Privdir,<<"\"}],
2235          RF([{max_list_size, 1 bsl 35} | GOpts]),
2236          RF(GOpts),
2237          RF([{max_list_size, 40000} | GOpts]),
2238          true = ets:insert(E, [{X,X} || X <- lists:seq(1, N)]),
2239          true = N+N =:= ets:info(E, size),
2240          RF([{max_list_size, 1 bsl 30} | GOpts]),
2241          RF(GOpts),
2242          RF([{max_list_size, 40000} | GOpts]),
2243          ets:delete(E)">>]
2244       end,
2245
2246       <<"%% Temporary file employed.
2247          etsc(fun(E) ->
2248                       Q0 = qlc:q([X || X <- ets:table(E),
2249                                        begin element(1, X) > 5 end],
2250                                  {cache,list}),
2251                       Q = qlc:q([{X, element(1,Y)} || X <- lists:seq(1, 5),
2252                                                       Y <- Q0]),
2253                       R = [{X,Y} || X <- lists:seq(1, 5),
2254                                     Y <- lists:seq(6, 10)],
2255                       R = lists:sort(qlc:e(Q, {max_list_size, 100*1024}))
2256               end, [{keypos,1}], [{I,a,lists:duplicate(100000,1)} ||
2257                                        I <- lists:seq(1, 10)])">>,
2258
2259       <<"%% Temporary file employed. The file is removed after error.
2260          L = [{I,a,lists:duplicate(100000,1)} || I <- lists:seq(1, 10)],
2261          Q0 = qlc:q([X || X <- qlc_SUITE:table_error(L, 1, err),
2262                           begin element(1, X) > 5 end],
2263                     {cache,list}),
2264          Q = qlc:q([{X, element(1,Y)} ||
2265                        X <- lists:seq(1, 5),
2266                        Y <- Q0]),
2267          err = qlc:e(Q)">>,
2268
2269       <<"%% Temporary file employed. The file is removed after error.
2270          L = [{I,a,lists:duplicate(100000,1)} || I <- lists:seq(1, 10)],
2271          Q0 = qlc:q([X || X <- qlc_SUITE:table(L, 1, []),
2272                           begin element(1, X) > 5 end],
2273                     {cache,list}),
2274          Q = qlc:q([{X, element(1,Y)} ||
2275                        X <- lists:seq(1, 5),
2276                        Y <- Q0]),
2277          {error, _, {file_error,_,_}} = qlc:e(Q, {tmpdir, \"/a/b/c\"})">>,
2278
2279       <<"Q = qlc:q([X || X <- [1,2]]),
2280          {'EXIT', {badarg, _}} = (catch qlc:e(Q, {max_list_size, -1}))">>,
2281
2282       <<"Q = qlc:q([X || X <- [1,2]]),
2283          {'EXIT', {badarg, _}} = (catch qlc:e(Q, {max_list_size, foo}))">>
2284
2285       ],
2286    run(Config, Ts),
2287    ok.
2288
2289%% Filters and match specs.
2290filter(Config) when is_list(Config) ->
2291    Ts = [
2292       <<"L = [1,2,3,4,5],
2293          QH1 = qlc:q([X || X <- L, X > 1, X < 4]),
2294          [2,3] = qlc:e(QH1),
2295          {list,{list,L},_MS} = i(QH1)
2296         ">>,
2297
2298       <<"L = [1,2,3,4,5],
2299          QH2 = qlc:q([X || X <- L, X > 1, X < 4, X > 2]),
2300          [3] = qlc:e(QH2),
2301          {list,{list,L},_MS} = i(QH2)
2302         ">>,
2303
2304          %% "X > 1" is skipped since the matchspec does the job
2305       <<"QH3 = qlc:q([X || X <- [1,2,3,4,5], X > 1, begin X < 4 end]),
2306          [2,3] = qlc:e(QH3),
2307          {qlc,_,[{generate,_,{list,{list,[1,2,3,4,5]},_MS}},_],[]} = i(QH3)
2308         ">>,
2309
2310       <<"QH4 = qlc:q([{X,Y} || X <- [1,2], Y <- [1,2]]),
2311          [{1,1},{1,2},{2,1},{2,2}] = qlc:e(QH4),
2312          {qlc,_,[{generate,_,{list,[1,2]}},{generate,_,{list,[1,2]}}],[]} =
2313              i(QH4)">>,
2314
2315          %% "X > 1" is skipped since the matchspec does the job
2316       <<"QH5 = qlc:q([{X,Y} || X <- [1,2], X > 1, Y <- [1,2]]),
2317          [{2,1},{2,2}] = qlc:e(QH5),
2318          {qlc,_,[{generate,_,{list,{list,[1,2]},_MS}},
2319                  {generate,_,{list,[1,2]}}],[]} =
2320              i(QH5)">>,
2321
2322       <<"%% Binaries are not handled at all when trying to find lookup values
2323          etsc(fun(E) ->
2324                      A = 2,
2325                      Q = qlc:q([X || {X} <- ets:table(E), <<A>> =:= <<X>>]),
2326                      [2] = lists:sort(qlc:e(Q)),
2327                      false = lookup_keys(Q)
2328              end, [{1},{2},{3}])">>,
2329
2330       <<"etsc(fun(E) ->
2331                      Q = qlc:q([X || {X,_} <- ets:table(E),
2332                                   qlc:e(qlc:q([Y || {Y,_} <- ets:table(E),
2333                                                              Y > X])) == []]),
2334                      [3] = qlc:e(Q)
2335              end, [{1,a},{2,b},{3,c}])">>,
2336
2337       <<"Q = qlc:q([X || {X} <- [], (false or (X/0 > 3))]),
2338          \"[]\" = qlc:info(Q),
2339          [] = qlc:e(Q)">>,
2340
2341       <<"%% match spec
2342          [] = qlc:e(qlc:q([X || {X} <- [{1},{2}],
2343                                 (false orelse (X/0 > 3))])),
2344          %% generated code
2345          {'EXIT', {badarith, _}} =
2346            (catch qlc:e(qlc:q([X || {X} <- [{1}],
2347                                     begin (false orelse (X/0 > 3)) end])))">>,
2348
2349       <<"%% Partial evaluation in filter.
2350          etsc(fun(E) ->
2351                     QH = qlc:q([{X+1,Y} || {X,Y} <- ets:table(E),
2352                                            X =:= 1-1+1+(+1)]),
2353                     [{3,2}] = qlc:e(QH),
2354                     [2] = lookup_keys(QH)
2355              end, [{1,1},{2,2},{3,3}])">>,
2356
2357       <<"%% =/2 in filters must not be recognized when 'badmatch' is
2358          %% possible.
2359          etsc(fun(E) ->
2360                     QH = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
2361                                          ((Y = X) =:= 3)]),
2362                     {'EXIT', {{badmatch,4},_}} = (catch qlc:e(QH)),
2363                     false = lookup_keys(QH)
2364               end, [{3,3},{4,true}])">>,
2365
2366       <<"%% One more of the same kind.
2367          etsc(fun(E) ->
2368                      QH = qlc:q([{X,Y} || {X,_} <- ets:table(E),
2369                                           (Y=X) =:= (Y=1+1)]),
2370                      {'EXIT', {{badmatch,2},_}} = (catch qlc:e(QH)),
2371                      false = lookup_keys(QH)
2372              end, [{1,1},{2,2},{3,3}])">>,
2373
2374       <<"%% OTP-5195. Used to return a value, but badarith is correct.
2375          etsc(fun(E) ->
2376                      QH = qlc:q([X || {X,_} <- ets:table(E),
2377                                       (X =:= 1) and
2378                                    if X =:= 1 -> true;
2379                                       true -> X/0
2380                                    end]),
2381                      {'EXIT',{badarith,_}} = (catch qlc:e(QH)),
2382                      false = lookup_keys(QH)
2383              end, [{1,1},{2,2},{3,3}])">>,
2384
2385       <<"fun(Z) ->
2386            Q = qlc:q([X || Z < 2, X <- [1,2,3]]),
2387            [] = qlc:e(Q)
2388          end(3)">>,
2389
2390       <<"H = qlc:q([{P1,A,P2,B,P3,C} ||
2391                  P1={A,_} <- [{1,a},{2,b}],
2392                  {_,B}=P2 <- [{1,a},{2,b}],
2393                  C=P3 <- [1],
2394                  {[X,_],{_,X}} <- [{[1,2],{3,1}}, {[a,b],{3,4}}],
2395                  A > 0,
2396                  B =/= c,
2397                  C > 0]),
2398          L = [{{1,a},1,{1,a},a,1,1}, {{1,a},1,{2,b},b,1,1},
2399               {{2,b},2,{1,a},a,1,1}, {{2,b},2,{2,b},b,1,1}],
2400          L = qlc:e(H)">>,
2401
2402       <<"H = qlc:q([{X,Y} ||
2403                  X = _ <- [1,2,3],
2404                  _ = Y <- [a,b,c],
2405                  _ = _ <- [foo],
2406                  X > 1,
2407                  Y =/= a]),
2408          [{2,b},{2,c},{3,b},{3,c}] = qlc:e(H)">>
2409
2410       ],
2411    run(Config, Ts),
2412    ok.
2413
2414%% info/2.
2415info(Config) when is_list(Config) ->
2416    Ts = [
2417       <<"{list, [1,2]} = i(qlc:q([X || X <- [1,2]])),
2418          {append,[{list, [1,2]}, {list, [3,4]}]} =
2419               i(qlc:append([1,2],[3,4])),
2420          {sort,{list, [1,2]},[]} = i(qlc:sort([1,2])),
2421          E = ets:new(foo, []),
2422          ets:insert(E, [{1},{2}]),
2423          {table, _} = i(ets:table(E)),
2424          true = ets:delete(E),
2425          {list, [1,2]} = i([1,2]),
2426          {append, [{list, [1,2]}, {list, [3,4]}]} =
2427             i(qlc:q([X || X <- qlc:append([1,2],[3,4])])),
2428
2429          H0 = qlc:q([X || X <- throw({throw,t})]),
2430          {throw,t} = (catch {any_term,qlc:info(H0)}),
2431          {'EXIT', {badarg, _}} =
2432               (catch qlc:info(foobar)),
2433          {'EXIT', {badarg, _}} =
2434               (catch qlc:info(qlc:q([X || X <- [1,2]]), badarg))">>,
2435
2436       <<"{'EXIT', {badarg, _}} =
2437               (catch qlc:info([X || {X} <- []], {n_elements, 0})),
2438          L = lists:seq(1, 1000),
2439          \"[1, 2, 3, 4, 5, 6, 7, 8, 9, 10 | '...']\" = qlc:info(L, {n_elements, 10}),
2440          {cons,A1,{integer,A2,1},{atom,A3,'...'}} =
2441            qlc:info(L, [{n_elements, 1},{format,abstract_code}]),
2442          1 = erl_anno:line(A1),
2443          1 = erl_anno:line(A2),
2444          1 = erl_anno:line(A3),
2445          Q = qlc:q([{X} || X <- [a,b,c,d,e,f]]),
2446          {call,_,_,[{cons,_,{atom,_,a},{cons,_,{atom,_,b},{cons,_,{atom,_,c},
2447                                                            {atom,_,'...'}}}},
2448                     {call,_,_,_}]} =
2449          qlc:info(Q, [{n_elements, 3},{format,abstract_code}]),
2450          \"ets:match_spec_run([a, b, c, d, e, f],\n\"
2451          \"                   ets:match_spec_compile([{'$1', [true], \"
2452          \"[{{'$1'}}]}]))\" =
2453             qlc:info(Q, [{n_elements, infinity}])">>,
2454
2455       <<"Q1 = qlc:q([{X} || X <- qlc:q([X || X <- [1,2]])]),
2456          {qlc, _, [{generate, _, {list, [1,2]}}],[]} = i(Q1),
2457          Q2 = qlc:q([X || X <- qlc:q([{X} || X <- [1,2]])]),
2458          {list,{list,[1,2]},_} = i(Q2),
2459          [{1},{2}] = qlc:eval(Q2),
2460          Q3 = qlc:q([{X,Y} || X <- qlc:q([X || X <- [a,b]]),
2461                               Y <- qlc:q([Z || Z <- [a,b]])]),
2462          {qlc, _, [{generate, _, {list, [a,b]}},
2463                    {generate, _, {list, [a,b]}}], []} = i(Q3),
2464          Q4 = qlc:q([X || X <- [a]]),
2465          {list, [a]} = i(Q4),
2466          Q5 = qlc:q([X || X <- qlc:q([Y || Y <- [a,b]], unique)]),
2467          {qlc, _, [{generate, _, {list, [a,b]}}], [{unique,true}]} =
2468             i(Q5)">>,
2469
2470       <<"H = qlc:q([X || X <- qlc:append([qlc:q([X || X <- [1,2]]),[1,2]])]),
2471          {append, [{list, [1,2]},{list, [1,2]}]} = i(H),
2472          [1,2,1,2] = qlc:e(H)">>,
2473
2474       <<"H = qlc:q([{X} || X <- [], X > 1]),
2475          {list, []} = i(H),
2476          [] = qlc:e(H)">>,
2477
2478       <<"H1 = qlc:q([{X} || X <- [], X > 1]),
2479          H = qlc:q([{X} || X <- H1, X < 10]),
2480          {list, []} = i(H),
2481          [] = qlc:e(H)">>,
2482
2483       <<"L = [1,2,3],
2484          QH1 = qlc:q([{X} || X <- L, X > 1]),
2485          QH2 = qlc:q([{X} || X <- QH1]),
2486          [{{2}},{{3}}] = qlc:e(QH2),
2487          {list,{list,{list,L},_},_} = i(QH2)">>,
2488
2489       <<"H = qlc:q([X || X <- qlc:q([Y || Y <- qlc:q([Z || Z <-[1,2,1]])])]),
2490          {list, [1,2,1]} = i(H),
2491          [1,2,1] = qlc:eval(H)">>,
2492
2493       <<"%% Used to replace empty ETS tables with [], but that won't work.
2494          E = ets:new(apa,[]),
2495          QH1 = qlc:q([{X} || X <- ets:table(E), X > 1]),
2496          QH2 = qlc:q([{X} || X <- QH1], cache),
2497          [] = qlc:e(QH2),
2498          {qlc,_,[{generate,_,{table,{ets,table,_}}}],[]} = i(QH2),
2499          ets:delete(E)">>,
2500
2501       <<"Q1 = qlc:q([W || W <- [a,b]]),
2502          Q2 = qlc:q([Z || Z <- qlc:sort([55296,56296,57296])], unique),
2503          Q3 = qlc:q([{X,Y} || X <- qlc:keysort([2], [{1,a}]),
2504                               Y <- qlc:append([Q1, Q2]),
2505                               X > Y]),
2506          {qlc, T1,
2507           [{generate, P1, {list, [{1,a}]}},
2508            {generate, P2, {append, [{list, [a,b]},
2509                                    {qlc, T2, [{generate, P3,
2510                                                {sort, {list,[55296,56296,57296]},[]}}],
2511                                     [{cache,ets},{unique,true}]}]}},F],
2512           []} = i(Q3, cache_all),
2513          {tuple, _, [{var,_,'X'}, {var,_,'Y'}]} = binary_to_term(T1),
2514          {var, _, 'X'} = binary_to_term(P1),
2515          {var, _, 'Y'} = binary_to_term(P2),
2516          {var, _, 'Z'} = binary_to_term(P3),
2517          {var, _, 'Z'} = binary_to_term(T2),
2518          {op, _, '>', {var, _, 'X'}, {var, _, 'Y'}} = binary_to_term(F),
2519          true = binary_to_list(<<
2520           \"beginV1=qlc:q([Z||Z<-qlc:sort([55296,56296,57296],[])],[{unique,true}]),\"
2521           \"qlc:q([{X,Y}||X<-[{1,a}],Y<-qlc:append([[a,b],V1]),X>Y])end\"
2522              >>) == format_info(Q3, true)">>,
2523
2524       <<"Q1 = qlc:q([{X} || X <- qlc:q([X || X <- [a,b]])]),
2525          {qlc, _, [{generate, _, {list, [a,b]}}], []} = i(Q1),
2526          Q2 = qlc:q([X || X <- qlc:q([{X} || X <- [a,b]])]),
2527          {list,{list,[a,b]},_} = i(Q2),
2528          [{a},{b}] = qlc:eval(Q2)">>,
2529
2530       <<"Q = qlc:keysort(2, [{1,a,b},{2,b,c},{3,4,c}]),
2531          {keysort,{list,[{1,a,b},{2,b,c},{3,4,c}]},2,[]} = i(Q),
2532          true = binary_to_list(<<
2533             \"qlc:keysort(2,[{1,a,b},{2,b,c},{3,4,c}],[])\">>)
2534              == format_info(Q, true),
2535          [{3,4,c},{1,a,b},{2,b,c}] = qlc:e(Q)">>,
2536
2537       <<"E = ets:new(foo, []),
2538          ets:insert(E, [{1},{2}]),
2539          Q = qlc_SUITE:default_table(E),
2540          {table,{'$MOD','$FUN',[]}} = i(Q),
2541          true = binary_to_list(<<\"'$MOD':'$FUN'()\">>)
2542                == format_info(Q, true),
2543          true = ets:delete(E)">>,
2544
2545       <<"\"[]\" = qlc:info([], flat),
2546          \"[]\" = qlc:info([]),
2547          \"[]\" = qlc:info([], {flat, true})">>,
2548
2549       <<"H = qlc:q([{X} || X <- [a,b]]),
2550         \"ets:match_spec_run([a,b],ets:match_spec_compile(\" ++ _ =
2551                format_info(H, true),
2552         \"ets:match_spec_run([a,b],ets:match_spec_compile(\" ++ _ =
2553                format_info(H, false)">>,
2554
2555       <<"H = qlc:q([{X} || X <- [a,b], begin true end]),
2556          true = binary_to_list(<<\"qlc:q([{X}||X<-[a,b],begintrueend])\">>)
2557             == format_info(H, true),
2558          true = binary_to_list(<<\"qlc:q([{X}||X<-[a,b],begintrueend])\">>)
2559             == format_info(H, false)">>,
2560
2561       <<"H = qlc:q([A || {A} <- [{1},{2}], (A =:= 2) andalso true]),
2562          {call,_,{remote,_,{atom,_,ets},{atom,_,match_spec_run}},_} =
2563             qlc:info(H, {format,abstract_code})">>,
2564
2565       <<"H = qlc:q([{X} || X <- qlc:q([{X} || X <- [a,b], begin true end],
2566                                       unique),
2567                            begin true end]),
2568          true = binary_to_list(<<
2569         \"beginV1=qlc:q([{X}||X<-[a,b],begintrueend],[{unique,true}]),\"
2570         \"qlc:q([{X}||X<-V1,begintrueend])end\">>) ==
2571              format_info(H, true),
2572          true = binary_to_list(<<
2573         \"qlc:q([{X}||X<-qlc:q([{X}||X<-[a,b],begintrueend],\"
2574         \"[{unique,true}]),begintrueend])\">>) == format_info(H, false)">>,
2575
2576       <<"H0 = qlc:q([{V3} || V3 <- qlc:q([{V1} || V1 <- [a,b],
2577                                                   begin true end], unique),
2578                              begin true end]),
2579          H = qlc:sort(H0),
2580          true = binary_to_list(<<
2581          \"qlc:sort(qlc:q([{V3}||V3<-qlc:q([{V1}||\"
2582          \"V1<-[a,b],begintrueend],[{unique,true}]),begintrueend]),[])\">>)
2583              == format_info(H, false),
2584          true = binary_to_list(<<
2585          \"beginV2=qlc:q([{V1}||V1<-[a,b],begintrueend],[{unique,true}]),\"
2586          \"V4=qlc:q([{V3}||V3<-V2,begintrueend]),qlc:sort(V4,[])end\">>)
2587              == format_info(H, true)">>,
2588
2589       <<"H0 = qlc:q([X || X <- [true], begin true end]),
2590          H1 = qlc:q([{X} || X <- [a,b], begin true end],
2591                     [{unique,begin [T] = qlc:e(H0), T end}]),
2592          {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},
2593                  [{lc,_,{tuple,_,[{var,_,'X'}]},
2594                         [{generate,_,{var,_,'X'},
2595                                      {cons,_,{atom,_,a},_}},
2596                          {block, _, [{atom, _, true}]}]},
2597                   {cons,_,_,_}]} = i(H1, {format, abstract_code})">>,
2598
2599       <<"E = ets:new(apa, [duplicate_bag]),
2600          true = ets:insert(E, [{1,a},{2,b},{3,c},{4,d}]),
2601          QH = qlc:q([X || {X,_} <- ets:tab2list(E), X > 2], unique),
2602          {qlc, _, [{generate, _, {list, _, _MS}}], [{unique, true}]} =
2603                i(QH),
2604          [3,4] = lists:sort(qlc:e(QH)),
2605          ets:delete(E)">>,
2606
2607       %% "Imported" variable.
2608       <<"F = fun(U) -> qlc:q([{X} || X <- [1,2,3,4,5,6], X > U]) end,
2609          QH = F(4),
2610          {call, _ ,
2611                {remote, _, {atom, _, ets},{atom, _, match_spec_run}},
2612                [{string, _, [1,2,3,4,5,6]},
2613                 {call, _,
2614                       _compile,
2615                       [{cons, _,
2616                              {tuple, _,
2617                                     [{atom, _,'$1'},
2618                                      {cons, _,
2619                                            {tuple,
2620                                                 _,
2621                                                [{atom, _,'>'},
2622                                                 {atom, _,'$1'},
2623                                                 {tuple,
2624                                                      _,
2625                                                     [{atom, _,const},
2626                                                      {integer, _,4}]}]},
2627                                            _},
2628                                      {cons, _, _, _}]},
2629                              {nil,_}}]}]} = i(QH, {format, abstract_code}),
2630          [{5},{6}] = qlc:e(QH),
2631          [{4},{5},{6}] = qlc:e(F(3))">>,
2632
2633          <<"Fun = fun ?MODULE:i/2,
2634             L = [{#{k => #{v => Fun}}, Fun}],
2635             H = qlc:q([Q || Q <- L, Q =:= {#{k => #{v => Fun}}, Fun}]),
2636             L = qlc:e(H),
2637             {call,_,_,[{lc,_,{var,_,'Q'},
2638                         [{generate,_,_,_},
2639                          {op,_,_,_,_}]}]} =
2640                qlc:info(H, [{format,abstract_code}])">>
2641
2642       ],
2643    run(Config, Ts),
2644    ok.
2645
2646%% Nested QLC expressions. QLC expressions in filter and template.
2647nested_info(Config) when is_list(Config) ->
2648    Ts = [
2649       <<"L = [{1,a},{2,b},{3,c}],
2650          Q = qlc:q(
2651                [{X,R} ||
2652                    {X,_} <- qlc_SUITE:table(L, []),
2653                    begin % X imported
2654                        R = qlc:e(qlc:q([{X,Y} || {Y,_}
2655                                                    <- qlc_SUITE:table(L, []),
2656                                                  Y > X])),
2657                        true
2658                    end]),
2659          true = binary_to_list(<<
2660            \"qlc:q([{X,R}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}]),\"
2661            \"beginR=qlc:e(qlc:q([{X,Y}||{Y,_}<-qlc_SUITE:table(L,[]),Y>X]))\"
2662            \",trueend])\">>) == format_info(Q, true),
2663          [{1,[{1,2},{1,3}]},{2,[{2,3}]},{3,[]}] = qlc:e(Q)">>,
2664
2665       <<"L = [{1,a},{2,b},{3,c}],
2666          Q = qlc:q( % X imported
2667                [{X,qlc:e(qlc:q([{X,Y} || {Y,_} <- qlc_SUITE:table(L, []),
2668                                          Y > X]))} ||
2669                    {X,_} <- qlc_SUITE:table(L, [])]),
2670          true = binary_to_list(<<
2671            \"qlc:q([{X,qlc:e(qlc:q([{X,Y}||{Y,_}<-qlc_SUITE:table(L,[]),\"
2672            \"Y>X]))}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}])])\">>)
2673              == format_info(Q, true),
2674          [{1,[{1,2},{1,3}]},{2,[{2,3}]},{3,[]}] = qlc:e(Q)">>,
2675
2676       <<"L = [{1,a},{2,b},{3,c}],
2677          Q = qlc:q(
2678                [{X,R} ||
2679                    {X,_} <- qlc_SUITE:table(L, []),
2680                    begin % X imported
2681                        R = qlc:e(qlc:q([{X,Y} || {Y,_}
2682                                                    <- qlc_SUITE:table(L, []),
2683                                                  Y =:= X])),
2684                        true
2685                    end]),
2686          true = binary_to_list(<<
2687            \"qlc:q([{X,R}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}]),\"
2688            \"beginR=qlc:e(qlc:q([{X,Y}||{Y,_}<-qlc_SUITE:table(L,[]),\"
2689            \"Y=:=X])),trueend])\">>) == format_info(Q, true),
2690          [{1,[{1,1}]},{2,[{2,2}]},{3,[{3,3}]}] = qlc:e(Q)">>,
2691
2692       <<"L = [{1,a},{2,b},{3,c}],
2693          Q = qlc:q(
2694                [{X, % X imported
2695                  qlc:e(qlc:q([{X,Y} || {Y,_} <- qlc_SUITE:table(L, []),
2696                                        Y =:= X]))} ||
2697                    {X,_} <- qlc_SUITE:table(L, [])]),
2698          true = binary_to_list(<<
2699            \"qlc:q([{X,qlc:e(qlc:q([{X,Y}||{Y,_}<-qlc_SUITE:table(L,[]),\"
2700            \"Y=:=X]))}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}])])\">>)
2701             == format_info(Q, true),
2702          [{1,[{1,1}]},{2,[{2,2}]},{3,[{3,3}]}] = qlc:e(Q)">>,
2703
2704       <<"L = [{1,a},{2,b},{3,c}],
2705          Q = qlc:q(
2706                [{X,R} ||
2707                    {X,_} <- qlc_SUITE:table(L, []),
2708                    begin
2709                        R = qlc:e(qlc:q([Y || Y <- [X]])),
2710                        true
2711                    end]),
2712          true = binary_to_list(<<
2713            \"qlc:q([{X,R}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}]),\"
2714            \"beginR=qlc:e(qlc:q([Y||Y<-[X]])),trueend])\">>)
2715             == format_info(Q, true),
2716          [{1,[1]},{2,[2]},{3,[3]}] = qlc:e(Q)">>,
2717
2718       <<"L = [{1,a},{2,b},{3,c}],
2719          Q = qlc:q(
2720                [{X,qlc:e(qlc:q([Y || Y <- [X]]))} ||
2721                    {X,_} <- qlc_SUITE:table(L, [])]),
2722          true = binary_to_list(<<
2723            \"qlc:q([{X,qlc:e(qlc:q([Y||Y<-[X]]))}||{X,_}<-qlc_SUITE:\"
2724            \"the_list([{1,a},{2,b},{3,c}])])\">>) == format_info(Q, true),
2725          [{1,[1]},{2,[2]},{3,[3]}] = qlc:e(Q)">>,
2726
2727       <<"L = [{1,a},{2,b}],
2728          Q = qlc:q(
2729                [{X,Y} ||
2730                    {X,_} <- qlc_SUITE:table(L, []),
2731                    {Y,_} <- qlc:q(
2732                               [{Z,V} ||
2733                                   {Z,_} <- qlc_SUITE:table(L, []),
2734                                   {V} <- qlc:q(
2735                                              [{W} || W
2736                                                  <- qlc_SUITE:table(L, [])])
2737                                      ])
2738                       ]),
2739          true = binary_to_list(<<
2740           \"beginV1=qlc:q([{W}||W<-qlc_SUITE:the_list([{1,a},{2,b}])]),\"
2741           \"V2=qlc:q([{Z,V}||{Z,_}<-qlc_SUITE:the_list([{1,a},{2,b}]),\"
2742           \"{V}<-V1]),qlc:q([{X,Y}||{X,_}<-qlc_SUITE:the_list([{1,a},\"
2743           \"{2,b}]),{Y,_}<-V2])end\">>) == format_info(Q, true),
2744          [{1,1},{1,1},{1,2},{1,2},{2,1},{2,1},{2,2},{2,2}] = qlc:e(Q)">>
2745
2746       ],
2747    run(Config, Ts),
2748    ok.
2749
2750
2751%% Lookup keys. Mostly test of patterns.
2752lookup1(Config) when is_list(Config) ->
2753    Ts = [
2754       <<"etsc(fun(E) ->
2755                Q = qlc:q([A || {A=3} <- ets:table(E)]),
2756                [3] = qlc:eval(Q),
2757                [3] = lookup_keys(Q)
2758          end, [{1},{2},{3},{4}])">>,
2759
2760       <<"etsc(fun(E) ->
2761                Q = qlc:q([A || {A=3} <- ets:table(E)],{max_lookup,0}),
2762                [3] = qlc:eval(Q),
2763                false = lookup_keys(Q)
2764          end, [{1},{2},{3},{4}])">>,
2765
2766       <<"%% The lookup and max_lookup options interact.
2767          etsc(fun(E) ->
2768                Q = qlc:q([X || {X} <- ets:table(E),
2769                                (X =:= 1) or (X =:= 2)],
2770                          [{lookup,true},{max_lookup,1}]),
2771                {'EXIT', {no_lookup_to_carry_out, _}} = (catch qlc:e(Q))
2772         end, [{1},{2}])">>,
2773
2774       <<"etsc(fun(E) ->
2775                Q = qlc:q([{A,B,C,D} || {A,B}={C,D} <- ets:table(E)]),
2776                [{1,2,1,2},{3,4,3,4}] = lists:sort(qlc:eval(Q)),
2777                false = lookup_keys(Q)
2778          end, [{1,2},{3,4}])">>,
2779
2780       <<"etsc(fun(E) ->
2781                Q = qlc:q([{A,B,D} || {A,B}={D,A} <- ets:table(E)]),
2782                [{1,1,1},{2,2,2}] = lists:sort(qlc:eval(Q)),
2783                false = lookup_keys(Q)
2784          end, [{1,2},{2,2},{1,1}])">>,
2785
2786       <<"etsc(fun(E) ->
2787                Q = qlc:q([{A,B,D} || {A,B}={D,A} <- ets:table(E),
2788                                      (D =:= 2) or (B =:= 1)],
2789                          {max_lookup,infinity}),
2790                [{1,1,1},{2,2,2}] = qlc:eval(Q),
2791                [1,2] = lookup_keys(Q)
2792         end, [{1,2},{2,2},{1,1}])">>,
2793
2794       <<"etsc(fun(E) ->
2795                Q = qlc:q([{A,B,D} || {A,B}={D,A} <- ets:table(E),
2796                                      (D =:= 2) xor (B =:= 1)]),
2797                [{1,1,1},{2,2,2}] = qlc:eval(Q),
2798                [1,2] = lookup_keys(Q)
2799         end, [{1,2},{2,2},{1,1}])">>,
2800
2801       <<"etsc(fun(E) ->
2802                Q = qlc:q([3 || {{[3,4],apa}} <- ets:table(E)]),
2803                [3] = qlc:e(Q),
2804                [{[3,4],apa}] = lookup_keys(Q)
2805        end, [{{[4,3],foo}},{{[3,4],apa}}])">>,
2806
2807       <<"etsc(fun(E) ->
2808                Q = qlc:q([3 || {3} <- ets:table(E)]),
2809                [3] = qlc:e(Q),
2810                [3] = lookup_keys(Q)
2811        end, [{2},{3},{4}])">>,
2812
2813       <<"etsc(fun(E) ->
2814                Q = qlc:q([{X,Y,Z} || {{X,_},Y,Y={_,Z},X,Y} <- ets:table(E)]),
2815                [] = qlc:e(Q),
2816                false = lookup_keys(Q)
2817        end, [{{1,1},1,{1,1},1,1}])">>,
2818
2819       <<"etsc(fun(E) ->
2820                Q = qlc:q([X || {X,X=2} <- ets:table(E)]),
2821                [2] = qlc:e(Q),
2822                [2] = lookup_keys(Q)
2823        end, [{2,2},{3,3}])">>,
2824
2825       <<"etsc(fun(E) ->
2826                Q = qlc:q([X || {{_,3}={4,_}=X} <- ets:table(E)]),
2827                [{4,3}] = qlc:e(Q),
2828                [{4,3}] = lookup_keys(Q)
2829        end, [{{2,3}},{{4,3}}])">>,
2830
2831       <<"U = 17.0,
2832          etsc(fun(E) ->
2833                Q = qlc:q([X || {_=X=_} <- ets:table(E)]),
2834                [U] = qlc:e(Q),
2835                false = lookup_keys(Q)
2836        end, [{U},{U+U,U}])">>,
2837
2838       <<"etsc(fun(E) ->
2839                Q = qlc:q([{X,Y,Z,W} || {X=Y}=Z={V=W} <- ets:table(E),
2840                                        V == {h,g}]),
2841                [{{h,g},{h,g},{{h,g}},{h,g}}] = qlc:e(Q),
2842                [{h,g}] = lookup_keys(Q)
2843        end, [{h,g},{{h,g}}])">>,
2844
2845       <<"etsc(fun(E) ->
2846                Q = qlc:q([{C,Y,Z,X} || {{X=Y}=Z}={{A=B}=C} <- ets:table(E),
2847                                        A == a, B =/= c]),
2848                [{{a},a,{a},a}] = qlc:e(Q),
2849                [{a}] = lookup_keys(Q)
2850        end, [{{1}},{{a}}])">>,
2851
2852       <<"etsc(fun(E) ->
2853               Q = qlc:q([{A,D,Y,X} ||
2854                             {{A={B=C}},{D={C}}} = {X,Y} <- ets:table(E),
2855                             [] == B]),
2856                [{{[]},{[]},{{[]}},{{[]}}}] = qlc:e(Q),
2857                [{{[]}}] = lookup_keys(Q)
2858        end, [{{{[]}},{{[]}}}])">>,
2859
2860       {cres,
2861        <<"etsc(fun(E) ->
2862                 Q = qlc:q([X || {X}=X <- ets:table(E)]),
2863                 [] = qlc:e(Q),
2864                 false = lookup_keys(Q)
2865         end, [{1},{a}])">>,
2866        %% {warnings,[{{2,37},qlc,nomatch_pattern}]}},
2867        []},
2868
2869       <<"etsc(fun(E) ->
2870                Q = qlc:q([X || {X=X,Y=Y}={Y=Y,X=X} <- ets:table(E),
2871                                {} == X]),
2872                [{}] = qlc:e(Q),
2873                [{}] = lookup_keys(Q)
2874        end, [{{},{}},{[],[]}])">>,
2875
2876       <<"etsc(fun(E) ->
2877                Q = qlc:q([X || {3+4=7,X} <- ets:table(E),
2878                                X =:= 3+997]),
2879                [1000] = qlc:e(Q),
2880                [7] = lookup_keys(Q)
2881        end, [{7,1000},{8,1000}])">>,
2882
2883       <<"etsc(fun(E) ->
2884                Q = qlc:q([{X, Y} || [X]=[Y] <- ets:table(E)]),
2885                [] = qlc:eval(Q),
2886                false = lookup_keys(Q)
2887        end, [{a}])">>,
2888
2889       {cres,
2890        <<"etsc(fun(E) ->
2891                 Q = qlc:q([X || X={1,2,3,X,5} <- ets:table(E)]),
2892                 [] = qlc:e(Q),
2893                 false = lookup_keys(Q)
2894         end, [{a},{b}])">>,
2895        %% {warnings,[{{2,35},qlc,nomatch_pattern}]}},
2896        []},
2897
2898       {cres,
2899        <<"etsc(fun(E) ->
2900                 Q = qlc:q([X || X=[1,2,3,X,5] <- ets:table(E)]),
2901                 [] = qlc:e(Q),
2902                 false = lookup_keys(Q)
2903         end, [{a},{b}])">>,
2904        %% {warnings,[{{2,35},qlc,nomatch_pattern}]}},
2905        []},
2906
2907       <<"etsc(fun(E) ->
2908                Q = qlc:q([X || X = <<X>> <- ets:table(E)]),
2909                [] = qlc:e(Q),
2910                false = lookup_keys(Q)
2911        end, [{a},{b}])">>,
2912
2913       <<"Tre = 3.0,
2914          etsc(fun(E) ->
2915                Q = qlc:q([{A,B} || {A,B}={{a,C},{a,C}} <- ets:table(E),
2916                                    C =:= Tre]),
2917                [] = qlc:e(Q),
2918                [{a,Tre}] = lookup_keys(Q)
2919        end, [{a,b}])">>,
2920
2921       <<"A = 3,
2922          etsc(fun(E) ->
2923                Q = qlc:q([X || X <- ets:table(E), A =:= element(1, X)]),
2924                [{3,3}] = qlc:e(Q),
2925                [3] = lookup_keys(Q)
2926        end, [{1,a},{3,3}])">>,
2927
2928       <<"A = 3,
2929          etsc(fun(E) ->
2930                Q = qlc:q([X || X <- ets:table(E), A =:= erlang:element(1, X)]),
2931                [{3,3}] = qlc:e(Q),
2932                [3] = lookup_keys(Q)
2933        end, [{1,a},{3,3}])">>,
2934
2935       <<"etsc(fun(E) ->
2936                A = 3,
2937                Q = qlc:q([X || X <- ets:table(E),
2938                                A == element(1,X),
2939                                element(1,X) =:= a]),
2940                [] = qlc:e(Q),
2941                [a] = lookup_keys(Q)
2942        end, [{a},{b},{c}])">>,
2943
2944       {cres,
2945        <<"etsc(fun(E) ->
2946                 Q = qlc:q([X || {X = {[a,Z]},
2947                                  Z = [foo, {[Y]}],
2948                                  Y = {{foo,[X]}}} <- ets:table(E)]),
2949                 [] = qlc:e(Q),
2950                 false = lookup_keys(Q)
2951         end, [{a,b,c},{d,e,f}])">>,
2952        %% {warnings,[{{2,34},qlc,nomatch_pattern}]}}
2953        []}
2954
2955       ],
2956    run(Config, Ts),
2957    ok.
2958
2959%% Lookup keys. Mostly test of filters.
2960lookup2(Config) when is_list(Config) ->
2961    Ts = [
2962       <<"%% Only guards are inspected. No lookup.
2963          etsc(fun(E) ->
2964                 Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
2965                                     ((Y = X) =:= 3)]),
2966                 {'EXIT', {{badmatch,4},_}} = (catch qlc:e(Q))
2967         end, [{3,3},{4,true}])">>,
2968
2969       <<"%% Only guards are inspected. No lookup.
2970          etsc(fun(E) ->
2971                 Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
2972                                     Y = (X =:= 3)]),
2973                 {'EXIT', {{badmatch,false},_}} = (catch qlc:e(Q))
2974         end, [{false,3},{true,3}])">>,
2975
2976       <<"%% Only guards are inspected. No lookup.
2977          etsc(fun(E) ->
2978                 Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
2979                                     Y = (X =:= 3)]),
2980                 {'EXIT', {{badmatch,false},_}} = (catch qlc:e(Q))
2981         end, [{3,true},{4,true}])">>,
2982
2983       <<"%% Only guards are inspected. No lookup.
2984          E1 = ets:new(e, [ordered_set]),
2985          true = ets:insert(E1, [{1,1}, {2,2}, {3,3}, {4,4}, {5,5}]),
2986          E2 = ets:new(join, [ordered_set]),
2987          true = ets:insert(E2, [{true,1},{false,2}]),
2988          Q = qlc:q([{X,Z} || {_,X} <- ets:table(E1),
2989                              {Y,Z} <- ets:table(E2),
2990                              Y = (X =:= 3)]),
2991          {'EXIT', {{badmatch,false},_}} = (catch qlc:e(Q)),
2992          ets:delete(E1),
2993          ets:delete(E2)">>,
2994
2995       <<"etsc(fun(E) ->
2996                Q = qlc:q([{A,B,D} || {A,B}={D,A} <- ets:table(E),
2997                                      (A =:= 3) or (4 =:= D)]),
2998                [{3,3,3},{4,4,4}] = lists:sort(qlc:e(Q)),
2999                [3,4] = lookup_keys(Q)
3000        end, [{2,2},{3,3},{4,4}])">>,
3001
3002       <<"etsc(fun(E) ->
3003               Q = qlc:q([X || {X,U} <- ets:table(E), X =:= U]),
3004               [1] = qlc:e(Q),
3005               false = lookup_keys(Q)
3006       end, [{1,1}])">>,
3007
3008       {cres,
3009        <<"etsc(fun(E) ->
3010                 Q = qlc:q([{X,Y} || {X=Y} <- ets:table(E),
3011                                     {[X],4} =:= {[3],X}]),
3012                 [] = qlc:e(Q),
3013                 false = lookup_keys(Q)
3014         end, [{1}, {2}])">>,
3015        %% {warnings,[{{3,46},qlc,nomatch_filter}]}},
3016        []},
3017
3018       {cres,
3019        <<"etsc(fun(E) ->
3020                Q = qlc:q([X || {X} <- ets:table(E),
3021                                X == 1, X =:= 2]),
3022                [] = qlc:e(Q),
3023                false = lookup_keys(Q)
3024        end, [{1}, {2}])">>,
3025        %% {warnings,[{{3,43},qlc,nomatch_filter}]}},
3026        []},
3027
3028       {cres,
3029        <<"etsc(fun(E) ->
3030                 Q = qlc:q([{X,Y} || {X=Y} <- ets:table(E),
3031                                     {[X,Y],4} =:= {[3,X],X}]),
3032                 [] = qlc:e(Q),
3033                 false = lookup_keys(Q)
3034         end, [{1}, {2}])">>,
3035        %% {warnings,[{{3,48},qlc,nomatch_filter}]}},
3036        []},
3037
3038       <<"etsc(fun(E) ->
3039                Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
3040                                    ({X,3} =:= {Y,Y}) or (X =:= 4)]),
3041                [{3,3},{4,4}] = lists:sort(qlc:e(Q)),
3042                [3,4] = lookup_keys(Q)
3043        end, [{2,2},{3,3},{4,4},{5,5}])">>,
3044
3045       {cres,
3046        <<"etsc(fun(E) ->
3047                 Q = qlc:q([X || {X} <- ets:table(E), {[X]} =:= {[3,4]}]),
3048                 [] = qlc:e(Q),
3049                 false = lookup_keys(Q)
3050         end, [{[3]},{[3,4]}])">>,
3051        %% {warnings,[{{2,61},qlc,nomatch_filter}]}},
3052        []},
3053
3054       <<"etsc(fun(E) ->
3055                U = 18,
3056                Q = qlc:q([{X,Y} || {X=Y} <- ets:table(E), [X|a] =:= [3|U]]),
3057                [] = qlc:e(Q),
3058                [3] = lookup_keys(Q)
3059        end, [{2}, {3}])">>,
3060
3061       <<"etsc(fun(E) ->
3062                U = 18, V = 19,
3063                Q = qlc:q([{X,Y} || {X=Y} <- ets:table(E),
3064                                    [X|V] =:= [3|U+1]]),
3065                [{3,3}] = qlc:e(Q),
3066                [3] = lookup_keys(Q)
3067        end, [{2},{3}])">>,
3068
3069       <<"%% Blocks are not handled.
3070          etsc(fun(E) ->
3071                Q = qlc:q([X || {X} <- ets:table(E), begin X == a end]),
3072                [a] = qlc:e(Q),
3073                false = lookup_keys(Q)
3074        end, [{a},{b}])">>,
3075
3076       {cres,
3077        <<"etsc(fun(E) ->
3078                 Q = qlc:q([X || {X} <- ets:table(E),
3079                                 (3 =:= X) or (X =:= 12),
3080                                 (8 =:= X) or (X =:= 10)]),
3081                 [] = lists:sort(qlc:e(Q)),
3082                 false = lookup_keys(Q)
3083         end, [{2},{3},{4},{8}])">>,
3084        %% {warnings,[{{4,44},qlc,nomatch_filter}]}},
3085        []},
3086
3087       {cres,
3088        <<"etsc(fun(E) ->
3089                 Q = qlc:q([X || {X} <- ets:table(E),
3090                                 ((3 =:= X) or (X =:= 12))
3091                                  and ((8 =:= X) or (X =:= 10))]),
3092                 [] = lists:sort(qlc:e(Q)),
3093                 false = lookup_keys(Q)
3094         end, [{2},{3},{4},{8}])">>,
3095        %% {warnings,[{{4,35},qlc,nomatch_filter}]}},
3096        []},
3097
3098       <<"F = fun(U) ->
3099                Q = qlc:q([X || {X} <- [a,b,c],
3100                                 X =:= if U -> true; true -> false end]),
3101                [] = qlc:eval(Q),
3102                false = lookup_keys(Q)
3103              end,
3104          F(apa)">>,
3105
3106       {cres,
3107        <<"etsc(fun(E) ->
3108                 Q = qlc:q([X || {X=1,X} <- ets:table(E), X =:= 2]),
3109                 [] = qlc:e(Q),
3110                 false = lookup_keys(Q)
3111           end, [{1,1},{2,1}])">>,
3112        %% {warnings,[{{2,61},qlc,nomatch_filter}]}},
3113        []},
3114
3115       <<"Two = 2.0,
3116          etsc(fun(E) ->
3117                Q = qlc:q([X || {X} <- ets:table(E), X =:= Two]),
3118                [Two] = qlc:e(Q),
3119                [Two] = lookup_keys(Q)
3120        end, [{2.0},{2}])">>,
3121
3122       <<"etsc(fun(E) ->
3123                %% This float is equal (==) to an integer. Not a constant!
3124                Q = qlc:q([X || {X} <- ets:table(E), X == {a,b,c,[2.0]}]),
3125                [_,_] = qlc:e(Q),
3126                false = lookup_keys(Q)
3127        end, [{{a,b,c,[2]}},{{a,b,c,[2.0]}}])">>,
3128
3129       <<"%% Must _not_ regard floats as constants. Check imported variables
3130          %% in runtime.
3131          etsc(fun(E) ->
3132                U = 3.0,
3133                QH = qlc:q([X || {X,_} <- ets:table(E), X =:= U]),
3134                [] = qlc:e(QH),
3135                [U] = lookup_keys(QH)
3136        end, [{1,a},{2,b},{3,c},{4,d}])">>,
3137
3138       <<"etsc(fun(E) ->
3139                Q = qlc:q([X || {X} <- ets:table(E),
3140                                length(X) =:= 1]),
3141                [[1]] = qlc:e(Q),
3142                false = lookup_keys(Q)
3143        end, [{[1]},{[2,3]}])">>,
3144
3145       <<"etsc(fun(E) ->
3146                A=3,
3147                Q = qlc:q([X || {X,Y} <- ets:table(E), X =:= A, Y =:= 3]),
3148                [3] = qlc:e(Q),
3149                [3] = lookup_keys(Q)
3150        end, [{3,3},{4,3}])">>,
3151
3152       <<"etsc(fun(E) ->
3153                A = 1,
3154                Q = qlc:q([X || {X} <- ets:table(E),
3155                                X =:= 1, <<X>> =:= <<A>>]),
3156                [1] = qlc:e(Q),
3157                [1] = lookup_keys(Q)
3158        end, [{1},{2}])">>,
3159
3160       <<"etsc(fun(E) ->
3161                Q = qlc:q([X || {X} <- ets:table(E), X == a]),
3162                [a] = qlc:e(Q),
3163                [a] = lookup_keys(Q)
3164        end, [{a},{b},{c}])">>,
3165
3166       <<"etsc(fun(E) ->
3167                 Q = qlc:q([X || {X}=Y <- ets:table(E),
3168                                 element(2, Y) == b,
3169                                 X =:= 1]),
3170                 [] = qlc:e(Q),
3171                 false = lookup_keys(Q)
3172        end, [{1,b},{2,3}])">>,
3173
3174       <<"etsc(fun(E) ->
3175                Q = qlc:q([X || {X} <- ets:table(E), element(1,{X}) =:= 1]),
3176                [1] = qlc:e(Q),
3177                [1] = lookup_keys(Q)
3178        end, [{1}, {2}])">>,
3179
3180       <<"etsc(fun(E) ->
3181                Q = qlc:q([X || {X} <- ets:table(E), 1 =:= element(1,{X})]),
3182                [1] = qlc:e(Q),
3183                [1] = lookup_keys(Q)
3184        end, [{1}, {2}])">>,
3185
3186       {cres,
3187        <<"etsc(fun(E) ->
3188                 Q = qlc:q([X || {X} <- ets:table(E),
3189                                 X =:= {1},
3190                                 element(1,X) =:= 2]),
3191                 [] = qlc:e(Q),
3192                 false = lookup_keys(Q)
3193         end, [{{1}},{{2}}])">>,
3194        %% {warnings,[{{4,47},qlc,nomatch_filter}]}},
3195        []},
3196
3197       {cres,
3198        <<"etsc(fun(E) ->
3199                 Q = qlc:q([X || {X} <- ets:table(E),
3200                                 X =:= {1},
3201                                 element(1,X) =:= element(1, {2})]),
3202                 [] = qlc:e(Q),
3203                 false = lookup_keys(Q)
3204         end, [{{1}},{{2}}])">>,
3205        %% {warnings,[{{4,47},qlc,nomatch_filter}]}},
3206        []},
3207
3208       <<"etsc(fun(E) ->
3209                Q = qlc:q([X || {X} <- ets:table(E),
3210                                element(1,X) =:= 1, X =:= {1}]),
3211                [{1}] = qlc:e(Q),
3212                [{1}] = lookup_keys(Q)
3213        end, [{{1}},{{2}}])">>,
3214
3215       <<"etsc(fun(E) ->
3216                Q = qlc:q([X || {X} <- ets:table(E),
3217                                {{element(1,element(1,{{1}}))}} =:= {X}]),
3218                [{1}] = qlc:e(Q),
3219                [{1}] = lookup_keys(Q)
3220        end, [{{1}},{{2}}])">>,
3221
3222       <<"etsc(fun(E) ->
3223                Q = qlc:q([X || X <- ets:table(E),
3224                                {element(1,element(1, {{1}}))} =:=
3225                                      {element(1,X)}]),
3226                [{1}] = qlc:e(Q),
3227                [1] = lookup_keys(Q)
3228        end, [{1},{2}])">>,
3229
3230       <<"etsc(fun(E) ->
3231                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3232                                (X =:= 1) and (Y =:= 2)
3233                                    or (X =:= 3) and (Y =:= 4)]),
3234                [1,3] = lists:sort(qlc:e(Q)),
3235                [{1,2}, {3,4}] = lookup_keys(Q)
3236        end, [{{1,2}}, {{3,4}}, {{2,3}}])">>,
3237
3238       <<"etsc(fun(E) ->
3239                Q = qlc:q([X || {{X,a}} <- ets:table(E), X =:= 3]),
3240                [3] = qlc:e(Q),
3241                [{3,a}] = lookup_keys(Q)
3242        end, [{{3,a}},{{3,b}}])">>,
3243
3244       <<"etsc(fun(E) ->
3245                Q = qlc:q([X || {{X,Y},_Z} <- ets:table(E),
3246                                X =:= 3, Y =:= a]),
3247                [3] = qlc:e(Q),
3248                [{3,a}] = lookup_keys(Q)
3249        end, [{{3,a},3}, {{4,a},3}])">>,
3250
3251       <<"etsc(fun(E) ->
3252                Q = qlc:q([X || {{X,Y},_Z} <- ets:table(E),
3253                                (X =:= 3) and (Y =:= a)
3254                                   or (X =:= 4) and (Y =:= a)]),
3255                [3,4] = qlc:e(Q),
3256                [{3,a}, {4,a}] = lookup_keys(Q)
3257        end, [{{3,a},3}, {{4,a},3}])">>,
3258
3259       {cres,
3260        <<"etsc(fun(E) ->
3261                 Q = qlc:q([X || {X} <- ets:table(E),
3262                                 (X =:= 3) and (X =:= a)]),
3263                 [] = qlc:e(Q),
3264                 false = lookup_keys(Q)
3265         end, [{3}, {4}])">>,
3266        %% {warnings,[{{3,44},qlc,nomatch_filter}]}},
3267        []},
3268
3269       <<"etsc(fun(E) ->
3270                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3271                                X =:= 3, ((Y =:= a) or (Y =:= b))]),
3272                [3,3] = qlc:e(Q),
3273                [{3,a},{3,b}] = lists:sort(lookup_keys(Q))
3274        end, [{{3,a}},{{2,b}},{{3,b}}])">>,
3275
3276       <<"etsc(fun(E) ->
3277                Q = qlc:q([X || {X,Y} <- ets:table(E),
3278                                ((X =:= 3) or (Y =:= 4))  and (X == a)]),
3279                [a] = qlc:e(Q),
3280                [a] = lookup_keys(Q)
3281        end, [{a,4},{3,3}])">>,
3282
3283       <<"etsc(fun(E) ->
3284                Q = qlc:q([X || {X,Y} <- ets:table(E),
3285                                (X =:= 3) or ((Y =:= 4)  and (X == a))]),
3286                [3,a] = lists:sort(qlc:e(Q)),
3287                [3,a] = lookup_keys(Q)
3288        end, [{a,4},{3,3}])">>,
3289
3290       <<"etsc(fun(E) ->
3291                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3292                                (X =:= 3) or ((Y =:= 4)  and (X == a))]),
3293                [3,a] = lists:sort(qlc:e(Q)),
3294                false = lookup_keys(Q)
3295        end, [{{3,a}},{{2,b}},{{a,4}}])">>,
3296
3297       <<"etsc(fun(E) ->
3298                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3299                                ((X =:= 3) or (Y =:= 4))  and (X == a)]),
3300                [a] = lists:sort(qlc:e(Q)),
3301                [{a,4}] = lookup_keys(Q)
3302        end, [{{3,a}},{{2,b}},{{a,4}}])">>,
3303
3304        <<"etsc(fun(E) ->
3305                NoAnswers = 3*3*3+2*2*2,
3306                Q = qlc:q([{X,Y,Z} ||
3307                              {{X,Y,Z}} <- ets:table(E),
3308                              (((X =:= 4) or (X =:= 5)) and
3309                               ((Y =:= 4) or (Y =:= 5)) and
3310                               ((Z =:= 4) or (Z =:= 5))) or
3311                              (((X =:= 1) or (X =:= 2) or (X =:= 3)) and
3312                               ((Y =:= 1) or (Y =:= 2) or (Y =:= 3)) and
3313                               ((Z =:= 1) or (Z =:= 2) or (Z =:= 3)))],
3314                          {max_lookup, NoAnswers}),
3315                 {list, {table, _}, _} = i(Q),
3316                 [{1,1,1},{2,2,2},{3,3,3}] = lists:sort(qlc:e(Q)),
3317                 true = NoAnswers =:= length(lookup_keys(Q))
3318         end, [{{1,1,1}},{{2,2,2}},{{3,3,3}},{{3,3,4}},{{4,1,1}}])">>,
3319
3320        <<"etsc(fun(E) ->
3321                Q = qlc:q([{X,Y,Z} ||
3322                              {{X,Y,Z}} <- ets:table(E),
3323                              (((X =:= 4) or (X =:= 5)) and
3324                               ((Y =:= 4) or (Y =:= 5)) and
3325                               ((Z =:= 4) or (Z =:= 5))) or
3326                              (((X =:= 1) or (X =:= 2) or (X =:= 3)) and
3327                               ((Y =:= 1) or (Y =:= 2) or (Y =:= 3)) and
3328                               ((Z =:= 1) or (Z =:= 2) or (Z =:= 3)))],
3329                          {max_lookup, 10}),
3330                 [{1,1,1},{2,2,2},{3,3,3}] = lists:sort(qlc:e(Q)),
3331                 {table,{ets,table,[_,[{traverse,{select,_}}]]}} = i(Q)
3332         end, [{{1,1,1}},{{2,2,2}},{{3,3,3}},{{3,3,4}},{{4,1,1}}])">>,
3333
3334       <<"etsc(fun(E) ->
3335                Q = qlc:q([X || X={_,_,_} <- ets:table(E),
3336                                element(1, X) =:= 3, element(2, X) == a]),
3337                [{3,a,s}] = qlc:e(Q),
3338                [3] = lookup_keys(Q)
3339        end, [{1,c,q},{2,b,r},{3,a,s}])">>,
3340
3341       <<"etsc(fun(E) ->
3342                Q = qlc:q([X || X <- ets:table(E),
3343                                element(0, X) =:= 3]),
3344                [] = qlc:e(Q),
3345                false = lookup_keys(Q)
3346        end, [{1},{2}])">>,
3347
3348       <<"etsc(fun(E) ->
3349                F = fun(_) -> 3 end,
3350                %% No occurs check; X =:= F(X) is ignored.
3351                Q = qlc:q([X || {X} <- ets:table(E),
3352                                X =:= 3, X =:= F(X)]),
3353                {qlc,_,[{generate,_,{list,{table,_},_}},_],[]} = i(Q),
3354                [3] = lists:sort(qlc:e(Q)),
3355                [3] = lookup_keys(Q)
3356        end, [{2},{3},{4}])">>,
3357
3358       <<"etsc(fun(E) ->
3359                A = a, B = a,
3360                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3361                                ((X =:= A) and (Y =:= B))
3362                                 or ((X =:= B) and (Y =:= A))]),
3363                [a] = qlc:e(Q),
3364                %% keys are usorted, duplicate removed:
3365                [{a,a}] = lookup_keys(Q)
3366        end, [{{a,a}},{{b,b}}])">>,
3367
3368       <<"etsc(fun(E) ->
3369                A = a, B = b,
3370                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3371                                ((X =:= A) and (Y =:= B))
3372                                 or ((X =:= B) and (Y =:= A))]),
3373                [a,b] = lists:sort(qlc:e(Q)),
3374                [{a,b},{b,a}] = lookup_keys(Q)
3375        end, [{{a,b}},{{b,a}},{{c,a}},{{d,b}}])">>,
3376
3377       %% The atom 'fail' is recognized - lookup.
3378       <<"etsc(fun(E) ->
3379                Q = qlc:q([A || {A} <- ets:table(E),
3380                                (A =:= 2)
3381                                    orelse fail
3382                                   ]),
3383                [2] = lists:sort(qlc:e(Q)),
3384                [2] = lookup_keys(Q)
3385           end, [{1},{2}])">>
3386
3387       ],
3388
3389    ok = run(Config, Ts),
3390
3391    TsR = [
3392       %% is_record/2,3:
3393       <<"etsc(fun(E) ->
3394                Q = qlc:q([element(1, X) || X <- ets:table(E),
3395                                            erlang:is_record(X, r, 2)]),
3396                 [r] = qlc:e(Q),
3397                 [r] = lookup_keys(Q)
3398         end, [{keypos,1}], [#r{}])">>,
3399       <<"etsc(fun(E) ->
3400                Q = qlc:q([element(1, X) || X <- ets:table(E),
3401                                            is_record(X, r, 2)]),
3402                 [r] = qlc:e(Q),
3403                 [r] = lookup_keys(Q)
3404         end, [{keypos,1}], [#r{}])">>,
3405       {cres,
3406        <<"etsc(fun(E) ->
3407                Q = qlc:q([element(1, X) || X <- ets:table(E),
3408                                            record(X, r)]),
3409                 [r] = qlc:e(Q),
3410                 [r] = lookup_keys(Q)
3411         end, [{keypos,1}], [#r{}])">>,
3412        {warnings,[{{4,45},erl_lint,{obsolete_guard,{record,2}}}]}},
3413       <<"etsc(fun(E) ->
3414                Q = qlc:q([element(1, X) || X <- ets:table(E),
3415                                            erlang:is_record(X, r)]),
3416                 [r] = qlc:e(Q),
3417                 [r] = lookup_keys(Q)
3418         end, [{keypos,1}], [#r{}])">>,
3419       <<"etsc(fun(E) ->
3420                Q = qlc:q([element(1, X) || X <- ets:table(E),
3421                                            is_record(X, r)]),
3422                 [r] = qlc:e(Q),
3423                 [r] = lookup_keys(Q)
3424         end, [{keypos,1}], [#r{}])">>
3425
3426       ],
3427
3428    ok = run(Config, <<"-record(r, {a}).\n">>, TsR),
3429
3430    Ts2 = [
3431       <<"etsc(fun(E) ->
3432                 Q0 = qlc:q([X ||
3433                                X <- ets:table(E),
3434                                (element(1, X) =:= 1) or
3435                                  (element(1, X) =:= 2)],
3436                           {cache,ets}),
3437                 Q = qlc:q([{X,Y} ||
3438                               X <- [1,2],
3439                               Y <- Q0]),
3440                 {qlc,_,[{generate,_,{list,[1,2]}},
3441                         {generate,_,{table,_}}], []} = i(Q),
3442                 [{1,{1}},{1,{2}},{2,{1}},{2,{2}}] = lists:sort(qlc:e(Q)),
3443                 [1,2] = lookup_keys(Q)
3444          end, [{keypos,1}], [{1},{2}])">>,
3445
3446       <<"etsc(fun(E) ->
3447                 Q0 = qlc:q([X ||
3448                                X <- ets:table(E),
3449                                (element(1, X) =:= 1) or
3450                                  (element(1, X) =:= 2)]),
3451                 Q = qlc:q([{X,Y} ||
3452                               X <- [1,2],
3453                               Y <- Q0],
3454                           {cache,true}),
3455                 {qlc,_,[{generate,_,{list,[1,2]}},
3456                         {generate,_,{table,_}}],[]} = i(Q),
3457                 [1,2] = lookup_keys(Q)
3458          end, [{keypos,1}], [{1},{2}])">>,
3459
3460       %% One introduced QLC expression (join, ms), and the cache option.
3461       <<"%% Match spec and lookup. The lookup is done twice, which might
3462          %% be confusing...
3463          etsc(fun(E) ->
3464                       Q = qlc:q([{X,Y} ||
3465                                     X <- [1,2],
3466                                     {Y} <- ets:table(E),
3467                                     (Y =:= 1) or (Y =:= 2)],
3468                                 []),
3469                       [{1,1},{1,2},{2,1},{2,2}] = qlc:e(Q),
3470                       {qlc,_,[{generate,_,{list,[1,2]}},
3471                               {generate,_,{list,{table,_},_}}],[]} = i(Q),
3472                       [1,2] = lookup_keys(Q)
3473               end, [{keypos,1}], [{1},{2},{3}])">>,
3474       <<"%% The same as last example, but with cache.
3475          %% No cache needed (always one lookup only).
3476          etsc(fun(E) ->
3477                       Q = qlc:q([{X,Y} ||
3478                                     X <- [1,2],
3479                                     {Y} <- ets:table(E),
3480                                     (Y =:= 1) or (Y =:= 2)],
3481                                 [cache]),
3482                       [{1,1},{1,2},{2,1},{2,2}] = qlc:e(Q),
3483                       {qlc,_,[{generate,_,{list,[1,2]}},
3484                               {generate,_,{list,{table,_},_}}],[]} = i(Q),
3485                       [1,2] = lookup_keys(Q)
3486               end, [{keypos,1}], [{1},{2},{3}])">>,
3487
3488       <<"%% And again, this time only lookup, no mach spec.
3489          etsc(fun(E) ->
3490                       Q = qlc:q([{X,Y} ||
3491                                     X <- [1,2],
3492                                     Y <- ets:table(E),
3493                                     (element(1, Y) =:= 1)
3494                                      or (element(1, Y) =:= 2)],
3495                                 []),
3496                       [{1,{1}},{1,{2}},{2,{1}},{2,{2}}] = qlc:e(Q),
3497                       {qlc,_,[{generate,_,{list,[1,2]}},
3498                               {generate,_,{table,_}}],[]} = i(Q),
3499                       [1,2] = lookup_keys(Q)
3500               end, [{keypos,1}], [{1},{2},{3}])">>,
3501       <<"%% As last one, but with cache.
3502          %% No cache needed (always one lookup only).
3503          etsc(fun(E) ->
3504                       Q = qlc:q([{X,Y} ||
3505                                     X <- [1,2],
3506                                     Y <- ets:table(E),
3507                                     (element(1, Y) =:= 1)
3508                                      or (element(1, Y) =:= 2)],
3509                                 [cache]),
3510                       {qlc,_,[{generate,_,{list,[1,2]}},
3511                               {generate,_,{table,_}}],[]} = i(Q),
3512                       [{1,{1}},{1,{2}},{2,{1}},{2,{2}}] = qlc:e(Q),
3513                       [1,2] = lookup_keys(Q)
3514               end, [{keypos,1}], [{1},{2},{3}])">>,
3515
3516       <<"%% Lookup only. No cache.
3517          etsc(fun(E) ->
3518                       Q = qlc:q([{X,Y} ||
3519                                     X <- [1,2],
3520                                     {Y=2} <- ets:table(E)],
3521                                 []),
3522                       {qlc,_,[{generate,_,{list,[1,2]}},
3523                               {generate,_,{table,_}}],[]} = i(Q),
3524                       [{1,2},{2,2}] = qlc:e(Q),
3525                       [2] = lookup_keys(Q)
3526               end, [{keypos,1}], [{1},{2},{3}])">>,
3527       <<"%% Lookup only. No cache.
3528          etsc(fun(E) ->
3529                       Q = qlc:q([{X,Y} ||
3530                                     X <- [1,2],
3531                                     {Y=2} <- ets:table(E)],
3532                                 [cache]),
3533                       {qlc,_,[{generate,_,{list,[1,2]}},
3534                               {generate,_,{table,_}}],[]} = i(Q),
3535                       [{1,2},{2,2}] = qlc:e(Q),
3536                       [2] = lookup_keys(Q)
3537               end, [{keypos,1}], [{1},{2},{3}])">>,
3538       <<"%% Matchspec only. No cache.
3539          etsc(fun(E) ->
3540                       Q = qlc:q([{X,Y} ||
3541                                     X <- [1,2],
3542                                     {Y} <- ets:table(E),
3543                                     Y > 1],
3544                                 []),
3545                       {qlc,_,[{generate,_,{list,[1,2]}},
3546                               {generate,_,
3547                                {table,{ets,_,[_,[{traverse,_}]]}}}],[]} =
3548                                       i(Q),
3549                       [{1,2},{1,3},{2,2},{2,3}] = lists:sort(qlc:e(Q)),
3550                       false = lookup_keys(Q)
3551               end, [{keypos,1}], [{1},{2},{3}])">>,
3552       <<"%% Matchspec only. Cache
3553          etsc(fun(E) ->
3554                       Q = qlc:q([{X,Y} ||
3555                                     X <- [1,2],
3556                                     {Y} <- ets:table(E),
3557                                     Y > 1],
3558                                 [cache]),
3559                       {qlc,_,[{generate,_,{list,[1,2]}},
3560                            {generate,_,{qlc,_,
3561                           [{generate,_,{table,{ets,_,[_,[{traverse,_}]]}}}],
3562                          [{cache,ets}]}}],[]} = i(Q),
3563                       [{1,2},{1,3},{2,2},{2,3}] = lists:sort(qlc:e(Q)),
3564                       false = lookup_keys(Q)
3565               end, [{keypos,1}], [{1},{2},{3}])">>,
3566       <<"%% An empty list. Always unique and cached.
3567          Q = qlc:q([X || {X} <- [], X =:= 1, begin X > 0 end],
3568                   [{cache,true},{unique,true}]),
3569          {qlc,_,[{generate,_,{list,[]}},_],[{unique,true}]} = i(Q),
3570          _ = qlc:info(Q),
3571          [] = qlc:e(Q)">>,
3572       <<"%% A list is always cached.
3573          Q = qlc:q([{X,Y} || Y <- [1,2], X <- [2,1,2]],
3574                    [cache]),
3575          {qlc,_,[{generate,_,{list,[1,2]}},
3576                  {generate,_,{list,[2,1,2]}}],[]} = i(Q),
3577          [{2,1},{1,1},{2,1},{2,2},{1,2},{2,2}] = qlc:e(Q)">>,
3578       <<"%% But a processed list is never cached.
3579          Q = qlc:q([{X,Y} || Y <- [1,2], X <- [2,1,2], X > 1],
3580                    [cache]),
3581          {qlc,_,[{generate,_, {list,[1,2]}},
3582                  {generate,_,{qlc,_,
3583                               [{generate,_,{list,{list,[2,1,2]},_}}],
3584                               [{cache,ets}]}}],[]} = i(Q),
3585          [{2,1},{2,1},{2,2},{2,2}] = qlc:e(Q)">>,
3586       <<"%% A bug fixed in R11B-2: coalescing simple_qlc:s works now.
3587          Q0 = qlc:q([X || {X} <- [{1},{2},{3}]],  {cache, ets}),
3588          Q1 = qlc:q([X || X <- Q0], {cache, list}),
3589          Q = qlc:q([{Y,X} || Y <- [1,2], X <- Q1, X < 2], {cache, list}),
3590          {qlc,_,[{generate,_,{list,_}},
3591                  {generate,_,{qlc,_,[{generate,_,{list,{list,_},_}}],
3592                               [{cache,ets}]}},_],[]} = i(Q),
3593          [{1,1},{2,1}] = qlc:e(Q)">>,
3594       <<"Q = qlc:q([{X,Y} || Y <- [1,2], X <- [1,2], X > 1],
3595                    [cache,unique]),
3596          {qlc,_,[{generate,_,{list,[1,2]}},
3597                  {generate,_,{qlc,_,
3598                               [{generate,_,{list,{list,[1,2]},_}}],
3599                               [{cache,ets},{unique,true}]}}],
3600           [{unique,true}]} = i(Q),
3601          [{2,1},{2,2}] = qlc:e(Q)">>,
3602       <<"L = [1,2,3],
3603          QH1 = qlc:q([{X} || X <- L, X > 1]),
3604          QH2 = qlc:q([{X} || X <- QH1, X > 0], [cache]),
3605          [{{2}},{{3}}] = qlc:e(QH2),
3606          {list,{list,{list,L},_},_} = i(QH2)">>,
3607       <<"L = [1,2,3,1,2,3],
3608          QH1 = qlc:q([{X} || X <- L, X > 1]),
3609          QH2 = qlc:q([{X} || X <- QH1, X > 0], [cache,unique]),
3610          [{{2}},{{3}}] = qlc:e(QH2),
3611          {qlc,_,[{generate,_,{list,{list,{list,L},_},_}}],
3612           [{unique,true}]} = i(QH2)">>
3613
3614      ],
3615
3616    ok = run(Config, Ts2),
3617
3618    LTs = [
3619       <<"etsc(fun(E) ->
3620                       Q  = qlc:q([X || X <- ets:table(E),
3621                                        element(1, X) =:= 1],
3622                                  {lookup,true}),
3623                       {table,L} = i(Q),
3624                       true = is_list(L),
3625                       [{1,a}] = qlc:e(Q),
3626                       [1] = lookup_keys(Q)
3627               end, [{1,a},{2,b}])">>,
3628       <<"%% No lookup, use the match spec for traversal instead.
3629          etsc(fun(E) ->
3630                       Q  = qlc:q([X || X <- ets:table(E),
3631                                        element(1, X) =:= 1],
3632                                  {lookup,false}),
3633                       {table,{ets,table,_}} = i(Q),
3634                       [{1,a}] = qlc:e(Q),
3635                       false = lookup_keys(Q)
3636               end, [{1,a},{2,b}])">>,
3637       <<"%% As last one. {max_lookup,0} has the same effect.
3638          etsc(fun(E) ->
3639                       Q  = qlc:q([X || X <- ets:table(E),
3640                                        element(1, X) =:= 1],
3641                                  {max_lookup,0}),
3642                       {table,{ets,table,_}} = i(Q),
3643                       [{1,a}] = qlc:e(Q),
3644                       false = lookup_keys(Q)
3645               end, [{1,a},{2,b}])">>
3646
3647       ],
3648
3649    ok = run(Config, LTs),
3650
3651    ok.
3652
3653%% Lookup keys. With records.
3654lookup_rec(Config) when is_list(Config) ->
3655    Ts = [
3656       <<"etsc(fun(E) ->
3657                Q = qlc:q([A || #r{a = A} <- ets:table(E),
3658                                (A =:= 3) or (4 =:= A)]),
3659                [3] = qlc:e(Q),
3660                [3,4] = lookup_keys(Q)
3661            end, [{keypos,2}], [#r{a = a}, #r{a = 3}, #r{a = 5}])">>,
3662
3663       {cres,
3664        <<"etsc(fun(E) ->
3665                 Q = qlc:q([A || #r{a = 17 = A} <- ets:table(E),
3666                                 (A =:= 3) or (4 =:= A)]),
3667                 [] = qlc:e(Q),
3668                 false = lookup_keys(Q)
3669             end, [{keypos,2}], [#r{a = 17}, #r{a = 3}, #r{a = 5}])">>,
3670        %% {warnings,[{{4,44},qlc,nomatch_filter}]}},
3671        []},
3672
3673      <<"%% Compares an integer and a float.
3674         etsc(fun(E) ->
3675                Q = qlc:q([A || #r{a = 17 = A} <- ets:table(E),
3676                                (A == 17) or (17.0 == A)]),
3677                [_] = qlc:e(Q),
3678                [_] = lookup_keys(Q)
3679            end, [{keypos,2}], [#r{a = 17}, #r{a = 3}, #r{a = 5}])">>,
3680
3681      <<"%% Compares an integer and a float.
3682         %% There is a test in qlc_pt.erl (Op =:= '=:=', C1 =:= C2), but
3683         %% that case is handled in an earlier clause (unify ... E, E).
3684         etsc(fun(E) ->
3685                Q = qlc:q([A || #r{a = 17.0 = A} <- ets:table(E),
3686                                (A =:= 17) or (17.0 =:= A)]),
3687                [_] = qlc:e(Q),
3688                [_] = lookup_keys(Q)
3689            end, [{keypos,2}], [#r{a = 17.0}, #r{a = 3}, #r{a = 5}])">>,
3690
3691      <<"%% Matches an integer and a float.
3692         etsc(fun(E) ->
3693                Q = qlc:q([A || #r{a = 17 = A} <- ets:table(E),
3694                                (A =:= 17) or (17.0 =:= A)]),
3695                [_] = qlc:e(Q),
3696                [_] = lookup_keys(Q)
3697            end, [{keypos,2}], [#r{a = 17}, #r{a = 3}, #r{a = 5}])">>,
3698
3699      <<"etsc(fun(E) ->
3700                F = fun(_) -> 17 end,
3701                Q = qlc:q([A || #r{a = A} <- ets:table(E),
3702                                (F(A) =:= 3) and (A =:= 4)]),
3703                [] = qlc:e(Q),
3704                false = lookup_keys(Q) % F(A) could fail
3705            end, [{keypos,2}], [#r{a = 4}, #r{a = 3}, #r{a = 5}])">>,
3706
3707      <<"etsc(fun(E) ->
3708                Q = qlc:q([X || {X} <- ets:table(E),
3709                                #r{} == X]),
3710                [#r{}] = lists:sort(qlc:e(Q)),
3711                {call,_,_,[_,_]} = i(Q, {format, abstract_code}),
3712                [#r{}] = lookup_keys(Q)
3713        end, [{#r{}},{#r{a=foo}}])">>,
3714
3715      <<"etsc(fun(E) ->
3716                Q = qlc:q([R#r.a || R <- ets:table(E), R#r.a =:= foo]),
3717                [foo] = qlc:e(Q),
3718                [_] = lookup_keys(Q)
3719        end, [{keypos,2}], [#r{a=foo}])">>
3720       ],
3721    run(Config, <<"-record(r, {a}).\n">>, Ts),
3722    ok.
3723
3724%% Using indices for lookup.
3725indices(Config) when is_list(Config) ->
3726    Ts = [
3727       <<"L = [{1,a},{2,b},{3,c}],
3728          QH = qlc:q([element(1, X) || X <- qlc_SUITE:table(L, [2]),
3729                                       (element(2, X) =:= a)
3730                                           or (b =:= element(2, X))]),
3731          {list, {table,{qlc_SUITE,list_keys,[[a,b],2,L]}}, _MS} = i(QH),
3732          [1,2] = qlc:eval(QH)">>,
3733
3734       <<"L = [{1,a},{2,b},{3,c}],
3735          QH = qlc:q([element(1, X) || X <- qlc_SUITE:table(L, [2]),
3736                                       begin (element(2, X) =:= a)
3737                                           or (b =:= element(2, X)) end]),
3738          {qlc,_,[{generate,_,{table,{call,_,
3739                               {remote,_,_,{atom,_,the_list}},_}}},_],[]}
3740                  = i(QH),
3741          [1,2] = qlc:eval(QH)">>,
3742
3743       <<"L = [{1,a,q},{2,b,r},{3,c,s}],
3744          QH = qlc:q([element(1, X) || X <- qlc_SUITE:table(L, [2,3]),
3745                                       (element(3, X) =:= q)
3746                                           or (r =:= element(3, X))]),
3747          {list, {table,{qlc_SUITE,list_keys, [[q,r],3,L]}}, _MS} = i(QH),
3748          [1,2] = qlc:eval(QH)">>,
3749
3750       <<"L = [{1,a,q},{2,b,r},{3,c,s}],
3751          QH = qlc:q([element(1, X) || X <- qlc_SUITE:table(L, 1, [2]),
3752                                       (element(3, X) =:= q)
3753                                           or (r =:= element(3, X))]),
3754          {qlc,_,[{generate,_,{table,{call,_,_,_}}},
3755                  _],[]} = i(QH),
3756          [1,2] = qlc:eval(QH)">>,
3757
3758       <<"L = [{a,1},{b,2},{c,3}],
3759          QH = qlc:q([E || {K,I}=E <- qlc_SUITE:table(L, 1, [2]),
3760                           ((K =:= a) or (K =:= b) or (K =:= c))
3761                               and ((I =:= 1) or (I =:= 2))],
3762                     {max_lookup, 3}),
3763          {list, {table,{qlc_SUITE,list_keys,[[a,b,c],1,L]}}, _MS} = i(QH),
3764          [{a,1},{b,2}] = qlc:eval(QH)">>,
3765
3766       <<"L = [{a,1},{b,2},{c,3}],
3767          QH = qlc:q([E || {K,I}=E <- qlc_SUITE:table(L, 1, [2]),
3768                           ((K =:= a) or (K =:= b) or (K =:= c))
3769                               and ((I =:= 1) or (I =:= 2))],
3770                     {max_lookup, 2}),
3771          {list, {table,{qlc_SUITE,list_keys, [[1,2],2,L]}}, _MS} = i(QH),
3772          [{a,1},{b,2}] = qlc:eval(QH)">>,
3773
3774       <<"L = [{a,1,x,u},{b,2,y,v},{c,3,z,w}],
3775          QH = qlc:q([E || {K,I1,I2,I3}=E <- qlc_SUITE:table(L, 1, [2,3,4]),
3776                           ((K =/= a) or (K =/= b) or (K =/= c))
3777                             and ((I1 =:= 1) or (I1 =:= 2) or
3778                                  (I1 =:= 3) or (I1 =:= 4))
3779                             and ((I2 =:= x) or (I2 =:= z))
3780                             and ((I3 =:= v) or (I3 =:= w))],
3781                     {max_lookup, 5}),
3782          {list, {table,{qlc_SUITE,list_keys, [[x,z],3,L]}}, _MS} = i(QH),
3783          [{c,3,z,w}] = qlc:eval(QH)">>
3784
3785       ],
3786    run(Config, <<"-record(r, {a}).\n">>, Ts),
3787    ok.
3788
3789%% Test the table/2 callback functions parent_fun and stop_fun.
3790pre_fun(Config) when is_list(Config) ->
3791    Ts = [
3792       <<"PF = process_flag(trap_exit, true),
3793          %% cursor: table killing parent
3794          L = [{1,a},{2,b},{3,c}],
3795          F1 = fun() ->
3796                   QH = qlc:q([element(1, X) ||
3797                                X <- qlc_SUITE:table_kill_parent(L, [2]),
3798                                (element(2, X) =:= a)
3799                                    or (b =:= element(2, X))]),
3800                   _ = qlc:info(QH),
3801                   _ = qlc:cursor(QH)
3802               end,
3803          Pid1 = spawn_link(F1),
3804          receive {'EXIT', Pid1, killed} ->
3805              ok
3806          end,
3807          timer:sleep(1),
3808          process_flag(trap_exit, PF)">>,
3809
3810       <<"PF = process_flag(trap_exit, true),
3811          %% eval without cursor: table killing parent
3812          L = [{1,a},{2,b},{3,c}],
3813          F2 = fun() ->
3814                 QH = qlc:q([element(1, X) ||
3815                                X <- qlc_SUITE:table_kill_parent(L, [2]),
3816                                (element(2, X) =:= a)
3817                                    or (b =:= element(2, X))]),
3818                 _ = qlc:eval(QH)
3819               end,
3820          Pid2 = spawn_link(F2),
3821          receive {'EXIT', Pid2, killed} ->
3822              ok
3823          end,
3824          process_flag(trap_exit, PF)">>,
3825
3826       <<"L = [{1,a},{2,b},{3,c}],
3827          QH = qlc:q([element(1, X) ||
3828                        X <- qlc_SUITE:table_parent_throws(L, [2]),
3829                        (element(2, X) =:= a)
3830                            or (b =:= element(2, X))]),
3831          _ = qlc:info(QH),
3832          {throw,thrown} = (catch {any_term,qlc:cursor(QH)}),
3833          {throw,thrown} = (catch {any_term,qlc:eval(QH)})">>,
3834
3835       <<"L = [{1,a},{2,b},{3,c}],
3836          QH = qlc:q([element(1, X) ||
3837                        X <- qlc_SUITE:table_parent_exits(L, [2]),
3838                        (element(2, X) =:= a)
3839                            or (b =:= element(2, X))]),
3840          _ = qlc:info(QH),
3841          {'EXIT', {badarith,_}} = (catch qlc:cursor(QH)),
3842          {'EXIT', {badarith,_}} = (catch qlc:eval(QH))">>,
3843
3844       <<"L = [{1,a},{2,b},{3,c}],
3845          QH = qlc:q([element(1, X) ||
3846                        X <- qlc_SUITE:table_bad_parent_fun(L, [2]),
3847                        (element(2, X) =:= a)
3848                            or (b =:= element(2, X))]),
3849          {'EXIT', {badarg,_}} = (catch qlc:cursor(QH)),
3850          {'EXIT', {badarg,_}} = (catch qlc:eval(QH))">>,
3851
3852       <<"%% Very simple test of stop_fun.
3853          Ets = ets:new(apa, [public]),
3854          L = [{1,a},{2,b},{3,c}],
3855          H = qlc:q([X || {X,_} <- qlc_SUITE:stop_list(L, Ets)]),
3856          C = qlc:cursor(H),
3857          [{stop_fun,StopFun}] = ets:lookup(Ets, stop_fun),
3858          StopFun(),
3859          {'EXIT', {{qlc_cursor_pid_no_longer_exists, _}, _}} =
3860                  (catch qlc:next_answers(C, all_remaining)),
3861          ets:delete(Ets)">>
3862
3863       ],
3864
3865    run(Config, Ts),
3866    ok.
3867
3868%% Lookup keys. With records.
3869skip_filters(Config) when is_list(Config) ->
3870    %% Skipped filters
3871    TsS = [
3872       %% Cannot skip the filter.
3873       <<"etsc(fun(E) ->
3874                H = qlc:q([X || X <- ets:table(E),
3875                          (element(1, X) =:= 1) xor (element(1, X) =:= 1)]),
3876                [] = qlc:eval(H),
3877                [1] = lookup_keys(H)
3878               end, [{keypos,1}], [{1},{2}])">>,
3879
3880       %% The filter can be skipped. Just a lookup remains.
3881       <<"etsc(fun(E) ->
3882                H = qlc:q([X || X <- ets:table(E),
3883                          (element(1, X) =:= 1) or (element(1, X) =:= 1)]),
3884                [{1}] = qlc:eval(H),
3885                {table, _} = i(H),
3886                [1] = lookup_keys(H)
3887               end, [{keypos,1}], [{1},{2}])">>,
3888
3889       %% safe_unify fails on 3 and <<X:32>>
3890       <<"etsc(fun(E) ->
3891                H = qlc:q([X || X <- ets:table(E),
3892                     (element(1, X) =:= 1) and (3 =:= <<X:32>>)]),
3893                [] = qlc:eval(H),
3894                [1] = lookup_keys(H)
3895               end, [{keypos,1}], [{1},{2}])">>,
3896
3897       %% Two filters are skipped.
3898       <<"etsc(fun(E) ->
3899                Q = qlc:q([{B,C,D} || {A={C},B} <- ets:table(E),
3900                                      (A =:= {1}) or (A =:= {2}),
3901                                      (C =:= 1) or (C =:= 2),
3902                                      D <- [1,2]]),
3903                {qlc,_,[{generate,_,{table,_}},{generate,_,{list,[1,2]}}],[]}
3904                  = i(Q),
3905                [{1,1,1},{1,1,2},{2,2,1},{2,2,2}] = lists:sort(qlc:eval(Q)),
3906                [{1},{2}] = lookup_keys(Q)
3907         end, [{{1},1},{{2},2},{{3},3}])">>,
3908
3909       <<"etsc(fun(E) ->
3910                Q = qlc:q([{B,C} || {A={C},B} <- ets:table(E),
3911                                    (A =:= {1}) or (A =:= {2}),
3912                                    (C =:= 1) or (C =:= 2)]),
3913                {qlc,_,[{generate,_,{table,_}}],[]} = i(Q),
3914                [{1,1},{2,2}] = lists:sort(qlc:eval(Q)),
3915                [{1},{2}] = lookup_keys(Q)
3916         end, [{{1},1},{{2},2},{{3},3}])">>,
3917
3918       %% Lookup. No match spec, no filter.
3919       <<"etsc(fun(E) ->
3920                Q = qlc:q([X || X <- ets:table(E),
3921                               element(1, X) =:= 1]),
3922                {table, _} = i(Q),
3923                [{1}] = qlc:e(Q),
3924                [1] = lookup_keys(Q)
3925         end, [{1},{2}])">>,
3926
3927       <<"etsc(fun(E) ->
3928                 Q = qlc:q([{X,Y} || X <- ets:table(E),
3929                                     element(1, X) =:= 1,
3930                                     Y <- [1,2]]),
3931                 {qlc,_,[{generate,_,{table,_}},{generate,_,{list,_}}],[]}
3932                      = i(Q),
3933                 [{{1},1},{{1},2}] = lists:sort(qlc:e(Q)),
3934                 [1] = lookup_keys(Q)
3935         end, [{1},{2}])">>,
3936
3937       <<"etsc(fun(E) ->
3938                 Q = qlc:q([X || {X,Y} <- ets:table(E),
3939                                 X =:= a,
3940                                 X =:= Y]),
3941                 {list,{table,_},_} = i(Q),
3942                 [a] = qlc:e(Q),
3943                 [a] = lookup_keys(Q)
3944          end, [{a,a},{b,c},{c,a}])">>,
3945
3946       %% The imported variable (A) is never looked up in the current
3947       %% implementation. This means that the first filter cannot be skipped;
3948       %% the constant 'a' is looked up, and then the first filter evaluates
3949       %% to false.
3950       <<"etsc(fun(E) ->
3951                 A = 3,
3952                 Q = qlc:q([X || X <- ets:table(E),
3953                                 A == element(1,X),
3954                                 element(1,X) =:= a]),
3955                 [] = qlc:e(Q),
3956                 [a] = lookup_keys(Q)
3957          end, [{a},{b},{c}])">>,
3958
3959       %% No lookup.
3960       {cres,
3961        <<"etsc(fun(E) ->
3962                  Q = qlc:q([X || {X} <- ets:table(E),
3963                                  X =:= 1,
3964                                  X =:= 2]),
3965                  {table, _} = i(Q),
3966                  [] = qlc:e(Q),
3967                  false = lookup_keys(Q)
3968          end, [{1,1},{2,0}])">>,
3969        %% {warnings,[{{4,37},qlc,nomatch_filter}]}},
3970        []},
3971
3972       <<"etsc(fun(E) ->
3973                 Q = qlc:q([{A,B,C} ||
3974                               {A} <- ets:table(E),
3975                               A =:= 1,
3976                               {B} <- ets:table(E),
3977                               B =:= 2,
3978                               {C} <- ets:table(E),
3979                               C =:= 3]),
3980                 {qlc,_,[{generate,_,{list,{table,_},_}},
3981                         {generate,_,{list,{table,_},_}},
3982                         {generate,_,{list,{table,_},_}}],[]} = i(Q),
3983                 [{1,2,3}] = qlc:e(Q),
3984                 [1,2,3] = lookup_keys(Q)
3985          end, [{0},{1},{2},{3},{4}])">>
3986
3987           ],
3988    run(Config, TsS),
3989
3990    Ts = [
3991       <<"etsc(fun(E) ->
3992                 H = qlc:q([X || {X,_} <- ets:table(E),
3993                                 X =:= 2]),
3994                 {list,{table,_},_} = i(H),
3995                 [2] = qlc:e(H)
3996         end, [{1,a},{2,b}])">>,
3997
3998       <<"etsc(fun(E) ->
3999                 H = qlc:q([X || {X,_} <- ets:table(E),
4000                                 ((X =:= 2) or (X =:= 1)) and (X > 1)]),
4001                 {list,{table,_},_} = i(H),
4002                 [2] = qlc:e(H)
4003         end, [{1,a},{2,b}])">>,
4004
4005       <<"etsc(fun(E) ->
4006                 H = qlc:q([X || {X,Y} <- ets:table(E),
4007                                 (X =:= 2) and (Y =:= b)]),
4008                 {list,{table,_},_} = i(H),
4009                 [2] = qlc:e(H)
4010         end, [{1,a},{2,b}])">>,
4011
4012       <<"etsc(fun(E) ->
4013                 H = qlc:q([X || X <- ets:table(E),
4014                                 (element(1,X) =:= 2) and (X =:= {2,b})]),
4015                 {list,{table,_},_} = i(H),
4016                 [{2,b}] = qlc:e(H)
4017         end, [{1,a},{2,b}])">>,
4018
4019       <<"etsc(fun(E) ->
4020                 H = qlc:q([{X,Y,Z,W} ||
4021                               {X,Y} <- ets:table(E),
4022                               {Z,W} <- ets:table(E),
4023                               (Y =:= 3) or (Y =:= 4)]),
4024                 {qlc,_,[{generate,_,{table,{ets,table,_}}},
4025                         {generate,_,{table,{ets,table,_}}}],[]} = i(H),
4026                 [{a,3,a,3},{a,3,b,5}] = lists:sort(qlc:e(H))
4027         end, [{a,3},{b,5}])">>,
4028
4029       <<"etsc(fun(E) ->
4030                 H = qlc:q([{X,Y} ||
4031                               {X,Y=3} <- ets:table(E), % no matchspec
4032                               %% Two columns restricted, but lookup anyway
4033                               (X =:= a)]),
4034                 {qlc,_,[{generate,_,{table,_}}],[]} = i(H),
4035                 [{a,3}] = qlc:e(H)
4036         end, [{a,3},{b,4}])">>,
4037
4038       <<"etsc(fun(E) ->
4039                 V = 3,
4040                 H = qlc:q([{X,Y} ||
4041                               {X,Y} <- ets:table(E),
4042                               (Y =:= V)]), % imported variable, no lookup
4043                 {table,{ets,table,_}} = i(H),
4044                 [{a,3}] = qlc:e(H)
4045         end, [{a,3},{b,4}])">>,
4046
4047       <<"etsc(fun(E) ->
4048                 V = b,
4049                 H = qlc:q([{X,Y} ||
4050                               {X,Y} <- ets:table(E),
4051                               (X =:= V)]), % imported variable, lookup
4052                 {list,{table,_},_} = i(H),
4053                 [{b,4}] = qlc:e(H)
4054         end, [{a,3},{b,4}])">>,
4055
4056       <<"H = qlc:q([{A,B} || {{A,B}} <- [{{1,a}},{{2,b}}],
4057                              A =:= 1,
4058                              B =:= a]),
4059              {list,{list,[_,_]},_} = i(H),
4060              [{1,a}] = qlc:e(H)">>,
4061
4062       <<"etsc(fun(E) ->
4063                 H = qlc:q([{A,B} || {{A,B}} <- ets:table(E),
4064                                     A =:= 1,
4065                                     B =:= a]),
4066                 {list,{table,_},_} = i(H),
4067                 [{1,a}] = qlc:e(H)
4068         end, [{{1,a}},{{2,b}}])">>,
4069
4070       %% The filters are skipped, and the guards of the match specifications
4071       %% are skipped as well. Only the transformations of the matchspecs
4072       %% are kept.
4073       <<"etsc(fun(E1) ->
4074                 etsc(fun(E2) ->
4075                              H = qlc:q([{X,Y,Z,W} ||
4076                                             {X,_}=Z <- ets:table(E1),
4077                                             W={Y} <- ets:table(E2),
4078                                             (X =:= 1) or (X =:= 2),
4079                                             (Y =:= a) or (Y =:= b)]
4080                                         ,{lookup,true}
4081                                        ),
4082                              {qlc,_,[{generate,_,{list,{table,_},
4083                                                   [{{'$1','_'},[],['$_']}]}},
4084                                      {generate,_,{list,{table,_},
4085                                                   [{{'$1'},[],['$_']}]}}],[]}
4086                              = i(H),
4087                              [{1,a,{1,a},{a}},
4088                               {1,b,{1,a},{b}},
4089                               {2,a,{2,b},{a}},
4090                               {2,b,{2,b},{b}}] = qlc:e(H)
4091                      end, [{a},{b}])
4092         end, [{1,a},{2,b}])">>,
4093
4094       %% The same example again, but this time no match specs are run.
4095       <<"fun(Z) ->
4096              etsc(fun(E1) ->
4097                     etsc(fun(E2) ->
4098                                  H = qlc:q([{X,Y} ||
4099                                                 Z > 2,
4100                                                 X <- ets:table(E1),
4101                                                 Y <- ets:table(E2),
4102                                                 (element(1, X) =:= 1) or
4103                                                 (element(1, X) =:= 2),
4104                                                 (element(1, Y) =:= a) or
4105                                                 (element(1, Y) =:= b)]
4106                                             ,{lookup,true}
4107                                            ),
4108                                  {qlc,_,[_,{generate,_,{table,_}},
4109                                          {generate,_,{table,_}}],[]} = i(H),
4110                                  [{{1,a},{a}},
4111                                   {{1,a},{b}},
4112                                   {{2,b},{a}},
4113                                   {{2,b},{b}}] = qlc:e(H)
4114                          end, [{a},{b}])
4115             end, [{1,a},{2,b}])
4116         end(4)">>,
4117
4118       %% Once again, this time with a join.
4119       <<"etsc(fun(E1) ->
4120                 etsc(fun(E2) ->
4121                              H = qlc:q([{X,Y,Z,W} ||
4122                                             {X,V}=Z <- ets:table(E1),
4123                                             W={Y} <- ets:table(E2),
4124                                             (X =:= 1) or (X =:= 2),
4125                                             (Y =:= a) or (Y =:= b),
4126                                             Y =:= V]
4127                                         ,[{lookup,true},{join,merge}]
4128                                        ),
4129                              {qlc,_,[{generate,_,{qlc,_,
4130                                [{generate,_,{qlc,_,[{generate,_,
4131                                    {keysort,{list,{table,_},_},2,[]}},
4132                                 _C1,_C2],[]}},
4133                                  {generate,_,
4134                                      {qlc,_,[{generate, _,
4135                                         {keysort,{list,{table,_},_},1,[]}},
4136                                              _C3],
4137                                       []}},
4138                                 _],
4139                                [{join,merge}]}},_],[]} = i(H),
4140                              [{1,a,{1,a},{a}},{2,b,{2,b},{b}}] =
4141                                  lists:sort(qlc:e(H))
4142                      end, [{a},{b}])
4143         end, [{1,a},{2,b}])">>,
4144
4145       %% Filters 2 and 3 are not skipped.
4146       %% (Only one filter at a time is tried by the parse transform.)
4147       <<"etsc(fun(E) ->
4148                 H = qlc:q([X || {{A,B}=X,Y} <- ets:table(E), % no matchspec
4149                                     Y =:= 3,
4150                                     A =:= 1,
4151                                     B =:= a]),
4152
4153                 {qlc,_,[{generate,_,{table,_}},_,_,_],[]}= i(H),
4154                 [{1,a}] = qlc:e(H)
4155         end, [{{1,a},3},{{2,b},4}])">>,
4156
4157       <<"etsc(fun(E) ->
4158                 H = qlc:q([X || {X=_,_} <- ets:table(E), % no matchspec
4159                                  (X =:= 3) and (X > 3)]),
4160                 {qlc,_,[{generate,_,{table,_}},_],[]} = i(H),
4161                 [] = qlc:e(H)
4162         end, [{3,a},{4,b}])">>,
4163
4164       <<"etsc(fun(E) ->
4165                 H = qlc:q([X || {X=_,_} <- ets:table(E), % no matchspec
4166                                 (X =:= 3) or true]),
4167                 {qlc,_,[{generate,_,{table,{ets,table,_}}},_],[]} = i(H),
4168                 [3,4] = lists:sort(qlc:e(H))
4169         end, [{3,a},{4,b}])">>,
4170
4171       <<"etsc(fun(E) ->
4172                 H = qlc:q([X || {X=_,_} <- ets:table(E), % no matchspec
4173                                 (X =:= 3) or false]),
4174                 {qlc,_,[{generate,_,{table,_}}],[]} = i(H),
4175                 [3] = lists:sort(qlc:e(H))
4176         end, [{3,a},{4,b}])">>,
4177
4178       <<"etsc(fun(E) ->
4179                 H = qlc:q([X || {X=_,_} <- ets:table(E), % no matchspec
4180                                 (X =:= X) and (X =:= 3)]),
4181                 {qlc,_,[{generate,_,{table,_}}],[]} = i(H),
4182                 [3] = lists:sort(qlc:e(H))
4183         end, [{3,a},{4,b}])">>,
4184
4185       %% The order of filters matters. A guard filter cannot be used
4186       %% unless there are no non-guard filter placed before the guard
4187       %% filter that uses the guard filter's generator. There is
4188       %% more examples in join_filter().
4189       <<"etsc(fun(E) ->
4190                 %% Lookup.
4191                 Q = qlc:q([{A,B,A} ||
4192                               {A=_,B} <- ets:table(E), % no match spec
4193                               A =:= 1,
4194                               begin 1/B > 0 end]),
4195                 [{1,1,1}] = lists:sort(qlc:e(Q))
4196         end, [{1,1},{2,0}])">>,
4197       <<"etsc(fun(E) ->
4198                 %% No lookup.
4199                 Q = qlc:q([{A,B,A} ||
4200                               {A=_,B} <- ets:table(E), % no match spec
4201                               begin 1/B > 0 end,
4202                               A =:= 1]),
4203                 {'EXIT', _} = (catch qlc:e(Q))
4204         end, [{1,1},{2,0}])">>,
4205       %% The same thing, with a match specification.
4206       <<"etsc(fun(E) ->
4207                 Q = qlc:q([{A,B,A} ||
4208                               {A,B} <- ets:table(E), % match spec
4209                               A < 2,
4210                               begin 1/B > 0 end]),
4211                 [{1,1,1}] = lists:sort(qlc:e(Q))
4212         end, [{1,1},{2,0}])">>,
4213       <<"etsc(fun(E) ->
4214                 Q = qlc:q([{A,B,A} ||
4215                               {A,B} <- ets:table(E), % match spec
4216                               begin 1/B > 0 end,
4217                               A < 2]),
4218                 {'EXIT', _} = (catch qlc:e(Q))
4219         end, [{1,1},{2,0}])">>,
4220       %% More examples, this time two tables.
4221       <<"etsc(fun(E) ->
4222                 Q = qlc:q([{A,B,C,D} ||
4223                               {A,B} <- ets:table(E), % match spec
4224                               A < 2,
4225                               {C,D} <- ets:table(E),
4226                               begin 1/B > 0 end, %\"invalidates\" next filter
4227                               C =:= 1,
4228                               begin 1/D > 0 end]),
4229                 {qlc,_,[{generate,_,{table,{ets,table,_}}},
4230                         {generate,_,{table,{ets,table,_}}},
4231                         _,_,_],[]} = i(Q),
4232                 [{1,1,1,1}] = lists:sort(qlc:e(Q))
4233         end, [{1,1},{2,0}])">>,
4234       <<"etsc(fun(E) ->
4235              Q = qlc:q([{A,B,C,D} ||
4236                            {A,B} <- ets:table(E),
4237                            {C,D} <- ets:table(E),
4238                            begin 1/B > 0 end, % \"invalidates\" two filters
4239                            A < 2,
4240                            C =:= 1,
4241                            begin 1/D > 0 end]),
4242              {qlc,_,[{generate,_,{table,{ets,table,_}}},
4243                      {generate,_,{table,{ets,table,_}}},_,_,_,_],[]} = i(Q),
4244              {'EXIT', _} = (catch qlc:e(Q))
4245         end, [{1,1},{2,0}])">>,
4246      <<"%% There are objects in the ETS table, but none passes the filter.
4247         %% F() would not be run if it did not \"invalidate\" the following
4248         %% guards.
4249         etsc(fun(E) ->
4250                      F = fun() -> [foo || A <- [0], 1/A] end,
4251                      Q1 = qlc:q([X || {X} <- ets:table(E),
4252                                       F(), % \"invalidates\" next guard
4253                                       X =:= 17]),
4254                      {'EXIT', _} = (catch qlc:e(Q1))
4255              end, [{1},{2},{3}])">>,
4256       <<"%% The last example works just like this one:
4257          etsc(fun(E) ->
4258                      F = fun() -> [foo || A <- [0], 1/A] end,
4259                      Q1 = qlc:q([X || {X} <- ets:table(E),
4260                                       F(),
4261                                       begin X =:= 17 end]),
4262                      {'EXIT', _} = (catch qlc:e(Q1))
4263              end, [{1},{2},{3}])">>
4264
4265          ],
4266    run(Config, Ts),
4267
4268    ok.
4269
4270
4271%% ets:table/1,2.
4272ets(Config) when is_list(Config) ->
4273    Ts = [
4274       <<"E = ets:new(t, [ordered_set]),
4275          true = ets:insert(E, [{1},{2}]),
4276          {'EXIT', _} =
4277              (catch qlc:e(qlc:q([X || {X} <- ets:table(E, bad_option)]))),
4278          {'EXIT', _} =
4279              (catch qlc:e(qlc:q([X || {X} <- ets:table(E,{traverse,bad})]))),
4280          All = [{'$1',[],['$1']}],
4281          TravAll = {traverse,{select,All}},
4282          [_, _] = qlc:e(qlc:q([X || {X} <- ets:table(E, TravAll)])),
4283          [_, _] = qlc:e(qlc:q([X || {X} <- ets:table(E,{traverse,select})])),
4284          [1,2] =
4285             qlc:e(qlc:q([X || {X} <- ets:table(E, {traverse, first_next})])),
4286          [2,1] =
4287             qlc:e(qlc:q([X || {X} <- ets:table(E, {traverse, last_prev})])),
4288          {table,{ets,table,[_,[{traverse,{select,_}},{n_objects,1}]]}} =
4289              i(qlc:q([X || {X} <- ets:table(E, {n_objects,1})])),
4290          {qlc,_,[{generate,_,{table,{ets,table,[_,{n_objects,1}]}}},_],[]} =
4291              i(qlc:q([X || {X} <- ets:table(E,{n_objects,1}),
4292                                   begin (X >= 1) or (X < 1) end])),
4293          {qlc,_,[{generate,_,{table,{ets,table,[_]}}},_],[]} =
4294              i(qlc:q([X || {X} <- ets:table(E),
4295                                   begin (X >= 1) or (X < 1) end])),
4296          ets:delete(E)">>,
4297
4298       begin
4299       MS = ets:fun2ms(fun({X,Y}) when X > 1 -> {X,Y} end),
4300       [<<"E = ets:new(apa,[]),
4301           true = ets:insert(E, [{1,a},{2,b},{3,c}]),
4302           MS =  ">>, io_lib:format("~w", [MS]), <<",
4303           Q = qlc:q([X || {X,_} <- ets:table(E, {traverse, {select, MS}}),
4304                           X =:= 1]),
4305           R = qlc:e(Q),
4306           ets:delete(E),
4307           [] = R">>]
4308       end,
4309
4310       <<"E2 = ets:new(test, [bag]),
4311          Ref = make_ref(),
4312          true = ets:insert(E2, [{Ref,Ref}]),
4313          Q2 = qlc:q([{Val1} ||
4314                         {Ref1, Val1} <- ets:table(E2),
4315                         Ref1 =:= Ref]),
4316          S = qlc:info(Q2),
4317          true = is_list(S),
4318          [{Ref}] = qlc:e(Q2),
4319          ets:delete(E2)">>
4320
4321       ],
4322
4323    run(Config, Ts),
4324    ok.
4325
4326%% dets:table/1,2.
4327dets(Config) when is_list(Config) ->
4328    dets:start(),
4329    T = t,
4330    Fname = filename(T, Config),
4331    Ts = [
4332       [<<"T = t, Fname = \"">>, Fname, <<"\",
4333           file:delete(Fname),
4334           {ok, _} = dets:open_file(T, [{file,Fname}]),
4335           ok = dets:insert(T, [{1},{2}]),
4336           {'EXIT', _} =
4337              (catch qlc:e(qlc:q([X || {X} <- dets:table(T, bad_option)]))),
4338           {'EXIT', _} =
4339              (catch qlc:e(qlc:q([X || {X} <- dets:table(T,{traverse,bad})]))),
4340           {'EXIT', _} =
4341              (catch
4342               qlc:e(qlc:q([X || {X} <- dets:table(T,{traverse,last_prev})]))),
4343           All = [{'$1',[],['$1']}],
4344           TravAll = {traverse,{select,All}},
4345           [_,_] = qlc:e(qlc:q([X || {X} <- dets:table(T, TravAll)])),
4346           [_,_] = qlc:e(qlc:q([X || {X} <- dets:table(T,{traverse,select})])),
4347           [_,_] =
4348             qlc:e(qlc:q([X || {X} <- dets:table(T, {traverse, first_next})])),
4349           {table,{dets,table,[T,[{traverse,{select,_}},{n_objects,1}]]}} =
4350               i(qlc:q([X || {X} <- dets:table(T, {n_objects,1})])),
4351           {qlc,_,[{generate,_,{table,{dets,table,[t,{n_objects,1}]}}},_],[]}=
4352               i(qlc:q([X || {X} <- dets:table(T,{n_objects,1}),
4353                             begin (X >= 1) or (X < 1) end])),
4354           {qlc,_,[{generate,_,{table,{dets,table,[_]}}},_],[]} =
4355               i(qlc:q([X || {X} <- dets:table(T),
4356                             begin (X >= 1) or (X < 1) end])),
4357           H = qlc:q([X || {X} <- dets:table(T, {n_objects, default}),
4358                           begin (X =:= 1) or (X =:= 2) or (X =:= 3) end]),
4359           [1,2] = lists:sort(qlc:e(H)),
4360           {qlc,_,[{generate,_,{table,_}},_],[]} = i(H),
4361
4362           H2 = qlc:q([X || {X} <- dets:table(T), (X =:= 1) or (X =:= 2)]),
4363           [1,2] = lists:sort(qlc:e(H2)),
4364           {list,{table,_},_} = i(H2),
4365           true = binary_to_list(<<
4366            \"ets:match_spec_run(lists:flatmap(fun(V)->dets:lookup(t,V)end,\"
4367            \"[1,2]),ets:match_spec_compile([{{'$1'},[],['$1']}]))\">>)
4368                   == format_info(H2, true),
4369
4370           H3 = qlc:q([X || {X} <- dets:table(T), (X =:= 1)]),
4371           [1] = qlc:e(H3),
4372           {list,{table,_},_} = i(H3),
4373
4374           ok = dets:close(T),
4375           file:delete(\"">>, Fname, <<"\"),
4376           ok">>],
4377
4378       begin
4379       MS = ets:fun2ms(fun({X,Y}) when X > 1 -> {X,Y} end),
4380       [<<"T = t, Fname = \"">>, Fname, <<"\",
4381           {ok, _} = dets:open_file(T, [{file,Fname}]),
4382           MS =  ">>, io_lib:format("~w", [MS]), <<",
4383           ok = dets:insert(T, [{1,a},{2,b},{3,c}]),
4384           Q = qlc:q([X || {X,_} <- dets:table(T, {traverse, {select, MS}}),
4385                           X =:= 1]),
4386           R = qlc:e(Q),
4387           ok = dets:close(T),
4388           file:delete(\"">>, Fname, <<"\"),
4389           [] = R">>]
4390       end,
4391
4392       [<<"T = t, Fname = \"">>, Fname, <<"\",
4393           {ok, _} = dets:open_file(T, [{file,Fname}]),
4394           Objs = [{X} || X <- lists:seq(1,10)],
4395           ok = dets:insert(T, Objs),
4396           {ok, Where} = dets:where(T, {2}),
4397           ok = dets:close(T),
4398           qlc_SUITE:crash(Fname, Where),
4399
4400           {ok, _} = dets:open_file(T, [{file,Fname}]),
4401           HT = qlc:q([X || {X} <- dets:table(T, {traverse, first_next})]),
4402           {'EXIT',{error,{{bad_object,_},_}}} = (catch qlc:e(HT)),
4403           _ = dets:close(T),
4404
4405           {ok, _} = dets:open_file(T, [{file,Fname}]),
4406           HMS = qlc:q([X || {X} <- dets:table(T, {traverse, select})]),
4407           {error,{{bad_object,_},_}} = qlc:e(HMS),
4408           _ = dets:close(T),
4409
4410           {ok, _} = dets:open_file(T, [{file,Fname}]),
4411           HLU = qlc:q([X || {X} <- dets:table(T), X =:= 2]),
4412           {error,{{bad_object,_},_}} = qlc:e(HLU),
4413           _ = dets:close(T),
4414
4415           file:delete(Fname)">>]
4416
4417       ],
4418
4419    run(Config, Ts),
4420    _ = file:delete(Fname),
4421    ok.
4422
4423
4424%% The 'join' option (any, lookup, merge, nested_loop). Also cache/unique.
4425join_option(Config) when is_list(Config) ->
4426    Ts = [
4427       <<"Q1 = qlc:q([X || X <- [1,2,3]],{join,merge}),
4428          {'EXIT', {no_join_to_carry_out,_}} = (catch {foo, qlc:info(Q1)}),
4429          {'EXIT', {no_join_to_carry_out,_}} = (catch {foo, qlc:e(Q1)}),
4430
4431          Q2 = qlc:q([X || X <- [1,2,3], X > 1],{join,merge}),
4432          {'EXIT', {no_join_to_carry_out,_}} = (catch {foo, qlc:info(Q2)}),
4433          {'EXIT', {no_join_to_carry_out,_}} = (catch {foo, qlc:e(Q2)}),
4434
4435          Q3 = qlc:q([{X,Y} ||
4436                         {X} <- [{1},{2},{3}],
4437                         {Y} <- [{a},{b},{c}],
4438                         X =:= Y],
4439                     {join, merge}),
4440
4441          {1,0,0,2} = join_info(Q3),
4442          [] = qlc:e(Q3),
4443
4444          Q4 = qlc:q([{X,Y} ||
4445                         {X} <- [{1},{2},{3}],
4446                         {Y} <- [{a},{b},{c}],
4447                         X > Y],
4448                     {join, lookup}),
4449          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:info(Q4)}),
4450          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:e(Q4)}),
4451
4452          Q5 = qlc:q([{X,Y} ||
4453                         {X} <- [{1},{2},{3}],
4454                         {Y} <- [{3},{4},{5}],
4455                         X == Y],
4456                     {join, merge}),
4457          [{3,3}] = qlc:e(Q5),
4458
4459          Q6 = qlc:q([{X,Y} ||
4460                         {X} <- [{1},{2},{3}],
4461                         {Y} <- [{3},{4},{5}],
4462                         X == Y],
4463                     {join, lookup}),
4464          {'EXIT', {cannot_carry_out_join, _}} = (catch {foo, qlc:info(Q6)}),
4465          {'EXIT', {cannot_carry_out_join, _}} = (catch {foo, qlc:e(Q6)}),
4466
4467          Q7 = qlc:q([{X,Y} ||
4468                         {X} <- [{1},{2},{3}],
4469                         {Y} <- [{3},{4},{5}],
4470                         X == Y],
4471                     {join, nested_loop}),
4472          {0,0,1,0} = join_info(Q7),
4473          [{3,3}] = qlc:e(Q7),
4474
4475          Q8 = qlc:q([{X,Y} ||
4476                         {X} <- [{1},{2},{3}],
4477                         {Y} <- [{3},{4},{5}],
4478                         X =:= Y],
4479                     {join, nested_loop}),
4480          {0,0,1,0} = join_info(Q8),
4481          [{3,3}] = qlc:e(Q8),
4482
4483          %% Only guards are inspected...
4484          Q9 = qlc:q([{X,Y} ||
4485                         {X} <- [{1},{2},{3}],
4486                         {Y} <- [{3},{4},{5}],
4487                         begin X =:= Y end],
4488                     {join, nested_loop}),
4489          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:info(Q9)}),
4490          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:e(Q9)}),
4491
4492          Q10 = qlc:q([{X,Y} ||
4493                         {X} <- [{1},{2},{3}],
4494                         {Y} <- [{3},{4},{5}],
4495                         X < Y],
4496                     {join, nested_loop}),
4497          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:info(Q10)}),
4498          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:e(Q10)}),
4499
4500          F = fun(J) -> qlc:q([X || X <- [1,2]], {join,J}) end,
4501          {'EXIT', {no_join_to_carry_out, _}} =
4502                (catch {foo, qlc:e(F(merge))}),
4503          {'EXIT', {no_join_to_carry_out, _}} =
4504                (catch {foo, qlc:e(F(lookup))}),
4505          {'EXIT', {no_join_to_carry_out, _}} =
4506                (catch {foo, qlc:e(F(nested_loop))}),
4507          [1,2] = qlc:e(F(any)),
4508
4509          %% No join of columns in the same table.
4510          Q11 = qlc:q([{X,Y} || {a = X, X = Y} <- [{a,1},{a,a},{a,3},{a,a}]],
4511                      {join,merge}),
4512          {'EXIT', {no_join_to_carry_out, _}} = (catch qlc:e(Q11)),
4513          Q12 = qlc:q([{X,Y} || {X = a, X = Y} <- [{a,1},{a,a},{a,3},{a,a}]],
4514                      {join,merge}),
4515          {'EXIT', {no_join_to_carry_out, _}} = (catch qlc:e(Q12)),
4516          %% X and Y are \"equal\" (same constants), but must not be joined.
4517          Q13 = qlc:q([{X,Y} || {X,_Z} <- [{a,1},{a,2},{b,1},{b,2}],
4518                                {Y} <- [{a}],
4519                                (X =:= a) and (Y =:= b) or
4520                                (X =:= b) and (Y =:= a)],
4521                     {join,merge}),
4522          {'EXIT', {no_join_to_carry_out, _}} = (catch qlc:e(Q13))
4523
4524">>,
4525
4526       <<"Q1 = qlc:q([X || X <- [1,2,3]], {lookup,true}),
4527          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:info(Q1)}),
4528          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:e(Q1)}),
4529          Q2 = qlc:q([{X,Y} || X <- [1,2,3], Y <- [x,y,z]], lookup),
4530          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:info(Q2)}),
4531          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:e(Q2)}),
4532          Q3 = qlc:q([X || {X} <- [{1},{2},{3}]], {lookup,true}),
4533          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:e(Q3)}),
4534          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:info(Q3)}),
4535
4536          E1 = create_ets(1, 10),
4537          Q4 = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), X =:= 3], lookup),
4538          {match_spec, _} = strip_qlc_call(Q4),
4539          [{3,3}] = qlc:e(Q4),
4540          Q5 = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), X =:= 3], {lookup,false}),
4541          {table, ets, _} = strip_qlc_call(Q5),
4542          [{3,3}] = qlc:e(Q5),
4543          Q6 = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), X =:= 3], {lookup,any}),
4544          {match_spec, _} = strip_qlc_call(Q6),
4545          [{3,3}] = qlc:e(Q6),
4546          ets:delete(E1)">>
4547
4548       ],
4549    run(Config, Ts),
4550
4551    %% The 'cache' and 'unique' options of qlc/2 affects join.
4552    CUTs = [
4553       <<"L1 = [1,2],
4554          L2 = [{1,a},{2,b}],
4555          L3 = [{a,1},{b,2}],
4556          Q = qlc:q([{X,Y,Z} ||
4557                        Z <- L1,
4558                        {X,_} <- L2,
4559                        {_,Y} <- L3,
4560                        X =:= Y],
4561                    [cache, unique]),
4562          {qlc,_,
4563              [{generate,_,{list,L1}},
4564               {generate,_,{qlc,_,[{generate,_,
4565                      {qlc,_,[{generate,_,{keysort,{list,L2},1,[]}}],[]}},
4566                                {generate,_,{qlc,_,
4567                              [{generate,_,{keysort,{list,L3},2,[]}}],[]}},_],
4568                            [{join,merge},{cache,ets},{unique,true}]}},_],
4569              [{unique,true}]} = i(Q),
4570          [{1,1,1},{2,2,1},{1,1,2},{2,2,2}] = qlc:e(Q)">>,
4571       <<"L1 = [1,2],
4572          L2 = [{1,a},{2,b}],
4573          L3 = [{a,1},{b,2}],
4574          Q = qlc:q([{X,Y,Z} ||
4575                        Z <- L1,
4576                        {X,_} <- L2,
4577                        {_,Y} <- L3,
4578                        X =:= Y],
4579                    []),
4580          Options = [{cache_all,ets}, unique_all],
4581          {qlc,_,[{generate,_,{qlc,_,[{generate,_,{list,L1}}],
4582                               [{unique,true}]}},
4583                  {generate,_,{qlc,_,
4584                              [{generate,_,{qlc,_,[{generate,_,
4585                                 {keysort,{qlc,_,[{generate,_,{list,L2}}],
4586                                           [{cache,ets},{unique,true}]},
4587                                          1,[]}}],[]}},
4588                               {generate,_,{qlc,_,
4589                                    [{generate,_,{keysort,
4590                                      {qlc,_,[{generate,_,{list,L3}}],
4591                                       [{cache,ets},{unique,true}]},
4592                                                  2,[]}}],[]}},_],
4593                              [{join,merge},{cache,ets},{unique,true}]}},
4594                  _],[{unique,true}]} = i(Q, Options),
4595          [{1,1,1},{2,2,1},{1,1,2},{2,2,2}] = qlc:e(Q, Options)">>
4596       ],
4597    run(Config, CUTs),
4598
4599    ok.
4600
4601%% Various aspects of filters and join.
4602join_filter(Config) when is_list(Config) ->
4603    Ts = [
4604      <<"E1 = create_ets(1, 10),
4605          Q = qlc:q([X || {X,_} <- ets:table(E1),
4606                          begin A = X * X end, % ej true (?)
4607                          X >= A]),
4608          {'EXIT', _} = (catch qlc:e(Q)),
4609          ets:delete(E1)">>,
4610
4611      %% The order of filters matters. See also skip_filters().
4612      <<"Q = qlc:q([{X,Y} || {X,Y} <- [{a,1},{b,2}],
4613         {Z,W} <- [{a,1},{c,0}],
4614         X =:= Z,
4615         begin Y/W > 0 end]),
4616         [{a,1}] = qlc:e(Q)">>,
4617      <<"Q = qlc:q([{X,Y} || {X,Y} <- [{a,1},{b,2}],
4618         {Z,W} <- [{a,1},{c,0}],
4619         begin Y/W > 0 end,
4620         X =:= Z]),
4621         {'EXIT', _} = (catch qlc:e(Q))">>,
4622
4623      <<"etsc(fun(E1) ->
4624                   etsc(fun(E2) ->
4625                             F = fun() -> [foo || A <- [0], 1/A] end,
4626                             Q1 = qlc:q([X || {X} <- ets:table(E1),
4627                                              {Y} <- ets:table(E2),
4628                                              F(), % invalidates next filter
4629                                              X =:= Y]),
4630                              {qlc,_,[{generate,_,{table,{ets,table,_}}},
4631                                      {generate,_,{table,{ets,table,_}}},_,_],
4632                              []} = i(Q1),
4633                             {'EXIT', _} = (catch qlc:e(Q1))
4634                        end, [{1},{2},{3}])
4635              end, [{a},{b},{c}])">>
4636
4637    ],
4638    run(Config, Ts),
4639    ok.
4640
4641%% Lookup join.
4642join_lookup(Config) when is_list(Config) ->
4643    Ts = [
4644       <<"E1 = create_ets(1, 10),
4645          E2 = create_ets(5, 15),
4646          Q = qlc:q([{X,Y} || {_,Y} <- ets:table(E2),
4647                              {X,_} <- ets:table(E1),
4648                              X =:= Y], [{join,lookup}]),
4649          {0,1,0,0} = join_info_count(Q),
4650          R = qlc:e(Q),
4651          ets:delete(E1),
4652          ets:delete(E2),
4653          [{5,5},{6,6},{7,7},{8,8},{9,9},{10,10}] = lists:sort(R)">>,
4654
4655       <<"E1 = create_ets(1, 10),
4656          E2 = create_ets(5, 15),
4657          F = fun(J) -> qlc:q([{X,Y} || {X,_} <- ets:table(E1),
4658                                        {_,Y} <- ets:table(E2),
4659                                        X =:= Y], {join, J})
4660              end,
4661          Q = F(lookup),
4662          {0,1,0,0} = join_info_count(Q),
4663          R = qlc:e(Q),
4664          ets:delete(E1),
4665          ets:delete(E2),
4666          [{5,5},{6,6},{7,7},{8,8},{9,9},{10,10}] = lists:sort(R)">>,
4667
4668       <<"etsc(fun(E1) ->
4669                  E2 = qlc_SUITE:table([{1,a},{a},{1,b},{b}], 2, []),
4670                  Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), % (1)
4671                                      {_,Z} <- E2,   % (2)
4672                                      (Z =:= Y) and (X =:= a)
4673                                      or
4674                                      (Z =:= Y) and (X =:= b)]),
4675                  %% Cannot look up in (1) (X is keypos). Can look up (2).
4676                  %% Lookup-join: traverse (1), look up in (2).
4677                  {0,1,0,0} = join_info_count(Q),
4678                  [{a,a},{b,a}] = qlc:e(Q)
4679               end, [{a,a},{b,a},{c,3},{d,4}])">>,
4680
4681       <<"%% The pattern {X,_} is used to filter out looked up objects.
4682          etsc(fun(E) ->
4683                       Q = qlc:q([X || {X,_} <- ets:table(E),
4684                                       Y <- [{a,b},{c,d},{1,2},{3,4}],
4685                                       X =:= element(1, Y)]),
4686                       {0,1,0,0} = join_info_count(Q),
4687                       [1] = qlc:e(Q)
4688               end, [{1,2},{3}])">>,
4689
4690       <<"E = ets:new(e, [bag,{keypos,2}]),
4691          L = lists:sort([{a,1},{b,1},{c,1},{d,1},
4692                          {aa,2},{bb,2},{cc,2},{dd,2}]),
4693          true = ets:insert(E, L ++ [{aaa,1,1},{bbb,2,2},{ccc,3,3}]),
4694          Q = qlc:q([Z || {_,Y}=Z <- ets:table(E),
4695                          {X} <- [{X} || X <- lists:seq(0, 10)],
4696                          X =:= Y]),
4697          {0,1,0,0} = join_info_count(Q),
4698          R = qlc:e(Q),
4699          ets:delete(E),
4700          L = lists:sort(R)">>,
4701
4702       <<"E = ets:new(e, [bag,{keypos,2}]),
4703          L = lists:sort([{a,1},{b,1},{c,1},{d,1},
4704                          {aa,2},{bb,2},{cc,2},{dd,2}]),
4705          true = ets:insert(E, L ++ [{aaa,1,1},{bbb,2,2},{ccc,3,3}]),
4706          Q = qlc:q([Z || {X} <- [{X} || X <- lists:seq(0, 10)],
4707                          {_,Y}=Z <- ets:table(E),
4708                          X =:= Y]),
4709          {0,1,0,0} = join_info_count(Q),
4710          R = qlc:e(Q),
4711          ets:delete(E),
4712          L = lists:sort(R)">>,
4713
4714       <<"Q = qlc:q([{XX,YY} ||
4715                            {XX,X} <- [{b,1},{c,3}],
4716                            {Y,YY} <- qlc_SUITE:table_lookup_error([{1,a}]),
4717                            X =:= Y],
4718                        {join,lookup}),
4719          {error, lookup, failed} = qlc:e(Q)">>,
4720
4721       <<"E = create_ets(1, 10),
4722          Q = qlc:q([{X,Y} ||
4723                        {X,_} <- ets:table(E),
4724                        {_,Y} <- qlc_SUITE:table_error([{a,1}], 1, err),
4725                        X =:= Y]),
4726          {0,1,0,0} = join_info_count(Q),
4727          err = qlc:e(Q),
4728          ets:delete(E)">>
4729
4730          ],
4731    run(Config, Ts),
4732    ok.
4733
4734%% Merge join.
4735join_merge(Config) when is_list(Config) ->
4736    Ts = [
4737       <<"Q = qlc:q([{X,Y} || {X} <- [], {Y} <- [{1}], X =:= Y],
4738                    {join,merge}),
4739          [] = qlc:e(Q)
4740       ">>,
4741
4742       <<"Q = qlc:q([{X,Y} || {X} <- [{1}], {Y} <- [], X =:= Y],
4743                    {join,merge}),
4744          [] = qlc:e(Q)
4745       ">>,
4746
4747       <<"Q = qlc:q([{X,Y} || {X} <- [{1},{1},{1}],
4748                              {Y} <- [{1},{1},{1}], X =:= Y],
4749                    {join,merge}),
4750          9 = length(qlc:e(Q))
4751       ">>,
4752
4753       <<"%% Two merge joins possible.
4754          Q = qlc:q([{X,Y,Z,W} || {X,Y} <- [{1,a},{1,b},{1,c}],
4755                                  {Z,W} <- [{1,a},{1,b},{1,c}],
4756                                  X =:= Z,
4757                                  Y =:= W]),
4758          {qlc,_,[{generate,_,
4759                   {qlc,_,
4760                    [{generate,_,
4761                      {qlc,_,[{generate,_,{keysort,{list,_},C,[]}}],[]}},
4762                     {generate,_,
4763                      {qlc,_,[{generate,_,{keysort,{list,_},C,[]}}],[]}},
4764                     _],
4765                    [{join,merge}]}},
4766                  _,_],[]} = qlc:info(Q, {format,debug}),
4767          [{1,a,1,a},{1,b,1,b},{1,c,1,c}] = qlc:e(Q)">>,
4768
4769       <<"%% As the last one, but comparison.
4770          Q = qlc:q([{X,Y,Z,W} || {X,Y} <- [{1,a},{1,b},{1,c}],
4771                                  {Z,W} <- [{1,a},{1,b},{1,c}],
4772                                  X == Z, % skipped
4773                                  Y =:= W]),
4774          {qlc,_,[{generate,_,
4775                   {qlc,_,
4776                    [{generate,_,
4777                      {qlc,_,[{generate,_,{keysort,{list,_},1,[]}}],[]}},
4778                     {generate,_,
4779                      {qlc,_,[{generate,_,{keysort,{list,_},1,[]}}],[]}},
4780                     _],
4781                    [{join,merge}]}},
4782                  _],[]} = qlc:info(Q, {format,debug}),
4783          [{1,a,1,a},{1,b,1,b},{1,c,1,c}] = qlc:e(Q)">>,
4784
4785       <<"%% This is no join.
4786          Q = qlc:q([{X,Y,Z,W} || {X,Y} <- [], {Z,W} <- [],
4787                                  X =:= Y, Z =:= W]),
4788          {0,0,0,0} = join_info_count(Q)">>,
4789
4790       <<"%% Used to replace empty ETS tables with [], but that won't work.
4791          E1 = ets:new(e1, []),
4792          E2 = ets:new(e2, []),
4793          Q = qlc:q([{X,Z,W} ||
4794                        {X, Z} <- ets:table(E1),
4795                        {W, Y} <- ets:table(E2),
4796                        X =:= Y],
4797                    {join, lookup}),
4798          [] = qlc:e(Q),
4799          ets:delete(E1),
4800          ets:delete(E2)">>,
4801
4802       <<"Q = qlc:q([{X,Y} || {X} <- [{3},{1},{0}],
4803                              {Y} <- [{1},{2},{3}],
4804                              X =:= Y]),
4805          {1,0,0,2} = join_info_count(Q),
4806          [{1,1},{3,3}] = qlc:e(Q)">>,
4807
4808       <<"QH = qlc:q([{X,Y,Z,W} || {X,Y} <- [{3,c},{2,b},{1,a}],
4809                                   {Z,W} <- [{2,b},{4,d},{5,e},{3,c}],
4810                                   X =:= Z,
4811                                   Y =:= W]),
4812          {1,0,0,2} = join_info_count(QH),
4813          [{2,b,2,b},{3,c,3,c}] = qlc:e(QH)">>,
4814
4815       <<"%% QLC finds no join column at run time...
4816          QH = qlc:q([1 || X <- [{1,2,3},{4,5,6}],
4817                           Y <- [{1,2},{3,4}],
4818                           X =:= Y]),
4819          {0,0,0,0} = join_info_count(QH),
4820          [] = qlc:e(QH)">>,
4821
4822       <<"QH = qlc:q([X || X <- [{1,2,3},{4,5,6}],
4823                           Y <- [{1,2},{3,4}],
4824                           element(1, X) =:= element(2, Y)]),
4825          {1,0,0,2} = join_info_count(QH),
4826          [{4,5,6}] = qlc:e(QH)">>,
4827
4828       <<"Q = qlc:q([{A,X,Z,W} ||
4829                        A <- [a,b,c],
4830                        {X,Z} <- [{a,1},{b,4},{c,6}],
4831                        {W,Y} <- [{2,a},{3,b},{4,c}],
4832                        X =:= Y],
4833                   {cache, list}),
4834          _ = qlc:info(Q),
4835         [{a,a,1,2},{a,b,4,3},{a,c,6,4},{b,a,1,2},{b,b,4,3},
4836          {b,c,6,4},{c,a,1,2},{c,b,4,3},{c,c,6,4}] = qlc:e(Q)">>,
4837
4838       <<"Q = qlc:q([{X,Y} ||
4839                        {X,Z} <- [{a,1},{b,4},{c,6}],
4840                        {W,Y} <- [{2,a},{3,b},{4,c}],
4841                        Z > W,
4842                        X =:= Y],
4843                    {join,merge}),
4844          {qlc,_,[{generate,_,{qlc,_,
4845                              [{generate,_,
4846                                {qlc,_,[{generate,_,{keysort,_,1,[]}}],[]}},
4847                               {generate,_,
4848                                {qlc,_,[{generate,_,{keysort,_,2,[]}}],
4849                                 []}},_],[{join,merge}]}},
4850                  _,_],[]} = i(Q),
4851          [{b,b},{c,c}] = qlc:e(Q)">>,
4852
4853       <<"E1 = create_ets(1, 10),
4854          E2 = create_ets(5, 15),
4855          %% A match spec.; Q does not see Q1 and Q2 as lookup-tables.
4856          Q1 = qlc:q([X || X <- ets:table(E1)]),
4857          Q2 = qlc:q([X || X <- ets:table(E2)]),
4858          F = fun(J) -> qlc:q([{X,Y} || X <- Q1,
4859                                        Y <- Q2,
4860                                        element(1,X) =:= element(1,Y)],
4861                              [{join,J}])
4862              end,
4863          {'EXIT',{cannot_carry_out_join,_}} = (catch qlc:e(F(lookup))),
4864          Q = F(merge),
4865          {1,0,0,2} = join_info(Q),
4866          R = lists:sort(qlc:e(Q)),
4867          ets:delete(E1),
4868          ets:delete(E2),
4869          true = [{Y,Y} || X <- lists:seq(5, 10), {} =/= (Y = {X,X})] =:= R
4870       ">>,
4871
4872       <<"E1 = create_ets(1, 10),
4873          E2 = create_ets(5, 15),
4874          Q = qlc:q([{X,Y} || X <- ets:table(E1),
4875                              Y <- ets:table(E2),
4876                              element(1,X) =:= element(1,Y)],
4877                    [{join,merge}]),
4878          {1,0,0,2} = join_info(Q),
4879          R = lists:sort(qlc:e(Q)),
4880          ets:delete(E1),
4881          ets:delete(E2),
4882          true = [{Y,Y} || X <- lists:seq(5, 10), {} =/= (Y = {X,X})] =:= R
4883       ">>,
4884
4885       <<"E1 = create_ets(1, 10),
4886          E2 = create_ets(5, 15),
4887          Q1 = qlc:q([Y || X <- ets:table(E1), begin Y = {X}, true end]),
4888          %% A match spec.; Q does not see Q2 as a lookup-table.
4889          %%
4890          %% OTP-6673: lookup join is considered but since there is no
4891          %% filter that can do the job of Q2, lookup join is not an option..
4892          Q2 = qlc:q([{X} || X <- ets:table(E2)]),
4893          F = fun(J) ->
4894                      qlc:q([{X,Y} || X <- Q1,
4895                                      Y <- Q2,
4896                                      element(1,X) =:= element(1,Y)],
4897                            [{join,J}])
4898              end,
4899          {'EXIT',{cannot_carry_out_join,_}} = (catch qlc:e(F(lookup))),
4900          Q = F(any),
4901          {1,0,0,2} = join_info(Q),
4902          R = lists:sort(qlc:e(Q)),
4903          ets:delete(E1),
4904          ets:delete(E2),
4905          true = [{Y,Y} || X <- lists:seq(5, 10), {} =/= (Y = {{X,X}})] =:= R
4906       ">>,
4907
4908       <<"L1 = [{1,a},{2,a},{1,b},{2,b},{1,c},{2,c}],
4909          L2 = [{b,Y} || Y <- lists:seq(1, 10000)],
4910          F = fun(J) ->
4911                      Q = qlc:q([{XX,YY} ||
4912                                    {X,XX} <- L1,
4913                                    {YY,Y} <- L2,
4914                                    X == Y],
4915                                {join,J}),
4916                      qlc:q([{XX1,YY1,XX2,YY2} ||
4917                                {XX1,YY1} <- Q,
4918                                {XX2,YY2} <- Q])
4919              end,
4920          Qm = F(merge),
4921          Qn = F(nested_loop),
4922          true = lists:sort(qlc:e(Qm)) =:= lists:sort(qlc:e(Qn))">>,
4923
4924       <<"L1 = [{{1,a},2},{{3,c},4}],
4925          L2 = [{a,{1,a}},{c,{4,d}}],
4926          Q = qlc:q([{X,Y} || {X,_} <- L1,
4927                              {_,{Y,Z}} <- L2,
4928                              X == {Y,Z}
4929                           ]),
4930          {qlc,_,[{generate,_,{qlc,_,
4931                   [{generate,_,
4932                     {qlc,_,[{generate,_,{keysort,{list,L1},1,[]}}],[]}},
4933                    {generate,_,
4934                     {qlc,_,[{generate,_,{keysort,{list,L2},2,[]}}],[]}},
4935                    _],
4936                   [{join,merge}]}}],[]}  = i(Q),
4937          [{{1,a},1}] = qlc:e(Q)">>,
4938
4939       <<"etsc(fun(E1) ->
4940                   etsc(fun(E2) ->
4941                      Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), % (1)
4942                                          {Z} <- ets:table(E2),   % (2)
4943                                            (Z =:= X) and
4944                                            (Y =:= a) and
4945                                            (X =:= Y) or
4946                                          (Y =:= b) and
4947                                          (Z =:= Y)]),
4948                      %% Cannot look up in (1) (X is keypos). Can look up (2).
4949                      %% Lookup join not possible (cannot look up in (1)).
4950                      %% Merge join is possible (after lookup in (2)).
4951                      {1,0,0,2} = join_info_count(Q),
4952                      {qlc,_,
4953                       [{generate,_,
4954                         {qlc,_,[{generate,_,
4955                                  {qlc,_,[{generate,_,
4956                                           {keysort,
4957                                            {table,{ets,table,_}},
4958                                                  2,[]}},_C1],[]}},
4959                                 {generate,_,
4960                                  {qlc,_,[{generate,_,
4961                                           {keysort,{table,_},1,[]}},_C2],
4962                                   []}},
4963                                 _],[{join,merge}]}},_],[]} = i(Q),
4964                      [{a,a}] = qlc:e(Q)
4965                   end, [{a}])
4966                end, [{a,1},{a,a},{b,1},{b,2}])">>,
4967
4968       <<"Q = qlc:q([{G1,G2} ||
4969                        G1<- [{1}],
4970                        G2 <- [{1}],
4971                        element(1, G1) =:= element(1, G2)]),
4972          {1,0,0,2} = join_info(Q),
4973          [{{1},{1}}] = qlc:e(Q)">>,
4974
4975       <<"Q = qlc:q([{X,Y} ||
4976                         X <- [{1}],
4977                         Y <- [{1}],
4978                         element(1, X) =:= element(1, Y)],
4979                     {join,merge}),
4980          {1,0,0,2} = join_info(Q),
4981          [{{1},{1}}] = qlc:e(Q)">>,
4982
4983       <<"%% Generator after the join-filter.
4984          Q = qlc:q([Z ||
4985                        {X} <- [{1},{2},{3}],
4986                        {Y} <- [{2},{3},{4}],
4987                        X =:= Y,
4988                        Z <- [1,2]]),
4989          {qlc,_,
4990           [{generate,_,{qlc,_,
4991                [{generate,_,{qlc,_,
4992                    [{generate,_,{keysort,{list,[{1},{2},{3}]},1,[]}}],[]}},
4993                {generate,_,{qlc,_,
4994                    [{generate,_,{keysort,{list,_},1,[]}}],[]}},_],
4995                [{join,merge}]}}, _,{generate,_,{list,_}}],[]} = i(Q),
4996          [1,2,1,2] = qlc:e(Q)">>,
4997
4998       <<"%% X and W occur twice in the pattern of the extra join handle.
4999          Q = qlc:q([{Z,W} ||
5000                        {X,Z,X} <- [{1,2,1},{1,2,2}],
5001                        {W,Y,W} <- [{a,1,a}],
5002                        X =:= Y]),
5003          [{2,a}] = qlc:e(Q)">>
5004
5005          ],
5006    run(Config, Ts),
5007
5008    %% Small examples. Returning an error term.
5009    ETs = [
5010       <<"F = fun(M) ->
5011                  qlc:q([{XX,YY} ||
5012                         {XX,X} <- [{a,1},{b,2},{bb,2},{c,3},{cc,3}],
5013                         {Y,YY} <- [{0,a},{1,a},{1,aa},{2,b},{2,bb},{2,bbb},
5014                                    {3,c},{3,cc}],
5015                          X =:= Y],
5016                        {join,M})
5017              end,
5018          R = qlc:e(F(nested_loop)),
5019          R = qlc:e(F(merge))">>,
5020
5021       <<"F = fun(M) ->
5022                qlc:q([{XX,YY} ||
5023                       {XX,X} <- [{a,1},{b,2},{bb,2},{c,3},{cc,3}],
5024                       {Y,YY} <- [{0,a},{1,a},{1,aa},{2,b},{2,bb},{2,bbb},
5025                                  {4,d}],
5026                        X =:= Y],
5027                      {join,M})
5028              end,
5029          R = qlc:e(F(nested_loop)),
5030          R = qlc:e(F(merge))">>,
5031
5032       <<"Q = qlc:q([{XX,YY} ||
5033                        {XX,X} <- [{b,1},{c,3}],
5034                        {Y,YY} <- [{1,a}],
5035                        X =:= Y],
5036                    {join,merge}),
5037          [{b,a}] = qlc:e(Q)">>,
5038
5039       <<"Q = qlc:q([{XX,YY} ||
5040                            {XX,X} <- [{b,1},{c,3}],
5041                            {Y,YY} <- qlc_SUITE:table_error([{1,a}], 1, err),
5042                            X =:= Y],
5043                        {join,merge}),
5044              err = qlc:e(Q)">>,
5045
5046       <<"Q = qlc:q([{XX,YY} ||
5047                            {XX,X} <- [{a,1},{aa,1}],
5048                            {Y,YY} <- [{1,a}],
5049                            X =:= Y],
5050                        {join,merge}),
5051              [{a,a},{aa,a}] = qlc:e(Q)">>,
5052
5053       <<"Q = qlc:q([{XX,YY} ||
5054                            {XX,X} <- qlc_SUITE:table_error([{a,1},{aa,1}],
5055                                                             2, err),
5056                            {Y,YY} <- [{1,a}],
5057                            X =:= Y],
5058                        {join,merge}),
5059              err = qlc:e(Q)">>,
5060
5061       <<"Q = qlc:q([{XX,YY} ||
5062                            {XX,X} <- [{a,1}],
5063                            {Y,YY} <- [{1,a},{1,aa}],
5064                            X =:= Y],
5065                        {join,merge}),
5066              [{a,a},{a,aa}]= qlc:e(Q)">>,
5067
5068       <<"Q = qlc:q([{XX,YY} ||
5069                            {XX,X} <- qlc_SUITE:table_error([{a,1}], 2, err),
5070                            {Y,YY} <- [{1,a},{1,aa}],
5071                            X =:= Y],
5072                        {join,merge}),
5073          C = qlc:cursor(Q),
5074          [{a,a}] = qlc:next_answers(C, 1),
5075          qlc:delete_cursor(C),
5076          err = qlc:e(Q)">>,
5077
5078       <<"F = fun(M) ->
5079                    qlc:q([{XX,YY} ||
5080                               {XX,X} <- [{a,1},{b,2},{bb,2},{c,3},{cc,3}],
5081                               {Y,YY} <- [{0,a},{1,a},{1,aa},{2,b},
5082                                          {2,bb},{2,bbb}],
5083                            X =:= Y],
5084                          {join,M})
5085              end,
5086              %% [{a,a},{a,aa},{b,b},{b,bb},{b,bbb},{bb,b},{bb,bb},{bb,bbb}]
5087              R = qlc:e(F(nested_loop)),
5088              R = qlc:e(F(merge))">>,
5089
5090
5091       <<"F = fun(M) ->
5092                   qlc:q([{XX,YY} ||
5093                          {XX,X} <- [{a,1},{b,2},{bb,2},{c,3},{cc,3}],
5094                          {Y,YY} <- qlc_SUITE:table_error([{0,a},{1,a},{1,aa},
5095                                                           {2,b},{2,bb},
5096                                                           {2,bbb}],
5097                                                          1, err),
5098                           X =:= Y],
5099                         {join,M})
5100              end,
5101              %% [{a,a},{a,aa},{b,b},{b,bb},{b,bbb},{bb,b},{bb,bb},{bb,bbb}]
5102              err = qlc:e(F(nested_loop)),
5103              err = qlc:e(F(merge))">>,
5104
5105       <<"Q = qlc:q([{XX,YY} ||
5106                            {XX,X} <- qlc_SUITE:table_error([], 2, err),
5107                            {Y,YY} <- [{2,b},{3,c}],
5108                            X =:= Y],
5109                        {join,merge}),
5110              err = qlc:e(Q)">>,
5111
5112       <<"Q = qlc:q([{XX,YY} ||
5113                            {XX,X} <- [{a,1},{c,3}],
5114                            {Y,YY} <- [{2,b},{3,c}],
5115                            X =:= Y],
5116                        {join,merge}),
5117              [{c,c}] = qlc:e(Q)">>,
5118
5119       <<"Q = qlc:q([{XX,YY} ||
5120                            {XX,X} <- [{a,1},{aa,1}],
5121                            {Y,YY} <- [{1,a},{1,aa}],
5122                            X =:= Y],
5123                        {join,merge}),
5124              [{a,a},{a,aa},{aa,a},{aa,aa}] = qlc:e(Q)">>,
5125
5126       <<"Q = qlc:q([{XX,YY} ||
5127                            {XX,X} <- [{a,1},{b,2}],
5128                            {Y,YY} <- [{1,a},{1,aa}],
5129                            X =:= Y],
5130                        {join,merge}),
5131              [{a,a},{a,aa}] = qlc:e(Q)">>,
5132
5133       <<"Q = qlc:q([{XX,YY} ||
5134                            {XX,X} <- [{a,1},{b,2}],
5135                            {Y,YY} <- qlc_SUITE:table_error([{1,a},{1,aa}],
5136                                                            1, err),
5137                            X =:= Y],
5138                        {join,merge}),
5139              err = qlc:e(Q)">>,
5140
5141       <<"Q = qlc:q([{XX,YY} ||
5142                            {XX,X} <- [{a,1},{b,2}],
5143                            {Y,YY} <- [{1,a},{1,aa},{1,aaa},{1,aaaa}],
5144                            X =:= Y],
5145                        {join,merge}),
5146              [{a,a},{a,aa},{a,aaa},{a,aaaa}]= qlc:e(Q)">>,
5147
5148       <<"Q = qlc:q([{element(1, X), element(2, Y)} ||
5149                            X <- [{a,1},{aa,1}],
5150                            Y <- [{1,a},{1,aa}],
5151                            element(2, X) =:= element(1, Y)],
5152                        {join,merge}),
5153              [{a,a},{a,aa},{aa,a},{aa,aa}] = qlc:e(Q)">>,
5154
5155       <<"Q = qlc:q([{element(1, X), element(2, Y)} ||
5156                            X <- [{a,1},{aa,1}],
5157                            Y <- qlc_SUITE:table_error([], 1, err),
5158                            element(2, X) =:= element(1, Y)],
5159                        {join,merge}),
5160              err = qlc:e(Q)">>,
5161
5162       <<"Q = qlc:q([{element(1, X), element(2, Y)} ||
5163                            X <- qlc_SUITE:table_error([{a,1}], 2, err),
5164                            Y <- [{2,b}],
5165                            element(2, X) =:= element(1, Y)],
5166                        {join,merge}),
5167              err = qlc:e(Q)">>,
5168
5169       <<"Q = qlc:q([{XX,YY} ||
5170                  {XX,X} <- [{1,a},{'1b',b},{2,b}],
5171                  {Y,YY} <- [{a,1},{b,'1b'},{c,1}],
5172                  X == Y],
5173              {join,merge}),
5174          [{1,1},{'1b','1b'},{2,'1b'}] = qlc:e(Q)">>,
5175
5176       <<"Q = qlc:q([{XX,YY} ||
5177                  {XX,X} <- qlc_SUITE:table_error([{1,a},{'1b',b},{2,b}],
5178                                                  2, err),
5179                  {Y,YY} <- [{a,1},{b,'1b'},{c,1}],
5180                  X == Y],
5181              {join,merge}),
5182          err = qlc:e(Q)">>
5183
5184          ],
5185    run(Config, ETs),
5186
5187    %% Mostly examples where temporary files are needed while merging.
5188    FTs = [
5189       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5190          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5191          F = fun(J) ->
5192                      qlc:q([{XX,YY} ||
5193                                {XX,X} <- L1,
5194                                {Y,YY} <- L2,
5195                                X == Y],
5196                            {join,J})
5197              end,
5198          Qm = F(merge),
5199          Qn = F(nested_loop),
5200          true = qlc:e(Qm,{max_list_size, 0}) =:= qlc:e(Qn)">>,
5201
5202       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5203          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5204          Q = qlc:q([{XX,YY} ||
5205                        {XX,X} <- L1,
5206                        {Y,YY} <- L2,
5207                        X == Y],
5208                    {join,merge}),
5209          {error,_,{file_error,_,_}} =
5210               qlc:e(Q, [{max_list_size,64*1024},{tmpdir,\"/a/b/c\"}])">>,
5211
5212       <<"L1 = qlc_SUITE:table_error([{1,a},{2,a}], 2, err),
5213          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5214          F = fun(J) ->
5215                      qlc:q([{XX,YY} ||
5216                                {XX,X} <- L1,
5217                                {Y,YY} <- L2,
5218                                X == Y],
5219                            {join,J})
5220              end,
5221          Qm = F(merge),
5222          Qn = F(nested_loop),
5223          err = qlc:e(Qm, {max_list_size,64*1024}),
5224          err = qlc:e(Qn)">>,
5225
5226       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5227          L2 = qlc_SUITE:table_error([{a,Y} || Y <- lists:seq(1, 10000)],
5228                                     1, err),
5229          F = fun(J) ->
5230                      qlc:q([{XX,YY} ||
5231                                {XX,X} <- L1,
5232                                {Y,YY} <- L2,
5233                                X == Y],
5234                            {join,J})
5235              end,
5236          Qm = F(merge),
5237          Qn = F(nested_loop),
5238          err = qlc:e(Qm, {max_list_size,64*1024}),
5239          err = qlc:e(Qn)">>,
5240
5241       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)] ++
5242               [{'1b',b},{2,b}] ++ [{Y,d} || Y <- lists:seq(1, 2)],
5243          L2 = [{a,Y} || Y <- lists:seq(1, 10000)] ++
5244               [{b,'1b'}] ++ [{c,1}] ++ [{d,Y} || Y <- lists:seq(1, 10000)],
5245          F = fun(J) ->
5246                      qlc:q([{XX,YY} ||
5247                                {XX,X} <- L1,
5248                                {Y,YY} <- L2,
5249                                X == Y],
5250                            {join,J})
5251              end,
5252          Qm = F(merge),
5253          Qn = F(nested_loop),
5254          true = lists:sort(qlc:e(Qm, {max_list_size,64*1024})) =:=
5255                 lists:sort(qlc:e(Qn))">>,
5256
5257       <<"F = fun(J) ->
5258                      qlc:q([{XX,YY} ||
5259                                {XX,X} <- [{Y,a} || Y <- lists:seq(1, 2)],
5260                                {Y,YY} <- [{a,Y} || Y <- lists:seq(1,100000)],
5261                                X == Y],
5262                            {join,J})
5263              end,
5264          Qm = F(merge),
5265          Qn = F(nested_loop),
5266          true = qlc:e(Qm, {max_list_size,64*1024}) =:= qlc:e(Qn)">>,
5267
5268       %% More than one join in one QLC expression.
5269       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5270          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5271          F = fun(J) ->
5272                      Q = qlc:q([{XX,YY} ||
5273                                    {XX,X} <- L1,
5274                                    {Y,YY} <- L2,
5275                                    X == Y,
5276                                    begin XX > 1 end,
5277                                    begin YY > 9999 end],
5278                                {join,J}),
5279                      qlc:q([{XX1,YY1,XX2,YY2} ||
5280                                {XX1,YY1} <- Q,
5281                                {XX2,YY2} <- Q])
5282              end,
5283          Qm = F(merge),
5284          Qn = F(nested_loop),
5285          R1 = lists:sort(qlc:e(Qm, {max_list_size,64*1024})),
5286          R2 = lists:sort(qlc:e(Qm, {max_list_size,1 bsl 31})),
5287          true = R1 =:= lists:sort(qlc:e(Qn)),
5288          true = R1 =:= R2">>,
5289
5290       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5291          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5292          F = fun(J) ->
5293                      Q = qlc:q([{XX,YY} ||
5294                                    {XX,X} <- L1,
5295                                    {Y,YY} <- L2,
5296                                    X == Y,
5297                                    begin XX > 1 end,
5298                                    begin YY > 9999 end],
5299                                {join,J}),
5300                      qlc:q([{XX1,YY1,XX2,YY2} ||
5301                                {XX1,YY1} <- Q,
5302                                {XX2,YY2} <- Q,
5303                                throw(thrown)])
5304              end,
5305          Qm = F(merge),
5306          thrown = (catch {any_term, qlc:e(Qm, {max_list_size,64*1024})})">>,
5307
5308       <<"%% Bigger than 64*1024.
5309          T1 = {1, lists:seq(1, 20000)},
5310          L1 = [{a,T1},{b,T1}],
5311          L2 = [{T1,a},{T1,b}],
5312          F = fun(J) ->
5313                      qlc:q([{XX,YY} ||
5314                                {XX,X} <- L1,
5315                                {Y,YY} <- L2,
5316                                X == Y],
5317                            {join,J})
5318              end,
5319          Qm = F(merge),
5320          Qn = F(nested_loop),
5321          R = [{a,a},{a,b},{b,a},{b,b}],
5322          R = qlc:e(Qm, {max_list_size,64*1024}),
5323          R = qlc:e(Qn)">>,
5324
5325       <<"%% Bigger than 64*1024. No temporary files.
5326          T1 = {1, lists:seq(1, 20000)},
5327          L1 = [{a,T1},{b,T1}],
5328          L2 = [{T1,a},{T1,b}],
5329          F = fun(J) ->
5330                      qlc:q([{XX,YY} ||
5331                                {XX,X} <- L1,
5332                                {Y,YY} <- L2,
5333                                X == Y],
5334                            {join,J})
5335              end,
5336          Qm = F(merge),
5337          Qn = F(nested_loop),
5338          R = [{a,a},{a,b},{b,a},{b,b}],
5339          R = qlc:e(Qm, {max_list_size,1 bsl 31}),
5340          R = qlc:e(Qn)">>
5341
5342
5343          ],
5344    run(Config, FTs),
5345
5346    ok.
5347
5348%% Merge join optimizations (avoid unnecessary sorting).
5349join_sort(Config) when is_list(Config) ->
5350    Ts = [
5351       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}]),
5352          H1 = qlc:q([X || X <- H1_1], unique),
5353          H2 = qlc:keysort(2, [{1,2},{3,4}]),
5354          H3 = qlc:q([{X,Y} || {X,_,_} <- H1,
5355                               {_,Y} <- H2,
5356                               X =:= Y]),
5357          {1,0,0,2} = join_info(H3),
5358          [{4,4}] = qlc:e(H3)">>,
5359
5360       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}]),
5361          H1 = qlc:q([X || X <- H1_1], unique), % keeps the order
5362          H2 = qlc:keysort(2, [{1,2},{3,4}]),
5363          H3 = qlc:q([{X,Y} || {X,_,_} <- H1, % no extra keysort
5364                               {Y,_} <- H2,   % an extra keysort
5365                               X =:= Y]),
5366          {1,0,0,3} = join_info(H3),
5367          [{1,1}] = qlc:e(H3)">>,
5368
5369       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}], {tmpdir,\"\"}),
5370          H1 = qlc:q([X || X <- H1_1], unique),
5371          H2 = qlc:keysort(2, [{1,2},{3,4}]),
5372          H3 = qlc:q([{X,Y} || {_,X,_} <- H1,
5373                               {_,Y} <- H2,
5374                               X =:= Y]),
5375          {1,0,0,3} = join_info(H3),
5376          [{2,2}] = qlc:e(H3)">>,
5377
5378       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}], {tmpdir,\"\"}),
5379          H1 = qlc:q([X || X <- H1_1], unique),
5380          H2 = qlc:keysort(2, [{1,2},{3,4}]),
5381          H3 = qlc:q([{X,Y} || {_,X,_} <- H1,
5382                               {_,Y} <- H2,
5383                               X =:= Y]),
5384          {1,0,0,3} = join_info(H3),
5385          [{2,2}] = qlc:e(H3)">>,
5386
5387       <<"H1 = qlc:sort([{1,a},{2,b},{3,c}]),
5388          %% Since H1 is sorted it is also keysorted on the first column.
5389          Q = qlc:q([{X, Y} || {X,_} <- H1,
5390                               {Y} <- [{0},{1},{2}],
5391                               X == Y]),
5392          {1,0,0,1} = join_info(Q),
5393          [{1,1},{2,2}] = qlc:e(Q)">>,
5394
5395       <<"H1 = qlc:sort([{r,a,1},{r,b,2},{r,c,3}]),
5396          Q = qlc:q([{X, Y} || {r,_,X} <- H1, % needs keysort(3)
5397                               {Y} <- [{0},{1},{2}],
5398                               X == Y]),
5399          {1,0,0,2} = join_info(Q),
5400          [{1,1},{2,2}] = qlc:e(Q)">>,
5401
5402       <<"QH = qlc:q([X || X <- [{1,2,3},{4,5,6}],
5403                           Y <- qlc:sort([{1,2},{3,4}]),
5404                           element(1, X) =:= element(2, Y)]),
5405          {1,0,0,2} = join_info_count(QH),
5406          [{4,5,6}] = qlc:e(QH)">>,
5407
5408       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6},{1,2,3}]),
5409          H1 = qlc:q([X || X <- H1_1], unique),
5410          H2 = qlc:keysort(2, [{2,1},{3,4}]),
5411          H3 = qlc:q([{X,Y} || {X,_,_} <- H1,
5412                               {_,Y} <- H2,
5413                               X =:= Y]),
5414          H4 = qlc:keysort(1, [{1,2},{3,4},{4,a}]),
5415          H5 = qlc:q([{X,Y} || {X,_} <- H4,
5416                               {_,Y} <- H3,
5417                               X =:= Y]),
5418          {2,0,0,3} = join_info_count(H5),
5419          [{1,1},{4,4}]= qlc:e(H5)">>,
5420
5421       <<"
5422          H1 = qlc:keysort(2, [{1,a,u},{2,b,k},{3,c,l}]),
5423          H2 = qlc:q([{a,X,Y,a} || {1,X,u} <- H1,
5424                                   {2,Y,k} <- H1]),
5425          %% Neither H1 nor H2 need to be key-sorted
5426          %% (the columns are constant).
5427          H3 = qlc:q([{A,B,C,D,E,F,G,H} ||
5428                         {A,B,C,D} <- H2,
5429                         {E,F,G,H} <- H2,
5430                         A =:= H],
5431                     {join,merge}),
5432          {1,0,0,4} = join_info_count(H3),
5433          [{a,a,b,a,a,a,b,a}] = qlc:e(H3)">>,
5434
5435       <<"%% Q1 is sorted on X or Y.
5436          Q1 = qlc:q([{X,Y} ||
5437                         {X,_} <- qlc:keysort(1, [{1,a},{2,b}]),
5438                         {_,Y} <- qlc:keysort(2, [{aa,11},{bb,22}]),
5439                         X < Y]),
5440          [{1,11},{1,22},{2,11},{2,22}] = qlc:e(Q1),
5441          Q = qlc:q([{X,Y} ||
5442                        {X,_} <- Q1, % no need to sort Q1
5443                        {Y} <- [{0},{1},{2},{3}],
5444                        X =:= Y]),
5445          {1,0,0,3} = join_info_count(Q),
5446          [{1,1},{1,1},{2,2},{2,2}] = qlc:e(Q)">>,
5447
5448       <<"H1 = qlc:keysort([2], [{r,1},{r,2},{r,3}]),
5449          %% H1 is actually sorted, but this info is not captured.
5450          Q = qlc:q([{X, Y} || {r,X} <- H1,
5451                               {Y} <- [{0},{1},{2}],
5452                               X == Y]),
5453          {1,0,0,2} = join_info_count(Q),
5454          [{1,1},{2,2}] = qlc:e(Q)">>,
5455
5456       <<"%% Two leading constants columns and sorted objects
5457          %% implies keysorted on column 3.
5458          H1 = qlc:sort(qlc:q([{a,X,Y} || {X,Y} <- [{1,2},{2,3},{3,3}]])),
5459          H2 = qlc:q([{X,Y} ||
5460                         {a,3,X} <- H1,
5461                         {a,2,Y} <- H1,
5462                         X =:= Y]),
5463          {1,0,0,0} = join_info_count(H2),
5464          [{3,3}] = qlc:e(H2)">>,
5465
5466       <<"QH = qlc:q([{X,Y} || {X,Y} <- [{1,4},{1,3}],
5467                               {Z} <- [{1}],
5468                               X =:= Z, (Y =:= 3) or (Y =:= 4)]),
5469          {1,0,0,1} = join_info_count(QH),
5470          [{1,4},{1,3}] = qlc:e(QH)">>,
5471
5472       <<"E = ets:new(join, [ordered_set]),
5473          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
5474          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E), % no need to sort
5475                               {Y} <- [{0},{1},{2}],
5476                               X == Y], {join,merge}),
5477          {1,0,0,1} = join_info(Q),
5478          [{1,1},{2,2}] = qlc:e(Q),
5479          ets:delete(E)">>,
5480
5481       <<"H1 = qlc:sort([{r,1,a},{r,2,b},{r,3,c}]),
5482          Q = qlc:q([{X, Y} || {r,X,_} <- H1, % does not need keysort(3)
5483                               {Y} <- [{0},{1},{2}],
5484                               X == Y]),
5485          {1,0,0,1} = join_info(Q),
5486          [{1,1},{2,2}] = qlc:e(Q)">>,
5487
5488       <<"H1 = qlc:keysort(2,[{r,1},{r,2},{r,3}]),
5489          H2 = [{a},{b}],
5490          %% Several columns in different qualifiers have initial
5491          %% constant columns.
5492          H3 = qlc:keysort(1,[{c1,c2,1},{foo,bar,2},{c1,c2,3},{c1,c2,2}]),
5493          Q = qlc:q([{r,X,Y,Z} || {r,X} <- H1,
5494                                  {Y} <- H2,
5495                                  {c1,c2,Z} <- H3,
5496                                  X =:= Z], {join,merge}),
5497          {1,0,0,3} = join_info(Q),
5498          [{r,1,a,1},{r,1,b,1},{r,2,a,2},{r,2,b,2},{r,3,a,3},{r,3,b,3}] =
5499              qlc:e(Q)">>,
5500
5501       <<"H1 = qlc:keysort(2,[{r,1},{r,2},{r,3}]),
5502          H2 = [{a},{b}],
5503          %% As the last one, but one keysort less.
5504          H3 = qlc:keysort(3,[{c1,c2,1},{foo,bar,2},{c1,c2,3},{c1,c2,2}]),
5505          Q = qlc:q([{r,X,Y,Z} || {r,X} <- H1,
5506                                  {Y} <- H2,
5507                                  {c1,c2,Z} <- H3,
5508                                  X =:= Z], {join,merge}),
5509          {1,0,0,2} = join_info(Q),
5510          [{r,1,a,1},{r,1,b,1},{r,2,a,2},{r,2,b,2},{r,3,a,3},{r,3,b,3}] =
5511              qlc:e(Q)">>,
5512
5513       <<"H1 = qlc:keysort(2,[{r,1},{r,2},{r,3}]),
5514          H2 = [{a},{b}],
5515          H3 = qlc:keysort(1,[{c1,c2,1},{foo,bar,2},{c1,c2,3},{c1,c2,2}]),
5516          %% One generator before the joined generators.
5517          Q = qlc:q([{r,X,Y,Z} || {Y} <- H2,
5518                                  {r,X} <- H1,
5519                                  {c1,c2,Z} <- H3,
5520                                  X =:= Z], {join,merge}),
5521          {1,0,0,3} = join_info(Q),
5522          [{r,1,a,1},{r,2,a,2},{r,3,a,3},{r,1,b,1},{r,2,b,2},{r,3,b,3}] =
5523              qlc:e(Q)">>,
5524
5525       <<"H1 = [{a,1},{b,2},{c,3},{d,4}],
5526          H2 = [{a},{b}],
5527          H3 = [{c1,c2,a},{foo,bar,b},{c1,c2,c},{c1,c2,d}],
5528          %% A couple of \"extra\" filters and generators.
5529          Q = qlc:q([{X,Y,Z} || {X,_} <- H1,
5530                                {Y} <- H2,
5531                                X > Y,
5532                                {c1,c2,Z} <- H3,
5533                                {W} <- [{a},{b}],
5534                                W > a,
5535                                X =:= Z]),
5536          {1,0,0,2} = join_info(Q),
5537          [{c,a,c},{c,b,c},{d,a,d},{d,b,d}] = qlc:e(Q)">>,
5538
5539       <<"H1 = qlc:keysort(2,[{r,1},{r,2},{r,3}]),
5540          H2 = qlc:sort([{c1,c2,1},{foo,bar,2},{c1,c2,3},{c1,c2,2}]),
5541          %% H2 is sorted, no keysort necessary.
5542          %% This example shows that the 'filter-part' of the pattern
5543          %% ({c1,c2,Z}) should be evaluated _before_ the join.
5544          %% Otherwise the objects cannot be assumed to be keysort:ed on the
5545          %% third column (if merge join), and lookup-join would lookup
5546          %% more keys than necessary.
5547          Q = qlc:q([{r,X,Z} || {r,X} <- H1,
5548                                {c1,c2,Z} <- H2,
5549                                X =:= Z] ,{join,merge}),
5550          {1,0,0,1} = join_info(Q),
5551          [{r,1,1},{r,2,2},{r,3,3}] = qlc:e(Q)">>,
5552
5553       <<"H1 = [{1,a},{2,b},{3,c}],
5554          H2 = [{0,0},{1,1},{2,2}],
5555          H3 = qlc:q([{A,C,D} ||
5556                         {A,_B} <- H1,
5557                         {C,D} <- H2,
5558                         A == D, C == D]),
5559          H4 = [{1,1},{2,2},{3,3}],
5560          H5 = qlc:q([{X,Y} ||
5561                         {X,_,_} <- H3, % no need to sort this one (merge join)
5562                         {_,Y} <- H4,
5563                         X == Y]),
5564          Q = qlc:q([{X,Y} ||
5565                        {X,_} <- H5, % no need to sort this one
5566                        {Y,_} <- H4,
5567                        X == Y]),
5568          {{3,0,0,4},{3,0,0,6}} = join_info(Q),
5569          [{1,1},{2,2}] = qlc:e(Q)">>,
5570
5571       <<"%% There is an extra test (_C1, element(1, X) =:= 1) that is not
5572          %% necessary since the match spec does the same check. This can be
5573          %% improved upon.
5574          Q = qlc:q([{X,Y} ||
5575                        X <- [{2},{1}],
5576                        element(1, X) =:= 1,
5577                        Y=_ <- [{2},{1}],
5578                        element(1, X) =:= element(1, Y)]),
5579          {qlc,_,
5580              [{generate,_,{qlc,_,
5581                              [{generate,_,{qlc,_,
5582                                             [{generate,_,{list,{list,_},_}},
5583                                              _C1],[]}},
5584                               {generate,_,{qlc,_,
5585                                             [{generate,_,{list,[{2},{1}]}},
5586                                              _C2],[]}},_],
5587                              [{join,merge}]}},_],[]} = i(Q),
5588          {1,0,0,0} = join_info_count(Q),
5589          [{{1},{1}}] = qlc:e(Q)">>,
5590
5591       <<"etsc(fun(E) ->
5592                       L = [{a,b,a},{c,d,b},{1,2,a},{3,4,b}],
5593                       Q = qlc:q([P1 || {X,2,Z}=P1 <- ets:table(E),
5594                                        Y <- L,
5595                                        X =:= 1,
5596                                        Z =:= a,
5597                                        P1 =:= Y,
5598                                        X =:= element(1, Y)]),
5599                       {1,0,0,0} = join_info_count(Q),
5600                       [{1,2,a}] = qlc:e(Q)
5601               end, [{1,2,a},{3,4,b}])">>,
5602
5603       %% Merge join on Z and element(3, Y). No need to sort!
5604       <<"etsc(fun(E) ->
5605                       L = [{a,b,a},{c,d,b},{1,2,a},{3,4,b}],
5606                       Q = qlc:q([P1 || {X,2,Z}=P1 <- ets:table(E),
5607                                        Y <- L,
5608                                        (X =:= 1) or (X =:= 2),
5609                                        Z =:= a,
5610                                        P1 =:= Y,
5611                                        X =:= element(1, Y)]),
5612                       {1,0,0,0} = join_info_count(Q),
5613                       [{1,2,a}] = qlc:e(Q)
5614               end, [{1,2,a},{3,4,b}])">>,
5615
5616       <<"%% Y is constant as well as X. No keysort, which means that
5617          %% Y must be filtered before merge join.
5618          etsc(fun(E) ->
5619                       Q = qlc:q([X || {1,2}=X <- ets:table(E),
5620                                       Y <- [{a,b},{c,d},{1,2},{3,4}],
5621                                       X =:= Y,
5622                                       element(1, X) =:= element(1, Y)]),
5623                       {1,0,0,0} = join_info_count(Q),
5624                       [{1,2}] = qlc:e(Q)
5625               end, [{1,2},{3,4}])">>
5626
5627         ],
5628    run(Config, Ts),
5629    ok.
5630
5631%% Join of more than two columns.
5632join_complex(Config) when is_list(Config) ->
5633    Ts = [{three,
5634           <<"three() ->
5635                  L = [],
5636                  Q = qlc:q([{X,Y,Z} || {X,_} <- L,
5637                                        {_,Y} <- L,
5638                                        {Z,_} <- L,
5639                                        X =:= Y, Y == Z
5640                                     ]),
5641                  qlc:e(Q).">>,
5642           [],
5643           {warnings,[{3,qlc,too_complex_join}]}},
5644
5645          {two,
5646           <<"two() ->
5647                  Q = qlc:q([{X,Y,Z,W} ||
5648                      {X} <- [],
5649                      {Y} <- [],
5650                      {Z} <- [],
5651                      {W} <- [],
5652                      X =:= Y,
5653                      Z =:= W],{join,merge}),
5654                  qlc:e(Q).">>,
5655           [],
5656           {warnings,[{2,qlc,too_many_joins}]}}
5657       ],
5658
5659    compile(Config, Ts),
5660
5661    Ts2 = [{three,
5662            <<"three() ->
5663                  L = [],
5664                  Q = qlc:q([{X,Y,Z} || {X,_} <- L,
5665                                        {_,Y} <- L,
5666                                        {Z,_} <- L,
5667                                        X =:= Y, Y == Z
5668                                     ]),
5669                  qlc:e(Q).">>,
5670            [],
5671            {[],
5672             ["cannot handle join of three or more generators efficiently"]}},
5673
5674          {two,
5675           <<"two() ->
5676                  Q = qlc:q([{X,Y,Z,W} ||
5677                      {X} <- [],
5678                      {Y} <- [],
5679                      {Z} <- [],
5680                      {W} <- [],
5681                      X =:= Y,
5682                      Z =:= W],{join,merge}),
5683                  qlc:e(Q).">>,
5684           [],
5685           {[],["cannot handle more than one join efficiently"]}}
5686       ],
5687
5688    compile_format(Config, Ts2),
5689
5690    ok.
5691
5692
5693%% OTP-5644. Handle the new language element M:F/A.
5694otp_5644(Config) when is_list(Config) ->
5695    Ts = [
5696       <<"Q = qlc:q([fun modul:mfa/0 || _ <- [1,2],
5697                                        is_function(fun modul:mfa/0, 0)]),
5698          [_,_] = qlc:eval(Q)">>
5699       ],
5700
5701    run(Config, Ts),
5702    ok.
5703
5704%% OTP-5195. Allow traverse functions returning terms.
5705otp_5195(Config) when is_list(Config) ->
5706    %% Several minor improvements have been implemented in OTP-5195.
5707    %% The test cases are spread all over... except these.
5708    %%
5709    %% Traverse functions returning terms.
5710
5711    Ts = [<<"L = [1,2,3],
5712             Err = {error,modul,err},
5713             H = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5714             Err = qlc:e(H)">>,
5715
5716          <<"Err = {error,modul,err},
5717             TravFun = fun() -> Err end,
5718             H1 = qlc:sort(qlc:q([X || X <- qlc:table(TravFun, [])])),
5719             H = qlc:q([{X} || X <- H1]),
5720             Err = qlc:e(H)">>,
5721
5722          <<"L = [1,2,3],
5723             Err = {error,modul,err},
5724             H = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5725             C = qlc:cursor(H),
5726             R = qlc:next_answers(C, all_remaining),
5727             qlc:delete_cursor(C),
5728             Err = R">>,
5729
5730          <<"L = [1,2,3],
5731             Err = {error,modul,err},
5732             H = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5733             F = fun(Obj, A) -> A++[Obj] end,
5734             Err = qlc:fold(F, [], H)">>,
5735
5736          <<"Err = {error,modul,err},
5737             TravFun = fun() -> Err end,
5738             H1 = qlc:sort(qlc:q([X || X <- qlc:table(TravFun, [])])),
5739             H = qlc:q([{X} || X <- H1]),
5740             F = fun(Obj, A) -> A++[Obj] end,
5741             Err = qlc:fold(F, [], H)">>,
5742
5743          <<"Q1 = qlc:append([qlc:append([ugly()]),[3]]),
5744             Q = qlc:q([X || X <- Q1]),
5745             42 = qlc:e(Q),
5746             ok.
5747
5748             ugly() ->
5749                 [apa | fun() -> 42 end].
5750             foo() -> bar">>,
5751
5752          <<"L = [1,2,3],
5753             Err = {error,modul,err},
5754             H = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5755             H1 = qlc:q([X || X <- H], unique),
5756             Err = qlc:e(H1)">>,
5757
5758          <<"Err = {error, module, err},
5759             L = [1,2,3],
5760             H1 = qlc:q([{X} || X <- qlc_SUITE:table_error(L, Err)]),
5761             H = qlc:q([{X,Y,Z} || X <- H1, Y <- H1, Z <- L], cache),
5762             qlc:e(H, cache_all)">>,
5763
5764          <<"Err = {error, module, err},
5765             L = [1,2,3],
5766             H1 = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5767             H = qlc:q([{X,Y,Z} || X <- H1, Y <- H1, Z <- L], cache),
5768             qlc:e(H, [cache_all,unique_all])">>,
5769
5770          <<"L = [{1},{2},{3}],
5771             H = qlc:q([X || {X} <- qlc_SUITE:table_lookup_error(L),
5772                             X =:= 2]),
5773             {error, lookup, failed} = qlc:e(H)">>,
5774
5775          %% The traverse function can return any value, but it must not
5776          %% return an improper list. Improper lists must not be given anyway.
5777          <<"{'EXIT', {{badfun,a},_}} =
5778             (catch qlc:e(qlc:q([{X} || X <- [1 | a], begin true end])))">>
5779
5780       ],
5781
5782    run(Config, Ts),
5783
5784    Ts2 = [<<"Q = qlc:q([{X,Y} || {X} <- [{1},{2},{3}],
5785                                  begin
5786                                      %% Used to generate a badly formed file
5787                                      Y = 3, true
5788                                  end,
5789                                  X =:= Y]),
5790              [{3,3}] = qlc:e(Q)">>],
5791    run(Config, Ts2),
5792
5793    ok.
5794
5795%% OTP-6038. Bug fixes: unique and keysort; cache.
5796otp_6038_bug(Config) when is_list(Config) ->
5797    %% The 'unique' option can no longer be merged with the keysort options.
5798    %% This used to return [{1,a},{1,c},{2,b},{2,d}], but since
5799    %% file_sorter:keysort now removes duplicates based on keys, the
5800    %% correct return value is [{1,a},{2,b}].
5801    Ts = [<<"H1 = qlc:q([X || X <- [{1,a},{2,b},{1,c},{2,d}]], unique),
5802             H2 = qlc:keysort(1, H1, [{unique,true}]),
5803             [{1,a},{2,b}] = qlc:e(H2)">>],
5804
5805    run(Config, Ts),
5806
5807    %% Sometimes the cache options did not empty the correct tables.
5808    CTs = [
5809       <<"Options = [cache,unique],
5810          V1 = qlc:q([{X,Y} || X <- [1,2], Y <- [3]], Options),
5811          V2 = qlc:q([{X,Y} || X <- [a,b], Y <- V1]),
5812          V3 = qlc:q([{X,Y} || X <- [5,6], Y <- [7]], Options),
5813          Q = qlc:q([{X,Y} || X <- V2, Y <- V3]),
5814          R = qlc:e(Q),
5815          L1 = [{X,Y} || X <- [1,2], Y <- [3]],
5816          L2 = [{X,Y} || X <- [a,b], Y <- L1],
5817          L3 = [{X,Y} || X <- [5,6], Y <- [7]],
5818          L = [{X,Y} || X <- L2, Y <- L3],
5819          true = R =:= L">>,
5820       <<"Options = [cache,unique],
5821          V1 = qlc:q([{X,Y} || X <- [1,2], Y <- [3]], Options),
5822          V2 = qlc:q([{X,Y} || X <- [a,b], Y <- V1]),
5823          V3 = qlc:q([{X,Y} || X <- [5,6], Y <- [7]], Options),
5824          V4 = qlc:q([{X,Y} || X <- V2, Y <- V3], Options),
5825          Q = qlc:q([{X,Y} || X <- [1,2], Y <- V4]),
5826          R = qlc:e(Q),
5827          L1 = [{X,Y} || X <- [1,2], Y <- [3]],
5828          L2 = [{X,Y} || X <- [a,b], Y <- L1],
5829          L3 = [{X,Y} || X <- [5,6], Y <- [7]],
5830          L4 = [{X,Y} || X <- L2, Y <- L3],
5831          L = [{X,Y} || X <- [1,2], Y <- L4],
5832          true = R =:= L">>
5833       ],
5834    run(Config, CTs),
5835
5836    ok.
5837
5838%% OTP-6359. dets:select() never returns the empty list.
5839otp_6359(Config) when is_list(Config) ->
5840    dets:start(),
5841    T = luna,
5842    Fname = filename(T, Config),
5843
5844    Ts = [
5845       [<<"T = luna, Fname = \"">>, Fname, <<"\",
5846           {ok, _} = dets:open_file(T, [{file,Fname}]),
5847           Q = qlc:q([F ||
5848                         F <- dets:table(T),
5849                         (F band ((1 bsl 0)) =/= 0),
5850                         true]),
5851           [] = qlc:eval(Q),
5852           ok = dets:close(T),
5853           file:delete(\"">>, Fname, <<"\"),
5854           ok">>]
5855    ],
5856
5857    run(Config, Ts),
5858    ok.
5859
5860%% OTP-6562. compressed = false (should be []) when sorting before join.
5861otp_6562(Config) when is_list(Config) ->
5862    Bug = [
5863      %% This example uses a file to sort E2 on the second column. It is
5864      %% not easy to verify that this happens; the file_sorter module's
5865      %% size option cannot be set in this case. But it is not likely
5866      %% that the default size (512 KiB) will ever change, so it should
5867      %% be future safe.
5868      <<"E1 = create_ets(1, 10),
5869         E2 = create_ets(5, 150000),
5870         Q = qlc:q([{XX,YY} ||
5871                       {X,XX} <- ets:table(E1),
5872                       {YY,Y} <- ets:table(E2),
5873                       X == Y],
5874                   {join,merge}),
5875         [{5,5},{6,6},{7,7},{8,8},{9,9},{10,10}] = qlc:e(Q),
5876         ets:delete(E1),
5877         ets:delete(E2)">>
5878    ],
5879    run(Config, Bug),
5880
5881    Bits = [
5882       {otp_6562_1,
5883        <<"otp_6562_1() ->
5884               Q = qlc:q([X || <<X:8>> <= <<\"hej\">>]),
5885               qlc:info(Q).
5886        ">>,
5887        [],
5888        {errors,[{2,qlc,binary_generator}],
5889         []}}
5890       ],
5891    [] = compile(Config, Bits),
5892
5893    R1 = {error,qlc,{1,qlc,binary_generator}}
5894             = qlc:string_to_handle("[X || <<X:8>> <= <<\"hej\">>]."),
5895    "1: cannot handle binary generators\n" =
5896             lists:flatten(qlc:format_error(R1)),
5897
5898    ok.
5899
5900%% OTP-6590. Bug fix (join info).
5901otp_6590(Config) when is_list(Config) ->
5902    Ts = [<<"fun(Tab1Value) ->
5903                    Q = qlc:q([T1#tab1.id || T1 <- [#tab1{id = id1,
5904                                                          value = v,
5905                                                          tab2_id = id}],
5906                                             T2 <- [#tab2{id = id}],
5907                                             T1#tab1.value =:= Tab1Value,
5908                                             T1#tab1.tab2_id =:= T2#tab2.id]),
5909                    [id1] = qlc:e(Q)
5910            end(v)">>],
5911
5912    run(Config, <<"-record(tab1, {id, tab2_id, value}).
5913                         -record(tab2, {id, value}).\n">>, Ts),
5914    ok.
5915
5916%% OTP-6673. Optimizations and fixes.
5917otp_6673(Config) when is_list(Config) ->
5918    Ts_PT =
5919        [<<"etsc(fun(E1) ->
5920                etsc(fun(E2) ->
5921                       Q = qlc:q([{A,B,C,D} ||
5922                                     {A,B} <- ets:table(E1),
5923                                     {C,D} <- ets:table(E2),
5924                                     A =:= 2, % lookup
5925                                     B =:= D, % join
5926                                     C =:= g]), % lookup invalidated by join
5927                       {qlc,_,[{generate,_,
5928                                {qlc,_,
5929                                 [{generate,_,
5930                                   {qlc,_,[{generate,_,
5931                                            {keysort,
5932                                             {list,{table,_},
5933                                              [{{'$1','$2'},[],['$_']}]},
5934                                             2,[]}},_],[]}},
5935                                  {generate,_,{qlc,_,
5936                                    [{generate,_,
5937                                      {keysort,{table,_},2,[]}}],
5938                                    []}},_],
5939                                 [{join,merge}]}},_,_],[]} = i(Q),
5940                       [{2,y,g,y}] = qlc:e(Q)
5941                     end, [{f,x},{g,y},{h,z}])
5942                 end,
5943                 [{1,x},{2,y},{3,z}])">>,
5944         <<"etsc(fun(E1) ->
5945                etsc(fun(E2) ->
5946                       Q = qlc:q([{A,B,C,D} ||
5947                                     {A,B} <- ets:table(E1),
5948                                     {C,D} <- ets:table(E2),
5949                                     A =:= 2, % lookup
5950                                     C =:= g, % lookup
5951                                     B =:= D]), % join
5952                       {qlc,_,[{generate,_,
5953                                {qlc,_,
5954                                 [{generate,_,
5955                                   {qlc,_,[{generate,_,
5956                                            {keysort,
5957                                             {list,{table,_},
5958                                              [{{'$1','$2'},[],['$_']}]},
5959                                             2,[]}},_],[]}},
5960                                  {generate,_,{qlc,_,
5961                                               [{generate,_,
5962                                                 {keysort,
5963                                                  {list,{table,_},
5964                                                   [{{'$1','$2'},[],['$_']}]},
5965                                                  2,[]}},_],[]}},_],
5966                                 [{join,merge}]}},_],[]} = i(Q),
5967                       [{2,y,g,y}] = qlc:e(Q)
5968                     end, [{f,x},{g,y},{h,z}])
5969                 end,
5970                 [{1,x},{2,y},{3,z}])">>],
5971
5972    run(Config, Ts_PT),
5973
5974    MS = ets:fun2ms(fun({X,_Y}=T) when X > 1 -> T end),
5975    Ts_RT = [
5976        [<<"%% Explicit match-spec. ets:table() ensures there is no lookup
5977            %% function, which means that lookup join will not be considered.
5978            MS = ">>, io_lib:format("~w", [MS]), <<",
5979            etsc(fun(E) ->
5980                         F = fun(J) ->
5981                                   qlc:q([{X,W} ||
5982                                             {X,_Y} <-
5983                                                 ets:table(E,{traverse,
5984                                                              {select,MS}}),
5985                                             {Z,W} <- [{1,1},{2,2},{3,3}],
5986                                             X =:= Z], {join,J})
5987                             end,
5988                         Qm = F(any),
5989                         [{2,2},{3,3}] = qlc:e(Qm),
5990                         {'EXIT',{cannot_carry_out_join,_}} =
5991                             (catch qlc:e(F(lookup)))
5992                 end, [{1,a},{2,b},{3,c}])">>],
5993
5994         <<"%% The filter 'A =< y' can be evaluated by traversing E1 using a
5995            %% match specification, but then lookup join cannot use E1 for
5996            %% looking up keys. This example shows that the filter is kept if
5997            %% lookup join is employed (otherwise it is optimized away since
5998            %% the match spec is used).
5999            etsc(fun(E1) ->
6000                         Q = qlc:q([{A,B,C,D} ||
6001                                       {A,B} <- ets:table(E1),
6002                                       {C,D} <- [{x,f},{y,g},{z,h}],
6003                                       A =< y, % kept
6004                                       A =:= C], {join,lookup}),
6005                         [{x,1,x,f},{y,2,y,g}] = lists:sort(qlc:e(Q))
6006                 end, [{x,1},{y,2},{z,3}])">>
6007
6008    ],
6009    run(Config, Ts_RT),
6010
6011    ok.
6012
6013%% OTP-6964. New option 'tmpdir_usage'.
6014otp_6964(Config) when is_list(Config) ->
6015    T1 = [
6016       <<"Q1 = qlc:q([{X} || X <- [1,2]]),
6017          {'EXIT', {badarg,_}} = (catch qlc:e(Q1, {tmpdir_usage,bad})),
6018          %% merge join
6019          F = fun(Use) ->
6020                      L1 = [{Y,a} || Y <- lists:seq(1, 2)],
6021                      L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
6022                      Q = qlc:q([{XX,YY} ||
6023                                    {XX,X} <- L1,
6024                                    {Y,YY} <- L2,
6025                                    X == Y],
6026                                {join,merge}),
6027                      qlc:e(Q, [{max_list_size,64*1024},{tmpdir_usage,Use}])
6028              end,
6029          D = erlang:system_flag(backtrace_depth, 0),
6030      try
6031          20000 = length(F(allowed)),
6032          ErrReply = F(not_allowed),
6033          {error, qlc, {tmpdir_usage,joining}} = ErrReply,
6034          \"temporary file was needed for joining\n\" =
6035              lists:flatten(qlc:format_error(ErrReply)),
6036          qlc_SUITE:install_error_logger(),
6037          20000 = length(F(warning_msg)),
6038          {warning, joining} = qlc_SUITE:read_error_logger(),
6039          20000 = length(F(info_msg)),
6040          {info, joining} = qlc_SUITE:read_error_logger(),
6041          20000 = length(F(error_msg)),
6042          {error, joining} = qlc_SUITE:read_error_logger()
6043      after
6044          _ = erlang:system_flag(backtrace_depth, D)
6045      end,
6046          qlc_SUITE:uninstall_error_logger()">>],
6047    run(Config, T1),
6048
6049    T2 = [
6050       <<"%% File sorter.
6051          T = lists:seq(1, 10000),
6052          Q0 = qlc:q([{X} || X <- [T,T,T], begin X > 0 end],
6053                     [{cache,list},unique]),
6054          Q1 = qlc:q([{X,Y,Z} ||
6055                         X <- Q0,
6056                         Y <- Q0,
6057                         Z <- Q0],
6058                     [{cache,list},unique]),
6059          Q = qlc:q([{X, Y} || Y <- [1], X <- Q1]),
6060          F = fun(Use) ->
6061                      qlc:e(Q, [{max_list_size,10000},{tmpdir_usage,Use}])
6062              end,
6063          1 = length(F(allowed)),
6064          ErrReply = F(not_allowed),
6065          {error, qlc, {tmpdir_usage,caching}} = ErrReply,
6066          \"temporary file was needed for caching\n\" =
6067              lists:flatten(qlc:format_error(ErrReply)),
6068          qlc_SUITE:install_error_logger(),
6069          1 = length(F(error_msg)),
6070          {error, caching} = qlc_SUITE:read_error_logger(),
6071          {error, caching} = qlc_SUITE:read_error_logger(),
6072          1 = length(F(warning_msg)),
6073          {warning, caching} = qlc_SUITE:read_error_logger(),
6074          {warning, caching} = qlc_SUITE:read_error_logger(),
6075          1 = length(F(info_msg)),
6076          {info, caching} = qlc_SUITE:read_error_logger(),
6077          {info, caching} = qlc_SUITE:read_error_logger(),
6078          qlc_SUITE:uninstall_error_logger()">>],
6079
6080    run(Config, T2),
6081
6082    T3 = [
6083       <<"%% sort/keysort
6084          E1 = create_ets(1, 10),
6085          E2 = create_ets(5, 50000),
6086          Q = qlc:q([{XX,YY} ||
6087                        {X,XX} <- ets:table(E1),
6088                        {YY,Y} <- ets:table(E2),
6089                        X == Y],
6090                    {join,merge}),
6091          F = fun(Use) ->
6092                      qlc:e(Q, {tmpdir_usage,Use})
6093              end,
6094          ErrReply = F(not_allowed),
6095          {error,qlc,{tmpdir_usage,sorting}} = ErrReply,
6096          \"temporary file was needed for sorting\n\" =
6097              lists:flatten(qlc:format_error(ErrReply)),
6098          qlc_SUITE:install_error_logger(),
6099          L = [{5,5},{6,6},{7,7},{8,8},{9,9},{10,10}],
6100          L = F(allowed),
6101          L = F(error_msg),
6102          {error, sorting} = qlc_SUITE:read_error_logger(),
6103          L = F(info_msg),
6104          {info, sorting} = qlc_SUITE:read_error_logger(),
6105          L = F(warning_msg),
6106          {warning, sorting} = qlc_SUITE:read_error_logger(),
6107          qlc_SUITE:uninstall_error_logger(),
6108          ets:delete(E1),
6109          ets:delete(E2)">>],
6110    run(Config, T3),
6111
6112    T4 = [
6113       <<"%% cache list
6114          etsc(fun(E) ->
6115                       Q0 = qlc:q([X || X <- ets:table(E),
6116                                        begin element(1, X) > 5 end],
6117                                  {cache,list}),
6118                       Q = qlc:q([{X, element(1,Y)} || X <- lists:seq(1, 5),
6119                                                       Y <- Q0]),
6120                       R = [{X,Y} || X <- lists:seq(1, 5),
6121                                     Y <- lists:seq(6, 10)],
6122                       F = fun(Use) ->
6123                                   qlc:e(Q, [{max_list_size, 100*1024},
6124                                             {tmpdir_usage, Use}])
6125                           end,
6126                       R = lists:sort(F(allowed)),
6127                       qlc_SUITE:install_error_logger(),
6128                       R = lists:sort(F(info_msg)),
6129                       {info, caching} = qlc_SUITE:read_error_logger(),
6130                       R = lists:sort(F(error_msg)),
6131                       {error, caching} = qlc_SUITE:read_error_logger(),
6132                       R = lists:sort(F(warning_msg)),
6133                       {warning, caching} = qlc_SUITE:read_error_logger(),
6134                       qlc_SUITE:uninstall_error_logger(),
6135                       ErrReply = F(not_allowed),
6136                       {error,qlc,{tmpdir_usage,caching}} = ErrReply,
6137                       \"temporary file was needed for caching\n\" =
6138                           lists:flatten(qlc:format_error(ErrReply))
6139               end, [{keypos,1}], [{I,a,lists:duplicate(100000,1)} ||
6140                                       I <- lists:seq(1, 10)])">>],
6141    run(Config, T4),
6142    ok.
6143
6144%% OTP-7238. info-option 'depth', &c.
6145otp_7238(Config) when is_list(Config) ->
6146    dets:start(),
6147    T = otp_7238,
6148    Fname = filename(T, Config),
6149
6150    ok = compile_gb_table(Config),
6151
6152    %% A few more warnings.
6153    T1 = [
6154       %% The same error message string, but with different tags
6155       %% (the strings are not compared :-(
6156       {nomatch_1,
6157        <<"nomatch_1() ->
6158               {qlc:q([X || X={X} <- []]), [t || \"a\"=\"b\" <- []]}.">>,
6159        [],
6160        %% {warnings,[{{2,30},qlc,nomatch_pattern},
6161        %%            {{2,44},v3_core,nomatch}]}},
6162        {warnings,[{2,v3_core,nomatch}]}},
6163
6164       %% Not found by qlc...
6165       {nomatch_2,
6166        <<"nomatch_2() ->
6167               qlc:q([t || {\"a\"++\"b\"} = {\"ac\"} <- []]).">>,
6168        [],
6169        {warnings,[{{2,22},v3_core,nomatch}]}},
6170
6171       {nomatch_3,
6172        <<"nomatch_3() ->
6173               qlc:q([t || [$a, $b] = \"ba\" <- []]).">>,
6174        [],
6175        %% {warnings,[{{2,37},qlc,nomatch_pattern}]}},
6176        {warnings,[{2,v3_core,nomatch}]}},
6177
6178       %% Not found by qlc...
6179       {nomatch_4,
6180        <<"nomatch_4() ->
6181               qlc:q([t || \"a\"++_=\"b\" <- []]).">>,
6182        [],
6183        {warnings,[{{2,22},v3_core,nomatch}]}},
6184
6185       %% Found neither by the compiler nor by qlc...
6186       {nomatch_5,
6187        <<"nomatch_5() ->
6188               qlc:q([X || X = <<X>> <- [3]]).">>,
6189        [],
6190        []},
6191
6192       {nomatch_6,
6193        <<"nomatch_6() ->
6194               qlc:q([X || X <- [],
6195                           X =:= {X}]).">>,
6196        [],
6197        %% {warnings,[{{3,30},qlc,nomatch_filter}]}},
6198        []},
6199
6200       {nomatch_7,
6201        <<"nomatch_7() ->
6202               qlc:q([X || {X=Y,{Y}=X} <- []]).">>,
6203        [],
6204        %% {warnings,[{{2,28},qlc,nomatch_pattern}]}},
6205        []},
6206
6207       {nomatch_8,
6208        <<"nomatch_8() ->
6209               qlc:q([X || {X={},X=[]} <- []]).">>,
6210        [],
6211        %% {warnings,[{{2,28},qlc,nomatch_pattern}]}},
6212        []},
6213
6214       {nomatch_9,
6215        <<"nomatch_9() ->
6216               qlc:q([X || X <- [], X =:= {}, X =:= []]).">>,
6217        [],
6218        %% {warnings,[{{2,49},qlc,nomatch_filter}]}},
6219        []},
6220
6221       {nomatch_10,
6222        <<"nomatch_10() ->
6223               qlc:q([X || X <- [],
6224                           ((X =:= 1) or (X =:= 2)) and (X =:= 3)]).">>,
6225        [],
6226        %% {warnings,[{{3,53},qlc,nomatch_filter}]}},
6227        []},
6228
6229       {nomatch_11,
6230        <<"nomatch_11() ->
6231               qlc:q([X || X <- [], x =:= []]).">>,
6232        [],
6233        %% {warnings,[{{2,39},qlc,nomatch_filter}]}},
6234        {warnings,[{2,sys_core_fold,nomatch_guard}]}},
6235
6236       {nomatch_12,
6237        <<"nomatch_12() ->
6238               qlc:q([X || X={} <- [], X =:= []]).">>,
6239        [],
6240        %% {warnings,[{{2,42},qlc,nomatch_filter}]}},
6241        []},
6242
6243       {nomatch_13,
6244        <<"nomatch_13() ->
6245               qlc:q([Z || Z <- [],
6246                           X={X} <- [],
6247                           Y={Y} <- []]).">>,
6248        [],
6249        %% {warnings,[{{3,29},qlc,nomatch_pattern},
6250        %%            {{4,29},qlc,nomatch_pattern}]}},
6251        []},
6252
6253       {nomatch_14,
6254        <<"nomatch_14() ->
6255               qlc:q([X || X={X} <- [],
6256                           1 > 0,
6257                           1 > X]).">>,
6258        [],
6259        %% {warnings,[{{2,29},qlc,nomatch_pattern}]}},
6260        []},
6261
6262       {nomatch_15,
6263        <<"nomatch_15() ->
6264              qlc:q([{X,Y} || X={X} <- [1],
6265                              Y <- [1],
6266                              1 > 0,
6267                              1 > X]).">>,
6268        [],
6269        %% {warnings,[{{2,32},qlc,nomatch_pattern}]}},
6270        []},
6271
6272       %% Template warning.
6273       {nomatch_template1,
6274        <<"nomatch_template1() ->
6275               qlc:q([{X} = {} || X <- []]).">>,
6276        [],
6277        {warnings,[{2,sys_core_fold,no_clause_match}]}}
6278         ],
6279    [] = compile(Config, T1),
6280
6281    %% 'depth' is a new option used by info()
6282    T2 = [
6283       %% Firstly: lists
6284       <<"L = [[a,b,c],{a,b,c},[],<<\"foobar\">>],
6285          Q = qlc:q([{X} || X <- L]),
6286          {call, _,
6287           {remote,_,{atom,_,ets},{atom,_,match_spec_run}},
6288           [{cons,_,{atom,_,'...'},
6289             {cons,_,{atom,_,'...'},
6290              {cons,_,{nil,_},{cons,_,{atom,_,'...'},{nil,_}}}}},
6291            _]} = qlc:info(Q, [{format,abstract_code},{depth,0}]),
6292
6293          {call,_,_,
6294           [{cons,_,{cons,_,{atom,_,'...'},{nil,_}},
6295             {cons,_,
6296              {tuple,_,[{atom,_,'...'}]},
6297              {cons,_,{nil,_},
6298               {cons,_,
6299                {bin,_,
6300                 [{_,_,{_,_,$.},_,_},
6301                  {_,_,{_,_,$.},_,_},
6302                  {_,_,{_,_,$.},_,_}]},
6303                {nil,_}}}}},
6304            _]} = qlc:info(Q, [{format,abstract_code},{depth,1}]),
6305
6306          {call,_,
6307           _,
6308          [{cons,_,{cons,_,{atom,_,a},{atom,_,'...'}},
6309            {cons,_,
6310             {tuple,_,[{atom,_,a},{atom,_,'...'}]},
6311             {cons,_,{nil,_},
6312              {cons,_,
6313               {bin,_,
6314                [{_,_,{_,_,$f},_,_},
6315                 {_,_,{_,_,$.},_,_},
6316                 {_,_,{_,_,$.},_,_},
6317                 {_,_,{_,_,$.},_,_}]},
6318               {nil,_}}}}},
6319          _]} = qlc:info(Q, [{format,abstract_code},{depth,2}]),
6320
6321          {call,_,_,
6322           [{cons,_,
6323             {cons,_,{atom,_,a},{cons,_,{atom,_,b},{atom,_,'...'}}},
6324             {cons,_,
6325              {tuple,_,[{atom,_,a},{atom,_,b},{atom,_,'...'}]},
6326              {cons,_,{nil,_},
6327               {cons,_,
6328                {bin,_,
6329                 [{_,_,{_,_,$f},_,_},
6330                  {_,_,{_,_,$o},_,_},_,_,_]},
6331                {nil,_}}}}},
6332            _]} = qlc:info(Q, [{format,abstract_code},{depth,3}]),
6333
6334          {call,_,_,
6335           [{cons,_,
6336             {cons,_,
6337              {atom,_,a},{cons,_,{atom,_,b},{cons,_,{atom,_,c},{nil,_}}}},
6338             {cons,_,
6339              {tuple,_,[{atom,_,a},{atom,_,b},{atom,_,c}]},
6340              {cons,_,{nil,_},
6341               {cons,_,
6342                {bin,_,
6343                 [{_,_,{_,_,$f},_,_},
6344                  {_,_,{_,_,$o},_,_},
6345                  {_,_,{_,_,$o},_,_},
6346                  {_,_,{_,_,$b},_,_},
6347                  {_,_,{_,_,$a},_,_},
6348                  {_,_,{_,_,$r},_,_}]},
6349                {nil,_}}}}},
6350            _]} = qlc:info(Q, [{format,abstract_code},{depth,10}]),
6351
6352          {call,_,_,
6353           [{cons,_,
6354             {cons,_,
6355              {atom,_,a},{cons,_,{atom,_,b},{cons,_,{atom,_,c},{nil,_}}}},
6356             {cons,_,
6357              {tuple,_,[{atom,_,a},{atom,_,b},{atom,_,c}]},
6358              {cons,_,{nil,_},
6359               {cons,_,
6360                {bin,_,
6361                 [{_,_,{_,_,$f},_,_},
6362                  {_,_,{_,_,$o},_,_},
6363                  {_,_,{_,_,$o},_,_},
6364                  {_,_,{_,_,$b},_,_},
6365                  {_,_,{_,_,$a},_,_},
6366                  {_,_,{_,_,$r},_,_}]},
6367                {nil,_}}}}},
6368            _]} = qlc:info(Q, [{format,abstract_code},{depth,infinity}])">>,
6369
6370       %% Secondly: looked up keys
6371       <<"F = fun(D) ->
6372                etsc(fun(E) ->
6373                       Q = qlc:q([C || {N,C} <- ets:table(E),
6374                                       (N =:= {2,2}) or (N =:= {3,3})]),
6375                       F = qlc:info(Q, [{format,abstract_code},{depth,D}]),
6376                       {call,_,_,[{call,_,_,[_Fun,Values]},_]} = F,
6377                       [b,c] = lists:sort(qlc:eval(Q)),
6378                       Values
6379                     end, [{{1,1},a},{{2,2},b},{{3,3},c},{{4,4},d}])
6380              end,
6381
6382          [{cons,_,{atom,_,'...'},{cons,_,{atom,_,'...'},{nil,_}}},
6383           {cons,_,
6384            {tuple,_,[{atom,_,'...'}]},
6385            {cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}},
6386           {cons,_,
6387            {tuple,_,[{integer,_,2},{atom,_,'...'}]},
6388            {cons,_,{tuple,_,[{integer,_,3},{atom,_,'...'}]},{nil,_}}},
6389           {cons,_,
6390            {tuple,_,[{integer,_,2},{integer,_,2}]},
6391            {cons,_,{tuple,_,[{integer,_,3},{integer,_,3}]},{nil,_}}},
6392           {cons,_,
6393            {tuple,_,[{integer,_,2},{integer,_,2}]},
6394            {cons,_,{tuple,_,[{integer,_,3},{integer,_,3}]},{nil,_}}}] =
6395              lists:map(F, [0,1,2,3,infinity])">>,
6396       [<<"T = otp_7238, Fname = \"">>, Fname, <<"\",
6397           {ok, _} = dets:open_file(T, [{file,Fname}]),
6398           ok = dets:insert(T, [{{1,1},a},{{2,2},b},{{3,3},c},{{4,4},d}]),
6399           Q = qlc:q([C || {N,C} <- dets:table(T),
6400                           (N =:= {2,2}) or (N =:= {3,3})]),
6401           F = qlc:info(Q, [{format,abstract_code},{depth,1}]),
6402           [b,c] = lists:sort(qlc:eval(Q)),
6403           {call,_,_,
6404            [{call,_,_,
6405              [_,
6406               {cons,_,
6407                {tuple,_,[{atom,_,'...'}]},
6408                {cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}}]},
6409             _]} = F,
6410           ok = dets:close(T),
6411           file:delete(\"">>, Fname, <<"\")">>],
6412
6413       %% Thirdly: format_fun has been extended (in particular: gb_table)
6414       <<"T = gb_trees:from_orddict([{{1,a},w},{{2,b},v},{{3,c},u}]),
6415          QH = qlc:q([X || {{X,Y},_} <- gb_table:table(T),
6416                           ((X =:= 1) or (X =:= 2)),
6417                           ((Y =:= a) or (Y =:= b) or (Y =:= c))]),
6418          {call,_,_,
6419           [{call,_,_,
6420             [{'fun',_,
6421               {clauses,
6422                [{clause,_,_,[],
6423                  [{'case',_,
6424                    {call,_,_,
6425                     [_,
6426                      {call,_,_,
6427                       [{cons,_,
6428                         {tuple,_,[{atom,_,'...'}]},
6429                         {cons,_,
6430                          {tuple,_,[{atom,_,'...'}]},
6431                          {cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}}}]}]},
6432                    [_,_]}]}]}},
6433              {cons,_,
6434               {tuple,_,[{atom,_,'...'}]},
6435               {cons,_,
6436                {tuple,_,[{atom,_,'...'}]},
6437                {cons,_,
6438                 {tuple,_,[{atom,_,'...'}]},
6439                 {cons,_,
6440                  {tuple,_,[{atom,_,'...'}]},
6441                  {cons,_,
6442                   {tuple,_,[{atom,_,'...'}]},
6443                   {cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}}}}}}]},
6444            {call,_,_,
6445             [{cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}]}]} =
6446            qlc:info(QH, [{format,abstract_code},{depth,1}])">>,
6447       <<"T1 = [{1,1,a},{2,2,b},{3,3,c},{4,4,d}],
6448          T2 = [{x,1},{y,1},{z,2}],
6449          QH1 = T1,
6450          T = gb_trees:from_orddict(T2),
6451          QH2 = qlc:q([X || {_,X} <- gb_table:table(T)], cache),
6452          Q = qlc:q([{X1,X2,X3} || {X1,X2,X3} <- QH1,
6453                                   Y2 <- QH2,
6454                                   X2 =:= Y2]),
6455          {block,_,
6456           [{match,_,_,
6457             {call,_,_,
6458              [{lc,_,_,
6459                [{generate,_,_,
6460                  {call,_,_,
6461                   [{call,_,_,
6462                     [{cons,_,
6463                       {tuple,_,[{atom,_,'...'}]},
6464                       {atom,_,'...'}}]}]}}]},
6465               _]}},
6466            {call,_,_,
6467             [{lc,_,_,
6468               [{generate,_,_,
6469                 {cons,_,{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}}},
6470                _,_]}]}]} =
6471              qlc:info(Q, [{format,abstract_code},{depth, 1},
6472                           {n_elements,1}])">>,
6473       <<"L = [{{key,1},a},{{key,2},b},{{key,3},c}],
6474          T = gb_trees:from_orddict(orddict:from_list(L)),
6475          Q = qlc:q([K || {K,_} <- gb_table:table(T),
6476                                   (K =:= {key,1}) or (K =:= {key,2})]),
6477{call,_,_,
6478 [{call,_,_,
6479   [{'fun',_,
6480     {clauses,
6481      [{clause,_,_,[],
6482        [{'case',_,
6483          {call,_,_,
6484           [_,
6485            {call,_,_,
6486             [{cons,_,
6487               {tuple,_,[{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}]},
6488               {cons,_,
6489                {tuple,_,[{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}]},
6490                {cons,_,
6491                 {tuple,_,[{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}]},
6492                 {nil,_}}}}]}]},
6493          _}]}]}},
6494    {cons,_,
6495     {tuple,_,[{atom,_,key},{atom,_,'...'}]},
6496     {cons,_,{tuple,_,[{atom,_,key},{atom,_,'...'}]},{nil,_}}}]},
6497  {call,_,
6498   {remote,_,{atom,_,ets},{atom,_,match_spec_compile}},
6499   [{cons,_,
6500     {tuple,_,[{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}]},
6501     {nil,_}}]}]} =
6502          qlc:info(Q, [{format,abstract_code},{depth, 2}])">>
6503
6504         ],
6505    run(Config, T2),
6506
6507    T3 = [
6508%%        {nomatch_6,
6509%%         <<"nomatch_6() ->
6510%%                qlc:q([X || X <- [],
6511%%                            X =:= {X}]).">>,
6512%%         [],
6513%%         {[],["filter evaluates to 'false'"]}},
6514
6515%%        {nomatch_7,
6516%%         <<"nomatch_7() ->
6517%%                qlc:q([X || {X=Y,{Y}=X} <- []]).">>,
6518%%         [],
6519%%         {[],["pattern cannot possibly match"]}}
6520       ],
6521    compile_format(Config, T3),
6522
6523    %% *Very* simple test - just check that it doesn't crash.
6524    Type = [{cres,
6525             <<"Q = qlc:q([X || {X} <- []]),
6526                {'EXIT',{{badfun,_},_}} = (catch qlc:e(Q))">>,
6527             [type_checker],
6528             []}],
6529    run(Config, Type),
6530
6531    ok.
6532
6533%% OTP-7114. Match spec, table and duplicated objects...
6534otp_7114(Config) when is_list(Config) ->
6535    Ts = [<<"T = ets:new(t, [bag]),
6536             [ets:insert(T, {t, I, I div 2}) || I <- lists:seq(1,10)],
6537             Q1 = qlc:q([element(3, E) || E <- ets:table(T)]),
6538             [0,1,1,2,2,3,3,4,4,5] = lists:sort(qlc:e(Q1)),
6539             [0,1,2,3,4,5] = qlc:e(Q1, unique_all),
6540             [0,1,2,3,4,5] = qlc:e(qlc:sort(Q1), unique_all),
6541             [0,1,2,3,4,5] = qlc:e(qlc:sort(qlc:e(Q1)), unique_all),
6542             ets:delete(T),
6543             ok">>],
6544    run(Config, Ts).
6545
6546%% OTP-7232. qlc:info() bug (pids, ports, refs, funs).
6547otp_7232(Config) when is_list(Config) ->
6548    Ts = [<<"L = [fun math:sqrt/1, list_to_pid(\"<0.4.1>\"),
6549                  erlang:make_ref()],
6550             \"[fun math:sqrt/1, <0.4.1>, #Ref<\" ++ _  = qlc:info(L),
6551             {call,_,
6552               {remote,_,{atom,_,qlc},{atom,_,sort}},
6553               [{cons,_,
6554                      {'fun',_,{function,{atom,_,math},{atom,_,sqrt},_}},
6555                      {cons,_,
6556                            {string,_,\"<0.4.1>\"}, % could use list_to_pid..
6557                            {cons,_,{string,_,\"#Ref<\"++_},{nil,_}}}},
6558                {nil,_}]} =
6559              qlc:info(qlc:sort(L),{format,abstract_code})">>,
6560
6561          <<"Q1 = qlc:q([X || X <- [55296,56296]]),
6562             Q = qlc:sort(Q1, {order, fun(A,B)-> A>B end}),
6563             \"qlc:sort([55296,56296],[{order,fun'-function/0-fun-2-'/2}])\" =
6564                format_info(Q, true),
6565             AC = qlc:info(Q, {format, abstract_code}),
6566             \"qlc:sort([55296, 56296], [{order, fun '-function/0-fun-2-'/2}])\" =
6567                binary_to_list(iolist_to_binary(erl_pp:expr(AC)))">>,
6568
6569         %% OTP-7234. erl_parse:abstract() handles bit strings
6570          <<"Q = qlc:sort([<<17:9>>]),
6571             \"[<<8,1:1>>]\" = qlc:info(Q)">>
6572
6573         ],
6574    run(Config, Ts).
6575
6576%% OTP-7552. Merge join bug.
6577otp_7552(Config) when is_list(Config) ->
6578    %% The poor performance cannot be observed unless the
6579    %% (redundant) join filter is skipped.
6580    Ts = [<<"Few = lists:seq(1, 2),
6581             Many = lists:seq(1, 10),
6582             S = [d,e],
6583             L1 = [{Y,a} || Y <- Few] ++ [{'1b',b},{2,b}] ++
6584                    [{Y,X} || X <- S, Y <- Few],
6585             L2 = [{a,Y} || Y <- Many] ++
6586                    [{b,'1b'}] ++ [{c,1}] ++
6587                    [{X,Y} || X <- S, Y <- Many],
6588                   F = fun(J) ->
6589                               qlc:q([{XX,YY} ||
6590                                         {XX,X} <- L1,
6591                                         {Y,YY} <- L2,
6592                                         X == Y],
6593                                     {join,J})
6594                       end,
6595                   Qm = F(merge),
6596                   Qn = F(nested_loop),
6597                   true = lists:sort(qlc:e(Qm, {max_list_size,20})) =:=
6598                          lists:sort(qlc:e(Qn))">>],
6599    run(Config, Ts).
6600
6601%% OTP-7714. Merge join bug.
6602otp_7714(Config) when is_list(Config) ->
6603    %% The original example uses Mnesia. This one does not.
6604    Ts = [<<"E1 = ets:new(set,[]),
6605             true = ets:insert(E1, {a,1}),
6606             E2 = ets:new(set,[]),
6607             _ = [true = ets:insert(E2, {I, 1}) ||
6608                     I <- lists:seq(1, 3)],
6609             Q = qlc:q([{A,B} ||
6610                           {A,I1} <- ets:table(E1),
6611                           {B,I2} <- ets:table(E2),
6612                           I1 =:= I2],{join,merge}),
6613             [{a,1},{a,2},{a,3}] = lists:sort(qlc:e(Q)),
6614             ets:delete(E1),
6615             ets:delete(E2)">>],
6616    run(Config, Ts).
6617
6618%% OTP-11758. Bug.
6619otp_11758(Config) when is_list(Config) ->
6620    Ts = [<<"T = ets:new(r, [{keypos, 2}]),
6621             L = [{rrr, xxx, aaa}, {rrr, yyy, bbb}],
6622             true = ets:insert(T, L),
6623             QH = qlc:q([{rrr, B, C} || {rrr, B, C} <- ets:table(T),
6624                              (B =:= xxx) or (B =:= yyy) and (C =:= aaa)]),
6625             [{rrr,xxx,aaa}] = qlc:e(QH),
6626             ets:delete(T)">>],
6627    run(Config, Ts).
6628
6629%% OTP-6674. match/comparison.
6630otp_6674(Config) when is_list(Config) ->
6631
6632    ok = compile_gb_table(Config),
6633
6634    Ts = [%% lookup join
6635          <<"E = ets:new(join, [ordered_set]),
6636             true = ets:insert(E, [{1,a},{2,b},{3,c}]),
6637             Q = qlc:q([{X, Y} || {X,_} <- ets:table(E),
6638                                  {Y} <- [{0},{1},{2}],
6639                                  X == Y]),
6640             {0,1,0,0} = join_info(Q),
6641             [{1,1},{2,2}] = qlc:e(Q),
6642             ets:delete(E)">>,
6643
6644          <<"E = ets:new(join, [ordered_set]),
6645             true = ets:insert(E, [{1,a},{2,b},{3,c}]),
6646             Q = qlc:q([{X, Y} || {X,_} <- ets:table(E),
6647                                  {Y} <- [{0},{1},{2}],
6648                                  X =:= Y]),
6649             {0,1,0,0} = join_info(Q),
6650             {block,_,
6651              [_,
6652               {match,_,_,
6653                 {call,_,_,
6654                  [{lc,_,_,
6655                    [_,_,{op,_,'==',_,_}]},
6656                   {cons,_,
6657                    {tuple,_,[{atom,_,join},{atom,_,lookup}]},_}]}},
6658               _]} = qlc:info(Q, {format, abstract_code}),
6659             [{1,1},{2,2}] = qlc:e(Q),
6660             ets:delete(E)">>,
6661
6662       <<"E = ets:new(join, [set]),
6663          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E),
6664                               {Y} <- [{0},{1},{2}],
6665                               X == Y], {join, lookup}),
6666          {'EXIT',{cannot_carry_out_join,_}} = (catch qlc:e(Q)),
6667          ets:delete(E)">>,
6668
6669       %% Lookup join possible in both directions.
6670       <<"E1 = ets:new(join, [ordered_set]),
6671          E2 = ets:new(join, [set]),
6672          true = ets:insert(E1, [{1.0,a},{2,b},{3,c}]),
6673          true = ets:insert(E2, [{0},{1},{2}]),
6674          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E1),
6675                               {Y} <- ets:table(E2),
6676                               X == Y],{join,lookup}), % skipped
6677          {qlc,_,
6678            [{generate,_,
6679                 {qlc,_,
6680                     [{generate,_,
6681                          {qlc,_,[{generate,_,{table,{ets,table,[_]}}}],[]}},
6682                      {generate,_,{table,{ets,table,[_]}}},
6683                      _],
6684                     [{join,lookup}]}}],
6685            []} = qlc:info(Q, {format,debug}),
6686          {0,1,0,0} = join_info(Q),
6687          [{1.0,1},{2,2}] = lists:sort(qlc:e(Q)),
6688          ets:delete(E1),
6689          ets:delete(E2)">>,
6690       <<"E1 = ets:new(join, [ordered_set]),
6691          E2 = ets:new(join, [set]),
6692          true = ets:insert(E1, [{1.0,a},{2,b},{3,c}]),
6693          true = ets:insert(E2, [{0},{1},{2}]),
6694          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E1),
6695                               {Y} <- ets:table(E2),
6696                               X =:= Y],{join,merge}), % not skipped
6697          {1,0,0,1} = join_info(Q),
6698          [{2,2}] = qlc:e(Q),
6699          ets:delete(E1),
6700          ets:delete(E2)">>,
6701       <<"E1 = ets:new(join, [ordered_set]),
6702          E2 = ets:new(join, [set]),
6703          true = ets:insert(E1, [{1.0,a},{2,b},{3,c}]),
6704          true = ets:insert(E2, [{0},{1},{2}]),
6705          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E1),
6706                               {Y} <- ets:table(E2),
6707                               X =:= Y],{join,lookup}), % skipped
6708          {qlc,_,
6709           [{generate,_,
6710             {qlc,_,
6711              [{generate,_,
6712                {qlc,_,
6713                 [{generate,_,{table,{ets,table,[_]}}}],
6714                 []}},
6715               {generate,_,{table,{ets,table,[_]}}},
6716               _],
6717              [{join,lookup}]}}],
6718            []} = qlc:info(Q, {format,debug}),
6719          {0,1,0,0} = join_info(Q),
6720          [{2,2}] = qlc:e(Q),
6721          ets:delete(E1),
6722          ets:delete(E2)">>,
6723       <<"E1 = ets:new(join, [ordered_set]),
6724          E2 = ets:new(join, [set]),
6725          true = ets:insert(E1, [{1.0,a},{2,b},{3,c}]),
6726          true = ets:insert(E2, [{0},{1},{2}]),
6727          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E1),
6728                               {Y} <- ets:table(E2),
6729                               %% Independent of term comparison:
6730                               X =:= Y, X == Y]),
6731          {0,1,0,0} = join_info(Q),
6732          [{2,2}] = qlc:e(Q),
6733          ets:delete(E1),
6734          ets:delete(E2)">>,
6735
6736       <<"E = ets:new(join, [ordered_set]),
6737          true = ets:insert(E, [{1,1},{2,2},{3,c}]),
6738          Q = qlc:q([{X, Y} || {X,Z} <- ets:table(E),
6739                               {Y} <- [{0},{1},{2}],
6740                               X == Z, Y == Z]), % cannot skip (yet)
6741          {qlc,_,
6742            [{generate,_,
6743                 {qlc,_,[_,_,_],[{join,lookup}]}},
6744             _,_],[]} = qlc:info(Q,{format,debug}),
6745          {0,1,0,0} = join_info(Q),
6746          [{1,1},{2,2}] = qlc:e(Q),
6747          ets:delete(E)">>,
6748
6749       %% The following moved here from skip_filters. It was buggy!
6750       <<"etsc(fun(E) ->
6751                 A = 3,
6752                 Q = qlc:q([X || X <- ets:table(E),
6753                                 A == element(1,X)]),
6754                 {table, _} = i(Q),
6755                 case qlc:e(Q) of
6756                       [{3},{3.0}] -> ok;
6757                       [{3.0},{3}] -> ok
6758                 end,
6759                 false = lookup_keys(Q)
6760         end, [{3},{3.0},{c}])">>,
6761    <<"H1 = qlc:sort([{{192,192.0},1,a},{{192.0,192.0},2,b},{{192,192.0},3,c}]),
6762       Q = qlc:q([{X, Y} || {{A,B},X,_} <- H1, % does not need keysort(3)
6763                            A == 192, B =:= 192.0,
6764                            {Y} <- [{0},{1},{2}],
6765                            X == Y]),
6766       A0 = erl_anno:new(0),
6767       {block,A0,
6768         [{match,_,_,
6769           {call,_,_,
6770            [{lc,_,_,
6771              [_,
6772               %% Has to compare extra constant:
6773               {op,_,'==',
6774                {tuple,_,[{integer,_,192},{float,_,192.0}]},
6775                {call,_,{atom,_,element},[{integer,_,1},{var,_,'P0'}]}}]}]}},
6776          _,_,
6777          {call,_,_,
6778           [{lc,_,_,
6779             [_,
6780              %% The join filter has been skipped.
6781              {op,_,'==',{var,_,'A'},{integer,_,192}},
6782              {op,_,'=:=',{var,_,'B'},{float,_,192.0}}]}]}]}
6783      = qlc:info(Q, {format,abstract_code}),
6784       {1,0,0,1} = join_info(Q),
6785       [{1,1},{2,2}] = qlc:e(Q)">>,
6786
6787    %% Does not handle more than one lookup value (conjunctive).
6788    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6789       H = qlc:q([X || {X,_} <- gb_table:table(T),
6790                                X =:= 1 andalso X == 1.0]),
6791       false = lookup_keys(H),
6792       [1] = qlc:e(H)">>,
6793
6794    %% EqualConstants...
6795    <<"etsc(fun(E) ->
6796                Q = qlc:q([{X,Y} || {X} <- ets:table(E),
6797                                {Y} <- [{{1}},{{2}},{{1.0}},{{2.0}}],
6798                                X =:= {1}, X == {1.0},
6799                                X == Y], {join, merge}),
6800                [{{1},{1}},{{1},{1.0}}] = lists:sort(qlc:e(Q)),
6801                false = lookup_keys(Q)
6802         end, [{{1}}, {{2}}])">>,
6803
6804    <<"T = gb_trees:from_orddict([{foo,{1}}, {bar,{2}}]),
6805       Q = qlc:q([{X,Y} || {_,X} <- gb_table:table(T),
6806                       {Y} <- [{{1}},{{2}},{{1.0}},{{2.0}}],
6807                         (X =:= {1}) or (X == {2}),
6808                         (X == {1.0}) or (X =:= {2.0}),
6809                       X == Y], {join, merge}),
6810       [{{1},{1}},{{1},{1.0}}] = qlc:e(Q)">>,
6811
6812    %% Compare key
6813    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6814       H = qlc:q([X || {X,_} <- gb_table:table(T),
6815                       X == 1]),
6816       [1] = lookup_keys(H),
6817       [1] = qlc:e(H)">>,
6818    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6819       H = qlc:q([X || {X,_} <- gb_table:table(T),
6820                       X == 1.0]),
6821       [1.0] = lookup_keys(H), % this is how gb_table works...
6822       [1.0] = qlc:e(H)">>,
6823    <<"etsc(fun(E) ->
6824                   H = qlc:q([X || {X,_} <- ets:table(E),
6825                                   X == 1.0]),
6826                   [1] = qlc:e(H), % and this is how ETS works.
6827                   [1.0] = lookup_keys(H)
6828           end, [ordered_set], [{1,a},{2,b}])">>,
6829
6830    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6831       H = qlc:q([X || {X,_} <- gb_table:table(T),
6832                       X =:= 2]),
6833       [2] = lookup_keys(H),
6834       %% Cannot (generally) remove the matching filter (the table
6835       %% compares the key). But note that gb_table returns the given
6836       %% term as key, so in this case the filter _could_ have been removed.
6837       %% However, there is no callback to inform qlc about that.
6838       {call,_,_,
6839             [_,{call,_,_,
6840               [{cons,_,{tuple,_,
6841                  [_,{cons,_,
6842                    {tuple,_,[{atom,_,'=:='},{atom,_,'$1'},{integer,_,2}]},
6843                    _},_]},_}]}]} =  qlc:info(H, {format,abstract_code}),
6844       [2] = qlc:e(H)">>,
6845    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6846       H = qlc:q([X || {X,_} <- gb_table:table(T),
6847                       X =:= 2.0]),
6848       %% Just shows that the term (not the key) is returned.
6849       [2.0] = lookup_keys(H),
6850       [2.0] = qlc:e(H)">>,
6851
6852    <<"I = 1,
6853       T = gb_trees:from_orddict([{1,a},{2,b}]),
6854       H = qlc:q([X || {X,_} <- gb_table:table(T),
6855                       X == I]), % imported variable
6856       [1] = lookup_keys(H),
6857       {call,_,_,
6858             [_,{call,_,_,
6859               [{cons,_,
6860                 {tuple,_,
6861                  [{tuple,_,[{atom,_,'$1'},{atom,_,'_'}]},
6862                   {nil,_}, % the filter has been skipped
6863                   {cons,_,{atom,_,'$1'},_}]},
6864                 _}]}]} = qlc:info(H, {format, abstract_code}),
6865       [1] = qlc:e(H)">>,
6866    <<"I = 2,
6867       T = gb_trees:from_orddict([{1,a},{2,b}]),
6868       H = qlc:q([X || {X,_} <- gb_table:table(T),
6869                       X =:= I]),
6870       [2] = lookup_keys(H),
6871       {call,_,_,
6872            [_,{call,_,_,
6873              [{cons,_,{tuple,_,
6874                 [_,{cons,_,
6875                   {tuple,_,
6876                    [{atom,_,'=:='},
6877                     {atom,_,'$1'},
6878                     {tuple,_,[{atom,_,const},{integer,_,2}]}]},
6879                   _},_]},
6880                _}]}]} = qlc:info(H, {format, abstract_code}),
6881          [2] = qlc:e(H)">>,
6882
6883    <<"etsc(fun(E) ->
6884                 Q = qlc:q([X || {X,_} <- ets:table(E),
6885                                 X =:= a]), % skipped
6886                 [a] = qlc:e(Q),
6887                 {list,{table,_},_} = i(Q),
6888                 [a] = lookup_keys(Q)
6889            end, [ordered_set], [{a,1},{b,2},{3,c}])">>,
6890
6891    %% Does not find that if for instance X =:= {1} then the filter
6892    %% X == {1} can be removed.
6893    <<"etsc(fun(E) ->
6894                Q = qlc:q([X || {X} <- ets:table(E),
6895                                X =:= {1}, X == {1.0}]),
6896                [{1}] = qlc:e(Q),
6897                [{1}] = lookup_keys(Q)
6898         end, [{{1}}, {{2}}])">>,
6899    <<"etsc(fun(E) ->
6900                Q = qlc:q([X || {X} <- ets:table(E),
6901                                X =:= {1}, X == {1.0}]),
6902                [{1}] = qlc:e(Q),
6903                false = lookup_keys(Q)
6904         end, [ordered_set], [{{1}}, {{2}}])">>,
6905    <<"etsc(fun(E) ->
6906                Q = qlc:q([X || {X} <- ets:table(E),
6907                                X == {1.0}, X =:= {1}]),
6908                [{1}] = qlc:e(Q),
6909                [{1}] = lookup_keys(Q)
6910         end, [{{1}}, {{2}}])">>,
6911    <<"etsc(fun(E) ->
6912                Q = qlc:q([X || {X} <- ets:table(E),
6913                                X == {1.0}, X =:= {1}]),
6914                [{1}] = qlc:e(Q),
6915                false = lookup_keys(Q)
6916         end, [ordered_set], [{{1}}, {{2}}])">>,
6917
6918    <<"E = ets:new(apa, []),
6919       true = ets:insert(E, [{1,a},{2,b}]),
6920       {'EXIT', {badarg, _}} =
6921              (catch qlc_SUITE:bad_table_key_equality(E)),
6922       ets:delete(E)">>,
6923
6924    <<"etsc(fun(E) ->
6925           Q = qlc:q([X || {X} <- ets:table(E),
6926                               X =:= 1, X =:= is_integer(X)]),
6927           [] = qlc:e(Q),
6928           [1] = lookup_keys(Q)
6929       end, [{1}, {2}])">>,
6930
6931    <<"etsc(fun(E) ->
6932                 Q = qlc:q([X || {X=1} <- ets:table(E),
6933                                 X =:= is_integer(X)]),
6934                 {call,_,_,
6935                  [{lc,_,_,
6936                    [_,
6937                     {op,_,'=:=',
6938                      {var,_,'X'},
6939                      {call,_,
6940                       {atom,_,is_integer},
6941                       [{var,_,'X'}]}}]}]} =
6942             qlc:info(Q, {format, abstract_code}),
6943             [] = qlc:e(Q),
6944             [1] = lookup_keys(Q)
6945         end, [{1}, {2}])">>,
6946
6947    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6948       H = qlc:q([X || {X,Y} <- gb_table:table(T),
6949                                Y =:= a, true, X =:= 1]),
6950       [1] = lookup_keys(H),
6951       [1] = qlc:e(H)">>,
6952
6953    <<"T = gb_trees:from_orddict([{{1.0,1},a},{{2.0,2},b}]),
6954       H = qlc:q([X || {{1.0,B}=X,_} <- gb_table:table(T),
6955                       B == 1]), % skipped
6956       [{1.0, 1}] = qlc:e(H),
6957       {qlc,_,[{generate,_,{table,_}}], []} = qlc:info(H, {format,debug})">>,
6958    <<"T = gb_trees:from_orddict([{{1.0,1},a},{{2.0,2},b}]),
6959       H = qlc:q([X || {{1.0,B}=X,_} <- gb_table:table(T),
6960                    B == 1.0]), % skipped
6961       [{1.0, 1.0}] = qlc:e(H), % this is how gb_table works...
6962       {qlc,_,[{generate,_,{table,_}}], []} = qlc:info(H, {format,debug})">>,
6963    <<"T = gb_trees:from_orddict([{{1.0,1},a},{{2.0,2},b}]),
6964       H = qlc:q([X || {{1.0,B}=X,_} <- gb_table:table(T),
6965                       B =:= 1.0]), % not skipped
6966       [{1.0, 1.0}] = qlc:e(H),
6967       {qlc,_,[{generate,_,{table,_}},_], []} = qlc:info(H,{format,debug})">>,
6968    <<"T = gb_trees:from_orddict([{{1.0,1},a},{{2.0,2},b}]),
6969       H = qlc:q([X || {{1.0,B}=X,_} <- gb_table:table(T),
6970                       B =:= 1]), % not skipped
6971       [{1.0, 1}] = qlc:e(H),
6972       {qlc,_,[{generate,_,{table,_}},_], []} = qlc:info(H,{format,debug})">>,
6973
6974    <<"%% The imported variables do not interfere with join.
6975       E = ets:new(join, [ordered_set]),
6976       {A, B} = {1,1},
6977       true = ets:insert(E, [{1,a},{2,b},{3,c}]),
6978       Q = qlc:q([{X, Y} || {X,_Z} <- ets:table(E),
6979                            {Y} <- [{0},{1},{2}],
6980                            X =:= A, Y =:= B,
6981                            Y == X], % skipped
6982                {join, merge}),
6983       [{1,1}] = qlc:e(Q),
6984       {qlc,_,
6985           [{generate,_,
6986             {qlc,_,
6987              [{generate,_,
6988                {qlc,_,[{generate,_,{list,{table,_},_}},_],[]}},
6989               {generate,_,
6990                {qlc,_,[{generate,_,{list,_,_}},_],[]}},
6991               _],
6992              [{join,merge}]}}],
6993           []} = qlc:info(Q, {format, debug}),
6994       ets:delete(E)">>,
6995
6996    <<"% An old bug: usort() should not be used when matching values
6997       etsc(fun(E) ->
6998                   I = 1,
6999                   H = qlc:q([X || {X,_} <- ets:table(E),
7000                                   X =:= 1.0 orelse X =:= I]),
7001                   [1] = qlc:e(H),
7002                   [1.0] = lookup_keys(H) % do not look up twice
7003            end, [set], [{1,a},{2,b}])">>,
7004    <<"etsc(fun(E) ->
7005                   H = qlc:q([X || {X,_} <- ets:table(E),
7006                                    X =:= 1.0 orelse X == 1]),
7007                   [1] = qlc:e(H),
7008                   false = lookup_keys(H) % doesn't handle this case
7009         end, [ordered_set], [{1,a},{2,b}])">>,
7010
7011    <<"etsc(fun(E) ->
7012                 I1 = 1, I2 = 1,
7013                 H = qlc:q([X || {X,_} <- ets:table(E),
7014                                 X =:= I1 orelse X == I2]),
7015                 [1] = qlc:e(H), % do not look up twice
7016                 [1] = lookup_keys(H)
7017         end, [ordered_set], [{1,a},{2,b}])">>,
7018
7019    <<"etsc(fun(E) ->
7020                 I1 = 1, I2 = 1, I3 = 1,
7021                 H = qlc:q([X || {X,_} <- ets:table(E),
7022                                 I1 == I2, I1 =:= I3, I3 == I2, I2 =:= I3,
7023                                 X =:= I1 orelse X == I2
7024                                 ]),
7025                 [1] = qlc:e(H),
7026                 [1] = lookup_keys(H)
7027         end, [ordered_set], [{1,a},{2,b}])">>,
7028
7029    <<"E = ets:new(join, [ordered_set]),
7030       true = ets:insert(E, [{1,a},{2,b,x},{3,c}]),
7031       Q = qlc:q([P || P <- ets:table(E),
7032                       P =:= {1,a} orelse P =:= {2,b,x}]),
7033       [{1,a},{2,b,x}] = qlc:e(Q),
7034       ets:delete(E)">>,
7035
7036    <<"etsc(fun(E) ->
7037                   Q = qlc:q([X || {X,Y} <- ets:table(E),
7038                                   ((X =:= 3) or (Y =:= 4))  and (X == a)]),
7039                   {list,{table,_},_} = i(Q),
7040                   [] = qlc:e(Q), % a is not an answer
7041                   [a] = lookup_keys(Q)
7042          end, [{keypos,1},ordered_set], [{a,3},{b,4}])">>,
7043
7044    <<"Q = qlc:q([{X,Y} ||
7045                  {X} <- [{<<3:4>>}],
7046                  {Y} <- [{<<3:4>>}],
7047                  X =:= <<1:3,1:1>>,        % <<3:4>>
7048                  Y =:= <<0:2,1:1,1:1>>,    % <<3:4>>
7049                  X =:= Y]),
7050                  [{<<3:4>>,<<3:4>>}] = qlc:e(Q)">>
7051
7052
7053    ],
7054
7055    run(Config, Ts).
7056
7057%% Syntax error.
7058otp_12946(Config) when is_list(Config) ->
7059    Text =
7060        <<"-export([init/0]).
7061           init() ->
7062               ok.
7063           y">>,
7064    {errors,[{4,erl_parse,_}],[]} = compile_file(Config, Text, []),
7065    ok.
7066
7067%% Examples from qlc(3).
7068manpage(Config) when is_list(Config) ->
7069    dets:start(),
7070    ok = compile_gb_table(Config),
7071
7072    Ts = [
7073       <<"QH = qlc:q([{X,Y} || X <- [a,b], Y <- [1,2]]),
7074          QC = qlc:cursor(QH),
7075          [{a,1}] = qlc:next_answers(QC, 1),
7076          [{a,2}] = qlc:next_answers(QC, 1),
7077          [{b,1},{b,2}] = qlc:next_answers(QC, all_remaining),
7078          ok = qlc:delete_cursor(QC)">>,
7079
7080       <<"QH = qlc:q([{X,Y} || X <- [a,b], Y <- [1,2]]),
7081          [{a,1},{a,2},{b,1},{b,2}] = qlc:eval(QH)">>,
7082
7083       <<"QH = [1,2,3,4,5,6],
7084          21 = qlc:fold(fun(X, Sum) -> X + Sum end, 0, QH)">>,
7085
7086       <<"QH = qlc:q([{X,Y} || X <- [x,y], Y <- [a,b]]),
7087          B = \"begin\n\"
7088              \"    V1 =\n\"
7089              \"        qlc:q([ \n\"
7090              \"               SQV ||\n\"
7091              \"                   SQV <- [x, y]\n\"
7092              \"              ],\n\"
7093              \"              [{unique, true}]),\n\"
7094              \"    V2 =\n\"
7095              \"        qlc:q([ \n\"
7096              \"               SQV ||\n\"
7097              \"                   SQV <- [a, b]\n\"
7098              \"              ],\n\"
7099              \"              [{unique, true}]),\n\"
7100              \"    qlc:q([ \n\"
7101              \"           {X, Y} ||\n\"
7102              \"               X <- V1,\n\"
7103              \"               Y <- V2\n\"
7104              \"          ],\n\"
7105              \"          [{unique, true}])\n\"
7106              \"end\",
7107          true = B =:= qlc:info(QH, unique_all)">>,
7108
7109       <<"E1 = ets:new(e1, []),
7110          E2 = ets:new(e2, []),
7111          true = ets:insert(E1, [{1,a},{2,b}]),
7112          true = ets:insert(E2, [{a,1},{b,2}]),
7113          Q = qlc:q([{X,Z,W} ||
7114                        {X, Z} <- ets:table(E1),
7115                        {W, Y} <- ets:table(E2),
7116                        X =:= Y]),
7117          L = \"begin\n\"
7118              \"    V1 =\n\"
7119              \"        qlc:q([ \n\"
7120              \"               P0 ||\n\"
7121              \"                   P0 = {W, Y} <- ets:table(_)\n\"
7122              \"              ]),\n\"
7123              \"    V2 =\n\"
7124              \"        qlc:q([ \n\"
7125              \"               [G1 | G2] ||\n\"
7126              \"                   G2 <- V1,\n\"
7127              \"                   G1 <- ets:table(_),\n\"
7128              \"                   element(2, G1) =:= element(1, G2)\n\"
7129              \"              ],\n\"
7130              \"              [{join, lookup}]),\n\"
7131              \"    qlc:q([ \n\"
7132              \"           {X, Z, W} ||\n\"
7133              \"               [{X, Z} | {W, Y}] <- V2\n\"
7134              \"          ])\n\"
7135              \"end\",
7136          Info1 =
7137             re:replace(qlc:info(Q),
7138                        \"table\\\\(#Ref<[\\.0-9]*>\",
7139                        \"table(_\", [{return,list},global]),
7140          F = fun(C) -> C =/= $\n andalso C =/= $\s end,
7141          Info = lists:filter(F, Info1),
7142          L1 = lists:filter(F, L),
7143          L1 = Info,
7144          ets:delete(E1),
7145          ets:delete(E2)">>,
7146
7147       <<"Q = qlc:q([{A,X,Z,W} ||
7148                        A <- [a,b,c],
7149                        {X,Z} <- [{a,1},{b,4},{c,6}],
7150                        {W,Y} <- [{2,a},{3,b},{4,c}],
7151                        X =:= Y],
7152                    {cache, list}),
7153          L =
7154       \"begin\n\"
7155       \"    V1 =\n\"
7156       \"        qlc:q([ \n\"
7157       \"               P0 ||\n\"
7158       \"                   P0 = {X, Z} <-\n\"
7159       \"                       qlc:keysort(1, [{a, 1}, {b, 4}, {c, 6}], [])\n\"
7160       \"              ]),\n\"
7161       \"    V2 =\n\"
7162       \"        qlc:q([ \n\"
7163       \"               P0 ||\n\"
7164       \"                   P0 = {W, Y} <-\n\"
7165       \"                       qlc:keysort(2, [{2, a}, {3, b}, {4, c}], [])\n\"
7166
7167       \"              ]),\n\"
7168       \"    V3 =\n\"
7169       \"        qlc:q([ \n\"
7170       \"               [G1 | G2] ||\n\"
7171       \"                   G1 <- V1,\n\"
7172       \"                   G2 <- V2,\n\"
7173       \"                   element(1, G1) == element(2, G2)\n\"
7174       \"              ],\n\"
7175       \"              [{join, merge}, {cache, list}]),\n\"
7176       \"    qlc:q([ \n\"
7177       \"           {A, X, Z, W} ||\n\"
7178       \"               A <- [a, b, c],\n\"
7179       \"               [{X, Z} | {W, Y}] <- V3,\n\"
7180       \"               X =:= Y\n\"
7181       \"          ])\n\"
7182       \"end\",
7183          L = qlc:info(Q)">>,
7184
7185       <<"E1 = ets:new(t, [set]), % uses =:=/2
7186          Q1 = qlc:q([K ||
7187          {K} <- ets:table(E1),
7188          K == 2.71 orelse K == a]),
7189          {list,{table,_}, [{{'$1'},[],['$1']}]} = i(Q1),
7190          true = ets:delete(E1)">>,
7191
7192       <<"F = fun(E, I) ->
7193                    qlc:q([V || {K,V} <- ets:table(E), K == I])
7194              end,
7195          E2 = ets:new(t, [set]),
7196          true = ets:insert(E2, [{{2,2},a},{{2,2.0},b},{{2.0,2},c}]),
7197          Q2 = F(E2, {2,2}),
7198          {table,{ets,table,[_,
7199                [{traverse,{select,[{{'$1','$2'},
7200                                     [{'==','$1',{const,{2,2}}}],
7201                                     ['$2']}]}}]]}} = i(Q2),
7202          [a,b,c] = lists:sort(qlc:e(Q2)),
7203          true = ets:delete(E2),
7204
7205          E3 = ets:new(t, [ordered_set]), % uses ==/2
7206          true = ets:insert(E3, [{{2,2.0},b}]),
7207          Q3 = F(E3,{2,2}),
7208          {list,{table,_},[{{'$1','$2'},[],['$2']}]} = i(Q3),
7209          [b] = qlc:e(Q3),
7210          true = ets:delete(E3)">>,
7211
7212       <<"T = gb_trees:empty(),
7213          QH = qlc:q([X || {{X,Y},_} <- gb_table:table(T),
7214                           ((X == 1) or (X == 2)) andalso
7215                           ((Y == a) or (Y == b) or (Y == c))]),
7216          L = \"ets:match_spec_run(lists:flatmap(fun(K) ->
7217                                        case
7218                                            gb_trees:lookup(K,
7219                                                            gb_trees:from_orddict([]))
7220                                        of
7221                                            {value, V} ->
7222                                                [{K, V}];
7223                                            none ->
7224                                                []
7225                                        end
7226                                 end,
7227                                 [{1, a},
7228                                  {1, b},
7229                                  {1, c},
7230                                  {2, a},
7231                                  {2, b},
7232                                  {2, c}]),
7233                   ets:match_spec_compile([{{{'$1', '$2'}, '_'},
7234                                            [],
7235                                            ['$1']}]))\",
7236          L = qlc:info(QH)">>
7237      ],
7238    run(Config, Ts),
7239
7240    L = [1,2,3],
7241    Bs = erl_eval:add_binding('L', L, erl_eval:new_bindings()),
7242    QH = qlc:string_to_handle("[X+1 || X <- L].", [], Bs),
7243    [2,3,4] = qlc:eval(QH),
7244
7245    %% ets(3)
7246    MS = ets:fun2ms(fun({X,Y}) when (X > 1) or (X < 5) -> {Y} end),
7247    ETs = [
7248        [<<"true = ets:insert(Tab = ets:new(t, []),[{1,a},{2,b},{3,c},{4,d}]),
7249            MS = ">>, io_lib:format("~w", [MS]), <<",
7250            QH1 = ets:table(Tab, [{traverse, {select, MS}}]),
7251
7252            QH2 = qlc:q([{Y} || {X,Y} <- ets:table(Tab), (X > 1) or (X < 5)]),
7253
7254            true = qlc:info(QH1) =:= qlc:info(QH2),
7255            true = ets:delete(Tab)">>]],
7256    run(Config, ETs),
7257
7258    %% dets(3)
7259    DTs = [
7260        [<<"{ok, T} = dets:open_file(t, []),
7261            ok = dets:insert(T, [{1,a},{2,b},{3,c},{4,d}]),
7262            MS = ">>, io_lib:format("~w", [MS]), <<",
7263            QH1 = dets:table(T, [{traverse, {select, MS}}]),
7264
7265            QH2 = qlc:q([{Y} || {X,Y} <- dets:table(t), (X > 1) or (X < 5)]),
7266
7267            true = qlc:info(QH1) =:= qlc:info(QH2),
7268            ok = dets:close(T)">>]],
7269    run(Config, DTs),
7270
7271    ok.
7272
7273compile_gb_table(Config) ->
7274    GB_table_file = filename("gb_table.erl", Config),
7275    ok = file:write_file(GB_table_file, gb_table()),
7276    {ok, gb_table} = compile:file(GB_table_file, [{outdir,?privdir}]),
7277    code:purge(gb_table),
7278    {module, gb_table} =
7279        code:load_abs(filename:rootname(GB_table_file)),
7280    ok.
7281
7282gb_table() ->
7283    <<"
7284-module(gb_table).
7285
7286-export([table/1]).
7287
7288table(T) ->
7289    TF = fun() -> qlc_next(gb_trees:next(gb_trees:iterator(T))) end,
7290    InfoFun = fun(num_of_objects) -> gb_trees:size(T);
7291                 (keypos) -> 1;
7292                 (is_sorted_key) -> true;
7293                 (is_unique_objects) -> true;
7294                 (_) -> undefined
7295              end,
7296    LookupFun =
7297        fun(1, Ks) ->
7298                lists:flatmap(fun(K) ->
7299                                      case gb_trees:lookup(K, T) of
7300                                          {value, V} -> [{K,V}];
7301                                          none -> []
7302                                      end
7303                              end, Ks)
7304        end,
7305    FormatFun =
7306        fun({all, NElements, ElementFun}) ->
7307                ValsS = io_lib:format(\"gb_trees:from_orddict(~w)\",
7308                                      [gb_nodes(T, NElements, ElementFun)]),
7309                io_lib:format(\"gb_table:table(~s)\", [ValsS]);
7310           ({lookup, 1, KeyValues, _NElements, ElementFun}) ->
7311                ValsS = io_lib:format(\"gb_trees:from_orddict(~w)\",
7312                                      [gb_nodes(T, infinity, ElementFun)]),
7313                io_lib:format(\"lists:flatmap(fun(K) -> \"
7314                              \"case gb_trees:lookup(K, ~s) of \"
7315                              \"{value, V} -> [{K,V}];none -> [] end \"
7316                              \"end, ~w)\",
7317                              [ValsS, [ElementFun(KV) || KV <- KeyValues]])
7318        end,
7319    qlc:table(TF, [{info_fun, InfoFun}, {format_fun, FormatFun},
7320                   {lookup_fun, LookupFun},{key_equality,'=='}]).
7321
7322qlc_next({X, V, S}) ->
7323    [{X,V} | fun() -> qlc_next(gb_trees:next(S)) end];
7324qlc_next(none) ->
7325    [].
7326
7327gb_nodes(T, infinity, ElementFun) ->
7328    gb_nodes(T, -1, ElementFun);
7329gb_nodes(T, NElements, ElementFun) ->
7330    gb_iter(gb_trees:iterator(T), NElements, ElementFun).
7331
7332gb_iter(_I, 0, _EFun) ->
7333    '...';
7334gb_iter(I0, N, EFun) ->
7335    case gb_trees:next(I0) of
7336        {X, V, I} ->
7337            [EFun({X,V}) | gb_iter(I, N-1, EFun)];
7338        none ->
7339            []
7340    end.
7341    ">>.
7342
7343
7344%% OTP-6674. Join info and extra constants.
7345backward(Config) when is_list(Config) ->
7346    try_old_join_info(Config),
7347    ok.
7348
7349try_old_join_info(Config) ->
7350    %% Check join info for handlers of extra constants.
7351    File = filename:join(?datadir, "join_info_compat.erl"),
7352    M = join_info_compat,
7353    {ok, M} = compile:file(File, [{outdir, ?datadir}]),
7354    {module, M} = code:load_abs(filename:rootname(File)),
7355    H = M:create_handle(),
7356    A0 = erl_anno:new(0),
7357    {block,A0,
7358     [{match,_,_,
7359       {call,_,_,
7360        [{lc,_,_,
7361          [_,
7362           {op,_,'=:=',
7363            {float,_,192.0},
7364            {call,_,{atom,_,element},[{integer,_,1},_]}}]}]}},
7365      _,_,
7366      {call,_,_,
7367       [{lc,_,_,
7368         [_,
7369          {op,_,'=:=',{var,_,'B'},{float,_,192.0}},
7370          {op,_,'==',{var,_,'X'},{var,_,'Y'}}]}]}]}
7371        = qlc:info(H,{format,abstract_code}),
7372    [{1,1},{2,2}] = qlc:e(H),
7373
7374    H2 = M:lookup_handle(),
7375    {qlc,_,[{generate,_,{qlc,_,_,[{join,lookup}]}},_],[]} =
7376        qlc:info(H2, {format,debug}),
7377    [{1,1},{2,2}] = qlc:e(H2).
7378
7379forward(Config) when is_list(Config) ->
7380    Ts = [
7381      %% LC_fun() returns something unknown.
7382      <<"FakeH = {qlc_handle,{qlc_lc,fun() -> {foo,bar} end,
7383                             {qlc_opt,false,false,-1,any,[],any,524288}}},
7384         {'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>,
7385
7386%% 'f1' should be used for new stuff that does not interfer with old behavior
7387%%       %% The unused element 'f1' of #qlc_table seems to be used.
7388%%       <<"DF = fun() -> foo end,
7389%%          FakeH = {qlc_handle,{qlc_table,DF,
7390%%                        true,DF,DF,DF,DF,DF,
7391%%                        undefined,not_undefined,undefined,no_match_spec}},
7392%%          {'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>,
7393
7394      %% #qlc_opt has changed.
7395      <<"H = qlc:q([X || X <- []]),
7396         {qlc_handle, {qlc_lc, Fun, _Opt}} = H,
7397         FakeH = {qlc_handle, {qlc_lc, Fun, {new_qlc_opt, a,b,c}}},
7398         {'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>
7399
7400     ],
7401    run(Config, Ts),
7402    ok.
7403
7404eep37(Config) when is_list(Config) ->
7405    Ts = [
7406        <<"H = (fun _Handle() -> qlc:q([X || X <- []]) end)(),
7407           [] = qlc:eval(H)">>
7408    ],
7409    run(Config, Ts),
7410    ok.
7411
7412%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7413
7414bad_table_throw(Tab) ->
7415    Limit = 1,
7416    Select = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7417    PreFun = fun(_) -> throw({throw,bad_pre_fun}) end,
7418    PostFun = fun() -> throw({throw,bad_post_fun}) end,
7419    InfoFun = fun(Tag) -> info(Tab, Tag) end,
7420    qlc:table(Select, [{pre_fun,PreFun}, {post_fun, PostFun},
7421                       {info_fun, InfoFun}]).
7422
7423bad_table_exit(Tab) ->
7424    Limit = 1,
7425    Select = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7426    PreFun = fun(_) -> erlang:error(bad_pre_fun) end,
7427    PostFun = fun() -> erlang:error(bad_post_fun) end,
7428    InfoFun = fun(Tag) -> info(Tab, Tag) end,
7429    qlc:table(Select, [{pre_fun,PreFun}, {post_fun, PostFun},
7430                       {info_fun, InfoFun}]).
7431
7432info(_Tab, is_unique_objects) ->
7433    false;
7434info(Tab, Tag) ->
7435    try ets:info(Tab, Tag) catch _:_ -> undefined end.
7436
7437create_ets(S, E) ->
7438    create_ets(lists:seq(S, E)).
7439
7440create_ets(L) ->
7441    E1 = ets:new(e, []),
7442    true = ets:insert(E1, [{X,X} || X <- L]),
7443    E1.
7444
7445etsc(F, Objs) ->
7446    etsc(F, [{keypos,1}], Objs).
7447
7448etsc(F, Opts, Objs) ->
7449    E = ets:new(test, Opts),
7450    true = ets:insert(E, Objs),
7451    V = F(E),
7452    ets:delete(E),
7453    V.
7454
7455join_info(H) ->
7456    {{qlc, S, Options}, Bs} = strip_qlc_call2(H),
7457    %% "Hide" the call to qlc_pt from the test in run_test().
7458    LoadedPT = code:is_loaded(qlc_pt),
7459    QH = qlc:string_to_handle(S, Options, Bs),
7460    _ = [unload_pt() || false <- [LoadedPT]], % doesn't take long...
7461    case {join_info_count(H), join_info_count(QH)} of
7462        {N, N} ->
7463            N;
7464        Ns ->
7465            Ns
7466    end.
7467
7468strip_qlc_call(H) ->
7469    {Expr, _Bs} = strip_qlc_call2(H),
7470    Expr.
7471
7472strip_qlc_call2(H) ->
7473    S = qlc:info(H, {flat, false}),
7474    {ok, Tokens, _EndLine} = erl_scan:string(S++".", 1, [text]),
7475    {ok, [Expr], Bs} = erl_eval:extended_parse_exprs(Tokens),
7476    {case Expr of
7477         {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC]} ->
7478             {qlc, lists:flatten([erl_pp:expr(LC), "."]), []};
7479         {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC, Opts]} ->
7480             {qlc, lists:flatten([erl_pp:expr(LC), "."]),
7481              erl_parse:normalise(Opts)};
7482         {call,_,{remote,_,{atom,_,ets},{atom,_,match_spec_run}},_} ->
7483             {match_spec, Expr};
7484         {call,_,{remote,_,{atom,_,M},{atom,_,table}},_} ->
7485             {table, M, Expr};
7486         _ ->
7487             []
7488     end, Bs}.
7489
7490-record(ji, {nmerge = 0, nlookup = 0, nnested_loop = 0, nkeysort = 0}).
7491
7492%% Counts join options and (all) calls to qlc:keysort().
7493join_info_count(H) ->
7494    S = qlc:info(H, {flat, false}),
7495    {ok, Tokens, _EndLine} = erl_scan:string(S++".", 1, [text]),
7496    {ok, [Expr], _Bs} = erl_eval:extended_parse_exprs(Tokens),
7497    #ji{nmerge = Nmerge, nlookup = Nlookup,
7498        nkeysort = NKeysort, nnested_loop = Nnested_loop} =
7499        ji(Expr, #ji{}),
7500    {Nmerge, Nlookup, Nnested_loop, NKeysort}.
7501
7502ji({call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC,Options]}, JI) ->
7503    NJI = case lists:keysearch(join, 1, erl_parse:normalise(Options)) of
7504              {value, {join, merge}} ->
7505                  JI#ji{nmerge = JI#ji.nmerge + 1};
7506              {value, {join, lookup}} ->
7507                  JI#ji{nlookup = JI#ji.nlookup + 1};
7508              {value, {join, nested_loop}} ->
7509                  JI#ji{nnested_loop = JI#ji.nnested_loop + 1};
7510              _  ->
7511                  JI
7512          end,
7513    ji(LC, NJI);
7514ji({call,_,{remote,_,{atom,_,qlc},{atom,_,keysort}},[_KP,H,_Options]}, JI) ->
7515    ji(H, JI#ji{nkeysort = JI#ji.nkeysort + 1});
7516ji(T, JI) when is_tuple(T) ->
7517    ji(tuple_to_list(T), JI);
7518ji([E | Es], JI) ->
7519    ji(Es, ji(E, JI));
7520ji(_, JI) ->
7521    JI.
7522
7523%% Designed for ETS' and gb_table's format funs.
7524lookup_keys(Q) ->
7525    case lists:flatten(lookup_keys(i(Q), [])) of
7526        [] -> false;
7527        L -> lists:usort(L)
7528    end.
7529
7530lookup_keys([Q | Qs], L) ->
7531    lookup_keys(Qs, lookup_keys(Q, L));
7532lookup_keys({qlc,_,Quals,_}, L) ->
7533    lookup_keys(Quals, L);
7534lookup_keys({list,Q,_}, L) ->
7535    lookup_keys(Q, L);
7536lookup_keys({generate,_,Q}, L) ->
7537    lookup_keys(Q, L);
7538lookup_keys({table,Chars}, L) when is_list(Chars) ->
7539    {ok, Tokens, _} = erl_scan:string(lists:flatten(Chars++"."), 1, [text]),
7540    {ok, [Expr], _Bs} = erl_eval:extended_parse_exprs(Tokens),
7541    case Expr of
7542        {call,_,_,[_fun,AKs]} ->
7543            case erl_parse:normalise(AKs) of
7544                Ks when is_list(Ks) ->
7545                    [lists:sort(Ks) | L];
7546                K -> % assume keys are never lists (ets only)
7547                    [K | L]
7548            end;
7549        _ -> % gb_table
7550            L
7551    end;
7552lookup_keys(_Q, L) ->
7553    L.
7554
7555bad_table_format(Tab) ->
7556    Limit = 1,
7557    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7558    FormatFun = {is, no, good},
7559    qlc:table(SelectFun, [{format_fun, FormatFun}]).
7560
7561bad_table_format_arity(Tab) ->
7562    Limit = 1,
7563    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7564    FormatFun = fun() -> {?MODULE, bad_table_format_arity, [Tab]} end,
7565    qlc:table(SelectFun, [{format_fun, FormatFun}]).
7566
7567bad_table_traverse(Tab) ->
7568    Limit = 1,
7569    Select = fun(MS, _) -> cb(ets:select(Tab, MS, Limit)) end,
7570    qlc:table(Select, []).
7571
7572bad_table_post(Tab) ->
7573    Limit = 1,
7574    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7575    qlc:table(SelectFun, [{pre_fun,undefined},
7576                          {post_fun, fun(X) -> X end},
7577                          {info_fun, undefined}]).
7578
7579bad_table_lookup(Tab) ->
7580    Limit = 1,
7581    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7582    qlc:table(SelectFun, {lookup_fun, fun(X) -> X end}).
7583
7584bad_table_max_lookup(Tab) ->
7585    Limit = 1,
7586    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7587    qlc:table(SelectFun, {max_lookup, -2}).
7588
7589bad_table_info_arity(Tab) ->
7590    Limit = 1,
7591    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7592    InfoFun = fun() -> {?MODULE, bad_table_info_arity, [Tab]} end,
7593    qlc:table(SelectFun, [{info_fun, InfoFun}]).
7594
7595default_table(Tab) ->
7596    Limit = 1,
7597    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7598    qlc:table(SelectFun, [{format_fun, undefined},
7599                          {info_fun, undefined},
7600                          {lookup_fun, undefined},
7601                          {parent_fun, undefined},
7602                          {pre_fun,undefined},
7603                          {post_fun, undefined}]).
7604
7605bad_table(Tab) ->
7606    Limit = 1,
7607    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7608    qlc:table(SelectFun, [{info, fun() -> ok end}]).
7609
7610bad_table_info_fun_n_objects(Tab) ->
7611    Limit = 1,
7612    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7613    LookupFun = fun(_Pos, Ks) ->
7614                        lists:flatmap(fun(K) -> ets:lookup(Tab, K) end, Ks)
7615                end,
7616    InfoFun = fun(num_of_objects) -> exit(finito);
7617                 (_) -> undefined
7618              end,
7619    qlc:table(SelectFun, [{info_fun, InfoFun}, {lookup_fun, LookupFun}]).
7620
7621bad_table_info_fun_indices(Tab) ->
7622    Limit = 1,
7623    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7624    LookupFun = fun(_Pos, Ks) ->
7625                        lists:flatmap(fun(K) -> ets:lookup(Tab, K) end, Ks)
7626                end,
7627    InfoFun = fun(indices) -> throw({throw,apa});
7628                 (_) -> undefined
7629              end,
7630    qlc:table(SelectFun, [{info_fun, InfoFun}, {lookup_fun, LookupFun}]).
7631
7632bad_table_info_fun_keypos(Tab) ->
7633    Limit = 1,
7634    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7635    LookupFun = fun(_Pos, Ks) ->
7636                        lists:flatmap(fun(K) -> ets:lookup(Tab, K) end, Ks)
7637                end,
7638    InfoFun = fun(indices) -> erlang:error(keypos);
7639                  (_) -> undefined
7640              end,
7641    qlc:table(SelectFun, [{info_fun, InfoFun}, {lookup_fun, LookupFun}]).
7642
7643bad_table_key_equality(Tab) ->
7644    Limit = 1,
7645    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7646    LookupFun = fun(_Pos, Ks) ->
7647                        lists:flatmap(fun(K) -> ets:lookup(Tab, K) end, Ks)
7648                end,
7649    qlc:table(SelectFun, [{lookup_fun, LookupFun},{key_equality,'=/='}]).
7650
7651cb('$end_of_table') ->
7652    [];
7653cb({Objects,Cont}) ->
7654    Objects ++ fun() -> cb(ets:select(Cont)) end.
7655
7656i(H) ->
7657    i(H, []).
7658
7659i(H, Options) when is_list(Options) ->
7660    case has_format(Options) of
7661        true -> qlc:info(H, Options);
7662        false -> qlc:info(H, [{format, debug} | Options])
7663    end;
7664i(H, Option) ->
7665    i(H, [Option]).
7666
7667has_format({format,_}) ->
7668    true;
7669has_format([E | Es]) ->
7670    has_format(E) or has_format(Es);
7671has_format(_) ->
7672    false.
7673
7674format_info(H, Flat) ->
7675    L = qlc:info(H, [{flat, Flat}, {format,string}]),
7676    re:replace(L, "\s|\n|\t|\f|\r|\v", "", [{return,list},global]).
7677
7678%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7679%% A list turned into a table...
7680
7681table_kill_parent(List, Indices) ->
7682    ParentFun = fun() -> exit(self(), kill) end,
7683    table_i(List, Indices, ParentFun).
7684
7685table_parent_throws(List, Indices) ->
7686    ParentFun = fun() -> throw({throw,thrown}) end,
7687    table_i(List, Indices, ParentFun).
7688
7689table_parent_exits(List, Indices) ->
7690    ParentFun = fun() -> 1 + Indices end,
7691    table_i(List, Indices, ParentFun).
7692
7693table_bad_parent_fun(List, Indices) ->
7694    ParentFun = fun(X) -> X end, % parent_fun should be nullary
7695    table_i(List, Indices, ParentFun).
7696
7697table(List, Indices) ->
7698    ParentFun = fun() -> self() end,
7699    table_i(List, Indices, ParentFun).
7700
7701table(List, KeyPos, Indices) ->
7702    ParentFun = fun() -> self() end,
7703    table(List, Indices, KeyPos, ParentFun).
7704
7705table_i(List, Indices, ParentFun) ->
7706    table(List, Indices, undefined, ParentFun).
7707
7708table(List, Indices, KeyPos, ParentFun) ->
7709    TraverseFun = fun() -> list_traverse(List) end,
7710    PreFun = fun(PreArgs) ->
7711                     {value, {parent_value, Pid}} =
7712                         lists:keysearch(parent_value, 1, PreArgs),
7713                     true = is_pid(Pid)
7714             end,
7715    PostFun = fun() -> ok end,
7716    InfoFun = fun(indices) ->
7717                      Indices;
7718                 (is_unique_objects) ->
7719                      undefined;
7720                 (keypos) ->
7721                      KeyPos;
7722                 (num_of_objects) ->
7723                      undefined;
7724                 (_) ->
7725                      undefined
7726              end,
7727    LookupFun =
7728        fun(Column, Values) ->
7729                lists:flatmap(fun(V) ->
7730                                      case lists:keysearch(V, Column, List) of
7731                                          false -> [];
7732                                          {value,Val} -> [Val]
7733                                      end
7734                              end, Values)
7735
7736                end,
7737    FormatFun = fun(all) ->
7738                        L = erl_anno:new(17),
7739                        {call,L,{remote,L,{atom,L,?MODULE},{atom,L,the_list}},
7740                                 [erl_parse:abstract(List, 17)]};
7741                   ({lookup, Column, Values}) ->
7742                        {?MODULE, list_keys, [Values, Column, List]}
7743                end,
7744    qlc:table(TraverseFun, [{info_fun,InfoFun}, {pre_fun, PreFun},
7745                            {post_fun, PostFun}, {lookup_fun, LookupFun},
7746                            {format_fun, FormatFun},
7747                            {parent_fun, ParentFun}]).
7748
7749stop_list(List, Ets) ->
7750    Traverse = fun() -> list_traverse(List) end,
7751    PV = a_sample_parent_value,
7752    ParentFun = fun() -> PV end,
7753    Pre = fun(PreArgs) ->
7754                  {value, {parent_value, PV}} =
7755                      lists:keysearch(parent_value, 1, PreArgs),
7756                  {value, {stop_fun, Fun}} =
7757                      lists:keysearch(stop_fun, 1, PreArgs),
7758                  true = ets:insert(Ets, {stop_fun, Fun})
7759          end,
7760    qlc:table(Traverse, [{pre_fun, Pre}, {parent_fun, ParentFun}]).
7761
7762list_traverse([]) ->
7763    [];
7764list_traverse([E | Es]) ->
7765    [E | fun() -> list_traverse(Es) end].
7766
7767table_error(List, Error) ->
7768    table_error(List, undefined, Error).
7769
7770table_error(List, KeyPos, Error) ->
7771    TraverseFun = fun() -> list_traverse2(lists:sort(List), Error) end,
7772    InfoFun = fun(is_sorted_key) -> true;
7773                 (keypos) -> KeyPos;
7774                 (_) -> undefined
7775              end,
7776    qlc:table(TraverseFun, [{info_fun,InfoFun}]).
7777
7778list_traverse2([], Err) ->
7779    Err;
7780list_traverse2([E | Es], Err) ->
7781    [E | fun() -> list_traverse2(Es, Err) end].
7782
7783table_lookup_error(List) ->
7784    TraverseFun = fun() -> list_traverse(List) end,
7785    LookupFun = fun(_Column, _Values) -> {error,lookup,failed} end,
7786    InfoFun = fun(keypos) -> 1;
7787                 (_) -> undefined
7788              end,
7789    qlc:table(TraverseFun, [{lookup_fun,LookupFun},{info_fun,InfoFun}]).
7790
7791prep_scratchdir(Dir) ->
7792    put('$qlc_tmpdir', true),
7793    _ = filelib:ensure_dir(Dir),
7794    lists:foreach(fun(F) -> file:delete(F)
7795                  end, filelib:wildcard(filename:join(Dir, "*"))),
7796    true.
7797
7798%% Truncate just once.
7799truncate_tmpfile(Dir, Where) ->
7800    case get('$qlc_tmpdir') of
7801        true ->
7802            {ok, [TmpFile0 | _]} = file:list_dir(Dir),
7803            TmpFile = filename:join(Dir, TmpFile0),
7804            truncate(TmpFile, Where),
7805            erase('$qlc_tmpdir');
7806        _ ->
7807            true
7808    end.
7809
7810truncate(File, Where) ->
7811    {ok, Fd} = file:open(File, [read, write]),
7812    {ok, _} = file:position(Fd, Where),
7813    ok = file:truncate(Fd),
7814    ok = file:close(Fd).
7815
7816%% Crash just once.
7817crash_tmpfile(Dir, Where) ->
7818    case get('$qlc_tmpdir') of
7819        true ->
7820            {ok, [TmpFile0 | _]} = file:list_dir(Dir),
7821            TmpFile = filename:join(Dir, TmpFile0),
7822            crash(TmpFile, Where),
7823            erase('$qlc_tmpdir');
7824        _ ->
7825            true
7826    end.
7827
7828crash(File, Where) ->
7829    {ok, Fd} = file:open(File, [read, write]),
7830    {ok, _} = file:position(Fd, Where),
7831    ok = file:write(Fd, [10]),
7832    ok = file:close(Fd).
7833
7834%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7835
7836run(Config, Tests) ->
7837    run(Config, [], Tests).
7838
7839run(Config, Extra, Tests) ->
7840    lists:foreach(fun(Body) -> run_test(Config, Extra, Body) end, Tests).
7841
7842run_test(Config, Extra, {cres, Body, ExpectedCompileReturn}) ->
7843    run_test(Config, Extra, {cres, Body, _Opts = [], ExpectedCompileReturn});
7844run_test(Config, Extra, {cres, Body, Opts, ExpectedCompileReturn}) ->
7845    {SourceFile, Mod} = compile_file_mod(Config),
7846    P = [Extra,<<"function() -> ">>, Body, <<", ok. ">>],
7847    CompileReturn = compile_file(Config, P, Opts),
7848    case comp_compare(ExpectedCompileReturn, CompileReturn) of
7849        true -> ok;
7850        false -> expected(ExpectedCompileReturn, CompileReturn, SourceFile)
7851    end,
7852    AbsFile = filename:rootname(SourceFile, ".erl"),
7853    _ = code:purge(Mod),
7854    {module, _} = code:load_abs(AbsFile, Mod),
7855
7856    Ms0 = erlang:process_info(self(),messages),
7857    Before = {{lget(), lists:sort(ets:all()), Ms0}, pps()},
7858
7859    %% Prepare the check that the qlc module does not call qlc_pt.
7860    _ = [unload_pt() || {file, Name} <- [code:is_loaded(qlc_pt)],
7861                        Name =/= cover_compiled],
7862
7863    R = case catch Mod:function() of
7864            {'EXIT', _Reason} = Error ->
7865                io:format("failed, got ~p~n", [Error]),
7866                fail(SourceFile);
7867            Reply ->
7868                Reply
7869        end,
7870
7871    %% Check that the qlc module does not call qlc_pt:
7872    case code:is_loaded(qlc_pt) of
7873        {file, cover_compiled} ->
7874            ok;
7875        {file, _} ->
7876            io:format("qlc_pt was loaded in runtime~n", []),
7877            fail(SourceFile);
7878        false ->
7879            ok
7880    end,
7881
7882    wait_for_expected(R, Before, SourceFile, true),
7883    code:purge(Mod);
7884run_test(Config, Extra, Body) ->
7885    run_test(Config, Extra, {cres,Body,[]}).
7886
7887wait_for_expected(R, {Strict0,PPS0}=Before, SourceFile, Wait) ->
7888    Ms = erlang:process_info(self(),messages),
7889    After = {_,PPS1} = {{lget(), lists:sort(ets:all()), Ms}, pps()},
7890    case {R, After} of
7891        {ok, Before} ->
7892            ok;
7893        {ok, {Strict0,_}} ->
7894            {Ports0,Procs0} = PPS0,
7895            {Ports1,Procs1} = PPS1,
7896            case {Ports1 -- Ports0, Procs1 -- Procs0} of
7897                {[], []} -> ok;
7898                _ when Wait ->
7899                    timer:sleep(1000),
7900                    wait_for_expected(R, Before, SourceFile, false);
7901                {PortsDiff,ProcsDiff} ->
7902                    io:format("failure, got ~p~n, expected ~p\n",
7903                              [PPS1, PPS0]),
7904                    show("Old port", Ports0 -- Ports1),
7905                    show("New port", PortsDiff),
7906                    show("Old proc", Procs0 -- Procs1),
7907                    show("New proc", ProcsDiff),
7908                    fail(SourceFile)
7909            end;
7910        _ when Wait ->
7911            timer:sleep(1000),
7912            wait_for_expected(R, Before, SourceFile, false);
7913        _ ->
7914            expected({ok,Before}, {R,After}, SourceFile)
7915    end.
7916
7917%% The qlc modules uses the process dictionary for storing names of files.
7918lget() ->
7919    lists:sort([T || {K, _} = T <- get(), is_qlc_key(K)]).
7920
7921%% Copied from the qlc module.
7922-define(LCACHE_FILE(Ref), {Ref, '$_qlc_cache_tmpfiles_'}).
7923-define(MERGE_JOIN_FILE, '$_qlc_merge_join_tmpfiles_').
7924
7925is_qlc_key(?LCACHE_FILE(_)) -> true;
7926is_qlc_key(?MERGE_JOIN_FILE) -> true;
7927is_qlc_key(_) -> false.
7928
7929unload_pt() ->
7930    erlang:garbage_collect(), % get rid of references to qlc_pt...
7931    _ = code:purge(qlc_pt),
7932    _ = code:delete(qlc_pt).
7933
7934compile_format(Config, Tests) ->
7935    Fun = fun(Test, Opts) ->
7936                  Return = compile_file(Config, Test, Opts),
7937                  format_messages(Return)
7938          end,
7939    compile(Config, Tests, Fun).
7940
7941format_messages({warnings,Ws}) ->
7942    format_messages({errors,[],Ws});
7943format_messages({errors,Es,Ws}) ->
7944    {[format_msg(E, Mod) || {_Line,Mod,E} <- Es],
7945     [format_msg(W, Mod) || {_Line,Mod,W} <- Ws]}.
7946
7947format_msg(Msg, Mod) ->
7948    IOlist = Mod:format_error(Msg),
7949    binary_to_list(iolist_to_binary(IOlist)).
7950
7951compile(Config, Tests) ->
7952    Fun = fun(Test, Opts) -> catch compile_file(Config, Test, Opts) end,
7953    compile(Config, Tests, Fun).
7954
7955compile(Config, Tests, Fun) ->
7956    F = fun({TestName,Test,Opts,Expected}, BadL) ->
7957                Return = Fun(Test, Opts),
7958                case comp_compare(Expected, Return) of
7959                    true ->
7960                        BadL;
7961                    false ->
7962                        {File, _Mod} = compile_file_mod(Config),
7963                        expected(TestName, Expected, Return, File)
7964                end
7965        end,
7966    lists:foldl(F, [], Tests).
7967
7968%% Compiles a test module and returns the list of errors and warnings.
7969
7970compile_file(Config, Test0, Opts0) ->
7971    {File, Mod} = compile_file_mod(Config),
7972    Test = list_to_binary(["-module(", atom_to_list(Mod), "). "
7973                           "-import(qlc_SUITE, [i/1,i/2,format_info/2]). "
7974                           "-import(qlc_SUITE, [etsc/2, etsc/3]). "
7975                           "-import(qlc_SUITE, [create_ets/2]). "
7976                           "-import(qlc_SUITE, [strip_qlc_call/1]). "
7977                           "-import(qlc_SUITE, [join_info/1]). "
7978                           "-import(qlc_SUITE, [join_info_count/1]). "
7979                           "-import(qlc_SUITE, [lookup_keys/1]). "
7980                           "-include_lib(\"stdlib/include/qlc.hrl\"). ",
7981                           Test0]),
7982    Opts = [export_all,nowarn_export_all,return,nowarn_unused_record,{outdir,?privdir}|Opts0],
7983    ok = file:write_file(File, Test),
7984    case compile:file(File, Opts) of
7985        {ok, _M, Ws} -> warnings(File, Ws);
7986        {error, [{File,Es}], []} -> {errors, Es, []};
7987        {error, [{File,Es}], [{File,Ws}]} -> {errors, Es, Ws}
7988    end.
7989
7990comp_compare(T, T) ->
7991    true;
7992comp_compare(T1, T2_0) ->
7993    T2 = wskip(T2_0),
7994    T1 =:= T2
7995       %% This clause should eventually be removed.
7996       orelse ln(T1) =:= T2 orelse T1 =:= ln(T2).
7997
7998wskip([]) ->
7999    [];
8000wskip([{_,sys_core_fold,{eval_failure,badarg}}|L]) ->
8001    wskip(L);
8002wskip([{{L,_C},sys_core_fold,M}|L]) ->
8003    [{L,sys_core_fold,M}|wskip(L)];
8004wskip({T,L}) ->
8005    {T,wskip(L)};
8006wskip([M|L]) ->
8007    [M|wskip(L)];
8008wskip(T) ->
8009    T.
8010
8011%% Replaces locations like {Line,Column} with Line.
8012ln({warnings,L}) ->
8013    {warnings,ln0(L)};
8014ln({errors,EL,WL}) ->
8015    {errors,ln0(EL),ln0(WL)};
8016ln(L) ->
8017    ln0(L).
8018
8019ln0(L) ->
8020    lists:sort(ln1(L)).
8021
8022ln1([]) ->
8023    [];
8024ln1([{File,Ms}|MsL]) when is_list(File) ->
8025    [{File,ln0(Ms)}|ln1(MsL)];
8026ln1([{{L,_C},Mod,Mess0}|Ms]) ->
8027    Mess = case Mess0 of
8028               {exported_var,V,{Where,{L1,_C1}}} ->
8029                   {exported_var,V,{Where,L1}};
8030               {unsafe_var,V,{Where,{L1,_C1}}} ->
8031                   {unsafe_var,V,{Where,L1}};
8032               %% There are more...
8033               M ->
8034                   M
8035           end,
8036    [{L,Mod,Mess}|ln1(Ms)];
8037ln1([M|Ms]) ->
8038    [M|ln1(Ms)].
8039
8040%% -> {FileName, Module}; {string(), atom()}
8041compile_file_mod(Config) ->
8042    NameL = lists:concat([?TESTMODULE, "_", ?testcase]),
8043    Name = list_to_atom(NameL),
8044    File = filename(NameL ++ ".erl", Config),
8045    {File, Name}.
8046
8047filename(Name, Config) when is_atom(Name) ->
8048    filename(atom_to_list(Name), Config);
8049filename(Name, Config) ->
8050    filename:join(?privdir, Name).
8051
8052show(_S, []) ->
8053    ok;
8054show(S, [{Pid, Name, InitCall}|Pids]) when is_pid(Pid) ->
8055    io:format("~s: ~w (~w), ~w: ~p~n",
8056              [S, Pid, proc_reg_name(Name), InitCall,
8057               erlang:process_info(Pid)]),
8058    show(S, Pids);
8059show(S, [{Port, _}|Ports]) when is_port(Port)->
8060    io:format("~s: ~w: ~p~n", [S, Port, erlang:port_info(Port)]),
8061    show(S, Ports).
8062
8063pps() ->
8064    {port_list(), process_list()}.
8065
8066port_list() ->
8067    [{P,safe_second_element(erlang:port_info(P, name))} ||
8068        P <- erlang:ports()].
8069
8070process_list() ->
8071    [{P,process_info(P, registered_name),
8072      safe_second_element(process_info(P, initial_call))} ||
8073        P <- processes(), is_process_alive(P)].
8074
8075proc_reg_name({registered_name, Name}) -> Name;
8076proc_reg_name([]) -> no_reg_name.
8077
8078safe_second_element({_,Info}) -> Info;
8079safe_second_element(Other) -> Other.
8080
8081warnings(File, Ws) ->
8082    case lists:append([W || {F, W} <- Ws, F =:= File]) of
8083        [] -> [];
8084        L -> {warnings, L}
8085    end.
8086
8087expected(Test, Expected, Got, File) ->
8088    io:format("~nTest ~p failed. ", [Test]),
8089    expected(Expected, Got, File).
8090
8091expected(Expected, Got, File) ->
8092    io:format("Expected~n  ~p~n, but got~n  ~p~n", [Expected, Got]),
8093    fail(File).
8094
8095fail(Source) ->
8096    ct:fail({failed,testcase,on,Source}).
8097
8098%% Copied from global_SUITE.erl.
8099
8100install_error_logger() ->
8101    error_logger:add_report_handler(?MODULE, self()).
8102
8103uninstall_error_logger() ->
8104    error_logger:delete_report_handler(?MODULE).
8105
8106read_error_logger() ->
8107    receive
8108	{error, Why} ->
8109            {error, Why};
8110        {info, Why} ->
8111            {info, Why};
8112        {warning, Why} ->
8113            {warning, Why};
8114        {error, Pid, Tuple} ->
8115            {error, Pid, Tuple}
8116    after 1000 ->
8117	    io:format("No reply after 1 s\n", []),
8118	    ct:fail(failed)
8119    end.
8120
8121%%-----------------------------------------------------------------
8122%% The error_logger handler used.
8123%% (Copied from stdlib/test/proc_lib_SUITE.erl.)
8124%%-----------------------------------------------------------------
8125init(Tester) ->
8126    {ok, Tester}.
8127
8128handle_event({error, _GL, {_Pid, _Msg, [Why, _]}}, Tester) when is_atom(Why) ->
8129    Tester ! {error, Why},
8130    {ok, Tester};
8131handle_event({error, _GL, {_Pid, _Msg, [P, T]}}, Tester) when is_pid(P) ->
8132    Tester ! {error, P, T},
8133    {ok, Tester};
8134handle_event({info_msg, _GL, {_Pid, _Msg, [Why, _]}}, Tester) ->
8135    Tester ! {info, Why},
8136    {ok, Tester};
8137handle_event({warning_msg, _GL, {_Pid, _Msg, [Why, _]}}, Tester) when is_atom(Why) ->
8138    Tester ! {warning, Why},
8139    {ok, Tester};
8140handle_event(_Event, State) ->
8141    {ok, State}.
8142
8143handle_info(_, State) ->
8144    {ok, State}.
8145
8146handle_call(_Query, State) -> {ok, {error, bad_query}, State}.
8147
8148terminate(_Reason, State) ->
8149    State.
8150