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,5},?QLC,not_a_query_list_comprehension},
174	 {{6,5},?QLC,not_a_query_list_comprehension},
175	 {{8,5},?QLC,not_a_query_list_comprehension},
176	 {{9,5},?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,24},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,21},v3_core,{nomatch,pattern}}]}},
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,27},v3_core,{nomatch,pattern}}]}},
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,37},v3_core,{nomatch,pattern}}]}},
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,38},v3_core,{nomatch,pattern}}]}}
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       {cres,
2386        <<"fun(Z) ->
2387            Q = qlc:q([X || Z < 2, X <- [1,2,3]]),
2388            [] = qlc:e(Q)
2389           end(3)">>, [], {warnings,[{{2,31},sys_core_fold,{nomatch,guard}},
2390                                     {{2,31},sys_core_fold,{nomatch,no_clause}}]}},
2391
2392       <<"H = qlc:q([{P1,A,P2,B,P3,C} ||
2393                  P1={A,_} <- [{1,a},{2,b}],
2394                  {_,B}=P2 <- [{1,a},{2,b}],
2395                  C=P3 <- [1],
2396                  {[X,_],{_,X}} <- [{[1,2],{3,1}}, {[a,b],{3,4}}],
2397                  A > 0,
2398                  B =/= c,
2399                  C > 0]),
2400          L = [{{1,a},1,{1,a},a,1,1}, {{1,a},1,{2,b},b,1,1},
2401               {{2,b},2,{1,a},a,1,1}, {{2,b},2,{2,b},b,1,1}],
2402          L = qlc:e(H)">>,
2403
2404       <<"H = qlc:q([{X,Y} ||
2405                  X = _ <- [1,2,3],
2406                  _ = Y <- [a,b,c],
2407                  _ = _ <- [foo],
2408                  X > 1,
2409                  Y =/= a]),
2410          [{2,b},{2,c},{3,b},{3,c}] = qlc:e(H)">>
2411
2412       ],
2413    run(Config, Ts),
2414    ok.
2415
2416%% info/2.
2417info(Config) when is_list(Config) ->
2418    Ts = [
2419       <<"{list, [1,2]} = i(qlc:q([X || X <- [1,2]])),
2420          {append,[{list, [1,2]}, {list, [3,4]}]} =
2421               i(qlc:append([1,2],[3,4])),
2422          {sort,{list, [1,2]},[]} = i(qlc:sort([1,2])),
2423          E = ets:new(foo, []),
2424          ets:insert(E, [{1},{2}]),
2425          {table, _} = i(ets:table(E)),
2426          true = ets:delete(E),
2427          {list, [1,2]} = i([1,2]),
2428          {append, [{list, [1,2]}, {list, [3,4]}]} =
2429             i(qlc:q([X || X <- qlc:append([1,2],[3,4])])),
2430
2431          H0 = qlc:q([X || X <- throw({throw,t})]),
2432          {throw,t} = (catch {any_term,qlc:info(H0)}),
2433          {'EXIT', {badarg, _}} =
2434               (catch qlc:info(foobar)),
2435          {'EXIT', {badarg, _}} =
2436               (catch qlc:info(qlc:q([X || X <- [1,2]]), badarg))">>,
2437
2438       <<"{'EXIT', {badarg, _}} =
2439               (catch qlc:info([X || {X} <- []], {n_elements, 0})),
2440          L = lists:seq(1, 1000),
2441          \"[1, 2, 3, 4, 5, 6, 7, 8, 9, 10 | '...']\" = qlc:info(L, {n_elements, 10}),
2442          {cons,A1,{integer,A2,1},{atom,A3,'...'}} =
2443            qlc:info(L, [{n_elements, 1},{format,abstract_code}]),
2444          1 = erl_anno:line(A1),
2445          1 = erl_anno:line(A2),
2446          1 = erl_anno:line(A3),
2447          Q = qlc:q([{X} || X <- [a,b,c,d,e,f]]),
2448          {call,_,_,[{cons,_,{atom,_,a},{cons,_,{atom,_,b},{cons,_,{atom,_,c},
2449                                                            {atom,_,'...'}}}},
2450                     {call,_,_,_}]} =
2451          qlc:info(Q, [{n_elements, 3},{format,abstract_code}]),
2452          \"ets:match_spec_run([a, b, c, d, e, f],\n\"
2453          \"                   ets:match_spec_compile([{'$1', [true], \"
2454          \"[{{'$1'}}]}]))\" =
2455             qlc:info(Q, [{n_elements, infinity}])">>,
2456
2457       <<"Q1 = qlc:q([{X} || X <- qlc:q([X || X <- [1,2]])]),
2458          {qlc, _, [{generate, _, {list, [1,2]}}],[]} = i(Q1),
2459          Q2 = qlc:q([X || X <- qlc:q([{X} || X <- [1,2]])]),
2460          {list,{list,[1,2]},_} = i(Q2),
2461          [{1},{2}] = qlc:eval(Q2),
2462          Q3 = qlc:q([{X,Y} || X <- qlc:q([X || X <- [a,b]]),
2463                               Y <- qlc:q([Z || Z <- [a,b]])]),
2464          {qlc, _, [{generate, _, {list, [a,b]}},
2465                    {generate, _, {list, [a,b]}}], []} = i(Q3),
2466          Q4 = qlc:q([X || X <- [a]]),
2467          {list, [a]} = i(Q4),
2468          Q5 = qlc:q([X || X <- qlc:q([Y || Y <- [a,b]], unique)]),
2469          {qlc, _, [{generate, _, {list, [a,b]}}], [{unique,true}]} =
2470             i(Q5)">>,
2471
2472       <<"H = qlc:q([X || X <- qlc:append([qlc:q([X || X <- [1,2]]),[1,2]])]),
2473          {append, [{list, [1,2]},{list, [1,2]}]} = i(H),
2474          [1,2,1,2] = qlc:e(H)">>,
2475
2476       <<"H = qlc:q([{X} || X <- [], X > 1]),
2477          {list, []} = i(H),
2478          [] = qlc:e(H)">>,
2479
2480       <<"H1 = qlc:q([{X} || X <- [], X > 1]),
2481          H = qlc:q([{X} || X <- H1, X < 10]),
2482          {list, []} = i(H),
2483          [] = qlc:e(H)">>,
2484
2485       <<"L = [1,2,3],
2486          QH1 = qlc:q([{X} || X <- L, X > 1]),
2487          QH2 = qlc:q([{X} || X <- QH1]),
2488          [{{2}},{{3}}] = qlc:e(QH2),
2489          {list,{list,{list,L},_},_} = i(QH2)">>,
2490
2491       <<"H = qlc:q([X || X <- qlc:q([Y || Y <- qlc:q([Z || Z <-[1,2,1]])])]),
2492          {list, [1,2,1]} = i(H),
2493          [1,2,1] = qlc:eval(H)">>,
2494
2495       <<"%% Used to replace empty ETS tables with [], but that won't work.
2496          E = ets:new(apa,[]),
2497          QH1 = qlc:q([{X} || X <- ets:table(E), X > 1]),
2498          QH2 = qlc:q([{X} || X <- QH1], cache),
2499          [] = qlc:e(QH2),
2500          {qlc,_,[{generate,_,{table,{ets,table,_}}}],[]} = i(QH2),
2501          ets:delete(E)">>,
2502
2503       <<"Q1 = qlc:q([W || W <- [a,b]]),
2504          Q2 = qlc:q([Z || Z <- qlc:sort([55296,56296,57296])], unique),
2505          Q3 = qlc:q([{X,Y} || X <- qlc:keysort([2], [{1,a}]),
2506                               Y <- qlc:append([Q1, Q2]),
2507                               X > Y]),
2508          {qlc, T1,
2509           [{generate, P1, {list, [{1,a}]}},
2510            {generate, P2, {append, [{list, [a,b]},
2511                                    {qlc, T2, [{generate, P3,
2512                                                {sort, {list,[55296,56296,57296]},[]}}],
2513                                     [{cache,ets},{unique,true}]}]}},F],
2514           []} = i(Q3, cache_all),
2515          {tuple, _, [{var,_,'X'}, {var,_,'Y'}]} = binary_to_term(T1),
2516          {var, _, 'X'} = binary_to_term(P1),
2517          {var, _, 'Y'} = binary_to_term(P2),
2518          {var, _, 'Z'} = binary_to_term(P3),
2519          {var, _, 'Z'} = binary_to_term(T2),
2520          {op, _, '>', {var, _, 'X'}, {var, _, 'Y'}} = binary_to_term(F),
2521          true = binary_to_list(<<
2522           \"beginV1=qlc:q([Z||Z<-qlc:sort([55296,56296,57296],[])],[{unique,true}]),\"
2523           \"qlc:q([{X,Y}||X<-[{1,a}],Y<-qlc:append([[a,b],V1]),X>Y])end\"
2524              >>) == format_info(Q3, true)">>,
2525
2526       <<"Q1 = qlc:q([{X} || X <- qlc:q([X || X <- [a,b]])]),
2527          {qlc, _, [{generate, _, {list, [a,b]}}], []} = i(Q1),
2528          Q2 = qlc:q([X || X <- qlc:q([{X} || X <- [a,b]])]),
2529          {list,{list,[a,b]},_} = i(Q2),
2530          [{a},{b}] = qlc:eval(Q2)">>,
2531
2532       <<"Q = qlc:keysort(2, [{1,a,b},{2,b,c},{3,4,c}]),
2533          {keysort,{list,[{1,a,b},{2,b,c},{3,4,c}]},2,[]} = i(Q),
2534          true = binary_to_list(<<
2535             \"qlc:keysort(2,[{1,a,b},{2,b,c},{3,4,c}],[])\">>)
2536              == format_info(Q, true),
2537          [{3,4,c},{1,a,b},{2,b,c}] = qlc:e(Q)">>,
2538
2539       <<"E = ets:new(foo, []),
2540          ets:insert(E, [{1},{2}]),
2541          Q = qlc_SUITE:default_table(E),
2542          {table,{'$MOD','$FUN',[]}} = i(Q),
2543          true = binary_to_list(<<\"'$MOD':'$FUN'()\">>)
2544                == format_info(Q, true),
2545          true = ets:delete(E)">>,
2546
2547       <<"\"[]\" = qlc:info([], flat),
2548          \"[]\" = qlc:info([]),
2549          \"[]\" = qlc:info([], {flat, true})">>,
2550
2551       <<"H = qlc:q([{X} || X <- [a,b]]),
2552         \"ets:match_spec_run([a,b],ets:match_spec_compile(\" ++ _ =
2553                format_info(H, true),
2554         \"ets:match_spec_run([a,b],ets:match_spec_compile(\" ++ _ =
2555                format_info(H, false)">>,
2556
2557       <<"H = qlc:q([{X} || X <- [a,b], begin true end]),
2558          true = binary_to_list(<<\"qlc:q([{X}||X<-[a,b],begintrueend])\">>)
2559             == format_info(H, true),
2560          true = binary_to_list(<<\"qlc:q([{X}||X<-[a,b],begintrueend])\">>)
2561             == format_info(H, false)">>,
2562
2563       <<"H = qlc:q([A || {A} <- [{1},{2}], (A =:= 2) andalso true]),
2564          {call,_,{remote,_,{atom,_,ets},{atom,_,match_spec_run}},_} =
2565             qlc:info(H, {format,abstract_code})">>,
2566
2567       <<"H = qlc:q([{X} || X <- qlc:q([{X} || X <- [a,b], begin true end],
2568                                       unique),
2569                            begin true end]),
2570          true = binary_to_list(<<
2571         \"beginV1=qlc:q([{X}||X<-[a,b],begintrueend],[{unique,true}]),\"
2572         \"qlc:q([{X}||X<-V1,begintrueend])end\">>) ==
2573              format_info(H, true),
2574          true = binary_to_list(<<
2575         \"qlc:q([{X}||X<-qlc:q([{X}||X<-[a,b],begintrueend],\"
2576         \"[{unique,true}]),begintrueend])\">>) == format_info(H, false)">>,
2577
2578       <<"H0 = qlc:q([{V3} || V3 <- qlc:q([{V1} || V1 <- [a,b],
2579                                                   begin true end], unique),
2580                              begin true end]),
2581          H = qlc:sort(H0),
2582          true = binary_to_list(<<
2583          \"qlc:sort(qlc:q([{V3}||V3<-qlc:q([{V1}||\"
2584          \"V1<-[a,b],begintrueend],[{unique,true}]),begintrueend]),[])\">>)
2585              == format_info(H, false),
2586          true = binary_to_list(<<
2587          \"beginV2=qlc:q([{V1}||V1<-[a,b],begintrueend],[{unique,true}]),\"
2588          \"V4=qlc:q([{V3}||V3<-V2,begintrueend]),qlc:sort(V4,[])end\">>)
2589              == format_info(H, true)">>,
2590
2591       <<"H0 = qlc:q([X || X <- [true], begin true end]),
2592          H1 = qlc:q([{X} || X <- [a,b], begin true end],
2593                     [{unique,begin [T] = qlc:e(H0), T end}]),
2594          {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},
2595                  [{lc,_,{tuple,_,[{var,_,'X'}]},
2596                         [{generate,_,{var,_,'X'},
2597                                      {cons,_,{atom,_,a},_}},
2598                          {block, _, [{atom, _, true}]}]},
2599                   {cons,_,_,_}]} = i(H1, {format, abstract_code})">>,
2600
2601       <<"E = ets:new(apa, [duplicate_bag]),
2602          true = ets:insert(E, [{1,a},{2,b},{3,c},{4,d}]),
2603          QH = qlc:q([X || {X,_} <- ets:tab2list(E), X > 2], unique),
2604          {qlc, _, [{generate, _, {list, _, _MS}}], [{unique, true}]} =
2605                i(QH),
2606          [3,4] = lists:sort(qlc:e(QH)),
2607          ets:delete(E)">>,
2608
2609       %% "Imported" variable.
2610       <<"F = fun(U) -> qlc:q([{X} || X <- [1,2,3,4,5,6], X > U]) end,
2611          QH = F(4),
2612          {call, _ ,
2613                {remote, _, {atom, _, ets},{atom, _, match_spec_run}},
2614                [{string, _, [1,2,3,4,5,6]},
2615                 {call, _,
2616                       _compile,
2617                       [{cons, _,
2618                              {tuple, _,
2619                                     [{atom, _,'$1'},
2620                                      {cons, _,
2621                                            {tuple,
2622                                                 _,
2623                                                [{atom, _,'>'},
2624                                                 {atom, _,'$1'},
2625                                                 {tuple,
2626                                                      _,
2627                                                     [{atom, _,const},
2628                                                      {integer, _,4}]}]},
2629                                            _},
2630                                      {cons, _, _, _}]},
2631                              {nil,_}}]}]} = i(QH, {format, abstract_code}),
2632          [{5},{6}] = qlc:e(QH),
2633          [{4},{5},{6}] = qlc:e(F(3))">>,
2634
2635          <<"Fun = fun ?MODULE:i/2,
2636             L = [{#{k => #{v => Fun}}, Fun}],
2637             H = qlc:q([Q || Q <- L, Q =:= {#{k => #{v => Fun}}, Fun}]),
2638             L = qlc:e(H),
2639             {call,_,_,[{lc,_,{var,_,'Q'},
2640                         [{generate,_,_,_},
2641                          {op,_,_,_,_}]}]} =
2642                qlc:info(H, [{format,abstract_code}])">>
2643
2644       ],
2645    run(Config, Ts),
2646    ok.
2647
2648%% Nested QLC expressions. QLC expressions in filter and template.
2649nested_info(Config) when is_list(Config) ->
2650    Ts = [
2651       <<"L = [{1,a},{2,b},{3,c}],
2652          Q = qlc:q(
2653                [{X,R} ||
2654                    {X,_} <- qlc_SUITE:table(L, []),
2655                    begin % X imported
2656                        R = qlc:e(qlc:q([{X,Y} || {Y,_}
2657                                                    <- qlc_SUITE:table(L, []),
2658                                                  Y > X])),
2659                        true
2660                    end]),
2661          true = binary_to_list(<<
2662            \"qlc:q([{X,R}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}]),\"
2663            \"beginR=qlc:e(qlc:q([{X,Y}||{Y,_}<-qlc_SUITE:table(L,[]),Y>X]))\"
2664            \",trueend])\">>) == format_info(Q, true),
2665          [{1,[{1,2},{1,3}]},{2,[{2,3}]},{3,[]}] = qlc:e(Q)">>,
2666
2667       <<"L = [{1,a},{2,b},{3,c}],
2668          Q = qlc:q( % X imported
2669                [{X,qlc:e(qlc:q([{X,Y} || {Y,_} <- qlc_SUITE:table(L, []),
2670                                          Y > X]))} ||
2671                    {X,_} <- qlc_SUITE:table(L, [])]),
2672          true = binary_to_list(<<
2673            \"qlc:q([{X,qlc:e(qlc:q([{X,Y}||{Y,_}<-qlc_SUITE:table(L,[]),\"
2674            \"Y>X]))}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}])])\">>)
2675              == format_info(Q, true),
2676          [{1,[{1,2},{1,3}]},{2,[{2,3}]},{3,[]}] = qlc:e(Q)">>,
2677
2678       <<"L = [{1,a},{2,b},{3,c}],
2679          Q = qlc:q(
2680                [{X,R} ||
2681                    {X,_} <- qlc_SUITE:table(L, []),
2682                    begin % X imported
2683                        R = qlc:e(qlc:q([{X,Y} || {Y,_}
2684                                                    <- qlc_SUITE:table(L, []),
2685                                                  Y =:= X])),
2686                        true
2687                    end]),
2688          true = binary_to_list(<<
2689            \"qlc:q([{X,R}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}]),\"
2690            \"beginR=qlc:e(qlc:q([{X,Y}||{Y,_}<-qlc_SUITE:table(L,[]),\"
2691            \"Y=:=X])),trueend])\">>) == format_info(Q, true),
2692          [{1,[{1,1}]},{2,[{2,2}]},{3,[{3,3}]}] = qlc:e(Q)">>,
2693
2694       <<"L = [{1,a},{2,b},{3,c}],
2695          Q = qlc:q(
2696                [{X, % X imported
2697                  qlc:e(qlc:q([{X,Y} || {Y,_} <- qlc_SUITE:table(L, []),
2698                                        Y =:= X]))} ||
2699                    {X,_} <- qlc_SUITE:table(L, [])]),
2700          true = binary_to_list(<<
2701            \"qlc:q([{X,qlc:e(qlc:q([{X,Y}||{Y,_}<-qlc_SUITE:table(L,[]),\"
2702            \"Y=:=X]))}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}])])\">>)
2703             == format_info(Q, true),
2704          [{1,[{1,1}]},{2,[{2,2}]},{3,[{3,3}]}] = qlc:e(Q)">>,
2705
2706       <<"L = [{1,a},{2,b},{3,c}],
2707          Q = qlc:q(
2708                [{X,R} ||
2709                    {X,_} <- qlc_SUITE:table(L, []),
2710                    begin
2711                        R = qlc:e(qlc:q([Y || Y <- [X]])),
2712                        true
2713                    end]),
2714          true = binary_to_list(<<
2715            \"qlc:q([{X,R}||{X,_}<-qlc_SUITE:the_list([{1,a},{2,b},{3,c}]),\"
2716            \"beginR=qlc:e(qlc:q([Y||Y<-[X]])),trueend])\">>)
2717             == format_info(Q, true),
2718          [{1,[1]},{2,[2]},{3,[3]}] = qlc:e(Q)">>,
2719
2720       <<"L = [{1,a},{2,b},{3,c}],
2721          Q = qlc:q(
2722                [{X,qlc:e(qlc:q([Y || Y <- [X]]))} ||
2723                    {X,_} <- qlc_SUITE:table(L, [])]),
2724          true = binary_to_list(<<
2725            \"qlc:q([{X,qlc:e(qlc:q([Y||Y<-[X]]))}||{X,_}<-qlc_SUITE:\"
2726            \"the_list([{1,a},{2,b},{3,c}])])\">>) == format_info(Q, true),
2727          [{1,[1]},{2,[2]},{3,[3]}] = qlc:e(Q)">>,
2728
2729       <<"L = [{1,a},{2,b}],
2730          Q = qlc:q(
2731                [{X,Y} ||
2732                    {X,_} <- qlc_SUITE:table(L, []),
2733                    {Y,_} <- qlc:q(
2734                               [{Z,V} ||
2735                                   {Z,_} <- qlc_SUITE:table(L, []),
2736                                   {V} <- qlc:q(
2737                                              [{W} || W
2738                                                  <- qlc_SUITE:table(L, [])])
2739                                      ])
2740                       ]),
2741          true = binary_to_list(<<
2742           \"beginV1=qlc:q([{W}||W<-qlc_SUITE:the_list([{1,a},{2,b}])]),\"
2743           \"V2=qlc:q([{Z,V}||{Z,_}<-qlc_SUITE:the_list([{1,a},{2,b}]),\"
2744           \"{V}<-V1]),qlc:q([{X,Y}||{X,_}<-qlc_SUITE:the_list([{1,a},\"
2745           \"{2,b}]),{Y,_}<-V2])end\">>) == format_info(Q, true),
2746          [{1,1},{1,1},{1,2},{1,2},{2,1},{2,1},{2,2},{2,2}] = qlc:e(Q)">>
2747
2748       ],
2749    run(Config, Ts),
2750    ok.
2751
2752
2753%% Lookup keys. Mostly test of patterns.
2754lookup1(Config) when is_list(Config) ->
2755    Ts = [
2756       <<"etsc(fun(E) ->
2757                Q = qlc:q([A || {A=3} <- ets:table(E)]),
2758                [3] = qlc:eval(Q),
2759                [3] = lookup_keys(Q)
2760          end, [{1},{2},{3},{4}])">>,
2761
2762       <<"etsc(fun(E) ->
2763                Q = qlc:q([A || {A=3} <- ets:table(E)],{max_lookup,0}),
2764                [3] = qlc:eval(Q),
2765                false = lookup_keys(Q)
2766          end, [{1},{2},{3},{4}])">>,
2767
2768       <<"%% The lookup and max_lookup options interact.
2769          etsc(fun(E) ->
2770                Q = qlc:q([X || {X} <- ets:table(E),
2771                                (X =:= 1) or (X =:= 2)],
2772                          [{lookup,true},{max_lookup,1}]),
2773                {'EXIT', {no_lookup_to_carry_out, _}} = (catch qlc:e(Q))
2774         end, [{1},{2}])">>,
2775
2776       <<"etsc(fun(E) ->
2777                Q = qlc:q([{A,B,C,D} || {A,B}={C,D} <- ets:table(E)]),
2778                [{1,2,1,2},{3,4,3,4}] = lists:sort(qlc:eval(Q)),
2779                false = lookup_keys(Q)
2780          end, [{1,2},{3,4}])">>,
2781
2782       <<"etsc(fun(E) ->
2783                Q = qlc:q([{A,B,D} || {A,B}={D,A} <- ets:table(E)]),
2784                [{1,1,1},{2,2,2}] = lists:sort(qlc:eval(Q)),
2785                false = lookup_keys(Q)
2786          end, [{1,2},{2,2},{1,1}])">>,
2787
2788       <<"etsc(fun(E) ->
2789                Q = qlc:q([{A,B,D} || {A,B}={D,A} <- ets:table(E),
2790                                      (D =:= 2) or (B =:= 1)],
2791                          {max_lookup,infinity}),
2792                [{1,1,1},{2,2,2}] = qlc:eval(Q),
2793                [1,2] = lookup_keys(Q)
2794         end, [{1,2},{2,2},{1,1}])">>,
2795
2796       <<"etsc(fun(E) ->
2797                Q = qlc:q([{A,B,D} || {A,B}={D,A} <- ets:table(E),
2798                                      (D =:= 2) xor (B =:= 1)]),
2799                [{1,1,1},{2,2,2}] = qlc:eval(Q),
2800                [1,2] = lookup_keys(Q)
2801         end, [{1,2},{2,2},{1,1}])">>,
2802
2803       <<"etsc(fun(E) ->
2804                Q = qlc:q([3 || {{[3,4],apa}} <- ets:table(E)]),
2805                [3] = qlc:e(Q),
2806                [{[3,4],apa}] = lookup_keys(Q)
2807        end, [{{[4,3],foo}},{{[3,4],apa}}])">>,
2808
2809       <<"etsc(fun(E) ->
2810                Q = qlc:q([3 || {3} <- ets:table(E)]),
2811                [3] = qlc:e(Q),
2812                [3] = lookup_keys(Q)
2813        end, [{2},{3},{4}])">>,
2814
2815       <<"etsc(fun(E) ->
2816                Q = qlc:q([{X,Y,Z} || {{X,_},Y,Y={_,Z},X,Y} <- ets:table(E)]),
2817                [] = qlc:e(Q),
2818                false = lookup_keys(Q)
2819        end, [{{1,1},1,{1,1},1,1}])">>,
2820
2821       <<"etsc(fun(E) ->
2822                Q = qlc:q([X || {X,X=2} <- ets:table(E)]),
2823                [2] = qlc:e(Q),
2824                [2] = lookup_keys(Q)
2825        end, [{2,2},{3,3}])">>,
2826
2827       <<"etsc(fun(E) ->
2828                Q = qlc:q([X || {{_,3}={4,_}=X} <- ets:table(E)]),
2829                [{4,3}] = qlc:e(Q),
2830                [{4,3}] = lookup_keys(Q)
2831        end, [{{2,3}},{{4,3}}])">>,
2832
2833       <<"U = 17.0,
2834          etsc(fun(E) ->
2835                Q = qlc:q([X || {_=X=_} <- ets:table(E)]),
2836                [U] = qlc:e(Q),
2837                false = lookup_keys(Q)
2838        end, [{U},{U+U,U}])">>,
2839
2840       <<"etsc(fun(E) ->
2841                Q = qlc:q([{X,Y,Z,W} || {X=Y}=Z={V=W} <- ets:table(E),
2842                                        V == {h,g}]),
2843                [{{h,g},{h,g},{{h,g}},{h,g}}] = qlc:e(Q),
2844                [{h,g}] = lookup_keys(Q)
2845        end, [{h,g},{{h,g}}])">>,
2846
2847       <<"etsc(fun(E) ->
2848                Q = qlc:q([{C,Y,Z,X} || {{X=Y}=Z}={{A=B}=C} <- ets:table(E),
2849                                        A == a, B =/= c]),
2850                [{{a},a,{a},a}] = qlc:e(Q),
2851                [{a}] = lookup_keys(Q)
2852        end, [{{1}},{{a}}])">>,
2853
2854       <<"etsc(fun(E) ->
2855               Q = qlc:q([{A,D,Y,X} ||
2856                             {{A={B=C}},{D={C}}} = {X,Y} <- ets:table(E),
2857                             [] == B]),
2858                [{{[]},{[]},{{[]}},{{[]}}}] = qlc:e(Q),
2859                [{{[]}}] = lookup_keys(Q)
2860        end, [{{{[]}},{{[]}}}])">>,
2861
2862       {cres,
2863        <<"etsc(fun(E) ->
2864                 Q = qlc:q([X || {X}=X <- ets:table(E)]),
2865                 [] = qlc:e(Q),
2866                 false = lookup_keys(Q)
2867         end, [{1},{a}])">>,
2868        %% {warnings,[{{2,37},qlc,nomatch_pattern}]}},
2869        []},
2870
2871       <<"etsc(fun(E) ->
2872                Q = qlc:q([X || {X=X,Y=Y}={Y=Y,X=X} <- ets:table(E),
2873                                {} == X]),
2874                [{}] = qlc:e(Q),
2875                [{}] = lookup_keys(Q)
2876        end, [{{},{}},{[],[]}])">>,
2877
2878       <<"etsc(fun(E) ->
2879                Q = qlc:q([X || {3+4=7,X} <- ets:table(E),
2880                                X =:= 3+997]),
2881                [1000] = qlc:e(Q),
2882                [7] = lookup_keys(Q)
2883        end, [{7,1000},{8,1000}])">>,
2884
2885       <<"etsc(fun(E) ->
2886                Q = qlc:q([{X, Y} || [X]=[Y] <- ets:table(E)]),
2887                [] = qlc:eval(Q),
2888                false = lookup_keys(Q)
2889        end, [{a}])">>,
2890
2891       {cres,
2892        <<"etsc(fun(E) ->
2893                 Q = qlc:q([X || X={1,2,3,X,5} <- ets:table(E)]),
2894                 [] = qlc:e(Q),
2895                 false = lookup_keys(Q)
2896         end, [{a},{b}])">>,
2897        %% {warnings,[{{2,35},qlc,nomatch_pattern}]}},
2898        []},
2899
2900       {cres,
2901        <<"etsc(fun(E) ->
2902                 Q = qlc:q([X || X=[1,2,3,X,5] <- ets:table(E)]),
2903                 [] = qlc:e(Q),
2904                 false = lookup_keys(Q)
2905         end, [{a},{b}])">>,
2906        %% {warnings,[{{2,35},qlc,nomatch_pattern}]}},
2907        []},
2908
2909       <<"etsc(fun(E) ->
2910                Q = qlc:q([X || X = <<X>> <- ets:table(E)]),
2911                [] = qlc:e(Q),
2912                false = lookup_keys(Q)
2913        end, [{a},{b}])">>,
2914
2915       <<"Tre = 3.0,
2916          etsc(fun(E) ->
2917                Q = qlc:q([{A,B} || {A,B}={{a,C},{a,C}} <- ets:table(E),
2918                                    C =:= Tre]),
2919                [] = qlc:e(Q),
2920                [{a,Tre}] = lookup_keys(Q)
2921        end, [{a,b}])">>,
2922
2923       <<"A = 3,
2924          etsc(fun(E) ->
2925                Q = qlc:q([X || X <- ets:table(E), A =:= element(1, X)]),
2926                [{3,3}] = qlc:e(Q),
2927                [3] = lookup_keys(Q)
2928        end, [{1,a},{3,3}])">>,
2929
2930       <<"A = 3,
2931          etsc(fun(E) ->
2932                Q = qlc:q([X || X <- ets:table(E), A =:= erlang:element(1, X)]),
2933                [{3,3}] = qlc:e(Q),
2934                [3] = lookup_keys(Q)
2935        end, [{1,a},{3,3}])">>,
2936
2937       <<"etsc(fun(E) ->
2938                A = 3,
2939                Q = qlc:q([X || X <- ets:table(E),
2940                                A == element(1,X),
2941                                element(1,X) =:= a]),
2942                [] = qlc:e(Q),
2943                [a] = lookup_keys(Q)
2944        end, [{a},{b},{c}])">>,
2945
2946       {cres,
2947        <<"etsc(fun(E) ->
2948                 Q = qlc:q([X || {X = {[a,Z]},
2949                                  Z = [foo, {[Y]}],
2950                                  Y = {{foo,[X]}}} <- ets:table(E)]),
2951                 [] = qlc:e(Q),
2952                 false = lookup_keys(Q)
2953         end, [{a,b,c},{d,e,f}])">>,
2954        %% {warnings,[{{2,34},qlc,nomatch_pattern}]}}
2955        []}
2956
2957       ],
2958    run(Config, Ts),
2959    ok.
2960
2961%% Lookup keys. Mostly test of filters.
2962lookup2(Config) when is_list(Config) ->
2963    Ts = [
2964       <<"%% Only guards are inspected. No lookup.
2965          etsc(fun(E) ->
2966                 Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
2967                                     ((Y = X) =:= 3)]),
2968                 {'EXIT', {{badmatch,4},_}} = (catch qlc:e(Q))
2969         end, [{3,3},{4,true}])">>,
2970
2971       <<"%% Only guards are inspected. No lookup.
2972          etsc(fun(E) ->
2973                 Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
2974                                     Y = (X =:= 3)]),
2975                 {'EXIT', {{badmatch,false},_}} = (catch qlc:e(Q))
2976         end, [{false,3},{true,3}])">>,
2977
2978       <<"%% Only guards are inspected. No lookup.
2979          etsc(fun(E) ->
2980                 Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
2981                                     Y = (X =:= 3)]),
2982                 {'EXIT', {{badmatch,false},_}} = (catch qlc:e(Q))
2983         end, [{3,true},{4,true}])">>,
2984
2985       <<"%% Only guards are inspected. No lookup.
2986          E1 = ets:new(e, [ordered_set]),
2987          true = ets:insert(E1, [{1,1}, {2,2}, {3,3}, {4,4}, {5,5}]),
2988          E2 = ets:new(join, [ordered_set]),
2989          true = ets:insert(E2, [{true,1},{false,2}]),
2990          Q = qlc:q([{X,Z} || {_,X} <- ets:table(E1),
2991                              {Y,Z} <- ets:table(E2),
2992                              Y = (X =:= 3)]),
2993          {'EXIT', {{badmatch,false},_}} = (catch qlc:e(Q)),
2994          ets:delete(E1),
2995          ets:delete(E2)">>,
2996
2997       <<"etsc(fun(E) ->
2998                Q = qlc:q([{A,B,D} || {A,B}={D,A} <- ets:table(E),
2999                                      (A =:= 3) or (4 =:= D)]),
3000                [{3,3,3},{4,4,4}] = lists:sort(qlc:e(Q)),
3001                [3,4] = lookup_keys(Q)
3002        end, [{2,2},{3,3},{4,4}])">>,
3003
3004       <<"etsc(fun(E) ->
3005               Q = qlc:q([X || {X,U} <- ets:table(E), X =:= U]),
3006               [1] = qlc:e(Q),
3007               false = lookup_keys(Q)
3008       end, [{1,1}])">>,
3009
3010       {cres,
3011        <<"etsc(fun(E) ->
3012                 Q = qlc:q([{X,Y} || {X=Y} <- ets:table(E),
3013                                     {[X],4} =:= {[3],X}]),
3014                 [] = qlc:e(Q),
3015                 false = lookup_keys(Q)
3016         end, [{1}, {2}])">>,
3017        %% {warnings,[{{3,46},qlc,nomatch_filter}]}},
3018        []},
3019
3020       {cres,
3021        <<"etsc(fun(E) ->
3022                Q = qlc:q([X || {X} <- ets:table(E),
3023                                X == 1, X =:= 2]),
3024                [] = qlc:e(Q),
3025                false = lookup_keys(Q)
3026        end, [{1}, {2}])">>,
3027        %% {warnings,[{{3,43},qlc,nomatch_filter}]}},
3028        []},
3029
3030       {cres,
3031        <<"etsc(fun(E) ->
3032                 Q = qlc:q([{X,Y} || {X=Y} <- ets:table(E),
3033                                     {[X,Y],4} =:= {[3,X],X}]),
3034                 [] = qlc:e(Q),
3035                 false = lookup_keys(Q)
3036         end, [{1}, {2}])">>,
3037        %% {warnings,[{{3,48},qlc,nomatch_filter}]}},
3038        []},
3039
3040       <<"etsc(fun(E) ->
3041                Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
3042                                    ({X,3} =:= {Y,Y}) or (X =:= 4)]),
3043                [{3,3},{4,4}] = lists:sort(qlc:e(Q)),
3044                [3,4] = lookup_keys(Q)
3045        end, [{2,2},{3,3},{4,4},{5,5}])">>,
3046
3047       {cres,
3048        <<"etsc(fun(E) ->
3049                 Q = qlc:q([X || {X} <- ets:table(E), {[X]} =:= {[3,4]}]),
3050                 [] = qlc:e(Q),
3051                 false = lookup_keys(Q)
3052         end, [{[3]},{[3,4]}])">>,
3053        %% {warnings,[{{2,61},qlc,nomatch_filter}]}},
3054        []},
3055
3056       <<"etsc(fun(E) ->
3057                U = 18,
3058                Q = qlc:q([{X,Y} || {X=Y} <- ets:table(E), [X|a] =:= [3|U]]),
3059                [] = qlc:e(Q),
3060                [3] = lookup_keys(Q)
3061        end, [{2}, {3}])">>,
3062
3063       <<"etsc(fun(E) ->
3064                U = 18, V = 19,
3065                Q = qlc:q([{X,Y} || {X=Y} <- ets:table(E),
3066                                    [X|V] =:= [3|U+1]]),
3067                [{3,3}] = qlc:e(Q),
3068                [3] = lookup_keys(Q)
3069        end, [{2},{3}])">>,
3070
3071       <<"%% Blocks are not handled.
3072          etsc(fun(E) ->
3073                Q = qlc:q([X || {X} <- ets:table(E), begin X == a end]),
3074                [a] = qlc:e(Q),
3075                false = lookup_keys(Q)
3076        end, [{a},{b}])">>,
3077
3078       {cres,
3079        <<"etsc(fun(E) ->
3080                 Q = qlc:q([X || {X} <- ets:table(E),
3081                                 (3 =:= X) or (X =:= 12),
3082                                 (8 =:= X) or (X =:= 10)]),
3083                 [] = lists:sort(qlc:e(Q)),
3084                 false = lookup_keys(Q)
3085         end, [{2},{3},{4},{8}])">>,
3086        %% {warnings,[{{4,44},qlc,nomatch_filter}]}},
3087        []},
3088
3089       {cres,
3090        <<"etsc(fun(E) ->
3091                 Q = qlc:q([X || {X} <- ets:table(E),
3092                                 ((3 =:= X) or (X =:= 12))
3093                                  and ((8 =:= X) or (X =:= 10))]),
3094                 [] = lists:sort(qlc:e(Q)),
3095                 false = lookup_keys(Q)
3096         end, [{2},{3},{4},{8}])">>,
3097        %% {warnings,[{{4,35},qlc,nomatch_filter}]}},
3098        []},
3099
3100       {cres,
3101        <<"F = fun(U) ->
3102                Q = qlc:q([X || {X} <- [a,b,c],
3103                                 X =:= if U -> true; true -> false end]),
3104                [] = qlc:eval(Q),
3105                false = lookup_keys(Q)
3106              end,
3107           F(apa)">>, [], {warnings,[{{3,43},sys_core_fold,{nomatch,guard}}]}},
3108
3109       {cres,
3110        <<"etsc(fun(E) ->
3111                 Q = qlc:q([X || {X=1,X} <- ets:table(E), X =:= 2]),
3112                 [] = qlc:e(Q),
3113                 false = lookup_keys(Q)
3114           end, [{1,1},{2,1}])">>,
3115        %% {warnings,[{{2,61},qlc,nomatch_filter}]}},
3116        []},
3117
3118       <<"Two = 2.0,
3119          etsc(fun(E) ->
3120                Q = qlc:q([X || {X} <- ets:table(E), X =:= Two]),
3121                [Two] = qlc:e(Q),
3122                [Two] = lookup_keys(Q)
3123        end, [{2.0},{2}])">>,
3124
3125       <<"etsc(fun(E) ->
3126                %% This float is equal (==) to an integer. Not a constant!
3127                Q = qlc:q([X || {X} <- ets:table(E), X == {a,b,c,[2.0]}]),
3128                [_,_] = qlc:e(Q),
3129                false = lookup_keys(Q)
3130        end, [{{a,b,c,[2]}},{{a,b,c,[2.0]}}])">>,
3131
3132       <<"%% Must _not_ regard floats as constants. Check imported variables
3133          %% in runtime.
3134          etsc(fun(E) ->
3135                U = 3.0,
3136                QH = qlc:q([X || {X,_} <- ets:table(E), X =:= U]),
3137                [] = qlc:e(QH),
3138                [U] = lookup_keys(QH)
3139        end, [{1,a},{2,b},{3,c},{4,d}])">>,
3140
3141       <<"etsc(fun(E) ->
3142                Q = qlc:q([X || {X} <- ets:table(E),
3143                                length(X) =:= 1]),
3144                [[1]] = qlc:e(Q),
3145                false = lookup_keys(Q)
3146        end, [{[1]},{[2,3]}])">>,
3147
3148       <<"etsc(fun(E) ->
3149                A=3,
3150                Q = qlc:q([X || {X,Y} <- ets:table(E), X =:= A, Y =:= 3]),
3151                [3] = qlc:e(Q),
3152                [3] = lookup_keys(Q)
3153        end, [{3,3},{4,3}])">>,
3154
3155       <<"etsc(fun(E) ->
3156                A = 1,
3157                Q = qlc:q([X || {X} <- ets:table(E),
3158                                X =:= 1, <<X>> =:= <<A>>]),
3159                [1] = qlc:e(Q),
3160                [1] = lookup_keys(Q)
3161        end, [{1},{2}])">>,
3162
3163       <<"etsc(fun(E) ->
3164                Q = qlc:q([X || {X} <- ets:table(E), X == a]),
3165                [a] = qlc:e(Q),
3166                [a] = lookup_keys(Q)
3167        end, [{a},{b},{c}])">>,
3168
3169       <<"etsc(fun(E) ->
3170                 Q = qlc:q([X || {X}=Y <- ets:table(E),
3171                                 element(2, Y) == b,
3172                                 X =:= 1]),
3173                 [] = qlc:e(Q),
3174                 false = lookup_keys(Q)
3175        end, [{1,b},{2,3}])">>,
3176
3177       <<"etsc(fun(E) ->
3178                Q = qlc:q([X || {X} <- ets:table(E), element(1,{X}) =:= 1]),
3179                [1] = qlc:e(Q),
3180                [1] = lookup_keys(Q)
3181        end, [{1}, {2}])">>,
3182
3183       <<"etsc(fun(E) ->
3184                Q = qlc:q([X || {X} <- ets:table(E), 1 =:= element(1,{X})]),
3185                [1] = qlc:e(Q),
3186                [1] = lookup_keys(Q)
3187        end, [{1}, {2}])">>,
3188
3189       {cres,
3190        <<"etsc(fun(E) ->
3191                 Q = qlc:q([X || {X} <- ets:table(E),
3192                                 X =:= {1},
3193                                 element(1,X) =:= 2]),
3194                 [] = qlc:e(Q),
3195                 false = lookup_keys(Q)
3196         end, [{{1}},{{2}}])">>,
3197        %% {warnings,[{{4,47},qlc,nomatch_filter}]}},
3198        []},
3199
3200       {cres,
3201        <<"etsc(fun(E) ->
3202                 Q = qlc:q([X || {X} <- ets:table(E),
3203                                 X =:= {1},
3204                                 element(1,X) =:= element(1, {2})]),
3205                 [] = qlc:e(Q),
3206                 false = lookup_keys(Q)
3207         end, [{{1}},{{2}}])">>,
3208        %% {warnings,[{{4,47},qlc,nomatch_filter}]}},
3209        []},
3210
3211       <<"etsc(fun(E) ->
3212                Q = qlc:q([X || {X} <- ets:table(E),
3213                                element(1,X) =:= 1, X =:= {1}]),
3214                [{1}] = qlc:e(Q),
3215                [{1}] = lookup_keys(Q)
3216        end, [{{1}},{{2}}])">>,
3217
3218       <<"etsc(fun(E) ->
3219                Q = qlc:q([X || {X} <- ets:table(E),
3220                                {{element(1,element(1,{{1}}))}} =:= {X}]),
3221                [{1}] = qlc:e(Q),
3222                [{1}] = lookup_keys(Q)
3223        end, [{{1}},{{2}}])">>,
3224
3225       <<"etsc(fun(E) ->
3226                Q = qlc:q([X || X <- ets:table(E),
3227                                {element(1,element(1, {{1}}))} =:=
3228                                      {element(1,X)}]),
3229                [{1}] = qlc:e(Q),
3230                [1] = lookup_keys(Q)
3231        end, [{1},{2}])">>,
3232
3233       <<"etsc(fun(E) ->
3234                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3235                                (X =:= 1) and (Y =:= 2)
3236                                    or (X =:= 3) and (Y =:= 4)]),
3237                [1,3] = lists:sort(qlc:e(Q)),
3238                [{1,2}, {3,4}] = lookup_keys(Q)
3239        end, [{{1,2}}, {{3,4}}, {{2,3}}])">>,
3240
3241       <<"etsc(fun(E) ->
3242                Q = qlc:q([X || {{X,a}} <- ets:table(E), X =:= 3]),
3243                [3] = qlc:e(Q),
3244                [{3,a}] = lookup_keys(Q)
3245        end, [{{3,a}},{{3,b}}])">>,
3246
3247       <<"etsc(fun(E) ->
3248                Q = qlc:q([X || {{X,Y},_Z} <- ets:table(E),
3249                                X =:= 3, Y =:= a]),
3250                [3] = qlc:e(Q),
3251                [{3,a}] = lookup_keys(Q)
3252        end, [{{3,a},3}, {{4,a},3}])">>,
3253
3254       <<"etsc(fun(E) ->
3255                Q = qlc:q([X || {{X,Y},_Z} <- ets:table(E),
3256                                (X =:= 3) and (Y =:= a)
3257                                   or (X =:= 4) and (Y =:= a)]),
3258                [3,4] = qlc:e(Q),
3259                [{3,a}, {4,a}] = lookup_keys(Q)
3260        end, [{{3,a},3}, {{4,a},3}])">>,
3261
3262       {cres,
3263        <<"etsc(fun(E) ->
3264                 Q = qlc:q([X || {X} <- ets:table(E),
3265                                 (X =:= 3) and (X =:= a)]),
3266                 [] = qlc:e(Q),
3267                 false = lookup_keys(Q)
3268         end, [{3}, {4}])">>,
3269        %% {warnings,[{{3,44},qlc,nomatch_filter}]}},
3270        []},
3271
3272       <<"etsc(fun(E) ->
3273                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3274                                X =:= 3, ((Y =:= a) or (Y =:= b))]),
3275                [3,3] = qlc:e(Q),
3276                [{3,a},{3,b}] = lists:sort(lookup_keys(Q))
3277        end, [{{3,a}},{{2,b}},{{3,b}}])">>,
3278
3279       <<"etsc(fun(E) ->
3280                Q = qlc:q([X || {X,Y} <- ets:table(E),
3281                                ((X =:= 3) or (Y =:= 4))  and (X == a)]),
3282                [a] = qlc:e(Q),
3283                [a] = lookup_keys(Q)
3284        end, [{a,4},{3,3}])">>,
3285
3286       <<"etsc(fun(E) ->
3287                Q = qlc:q([X || {X,Y} <- ets:table(E),
3288                                (X =:= 3) or ((Y =:= 4)  and (X == a))]),
3289                [3,a] = lists:sort(qlc:e(Q)),
3290                [3,a] = lookup_keys(Q)
3291        end, [{a,4},{3,3}])">>,
3292
3293       <<"etsc(fun(E) ->
3294                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3295                                (X =:= 3) or ((Y =:= 4)  and (X == a))]),
3296                [3,a] = lists:sort(qlc:e(Q)),
3297                false = lookup_keys(Q)
3298        end, [{{3,a}},{{2,b}},{{a,4}}])">>,
3299
3300       <<"etsc(fun(E) ->
3301                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3302                                ((X =:= 3) or (Y =:= 4))  and (X == a)]),
3303                [a] = lists:sort(qlc:e(Q)),
3304                [{a,4}] = lookup_keys(Q)
3305        end, [{{3,a}},{{2,b}},{{a,4}}])">>,
3306
3307        <<"etsc(fun(E) ->
3308                NoAnswers = 3*3*3+2*2*2,
3309                Q = qlc:q([{X,Y,Z} ||
3310                              {{X,Y,Z}} <- ets:table(E),
3311                              (((X =:= 4) or (X =:= 5)) and
3312                               ((Y =:= 4) or (Y =:= 5)) and
3313                               ((Z =:= 4) or (Z =:= 5))) or
3314                              (((X =:= 1) or (X =:= 2) or (X =:= 3)) and
3315                               ((Y =:= 1) or (Y =:= 2) or (Y =:= 3)) and
3316                               ((Z =:= 1) or (Z =:= 2) or (Z =:= 3)))],
3317                          {max_lookup, NoAnswers}),
3318                 {list, {table, _}, _} = i(Q),
3319                 [{1,1,1},{2,2,2},{3,3,3}] = lists:sort(qlc:e(Q)),
3320                 true = NoAnswers =:= length(lookup_keys(Q))
3321         end, [{{1,1,1}},{{2,2,2}},{{3,3,3}},{{3,3,4}},{{4,1,1}}])">>,
3322
3323        <<"etsc(fun(E) ->
3324                Q = qlc:q([{X,Y,Z} ||
3325                              {{X,Y,Z}} <- ets:table(E),
3326                              (((X =:= 4) or (X =:= 5)) and
3327                               ((Y =:= 4) or (Y =:= 5)) and
3328                               ((Z =:= 4) or (Z =:= 5))) or
3329                              (((X =:= 1) or (X =:= 2) or (X =:= 3)) and
3330                               ((Y =:= 1) or (Y =:= 2) or (Y =:= 3)) and
3331                               ((Z =:= 1) or (Z =:= 2) or (Z =:= 3)))],
3332                          {max_lookup, 10}),
3333                 [{1,1,1},{2,2,2},{3,3,3}] = lists:sort(qlc:e(Q)),
3334                 {table,{ets,table,[_,[{traverse,{select,_}}]]}} = i(Q)
3335         end, [{{1,1,1}},{{2,2,2}},{{3,3,3}},{{3,3,4}},{{4,1,1}}])">>,
3336
3337       <<"etsc(fun(E) ->
3338                Q = qlc:q([X || X={_,_,_} <- ets:table(E),
3339                                element(1, X) =:= 3, element(2, X) == a]),
3340                [{3,a,s}] = qlc:e(Q),
3341                [3] = lookup_keys(Q)
3342        end, [{1,c,q},{2,b,r},{3,a,s}])">>,
3343
3344       <<"etsc(fun(E) ->
3345                Q = qlc:q([X || X <- ets:table(E),
3346                                element(0, X) =:= 3]),
3347                [] = qlc:e(Q),
3348                false = lookup_keys(Q)
3349        end, [{1},{2}])">>,
3350
3351       <<"etsc(fun(E) ->
3352                F = fun(_) -> 3 end,
3353                %% No occurs check; X =:= F(X) is ignored.
3354                Q = qlc:q([X || {X} <- ets:table(E),
3355                                X =:= 3, X =:= F(X)]),
3356                {qlc,_,[{generate,_,{list,{table,_},_}},_],[]} = i(Q),
3357                [3] = lists:sort(qlc:e(Q)),
3358                [3] = lookup_keys(Q)
3359        end, [{2},{3},{4}])">>,
3360
3361       <<"etsc(fun(E) ->
3362                A = a, B = a,
3363                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3364                                ((X =:= A) and (Y =:= B))
3365                                 or ((X =:= B) and (Y =:= A))]),
3366                [a] = qlc:e(Q),
3367                %% keys are usorted, duplicate removed:
3368                [{a,a}] = lookup_keys(Q)
3369        end, [{{a,a}},{{b,b}}])">>,
3370
3371       <<"etsc(fun(E) ->
3372                A = a, B = b,
3373                Q = qlc:q([X || {{X,Y}} <- ets:table(E),
3374                                ((X =:= A) and (Y =:= B))
3375                                 or ((X =:= B) and (Y =:= A))]),
3376                [a,b] = lists:sort(qlc:e(Q)),
3377                [{a,b},{b,a}] = lookup_keys(Q)
3378        end, [{{a,b}},{{b,a}},{{c,a}},{{d,b}}])">>,
3379
3380       %% The atom 'fail' is recognized - lookup.
3381       <<"etsc(fun(E) ->
3382                Q = qlc:q([A || {A} <- ets:table(E),
3383                                (A =:= 2)
3384                                    orelse fail
3385                                   ]),
3386                [2] = lists:sort(qlc:e(Q)),
3387                [2] = lookup_keys(Q)
3388           end, [{1},{2}])">>
3389
3390       ],
3391
3392    ok = run(Config, Ts),
3393
3394    TsR = [
3395       %% is_record/2,3:
3396       <<"etsc(fun(E) ->
3397                Q = qlc:q([element(1, X) || X <- ets:table(E),
3398                                            erlang:is_record(X, r, 2)]),
3399                 [r] = qlc:e(Q),
3400                 [r] = lookup_keys(Q)
3401         end, [{keypos,1}], [#r{}])">>,
3402       <<"etsc(fun(E) ->
3403                Q = qlc:q([element(1, X) || X <- ets:table(E),
3404                                            is_record(X, r, 2)]),
3405                 [r] = qlc:e(Q),
3406                 [r] = lookup_keys(Q)
3407         end, [{keypos,1}], [#r{}])">>,
3408       {cres,
3409        <<"etsc(fun(E) ->
3410                Q = qlc:q([element(1, X) || X <- ets:table(E),
3411                                            record(X, r)]),
3412                 [r] = qlc:e(Q),
3413                 [r] = lookup_keys(Q)
3414         end, [{keypos,1}], [#r{}])">>,
3415        {warnings,[{{4,45},erl_lint,{obsolete_guard,{record,2}}}]}},
3416       <<"etsc(fun(E) ->
3417                Q = qlc:q([element(1, X) || X <- ets:table(E),
3418                                            erlang:is_record(X, r)]),
3419                 [r] = qlc:e(Q),
3420                 [r] = lookup_keys(Q)
3421         end, [{keypos,1}], [#r{}])">>,
3422       <<"etsc(fun(E) ->
3423                Q = qlc:q([element(1, X) || X <- ets:table(E),
3424                                            is_record(X, r)]),
3425                 [r] = qlc:e(Q),
3426                 [r] = lookup_keys(Q)
3427         end, [{keypos,1}], [#r{}])">>
3428
3429       ],
3430
3431    ok = run(Config, <<"-record(r, {a}).\n">>, TsR),
3432
3433    Ts2 = [
3434       <<"etsc(fun(E) ->
3435                 Q0 = qlc:q([X ||
3436                                X <- ets:table(E),
3437                                (element(1, X) =:= 1) or
3438                                  (element(1, X) =:= 2)],
3439                           {cache,ets}),
3440                 Q = qlc:q([{X,Y} ||
3441                               X <- [1,2],
3442                               Y <- Q0]),
3443                 {qlc,_,[{generate,_,{list,[1,2]}},
3444                         {generate,_,{table,_}}], []} = i(Q),
3445                 [{1,{1}},{1,{2}},{2,{1}},{2,{2}}] = lists:sort(qlc:e(Q)),
3446                 [1,2] = lookup_keys(Q)
3447          end, [{keypos,1}], [{1},{2}])">>,
3448
3449       <<"etsc(fun(E) ->
3450                 Q0 = qlc:q([X ||
3451                                X <- ets:table(E),
3452                                (element(1, X) =:= 1) or
3453                                  (element(1, X) =:= 2)]),
3454                 Q = qlc:q([{X,Y} ||
3455                               X <- [1,2],
3456                               Y <- Q0],
3457                           {cache,true}),
3458                 {qlc,_,[{generate,_,{list,[1,2]}},
3459                         {generate,_,{table,_}}],[]} = i(Q),
3460                 [1,2] = lookup_keys(Q)
3461          end, [{keypos,1}], [{1},{2}])">>,
3462
3463       %% One introduced QLC expression (join, ms), and the cache option.
3464       <<"%% Match spec and lookup. The lookup is done twice, which might
3465          %% be confusing...
3466          etsc(fun(E) ->
3467                       Q = qlc:q([{X,Y} ||
3468                                     X <- [1,2],
3469                                     {Y} <- ets:table(E),
3470                                     (Y =:= 1) or (Y =:= 2)],
3471                                 []),
3472                       [{1,1},{1,2},{2,1},{2,2}] = qlc:e(Q),
3473                       {qlc,_,[{generate,_,{list,[1,2]}},
3474                               {generate,_,{list,{table,_},_}}],[]} = i(Q),
3475                       [1,2] = lookup_keys(Q)
3476               end, [{keypos,1}], [{1},{2},{3}])">>,
3477       <<"%% The same as last example, but with cache.
3478          %% No cache needed (always one lookup only).
3479          etsc(fun(E) ->
3480                       Q = qlc:q([{X,Y} ||
3481                                     X <- [1,2],
3482                                     {Y} <- ets:table(E),
3483                                     (Y =:= 1) or (Y =:= 2)],
3484                                 [cache]),
3485                       [{1,1},{1,2},{2,1},{2,2}] = qlc:e(Q),
3486                       {qlc,_,[{generate,_,{list,[1,2]}},
3487                               {generate,_,{list,{table,_},_}}],[]} = i(Q),
3488                       [1,2] = lookup_keys(Q)
3489               end, [{keypos,1}], [{1},{2},{3}])">>,
3490
3491       <<"%% And again, this time only lookup, no mach spec.
3492          etsc(fun(E) ->
3493                       Q = qlc:q([{X,Y} ||
3494                                     X <- [1,2],
3495                                     Y <- ets:table(E),
3496                                     (element(1, Y) =:= 1)
3497                                      or (element(1, Y) =:= 2)],
3498                                 []),
3499                       [{1,{1}},{1,{2}},{2,{1}},{2,{2}}] = qlc:e(Q),
3500                       {qlc,_,[{generate,_,{list,[1,2]}},
3501                               {generate,_,{table,_}}],[]} = i(Q),
3502                       [1,2] = lookup_keys(Q)
3503               end, [{keypos,1}], [{1},{2},{3}])">>,
3504       <<"%% As last one, but with cache.
3505          %% No cache needed (always one lookup only).
3506          etsc(fun(E) ->
3507                       Q = qlc:q([{X,Y} ||
3508                                     X <- [1,2],
3509                                     Y <- ets:table(E),
3510                                     (element(1, Y) =:= 1)
3511                                      or (element(1, Y) =:= 2)],
3512                                 [cache]),
3513                       {qlc,_,[{generate,_,{list,[1,2]}},
3514                               {generate,_,{table,_}}],[]} = i(Q),
3515                       [{1,{1}},{1,{2}},{2,{1}},{2,{2}}] = qlc:e(Q),
3516                       [1,2] = lookup_keys(Q)
3517               end, [{keypos,1}], [{1},{2},{3}])">>,
3518
3519       <<"%% Lookup only. No cache.
3520          etsc(fun(E) ->
3521                       Q = qlc:q([{X,Y} ||
3522                                     X <- [1,2],
3523                                     {Y=2} <- ets:table(E)],
3524                                 []),
3525                       {qlc,_,[{generate,_,{list,[1,2]}},
3526                               {generate,_,{table,_}}],[]} = i(Q),
3527                       [{1,2},{2,2}] = qlc:e(Q),
3528                       [2] = lookup_keys(Q)
3529               end, [{keypos,1}], [{1},{2},{3}])">>,
3530       <<"%% Lookup only. No cache.
3531          etsc(fun(E) ->
3532                       Q = qlc:q([{X,Y} ||
3533                                     X <- [1,2],
3534                                     {Y=2} <- ets:table(E)],
3535                                 [cache]),
3536                       {qlc,_,[{generate,_,{list,[1,2]}},
3537                               {generate,_,{table,_}}],[]} = i(Q),
3538                       [{1,2},{2,2}] = qlc:e(Q),
3539                       [2] = lookup_keys(Q)
3540               end, [{keypos,1}], [{1},{2},{3}])">>,
3541       <<"%% Matchspec only. No cache.
3542          etsc(fun(E) ->
3543                       Q = qlc:q([{X,Y} ||
3544                                     X <- [1,2],
3545                                     {Y} <- ets:table(E),
3546                                     Y > 1],
3547                                 []),
3548                       {qlc,_,[{generate,_,{list,[1,2]}},
3549                               {generate,_,
3550                                {table,{ets,_,[_,[{traverse,_}]]}}}],[]} =
3551                                       i(Q),
3552                       [{1,2},{1,3},{2,2},{2,3}] = lists:sort(qlc:e(Q)),
3553                       false = lookup_keys(Q)
3554               end, [{keypos,1}], [{1},{2},{3}])">>,
3555       <<"%% Matchspec only. Cache
3556          etsc(fun(E) ->
3557                       Q = qlc:q([{X,Y} ||
3558                                     X <- [1,2],
3559                                     {Y} <- ets:table(E),
3560                                     Y > 1],
3561                                 [cache]),
3562                       {qlc,_,[{generate,_,{list,[1,2]}},
3563                            {generate,_,{qlc,_,
3564                           [{generate,_,{table,{ets,_,[_,[{traverse,_}]]}}}],
3565                          [{cache,ets}]}}],[]} = i(Q),
3566                       [{1,2},{1,3},{2,2},{2,3}] = lists:sort(qlc:e(Q)),
3567                       false = lookup_keys(Q)
3568               end, [{keypos,1}], [{1},{2},{3}])">>,
3569       <<"%% An empty list. Always unique and cached.
3570          Q = qlc:q([X || {X} <- [], X =:= 1, begin X > 0 end],
3571                   [{cache,true},{unique,true}]),
3572          {qlc,_,[{generate,_,{list,[]}},_],[{unique,true}]} = i(Q),
3573          _ = qlc:info(Q),
3574          [] = qlc:e(Q)">>,
3575       <<"%% A list is always cached.
3576          Q = qlc:q([{X,Y} || Y <- [1,2], X <- [2,1,2]],
3577                    [cache]),
3578          {qlc,_,[{generate,_,{list,[1,2]}},
3579                  {generate,_,{list,[2,1,2]}}],[]} = i(Q),
3580          [{2,1},{1,1},{2,1},{2,2},{1,2},{2,2}] = qlc:e(Q)">>,
3581       <<"%% But a processed list is never cached.
3582          Q = qlc:q([{X,Y} || Y <- [1,2], X <- [2,1,2], X > 1],
3583                    [cache]),
3584          {qlc,_,[{generate,_, {list,[1,2]}},
3585                  {generate,_,{qlc,_,
3586                               [{generate,_,{list,{list,[2,1,2]},_}}],
3587                               [{cache,ets}]}}],[]} = i(Q),
3588          [{2,1},{2,1},{2,2},{2,2}] = qlc:e(Q)">>,
3589       <<"%% A bug fixed in R11B-2: coalescing simple_qlc:s works now.
3590          Q0 = qlc:q([X || {X} <- [{1},{2},{3}]],  {cache, ets}),
3591          Q1 = qlc:q([X || X <- Q0], {cache, list}),
3592          Q = qlc:q([{Y,X} || Y <- [1,2], X <- Q1, X < 2], {cache, list}),
3593          {qlc,_,[{generate,_,{list,_}},
3594                  {generate,_,{qlc,_,[{generate,_,{list,{list,_},_}}],
3595                               [{cache,ets}]}},_],[]} = i(Q),
3596          [{1,1},{2,1}] = qlc:e(Q)">>,
3597       <<"Q = qlc:q([{X,Y} || Y <- [1,2], X <- [1,2], X > 1],
3598                    [cache,unique]),
3599          {qlc,_,[{generate,_,{list,[1,2]}},
3600                  {generate,_,{qlc,_,
3601                               [{generate,_,{list,{list,[1,2]},_}}],
3602                               [{cache,ets},{unique,true}]}}],
3603           [{unique,true}]} = i(Q),
3604          [{2,1},{2,2}] = qlc:e(Q)">>,
3605       <<"L = [1,2,3],
3606          QH1 = qlc:q([{X} || X <- L, X > 1]),
3607          QH2 = qlc:q([{X} || X <- QH1, X > 0], [cache]),
3608          [{{2}},{{3}}] = qlc:e(QH2),
3609          {list,{list,{list,L},_},_} = i(QH2)">>,
3610       <<"L = [1,2,3,1,2,3],
3611          QH1 = qlc:q([{X} || X <- L, X > 1]),
3612          QH2 = qlc:q([{X} || X <- QH1, X > 0], [cache,unique]),
3613          [{{2}},{{3}}] = qlc:e(QH2),
3614          {qlc,_,[{generate,_,{list,{list,{list,L},_},_}}],
3615           [{unique,true}]} = i(QH2)">>
3616
3617      ],
3618
3619    ok = run(Config, Ts2),
3620
3621    LTs = [
3622       <<"etsc(fun(E) ->
3623                       Q  = qlc:q([X || X <- ets:table(E),
3624                                        element(1, X) =:= 1],
3625                                  {lookup,true}),
3626                       {table,L} = i(Q),
3627                       true = is_list(L),
3628                       [{1,a}] = qlc:e(Q),
3629                       [1] = lookup_keys(Q)
3630               end, [{1,a},{2,b}])">>,
3631       <<"%% No lookup, use the match spec for traversal instead.
3632          etsc(fun(E) ->
3633                       Q  = qlc:q([X || X <- ets:table(E),
3634                                        element(1, X) =:= 1],
3635                                  {lookup,false}),
3636                       {table,{ets,table,_}} = i(Q),
3637                       [{1,a}] = qlc:e(Q),
3638                       false = lookup_keys(Q)
3639               end, [{1,a},{2,b}])">>,
3640       <<"%% As last one. {max_lookup,0} has the same effect.
3641          etsc(fun(E) ->
3642                       Q  = qlc:q([X || X <- ets:table(E),
3643                                        element(1, X) =:= 1],
3644                                  {max_lookup,0}),
3645                       {table,{ets,table,_}} = i(Q),
3646                       [{1,a}] = qlc:e(Q),
3647                       false = lookup_keys(Q)
3648               end, [{1,a},{2,b}])">>
3649
3650       ],
3651
3652    ok = run(Config, LTs),
3653
3654    ok.
3655
3656%% Lookup keys. With records.
3657lookup_rec(Config) when is_list(Config) ->
3658    Ts = [
3659       <<"etsc(fun(E) ->
3660                Q = qlc:q([A || #r{a = A} <- ets:table(E),
3661                                (A =:= 3) or (4 =:= A)]),
3662                [3] = qlc:e(Q),
3663                [3,4] = lookup_keys(Q)
3664            end, [{keypos,2}], [#r{a = a}, #r{a = 3}, #r{a = 5}])">>,
3665
3666       {cres,
3667        <<"etsc(fun(E) ->
3668                 Q = qlc:q([A || #r{a = 17 = A} <- ets:table(E),
3669                                 (A =:= 3) or (4 =:= A)]),
3670                 [] = qlc:e(Q),
3671                 false = lookup_keys(Q)
3672             end, [{keypos,2}], [#r{a = 17}, #r{a = 3}, #r{a = 5}])">>,
3673        %% {warnings,[{{4,44},qlc,nomatch_filter}]}},
3674        []},
3675
3676      <<"%% Compares an integer and a float.
3677         etsc(fun(E) ->
3678                Q = qlc:q([A || #r{a = 17 = A} <- ets:table(E),
3679                                (A == 17) or (17.0 == A)]),
3680                [_] = qlc:e(Q),
3681                [_] = lookup_keys(Q)
3682            end, [{keypos,2}], [#r{a = 17}, #r{a = 3}, #r{a = 5}])">>,
3683
3684      <<"%% Compares an integer and a float.
3685         %% There is a test in qlc_pt.erl (Op =:= '=:=', C1 =:= C2), but
3686         %% that case is handled in an earlier clause (unify ... E, E).
3687         etsc(fun(E) ->
3688                Q = qlc:q([A || #r{a = 17.0 = A} <- ets:table(E),
3689                                (A =:= 17) or (17.0 =:= A)]),
3690                [_] = qlc:e(Q),
3691                [_] = lookup_keys(Q)
3692            end, [{keypos,2}], [#r{a = 17.0}, #r{a = 3}, #r{a = 5}])">>,
3693
3694      <<"%% Matches an integer and a float.
3695         etsc(fun(E) ->
3696                Q = qlc:q([A || #r{a = 17 = A} <- ets:table(E),
3697                                (A =:= 17) or (17.0 =:= A)]),
3698                [_] = qlc:e(Q),
3699                [_] = lookup_keys(Q)
3700            end, [{keypos,2}], [#r{a = 17}, #r{a = 3}, #r{a = 5}])">>,
3701
3702      <<"etsc(fun(E) ->
3703                F = fun(_) -> 17 end,
3704                Q = qlc:q([A || #r{a = A} <- ets:table(E),
3705                                (F(A) =:= 3) and (A =:= 4)]),
3706                [] = qlc:e(Q),
3707                false = lookup_keys(Q) % F(A) could fail
3708            end, [{keypos,2}], [#r{a = 4}, #r{a = 3}, #r{a = 5}])">>,
3709
3710      <<"etsc(fun(E) ->
3711                Q = qlc:q([X || {X} <- ets:table(E),
3712                                #r{} == X]),
3713                [#r{}] = lists:sort(qlc:e(Q)),
3714                {call,_,_,[_,_]} = i(Q, {format, abstract_code}),
3715                [#r{}] = lookup_keys(Q)
3716        end, [{#r{}},{#r{a=foo}}])">>,
3717
3718      <<"etsc(fun(E) ->
3719                Q = qlc:q([R#r.a || R <- ets:table(E), R#r.a =:= foo]),
3720                [foo] = qlc:e(Q),
3721                [_] = lookup_keys(Q)
3722        end, [{keypos,2}], [#r{a=foo}])">>
3723       ],
3724    run(Config, <<"-record(r, {a}).\n">>, Ts),
3725    ok.
3726
3727%% Using indices for lookup.
3728indices(Config) when is_list(Config) ->
3729    Ts = [
3730       <<"L = [{1,a},{2,b},{3,c}],
3731          QH = qlc:q([element(1, X) || X <- qlc_SUITE:table(L, [2]),
3732                                       (element(2, X) =:= a)
3733                                           or (b =:= element(2, X))]),
3734          {list, {table,{qlc_SUITE,list_keys,[[a,b],2,L]}}, _MS} = i(QH),
3735          [1,2] = qlc:eval(QH)">>,
3736
3737       <<"L = [{1,a},{2,b},{3,c}],
3738          QH = qlc:q([element(1, X) || X <- qlc_SUITE:table(L, [2]),
3739                                       begin (element(2, X) =:= a)
3740                                           or (b =:= element(2, X)) end]),
3741          {qlc,_,[{generate,_,{table,{call,_,
3742                               {remote,_,_,{atom,_,the_list}},_}}},_],[]}
3743                  = i(QH),
3744          [1,2] = qlc:eval(QH)">>,
3745
3746       <<"L = [{1,a,q},{2,b,r},{3,c,s}],
3747          QH = qlc:q([element(1, X) || X <- qlc_SUITE:table(L, [2,3]),
3748                                       (element(3, X) =:= q)
3749                                           or (r =:= element(3, X))]),
3750          {list, {table,{qlc_SUITE,list_keys, [[q,r],3,L]}}, _MS} = i(QH),
3751          [1,2] = qlc:eval(QH)">>,
3752
3753       <<"L = [{1,a,q},{2,b,r},{3,c,s}],
3754          QH = qlc:q([element(1, X) || X <- qlc_SUITE:table(L, 1, [2]),
3755                                       (element(3, X) =:= q)
3756                                           or (r =:= element(3, X))]),
3757          {qlc,_,[{generate,_,{table,{call,_,_,_}}},
3758                  _],[]} = i(QH),
3759          [1,2] = qlc:eval(QH)">>,
3760
3761       <<"L = [{a,1},{b,2},{c,3}],
3762          QH = qlc:q([E || {K,I}=E <- qlc_SUITE:table(L, 1, [2]),
3763                           ((K =:= a) or (K =:= b) or (K =:= c))
3764                               and ((I =:= 1) or (I =:= 2))],
3765                     {max_lookup, 3}),
3766          {list, {table,{qlc_SUITE,list_keys,[[a,b,c],1,L]}}, _MS} = i(QH),
3767          [{a,1},{b,2}] = qlc:eval(QH)">>,
3768
3769       <<"L = [{a,1},{b,2},{c,3}],
3770          QH = qlc:q([E || {K,I}=E <- qlc_SUITE:table(L, 1, [2]),
3771                           ((K =:= a) or (K =:= b) or (K =:= c))
3772                               and ((I =:= 1) or (I =:= 2))],
3773                     {max_lookup, 2}),
3774          {list, {table,{qlc_SUITE,list_keys, [[1,2],2,L]}}, _MS} = i(QH),
3775          [{a,1},{b,2}] = qlc:eval(QH)">>,
3776
3777       <<"L = [{a,1,x,u},{b,2,y,v},{c,3,z,w}],
3778          QH = qlc:q([E || {K,I1,I2,I3}=E <- qlc_SUITE:table(L, 1, [2,3,4]),
3779                           ((K =/= a) or (K =/= b) or (K =/= c))
3780                             and ((I1 =:= 1) or (I1 =:= 2) or
3781                                  (I1 =:= 3) or (I1 =:= 4))
3782                             and ((I2 =:= x) or (I2 =:= z))
3783                             and ((I3 =:= v) or (I3 =:= w))],
3784                     {max_lookup, 5}),
3785          {list, {table,{qlc_SUITE,list_keys, [[x,z],3,L]}}, _MS} = i(QH),
3786          [{c,3,z,w}] = qlc:eval(QH)">>
3787
3788       ],
3789    run(Config, <<"-record(r, {a}).\n">>, Ts),
3790    ok.
3791
3792%% Test the table/2 callback functions parent_fun and stop_fun.
3793pre_fun(Config) when is_list(Config) ->
3794    Ts = [
3795       <<"PF = process_flag(trap_exit, true),
3796          %% cursor: table killing parent
3797          L = [{1,a},{2,b},{3,c}],
3798          F1 = fun() ->
3799                   QH = qlc:q([element(1, X) ||
3800                                X <- qlc_SUITE:table_kill_parent(L, [2]),
3801                                (element(2, X) =:= a)
3802                                    or (b =:= element(2, X))]),
3803                   _ = qlc:info(QH),
3804                   _ = qlc:cursor(QH)
3805               end,
3806          Pid1 = spawn_link(F1),
3807          receive {'EXIT', Pid1, killed} ->
3808              ok
3809          end,
3810          timer:sleep(1),
3811          process_flag(trap_exit, PF)">>,
3812
3813       <<"PF = process_flag(trap_exit, true),
3814          %% eval without cursor: table killing parent
3815          L = [{1,a},{2,b},{3,c}],
3816          F2 = fun() ->
3817                 QH = qlc:q([element(1, X) ||
3818                                X <- qlc_SUITE:table_kill_parent(L, [2]),
3819                                (element(2, X) =:= a)
3820                                    or (b =:= element(2, X))]),
3821                 _ = qlc:eval(QH)
3822               end,
3823          Pid2 = spawn_link(F2),
3824          receive {'EXIT', Pid2, killed} ->
3825              ok
3826          end,
3827          process_flag(trap_exit, PF)">>,
3828
3829       <<"L = [{1,a},{2,b},{3,c}],
3830          QH = qlc:q([element(1, X) ||
3831                        X <- qlc_SUITE:table_parent_throws(L, [2]),
3832                        (element(2, X) =:= a)
3833                            or (b =:= element(2, X))]),
3834          _ = qlc:info(QH),
3835          {throw,thrown} = (catch {any_term,qlc:cursor(QH)}),
3836          {throw,thrown} = (catch {any_term,qlc:eval(QH)})">>,
3837
3838       <<"L = [{1,a},{2,b},{3,c}],
3839          QH = qlc:q([element(1, X) ||
3840                        X <- qlc_SUITE:table_parent_exits(L, [2]),
3841                        (element(2, X) =:= a)
3842                            or (b =:= element(2, X))]),
3843          _ = qlc:info(QH),
3844          {'EXIT', {badarith,_}} = (catch qlc:cursor(QH)),
3845          {'EXIT', {badarith,_}} = (catch qlc:eval(QH))">>,
3846
3847       <<"L = [{1,a},{2,b},{3,c}],
3848          QH = qlc:q([element(1, X) ||
3849                        X <- qlc_SUITE:table_bad_parent_fun(L, [2]),
3850                        (element(2, X) =:= a)
3851                            or (b =:= element(2, X))]),
3852          {'EXIT', {badarg,_}} = (catch qlc:cursor(QH)),
3853          {'EXIT', {badarg,_}} = (catch qlc:eval(QH))">>,
3854
3855       <<"%% Very simple test of stop_fun.
3856          Ets = ets:new(apa, [public]),
3857          L = [{1,a},{2,b},{3,c}],
3858          H = qlc:q([X || {X,_} <- qlc_SUITE:stop_list(L, Ets)]),
3859          C = qlc:cursor(H),
3860          [{stop_fun,StopFun}] = ets:lookup(Ets, stop_fun),
3861          StopFun(),
3862          {'EXIT', {{qlc_cursor_pid_no_longer_exists, _}, _}} =
3863                  (catch qlc:next_answers(C, all_remaining)),
3864          ets:delete(Ets)">>
3865
3866       ],
3867
3868    run(Config, Ts),
3869    ok.
3870
3871%% Lookup keys. With records.
3872skip_filters(Config) when is_list(Config) ->
3873    %% Skipped filters
3874    TsS = [
3875       %% Cannot skip the filter.
3876       <<"etsc(fun(E) ->
3877                H = qlc:q([X || X <- ets:table(E),
3878                          (element(1, X) =:= 1) xor (element(1, X) =:= 1)]),
3879                [] = qlc:eval(H),
3880                [1] = lookup_keys(H)
3881               end, [{keypos,1}], [{1},{2}])">>,
3882
3883       %% The filter can be skipped. Just a lookup remains.
3884       <<"etsc(fun(E) ->
3885                H = qlc:q([X || X <- ets:table(E),
3886                          (element(1, X) =:= 1) or (element(1, X) =:= 1)]),
3887                [{1}] = qlc:eval(H),
3888                {table, _} = i(H),
3889                [1] = lookup_keys(H)
3890               end, [{keypos,1}], [{1},{2}])">>,
3891
3892       %% safe_unify fails on 3 and <<X:32>>
3893       <<"etsc(fun(E) ->
3894                H = qlc:q([X || X <- ets:table(E),
3895                     (element(1, X) =:= 1) and (3 =:= <<X:32>>)]),
3896                [] = qlc:eval(H),
3897                [1] = lookup_keys(H)
3898               end, [{keypos,1}], [{1},{2}])">>,
3899
3900       %% Two filters are skipped.
3901       <<"etsc(fun(E) ->
3902                Q = qlc:q([{B,C,D} || {A={C},B} <- ets:table(E),
3903                                      (A =:= {1}) or (A =:= {2}),
3904                                      (C =:= 1) or (C =:= 2),
3905                                      D <- [1,2]]),
3906                {qlc,_,[{generate,_,{table,_}},{generate,_,{list,[1,2]}}],[]}
3907                  = i(Q),
3908                [{1,1,1},{1,1,2},{2,2,1},{2,2,2}] = lists:sort(qlc:eval(Q)),
3909                [{1},{2}] = lookup_keys(Q)
3910         end, [{{1},1},{{2},2},{{3},3}])">>,
3911
3912       <<"etsc(fun(E) ->
3913                Q = qlc:q([{B,C} || {A={C},B} <- ets:table(E),
3914                                    (A =:= {1}) or (A =:= {2}),
3915                                    (C =:= 1) or (C =:= 2)]),
3916                {qlc,_,[{generate,_,{table,_}}],[]} = i(Q),
3917                [{1,1},{2,2}] = lists:sort(qlc:eval(Q)),
3918                [{1},{2}] = lookup_keys(Q)
3919         end, [{{1},1},{{2},2},{{3},3}])">>,
3920
3921       %% Lookup. No match spec, no filter.
3922       <<"etsc(fun(E) ->
3923                Q = qlc:q([X || X <- ets:table(E),
3924                               element(1, X) =:= 1]),
3925                {table, _} = i(Q),
3926                [{1}] = qlc:e(Q),
3927                [1] = lookup_keys(Q)
3928         end, [{1},{2}])">>,
3929
3930       <<"etsc(fun(E) ->
3931                 Q = qlc:q([{X,Y} || X <- ets:table(E),
3932                                     element(1, X) =:= 1,
3933                                     Y <- [1,2]]),
3934                 {qlc,_,[{generate,_,{table,_}},{generate,_,{list,_}}],[]}
3935                      = i(Q),
3936                 [{{1},1},{{1},2}] = lists:sort(qlc:e(Q)),
3937                 [1] = lookup_keys(Q)
3938         end, [{1},{2}])">>,
3939
3940       <<"etsc(fun(E) ->
3941                 Q = qlc:q([X || {X,Y} <- ets:table(E),
3942                                 X =:= a,
3943                                 X =:= Y]),
3944                 {list,{table,_},_} = i(Q),
3945                 [a] = qlc:e(Q),
3946                 [a] = lookup_keys(Q)
3947          end, [{a,a},{b,c},{c,a}])">>,
3948
3949       %% The imported variable (A) is never looked up in the current
3950       %% implementation. This means that the first filter cannot be skipped;
3951       %% the constant 'a' is looked up, and then the first filter evaluates
3952       %% to false.
3953       <<"etsc(fun(E) ->
3954                 A = 3,
3955                 Q = qlc:q([X || X <- ets:table(E),
3956                                 A == element(1,X),
3957                                 element(1,X) =:= a]),
3958                 [] = qlc:e(Q),
3959                 [a] = lookup_keys(Q)
3960          end, [{a},{b},{c}])">>,
3961
3962       %% No lookup.
3963       {cres,
3964        <<"etsc(fun(E) ->
3965                  Q = qlc:q([X || {X} <- ets:table(E),
3966                                  X =:= 1,
3967                                  X =:= 2]),
3968                  {table, _} = i(Q),
3969                  [] = qlc:e(Q),
3970                  false = lookup_keys(Q)
3971          end, [{1,1},{2,0}])">>,
3972        %% {warnings,[{{4,37},qlc,nomatch_filter}]}},
3973        []},
3974
3975       <<"etsc(fun(E) ->
3976                 Q = qlc:q([{A,B,C} ||
3977                               {A} <- ets:table(E),
3978                               A =:= 1,
3979                               {B} <- ets:table(E),
3980                               B =:= 2,
3981                               {C} <- ets:table(E),
3982                               C =:= 3]),
3983                 {qlc,_,[{generate,_,{list,{table,_},_}},
3984                         {generate,_,{list,{table,_},_}},
3985                         {generate,_,{list,{table,_},_}}],[]} = i(Q),
3986                 [{1,2,3}] = qlc:e(Q),
3987                 [1,2,3] = lookup_keys(Q)
3988          end, [{0},{1},{2},{3},{4}])">>
3989
3990           ],
3991    run(Config, TsS),
3992
3993    Ts = [
3994       <<"etsc(fun(E) ->
3995                 H = qlc:q([X || {X,_} <- ets:table(E),
3996                                 X =:= 2]),
3997                 {list,{table,_},_} = i(H),
3998                 [2] = qlc:e(H)
3999         end, [{1,a},{2,b}])">>,
4000
4001       <<"etsc(fun(E) ->
4002                 H = qlc:q([X || {X,_} <- ets:table(E),
4003                                 ((X =:= 2) or (X =:= 1)) and (X > 1)]),
4004                 {list,{table,_},_} = i(H),
4005                 [2] = qlc:e(H)
4006         end, [{1,a},{2,b}])">>,
4007
4008       <<"etsc(fun(E) ->
4009                 H = qlc:q([X || {X,Y} <- ets:table(E),
4010                                 (X =:= 2) and (Y =:= b)]),
4011                 {list,{table,_},_} = i(H),
4012                 [2] = qlc:e(H)
4013         end, [{1,a},{2,b}])">>,
4014
4015       <<"etsc(fun(E) ->
4016                 H = qlc:q([X || X <- ets:table(E),
4017                                 (element(1,X) =:= 2) and (X =:= {2,b})]),
4018                 {list,{table,_},_} = i(H),
4019                 [{2,b}] = qlc:e(H)
4020         end, [{1,a},{2,b}])">>,
4021
4022       <<"etsc(fun(E) ->
4023                 H = qlc:q([{X,Y,Z,W} ||
4024                               {X,Y} <- ets:table(E),
4025                               {Z,W} <- ets:table(E),
4026                               (Y =:= 3) or (Y =:= 4)]),
4027                 {qlc,_,[{generate,_,{table,{ets,table,_}}},
4028                         {generate,_,{table,{ets,table,_}}}],[]} = i(H),
4029                 [{a,3,a,3},{a,3,b,5}] = lists:sort(qlc:e(H))
4030         end, [{a,3},{b,5}])">>,
4031
4032       <<"etsc(fun(E) ->
4033                 H = qlc:q([{X,Y} ||
4034                               {X,Y=3} <- ets:table(E), % no matchspec
4035                               %% Two columns restricted, but lookup anyway
4036                               (X =:= a)]),
4037                 {qlc,_,[{generate,_,{table,_}}],[]} = i(H),
4038                 [{a,3}] = qlc:e(H)
4039         end, [{a,3},{b,4}])">>,
4040
4041       <<"etsc(fun(E) ->
4042                 V = 3,
4043                 H = qlc:q([{X,Y} ||
4044                               {X,Y} <- ets:table(E),
4045                               (Y =:= V)]), % imported variable, no lookup
4046                 {table,{ets,table,_}} = i(H),
4047                 [{a,3}] = qlc:e(H)
4048         end, [{a,3},{b,4}])">>,
4049
4050       <<"etsc(fun(E) ->
4051                 V = b,
4052                 H = qlc:q([{X,Y} ||
4053                               {X,Y} <- ets:table(E),
4054                               (X =:= V)]), % imported variable, lookup
4055                 {list,{table,_},_} = i(H),
4056                 [{b,4}] = qlc:e(H)
4057         end, [{a,3},{b,4}])">>,
4058
4059       <<"H = qlc:q([{A,B} || {{A,B}} <- [{{1,a}},{{2,b}}],
4060                              A =:= 1,
4061                              B =:= a]),
4062              {list,{list,[_,_]},_} = i(H),
4063              [{1,a}] = qlc:e(H)">>,
4064
4065       <<"etsc(fun(E) ->
4066                 H = qlc:q([{A,B} || {{A,B}} <- ets:table(E),
4067                                     A =:= 1,
4068                                     B =:= a]),
4069                 {list,{table,_},_} = i(H),
4070                 [{1,a}] = qlc:e(H)
4071         end, [{{1,a}},{{2,b}}])">>,
4072
4073       %% The filters are skipped, and the guards of the match specifications
4074       %% are skipped as well. Only the transformations of the matchspecs
4075       %% are kept.
4076       <<"etsc(fun(E1) ->
4077                 etsc(fun(E2) ->
4078                              H = qlc:q([{X,Y,Z,W} ||
4079                                             {X,_}=Z <- ets:table(E1),
4080                                             W={Y} <- ets:table(E2),
4081                                             (X =:= 1) or (X =:= 2),
4082                                             (Y =:= a) or (Y =:= b)]
4083                                         ,{lookup,true}
4084                                        ),
4085                              {qlc,_,[{generate,_,{list,{table,_},
4086                                                   [{{'$1','_'},[],['$_']}]}},
4087                                      {generate,_,{list,{table,_},
4088                                                   [{{'$1'},[],['$_']}]}}],[]}
4089                              = i(H),
4090                              [{1,a,{1,a},{a}},
4091                               {1,b,{1,a},{b}},
4092                               {2,a,{2,b},{a}},
4093                               {2,b,{2,b},{b}}] = qlc:e(H)
4094                      end, [{a},{b}])
4095         end, [{1,a},{2,b}])">>,
4096
4097       %% The same example again, but this time no match specs are run.
4098       <<"fun(Z) ->
4099              etsc(fun(E1) ->
4100                     etsc(fun(E2) ->
4101                                  H = qlc:q([{X,Y} ||
4102                                                 Z > 2,
4103                                                 X <- ets:table(E1),
4104                                                 Y <- ets:table(E2),
4105                                                 (element(1, X) =:= 1) or
4106                                                 (element(1, X) =:= 2),
4107                                                 (element(1, Y) =:= a) or
4108                                                 (element(1, Y) =:= b)]
4109                                             ,{lookup,true}
4110                                            ),
4111                                  {qlc,_,[_,{generate,_,{table,_}},
4112                                          {generate,_,{table,_}}],[]} = i(H),
4113                                  [{{1,a},{a}},
4114                                   {{1,a},{b}},
4115                                   {{2,b},{a}},
4116                                   {{2,b},{b}}] = qlc:e(H)
4117                          end, [{a},{b}])
4118             end, [{1,a},{2,b}])
4119         end(4)">>,
4120
4121       %% Once again, this time with a join.
4122       <<"etsc(fun(E1) ->
4123                 etsc(fun(E2) ->
4124                              H = qlc:q([{X,Y,Z,W} ||
4125                                             {X,V}=Z <- ets:table(E1),
4126                                             W={Y} <- ets:table(E2),
4127                                             (X =:= 1) or (X =:= 2),
4128                                             (Y =:= a) or (Y =:= b),
4129                                             Y =:= V]
4130                                         ,[{lookup,true},{join,merge}]
4131                                        ),
4132                              {qlc,_,[{generate,_,{qlc,_,
4133                                [{generate,_,{qlc,_,[{generate,_,
4134                                    {keysort,{list,{table,_},_},2,[]}},
4135                                 _C1,_C2],[]}},
4136                                  {generate,_,
4137                                      {qlc,_,[{generate, _,
4138                                         {keysort,{list,{table,_},_},1,[]}},
4139                                              _C3],
4140                                       []}},
4141                                 _],
4142                                [{join,merge}]}},_],[]} = i(H),
4143                              [{1,a,{1,a},{a}},{2,b,{2,b},{b}}] =
4144                                  lists:sort(qlc:e(H))
4145                      end, [{a},{b}])
4146         end, [{1,a},{2,b}])">>,
4147
4148       %% Filters 2 and 3 are not skipped.
4149       %% (Only one filter at a time is tried by the parse transform.)
4150       <<"etsc(fun(E) ->
4151                 H = qlc:q([X || {{A,B}=X,Y} <- ets:table(E), % no matchspec
4152                                     Y =:= 3,
4153                                     A =:= 1,
4154                                     B =:= a]),
4155
4156                 {qlc,_,[{generate,_,{table,_}},_,_,_],[]}= i(H),
4157                 [{1,a}] = qlc:e(H)
4158         end, [{{1,a},3},{{2,b},4}])">>,
4159
4160       <<"etsc(fun(E) ->
4161                 H = qlc:q([X || {X=_,_} <- ets:table(E), % no matchspec
4162                                  (X =:= 3) and (X > 3)]),
4163                 {qlc,_,[{generate,_,{table,_}},_],[]} = i(H),
4164                 [] = qlc:e(H)
4165         end, [{3,a},{4,b}])">>,
4166
4167       <<"etsc(fun(E) ->
4168                 H = qlc:q([X || {X=_,_} <- ets:table(E), % no matchspec
4169                                 (X =:= 3) or true]),
4170                 {qlc,_,[{generate,_,{table,{ets,table,_}}},_],[]} = i(H),
4171                 [3,4] = lists:sort(qlc:e(H))
4172         end, [{3,a},{4,b}])">>,
4173
4174       <<"etsc(fun(E) ->
4175                 H = qlc:q([X || {X=_,_} <- ets:table(E), % no matchspec
4176                                 (X =:= 3) or false]),
4177                 {qlc,_,[{generate,_,{table,_}}],[]} = i(H),
4178                 [3] = lists:sort(qlc:e(H))
4179         end, [{3,a},{4,b}])">>,
4180
4181       <<"etsc(fun(E) ->
4182                 H = qlc:q([X || {X=_,_} <- ets:table(E), % no matchspec
4183                                 (X =:= X) and (X =:= 3)]),
4184                 {qlc,_,[{generate,_,{table,_}}],[]} = i(H),
4185                 [3] = lists:sort(qlc:e(H))
4186         end, [{3,a},{4,b}])">>,
4187
4188       %% The order of filters matters. A guard filter cannot be used
4189       %% unless there are no non-guard filter placed before the guard
4190       %% filter that uses the guard filter's generator. There is
4191       %% more examples in join_filter().
4192       <<"etsc(fun(E) ->
4193                 %% Lookup.
4194                 Q = qlc:q([{A,B,A} ||
4195                               {A=_,B} <- ets:table(E), % no match spec
4196                               A =:= 1,
4197                               begin 1/B > 0 end]),
4198                 [{1,1,1}] = lists:sort(qlc:e(Q))
4199         end, [{1,1},{2,0}])">>,
4200       <<"etsc(fun(E) ->
4201                 %% No lookup.
4202                 Q = qlc:q([{A,B,A} ||
4203                               {A=_,B} <- ets:table(E), % no match spec
4204                               begin 1/B > 0 end,
4205                               A =:= 1]),
4206                 {'EXIT', _} = (catch qlc:e(Q))
4207         end, [{1,1},{2,0}])">>,
4208       %% The same thing, with a match specification.
4209       <<"etsc(fun(E) ->
4210                 Q = qlc:q([{A,B,A} ||
4211                               {A,B} <- ets:table(E), % match spec
4212                               A < 2,
4213                               begin 1/B > 0 end]),
4214                 [{1,1,1}] = lists:sort(qlc:e(Q))
4215         end, [{1,1},{2,0}])">>,
4216       <<"etsc(fun(E) ->
4217                 Q = qlc:q([{A,B,A} ||
4218                               {A,B} <- ets:table(E), % match spec
4219                               begin 1/B > 0 end,
4220                               A < 2]),
4221                 {'EXIT', _} = (catch qlc:e(Q))
4222         end, [{1,1},{2,0}])">>,
4223       %% More examples, this time two tables.
4224       <<"etsc(fun(E) ->
4225                 Q = qlc:q([{A,B,C,D} ||
4226                               {A,B} <- ets:table(E), % match spec
4227                               A < 2,
4228                               {C,D} <- ets:table(E),
4229                               begin 1/B > 0 end, %\"invalidates\" next filter
4230                               C =:= 1,
4231                               begin 1/D > 0 end]),
4232                 {qlc,_,[{generate,_,{table,{ets,table,_}}},
4233                         {generate,_,{table,{ets,table,_}}},
4234                         _,_,_],[]} = i(Q),
4235                 [{1,1,1,1}] = lists:sort(qlc:e(Q))
4236         end, [{1,1},{2,0}])">>,
4237       <<"etsc(fun(E) ->
4238              Q = qlc:q([{A,B,C,D} ||
4239                            {A,B} <- ets:table(E),
4240                            {C,D} <- ets:table(E),
4241                            begin 1/B > 0 end, % \"invalidates\" two filters
4242                            A < 2,
4243                            C =:= 1,
4244                            begin 1/D > 0 end]),
4245              {qlc,_,[{generate,_,{table,{ets,table,_}}},
4246                      {generate,_,{table,{ets,table,_}}},_,_,_,_],[]} = i(Q),
4247              {'EXIT', _} = (catch qlc:e(Q))
4248         end, [{1,1},{2,0}])">>,
4249      <<"%% There are objects in the ETS table, but none passes the filter.
4250         %% F() would not be run if it did not \"invalidate\" the following
4251         %% guards.
4252         etsc(fun(E) ->
4253                      F = fun() -> [foo || A <- [0], 1/A] end,
4254                      Q1 = qlc:q([X || {X} <- ets:table(E),
4255                                       F(), % \"invalidates\" next guard
4256                                       X =:= 17]),
4257                      {'EXIT', _} = (catch qlc:e(Q1))
4258              end, [{1},{2},{3}])">>,
4259       <<"%% The last example works just like this one:
4260          etsc(fun(E) ->
4261                      F = fun() -> [foo || A <- [0], 1/A] end,
4262                      Q1 = qlc:q([X || {X} <- ets:table(E),
4263                                       F(),
4264                                       begin X =:= 17 end]),
4265                      {'EXIT', _} = (catch qlc:e(Q1))
4266              end, [{1},{2},{3}])">>
4267
4268          ],
4269    run(Config, Ts),
4270
4271    ok.
4272
4273
4274%% ets:table/1,2.
4275ets(Config) when is_list(Config) ->
4276    Ts = [
4277       <<"E = ets:new(t, [ordered_set]),
4278          true = ets:insert(E, [{1},{2}]),
4279          {'EXIT', _} =
4280              (catch qlc:e(qlc:q([X || {X} <- ets:table(E, bad_option)]))),
4281          {'EXIT', _} =
4282              (catch qlc:e(qlc:q([X || {X} <- ets:table(E,{traverse,bad})]))),
4283          All = [{'$1',[],['$1']}],
4284          TravAll = {traverse,{select,All}},
4285          [_, _] = qlc:e(qlc:q([X || {X} <- ets:table(E, TravAll)])),
4286          [_, _] = qlc:e(qlc:q([X || {X} <- ets:table(E,{traverse,select})])),
4287          [1,2] =
4288             qlc:e(qlc:q([X || {X} <- ets:table(E, {traverse, first_next})])),
4289          [2,1] =
4290             qlc:e(qlc:q([X || {X} <- ets:table(E, {traverse, last_prev})])),
4291          {table,{ets,table,[_,[{traverse,{select,_}},{n_objects,1}]]}} =
4292              i(qlc:q([X || {X} <- ets:table(E, {n_objects,1})])),
4293          {qlc,_,[{generate,_,{table,{ets,table,[_,{n_objects,1}]}}},_],[]} =
4294              i(qlc:q([X || {X} <- ets:table(E,{n_objects,1}),
4295                                   begin (X >= 1) or (X < 1) end])),
4296          {qlc,_,[{generate,_,{table,{ets,table,[_]}}},_],[]} =
4297              i(qlc:q([X || {X} <- ets:table(E),
4298                                   begin (X >= 1) or (X < 1) end])),
4299          ets:delete(E)">>,
4300
4301       begin
4302       MS = ets:fun2ms(fun({X,Y}) when X > 1 -> {X,Y} end),
4303       [<<"E = ets:new(apa,[]),
4304           true = ets:insert(E, [{1,a},{2,b},{3,c}]),
4305           MS =  ">>, io_lib:format("~w", [MS]), <<",
4306           Q = qlc:q([X || {X,_} <- ets:table(E, {traverse, {select, MS}}),
4307                           X =:= 1]),
4308           R = qlc:e(Q),
4309           ets:delete(E),
4310           [] = R">>]
4311       end,
4312
4313       <<"E2 = ets:new(test, [bag]),
4314          Ref = make_ref(),
4315          true = ets:insert(E2, [{Ref,Ref}]),
4316          Q2 = qlc:q([{Val1} ||
4317                         {Ref1, Val1} <- ets:table(E2),
4318                         Ref1 =:= Ref]),
4319          S = qlc:info(Q2),
4320          true = is_list(S),
4321          [{Ref}] = qlc:e(Q2),
4322          ets:delete(E2)">>
4323
4324       ],
4325
4326    run(Config, Ts),
4327    ok.
4328
4329%% dets:table/1,2.
4330dets(Config) when is_list(Config) ->
4331    dets:start(),
4332    T = t,
4333    Fname = filename(T, Config),
4334    Ts = [
4335       [<<"T = t, Fname = \"">>, Fname, <<"\",
4336           file:delete(Fname),
4337           {ok, _} = dets:open_file(T, [{file,Fname}]),
4338           ok = dets:insert(T, [{1},{2}]),
4339           {'EXIT', _} =
4340              (catch qlc:e(qlc:q([X || {X} <- dets:table(T, bad_option)]))),
4341           {'EXIT', _} =
4342              (catch qlc:e(qlc:q([X || {X} <- dets:table(T,{traverse,bad})]))),
4343           {'EXIT', _} =
4344              (catch
4345               qlc:e(qlc:q([X || {X} <- dets:table(T,{traverse,last_prev})]))),
4346           All = [{'$1',[],['$1']}],
4347           TravAll = {traverse,{select,All}},
4348           [_,_] = qlc:e(qlc:q([X || {X} <- dets:table(T, TravAll)])),
4349           [_,_] = qlc:e(qlc:q([X || {X} <- dets:table(T,{traverse,select})])),
4350           [_,_] =
4351             qlc:e(qlc:q([X || {X} <- dets:table(T, {traverse, first_next})])),
4352           {table,{dets,table,[T,[{traverse,{select,_}},{n_objects,1}]]}} =
4353               i(qlc:q([X || {X} <- dets:table(T, {n_objects,1})])),
4354           {qlc,_,[{generate,_,{table,{dets,table,[t,{n_objects,1}]}}},_],[]}=
4355               i(qlc:q([X || {X} <- dets:table(T,{n_objects,1}),
4356                             begin (X >= 1) or (X < 1) end])),
4357           {qlc,_,[{generate,_,{table,{dets,table,[_]}}},_],[]} =
4358               i(qlc:q([X || {X} <- dets:table(T),
4359                             begin (X >= 1) or (X < 1) end])),
4360           H = qlc:q([X || {X} <- dets:table(T, {n_objects, default}),
4361                           begin (X =:= 1) or (X =:= 2) or (X =:= 3) end]),
4362           [1,2] = lists:sort(qlc:e(H)),
4363           {qlc,_,[{generate,_,{table,_}},_],[]} = i(H),
4364
4365           H2 = qlc:q([X || {X} <- dets:table(T), (X =:= 1) or (X =:= 2)]),
4366           [1,2] = lists:sort(qlc:e(H2)),
4367           {list,{table,_},_} = i(H2),
4368           true = binary_to_list(<<
4369            \"ets:match_spec_run(lists:flatmap(fun(V)->dets:lookup(t,V)end,\"
4370            \"[1,2]),ets:match_spec_compile([{{'$1'},[],['$1']}]))\">>)
4371                   == format_info(H2, true),
4372
4373           H3 = qlc:q([X || {X} <- dets:table(T), (X =:= 1)]),
4374           [1] = qlc:e(H3),
4375           {list,{table,_},_} = i(H3),
4376
4377           ok = dets:close(T),
4378           file:delete(\"">>, Fname, <<"\"),
4379           ok">>],
4380
4381       begin
4382       MS = ets:fun2ms(fun({X,Y}) when X > 1 -> {X,Y} end),
4383       [<<"T = t, Fname = \"">>, Fname, <<"\",
4384           {ok, _} = dets:open_file(T, [{file,Fname}]),
4385           MS =  ">>, io_lib:format("~w", [MS]), <<",
4386           ok = dets:insert(T, [{1,a},{2,b},{3,c}]),
4387           Q = qlc:q([X || {X,_} <- dets:table(T, {traverse, {select, MS}}),
4388                           X =:= 1]),
4389           R = qlc:e(Q),
4390           ok = dets:close(T),
4391           file:delete(\"">>, Fname, <<"\"),
4392           [] = R">>]
4393       end,
4394
4395       [<<"T = t, Fname = \"">>, Fname, <<"\",
4396           {ok, _} = dets:open_file(T, [{file,Fname}]),
4397           Objs = [{X} || X <- lists:seq(1,10)],
4398           ok = dets:insert(T, Objs),
4399           {ok, Where} = dets:where(T, {2}),
4400           ok = dets:close(T),
4401           qlc_SUITE:crash(Fname, Where),
4402
4403           {ok, _} = dets:open_file(T, [{file,Fname}]),
4404           HT = qlc:q([X || {X} <- dets:table(T, {traverse, first_next})]),
4405           {'EXIT',{error,{{bad_object,_},_}}} = (catch qlc:e(HT)),
4406           _ = dets:close(T),
4407
4408           {ok, _} = dets:open_file(T, [{file,Fname}]),
4409           HMS = qlc:q([X || {X} <- dets:table(T, {traverse, select})]),
4410           {error,{{bad_object,_},_}} = qlc:e(HMS),
4411           _ = dets:close(T),
4412
4413           {ok, _} = dets:open_file(T, [{file,Fname}]),
4414           HLU = qlc:q([X || {X} <- dets:table(T), X =:= 2]),
4415           {error,{{bad_object,_},_}} = qlc:e(HLU),
4416           _ = dets:close(T),
4417
4418           file:delete(Fname)">>]
4419
4420       ],
4421
4422    run(Config, Ts),
4423    _ = file:delete(Fname),
4424    ok.
4425
4426
4427%% The 'join' option (any, lookup, merge, nested_loop). Also cache/unique.
4428join_option(Config) when is_list(Config) ->
4429    Ts = [
4430       <<"Q1 = qlc:q([X || X <- [1,2,3]],{join,merge}),
4431          {'EXIT', {no_join_to_carry_out,_}} = (catch {foo, qlc:info(Q1)}),
4432          {'EXIT', {no_join_to_carry_out,_}} = (catch {foo, qlc:e(Q1)}),
4433
4434          Q2 = qlc:q([X || X <- [1,2,3], X > 1],{join,merge}),
4435          {'EXIT', {no_join_to_carry_out,_}} = (catch {foo, qlc:info(Q2)}),
4436          {'EXIT', {no_join_to_carry_out,_}} = (catch {foo, qlc:e(Q2)}),
4437
4438          Q3 = qlc:q([{X,Y} ||
4439                         {X} <- [{1},{2},{3}],
4440                         {Y} <- [{a},{b},{c}],
4441                         X =:= Y],
4442                     {join, merge}),
4443
4444          {1,0,0,2} = join_info(Q3),
4445          [] = qlc:e(Q3),
4446
4447          Q4 = qlc:q([{X,Y} ||
4448                         {X} <- [{1},{2},{3}],
4449                         {Y} <- [{a},{b},{c}],
4450                         X > Y],
4451                     {join, lookup}),
4452          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:info(Q4)}),
4453          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:e(Q4)}),
4454
4455          Q5 = qlc:q([{X,Y} ||
4456                         {X} <- [{1},{2},{3}],
4457                         {Y} <- [{3},{4},{5}],
4458                         X == Y],
4459                     {join, merge}),
4460          [{3,3}] = qlc:e(Q5),
4461
4462          Q6 = qlc:q([{X,Y} ||
4463                         {X} <- [{1},{2},{3}],
4464                         {Y} <- [{3},{4},{5}],
4465                         X == Y],
4466                     {join, lookup}),
4467          {'EXIT', {cannot_carry_out_join, _}} = (catch {foo, qlc:info(Q6)}),
4468          {'EXIT', {cannot_carry_out_join, _}} = (catch {foo, qlc:e(Q6)}),
4469
4470          Q7 = qlc:q([{X,Y} ||
4471                         {X} <- [{1},{2},{3}],
4472                         {Y} <- [{3},{4},{5}],
4473                         X == Y],
4474                     {join, nested_loop}),
4475          {0,0,1,0} = join_info(Q7),
4476          [{3,3}] = qlc:e(Q7),
4477
4478          Q8 = qlc:q([{X,Y} ||
4479                         {X} <- [{1},{2},{3}],
4480                         {Y} <- [{3},{4},{5}],
4481                         X =:= Y],
4482                     {join, nested_loop}),
4483          {0,0,1,0} = join_info(Q8),
4484          [{3,3}] = qlc:e(Q8),
4485
4486          %% Only guards are inspected...
4487          Q9 = qlc:q([{X,Y} ||
4488                         {X} <- [{1},{2},{3}],
4489                         {Y} <- [{3},{4},{5}],
4490                         begin X =:= Y end],
4491                     {join, nested_loop}),
4492          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:info(Q9)}),
4493          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:e(Q9)}),
4494
4495          Q10 = qlc:q([{X,Y} ||
4496                         {X} <- [{1},{2},{3}],
4497                         {Y} <- [{3},{4},{5}],
4498                         X < Y],
4499                     {join, nested_loop}),
4500          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:info(Q10)}),
4501          {'EXIT', {no_join_to_carry_out, _}} = (catch {foo, qlc:e(Q10)}),
4502
4503          F = fun(J) -> qlc:q([X || X <- [1,2]], {join,J}) end,
4504          {'EXIT', {no_join_to_carry_out, _}} =
4505                (catch {foo, qlc:e(F(merge))}),
4506          {'EXIT', {no_join_to_carry_out, _}} =
4507                (catch {foo, qlc:e(F(lookup))}),
4508          {'EXIT', {no_join_to_carry_out, _}} =
4509                (catch {foo, qlc:e(F(nested_loop))}),
4510          [1,2] = qlc:e(F(any)),
4511
4512          %% No join of columns in the same table.
4513          Q11 = qlc:q([{X,Y} || {a = X, X = Y} <- [{a,1},{a,a},{a,3},{a,a}]],
4514                      {join,merge}),
4515          {'EXIT', {no_join_to_carry_out, _}} = (catch qlc:e(Q11)),
4516          Q12 = qlc:q([{X,Y} || {X = a, X = Y} <- [{a,1},{a,a},{a,3},{a,a}]],
4517                      {join,merge}),
4518          {'EXIT', {no_join_to_carry_out, _}} = (catch qlc:e(Q12)),
4519          %% X and Y are \"equal\" (same constants), but must not be joined.
4520          Q13 = qlc:q([{X,Y} || {X,_Z} <- [{a,1},{a,2},{b,1},{b,2}],
4521                                {Y} <- [{a}],
4522                                (X =:= a) and (Y =:= b) or
4523                                (X =:= b) and (Y =:= a)],
4524                     {join,merge}),
4525          {'EXIT', {no_join_to_carry_out, _}} = (catch qlc:e(Q13))
4526
4527">>,
4528
4529       <<"Q1 = qlc:q([X || X <- [1,2,3]], {lookup,true}),
4530          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:info(Q1)}),
4531          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:e(Q1)}),
4532          Q2 = qlc:q([{X,Y} || X <- [1,2,3], Y <- [x,y,z]], lookup),
4533          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:info(Q2)}),
4534          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:e(Q2)}),
4535          Q3 = qlc:q([X || {X} <- [{1},{2},{3}]], {lookup,true}),
4536          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:e(Q3)}),
4537          {'EXIT', {no_lookup_to_carry_out, _}} = (catch {foo, qlc:info(Q3)}),
4538
4539          E1 = create_ets(1, 10),
4540          Q4 = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), X =:= 3], lookup),
4541          {match_spec, _} = strip_qlc_call(Q4),
4542          [{3,3}] = qlc:e(Q4),
4543          Q5 = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), X =:= 3], {lookup,false}),
4544          {table, ets, _} = strip_qlc_call(Q5),
4545          [{3,3}] = qlc:e(Q5),
4546          Q6 = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), X =:= 3], {lookup,any}),
4547          {match_spec, _} = strip_qlc_call(Q6),
4548          [{3,3}] = qlc:e(Q6),
4549          ets:delete(E1)">>
4550
4551       ],
4552    run(Config, Ts),
4553
4554    %% The 'cache' and 'unique' options of qlc/2 affects join.
4555    CUTs = [
4556       <<"L1 = [1,2],
4557          L2 = [{1,a},{2,b}],
4558          L3 = [{a,1},{b,2}],
4559          Q = qlc:q([{X,Y,Z} ||
4560                        Z <- L1,
4561                        {X,_} <- L2,
4562                        {_,Y} <- L3,
4563                        X =:= Y],
4564                    [cache, unique]),
4565          {qlc,_,
4566              [{generate,_,{list,L1}},
4567               {generate,_,{qlc,_,[{generate,_,
4568                      {qlc,_,[{generate,_,{keysort,{list,L2},1,[]}}],[]}},
4569                                {generate,_,{qlc,_,
4570                              [{generate,_,{keysort,{list,L3},2,[]}}],[]}},_],
4571                            [{join,merge},{cache,ets},{unique,true}]}},_],
4572              [{unique,true}]} = i(Q),
4573          [{1,1,1},{2,2,1},{1,1,2},{2,2,2}] = qlc:e(Q)">>,
4574       <<"L1 = [1,2],
4575          L2 = [{1,a},{2,b}],
4576          L3 = [{a,1},{b,2}],
4577          Q = qlc:q([{X,Y,Z} ||
4578                        Z <- L1,
4579                        {X,_} <- L2,
4580                        {_,Y} <- L3,
4581                        X =:= Y],
4582                    []),
4583          Options = [{cache_all,ets}, unique_all],
4584          {qlc,_,[{generate,_,{qlc,_,[{generate,_,{list,L1}}],
4585                               [{unique,true}]}},
4586                  {generate,_,{qlc,_,
4587                              [{generate,_,{qlc,_,[{generate,_,
4588                                 {keysort,{qlc,_,[{generate,_,{list,L2}}],
4589                                           [{cache,ets},{unique,true}]},
4590                                          1,[]}}],[]}},
4591                               {generate,_,{qlc,_,
4592                                    [{generate,_,{keysort,
4593                                      {qlc,_,[{generate,_,{list,L3}}],
4594                                       [{cache,ets},{unique,true}]},
4595                                                  2,[]}}],[]}},_],
4596                              [{join,merge},{cache,ets},{unique,true}]}},
4597                  _],[{unique,true}]} = i(Q, Options),
4598          [{1,1,1},{2,2,1},{1,1,2},{2,2,2}] = qlc:e(Q, Options)">>
4599       ],
4600    run(Config, CUTs),
4601
4602    ok.
4603
4604%% Various aspects of filters and join.
4605join_filter(Config) when is_list(Config) ->
4606    Ts = [
4607      <<"E1 = create_ets(1, 10),
4608          Q = qlc:q([X || {X,_} <- ets:table(E1),
4609                          begin A = X * X end, % ej true (?)
4610                          X >= A]),
4611          {'EXIT', _} = (catch qlc:e(Q)),
4612          ets:delete(E1)">>,
4613
4614      %% The order of filters matters. See also skip_filters().
4615      <<"Q = qlc:q([{X,Y} || {X,Y} <- [{a,1},{b,2}],
4616         {Z,W} <- [{a,1},{c,0}],
4617         X =:= Z,
4618         begin Y/W > 0 end]),
4619         [{a,1}] = qlc:e(Q)">>,
4620      <<"Q = qlc:q([{X,Y} || {X,Y} <- [{a,1},{b,2}],
4621         {Z,W} <- [{a,1},{c,0}],
4622         begin Y/W > 0 end,
4623         X =:= Z]),
4624         {'EXIT', _} = (catch qlc:e(Q))">>,
4625
4626      <<"etsc(fun(E1) ->
4627                   etsc(fun(E2) ->
4628                             F = fun() -> [foo || A <- [0], 1/A] end,
4629                             Q1 = qlc:q([X || {X} <- ets:table(E1),
4630                                              {Y} <- ets:table(E2),
4631                                              F(), % invalidates next filter
4632                                              X =:= Y]),
4633                              {qlc,_,[{generate,_,{table,{ets,table,_}}},
4634                                      {generate,_,{table,{ets,table,_}}},_,_],
4635                              []} = i(Q1),
4636                             {'EXIT', _} = (catch qlc:e(Q1))
4637                        end, [{1},{2},{3}])
4638              end, [{a},{b},{c}])">>
4639
4640    ],
4641    run(Config, Ts),
4642    ok.
4643
4644%% Lookup join.
4645join_lookup(Config) when is_list(Config) ->
4646    Ts = [
4647       <<"E1 = create_ets(1, 10),
4648          E2 = create_ets(5, 15),
4649          Q = qlc:q([{X,Y} || {_,Y} <- ets:table(E2),
4650                              {X,_} <- ets:table(E1),
4651                              X =:= Y], [{join,lookup}]),
4652          {0,1,0,0} = join_info_count(Q),
4653          R = qlc:e(Q),
4654          ets:delete(E1),
4655          ets:delete(E2),
4656          [{5,5},{6,6},{7,7},{8,8},{9,9},{10,10}] = lists:sort(R)">>,
4657
4658       <<"E1 = create_ets(1, 10),
4659          E2 = create_ets(5, 15),
4660          F = fun(J) -> qlc:q([{X,Y} || {X,_} <- ets:table(E1),
4661                                        {_,Y} <- ets:table(E2),
4662                                        X =:= Y], {join, J})
4663              end,
4664          Q = F(lookup),
4665          {0,1,0,0} = join_info_count(Q),
4666          R = qlc:e(Q),
4667          ets:delete(E1),
4668          ets:delete(E2),
4669          [{5,5},{6,6},{7,7},{8,8},{9,9},{10,10}] = lists:sort(R)">>,
4670
4671       <<"etsc(fun(E1) ->
4672                  E2 = qlc_SUITE:table([{1,a},{a},{1,b},{b}], 2, []),
4673                  Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), % (1)
4674                                      {_,Z} <- E2,   % (2)
4675                                      (Z =:= Y) and (X =:= a)
4676                                      or
4677                                      (Z =:= Y) and (X =:= b)]),
4678                  %% Cannot look up in (1) (X is keypos). Can look up (2).
4679                  %% Lookup-join: traverse (1), look up in (2).
4680                  {0,1,0,0} = join_info_count(Q),
4681                  [{a,a},{b,a}] = qlc:e(Q)
4682               end, [{a,a},{b,a},{c,3},{d,4}])">>,
4683
4684       <<"%% The pattern {X,_} is used to filter out looked up objects.
4685          etsc(fun(E) ->
4686                       Q = qlc:q([X || {X,_} <- ets:table(E),
4687                                       Y <- [{a,b},{c,d},{1,2},{3,4}],
4688                                       X =:= element(1, Y)]),
4689                       {0,1,0,0} = join_info_count(Q),
4690                       [1] = qlc:e(Q)
4691               end, [{1,2},{3}])">>,
4692
4693       <<"E = ets:new(e, [bag,{keypos,2}]),
4694          L = lists:sort([{a,1},{b,1},{c,1},{d,1},
4695                          {aa,2},{bb,2},{cc,2},{dd,2}]),
4696          true = ets:insert(E, L ++ [{aaa,1,1},{bbb,2,2},{ccc,3,3}]),
4697          Q = qlc:q([Z || {_,Y}=Z <- ets:table(E),
4698                          {X} <- [{X} || X <- lists:seq(0, 10)],
4699                          X =:= Y]),
4700          {0,1,0,0} = join_info_count(Q),
4701          R = qlc:e(Q),
4702          ets:delete(E),
4703          L = lists:sort(R)">>,
4704
4705       <<"E = ets:new(e, [bag,{keypos,2}]),
4706          L = lists:sort([{a,1},{b,1},{c,1},{d,1},
4707                          {aa,2},{bb,2},{cc,2},{dd,2}]),
4708          true = ets:insert(E, L ++ [{aaa,1,1},{bbb,2,2},{ccc,3,3}]),
4709          Q = qlc:q([Z || {X} <- [{X} || X <- lists:seq(0, 10)],
4710                          {_,Y}=Z <- ets:table(E),
4711                          X =:= Y]),
4712          {0,1,0,0} = join_info_count(Q),
4713          R = qlc:e(Q),
4714          ets:delete(E),
4715          L = lists:sort(R)">>,
4716
4717       <<"Q = qlc:q([{XX,YY} ||
4718                            {XX,X} <- [{b,1},{c,3}],
4719                            {Y,YY} <- qlc_SUITE:table_lookup_error([{1,a}]),
4720                            X =:= Y],
4721                        {join,lookup}),
4722          {error, lookup, failed} = qlc:e(Q)">>,
4723
4724       <<"E = create_ets(1, 10),
4725          Q = qlc:q([{X,Y} ||
4726                        {X,_} <- ets:table(E),
4727                        {_,Y} <- qlc_SUITE:table_error([{a,1}], 1, err),
4728                        X =:= Y]),
4729          {0,1,0,0} = join_info_count(Q),
4730          err = qlc:e(Q),
4731          ets:delete(E)">>
4732
4733          ],
4734    run(Config, Ts),
4735    ok.
4736
4737%% Merge join.
4738join_merge(Config) when is_list(Config) ->
4739    Ts = [
4740       <<"Q = qlc:q([{X,Y} || {X} <- [], {Y} <- [{1}], X =:= Y],
4741                    {join,merge}),
4742          [] = qlc:e(Q)
4743       ">>,
4744
4745       <<"Q = qlc:q([{X,Y} || {X} <- [{1}], {Y} <- [], X =:= Y],
4746                    {join,merge}),
4747          [] = qlc:e(Q)
4748       ">>,
4749
4750       <<"Q = qlc:q([{X,Y} || {X} <- [{1},{1},{1}],
4751                              {Y} <- [{1},{1},{1}], X =:= Y],
4752                    {join,merge}),
4753          9 = length(qlc:e(Q))
4754       ">>,
4755
4756       <<"%% Two merge joins possible.
4757          Q = qlc:q([{X,Y,Z,W} || {X,Y} <- [{1,a},{1,b},{1,c}],
4758                                  {Z,W} <- [{1,a},{1,b},{1,c}],
4759                                  X =:= Z,
4760                                  Y =:= W]),
4761          {qlc,_,[{generate,_,
4762                   {qlc,_,
4763                    [{generate,_,
4764                      {qlc,_,[{generate,_,{keysort,{list,_},C,[]}}],[]}},
4765                     {generate,_,
4766                      {qlc,_,[{generate,_,{keysort,{list,_},C,[]}}],[]}},
4767                     _],
4768                    [{join,merge}]}},
4769                  _,_],[]} = qlc:info(Q, {format,debug}),
4770          [{1,a,1,a},{1,b,1,b},{1,c,1,c}] = qlc:e(Q)">>,
4771
4772       <<"%% As the last one, but comparison.
4773          Q = qlc:q([{X,Y,Z,W} || {X,Y} <- [{1,a},{1,b},{1,c}],
4774                                  {Z,W} <- [{1,a},{1,b},{1,c}],
4775                                  X == Z, % skipped
4776                                  Y =:= W]),
4777          {qlc,_,[{generate,_,
4778                   {qlc,_,
4779                    [{generate,_,
4780                      {qlc,_,[{generate,_,{keysort,{list,_},1,[]}}],[]}},
4781                     {generate,_,
4782                      {qlc,_,[{generate,_,{keysort,{list,_},1,[]}}],[]}},
4783                     _],
4784                    [{join,merge}]}},
4785                  _],[]} = qlc:info(Q, {format,debug}),
4786          [{1,a,1,a},{1,b,1,b},{1,c,1,c}] = qlc:e(Q)">>,
4787
4788       <<"%% This is no join.
4789          Q = qlc:q([{X,Y,Z,W} || {X,Y} <- [], {Z,W} <- [],
4790                                  X =:= Y, Z =:= W]),
4791          {0,0,0,0} = join_info_count(Q)">>,
4792
4793       <<"%% Used to replace empty ETS tables with [], but that won't work.
4794          E1 = ets:new(e1, []),
4795          E2 = ets:new(e2, []),
4796          Q = qlc:q([{X,Z,W} ||
4797                        {X, Z} <- ets:table(E1),
4798                        {W, Y} <- ets:table(E2),
4799                        X =:= Y],
4800                    {join, lookup}),
4801          [] = qlc:e(Q),
4802          ets:delete(E1),
4803          ets:delete(E2)">>,
4804
4805       <<"Q = qlc:q([{X,Y} || {X} <- [{3},{1},{0}],
4806                              {Y} <- [{1},{2},{3}],
4807                              X =:= Y]),
4808          {1,0,0,2} = join_info_count(Q),
4809          [{1,1},{3,3}] = qlc:e(Q)">>,
4810
4811       <<"QH = qlc:q([{X,Y,Z,W} || {X,Y} <- [{3,c},{2,b},{1,a}],
4812                                   {Z,W} <- [{2,b},{4,d},{5,e},{3,c}],
4813                                   X =:= Z,
4814                                   Y =:= W]),
4815          {1,0,0,2} = join_info_count(QH),
4816          [{2,b,2,b},{3,c,3,c}] = qlc:e(QH)">>,
4817
4818       <<"%% QLC finds no join column at run time...
4819          QH = qlc:q([1 || X <- [{1,2,3},{4,5,6}],
4820                           Y <- [{1,2},{3,4}],
4821                           X =:= Y]),
4822          {0,0,0,0} = join_info_count(QH),
4823          [] = qlc:e(QH)">>,
4824
4825       <<"QH = qlc:q([X || X <- [{1,2,3},{4,5,6}],
4826                           Y <- [{1,2},{3,4}],
4827                           element(1, X) =:= element(2, Y)]),
4828          {1,0,0,2} = join_info_count(QH),
4829          [{4,5,6}] = qlc:e(QH)">>,
4830
4831       <<"Q = qlc:q([{A,X,Z,W} ||
4832                        A <- [a,b,c],
4833                        {X,Z} <- [{a,1},{b,4},{c,6}],
4834                        {W,Y} <- [{2,a},{3,b},{4,c}],
4835                        X =:= Y],
4836                   {cache, list}),
4837          _ = qlc:info(Q),
4838         [{a,a,1,2},{a,b,4,3},{a,c,6,4},{b,a,1,2},{b,b,4,3},
4839          {b,c,6,4},{c,a,1,2},{c,b,4,3},{c,c,6,4}] = qlc:e(Q)">>,
4840
4841       <<"Q = qlc:q([{X,Y} ||
4842                        {X,Z} <- [{a,1},{b,4},{c,6}],
4843                        {W,Y} <- [{2,a},{3,b},{4,c}],
4844                        Z > W,
4845                        X =:= Y],
4846                    {join,merge}),
4847          {qlc,_,[{generate,_,{qlc,_,
4848                              [{generate,_,
4849                                {qlc,_,[{generate,_,{keysort,_,1,[]}}],[]}},
4850                               {generate,_,
4851                                {qlc,_,[{generate,_,{keysort,_,2,[]}}],
4852                                 []}},_],[{join,merge}]}},
4853                  _,_],[]} = i(Q),
4854          [{b,b},{c,c}] = qlc:e(Q)">>,
4855
4856       <<"E1 = create_ets(1, 10),
4857          E2 = create_ets(5, 15),
4858          %% A match spec.; Q does not see Q1 and Q2 as lookup-tables.
4859          Q1 = qlc:q([X || X <- ets:table(E1)]),
4860          Q2 = qlc:q([X || X <- ets:table(E2)]),
4861          F = fun(J) -> qlc:q([{X,Y} || X <- Q1,
4862                                        Y <- Q2,
4863                                        element(1,X) =:= element(1,Y)],
4864                              [{join,J}])
4865              end,
4866          {'EXIT',{cannot_carry_out_join,_}} = (catch qlc:e(F(lookup))),
4867          Q = F(merge),
4868          {1,0,0,2} = join_info(Q),
4869          R = lists:sort(qlc:e(Q)),
4870          ets:delete(E1),
4871          ets:delete(E2),
4872          true = [{Y,Y} || X <- lists:seq(5, 10), {} =/= (Y = {X,X})] =:= R
4873       ">>,
4874
4875       <<"E1 = create_ets(1, 10),
4876          E2 = create_ets(5, 15),
4877          Q = qlc:q([{X,Y} || X <- ets:table(E1),
4878                              Y <- ets:table(E2),
4879                              element(1,X) =:= element(1,Y)],
4880                    [{join,merge}]),
4881          {1,0,0,2} = join_info(Q),
4882          R = lists:sort(qlc:e(Q)),
4883          ets:delete(E1),
4884          ets:delete(E2),
4885          true = [{Y,Y} || X <- lists:seq(5, 10), {} =/= (Y = {X,X})] =:= R
4886       ">>,
4887
4888       <<"E1 = create_ets(1, 10),
4889          E2 = create_ets(5, 15),
4890          Q1 = qlc:q([Y || X <- ets:table(E1), begin Y = {X}, true end]),
4891          %% A match spec.; Q does not see Q2 as a lookup-table.
4892          %%
4893          %% OTP-6673: lookup join is considered but since there is no
4894          %% filter that can do the job of Q2, lookup join is not an option..
4895          Q2 = qlc:q([{X} || X <- ets:table(E2)]),
4896          F = fun(J) ->
4897                      qlc:q([{X,Y} || X <- Q1,
4898                                      Y <- Q2,
4899                                      element(1,X) =:= element(1,Y)],
4900                            [{join,J}])
4901              end,
4902          {'EXIT',{cannot_carry_out_join,_}} = (catch qlc:e(F(lookup))),
4903          Q = F(any),
4904          {1,0,0,2} = join_info(Q),
4905          R = lists:sort(qlc:e(Q)),
4906          ets:delete(E1),
4907          ets:delete(E2),
4908          true = [{Y,Y} || X <- lists:seq(5, 10), {} =/= (Y = {{X,X}})] =:= R
4909       ">>,
4910
4911       <<"L1 = [{1,a},{2,a},{1,b},{2,b},{1,c},{2,c}],
4912          L2 = [{b,Y} || Y <- lists:seq(1, 10000)],
4913          F = fun(J) ->
4914                      Q = qlc:q([{XX,YY} ||
4915                                    {X,XX} <- L1,
4916                                    {YY,Y} <- L2,
4917                                    X == Y],
4918                                {join,J}),
4919                      qlc:q([{XX1,YY1,XX2,YY2} ||
4920                                {XX1,YY1} <- Q,
4921                                {XX2,YY2} <- Q])
4922              end,
4923          Qm = F(merge),
4924          Qn = F(nested_loop),
4925          true = lists:sort(qlc:e(Qm)) =:= lists:sort(qlc:e(Qn))">>,
4926
4927       <<"L1 = [{{1,a},2},{{3,c},4}],
4928          L2 = [{a,{1,a}},{c,{4,d}}],
4929          Q = qlc:q([{X,Y} || {X,_} <- L1,
4930                              {_,{Y,Z}} <- L2,
4931                              X == {Y,Z}
4932                           ]),
4933          {qlc,_,[{generate,_,{qlc,_,
4934                   [{generate,_,
4935                     {qlc,_,[{generate,_,{keysort,{list,L1},1,[]}}],[]}},
4936                    {generate,_,
4937                     {qlc,_,[{generate,_,{keysort,{list,L2},2,[]}}],[]}},
4938                    _],
4939                   [{join,merge}]}}],[]}  = i(Q),
4940          [{{1,a},1}] = qlc:e(Q)">>,
4941
4942       <<"etsc(fun(E1) ->
4943                   etsc(fun(E2) ->
4944                      Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E1), % (1)
4945                                          {Z} <- ets:table(E2),   % (2)
4946                                            (Z =:= X) and
4947                                            (Y =:= a) and
4948                                            (X =:= Y) or
4949                                          (Y =:= b) and
4950                                          (Z =:= Y)]),
4951                      %% Cannot look up in (1) (X is keypos). Can look up (2).
4952                      %% Lookup join not possible (cannot look up in (1)).
4953                      %% Merge join is possible (after lookup in (2)).
4954                      {1,0,0,2} = join_info_count(Q),
4955                      {qlc,_,
4956                       [{generate,_,
4957                         {qlc,_,[{generate,_,
4958                                  {qlc,_,[{generate,_,
4959                                           {keysort,
4960                                            {table,{ets,table,_}},
4961                                                  2,[]}},_C1],[]}},
4962                                 {generate,_,
4963                                  {qlc,_,[{generate,_,
4964                                           {keysort,{table,_},1,[]}},_C2],
4965                                   []}},
4966                                 _],[{join,merge}]}},_],[]} = i(Q),
4967                      [{a,a}] = qlc:e(Q)
4968                   end, [{a}])
4969                end, [{a,1},{a,a},{b,1},{b,2}])">>,
4970
4971       <<"Q = qlc:q([{G1,G2} ||
4972                        G1<- [{1}],
4973                        G2 <- [{1}],
4974                        element(1, G1) =:= element(1, G2)]),
4975          {1,0,0,2} = join_info(Q),
4976          [{{1},{1}}] = qlc:e(Q)">>,
4977
4978       <<"Q = qlc:q([{X,Y} ||
4979                         X <- [{1}],
4980                         Y <- [{1}],
4981                         element(1, X) =:= element(1, Y)],
4982                     {join,merge}),
4983          {1,0,0,2} = join_info(Q),
4984          [{{1},{1}}] = qlc:e(Q)">>,
4985
4986       <<"%% Generator after the join-filter.
4987          Q = qlc:q([Z ||
4988                        {X} <- [{1},{2},{3}],
4989                        {Y} <- [{2},{3},{4}],
4990                        X =:= Y,
4991                        Z <- [1,2]]),
4992          {qlc,_,
4993           [{generate,_,{qlc,_,
4994                [{generate,_,{qlc,_,
4995                    [{generate,_,{keysort,{list,[{1},{2},{3}]},1,[]}}],[]}},
4996                {generate,_,{qlc,_,
4997                    [{generate,_,{keysort,{list,_},1,[]}}],[]}},_],
4998                [{join,merge}]}}, _,{generate,_,{list,_}}],[]} = i(Q),
4999          [1,2,1,2] = qlc:e(Q)">>,
5000
5001       <<"%% X and W occur twice in the pattern of the extra join handle.
5002          Q = qlc:q([{Z,W} ||
5003                        {X,Z,X} <- [{1,2,1},{1,2,2}],
5004                        {W,Y,W} <- [{a,1,a}],
5005                        X =:= Y]),
5006          [{2,a}] = qlc:e(Q)">>
5007
5008          ],
5009    run(Config, Ts),
5010
5011    %% Small examples. Returning an error term.
5012    ETs = [
5013       <<"F = fun(M) ->
5014                  qlc:q([{XX,YY} ||
5015                         {XX,X} <- [{a,1},{b,2},{bb,2},{c,3},{cc,3}],
5016                         {Y,YY} <- [{0,a},{1,a},{1,aa},{2,b},{2,bb},{2,bbb},
5017                                    {3,c},{3,cc}],
5018                          X =:= Y],
5019                        {join,M})
5020              end,
5021          R = qlc:e(F(nested_loop)),
5022          R = qlc:e(F(merge))">>,
5023
5024       <<"F = fun(M) ->
5025                qlc:q([{XX,YY} ||
5026                       {XX,X} <- [{a,1},{b,2},{bb,2},{c,3},{cc,3}],
5027                       {Y,YY} <- [{0,a},{1,a},{1,aa},{2,b},{2,bb},{2,bbb},
5028                                  {4,d}],
5029                        X =:= Y],
5030                      {join,M})
5031              end,
5032          R = qlc:e(F(nested_loop)),
5033          R = qlc:e(F(merge))">>,
5034
5035       <<"Q = qlc:q([{XX,YY} ||
5036                        {XX,X} <- [{b,1},{c,3}],
5037                        {Y,YY} <- [{1,a}],
5038                        X =:= Y],
5039                    {join,merge}),
5040          [{b,a}] = qlc:e(Q)">>,
5041
5042       <<"Q = qlc:q([{XX,YY} ||
5043                            {XX,X} <- [{b,1},{c,3}],
5044                            {Y,YY} <- qlc_SUITE:table_error([{1,a}], 1, err),
5045                            X =:= Y],
5046                        {join,merge}),
5047              err = qlc:e(Q)">>,
5048
5049       <<"Q = qlc:q([{XX,YY} ||
5050                            {XX,X} <- [{a,1},{aa,1}],
5051                            {Y,YY} <- [{1,a}],
5052                            X =:= Y],
5053                        {join,merge}),
5054              [{a,a},{aa,a}] = qlc:e(Q)">>,
5055
5056       <<"Q = qlc:q([{XX,YY} ||
5057                            {XX,X} <- qlc_SUITE:table_error([{a,1},{aa,1}],
5058                                                             2, err),
5059                            {Y,YY} <- [{1,a}],
5060                            X =:= Y],
5061                        {join,merge}),
5062              err = qlc:e(Q)">>,
5063
5064       <<"Q = qlc:q([{XX,YY} ||
5065                            {XX,X} <- [{a,1}],
5066                            {Y,YY} <- [{1,a},{1,aa}],
5067                            X =:= Y],
5068                        {join,merge}),
5069              [{a,a},{a,aa}]= qlc:e(Q)">>,
5070
5071       <<"Q = qlc:q([{XX,YY} ||
5072                            {XX,X} <- qlc_SUITE:table_error([{a,1}], 2, err),
5073                            {Y,YY} <- [{1,a},{1,aa}],
5074                            X =:= Y],
5075                        {join,merge}),
5076          C = qlc:cursor(Q),
5077          [{a,a}] = qlc:next_answers(C, 1),
5078          qlc:delete_cursor(C),
5079          err = qlc:e(Q)">>,
5080
5081       <<"F = fun(M) ->
5082                    qlc:q([{XX,YY} ||
5083                               {XX,X} <- [{a,1},{b,2},{bb,2},{c,3},{cc,3}],
5084                               {Y,YY} <- [{0,a},{1,a},{1,aa},{2,b},
5085                                          {2,bb},{2,bbb}],
5086                            X =:= Y],
5087                          {join,M})
5088              end,
5089              %% [{a,a},{a,aa},{b,b},{b,bb},{b,bbb},{bb,b},{bb,bb},{bb,bbb}]
5090              R = qlc:e(F(nested_loop)),
5091              R = qlc:e(F(merge))">>,
5092
5093
5094       <<"F = fun(M) ->
5095                   qlc:q([{XX,YY} ||
5096                          {XX,X} <- [{a,1},{b,2},{bb,2},{c,3},{cc,3}],
5097                          {Y,YY} <- qlc_SUITE:table_error([{0,a},{1,a},{1,aa},
5098                                                           {2,b},{2,bb},
5099                                                           {2,bbb}],
5100                                                          1, err),
5101                           X =:= Y],
5102                         {join,M})
5103              end,
5104              %% [{a,a},{a,aa},{b,b},{b,bb},{b,bbb},{bb,b},{bb,bb},{bb,bbb}]
5105              err = qlc:e(F(nested_loop)),
5106              err = qlc:e(F(merge))">>,
5107
5108       <<"Q = qlc:q([{XX,YY} ||
5109                            {XX,X} <- qlc_SUITE:table_error([], 2, err),
5110                            {Y,YY} <- [{2,b},{3,c}],
5111                            X =:= Y],
5112                        {join,merge}),
5113              err = qlc:e(Q)">>,
5114
5115       <<"Q = qlc:q([{XX,YY} ||
5116                            {XX,X} <- [{a,1},{c,3}],
5117                            {Y,YY} <- [{2,b},{3,c}],
5118                            X =:= Y],
5119                        {join,merge}),
5120              [{c,c}] = qlc:e(Q)">>,
5121
5122       <<"Q = qlc:q([{XX,YY} ||
5123                            {XX,X} <- [{a,1},{aa,1}],
5124                            {Y,YY} <- [{1,a},{1,aa}],
5125                            X =:= Y],
5126                        {join,merge}),
5127              [{a,a},{a,aa},{aa,a},{aa,aa}] = qlc:e(Q)">>,
5128
5129       <<"Q = qlc:q([{XX,YY} ||
5130                            {XX,X} <- [{a,1},{b,2}],
5131                            {Y,YY} <- [{1,a},{1,aa}],
5132                            X =:= Y],
5133                        {join,merge}),
5134              [{a,a},{a,aa}] = qlc:e(Q)">>,
5135
5136       <<"Q = qlc:q([{XX,YY} ||
5137                            {XX,X} <- [{a,1},{b,2}],
5138                            {Y,YY} <- qlc_SUITE:table_error([{1,a},{1,aa}],
5139                                                            1, err),
5140                            X =:= Y],
5141                        {join,merge}),
5142              err = qlc:e(Q)">>,
5143
5144       <<"Q = qlc:q([{XX,YY} ||
5145                            {XX,X} <- [{a,1},{b,2}],
5146                            {Y,YY} <- [{1,a},{1,aa},{1,aaa},{1,aaaa}],
5147                            X =:= Y],
5148                        {join,merge}),
5149              [{a,a},{a,aa},{a,aaa},{a,aaaa}]= qlc:e(Q)">>,
5150
5151       <<"Q = qlc:q([{element(1, X), element(2, Y)} ||
5152                            X <- [{a,1},{aa,1}],
5153                            Y <- [{1,a},{1,aa}],
5154                            element(2, X) =:= element(1, Y)],
5155                        {join,merge}),
5156              [{a,a},{a,aa},{aa,a},{aa,aa}] = qlc:e(Q)">>,
5157
5158       <<"Q = qlc:q([{element(1, X), element(2, Y)} ||
5159                            X <- [{a,1},{aa,1}],
5160                            Y <- qlc_SUITE:table_error([], 1, err),
5161                            element(2, X) =:= element(1, Y)],
5162                        {join,merge}),
5163              err = qlc:e(Q)">>,
5164
5165       <<"Q = qlc:q([{element(1, X), element(2, Y)} ||
5166                            X <- qlc_SUITE:table_error([{a,1}], 2, err),
5167                            Y <- [{2,b}],
5168                            element(2, X) =:= element(1, Y)],
5169                        {join,merge}),
5170              err = qlc:e(Q)">>,
5171
5172       <<"Q = qlc:q([{XX,YY} ||
5173                  {XX,X} <- [{1,a},{'1b',b},{2,b}],
5174                  {Y,YY} <- [{a,1},{b,'1b'},{c,1}],
5175                  X == Y],
5176              {join,merge}),
5177          [{1,1},{'1b','1b'},{2,'1b'}] = qlc:e(Q)">>,
5178
5179       <<"Q = qlc:q([{XX,YY} ||
5180                  {XX,X} <- qlc_SUITE:table_error([{1,a},{'1b',b},{2,b}],
5181                                                  2, err),
5182                  {Y,YY} <- [{a,1},{b,'1b'},{c,1}],
5183                  X == Y],
5184              {join,merge}),
5185          err = qlc:e(Q)">>
5186
5187          ],
5188    run(Config, ETs),
5189
5190    %% Mostly examples where temporary files are needed while merging.
5191    FTs = [
5192       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5193          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5194          F = fun(J) ->
5195                      qlc:q([{XX,YY} ||
5196                                {XX,X} <- L1,
5197                                {Y,YY} <- L2,
5198                                X == Y],
5199                            {join,J})
5200              end,
5201          Qm = F(merge),
5202          Qn = F(nested_loop),
5203          true = qlc:e(Qm,{max_list_size, 0}) =:= qlc:e(Qn)">>,
5204
5205       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5206          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5207          Q = qlc:q([{XX,YY} ||
5208                        {XX,X} <- L1,
5209                        {Y,YY} <- L2,
5210                        X == Y],
5211                    {join,merge}),
5212          {error,_,{file_error,_,_}} =
5213               qlc:e(Q, [{max_list_size,64*1024},{tmpdir,\"/a/b/c\"}])">>,
5214
5215       <<"L1 = qlc_SUITE:table_error([{1,a},{2,a}], 2, err),
5216          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5217          F = fun(J) ->
5218                      qlc:q([{XX,YY} ||
5219                                {XX,X} <- L1,
5220                                {Y,YY} <- L2,
5221                                X == Y],
5222                            {join,J})
5223              end,
5224          Qm = F(merge),
5225          Qn = F(nested_loop),
5226          err = qlc:e(Qm, {max_list_size,64*1024}),
5227          err = qlc:e(Qn)">>,
5228
5229       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5230          L2 = qlc_SUITE:table_error([{a,Y} || Y <- lists:seq(1, 10000)],
5231                                     1, err),
5232          F = fun(J) ->
5233                      qlc:q([{XX,YY} ||
5234                                {XX,X} <- L1,
5235                                {Y,YY} <- L2,
5236                                X == Y],
5237                            {join,J})
5238              end,
5239          Qm = F(merge),
5240          Qn = F(nested_loop),
5241          err = qlc:e(Qm, {max_list_size,64*1024}),
5242          err = qlc:e(Qn)">>,
5243
5244       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)] ++
5245               [{'1b',b},{2,b}] ++ [{Y,d} || Y <- lists:seq(1, 2)],
5246          L2 = [{a,Y} || Y <- lists:seq(1, 10000)] ++
5247               [{b,'1b'}] ++ [{c,1}] ++ [{d,Y} || Y <- lists:seq(1, 10000)],
5248          F = fun(J) ->
5249                      qlc:q([{XX,YY} ||
5250                                {XX,X} <- L1,
5251                                {Y,YY} <- L2,
5252                                X == Y],
5253                            {join,J})
5254              end,
5255          Qm = F(merge),
5256          Qn = F(nested_loop),
5257          true = lists:sort(qlc:e(Qm, {max_list_size,64*1024})) =:=
5258                 lists:sort(qlc:e(Qn))">>,
5259
5260       <<"F = fun(J) ->
5261                      qlc:q([{XX,YY} ||
5262                                {XX,X} <- [{Y,a} || Y <- lists:seq(1, 2)],
5263                                {Y,YY} <- [{a,Y} || Y <- lists:seq(1,100000)],
5264                                X == Y],
5265                            {join,J})
5266              end,
5267          Qm = F(merge),
5268          Qn = F(nested_loop),
5269          true = qlc:e(Qm, {max_list_size,64*1024}) =:= qlc:e(Qn)">>,
5270
5271       %% More than one join in one QLC expression.
5272       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5273          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5274          F = fun(J) ->
5275                      Q = qlc:q([{XX,YY} ||
5276                                    {XX,X} <- L1,
5277                                    {Y,YY} <- L2,
5278                                    X == Y,
5279                                    begin XX > 1 end,
5280                                    begin YY > 9999 end],
5281                                {join,J}),
5282                      qlc:q([{XX1,YY1,XX2,YY2} ||
5283                                {XX1,YY1} <- Q,
5284                                {XX2,YY2} <- Q])
5285              end,
5286          Qm = F(merge),
5287          Qn = F(nested_loop),
5288          R1 = lists:sort(qlc:e(Qm, {max_list_size,64*1024})),
5289          R2 = lists:sort(qlc:e(Qm, {max_list_size,1 bsl 31})),
5290          true = R1 =:= lists:sort(qlc:e(Qn)),
5291          true = R1 =:= R2">>,
5292
5293       <<"L1 = [{Y,a} || Y <- lists:seq(1, 2)],
5294          L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
5295          F = fun(J) ->
5296                      Q = qlc:q([{XX,YY} ||
5297                                    {XX,X} <- L1,
5298                                    {Y,YY} <- L2,
5299                                    X == Y,
5300                                    begin XX > 1 end,
5301                                    begin YY > 9999 end],
5302                                {join,J}),
5303                      qlc:q([{XX1,YY1,XX2,YY2} ||
5304                                {XX1,YY1} <- Q,
5305                                {XX2,YY2} <- Q,
5306                                throw(thrown)])
5307              end,
5308          Qm = F(merge),
5309          thrown = (catch {any_term, qlc:e(Qm, {max_list_size,64*1024})})">>,
5310
5311       <<"%% Bigger than 64*1024.
5312          T1 = {1, lists:seq(1, 20000)},
5313          L1 = [{a,T1},{b,T1}],
5314          L2 = [{T1,a},{T1,b}],
5315          F = fun(J) ->
5316                      qlc:q([{XX,YY} ||
5317                                {XX,X} <- L1,
5318                                {Y,YY} <- L2,
5319                                X == Y],
5320                            {join,J})
5321              end,
5322          Qm = F(merge),
5323          Qn = F(nested_loop),
5324          R = [{a,a},{a,b},{b,a},{b,b}],
5325          R = qlc:e(Qm, {max_list_size,64*1024}),
5326          R = qlc:e(Qn)">>,
5327
5328       <<"%% Bigger than 64*1024. No temporary files.
5329          T1 = {1, lists:seq(1, 20000)},
5330          L1 = [{a,T1},{b,T1}],
5331          L2 = [{T1,a},{T1,b}],
5332          F = fun(J) ->
5333                      qlc:q([{XX,YY} ||
5334                                {XX,X} <- L1,
5335                                {Y,YY} <- L2,
5336                                X == Y],
5337                            {join,J})
5338              end,
5339          Qm = F(merge),
5340          Qn = F(nested_loop),
5341          R = [{a,a},{a,b},{b,a},{b,b}],
5342          R = qlc:e(Qm, {max_list_size,1 bsl 31}),
5343          R = qlc:e(Qn)">>
5344
5345
5346          ],
5347    run(Config, FTs),
5348
5349    ok.
5350
5351%% Merge join optimizations (avoid unnecessary sorting).
5352join_sort(Config) when is_list(Config) ->
5353    Ts = [
5354       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}]),
5355          H1 = qlc:q([X || X <- H1_1], unique),
5356          H2 = qlc:keysort(2, [{1,2},{3,4}]),
5357          H3 = qlc:q([{X,Y} || {X,_,_} <- H1,
5358                               {_,Y} <- H2,
5359                               X =:= Y]),
5360          {1,0,0,2} = join_info(H3),
5361          [{4,4}] = qlc:e(H3)">>,
5362
5363       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}]),
5364          H1 = qlc:q([X || X <- H1_1], unique), % keeps the order
5365          H2 = qlc:keysort(2, [{1,2},{3,4}]),
5366          H3 = qlc:q([{X,Y} || {X,_,_} <- H1, % no extra keysort
5367                               {Y,_} <- H2,   % an extra keysort
5368                               X =:= Y]),
5369          {1,0,0,3} = join_info(H3),
5370          [{1,1}] = qlc:e(H3)">>,
5371
5372       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}], {tmpdir,\"\"}),
5373          H1 = qlc:q([X || X <- H1_1], unique),
5374          H2 = qlc:keysort(2, [{1,2},{3,4}]),
5375          H3 = qlc:q([{X,Y} || {_,X,_} <- H1,
5376                               {_,Y} <- H2,
5377                               X =:= Y]),
5378          {1,0,0,3} = join_info(H3),
5379          [{2,2}] = qlc:e(H3)">>,
5380
5381       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6}], {tmpdir,\"\"}),
5382          H1 = qlc:q([X || X <- H1_1], unique),
5383          H2 = qlc:keysort(2, [{1,2},{3,4}]),
5384          H3 = qlc:q([{X,Y} || {_,X,_} <- H1,
5385                               {_,Y} <- H2,
5386                               X =:= Y]),
5387          {1,0,0,3} = join_info(H3),
5388          [{2,2}] = qlc:e(H3)">>,
5389
5390       <<"H1 = qlc:sort([{1,a},{2,b},{3,c}]),
5391          %% Since H1 is sorted it is also keysorted on the first column.
5392          Q = qlc:q([{X, Y} || {X,_} <- H1,
5393                               {Y} <- [{0},{1},{2}],
5394                               X == Y]),
5395          {1,0,0,1} = join_info(Q),
5396          [{1,1},{2,2}] = qlc:e(Q)">>,
5397
5398       <<"H1 = qlc:sort([{r,a,1},{r,b,2},{r,c,3}]),
5399          Q = qlc:q([{X, Y} || {r,_,X} <- H1, % needs keysort(3)
5400                               {Y} <- [{0},{1},{2}],
5401                               X == Y]),
5402          {1,0,0,2} = join_info(Q),
5403          [{1,1},{2,2}] = qlc:e(Q)">>,
5404
5405       <<"QH = qlc:q([X || X <- [{1,2,3},{4,5,6}],
5406                           Y <- qlc:sort([{1,2},{3,4}]),
5407                           element(1, X) =:= element(2, Y)]),
5408          {1,0,0,2} = join_info_count(QH),
5409          [{4,5,6}] = qlc:e(QH)">>,
5410
5411       <<"H1_1 = qlc:keysort(1, [{1,2,3},{4,5,6},{1,2,3}]),
5412          H1 = qlc:q([X || X <- H1_1], unique),
5413          H2 = qlc:keysort(2, [{2,1},{3,4}]),
5414          H3 = qlc:q([{X,Y} || {X,_,_} <- H1,
5415                               {_,Y} <- H2,
5416                               X =:= Y]),
5417          H4 = qlc:keysort(1, [{1,2},{3,4},{4,a}]),
5418          H5 = qlc:q([{X,Y} || {X,_} <- H4,
5419                               {_,Y} <- H3,
5420                               X =:= Y]),
5421          {2,0,0,3} = join_info_count(H5),
5422          [{1,1},{4,4}]= qlc:e(H5)">>,
5423
5424       <<"
5425          H1 = qlc:keysort(2, [{1,a,u},{2,b,k},{3,c,l}]),
5426          H2 = qlc:q([{a,X,Y,a} || {1,X,u} <- H1,
5427                                   {2,Y,k} <- H1]),
5428          %% Neither H1 nor H2 need to be key-sorted
5429          %% (the columns are constant).
5430          H3 = qlc:q([{A,B,C,D,E,F,G,H} ||
5431                         {A,B,C,D} <- H2,
5432                         {E,F,G,H} <- H2,
5433                         A =:= H],
5434                     {join,merge}),
5435          {1,0,0,4} = join_info_count(H3),
5436          [{a,a,b,a,a,a,b,a}] = qlc:e(H3)">>,
5437
5438       <<"%% Q1 is sorted on X or Y.
5439          Q1 = qlc:q([{X,Y} ||
5440                         {X,_} <- qlc:keysort(1, [{1,a},{2,b}]),
5441                         {_,Y} <- qlc:keysort(2, [{aa,11},{bb,22}]),
5442                         X < Y]),
5443          [{1,11},{1,22},{2,11},{2,22}] = qlc:e(Q1),
5444          Q = qlc:q([{X,Y} ||
5445                        {X,_} <- Q1, % no need to sort Q1
5446                        {Y} <- [{0},{1},{2},{3}],
5447                        X =:= Y]),
5448          {1,0,0,3} = join_info_count(Q),
5449          [{1,1},{1,1},{2,2},{2,2}] = qlc:e(Q)">>,
5450
5451       <<"H1 = qlc:keysort([2], [{r,1},{r,2},{r,3}]),
5452          %% H1 is actually sorted, but this info is not captured.
5453          Q = qlc:q([{X, Y} || {r,X} <- H1,
5454                               {Y} <- [{0},{1},{2}],
5455                               X == Y]),
5456          {1,0,0,2} = join_info_count(Q),
5457          [{1,1},{2,2}] = qlc:e(Q)">>,
5458
5459       <<"%% Two leading constants columns and sorted objects
5460          %% implies keysorted on column 3.
5461          H1 = qlc:sort(qlc:q([{a,X,Y} || {X,Y} <- [{1,2},{2,3},{3,3}]])),
5462          H2 = qlc:q([{X,Y} ||
5463                         {a,3,X} <- H1,
5464                         {a,2,Y} <- H1,
5465                         X =:= Y]),
5466          {1,0,0,0} = join_info_count(H2),
5467          [{3,3}] = qlc:e(H2)">>,
5468
5469       <<"QH = qlc:q([{X,Y} || {X,Y} <- [{1,4},{1,3}],
5470                               {Z} <- [{1}],
5471                               X =:= Z, (Y =:= 3) or (Y =:= 4)]),
5472          {1,0,0,1} = join_info_count(QH),
5473          [{1,4},{1,3}] = qlc:e(QH)">>,
5474
5475       <<"E = ets:new(join, [ordered_set]),
5476          true = ets:insert(E, [{1,a},{2,b},{3,c}]),
5477          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E), % no need to sort
5478                               {Y} <- [{0},{1},{2}],
5479                               X == Y], {join,merge}),
5480          {1,0,0,1} = join_info(Q),
5481          [{1,1},{2,2}] = qlc:e(Q),
5482          ets:delete(E)">>,
5483
5484       <<"H1 = qlc:sort([{r,1,a},{r,2,b},{r,3,c}]),
5485          Q = qlc:q([{X, Y} || {r,X,_} <- H1, % does not need keysort(3)
5486                               {Y} <- [{0},{1},{2}],
5487                               X == Y]),
5488          {1,0,0,1} = join_info(Q),
5489          [{1,1},{2,2}] = qlc:e(Q)">>,
5490
5491       <<"H1 = qlc:keysort(2,[{r,1},{r,2},{r,3}]),
5492          H2 = [{a},{b}],
5493          %% Several columns in different qualifiers have initial
5494          %% constant columns.
5495          H3 = qlc:keysort(1,[{c1,c2,1},{foo,bar,2},{c1,c2,3},{c1,c2,2}]),
5496          Q = qlc:q([{r,X,Y,Z} || {r,X} <- H1,
5497                                  {Y} <- H2,
5498                                  {c1,c2,Z} <- H3,
5499                                  X =:= Z], {join,merge}),
5500          {1,0,0,3} = join_info(Q),
5501          [{r,1,a,1},{r,1,b,1},{r,2,a,2},{r,2,b,2},{r,3,a,3},{r,3,b,3}] =
5502              qlc:e(Q)">>,
5503
5504       <<"H1 = qlc:keysort(2,[{r,1},{r,2},{r,3}]),
5505          H2 = [{a},{b}],
5506          %% As the last one, but one keysort less.
5507          H3 = qlc:keysort(3,[{c1,c2,1},{foo,bar,2},{c1,c2,3},{c1,c2,2}]),
5508          Q = qlc:q([{r,X,Y,Z} || {r,X} <- H1,
5509                                  {Y} <- H2,
5510                                  {c1,c2,Z} <- H3,
5511                                  X =:= Z], {join,merge}),
5512          {1,0,0,2} = join_info(Q),
5513          [{r,1,a,1},{r,1,b,1},{r,2,a,2},{r,2,b,2},{r,3,a,3},{r,3,b,3}] =
5514              qlc:e(Q)">>,
5515
5516       <<"H1 = qlc:keysort(2,[{r,1},{r,2},{r,3}]),
5517          H2 = [{a},{b}],
5518          H3 = qlc:keysort(1,[{c1,c2,1},{foo,bar,2},{c1,c2,3},{c1,c2,2}]),
5519          %% One generator before the joined generators.
5520          Q = qlc:q([{r,X,Y,Z} || {Y} <- H2,
5521                                  {r,X} <- H1,
5522                                  {c1,c2,Z} <- H3,
5523                                  X =:= Z], {join,merge}),
5524          {1,0,0,3} = join_info(Q),
5525          [{r,1,a,1},{r,2,a,2},{r,3,a,3},{r,1,b,1},{r,2,b,2},{r,3,b,3}] =
5526              qlc:e(Q)">>,
5527
5528       <<"H1 = [{a,1},{b,2},{c,3},{d,4}],
5529          H2 = [{a},{b}],
5530          H3 = [{c1,c2,a},{foo,bar,b},{c1,c2,c},{c1,c2,d}],
5531          %% A couple of \"extra\" filters and generators.
5532          Q = qlc:q([{X,Y,Z} || {X,_} <- H1,
5533                                {Y} <- H2,
5534                                X > Y,
5535                                {c1,c2,Z} <- H3,
5536                                {W} <- [{a},{b}],
5537                                W > a,
5538                                X =:= Z]),
5539          {1,0,0,2} = join_info(Q),
5540          [{c,a,c},{c,b,c},{d,a,d},{d,b,d}] = qlc:e(Q)">>,
5541
5542       <<"H1 = qlc:keysort(2,[{r,1},{r,2},{r,3}]),
5543          H2 = qlc:sort([{c1,c2,1},{foo,bar,2},{c1,c2,3},{c1,c2,2}]),
5544          %% H2 is sorted, no keysort necessary.
5545          %% This example shows that the 'filter-part' of the pattern
5546          %% ({c1,c2,Z}) should be evaluated _before_ the join.
5547          %% Otherwise the objects cannot be assumed to be keysort:ed on the
5548          %% third column (if merge join), and lookup-join would lookup
5549          %% more keys than necessary.
5550          Q = qlc:q([{r,X,Z} || {r,X} <- H1,
5551                                {c1,c2,Z} <- H2,
5552                                X =:= Z] ,{join,merge}),
5553          {1,0,0,1} = join_info(Q),
5554          [{r,1,1},{r,2,2},{r,3,3}] = qlc:e(Q)">>,
5555
5556       <<"H1 = [{1,a},{2,b},{3,c}],
5557          H2 = [{0,0},{1,1},{2,2}],
5558          H3 = qlc:q([{A,C,D} ||
5559                         {A,_B} <- H1,
5560                         {C,D} <- H2,
5561                         A == D, C == D]),
5562          H4 = [{1,1},{2,2},{3,3}],
5563          H5 = qlc:q([{X,Y} ||
5564                         {X,_,_} <- H3, % no need to sort this one (merge join)
5565                         {_,Y} <- H4,
5566                         X == Y]),
5567          Q = qlc:q([{X,Y} ||
5568                        {X,_} <- H5, % no need to sort this one
5569                        {Y,_} <- H4,
5570                        X == Y]),
5571          {{3,0,0,4},{3,0,0,6}} = join_info(Q),
5572          [{1,1},{2,2}] = qlc:e(Q)">>,
5573
5574       <<"%% There is an extra test (_C1, element(1, X) =:= 1) that is not
5575          %% necessary since the match spec does the same check. This can be
5576          %% improved upon.
5577          Q = qlc:q([{X,Y} ||
5578                        X <- [{2},{1}],
5579                        element(1, X) =:= 1,
5580                        Y=_ <- [{2},{1}],
5581                        element(1, X) =:= element(1, Y)]),
5582          {qlc,_,
5583              [{generate,_,{qlc,_,
5584                              [{generate,_,{qlc,_,
5585                                             [{generate,_,{list,{list,_},_}},
5586                                              _C1],[]}},
5587                               {generate,_,{qlc,_,
5588                                             [{generate,_,{list,[{2},{1}]}},
5589                                              _C2],[]}},_],
5590                              [{join,merge}]}},_],[]} = i(Q),
5591          {1,0,0,0} = join_info_count(Q),
5592          [{{1},{1}}] = qlc:e(Q)">>,
5593
5594       <<"etsc(fun(E) ->
5595                       L = [{a,b,a},{c,d,b},{1,2,a},{3,4,b}],
5596                       Q = qlc:q([P1 || {X,2,Z}=P1 <- ets:table(E),
5597                                        Y <- L,
5598                                        X =:= 1,
5599                                        Z =:= a,
5600                                        P1 =:= Y,
5601                                        X =:= element(1, Y)]),
5602                       {1,0,0,0} = join_info_count(Q),
5603                       [{1,2,a}] = qlc:e(Q)
5604               end, [{1,2,a},{3,4,b}])">>,
5605
5606       %% Merge join on Z and element(3, Y). No need to sort!
5607       <<"etsc(fun(E) ->
5608                       L = [{a,b,a},{c,d,b},{1,2,a},{3,4,b}],
5609                       Q = qlc:q([P1 || {X,2,Z}=P1 <- ets:table(E),
5610                                        Y <- L,
5611                                        (X =:= 1) or (X =:= 2),
5612                                        Z =:= a,
5613                                        P1 =:= Y,
5614                                        X =:= element(1, Y)]),
5615                       {1,0,0,0} = join_info_count(Q),
5616                       [{1,2,a}] = qlc:e(Q)
5617               end, [{1,2,a},{3,4,b}])">>,
5618
5619       <<"%% Y is constant as well as X. No keysort, which means that
5620          %% Y must be filtered before merge join.
5621          etsc(fun(E) ->
5622                       Q = qlc:q([X || {1,2}=X <- ets:table(E),
5623                                       Y <- [{a,b},{c,d},{1,2},{3,4}],
5624                                       X =:= Y,
5625                                       element(1, X) =:= element(1, Y)]),
5626                       {1,0,0,0} = join_info_count(Q),
5627                       [{1,2}] = qlc:e(Q)
5628               end, [{1,2},{3,4}])">>
5629
5630         ],
5631    run(Config, Ts),
5632    ok.
5633
5634%% Join of more than two columns.
5635join_complex(Config) when is_list(Config) ->
5636    Ts = [{three,
5637           <<"three() ->
5638                  L = [],
5639                  Q = qlc:q([{X,Y,Z} || {X,_} <- L,
5640                                        {_,Y} <- L,
5641                                        {Z,_} <- L,
5642                                        X =:= Y, Y == Z
5643                                     ]),
5644                  qlc:e(Q).">>,
5645           [],
5646           {warnings,[{{3,23},qlc,too_complex_join}]}},
5647
5648          {two,
5649           <<"two() ->
5650                  Q = qlc:q([{X,Y,Z,W} ||
5651                      {X} <- [],
5652                      {Y} <- [],
5653                      {Z} <- [],
5654                      {W} <- [],
5655                      X =:= Y,
5656                      Z =:= W],{join,merge}),
5657                  qlc:e(Q).">>,
5658           [],
5659           {warnings,[{{2,23},qlc,too_many_joins}]}},
5660
5661          {two_again,
5662           <<"two() ->
5663                  Q = qlc:q([{X,Y,Z,W} ||
5664                      {X} <- [],
5665                      {Y} <- [],
5666                      {Z} <- [],
5667                      {W} <- [],
5668                      X =:= Y,
5669                      Z =:= W],{join,merge}),
5670                  qlc:e(Q).">>,
5671           [{error_location, line}],
5672           {warnings,[{2,qlc,too_many_joins}]}}
5673       ],
5674
5675    compile(Config, Ts),
5676
5677    Ts2 = [{three,
5678            <<"three() ->
5679                  L = [],
5680                  Q = qlc:q([{X,Y,Z} || {X,_} <- L,
5681                                        {_,Y} <- L,
5682                                        {Z,_} <- L,
5683                                        X =:= Y, Y == Z
5684                                     ]),
5685                  qlc:e(Q).">>,
5686            [],
5687            {[],
5688             ["cannot handle join of three or more generators efficiently"]}},
5689
5690          {two,
5691           <<"two() ->
5692                  Q = qlc:q([{X,Y,Z,W} ||
5693                      {X} <- [],
5694                      {Y} <- [],
5695                      {Z} <- [],
5696                      {W} <- [],
5697                      X =:= Y,
5698                      Z =:= W],{join,merge}),
5699                  qlc:e(Q).">>,
5700           [],
5701           {[],["cannot handle more than one join efficiently"]}}
5702       ],
5703
5704    compile_format(Config, Ts2),
5705
5706    ok.
5707
5708
5709%% OTP-5644. Handle the new language element M:F/A.
5710otp_5644(Config) when is_list(Config) ->
5711    Ts = [
5712       <<"Q = qlc:q([fun modul:mfa/0 || _ <- [1,2],
5713                                        is_function(fun modul:mfa/0, 0)]),
5714          [_,_] = qlc:eval(Q)">>
5715       ],
5716
5717    run(Config, Ts),
5718    ok.
5719
5720%% OTP-5195. Allow traverse functions returning terms.
5721otp_5195(Config) when is_list(Config) ->
5722    %% Several minor improvements have been implemented in OTP-5195.
5723    %% The test cases are spread all over... except these.
5724    %%
5725    %% Traverse functions returning terms.
5726
5727    Ts = [<<"L = [1,2,3],
5728             Err = {error,modul,err},
5729             H = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5730             Err = qlc:e(H)">>,
5731
5732          <<"Err = {error,modul,err},
5733             TravFun = fun() -> Err end,
5734             H1 = qlc:sort(qlc:q([X || X <- qlc:table(TravFun, [])])),
5735             H = qlc:q([{X} || X <- H1]),
5736             Err = qlc:e(H)">>,
5737
5738          <<"L = [1,2,3],
5739             Err = {error,modul,err},
5740             H = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5741             C = qlc:cursor(H),
5742             R = qlc:next_answers(C, all_remaining),
5743             qlc:delete_cursor(C),
5744             Err = R">>,
5745
5746          <<"L = [1,2,3],
5747             Err = {error,modul,err},
5748             H = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5749             F = fun(Obj, A) -> A++[Obj] end,
5750             Err = qlc:fold(F, [], H)">>,
5751
5752          <<"Err = {error,modul,err},
5753             TravFun = fun() -> Err end,
5754             H1 = qlc:sort(qlc:q([X || X <- qlc:table(TravFun, [])])),
5755             H = qlc:q([{X} || X <- H1]),
5756             F = fun(Obj, A) -> A++[Obj] end,
5757             Err = qlc:fold(F, [], H)">>,
5758
5759          <<"Q1 = qlc:append([qlc:append([ugly()]),[3]]),
5760             Q = qlc:q([X || X <- Q1]),
5761             42 = qlc:e(Q),
5762             ok.
5763
5764             ugly() ->
5765                 [apa | fun() -> 42 end].
5766             foo() -> bar">>,
5767
5768          <<"L = [1,2,3],
5769             Err = {error,modul,err},
5770             H = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5771             H1 = qlc:q([X || X <- H], unique),
5772             Err = qlc:e(H1)">>,
5773
5774          <<"Err = {error, module, err},
5775             L = [1,2,3],
5776             H1 = qlc:q([{X} || X <- qlc_SUITE:table_error(L, Err)]),
5777             H = qlc:q([{X,Y,Z} || X <- H1, Y <- H1, Z <- L], cache),
5778             qlc:e(H, cache_all)">>,
5779
5780          <<"Err = {error, module, err},
5781             L = [1,2,3],
5782             H1 = qlc:q([X || X <- qlc_SUITE:table_error(L, Err)]),
5783             H = qlc:q([{X,Y,Z} || X <- H1, Y <- H1, Z <- L], cache),
5784             qlc:e(H, [cache_all,unique_all])">>,
5785
5786          <<"L = [{1},{2},{3}],
5787             H = qlc:q([X || {X} <- qlc_SUITE:table_lookup_error(L),
5788                             X =:= 2]),
5789             {error, lookup, failed} = qlc:e(H)">>,
5790
5791          %% The traverse function can return any value, but it must not
5792          %% return an improper list. Improper lists must not be given anyway.
5793          <<"{'EXIT', {{badfun,a},_}} =
5794             (catch qlc:e(qlc:q([{X} || X <- [1 | a], begin true end])))">>
5795
5796       ],
5797
5798    run(Config, Ts),
5799
5800    Ts2 = [<<"Q = qlc:q([{X,Y} || {X} <- [{1},{2},{3}],
5801                                  begin
5802                                      %% Used to generate a badly formed file
5803                                      Y = 3, true
5804                                  end,
5805                                  X =:= Y]),
5806              [{3,3}] = qlc:e(Q)">>],
5807    run(Config, Ts2),
5808
5809    ok.
5810
5811%% OTP-6038. Bug fixes: unique and keysort; cache.
5812otp_6038_bug(Config) when is_list(Config) ->
5813    %% The 'unique' option can no longer be merged with the keysort options.
5814    %% This used to return [{1,a},{1,c},{2,b},{2,d}], but since
5815    %% file_sorter:keysort now removes duplicates based on keys, the
5816    %% correct return value is [{1,a},{2,b}].
5817    Ts = [<<"H1 = qlc:q([X || X <- [{1,a},{2,b},{1,c},{2,d}]], unique),
5818             H2 = qlc:keysort(1, H1, [{unique,true}]),
5819             [{1,a},{2,b}] = qlc:e(H2)">>],
5820
5821    run(Config, Ts),
5822
5823    %% Sometimes the cache options did not empty the correct tables.
5824    CTs = [
5825       <<"Options = [cache,unique],
5826          V1 = qlc:q([{X,Y} || X <- [1,2], Y <- [3]], Options),
5827          V2 = qlc:q([{X,Y} || X <- [a,b], Y <- V1]),
5828          V3 = qlc:q([{X,Y} || X <- [5,6], Y <- [7]], Options),
5829          Q = qlc:q([{X,Y} || X <- V2, Y <- V3]),
5830          R = qlc:e(Q),
5831          L1 = [{X,Y} || X <- [1,2], Y <- [3]],
5832          L2 = [{X,Y} || X <- [a,b], Y <- L1],
5833          L3 = [{X,Y} || X <- [5,6], Y <- [7]],
5834          L = [{X,Y} || X <- L2, Y <- L3],
5835          true = R =:= L">>,
5836       <<"Options = [cache,unique],
5837          V1 = qlc:q([{X,Y} || X <- [1,2], Y <- [3]], Options),
5838          V2 = qlc:q([{X,Y} || X <- [a,b], Y <- V1]),
5839          V3 = qlc:q([{X,Y} || X <- [5,6], Y <- [7]], Options),
5840          V4 = qlc:q([{X,Y} || X <- V2, Y <- V3], Options),
5841          Q = qlc:q([{X,Y} || X <- [1,2], Y <- V4]),
5842          R = qlc:e(Q),
5843          L1 = [{X,Y} || X <- [1,2], Y <- [3]],
5844          L2 = [{X,Y} || X <- [a,b], Y <- L1],
5845          L3 = [{X,Y} || X <- [5,6], Y <- [7]],
5846          L4 = [{X,Y} || X <- L2, Y <- L3],
5847          L = [{X,Y} || X <- [1,2], Y <- L4],
5848          true = R =:= L">>
5849       ],
5850    run(Config, CTs),
5851
5852    ok.
5853
5854%% OTP-6359. dets:select() never returns the empty list.
5855otp_6359(Config) when is_list(Config) ->
5856    dets:start(),
5857    T = luna,
5858    Fname = filename(T, Config),
5859
5860    Ts = [
5861       [<<"T = luna, Fname = \"">>, Fname, <<"\",
5862           {ok, _} = dets:open_file(T, [{file,Fname}]),
5863           Q = qlc:q([F ||
5864                         F <- dets:table(T),
5865                         (F band ((1 bsl 0)) =/= 0),
5866                         true]),
5867           [] = qlc:eval(Q),
5868           ok = dets:close(T),
5869           file:delete(\"">>, Fname, <<"\"),
5870           ok">>]
5871    ],
5872
5873    run(Config, Ts),
5874    ok.
5875
5876%% OTP-6562. compressed = false (should be []) when sorting before join.
5877otp_6562(Config) when is_list(Config) ->
5878    Bug = [
5879      %% This example uses a file to sort E2 on the second column. It is
5880      %% not easy to verify that this happens; the file_sorter module's
5881      %% size option cannot be set in this case. But it is not likely
5882      %% that the default size (512 KiB) will ever change, so it should
5883      %% be future safe.
5884      <<"E1 = create_ets(1, 10),
5885         E2 = create_ets(5, 150000),
5886         Q = qlc:q([{XX,YY} ||
5887                       {X,XX} <- ets:table(E1),
5888                       {YY,Y} <- ets:table(E2),
5889                       X == Y],
5890                   {join,merge}),
5891         [{5,5},{6,6},{7,7},{8,8},{9,9},{10,10}] = qlc:e(Q),
5892         ets:delete(E1),
5893         ets:delete(E2)">>
5894    ],
5895    run(Config, Bug),
5896
5897    Bits = [
5898       {otp_6562_1,
5899        <<"otp_6562_1() ->
5900               Q = qlc:q([X || <<X:8>> <= <<\"hej\">>]),
5901               qlc:info(Q).
5902        ">>,
5903        [],
5904        {errors,[{{2,40},qlc,binary_generator}],
5905         []}}
5906       ],
5907    [] = compile(Config, Bits),
5908
5909    R1 = {error,qlc,{1,qlc,binary_generator}}
5910             = qlc:string_to_handle("[X || <<X:8>> <= <<\"hej\">>]."),
5911    "1: cannot handle binary generators\n" =
5912             lists:flatten(qlc:format_error(R1)),
5913
5914    ok.
5915
5916%% OTP-6590. Bug fix (join info).
5917otp_6590(Config) when is_list(Config) ->
5918    Ts = [<<"fun(Tab1Value) ->
5919                    Q = qlc:q([T1#tab1.id || T1 <- [#tab1{id = id1,
5920                                                          value = v,
5921                                                          tab2_id = id}],
5922                                             T2 <- [#tab2{id = id}],
5923                                             T1#tab1.value =:= Tab1Value,
5924                                             T1#tab1.tab2_id =:= T2#tab2.id]),
5925                    [id1] = qlc:e(Q)
5926            end(v)">>],
5927
5928    run(Config, <<"-record(tab1, {id, tab2_id, value}).
5929                         -record(tab2, {id, value}).\n">>, Ts),
5930    ok.
5931
5932%% OTP-6673. Optimizations and fixes.
5933otp_6673(Config) when is_list(Config) ->
5934    Ts_PT =
5935        [<<"etsc(fun(E1) ->
5936                etsc(fun(E2) ->
5937                       Q = qlc:q([{A,B,C,D} ||
5938                                     {A,B} <- ets:table(E1),
5939                                     {C,D} <- ets:table(E2),
5940                                     A =:= 2, % lookup
5941                                     B =:= D, % join
5942                                     C =:= g]), % lookup invalidated by join
5943                       {qlc,_,[{generate,_,
5944                                {qlc,_,
5945                                 [{generate,_,
5946                                   {qlc,_,[{generate,_,
5947                                            {keysort,
5948                                             {list,{table,_},
5949                                              [{{'$1','$2'},[],['$_']}]},
5950                                             2,[]}},_],[]}},
5951                                  {generate,_,{qlc,_,
5952                                    [{generate,_,
5953                                      {keysort,{table,_},2,[]}}],
5954                                    []}},_],
5955                                 [{join,merge}]}},_,_],[]} = i(Q),
5956                       [{2,y,g,y}] = qlc:e(Q)
5957                     end, [{f,x},{g,y},{h,z}])
5958                 end,
5959                 [{1,x},{2,y},{3,z}])">>,
5960         <<"etsc(fun(E1) ->
5961                etsc(fun(E2) ->
5962                       Q = qlc:q([{A,B,C,D} ||
5963                                     {A,B} <- ets:table(E1),
5964                                     {C,D} <- ets:table(E2),
5965                                     A =:= 2, % lookup
5966                                     C =:= g, % lookup
5967                                     B =:= D]), % join
5968                       {qlc,_,[{generate,_,
5969                                {qlc,_,
5970                                 [{generate,_,
5971                                   {qlc,_,[{generate,_,
5972                                            {keysort,
5973                                             {list,{table,_},
5974                                              [{{'$1','$2'},[],['$_']}]},
5975                                             2,[]}},_],[]}},
5976                                  {generate,_,{qlc,_,
5977                                               [{generate,_,
5978                                                 {keysort,
5979                                                  {list,{table,_},
5980                                                   [{{'$1','$2'},[],['$_']}]},
5981                                                  2,[]}},_],[]}},_],
5982                                 [{join,merge}]}},_],[]} = i(Q),
5983                       [{2,y,g,y}] = qlc:e(Q)
5984                     end, [{f,x},{g,y},{h,z}])
5985                 end,
5986                 [{1,x},{2,y},{3,z}])">>],
5987
5988    run(Config, Ts_PT),
5989
5990    MS = ets:fun2ms(fun({X,_Y}=T) when X > 1 -> T end),
5991    Ts_RT = [
5992        [<<"%% Explicit match-spec. ets:table() ensures there is no lookup
5993            %% function, which means that lookup join will not be considered.
5994            MS = ">>, io_lib:format("~w", [MS]), <<",
5995            etsc(fun(E) ->
5996                         F = fun(J) ->
5997                                   qlc:q([{X,W} ||
5998                                             {X,_Y} <-
5999                                                 ets:table(E,{traverse,
6000                                                              {select,MS}}),
6001                                             {Z,W} <- [{1,1},{2,2},{3,3}],
6002                                             X =:= Z], {join,J})
6003                             end,
6004                         Qm = F(any),
6005                         [{2,2},{3,3}] = qlc:e(Qm),
6006                         {'EXIT',{cannot_carry_out_join,_}} =
6007                             (catch qlc:e(F(lookup)))
6008                 end, [{1,a},{2,b},{3,c}])">>],
6009
6010         <<"%% The filter 'A =< y' can be evaluated by traversing E1 using a
6011            %% match specification, but then lookup join cannot use E1 for
6012            %% looking up keys. This example shows that the filter is kept if
6013            %% lookup join is employed (otherwise it is optimized away since
6014            %% the match spec is used).
6015            etsc(fun(E1) ->
6016                         Q = qlc:q([{A,B,C,D} ||
6017                                       {A,B} <- ets:table(E1),
6018                                       {C,D} <- [{x,f},{y,g},{z,h}],
6019                                       A =< y, % kept
6020                                       A =:= C], {join,lookup}),
6021                         [{x,1,x,f},{y,2,y,g}] = lists:sort(qlc:e(Q))
6022                 end, [{x,1},{y,2},{z,3}])">>
6023
6024    ],
6025    run(Config, Ts_RT),
6026
6027    ok.
6028
6029%% OTP-6964. New option 'tmpdir_usage'.
6030otp_6964(Config) when is_list(Config) ->
6031    T1 = [
6032       <<"Q1 = qlc:q([{X} || X <- [1,2]]),
6033          {'EXIT', {badarg,_}} = (catch qlc:e(Q1, {tmpdir_usage,bad})),
6034          %% merge join
6035          F = fun(Use) ->
6036                      L1 = [{Y,a} || Y <- lists:seq(1, 2)],
6037                      L2 = [{a,Y} || Y <- lists:seq(1, 10000)],
6038                      Q = qlc:q([{XX,YY} ||
6039                                    {XX,X} <- L1,
6040                                    {Y,YY} <- L2,
6041                                    X == Y],
6042                                {join,merge}),
6043                      qlc:e(Q, [{max_list_size,64*1024},{tmpdir_usage,Use}])
6044              end,
6045          D = erlang:system_flag(backtrace_depth, 0),
6046      try
6047          20000 = length(F(allowed)),
6048          ErrReply = F(not_allowed),
6049          {error, qlc, {tmpdir_usage,joining}} = ErrReply,
6050          \"temporary file was needed for joining\n\" =
6051              lists:flatten(qlc:format_error(ErrReply)),
6052          qlc_SUITE:install_error_logger(),
6053          20000 = length(F(warning_msg)),
6054          {warning, joining} = qlc_SUITE:read_error_logger(),
6055          20000 = length(F(info_msg)),
6056          {info, joining} = qlc_SUITE:read_error_logger(),
6057          20000 = length(F(error_msg)),
6058          {error, joining} = qlc_SUITE:read_error_logger()
6059      after
6060          _ = erlang:system_flag(backtrace_depth, D)
6061      end,
6062          qlc_SUITE:uninstall_error_logger()">>],
6063    run(Config, T1),
6064
6065    T2 = [
6066       <<"%% File sorter.
6067          T = lists:seq(1, 10000),
6068          Q0 = qlc:q([{X} || X <- [T,T,T], begin X > 0 end],
6069                     [{cache,list},unique]),
6070          Q1 = qlc:q([{X,Y,Z} ||
6071                         X <- Q0,
6072                         Y <- Q0,
6073                         Z <- Q0],
6074                     [{cache,list},unique]),
6075          Q = qlc:q([{X, Y} || Y <- [1], X <- Q1]),
6076          F = fun(Use) ->
6077                      qlc:e(Q, [{max_list_size,10000},{tmpdir_usage,Use}])
6078              end,
6079          1 = length(F(allowed)),
6080          ErrReply = F(not_allowed),
6081          {error, qlc, {tmpdir_usage,caching}} = ErrReply,
6082          \"temporary file was needed for caching\n\" =
6083              lists:flatten(qlc:format_error(ErrReply)),
6084          qlc_SUITE:install_error_logger(),
6085          1 = length(F(error_msg)),
6086          {error, caching} = qlc_SUITE:read_error_logger(),
6087          {error, caching} = qlc_SUITE:read_error_logger(),
6088          1 = length(F(warning_msg)),
6089          {warning, caching} = qlc_SUITE:read_error_logger(),
6090          {warning, caching} = qlc_SUITE:read_error_logger(),
6091          1 = length(F(info_msg)),
6092          {info, caching} = qlc_SUITE:read_error_logger(),
6093          {info, caching} = qlc_SUITE:read_error_logger(),
6094          qlc_SUITE:uninstall_error_logger()">>],
6095
6096    run(Config, T2),
6097
6098    T3 = [
6099       <<"%% sort/keysort
6100          E1 = create_ets(1, 10),
6101          E2 = create_ets(5, 50000),
6102          Q = qlc:q([{XX,YY} ||
6103                        {X,XX} <- ets:table(E1),
6104                        {YY,Y} <- ets:table(E2),
6105                        X == Y],
6106                    {join,merge}),
6107          F = fun(Use) ->
6108                      qlc:e(Q, {tmpdir_usage,Use})
6109              end,
6110          ErrReply = F(not_allowed),
6111          {error,qlc,{tmpdir_usage,sorting}} = ErrReply,
6112          \"temporary file was needed for sorting\n\" =
6113              lists:flatten(qlc:format_error(ErrReply)),
6114          qlc_SUITE:install_error_logger(),
6115          L = [{5,5},{6,6},{7,7},{8,8},{9,9},{10,10}],
6116          L = F(allowed),
6117          L = F(error_msg),
6118          {error, sorting} = qlc_SUITE:read_error_logger(),
6119          L = F(info_msg),
6120          {info, sorting} = qlc_SUITE:read_error_logger(),
6121          L = F(warning_msg),
6122          {warning, sorting} = qlc_SUITE:read_error_logger(),
6123          qlc_SUITE:uninstall_error_logger(),
6124          ets:delete(E1),
6125          ets:delete(E2)">>],
6126    run(Config, T3),
6127
6128    T4 = [
6129       <<"%% cache list
6130          etsc(fun(E) ->
6131                       Q0 = qlc:q([X || X <- ets:table(E),
6132                                        begin element(1, X) > 5 end],
6133                                  {cache,list}),
6134                       Q = qlc:q([{X, element(1,Y)} || X <- lists:seq(1, 5),
6135                                                       Y <- Q0]),
6136                       R = [{X,Y} || X <- lists:seq(1, 5),
6137                                     Y <- lists:seq(6, 10)],
6138                       F = fun(Use) ->
6139                                   qlc:e(Q, [{max_list_size, 100*1024},
6140                                             {tmpdir_usage, Use}])
6141                           end,
6142                       R = lists:sort(F(allowed)),
6143                       qlc_SUITE:install_error_logger(),
6144                       R = lists:sort(F(info_msg)),
6145                       {info, caching} = qlc_SUITE:read_error_logger(),
6146                       R = lists:sort(F(error_msg)),
6147                       {error, caching} = qlc_SUITE:read_error_logger(),
6148                       R = lists:sort(F(warning_msg)),
6149                       {warning, caching} = qlc_SUITE:read_error_logger(),
6150                       qlc_SUITE:uninstall_error_logger(),
6151                       ErrReply = F(not_allowed),
6152                       {error,qlc,{tmpdir_usage,caching}} = ErrReply,
6153                       \"temporary file was needed for caching\n\" =
6154                           lists:flatten(qlc:format_error(ErrReply))
6155               end, [{keypos,1}], [{I,a,lists:duplicate(100000,1)} ||
6156                                       I <- lists:seq(1, 10)])">>],
6157    run(Config, T4),
6158    ok.
6159
6160%% OTP-7238. info-option 'depth', &c.
6161otp_7238(Config) when is_list(Config) ->
6162    dets:start(),
6163    T = otp_7238,
6164    Fname = filename(T, Config),
6165
6166    ok = compile_gb_table(Config),
6167
6168    %% A few more warnings.
6169    T1 = [
6170       %% The same error message string, but with different tags
6171       %% (the strings are not compared :-(
6172       {nomatch_1,
6173        <<"nomatch_1() ->
6174               {qlc:q([X || X={X} <- []]), [t || \"a\"=\"b\" <- []]}.">>,
6175        [],
6176        %% {warnings,[{{2,30},qlc,nomatch_pattern},
6177        {warnings,[{{2,44},v3_core,{nomatch,pattern}}]}},
6178
6179       %% Not found by qlc...
6180       {nomatch_2,
6181        <<"nomatch_2() ->
6182               qlc:q([t || {\"a\"++\"b\"} = {\"ac\"} <- []]).">>,
6183        [],
6184        {warnings,[{{2,22},v3_core,{nomatch,pattern}}]}},
6185
6186       {nomatch_3,
6187        <<"nomatch_3() ->
6188               qlc:q([t || [$a, $b] = \"ba\" <- []]).">>,
6189        [],
6190        %% {warnings,[{{2,37},qlc,nomatch_pattern}]}},
6191        {warnings,[{{2,22},v3_core,{nomatch,pattern}}]}},
6192
6193       %% Not found by qlc...
6194       {nomatch_4,
6195        <<"nomatch_4() ->
6196               qlc:q([t || \"a\"++_=\"b\" <- []]).">>,
6197        [],
6198        {warnings,[{{2,22},v3_core,{nomatch,pattern}}]}},
6199
6200       %% Found neither by the compiler nor by qlc...
6201       {nomatch_5,
6202        <<"nomatch_5() ->
6203               qlc:q([X || X = <<X>> <- [3]]).">>,
6204        [],
6205        []},
6206
6207       {nomatch_6,
6208        <<"nomatch_6() ->
6209               qlc:q([X || X <- [],
6210                           X =:= {X}]).">>,
6211        [],
6212        %% {warnings,[{{3,30},qlc,nomatch_filter}]}},
6213        []},
6214
6215       {nomatch_7,
6216        <<"nomatch_7() ->
6217               qlc:q([X || {X=Y,{Y}=X} <- []]).">>,
6218        [],
6219        %% {warnings,[{{2,28},qlc,nomatch_pattern}]}},
6220        []},
6221
6222       {nomatch_8,
6223        <<"nomatch_8() ->
6224               qlc:q([X || {X={},X=[]} <- []]).">>,
6225        [],
6226        %% {warnings,[{{2,28},qlc,nomatch_pattern}]}},
6227        []},
6228
6229       {nomatch_9,
6230        <<"nomatch_9() ->
6231               qlc:q([X || X <- [], X =:= {}, X =:= []]).">>,
6232        [],
6233        %% {warnings,[{{2,49},qlc,nomatch_filter}]}},
6234        []},
6235
6236       {nomatch_10,
6237        <<"nomatch_10() ->
6238               qlc:q([X || X <- [],
6239                           ((X =:= 1) or (X =:= 2)) and (X =:= 3)]).">>,
6240        [],
6241        %% {warnings,[{{3,53},qlc,nomatch_filter}]}},
6242        []},
6243
6244       {nomatch_11,
6245        <<"nomatch_11() ->
6246               qlc:q([X || X <- [], x =:= []]).">>,
6247        [],
6248        %% {warnings,[{{2,39},qlc,nomatch_filter}]}},
6249        {warnings,[{{2,22},sys_core_fold,{nomatch,guard}}]}},
6250
6251       {nomatch_12,
6252        <<"nomatch_12() ->
6253               qlc:q([X || X={} <- [], X =:= []]).">>,
6254        [],
6255        %% {warnings,[{{2,42},qlc,nomatch_filter}]}},
6256        []},
6257
6258       {nomatch_13,
6259        <<"nomatch_13() ->
6260               qlc:q([Z || Z <- [],
6261                           X={X} <- [],
6262                           Y={Y} <- []]).">>,
6263        [],
6264        %% {warnings,[{{3,29},qlc,nomatch_pattern},
6265        %%            {{4,29},qlc,nomatch_pattern}]}},
6266        []},
6267
6268       {nomatch_14,
6269        <<"nomatch_14() ->
6270               qlc:q([X || X={X} <- [],
6271                           1 > 0,
6272                           1 > X]).">>,
6273        [],
6274        %% {warnings,[{{2,29},qlc,nomatch_pattern}]}},
6275        []},
6276
6277       {nomatch_15,
6278        <<"nomatch_15() ->
6279              qlc:q([{X,Y} || X={X} <- [1],
6280                              Y <- [1],
6281                              1 > 0,
6282                              1 > X]).">>,
6283        [],
6284        %% {warnings,[{{2,32},qlc,nomatch_pattern}]}},
6285        []},
6286
6287       %% Template warning.
6288       {nomatch_template1,
6289        <<"nomatch_template1() ->
6290               qlc:q([{X} = {} || X <- []]).">>,
6291        [],
6292        {warnings,[{{2,23},sys_core_fold,{nomatch,no_clause}}]}}
6293         ],
6294    [] = compile(Config, T1),
6295
6296    %% 'depth' is a new option used by info()
6297    T2 = [
6298       %% Firstly: lists
6299       <<"L = [[a,b,c],{a,b,c},[],<<\"foobar\">>],
6300          Q = qlc:q([{X} || X <- L]),
6301          {call, _,
6302           {remote,_,{atom,_,ets},{atom,_,match_spec_run}},
6303           [{cons,_,{atom,_,'...'},
6304             {cons,_,{atom,_,'...'},
6305              {cons,_,{nil,_},{cons,_,{atom,_,'...'},{nil,_}}}}},
6306            _]} = qlc:info(Q, [{format,abstract_code},{depth,0}]),
6307
6308          {call,_,_,
6309           [{cons,_,{cons,_,{atom,_,'...'},{nil,_}},
6310             {cons,_,
6311              {tuple,_,[{atom,_,'...'}]},
6312              {cons,_,{nil,_},
6313               {cons,_,
6314                {bin,_,
6315                 [{_,_,{_,_,$.},_,_},
6316                  {_,_,{_,_,$.},_,_},
6317                  {_,_,{_,_,$.},_,_}]},
6318                {nil,_}}}}},
6319            _]} = qlc:info(Q, [{format,abstract_code},{depth,1}]),
6320
6321          {call,_,
6322           _,
6323          [{cons,_,{cons,_,{atom,_,a},{atom,_,'...'}},
6324            {cons,_,
6325             {tuple,_,[{atom,_,a},{atom,_,'...'}]},
6326             {cons,_,{nil,_},
6327              {cons,_,
6328               {bin,_,
6329                [{_,_,{_,_,$f},_,_},
6330                 {_,_,{_,_,$.},_,_},
6331                 {_,_,{_,_,$.},_,_},
6332                 {_,_,{_,_,$.},_,_}]},
6333               {nil,_}}}}},
6334          _]} = qlc:info(Q, [{format,abstract_code},{depth,2}]),
6335
6336          {call,_,_,
6337           [{cons,_,
6338             {cons,_,{atom,_,a},{cons,_,{atom,_,b},{atom,_,'...'}}},
6339             {cons,_,
6340              {tuple,_,[{atom,_,a},{atom,_,b},{atom,_,'...'}]},
6341              {cons,_,{nil,_},
6342               {cons,_,
6343                {bin,_,
6344                 [{_,_,{_,_,$f},_,_},
6345                  {_,_,{_,_,$o},_,_},_,_,_]},
6346                {nil,_}}}}},
6347            _]} = qlc:info(Q, [{format,abstract_code},{depth,3}]),
6348
6349          {call,_,_,
6350           [{cons,_,
6351             {cons,_,
6352              {atom,_,a},{cons,_,{atom,_,b},{cons,_,{atom,_,c},{nil,_}}}},
6353             {cons,_,
6354              {tuple,_,[{atom,_,a},{atom,_,b},{atom,_,c}]},
6355              {cons,_,{nil,_},
6356               {cons,_,
6357                {bin,_,
6358                 [{_,_,{_,_,$f},_,_},
6359                  {_,_,{_,_,$o},_,_},
6360                  {_,_,{_,_,$o},_,_},
6361                  {_,_,{_,_,$b},_,_},
6362                  {_,_,{_,_,$a},_,_},
6363                  {_,_,{_,_,$r},_,_}]},
6364                {nil,_}}}}},
6365            _]} = qlc:info(Q, [{format,abstract_code},{depth,10}]),
6366
6367          {call,_,_,
6368           [{cons,_,
6369             {cons,_,
6370              {atom,_,a},{cons,_,{atom,_,b},{cons,_,{atom,_,c},{nil,_}}}},
6371             {cons,_,
6372              {tuple,_,[{atom,_,a},{atom,_,b},{atom,_,c}]},
6373              {cons,_,{nil,_},
6374               {cons,_,
6375                {bin,_,
6376                 [{_,_,{_,_,$f},_,_},
6377                  {_,_,{_,_,$o},_,_},
6378                  {_,_,{_,_,$o},_,_},
6379                  {_,_,{_,_,$b},_,_},
6380                  {_,_,{_,_,$a},_,_},
6381                  {_,_,{_,_,$r},_,_}]},
6382                {nil,_}}}}},
6383            _]} = qlc:info(Q, [{format,abstract_code},{depth,infinity}])">>,
6384
6385       %% Secondly: looked up keys
6386       <<"F = fun(D) ->
6387                etsc(fun(E) ->
6388                       Q = qlc:q([C || {N,C} <- ets:table(E),
6389                                       (N =:= {2,2}) or (N =:= {3,3})]),
6390                       F = qlc:info(Q, [{format,abstract_code},{depth,D}]),
6391                       {call,_,_,[{call,_,_,[_Fun,Values]},_]} = F,
6392                       [b,c] = lists:sort(qlc:eval(Q)),
6393                       Values
6394                     end, [{{1,1},a},{{2,2},b},{{3,3},c},{{4,4},d}])
6395              end,
6396
6397          [{cons,_,{atom,_,'...'},{cons,_,{atom,_,'...'},{nil,_}}},
6398           {cons,_,
6399            {tuple,_,[{atom,_,'...'}]},
6400            {cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}},
6401           {cons,_,
6402            {tuple,_,[{integer,_,2},{atom,_,'...'}]},
6403            {cons,_,{tuple,_,[{integer,_,3},{atom,_,'...'}]},{nil,_}}},
6404           {cons,_,
6405            {tuple,_,[{integer,_,2},{integer,_,2}]},
6406            {cons,_,{tuple,_,[{integer,_,3},{integer,_,3}]},{nil,_}}},
6407           {cons,_,
6408            {tuple,_,[{integer,_,2},{integer,_,2}]},
6409            {cons,_,{tuple,_,[{integer,_,3},{integer,_,3}]},{nil,_}}}] =
6410              lists:map(F, [0,1,2,3,infinity])">>,
6411       [<<"T = otp_7238, Fname = \"">>, Fname, <<"\",
6412           {ok, _} = dets:open_file(T, [{file,Fname}]),
6413           ok = dets:insert(T, [{{1,1},a},{{2,2},b},{{3,3},c},{{4,4},d}]),
6414           Q = qlc:q([C || {N,C} <- dets:table(T),
6415                           (N =:= {2,2}) or (N =:= {3,3})]),
6416           F = qlc:info(Q, [{format,abstract_code},{depth,1}]),
6417           [b,c] = lists:sort(qlc:eval(Q)),
6418           {call,_,_,
6419            [{call,_,_,
6420              [_,
6421               {cons,_,
6422                {tuple,_,[{atom,_,'...'}]},
6423                {cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}}]},
6424             _]} = F,
6425           ok = dets:close(T),
6426           file:delete(\"">>, Fname, <<"\")">>],
6427
6428       %% Thirdly: format_fun has been extended (in particular: gb_table)
6429       <<"T = gb_trees:from_orddict([{{1,a},w},{{2,b},v},{{3,c},u}]),
6430          QH = qlc:q([X || {{X,Y},_} <- gb_table:table(T),
6431                           ((X =:= 1) or (X =:= 2)),
6432                           ((Y =:= a) or (Y =:= b) or (Y =:= c))]),
6433          {call,_,_,
6434           [{call,_,_,
6435             [{'fun',_,
6436               {clauses,
6437                [{clause,_,_,[],
6438                  [{'case',_,
6439                    {call,_,_,
6440                     [_,
6441                      {call,_,_,
6442                       [{cons,_,
6443                         {tuple,_,[{atom,_,'...'}]},
6444                         {cons,_,
6445                          {tuple,_,[{atom,_,'...'}]},
6446                          {cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}}}]}]},
6447                    [_,_]}]}]}},
6448              {cons,_,
6449               {tuple,_,[{atom,_,'...'}]},
6450               {cons,_,
6451                {tuple,_,[{atom,_,'...'}]},
6452                {cons,_,
6453                 {tuple,_,[{atom,_,'...'}]},
6454                 {cons,_,
6455                  {tuple,_,[{atom,_,'...'}]},
6456                  {cons,_,
6457                   {tuple,_,[{atom,_,'...'}]},
6458                   {cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}}}}}}]},
6459            {call,_,_,
6460             [{cons,_,{tuple,_,[{atom,_,'...'}]},{nil,_}}]}]} =
6461            qlc:info(QH, [{format,abstract_code},{depth,1}])">>,
6462       <<"T1 = [{1,1,a},{2,2,b},{3,3,c},{4,4,d}],
6463          T2 = [{x,1},{y,1},{z,2}],
6464          QH1 = T1,
6465          T = gb_trees:from_orddict(T2),
6466          QH2 = qlc:q([X || {_,X} <- gb_table:table(T)], cache),
6467          Q = qlc:q([{X1,X2,X3} || {X1,X2,X3} <- QH1,
6468                                   Y2 <- QH2,
6469                                   X2 =:= Y2]),
6470          {block,_,
6471           [{match,_,_,
6472             {call,_,_,
6473              [{lc,_,_,
6474                [{generate,_,_,
6475                  {call,_,_,
6476                   [{call,_,_,
6477                     [{cons,_,
6478                       {tuple,_,[{atom,_,'...'}]},
6479                       {atom,_,'...'}}]}]}}]},
6480               _]}},
6481            {call,_,_,
6482             [{lc,_,_,
6483               [{generate,_,_,
6484                 {cons,_,{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}}},
6485                _,_]}]}]} =
6486              qlc:info(Q, [{format,abstract_code},{depth, 1},
6487                           {n_elements,1}])">>,
6488       <<"L = [{{key,1},a},{{key,2},b},{{key,3},c}],
6489          T = gb_trees:from_orddict(orddict:from_list(L)),
6490          Q = qlc:q([K || {K,_} <- gb_table:table(T),
6491                                   (K =:= {key,1}) or (K =:= {key,2})]),
6492{call,_,_,
6493 [{call,_,_,
6494   [{'fun',_,
6495     {clauses,
6496      [{clause,_,_,[],
6497        [{'case',_,
6498          {call,_,_,
6499           [_,
6500            {call,_,_,
6501             [{cons,_,
6502               {tuple,_,[{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}]},
6503               {cons,_,
6504                {tuple,_,[{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}]},
6505                {cons,_,
6506                 {tuple,_,[{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}]},
6507                 {nil,_}}}}]}]},
6508          _}]}]}},
6509    {cons,_,
6510     {tuple,_,[{atom,_,key},{atom,_,'...'}]},
6511     {cons,_,{tuple,_,[{atom,_,key},{atom,_,'...'}]},{nil,_}}}]},
6512  {call,_,
6513   {remote,_,{atom,_,ets},{atom,_,match_spec_compile}},
6514   [{cons,_,
6515     {tuple,_,[{tuple,_,[{atom,_,'...'}]},{atom,_,'...'}]},
6516     {nil,_}}]}]} =
6517          qlc:info(Q, [{format,abstract_code},{depth, 2}])">>
6518
6519         ],
6520    run(Config, T2),
6521
6522    T3 = [
6523%%        {nomatch_6,
6524%%         <<"nomatch_6() ->
6525%%                qlc:q([X || X <- [],
6526%%                            X =:= {X}]).">>,
6527%%         [],
6528%%         {[],["filter evaluates to 'false'"]}},
6529
6530%%        {nomatch_7,
6531%%         <<"nomatch_7() ->
6532%%                qlc:q([X || {X=Y,{Y}=X} <- []]).">>,
6533%%         [],
6534%%         {[],["pattern cannot possibly match"]}}
6535       ],
6536    compile_format(Config, T3),
6537
6538    %% *Very* simple test - just check that it doesn't crash.
6539    Type = [{cres,
6540             <<"Q = qlc:q([X || {X} <- []]),
6541                {'EXIT',{{badfun,_},_}} = (catch qlc:e(Q))">>,
6542             [type_checker],
6543             []}],
6544    run(Config, Type),
6545
6546    ok.
6547
6548%% OTP-7114. Match spec, table and duplicated objects...
6549otp_7114(Config) when is_list(Config) ->
6550    Ts = [<<"T = ets:new(t, [bag]),
6551             [ets:insert(T, {t, I, I div 2}) || I <- lists:seq(1,10)],
6552             Q1 = qlc:q([element(3, E) || E <- ets:table(T)]),
6553             [0,1,1,2,2,3,3,4,4,5] = lists:sort(qlc:e(Q1)),
6554             [0,1,2,3,4,5] = qlc:e(Q1, unique_all),
6555             [0,1,2,3,4,5] = qlc:e(qlc:sort(Q1), unique_all),
6556             [0,1,2,3,4,5] = qlc:e(qlc:sort(qlc:e(Q1)), unique_all),
6557             ets:delete(T),
6558             ok">>],
6559    run(Config, Ts).
6560
6561%% OTP-7232. qlc:info() bug (pids, ports, refs, funs).
6562otp_7232(Config) when is_list(Config) ->
6563    Ts = [<<"L = [fun math:sqrt/1, list_to_pid(\"<0.4.1>\"),
6564                  erlang:make_ref()],
6565             \"[fun math:sqrt/1, <0.4.1>, #Ref<\" ++ _  = qlc:info(L),
6566             {call,_,
6567               {remote,_,{atom,_,qlc},{atom,_,sort}},
6568               [{cons,_,
6569                      {'fun',_,{function,{atom,_,math},{atom,_,sqrt},_}},
6570                      {cons,_,
6571                            {string,_,\"<0.4.1>\"}, % could use list_to_pid..
6572                            {cons,_,{string,_,\"#Ref<\"++_},{nil,_}}}},
6573                {nil,_}]} =
6574              qlc:info(qlc:sort(L),{format,abstract_code})">>,
6575
6576          <<"Q1 = qlc:q([X || X <- [55296,56296]]),
6577             Q = qlc:sort(Q1, {order, fun(A,B)-> A>B end}),
6578             \"qlc:sort([55296,56296],[{order,fun'-function/0-fun-2-'/2}])\" =
6579                format_info(Q, true),
6580             AC = qlc:info(Q, {format, abstract_code}),
6581             \"qlc:sort([55296, 56296], [{order, fun '-function/0-fun-2-'/2}])\" =
6582                binary_to_list(iolist_to_binary(erl_pp:expr(AC)))">>,
6583
6584         %% OTP-7234. erl_parse:abstract() handles bit strings
6585          <<"Q = qlc:sort([<<17:9>>]),
6586             \"[<<8,1:1>>]\" = qlc:info(Q)">>
6587
6588         ],
6589    run(Config, Ts).
6590
6591%% OTP-7552. Merge join bug.
6592otp_7552(Config) when is_list(Config) ->
6593    %% The poor performance cannot be observed unless the
6594    %% (redundant) join filter is skipped.
6595    Ts = [<<"Few = lists:seq(1, 2),
6596             Many = lists:seq(1, 10),
6597             S = [d,e],
6598             L1 = [{Y,a} || Y <- Few] ++ [{'1b',b},{2,b}] ++
6599                    [{Y,X} || X <- S, Y <- Few],
6600             L2 = [{a,Y} || Y <- Many] ++
6601                    [{b,'1b'}] ++ [{c,1}] ++
6602                    [{X,Y} || X <- S, Y <- Many],
6603                   F = fun(J) ->
6604                               qlc:q([{XX,YY} ||
6605                                         {XX,X} <- L1,
6606                                         {Y,YY} <- L2,
6607                                         X == Y],
6608                                     {join,J})
6609                       end,
6610                   Qm = F(merge),
6611                   Qn = F(nested_loop),
6612                   true = lists:sort(qlc:e(Qm, {max_list_size,20})) =:=
6613                          lists:sort(qlc:e(Qn))">>],
6614    run(Config, Ts).
6615
6616%% OTP-7714. Merge join bug.
6617otp_7714(Config) when is_list(Config) ->
6618    %% The original example uses Mnesia. This one does not.
6619    Ts = [<<"E1 = ets:new(set,[]),
6620             true = ets:insert(E1, {a,1}),
6621             E2 = ets:new(set,[]),
6622             _ = [true = ets:insert(E2, {I, 1}) ||
6623                     I <- lists:seq(1, 3)],
6624             Q = qlc:q([{A,B} ||
6625                           {A,I1} <- ets:table(E1),
6626                           {B,I2} <- ets:table(E2),
6627                           I1 =:= I2],{join,merge}),
6628             [{a,1},{a,2},{a,3}] = lists:sort(qlc:e(Q)),
6629             ets:delete(E1),
6630             ets:delete(E2)">>],
6631    run(Config, Ts).
6632
6633%% OTP-11758. Bug.
6634otp_11758(Config) when is_list(Config) ->
6635    Ts = [<<"T = ets:new(r, [{keypos, 2}]),
6636             L = [{rrr, xxx, aaa}, {rrr, yyy, bbb}],
6637             true = ets:insert(T, L),
6638             QH = qlc:q([{rrr, B, C} || {rrr, B, C} <- ets:table(T),
6639                              (B =:= xxx) or (B =:= yyy) and (C =:= aaa)]),
6640             [{rrr,xxx,aaa}] = qlc:e(QH),
6641             ets:delete(T)">>],
6642    run(Config, Ts).
6643
6644%% OTP-6674. match/comparison.
6645otp_6674(Config) when is_list(Config) ->
6646
6647    ok = compile_gb_table(Config),
6648
6649    Ts = [%% lookup join
6650          <<"E = ets:new(join, [ordered_set]),
6651             true = ets:insert(E, [{1,a},{2,b},{3,c}]),
6652             Q = qlc:q([{X, Y} || {X,_} <- ets:table(E),
6653                                  {Y} <- [{0},{1},{2}],
6654                                  X == Y]),
6655             {0,1,0,0} = join_info(Q),
6656             [{1,1},{2,2}] = qlc:e(Q),
6657             ets:delete(E)">>,
6658
6659          <<"E = ets:new(join, [ordered_set]),
6660             true = ets:insert(E, [{1,a},{2,b},{3,c}]),
6661             Q = qlc:q([{X, Y} || {X,_} <- ets:table(E),
6662                                  {Y} <- [{0},{1},{2}],
6663                                  X =:= Y]),
6664             {0,1,0,0} = join_info(Q),
6665             {block,_,
6666              [_,
6667               {match,_,_,
6668                 {call,_,_,
6669                  [{lc,_,_,
6670                    [_,_,{op,_,'==',_,_}]},
6671                   {cons,_,
6672                    {tuple,_,[{atom,_,join},{atom,_,lookup}]},_}]}},
6673               _]} = qlc:info(Q, {format, abstract_code}),
6674             [{1,1},{2,2}] = qlc:e(Q),
6675             ets:delete(E)">>,
6676
6677       <<"E = ets:new(join, [set]),
6678          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E),
6679                               {Y} <- [{0},{1},{2}],
6680                               X == Y], {join, lookup}),
6681          {'EXIT',{cannot_carry_out_join,_}} = (catch qlc:e(Q)),
6682          ets:delete(E)">>,
6683
6684       %% Lookup join possible in both directions.
6685       <<"E1 = ets:new(join, [ordered_set]),
6686          E2 = ets:new(join, [set]),
6687          true = ets:insert(E1, [{1.0,a},{2,b},{3,c}]),
6688          true = ets:insert(E2, [{0},{1},{2}]),
6689          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E1),
6690                               {Y} <- ets:table(E2),
6691                               X == Y],{join,lookup}), % skipped
6692          {qlc,_,
6693            [{generate,_,
6694                 {qlc,_,
6695                     [{generate,_,
6696                          {qlc,_,[{generate,_,{table,{ets,table,[_]}}}],[]}},
6697                      {generate,_,{table,{ets,table,[_]}}},
6698                      _],
6699                     [{join,lookup}]}}],
6700            []} = qlc:info(Q, {format,debug}),
6701          {0,1,0,0} = join_info(Q),
6702          [{1.0,1},{2,2}] = lists:sort(qlc:e(Q)),
6703          ets:delete(E1),
6704          ets:delete(E2)">>,
6705       <<"E1 = ets:new(join, [ordered_set]),
6706          E2 = ets:new(join, [set]),
6707          true = ets:insert(E1, [{1.0,a},{2,b},{3,c}]),
6708          true = ets:insert(E2, [{0},{1},{2}]),
6709          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E1),
6710                               {Y} <- ets:table(E2),
6711                               X =:= Y],{join,merge}), % not skipped
6712          {1,0,0,1} = join_info(Q),
6713          [{2,2}] = qlc:e(Q),
6714          ets:delete(E1),
6715          ets:delete(E2)">>,
6716       <<"E1 = ets:new(join, [ordered_set]),
6717          E2 = ets:new(join, [set]),
6718          true = ets:insert(E1, [{1.0,a},{2,b},{3,c}]),
6719          true = ets:insert(E2, [{0},{1},{2}]),
6720          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E1),
6721                               {Y} <- ets:table(E2),
6722                               X =:= Y],{join,lookup}), % skipped
6723          {qlc,_,
6724           [{generate,_,
6725             {qlc,_,
6726              [{generate,_,
6727                {qlc,_,
6728                 [{generate,_,{table,{ets,table,[_]}}}],
6729                 []}},
6730               {generate,_,{table,{ets,table,[_]}}},
6731               _],
6732              [{join,lookup}]}}],
6733            []} = qlc:info(Q, {format,debug}),
6734          {0,1,0,0} = join_info(Q),
6735          [{2,2}] = qlc:e(Q),
6736          ets:delete(E1),
6737          ets:delete(E2)">>,
6738       <<"E1 = ets:new(join, [ordered_set]),
6739          E2 = ets:new(join, [set]),
6740          true = ets:insert(E1, [{1.0,a},{2,b},{3,c}]),
6741          true = ets:insert(E2, [{0},{1},{2}]),
6742          Q = qlc:q([{X, Y} || {X,_} <- ets:table(E1),
6743                               {Y} <- ets:table(E2),
6744                               %% Independent of term comparison:
6745                               X =:= Y, X == Y]),
6746          {0,1,0,0} = join_info(Q),
6747          [{2,2}] = qlc:e(Q),
6748          ets:delete(E1),
6749          ets:delete(E2)">>,
6750
6751       <<"E = ets:new(join, [ordered_set]),
6752          true = ets:insert(E, [{1,1},{2,2},{3,c}]),
6753          Q = qlc:q([{X, Y} || {X,Z} <- ets:table(E),
6754                               {Y} <- [{0},{1},{2}],
6755                               X == Z, Y == Z]), % cannot skip (yet)
6756          {qlc,_,
6757            [{generate,_,
6758                 {qlc,_,[_,_,_],[{join,lookup}]}},
6759             _,_],[]} = qlc:info(Q,{format,debug}),
6760          {0,1,0,0} = join_info(Q),
6761          [{1,1},{2,2}] = qlc:e(Q),
6762          ets:delete(E)">>,
6763
6764       %% The following moved here from skip_filters. It was buggy!
6765       <<"etsc(fun(E) ->
6766                 A = 3,
6767                 Q = qlc:q([X || X <- ets:table(E),
6768                                 A == element(1,X)]),
6769                 {table, _} = i(Q),
6770                 case qlc:e(Q) of
6771                       [{3},{3.0}] -> ok;
6772                       [{3.0},{3}] -> ok
6773                 end,
6774                 false = lookup_keys(Q)
6775         end, [{3},{3.0},{c}])">>,
6776    <<"H1 = qlc:sort([{{192,192.0},1,a},{{192.0,192.0},2,b},{{192,192.0},3,c}]),
6777       Q = qlc:q([{X, Y} || {{A,B},X,_} <- H1, % does not need keysort(3)
6778                            A == 192, B =:= 192.0,
6779                            {Y} <- [{0},{1},{2}],
6780                            X == Y]),
6781       A0 = erl_anno:new(0),
6782       {block,A0,
6783         [{match,_,_,
6784           {call,_,_,
6785            [{lc,_,_,
6786              [_,
6787               %% Has to compare extra constant:
6788               {op,_,'==',
6789                {tuple,_,[{integer,_,192},{float,_,192.0}]},
6790                {call,_,{atom,_,element},[{integer,_,1},{var,_,'P0'}]}}]}]}},
6791          _,_,
6792          {call,_,_,
6793           [{lc,_,_,
6794             [_,
6795              %% The join filter has been skipped.
6796              {op,_,'==',{var,_,'A'},{integer,_,192}},
6797              {op,_,'=:=',{var,_,'B'},{float,_,192.0}}]}]}]}
6798      = qlc:info(Q, {format,abstract_code}),
6799       {1,0,0,1} = join_info(Q),
6800       [{1,1},{2,2}] = qlc:e(Q)">>,
6801
6802    %% Does not handle more than one lookup value (conjunctive).
6803    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6804       H = qlc:q([X || {X,_} <- gb_table:table(T),
6805                                X =:= 1 andalso X == 1.0]),
6806       false = lookup_keys(H),
6807       [1] = qlc:e(H)">>,
6808
6809    %% EqualConstants...
6810    <<"etsc(fun(E) ->
6811                Q = qlc:q([{X,Y} || {X} <- ets:table(E),
6812                                {Y} <- [{{1}},{{2}},{{1.0}},{{2.0}}],
6813                                X =:= {1}, X == {1.0},
6814                                X == Y], {join, merge}),
6815                [{{1},{1}},{{1},{1.0}}] = lists:sort(qlc:e(Q)),
6816                false = lookup_keys(Q)
6817         end, [{{1}}, {{2}}])">>,
6818
6819    <<"T = gb_trees:from_orddict([{foo,{1}}, {bar,{2}}]),
6820       Q = qlc:q([{X,Y} || {_,X} <- gb_table:table(T),
6821                       {Y} <- [{{1}},{{2}},{{1.0}},{{2.0}}],
6822                         (X =:= {1}) or (X == {2}),
6823                         (X == {1.0}) or (X =:= {2.0}),
6824                       X == Y], {join, merge}),
6825       [{{1},{1}},{{1},{1.0}}] = qlc:e(Q)">>,
6826
6827    %% Compare key
6828    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6829       H = qlc:q([X || {X,_} <- gb_table:table(T),
6830                       X == 1]),
6831       [1] = lookup_keys(H),
6832       [1] = qlc:e(H)">>,
6833    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6834       H = qlc:q([X || {X,_} <- gb_table:table(T),
6835                       X == 1.0]),
6836       [1.0] = lookup_keys(H), % this is how gb_table works...
6837       [1.0] = qlc:e(H)">>,
6838    <<"etsc(fun(E) ->
6839                   H = qlc:q([X || {X,_} <- ets:table(E),
6840                                   X == 1.0]),
6841                   [1] = qlc:e(H), % and this is how ETS works.
6842                   [1.0] = lookup_keys(H)
6843           end, [ordered_set], [{1,a},{2,b}])">>,
6844
6845    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6846       H = qlc:q([X || {X,_} <- gb_table:table(T),
6847                       X =:= 2]),
6848       [2] = lookup_keys(H),
6849       %% Cannot (generally) remove the matching filter (the table
6850       %% compares the key). But note that gb_table returns the given
6851       %% term as key, so in this case the filter _could_ have been removed.
6852       %% However, there is no callback to inform qlc about that.
6853       {call,_,_,
6854             [_,{call,_,_,
6855               [{cons,_,{tuple,_,
6856                  [_,{cons,_,
6857                    {tuple,_,[{atom,_,'=:='},{atom,_,'$1'},{integer,_,2}]},
6858                    _},_]},_}]}]} =  qlc:info(H, {format,abstract_code}),
6859       [2] = qlc:e(H)">>,
6860    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6861       H = qlc:q([X || {X,_} <- gb_table:table(T),
6862                       X =:= 2.0]),
6863       %% Just shows that the term (not the key) is returned.
6864       [2.0] = lookup_keys(H),
6865       [2.0] = qlc:e(H)">>,
6866
6867    <<"I = 1,
6868       T = gb_trees:from_orddict([{1,a},{2,b}]),
6869       H = qlc:q([X || {X,_} <- gb_table:table(T),
6870                       X == I]), % imported variable
6871       [1] = lookup_keys(H),
6872       {call,_,_,
6873             [_,{call,_,_,
6874               [{cons,_,
6875                 {tuple,_,
6876                  [{tuple,_,[{atom,_,'$1'},{atom,_,'_'}]},
6877                   {nil,_}, % the filter has been skipped
6878                   {cons,_,{atom,_,'$1'},_}]},
6879                 _}]}]} = qlc:info(H, {format, abstract_code}),
6880       [1] = qlc:e(H)">>,
6881    <<"I = 2,
6882       T = gb_trees:from_orddict([{1,a},{2,b}]),
6883       H = qlc:q([X || {X,_} <- gb_table:table(T),
6884                       X =:= I]),
6885       [2] = lookup_keys(H),
6886       {call,_,_,
6887            [_,{call,_,_,
6888              [{cons,_,{tuple,_,
6889                 [_,{cons,_,
6890                   {tuple,_,
6891                    [{atom,_,'=:='},
6892                     {atom,_,'$1'},
6893                     {tuple,_,[{atom,_,const},{integer,_,2}]}]},
6894                   _},_]},
6895                _}]}]} = qlc:info(H, {format, abstract_code}),
6896          [2] = qlc:e(H)">>,
6897
6898    <<"etsc(fun(E) ->
6899                 Q = qlc:q([X || {X,_} <- ets:table(E),
6900                                 X =:= a]), % skipped
6901                 [a] = qlc:e(Q),
6902                 {list,{table,_},_} = i(Q),
6903                 [a] = lookup_keys(Q)
6904            end, [ordered_set], [{a,1},{b,2},{3,c}])">>,
6905
6906    %% Does not find that if for instance X =:= {1} then the filter
6907    %% X == {1} can be removed.
6908    <<"etsc(fun(E) ->
6909                Q = qlc:q([X || {X} <- ets:table(E),
6910                                X =:= {1}, X == {1.0}]),
6911                [{1}] = qlc:e(Q),
6912                [{1}] = lookup_keys(Q)
6913         end, [{{1}}, {{2}}])">>,
6914    <<"etsc(fun(E) ->
6915                Q = qlc:q([X || {X} <- ets:table(E),
6916                                X =:= {1}, X == {1.0}]),
6917                [{1}] = qlc:e(Q),
6918                false = lookup_keys(Q)
6919         end, [ordered_set], [{{1}}, {{2}}])">>,
6920    <<"etsc(fun(E) ->
6921                Q = qlc:q([X || {X} <- ets:table(E),
6922                                X == {1.0}, X =:= {1}]),
6923                [{1}] = qlc:e(Q),
6924                [{1}] = lookup_keys(Q)
6925         end, [{{1}}, {{2}}])">>,
6926    <<"etsc(fun(E) ->
6927                Q = qlc:q([X || {X} <- ets:table(E),
6928                                X == {1.0}, X =:= {1}]),
6929                [{1}] = qlc:e(Q),
6930                false = lookup_keys(Q)
6931         end, [ordered_set], [{{1}}, {{2}}])">>,
6932
6933    <<"E = ets:new(apa, []),
6934       true = ets:insert(E, [{1,a},{2,b}]),
6935       {'EXIT', {badarg, _}} =
6936              (catch qlc_SUITE:bad_table_key_equality(E)),
6937       ets:delete(E)">>,
6938
6939    <<"etsc(fun(E) ->
6940           Q = qlc:q([X || {X} <- ets:table(E),
6941                               X =:= 1, X =:= is_integer(X)]),
6942           [] = qlc:e(Q),
6943           [1] = lookup_keys(Q)
6944       end, [{1}, {2}])">>,
6945
6946    <<"etsc(fun(E) ->
6947                 Q = qlc:q([X || {X=1} <- ets:table(E),
6948                                 X =:= is_integer(X)]),
6949                 {call,_,_,
6950                  [{lc,_,_,
6951                    [_,
6952                     {op,_,'=:=',
6953                      {var,_,'X'},
6954                      {call,_,
6955                       {atom,_,is_integer},
6956                       [{var,_,'X'}]}}]}]} =
6957             qlc:info(Q, {format, abstract_code}),
6958             [] = qlc:e(Q),
6959             [1] = lookup_keys(Q)
6960         end, [{1}, {2}])">>,
6961
6962    <<"T = gb_trees:from_orddict([{1,a},{2,b}]),
6963       H = qlc:q([X || {X,Y} <- gb_table:table(T),
6964                                Y =:= a, true, X =:= 1]),
6965       [1] = lookup_keys(H),
6966       [1] = qlc:e(H)">>,
6967
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]), % skipped
6971       [{1.0, 1}] = qlc:e(H),
6972       {qlc,_,[{generate,_,{table,_}}], []} = qlc:info(H, {format,debug})">>,
6973    <<"T = gb_trees:from_orddict([{{1.0,1},a},{{2.0,2},b}]),
6974       H = qlc:q([X || {{1.0,B}=X,_} <- gb_table:table(T),
6975                    B == 1.0]), % skipped
6976       [{1.0, 1.0}] = qlc:e(H), % this is how gb_table works...
6977       {qlc,_,[{generate,_,{table,_}}], []} = qlc:info(H, {format,debug})">>,
6978    <<"T = gb_trees:from_orddict([{{1.0,1},a},{{2.0,2},b}]),
6979       H = qlc:q([X || {{1.0,B}=X,_} <- gb_table:table(T),
6980                       B =:= 1.0]), % not skipped
6981       [{1.0, 1.0}] = qlc:e(H),
6982       {qlc,_,[{generate,_,{table,_}},_], []} = qlc:info(H,{format,debug})">>,
6983    <<"T = gb_trees:from_orddict([{{1.0,1},a},{{2.0,2},b}]),
6984       H = qlc:q([X || {{1.0,B}=X,_} <- gb_table:table(T),
6985                       B =:= 1]), % not skipped
6986       [{1.0, 1}] = qlc:e(H),
6987       {qlc,_,[{generate,_,{table,_}},_], []} = qlc:info(H,{format,debug})">>,
6988
6989    <<"%% The imported variables do not interfere with join.
6990       E = ets:new(join, [ordered_set]),
6991       {A, B} = {1,1},
6992       true = ets:insert(E, [{1,a},{2,b},{3,c}]),
6993       Q = qlc:q([{X, Y} || {X,_Z} <- ets:table(E),
6994                            {Y} <- [{0},{1},{2}],
6995                            X =:= A, Y =:= B,
6996                            Y == X], % skipped
6997                {join, merge}),
6998       [{1,1}] = qlc:e(Q),
6999       {qlc,_,
7000           [{generate,_,
7001             {qlc,_,
7002              [{generate,_,
7003                {qlc,_,[{generate,_,{list,{table,_},_}},_],[]}},
7004               {generate,_,
7005                {qlc,_,[{generate,_,{list,_,_}},_],[]}},
7006               _],
7007              [{join,merge}]}}],
7008           []} = qlc:info(Q, {format, debug}),
7009       ets:delete(E)">>,
7010
7011    <<"% An old bug: usort() should not be used when matching values
7012       etsc(fun(E) ->
7013                   I = 1,
7014                   H = qlc:q([X || {X,_} <- ets:table(E),
7015                                   X =:= 1.0 orelse X =:= I]),
7016                   [1] = qlc:e(H),
7017                   [1.0] = lookup_keys(H) % do not look up twice
7018            end, [set], [{1,a},{2,b}])">>,
7019    <<"etsc(fun(E) ->
7020                   H = qlc:q([X || {X,_} <- ets:table(E),
7021                                    X =:= 1.0 orelse X == 1]),
7022                   [1] = qlc:e(H),
7023                   false = lookup_keys(H) % doesn't handle this case
7024         end, [ordered_set], [{1,a},{2,b}])">>,
7025
7026    <<"etsc(fun(E) ->
7027                 I1 = 1, I2 = 1,
7028                 H = qlc:q([X || {X,_} <- ets:table(E),
7029                                 X =:= I1 orelse X == I2]),
7030                 [1] = qlc:e(H), % do not look up twice
7031                 [1] = lookup_keys(H)
7032         end, [ordered_set], [{1,a},{2,b}])">>,
7033
7034    <<"etsc(fun(E) ->
7035                 I1 = 1, I2 = 1, I3 = 1,
7036                 H = qlc:q([X || {X,_} <- ets:table(E),
7037                                 I1 == I2, I1 =:= I3, I3 == I2, I2 =:= I3,
7038                                 X =:= I1 orelse X == I2
7039                                 ]),
7040                 [1] = qlc:e(H),
7041                 [1] = lookup_keys(H)
7042         end, [ordered_set], [{1,a},{2,b}])">>,
7043
7044    <<"E = ets:new(join, [ordered_set]),
7045       true = ets:insert(E, [{1,a},{2,b,x},{3,c}]),
7046       Q = qlc:q([P || P <- ets:table(E),
7047                       P =:= {1,a} orelse P =:= {2,b,x}]),
7048       [{1,a},{2,b,x}] = qlc:e(Q),
7049       ets:delete(E)">>,
7050
7051    <<"etsc(fun(E) ->
7052                   Q = qlc:q([X || {X,Y} <- ets:table(E),
7053                                   ((X =:= 3) or (Y =:= 4))  and (X == a)]),
7054                   {list,{table,_},_} = i(Q),
7055                   [] = qlc:e(Q), % a is not an answer
7056                   [a] = lookup_keys(Q)
7057          end, [{keypos,1},ordered_set], [{a,3},{b,4}])">>,
7058
7059    <<"Q = qlc:q([{X,Y} ||
7060                  {X} <- [{<<3:4>>}],
7061                  {Y} <- [{<<3:4>>}],
7062                  X =:= <<1:3,1:1>>,        % <<3:4>>
7063                  Y =:= <<0:2,1:1,1:1>>,    % <<3:4>>
7064                  X =:= Y]),
7065                  [{<<3:4>>,<<3:4>>}] = qlc:e(Q)">>
7066
7067
7068    ],
7069
7070    run(Config, Ts).
7071
7072%% Syntax error.
7073otp_12946(Config) when is_list(Config) ->
7074    Text =
7075        <<"-export([init/0]).
7076           init() ->
7077               ok.
7078           y">>,
7079    {errors,[{{4,12},erl_parse,_}],[]} = compile_file(Config, Text, []),
7080    {errors,[{4,erl_parse,_}],[]} =
7081        compile_file(Config, Text, [{error_location, line}]),
7082    ok.
7083
7084%% Examples from qlc(3).
7085manpage(Config) when is_list(Config) ->
7086    dets:start(),
7087    ok = compile_gb_table(Config),
7088
7089    Ts = [
7090       <<"QH = qlc:q([{X,Y} || X <- [a,b], Y <- [1,2]]),
7091          QC = qlc:cursor(QH),
7092          [{a,1}] = qlc:next_answers(QC, 1),
7093          [{a,2}] = qlc:next_answers(QC, 1),
7094          [{b,1},{b,2}] = qlc:next_answers(QC, all_remaining),
7095          ok = qlc:delete_cursor(QC)">>,
7096
7097       <<"QH = qlc:q([{X,Y} || X <- [a,b], Y <- [1,2]]),
7098          [{a,1},{a,2},{b,1},{b,2}] = qlc:eval(QH)">>,
7099
7100       <<"QH = [1,2,3,4,5,6],
7101          21 = qlc:fold(fun(X, Sum) -> X + Sum end, 0, QH)">>,
7102
7103       <<"QH = qlc:q([{X,Y} || X <- [x,y], Y <- [a,b]]),
7104          B = \"begin\n\"
7105              \"    V1 =\n\"
7106              \"        qlc:q([ \n\"
7107              \"               SQV ||\n\"
7108              \"                   SQV <- [x, y]\n\"
7109              \"              ],\n\"
7110              \"              [{unique, true}]),\n\"
7111              \"    V2 =\n\"
7112              \"        qlc:q([ \n\"
7113              \"               SQV ||\n\"
7114              \"                   SQV <- [a, b]\n\"
7115              \"              ],\n\"
7116              \"              [{unique, true}]),\n\"
7117              \"    qlc:q([ \n\"
7118              \"           {X, Y} ||\n\"
7119              \"               X <- V1,\n\"
7120              \"               Y <- V2\n\"
7121              \"          ],\n\"
7122              \"          [{unique, true}])\n\"
7123              \"end\",
7124          true = B =:= qlc:info(QH, unique_all)">>,
7125
7126       <<"E1 = ets:new(e1, []),
7127          E2 = ets:new(e2, []),
7128          true = ets:insert(E1, [{1,a},{2,b}]),
7129          true = ets:insert(E2, [{a,1},{b,2}]),
7130          Q = qlc:q([{X,Z,W} ||
7131                        {X, Z} <- ets:table(E1),
7132                        {W, Y} <- ets:table(E2),
7133                        X =:= Y]),
7134          L = \"begin\n\"
7135              \"    V1 =\n\"
7136              \"        qlc:q([ \n\"
7137              \"               P0 ||\n\"
7138              \"                   P0 = {W, Y} <- ets:table(_)\n\"
7139              \"              ]),\n\"
7140              \"    V2 =\n\"
7141              \"        qlc:q([ \n\"
7142              \"               [G1 | G2] ||\n\"
7143              \"                   G2 <- V1,\n\"
7144              \"                   G1 <- ets:table(_),\n\"
7145              \"                   element(2, G1) =:= element(1, G2)\n\"
7146              \"              ],\n\"
7147              \"              [{join, lookup}]),\n\"
7148              \"    qlc:q([ \n\"
7149              \"           {X, Z, W} ||\n\"
7150              \"               [{X, Z} | {W, Y}] <- V2\n\"
7151              \"          ])\n\"
7152              \"end\",
7153          Info1 =
7154             re:replace(qlc:info(Q),
7155                        \"table\\\\(#Ref<[\\.0-9]*>\",
7156                        \"table(_\", [{return,list},global]),
7157          F = fun(C) -> C =/= $\n andalso C =/= $\s end,
7158          Info = lists:filter(F, Info1),
7159          L1 = lists:filter(F, L),
7160          L1 = Info,
7161          ets:delete(E1),
7162          ets:delete(E2)">>,
7163
7164       <<"Q = qlc:q([{A,X,Z,W} ||
7165                        A <- [a,b,c],
7166                        {X,Z} <- [{a,1},{b,4},{c,6}],
7167                        {W,Y} <- [{2,a},{3,b},{4,c}],
7168                        X =:= Y],
7169                    {cache, list}),
7170          L =
7171       \"begin\n\"
7172       \"    V1 =\n\"
7173       \"        qlc:q([ \n\"
7174       \"               P0 ||\n\"
7175       \"                   P0 = {X, Z} <-\n\"
7176       \"                       qlc:keysort(1, [{a, 1}, {b, 4}, {c, 6}], [])\n\"
7177       \"              ]),\n\"
7178       \"    V2 =\n\"
7179       \"        qlc:q([ \n\"
7180       \"               P0 ||\n\"
7181       \"                   P0 = {W, Y} <-\n\"
7182       \"                       qlc:keysort(2, [{2, a}, {3, b}, {4, c}], [])\n\"
7183
7184       \"              ]),\n\"
7185       \"    V3 =\n\"
7186       \"        qlc:q([ \n\"
7187       \"               [G1 | G2] ||\n\"
7188       \"                   G1 <- V1,\n\"
7189       \"                   G2 <- V2,\n\"
7190       \"                   element(1, G1) == element(2, G2)\n\"
7191       \"              ],\n\"
7192       \"              [{join, merge}, {cache, list}]),\n\"
7193       \"    qlc:q([ \n\"
7194       \"           {A, X, Z, W} ||\n\"
7195       \"               A <- [a, b, c],\n\"
7196       \"               [{X, Z} | {W, Y}] <- V3,\n\"
7197       \"               X =:= Y\n\"
7198       \"          ])\n\"
7199       \"end\",
7200          L = qlc:info(Q)">>,
7201
7202       <<"E1 = ets:new(t, [set]), % uses =:=/2
7203          Q1 = qlc:q([K ||
7204          {K} <- ets:table(E1),
7205          K == 2.71 orelse K == a]),
7206          {list,{table,_}, [{{'$1'},[],['$1']}]} = i(Q1),
7207          true = ets:delete(E1)">>,
7208
7209       <<"F = fun(E, I) ->
7210                    qlc:q([V || {K,V} <- ets:table(E), K == I])
7211              end,
7212          E2 = ets:new(t, [set]),
7213          true = ets:insert(E2, [{{2,2},a},{{2,2.0},b},{{2.0,2},c}]),
7214          Q2 = F(E2, {2,2}),
7215          {table,{ets,table,[_,
7216                [{traverse,{select,[{{'$1','$2'},
7217                                     [{'==','$1',{const,{2,2}}}],
7218                                     ['$2']}]}}]]}} = i(Q2),
7219          [a,b,c] = lists:sort(qlc:e(Q2)),
7220          true = ets:delete(E2),
7221
7222          E3 = ets:new(t, [ordered_set]), % uses ==/2
7223          true = ets:insert(E3, [{{2,2.0},b}]),
7224          Q3 = F(E3,{2,2}),
7225          {list,{table,_},[{{'$1','$2'},[],['$2']}]} = i(Q3),
7226          [b] = qlc:e(Q3),
7227          true = ets:delete(E3)">>,
7228
7229       <<"T = gb_trees:empty(),
7230          QH = qlc:q([X || {{X,Y},_} <- gb_table:table(T),
7231                           ((X == 1) or (X == 2)) andalso
7232                           ((Y == a) or (Y == b) or (Y == c))]),
7233          L = \"ets:match_spec_run(lists:flatmap(fun(K) ->
7234                                        case
7235                                            gb_trees:lookup(K,
7236                                                            gb_trees:from_orddict([]))
7237                                        of
7238                                            {value, V} ->
7239                                                [{K, V}];
7240                                            none ->
7241                                                []
7242                                        end
7243                                 end,
7244                                 [{1, a},
7245                                  {1, b},
7246                                  {1, c},
7247                                  {2, a},
7248                                  {2, b},
7249                                  {2, c}]),
7250                   ets:match_spec_compile([{{{'$1', '$2'}, '_'},
7251                                            [],
7252                                            ['$1']}]))\",
7253          L = qlc:info(QH)">>
7254      ],
7255    run(Config, Ts),
7256
7257    L = [1,2,3],
7258    Bs = erl_eval:add_binding('L', L, erl_eval:new_bindings()),
7259    QH = qlc:string_to_handle("[X+1 || X <- L].", [], Bs),
7260    [2,3,4] = qlc:eval(QH),
7261
7262    %% ets(3)
7263    MS = ets:fun2ms(fun({X,Y}) when (X > 1) or (X < 5) -> {Y} end),
7264    ETs = [
7265        [<<"true = ets:insert(Tab = ets:new(t, []),[{1,a},{2,b},{3,c},{4,d}]),
7266            MS = ">>, io_lib:format("~w", [MS]), <<",
7267            QH1 = ets:table(Tab, [{traverse, {select, MS}}]),
7268
7269            QH2 = qlc:q([{Y} || {X,Y} <- ets:table(Tab), (X > 1) or (X < 5)]),
7270
7271            true = qlc:info(QH1) =:= qlc:info(QH2),
7272            true = ets:delete(Tab)">>]],
7273    run(Config, ETs),
7274
7275    %% dets(3)
7276    DTs = [
7277        [<<"{ok, T} = dets:open_file(t, []),
7278            ok = dets:insert(T, [{1,a},{2,b},{3,c},{4,d}]),
7279            MS = ">>, io_lib:format("~w", [MS]), <<",
7280            QH1 = dets:table(T, [{traverse, {select, MS}}]),
7281
7282            QH2 = qlc:q([{Y} || {X,Y} <- dets:table(t), (X > 1) or (X < 5)]),
7283
7284            true = qlc:info(QH1) =:= qlc:info(QH2),
7285            ok = dets:close(T)">>]],
7286    run(Config, DTs),
7287
7288    ok.
7289
7290compile_gb_table(Config) ->
7291    GB_table_file = filename("gb_table.erl", Config),
7292    ok = file:write_file(GB_table_file, gb_table()),
7293    {ok, gb_table} = compile:file(GB_table_file, [{outdir,?privdir}]),
7294    code:purge(gb_table),
7295    {module, gb_table} =
7296        code:load_abs(filename:rootname(GB_table_file)),
7297    ok.
7298
7299gb_table() ->
7300    <<"
7301-module(gb_table).
7302
7303-export([table/1]).
7304
7305table(T) ->
7306    TF = fun() -> qlc_next(gb_trees:next(gb_trees:iterator(T))) end,
7307    InfoFun = fun(num_of_objects) -> gb_trees:size(T);
7308                 (keypos) -> 1;
7309                 (is_sorted_key) -> true;
7310                 (is_unique_objects) -> true;
7311                 (_) -> undefined
7312              end,
7313    LookupFun =
7314        fun(1, Ks) ->
7315                lists:flatmap(fun(K) ->
7316                                      case gb_trees:lookup(K, T) of
7317                                          {value, V} -> [{K,V}];
7318                                          none -> []
7319                                      end
7320                              end, Ks)
7321        end,
7322    FormatFun =
7323        fun({all, NElements, ElementFun}) ->
7324                ValsS = io_lib:format(\"gb_trees:from_orddict(~w)\",
7325                                      [gb_nodes(T, NElements, ElementFun)]),
7326                io_lib:format(\"gb_table:table(~s)\", [ValsS]);
7327           ({lookup, 1, KeyValues, _NElements, ElementFun}) ->
7328                ValsS = io_lib:format(\"gb_trees:from_orddict(~w)\",
7329                                      [gb_nodes(T, infinity, ElementFun)]),
7330                io_lib:format(\"lists:flatmap(fun(K) -> \"
7331                              \"case gb_trees:lookup(K, ~s) of \"
7332                              \"{value, V} -> [{K,V}];none -> [] end \"
7333                              \"end, ~w)\",
7334                              [ValsS, [ElementFun(KV) || KV <- KeyValues]])
7335        end,
7336    qlc:table(TF, [{info_fun, InfoFun}, {format_fun, FormatFun},
7337                   {lookup_fun, LookupFun},{key_equality,'=='}]).
7338
7339qlc_next({X, V, S}) ->
7340    [{X,V} | fun() -> qlc_next(gb_trees:next(S)) end];
7341qlc_next(none) ->
7342    [].
7343
7344gb_nodes(T, infinity, ElementFun) ->
7345    gb_nodes(T, -1, ElementFun);
7346gb_nodes(T, NElements, ElementFun) ->
7347    gb_iter(gb_trees:iterator(T), NElements, ElementFun).
7348
7349gb_iter(_I, 0, _EFun) ->
7350    '...';
7351gb_iter(I0, N, EFun) ->
7352    case gb_trees:next(I0) of
7353        {X, V, I} ->
7354            [EFun({X,V}) | gb_iter(I, N-1, EFun)];
7355        none ->
7356            []
7357    end.
7358    ">>.
7359
7360
7361%% OTP-6674. Join info and extra constants.
7362backward(Config) when is_list(Config) ->
7363    try_old_join_info(Config),
7364    ok.
7365
7366try_old_join_info(Config) ->
7367    %% Check join info for handlers of extra constants.
7368    File = filename:join(?datadir, "join_info_compat.erl"),
7369    M = join_info_compat,
7370    {ok, M} = compile:file(File, [{outdir, ?datadir}]),
7371    {module, M} = code:load_abs(filename:rootname(File)),
7372    H = M:create_handle(),
7373    A0 = erl_anno:new(0),
7374    {block,A0,
7375     [{match,_,_,
7376       {call,_,_,
7377        [{lc,_,_,
7378          [_,
7379           {op,_,'=:=',
7380            {float,_,192.0},
7381            {call,_,{atom,_,element},[{integer,_,1},_]}}]}]}},
7382      _,_,
7383      {call,_,_,
7384       [{lc,_,_,
7385         [_,
7386          {op,_,'=:=',{var,_,'B'},{float,_,192.0}},
7387          {op,_,'==',{var,_,'X'},{var,_,'Y'}}]}]}]}
7388        = qlc:info(H,{format,abstract_code}),
7389    [{1,1},{2,2}] = qlc:e(H),
7390
7391    H2 = M:lookup_handle(),
7392    {qlc,_,[{generate,_,{qlc,_,_,[{join,lookup}]}},_],[]} =
7393        qlc:info(H2, {format,debug}),
7394    [{1,1},{2,2}] = qlc:e(H2).
7395
7396forward(Config) when is_list(Config) ->
7397    Ts = [
7398      %% LC_fun() returns something unknown.
7399      <<"FakeH = {qlc_handle,{qlc_lc,fun() -> {foo,bar} end,
7400                             {qlc_opt,false,false,-1,any,[],any,524288}}},
7401         {'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>,
7402
7403%% 'f1' should be used for new stuff that does not interfer with old behavior
7404%%       %% The unused element 'f1' of #qlc_table seems to be used.
7405%%       <<"DF = fun() -> foo end,
7406%%          FakeH = {qlc_handle,{qlc_table,DF,
7407%%                        true,DF,DF,DF,DF,DF,
7408%%                        undefined,not_undefined,undefined,no_match_spec}},
7409%%          {'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>,
7410
7411      %% #qlc_opt has changed.
7412      <<"H = qlc:q([X || X <- []]),
7413         {qlc_handle, {qlc_lc, Fun, _Opt}} = H,
7414         FakeH = {qlc_handle, {qlc_lc, Fun, {new_qlc_opt, a,b,c}}},
7415         {'EXIT', {{unsupported_qlc_handle,_},_}} = (catch qlc:e(FakeH))">>
7416
7417     ],
7418    run(Config, Ts),
7419    ok.
7420
7421eep37(Config) when is_list(Config) ->
7422    Ts = [
7423        <<"H = (fun _Handle() -> qlc:q([X || X <- []]) end)(),
7424           [] = qlc:eval(H)">>
7425    ],
7426    run(Config, Ts),
7427    ok.
7428
7429%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7430
7431bad_table_throw(Tab) ->
7432    Limit = 1,
7433    Select = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7434    PreFun = fun(_) -> throw({throw,bad_pre_fun}) end,
7435    PostFun = fun() -> throw({throw,bad_post_fun}) end,
7436    InfoFun = fun(Tag) -> info(Tab, Tag) end,
7437    qlc:table(Select, [{pre_fun,PreFun}, {post_fun, PostFun},
7438                       {info_fun, InfoFun}]).
7439
7440bad_table_exit(Tab) ->
7441    Limit = 1,
7442    Select = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7443    PreFun = fun(_) -> erlang:error(bad_pre_fun) end,
7444    PostFun = fun() -> erlang:error(bad_post_fun) end,
7445    InfoFun = fun(Tag) -> info(Tab, Tag) end,
7446    qlc:table(Select, [{pre_fun,PreFun}, {post_fun, PostFun},
7447                       {info_fun, InfoFun}]).
7448
7449info(_Tab, is_unique_objects) ->
7450    false;
7451info(Tab, Tag) ->
7452    try ets:info(Tab, Tag) catch _:_ -> undefined end.
7453
7454create_ets(S, E) ->
7455    create_ets(lists:seq(S, E)).
7456
7457create_ets(L) ->
7458    E1 = ets:new(e, []),
7459    true = ets:insert(E1, [{X,X} || X <- L]),
7460    E1.
7461
7462etsc(F, Objs) ->
7463    etsc(F, [{keypos,1}], Objs).
7464
7465etsc(F, Opts, Objs) ->
7466    E = ets:new(test, Opts),
7467    true = ets:insert(E, Objs),
7468    V = F(E),
7469    ets:delete(E),
7470    V.
7471
7472join_info(H) ->
7473    {{qlc, S, Options}, Bs} = strip_qlc_call2(H),
7474    %% "Hide" the call to qlc_pt from the test in run_test().
7475    LoadedPT = code:is_loaded(qlc_pt),
7476    QH = qlc:string_to_handle(S, Options, Bs),
7477    _ = [unload_pt() || false <- [LoadedPT]], % doesn't take long...
7478    case {join_info_count(H), join_info_count(QH)} of
7479        {N, N} ->
7480            N;
7481        Ns ->
7482            Ns
7483    end.
7484
7485strip_qlc_call(H) ->
7486    {Expr, _Bs} = strip_qlc_call2(H),
7487    Expr.
7488
7489strip_qlc_call2(H) ->
7490    S = qlc:info(H, {flat, false}),
7491    {ok, Tokens, _EndLine} = erl_scan:string(S++".", 1, [text]),
7492    {ok, [Expr], Bs} = erl_eval:extended_parse_exprs(Tokens),
7493    {case Expr of
7494         {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC]} ->
7495             {qlc, lists:flatten([erl_pp:expr(LC), "."]), []};
7496         {call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC, Opts]} ->
7497             {qlc, lists:flatten([erl_pp:expr(LC), "."]),
7498              erl_parse:normalise(Opts)};
7499         {call,_,{remote,_,{atom,_,ets},{atom,_,match_spec_run}},_} ->
7500             {match_spec, Expr};
7501         {call,_,{remote,_,{atom,_,M},{atom,_,table}},_} ->
7502             {table, M, Expr};
7503         _ ->
7504             []
7505     end, Bs}.
7506
7507-record(ji, {nmerge = 0, nlookup = 0, nnested_loop = 0, nkeysort = 0}).
7508
7509%% Counts join options and (all) calls to qlc:keysort().
7510join_info_count(H) ->
7511    S = qlc:info(H, {flat, false}),
7512    {ok, Tokens, _EndLine} = erl_scan:string(S++".", 1, [text]),
7513    {ok, [Expr], _Bs} = erl_eval:extended_parse_exprs(Tokens),
7514    #ji{nmerge = Nmerge, nlookup = Nlookup,
7515        nkeysort = NKeysort, nnested_loop = Nnested_loop} =
7516        ji(Expr, #ji{}),
7517    {Nmerge, Nlookup, Nnested_loop, NKeysort}.
7518
7519ji({call,_,{remote,_,{atom,_,qlc},{atom,_,q}},[LC,Options]}, JI) ->
7520    NJI = case lists:keysearch(join, 1, erl_parse:normalise(Options)) of
7521              {value, {join, merge}} ->
7522                  JI#ji{nmerge = JI#ji.nmerge + 1};
7523              {value, {join, lookup}} ->
7524                  JI#ji{nlookup = JI#ji.nlookup + 1};
7525              {value, {join, nested_loop}} ->
7526                  JI#ji{nnested_loop = JI#ji.nnested_loop + 1};
7527              _  ->
7528                  JI
7529          end,
7530    ji(LC, NJI);
7531ji({call,_,{remote,_,{atom,_,qlc},{atom,_,keysort}},[_KP,H,_Options]}, JI) ->
7532    ji(H, JI#ji{nkeysort = JI#ji.nkeysort + 1});
7533ji(T, JI) when is_tuple(T) ->
7534    ji(tuple_to_list(T), JI);
7535ji([E | Es], JI) ->
7536    ji(Es, ji(E, JI));
7537ji(_, JI) ->
7538    JI.
7539
7540%% Designed for ETS' and gb_table's format funs.
7541lookup_keys(Q) ->
7542    case lists:flatten(lookup_keys(i(Q), [])) of
7543        [] -> false;
7544        L -> lists:usort(L)
7545    end.
7546
7547lookup_keys([Q | Qs], L) ->
7548    lookup_keys(Qs, lookup_keys(Q, L));
7549lookup_keys({qlc,_,Quals,_}, L) ->
7550    lookup_keys(Quals, L);
7551lookup_keys({list,Q,_}, L) ->
7552    lookup_keys(Q, L);
7553lookup_keys({generate,_,Q}, L) ->
7554    lookup_keys(Q, L);
7555lookup_keys({table,Chars}, L) when is_list(Chars) ->
7556    {ok, Tokens, _} = erl_scan:string(lists:flatten(Chars++"."), 1, [text]),
7557    {ok, [Expr], _Bs} = erl_eval:extended_parse_exprs(Tokens),
7558    case Expr of
7559        {call,_,_,[_fun,AKs]} ->
7560            case erl_parse:normalise(AKs) of
7561                Ks when is_list(Ks) ->
7562                    [lists:sort(Ks) | L];
7563                K -> % assume keys are never lists (ets only)
7564                    [K | L]
7565            end;
7566        _ -> % gb_table
7567            L
7568    end;
7569lookup_keys(_Q, L) ->
7570    L.
7571
7572bad_table_format(Tab) ->
7573    Limit = 1,
7574    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7575    FormatFun = {is, no, good},
7576    qlc:table(SelectFun, [{format_fun, FormatFun}]).
7577
7578bad_table_format_arity(Tab) ->
7579    Limit = 1,
7580    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7581    FormatFun = fun() -> {?MODULE, bad_table_format_arity, [Tab]} end,
7582    qlc:table(SelectFun, [{format_fun, FormatFun}]).
7583
7584bad_table_traverse(Tab) ->
7585    Limit = 1,
7586    Select = fun(MS, _) -> cb(ets:select(Tab, MS, Limit)) end,
7587    qlc:table(Select, []).
7588
7589bad_table_post(Tab) ->
7590    Limit = 1,
7591    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7592    qlc:table(SelectFun, [{pre_fun,undefined},
7593                          {post_fun, fun(X) -> X end},
7594                          {info_fun, undefined}]).
7595
7596bad_table_lookup(Tab) ->
7597    Limit = 1,
7598    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7599    qlc:table(SelectFun, {lookup_fun, fun(X) -> X end}).
7600
7601bad_table_max_lookup(Tab) ->
7602    Limit = 1,
7603    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7604    qlc:table(SelectFun, {max_lookup, -2}).
7605
7606bad_table_info_arity(Tab) ->
7607    Limit = 1,
7608    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7609    InfoFun = fun() -> {?MODULE, bad_table_info_arity, [Tab]} end,
7610    qlc:table(SelectFun, [{info_fun, InfoFun}]).
7611
7612default_table(Tab) ->
7613    Limit = 1,
7614    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7615    qlc:table(SelectFun, [{format_fun, undefined},
7616                          {info_fun, undefined},
7617                          {lookup_fun, undefined},
7618                          {parent_fun, undefined},
7619                          {pre_fun,undefined},
7620                          {post_fun, undefined}]).
7621
7622bad_table(Tab) ->
7623    Limit = 1,
7624    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7625    qlc:table(SelectFun, [{info, fun() -> ok end}]).
7626
7627bad_table_info_fun_n_objects(Tab) ->
7628    Limit = 1,
7629    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7630    LookupFun = fun(_Pos, Ks) ->
7631                        lists:flatmap(fun(K) -> ets:lookup(Tab, K) end, Ks)
7632                end,
7633    InfoFun = fun(num_of_objects) -> exit(finito);
7634                 (_) -> undefined
7635              end,
7636    qlc:table(SelectFun, [{info_fun, InfoFun}, {lookup_fun, LookupFun}]).
7637
7638bad_table_info_fun_indices(Tab) ->
7639    Limit = 1,
7640    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7641    LookupFun = fun(_Pos, Ks) ->
7642                        lists:flatmap(fun(K) -> ets:lookup(Tab, K) end, Ks)
7643                end,
7644    InfoFun = fun(indices) -> throw({throw,apa});
7645                 (_) -> undefined
7646              end,
7647    qlc:table(SelectFun, [{info_fun, InfoFun}, {lookup_fun, LookupFun}]).
7648
7649bad_table_info_fun_keypos(Tab) ->
7650    Limit = 1,
7651    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7652    LookupFun = fun(_Pos, Ks) ->
7653                        lists:flatmap(fun(K) -> ets:lookup(Tab, K) end, Ks)
7654                end,
7655    InfoFun = fun(indices) -> erlang:error(keypos);
7656                  (_) -> undefined
7657              end,
7658    qlc:table(SelectFun, [{info_fun, InfoFun}, {lookup_fun, LookupFun}]).
7659
7660bad_table_key_equality(Tab) ->
7661    Limit = 1,
7662    SelectFun = fun(MS) -> cb(ets:select(Tab, MS, Limit)) end,
7663    LookupFun = fun(_Pos, Ks) ->
7664                        lists:flatmap(fun(K) -> ets:lookup(Tab, K) end, Ks)
7665                end,
7666    qlc:table(SelectFun, [{lookup_fun, LookupFun},{key_equality,'=/='}]).
7667
7668cb('$end_of_table') ->
7669    [];
7670cb({Objects,Cont}) ->
7671    Objects ++ fun() -> cb(ets:select(Cont)) end.
7672
7673i(H) ->
7674    i(H, []).
7675
7676i(H, Options) when is_list(Options) ->
7677    case has_format(Options) of
7678        true -> qlc:info(H, Options);
7679        false -> qlc:info(H, [{format, debug} | Options])
7680    end;
7681i(H, Option) ->
7682    i(H, [Option]).
7683
7684has_format({format,_}) ->
7685    true;
7686has_format([E | Es]) ->
7687    has_format(E) or has_format(Es);
7688has_format(_) ->
7689    false.
7690
7691format_info(H, Flat) ->
7692    L = qlc:info(H, [{flat, Flat}, {format,string}]),
7693    re:replace(L, "\s|\n|\t|\f|\r|\v", "", [{return,list},global]).
7694
7695%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7696%% A list turned into a table...
7697
7698table_kill_parent(List, Indices) ->
7699    ParentFun = fun() -> exit(self(), kill) end,
7700    table_i(List, Indices, ParentFun).
7701
7702table_parent_throws(List, Indices) ->
7703    ParentFun = fun() -> throw({throw,thrown}) end,
7704    table_i(List, Indices, ParentFun).
7705
7706table_parent_exits(List, Indices) ->
7707    ParentFun = fun() -> 1 + Indices end,
7708    table_i(List, Indices, ParentFun).
7709
7710table_bad_parent_fun(List, Indices) ->
7711    ParentFun = fun(X) -> X end, % parent_fun should be nullary
7712    table_i(List, Indices, ParentFun).
7713
7714table(List, Indices) ->
7715    ParentFun = fun() -> self() end,
7716    table_i(List, Indices, ParentFun).
7717
7718table(List, KeyPos, Indices) ->
7719    ParentFun = fun() -> self() end,
7720    table(List, Indices, KeyPos, ParentFun).
7721
7722table_i(List, Indices, ParentFun) ->
7723    table(List, Indices, undefined, ParentFun).
7724
7725table(List, Indices, KeyPos, ParentFun) ->
7726    TraverseFun = fun() -> list_traverse(List) end,
7727    PreFun = fun(PreArgs) ->
7728                     {value, {parent_value, Pid}} =
7729                         lists:keysearch(parent_value, 1, PreArgs),
7730                     true = is_pid(Pid)
7731             end,
7732    PostFun = fun() -> ok end,
7733    InfoFun = fun(indices) ->
7734                      Indices;
7735                 (is_unique_objects) ->
7736                      undefined;
7737                 (keypos) ->
7738                      KeyPos;
7739                 (num_of_objects) ->
7740                      undefined;
7741                 (_) ->
7742                      undefined
7743              end,
7744    LookupFun =
7745        fun(Column, Values) ->
7746                lists:flatmap(fun(V) ->
7747                                      case lists:keysearch(V, Column, List) of
7748                                          false -> [];
7749                                          {value,Val} -> [Val]
7750                                      end
7751                              end, Values)
7752
7753                end,
7754    FormatFun = fun(all) ->
7755                        A = erl_anno:new(17),
7756                        {call,A,{remote,A,{atom,A,?MODULE},{atom,A,the_list}},
7757                                 [erl_parse:abstract(List, 17)]};
7758                   ({lookup, Column, Values}) ->
7759                        {?MODULE, list_keys, [Values, Column, List]}
7760                end,
7761    qlc:table(TraverseFun, [{info_fun,InfoFun}, {pre_fun, PreFun},
7762                            {post_fun, PostFun}, {lookup_fun, LookupFun},
7763                            {format_fun, FormatFun},
7764                            {parent_fun, ParentFun}]).
7765
7766stop_list(List, Ets) ->
7767    Traverse = fun() -> list_traverse(List) end,
7768    PV = a_sample_parent_value,
7769    ParentFun = fun() -> PV end,
7770    Pre = fun(PreArgs) ->
7771                  {value, {parent_value, PV}} =
7772                      lists:keysearch(parent_value, 1, PreArgs),
7773                  {value, {stop_fun, Fun}} =
7774                      lists:keysearch(stop_fun, 1, PreArgs),
7775                  true = ets:insert(Ets, {stop_fun, Fun})
7776          end,
7777    qlc:table(Traverse, [{pre_fun, Pre}, {parent_fun, ParentFun}]).
7778
7779list_traverse([]) ->
7780    [];
7781list_traverse([E | Es]) ->
7782    [E | fun() -> list_traverse(Es) end].
7783
7784table_error(List, Error) ->
7785    table_error(List, undefined, Error).
7786
7787table_error(List, KeyPos, Error) ->
7788    TraverseFun = fun() -> list_traverse2(lists:sort(List), Error) end,
7789    InfoFun = fun(is_sorted_key) -> true;
7790                 (keypos) -> KeyPos;
7791                 (_) -> undefined
7792              end,
7793    qlc:table(TraverseFun, [{info_fun,InfoFun}]).
7794
7795list_traverse2([], Err) ->
7796    Err;
7797list_traverse2([E | Es], Err) ->
7798    [E | fun() -> list_traverse2(Es, Err) end].
7799
7800table_lookup_error(List) ->
7801    TraverseFun = fun() -> list_traverse(List) end,
7802    LookupFun = fun(_Column, _Values) -> {error,lookup,failed} end,
7803    InfoFun = fun(keypos) -> 1;
7804                 (_) -> undefined
7805              end,
7806    qlc:table(TraverseFun, [{lookup_fun,LookupFun},{info_fun,InfoFun}]).
7807
7808prep_scratchdir(Dir) ->
7809    put('$qlc_tmpdir', true),
7810    _ = filelib:ensure_dir(Dir),
7811    lists:foreach(fun(F) -> file:delete(F)
7812                  end, filelib:wildcard(filename:join(Dir, "*"))),
7813    true.
7814
7815%% Truncate just once.
7816truncate_tmpfile(Dir, Where) ->
7817    case get('$qlc_tmpdir') of
7818        true ->
7819            {ok, [TmpFile0 | _]} = file:list_dir(Dir),
7820            TmpFile = filename:join(Dir, TmpFile0),
7821            truncate(TmpFile, Where),
7822            erase('$qlc_tmpdir');
7823        _ ->
7824            true
7825    end.
7826
7827truncate(File, Where) ->
7828    {ok, Fd} = file:open(File, [read, write]),
7829    {ok, _} = file:position(Fd, Where),
7830    ok = file:truncate(Fd),
7831    ok = file:close(Fd).
7832
7833%% Crash just once.
7834crash_tmpfile(Dir, Where) ->
7835    case get('$qlc_tmpdir') of
7836        true ->
7837            {ok, [TmpFile0 | _]} = file:list_dir(Dir),
7838            TmpFile = filename:join(Dir, TmpFile0),
7839            crash(TmpFile, Where),
7840            erase('$qlc_tmpdir');
7841        _ ->
7842            true
7843    end.
7844
7845crash(File, Where) ->
7846    {ok, Fd} = file:open(File, [read, write]),
7847    {ok, _} = file:position(Fd, Where),
7848    ok = file:write(Fd, [10]),
7849    ok = file:close(Fd).
7850
7851%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7852
7853run(Config, Tests) ->
7854    run(Config, [], Tests).
7855
7856run(Config, Extra, Tests) ->
7857    lists:foreach(fun(Body) -> run_test(Config, Extra, Body) end, Tests).
7858
7859run_test(Config, Extra, {cres, Body, ExpectedCompileReturn}) ->
7860    run_test(Config, Extra, {cres, Body, _Opts = [], ExpectedCompileReturn});
7861run_test(Config, Extra, {cres, Body, Opts, ExpectedCompileReturn}) ->
7862    {SourceFile, Mod} = compile_file_mod(Config),
7863    P = [Extra,<<"function() -> ">>, Body, <<", ok. ">>],
7864    CompileReturn = compile_file(Config, P, Opts),
7865    case comp_compare(ExpectedCompileReturn, CompileReturn) of
7866        true -> ok;
7867        false -> expected(ExpectedCompileReturn, CompileReturn, SourceFile)
7868    end,
7869    AbsFile = filename:rootname(SourceFile, ".erl"),
7870    _ = code:purge(Mod),
7871    {module, _} = code:load_abs(AbsFile, Mod),
7872
7873    Ms0 = erlang:process_info(self(),messages),
7874    Before = {{lget(), lists:sort(ets:all()), Ms0}, pps()},
7875
7876    %% Prepare the check that the qlc module does not call qlc_pt.
7877    _ = [unload_pt() || {file, Name} <- [code:is_loaded(qlc_pt)],
7878                        Name =/= cover_compiled],
7879
7880    R = case catch Mod:function() of
7881            {'EXIT', _Reason} = Error ->
7882                io:format("failed, got ~p~n", [Error]),
7883                fail(SourceFile);
7884            Reply ->
7885                Reply
7886        end,
7887
7888    %% Check that the qlc module does not call qlc_pt:
7889    case code:is_loaded(qlc_pt) of
7890        {file, cover_compiled} ->
7891            ok;
7892        {file, _} ->
7893            io:format("qlc_pt was loaded in runtime~n", []),
7894            fail(SourceFile);
7895        false ->
7896            ok
7897    end,
7898
7899    wait_for_expected(R, Before, SourceFile, true),
7900    code:purge(Mod);
7901run_test(Config, Extra, Body) ->
7902    run_test(Config, Extra, {cres,Body,[]}).
7903
7904wait_for_expected(R, {Strict0,PPS0}=Before, SourceFile, Wait) ->
7905    Ms = erlang:process_info(self(),messages),
7906    After = {_,PPS1} = {{lget(), lists:sort(ets:all()), Ms}, pps()},
7907    case {R, After} of
7908        {ok, Before} ->
7909            ok;
7910        {ok, {Strict0,_}} ->
7911            {Ports0,Procs0} = PPS0,
7912            {Ports1,Procs1} = PPS1,
7913            case {Ports1 -- Ports0, Procs1 -- Procs0} of
7914                {[], []} -> ok;
7915                _ when Wait ->
7916                    timer:sleep(1000),
7917                    wait_for_expected(R, Before, SourceFile, false);
7918                {PortsDiff,ProcsDiff} ->
7919                    io:format("failure, got ~p~n, expected ~p\n",
7920                              [PPS1, PPS0]),
7921                    show("Old port", Ports0 -- Ports1),
7922                    show("New port", PortsDiff),
7923                    show("Old proc", Procs0 -- Procs1),
7924                    show("New proc", ProcsDiff),
7925                    fail(SourceFile)
7926            end;
7927        _ when Wait ->
7928            timer:sleep(1000),
7929            wait_for_expected(R, Before, SourceFile, false);
7930        _ ->
7931            expected({ok,Before}, {R,After}, SourceFile)
7932    end.
7933
7934%% The qlc modules uses the process dictionary for storing names of files.
7935lget() ->
7936    lists:sort([T || {K, _} = T <- get(), is_qlc_key(K)]).
7937
7938%% Copied from the qlc module.
7939-define(LCACHE_FILE(Ref), {Ref, '$_qlc_cache_tmpfiles_'}).
7940-define(MERGE_JOIN_FILE, '$_qlc_merge_join_tmpfiles_').
7941
7942is_qlc_key(?LCACHE_FILE(_)) -> true;
7943is_qlc_key(?MERGE_JOIN_FILE) -> true;
7944is_qlc_key(_) -> false.
7945
7946unload_pt() ->
7947    erlang:garbage_collect(), % get rid of references to qlc_pt...
7948    _ = code:purge(qlc_pt),
7949    _ = code:delete(qlc_pt).
7950
7951compile_format(Config, Tests) ->
7952    Fun = fun(Test, Opts) ->
7953                  Return = compile_file(Config, Test, Opts),
7954                  format_messages(Return)
7955          end,
7956    compile(Config, Tests, Fun).
7957
7958format_messages({warnings,Ws}) ->
7959    format_messages({errors,[],Ws});
7960format_messages({errors,Es,Ws}) ->
7961    {[format_msg(E, Mod) || {_Line,Mod,E} <- Es],
7962     [format_msg(W, Mod) || {_Line,Mod,W} <- Ws]}.
7963
7964format_msg(Msg, Mod) ->
7965    IOlist = Mod:format_error(Msg),
7966    binary_to_list(iolist_to_binary(IOlist)).
7967
7968compile(Config, Tests) ->
7969    Fun = fun(Test, Opts) -> catch compile_file(Config, Test, Opts) end,
7970    compile(Config, Tests, Fun).
7971
7972compile(Config, Tests, Fun) ->
7973    F = fun({TestName,Test,Opts,Expected}, BadL) ->
7974                Return = Fun(Test, Opts),
7975                case comp_compare(Expected, Return) of
7976                    true ->
7977                        BadL;
7978                    false ->
7979                        {File, _Mod} = compile_file_mod(Config),
7980                        expected(TestName, Expected, Return, File)
7981                end
7982        end,
7983    lists:foldl(F, [], Tests).
7984
7985%% Compiles a test module and returns the list of errors and warnings.
7986
7987compile_file(Config, Test0, Opts0) ->
7988    {File, Mod} = compile_file_mod(Config),
7989    Test = list_to_binary(["-module(", atom_to_list(Mod), "). "
7990                           "-import(qlc_SUITE, [i/1,i/2,format_info/2]). "
7991                           "-import(qlc_SUITE, [etsc/2, etsc/3]). "
7992                           "-import(qlc_SUITE, [create_ets/2]). "
7993                           "-import(qlc_SUITE, [strip_qlc_call/1]). "
7994                           "-import(qlc_SUITE, [join_info/1]). "
7995                           "-import(qlc_SUITE, [join_info_count/1]). "
7996                           "-import(qlc_SUITE, [lookup_keys/1]). "
7997                           "-include_lib(\"stdlib/include/qlc.hrl\"). ",
7998                           Test0]),
7999    Opts = [export_all,nowarn_export_all,return,nowarn_unused_record,{outdir,?privdir}|Opts0],
8000    ok = file:write_file(File, Test),
8001    case compile:file(File, Opts) of
8002        {ok, _M, Ws} -> warnings(File, Ws);
8003        {error, [{File,Es}], []} -> {errors, Es, []};
8004        {error, [{File,Es}], [{File,Ws}]} -> {errors, Es, Ws}
8005    end.
8006
8007comp_compare(T, T) ->
8008    true;
8009comp_compare(T1, T2_0) ->
8010    T2 = wskip(T2_0),
8011    T1 =:= T2.
8012
8013wskip([]) ->
8014    [];
8015wskip([{_,sys_core_fold,{eval_failure,badarg}}|L]) ->
8016    wskip(L);
8017wskip([{{L,_C},sys_core_fold,M}|L]) ->
8018    [{L,sys_core_fold,M}|wskip(L)];
8019wskip({T,L}) ->
8020    {T,wskip(L)};
8021wskip([M|L]) ->
8022    [M|wskip(L)];
8023wskip(T) ->
8024    T.
8025
8026%% -> {FileName, Module}; {string(), atom()}
8027compile_file_mod(Config) ->
8028    NameL = lists:concat([?TESTMODULE, "_", ?testcase]),
8029    Name = list_to_atom(NameL),
8030    File = filename(NameL ++ ".erl", Config),
8031    {File, Name}.
8032
8033filename(Name, Config) when is_atom(Name) ->
8034    filename(atom_to_list(Name), Config);
8035filename(Name, Config) ->
8036    filename:join(?privdir, Name).
8037
8038show(_S, []) ->
8039    ok;
8040show(S, [{Pid, Name, InitCall}|Pids]) when is_pid(Pid) ->
8041    io:format("~s: ~w (~w), ~w: ~p~n",
8042              [S, Pid, proc_reg_name(Name), InitCall,
8043               erlang:process_info(Pid)]),
8044    show(S, Pids);
8045show(S, [{Port, _}|Ports]) when is_port(Port)->
8046    io:format("~s: ~w: ~p~n", [S, Port, erlang:port_info(Port)]),
8047    show(S, Ports).
8048
8049pps() ->
8050    {port_list(), process_list()}.
8051
8052port_list() ->
8053    [{P,safe_second_element(erlang:port_info(P, name))} ||
8054        P <- erlang:ports()].
8055
8056process_list() ->
8057    [{P,process_info(P, registered_name),
8058      safe_second_element(process_info(P, initial_call))} ||
8059        P <- processes(), is_process_alive(P)].
8060
8061proc_reg_name({registered_name, Name}) -> Name;
8062proc_reg_name([]) -> no_reg_name.
8063
8064safe_second_element({_,Info}) -> Info;
8065safe_second_element(Other) -> Other.
8066
8067warnings(File, Ws) ->
8068    case lists:append([W || {F, W} <- Ws, F =:= File]) of
8069        [] -> [];
8070        L -> {warnings, L}
8071    end.
8072
8073expected(Test, Expected, Got, File) ->
8074    io:format("~nTest ~p failed. ", [Test]),
8075    expected(Expected, Got, File).
8076
8077expected(Expected, Got, File) ->
8078    io:format("Expected~n  ~p~n, but got~n  ~p~n", [Expected, Got]),
8079    fail(File).
8080
8081fail(Source) ->
8082    ct:fail({failed,testcase,on,Source}).
8083
8084%% Copied from global_SUITE.erl.
8085
8086install_error_logger() ->
8087    error_logger:add_report_handler(?MODULE, self()).
8088
8089uninstall_error_logger() ->
8090    error_logger:delete_report_handler(?MODULE).
8091
8092read_error_logger() ->
8093    receive
8094	{error, Why} ->
8095            {error, Why};
8096        {info, Why} ->
8097            {info, Why};
8098        {warning, Why} ->
8099            {warning, Why};
8100        {error, Pid, Tuple} ->
8101            {error, Pid, Tuple}
8102    after 1000 ->
8103	    io:format("No reply after 1 s\n", []),
8104	    ct:fail(failed)
8105    end.
8106
8107%%-----------------------------------------------------------------
8108%% The error_logger handler used.
8109%% (Copied from stdlib/test/proc_lib_SUITE.erl.)
8110%%-----------------------------------------------------------------
8111init(Tester) ->
8112    {ok, Tester}.
8113
8114handle_event({error, _GL, {_Pid, _Msg, [Why, _]}}, Tester) when is_atom(Why) ->
8115    Tester ! {error, Why},
8116    {ok, Tester};
8117handle_event({error, _GL, {_Pid, _Msg, [P, T]}}, Tester) when is_pid(P) ->
8118    Tester ! {error, P, T},
8119    {ok, Tester};
8120handle_event({info_msg, _GL, {_Pid, _Msg, [Why, _]}}, Tester) ->
8121    Tester ! {info, Why},
8122    {ok, Tester};
8123handle_event({warning_msg, _GL, {_Pid, _Msg, [Why, _]}}, Tester) when is_atom(Why) ->
8124    Tester ! {warning, Why},
8125    {ok, Tester};
8126handle_event(_Event, State) ->
8127    {ok, State}.
8128
8129handle_info(_, State) ->
8130    {ok, State}.
8131
8132handle_call(_Query, State) -> {ok, {error, bad_query}, State}.
8133
8134terminate(_Reason, State) ->
8135    State.
8136